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

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