source: LMDZ6/trunk/libf/phylmd/thermcell_plume_6A.F90 @ 4095

Last change on this file since 4095 was 4095, checked in by fhourdin, 2 years ago

Nettoyage thermiques (suite)

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 40.2 KB
Line 
1!
2! $Id: thermcell_plume_6A.F90 4095 2022-03-14 06:57:55Z fhourdin $
3!
4      SUBROUTINE thermcell_plume_6A(itap,ngrid,nlay,ptimestep,ztv,zthl,po,zl,rhobarz,  &
5     &           zlev,pplev,pphi,zpspsk,alim_star,alim_star_tot,  &
6     &           lalim,f0,detr_star,entr_star,f_star,csc,ztva,  &
7     &           ztla,zqla,zqta,zha,zw2,w_est,ztva_est,zqsatth,lmix,lmix_bis,linter &
8    &           ,lev_out,lunout1,igout)
9!     &           ,lev_out,lunout1,igout,zbuoy,zbuoyjam)
10!--------------------------------------------------------------------------
11!thermcell_plume: calcule les valeurs de qt, thetal et w dans l ascendance
12!--------------------------------------------------------------------------
13
14       USE thermcell_ini_mod, ONLY: prt_level,fact_thermals_ed_dz,iflag_thermals_ed,RLvCP,RETV,RG
15       USE thermcell_ini_mod, ONLY: fact_epsilon, betalpha, afact, fact_shell
16       USE thermcell_ini_mod, ONLY: detr_min, entr_min, detr_q_coef, detr_q_power
17       USE thermcell_ini_mod, ONLY: mix0, thermals_flag_alim
18
19       IMPLICIT NONE
20
21      integer,intent(in) :: itap,lev_out,lunout1,igout,ngrid,nlay
22      real,intent(in) :: ptimestep
23      real,intent(in),dimension(ngrid,nlay) :: ztv
24      real,intent(in),dimension(ngrid,nlay) :: zthl
25      real,intent(in),dimension(ngrid,nlay) :: po
26      real,intent(in),dimension(ngrid,nlay) :: zl
27      real,intent(in),dimension(ngrid,nlay) :: rhobarz
28      real,intent(in),dimension(ngrid,nlay+1) :: zlev
29      real,intent(in),dimension(ngrid,nlay+1) :: pplev
30      real,intent(in),dimension(ngrid,nlay) :: pphi
31      real,intent(in),dimension(ngrid,nlay) :: zpspsk
32      real,intent(in),dimension(ngrid) :: f0
33
34      integer,intent(out) :: lalim(ngrid)
35      real,intent(out),dimension(ngrid,nlay) :: alim_star
36      real,intent(out),dimension(ngrid) :: alim_star_tot
37      real,intent(out),dimension(ngrid,nlay) :: detr_star
38      real,intent(out),dimension(ngrid,nlay) :: entr_star
39      real,intent(out),dimension(ngrid,nlay+1) :: f_star
40      real,intent(out),dimension(ngrid,nlay) :: csc
41      real,intent(out),dimension(ngrid,nlay) :: ztva
42      real,intent(out),dimension(ngrid,nlay) :: ztla
43      real,intent(out),dimension(ngrid,nlay) :: zqla
44      real,intent(out),dimension(ngrid,nlay) :: zqta
45      real,intent(out),dimension(ngrid,nlay) :: zha
46      real,intent(out),dimension(ngrid,nlay+1) :: zw2
47      real,intent(out),dimension(ngrid,nlay+1) :: w_est
48      real,intent(out),dimension(ngrid,nlay) :: ztva_est
49      real,intent(out),dimension(ngrid,nlay) :: zqsatth
50      integer,intent(out),dimension(ngrid) :: lmix
51      integer,intent(out),dimension(ngrid) :: lmix_bis
52      real,intent(out),dimension(ngrid) :: linter
53
54      REAL zdw2,zdw2bis
55      REAL zw2modif
56      REAL zw2fact,zw2factbis
57      REAL zeps(ngrid,nlay)
58
59      REAL    wmaxa(ngrid)
60
61      INTEGER ig,l,k,lt,it,lm
62      integer nbpb
63
64      real,dimension(ngrid,nlay) :: detr
65      real,dimension(ngrid,nlay) :: entr
66      real,dimension(ngrid,nlay+1) :: wa_moy
67      real,dimension(ngrid,nlay) :: ztv_est
68      real,dimension(ngrid) :: ztemp,zqsat
69      real,dimension(ngrid,nlay) :: zqla_est
70      real,dimension(ngrid,nlay) :: zta_est
71
72      real zdz,zbuoy(ngrid,nlay),zalpha,gamma(ngrid,nlay),zdqt(ngrid,nlay),zw2m
73      real zbuoyjam(ngrid,nlay),zdqtjam(ngrid,nlay)
74      real zbuoybis,zdz2,zdz3,lmel,entrbis,zdzbis
75      real d_temp(ngrid)
76      real ztv1,ztv2,factinv,zinv,zlmel
77      real zlmelup,zlmeldwn,zlt,zltdwn,zltup
78      real atv1,atv2,btv1,btv2
79      real ztv_est1,ztv_est2
80      real zcor,zdelta,zcvm5,qlbef
81      real zbetalpha, coefzlmel
82      real eps
83      logical Zsat
84      LOGICAL active(ngrid),activetmp(ngrid)
85      REAL fact_gamma,fact_gamma2,fact_epsilon2
86      REAL coefc
87      REAL c2(ngrid,nlay)
88
89      if (ngrid==1) print*,'THERMCELL PLUME MODIFIE 2014/07/11'
90      Zsat=.false.
91! Initialisation
92
93
94      zbetalpha=betalpha/(1.+betalpha)
95
96
97! Initialisations des variables r?elles
98if (1==1) then
99      ztva(:,:)=ztv(:,:)
100      ztva_est(:,:)=ztva(:,:)
101      ztv_est(:,:)=ztv(:,:)
102      ztla(:,:)=zthl(:,:)
103      zqta(:,:)=po(:,:)
104      zqla(:,:)=0.
105      zha(:,:) = ztva(:,:)
106else
107      ztva(:,:)=0.
108      ztv_est(:,:)=0.
109      ztva_est(:,:)=0.
110      ztla(:,:)=0.
111      zqta(:,:)=0.
112      zha(:,:) =0.
113endif
114
115      zqla_est(:,:)=0.
116      zqsatth(:,:)=0.
117      zqla(:,:)=0.
118      detr_star(:,:)=0.
119      entr_star(:,:)=0.
120      alim_star(:,:)=0.
121      alim_star_tot(:)=0.
122      csc(:,:)=0.
123      detr(:,:)=0.
124      entr(:,:)=0.
125      zw2(:,:)=0.
126      zbuoy(:,:)=0.
127      zbuoyjam(:,:)=0.
128      gamma(:,:)=0.
129      zeps(:,:)=0.
130      w_est(:,:)=0.
131      f_star(:,:)=0.
132      wa_moy(:,:)=0.
133      linter(:)=1.
134!     linter(:)=1.
135! Initialisation des variables entieres
136      lmix(:)=1
137      lmix_bis(:)=2
138      wmaxa(:)=0.
139
140
141!-------------------------------------------------------------------------
142! On ne considere comme actif que les colonnes dont les deux premieres
143! couches sont instables.
144!-------------------------------------------------------------------------
145
146      active(:)=ztv(:,1)>ztv(:,2)
147      d_temp(:)=0. ! Pour activer un contraste de temperature a la base
148                   ! du panache
149!  Cet appel pourrait être fait avant thermcell_plume dans thermcell_main
150      CALL thermcell_alim(thermals_flag_alim,ngrid,nlay,ztv,d_temp,zlev,alim_star,lalim)
151
152!------------------------------------------------------------------------------
153! Calcul dans la premiere couche
154! On decide dans cette version que le thermique n'est actif que si la premiere
155! couche est instable.
156! Pourrait etre change si on veut que le thermiques puisse se d??clencher
157! dans une couche l>1
158!------------------------------------------------------------------------------
159do ig=1,ngrid
160! Le panache va prendre au debut les caracteristiques de l'air contenu
161! dans cette couche.
162    if (active(ig)) then
163    ztla(ig,1)=zthl(ig,1)
164    zqta(ig,1)=po(ig,1)
165    zqla(ig,1)=zl(ig,1)
166!cr: attention, prise en compte de f*(1)=1
167    f_star(ig,2)=alim_star(ig,1)
168    zw2(ig,2)=2.*RG*(ztv(ig,1)-ztv(ig,2))/ztv(ig,2)  &
169&                     *(zlev(ig,2)-zlev(ig,1))  &
170&                     *0.4*pphi(ig,1)/(pphi(ig,2)-pphi(ig,1))
171    w_est(ig,2)=zw2(ig,2)
172    endif
173enddo
174!
175
176!==============================================================================
177!boucle de calcul de la vitesse verticale dans le thermique
178!==============================================================================
179do l=2,nlay-1
180!==============================================================================
181
182
183! On decide si le thermique est encore actif ou non
184! AFaire : Il faut sans doute ajouter entr_star a alim_star dans ce test
185    do ig=1,ngrid
186       active(ig)=active(ig) &
187&                 .and. zw2(ig,l)>1.e-10 &
188&                 .and. f_star(ig,l)+alim_star(ig,l)>1.e-10
189    enddo
190
191
192
193!---------------------------------------------------------------------------
194! calcul des proprietes thermodynamiques et de la vitesse de la couche l
195! sans tenir compte du detrainement et de l'entrainement dans cette
196! couche
197! C'est a dire qu'on suppose
198! ztla(l)=ztla(l-1) et zqta(l)=zqta(l-1)
199! Ici encore, on doit pouvoir ajouter entr_star (qui peut etre calculer
200! avant) a l'alimentation pour avoir un calcul plus propre
201!---------------------------------------------------------------------------
202
203   ztemp(:)=zpspsk(:,l)*ztla(:,l-1)
204   call thermcell_qsat(ngrid,active,pplev(:,l),ztemp,zqta(:,l-1),zqsat(:))
205    do ig=1,ngrid
206!       print*,'active',active(ig),ig,l
207        if(active(ig)) then
208        zqla_est(ig,l)=max(0.,zqta(ig,l-1)-zqsat(ig))
209        ztva_est(ig,l) = ztla(ig,l-1)*zpspsk(ig,l)+RLvCp*zqla_est(ig,l)
210        zta_est(ig,l)=ztva_est(ig,l)
211        ztva_est(ig,l) = ztva_est(ig,l)/zpspsk(ig,l)
212        ztva_est(ig,l) = ztva_est(ig,l)*(1.+RETV*(zqta(ig,l-1)  &
213     &      -zqla_est(ig,l))-zqla_est(ig,l))
214 
215
216!Modif AJAM
217
218        zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
219        zdz=zlev(ig,l+1)-zlev(ig,l)         
220        lmel=fact_thermals_ed_dz*zlev(ig,l)
221!        lmel=0.09*zlev(ig,l)
222        zlmel=zlev(ig,l)+lmel
223        zlmelup=zlmel+(zdz/2)
224        zlmeldwn=zlmel-(zdz/2)
225
226        lt=l+1
227        zlt=zlev(ig,lt)
228        zdz3=zlev(ig,lt+1)-zlt
229        zltdwn=zlt-zdz3/2
230        zltup=zlt+zdz3/2
231         
232!=========================================================================
233! 3. Calcul de la flotabilite modifie par melange avec l'air au dessus
234!=========================================================================
235
236!--------------------------------------------------
237        if (iflag_thermals_ed.lt.8) then
238!--------------------------------------------------
239!AJ052014: J'ai remplac?? la boucle do par un do while
240! afin de faire moins de calcul dans la boucle
241!--------------------------------------------------
242            do while (zlmelup.gt.zltup)
243               lt=lt+1
244               zlt=zlev(ig,lt)
245               zdz3=zlev(ig,lt+1)-zlt
246               zltdwn=zlt-zdz3/2
247               zltup=zlt+zdz3/2       
248            enddo
249!--------------------------------------------------
250!AJ052014: Si iflag_thermals_ed<8 (par ex 6), alors
251! on cherche o?? se trouve l'altitude d'inversion
252! en calculant ztv1 (interpolation de la valeur de
253! theta au niveau lt en utilisant les niveaux lt-1 et
254! lt-2) et ztv2 (interpolation avec les niveaux lt+1
255! et lt+2). Si theta r??ellement calcul??e au niveau lt
256! comprise entre ztv1 et ztv2, alors il y a inversion
257! et on calcule son altitude zinv en supposant que ztv(lt)
258! est une combinaison lineaire de ztv1 et ztv2.
259! Ensuite, on calcule la flottabilite en comparant
260! la temperature de la couche l a celle de l'air situe
261! l+lmel plus haut, ce qui necessite de savoir quel fraction
262! de cet air est au-dessus ou en-dessous de l'inversion   
263!--------------------------------------------------
264            atv1=(ztv(ig,lt-1)-ztv(ig,lt-2))/(zlev(ig,lt-1)-zlev(ig,lt-2))
265            btv1=(ztv(ig,lt-2)*zlev(ig,lt-1)-ztv(ig,lt-1)*zlev(ig,lt-2)) &
266    &          /(zlev(ig,lt-1)-zlev(ig,lt-2))
267            atv2=(ztv(ig,lt+2)-ztv(ig,lt+1))/(zlev(ig,lt+2)-zlev(ig,lt+1))
268            btv2=(ztv(ig,lt+1)*zlev(ig,lt+2)-ztv(ig,lt+2)*zlev(ig,lt+1)) &
269    &          /(zlev(ig,lt+2)-zlev(ig,lt+1))
270
271             ztv1=atv1*zlt+btv1
272             ztv2=atv2*zlt+btv2
273
274             if (ztv(ig,lt).gt.ztv1.and.ztv(ig,lt).lt.ztv2) then 
275
276!--------------------------------------------------
277!AJ052014: D??calage de zinv qui est entre le haut
278!          et le bas de la couche lt
279!--------------------------------------------------
280                factinv=(ztv2-ztv(ig,lt))/(ztv2-ztv1)
281                zinv=zltdwn+zdz3*factinv
282
283         
284                if (zlmeldwn.ge.zinv) then
285                   ztv_est(ig,l)=atv2*zlmel+btv2
286                   zbuoyjam(ig,l)=fact_shell*RG*(ztva_est(ig,l)-ztv_est(ig,l))/ztv_est(ig,l) &
287    &                    +(1.-fact_shell)*zbuoy(ig,l)
288                elseif (zlmelup.ge.zinv) then
289                 ztv_est2=atv2*0.5*(zlmelup+zinv)+btv2
290                   ztv_est1=atv1*0.5*(zinv+zlmeldwn)+btv1
291                   ztv_est(ig,l)=((zlmelup-zinv)/zdz)*ztv_est2+((zinv-zlmeldwn)/zdz)*ztv_est1
292
293                   zbuoyjam(ig,l)=fact_shell*RG*(((zlmelup-zinv)/zdz)*(ztva_est(ig,l)- &
294    &            ztv_est2)/ztv_est2+((zinv-zlmeldwn)/zdz)*(ztva_est(ig,l)- &
295    &            ztv_est1)/ztv_est1)+(1.-fact_shell)*zbuoy(ig,l)
296
297                else
298                   ztv_est(ig,l)=atv1*zlmel+btv1
299                   zbuoyjam(ig,l)=fact_shell*RG*(ztva_est(ig,l)-ztv_est(ig,l))/ztv_est(ig,l) &
300    &                           +(1.-fact_shell)*zbuoy(ig,l)
301                endif
302
303             else ! if (ztv(ig,lt).gt.ztv1.and.ztv(ig,lt).lt.ztv2) then
304
305                if (zlmeldwn.gt.zltdwn) then
306                   zbuoyjam(ig,l)=fact_shell*RG*((ztva_est(ig,l)- &
307    &                ztv(ig,lt))/ztv(ig,lt))+(1.-fact_shell)*zbuoy(ig,l)
308                else
309                   zbuoyjam(ig,l)=fact_shell*RG*(((zlmelup-zltdwn)/zdz)*(ztva_est(ig,l)- &
310    &                ztv(ig,lt))/ztv(ig,lt)+((zltdwn-zlmeldwn)/zdz)*(ztva_est(ig,l)- &
311    &                ztv(ig,lt-1))/ztv(ig,lt-1))+(1.-fact_shell)*zbuoy(ig,l)
312
313                endif
314
315!          zbuoyjam(ig,l)=fact_shell*RG*(((zlmelup-zltdwn)/zdz)*(ztva_est(ig,l)- &
316!    &          ztv1)/ztv1+((zltdwn-zlmeldwn)/zdz)*(ztva_est(ig,l)- &
317!    &          ztv(ig,lt-1))/ztv(ig,lt-1))+(1.-fact_shell)*zbuoy(ig,l)
318!         zdqt(ig,l)=Max(0.,((lmel+zdz3-zdz2)/zdz3)*(zqta(ig,l-1)- &
319!    &          po(ig,lt))/po(ig,lt)+((zdz2-lmel)/zdz3)*(zqta(ig,l-1)- &
320!     &          po(ig,lt-1))/po(ig,lt-1))
321          endif ! if (ztv(ig,lt).gt.ztv1.and.ztv(ig,lt).lt.ztv2) then
322
323        else  !   if (iflag_thermals_ed.lt.8) then
324           lt=l+1
325           zlt=zlev(ig,lt)
326           zdz2=zlev(ig,lt)-zlev(ig,l)
327
328           do while (lmel.gt.zdz2)
329             lt=lt+1
330             zlt=zlev(ig,lt)
331             zdz2=zlt-zlev(ig,l)
332           enddo
333           zdz3=zlev(ig,lt+1)-zlt
334           zltdwn=zlev(ig,lt)-zdz3/2
335           zlmelup=zlmel+(zdz/2)
336           coefzlmel=Min(1.,(zlmelup-zltdwn)/zdz)
337           zbuoyjam(ig,l)=1.*RG*(coefzlmel*(ztva_est(ig,l)- &
338    &          ztv(ig,lt))/ztv(ig,lt)+(1.-coefzlmel)*(ztva_est(ig,l)- &
339    &          ztv(ig,lt-1))/ztv(ig,lt-1))+0.*zbuoy(ig,l)
340        endif !   if (iflag_thermals_ed.lt.8) then
341
342!------------------------------------------------
343!AJAM:nouveau calcul de w? 
344!------------------------------------------------
345              zdz=zlev(ig,l+1)-zlev(ig,l)
346              zdzbis=zlev(ig,l)-zlev(ig,l-1)
347              zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
348
349              zw2fact=fact_epsilon*2.*zdz/(1.+betalpha)
350              zw2factbis=fact_epsilon*2.*zdzbis/(1.+betalpha)
351              zdw2=afact*zbuoy(ig,l)/fact_epsilon
352              zdw2bis=afact*zbuoy(ig,l-1)/fact_epsilon
353!              zdw2bis=0.5*(zdw2+zdw2bis)
354              lm=Max(1,l-2)
355!              zdw2=(afact/fact_epsilon)*((zdz/zdzbis)*zbuoy(ig,l) &
356!    &              +((zdzbis-zdz)/zdzbis)*zbuoy(ig,l-1))
357!              zdw2bis=(afact/fact_epsilon)*((zdz/zdzbis)*zbuoy(ig,l-1) &
358!    &              +((zdzbis-zdz)/zdzbis)*zbuoy(ig,l-1))
359!             w_est(ig,l+1)=Max(0.0001,exp(-zw2fact)*(w_est(ig,l)-zdw2)+zdw2)
360!             w_est(ig,l+1)=(zdz/zdzbis)*Max(0.0001,exp(-zw2fact)* &
361!    &                     (w_est(ig,l)-zdw2)+zdw2)+(zdzbis-zdz)/zdzbis* &
362!    &                     Max(0.0001,exp(-zw2factbis)*(w_est(ig,l-1)-zdw2bis)+zdw2)
363!              w_est(ig,l+1)=Max(0.0001,(1-exp(-zw2fact))*zdw2+w_est(ig,l)*exp(-zw2fact))
364
365!--------------------------------------------------
366!AJ052014: J'ai remplac? w_est(ig,l) par zw2(ig,l)
367!--------------------------------------------------
368         if (iflag_thermals_ed==8) then
369! Ancienne version
370!             w_est(ig,l+1)=Max(0.0001,(zdz/zdzbis)*(exp(-zw2fact)* &
371!    &                     (w_est(ig,l)-zdw2)+zdw2)+(zdzbis-zdz)/zdzbis* &
372!    &                     (exp(-zw2factbis)*(w_est(ig,l-1)-zdw2bis)+zdw2))
373
374            w_est(ig,l+1)=Max(0.0001,exp(-zw2fact)*(w_est(ig,l)-zdw2)+zdw2)
375
376! Nouvelle version Arnaud
377         else
378!             w_est(ig,l+1)=Max(0.0001,(zdz/zdzbis)*(exp(-zw2fact)* &
379!    &                     (w_est(ig,l)-zdw2)+zdw2)+(zdzbis-zdz)/zdzbis* &
380!    &                     (exp(-zw2factbis)*(w_est(ig,l-1)-zdw2bis)+zdw2))
381
382            w_est(ig,l+1)=Max(0.0001,exp(-zw2fact)*(w_est(ig,l)-zdw2bis)+zdw2)
383
384!             w_est(ig,l+1)=Max(0.0001,(zdz/(zdzbis+zdz))*(exp(-zw2fact)* &
385!    &                     (w_est(ig,l)-zdw2bis)+zdw2)+(zdzbis/(zdzbis+zdz))* &
386!    &                     (exp(-zw2factbis)*(w_est(ig,l-1)-zdw2bis)+zdw2bis))
387
388
389
390!            w_est(ig,l+1)=Max(0.0001,(w_est(ig,l)+zdw2bis*zw2fact)*exp(-zw2fact))
391
392!             w_est(ig,l+1)=Max(0.0001,(zdz/zdzbis)*(zw2(ig,l)+zdw2*zw2fact)*exp(-zw2fact)+ &
393!    &                      (zdzbis-zdz)/zdzbis*(zw2(ig,l-1)+zdw2bis*zw2factbis)*exp(-zw2factbis))
394
395!             w_est(ig,l+1)=Max(0.0001,exp(-zw2factbis)*(w_est(ig,l-1)-zdw2bis)+zdw2)
396
397         endif
398
399
400         if (iflag_thermals_ed<6) then
401             zalpha=f0(ig)*f_star(ig,l)/sqrt(w_est(ig,l+1))/rhobarz(ig,l)
402!              fact_epsilon=0.0005/(zalpha+0.025)**0.5
403!              fact_epsilon=Min(0.003,0.0004/(zalpha)**0.5)
404              fact_epsilon=0.0002/(zalpha+0.1)
405              zw2fact=fact_epsilon*2.*zdz/(1.+betalpha)
406              zw2factbis=fact_epsilon*2.*zdzbis/(1.+betalpha)
407              zdw2=afact*zbuoy(ig,l)/fact_epsilon
408              zdw2bis=afact*zbuoy(ig,l-1)/fact_epsilon
409!              w_est(ig,l+1)=Max(0.0001,(zw2(ig,l)+zdw2*zw2fact)*exp(-zw2fact))
410
411!              w_est(ig,l+1)=Max(0.0001,(zdz/zdzbis)*(exp(-zw2fact)* &
412!    &                     (zw2(ig,l)-zdw2)+zdw2)+(zdzbis-zdz)/zdzbis* &
413!    &                     (exp(-zw2factbis)*(zw2(ig,l-1)-zdw2bis)+zdw2))
414
415            w_est(ig,l+1)=Max(0.0001,exp(-zw2fact)*(w_est(ig,l)-zdw2bis)+zdw2)
416
417
418         endif
419!--------------------------------------------------
420!AJ052014: J'ai comment? ce if plus n?cessaire puisqu'
421!on fait max(0.0001,.....)
422!--------------------------------------------------         
423
424!             if (w_est(ig,l+1).lt.0.) then
425!               w_est(ig,l+1)=zw2(ig,l)
426!                w_est(ig,l+1)=0.0001
427!             endif
428
429       endif
430    enddo
431
432
433!-------------------------------------------------
434!calcul des taux d'entrainement et de detrainement
435!-------------------------------------------------
436
437     do ig=1,ngrid
438        if (active(ig)) then
439
440!          zw2m=max(0.5*(w_est(ig,l)+w_est(ig,l+1)),0.1)
441          zw2m=w_est(ig,l+1)
442!          zw2m=zw2(ig,l)
443          zdz=zlev(ig,l+1)-zlev(ig,l)
444          zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
445!          zbuoybis=zbuoy(ig,l)+RG*0.1/300.
446          zbuoybis=zbuoy(ig,l)
447          zalpha=f0(ig)*f_star(ig,l)/sqrt(w_est(ig,l+1))/rhobarz(ig,l)
448          zdqt(ig,l)=max(zqta(ig,l-1)-po(ig,l),0.)/po(ig,l)
449
450         
451!          entr_star(ig,l)=f_star(ig,l)*zdz*zbetalpha*MAX(0.,  &
452!    &     afact*zbuoybis/zw2m - fact_epsilon )
453
454!          entr_star(ig,l)=MAX(0.,f_star(ig,l)*zdz*zbetalpha*  &
455!    &     afact*zbuoybis/zw2m - fact_epsilon )
456
457
458
459!          zbuoyjam(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
460
461!=========================================================================
462! 4. Calcul de l'entrainement et du detrainement
463!=========================================================================
464
465!          entr_star(ig,l)=f_star(ig,l)*zdz*zbetalpha*MAX(0.,  &
466!    &     afact*zbuoyjam(ig,l)/zw2m - fact_epsilon )
467!          entrbis=entr_star(ig,l)
468
469          if (iflag_thermals_ed.lt.6) then
470          fact_epsilon=0.0002/(zalpha+0.1)
471          endif
472         
473
474
475          detr_star(ig,l)=f_star(ig,l)*zdz             &
476    &     *( mix0 * 0.1 / (zalpha+0.001)               &
477    &     + MAX(detr_min, -afact*zbetalpha*zbuoyjam(ig,l)/zw2m   &
478    &     + detr_q_coef*(zdqt(ig,l)/zw2m)**detr_q_power))
479
480!          detr_star(ig,l)=(zdz/zdzbis)*detr_star(ig,l)+ &
481!    &                          ((zdzbis-zdz)/zdzbis)*detr_star(ig,l-1)
482
483          zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
484
485          entr_star(ig,l)=f_star(ig,l)*zdz* (         &
486    &       mix0 * 0.1 / (zalpha+0.001)               &
487    &     + zbetalpha*MAX(entr_min,                   &
488    &     afact*zbuoyjam(ig,l)/zw2m - fact_epsilon))
489
490
491!          entr_star(ig,l)=f_star(ig,l)*zdz* (         &
492!    &       mix0 * 0.1 / (zalpha+0.001)               &
493!    &     + MAX(entr_min,                   &
494!    &     zbetalpha*afact*zbuoyjam(ig,l)/zw2m - fact_epsilon +  &
495!    &     detr_q_coef*(zdqt(ig,l)/zw2m)**detr_q_power))
496
497
498!          entr_star(ig,l)=(zdz/zdzbis)*entr_star(ig,l)+ &
499!    &                          ((zdzbis-zdz)/zdzbis)*entr_star(ig,l-1)
500
501!          entr_star(ig,l)=Max(0.,f_star(ig,l)*zdz*zbetalpha*  &     
502!    &     afact*zbuoy(ig,l)/zw2m &
503!    &     - 1.*fact_epsilon)
504
505         
506! En dessous de lalim, on prend le max de alim_star et entr_star pour
507! alim_star et 0 sinon
508        if (l.lt.lalim(ig)) then
509          alim_star(ig,l)=max(alim_star(ig,l),entr_star(ig,l))
510          entr_star(ig,l)=0.
511        endif
512!        if (l.lt.lalim(ig).and.alim_star(ig,l)>alim_star(ig,l-1)) then
513!          alim_star(ig,l)=entrbis
514!        endif
515
516!        print*,'alim0',zlev(ig,l),entr_star(ig,l),detr_star(ig,l),zw2m,zbuoy(ig,l),f_star(ig,l)
517! Calcul du flux montant normalise
518      f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
519     &              -detr_star(ig,l)
520
521      endif
522   enddo
523
524
525!============================================================================
526! 5. calcul de la vitesse verticale en melangeant Tl et qt du thermique
527!===========================================================================
528
529   activetmp(:)=active(:) .and. f_star(:,l+1)>1.e-10
530   do ig=1,ngrid
531       if (activetmp(ig)) then
532           Zsat=.false.
533           ztla(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
534     &            (alim_star(ig,l)+entr_star(ig,l))*zthl(ig,l))  &
535     &            /(f_star(ig,l+1)+detr_star(ig,l))
536           zqta(ig,l)=(f_star(ig,l)*zqta(ig,l-1)+  &
537     &            (alim_star(ig,l)+entr_star(ig,l))*po(ig,l))  &
538     &            /(f_star(ig,l+1)+detr_star(ig,l))
539
540        endif
541    enddo
542
543   ztemp(:)=zpspsk(:,l)*ztla(:,l)
544   call thermcell_qsat(ngrid,activetmp,pplev(:,l),ztemp,zqta(:,l),zqsatth(:,l))
545   do ig=1,ngrid
546      if (activetmp(ig)) then
547! on ecrit de maniere conservative (sat ou non)
548!          T = Tl +Lv/Cp ql
549           zqla(ig,l)=max(0.,zqta(ig,l)-zqsatth(ig,l))
550           ztva(ig,l) = ztla(ig,l)*zpspsk(ig,l)+RLvCp*zqla(ig,l)
551           ztva(ig,l) = ztva(ig,l)/zpspsk(ig,l)
552!on rajoute le calcul de zha pour diagnostiques (temp potentielle)
553           zha(ig,l) = ztva(ig,l)
554           ztva(ig,l) = ztva(ig,l)*(1.+RETV*(zqta(ig,l)  &
555     &              -zqla(ig,l))-zqla(ig,l))
556           zbuoy(ig,l)=RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
557           zdz=zlev(ig,l+1)-zlev(ig,l)
558           zdzbis=zlev(ig,l)-zlev(ig,l-1)
559           zeps(ig,l)=(entr_star(ig,l)+alim_star(ig,l))/(f_star(ig,l)*zdz)
560!!!!!!!          fact_epsilon=0.002
561            zw2fact=fact_epsilon*2.*zdz/(1.+betalpha)
562            zw2factbis=fact_epsilon*2.*zdzbis/(1.+betalpha)
563            zdw2= afact*zbuoy(ig,l)/(fact_epsilon)
564            zdw2bis= afact*zbuoy(ig,l-1)/(fact_epsilon)
565!              zdw2=(afact/fact_epsilon)*((zdz/zdzbis)*zbuoy(ig,l) &
566!    &              +((zdzbis-zdz)/zdzbis)*zbuoy(ig,l-1))
567!              lm=Max(1,l-2)
568!              zdw2bis=(afact/fact_epsilon)*((zdz/zdzbis)*zbuoy(ig,l-1) &
569!    &              +((zdzbis-zdz)/zdzbis)*zbuoy(ig,l-1))
570!            zw2(ig,l+1)=Max(0.0001,exp(-zw2fact)*(zw2(ig,l)-zdw2bis)+zdw2)
571!            zw2(ig,l+1)=Max(0.0001,(zdz/zdzbis)*(zw2(ig,l)+zdw2*zw2fact)*exp(-zw2fact)+ &
572!     &                   (zdzbis-zdz)/zdzbis*(zw2(ig,l-1)+zdw2bis*zw2factbis)*exp(-zw2factbis))
573!            zw2(ig,l+1)=Max(0.0001,(zw2(ig,l)+zdw2*zw2fact)*exp(-zw2fact))
574!            zw2(ig,l+1)=Max(0.0001,(zdz/zdzbis)*(exp(-zw2fact)* &
575!    &                     (zw2(ig,l)-zdw2)+zdw2)+(zdzbis-zdz)/zdzbis* &
576!    &                     (exp(-zw2factbis)*(zw2(ig,l-1)-zdw2bis)+zdw2))
577            if (iflag_thermals_ed==8) then
578            zw2(ig,l+1)=Max(0.0001,exp(-zw2fact)*(zw2(ig,l)-zdw2)+zdw2)
579            else
580            zw2(ig,l+1)=Max(0.0001,exp(-zw2fact)*(zw2(ig,l)-zdw2bis)+zdw2)
581            endif
582!            zw2(ig,l+1)=Max(0.0001,(zdz/(zdz+zdzbis))*(exp(-zw2fact)* &
583!    &                     (zw2(ig,l)-zdw2)+zdw2bis)+(zdzbis/(zdz+zdzbis))* &
584!    &                     (exp(-zw2factbis)*(zw2(ig,l-1)-zdw2bis)+zdw2bis))
585
586
587           if (iflag_thermals_ed.lt.6) then
588           zalpha=f0(ig)*f_star(ig,l)/sqrt(zw2(ig,l+1))/rhobarz(ig,l)
589!           fact_epsilon=0.0005/(zalpha+0.025)**0.5
590!           fact_epsilon=Min(0.003,0.0004/(zalpha)**0.5)
591           fact_epsilon=0.0002/(zalpha+0.1)**1
592            zw2fact=fact_epsilon*2.*zdz/(1.+betalpha)
593            zw2factbis=fact_epsilon*2.*zdzbis/(1.+betalpha)
594            zdw2= afact*zbuoy(ig,l)/(fact_epsilon)
595            zdw2bis= afact*zbuoy(ig,l-1)/(fact_epsilon)
596
597!            zw2(ig,l+1)=Max(0.0001,(zdz/zdzbis)*(exp(-zw2fact)* &
598!    &                     (zw2(ig,l)-zdw2)+zdw2)+(zdzbis-zdz)/zdzbis* &
599!    &                     (exp(-zw2factbis)*(zw2(ig,l-1)-zdw2bis)+zdw2))
600!            zw2(ig,l+1)=Max(0.0001,(zw2(ig,l)+zdw2*zw2fact)*exp(-zw2fact))
601            zw2(ig,l+1)=Max(0.0001,exp(-zw2fact)*(zw2(ig,l)-zdw2bis)+zdw2)
602
603           endif
604
605
606      endif
607   enddo
608
609        if (prt_level.ge.20) print*,'coucou calcul detr 460: ig, l',ig, l
610!
611!===========================================================================
612! 6. initialisations pour le calcul de la hauteur du thermique, de l'inversion et de la vitesse verticale max
613!===========================================================================
614
615   nbpb=0
616   do ig=1,ngrid
617            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
618!               stop'On tombe sur le cas particulier de thermcell_dry'
619!               print*,'On tombe sur le cas particulier de thermcell_plume'
620                nbpb=nbpb+1
621                zw2(ig,l+1)=0.
622                linter(ig)=l+1
623            endif
624
625        if (zw2(ig,l+1).lt.0.) then
626           linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
627     &               -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
628           zw2(ig,l+1)=0.
629!+CR:04/05/12:correction calcul linter pour calcul de zmax continu
630        elseif (f_star(ig,l+1).lt.0.) then
631           linter(ig)=(l*(f_star(ig,l+1)-f_star(ig,l))  &
632     &               -f_star(ig,l))/(f_star(ig,l+1)-f_star(ig,l))
633           zw2(ig,l+1)=0.
634!fin CR:04/05/12
635        endif
636
637           wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
638
639        if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
640!   lmix est le niveau de la couche ou w (wa_moy) est maximum
641!on rajoute le calcul de lmix_bis
642            if (zqla(ig,l).lt.1.e-10) then
643               lmix_bis(ig)=l+1
644            endif
645            lmix(ig)=l+1
646            wmaxa(ig)=wa_moy(ig,l+1)
647        endif
648   enddo
649
650   if (nbpb>0) then
651   print*,'WARNING on tombe ',nbpb,' x sur un pb pour l=',l,' dans thermcell_plume'
652   endif
653
654!=========================================================================
655! FIN DE LA BOUCLE VERTICALE
656      enddo
657!=========================================================================
658
659!on recalcule alim_star_tot
660       do ig=1,ngrid
661          alim_star_tot(ig)=0.
662       enddo
663       do ig=1,ngrid
664          do l=1,lalim(ig)-1
665          alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
666          enddo
667       enddo
668       
669
670        if (prt_level.ge.20) print*,'coucou calcul detr 470: ig, l', ig, l
671
672#undef wrgrads_thermcell
673#ifdef wrgrads_thermcell
674         call wrgradsfi(1,nlay,entr_star(igout,1:nlay),'esta      ','esta      ')
675         call wrgradsfi(1,nlay,detr_star(igout,1:nlay),'dsta      ','dsta      ')
676         call wrgradsfi(1,nlay,zbuoy(igout,1:nlay),'buoy      ','buoy      ')
677         call wrgradsfi(1,nlay,zdqt(igout,1:nlay),'dqt      ','dqt      ')
678         call wrgradsfi(1,nlay,w_est(igout,1:nlay),'w_est     ','w_est     ')
679         call wrgradsfi(1,nlay,w_est(igout,2:nlay+1),'w_es2     ','w_es2     ')
680         call wrgradsfi(1,nlay,zw2(igout,1:nlay),'zw2A      ','zw2A      ')
681#endif
682
683
684 RETURN
685     end
686
687
688
689
690
691
692
693!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
694!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
695!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
696!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
697!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
698!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
699 SUBROUTINE thermcell_plume_5B(itap,ngrid,nlay,ptimestep,ztv,zthl,po,zl,rhobarz,  &
700&           zlev,pplev,pphi,zpspsk,alim_star,alim_star_tot,  &
701&           lalim,f0,detr_star,entr_star,f_star,csc,ztva,  &
702&           ztla,zqla,zqta,zha,zw2,w_est,ztva_est,zqsatth,lmix,lmix_bis,linter &
703&           ,lev_out,lunout1,igout)
704!&           ,lev_out,lunout1,igout,zbuoy,zbuoyjam)
705
706!--------------------------------------------------------------------------
707!thermcell_plume: calcule les valeurs de qt, thetal et w dans l ascendance
708! Version conforme a l'article de Rio et al. 2010.
709! Code ecrit par Catherine Rio, Arnaud Jam et Frederic Hourdin
710!--------------------------------------------------------------------------
711
712      USE thermcell_ini_mod, ONLY: prt_level,fact_thermals_ed_dz,iflag_thermals_ed,RLvCP,RETV,RG
713      IMPLICIT NONE
714
715      INTEGER itap
716      INTEGER lunout1,igout
717      INTEGER ngrid,nlay
718      REAL ptimestep
719      REAL ztv(ngrid,nlay)
720      REAL zthl(ngrid,nlay)
721      REAL po(ngrid,nlay)
722      REAL zl(ngrid,nlay)
723      REAL rhobarz(ngrid,nlay)
724      REAL zlev(ngrid,nlay+1)
725      REAL pplev(ngrid,nlay+1)
726      REAL pphi(ngrid,nlay)
727      REAL zpspsk(ngrid,nlay)
728      REAL alim_star(ngrid,nlay)
729      REAL f0(ngrid)
730      INTEGER lalim(ngrid)
731      integer lev_out                           ! niveau pour les print
732      integer nbpb
733   
734      real alim_star_tot(ngrid)
735
736      REAL ztva(ngrid,nlay)
737      REAL ztla(ngrid,nlay)
738      REAL zqla(ngrid,nlay)
739      REAL zqta(ngrid,nlay)
740      REAL zha(ngrid,nlay)
741
742      REAL detr_star(ngrid,nlay)
743      REAL coefc
744      REAL entr_star(ngrid,nlay)
745      REAL detr(ngrid,nlay)
746      REAL entr(ngrid,nlay)
747
748      REAL csc(ngrid,nlay)
749
750      REAL zw2(ngrid,nlay+1)
751      REAL w_est(ngrid,nlay+1)
752      REAL f_star(ngrid,nlay+1)
753      REAL wa_moy(ngrid,nlay+1)
754
755      REAL ztva_est(ngrid,nlay)
756      REAL zqla_est(ngrid,nlay)
757      REAL zqsatth(ngrid,nlay)
758      REAL zta_est(ngrid,nlay)
759      REAL zbuoyjam(ngrid,nlay)
760      REAL ztemp(ngrid),zqsat(ngrid)
761      REAL zdw2
762      REAL zw2modif
763      REAL zw2fact
764      REAL zeps(ngrid,nlay)
765
766      REAL linter(ngrid)
767      INTEGER lmix(ngrid)
768      INTEGER lmix_bis(ngrid)
769      REAL    wmaxa(ngrid)
770
771      INTEGER ig,l,k
772
773      real zdz,zbuoy(ngrid,nlay),zalpha,gamma(ngrid,nlay),zdqt(ngrid,nlay),zw2m
774      real zbuoybis
775      real zcor,zdelta,zcvm5,qlbef,zdz2
776      real betalpha,zbetalpha
777      real eps, afact
778      logical Zsat
779      LOGICAL active(ngrid),activetmp(ngrid)
780      REAL fact_gamma,fact_epsilon,fact_gamma2,fact_epsilon2
781      REAL c2(ngrid,nlay)
782      Zsat=.false.
783! Initialisation
784
785      fact_epsilon=0.002
786      betalpha=0.9
787      afact=2./3.           
788
789      zbetalpha=betalpha/(1.+betalpha)
790
791
792! Initialisations des variables reeles
793if (1==1) then
794      ztva(:,:)=ztv(:,:)
795      ztva_est(:,:)=ztva(:,:)
796      ztla(:,:)=zthl(:,:)
797      zqta(:,:)=po(:,:)
798      zha(:,:) = ztva(:,:)
799else
800      ztva(:,:)=0.
801      ztva_est(:,:)=0.
802      ztla(:,:)=0.
803      zqta(:,:)=0.
804      zha(:,:) =0.
805endif
806
807      zqla_est(:,:)=0.
808      zqsatth(:,:)=0.
809      zqla(:,:)=0.
810      detr_star(:,:)=0.
811      entr_star(:,:)=0.
812      alim_star(:,:)=0.
813      alim_star_tot(:)=0.
814      csc(:,:)=0.
815      detr(:,:)=0.
816      entr(:,:)=0.
817      zw2(:,:)=0.
818      zbuoy(:,:)=0.
819      zbuoyjam(:,:)=0.
820      gamma(:,:)=0.
821      zeps(:,:)=0.
822      w_est(:,:)=0.
823      f_star(:,:)=0.
824      wa_moy(:,:)=0.
825      linter(:)=1.
826!     linter(:)=1.
827! Initialisation des variables entieres
828      lmix(:)=1
829      lmix_bis(:)=2
830      wmaxa(:)=0.
831      lalim(:)=1
832
833
834!-------------------------------------------------------------------------
835! On ne considere comme actif que les colonnes dont les deux premieres
836! couches sont instables.
837!-------------------------------------------------------------------------
838      active(:)=ztv(:,1)>ztv(:,2)
839
840!-------------------------------------------------------------------------
841! Definition de l'alimentation
842!-------------------------------------------------------------------------
843      do l=1,nlay-1
844         do ig=1,ngrid
845            if (ztv(ig,l)> ztv(ig,l+1) .and. ztv(ig,1)>=ztv(ig,l) ) then
846               alim_star(ig,l)=MAX((ztv(ig,l)-ztv(ig,l+1)),0.)  &
847     &                       *sqrt(zlev(ig,l+1))
848               lalim(ig)=l+1
849               alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
850            endif
851         enddo
852      enddo
853      do l=1,nlay
854         do ig=1,ngrid
855            if (alim_star_tot(ig) > 1.e-10 ) then
856               alim_star(ig,l)=alim_star(ig,l)/alim_star_tot(ig)
857            endif
858         enddo
859      enddo
860      alim_star_tot(:)=1.
861
862
863
864!------------------------------------------------------------------------------
865! Calcul dans la premiere couche
866! On decide dans cette version que le thermique n'est actif que si la premiere
867! couche est instable.
868! Pourrait etre change si on veut que le thermiques puisse se d??clencher
869! dans une couche l>1
870!------------------------------------------------------------------------------
871do ig=1,ngrid
872! Le panache va prendre au debut les caracteristiques de l'air contenu
873! dans cette couche.
874    if (active(ig)) then
875    ztla(ig,1)=zthl(ig,1)
876    zqta(ig,1)=po(ig,1)
877    zqla(ig,1)=zl(ig,1)
878!cr: attention, prise en compte de f*(1)=1
879    f_star(ig,2)=alim_star(ig,1)
880    zw2(ig,2)=2.*RG*(ztv(ig,1)-ztv(ig,2))/ztv(ig,2)  &
881&                     *(zlev(ig,2)-zlev(ig,1))  &
882&                     *0.4*pphi(ig,1)/(pphi(ig,2)-pphi(ig,1))
883    w_est(ig,2)=zw2(ig,2)
884    endif
885enddo
886!
887
888!==============================================================================
889!boucle de calcul de la vitesse verticale dans le thermique
890!==============================================================================
891do l=2,nlay-1
892!==============================================================================
893
894
895! On decide si le thermique est encore actif ou non
896! AFaire : Il faut sans doute ajouter entr_star a alim_star dans ce test
897    do ig=1,ngrid
898       active(ig)=active(ig) &
899&                 .and. zw2(ig,l)>1.e-10 &
900&                 .and. f_star(ig,l)+alim_star(ig,l)>1.e-10
901    enddo
902
903
904
905!---------------------------------------------------------------------------
906! calcul des proprietes thermodynamiques et de la vitesse de la couche l
907! sans tenir compte du detrainement et de l'entrainement dans cette
908! couche
909! C'est a dire qu'on suppose
910! ztla(l)=ztla(l-1) et zqta(l)=zqta(l-1)
911! Ici encore, on doit pouvoir ajouter entr_star (qui peut etre calculer
912! avant) a l'alimentation pour avoir un calcul plus propre
913!---------------------------------------------------------------------------
914
915   ztemp(:)=zpspsk(:,l)*ztla(:,l-1)
916   call thermcell_qsat(ngrid,active,pplev(:,l),ztemp,zqta(:,l-1),zqsat(:))
917
918    do ig=1,ngrid
919!       print*,'active',active(ig),ig,l
920        if(active(ig)) then
921        zqla_est(ig,l)=max(0.,zqta(ig,l-1)-zqsat(ig))
922        ztva_est(ig,l) = ztla(ig,l-1)*zpspsk(ig,l)+RLvCp*zqla_est(ig,l)
923        zta_est(ig,l)=ztva_est(ig,l)
924        ztva_est(ig,l) = ztva_est(ig,l)/zpspsk(ig,l)
925        ztva_est(ig,l) = ztva_est(ig,l)*(1.+RETV*(zqta(ig,l-1)  &
926     &      -zqla_est(ig,l))-zqla_est(ig,l))
927
928!------------------------------------------------
929!AJAM:nouveau calcul de w? 
930!------------------------------------------------
931              zdz=zlev(ig,l+1)-zlev(ig,l)
932              zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
933
934              zw2fact=fact_epsilon*2.*zdz/(1.+betalpha)
935              zdw2=(afact)*zbuoy(ig,l)/(fact_epsilon)
936              w_est(ig,l+1)=Max(0.0001,exp(-zw2fact)*(w_est(ig,l)-zdw2)+zdw2)
937 
938
939             if (w_est(ig,l+1).lt.0.) then
940                w_est(ig,l+1)=zw2(ig,l)
941             endif
942       endif
943    enddo
944
945
946!-------------------------------------------------
947!calcul des taux d'entrainement et de detrainement
948!-------------------------------------------------
949
950     do ig=1,ngrid
951        if (active(ig)) then
952
953          zw2m=max(0.5*(w_est(ig,l)+w_est(ig,l+1)),0.1)
954          zw2m=w_est(ig,l+1)
955          zdz=zlev(ig,l+1)-zlev(ig,l)
956          zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
957!          zbuoybis=zbuoy(ig,l)+RG*0.1/300.
958          zbuoybis=zbuoy(ig,l)
959          zalpha=f0(ig)*f_star(ig,l)/sqrt(w_est(ig,l+1))/rhobarz(ig,l)
960          zdqt(ig,l)=max(zqta(ig,l-1)-po(ig,l),0.)/po(ig,l)
961
962         
963          entr_star(ig,l)=f_star(ig,l)*zdz*  zbetalpha*MAX(0.,  &
964    &     afact*zbuoybis/zw2m - fact_epsilon )
965
966
967          detr_star(ig,l)=f_star(ig,l)*zdz                        &
968    &     *MAX(1.e-3, -afact*zbetalpha*zbuoy(ig,l)/zw2m          &
969    &     + 0.012*(zdqt(ig,l)/zw2m)**0.5 )
970         
971! En dessous de lalim, on prend le max de alim_star et entr_star pour
972! alim_star et 0 sinon
973        if (l.lt.lalim(ig)) then
974          alim_star(ig,l)=max(alim_star(ig,l),entr_star(ig,l))
975          entr_star(ig,l)=0.
976        endif
977
978! Calcul du flux montant normalise
979      f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
980     &              -detr_star(ig,l)
981
982      endif
983   enddo
984
985
986!----------------------------------------------------------------------------
987!calcul de la vitesse verticale en melangeant Tl et qt du thermique
988!---------------------------------------------------------------------------
989   activetmp(:)=active(:) .and. f_star(:,l+1)>1.e-10
990   do ig=1,ngrid
991       if (activetmp(ig)) then
992           Zsat=.false.
993           ztla(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
994     &            (alim_star(ig,l)+entr_star(ig,l))*zthl(ig,l))  &
995     &            /(f_star(ig,l+1)+detr_star(ig,l))
996           zqta(ig,l)=(f_star(ig,l)*zqta(ig,l-1)+  &
997     &            (alim_star(ig,l)+entr_star(ig,l))*po(ig,l))  &
998     &            /(f_star(ig,l+1)+detr_star(ig,l))
999
1000        endif
1001    enddo
1002
1003   ztemp(:)=zpspsk(:,l)*ztla(:,l)
1004   call thermcell_qsat(ngrid,activetmp,pplev(:,l),ztemp,zqta(:,l),zqsatth(:,l))
1005
1006   do ig=1,ngrid
1007      if (activetmp(ig)) then
1008! on ecrit de maniere conservative (sat ou non)
1009!          T = Tl +Lv/Cp ql
1010           zqla(ig,l)=max(0.,zqta(ig,l)-zqsatth(ig,l))
1011           ztva(ig,l) = ztla(ig,l)*zpspsk(ig,l)+RLvCp*zqla(ig,l)
1012           ztva(ig,l) = ztva(ig,l)/zpspsk(ig,l)
1013!on rajoute le calcul de zha pour diagnostiques (temp potentielle)
1014           zha(ig,l) = ztva(ig,l)
1015           ztva(ig,l) = ztva(ig,l)*(1.+RETV*(zqta(ig,l)  &
1016     &              -zqla(ig,l))-zqla(ig,l))
1017           zbuoy(ig,l)=RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
1018           zdz=zlev(ig,l+1)-zlev(ig,l)
1019           zeps(ig,l)=(entr_star(ig,l)+alim_star(ig,l))/(f_star(ig,l)*zdz)
1020
1021            zw2fact=fact_epsilon*2.*zdz/(1.+betalpha)
1022            zdw2=afact*zbuoy(ig,l)/(fact_epsilon)
1023            zw2(ig,l+1)=Max(0.0001,exp(-zw2fact)*(zw2(ig,l)-zdw2)+zdw2)
1024      endif
1025   enddo
1026
1027        if (prt_level.ge.20) print*,'coucou calcul detr 460: ig, l',ig, l
1028!
1029!---------------------------------------------------------------------------
1030!initialisations pour le calcul de la hauteur du thermique, de l'inversion et de la vitesse verticale max
1031!---------------------------------------------------------------------------
1032
1033   nbpb=0
1034   do ig=1,ngrid
1035            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
1036!               stop'On tombe sur le cas particulier de thermcell_dry'
1037!               print*,'On tombe sur le cas particulier de thermcell_plume'
1038                nbpb=nbpb+1
1039                zw2(ig,l+1)=0.
1040                linter(ig)=l+1
1041            endif
1042
1043        if (zw2(ig,l+1).lt.0.) then
1044           linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
1045     &               -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
1046           zw2(ig,l+1)=0.
1047        elseif (f_star(ig,l+1).lt.0.) then
1048           linter(ig)=(l*(f_star(ig,l+1)-f_star(ig,l))  &
1049     &               -f_star(ig,l))/(f_star(ig,l+1)-f_star(ig,l))
1050!           print*,"linter plume", linter(ig)
1051           zw2(ig,l+1)=0.
1052        endif
1053
1054           wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
1055
1056        if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
1057!   lmix est le niveau de la couche ou w (wa_moy) est maximum
1058!on rajoute le calcul de lmix_bis
1059            if (zqla(ig,l).lt.1.e-10) then
1060               lmix_bis(ig)=l+1
1061            endif
1062            lmix(ig)=l+1
1063            wmaxa(ig)=wa_moy(ig,l+1)
1064        endif
1065   enddo
1066
1067   if (nbpb>0) then
1068   print*,'WARNING on tombe ',nbpb,' x sur un pb pour l=',l,' dans thermcell_plume'
1069   endif
1070
1071!=========================================================================
1072! FIN DE LA BOUCLE VERTICALE
1073      enddo
1074!=========================================================================
1075
1076!on recalcule alim_star_tot
1077       do ig=1,ngrid
1078          alim_star_tot(ig)=0.
1079       enddo
1080       do ig=1,ngrid
1081          do l=1,lalim(ig)-1
1082          alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
1083          enddo
1084       enddo
1085       
1086
1087        if (prt_level.ge.20) print*,'coucou calcul detr 470: ig, l', ig, l
1088
1089#undef wrgrads_thermcell
1090#ifdef wrgrads_thermcell
1091         call wrgradsfi(1,nlay,entr_star(igout,1:nlay),'esta      ','esta      ')
1092         call wrgradsfi(1,nlay,detr_star(igout,1:nlay),'dsta      ','dsta      ')
1093         call wrgradsfi(1,nlay,zbuoy(igout,1:nlay),'buoy      ','buoy      ')
1094         call wrgradsfi(1,nlay,zdqt(igout,1:nlay),'dqt      ','dqt      ')
1095         call wrgradsfi(1,nlay,w_est(igout,1:nlay),'w_est     ','w_est     ')
1096         call wrgradsfi(1,nlay,w_est(igout,2:nlay+1),'w_es2     ','w_es2     ')
1097         call wrgradsfi(1,nlay,zw2(igout,1:nlay),'zw2A      ','zw2A      ')
1098#endif
1099
1100
1101     return
1102     end
Note: See TracBrowser for help on using the repository browser.