source: LMDZ6/trunk/libf/phylmd/thermcell_plume.F90 @ 4089

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

Reecriture des thermiques

File size: 15.6 KB
Line 
1!
2! $Id: thermcell_plume.F90 3074 2017-11-15 13:31:44Z fhourdin $
3!
4      SUBROUTINE thermcell_plume(itap,ngrid,klev,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! Auhtors : Catherine Rio, Frédéric Hourdin, Arnaud Jam
12!
13!thermcell_plume: calcule les valeurs de qt, thetal et w dans l ascendance
14!   This versions starts from a cleaning of thermcell_plume_6A (2019/01/20)
15!   thermcell_plume_6A is activate for flag_thermas_ed < 10
16!   thermcell_plume_5B for flag_thermas_ed < 20
17!   thermcell_plume for flag_thermals_ed>= 20
18!   Various options are controled by the flag_thermals_ed parameter
19!   = 20 : equivalent to thermcell_plume_6A with flag_thermals_ed=8
20!   = 21 : the Jam strato-cumulus modif is not activated in detrainment
21!   = 29 : an other way to compute the modified buoyancy (to be tested)
22!--------------------------------------------------------------------------
23       USE thermcell_ini_mod, ONLY: prt_level,fact_thermals_ed_dz,iflag_thermals_ed,RLvCP,RETV,RG
24       USE thermcell_ini_mod, ONLY: fact_epsilon, betalpha, afact, fact_shell
25       USE thermcell_ini_mod, ONLY: detr_min, entr_min, detr_q_coef, detr_q_power
26       USE thermcell_ini_mod, ONLY: mix0, thermals_flag_alim
27
28
29       IMPLICIT NONE
30
31      INTEGER itap
32      INTEGER lunout1,igout
33      INTEGER ngrid,klev
34      REAL ptimestep
35      REAL ztv(ngrid,klev)
36      REAL zthl(ngrid,klev)
37      REAL po(ngrid,klev)
38      REAL zl(ngrid,klev)
39      REAL rhobarz(ngrid,klev)
40      REAL zlev(ngrid,klev+1)
41      REAL pplev(ngrid,klev+1)
42      REAL pphi(ngrid,klev)
43      REAL zpspsk(ngrid,klev)
44      REAL alim_star(ngrid,klev)
45      REAL f0(ngrid)
46      INTEGER lalim(ngrid)
47      integer lev_out                           ! niveau pour les print
48      integer nbpb
49   
50      real alim_star_tot(ngrid)
51
52      REAL ztva(ngrid,klev)
53      REAL ztla(ngrid,klev)
54      REAL zqla(ngrid,klev)
55      REAL zqta(ngrid,klev)
56      REAL zha(ngrid,klev)
57
58      REAL detr_star(ngrid,klev)
59      REAL coefc
60      REAL entr_star(ngrid,klev)
61      REAL detr(ngrid,klev)
62      REAL entr(ngrid,klev)
63
64      REAL csc(ngrid,klev)
65
66      REAL zw2(ngrid,klev+1)
67      REAL w_est(ngrid,klev+1)
68      REAL f_star(ngrid,klev+1)
69      REAL wa_moy(ngrid,klev+1)
70
71      REAL ztva_est(ngrid,klev)
72      REAL ztv_est(ngrid,klev)
73      REAL zqla_est(ngrid,klev)
74      REAL zqsatth(ngrid,klev)
75      REAL zta_est(ngrid,klev)
76      REAL ztemp(ngrid),zqsat(ngrid)
77      REAL zdw2,zdw2bis
78      REAL zw2modif
79      REAL zw2fact,zw2factbis
80      REAL zeps(ngrid,klev)
81
82      REAL linter(ngrid)
83      INTEGER lmix(ngrid)
84      INTEGER lmix_bis(ngrid)
85      REAL    wmaxa(ngrid)
86
87      INTEGER ig,l,k,lt,it,lm
88
89      real zdz,zbuoy(ngrid,klev),zalpha,gamma(ngrid,klev),zdqt(ngrid,klev),zw2m
90      real zbuoyjam(ngrid,klev),zdqtjam(ngrid,klev)
91      real zdz2,zdz3,lmel,entrbis,zdzbis
92      real d_temp(ngrid)
93      real ztv1,ztv2,factinv,zinv,zlmel
94      real zlmelup,zlmeldwn,zlt,zltdwn,zltup
95      real atv1,atv2,btv1,btv2
96      real ztv_est1,ztv_est2
97      real zcor,zdelta,zcvm5,qlbef
98      real zbetalpha, coefzlmel
99      real eps
100      logical Zsat
101      LOGICAL active(ngrid),activetmp(ngrid)
102      REAL fact_gamma,fact_gamma2,fact_epsilon2
103
104
105      REAL c2(ngrid,klev)
106
107      if (ngrid==1) print*,'THERMCELL PLUME MODIFIE 2014/07/11'
108      Zsat=.false.
109! Initialisation
110
111
112      zbetalpha=betalpha/(1.+betalpha)
113
114
115! Initialisations des variables r?elles
116if (1==1) then
117      ztva(:,:)=ztv(:,:)
118      ztva_est(:,:)=ztva(:,:)
119      ztv_est(:,:)=ztv(:,:)
120      ztla(:,:)=zthl(:,:)
121      zqta(:,:)=po(:,:)
122      zqla(:,:)=0.
123      zha(:,:) = ztva(:,:)
124else
125      ztva(:,:)=0.
126      ztv_est(:,:)=0.
127      ztva_est(:,:)=0.
128      ztla(:,:)=0.
129      zqta(:,:)=0.
130      zha(:,:) =0.
131endif
132
133      zqla_est(:,:)=0.
134      zqsatth(:,:)=0.
135      zqla(:,:)=0.
136      detr_star(:,:)=0.
137      entr_star(:,:)=0.
138      alim_star(:,:)=0.
139      alim_star_tot(:)=0.
140      csc(:,:)=0.
141      detr(:,:)=0.
142      entr(:,:)=0.
143      zw2(:,:)=0.
144      zbuoy(:,:)=0.
145      zbuoyjam(:,:)=0.
146      gamma(:,:)=0.
147      zeps(:,:)=0.
148      w_est(:,:)=0.
149      f_star(:,:)=0.
150      wa_moy(:,:)=0.
151      linter(:)=1.
152!     linter(:)=1.
153! Initialisation des variables entieres
154      lmix(:)=1
155      lmix_bis(:)=2
156      wmaxa(:)=0.
157
158
159!-------------------------------------------------------------------------
160! On ne considere comme actif que les colonnes dont les deux premieres
161! couches sont instables.
162!-------------------------------------------------------------------------
163
164      active(:)=ztv(:,1)>ztv(:,2)
165      d_temp(:)=0. ! Pour activer un contraste de temperature a la base
166                   ! du panache
167!  Cet appel pourrait être fait avant thermcell_plume dans thermcell_main
168      CALL thermcell_alim(thermals_flag_alim,ngrid,klev,ztv,d_temp,zlev,alim_star,lalim)
169
170!------------------------------------------------------------------------------
171! Calcul dans la premiere couche
172! On decide dans cette version que le thermique n'est actif que si la premiere
173! couche est instable.
174! Pourrait etre change si on veut que le thermiques puisse se d??clencher
175! dans une couche l>1
176!------------------------------------------------------------------------------
177do ig=1,ngrid
178! Le panache va prendre au debut les caracteristiques de l'air contenu
179! dans cette couche.
180    if (active(ig)) then
181    ztla(ig,1)=zthl(ig,1)
182    zqta(ig,1)=po(ig,1)
183    zqla(ig,1)=zl(ig,1)
184!cr: attention, prise en compte de f*(1)=1
185    f_star(ig,2)=alim_star(ig,1)
186    zw2(ig,2)=2.*RG*(ztv(ig,1)-ztv(ig,2))/ztv(ig,2)  &
187&                     *(zlev(ig,2)-zlev(ig,1))  &
188&                     *0.4*pphi(ig,1)/(pphi(ig,2)-pphi(ig,1))
189    w_est(ig,2)=zw2(ig,2)
190    endif
191enddo
192!
193
194!==============================================================================
195!boucle de calcul de la vitesse verticale dans le thermique
196!==============================================================================
197do l=2,klev-1
198!==============================================================================
199
200
201! On decide si le thermique est encore actif ou non
202! AFaire : Il faut sans doute ajouter entr_star a alim_star dans ce test
203    do ig=1,ngrid
204       active(ig)=active(ig) &
205&                 .and. zw2(ig,l)>1.e-10 &
206&                 .and. f_star(ig,l)+alim_star(ig,l)>1.e-10
207    enddo
208
209
210
211!---------------------------------------------------------------------------
212! calcul des proprietes thermodynamiques et de la vitesse de la couche l
213! sans tenir compte du detrainement et de l'entrainement dans cette
214! couche
215! C'est a dire qu'on suppose
216! ztla(l)=ztla(l-1) et zqta(l)=zqta(l-1)
217! Ici encore, on doit pouvoir ajouter entr_star (qui peut etre calculer
218! avant) a l'alimentation pour avoir un calcul plus propre
219!---------------------------------------------------------------------------
220
221   ztemp(:)=zpspsk(:,l)*ztla(:,l-1)
222   call thermcell_qsat(ngrid,active,pplev(:,l),ztemp,zqta(:,l-1),zqsat(:))
223    do ig=1,ngrid
224!       print*,'active',active(ig),ig,l
225        if(active(ig)) then
226        zqla_est(ig,l)=max(0.,zqta(ig,l-1)-zqsat(ig))
227        ztva_est(ig,l) = ztla(ig,l-1)*zpspsk(ig,l)+RLvCp*zqla_est(ig,l)
228        zta_est(ig,l)=ztva_est(ig,l)
229        ztva_est(ig,l) = ztva_est(ig,l)/zpspsk(ig,l)
230        ztva_est(ig,l) = ztva_est(ig,l)*(1.+RETV*(zqta(ig,l-1)  &
231     &      -zqla_est(ig,l))-zqla_est(ig,l))
232 
233
234!Modif AJAM
235
236        zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
237        zdz=zlev(ig,l+1)-zlev(ig,l)         
238        lmel=fact_thermals_ed_dz*zlev(ig,l)
239!        lmel=0.09*zlev(ig,l)
240        zlmel=zlev(ig,l)+lmel
241        zlmelup=zlmel+(zdz/2)
242        zlmeldwn=zlmel-(zdz/2)
243
244        lt=l+1
245        zlt=zlev(ig,lt)
246        zdz3=zlev(ig,lt+1)-zlt
247        zltdwn=zlt-zdz3/2
248        zltup=zlt+zdz3/2
249         
250!=========================================================================
251! 3. Calcul de la flotabilite modifie par melange avec l'air au dessus
252!=========================================================================
253
254!--------------------------------------------------
255        lt=l+1
256        zlt=zlev(ig,lt)
257        zdz2=zlev(ig,lt)-zlev(ig,l)
258
259        do while (lmel.gt.zdz2)
260           lt=lt+1
261           zlt=zlev(ig,lt)
262           zdz2=zlt-zlev(ig,l)
263        enddo
264        zdz3=zlev(ig,lt+1)-zlt
265        zltdwn=zlev(ig,lt)-zdz3/2
266        zlmelup=zlmel+(zdz/2)
267        coefzlmel=Min(1.,(zlmelup-zltdwn)/zdz)
268        zbuoyjam(ig,l)=1.*RG*(coefzlmel*(ztva_est(ig,l)- &
269    &   ztv(ig,lt))/ztv(ig,lt)+(1.-coefzlmel)*(ztva_est(ig,l)- &
270    &   ztv(ig,lt-1))/ztv(ig,lt-1))+0.*zbuoy(ig,l)
271
272!------------------------------------------------
273!AJAM:nouveau calcul de w? 
274!------------------------------------------------
275        zdz=zlev(ig,l+1)-zlev(ig,l)
276        zdzbis=zlev(ig,l)-zlev(ig,l-1)
277        zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
278        zw2fact=fact_epsilon*2.*zdz/(1.+betalpha)
279        zw2factbis=fact_epsilon*2.*zdzbis/(1.+betalpha)
280        zdw2=afact*zbuoy(ig,l)/fact_epsilon
281        zdw2bis=afact*zbuoy(ig,l-1)/fact_epsilon
282        lm=Max(1,l-2)
283        w_est(ig,l+1)=Max(0.0001,exp(-zw2fact)*(w_est(ig,l)-zdw2)+zdw2)
284       endif
285    enddo
286
287
288!-------------------------------------------------
289!calcul des taux d'entrainement et de detrainement
290!-------------------------------------------------
291
292     do ig=1,ngrid
293        if (active(ig)) then
294
295!          zw2m=max(0.5*(w_est(ig,l)+w_est(ig,l+1)),0.1)
296          zw2m=w_est(ig,l+1)
297          zdz=zlev(ig,l+1)-zlev(ig,l)
298          zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
299          zalpha=f0(ig)*f_star(ig,l)/sqrt(w_est(ig,l+1))/rhobarz(ig,l)
300          zdqt(ig,l)=max(zqta(ig,l-1)-po(ig,l),0.)/po(ig,l)
301
302!=========================================================================
303! 4. Calcul de l'entrainement et du detrainement
304!=========================================================================
305
306          detr_star(ig,l)=f_star(ig,l)*zdz             &
307    &     *( mix0 * 0.1 / (zalpha+0.001)               &
308    &     + MAX(detr_min, -afact*zbetalpha*zbuoyjam(ig,l)/zw2m   &
309    &     + detr_q_coef*(zdqt(ig,l)/zw2m)**detr_q_power))
310
311          if ( iflag_thermals_ed == 20 ) then
312             entr_star(ig,l)=f_star(ig,l)*zdz* (         &
313    &          mix0 * 0.1 / (zalpha+0.001)               &
314    &        + zbetalpha*MAX(entr_min,                   &
315    &        afact*zbuoyjam(ig,l)/zw2m - fact_epsilon))
316          else
317             entr_star(ig,l)=f_star(ig,l)*zdz* (         &
318    &          mix0 * 0.1 / (zalpha+0.001)               &
319    &        + zbetalpha*MAX(entr_min,                   &
320    &        afact*zbuoy(ig,l)/zw2m - fact_epsilon))
321          endif
322         
323! En dessous de lalim, on prend le max de alim_star et entr_star pour
324! alim_star et 0 sinon
325        if (l.lt.lalim(ig)) then
326          alim_star(ig,l)=max(alim_star(ig,l),entr_star(ig,l))
327          entr_star(ig,l)=0.
328        endif
329        f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
330     &              -detr_star(ig,l)
331
332      endif
333   enddo
334
335
336!============================================================================
337! 5. calcul de la vitesse verticale en melangeant Tl et qt du thermique
338!===========================================================================
339
340   activetmp(:)=active(:) .and. f_star(:,l+1)>1.e-10
341   do ig=1,ngrid
342       if (activetmp(ig)) then
343           Zsat=.false.
344           ztla(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
345     &            (alim_star(ig,l)+entr_star(ig,l))*zthl(ig,l))  &
346     &            /(f_star(ig,l+1)+detr_star(ig,l))
347           zqta(ig,l)=(f_star(ig,l)*zqta(ig,l-1)+  &
348     &            (alim_star(ig,l)+entr_star(ig,l))*po(ig,l))  &
349     &            /(f_star(ig,l+1)+detr_star(ig,l))
350
351        endif
352    enddo
353
354   ztemp(:)=zpspsk(:,l)*ztla(:,l)
355   call thermcell_qsat(ngrid,activetmp,pplev(:,l),ztemp,zqta(:,l),zqsatth(:,l))
356   do ig=1,ngrid
357      if (activetmp(ig)) then
358! on ecrit de maniere conservative (sat ou non)
359!          T = Tl +Lv/Cp ql
360           zqla(ig,l)=max(0.,zqta(ig,l)-zqsatth(ig,l))
361           ztva(ig,l) = ztla(ig,l)*zpspsk(ig,l)+RLvCp*zqla(ig,l)
362           ztva(ig,l) = ztva(ig,l)/zpspsk(ig,l)
363!on rajoute le calcul de zha pour diagnostiques (temp potentielle)
364           zha(ig,l) = ztva(ig,l)
365           ztva(ig,l) = ztva(ig,l)*(1.+RETV*(zqta(ig,l)  &
366     &              -zqla(ig,l))-zqla(ig,l))
367           zbuoy(ig,l)=RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
368           zdz=zlev(ig,l+1)-zlev(ig,l)
369           zdzbis=zlev(ig,l)-zlev(ig,l-1)
370           zeps(ig,l)=(entr_star(ig,l)+alim_star(ig,l))/(f_star(ig,l)*zdz)
371           zw2fact=fact_epsilon*2.*zdz/(1.+betalpha)
372           zw2factbis=fact_epsilon*2.*zdzbis/(1.+betalpha)
373           zdw2= afact*zbuoy(ig,l)/(fact_epsilon)
374           zdw2bis= afact*zbuoy(ig,l-1)/(fact_epsilon)
375           zw2(ig,l+1)=Max(0.0001,exp(-zw2fact)*(zw2(ig,l)-zdw2)+zdw2)
376      endif
377   enddo
378
379   if (prt_level.ge.20) print*,'coucou calcul detr 460: ig, l',ig, l
380!
381!===========================================================================
382! 6. initialisations pour le calcul de la hauteur du thermique, de l'inversion et de la vitesse verticale max
383!===========================================================================
384
385   nbpb=0
386   do ig=1,ngrid
387            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
388!               stop'On tombe sur le cas particulier de thermcell_dry'
389!               print*,'On tombe sur le cas particulier de thermcell_plume'
390                nbpb=nbpb+1
391                zw2(ig,l+1)=0.
392                linter(ig)=l+1
393            endif
394
395        if (zw2(ig,l+1).lt.0.) then
396           linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
397     &               -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
398           zw2(ig,l+1)=0.
399!+CR:04/05/12:correction calcul linter pour calcul de zmax continu
400        elseif (f_star(ig,l+1).lt.0.) then
401           linter(ig)=(l*(f_star(ig,l+1)-f_star(ig,l))  &
402     &               -f_star(ig,l))/(f_star(ig,l+1)-f_star(ig,l))
403           zw2(ig,l+1)=0.
404!fin CR:04/05/12
405        endif
406
407           wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
408
409        if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
410!   lmix est le niveau de la couche ou w (wa_moy) est maximum
411!on rajoute le calcul de lmix_bis
412            if (zqla(ig,l).lt.1.e-10) then
413               lmix_bis(ig)=l+1
414            endif
415            lmix(ig)=l+1
416            wmaxa(ig)=wa_moy(ig,l+1)
417        endif
418   enddo
419
420   if (nbpb>0) then
421   print*,'WARNING on tombe ',nbpb,' x sur un pb pour l=',l,' dans thermcell_plume'
422   endif
423
424!=========================================================================
425! FIN DE LA BOUCLE VERTICALE
426      enddo
427!=========================================================================
428
429!on recalcule alim_star_tot
430       do ig=1,ngrid
431          alim_star_tot(ig)=0.
432       enddo
433       do ig=1,ngrid
434          do l=1,lalim(ig)-1
435          alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
436          enddo
437       enddo
438       
439
440        if (prt_level.ge.20) print*,'coucou calcul detr 470: ig, l', ig, l
441
442#undef wrgrads_thermcell
443#ifdef wrgrads_thermcell
444         call wrgradsfi(1,klev,entr_star(igout,1:klev),'esta      ','esta      ')
445         call wrgradsfi(1,klev,detr_star(igout,1:klev),'dsta      ','dsta      ')
446         call wrgradsfi(1,klev,zbuoy(igout,1:klev),'buoy      ','buoy      ')
447         call wrgradsfi(1,klev,zdqt(igout,1:klev),'dqt      ','dqt      ')
448         call wrgradsfi(1,klev,w_est(igout,1:klev),'w_est     ','w_est     ')
449         call wrgradsfi(1,klev,w_est(igout,2:klev+1),'w_es2     ','w_es2     ')
450         call wrgradsfi(1,klev,zw2(igout,1:klev),'zw2A      ','zw2A      ')
451#endif
452
453
454     return
455     end
Note: See TracBrowser for help on using the repository browser.