source: LMDZ4/branches/LMDZ4V5.0-LF/libf/phylmd/thermcellV0_main.F90 @ 1317

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

Nettoyage general pour se rapprocher des normes et éviter des erreurs a la
compilation:

  • tous les FLOAT() sont remplacés par des REAL()
  • tous les STOP dans phylmd sont remplacés par des appels à abort_gcm
  • le common control défini dans le fichier control.h est remplacé par le module control_mod pour éviter des messages sur l'alignement des variables dans les déclarations
  • des $Header$ remplacés par des $Id$ pour svn

Quelques remplacements à faire ont pu m'échapper


General cleanup of the code to try and adhere to norms and to prevent some
compilation errors:

  • all FLOAT() instructions have been replaced by REAL() instructions
  • all STOP instructions in phylmd have been replaced by calls to abort_gcm
  • the common block control defined in the control.h file has been replaced by the control_mod to prevent compilation warnings on the alignement of declared variables
  • $Header$ replaced by $Id$ for svn

Some changes which should have been made might have escaped me

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