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

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

Optimisation des thermiques

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