source: LMDZ4/trunk/libf/phytherm/thermcell_plume.F90 @ 815

Last change on this file since 815 was 814, checked in by Laurent Fairhead, 17 years ago

Rajout de la physique utilisant les thermiques FH
LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 11.4 KB
Line 
1      SUBROUTINE thermcell_plume(ngrid,klev,ztv,zthl,po,zl,rhobarz,  &
2     &           zlev,pplev,pphi,zpspsk,l_mix,r_aspect,alim_star,  &
3     &           lentr,zmax_sec,f0,detr_star,entr_star,f_star,ztva,  &
4     &           ztla,zqla,zqta,zha,zw2,zqsatth,lmix,linter,lev_out)
5
6!--------------------------------------------------------------------------
7!thermcell_plume: calcule les valeurs de qt, thetal et w dans l ascendance
8!--------------------------------------------------------------------------
9
10      IMPLICIT NONE
11
12#include "YOMCST.h"
13#include "YOETHF.h"
14#include "FCTTRE.h"
15
16      INTEGER ngrid,klev
17      REAL ztv(ngrid,klev)
18      REAL zthl(ngrid,klev)
19      REAL po(ngrid,klev)
20      REAL zl(ngrid,klev)
21      REAL rhobarz(ngrid,klev)
22      REAL zlev(ngrid,klev+1)
23      REAL pplev(ngrid,klev+1)
24      REAL pphi(ngrid,klev)
25      REAL zpspsk(ngrid,klev)
26      REAL alim_star(ngrid,klev)
27      REAL zmax_sec(ngrid)
28      REAL f0(ngrid)
29      REAL l_mix
30      REAL r_aspect
31      INTEGER lentr(ngrid)
32      integer lev_out                           ! niveau pour les print
33
34      REAL ztva(ngrid,klev)
35      REAL ztla(ngrid,klev)
36      REAL zqla(ngrid,klev)
37      REAL zqta(ngrid,klev)
38      REAL zha(ngrid,klev)
39
40      REAL detr_star(ngrid,klev)
41      REAL entr_star(ngrid,klev)
42      REAL detr(ngrid,klev)
43      REAL entr(ngrid,klev)
44
45      REAL zw2(ngrid,klev+1)
46      REAL w_est(ngrid,klev+1)
47      REAL f_star(ngrid,klev+1)
48      REAL wa_moy(ngrid,klev+1)
49
50      REAL ztva_est(ngrid,klev)
51      REAL zqla_est(ngrid,klev)
52      REAL zqsatth(ngrid,klev)
53
54      REAL linter(ngrid)
55      INTEGER lmix(ngrid)
56      REAL    wmaxa(ngrid)
57
58      INTEGER ig,l,k
59
60      real zcor,zdelta,zcvm5,qlbef
61      real Tbef,qsatbef
62      real dqsat_dT,DT,num,denom
63      REAL REPS,RLvCp,DDT0
64      PARAMETER (DDT0=.01)
65      logical Zsat
66
67      Zsat=.false.
68! Initialisation
69      RLvCp = RLVTT/RCPD
70     
71      do l=1,klev
72         do ig=1,ngrid
73            zqla_est(ig,l)=0.
74            ztva_est(ig,l)=ztva(ig,l)
75            zqsatth(ig,l)=0.
76         enddo
77      enddo
78
79!AM:initialisations du thermique
80      do k=1,klev
81         do ig=1,ngrid
82            ztva(ig,k)=ztv(ig,k)
83            ztla(ig,k)=zthl(ig,k)
84            zqla(ig,k)=0.
85            zqta(ig,k)=po(ig,k)
86         enddo
87      enddo
88      do k=1,klev
89        do ig=1,ngrid
90           detr_star(ig,k)=0.
91           entr_star(ig,k)=0.
92           detr(ig,k)=0.
93           entr(ig,k)=0.
94        enddo
95      enddo
96      if (lev_out.ge.1) print*,'7 OK convect8'
97      do k=1,klev+1
98         do ig=1,ngrid
99            zw2(ig,k)=0.
100            w_est(ig,k)=0.
101            f_star(ig,k)=0.
102            wa_moy(ig,k)=0.
103         enddo
104      enddo
105
106      if (lev_out.ge.1) print*,'8 OK convect8'
107      do ig=1,ngrid
108         linter(ig)=1.
109         lmix(ig)=1
110         wmaxa(ig)=0.
111      enddo
112
113!-----------------------------------------------------------------------------------
114!boucle de calcul de la vitesse verticale dans le thermique
115!-----------------------------------------------------------------------------------
116      do l=1,klev-1
117         do ig=1,ngrid
118            if (ztv(ig,l).gt.ztv(ig,l+1)  &
119     &         .and.alim_star(ig,l).gt.1.e-10  &
120     &         .and.zw2(ig,l).lt.1e-10) then
121               ztla(ig,l)=zthl(ig,l)
122               zqta(ig,l)=po(ig,l)
123               zqla(ig,l)=zl(ig,l)
124               f_star(ig,l+1)=alim_star(ig,l)
125               zw2(ig,l+1)=2.*RG*(ztv(ig,l)-ztv(ig,l+1))/ztv(ig,l+1)  &
126     &                     *(zlev(ig,l+1)-zlev(ig,l))  &
127     &                     *0.4*pphi(ig,l)/(pphi(ig,l+1)-pphi(ig,l))
128               w_est(ig,l+1)=zw2(ig,l+1)
129!
130            else if ((zw2(ig,l).ge.1e-10).and.  &
131     &         (f_star(ig,l)+alim_star(ig,l)).gt.1.e-10) then
132!estimation du detrainement a partir de la geometrie du pas precedent
133!tests sur la definition du detr
134!calcul de detr_star et entr_star
135                w_est(ig,3)=zw2(ig,2)*  &
136     &                   ((f_star(ig,2))**2)  &
137     &                   /(f_star(ig,2)+alim_star(ig,2))**2+  &
138     &                   2.*RG*(ztva(ig,1)-ztv(ig,2))/ztv(ig,2)  &
139     &                   *(zlev(ig,3)-zlev(ig,2))
140      if (l.gt.2) then
141!---------------------------------------------------------------------------
142!calcul de l entrainement et du detrainement lateral
143!---------------------------------------------------------------------------
144!
145!test:estimation de ztva_new_est sans entrainement
146               Tbef=ztla(ig,l-1)*zpspsk(ig,l)
147               zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
148               qsatbef= R2ES * FOEEW(Tbef,zdelta)/pplev(ig,l)
149               qsatbef=MIN(0.5,qsatbef)
150               zcor=1./(1.-retv*qsatbef)
151               qsatbef=qsatbef*zcor
152               Zsat = (max(0.,zqta(ig,l-1)-qsatbef) .gt. 1.e-10)
153               if (Zsat) then
154               qlbef=max(0.,zqta(ig,l-1)-qsatbef)
155               DT = 0.5*RLvCp*qlbef
156               do while (abs(DT).gt.DDT0)
157                 Tbef=Tbef+DT
158                 zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
159                 qsatbef= R2ES * FOEEW(Tbef,zdelta)/pplev(ig,l)
160                 qsatbef=MIN(0.5,qsatbef)
161                 zcor=1./(1.-retv*qsatbef)
162                 qsatbef=qsatbef*zcor
163                 qlbef=zqta(ig,l-1)-qsatbef
164
165                 zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
166                 zcvm5=R5LES*(1.-zdelta) + R5IES*zdelta
167                 zcor=1./(1.-retv*qsatbef)
168                 dqsat_dT=FOEDE(Tbef,zdelta,zcvm5,qsatbef,zcor)
169                 num=-Tbef+ztla(ig,l-1)*zpspsk(ig,l)+RLvCp*qlbef
170                 denom=1.+RLvCp*dqsat_dT
171                 DT=num/denom
172               enddo
173                 zqla_est(ig,l) = max(0.,zqta(ig,l-1)-qsatbef)
174               endif
175        ztva_est(ig,l) = ztla(ig,l-1)*zpspsk(ig,l)+RLvCp*zqla_est(ig,l)
176        ztva_est(ig,l) = ztva_est(ig,l)/zpspsk(ig,l)
177        ztva_est(ig,l) = ztva_est(ig,l)*(1.+RETV*(zqta(ig,l-1)  &
178     &      -zqla_est(ig,l))-zqla_est(ig,l))
179
180             w_est(ig,l+1)=zw2(ig,l)*  &
181     &                   ((f_star(ig,l))**2)  &
182     &                   /(f_star(ig,l)+alim_star(ig,l))**2+  &
183     &                   2.*RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)  &
184     &                   *(zlev(ig,l+1)-zlev(ig,l))
185             if (w_est(ig,l+1).lt.0.) then
186                w_est(ig,l+1)=zw2(ig,l)
187             endif
188!
189!calcul du detrainement
190          if ((w_est(ig,l+1).gt.w_est(ig,l)).and.  &
191     &       (zlev(ig,l+1).lt.zmax_sec(ig)).and.  &
192     &       (zqla(ig,l-1).lt.1.e-10)) then
193             detr_star(ig,l)=MAX(0.,(rhobarz(ig,l+1)  &
194     &       *sqrt(w_est(ig,l+1))*sqrt(l_mix*zlev(ig,l+1))  &
195     &       -rhobarz(ig,l)*sqrt(w_est(ig,l))*sqrt(l_mix*zlev(ig,l)))  &
196     &       /(r_aspect*zmax_sec(ig)))
197       if (lev_out.ge.20) print*,'coucou calcul detr 1'
198          else if ((zlev(ig,l+1).lt.zmax_sec(ig)).and.  &
199     &            (zqla(ig,l-1).lt.1.e-10)) then
200             detr_star(ig,l)=-f0(ig)*f_star(ig,lmix(ig))  &
201     &       /(rhobarz(ig,lmix(ig))*wmaxa(ig))*  &
202     &       (rhobarz(ig,l+1)*sqrt(w_est(ig,l+1))  &
203     &       *((zmax_sec(ig)-zlev(ig,l+1))/  &
204     &       ((zmax_sec(ig)-zlev(ig,lmix(ig)))))**2.  &
205     &       -rhobarz(ig,l)*sqrt(w_est(ig,l))  &
206     &       *((zmax_sec(ig)-zlev(ig,l))/  &
207     &       ((zmax_sec(ig)-zlev(ig,lmix(ig)))))**2.)
208        if (lev_out.ge.20) print*,'coucou calcul detr 2'
209          else
210             detr_star(ig,l)=0.002*f0(ig)*f_star(ig,l)  &
211     &                      *(zlev(ig,l+1)-zlev(ig,l))
212        if (lev_out.ge.20) print*,'coucou calcul detr 3'
213             
214          endif
215          detr_star(ig,l)=detr_star(ig,l)/f0(ig)
216!
217!calcul de entr_star
218!
219        if (detr_star(ig,l).gt.f_star(ig,l)) then
220           detr_star(ig,l)=f_star(ig,l)
221!a decommenter ou pas?
222!           entr_star(ig,l)=0.
223        endif
224
225! Deplacement du calcul de entr_star pour eviter d'avoir aussi
226! entr_star > fstar.
227! FH
228          entr_star(ig,l)=0.4*detr_star(ig,l)
229!
230      else
231         detr_star(ig,l)=0.
232         entr_star(ig,l)=0.
233      endif
234!pas d entrainement dans la couche alim
235      if ((l.lt.lentr(ig))) then
236           entr_star(ig,l)=0.
237      endif
238!
239!prise en compte du detrainement et de l entrainement dans le calcul du flux
240      f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
241     &              -detr_star(ig,l)
242
243!test sur le signe de f_star
244       if (f_star(ig,l+1).gt.1.e-10) then
245!----------------------------------------------------------------------------
246!calcul de la vitesse verticale en melangeant Tl et qt du thermique
247!---------------------------------------------------------------------------
248!
249       Zsat=.false.
250       ztla(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
251     &            (alim_star(ig,l)+entr_star(ig,l))*zthl(ig,l))  &
252     &            /(f_star(ig,l+1)+detr_star(ig,l))
253!
254       zqta(ig,l)=(f_star(ig,l)*zqta(ig,l-1)+  &
255     &            (alim_star(ig,l)+entr_star(ig,l))*po(ig,l))  &
256     &            /(f_star(ig,l+1)+detr_star(ig,l))
257
258               Tbef=ztla(ig,l)*zpspsk(ig,l)
259               zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
260               qsatbef= R2ES * FOEEW(Tbef,zdelta)/pplev(ig,l)               
261               qsatbef=MIN(0.5,qsatbef)
262               zcor=1./(1.-retv*qsatbef)
263               qsatbef=qsatbef*zcor
264               Zsat = (max(0.,zqta(ig,l)-qsatbef) .gt. 1.e-10)
265               if (Zsat) then
266               qlbef=max(0.,zqta(ig,l)-qsatbef)
267               DT = 0.5*RLvCp*qlbef
268               do while (abs(DT).gt.DDT0)
269                 Tbef=Tbef+DT
270                 zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
271                 qsatbef= R2ES * FOEEW(Tbef,zdelta)/pplev(ig,l)
272                 qsatbef=MIN(0.5,qsatbef)
273                 zcor=1./(1.-retv*qsatbef)
274                 qsatbef=qsatbef*zcor
275                 qlbef=zqta(ig,l)-qsatbef
276
277                 zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
278                 zcvm5=R5LES*(1.-zdelta) + R5IES*zdelta
279                 zcor=1./(1.-retv*qsatbef)
280                 dqsat_dT=FOEDE(Tbef,zdelta,zcvm5,qsatbef,zcor)
281                 num=-Tbef+ztla(ig,l)*zpspsk(ig,l)+RLvCp*qlbef
282                 denom=1.+RLvCp*dqsat_dT
283                 DT=num/denom
284              enddo
285                 zqla(ig,l) = max(0.,qlbef)
286              endif
287!   
288! on ecrit de maniere conservative (sat ou non)
289!          T = Tl +Lv/Cp ql
290           ztva(ig,l) = ztla(ig,l)*zpspsk(ig,l)+RLvCp*zqla(ig,l)
291           ztva(ig,l) = ztva(ig,l)/zpspsk(ig,l)
292!on rajoute le calcul de zha pour diagnostiques (temp potentielle)
293           zha(ig,l) = ztva(ig,l)
294           ztva(ig,l) = ztva(ig,l)*(1.+RETV*(zqta(ig,l)  &
295     &              -zqla(ig,l))-zqla(ig,l))
296
297!on ecrit zqsat
298           zqsatth(ig,l)=qsatbef 
299!calcul de vitesse
300           zw2(ig,l+1)=zw2(ig,l)*  &
301     &                 ((f_star(ig,l))**2)  &
302     &                 /(f_star(ig,l+1)+detr_star(ig,l))**2+             &
303     &                 2.*RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)  &
304     &                 *(zlev(ig,l+1)-zlev(ig,l))
305               
306            endif
307        endif
308!
309!initialisations pour le calcul de la hauteur du thermique, de l'inversion et de la vitesse verticale max
310        if (zw2(ig,l+1).lt.0.) then
311           linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
312     &               -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
313           zw2(ig,l+1)=0.
314        else
315           wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
316        endif
317        if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
318!   lmix est le niveau de la couche ou w (wa_moy) est maximum
319            lmix(ig)=l+1
320            wmaxa(ig)=wa_moy(ig,l+1)
321        endif
322        enddo
323      enddo
324
325
326      return
327      end
Note: See TracBrowser for help on using the repository browser.