source: trunk/LMDZ.MARS/libf/phymars/thermcell_main_mars.F90 @ 567

Last change on this file since 567 was 557, checked in by acolaitis, 13 years ago

Yamada4 is now ON when using thermals. Advised setup with thermals: modified z2sig (one more level in PBL) and at least 72 timesteps per day (for now...).

File size: 52.8 KB
RevLine 
[161]1!
2!
[185]3      SUBROUTINE thermcell_main_mars(ptimestep  &
[161]4     &                  ,pplay,pplev,pphi,zlev,zlay  &
5     &                  ,pu,pv,pt,pq,pq2  &
6     &                  ,pduadj,pdvadj,pdtadj,pdqadj,pdq2adj  &
[185]7     &                  ,fm,entr,detr,lmax,zmax  &
[161]8     &                  ,r_aspect &
9     &                  ,zw2,fraca &
10     &                  ,zpopsk,ztla,heatFlux,heatFlux_down &
11     &                  ,buoyancyOut, buoyancyEst)
12
13      IMPLICIT NONE
14
15!=======================================================================
16! Mars version of thermcell_main. Author : A Colaitis
17!=======================================================================
[185]18
19#include "dimensions.h"
20#include "dimphys.h"
21#include "comcstfi.h"
[508]22#include "tracer.h"
23#include "callkeys.h"
[185]24
[161]25! ============== INPUTS ==============
26
27      REAL, INTENT(IN) :: ptimestep,r_aspect
[185]28      REAL, INTENT(IN) :: pt(ngridmx,nlayermx)
29      REAL, INTENT(IN) :: pu(ngridmx,nlayermx)
30      REAL, INTENT(IN) :: pv(ngridmx,nlayermx)
31      REAL, INTENT(IN) :: pq(ngridmx,nlayermx,nqmx)
32      REAL, INTENT(IN) :: pq2(ngridmx,nlayermx)
33      REAL, INTENT(IN) :: pplay(ngridmx,nlayermx)
34      REAL, INTENT(IN) :: pplev(ngridmx,nlayermx+1)
35      REAL, INTENT(IN) :: pphi(ngridmx,nlayermx)
36      REAL, INTENT(IN) :: zlay(ngridmx,nlayermx)
37      REAL, INTENT(IN) :: zlev(ngridmx,nlayermx+1)
[161]38
39! ============== OUTPUTS ==============
40
[185]41      REAL, INTENT(OUT) :: pdtadj(ngridmx,nlayermx)
[337]42      REAL :: pduadj(ngridmx,nlayermx)
43      REAL :: pdvadj(ngridmx,nlayermx)
44      REAL :: pdqadj(ngridmx,nlayermx,nqmx)
[313]45!      REAL, INTENT(OUT) :: pdq2adj(ngridmx,nlayermx)
46      REAL :: pdq2adj(ngridmx,nlayermx)
[185]47      REAL, INTENT(OUT) :: zw2(ngridmx,nlayermx+1)
[161]48
49! Diagnostics
[185]50      REAL, INTENT(OUT) :: heatFlux(ngridmx,nlayermx)   ! interface heatflux
[313]51     REAL, INTENT(OUT) :: heatFlux_down(ngridmx,nlayermx) ! interface heat flux from downdraft
52!      REAL, INTENT(OUT) :: buoyancyOut(ngridmx,nlayermx)  ! interlayer buoyancy term
53!      REAL, INTENT(OUT) :: buoyancyEst(ngridmx,nlayermx)  ! interlayer estimated buoyancy term
[161]54
55! dummy variables when output not needed :
56
[185]57!      REAL :: heatFlux(ngridmx,nlayermx)   ! interface heatflux
58!      REAL :: heatFlux_down(ngridmx,nlayermx) ! interface heat flux from downdraft
[313]59      REAL :: buoyancyOut(ngridmx,nlayermx)  ! interlayer buoyancy term
60      REAL :: buoyancyEst(ngridmx,nlayermx)  ! interlayer estimated buoyancy term
[161]61
62
63! ============== LOCAL ================
64
65      INTEGER ig,k,l,ll,iq
[185]66      INTEGER lmax(ngridmx),lmin(ngridmx),lalim(ngridmx)
67      REAL linter(ngridmx)
68      REAL zmax(ngridmx)
69      REAL ztva(ngridmx,nlayermx),zw_est(ngridmx,nlayermx+1),ztva_est(ngridmx,nlayermx)
70      REAL zmax_sec(ngridmx)
71      REAL zh(ngridmx,nlayermx)
72      REAL zdthladj(ngridmx,nlayermx)
73      REAL zdthladj_down(ngridmx,nlayermx)
74      REAL ztvd(ngridmx,nlayermx)
75      REAL ztv(ngridmx,nlayermx)
76      REAL zu(ngridmx,nlayermx),zv(ngridmx,nlayermx),zo(ngridmx,nlayermx)
77      REAL zva(ngridmx,nlayermx)
78      REAL zua(ngridmx,nlayermx)
[161]79
[185]80      REAL zta(ngridmx,nlayermx)
81      REAL fraca(ngridmx,nlayermx+1)
82      REAL q2(ngridmx,nlayermx)
83      REAL rho(ngridmx,nlayermx),rhobarz(ngridmx,nlayermx),masse(ngridmx,nlayermx)
84      REAL zpopsk(ngridmx,nlayermx)
[161]85
[185]86      REAL wmax(ngridmx)
87      REAL wmax_sec(ngridmx)
88      REAL fm(ngridmx,nlayermx+1),entr(ngridmx,nlayermx),detr(ngridmx,nlayermx)
[161]89
[185]90      REAL fm_down(ngridmx,nlayermx+1)
[161]91
[185]92      REAL ztla(ngridmx,nlayermx)
[161]93
[185]94      REAL f_star(ngridmx,nlayermx+1),entr_star(ngridmx,nlayermx)
95      REAL detr_star(ngridmx,nlayermx)
96      REAL alim_star_tot(ngridmx)
97      REAL alim_star(ngridmx,nlayermx)
98      REAL alim_star_clos(ngridmx,nlayermx)
99      REAL f(ngridmx)
[161]100
[185]101      REAL teta_th_int(ngridmx,nlayermx)
102      REAL teta_env_int(ngridmx,nlayermx)
103      REAL teta_down_int(ngridmx,nlayermx)
[161]104
105      CHARACTER (LEN=20) :: modname
106      CHARACTER (LEN=80) :: abort_message
107
108! ============= PLUME VARIABLES ============
109
[185]110      REAL w_est(ngridmx,nlayermx+1)
111      REAL wa_moy(ngridmx,nlayermx+1)
112      REAL wmaxa(ngridmx)
113      REAL zdz,zbuoy(ngridmx,nlayermx),zw2m
[508]114      LOGICAL activecell(ngridmx),activetmp(ngridmx)
[544]115      REAL a1,b1,ae,be,ad,bd,fdfu,b1inv,a1inv,omega,adalim
[290]116      INTEGER tic
[161]117
118! ==========================================
119
120! ============= HEIGHT VARIABLES ===========
121
[185]122      REAL num(ngridmx)
123      REAL denom(ngridmx)
124      REAL zlevinter(ngridmx)
[161]125
126! =========================================
127
128! ============= CLOSURE VARIABLES =========
129
[185]130      REAL zdenom(ngridmx)
131      REAL alim_star2(ngridmx)
132      REAL alim_star_tot_clos(ngridmx)
[161]133      INTEGER llmax
134
135! =========================================
136
137! ============= FLUX2 VARIABLES ===========
138
139      INTEGER ncorecfm1,ncorecfm2,ncorecfm3,ncorecalpha
140      INTEGER ncorecfm4,ncorecfm5,ncorecfm6,ncorecfm7,ncorecfm8
141      REAL zfm
142      REAL f_old,ddd0,eee0,ddd,eee,zzz
143      REAL fomass_max,alphamax
144
145! =========================================
146
147! ============= DTETA VARIABLES ===========
148
149! rien : on prends la divergence du flux turbulent
150
151! =========================================
152
153! ============= DV2 VARIABLES =============
154!               not used for now
155
[185]156      REAL qa(ngridmx,nlayermx),detr_dv2(ngridmx,nlayermx),zf,zf2
157      REAL wvd(ngridmx,nlayermx+1),wud(ngridmx,nlayermx+1)
158      REAL gamma0(ngridmx,nlayermx+1),gamma(ngridmx,nlayermx+1)
159      REAL ue(ngridmx,nlayermx),ve(ngridmx,nlayermx)
160      LOGICAL ltherm(ngridmx,nlayermx)
161      REAL dua(ngridmx,nlayermx),dva(ngridmx,nlayermx)
[161]162      INTEGER iter
163      INTEGER nlarga0
164
165! =========================================
166
[508]167! ============== Theta_M Variables ========
168
169      INTEGER ico2
170      SAVE ico2
171      REAL m_co2, m_noco2, A , B
172      SAVE A, B
173      LOGICAL firstcall
174      save firstcall
175      data firstcall/.true./
176      REAL zhc(ngridmx,nlayermx)
177      REAL zdzfull(ngridmx,nlayermx)
178      REAL ratiom(ngridmx,nlayermx)
179
180! =========================================
181
[161]182!-----------------------------------------------------------------------
183!   initialisation:
184!   ---------------
185
[336]186      entr(:,:)=0.
187      detr(:,:)=0.
188      fm(:,:)=0.
[337]189!      zu(:,:)=pu(:,:)
190!      zv(:,:)=pv(:,:)
[508]191      zhc(:,:)=pt(:,:)/zpopsk(:,:)
[161]192
[508]193! **********************************************************************
194! Taking into account vertical molar mass gradients
195! **********************************************************************
196
197      if(firstcall) then
198        ico2=0
199        if (tracer) then
200!     Prepare Special treatment if one of the tracers is CO2 gas
201           do iq=1,nqmx
202             if (noms(iq).eq."co2") then
203                ico2=iq
204                m_co2 = 44.01E-3  ! CO2 molecular mass (kg/mol)
205                m_noco2 = 33.37E-3  ! Non condensible mol mass (kg/mol)
206!               Compute A and B coefficient use to compute
207!               mean molecular mass Mair defined by
208!               1/Mair = q(ico2)/m_co2 + (1-q(ico2))/m_noco2
209!               1/Mair = A*q(ico2) + B
210                A =(1/m_co2 - 1/m_noco2)
211                B=1/m_noco2
212             end if
213           enddo
214        endif
215
216      firstcall=.false.
217      endif !of if firstcall
218
219!.......................................................................
220!  Special treatment for co2
221!.......................................................................
222
223      if (ico2.ne.0) then
224!     Special case if one of the tracers is CO2 gas
225         DO l=1,nlayermx
226           DO ig=1,ngridmx
227            ztv(ig,l) = zhc(ig,l)*(A*pq(ig,l,ico2)+B)
228           ENDDO
229         ENDDO
230       else
231          ztv(:,:)=zhc(:,:)
232       end if
233
234
[161]235!------------------------------------------------------------------------
236!                       --------------------
237!
238!
239!                       + + + + + + + + + + +
240!
241!
242!  wa, fraca, wd, fracd --------------------   zlev(2), rhobarz
243!  wh,wt,wo ...
244!
245!                       + + + + + + + + + + +  zh,zu,zv,zo,rho
246!
247!
248!                       --------------------   zlev(1)
249!                       \\\\\\\\\\\\\\\\\\\\
250!
251!
252
253!-----------------------------------------------------------------------
254!   Calcul des altitudes des couches
255!-----------------------------------------------------------------------
256
[185]257!      do l=2,nlayermx
258!         zlev(:,l)=0.5*(pphi(:,l)+pphi(:,l-1))/g
[161]259!      enddo
260!         zlev(:,1)=0.
[185]261!         zlev(:,nlayermx+1)=(2.*pphi(:,nlayermx)-pphi(:,nlayermx-1))/g
[161]262
[185]263!         zlay(:,:)=pphi(:,:)/g
[161]264!-----------------------------------------------------------------------
265!   Calcul des densites
266!-----------------------------------------------------------------------
267
[185]268      rho(:,:)=pplay(:,:)/(r*pt(:,:))
[161]269
270      rhobarz(:,1)=rho(:,1)
271
[185]272      do l=2,nlayermx
[161]273         rhobarz(:,l)=0.5*(rho(:,l)+rho(:,l-1))
274      enddo
275
276!calcul de la masse
[185]277      do l=1,nlayermx
278         masse(:,l)=(pplev(:,l)-pplev(:,l+1))/g
[161]279      enddo
280
281
282!------------------------------------------------------------------
283!
284!             /|\
285!    --------  |  F_k+1 -------   
286!                              ----> D_k
287!             /|\              <---- E_k , A_k
288!    --------  |  F_k ---------
289!                              ----> D_k-1
290!                              <---- E_k-1 , A_k-1
291!
292!
293!    ---------------------------
294!
295!    ----- F_lmax+1=0 ----------         \
296!            lmax     (zmax)              |
297!    ---------------------------          |
298!                                         |
299!    ---------------------------          |
300!                                         |
301!    ---------------------------          |
302!                                         |
303!    ---------------------------          |
304!                                         |
305!    ---------------------------          |
306!                                         |  E
307!    ---------------------------          |  D
308!                                         |
309!    ---------------------------          |
310!                                         |
311!    ---------------------------  \       |
312!            lalim                 |      |
313!    ---------------------------   |      |
314!                                  |      |
315!    ---------------------------   |      |
316!                                  | A    |
317!    ---------------------------   |      |
318!                                  |      |
319!    ---------------------------   |      |
320!    lmin  (=1 pour le moment)     |      |
321!    ----- F_lmin=0 ------------  /      /
322!
323!    ---------------------------
324!    //////////////////////////
325!
326
327!=============================================================================
328!  Calculs initiaux ne faisant pas intervenir les changements de phase
329!=============================================================================
330
331!------------------------------------------------------------------
332!  1. alim_star est le profil vertical de l'alimentation a la base du
333!     panache thermique, calcule a partir de la flotabilite de l'air sec
334!  2. lmin et lalim sont les indices inferieurs et superieurs de alim_star
335!------------------------------------------------------------------
336!
337      entr_star=0. ; detr_star=0. ; alim_star=0. ; alim_star_tot=0.
338      lmin=1
339
340!-----------------------------------------------------------------------------
341!  3. wmax_sec et zmax_sec sont les vitesses et altitudes maximum d'un
342!     panache sec conservatif (e=d=0) alimente selon alim_star
343!     Il s'agit d'un calcul de type CAPE
344!     zmax_sec est utilise pour determiner la geometrie du thermique.
345!------------------------------------------------------------------------------
346!---------------------------------------------------------------------------------
347!calcul du melange et des variables dans le thermique
348!--------------------------------------------------------------------------------
349
350! ===========================================================================
351! ===================== PLUME ===============================================
352! ===========================================================================
353
354! Initialisations des variables reeles
355      ztva(:,:)=ztv(:,:)
356      ztva_est(:,:)=ztva(:,:)
357      ztla(:,:)=0.
[173]358      zdz=0.
[161]359      zbuoy(:,:)=0.
360      w_est(:,:)=0.
361      f_star(:,:)=0.
362      wa_moy(:,:)=0.
363      linter(:)=1.
[185]364
[496]365! --------------------------------------------------------------------------
366! -------------- MAIN PARAMETERS FOR THERMALS MODEL ------------------------
367! --------------  see thermiques.pro and getfit.py -------------------------
368
[185]369!      a1=2.5 ; b1=0.0015 ; ae=0.045 ; be = 0.6  ! svn baseline
370
[496]371! Using broad downdraft selection
372!      a1=1.60226 ; b1=0.0006 ; ae=0.0454 ; be = 0.57
373!      ad = 0.0005114  ; bd = -0.662
374!      fdfu = -1.9
[185]375
[496]376! Using conditional sampling downdraft selection
377      a1=1.4716 ; b1=0.0005698 ; ae=0.03683 ; be = 0.57421
378      ad = 0.00048088  ; bd = -0.6697
379      fdfu = -1.3
[532]380      a1inv=a1
381      b1inv=b1
382      omega=0.
[544]383      adalim=0.
[496]384
[532]385! One good config for 34/35 levels
386!      a1inv=a1
387!      b1inv=b1
388!      be=1.1*be
389
[512]390! Best configuration for 222 levels:
[532]391
[544]392!      omega=0.06
393!      b1=0.
394!      a1=1.
395!      a1inv=0.25*a1
396!      b1inv=0.0002
397!!
398!!
399!!      ae=0.9*ae
[512]400
[532]401! Best config for norad 222 levels:
402
[544]403       omega=0.06
404       a1=1.
405       b1=0.
406       a1inv=a1
407       be=1.1*be
408       ad = 0.0004
409       adalim=0.
[546]410       b1inv=0.00025
[532]411
[546]412!      omega=0.06
[532]413! Trying stuff :
414
[546]415!      ad=0.00035
416!      ae=0.95*ae
417!      b1=0.00055
[544]418!      omega=0.04
[546]419!
420!      ad = 0.0003
421!      ae=0.9*ae
422
423!      omega=0.04
[544]424!!      b1=0.
425!      a1=1.
426!      a1inv=a1
427!      b1inv=0.0005689
428!!      be=1.1*be
429!!      ae=0.96*ae
430
431
[532]432!       omega=0.06
433!       a1=1.
434!       b1=0.
435!       be=be
436!       a1inv=0.25*a1
437!       b1inv=0.0002   
438!       ad=1.1*ad
439!       ae=1.*ae
[496]440! --------------------------------------------------------------------------
441! --------------------------------------------------------------------------
442! --------------------------------------------------------------------------
443
[161]444! Initialisation des variables entieres
445      wmaxa(:)=0.
446      lalim(:)=1
447
448!-------------------------------------------------------------------------
449! On ne considere comme actif que les colonnes dont les deux premieres
450! couches sont instables.
451!-------------------------------------------------------------------------
[508]452      activecell(:)=ztv(:,1)>ztv(:,2)
[185]453          do ig=1,ngridmx
[161]454            if (ztv(ig,1)>=(ztv(ig,2))) then
455               alim_star(ig,1)=MAX((ztv(ig,1)-ztv(ig,2)),0.)  &
[557]456!     &                       *log(1.+zlev(ig,2))
457     &                       *sqrt(zlev(ig,2))
458!     &                       *sqrt(sqrt(zlev(ig,2)))
[290]459!     &                       /sqrt(zlev(ig,2))
[557]460!      &                       *zlev(ig,2)
[546]461!      &                     *exp(-zlev(ig,2)/1000.)
[161]462               lalim(ig)=2
463               alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,1)
464            endif
465         enddo
466
[185]467       do l=2,nlayermx-1
468!        do l=2,4
469         do ig=1,ngridmx
[513]470           if (ztv(ig,l)>(ztv(ig,l+1)+0.) .and. ztv(ig,1)>=ztv(ig,l) .and. (alim_star(ig,l-1) .ne. 0.)) then ! .and. (zlev(ig,l+1) .lt. 1000.)) then
[161]471               alim_star(ig,l)=MAX((ztv(ig,l)-ztv(ig,l+1)),0.)  &
[557]472!     &                       *log(1.+zlev(ig,l+1))
473     &                       *sqrt(zlev(ig,l+1))
474!     &                       *sqrt(sqrt(zlev(ig,l+1)))
[544]475!     &                       /sqrt(zlev(ig,l+1))
[557]476!      &                       *zlev(ig,l+1)
[546]477!      &                     *exp(-zlev(ig,l+1)/1000.)
[161]478                lalim(ig)=l+1
479               alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
480           endif
481        enddo
482      enddo
[185]483      do l=1,nlayermx
484         do ig=1,ngridmx
[161]485            if (alim_star_tot(ig) > 1.e-10 ) then
486               alim_star(ig,l)=alim_star(ig,l)/alim_star_tot(ig)
487            endif
488         enddo
489      enddo
490
491      alim_star_tot(:)=1.
[185]492!      if(alim_star(1,1) .ne. 0.) then
493!      print*, 'lalim star' ,lalim(1)
494!      endif
[161]495
496!------------------------------------------------------------------------------
497! Calcul dans la premiere couche
498! On decide dans cette version que le thermique n'est actif que si la premiere
499! couche est instable.
500! Pourrait etre change si on veut que le thermiques puisse se déclencher
501! dans une couche l>1
502!------------------------------------------------------------------------------
503
[185]504      do ig=1,ngridmx
[161]505! Le panache va prendre au debut les caracteristiques de l'air contenu
506! dans cette couche.
[508]507          if (activecell(ig)) then
[161]508          ztla(ig,1)=ztv(ig,1)
509!cr: attention, prise en compte de f*(1)=1 => AC : what ? f*(1) =0. ! (d'ou f*(2)=a*(1)
510! dans un panache conservatif
511          f_star(ig,1)=0.
[290]512         
[161]513          f_star(ig,2)=alim_star(ig,1)
[290]514
[185]515          zw2(ig,2)=2.*g*(ztv(ig,1)-ztv(ig,2))/ztv(ig,2)  &
[161]516      &                     *(zlev(ig,2)-zlev(ig,1))  &
[290]517      &                    *0.4*pphi(ig,1)/(pphi(ig,2)-pphi(ig,1))
[161]518          w_est(ig,2)=zw2(ig,2)
519
520          endif
521      enddo
522
523
524!==============================================================================
525!boucle de calcul de la vitesse verticale dans le thermique
526!==============================================================================
[185]527      do l=2,nlayermx-1
[161]528!==============================================================================
529
530
531! On decide si le thermique est encore actif ou non
532! AFaire : Il faut sans doute ajouter entr_star a alim_star dans ce test
[185]533          do ig=1,ngridmx
[508]534             activecell(ig)=activecell(ig) &
[161]535      &                 .and. zw2(ig,l)>1.e-10 &
536      &                 .and. f_star(ig,l)+alim_star(ig,l)>1.e-10
537          enddo
538
539!---------------------------------------------------------------------------
540! calcul des proprietes thermodynamiques et de la vitesse de la couche l
541! sans tenir compte du detrainement et de l'entrainement dans cette
542! couche
543! C'est a dire qu'on suppose
544! ztla(l)=ztla(l-1)
545! Ici encore, on doit pouvoir ajouter entr_star (qui peut etre calculer
546! avant) a l'alimentation pour avoir un calcul plus propre
547!---------------------------------------------------------------------------
548
[185]549          do ig=1,ngridmx
[508]550             if(activecell(ig)) then
[165]551!                if(l .lt. lalim(ig)) then
[290]552!               ztva_est(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
[165]553!     &            alim_star(ig,l)*ztv(ig,l))  &
554!     &            /(f_star(ig,l)+alim_star(ig,l))
555!                else
[161]556                ztva_est(ig,l)=ztla(ig,l-1)
[165]557!                endif
[161]558
559                zdz=zlev(ig,l+1)-zlev(ig,l)
[185]560                zbuoy(ig,l)=g*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
561
562                if (((a1*zbuoy(ig,l)/w_est(ig,l)-b1) .gt. 0.) .and. (w_est(ig,l) .ne. 0.)) then
563                w_est(ig,l+1)=Max(0.0001,w_est(ig,l)+2.*zdz*a1*zbuoy(ig,l)-2.*zdz*w_est(ig,l)*b1 &
[532]564     & -2.*(1.-omega)*zdz*w_est(ig,l)*ae*(a1*zbuoy(ig,l)/w_est(ig,l)-b1)**be)
[161]565                else
[512]566                w_est(ig,l+1)=Max(0.0001,w_est(ig,l)+2.*zdz*a1inv*zbuoy(ig,l)-2.*zdz*w_est(ig,l)*b1inv)
[161]567                endif
568                if (w_est(ig,l+1).lt.0.) then
569                w_est(ig,l+1)=zw2(ig,l)
570                endif
571             endif
572          enddo
573
574!-------------------------------------------------
575!calcul des taux d'entrainement et de detrainement
576!-------------------------------------------------
577
[185]578      do ig=1,ngridmx
[508]579        if (activecell(ig)) then
[161]580
581          zw2m=w_est(ig,l+1)
[185]582
583          if((a1*(zbuoy(ig,l)/zw2m)-b1) .gt. 0.) then
[161]584          entr_star(ig,l)=f_star(ig,l)*zdz*  &
[512]585        &   MAX(0.,ae*(a1*(zbuoy(ig,l)/zw2m)-b1)**be)
586!         &  MAX(0.,log(1. + 0.03*sqrt(a1*(zbuoy(ig,l)/zw2m)-b1)))
[161]587          else
588          entr_star(ig,l)=0.
589          endif
[185]590
[161]591          if(zbuoy(ig,l) .gt. 0.) then
592             if(l .lt. lalim(ig)) then
[544]593
594!                detr_star(ig,l)=0.
595                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
596            &  adalim
[161]597             else
[185]598
[161]599!                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
600!              &     0.0105*((zbuoy(ig,l)/zw2m)/0.048)**(1./1.7)
601!                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
602!              &     0.0085*((zbuoy(ig,l)/zw2m)/0.05)**(1./1.55)
603
604! last baseline from direct les
605!                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
606!               &     0.065*(2.5*(zbuoy(ig,l)/zw2m))**0.75
607
608! new param from continuity eq with a fit on dfdz
609                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
[512]610            &  ad
611!             &  Max(0., 0.0005 - 0.55*zbuoy(ig,l)/zw2m)
[161]612
[185]613!               &     MAX(0.,-0.38*zbuoy(ig,l)/zw2m+0.0005)   !svn baseline
614!                &     MAX(0.,-0.38*zbuoy(ig,l)/zw2m+0.0008)     
615
[161]616!              &     0.014*((zbuoy(ig,l)/zw2m)/0.05)**(1./1.35)
617!                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
618!              &     ((zbuoy(ig,l)/zw2m)/2.222)! + 0.0002)
619
620             endif
621          else
622          detr_star(ig,l)=f_star(ig,l)*zdz*                        &
[512]623                &     bd*zbuoy(ig,l)/zw2m
624!             &  Max(0., 0.001 - 0.45*zbuoy(ig,l)/zw2m)
625!             &  Max(0., Min(0.001,0.0005 - 0.55*zbuoy(ig,l)/zw2m))
[161]626
[508]627
[185]628!               &     MAX(0.,-0.38*zbuoy(ig,l)/zw2m+0.0005)      !svn baseline
629
[161]630!              &  *5.*(-afact*zbetalpha*zbuoy(ig,l)/zw2m)
631!              &  *5.*(-afact*zbuoy(ig,l)/zw2m)
632
633! last baseline from direct les
634!               &     0.065*(-2.5*(zbuoy(ig,l)/zw2m))**0.75
635
636! new param from continuity eq with a fit on dfdz
637
638
639          endif
640
641! En dessous de lalim, on prend le max de alim_star et entr_star pour
642! alim_star et 0 sinon
643
[512]644       if (l.lt.lalim(ig)) then
[161]645          alim_star(ig,l)=max(alim_star(ig,l),entr_star(ig,l))
[512]646          entr_star(ig,l)=0.
647       endif
[161]648
649! Calcul du flux montant normalise
650
651      f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
652     &              -detr_star(ig,l)
653
654      endif
655      enddo
656
657
658!----------------------------------------------------------------------------
659!calcul de la vitesse verticale en melangeant Tl et qt du thermique
660!---------------------------------------------------------------------------
661
[546]662      DO tic=0,0  ! internal convergence loop
[508]663      activetmp(:)=activecell(:) .and. f_star(:,l+1)>1.e-10
[185]664      do ig=1,ngridmx
[161]665       if (activetmp(ig)) then
666
667           ztla(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
668     &            (alim_star(ig,l)+entr_star(ig,l))*ztv(ig,l))  &
669     &            /(f_star(ig,l+1)+detr_star(ig,l))
670
671        endif
672      enddo
673
[313]674      activetmp(:)=activetmp(:).and.(abs(ztla(:,l)-ztva(:,l)).gt.0.01)
675
[185]676      do ig=1,ngridmx
[161]677      if (activetmp(ig)) then
678           ztva(ig,l) = ztla(ig,l)
[185]679           zbuoy(ig,l)=g*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
[161]680
[185]681           if (((a1*zbuoy(ig,l)/zw2(ig,l)-b1) .gt. 0.) .and. (zw2(ig,l) .ne. 0.) ) then
682           zw2(ig,l+1)=Max(0.,zw2(ig,l)+2.*zdz*a1*zbuoy(ig,l)-         &
[532]683     & 2.*zdz*zw2(ig,l)*b1-2.*(1.-omega)*zdz*zw2(ig,l)*ae*(a1*zbuoy(ig,l)/zw2(ig,l)-b1)**be)
[161]684           else
[512]685           zw2(ig,l+1)=Max(0.,zw2(ig,l)+2.*zdz*a1inv*zbuoy(ig,l)-2.*zdz*zw2(ig,l)*b1inv)
[161]686           endif
687      endif
688      enddo
689
[290]690! ================ RECOMPUTE ENTR, DETR, and F FROM NEW W2 ===================
691
692      do ig=1,ngridmx
693        if (activetmp(ig)) then
694
695          zw2m=zw2(ig,l+1)
696          if(zw2m .gt. 0) then
697          if((a1*(zbuoy(ig,l)/zw2m)-b1) .gt. 0.) then
698          entr_star(ig,l)=f_star(ig,l)*zdz*  &
699        &   MAX(0.,ae*(a1*(zbuoy(ig,l)/zw2m)-b1)**be)
[512]700!         &  MAX(0.,log(1. + 0.03*sqrt(a1*(zbuoy(ig,l)/zw2m)-b1)))
[290]701          else
702          entr_star(ig,l)=0.
703          endif
704
705          if(zbuoy(ig,l) .gt. 0.) then
706             if(l .lt. lalim(ig)) then
[544]707
708!                detr_star(ig,l)=0.
709                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
710            &  adalim
711
[290]712             else
713                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
714            &  ad
[512]715!             &  Max(0., 0.0005 - 0.55*zbuoy(ig,l)/zw2m)
716
[290]717             endif
718          else
719          detr_star(ig,l)=f_star(ig,l)*zdz*                        &
720                &     bd*zbuoy(ig,l)/zw2m
[512]721!             &  Max(0.,Min(0.001,0.0005 - 0.55*zbuoy(ig,l)/zw2m))
722
[290]723          endif
724          else
725          entr_star(ig,l)=0.
726          detr_star(ig,l)=0.
727          endif
728
729! En dessous de lalim, on prend le max de alim_star et entr_star pour
730! alim_star et 0 sinon
731
732        if (l.lt.lalim(ig)) then
733          alim_star(ig,l)=max(alim_star(ig,l),entr_star(ig,l))
734          entr_star(ig,l)=0.
735        endif
736
737! Calcul du flux montant normalise
738
739      f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
740     &              -detr_star(ig,l)
741
742      endif
743      enddo
[546]744 
[313]745      ENDDO   ! of tic
746
[161]747!---------------------------------------------------------------------------
748!initialisations pour le calcul de la hauteur du thermique, de l'inversion et de la vitesse verticale max
749!---------------------------------------------------------------------------
750
[185]751      do ig=1,ngridmx
[161]752            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
753             print*,'On tombe sur le cas particulier de thermcell_plume'
754                zw2(ig,l+1)=0.
755                linter(ig)=l+1
756            endif
757
758        if (zw2(ig,l+1).lt.0.) then
759           linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
760     &               -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
761           zw2(ig,l+1)=0.
762        endif
763           wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
764
765        if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
766!   lmix est le niveau de la couche ou w (wa_moy) est maximum
767            wmaxa(ig)=wa_moy(ig,l+1)
768        endif
769      enddo
770
771!=========================================================================
772! FIN DE LA BOUCLE VERTICALE
773      enddo
774!=========================================================================
775
776!on recalcule alim_star_tot
[185]777       do ig=1,ngridmx
[161]778          alim_star_tot(ig)=0.
779       enddo
[185]780       do ig=1,ngridmx
[161]781          do l=1,lalim(ig)-1
782          alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
783          enddo
784       enddo
785
[185]786      do l=1,nlayermx
787         do ig=1,ngridmx
[165]788            if (alim_star_tot(ig) > 1.e-10 ) then
789               alim_star(ig,l)=alim_star(ig,l)/alim_star_tot(ig)
790            endif
791         enddo
792      enddo
[161]793
794! ===========================================================================
795! ================= FIN PLUME ===============================================
796! ===========================================================================
797
798! ===========================================================================
799! ================= HEIGHT ==================================================
800! ===========================================================================
801
802! Attention, w2 est transforme en sa racine carree dans cette routine
803
804!-------------------------------------------------------------------------------
[356]805! Calcul des caracteristiques du thermique:zmax,wmax
[161]806!-------------------------------------------------------------------------------
807
808!calcul de la hauteur max du thermique
[185]809      do ig=1,ngridmx
[161]810         lmax(ig)=lalim(ig)
811      enddo
[185]812      do ig=1,ngridmx
813         do l=nlayermx,lalim(ig)+1,-1
[161]814            if (zw2(ig,l).le.1.e-10) then
[512]815               lmax(ig)=l-1
[161]816            endif
817         enddo
818      enddo
819
820! On traite le cas particulier qu'il faudrait éviter ou le thermique
821! atteind le haut du modele ...
[185]822      do ig=1,ngridmx
823      if ( zw2(ig,nlayermx) > 1.e-10 ) then
[161]824          print*,'WARNING !!!!! W2 thermiques non nul derniere couche '
[185]825          lmax(ig)=nlayermx
[161]826      endif
827      enddo
828
829! pas de thermique si couche 1 stable
[185]830!      do ig=1,ngridmx
[161]831!         if (lmin(ig).gt.1) then
832!             lmax(ig)=1
833!             lmin(ig)=1
834!             lalim(ig)=1
835!         endif
836!      enddo
837!
838! Determination de zw2 max
[185]839      do ig=1,ngridmx
[161]840         wmax(ig)=0.
841      enddo
842
[185]843      do l=1,nlayermx
844         do ig=1,ngridmx
[161]845            if (l.le.lmax(ig)) then
846                if (zw2(ig,l).lt.0.)then
847                  print*,'pb2 zw2<0'
848                endif
849                zw2(ig,l)=sqrt(zw2(ig,l))
850                wmax(ig)=max(wmax(ig),zw2(ig,l))
851            else
852                 zw2(ig,l)=0.
853            endif
854          enddo
855      enddo
856!   Longueur caracteristique correspondant a la hauteur des thermiques.
[185]857      do  ig=1,ngridmx
[161]858         zmax(ig)=0.
859         zlevinter(ig)=zlev(ig,1)
860      enddo
861
862         num(:)=0.
863         denom(:)=0.
[185]864         do ig=1,ngridmx
865          do l=1,nlayermx
[161]866             num(ig)=num(ig)+zw2(ig,l)*zlev(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
867             denom(ig)=denom(ig)+zw2(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
868          enddo
869       enddo
[185]870       do ig=1,ngridmx
[161]871       if (denom(ig).gt.1.e-10) then
872          zmax(ig)=2.*num(ig)/denom(ig)
873       endif
874       enddo
875
876! Attention, w2 est transforme en sa racine carree dans cette routine
877
878! ===========================================================================
879! ================= FIN HEIGHT ==============================================
880! ===========================================================================
881
882! Choix de la fonction d'alimentation utilisee pour la fermeture.
883
884      alim_star_clos(:,:)=entr_star(:,:)+alim_star(:,:)
885
886! ===========================================================================
887! ============= CLOSURE =====================================================
888! ===========================================================================
889
890!-------------------------------------------------------------------------------
891! Fermeture,determination de f
892!-------------------------------------------------------------------------------
893! Appel avec la version seche
894
895      alim_star2(:)=0.
896      alim_star_tot_clos(:)=0.
897      f(:)=0.
898
899! Indice vertical max (max de lalim) atteint par les thermiques sur le domaine
900      llmax=1
[185]901      do ig=1,ngridmx
[161]902         if (lalim(ig)>llmax) llmax=lalim(ig)
903      enddo
904
905
906! Calcul des integrales sur la verticale de alim_star et de
907!   alim_star^2/(rho dz)
908      do k=1,llmax-1
[185]909         do ig=1,ngridmx
[161]910            if (k<lalim(ig)) then
[185]911         alim_star2(ig)=alim_star2(ig)+alim_star_clos(ig,k)*alim_star_clos(ig,k)  &
[161]912      &                    /(rho(ig,k)*(zlev(ig,k+1)-zlev(ig,k)))
913         alim_star_tot_clos(ig)=alim_star_tot_clos(ig)+alim_star_clos(ig,k)
914      endif
915         enddo
916      enddo
[185]917 
[161]918! WARNING : MARS MODIF : we have added 2. : ratio of wmax/vmoy
919! True ratio is 3.5 but wetake into account the vmoy is the one alimentating
920! the thermal, so there are vs=0 into the vmoy... the true vmoy is lower. (a la louche)
921! And r_aspect has been changed from 2 to 1.5 from observations
[185]922      do ig=1,ngridmx
[161]923         if (alim_star2(ig)>1.e-10) then
[185]924!            f(ig)=wmax_sec(ig)*alim_star_tot_clos(ig)/  &
925!      &     (max(500.,zmax_sec(ig))*r_aspect*alim_star2(ig))
926             f(ig)=wmax(ig)*alim_star_tot_clos(ig)/  &
927      &     (max(500.,zmax(ig))*r_aspect*alim_star2(ig))
928
[161]929         endif
930      enddo
931
932! ===========================================================================
933! ============= FIN CLOSURE =================================================
934! ===========================================================================
935
936
937! ===========================================================================
938! ============= FLUX2 =======================================================
939! ===========================================================================
940
941!-------------------------------------------------------------------------------
942!deduction des flux
943!-------------------------------------------------------------------------------
944
945      fomass_max=0.8
946      alphamax=0.5
947
948      ncorecfm1=0
949      ncorecfm2=0
950      ncorecfm3=0
951      ncorecfm4=0
952      ncorecfm5=0
953      ncorecfm6=0
954      ncorecfm7=0
955      ncorecfm8=0
956      ncorecalpha=0
957
958!-------------------------------------------------------------------------
959! Multiplication par le flux de masse issu de la femreture
960!-------------------------------------------------------------------------
961
[185]962      do l=1,nlayermx
[161]963         entr(:,l)=f(:)*(entr_star(:,l)+alim_star(:,l))
964         detr(:,l)=f(:)*detr_star(:,l)
965      enddo
966
[185]967      do l=1,nlayermx
968         do ig=1,ngridmx
[161]969            if (l.lt.lmax(ig)) then
970               fm(ig,l+1)=fm(ig,l)+entr(ig,l)-detr(ig,l)
971            elseif(l.eq.lmax(ig)) then
972               fm(ig,l+1)=0.
973               detr(ig,l)=fm(ig,l)+entr(ig,l)
974            else
975               fm(ig,l+1)=0.
976            endif
977         enddo
978      enddo
979
980! Test provisoire : pour comprendre pourquoi on corrige plein de fois
981! le cas fm6, on commence par regarder une premiere fois avant les
982! autres corrections.
983
[314]984!      do l=1,nlayermx
985!         do ig=1,ngridmx
986!            if (detr(ig,l).gt.fm(ig,l)) then
987!               ncorecfm8=ncorecfm8+1
988!            endif
989!         enddo
990!      enddo
[161]991
992!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
993! FH Version en cours de test;
994! par rapport a thermcell_flux, on fait une grande boucle sur "l"
995! et on modifie le flux avec tous les contr�les appliques d'affilee
996! pour la meme couche
997! Momentanement, on duplique le calcule du flux pour pouvoir comparer
998! les flux avant et apres modif
999!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1000
[185]1001      do l=1,nlayermx
[161]1002
[185]1003         do ig=1,ngridmx
[161]1004            if (l.lt.lmax(ig)) then
1005               fm(ig,l+1)=fm(ig,l)+entr(ig,l)-detr(ig,l)
1006            elseif(l.eq.lmax(ig)) then
1007               fm(ig,l+1)=0.
1008               detr(ig,l)=fm(ig,l)+entr(ig,l)
1009            else
1010               fm(ig,l+1)=0.
1011            endif
1012         enddo
1013
1014
1015!-------------------------------------------------------------------------
1016! Verification de la positivite des flux de masse
1017!-------------------------------------------------------------------------
1018
[185]1019         do ig=1,ngridmx
[190]1020
[161]1021            if (fm(ig,l+1).lt.0.) then
[190]1022               if((l+1) .eq. lmax(ig)) then
1023               detr(ig,l)=detr(ig,l)+fm(ig,l+1)
1024               fm(ig,l+1)=0.
[336]1025               entr(ig,l+1)=0.
[190]1026               ncorecfm2=ncorecfm2+1
1027               else
1028          print*,'fm(l+1)<0 : ig, l+1,lmax :',ig,l+1,lmax(ig),fm(ig,l+1)
1029               ncorecfm1=ncorecfm1+1
[161]1030               fm(ig,l+1)=fm(ig,l)
1031               detr(ig,l)=entr(ig,l)
[190]1032               endif
[161]1033            endif
[190]1034
[161]1035         enddo
1036
[508]1037!  Les "optimisations" du flux sont desactivecelles : moins de bidouilles
[161]1038!  je considere que celles ci ne sont pas justifiees ou trop delicates
1039!  pour MARS, d'apres des observations LES.
1040!-------------------------------------------------------------------------
1041!Test sur fraca croissant
1042!-------------------------------------------------------------------------
1043!      if (iflag_thermals_optflux==0) then
[185]1044!         do ig=1,ngridmx
[161]1045!          if (l.ge.lalim(ig).and.l.le.lmax(ig) &
1046!     &    .and.(zw2(ig,l+1).gt.1.e-10).and.(zw2(ig,l).gt.1.e-10) ) then
1047!!  zzz est le flux en l+1 a frac constant
1048!             zzz=fm(ig,l)*rhobarz(ig,l+1)*zw2(ig,l+1)  &
1049!     &                          /(rhobarz(ig,l)*zw2(ig,l))
1050!             if (fm(ig,l+1).gt.zzz) then
1051!                detr(ig,l)=detr(ig,l)+fm(ig,l+1)-zzz
1052!                fm(ig,l+1)=zzz
1053!                ncorecfm4=ncorecfm4+1
1054!             endif
1055!          endif
1056!        enddo
1057!      endif
1058!
1059!-------------------------------------------------------------------------
1060!test sur flux de masse croissant
1061!-------------------------------------------------------------------------
1062!      if (iflag_thermals_optflux==0) then
[185]1063!         do ig=1,ngridmx
[161]1064!            if ((fm(ig,l+1).gt.fm(ig,l)).and.(l.gt.lalim(ig))) then
1065!              f_old=fm(ig,l+1)
1066!              fm(ig,l+1)=fm(ig,l)
1067!              detr(ig,l)=detr(ig,l)+f_old-fm(ig,l+1)
1068!               ncorecfm5=ncorecfm5+1
1069!            endif
1070!         enddo
1071!      endif
1072!
1073!-------------------------------------------------------------------------
1074!detr ne peut pas etre superieur a fm
1075!-------------------------------------------------------------------------
1076
[185]1077         do ig=1,ngridmx
[161]1078            if (detr(ig,l).gt.fm(ig,l)) then
1079               ncorecfm6=ncorecfm6+1
1080               detr(ig,l)=fm(ig,l)
1081               entr(ig,l)=fm(ig,l+1)
1082
1083! Dans le cas ou on est au dessus de la couche d'alimentation et que le
1084! detrainement est plus fort que le flux de masse, on stope le thermique.
[314]1085!            endif
[161]1086
[336]1087            if(l.gt.lmax(ig)) then
1088!            if(l.gt.lalim(ig)) then
[161]1089               detr(ig,l)=0.
1090               fm(ig,l+1)=0.
1091               entr(ig,l)=0.
1092            endif
[314]1093           
1094            endif
1095
[161]1096         enddo
1097
1098!-------------------------------------------------------------------------
1099!fm ne peut pas etre negatif
1100!-------------------------------------------------------------------------
1101
[185]1102         do ig=1,ngridmx
[161]1103            if (fm(ig,l+1).lt.0.) then
1104               detr(ig,l)=detr(ig,l)+fm(ig,l+1)
1105               fm(ig,l+1)=0.
1106               ncorecfm2=ncorecfm2+1
1107            endif
1108         enddo
1109
1110!-----------------------------------------------------------------------
1111!la fraction couverte ne peut pas etre superieure a 1
1112!-----------------------------------------------------------------------
1113!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1114! FH Partie a revisiter.
1115! Il semble qu'etaient codees ici deux optiques dans le cas
1116! F/ (rho *w) > 1
1117! soit limiter la hauteur du thermique en considerant que c'est
1118! la derniere chouche, soit limiter F a rho w.
1119! Dans le second cas, il faut en fait limiter a un peu moins
1120! que ca parce qu'on a des 1 / ( 1 -alpha) un peu plus loin
1121! dans thermcell_main et qu'il semble de toutes facons deraisonable
1122! d'avoir des fractions de 1..
1123! Ci dessous, et dans l'etat actuel, le premier des  deux if est
1124! sans doute inutile.
1125!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1126
[185]1127        do ig=1,ngridmx
[161]1128           if (zw2(ig,l+1).gt.1.e-10) then
1129           zfm=rhobarz(ig,l+1)*zw2(ig,l+1)*alphamax
1130           if ( fm(ig,l+1) .gt. zfm) then
1131              f_old=fm(ig,l+1)
1132              fm(ig,l+1)=zfm
1133              detr(ig,l)=detr(ig,l)+f_old-fm(ig,l+1)
1134              ncorecalpha=ncorecalpha+1
1135           endif
1136           endif
1137
1138        enddo
1139
1140! Fin de la grande boucle sur les niveaux verticaux
1141      enddo
1142
1143!-----------------------------------------------------------------------
1144! On fait en sorte que la quantite totale d'air entraine dans le
1145! panache ne soit pas trop grande comparee a la masse de la maille
1146!-----------------------------------------------------------------------
1147
[185]1148      do l=1,nlayermx-1
1149         do ig=1,ngridmx
[161]1150            eee0=entr(ig,l)
1151            ddd0=detr(ig,l)
1152            eee=entr(ig,l)-masse(ig,l)*fomass_max/ptimestep
1153            ddd=detr(ig,l)-eee
1154            if (eee.gt.0.) then
1155                ncorecfm3=ncorecfm3+1
1156                entr(ig,l)=entr(ig,l)-eee
1157                if ( ddd.gt.0.) then
1158!   l'entrainement est trop fort mais l'exces peut etre compense par une
1159!   diminution du detrainement)
1160                   detr(ig,l)=ddd
1161                else
1162!   l'entrainement est trop fort mais l'exces doit etre compense en partie
1163!   par un entrainement plus fort dans la couche superieure
1164                   if(l.eq.lmax(ig)) then
1165                      detr(ig,l)=fm(ig,l)+entr(ig,l)
1166                   else
1167                      entr(ig,l+1)=entr(ig,l+1)-ddd
1168                      detr(ig,l)=0.
1169                      fm(ig,l+1)=fm(ig,l)+entr(ig,l)
1170                      detr(ig,l)=0.
1171                   endif
1172                endif
1173            endif
1174         enddo
1175      enddo
1176!
1177!              ddd=detr(ig)-entre
1178!on s assure que tout s annule bien en zmax
[185]1179      do ig=1,ngridmx
[161]1180         fm(ig,lmax(ig)+1)=0.
1181         entr(ig,lmax(ig))=0.
1182         detr(ig,lmax(ig))=fm(ig,lmax(ig))+entr(ig,lmax(ig))
1183      enddo
1184
1185!-----------------------------------------------------------------------
1186! Impression du nombre de bidouilles qui ont ete necessaires
1187!-----------------------------------------------------------------------
1188
1189!IM 090508 beg
[185]1190      if (ncorecfm1+ncorecfm2+ncorecfm3+ncorecfm4+ncorecfm5+ncorecalpha > ngridmx/4. ) then
[161]1191         print*,'thermcell warning : large number of corrections'
1192         print*,'PB thermcell : on a du coriger ',ncorecfm1,'x fm1',&
1193     &     ncorecfm2,'x fm2',ncorecfm3,'x fm3 et', &
1194     &     ncorecfm4,'x fm4',ncorecfm5,'x fm5 et', &
1195     &     ncorecfm6,'x fm6', &
1196     &     ncorecfm7,'x fm7', &
1197     &     ncorecfm8,'x fm8', &
1198     &     ncorecalpha,'x alpha'
1199      endif
1200
1201! ===========================================================================
1202! ============= FIN FLUX2 ===================================================
1203! ===========================================================================
1204
1205
1206! ===========================================================================
1207! ============= TRANSPORT ===================================================
1208! ===========================================================================
1209
1210!------------------------------------------------------------------
1211!   calcul du transport vertical
1212!------------------------------------------------------------------
1213
1214! ------------------------------------------------------------------
1215! Transport de teta dans l'updraft : (remplace thermcell_dq)
1216! ------------------------------------------------------------------
1217
1218      zdthladj(:,:)=0.
1219
[185]1220      do ig=1,ngridmx
[161]1221         if(lmax(ig) .gt. 1) then
1222         do k=1,lmax(ig)
1223            zdthladj(ig,k)=(1./masse(ig,k))*(fm(ig,k+1)*ztv(ig,k+1)-    &
1224     &   fm(ig,k)*ztv(ig,k)+fm(ig,k)*ztva(ig,k)-fm(ig,k+1)*ztva(ig,k+1))
1225            if (ztv(ig,k) + ptimestep*zdthladj(ig,k) .le. 0.) then
[165]1226              print*,'Teta<0 in thermcell_dTeta up: qenv .. dq : ', ztv(ig,k),ptimestep*zdthladj(ig,k)
1227              if(ztv(ig,k) .gt. 0.) then
1228              zdthladj(ig,k)=0.
1229              endif
[161]1230            endif
1231         enddo
1232         endif
1233      enddo
1234
1235! ------------------------------------------------------------------
1236! Prescription des proprietes du downdraft
1237! ------------------------------------------------------------------
1238
1239      ztvd(:,:)=ztv(:,:)
1240      fm_down(:,:)=0.
[185]1241      do ig=1,ngridmx
[161]1242         if (lmax(ig) .gt. 1) then
1243         do l=1,lmax(ig)
[512]1244!              if(zlay(ig,l) .le. 0.8*zmax(ig)) then
1245              if(zlay(ig,l) .le. zmax(ig)) then
[496]1246              fm_down(ig,l) =fm(ig,l)* &
1247     &      max(fdfu,-3*max(0.,(zlay(ig,l)/zmax(ig)))-0.9)
[161]1248              endif
1249
[512]1250!             if(zlay(ig,l) .le. 0.06*zmax(ig)) then
1251!          ztvd(ig,l)=ztv(ig,l)*max(0.,(1.+(sqrt((zlay(ig,l)/zmax(ig))/0.122449) - 1.)*(ztva(ig,l)/ztv(ig,l) - 1.)))
1252!             elseif(zlay(ig,l) .le. 0.4*zmax(ig)) then
1253!          ztvd(ig,l)=ztv(ig,l)*max(0.,1.-0.25*(ztva(ig,l)/ztv(ig,l) - 1.))
1254!             elseif(zlay(ig,l) .le. 0.7*zmax(ig)) then
1255!          ztvd(ig,l)=ztv(ig,l)*max(0.,(1.+(((zlay(ig,l)/zmax(ig))-0.7)/1.)*(ztva(ig,l)/ztv(ig,l) - 1.)))
1256!             else
1257!          ztvd(ig,l)=ztv(ig,l)
1258!            endif
1259
1260!            if(zlay(ig,l) .le. 0.6*zmax(ig)) then
1261!          ztvd(ig,l)=ztv(ig,l)*((zlay(ig,l)/zmax(ig))/179.848 + 0.997832)
1262!            elseif(zlay(ig,l) .le. 0.8*zmax(ig)) then
1263!          ztvd(ig,l)=-ztv(ig,l)*(((zlay(ig,l)/zmax(ig))-171.74)/170.94)
1264!             else
1265!          ztvd(ig,l)=ztv(ig,l)
1266!            endif
1267
1268
1269!            if(zlay(ig,l) .le. 0.8*zmax(ig)) then
1270!          ztvd(ig,l)=ztv(ig,l)*((zlay(ig,l)/zmax(ig))/224.81 + 0.997832)
1271!            elseif(zlay(ig,l) .le. zmax(ig)) then
1272!          ztvd(ig,l)=-ztv(ig,l)*(((zlay(ig,l)/zmax(ig))-144.685)/143.885)
1273!             else
1274!          ztvd(ig,l)=ztv(ig,l)
1275!            endif
1276
1277
[546]1278!             if (zbuoy(ig,l) .gt. 0.) then
1279!               ztvd(ig,l)=ztva(ig,l)*0.9998
1280!!               ztvd(ig,l)=ztv(ig,l)*0.997832
1281!!             else
1282!!               if(zlay(ig,l) .le. zmax(ig)) then           
1283!!               ztvd(ig,l)=ztv(ig,l)*((zlay(ig,l)/zmax(ig))/299.7 + 0.997832)
1284!!               endif
1285!             endif
1286
1287            if(zlay(ig,l) .le. zmax(ig)) then           
1288          ztvd(ig,l)=min(ztv(ig,l),ztv(ig,l)*((zlay(ig,l)/zmax(ig))/400. + 0.997832))
1289!          ztvd(ig,l)=min(ztv(ig,l),ztv(ig,l)*((zlay(ig,l)/zmax(ig))/299.7 + 0.997832))
[161]1290             else
1291          ztvd(ig,l)=ztv(ig,l)
1292            endif
1293
1294         enddo
1295         endif
1296      enddo
1297
1298! ------------------------------------------------------------------
1299! Transport de teta dans le downdraft : (remplace thermcell_dq)
1300! ------------------------------------------------------------------
1301
1302       zdthladj_down(:,:)=0.
1303
[185]1304      do ig=1,ngridmx
[161]1305         if(lmax(ig) .gt. 1) then
[290]1306! No downdraft in the very-near surface layer, we begin at k=3
[496]1307 
1308         do k=3,lmax(ig)
[161]1309            zdthladj_down(ig,k)=(1./masse(ig,k))*(fm_down(ig,k+1)*ztv(ig,k+1)- &
1310     & fm_down(ig,k)*ztv(ig,k)+fm_down(ig,k)*ztvd(ig,k)-fm_down(ig,k+1)*ztvd(ig,k+1))
1311            if (ztv(ig,k) + ptimestep*zdthladj_down(ig,k) .le. 0.) then
1312              print*,'q<0 in thermcell_dTeta down: qenv .. dq : ', ztv(ig,k),ptimestep*zdthladj_down(ig,k)
[165]1313              if(ztv(ig,k) .gt. 0.) then
1314              zdthladj(ig,k)=0.
1315              endif
[161]1316            endif
1317         enddo
1318         endif
1319      enddo
1320
1321!------------------------------------------------------------------
1322! Calcul de la fraction de l'ascendance
1323!------------------------------------------------------------------
[185]1324      do ig=1,ngridmx
[161]1325         fraca(ig,1)=0.
[185]1326         fraca(ig,nlayermx+1)=0.
[161]1327      enddo
[185]1328      do l=2,nlayermx
1329         do ig=1,ngridmx
[161]1330            if (zw2(ig,l).gt.1.e-10) then
1331            fraca(ig,l)=fm(ig,l)/(rhobarz(ig,l)*zw2(ig,l))
1332            else
1333            fraca(ig,l)=0.
1334            endif
1335         enddo
1336      enddo
1337
1338
1339
1340! ===========================================================================
1341! ============= DV2 =========================================================
1342! ===========================================================================
1343! ROUTINE OVERIDE : ne prends pas en compte le downdraft
1344! de plus, le gradient de pression horizontal semble tout deregler... A VOIR
1345
1346      if (0 .eq. 1) then
1347
1348!------------------------------------------------------------------
1349!  calcul du transport vertical du moment horizontal
1350!------------------------------------------------------------------
1351
1352! Calcul du transport de V tenant compte d'echange par gradient
1353! de pression horizontal avec l'environnement
1354
1355!   calcul du detrainement
1356!---------------------------
1357
1358      nlarga0=0.
1359
[185]1360      do k=1,nlayermx
1361         do ig=1,ngridmx
[161]1362            detr_dv2(ig,k)=fm(ig,k)-fm(ig,k+1)+entr(ig,k)
1363         enddo
1364      enddo
1365
1366!   calcul de la valeur dans les ascendances
[185]1367      do ig=1,ngridmx
[161]1368         zua(ig,1)=zu(ig,1)
1369         zva(ig,1)=zv(ig,1)
1370         ue(ig,1)=zu(ig,1)
1371         ve(ig,1)=zv(ig,1)
1372      enddo
1373
[185]1374      gamma(1:ngridmx,1)=0.
1375      do k=2,nlayermx
1376         do ig=1,ngridmx
[161]1377            ltherm(ig,k)=(fm(ig,k+1)+detr_dv2(ig,k))*ptimestep > 1.e-5*masse(ig,k)
1378            if(ltherm(ig,k).and.zmax(ig)>0.) then
1379               gamma0(ig,k)=masse(ig,k)  &
1380     &         *sqrt( 0.5*(fraca(ig,k+1)+fraca(ig,k)) )  &
1381     &         *0.5/zmax(ig)  &
1382     &         *1.
1383            else
1384               gamma0(ig,k)=0.
1385            endif
1386            if (ltherm(ig,k).and.zmax(ig)<=0.) nlarga0=nlarga0+1
1387          enddo
1388      enddo
1389
1390      gamma(:,:)=0.
1391
[185]1392      do k=2,nlayermx
[161]1393
[185]1394         do ig=1,ngridmx
[161]1395
1396            if (ltherm(ig,k)) then
1397               dua(ig,k)=zua(ig,k-1)-zu(ig,k-1)
1398               dva(ig,k)=zva(ig,k-1)-zv(ig,k-1)
1399            else
1400               zua(ig,k)=zu(ig,k)
1401               zva(ig,k)=zv(ig,k)
1402               ue(ig,k)=zu(ig,k)
1403               ve(ig,k)=zv(ig,k)
1404            endif
1405         enddo
1406
1407
1408! Debut des iterations
1409!----------------------
1410
1411! AC WARNING : SALE !
1412
1413      do iter=1,5
[185]1414         do ig=1,ngridmx
[161]1415! Pour memoire : calcul prenant en compte la fraction reelle
1416!              zf=0.5*(fraca(ig,k)+fraca(ig,k+1))
1417!              zf2=1./(1.-zf)
1418! Calcul avec fraction infiniement petite
1419               zf=0.
1420               zf2=1.
1421
1422!  la première fois on multiplie le coefficient de freinage
1423!  par le module du vent dans la couche en dessous.
1424!  Mais pourquoi donc ???
1425               if (ltherm(ig,k)) then
1426!   On choisit une relaxation lineaire.
1427!                 gamma(ig,k)=gamma0(ig,k)
1428!   On choisit une relaxation quadratique.
[337]1429                gamma(ig,k)=gamma0(ig,k)*sqrt(dua(ig,k)**2+dva(ig,k)**2)
[161]1430                  zua(ig,k)=(fm(ig,k)*zua(ig,k-1)  &
1431     &               +(zf2*entr(ig,k)+gamma(ig,k))*zu(ig,k))  &
1432     &               /(fm(ig,k+1)+detr_dv2(ig,k)+entr(ig,k)*zf*zf2  &
1433     &                 +gamma(ig,k))
1434                  zva(ig,k)=(fm(ig,k)*zva(ig,k-1)  &
1435     &               +(zf2*entr(ig,k)+gamma(ig,k))*zv(ig,k))  &
1436     &               /(fm(ig,k+1)+detr_dv2(ig,k)+entr(ig,k)*zf*zf2  &
1437     &                 +gamma(ig,k))
1438
1439!                  print*,' OUTPUT DV2 !!!!!!!!!!!!!!!!!!!!',k,zua(ig,k),zva(ig,k),zu(ig,k),zv(ig,k),dua(ig,k),dva(ig,k)
1440                  dua(ig,k)=zua(ig,k)-zu(ig,k)
1441                  dva(ig,k)=zva(ig,k)-zv(ig,k)
1442                  ue(ig,k)=(zu(ig,k)-zf*zua(ig,k))*zf2
1443                  ve(ig,k)=(zv(ig,k)-zf*zva(ig,k))*zf2
1444               endif
1445         enddo
1446! Fin des iterations
1447!--------------------
1448      enddo
1449
[185]1450      enddo ! k=2,nlayermx
[161]1451
1452! Calcul du flux vertical de moment dans l'environnement.
1453!---------------------------------------------------------
[185]1454      do k=2,nlayermx
1455         do ig=1,ngridmx
[161]1456            wud(ig,k)=fm(ig,k)*ue(ig,k)
1457            wvd(ig,k)=fm(ig,k)*ve(ig,k)
1458         enddo
1459      enddo
[185]1460      do ig=1,ngridmx
[161]1461         wud(ig,1)=0.
[185]1462         wud(ig,nlayermx+1)=0.
[161]1463         wvd(ig,1)=0.
[185]1464         wvd(ig,nlayermx+1)=0.
[161]1465      enddo
1466
1467! calcul des tendances.
1468!-----------------------
[185]1469      do k=1,nlayermx
1470         do ig=1,ngridmx
[161]1471            pduadj(ig,k)=((detr_dv2(ig,k)+gamma(ig,k))*zua(ig,k)  &
1472     &               -(entr(ig,k)+gamma(ig,k))*ue(ig,k)  &
1473     &               -wud(ig,k)+wud(ig,k+1))  &
1474     &               /masse(ig,k)
1475            pdvadj(ig,k)=((detr_dv2(ig,k)+gamma(ig,k))*zva(ig,k)  &
1476     &               -(entr(ig,k)+gamma(ig,k))*ve(ig,k)  &
1477     &               -wvd(ig,k)+wvd(ig,k+1))  &
1478     &               /masse(ig,k)
1479         enddo
1480      enddo
1481
1482
1483! Sorties eventuelles.
1484!----------------------
1485
1486!      if (nlarga0>0) then
1487!          print*,'WARNING !!!!!! DANS THERMCELL_DV2 '
1488!      print*,nlarga0,' points pour lesquels laraga=0. dans un thermique'
1489!          print*,'Il faudrait decortiquer ces points'
1490!      endif
1491
1492! ===========================================================================
1493! ============= FIN DV2 =====================================================
1494! ===========================================================================
1495
1496      else
1497
[337]1498!      modname='momentum'
1499!      call thermcell_dqupdown(ngridmx,nlayermx,ptimestep,fm,entr,detr,  &
1500!     &     masse,zu,pduadj,ztvd,fm_down,ztv,modname,lmax)
1501!
1502!      call thermcell_dqupdown(ngridmx,nlayermx,ptimestep,fm,entr,detr,  &
1503!     &     masse,zv,pdvadj,ztvd,fm_down,ztv,modname,lmax)
[161]1504
1505      endif
1506
1507!------------------------------------------------------------------
[508]1508!  calcul du transport vertical de traceurs
[161]1509!------------------------------------------------------------------
1510
[508]1511! We only transport co2 tracer because it is coupled to the scheme through theta_m
1512! The rest is transported outside the sub-timestep loop
1513
1514      if (ico2.ne.0) then
1515!      if (nqmx .ne. 0.) then
[185]1516      do l=1,nlayermx
[508]1517         zdzfull(:,l)=zlev(:,l+1)-zlev(:,l)
[161]1518      enddo
1519
[508]1520      modname='tracer'
1521      call thermcell_dqup(ngridmx,nlayermx,ptimestep     &
1522     &     ,fm,entr,detr,  &
1523     &    masse,pq(:,:,ico2),pdqadj(:,:,ico2),modname,zdzfull)
1524!      endif
1525
1526! Compute the ratio between theta and theta_m
1527     
1528       do l=1,nlayermx
1529          do ig=1,ngridmx
1530             ratiom(ig,l)=1./(A*(pq(ig,l,ico2)+pdqadj(ig,l,ico2)*ptimestep)+B)
1531          enddo
1532       enddo
1533       else
1534          ratiom(:,:)=1.
1535       endif
1536
1537
[161]1538!------------------------------------------------------------------
[508]1539!  incrementation dt
[161]1540!------------------------------------------------------------------
1541
[508]1542      do l=1,nlayermx
1543         do ig=1,ngridmx
1544         pdtadj(ig,l)=(zdthladj(ig,l)+zdthladj_down(ig,l))*zpopsk(ig,l)*ratiom(ig,l)
[512]1545!         pdtadj(ig,l)=zdthladj(ig,l)*zpopsk(ig,l)*ratiom(ig,l)
[508]1546         enddo
1547      enddo
[161]1548
1549!------------------------------------------------------------------
1550!  calcul du transport vertical de la tke
1551!------------------------------------------------------------------
1552
[313]1553!      modname='tke'
1554!      call thermcell_dqupdown(ngridmx,nlayermx,ptimestep,fm,entr,detr,  &
1555!      &      masse,pq2,pdq2adj,ztvd,fm_down,ztv,modname,lmax)
[161]1556
1557! ===========================================================================
1558! ============= FIN TRANSPORT ===============================================
1559! ===========================================================================
1560
1561
1562!------------------------------------------------------------------
1563!   Calculs de diagnostiques pour les sorties
1564!------------------------------------------------------------------
1565! DIAGNOSTIQUE
1566! We compute interface values for teta env and th. The last interface
1567! value does not matter, as the mass flux is 0 there.
1568
1569   
[185]1570      do l=1,nlayermx-1
1571       do ig=1,ngridmx
[508]1572        teta_th_int(ig,l)=0.5*(ztva(ig,l+1)+ztva(ig,l))*ratiom(ig,l)
1573        teta_down_int(ig,l) = 0.5*(ztvd(ig,l+1)+ztvd(ig,l))*ratiom(ig,l)
1574        teta_env_int(ig,l)=0.5*(ztv(ig,l+1)+ztv(ig,l))*ratiom(ig,l)
[161]1575       enddo
1576      enddo
[185]1577      do ig=1,ngridmx
1578       teta_th_int(ig,nlayermx)=teta_th_int(ig,nlayermx-1)
1579       teta_env_int(ig,nlayermx)=teta_env_int(ig,nlayermx-1)
1580       teta_down_int(ig,nlayermx)=teta_down_int(ig,nlayermx-1)
[161]1581      enddo
[185]1582      do l=1,nlayermx
1583       do ig=1,ngridmx
[161]1584        heatFlux(ig,l)=fm(ig,l)*(teta_th_int(ig,l)-teta_env_int(ig,l))/(rhobarz(ig,l))
[508]1585        buoyancyOut(ig,l)=g*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
1586        buoyancyEst(ig,l)=g*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
[161]1587        heatFlux_down(ig,l)=fm_down(ig,l)*(teta_down_int(ig,l)-teta_env_int(ig,l))/rhobarz(ig,l)
1588       enddo
1589      enddo
1590
1591      return
1592      end
Note: See TracBrowser for help on using the repository browser.