source: LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/thermcell_plume.F90 @ 1338

Last change on this file since 1338 was 1338, checked in by idelkadi, 14 years ago

Nouvelle version des thermiques

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 29.3 KB
Line 
1!
2! $Id: thermcell_plume.F90 1338 2010-04-06 12:49:00Z idelkadi $
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
10!--------------------------------------------------------------------------
11!thermcell_plume: calcule les valeurs de qt, thetal et w dans l ascendance
12!--------------------------------------------------------------------------
13
14      IMPLICIT NONE
15
16#include "YOMCST.h"
17#include "YOETHF.h"
18#include "FCTTRE.h"
19#include "iniprint.h"
20#include "thermcell.h"
21
22      INTEGER itap
23      INTEGER lunout1,igout
24      INTEGER ngrid,klev
25      REAL ptimestep
26      REAL ztv(ngrid,klev)
27      REAL zthl(ngrid,klev)
28      REAL po(ngrid,klev)
29      REAL zl(ngrid,klev)
30      REAL rhobarz(ngrid,klev)
31      REAL zlev(ngrid,klev+1)
32      REAL pplev(ngrid,klev+1)
33      REAL pphi(ngrid,klev)
34      REAL zpspsk(ngrid,klev)
35      REAL alim_star(ngrid,klev)
36      REAL f0(ngrid)
37      INTEGER lalim(ngrid)
38      integer lev_out                           ! niveau pour les print
39      real zcon2(ngrid)
40   
41      real alim_star_tot(ngrid)
42
43      REAL ztva(ngrid,klev)
44      REAL ztla(ngrid,klev)
45      REAL zqla(ngrid,klev)
46      REAL zqta(ngrid,klev)
47      REAL zha(ngrid,klev)
48
49      REAL detr_star(ngrid,klev)
50      REAL coefc
51      REAL entr_star(ngrid,klev)
52      REAL detr(ngrid,klev)
53      REAL entr(ngrid,klev)
54
55      REAL csc(ngrid,klev)
56
57      REAL zw2(ngrid,klev+1)
58      REAL w_est(ngrid,klev+1)
59      REAL f_star(ngrid,klev+1)
60      REAL wa_moy(ngrid,klev+1)
61
62      REAL ztva_est(ngrid,klev)
63      REAL zqla_est(ngrid,klev)
64      REAL zqsatth(ngrid,klev)
65      REAL zta_est(ngrid,klev)
66      REAL ztemp(ngrid),zqsat(ngrid)
67      REAL zdw2
68      REAL zw2modif
69      REAL zeps
70
71      REAL linter(ngrid)
72      INTEGER lmix(ngrid)
73      INTEGER lmix_bis(ngrid)
74      REAL    wmaxa(ngrid)
75
76      INTEGER ig,l,k
77
78      real zdz,zfact,zbuoy,zalpha
79      real zcor,zdelta,zcvm5,qlbef
80      REAL REPS,RLvCp,DDT0
81      PARAMETER (DDT0=.01)
82      logical Zsat
83      LOGICAL active(ngrid),activetmp(ngrid)
84      REAL fact_gamma,fact_epsilon,fact_gamma2
85      REAL c2(ngrid,klev)
86
87      REAL zw2fact,expa
88      Zsat=.false.
89! Initialisation
90      RLvCp = RLVTT/RCPD
91     
92      if (iflag_thermals_ed==0) then
93         fact_gamma=1.
94         fact_epsilon=1.
95      else if (iflag_thermals_ed==1)  then
96! Valeurs au moment de la premiere soumission des papiers
97         fact_gamma=1.
98         fact_epsilon=0.002
99         fact_gamma2=0.6
100! Suggestions des Fleurs, Septembre 2009
101         fact_epsilon=0.015
102!test cr
103!         fact_epsilon=0.002
104         fact_gamma=0.9
105         fact_gamma2=0.7
106
107      else if (iflag_thermals_ed==2)  then
108         fact_gamma=1.
109         fact_epsilon=2.
110      else if (iflag_thermals_ed==3)  then
111         fact_gamma=3./4.
112         fact_epsilon=3.
113      endif
114
115!      write(lunout,*)'THERM 31H '
116
117      print*,'THERMCELL_PLUME OPTIMISE V0 '
118! Initialisations des variables reeles
119if (1==0) then
120      ztva(:,:)=ztv(:,:)
121      ztva_est(:,:)=ztva(:,:)
122      ztla(:,:)=zthl(:,:)
123      zqta(:,:)=po(:,:)
124      zha(:,:) = ztva(:,:)
125else
126      ztva(:,:)=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      w_est(:,:)=0.
145      f_star(:,:)=0.
146      wa_moy(:,:)=0.
147      linter(:)=1.
148      linter(:)=1.
149
150! Initialisation des variables entieres
151      lmix(:)=1
152      lmix_bis(:)=2
153      wmaxa(:)=0.
154      lalim(:)=1
155
156!-------------------------------------------------------------------------
157! On ne considere comme actif que les colonnes dont les deux premieres
158! couches sont instables.
159!-------------------------------------------------------------------------
160      active(:)=ztv(:,1)>ztv(:,2)
161
162!-------------------------------------------------------------------------
163! Definition de l'alimentation a l'origine dans thermcell_init
164!-------------------------------------------------------------------------
165      do l=1,klev-1
166         do ig=1,ngrid
167            if (ztv(ig,l)> ztv(ig,l+1) .and. ztv(ig,1)>=ztv(ig,l) ) then
168               alim_star(ig,l)=MAX((ztv(ig,l)-ztv(ig,l+1)),0.)  &
169     &                       *sqrt(zlev(ig,l+1))
170               lalim(:)=l+1
171               alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
172            endif
173         enddo
174      enddo
175      do l=1,klev
176         do ig=1,ngrid
177            if (alim_star_tot(ig) > 1.e-10 ) then
178               alim_star(ig,l)=alim_star(ig,l)/alim_star_tot(ig)
179            endif
180         enddo
181      enddo
182      alim_star_tot(:)=1.
183
184
185!------------------------------------------------------------------------------
186! Calcul dans la premiere couche
187! On decide dans cette version que le thermique n'est actif que si la premiere
188! couche est instable.
189! Pourrait etre change si on veut que le thermiques puisse se déclencher
190! dans une couche l>1
191!------------------------------------------------------------------------------
192do ig=1,ngrid
193! Le panache va prendre au debut les caracteristiques de l'air contenu
194! dans cette couche.
195    if (active(ig)) then
196    ztla(ig,1)=zthl(ig,1)
197    zqta(ig,1)=po(ig,1)
198    zqla(ig,1)=zl(ig,1)
199!cr: attention, prise en compte de f*(1)=1
200    f_star(ig,2)=alim_star(ig,1)
201    zw2(ig,2)=2.*RG*(ztv(ig,1)-ztv(ig,2))/ztv(ig,2)  &
202&                     *(zlev(ig,2)-zlev(ig,1))  &
203&                     *0.4*pphi(ig,1)/(pphi(ig,2)-pphi(ig,1))
204    w_est(ig,2)=zw2(ig,2)
205    endif
206enddo
207!
208
209!==============================================================================
210!boucle de calcul de la vitesse verticale dans le thermique
211!==============================================================================
212do l=2,klev-1
213!==============================================================================
214
215
216! On decide si le thermique est encore actif ou non
217! AFaire : Il faut sans doute ajouter entr_star a alim_star dans ce test
218    do ig=1,ngrid
219       active(ig)=active(ig) &
220&                 .and. zw2(ig,l)>1.e-10 &
221&                 .and. f_star(ig,l)+alim_star(ig,l)>1.e-10
222    enddo
223
224
225
226! Premier calcul de la vitesse verticale a partir de la temperature
227! potentielle virtuelle
228!     if (1.eq.1) then
229!         w_est(ig,3)=zw2(ig,2)* &
230!    &      ((f_star(ig,2))**2) &
231!    &      /(f_star(ig,2)+alim_star(ig,2))**2+ &
232!    &      2.*RG*(ztva(ig,2)-ztv(ig,2))/ztv(ig,2) &
233!    &      *(zlev(ig,3)-zlev(ig,2))
234!      endif
235
236
237!---------------------------------------------------------------------------
238! calcul des proprietes thermodynamiques et de la vitesse de la couche l
239! sans tenir compte du detrainement et de l'entrainement dans cette
240! couche
241! C'est a dire qu'on suppose
242! ztla(l)=ztla(l-1) et zqta(l)=zqta(l-1)
243! Ici encore, on doit pouvoir ajouter entr_star (qui peut etre calculer
244! avant) a l'alimentation pour avoir un calcul plus propre
245!---------------------------------------------------------------------------
246
247   ztemp(:)=zpspsk(:,l)*ztla(:,l-1)
248   call thermcell_qsat(ngrid,active,pplev(:,l),ztemp,zqta(:,l-1),zqsat)
249
250
251    do ig=1,ngrid
252        if(active(ig)) then
253        zqla_est(ig,l) = max(0.,zqta(ig,l-1)-zqsat(ig))
254        ztva_est(ig,l) = ztla(ig,l-1)*zpspsk(ig,l)+RLvCp*zqla_est(ig,l)
255        zta_est(ig,l)=ztva_est(ig,l)
256        ztva_est(ig,l) = ztva_est(ig,l)/zpspsk(ig,l)
257        ztva_est(ig,l) = ztva_est(ig,l)*(1.+RETV*(zqta(ig,l-1)  &
258     &      -zqla_est(ig,l))-zqla_est(ig,l))
259
260             w_est(ig,l+1)=zw2(ig,l)*  &
261     &                   ((f_star(ig,l))**2)  &
262     &                   /(f_star(ig,l)+alim_star(ig,l))**2+  &
263     &                   2.*RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)  &
264     &                   *(zlev(ig,l+1)-zlev(ig,l))
265             if (w_est(ig,l+1).lt.0.) then
266                w_est(ig,l+1)=zw2(ig,l)
267             endif
268       endif
269    enddo
270
271!-------------------------------------------------
272!calcul des taux d'entrainement et de detrainement
273!-------------------------------------------------
274
275     do ig=1,ngrid
276        if (active(ig)) then
277          zdz=zlev(ig,l+1)-zlev(ig,l)
278          zbuoy=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
279          zfact=fact_gamma/(1.+fact_gamma)
280 
281! estimation de la fraction couverte par les thermiques
282          zalpha=f0(ig)*f_star(ig,l)/sqrt(w_est(ig,l))/rhobarz(ig,l)
283
284!calcul de la soumission papier
285          if (1.eq.1) then
286             fact_epsilon=0.0007
287!             zfact=0.9/(1.+0.9)
288             zfact=0.3
289             fact_gamma=0.7
290             fact_gamma2=0.6
291             expa=0.25
292! Calcul  du taux d'entrainement entr_star (epsilon)
293           entr_star(ig,l)=f_star(ig,l)*zdz * (  zfact * MAX(0.,  &     
294     &     zbuoy/w_est(ig,l+1) )&
295!- fact_epsilon/zalpha**0.25  ) &
296     &     +0.000 )
297
298!           entr_star(ig,l)=f_star(ig,l)*zdz * (  1./3 * MAX(0.,  &     
299!     &     zbuoy/w_est(ig,l+1) - 1./zalpha**0.25  ) &
300!     &     +0.000 )
301! Calcul du taux de detrainement detr_star (delta)
302!           if (zqla_est(ig,l).lt.1.e-10) then
303!           detr_star(ig,l)=f_star(ig,l)*zdz * (                           &
304!     &     fact_gamma2 * MAX(0.,fact_epsilon-zbuoy/w_est(ig,l+1) )       &
305!     &     +0.0006 )
306!           else
307!           detr_star(ig,l)=f_star(ig,l)*zdz * (                           &
308!     &     fact_gamma2 * MAX(0.,fact_epsilon-zbuoy/w_est(ig,l+1) )       &
309!     &     +0.002 )
310!           endif
311           detr_star(ig,l)=f_star(ig,l)*zdz * (                           &
312     &     fact_gamma2 * MAX(0., &
313!fact_epsilon/zalpha**0.25
314     &      -zbuoy/w_est(ig,l+1) )       &
315!     &     + 0.002*(max(zqta(ig,l-1)-po(ig,l),0.)/po(ig,l))**0.6  &
316!test
317     &     +  0.006*(max(zqta(ig,l-1)-po(ig,l),0.)/po(ig,l))**0.6  &   
318     &     +0.0000 )
319          else
320
321! Calcul  du taux d'entrainement entr_star (epsilon)
322           entr_star(ig,l)=f_star(ig,l)*zdz * (  zfact * MAX(0.,  &     
323     &     zbuoy/w_est(ig,l+1) - fact_epsilon  ) &
324     &     +0.0000 )
325
326! Calcul du taux de detrainement detr_star (delta)
327           detr_star(ig,l)=f_star(ig,l)*zdz * (                           &
328     &     fact_gamma2 * MAX(0.,fact_epsilon-zbuoy/w_est(ig,l+1) )       &
329     &     + 0.002*(max(zqta(ig,l-1)-po(ig,l),0.)/po(ig,l))**0.6  &
330     &     +0.0000 )
331
332          endif
333!endif choix du calcul de E* et D*
334
335!cr test
336!           entr_star(ig,l)=entr_star(ig,l)+0.2*detr_star(ig,l)     
337
338! Prise en compte de la fraction
339!      detr_star(ig,l)=detr_star(ig,l)*sqrt(0.01/max(zalpha,1.e-5))
340
341! En dessous de lalim, on prend le max de alim_star et entr_star pour
342! alim_star et 0 sinon
343        if (l.lt.lalim(ig)) then
344          alim_star(ig,l)=max(alim_star(ig,l),entr_star(ig,l))
345          entr_star(ig,l)=0.
346        endif
347
348! Calcul du flux montant normalise
349      f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
350     &              -detr_star(ig,l)
351
352      endif
353   enddo
354
355!----------------------------------------------------------------------------
356!calcul de la vitesse verticale en melangeant Tl et qt du thermique
357!---------------------------------------------------------------------------
358   activetmp(:)=active(:) .and. f_star(:,l+1)>1.e-10
359   do ig=1,ngrid
360       if (activetmp(ig)) then
361           Zsat=.false.
362           ztla(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
363     &            (alim_star(ig,l)+entr_star(ig,l))*zthl(ig,l))  &
364     &            /(f_star(ig,l+1)+detr_star(ig,l))
365           zqta(ig,l)=(f_star(ig,l)*zqta(ig,l-1)+  &
366     &            (alim_star(ig,l)+entr_star(ig,l))*po(ig,l))  &
367     &            /(f_star(ig,l+1)+detr_star(ig,l))
368
369        endif
370    enddo
371
372   ztemp(:)=zpspsk(:,l)*ztla(:,l)
373   call thermcell_qsat(ngrid,activetmp,pplev(:,l),ztemp,zqta(:,l),zqsatth(:,l))
374
375   do ig=1,ngrid
376      if (activetmp(ig)) then
377        if (prt_level.ge.20) print*,'coucou calcul detr 4512: ig, l', ig, l
378! on ecrit de maniere conservative (sat ou non)
379           zqla(ig,l) = max(0.,zqta(ig,l)-zqsatth(ig,l))
380!          T = Tl +Lv/Cp ql
381           ztva(ig,l) = ztla(ig,l)*zpspsk(ig,l)+RLvCp*zqla(ig,l)
382           ztva(ig,l) = ztva(ig,l)/zpspsk(ig,l)
383!on rajoute le calcul de zha pour diagnostiques (temp potentielle)
384           zha(ig,l) = ztva(ig,l)
385           ztva(ig,l) = ztva(ig,l)*(1.+RETV*(zqta(ig,l)  &
386     &              -zqla(ig,l))-zqla(ig,l))
387
388!on ecrit zqsat
389
390!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
391!          zw2(ig,l+1)=&
392!     &                 zw2(ig,l)*(1-fact_epsilon/(1.+fact_gamma)*2.*(zlev(ig,l+1)-zlev(ig,l))) &
393!     &                 +2.*RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)  &
394!     &                 *1./(1.+fact_gamma) &
395!     &                 *(zlev(ig,l+1)-zlev(ig,l))
396!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
397! La meme en plus modulaire :
398           zbuoy=RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
399           zdz=zlev(ig,l+1)-zlev(ig,l)
400
401
402           zeps=(entr_star(ig,l)+alim_star(ig,l))/(f_star(ig,l)*zdz)
403
404if (1==0) then
405           zw2modif=zw2(ig,l)*(1-fact_epsilon/(1.+fact_gamma)*2.*zdz)
406           zdw2=2.*zbuoy/(1.+fact_gamma)*zdz
407           zw2(ig,l+1)=zw2modif+zdw2
408else
409! Tentative de reecriture de l'equation de w2. A reprendre ...
410!           zdw2=2*zdz*zbuoy
411!           zw2modif=zw2(ig,l)*(1.-2.*zdz*(zeps+fact_epsilon))
412!!!!!      zw2(ig,l+1)=(zw2(ig,l)+zdw2)/(1.+2.*zfactw2(ig,l))
413!formulation Arnaud
414!           zw2fact=zbuoy*zalpha**expa/fact_epsilon
415!           zw2(ig,l+1)=(zw2(ig,l)-zw2fact)*exp(-2.*fact_epsilon/(zalpha**expa*(1+fact_gamma))*zdz) &
416!      &    +zw2fact
417           if (zbuoy.gt.1.e-10) then
418           zw2fact=zbuoy*zalpha**expa/fact_epsilon*(fact_gamma-zfact)
419           zw2(ig,l+1)=(zw2(ig,l)-zw2fact)*exp(-2.*fact_epsilon/(zalpha**expa)*zdz) &
420      &    +zw2fact
421           else
422           zw2fact=zbuoy*zalpha**expa/fact_epsilon*(fact_gamma)
423           zw2(ig,l+1)=(zw2(ig,l)-zw2fact)*exp(-2.*fact_epsilon/(zalpha**expa)*zdz) &
424      &    +zw2fact
425
426           endif
427
428endif
429!           zw2(ig,l+1)=zw2modif+zdw2
430      endif
431   enddo
432
433        if (prt_level.ge.20) print*,'coucou calcul detr 460: ig, l',ig, l
434!
435!---------------------------------------------------------------------------
436!initialisations pour le calcul de la hauteur du thermique, de l'inversion et de la vitesse verticale max
437!---------------------------------------------------------------------------
438
439   do ig=1,ngrid
440            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
441!               stop'On tombe sur le cas particulier de thermcell_dry'
442                write(lunout,*)                                         &
443     &          'On tombe sur le cas particulier de thermcell_plume'
444                zw2(ig,l+1)=0.
445                linter(ig)=l+1
446            endif
447
448        if (zw2(ig,l+1).lt.0.) then
449           linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
450     &               -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
451           zw2(ig,l+1)=0.
452        endif
453
454           wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
455
456        if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
457!   lmix est le niveau de la couche ou w (wa_moy) est maximum
458!on rajoute le calcul de lmix_bis
459            if (zqla(ig,l).lt.1.e-10) then
460               lmix_bis(ig)=l+1
461            endif
462            lmix(ig)=l+1
463            wmaxa(ig)=wa_moy(ig,l+1)
464        endif
465   enddo
466
467!=========================================================================
468! FIN DE LA BOUCLE VERTICALE
469      enddo
470!=========================================================================
471
472!on recalcule alim_star_tot
473       do ig=1,ngrid
474          alim_star_tot(ig)=0.
475       enddo
476       do ig=1,ngrid
477          do l=1,lalim(ig)-1
478          alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
479          enddo
480       enddo
481       
482
483        if (prt_level.ge.20) print*,'coucou calcul detr 470: ig, l', ig, l
484
485!     print*,'thermcell_plume OK'
486
487      return
488      end
489
490
491!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
492!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
493!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
494!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
495!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
496!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
497 SUBROUTINE thermcellV1_plume(itap,ngrid,klev,ptimestep,ztv,zthl,po,zl,rhobarz,  &
498&           zlev,pplev,pphi,zpspsk,alim_star,alim_star_tot,  &
499&           lalim,f0,detr_star,entr_star,f_star,csc,ztva,  &
500&           ztla,zqla,zqta,zha,zw2,w_est,ztva_est,zqsatth,lmix,lmix_bis,linter &
501&           ,lev_out,lunout1,igout)
502
503!--------------------------------------------------------------------------
504!thermcell_plume: calcule les valeurs de qt, thetal et w dans l ascendance
505! Version conforme a l'article de Rio et al. 2010.
506! Code ecrit par Catherine Rio, Arnaud Jam et Frederic Hourdin
507!--------------------------------------------------------------------------
508
509      IMPLICIT NONE
510
511#include "YOMCST.h"
512#include "YOETHF.h"
513#include "FCTTRE.h"
514#include "iniprint.h"
515#include "thermcell.h"
516
517      INTEGER itap
518      INTEGER lunout1,igout
519      INTEGER ngrid,klev
520      REAL ptimestep
521      REAL ztv(ngrid,klev)
522      REAL zthl(ngrid,klev)
523      REAL po(ngrid,klev)
524      REAL zl(ngrid,klev)
525      REAL rhobarz(ngrid,klev)
526      REAL zlev(ngrid,klev+1)
527      REAL pplev(ngrid,klev+1)
528      REAL pphi(ngrid,klev)
529      REAL zpspsk(ngrid,klev)
530      REAL alim_star(ngrid,klev)
531      REAL f0(ngrid)
532      INTEGER lalim(ngrid)
533      integer lev_out                           ! niveau pour les print
534   
535      real alim_star_tot(ngrid)
536
537      REAL ztva(ngrid,klev)
538      REAL ztla(ngrid,klev)
539      REAL zqla(ngrid,klev)
540      REAL zqta(ngrid,klev)
541      REAL zha(ngrid,klev)
542
543      REAL detr_star(ngrid,klev)
544      REAL coefc
545      REAL entr_star(ngrid,klev)
546      REAL detr(ngrid,klev)
547      REAL entr(ngrid,klev)
548
549      REAL csc(ngrid,klev)
550
551      REAL zw2(ngrid,klev+1)
552      REAL w_est(ngrid,klev+1)
553      REAL f_star(ngrid,klev+1)
554      REAL wa_moy(ngrid,klev+1)
555
556      REAL ztva_est(ngrid,klev)
557      REAL zqla_est(ngrid,klev)
558      REAL zqsatth(ngrid,klev)
559      REAL zta_est(ngrid,klev)
560      REAL ztemp(ngrid),zqsat(ngrid)
561      REAL zdw2
562      REAL zw2modif
563      REAL zw2fact
564      REAL zeps(ngrid,klev)
565
566      REAL linter(ngrid)
567      INTEGER lmix(ngrid)
568      INTEGER lmix_bis(ngrid)
569      REAL    wmaxa(ngrid)
570
571      INTEGER ig,l,k
572
573      real zdz,zbuoy(ngrid,klev),zalpha,gamma(ngrid,klev),zdqt(ngrid,klev),zw2m
574      real zbuoybis
575      real zcor,zdelta,zcvm5,qlbef,zdz2
576      real betalpha,zbetalpha
577      real eps, afact
578      REAL REPS,RLvCp,DDT0
579      PARAMETER (DDT0=.01)
580      logical Zsat
581      LOGICAL active(ngrid),activetmp(ngrid)
582      REAL fact_gamma,fact_epsilon,fact_gamma2,fact_epsilon2
583      REAL c2(ngrid,klev)
584      Zsat=.false.
585! Initialisation
586
587      RLvCp = RLVTT/RCPD
588      fact_epsilon=0.002
589      betalpha=0.9
590      afact=2./3.           
591
592      zbetalpha=betalpha/(1.+betalpha)
593
594!      print*,'THERM 31B'
595      print*,'THERMCELL_PLUME OPTIMISE V1 CCC '
596
597! Initialisations des variables reeles
598if (1==0) then
599      ztva(:,:)=ztv(:,:)
600      ztva_est(:,:)=ztva(:,:)
601      ztla(:,:)=zthl(:,:)
602      zqta(:,:)=po(:,:)
603      zha(:,:) = ztva(:,:)
604else
605      ztva(:,:)=0.
606      ztva_est(:,:)=0.
607      ztla(:,:)=0.
608      zqta(:,:)=0.
609      zha(:,:) =0.
610endif
611
612      zqla_est(:,:)=0.
613      zqsatth(:,:)=0.
614      zqla(:,:)=0.
615      detr_star(:,:)=0.
616      entr_star(:,:)=0.
617      alim_star(:,:)=0.
618      alim_star_tot(:)=0.
619      csc(:,:)=0.
620      detr(:,:)=0.
621      entr(:,:)=0.
622      zw2(:,:)=0.
623      zbuoy(:,:)=0.
624      gamma(:,:)=0.
625      zeps(:,:)=0.
626      w_est(:,:)=0.
627      f_star(:,:)=0.
628      wa_moy(:,:)=0.
629      linter(:)=1.
630!     linter(:)=1.
631! Initialisation des variables entieres
632      lmix(:)=1
633      lmix_bis(:)=2
634      wmaxa(:)=0.
635      lalim(:)=1
636
637   print*,'THERMCELL PLUME QSAT2 NDDDDN'
638
639!-------------------------------------------------------------------------
640! On ne considere comme actif que les colonnes dont les deux premieres
641! couches sont instables.
642!-------------------------------------------------------------------------
643      active(:)=ztv(:,1)>ztv(:,2)
644
645!-------------------------------------------------------------------------
646! Definition de l'alimentation a l'origine dans thermcell_init
647!-------------------------------------------------------------------------
648      do l=1,klev-1
649         do ig=1,ngrid
650            if (ztv(ig,l)> ztv(ig,l+1) .and. ztv(ig,1)>=ztv(ig,l) ) then
651               alim_star(ig,l)=MAX((ztv(ig,l)-ztv(ig,l+1)),0.)  &
652     &                       *sqrt(zlev(ig,l+1))
653               lalim(:)=l+1
654               alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
655            endif
656         enddo
657      enddo
658      do l=1,klev
659         do ig=1,ngrid
660            if (alim_star_tot(ig) > 1.e-10 ) then
661               alim_star(ig,l)=alim_star(ig,l)/alim_star_tot(ig)
662            endif
663         enddo
664      enddo
665      alim_star_tot(:)=1.
666
667
668
669!------------------------------------------------------------------------------
670! Calcul dans la premiere couche
671! On decide dans cette version que le thermique n'est actif que si la premiere
672! couche est instable.
673! Pourrait etre change si on veut que le thermiques puisse se déclencher
674! dans une couche l>1
675!------------------------------------------------------------------------------
676do ig=1,ngrid
677! Le panache va prendre au debut les caracteristiques de l'air contenu
678! dans cette couche.
679    if (active(ig)) then
680    ztla(ig,1)=zthl(ig,1)
681    zqta(ig,1)=po(ig,1)
682    zqla(ig,1)=zl(ig,1)
683!cr: attention, prise en compte de f*(1)=1
684    f_star(ig,2)=alim_star(ig,1)
685    zw2(ig,2)=2.*RG*(ztv(ig,1)-ztv(ig,2))/ztv(ig,2)  &
686&                     *(zlev(ig,2)-zlev(ig,1))  &
687&                     *0.4*pphi(ig,1)/(pphi(ig,2)-pphi(ig,1))
688    w_est(ig,2)=zw2(ig,2)
689    endif
690enddo
691!
692
693!==============================================================================
694!boucle de calcul de la vitesse verticale dans le thermique
695!==============================================================================
696do l=2,klev-1
697!==============================================================================
698
699
700! On decide si le thermique est encore actif ou non
701! AFaire : Il faut sans doute ajouter entr_star a alim_star dans ce test
702    do ig=1,ngrid
703       active(ig)=active(ig) &
704&                 .and. zw2(ig,l)>1.e-10 &
705&                 .and. f_star(ig,l)+alim_star(ig,l)>1.e-10
706    enddo
707
708
709
710!---------------------------------------------------------------------------
711! calcul des proprietes thermodynamiques et de la vitesse de la couche l
712! sans tenir compte du detrainement et de l'entrainement dans cette
713! couche
714! C'est a dire qu'on suppose
715! ztla(l)=ztla(l-1) et zqta(l)=zqta(l-1)
716! Ici encore, on doit pouvoir ajouter entr_star (qui peut etre calculer
717! avant) a l'alimentation pour avoir un calcul plus propre
718!---------------------------------------------------------------------------
719
720   ztemp(:)=zpspsk(:,l)*ztla(:,l-1)
721   call thermcell_qsat(ngrid,active,pplev(:,l),ztemp,zqta(:,l-1),zqsat(:))
722
723    do ig=1,ngrid
724!       print*,'active',active(ig),ig,l
725        if(active(ig)) then
726        zqla_est(ig,l)=max(0.,zqta(ig,l-1)-zqsat(ig))
727        ztva_est(ig,l) = ztla(ig,l-1)*zpspsk(ig,l)+RLvCp*zqla_est(ig,l)
728        zta_est(ig,l)=ztva_est(ig,l)
729        ztva_est(ig,l) = ztva_est(ig,l)/zpspsk(ig,l)
730        ztva_est(ig,l) = ztva_est(ig,l)*(1.+RETV*(zqta(ig,l-1)  &
731     &      -zqla_est(ig,l))-zqla_est(ig,l))
732
733!------------------------------------------------
734!AJAM:nouveau calcul de w² 
735!------------------------------------------------
736              zdz=zlev(ig,l+1)-zlev(ig,l)
737              zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
738
739              zw2fact=fact_epsilon*2.*zdz/(1.+betalpha)
740              zdw2=(afact)*zbuoy(ig,l)/(fact_epsilon)
741              w_est(ig,l+1)=Max(0.0001,exp(-zw2fact)*(w_est(ig,l)-zdw2)+zdw2)
742 
743
744             if (w_est(ig,l+1).lt.0.) then
745                w_est(ig,l+1)=zw2(ig,l)
746             endif
747       endif
748    enddo
749
750
751!-------------------------------------------------
752!calcul des taux d'entrainement et de detrainement
753!-------------------------------------------------
754
755     print*,'THERM V1 SANS DQ'
756     do ig=1,ngrid
757        if (active(ig)) then
758
759          zw2m=max(0.5*(w_est(ig,l)+w_est(ig,l+1)),0.1)
760          zw2m=w_est(ig,l+1)
761          zdz=zlev(ig,l+1)-zlev(ig,l)
762          zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
763!          zbuoybis=zbuoy(ig,l)+RG*0.1/300.
764          zbuoybis=zbuoy(ig,l)
765          zalpha=f0(ig)*f_star(ig,l)/sqrt(w_est(ig,l+1))/rhobarz(ig,l)
766          zdqt(ig,l)=max(zqta(ig,l-1)-po(ig,l),0.)/po(ig,l)
767          zdqt(ig,l)=0.
768
769         
770          entr_star(ig,l)=f_star(ig,l)*zdz*  zbetalpha*MAX(0.,  &
771    &     afact*zbuoybis/zw2m - fact_epsilon )
772
773
774          detr_star(ig,l)=f_star(ig,l)*zdz                        &
775    &     *MAX(1.e-3, -afact*zbetalpha*zbuoy(ig,l)/zw2m          &
776    &     + 0.012*(zdqt(ig,l)/zw2m)**0.5 )
777         
778! En dessous de lalim, on prend le max de alim_star et entr_star pour
779! alim_star et 0 sinon
780        if (l.lt.lalim(ig)) then
781          alim_star(ig,l)=max(alim_star(ig,l),entr_star(ig,l))
782          entr_star(ig,l)=0.
783        endif
784
785! Calcul du flux montant normalise
786      f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
787     &              -detr_star(ig,l)
788
789      endif
790   enddo
791
792
793!----------------------------------------------------------------------------
794!calcul de la vitesse verticale en melangeant Tl et qt du thermique
795!---------------------------------------------------------------------------
796   activetmp(:)=active(:) .and. f_star(:,l+1)>1.e-10
797   do ig=1,ngrid
798       if (activetmp(ig)) then
799           Zsat=.false.
800           ztla(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
801     &            (alim_star(ig,l)+entr_star(ig,l))*zthl(ig,l))  &
802     &            /(f_star(ig,l+1)+detr_star(ig,l))
803           zqta(ig,l)=(f_star(ig,l)*zqta(ig,l-1)+  &
804     &            (alim_star(ig,l)+entr_star(ig,l))*po(ig,l))  &
805     &            /(f_star(ig,l+1)+detr_star(ig,l))
806
807        endif
808    enddo
809
810   ztemp(:)=zpspsk(:,l)*ztla(:,l)
811   call thermcell_qsat(ngrid,activetmp,pplev(:,l),ztemp,zqta(:,l),zqsatth(:,l))
812
813   do ig=1,ngrid
814      if (activetmp(ig)) then
815        if (prt_level.ge.20) print*,'coucou calcul detr 4512: ig, l', ig, l
816! on ecrit de maniere conservative (sat ou non)
817!          T = Tl +Lv/Cp ql
818           zqla(ig,l)=max(0.,zqta(ig,l)-zqsatth(ig,l))
819           ztva(ig,l) = ztla(ig,l)*zpspsk(ig,l)+RLvCp*zqla(ig,l)
820           ztva(ig,l) = ztva(ig,l)/zpspsk(ig,l)
821!on rajoute le calcul de zha pour diagnostiques (temp potentielle)
822           zha(ig,l) = ztva(ig,l)
823           ztva(ig,l) = ztva(ig,l)*(1.+RETV*(zqta(ig,l)  &
824     &              -zqla(ig,l))-zqla(ig,l))
825           zbuoy(ig,l)=RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
826           zdz=zlev(ig,l+1)-zlev(ig,l)
827           zeps(ig,l)=(entr_star(ig,l)+alim_star(ig,l))/(f_star(ig,l)*zdz)
828
829            zw2fact=fact_epsilon*2.*zdz/(1.+betalpha)
830            zdw2=afact*zbuoy(ig,l)/(fact_epsilon)
831            zw2(ig,l+1)=Max(0.0001,exp(-zw2fact)*(zw2(ig,l)-zdw2)+zdw2)
832      endif
833   enddo
834
835        if (prt_level.ge.20) print*,'coucou calcul detr 460: ig, l',ig, l
836!
837!---------------------------------------------------------------------------
838!initialisations pour le calcul de la hauteur du thermique, de l'inversion et de la vitesse verticale max
839!---------------------------------------------------------------------------
840
841   do ig=1,ngrid
842            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
843!               stop'On tombe sur le cas particulier de thermcell_dry'
844                print*,'On tombe sur le cas particulier de thermcell_plume'
845                zw2(ig,l+1)=0.
846                linter(ig)=l+1
847            endif
848
849        if (zw2(ig,l+1).lt.0.) then
850           linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
851     &               -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
852           zw2(ig,l+1)=0.
853        endif
854
855           wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
856
857        if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
858!   lmix est le niveau de la couche ou w (wa_moy) est maximum
859!on rajoute le calcul de lmix_bis
860            if (zqla(ig,l).lt.1.e-10) then
861               lmix_bis(ig)=l+1
862            endif
863            lmix(ig)=l+1
864            wmaxa(ig)=wa_moy(ig,l+1)
865        endif
866   enddo
867
868!=========================================================================
869! FIN DE LA BOUCLE VERTICALE
870      enddo
871!=========================================================================
872
873!      print*,'THERMCELL PLUME ARNAUD DEDANS 7'
874!on recalcule alim_star_tot
875       do ig=1,ngrid
876          alim_star_tot(ig)=0.
877       enddo
878       do ig=1,ngrid
879          do l=1,lalim(ig)-1
880          alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
881          enddo
882       enddo
883       
884
885        if (prt_level.ge.20) print*,'coucou calcul detr 470: ig, l', ig, l
886
887#undef wrgrads_thermcell
888#ifdef wrgrads_thermcell
889         call wrgradsfi(1,klev,entr_star(igout,1:klev),'esta      ','esta      ')
890         call wrgradsfi(1,klev,detr_star(igout,1:klev),'dsta      ','dsta      ')
891         call wrgradsfi(1,klev,zbuoy(igout,1:klev),'buoy      ','buoy      ')
892         call wrgradsfi(1,klev,zdqt(igout,1:klev),'dqt      ','dqt      ')
893         call wrgradsfi(1,klev,w_est(igout,1:klev),'w_est     ','w_est     ')
894         call wrgradsfi(1,klev,w_est(igout,2:klev+1),'w_es2     ','w_es2     ')
895         call wrgradsfi(1,klev,zw2(igout,1:klev),'zw2A      ','zw2A      ')
896#endif
897
898
899!      print*,'THERMCELL PLUME ARNAUD DEDANS 8'
900     return
901     end
902
Note: See TracBrowser for help on using the repository browser.