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

Last change on this file since 3043 was 3036, checked in by fhourdin, 7 years ago

passage de getin a getin_p et supression des
variables _omp qui n'etaient pas en THREADPRIVATE.

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