source: LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/thermcellV0_main.F90 @ 1294

Last change on this file since 1294 was 1294, checked in by Laurent Fairhead, 15 years ago

Modifications pour la nouvelle version des thermiques (2009/2010) CR et FH

File size: 68.1 KB
Line 
1!
2! $Header$
3!
4      SUBROUTINE thermcellV0_main(itap,ngrid,nlay,ptimestep  &
5     &                  ,pplay,pplev,pphi,debut  &
6     &                  ,pu,pv,pt,po  &
7     &                  ,pduadj,pdvadj,pdtadj,pdoadj  &
8     &                  ,fm0,entr0,detr0,zqta,zqla,lmax  &
9     &                  ,ratqscth,ratqsdiff,zqsatth  &
10     &                  ,r_aspect,l_mix,tau_thermals &
11     &                  ,Ale_bl,Alp_bl,lalim_conv,wght_th &
12     &                  ,zmax0, f0,zw2,fraca)
13
14      USE dimphy
15      USE comgeomphy , ONLY:rlond,rlatd
16      IMPLICIT NONE
17
18!=======================================================================
19!   Auteurs: Frederic Hourdin, Catherine Rio, Anne Mathieu
20!   Version du 09.02.07
21!   Calcul du transport vertical dans la couche limite en presence
22!   de "thermiques" explicitement representes avec processus nuageux
23!
24!   Réécriture à partir d'un listing papier à Habas, le 14/02/00
25!
26!   le thermique est supposé homogène et dissipé par mélange avec
27!   son environnement. la longueur l_mix contrôle l'efficacité du
28!   mélange
29!
30!   Le calcul du transport des différentes espèces se fait en prenant
31!   en compte:
32!     1. un flux de masse montant
33!     2. un flux de masse descendant
34!     3. un entrainement
35!     4. un detrainement
36!
37!=======================================================================
38
39!-----------------------------------------------------------------------
40!   declarations:
41!   -------------
42
43#include "dimensions.h"
44#include "YOMCST.h"
45#include "YOETHF.h"
46#include "FCTTRE.h"
47#include "iniprint.h"
48
49!   arguments:
50!   ----------
51
52!IM 140508
53      INTEGER itap
54
55      INTEGER ngrid,nlay,w2di
56      real tau_thermals
57      real ptimestep,l_mix,r_aspect
58      REAL pt(ngrid,nlay),pdtadj(ngrid,nlay)
59      REAL pu(ngrid,nlay),pduadj(ngrid,nlay)
60      REAL pv(ngrid,nlay),pdvadj(ngrid,nlay)
61      REAL po(ngrid,nlay),pdoadj(ngrid,nlay)
62      REAL pplay(ngrid,nlay),pplev(ngrid,nlay+1)
63      real pphi(ngrid,nlay)
64
65!   local:
66!   ------
67
68      integer icount
69      data icount/0/
70      save icount
71!$OMP THREADPRIVATE(icount)
72
73      integer,save :: igout=1
74!$OMP THREADPRIVATE(igout)
75      integer,save :: lunout1=6
76!$OMP THREADPRIVATE(lunout1)
77      integer,save :: lev_out=10
78!$OMP THREADPRIVATE(lev_out)
79
80      INTEGER ig,k,l,ll
81      real zsortie1d(klon)
82      INTEGER lmax(klon),lmin(klon),lalim(klon)
83      INTEGER lmix(klon)
84      INTEGER lmix_bis(klon)
85      real linter(klon)
86      real zmix(klon)
87      real zmax(klon),zw2(klon,klev+1),ztva(klon,klev),zw_est(klon,klev+1)
88!      real fraca(klon,klev)
89
90      real zmax_sec(klon)
91!on garde le zmax du pas de temps precedent
92      real zmax0(klon)
93!FH/IM     save zmax0
94
95      real lambda
96
97      real zlev(klon,klev+1),zlay(klon,klev)
98      real deltaz(klon,klev)
99      REAL zh(klon,klev)
100      real zthl(klon,klev),zdthladj(klon,klev)
101      REAL ztv(klon,klev)
102      real zu(klon,klev),zv(klon,klev),zo(klon,klev)
103      real zl(klon,klev)
104      real zsortie(klon,klev)
105      real zva(klon,klev)
106      real zua(klon,klev)
107      real zoa(klon,klev)
108
109      real zta(klon,klev)
110      real zha(klon,klev)
111      real fraca(klon,klev+1)
112      real zf,zf2
113      real thetath2(klon,klev),wth2(klon,klev),wth3(klon,klev)
114      real q2(klon,klev)
115! FH probleme de dimensionnement avec l'allocation dynamique
116!     common/comtherm/thetath2,wth2
117   
118      real ratqscth(klon,klev)
119      real var
120      real vardiff
121      real ratqsdiff(klon,klev)
122
123      logical sorties
124      real rho(klon,klev),rhobarz(klon,klev),masse(klon,klev)
125      real zpspsk(klon,klev)
126
127      real wmax(klon)
128      real wmax_sec(klon)
129      real fm0(klon,klev+1),entr0(klon,klev),detr0(klon,klev)
130      real fm(klon,klev+1),entr(klon,klev),detr(klon,klev)
131
132      real ztla(klon,klev),zqla(klon,klev),zqta(klon,klev)
133!niveau de condensation
134      integer nivcon(klon)
135      real zcon(klon)
136      REAL CHI
137      real zcon2(klon)
138      real pcon(klon)
139      real zqsat(klon,klev)
140      real zqsatth(klon,klev)
141
142      real f_star(klon,klev+1),entr_star(klon,klev)
143      real detr_star(klon,klev)
144      real alim_star_tot(klon),alim_star2(klon)
145      real alim_star(klon,klev)
146      real f(klon), f0(klon)
147!FH/IM     save f0
148      real zlevinter(klon)
149      logical debut
150       real seuil
151
152!
153      !nouvelles variables pour la convection
154      real Ale_bl(klon)
155      real Alp_bl(klon)
156      real alp_int(klon)
157      real ale_int(klon)
158      integer n_int(klon)
159      real fm_tot(klon)
160      real wght_th(klon,klev)
161      integer lalim_conv(klon)
162!v1d     logical therm
163!v1d     save therm
164
165      character*2 str2
166      character*10 str10
167
168      EXTERNAL SCOPY
169!
170
171!-----------------------------------------------------------------------
172!   initialisation:
173!   ---------------
174!
175
176      seuil=0.25
177
178      if (debut)  then
179         fm0=0.
180         entr0=0.
181         detr0=0.
182
183
184! #define wrgrads_thermcell
185#undef wrgrads_thermcell
186#ifdef wrgrads_thermcell
187! Initialisation des sorties grads pour les thermiques.
188! Pour l'instant en 1D sur le point igout.
189! Utilise par thermcell_out3d.h
190         str10='therm'
191         call inigrads(1,1,rlond(igout),1.,-180.,180.,jjm, &
192     &   rlatd(igout),-90.,90.,1.,llm,pplay(igout,:),1.,   &
193     &   ptimestep,str10,'therm ')
194#endif
195
196
197
198      endif
199
200      fm=0. ; entr=0. ; detr=0.
201
202      icount=icount+1
203
204!IM 090508 beg
205!print*,'====================================================================='
206!print*,'====================================================================='
207!print*,' PAS ',icount,' PAS ',icount,' PAS ',icount,' PAS ',icount
208!print*,'====================================================================='
209!print*,'====================================================================='
210!IM 090508 end
211
212      if (prt_level.ge.1) print*,'thermcell_main V4'
213
214       sorties=.true.
215      IF(ngrid.NE.klon) THEN
216         PRINT*
217         PRINT*,'STOP dans convadj'
218         PRINT*,'ngrid    =',ngrid
219         PRINT*,'klon  =',klon
220      ENDIF
221!
222!Initialisation
223!
224!    IF (1.eq.0) THEN
225!     do ig=1,klon     
226!FH/IM 130308     if ((debut).or.((.not.debut).and.(f0(ig).lt.1.e-10))) then
227!     if ((.not.debut).and.(f0(ig).lt.1.e-10)) then
228!           f0(ig)=1.e-5
229!           zmax0(ig)=40.
230!v1d        therm=.false.
231!     endif
232!     enddo
233!    ENDIF !(1.eq.0) THEN
234     if (prt_level.ge.10)write(lunout,*)                                &
235    &     'WARNING thermcell_main f0=max(f0,1.e-2)'
236     do ig=1,klon
237      if (prt_level.ge.20) then
238       print*,'th_main ig f0',ig,f0(ig)
239      endif
240         f0(ig)=max(f0(ig),1.e-2)
241!IMmarche pas ?!       if (f0(ig)<1.e-2) f0(ig)=1.e-2
242     enddo
243
244!-----------------------------------------------------------------------
245! Calcul de T,q,ql a partir de Tl et qT dans l environnement
246!   --------------------------------------------------------------------
247!
248      CALL thermcell_env(ngrid,nlay,po,pt,pu,pv,pplay,  &
249     &           pplev,zo,zh,zl,ztv,zthl,zu,zv,zpspsk,zqsat,lev_out)
250       
251      if (prt_level.ge.1) print*,'thermcell_main apres thermcell_env'
252
253!------------------------------------------------------------------------
254!                       --------------------
255!
256!
257!                       + + + + + + + + + + +
258!
259!
260!  wa, fraca, wd, fracd --------------------   zlev(2), rhobarz
261!  wh,wt,wo ...
262!
263!                       + + + + + + + + + + +  zh,zu,zv,zo,rho
264!
265!
266!                       --------------------   zlev(1)
267!                       \\\\\\\\\\\\\\\\\\\\
268!
269!
270
271!-----------------------------------------------------------------------
272!   Calcul des altitudes des couches
273!-----------------------------------------------------------------------
274
275      do l=2,nlay
276         zlev(:,l)=0.5*(pphi(:,l)+pphi(:,l-1))/RG
277      enddo
278         zlev(:,1)=0.
279         zlev(:,nlay+1)=(2.*pphi(:,klev)-pphi(:,klev-1))/RG
280      do l=1,nlay
281         zlay(:,l)=pphi(:,l)/RG
282      enddo
283!calcul de l epaisseur des couches
284      do l=1,nlay
285         deltaz(:,l)=zlev(:,l+1)-zlev(:,l)
286      enddo
287
288!     print*,'2 OK convect8'
289!-----------------------------------------------------------------------
290!   Calcul des densites
291!-----------------------------------------------------------------------
292
293      do l=1,nlay
294         rho(:,l)=pplay(:,l)/(zpspsk(:,l)*RD*ztv(:,l))
295      enddo
296
297!IM
298     if (prt_level.ge.10)write(lunout,*)                                &
299    &    'WARNING thermcell_main rhobarz(:,1)=rho(:,1)'
300      rhobarz(:,1)=rho(:,1)
301
302      do l=2,nlay
303         rhobarz(:,l)=0.5*(rho(:,l)+rho(:,l-1))
304      enddo
305
306!calcul de la masse
307      do l=1,nlay
308         masse(:,l)=(pplev(:,l)-pplev(:,l+1))/RG
309      enddo
310
311      if (prt_level.ge.1) print*,'thermcell_main apres initialisation'
312
313!------------------------------------------------------------------
314!
315!             /|\
316!    --------  |  F_k+1 -------   
317!                              ----> D_k
318!             /|\              <---- E_k , A_k
319!    --------  |  F_k ---------
320!                              ----> D_k-1
321!                              <---- E_k-1 , A_k-1
322!
323!
324!
325!
326!
327!    ---------------------------
328!
329!    ----- F_lmax+1=0 ----------         \
330!            lmax     (zmax)              |
331!    ---------------------------          |
332!                                         |
333!    ---------------------------          |
334!                                         |
335!    ---------------------------          |
336!                                         |
337!    ---------------------------          |
338!                                         |
339!    ---------------------------          |
340!                                         |  E
341!    ---------------------------          |  D
342!                                         |
343!    ---------------------------          |
344!                                         |
345!    ---------------------------  \       |
346!            lalim                 |      |
347!    ---------------------------   |      |
348!                                  |      |
349!    ---------------------------   |      |
350!                                  | A    |
351!    ---------------------------   |      |
352!                                  |      |
353!    ---------------------------   |      |
354!    lmin  (=1 pour le moment)     |      |
355!    ----- F_lmin=0 ------------  /      /
356!
357!    ---------------------------
358!    //////////////////////////
359!
360!
361!=============================================================================
362!  Calculs initiaux ne faisant pas intervenir les changements de phase
363!=============================================================================
364
365!------------------------------------------------------------------
366!  1. alim_star est le profil vertical de l'alimentation à la base du
367!     panache thermique, calculé à partir de la flotabilité de l'air sec
368!  2. lmin et lalim sont les indices inferieurs et superieurs de alim_star
369!------------------------------------------------------------------
370!
371      entr_star=0. ; detr_star=0. ; alim_star=0. ; alim_star_tot=0.
372      CALL thermcellV0_init(ngrid,nlay,ztv,zlay,zlev,  &
373     &                    lalim,lmin,alim_star,alim_star_tot,lev_out)
374
375call testV0_ltherm(ngrid,nlay,pplev,pplay,lmin,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_init lmin  ')
376call testV0_ltherm(ngrid,nlay,pplev,pplay,lalim,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_init lalim ')
377
378
379      if (prt_level.ge.1) print*,'thermcell_main apres thermcell_init'
380      if (prt_level.ge.10) then
381         write(lunout1,*) 'Dans thermcell_main 1'
382         write(lunout1,*) 'lmin ',lmin(igout)
383         write(lunout1,*) 'lalim ',lalim(igout)
384         write(lunout1,*) ' ig l alim_star thetav'
385         write(lunout1,'(i6,i4,2e15.5)') (igout,l,alim_star(igout,l) &
386     &   ,ztv(igout,l),l=1,lalim(igout)+4)
387      endif
388
389!v1d      do ig=1,klon
390!v1d     if (alim_star(ig,1).gt.1.e-10) then
391!v1d     therm=.true.
392!v1d     endif
393!v1d      enddo
394!-----------------------------------------------------------------------------
395!  3. wmax_sec et zmax_sec sont les vitesses et altitudes maximum d'un
396!     panache sec conservatif (e=d=0) alimente selon alim_star
397!     Il s'agit d'un calcul de type CAPE
398!     zmax_sec est utilisé pour déterminer la géométrie du thermique.
399!------------------------------------------------------------------------------
400!
401      CALL thermcellV0_dry(ngrid,nlay,zlev,pphi,ztv,alim_star,  &
402     &                      lalim,lmin,zmax_sec,wmax_sec,lev_out)
403
404call testV0_ltherm(ngrid,nlay,pplev,pplay,lmin,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_dry  lmin  ')
405call testV0_ltherm(ngrid,nlay,pplev,pplay,lalim,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_dry  lalim ')
406
407      if (prt_level.ge.1) print*,'thermcell_main apres thermcell_dry'
408      if (prt_level.ge.10) then
409         write(lunout1,*) 'Dans thermcell_main 1b'
410         write(lunout1,*) 'lmin ',lmin(igout)
411         write(lunout1,*) 'lalim ',lalim(igout)
412         write(lunout1,*) ' ig l alim_star entr_star detr_star f_star '
413         write(lunout1,'(i6,i4,e15.5)') (igout,l,alim_star(igout,l) &
414     &    ,l=1,lalim(igout)+4)
415      endif
416
417
418
419!---------------------------------------------------------------------------------
420!calcul du melange et des variables dans le thermique
421!--------------------------------------------------------------------------------
422!
423      if (prt_level.ge.1) print*,'avant thermcell_plume ',lev_out
424!IM 140508   CALL thermcell_plume(ngrid,nlay,ptimestep,ztv,zthl,po,zl,rhobarz,  &
425      CALL thermcellV0_plume(itap,ngrid,nlay,ptimestep,ztv,zthl,po,zl,rhobarz,  &
426     &           zlev,pplev,pphi,zpspsk,l_mix,r_aspect,alim_star,alim_star_tot,  &
427     &           lalim,zmax_sec,f0,detr_star,entr_star,f_star,ztva,  &
428     &           ztla,zqla,zqta,zha,zw2,zw_est,zqsatth,lmix,lmix_bis,linter &
429     &            ,lev_out,lunout1,igout)
430      if (prt_level.ge.1) print*,'apres thermcell_plume ',lev_out
431
432      call testV0_ltherm(ngrid,nlay,pplev,pplay,lalim,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_plum lalim ')
433      call testV0_ltherm(ngrid,nlay,pplev,pplay,lmix ,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_plum lmix  ')
434
435      if (prt_level.ge.1) print*,'thermcell_main apres thermcell_plume'
436      if (prt_level.ge.10) then
437         write(lunout1,*) 'Dans thermcell_main 2'
438         write(lunout1,*) 'lmin ',lmin(igout)
439         write(lunout1,*) 'lalim ',lalim(igout)
440         write(lunout1,*) ' ig l alim_star entr_star detr_star f_star '
441         write(lunout1,'(i6,i4,4e15.5)') (igout,l,alim_star(igout,l),entr_star(igout,l),detr_star(igout,l) &
442     &    ,f_star(igout,l+1),l=1,nint(linter(igout))+5)
443      endif
444
445!-------------------------------------------------------------------------------
446! Calcul des caracteristiques du thermique:zmax,zmix,wmax
447!-------------------------------------------------------------------------------
448!
449      CALL thermcell_height(ngrid,nlay,lalim,lmin,linter,lmix,zw2,  &
450     &           zlev,lmax,zmax,zmax0,zmix,wmax,lev_out)
451
452
453      call testV0_ltherm(ngrid,nlay,pplev,pplay,lalim,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_heig lalim ')
454      call testV0_ltherm(ngrid,nlay,pplev,pplay,lmin ,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_heig lmin  ')
455      call testV0_ltherm(ngrid,nlay,pplev,pplay,lmix ,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_heig lmix  ')
456      call testV0_ltherm(ngrid,nlay,pplev,pplay,lmax ,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_heig lmax  ')
457
458      if (prt_level.ge.1) print*,'thermcell_main apres thermcell_height'
459
460!-------------------------------------------------------------------------------
461! Fermeture,determination de f
462!-------------------------------------------------------------------------------
463!
464!avant closure: on redéfinit lalim, alim_star_tot et alim_star
465!       do ig=1,klon
466!       do l=2,lalim(ig)
467!       alim_star(ig,l)=entr_star(ig,l)
468!       entr_star(ig,l)=0.
469!       enddo
470!       enddo
471
472      CALL thermcellV0_closure(ngrid,nlay,r_aspect,ptimestep,rho,  &
473     &   zlev,lalim,alim_star,alim_star_tot,zmax_sec,wmax_sec,zmax,wmax,f,lev_out)
474
475      if(prt_level.ge.1)print*,'thermcell_closure apres thermcell_closure'
476
477      if (tau_thermals>1.) then
478         lambda=exp(-ptimestep/tau_thermals)
479         f0=(1.-lambda)*f+lambda*f0
480      else
481         f0=f
482      endif
483
484! Test valable seulement en 1D mais pas genant
485      if (.not. (f0(1).ge.0.) ) then
486           stop 'Dans thermcell_main'
487      endif
488
489!-------------------------------------------------------------------------------
490!deduction des flux
491!-------------------------------------------------------------------------------
492
493      CALL thermcell_flux2(ngrid,nlay,ptimestep,masse, &
494     &       lalim,lmax,alim_star,  &
495     &       entr_star,detr_star,f,rhobarz,zlev,zw2,fm,entr,  &
496     &       detr,zqla,lev_out,lunout1,igout)
497!IM 060508    &       detr,zqla,zmax,lev_out,lunout,igout)
498
499      if (prt_level.ge.1) print*,'thermcell_main apres thermcell_flux'
500      call testV0_ltherm(ngrid,nlay,pplev,pplay,lalim,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_flux lalim ')
501      call testV0_ltherm(ngrid,nlay,pplev,pplay,lmax ,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_flux lmax  ')
502
503!------------------------------------------------------------------
504!   On ne prend pas directement les profils issus des calculs precedents
505!   mais on s'autorise genereusement une relaxation vers ceci avec
506!   une constante de temps tau_thermals (typiquement 1800s).
507!------------------------------------------------------------------
508
509      if (tau_thermals>1.) then
510         lambda=exp(-ptimestep/tau_thermals)
511         fm0=(1.-lambda)*fm+lambda*fm0
512         entr0=(1.-lambda)*entr+lambda*entr0
513!        detr0=(1.-lambda)*detr+lambda*detr0
514      else
515         fm0=fm
516         entr0=entr
517         detr0=detr
518      endif
519
520!c------------------------------------------------------------------
521!   calcul du transport vertical
522!------------------------------------------------------------------
523
524      call thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,masse,  &
525     &                    zthl,zdthladj,zta,lev_out)
526      call thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,masse,  &
527     &                   po,pdoadj,zoa,lev_out)
528
529!------------------------------------------------------------------
530! Calcul de la fraction de l'ascendance
531!------------------------------------------------------------------
532      do ig=1,klon
533         fraca(ig,1)=0.
534         fraca(ig,nlay+1)=0.
535      enddo
536      do l=2,nlay
537         do ig=1,klon
538            if (zw2(ig,l).gt.1.e-10) then
539            fraca(ig,l)=fm(ig,l)/(rhobarz(ig,l)*zw2(ig,l))
540            else
541            fraca(ig,l)=0.
542            endif
543         enddo
544      enddo
545     
546!------------------------------------------------------------------
547!  calcul du transport vertical du moment horizontal
548!------------------------------------------------------------------
549
550!IM 090508 
551      if (1.eq.1) then
552!IM 070508 vers. _dq       
553!     if (1.eq.0) then
554
555
556! Calcul du transport de V tenant compte d'echange par gradient
557! de pression horizontal avec l'environnement
558
559         call thermcell_dv2(ngrid,nlay,ptimestep,fm0,entr0,masse  &
560     &    ,fraca,zmax  &
561     &    ,zu,zv,pduadj,pdvadj,zua,zva,lev_out)
562!IM 050508    &    ,zu,zv,pduadj,pdvadj,zua,zva,igout,lev_out)
563      else
564
565! calcul purement conservatif pour le transport de V
566         call thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,masse  &
567     &    ,zu,pduadj,zua,lev_out)
568         call thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,masse  &
569     &    ,zv,pdvadj,zva,lev_out)
570      endif
571
572!     print*,'13 OK convect8'
573      do l=1,nlay
574         do ig=1,ngrid
575           pdtadj(ig,l)=zdthladj(ig,l)*zpspsk(ig,l) 
576         enddo
577      enddo
578
579      if (prt_level.ge.1) print*,'14 OK convect8'
580!------------------------------------------------------------------
581!   Calculs de diagnostiques pour les sorties
582!------------------------------------------------------------------
583!calcul de fraca pour les sorties
584     
585      if (sorties) then
586      if (prt_level.ge.1) print*,'14a OK convect8'
587! calcul du niveau de condensation
588! initialisation
589      do ig=1,ngrid
590         nivcon(ig)=0
591         zcon(ig)=0.
592      enddo
593!nouveau calcul
594      do ig=1,ngrid
595      CHI=zh(ig,1)/(1669.0-122.0*zo(ig,1)/zqsat(ig,1)-zh(ig,1))
596      pcon(ig)=pplay(ig,1)*(zo(ig,1)/zqsat(ig,1))**CHI
597      enddo
598      do k=1,nlay
599         do ig=1,ngrid
600         if ((pcon(ig).le.pplay(ig,k))  &
601     &      .and.(pcon(ig).gt.pplay(ig,k+1))) then
602            zcon2(ig)=zlay(ig,k)-(pcon(ig)-pplay(ig,k))/(RG*rho(ig,k))/100.
603         endif
604         enddo
605      enddo
606      if (prt_level.ge.1) print*,'14b OK convect8'
607      do k=nlay,1,-1
608         do ig=1,ngrid
609            if (zqla(ig,k).gt.1e-10) then
610               nivcon(ig)=k
611               zcon(ig)=zlev(ig,k)
612            endif
613         enddo
614      enddo
615      if (prt_level.ge.1) print*,'14c OK convect8'
616!calcul des moments
617!initialisation
618      do l=1,nlay
619         do ig=1,ngrid
620            q2(ig,l)=0.
621            wth2(ig,l)=0.
622            wth3(ig,l)=0.
623            ratqscth(ig,l)=0.
624            ratqsdiff(ig,l)=0.
625         enddo
626      enddo     
627      if (prt_level.ge.1) print*,'14d OK convect8'
628      if (prt_level.ge.10)write(lunout,*)                                &
629    &     'WARNING thermcell_main wth2=0. si zw2 > 1.e-10'
630      do l=1,nlay
631         do ig=1,ngrid
632            zf=fraca(ig,l)
633            zf2=zf/(1.-zf)
634!
635      if (prt_level.ge.10) print*,'14e OK convect8 ig,l,zf,zf2',ig,l,zf,zf2
636!
637      if (prt_level.ge.10) print*,'14f OK convect8 ig,l,zha zh zpspsk ',ig,l,zha(ig,l),zh(ig,l),zpspsk(ig,l)
638            thetath2(ig,l)=zf2*(zha(ig,l)-zh(ig,l)/zpspsk(ig,l))**2
639            if(zw2(ig,l).gt.1.e-10) then
640             wth2(ig,l)=zf2*(zw2(ig,l))**2
641            else
642             wth2(ig,l)=0.
643            endif
644!           print*,'wth2=',wth2(ig,l)
645            wth3(ig,l)=zf2*(1-2.*fraca(ig,l))/(1-fraca(ig,l))  &
646     &                *zw2(ig,l)*zw2(ig,l)*zw2(ig,l)
647      if (prt_level.ge.10) print*,'14g OK convect8 ig,l,po',ig,l,po(ig,l)
648            q2(ig,l)=zf2*(zqta(ig,l)*1000.-po(ig,l)*1000.)**2
649!test: on calcul q2/po=ratqsc
650            ratqscth(ig,l)=sqrt(max(q2(ig,l),1.e-6)/(po(ig,l)*1000.))
651         enddo
652      enddo
653!calcul de ale_bl et alp_bl
654!pour le calcul d'une valeur intégrée entre la surface et lmax
655      do ig=1,ngrid
656      alp_int(ig)=0.
657      ale_int(ig)=0.
658      n_int(ig)=0
659      enddo
660!
661      do l=1,nlay
662      do ig=1,ngrid
663       if(l.LE.lmax(ig)) THEN
664        alp_int(ig)=alp_int(ig)+0.5*rhobarz(ig,l)*wth3(ig,l)
665        ale_int(ig)=ale_int(ig)+0.5*zw2(ig,l)**2
666        n_int(ig)=n_int(ig)+1
667       endif
668      enddo
669      enddo
670!      print*,'avant calcul ale et alp'
671!calcul de ALE et ALP pour la convection
672      do ig=1,ngrid
673!      Alp_bl(ig)=0.5*rhobarz(ig,lmix_bis(ig))*wth3(ig,lmix(ig))
674!          Alp_bl(ig)=0.5*rhobarz(ig,nivcon(ig))*wth3(ig,nivcon(ig))
675!      Alp_bl(ig)=0.5*rhobarz(ig,lmix(ig))*wth3(ig,lmix(ig))
676!     &           *0.1
677!valeur integree de alp_bl * 0.5:
678       if (n_int(ig).gt.0) then
679       Alp_bl(ig)=0.5*alp_int(ig)/n_int(ig)
680!       if (Alp_bl(ig).lt.0.) then
681!       Alp_bl(ig)=0.
682       endif
683!       endif
684!         write(18,*),'rhobarz,wth3,Alp',rhobarz(ig,nivcon(ig)),
685!     s               wth3(ig,nivcon(ig)),Alp_bl(ig)
686!            write(18,*),'ALP_BL',Alp_bl(ig),lmix(ig)
687!      Ale_bl(ig)=0.5*zw2(ig,lmix_bis(ig))**2
688!      if (nivcon(ig).eq.1) then
689!       Ale_bl(ig)=0.
690!       else
691!valeur max de ale_bl:
692       Ale_bl(ig)=0.5*zw2(ig,lmix(ig))**2
693!     & /2.
694!     & *0.1
695!        Ale_bl(ig)=0.5*zw2(ig,lmix_bis(ig))**2
696!       if (n_int(ig).gt.0) then
697!       Ale_bl(ig)=ale_int(ig)/n_int(ig)
698!        Ale_bl(ig)=4.
699!       endif
700!       endif
701!            Ale_bl(ig)=0.5*wth2(ig,lmix_bis(ig))
702!          Ale_bl(ig)=wth2(ig,nivcon(ig))
703!          write(19,*),'wth2,ALE_BL',wth2(ig,nivcon(ig)),Ale_bl(ig)
704      enddo
705!test:calcul de la ponderation des couches pour KE
706!initialisations
707!      print*,'ponderation'
708      do ig=1,ngrid
709           fm_tot(ig)=0.
710      enddo
711       do ig=1,ngrid
712        do k=1,klev
713           wght_th(ig,k)=1.
714        enddo
715       enddo
716       do ig=1,ngrid
717!         lalim_conv(ig)=lmix_bis(ig)
718!la hauteur de la couche alim_conv = hauteur couche alim_therm
719         lalim_conv(ig)=lalim(ig)
720!         zentr(ig)=zlev(ig,lalim(ig))
721      enddo
722      do ig=1,ngrid
723        do k=1,lalim_conv(ig)
724           fm_tot(ig)=fm_tot(ig)+fm(ig,k)
725        enddo
726      enddo
727      do ig=1,ngrid
728        do k=1,lalim_conv(ig)
729           if (fm_tot(ig).gt.1.e-10) then
730!           wght_th(ig,k)=fm(ig,k)/fm_tot(ig)
731           endif
732!on pondere chaque couche par a*
733             if (alim_star(ig,k).gt.1.e-10) then
734             wght_th(ig,k)=alim_star(ig,k)
735             else
736             wght_th(ig,k)=1.
737             endif
738        enddo
739      enddo
740!      print*,'apres wght_th'
741!test pour prolonger la convection
742      do ig=1,ngrid
743!v1d  if ((alim_star(ig,1).lt.1.e-10).and.(therm)) then
744      if ((alim_star(ig,1).lt.1.e-10)) then
745      lalim_conv(ig)=1
746      wght_th(ig,1)=1.
747!      print*,'lalim_conv ok',lalim_conv(ig),wght_th(ig,1)
748      endif
749      enddo
750
751!calcul du ratqscdiff
752      if (prt_level.ge.1) print*,'14e OK convect8'
753      var=0.
754      vardiff=0.
755      ratqsdiff(:,:)=0.
756      do ig=1,ngrid
757         do l=1,lalim(ig)
758            var=var+alim_star(ig,l)*zqta(ig,l)*1000.
759         enddo
760      enddo
761      if (prt_level.ge.1) print*,'14f OK convect8'
762      do ig=1,ngrid
763          do l=1,lalim(ig)
764          zf=fraca(ig,l)
765          zf2=zf/(1.-zf)
766          vardiff=vardiff+alim_star(ig,l)  &
767     &           *(zqta(ig,l)*1000.-var)**2
768!         ratqsdiff=ratqsdiff+alim_star(ig,l)*
769!     s          (zqta(ig,l)*1000.-po(ig,l)*1000.)**2
770          enddo
771      enddo
772      if (prt_level.ge.1) print*,'14g OK convect8'
773      do l=1,nlay
774         do ig=1,ngrid
775            ratqsdiff(ig,l)=sqrt(vardiff)/(po(ig,l)*1000.)   
776!           write(11,*)'ratqsdiff=',ratqsdiff(ig,l)
777         enddo
778      enddo
779!--------------------------------------------------------------------   
780!
781!ecriture des fichiers sortie
782!     print*,'15 OK convect8'
783
784      if (prt_level.ge.1) print*,'thermcell_main sorties 3D'
785#ifdef wrgrads_thermcell
786#include "thermcell_out3d.h"
787#endif
788
789      endif
790
791      if (prt_level.ge.1) print*,'thermcell_main FIN  OK'
792
793!     if(icount.eq.501) stop'au pas 301 dans thermcell_main'
794      return
795      end
796
797!-----------------------------------------------------------------------------
798
799      subroutine testV0_ltherm(klon,klev,pplev,pplay,long,seuil,ztv,po,ztva,zqla,f_star,zw2,comment)
800      IMPLICIT NONE
801#include "iniprint.h"
802
803      integer i, k, klon,klev
804      real pplev(klon,klev+1),pplay(klon,klev)
805      real ztv(klon,klev)
806      real po(klon,klev)
807      real ztva(klon,klev)
808      real zqla(klon,klev)
809      real f_star(klon,klev)
810      real zw2(klon,klev)
811      integer long(klon)
812      real seuil
813      character*21 comment
814
815      if (prt_level.ge.1) THEN
816       print*,'WARNING !!! TEST ',comment
817      endif
818      return
819
820!  test sur la hauteur des thermiques ...
821         do i=1,klon
822!IMtemp           if (pplay(i,long(i)).lt.seuil*pplev(i,1)) then
823           if (prt_level.ge.10) then
824               print*,'WARNING ',comment,' au point ',i,' K= ',long(i)
825               print*,'  K  P(MB)  THV(K)     Qenv(g/kg)THVA        QLA(g/kg)   F*        W2'
826               do k=1,klev
827                  write(6,'(i3,7f10.3)') k,pplay(i,k),ztv(i,k),1000*po(i,k),ztva(i,k),1000*zqla(i,k),f_star(i,k),zw2(i,k)
828               enddo
829!              stop
830           endif
831         enddo
832
833
834      return
835      end
836
837!==============================================================================
838      SUBROUTINE thermcellV0_closure(ngrid,nlay,r_aspect,ptimestep,rho,  &
839     &   zlev,lalim,alim_star,alim_star_tot,zmax_sec,wmax_sec,zmax,wmax,f,lev_out)
840
841!-------------------------------------------------------------------------
842!thermcell_closure: fermeture, determination de f
843!-------------------------------------------------------------------------
844      IMPLICIT NONE
845
846#include "iniprint.h"
847#include "thermcell.h"
848      INTEGER ngrid,nlay
849      INTEGER ig,k       
850      REAL r_aspect,ptimestep
851      integer lev_out                           ! niveau pour les print
852
853      INTEGER lalim(ngrid)
854      REAL alim_star(ngrid,nlay)
855      REAL alim_star_tot(ngrid)
856      REAL rho(ngrid,nlay)
857      REAL zlev(ngrid,nlay)
858      REAL zmax(ngrid),zmax_sec(ngrid)
859      REAL wmax(ngrid),wmax_sec(ngrid)
860      real zdenom
861
862      REAL alim_star2(ngrid)
863
864      REAL f(ngrid)
865
866      do ig=1,ngrid
867         alim_star2(ig)=0.
868      enddo
869      do ig=1,ngrid
870         if (alim_star(ig,1).LT.1.e-10) then
871            f(ig)=0.
872         else   
873             do k=1,lalim(ig)
874                alim_star2(ig)=alim_star2(ig)+alim_star(ig,k)**2  &
875     &                    /(rho(ig,k)*(zlev(ig,k+1)-zlev(ig,k)))
876             enddo
877             zdenom=max(500.,zmax(ig))*r_aspect*alim_star2(ig)
878             if (zdenom<1.e-14) then
879                print*,'ig=',ig
880                print*,'alim_star2',alim_star2(ig)
881                print*,'zmax',zmax(ig)
882                print*,'r_aspect',r_aspect
883                print*,'zdenom',zdenom
884                print*,'alim_star',alim_star(ig,:)
885                print*,'zmax_sec',zmax_sec(ig)
886                print*,'wmax_sec',wmax_sec(ig)
887                stop
888             endif
889             if ((zmax_sec(ig).gt.1.e-10).and.(iflag_thermals_ed.eq.0)) then
890             f(ig)=wmax_sec(ig)*alim_star_tot(ig)/(max(500.,zmax_sec(ig))*r_aspect  &
891     &             *alim_star2(ig))
892!            f(ig)=f(ig)+(f0(ig)-f(ig))*exp((-ptimestep/  &
893!    &                     zmax_sec(ig))*wmax_sec(ig))
894             if(prt_level.GE.10) write(lunout,*)'closure dry',f(ig),wmax_sec(ig),alim_star_tot(ig),zmax_sec(ig)
895             else
896             f(ig)=wmax(ig)*alim_star_tot(ig)/zdenom
897!            f(ig)=f(ig)+(f0(ig)-f(ig))*exp((-ptimestep/  &
898!     &                     zmax(ig))*wmax(ig))
899             if(prt_level.GE.10) print*,'closure moist',f(ig),wmax(ig),alim_star_tot(ig),zmax(ig)
900             endif
901         endif
902!         f0(ig)=f(ig)
903      enddo
904      if (prt_level.ge.1) print*,'apres fermeture'
905
906!
907      return
908      end
909!==============================================================================
910      SUBROUTINE thermcellV0_plume(itap,ngrid,klev,ptimestep,ztv,zthl,po,zl,rhobarz,  &
911     &           zlev,pplev,pphi,zpspsk,l_mix,r_aspect,alim_star,alim_star_tot,  &
912     &           lalim,zmax_sec,f0,detr_star,entr_star,f_star,ztva,  &
913     &           ztla,zqla,zqta,zha,zw2,w_est,zqsatth,lmix,lmix_bis,linter &
914     &           ,lev_out,lunout1,igout)
915
916!--------------------------------------------------------------------------
917!thermcell_plume: calcule les valeurs de qt, thetal et w dans l ascendance
918!--------------------------------------------------------------------------
919
920      IMPLICIT NONE
921
922#include "YOMCST.h"
923#include "YOETHF.h"
924#include "FCTTRE.h"
925#include "iniprint.h"
926#include "thermcell.h"
927
928      INTEGER itap
929      INTEGER lunout1,igout
930      INTEGER ngrid,klev
931      REAL ptimestep
932      REAL ztv(ngrid,klev)
933      REAL zthl(ngrid,klev)
934      REAL po(ngrid,klev)
935      REAL zl(ngrid,klev)
936      REAL rhobarz(ngrid,klev)
937      REAL zlev(ngrid,klev+1)
938      REAL pplev(ngrid,klev+1)
939      REAL pphi(ngrid,klev)
940      REAL zpspsk(ngrid,klev)
941      REAL alim_star(ngrid,klev)
942      REAL zmax_sec(ngrid)
943      REAL f0(ngrid)
944      REAL l_mix
945      REAL r_aspect
946      INTEGER lalim(ngrid)
947      integer lev_out                           ! niveau pour les print
948      real zcon2(ngrid)
949   
950      real alim_star_tot(ngrid)
951
952      REAL ztva(ngrid,klev)
953      REAL ztla(ngrid,klev)
954      REAL zqla(ngrid,klev)
955      REAL zqla0(ngrid,klev)
956      REAL zqta(ngrid,klev)
957      REAL zha(ngrid,klev)
958
959      REAL detr_star(ngrid,klev)
960      REAL coefc
961      REAL detr_stara(ngrid,klev)
962      REAL detr_starb(ngrid,klev)
963      REAL detr_starc(ngrid,klev)
964      REAL detr_star0(ngrid,klev)
965      REAL detr_star1(ngrid,klev)
966      REAL detr_star2(ngrid,klev)
967
968      REAL entr_star(ngrid,klev)
969      REAL entr_star1(ngrid,klev)
970      REAL entr_star2(ngrid,klev)
971      REAL detr(ngrid,klev)
972      REAL entr(ngrid,klev)
973
974      REAL zw2(ngrid,klev+1)
975      REAL w_est(ngrid,klev+1)
976      REAL f_star(ngrid,klev+1)
977      REAL wa_moy(ngrid,klev+1)
978
979      REAL ztva_est(ngrid,klev)
980      REAL zqla_est(ngrid,klev)
981      REAL zqsatth(ngrid,klev)
982      REAL zta_est(ngrid,klev)
983
984      REAL linter(ngrid)
985      INTEGER lmix(ngrid)
986      INTEGER lmix_bis(ngrid)
987      REAL    wmaxa(ngrid)
988
989      INTEGER ig,l,k
990
991      real zcor,zdelta,zcvm5,qlbef
992      real Tbef,qsatbef
993      real dqsat_dT,DT,num,denom
994      REAL REPS,RLvCp,DDT0
995      PARAMETER (DDT0=.01)
996      logical Zsat
997      REAL fact_gamma,fact_epsilon
998      REAL c2(ngrid,klev)
999
1000      Zsat=.false.
1001! Initialisation
1002      RLvCp = RLVTT/RCPD
1003     
1004      if (iflag_thermals_ed==0) then
1005         fact_gamma=1.
1006         fact_epsilon=1.
1007      else if (iflag_thermals_ed==1)  then
1008         fact_gamma=1.
1009         fact_epsilon=1.
1010      else if (iflag_thermals_ed==2)  then
1011         fact_gamma=1.
1012         fact_epsilon=2.
1013      endif
1014
1015      do l=1,klev
1016         do ig=1,ngrid
1017            zqla_est(ig,l)=0.
1018            ztva_est(ig,l)=ztva(ig,l)
1019            zqsatth(ig,l)=0.
1020         enddo
1021      enddo
1022
1023!CR: attention test couche alim
1024!     do l=2,klev
1025!     do ig=1,ngrid
1026!        alim_star(ig,l)=0.
1027!     enddo
1028!     enddo
1029!AM:initialisations du thermique
1030      do k=1,klev
1031         do ig=1,ngrid
1032            ztva(ig,k)=ztv(ig,k)
1033            ztla(ig,k)=zthl(ig,k)
1034            zqla(ig,k)=0.
1035            zqta(ig,k)=po(ig,k)
1036!
1037            ztva(ig,k) = ztla(ig,k)*zpspsk(ig,k)+RLvCp*zqla(ig,k)
1038            ztva(ig,k) = ztva(ig,k)/zpspsk(ig,k)
1039            zha(ig,k) = ztva(ig,k)
1040!
1041         enddo
1042      enddo
1043      do k=1,klev
1044        do ig=1,ngrid
1045           detr_star(ig,k)=0.
1046           entr_star(ig,k)=0.
1047
1048           detr_stara(ig,k)=0.
1049           detr_starb(ig,k)=0.
1050           detr_starc(ig,k)=0.
1051           detr_star0(ig,k)=0.
1052           zqla0(ig,k)=0.
1053           detr_star1(ig,k)=0.
1054           detr_star2(ig,k)=0.
1055           entr_star1(ig,k)=0.
1056           entr_star2(ig,k)=0.
1057
1058           detr(ig,k)=0.
1059           entr(ig,k)=0.
1060        enddo
1061      enddo
1062      if (prt_level.ge.1) print*,'7 OK convect8'
1063      do k=1,klev+1
1064         do ig=1,ngrid
1065            zw2(ig,k)=0.
1066            w_est(ig,k)=0.
1067            f_star(ig,k)=0.
1068            wa_moy(ig,k)=0.
1069         enddo
1070      enddo
1071
1072      if (prt_level.ge.1) print*,'8 OK convect8'
1073      do ig=1,ngrid
1074         linter(ig)=1.
1075         lmix(ig)=1
1076         lmix_bis(ig)=2
1077         wmaxa(ig)=0.
1078      enddo
1079
1080!-----------------------------------------------------------------------------------
1081!boucle de calcul de la vitesse verticale dans le thermique
1082!-----------------------------------------------------------------------------------
1083      do l=1,klev-1
1084         do ig=1,ngrid
1085
1086
1087
1088! Calcul dans la premiere couche active du thermique (ce qu'on teste
1089! en disant que la couche est instable et que w2 en bas de la couche
1090! est nulle.
1091
1092            if (ztv(ig,l).gt.ztv(ig,l+1)  &
1093     &         .and.alim_star(ig,l).gt.1.e-10  &
1094     &         .and.zw2(ig,l).lt.1e-10) then
1095
1096
1097! Le panache va prendre au debut les caracteristiques de l'air contenu
1098! dans cette couche.
1099               ztla(ig,l)=zthl(ig,l)
1100               zqta(ig,l)=po(ig,l)
1101               zqla(ig,l)=zl(ig,l)
1102               f_star(ig,l+1)=alim_star(ig,l)
1103
1104               zw2(ig,l+1)=2.*RG*(ztv(ig,l)-ztv(ig,l+1))/ztv(ig,l+1)  &
1105     &                     *(zlev(ig,l+1)-zlev(ig,l))  &
1106     &                     *0.4*pphi(ig,l)/(pphi(ig,l+1)-pphi(ig,l))
1107               w_est(ig,l+1)=zw2(ig,l+1)
1108!
1109
1110
1111            else if ((zw2(ig,l).ge.1e-10).and.  &
1112     &         (f_star(ig,l)+alim_star(ig,l)).gt.1.e-10) then
1113!estimation du detrainement a partir de la geometrie du pas precedent
1114!tests sur la definition du detr
1115!calcul de detr_star et entr_star
1116
1117
1118
1119!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1120! FH le test miraculeux de Catherine ? Le bout du tunel ?
1121!               w_est(ig,3)=zw2(ig,2)*  &
1122!    &                   ((f_star(ig,2))**2)  &
1123!    &                   /(f_star(ig,2)+alim_star(ig,2))**2+  &
1124!    &                   2.*RG*(ztva(ig,1)-ztv(ig,2))/ztv(ig,2)  &
1125!    &                   *(zlev(ig,3)-zlev(ig,2))
1126!     if (l.gt.2) then
1127!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1128
1129
1130
1131! Premier calcul de la vitesse verticale a partir de la temperature
1132! potentielle virtuelle
1133
1134! FH CESTQUOI CA ????
1135#define int1d2
1136!#undef int1d2
1137#ifdef int1d2
1138      if (l.ge.2) then
1139#else
1140      if (l.gt.2) then
1141#endif
1142
1143      if (1.eq.1) then
1144          w_est(ig,3)=zw2(ig,2)* &
1145     &      ((f_star(ig,2))**2) &
1146     &      /(f_star(ig,2)+alim_star(ig,2))**2+ &
1147     &      2.*RG*(ztva(ig,2)-ztv(ig,2))/ztv(ig,2) &
1148!     &      *1./3. &
1149     &      *(zlev(ig,3)-zlev(ig,2))
1150       endif
1151
1152
1153!---------------------------------------------------------------------------
1154!calcul de l entrainement et du detrainement lateral
1155!---------------------------------------------------------------------------
1156!
1157!test:estimation de ztva_new_est sans entrainement
1158
1159               Tbef=ztla(ig,l-1)*zpspsk(ig,l)
1160               zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
1161               qsatbef= R2ES * FOEEW(Tbef,zdelta)/pplev(ig,l)
1162               qsatbef=MIN(0.5,qsatbef)
1163               zcor=1./(1.-retv*qsatbef)
1164               qsatbef=qsatbef*zcor
1165               Zsat = (max(0.,zqta(ig,l-1)-qsatbef) .gt. 1.e-10)
1166               if (Zsat) then
1167               qlbef=max(0.,zqta(ig,l-1)-qsatbef)
1168               DT = 0.5*RLvCp*qlbef
1169               do while (abs(DT).gt.DDT0)
1170                 Tbef=Tbef+DT
1171                 zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
1172                 qsatbef= R2ES * FOEEW(Tbef,zdelta)/pplev(ig,l)
1173                 qsatbef=MIN(0.5,qsatbef)
1174                 zcor=1./(1.-retv*qsatbef)
1175                 qsatbef=qsatbef*zcor
1176                 qlbef=zqta(ig,l-1)-qsatbef
1177
1178                 zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
1179                 zcvm5=R5LES*(1.-zdelta) + R5IES*zdelta
1180                 zcor=1./(1.-retv*qsatbef)
1181                 dqsat_dT=FOEDE(Tbef,zdelta,zcvm5,qsatbef,zcor)
1182                 num=-Tbef+ztla(ig,l-1)*zpspsk(ig,l)+RLvCp*qlbef
1183                 denom=1.+RLvCp*dqsat_dT
1184                 DT=num/denom
1185               enddo
1186                 zqla_est(ig,l) = max(0.,zqta(ig,l-1)-qsatbef)
1187               endif
1188        ztva_est(ig,l) = ztla(ig,l-1)*zpspsk(ig,l)+RLvCp*zqla_est(ig,l)
1189        ztva_est(ig,l) = ztva_est(ig,l)/zpspsk(ig,l)
1190        zta_est(ig,l)=ztva_est(ig,l)
1191        ztva_est(ig,l) = ztva_est(ig,l)*(1.+RETV*(zqta(ig,l-1)  &
1192     &      -zqla_est(ig,l))-zqla_est(ig,l))
1193
1194             w_est(ig,l+1)=zw2(ig,l)*  &
1195     &                   ((f_star(ig,l))**2)  &
1196     &                   /(f_star(ig,l)+alim_star(ig,l))**2+  &
1197     &                   2.*RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)  &
1198!     &                   *1./3. &
1199     &                   *(zlev(ig,l+1)-zlev(ig,l))
1200             if (w_est(ig,l+1).lt.0.) then
1201                w_est(ig,l+1)=zw2(ig,l)
1202             endif
1203!
1204!calcul du detrainement
1205!=======================
1206
1207!CR:on vire les modifs
1208         if (iflag_thermals_ed==0) then
1209
1210! Modifications du calcul du detrainement.
1211! Dans la version de la these de Catherine, on passe brusquement
1212! de la version seche a la version nuageuse pour le detrainement
1213! ce qui peut occasioner des oscillations.
1214! dans la nouvelle version, on commence par calculer un detrainement sec.
1215! Puis un autre en cas de nuages.
1216! Puis on combine les deux lineairement en fonction de la quantite d'eau.
1217
1218#define int1d3
1219!#undef int1d3
1220#define RIO_TH
1221#ifdef RIO_TH
1222!1. Cas non nuageux
1223! 1.1 on est sous le zmax_sec et w croit
1224          if ((w_est(ig,l+1).gt.w_est(ig,l)).and.  &
1225     &       (zlev(ig,l+1).lt.zmax_sec(ig)).and.  &
1226#ifdef int1d3
1227     &       (zqla_est(ig,l).lt.1.e-10)) then
1228#else
1229     &       (zqla(ig,l-1).lt.1.e-10)) then
1230#endif
1231             detr_star(ig,l)=MAX(0.,(rhobarz(ig,l+1)  &
1232     &       *sqrt(w_est(ig,l+1))*sqrt(l_mix*zlev(ig,l+1))  &
1233     &       -rhobarz(ig,l)*sqrt(w_est(ig,l))*sqrt(l_mix*zlev(ig,l)))  &
1234     &       /(r_aspect*zmax_sec(ig)))
1235             detr_stara(ig,l)=detr_star(ig,l)
1236
1237       if (prt_level.ge.20) print*,'coucou calcul detr 1: ig, l',ig,l
1238
1239! 1.2 on est sous le zmax_sec et w decroit
1240          else if ((zlev(ig,l+1).lt.zmax_sec(ig)).and.  &
1241#ifdef int1d3
1242     &            (zqla_est(ig,l).lt.1.e-10)) then
1243#else
1244     &            (zqla(ig,l-1).lt.1.e-10)) then
1245#endif
1246             detr_star(ig,l)=-f0(ig)*f_star(ig,lmix(ig))  &
1247     &       /(rhobarz(ig,lmix(ig))*wmaxa(ig))*  &
1248     &       (rhobarz(ig,l+1)*sqrt(w_est(ig,l+1))  &
1249     &       *((zmax_sec(ig)-zlev(ig,l+1))/  &
1250     &       ((zmax_sec(ig)-zlev(ig,lmix(ig)))))**2.  &
1251     &       -rhobarz(ig,l)*sqrt(w_est(ig,l))  &
1252     &       *((zmax_sec(ig)-zlev(ig,l))/  &
1253     &       ((zmax_sec(ig)-zlev(ig,lmix(ig)))))**2.)
1254             detr_starb(ig,l)=detr_star(ig,l)
1255
1256        if (prt_level.ge.20) print*,'coucou calcul detr 2: ig, l',ig,l
1257
1258          else
1259
1260! 1.3 dans les autres cas
1261             detr_star(ig,l)=0.002*f0(ig)*f_star(ig,l)  &
1262     &                      *(zlev(ig,l+1)-zlev(ig,l))
1263             detr_starc(ig,l)=detr_star(ig,l)
1264
1265        if (prt_level.ge.20) print*,'coucou calcul detr 3 n: ig, l',ig, l
1266             
1267          endif
1268
1269#else
1270
1271! 1.1 on est sous le zmax_sec et w croit
1272          if ((w_est(ig,l+1).gt.w_est(ig,l)).and.  &
1273     &       (zlev(ig,l+1).lt.zmax_sec(ig)) ) then
1274             detr_star(ig,l)=MAX(0.,(rhobarz(ig,l+1)  &
1275     &       *sqrt(w_est(ig,l+1))*sqrt(l_mix*zlev(ig,l+1))  &
1276     &       -rhobarz(ig,l)*sqrt(w_est(ig,l))*sqrt(l_mix*zlev(ig,l)))  &
1277     &       /(r_aspect*zmax_sec(ig)))
1278
1279       if (prt_level.ge.20) print*,'coucou calcul detr 1: ig, l', ig, l
1280
1281! 1.2 on est sous le zmax_sec et w decroit
1282          else if ((zlev(ig,l+1).lt.zmax_sec(ig)) ) then
1283             detr_star(ig,l)=-f0(ig)*f_star(ig,lmix(ig))  &
1284     &       /(rhobarz(ig,lmix(ig))*wmaxa(ig))*  &
1285     &       (rhobarz(ig,l+1)*sqrt(w_est(ig,l+1))  &
1286     &       *((zmax_sec(ig)-zlev(ig,l+1))/  &
1287     &       ((zmax_sec(ig)-zlev(ig,lmix(ig)))))**2.  &
1288     &       -rhobarz(ig,l)*sqrt(w_est(ig,l))  &
1289     &       *((zmax_sec(ig)-zlev(ig,l))/  &
1290     &       ((zmax_sec(ig)-zlev(ig,lmix(ig)))))**2.)
1291       if (prt_level.ge.20) print*,'coucou calcul detr 1: ig, l', ig, l
1292
1293          else
1294             detr_star=0.
1295          endif
1296
1297! 1.3 dans les autres cas
1298          detr_starc(ig,l)=0.002*f0(ig)*f_star(ig,l)  &
1299     &                      *(zlev(ig,l+1)-zlev(ig,l))
1300
1301          coefc=min(zqla(ig,l-1)/1.e-3,1.)
1302          if (zlev(ig,l+1).ge.zmax_sec(ig)) coefc=1.
1303          coefc=1.
1304! il semble qu'il soit important de baser le calcul sur
1305! zqla_est(ig,l-1) plutot que sur zqla_est(ig,l)
1306          detr_star(ig,l)=detr_starc(ig,l)*coefc+detr_star(ig,l)*(1.-coefc)
1307
1308        if (prt_level.ge.20) print*,'coucou calcul detr 2: ig, l', ig, l
1309
1310#endif
1311
1312
1313        if (prt_level.ge.20) print*,'coucou calcul detr 444: ig, l', ig, l
1314!IM 730508 beg
1315!        if(itap.GE.7200) THEN
1316!         print*,'th_plume ig,l,itap,zqla_est=',ig,l,itap,zqla_est(ig,l)
1317!        endif
1318!IM 730508 end
1319         
1320         zqla0(ig,l)=zqla_est(ig,l)
1321         detr_star0(ig,l)=detr_star(ig,l)
1322!IM 060508 beg
1323!         if(detr_star(ig,l).GT.1.) THEN
1324!          print*,'th_plumeBEF ig l detr_star detr_starc coefc',ig,l,detr_star(ig,l) &
1325!   &      ,detr_starc(ig,l),coefc
1326!         endif
1327!IM 060508 end
1328!IM 160508 beg
1329!IM 160508       IF (f0(ig).NE.0.) THEN
1330           detr_star(ig,l)=detr_star(ig,l)/f0(ig)
1331!IM 160508       ELSE IF(detr_star(ig,l).EQ.0.) THEN
1332!IM 160508        print*,'WARNING1  : th_plume f0=0, detr_star=0: ig, l, itap',ig,l,itap
1333!IM 160508       ELSE
1334!IM 160508        print*,'WARNING2  : th_plume f0=0, ig, l, itap, detr_star',ig,l,itap,detr_star(ig,l)
1335!IM 160508       ENDIF
1336!IM 160508 end
1337!IM 060508 beg
1338!        if(detr_star(ig,l).GT.1.) THEN
1339!         print*,'th_plumeAFT ig l detr_star f0 1/f0',ig,l,detr_star(ig,l),f0(ig), &
1340!   &     float(1)/f0(ig)
1341!        endif
1342!IM 060508 end
1343        if (prt_level.ge.20) print*,'coucou calcul detr 445: ig, l', ig, l
1344!
1345!calcul de entr_star
1346
1347! #undef test2
1348! #ifdef test2
1349! La version test2 destabilise beaucoup le modele.
1350! Il semble donc que ca aide d'avoir un entrainement important sous
1351! le nuage.
1352!         if (zqla_est(ig,l-1).ge.1.e-10.and.l.gt.lalim(ig)) then
1353!          entr_star(ig,l)=0.4*detr_star(ig,l)
1354!         else
1355!          entr_star(ig,l)=0.
1356!         endif
1357! #else
1358!
1359! Deplacement du calcul de entr_star pour eviter d'avoir aussi
1360! entr_star > fstar.
1361! Redeplacer suite a la transformation du cas detr>f
1362! FH
1363
1364        if (prt_level.ge.20) print*,'coucou calcul detr 446: ig, l', ig, l
1365#define int1d
1366!FH 070508 #define int1d4
1367!#undef int1d4
1368! L'option int1d4 correspond au choix dans le cas ou le detrainement
1369! devient trop grand.
1370
1371#ifdef int1d
1372
1373#ifdef int1d4
1374#else
1375       detr_star(ig,l)=min(detr_star(ig,l),f_star(ig,l))
1376!FH 070508 plus
1377       detr_star(ig,l)=min(detr_star(ig,l),1.)
1378#endif
1379
1380       entr_star(ig,l)=max(0.4*detr_star(ig,l)-alim_star(ig,l),0.)
1381
1382        if (prt_level.ge.20) print*,'coucou calcul detr 447: ig, l', ig, l
1383#ifdef int1d4
1384! Si le detrainement excede le flux en bas + l'entrainement, le thermique
1385! doit disparaitre.
1386       if (detr_star(ig,l)>f_star(ig,l)+entr_star(ig,l)) then
1387          detr_star(ig,l)=f_star(ig,l)+entr_star(ig,l)
1388          f_star(ig,l+1)=0.
1389          linter(ig)=l+1
1390          zw2(ig,l+1)=-1.e-10
1391       endif
1392#endif
1393
1394
1395#else
1396
1397        if (prt_level.ge.20) print*,'coucou calcul detr 448: ig, l', ig, l
1398        if(l.gt.lalim(ig)) then
1399         entr_star(ig,l)=0.4*detr_star(ig,l)
1400        else
1401
1402! FH :
1403! Cette ligne doit permettre de garantir qu'on a toujours un flux = 1
1404! en haut de la couche d'alimentation.
1405! A remettre en questoin a la premiere occasion mais ca peut aider a
1406! ecrire un code robuste.
1407! Que ce soit avec ca ou avec l'ancienne facon de faire (e* = 0 mais
1408! d* non nul) on a une discontinuité de e* ou d* en haut de la couche
1409! d'alimentation, ce qui n'est pas forcement heureux.
1410
1411        if (prt_level.ge.20) print*,'coucou calcul detr 449: ig, l', ig, l
1412#undef pre_int1c
1413#ifdef pre_int1c
1414         entr_star(ig,l)=max(detr_star(ig,l)-alim_star(ig,l),0.)
1415         detr_star(ig,l)=entr_star(ig,l)
1416#else
1417         entr_star(ig,l)=0.
1418#endif
1419
1420        endif
1421
1422#endif
1423
1424        if (prt_level.ge.20) print*,'coucou calcul detr 440: ig, l', ig, l
1425        entr_star1(ig,l)=entr_star(ig,l)
1426        detr_star1(ig,l)=detr_star(ig,l)
1427!
1428
1429#ifdef int1d
1430#else
1431        if (detr_star(ig,l).gt.f_star(ig,l)) then
1432
1433!  Ce test est là entre autres parce qu'on passe par des valeurs
1434!  delirantes de detr_star.
1435!  ca vaut sans doute le coup de verifier pourquoi.
1436
1437           detr_star(ig,l)=f_star(ig,l)
1438#ifdef pre_int1c
1439           if (l.gt.lalim(ig)+1) then
1440               entr_star(ig,l)=0.
1441               alim_star(ig,l)=0.
1442! FH ajout pour forcer a stoper le thermique juste sous le sommet
1443! de la couche (voir calcul de finter)
1444               zw2(ig,l+1)=-1.e-10
1445               linter(ig)=l+1
1446            else
1447               entr_star(ig,l)=0.4*detr_star(ig,l)
1448            endif
1449#else
1450           entr_star(ig,l)=0.4*detr_star(ig,l)
1451#endif
1452        endif
1453#endif
1454
1455      else !l > 2
1456         detr_star(ig,l)=0.
1457         entr_star(ig,l)=0.
1458      endif
1459
1460        entr_star2(ig,l)=entr_star(ig,l)
1461        detr_star2(ig,l)=detr_star(ig,l)
1462        if (prt_level.ge.20) print*,'coucou calcul detr 450: ig, l', ig, l
1463
1464       endif  ! iflag_thermals_ed==0
1465
1466!CR:nvlle def de entr_star et detr_star
1467      if (iflag_thermals_ed>=1) then
1468!      if (l.lt.lalim(ig)) then
1469!      if (l.lt.2) then
1470!        entr_star(ig,l)=0.
1471!        detr_star(ig,l)=0.
1472!      else
1473!      if (0.001.gt.(RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l))/(2.*w_est(ig,l+1)))) then
1474!         entr_star(ig,l)=0.001*f_star(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
1475!      else
1476!         entr_star(ig,l)=  &
1477!     &                f_star(ig,l)/(2.*w_est(ig,l+1))        &
1478!     &                *RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l))   &
1479!     &                *(zlev(ig,l+1)-zlev(ig,l))
1480
1481 
1482         entr_star(ig,l)=MAX(0.*f_star(ig,l)*(zlev(ig,l+1)-zlev(ig,l)),  &         
1483     &                f_star(ig,l)/(2.*w_est(ig,l+1))        &
1484     &                *RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)   &
1485     &                *(zlev(ig,l+1)-zlev(ig,l))) &
1486     &                +0.0001*f_star(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
1487
1488        if (((ztva_est(ig,l)-ztv(ig,l)).gt.1.e-10).and.(l.le.lmix_bis(ig))) then
1489            alim_star_tot(ig)=alim_star_tot(ig)+entr_star(ig,l)
1490            lalim(ig)=lmix_bis(ig)
1491            if(prt_level.GE.10) print*,'alim_star_tot',alim_star_tot(ig),entr_star(ig,l)
1492        endif
1493
1494        if (((ztva_est(ig,l)-ztv(ig,l)).gt.1.e-10).and.(l.le.lmix_bis(ig))) then
1495!        c2(ig,l)=2500000.*zqla_est(ig,l)/(1004.*zta_est(ig,l))
1496         c2(ig,l)=0.001
1497         detr_star(ig,l)=MAX(0.*f_star(ig,l)*(zlev(ig,l+1)-zlev(ig,l)),  &
1498     &                c2(ig,l)*f_star(ig,l)*(zlev(ig,l+1)-zlev(ig,l)) &
1499     &                -f_star(ig,l)/(2.*w_est(ig,l+1))       &
1500     &                *RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)       &
1501     &                *(zlev(ig,l+1)-zlev(ig,l)))                    &
1502     &                +0.0001*f_star(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
1503
1504       else
1505!         c2(ig,l)=2500000.*zqla_est(ig,l)/(1004.*zta_est(ig,l))
1506          c2(ig,l)=0.003
1507
1508         detr_star(ig,l)=MAX(0.*f_star(ig,l)*(zlev(ig,l+1)-zlev(ig,l)),  &
1509     &                c2(ig,l)*f_star(ig,l)*(zlev(ig,l+1)-zlev(ig,l)) &
1510     &                -f_star(ig,l)/(2.*w_est(ig,l+1))       &
1511     &                *RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)       &
1512     &                *(zlev(ig,l+1)-zlev(ig,l))) &
1513     &                +0.0002*f_star(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
1514       endif
1515         
1516           
1517!        detr_star(ig,l)=detr_star(ig,l)*3.
1518!        if (l.lt.lalim(ig)) then
1519!          entr_star(ig,l)=0.
1520!        endif
1521!        if (l.lt.2) then
1522!          entr_star(ig,l)=0.
1523!          detr_star(ig,l)=0.
1524!        endif
1525
1526
1527!      endif
1528!      else if ((ztva_est(ig,l)-ztv(ig,l)).gt.1.e-10) then
1529!      entr_star(ig,l)=MAX(0.,0.8*f_star(ig,l)/(2.*w_est(ig,l+1))        &
1530!     &                *RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l))   &
1531!     &                *(zlev(ig,l+1)-zlev(ig,l))
1532!      detr_star(ig,l)=0.002*f_star(ig,l)                         &
1533!     &                *(zlev(ig,l+1)-zlev(ig,l))
1534!      else
1535!      entr_star(ig,l)=0.001*f_star(ig,l)                         &
1536!     &                *(zlev(ig,l+1)-zlev(ig,l))
1537!      detr_star(ig,l)=MAX(0.,-0.2*f_star(ig,l)/(2.*w_est(ig,l+1))       &
1538!     &                *RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l))       &
1539!     &                *(zlev(ig,l+1)-zlev(ig,l))                      &
1540!     &                +0.002*f_star(ig,l)                             &
1541!     &                *(zlev(ig,l+1)-zlev(ig,l))
1542!      endif
1543
1544      endif   ! iflag_thermals_ed==1
1545
1546!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1547! FH inutile si on conserve comme on l'a fait plus haut entr=detr
1548! dans la couche d'alimentation
1549!pas d entrainement dans la couche alim
1550!      if ((l.le.lalim(ig))) then
1551!           entr_star(ig,l)=0.
1552!      endif
1553!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1554!
1555!prise en compte du detrainement et de l entrainement dans le calcul du flux
1556
1557      f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
1558     &              -detr_star(ig,l)
1559
1560!test sur le signe de f_star
1561        if (prt_level.ge.20) print*,'coucou calcul detr 451: ig, l', ig, l
1562       if (f_star(ig,l+1).gt.1.e-10) then
1563!----------------------------------------------------------------------------
1564!calcul de la vitesse verticale en melangeant Tl et qt du thermique
1565!---------------------------------------------------------------------------
1566!
1567       Zsat=.false.
1568       ztla(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
1569     &            (alim_star(ig,l)+entr_star(ig,l))*zthl(ig,l))  &
1570     &            /(f_star(ig,l+1)+detr_star(ig,l))
1571!
1572       zqta(ig,l)=(f_star(ig,l)*zqta(ig,l-1)+  &
1573     &            (alim_star(ig,l)+entr_star(ig,l))*po(ig,l))  &
1574     &            /(f_star(ig,l+1)+detr_star(ig,l))
1575
1576               Tbef=ztla(ig,l)*zpspsk(ig,l)
1577               zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
1578               qsatbef= R2ES * FOEEW(Tbef,zdelta)/pplev(ig,l)               
1579               qsatbef=MIN(0.5,qsatbef)
1580               zcor=1./(1.-retv*qsatbef)
1581               qsatbef=qsatbef*zcor
1582               Zsat = (max(0.,zqta(ig,l)-qsatbef) .gt. 1.e-10)
1583               if (Zsat) then
1584               qlbef=max(0.,zqta(ig,l)-qsatbef)
1585               DT = 0.5*RLvCp*qlbef
1586               do while (abs(DT).gt.DDT0)
1587                 Tbef=Tbef+DT
1588                 zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
1589                 qsatbef= R2ES * FOEEW(Tbef,zdelta)/pplev(ig,l)
1590                 qsatbef=MIN(0.5,qsatbef)
1591                 zcor=1./(1.-retv*qsatbef)
1592                 qsatbef=qsatbef*zcor
1593                 qlbef=zqta(ig,l)-qsatbef
1594
1595                 zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
1596                 zcvm5=R5LES*(1.-zdelta) + R5IES*zdelta
1597                 zcor=1./(1.-retv*qsatbef)
1598                 dqsat_dT=FOEDE(Tbef,zdelta,zcvm5,qsatbef,zcor)
1599                 num=-Tbef+ztla(ig,l)*zpspsk(ig,l)+RLvCp*qlbef
1600                 denom=1.+RLvCp*dqsat_dT
1601                 DT=num/denom
1602              enddo
1603                 zqla(ig,l) = max(0.,qlbef)
1604              endif
1605!   
1606        if (prt_level.ge.20) print*,'coucou calcul detr 4512: ig, l', ig, l
1607! on ecrit de maniere conservative (sat ou non)
1608!          T = Tl +Lv/Cp ql
1609           ztva(ig,l) = ztla(ig,l)*zpspsk(ig,l)+RLvCp*zqla(ig,l)
1610           ztva(ig,l) = ztva(ig,l)/zpspsk(ig,l)
1611!on rajoute le calcul de zha pour diagnostiques (temp potentielle)
1612           zha(ig,l) = ztva(ig,l)
1613           ztva(ig,l) = ztva(ig,l)*(1.+RETV*(zqta(ig,l)  &
1614     &              -zqla(ig,l))-zqla(ig,l))
1615
1616!on ecrit zqsat
1617           zqsatth(ig,l)=qsatbef 
1618!calcul de vitesse
1619           zw2(ig,l+1)=zw2(ig,l)*  &
1620     &                 ((f_star(ig,l))**2)  &
1621!  Tests de Catherine
1622!     &                 /(f_star(ig,l+1)+detr_star(ig,l))**2+             &
1623     &      /(f_star(ig,l+1)+detr_star(ig,l)-entr_star(ig,l)*(1.-fact_epsilon))**2+ &
1624     &                 2.*RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)  &
1625     &                 *fact_gamma &
1626     &                 *(zlev(ig,l+1)-zlev(ig,l))
1627!prise en compte des forces de pression que qd flottabilité<0
1628!              zw2(ig,l+1)=zw2(ig,l)*  &
1629!     &            1./(1.+2.*entr_star(ig,l)/f_star(ig,l)) + &       
1630!     &                 (f_star(ig,l))**2 &
1631!     &                 /(f_star(ig,l)+entr_star(ig,l))**2+ &
1632!     &                 (f_star(ig,l)-2.*entr_star(ig,l))**2/(f_star(ig,l)+2.*entr_star(ig,l))**2+  &       
1633!     &                 /(f_star(ig,l+1)+detr_star(ig,l)-entr_star(ig,l)*(1.-2.))**2+ &
1634!     &                 /(f_star(ig,l)**2+2.*2.*detr_star(ig,l)*f_star(ig,l)+2.*entr_star(ig,l)*f_star(ig,l))+ &
1635!     &                 2.*RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)  &
1636!     &                 *1./3. &
1637!     &                 *(zlev(ig,l+1)-zlev(ig,l))
1638         
1639!        write(30,*),l+1,zw2(ig,l+1)-zw2(ig,l), &
1640!     &              -2.*entr_star(ig,l)/f_star(ig,l)*zw2(ig,l), &
1641!     &               2.*RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
1642
1643 
1644!             zw2(ig,l+1)=zw2(ig,l)*  &
1645!     &                 (2.-2.*entr_star(ig,l)/f_star(ig,l)) & 
1646!     &                 -zw2(ig,l-1)+  &       
1647!     &                 2.*RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)  &
1648!     &                 *1./3. &
1649!     &                 *(zlev(ig,l+1)-zlev(ig,l))             
1650
1651            endif
1652        endif
1653        if (prt_level.ge.20) print*,'coucou calcul detr 460: ig, l',ig, l
1654!
1655!initialisations pour le calcul de la hauteur du thermique, de l'inversion et de la vitesse verticale max
1656
1657            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
1658!               stop'On tombe sur le cas particulier de thermcell_dry'
1659                print*,'On tombe sur le cas particulier de thermcell_plume'
1660                zw2(ig,l+1)=0.
1661                linter(ig)=l+1
1662            endif
1663
1664!        if ((zw2(ig,l).gt.0.).and. (zw2(ig,l+1).le.0.)) then
1665        if (zw2(ig,l+1).lt.0.) then
1666           linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
1667     &               -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
1668           zw2(ig,l+1)=0.
1669        endif
1670
1671           wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
1672
1673        if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
1674!   lmix est le niveau de la couche ou w (wa_moy) est maximum
1675!on rajoute le calcul de lmix_bis
1676            if (zqla(ig,l).lt.1.e-10) then
1677               lmix_bis(ig)=l+1
1678            endif
1679            lmix(ig)=l+1
1680            wmaxa(ig)=wa_moy(ig,l+1)
1681        endif
1682        enddo
1683      enddo
1684
1685!on remplace a* par e* ds premiere couche
1686!      if (iflag_thermals_ed.ge.1) then
1687!       do ig=1,ngrid
1688!       do l=2,klev
1689!          if (l.lt.lalim(ig)) then
1690!             alim_star(ig,l)=entr_star(ig,l)
1691!          endif
1692!       enddo
1693!       enddo
1694!       do ig=1,ngrid
1695!          lalim(ig)=lmix_bis(ig)
1696!       enddo
1697!      endif
1698       if (iflag_thermals_ed.ge.1) then
1699          do ig=1,ngrid
1700             do l=2,lalim(ig)
1701                alim_star(ig,l)=entr_star(ig,l)
1702                entr_star(ig,l)=0.
1703             enddo
1704           enddo
1705       endif
1706        if (prt_level.ge.20) print*,'coucou calcul detr 470: ig, l', ig, l
1707
1708!     print*,'thermcell_plume OK'
1709
1710      return
1711      end
1712!==============================================================================
1713       SUBROUTINE thermcellV0_dry(ngrid,nlay,zlev,pphi,ztv,alim_star,  &
1714     &                            lalim,lmin,zmax,wmax,lev_out)
1715
1716!--------------------------------------------------------------------------
1717!thermcell_dry: calcul de zmax et wmax du thermique sec
1718!--------------------------------------------------------------------------
1719       IMPLICIT NONE
1720#include "YOMCST.h"       
1721#include "iniprint.h"
1722       INTEGER l,ig
1723
1724       INTEGER ngrid,nlay
1725       REAL zlev(ngrid,nlay+1)
1726       REAL pphi(ngrid,nlay)
1727       REAl ztv(ngrid,nlay)
1728       REAL alim_star(ngrid,nlay)
1729       INTEGER lalim(ngrid)
1730      integer lev_out                           ! niveau pour les print
1731
1732       REAL zmax(ngrid)
1733       REAL wmax(ngrid)
1734
1735!variables locales
1736       REAL zw2(ngrid,nlay+1)
1737       REAL f_star(ngrid,nlay+1)
1738       REAL ztva(ngrid,nlay+1)
1739       REAL wmaxa(ngrid)
1740       REAL wa_moy(ngrid,nlay+1)
1741       REAL linter(ngrid),zlevinter(ngrid)
1742       INTEGER lmix(ngrid),lmax(ngrid),lmin(ngrid)
1743
1744!initialisations
1745       do ig=1,ngrid
1746          do l=1,nlay+1
1747             zw2(ig,l)=0.
1748             wa_moy(ig,l)=0.
1749          enddo
1750       enddo
1751       do ig=1,ngrid
1752          do l=1,nlay
1753             ztva(ig,l)=ztv(ig,l)
1754          enddo
1755       enddo
1756       do ig=1,ngrid
1757          wmax(ig)=0.
1758          wmaxa(ig)=0.
1759       enddo
1760!calcul de la vitesse a partir de la CAPE en melangeant thetav
1761
1762!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1763! A eliminer
1764! Ce if complique etait fait pour reperer la premiere couche instable
1765! Ici, c'est lmin.
1766!
1767!       do l=1,nlay-2
1768!         do ig=1,ngrid
1769!            if (ztv(ig,l).gt.ztv(ig,l+1)  &
1770!     &         .and.alim_star(ig,l).gt.1.e-10  &
1771!     &         .and.zw2(ig,l).lt.1e-10) then
1772!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1773
1774
1775! Calcul des F^*, integrale verticale de E^*
1776       f_star(:,1)=0.
1777       do l=1,nlay
1778          f_star(:,l+1)=f_star(:,l)+alim_star(:,l)
1779       enddo
1780
1781! niveau (reel) auquel zw2 s'annule FH :n'etait pas initialise
1782       linter(:)=0.
1783
1784! couche la plus haute concernee par le thermique.
1785       lmax(:)=1
1786
1787! Le niveau linter est une variable continue qui se trouve dans la couche
1788! lmax
1789
1790       do l=1,nlay-2
1791         do ig=1,ngrid
1792            if (l.eq.lmin(ig).and.lalim(ig).gt.1) then
1793
1794!------------------------------------------------------------------------
1795!  Calcul de la vitesse en haut de la premiere couche instable.
1796!  Premiere couche du panache thermique
1797!------------------------------------------------------------------------
1798               zw2(ig,l+1)=2.*RG*(ztv(ig,l)-ztv(ig,l+1))/ztv(ig,l+1)  &
1799     &                     *(zlev(ig,l+1)-zlev(ig,l))  &
1800     &                     *0.4*pphi(ig,l)/(pphi(ig,l+1)-pphi(ig,l))
1801
1802!------------------------------------------------------------------------
1803! Tant que la vitesse en bas de la couche et la somme du flux de masse
1804! et de l'entrainement (c'est a dire le flux de masse en haut) sont
1805! positifs, on calcul
1806! 1. le flux de masse en haut  f_star(ig,l+1)
1807! 2. la temperature potentielle virtuelle dans la couche ztva(ig,l)
1808! 3. la vitesse au carré en haut zw2(ig,l+1)
1809!------------------------------------------------------------------------
1810
1811!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1812!  A eliminer : dans cette version, si zw2 est > 0 on a un therique.
1813!  et donc, au dessus, f_star(ig,l+1) est forcement suffisamment
1814!  grand puisque on n'a pas de detrainement.
1815!  f_star est une fonction croissante.
1816!  c'est donc vraiment sur zw2 uniquement qu'il faut faire le test.
1817!           else if ((zw2(ig,l).ge.1e-10).and.  &
1818!    &               (f_star(ig,l)+alim_star(ig,l).gt.1.e-10)) then
1819!              f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)
1820!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1821
1822            else if (zw2(ig,l).ge.1e-10) then
1823
1824               ztva(ig,l)=(f_star(ig,l)*ztva(ig,l-1)+alim_star(ig,l)  &
1825     &                    *ztv(ig,l))/f_star(ig,l+1)
1826               zw2(ig,l+1)=zw2(ig,l)*(f_star(ig,l)/f_star(ig,l+1))**2+  &
1827     &                     2.*RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)  &
1828     &                     *(zlev(ig,l+1)-zlev(ig,l))
1829            endif
1830! determination de zmax continu par interpolation lineaire
1831!------------------------------------------------------------------------
1832
1833            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
1834!               stop'On tombe sur le cas particulier de thermcell_dry'
1835!               print*,'On tombe sur le cas particulier de thermcell_dry'
1836                zw2(ig,l+1)=0.
1837                linter(ig)=l+1
1838                lmax(ig)=l
1839            endif
1840
1841            if (zw2(ig,l+1).lt.0.) then
1842               linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
1843     &           -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
1844               zw2(ig,l+1)=0.
1845               lmax(ig)=l
1846            endif
1847
1848               wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
1849
1850            if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
1851!   lmix est le niveau de la couche ou w (wa_moy) est maximum
1852               lmix(ig)=l+1
1853               wmaxa(ig)=wa_moy(ig,l+1)
1854            endif
1855         enddo
1856      enddo
1857       if (prt_level.ge.1) print*,'fin calcul zw2'
1858!
1859!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1860! A eliminer :
1861! Ce calcul de lmax est fait en meme temps que celui de linter, plus haut
1862! Calcul de la couche correspondant a la hauteur du thermique
1863!      do ig=1,ngrid
1864!         lmax(ig)=lalim(ig)
1865!      enddo
1866!      do ig=1,ngrid
1867!         do l=nlay,lalim(ig)+1,-1
1868!            if (zw2(ig,l).le.1.e-10) then
1869!               lmax(ig)=l-1
1870!            endif
1871!         enddo
1872!      enddo
1873!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1874
1875!   
1876! Determination de zw2 max
1877      do ig=1,ngrid
1878         wmax(ig)=0.
1879      enddo
1880
1881      do l=1,nlay
1882         do ig=1,ngrid
1883            if (l.le.lmax(ig)) then
1884                zw2(ig,l)=sqrt(zw2(ig,l))
1885                wmax(ig)=max(wmax(ig),zw2(ig,l))
1886            else
1887                 zw2(ig,l)=0.
1888            endif
1889          enddo
1890      enddo
1891
1892!   Longueur caracteristique correspondant a la hauteur des thermiques.
1893      do  ig=1,ngrid
1894         zmax(ig)=0.
1895         zlevinter(ig)=zlev(ig,1)
1896      enddo
1897      do  ig=1,ngrid
1898! calcul de zlevinter
1899
1900!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1901! FH A eliminer
1902! Simplification
1903!          zlevinter(ig)=(zlev(ig,lmax(ig)+1)-zlev(ig,lmax(ig)))*  &
1904!     &    linter(ig)+zlev(ig,lmax(ig))-lmax(ig)*(zlev(ig,lmax(ig)+1)  &
1905!     &    -zlev(ig,lmax(ig)))
1906!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1907
1908          zlevinter(ig)=zlev(ig,lmax(ig)) + &
1909     &    (linter(ig)-lmax(ig))*(zlev(ig,lmax(ig)+1)-zlev(ig,lmax(ig)))
1910           zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,lmin(ig)))
1911      enddo
1912
1913! Verification que lalim<=lmax
1914      do ig=1,ngrid
1915         if(lalim(ig)>lmax(ig)) then
1916           if ( prt_level > 1 ) THEN
1917            print*,'WARNING thermcell_dry ig=',ig,'  lalim=',lalim(ig),'  lmax(ig)=',lmax(ig)
1918           endif
1919           lmax(ig)=lalim(ig)
1920         endif
1921      enddo
1922     
1923      RETURN
1924      END
1925!==============================================================================
1926      SUBROUTINE thermcellV0_init(ngrid,nlay,ztv,zlay,zlev,  &
1927     &                  lalim,lmin,alim_star,alim_star_tot,lev_out)
1928
1929!----------------------------------------------------------------------
1930!thermcell_init: calcul du profil d alimentation du thermique
1931!----------------------------------------------------------------------
1932      IMPLICIT NONE
1933#include "iniprint.h"
1934#include "thermcell.h"
1935
1936      INTEGER l,ig
1937!arguments d entree
1938      INTEGER ngrid,nlay
1939      REAL ztv(ngrid,nlay)
1940      REAL zlay(ngrid,nlay)
1941      REAL zlev(ngrid,nlay+1)
1942!arguments de sortie
1943      INTEGER lalim(ngrid)
1944      INTEGER lmin(ngrid)
1945      REAL alim_star(ngrid,nlay)
1946      REAL alim_star_tot(ngrid)
1947      integer lev_out                           ! niveau pour les print
1948     
1949      REAL zzalim(ngrid)
1950!CR: ponderation entrainement des couches instables
1951!def des alim_star tels que alim=f*alim_star     
1952
1953      do l=1,nlay
1954         do ig=1,ngrid
1955            alim_star(ig,l)=0.
1956         enddo
1957      enddo
1958! determination de la longueur de la couche d entrainement
1959      do ig=1,ngrid
1960         lalim(ig)=1
1961      enddo
1962
1963      if (iflag_thermals_ed.ge.1) then
1964!si la première couche est instable, on declenche un thermique
1965         do ig=1,ngrid
1966            if (ztv(ig,1).gt.ztv(ig,2)) then
1967               lmin(ig)=1
1968               lalim(ig)=2
1969               alim_star(ig,1)=1.
1970               alim_star_tot(ig)=alim_star(ig,1)
1971               if(prt_level.GE.10) print*,'init',alim_star(ig,1),alim_star_tot(ig)
1972            else
1973                lmin(ig)=1
1974                lalim(ig)=1
1975                alim_star(ig,1)=0.
1976                alim_star_tot(ig)=0.
1977            endif
1978         enddo
1979 
1980         else
1981!else iflag_thermals_ed=0 ancienne def de l alim
1982
1983!on ne considere que les premieres couches instables
1984      do l=nlay-2,1,-1
1985         do ig=1,ngrid
1986            if (ztv(ig,l).gt.ztv(ig,l+1).and.  &
1987     &          ztv(ig,l+1).le.ztv(ig,l+2)) then
1988               lalim(ig)=l+1
1989            endif
1990          enddo
1991      enddo
1992
1993! determination du lmin: couche d ou provient le thermique
1994
1995      do ig=1,ngrid
1996! FH initialisation de lmin a nlay plutot que 1.
1997!        lmin(ig)=nlay
1998         lmin(ig)=1
1999      enddo
2000      do l=nlay,2,-1
2001         do ig=1,ngrid
2002            if (ztv(ig,l-1).gt.ztv(ig,l)) then
2003               lmin(ig)=l-1
2004            endif
2005         enddo
2006      enddo
2007!
2008      zzalim(:)=0.
2009      do l=1,nlay-1
2010         do ig=1,ngrid
2011             if (l<lalim(ig)) then
2012                zzalim(ig)=zzalim(ig)+zlay(ig,l)*(ztv(ig,l)-ztv(ig,l+1))
2013             endif
2014          enddo
2015      enddo
2016      do ig=1,ngrid
2017          if (lalim(ig)>1) then
2018             zzalim(ig)=zlay(ig,1)+zzalim(ig)/(ztv(ig,1)-ztv(ig,lalim(ig)))
2019          else
2020             zzalim(ig)=zlay(ig,1)
2021          endif
2022      enddo
2023
2024      if(prt_level.GE.10) print*,'ZZALIM LALIM ',zzalim,lalim,zlay(1,lalim(1))
2025
2026! definition de l'entrainement des couches
2027      if (1.eq.1) then
2028      do l=1,nlay-1
2029         do ig=1,ngrid
2030            if (ztv(ig,l).gt.ztv(ig,l+1).and.  &
2031     &          l.ge.lmin(ig).and.l.lt.lalim(ig)) then
2032!def possibles pour alim_star: zdthetadz, dthetadz, zdtheta
2033             alim_star(ig,l)=MAX((ztv(ig,l)-ztv(ig,l+1)),0.)  &
2034     &                       *sqrt(zlev(ig,l+1))
2035            endif
2036         enddo
2037      enddo
2038      else
2039      do l=1,nlay-1
2040         do ig=1,ngrid
2041            if (ztv(ig,l).gt.ztv(ig,l+1).and.  &
2042     &          l.ge.lmin(ig).and.l.lt.lalim(ig)) then
2043             alim_star(ig,l)=max(3.*zzalim(ig)-zlay(ig,l),0.) &
2044     &        *(zlev(ig,l+1)-zlev(ig,l))
2045            endif
2046         enddo
2047      enddo
2048      endif
2049     
2050! pas de thermique si couche 1 stable
2051      do ig=1,ngrid
2052!CRnouveau test
2053        if (alim_star(ig,1).lt.1.e-10) then
2054            do l=1,nlay
2055                alim_star(ig,l)=0.
2056            enddo
2057            lmin(ig)=1
2058         endif
2059      enddo
2060! calcul de l alimentation totale
2061      do ig=1,ngrid
2062         alim_star_tot(ig)=0.
2063      enddo
2064      do l=1,nlay
2065         do ig=1,ngrid
2066            alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
2067         enddo
2068      enddo
2069!
2070! Calcul entrainement normalise
2071      do l=1,nlay
2072         do ig=1,ngrid
2073            if (alim_star_tot(ig).gt.1.e-10) then
2074               alim_star(ig,l)=alim_star(ig,l)/alim_star_tot(ig)
2075            endif
2076         enddo
2077      enddo
2078       
2079!on remet alim_star_tot a 1
2080      do ig=1,ngrid
2081         alim_star_tot(ig)=1.
2082      enddo
2083
2084      endif
2085!endif iflag_thermals_ed
2086      return
2087      end 
2088!==============================================================================
Note: See TracBrowser for help on using the repository browser.