source: trunk/LMDZ.MARS/libf/phymars/thermcell_main_mars.F90 @ 616

Last change on this file since 616 was 616, checked in by acolaitis, 13 years ago

Forgot to mask some diagnostic outputs from thermals in previous commit

File size: 53.1 KB
Line 
1!
2!
3      SUBROUTINE thermcell_main_mars(ptimestep  &
4     &                  ,pplay,pplev,pphi,zlev,zlay  &
5     &                  ,pu,pv,pt,pq,pq2  &
6     &                  ,pduadj,pdvadj,pdtadj,pdqadj,pdq2adj  &
7     &                  ,fm,entr,detr,lmax,zmax  &
8     &                  ,r_aspect &
9     &                  ,zw2,fraca &
10     &                  ,zpopsk,ztla,heatFlux,heatFlux_down &
11     &                  ,buoyancyOut, buoyancyEst)
12
13      IMPLICIT NONE
14
15!=======================================================================
16! Mars version of thermcell_main. Author : A Colaitis
17!=======================================================================
18
19#include "dimensions.h"
20#include "dimphys.h"
21#include "comcstfi.h"
22#include "tracer.h"
23#include "callkeys.h"
24
25! ============== INPUTS ==============
26
27      REAL, INTENT(IN) :: ptimestep,r_aspect
28      REAL, INTENT(IN) :: pt(ngridmx,nlayermx)
29      REAL, INTENT(IN) :: pu(ngridmx,nlayermx)
30      REAL, INTENT(IN) :: pv(ngridmx,nlayermx)
31      REAL, INTENT(IN) :: pq(ngridmx,nlayermx,nqmx)
32      REAL, INTENT(IN) :: pq2(ngridmx,nlayermx)
33      REAL, INTENT(IN) :: pplay(ngridmx,nlayermx)
34      REAL, INTENT(IN) :: pplev(ngridmx,nlayermx+1)
35      REAL, INTENT(IN) :: pphi(ngridmx,nlayermx)
36      REAL, INTENT(IN) :: zlay(ngridmx,nlayermx)
37      REAL, INTENT(IN) :: zlev(ngridmx,nlayermx+1)
38
39! ============== OUTPUTS ==============
40
41      REAL, INTENT(OUT) :: pdtadj(ngridmx,nlayermx)
42      REAL :: pduadj(ngridmx,nlayermx)
43      REAL :: pdvadj(ngridmx,nlayermx)
44      REAL :: pdqadj(ngridmx,nlayermx,nqmx)
45!      REAL, INTENT(OUT) :: pdq2adj(ngridmx,nlayermx)
46      REAL :: pdq2adj(ngridmx,nlayermx)
47      REAL, INTENT(OUT) :: zw2(ngridmx,nlayermx+1)
48
49! Diagnostics
50      REAL, INTENT(OUT) :: heatFlux(ngridmx,nlayermx)   ! interface heatflux
51     REAL, INTENT(OUT) :: heatFlux_down(ngridmx,nlayermx) ! interface heat flux from downdraft
52!      REAL, INTENT(OUT) :: buoyancyOut(ngridmx,nlayermx)  ! interlayer buoyancy term
53!      REAL, INTENT(OUT) :: buoyancyEst(ngridmx,nlayermx)  ! interlayer estimated buoyancy term
54
55! dummy variables when output not needed :
56
57!      REAL :: heatFlux(ngridmx,nlayermx)   ! interface heatflux
58!      REAL :: heatFlux_down(ngridmx,nlayermx) ! interface heat flux from downdraft
59      REAL :: buoyancyOut(ngridmx,nlayermx)  ! interlayer buoyancy term
60      REAL :: buoyancyEst(ngridmx,nlayermx)  ! interlayer estimated buoyancy term
61
62
63! ============== LOCAL ================
64
65      INTEGER ig,k,l,ll,iq
66      INTEGER lmax(ngridmx),lmin(ngridmx),lalim(ngridmx)
67      REAL linter(ngridmx)
68      REAL zmax(ngridmx)
69      REAL ztva(ngridmx,nlayermx),zw_est(ngridmx,nlayermx+1),ztva_est(ngridmx,nlayermx)
70      REAL zmax_sec(ngridmx)
71      REAL zh(ngridmx,nlayermx)
72      REAL zdthladj(ngridmx,nlayermx)
73      REAL zdthladj_down(ngridmx,nlayermx)
74      REAL ztvd(ngridmx,nlayermx)
75      REAL ztv(ngridmx,nlayermx)
76      REAL zu(ngridmx,nlayermx),zv(ngridmx,nlayermx),zo(ngridmx,nlayermx)
77      REAL zva(ngridmx,nlayermx)
78      REAL zua(ngridmx,nlayermx)
79
80      REAL zta(ngridmx,nlayermx)
81      REAL fraca(ngridmx,nlayermx+1)
82      REAL q2(ngridmx,nlayermx)
83      REAL rho(ngridmx,nlayermx),rhobarz(ngridmx,nlayermx),masse(ngridmx,nlayermx)
84      REAL zpopsk(ngridmx,nlayermx)
85
86      REAL wmax(ngridmx)
87      REAL wmax_sec(ngridmx)
88      REAL fm(ngridmx,nlayermx+1),entr(ngridmx,nlayermx),detr(ngridmx,nlayermx)
89
90      REAL fm_down(ngridmx,nlayermx+1)
91
92      REAL ztla(ngridmx,nlayermx)
93
94      REAL f_star(ngridmx,nlayermx+1),entr_star(ngridmx,nlayermx)
95      REAL detr_star(ngridmx,nlayermx)
96      REAL alim_star_tot(ngridmx)
97      REAL alim_star(ngridmx,nlayermx)
98      REAL alim_star_clos(ngridmx,nlayermx)
99      REAL f(ngridmx)
100
101      REAL teta_th_int(ngridmx,nlayermx)
102      REAL teta_env_int(ngridmx,nlayermx)
103      REAL teta_down_int(ngridmx,nlayermx)
104
105      CHARACTER (LEN=20) :: modname
106      CHARACTER (LEN=80) :: abort_message
107
108! ============= PLUME VARIABLES ============
109
110      REAL w_est(ngridmx,nlayermx+1)
111      REAL wa_moy(ngridmx,nlayermx+1)
112      REAL wmaxa(ngridmx)
113      REAL zdz,zbuoy(ngridmx,nlayermx),zw2m
114      LOGICAL activecell(ngridmx),activetmp(ngridmx)
115      REAL a1,b1,ae,be,ad,bd,fdfu,b1inv,a1inv,omega,adalim
116      INTEGER tic
117
118! ==========================================
119
120! ============= HEIGHT VARIABLES ===========
121
122      REAL num(ngridmx)
123      REAL denom(ngridmx)
124      REAL zlevinter(ngridmx)
125
126! =========================================
127
128! ============= CLOSURE VARIABLES =========
129
130      REAL zdenom(ngridmx)
131      REAL alim_star2(ngridmx)
132      REAL alim_star_tot_clos(ngridmx)
133      INTEGER llmax
134
135! =========================================
136
137! ============= FLUX2 VARIABLES ===========
138
139      INTEGER ncorecfm1,ncorecfm2,ncorecfm3,ncorecalpha
140      INTEGER ncorecfm4,ncorecfm5,ncorecfm6,ncorecfm7,ncorecfm8
141      REAL zfm
142      REAL f_old,ddd0,eee0,ddd,eee,zzz
143      REAL fomass_max,alphamax
144
145! =========================================
146
147! ============= DTETA VARIABLES ===========
148
149! rien : on prends la divergence du flux turbulent
150
151! =========================================
152
153! ============= DV2 VARIABLES =============
154!               not used for now
155
156      REAL qa(ngridmx,nlayermx),detr_dv2(ngridmx,nlayermx),zf,zf2
157      REAL wvd(ngridmx,nlayermx+1),wud(ngridmx,nlayermx+1)
158      REAL gamma0(ngridmx,nlayermx+1),gamma(ngridmx,nlayermx+1)
159      REAL ue(ngridmx,nlayermx),ve(ngridmx,nlayermx)
160      LOGICAL ltherm(ngridmx,nlayermx)
161      REAL dua(ngridmx,nlayermx),dva(ngridmx,nlayermx)
162      INTEGER iter
163      INTEGER nlarga0
164
165! =========================================
166
167! ============== Theta_M Variables ========
168
169      INTEGER ico2
170      SAVE ico2
171      REAL m_co2, m_noco2, A , B
172      SAVE A, B
173      LOGICAL firstcall
174      save firstcall
175      data firstcall/.true./
176      REAL zhc(ngridmx,nlayermx)
177      REAL zdzfull(ngridmx,nlayermx)
178      REAL ratiom(ngridmx,nlayermx)
179
180! =========================================
181
182!-----------------------------------------------------------------------
183!   initialisation:
184!   ---------------
185
186      entr(:,:)=0.
187      detr(:,:)=0.
188      fm(:,:)=0.
189!      zu(:,:)=pu(:,:)
190!      zv(:,:)=pv(:,:)
191      zhc(:,:)=pt(:,:)/zpopsk(:,:)
192
193! **********************************************************************
194! Taking into account vertical molar mass gradients
195! **********************************************************************
196
197      if(firstcall) then
198        ico2=0
199        if (tracer) then
200!     Prepare Special treatment if one of the tracers is CO2 gas
201           do iq=1,nqmx
202             if (noms(iq).eq."co2") then
203                ico2=iq
204                m_co2 = 44.01E-3  ! CO2 molecular mass (kg/mol)
205                m_noco2 = 33.37E-3  ! Non condensible mol mass (kg/mol)
206!               Compute A and B coefficient use to compute
207!               mean molecular mass Mair defined by
208!               1/Mair = q(ico2)/m_co2 + (1-q(ico2))/m_noco2
209!               1/Mair = A*q(ico2) + B
210                A =(1/m_co2 - 1/m_noco2)
211                B=1/m_noco2
212             end if
213           enddo
214        endif
215
216      firstcall=.false.
217      endif !of if firstcall
218
219!.......................................................................
220!  Special treatment for co2
221!.......................................................................
222
223      if (ico2.ne.0) then
224!     Special case if one of the tracers is CO2 gas
225         DO l=1,nlayermx
226           DO ig=1,ngridmx
227            ztv(ig,l) = zhc(ig,l)*(A*pq(ig,l,ico2)+B)
228           ENDDO
229         ENDDO
230       else
231          ztv(:,:)=zhc(:,:)
232       end if
233
234
235!------------------------------------------------------------------------
236!                       --------------------
237!
238!
239!                       + + + + + + + + + + +
240!
241!
242!  wa, fraca, wd, fracd --------------------   zlev(2), rhobarz
243!  wh,wt,wo ...
244!
245!                       + + + + + + + + + + +  zh,zu,zv,zo,rho
246!
247!
248!                       --------------------   zlev(1)
249!                       \\\\\\\\\\\\\\\\\\\\
250!
251!
252
253!-----------------------------------------------------------------------
254!   Calcul des altitudes des couches
255!-----------------------------------------------------------------------
256
257!      do l=2,nlayermx
258!         zlev(:,l)=0.5*(pphi(:,l)+pphi(:,l-1))/g
259!      enddo
260!         zlev(:,1)=0.
261!         zlev(:,nlayermx+1)=(2.*pphi(:,nlayermx)-pphi(:,nlayermx-1))/g
262
263!         zlay(:,:)=pphi(:,:)/g
264!-----------------------------------------------------------------------
265!   Calcul des densites
266!-----------------------------------------------------------------------
267
268      rho(:,:)=pplay(:,:)/(r*pt(:,:))
269
270      rhobarz(:,1)=rho(:,1)
271
272      do l=2,nlayermx
273         rhobarz(:,l)=0.5*(rho(:,l)+rho(:,l-1))
274      enddo
275
276!calcul de la masse
277      do l=1,nlayermx
278         masse(:,l)=(pplev(:,l)-pplev(:,l+1))/g
279      enddo
280
281
282!------------------------------------------------------------------
283!
284!             /|\
285!    --------  |  F_k+1 -------   
286!                              ----> D_k
287!             /|\              <---- E_k , A_k
288!    --------  |  F_k ---------
289!                              ----> D_k-1
290!                              <---- E_k-1 , A_k-1
291!
292!
293!    ---------------------------
294!
295!    ----- F_lmax+1=0 ----------         \
296!            lmax     (zmax)              |
297!    ---------------------------          |
298!                                         |
299!    ---------------------------          |
300!                                         |
301!    ---------------------------          |
302!                                         |
303!    ---------------------------          |
304!                                         |
305!    ---------------------------          |
306!                                         |  E
307!    ---------------------------          |  D
308!                                         |
309!    ---------------------------          |
310!                                         |
311!    ---------------------------  \       |
312!            lalim                 |      |
313!    ---------------------------   |      |
314!                                  |      |
315!    ---------------------------   |      |
316!                                  | A    |
317!    ---------------------------   |      |
318!                                  |      |
319!    ---------------------------   |      |
320!    lmin  (=1 pour le moment)     |      |
321!    ----- F_lmin=0 ------------  /      /
322!
323!    ---------------------------
324!    //////////////////////////
325!
326
327!=============================================================================
328!  Calculs initiaux ne faisant pas intervenir les changements de phase
329!=============================================================================
330
331!------------------------------------------------------------------
332!  1. alim_star est le profil vertical de l'alimentation a la base du
333!     panache thermique, calcule a partir de la flotabilite de l'air sec
334!  2. lmin et lalim sont les indices inferieurs et superieurs de alim_star
335!------------------------------------------------------------------
336!
337      entr_star=0. ; detr_star=0. ; alim_star=0. ; alim_star_tot=0.
338      lmin=1
339
340!-----------------------------------------------------------------------------
341!  3. wmax_sec et zmax_sec sont les vitesses et altitudes maximum d'un
342!     panache sec conservatif (e=d=0) alimente selon alim_star
343!     Il s'agit d'un calcul de type CAPE
344!     zmax_sec est utilise pour determiner la geometrie du thermique.
345!------------------------------------------------------------------------------
346!---------------------------------------------------------------------------------
347!calcul du melange et des variables dans le thermique
348!--------------------------------------------------------------------------------
349
350! ===========================================================================
351! ===================== PLUME ===============================================
352! ===========================================================================
353
354! Initialisations des variables reeles
355      ztva(:,:)=ztv(:,:)
356      ztva_est(:,:)=ztva(:,:)
357      ztla(:,:)=0.
358      zdz=0.
359      zbuoy(:,:)=0.
360      w_est(:,:)=0.
361      f_star(:,:)=0.
362      wa_moy(:,:)=0.
363      linter(:)=1.
364
365! --------------------------------------------------------------------------
366! -------------- MAIN PARAMETERS FOR THERMALS MODEL ------------------------
367! --------------  see thermiques.pro and getfit.py -------------------------
368
369!      a1=2.5 ; b1=0.0015 ; ae=0.045 ; be = 0.6  ! svn baseline
370
371! Using broad downdraft selection
372!      a1=1.60226 ; b1=0.0006 ; ae=0.0454 ; be = 0.57
373!      ad = 0.0005114  ; bd = -0.662
374!      fdfu = -1.9
375
376! Using conditional sampling downdraft selection
377      a1=1.4716 ; b1=0.0005698 ; ae=0.03683 ; be = 0.57421
378      ad = 0.00048088  ; bd = -0.6697
379      fdfu = -1.3
380      a1inv=a1
381      b1inv=b1
382      omega=0.
383      adalim=0.
384
385! One good config for 34/35 levels
386!      a1inv=a1
387!      b1inv=b1
388!      be=1.1*be
389
390! Best configuration for 222 levels:
391
392!      omega=0.06
393!      b1=0.
394!      a1=1.
395!      a1inv=0.25*a1
396!      b1inv=0.0002
397!!
398!!
399!!      ae=0.9*ae
400
401! Best config for norad 222 levels:
402
403       omega=0.06
404!       omega=0.
405       a1=1.
406!       b1=0.
407       b1=0.0001
408       a1inv=a1
409       be=1.1*be
410       ad = 0.0004
411       adalim=0.
412       b1inv=0.00025
413!       b1inv = 0.0003
414
415!      omega=0.06
416! Trying stuff :
417
418!      ad=0.00035
419!      ae=0.95*ae
420!      b1=0.00055
421!      omega=0.04
422!
423!      ad = 0.0003
424!      ae=0.9*ae
425
426!      omega=0.04
427!!      b1=0.
428!      a1=1.
429!      a1inv=a1
430!      b1inv=0.0005689
431!!      be=1.1*be
432!!      ae=0.96*ae
433
434
435!       omega=0.06
436!       a1=1.
437!       b1=0.
438!       be=be
439!       a1inv=0.25*a1
440!       b1inv=0.0002   
441!       ad=1.1*ad
442!       ae=1.*ae
443! --------------------------------------------------------------------------
444! --------------------------------------------------------------------------
445! --------------------------------------------------------------------------
446
447! Initialisation des variables entieres
448      wmaxa(:)=0.
449      lalim(:)=1
450
451!-------------------------------------------------------------------------
452! On ne considere comme actif que les colonnes dont les deux premieres
453! couches sont instables.
454!-------------------------------------------------------------------------
455      activecell(:)=ztv(:,1)>ztv(:,2)
456          do ig=1,ngridmx
457            if (ztv(ig,1)>=(ztv(ig,2))) then
458               alim_star(ig,1)=MAX((ztv(ig,1)-ztv(ig,2)),0.)  &
459!     &                       *log(1.+zlev(ig,2))
460     &                       *sqrt(zlev(ig,2))
461!     &                       *sqrt(sqrt(zlev(ig,2)))
462!     &                       /sqrt(zlev(ig,2))
463!      &                       *zlev(ig,2)
464!      &                     *exp(-zlev(ig,2)/1000.)
465               lalim(ig)=2
466               alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,1)
467            endif
468         enddo
469
470       do l=2,nlayermx-1
471!        do l=2,4
472         do ig=1,ngridmx
473           if (ztv(ig,l)>(ztv(ig,l+1)+0.) .and. ztv(ig,1)>=ztv(ig,l) .and. (alim_star(ig,l-1) .ne. 0.)) then ! .and. (zlev(ig,l+1) .lt. 1000.)) then
474               alim_star(ig,l)=MAX((ztv(ig,l)-ztv(ig,l+1)),0.)  &
475!     &                       *log(1.+zlev(ig,l+1))
476     &                       *sqrt(zlev(ig,l+1))
477!     &                       *sqrt(sqrt(zlev(ig,l+1)))
478!     &                       /sqrt(zlev(ig,l+1))
479!      &                       *zlev(ig,l+1)
480!      &                     *exp(-zlev(ig,l+1)/1000.)
481                lalim(ig)=l+1
482               alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
483           endif
484        enddo
485      enddo
486      do l=1,nlayermx
487         do ig=1,ngridmx
488            if (alim_star_tot(ig) > 1.e-10 ) then
489               alim_star(ig,l)=alim_star(ig,l)/alim_star_tot(ig)
490            endif
491         enddo
492      enddo
493
494      alim_star_tot(:)=1.
495!      if(alim_star(1,1) .ne. 0.) then
496!      print*, 'lalim star' ,lalim(1)
497!      endif
498
499!------------------------------------------------------------------------------
500! Calcul dans la premiere couche
501! On decide dans cette version que le thermique n'est actif que si la premiere
502! couche est instable.
503! Pourrait etre change si on veut que le thermiques puisse se déclencher
504! dans une couche l>1
505!------------------------------------------------------------------------------
506
507      do ig=1,ngridmx
508! Le panache va prendre au debut les caracteristiques de l'air contenu
509! dans cette couche.
510          if (activecell(ig)) then
511          ztla(ig,1)=ztv(ig,1)
512!cr: attention, prise en compte de f*(1)=1 => AC : what ? f*(1) =0. ! (d'ou f*(2)=a*(1)
513! dans un panache conservatif
514          f_star(ig,1)=0.
515         
516          f_star(ig,2)=alim_star(ig,1)
517
518          zw2(ig,2)=2.*g*(ztv(ig,1)-ztv(ig,2))/ztv(ig,2)  &
519      &                     *(zlev(ig,2)-zlev(ig,1))  &
520      &                    *0.4*pphi(ig,1)/(pphi(ig,2)-pphi(ig,1))
521          w_est(ig,2)=zw2(ig,2)
522
523          endif
524      enddo
525
526
527!==============================================================================
528!boucle de calcul de la vitesse verticale dans le thermique
529!==============================================================================
530      do l=2,nlayermx-1
531!==============================================================================
532
533
534! On decide si le thermique est encore actif ou non
535! AFaire : Il faut sans doute ajouter entr_star a alim_star dans ce test
536          do ig=1,ngridmx
537             activecell(ig)=activecell(ig) &
538      &                 .and. zw2(ig,l)>1.e-10 &
539      &                 .and. f_star(ig,l)+alim_star(ig,l)>1.e-10
540          enddo
541
542!---------------------------------------------------------------------------
543! calcul des proprietes thermodynamiques et de la vitesse de la couche l
544! sans tenir compte du detrainement et de l'entrainement dans cette
545! couche
546! C'est a dire qu'on suppose
547! ztla(l)=ztla(l-1)
548! Ici encore, on doit pouvoir ajouter entr_star (qui peut etre calculer
549! avant) a l'alimentation pour avoir un calcul plus propre
550!---------------------------------------------------------------------------
551
552          do ig=1,ngridmx
553             if(activecell(ig)) then
554!                if(l .lt. lalim(ig)) then
555!               ztva_est(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
556!     &            alim_star(ig,l)*ztv(ig,l))  &
557!     &            /(f_star(ig,l)+alim_star(ig,l))
558!                else
559                ztva_est(ig,l)=ztla(ig,l-1)
560!                endif
561
562                zdz=zlev(ig,l+1)-zlev(ig,l)
563                zbuoy(ig,l)=g*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
564
565                if (((a1*zbuoy(ig,l)/w_est(ig,l)-b1) .gt. 0.) .and. (w_est(ig,l) .ne. 0.)) then
566                w_est(ig,l+1)=Max(0.0001,w_est(ig,l)+2.*zdz*a1*zbuoy(ig,l)-2.*zdz*w_est(ig,l)*b1 &
567     & -2.*(1.-omega)*zdz*w_est(ig,l)*ae*(a1*zbuoy(ig,l)/w_est(ig,l)-b1)**be)
568                else
569                w_est(ig,l+1)=Max(0.0001,w_est(ig,l)+2.*zdz*a1inv*zbuoy(ig,l)-2.*zdz*w_est(ig,l)*b1inv)
570                endif
571                if (w_est(ig,l+1).lt.0.) then
572                w_est(ig,l+1)=zw2(ig,l)
573                endif
574             endif
575          enddo
576
577!-------------------------------------------------
578!calcul des taux d'entrainement et de detrainement
579!-------------------------------------------------
580
581      do ig=1,ngridmx
582        if (activecell(ig)) then
583
584          zw2m=w_est(ig,l+1)
585
586          if((a1*(zbuoy(ig,l)/zw2m)-b1) .gt. 0.) then
587          entr_star(ig,l)=f_star(ig,l)*zdz*  &
588        &   MAX(0.,ae*(a1*(zbuoy(ig,l)/zw2m)-b1)**be)
589!         &  MAX(0.,log(1. + 0.03*sqrt(a1*(zbuoy(ig,l)/zw2m)-b1)))
590          else
591          entr_star(ig,l)=0.
592          endif
593
594          if(zbuoy(ig,l) .gt. 0.) then
595             if(l .lt. lalim(ig)) then
596
597!                detr_star(ig,l)=0.
598                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
599            &  adalim
600             else
601
602!                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
603!              &     0.0105*((zbuoy(ig,l)/zw2m)/0.048)**(1./1.7)
604!                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
605!              &     0.0085*((zbuoy(ig,l)/zw2m)/0.05)**(1./1.55)
606
607! last baseline from direct les
608!                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
609!               &     0.065*(2.5*(zbuoy(ig,l)/zw2m))**0.75
610
611! new param from continuity eq with a fit on dfdz
612                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
613            &  ad
614!             &  Max(0., 0.0005 - 0.55*zbuoy(ig,l)/zw2m)
615
616!               &     MAX(0.,-0.38*zbuoy(ig,l)/zw2m+0.0005)   !svn baseline
617!                &     MAX(0.,-0.38*zbuoy(ig,l)/zw2m+0.0008)     
618
619!              &     0.014*((zbuoy(ig,l)/zw2m)/0.05)**(1./1.35)
620!                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
621!              &     ((zbuoy(ig,l)/zw2m)/2.222)! + 0.0002)
622
623             endif
624          else
625          detr_star(ig,l)=f_star(ig,l)*zdz*                        &
626                &     MAX(ad,bd*zbuoy(ig,l)/zw2m)
627!             &  Max(0., 0.001 - 0.45*zbuoy(ig,l)/zw2m)
628!             &  Max(0., Min(0.001,0.0005 - 0.55*zbuoy(ig,l)/zw2m))
629
630
631!               &     MAX(0.,-0.38*zbuoy(ig,l)/zw2m+0.0005)      !svn baseline
632
633!              &  *5.*(-afact*zbetalpha*zbuoy(ig,l)/zw2m)
634!              &  *5.*(-afact*zbuoy(ig,l)/zw2m)
635
636! last baseline from direct les
637!               &     0.065*(-2.5*(zbuoy(ig,l)/zw2m))**0.75
638
639! new param from continuity eq with a fit on dfdz
640
641
642          endif
643
644! En dessous de lalim, on prend le max de alim_star et entr_star pour
645! alim_star et 0 sinon
646
647       if (l.lt.lalim(ig)) then
648          alim_star(ig,l)=max(alim_star(ig,l),entr_star(ig,l))
649          entr_star(ig,l)=0.
650       endif
651
652! Calcul du flux montant normalise
653
654      f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
655     &              -detr_star(ig,l)
656
657      endif
658      enddo
659
660
661!----------------------------------------------------------------------------
662!calcul de la vitesse verticale en melangeant Tl et qt du thermique
663!---------------------------------------------------------------------------
664
665      DO tic=0,5  ! internal convergence loop
666      activetmp(:)=activecell(:) .and. f_star(:,l+1)>1.e-10
667      do ig=1,ngridmx
668       if (activetmp(ig)) then
669
670           ztla(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
671     &            (alim_star(ig,l)+entr_star(ig,l))*ztv(ig,l))  &
672     &            /(f_star(ig,l+1)+detr_star(ig,l))
673
674        endif
675      enddo
676
677      activetmp(:)=activetmp(:).and.(abs(ztla(:,l)-ztva(:,l)).gt.0.01)
678
679      do ig=1,ngridmx
680      if (activetmp(ig)) then
681           ztva(ig,l) = ztla(ig,l)
682           zbuoy(ig,l)=g*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
683
684           if (((a1*zbuoy(ig,l)/zw2(ig,l)-b1) .gt. 0.) .and. (zw2(ig,l) .ne. 0.) ) then
685           zw2(ig,l+1)=Max(0.,zw2(ig,l)+2.*zdz*a1*zbuoy(ig,l)-         &
686     & 2.*zdz*zw2(ig,l)*b1-2.*(1.-omega)*zdz*zw2(ig,l)*ae*(a1*zbuoy(ig,l)/zw2(ig,l)-b1)**be)
687           else
688           zw2(ig,l+1)=Max(0.,zw2(ig,l)+2.*zdz*a1inv*zbuoy(ig,l)-2.*zdz*zw2(ig,l)*b1inv)
689           endif
690      endif
691      enddo
692
693! ================ RECOMPUTE ENTR, DETR, and F FROM NEW W2 ===================
694
695      do ig=1,ngridmx
696        if (activetmp(ig)) then
697
698          zw2m=zw2(ig,l+1)
699          if(zw2m .gt. 0) then
700          if((a1*(zbuoy(ig,l)/zw2m)-b1) .gt. 0.) then
701          entr_star(ig,l)=f_star(ig,l)*zdz*  &
702        &   MAX(0.,ae*(a1*(zbuoy(ig,l)/zw2m)-b1)**be)
703!         &  MAX(0.,log(1. + 0.03*sqrt(a1*(zbuoy(ig,l)/zw2m)-b1)))
704          else
705          entr_star(ig,l)=0.
706          endif
707
708          if(zbuoy(ig,l) .gt. 0.) then
709             if(l .lt. lalim(ig)) then
710
711!                detr_star(ig,l)=0.
712                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
713            &  adalim
714
715             else
716                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
717            &  ad
718!             &  Max(0., 0.0005 - 0.55*zbuoy(ig,l)/zw2m)
719
720             endif
721          else
722          detr_star(ig,l)=f_star(ig,l)*zdz*                        &
723                &     MAX(ad,bd*zbuoy(ig,l)/zw2m)
724!             &  Max(0.,Min(0.001,0.0005 - 0.55*zbuoy(ig,l)/zw2m))
725
726          endif
727          else
728          entr_star(ig,l)=0.
729          detr_star(ig,l)=0.
730          endif
731
732! En dessous de lalim, on prend le max de alim_star et entr_star pour
733! alim_star et 0 sinon
734
735        if (l.lt.lalim(ig)) then
736          alim_star(ig,l)=max(alim_star(ig,l),entr_star(ig,l))
737          entr_star(ig,l)=0.
738        endif
739
740! Calcul du flux montant normalise
741
742      f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
743     &              -detr_star(ig,l)
744
745      endif
746      enddo
747 
748      ENDDO   ! of tic
749
750!---------------------------------------------------------------------------
751!initialisations pour le calcul de la hauteur du thermique, de l'inversion et de la vitesse verticale max
752!---------------------------------------------------------------------------
753
754      do ig=1,ngridmx
755            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
756      IF (lwrite) THEN
757             print*,'On tombe sur le cas particulier de thermcell_plume'
758      ENDIF
759                zw2(ig,l+1)=0.
760                linter(ig)=l+1
761            endif
762
763        if (zw2(ig,l+1).lt.0.) then
764           linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
765     &               -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
766           zw2(ig,l+1)=0.
767        endif
768           wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
769
770        if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
771!   lmix est le niveau de la couche ou w (wa_moy) est maximum
772            wmaxa(ig)=wa_moy(ig,l+1)
773        endif
774      enddo
775
776!=========================================================================
777! FIN DE LA BOUCLE VERTICALE
778      enddo
779!=========================================================================
780
781!on recalcule alim_star_tot
782       do ig=1,ngridmx
783          alim_star_tot(ig)=0.
784       enddo
785       do ig=1,ngridmx
786          do l=1,lalim(ig)-1
787          alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
788          enddo
789       enddo
790
791      do l=1,nlayermx
792         do ig=1,ngridmx
793            if (alim_star_tot(ig) > 1.e-10 ) then
794               alim_star(ig,l)=alim_star(ig,l)/alim_star_tot(ig)
795            endif
796         enddo
797      enddo
798
799! ===========================================================================
800! ================= FIN PLUME ===============================================
801! ===========================================================================
802
803! ===========================================================================
804! ================= HEIGHT ==================================================
805! ===========================================================================
806
807! Attention, w2 est transforme en sa racine carree dans cette routine
808
809!-------------------------------------------------------------------------------
810! Calcul des caracteristiques du thermique:zmax,wmax
811!-------------------------------------------------------------------------------
812
813!calcul de la hauteur max du thermique
814      do ig=1,ngridmx
815         lmax(ig)=lalim(ig)
816      enddo
817      do ig=1,ngridmx
818         do l=nlayermx,lalim(ig)+1,-1
819            if (zw2(ig,l).le.1.e-10) then
820               lmax(ig)=l-1
821            endif
822         enddo
823      enddo
824
825! On traite le cas particulier qu'il faudrait éviter ou le thermique
826! atteind le haut du modele ...
827      do ig=1,ngridmx
828      if ( zw2(ig,nlayermx) > 1.e-10 ) then
829          print*,'WARNING !!!!! W2 thermiques non nul derniere couche '
830          lmax(ig)=nlayermx
831      endif
832      enddo
833
834! pas de thermique si couche 1 stable
835!      do ig=1,ngridmx
836!         if (lmin(ig).gt.1) then
837!             lmax(ig)=1
838!             lmin(ig)=1
839!             lalim(ig)=1
840!         endif
841!      enddo
842!
843! Determination de zw2 max
844      do ig=1,ngridmx
845         wmax(ig)=0.
846      enddo
847
848      do l=1,nlayermx
849         do ig=1,ngridmx
850            if (l.le.lmax(ig)) then
851                if (zw2(ig,l).lt.0.)then
852                  print*,'pb2 zw2<0'
853                endif
854                zw2(ig,l)=sqrt(zw2(ig,l))
855                wmax(ig)=max(wmax(ig),zw2(ig,l))
856            else
857                 zw2(ig,l)=0.
858            endif
859          enddo
860      enddo
861!   Longueur caracteristique correspondant a la hauteur des thermiques.
862      do  ig=1,ngridmx
863         zmax(ig)=0.
864         zlevinter(ig)=zlev(ig,1)
865      enddo
866
867         num(:)=0.
868         denom(:)=0.
869         do ig=1,ngridmx
870          do l=1,nlayermx
871             num(ig)=num(ig)+zw2(ig,l)*zlev(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
872             denom(ig)=denom(ig)+zw2(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
873          enddo
874       enddo
875       do ig=1,ngridmx
876       if (denom(ig).gt.1.e-10) then
877          zmax(ig)=2.*num(ig)/denom(ig)
878       endif
879       enddo
880
881! Attention, w2 est transforme en sa racine carree dans cette routine
882
883! ===========================================================================
884! ================= FIN HEIGHT ==============================================
885! ===========================================================================
886
887! Choix de la fonction d'alimentation utilisee pour la fermeture.
888
889      alim_star_clos(:,:)=entr_star(:,:)+alim_star(:,:)
890
891! ===========================================================================
892! ============= CLOSURE =====================================================
893! ===========================================================================
894
895!-------------------------------------------------------------------------------
896! Fermeture,determination de f
897!-------------------------------------------------------------------------------
898! Appel avec la version seche
899
900      alim_star2(:)=0.
901      alim_star_tot_clos(:)=0.
902      f(:)=0.
903
904! Indice vertical max (max de lalim) atteint par les thermiques sur le domaine
905      llmax=1
906      do ig=1,ngridmx
907         if (lalim(ig)>llmax) llmax=lalim(ig)
908      enddo
909
910
911! Calcul des integrales sur la verticale de alim_star et de
912!   alim_star^2/(rho dz)
913      do k=1,llmax-1
914         do ig=1,ngridmx
915            if (k<lalim(ig)) then
916         alim_star2(ig)=alim_star2(ig)+alim_star_clos(ig,k)*alim_star_clos(ig,k)  &
917      &                    /(rho(ig,k)*(zlev(ig,k+1)-zlev(ig,k)))
918         alim_star_tot_clos(ig)=alim_star_tot_clos(ig)+alim_star_clos(ig,k)
919      endif
920         enddo
921      enddo
922 
923! WARNING : MARS MODIF : we have added 2. : ratio of wmax/vmoy
924! True ratio is 3.5 but wetake into account the vmoy is the one alimentating
925! the thermal, so there are vs=0 into the vmoy... the true vmoy is lower. (a la louche)
926! And r_aspect has been changed from 2 to 1.5 from observations
927      do ig=1,ngridmx
928         if (alim_star2(ig)>1.e-10) then
929!            f(ig)=wmax_sec(ig)*alim_star_tot_clos(ig)/  &
930!      &     (max(500.,zmax_sec(ig))*r_aspect*alim_star2(ig))
931             f(ig)=wmax(ig)*alim_star_tot_clos(ig)/  &
932      &     (max(500.,zmax(ig))*r_aspect*alim_star2(ig))
933
934         endif
935      enddo
936
937! ===========================================================================
938! ============= FIN CLOSURE =================================================
939! ===========================================================================
940
941
942! ===========================================================================
943! ============= FLUX2 =======================================================
944! ===========================================================================
945
946!-------------------------------------------------------------------------------
947!deduction des flux
948!-------------------------------------------------------------------------------
949
950      fomass_max=0.8
951      alphamax=0.5
952
953      ncorecfm1=0
954      ncorecfm2=0
955      ncorecfm3=0
956      ncorecfm4=0
957      ncorecfm5=0
958      ncorecfm6=0
959      ncorecfm7=0
960      ncorecfm8=0
961      ncorecalpha=0
962
963!-------------------------------------------------------------------------
964! Multiplication par le flux de masse issu de la femreture
965!-------------------------------------------------------------------------
966
967      do l=1,nlayermx
968         entr(:,l)=f(:)*(entr_star(:,l)+alim_star(:,l))
969         detr(:,l)=f(:)*detr_star(:,l)
970      enddo
971
972      do l=1,nlayermx
973         do ig=1,ngridmx
974            if (l.lt.lmax(ig)) then
975               fm(ig,l+1)=fm(ig,l)+entr(ig,l)-detr(ig,l)
976            elseif(l.eq.lmax(ig)) then
977               fm(ig,l+1)=0.
978               detr(ig,l)=fm(ig,l)+entr(ig,l)
979            else
980               fm(ig,l+1)=0.
981            endif
982         enddo
983      enddo
984
985! Test provisoire : pour comprendre pourquoi on corrige plein de fois
986! le cas fm6, on commence par regarder une premiere fois avant les
987! autres corrections.
988
989!      do l=1,nlayermx
990!         do ig=1,ngridmx
991!            if (detr(ig,l).gt.fm(ig,l)) then
992!               ncorecfm8=ncorecfm8+1
993!            endif
994!         enddo
995!      enddo
996
997!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
998! FH Version en cours de test;
999! par rapport a thermcell_flux, on fait une grande boucle sur "l"
1000! et on modifie le flux avec tous les contr�les appliques d'affilee
1001! pour la meme couche
1002! Momentanement, on duplique le calcule du flux pour pouvoir comparer
1003! les flux avant et apres modif
1004!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1005
1006      do l=1,nlayermx
1007
1008         do ig=1,ngridmx
1009            if (l.lt.lmax(ig)) then
1010               fm(ig,l+1)=fm(ig,l)+entr(ig,l)-detr(ig,l)
1011            elseif(l.eq.lmax(ig)) then
1012               fm(ig,l+1)=0.
1013               detr(ig,l)=fm(ig,l)+entr(ig,l)
1014            else
1015               fm(ig,l+1)=0.
1016            endif
1017         enddo
1018
1019
1020!-------------------------------------------------------------------------
1021! Verification de la positivite des flux de masse
1022!-------------------------------------------------------------------------
1023
1024         do ig=1,ngridmx
1025
1026            if (fm(ig,l+1).lt.0.) then
1027               if((l+1) .eq. lmax(ig)) then
1028               detr(ig,l)=detr(ig,l)+fm(ig,l+1)
1029               fm(ig,l+1)=0.
1030               entr(ig,l+1)=0.
1031               ncorecfm2=ncorecfm2+1
1032               else
1033               IF (lwrite) THEN
1034          print*,'fm(l+1)<0 : ig, l+1,lmax :',ig,l+1,lmax(ig),fm(ig,l+1)
1035               ENDIF
1036               ncorecfm1=ncorecfm1+1
1037               fm(ig,l+1)=fm(ig,l)
1038               detr(ig,l)=entr(ig,l)
1039               endif
1040            endif
1041
1042         enddo
1043
1044!  Les "optimisations" du flux sont desactivecelles : moins de bidouilles
1045!  je considere que celles ci ne sont pas justifiees ou trop delicates
1046!  pour MARS, d'apres des observations LES.
1047!-------------------------------------------------------------------------
1048!Test sur fraca croissant
1049!-------------------------------------------------------------------------
1050!      if (iflag_thermals_optflux==0) then
1051!         do ig=1,ngridmx
1052!          if (l.ge.lalim(ig).and.l.le.lmax(ig) &
1053!     &    .and.(zw2(ig,l+1).gt.1.e-10).and.(zw2(ig,l).gt.1.e-10) ) then
1054!!  zzz est le flux en l+1 a frac constant
1055!             zzz=fm(ig,l)*rhobarz(ig,l+1)*zw2(ig,l+1)  &
1056!     &                          /(rhobarz(ig,l)*zw2(ig,l))
1057!             if (fm(ig,l+1).gt.zzz) then
1058!                detr(ig,l)=detr(ig,l)+fm(ig,l+1)-zzz
1059!                fm(ig,l+1)=zzz
1060!                ncorecfm4=ncorecfm4+1
1061!             endif
1062!          endif
1063!        enddo
1064!      endif
1065!
1066!-------------------------------------------------------------------------
1067!test sur flux de masse croissant
1068!-------------------------------------------------------------------------
1069!      if (iflag_thermals_optflux==0) then
1070!         do ig=1,ngridmx
1071!            if ((fm(ig,l+1).gt.fm(ig,l)).and.(l.gt.lalim(ig))) then
1072!              f_old=fm(ig,l+1)
1073!              fm(ig,l+1)=fm(ig,l)
1074!              detr(ig,l)=detr(ig,l)+f_old-fm(ig,l+1)
1075!               ncorecfm5=ncorecfm5+1
1076!            endif
1077!         enddo
1078!      endif
1079!
1080!-------------------------------------------------------------------------
1081!detr ne peut pas etre superieur a fm
1082!-------------------------------------------------------------------------
1083
1084         do ig=1,ngridmx
1085            if (detr(ig,l).gt.fm(ig,l)) then
1086               ncorecfm6=ncorecfm6+1
1087               detr(ig,l)=fm(ig,l)
1088               entr(ig,l)=fm(ig,l+1)
1089
1090! Dans le cas ou on est au dessus de la couche d'alimentation et que le
1091! detrainement est plus fort que le flux de masse, on stope le thermique.
1092!            endif
1093
1094            if(l.gt.lmax(ig)) then
1095!            if(l.gt.lalim(ig)) then
1096               detr(ig,l)=0.
1097               fm(ig,l+1)=0.
1098               entr(ig,l)=0.
1099            endif
1100           
1101            endif
1102
1103         enddo
1104
1105!-------------------------------------------------------------------------
1106!fm ne peut pas etre negatif
1107!-------------------------------------------------------------------------
1108
1109         do ig=1,ngridmx
1110            if (fm(ig,l+1).lt.0.) then
1111               detr(ig,l)=detr(ig,l)+fm(ig,l+1)
1112               fm(ig,l+1)=0.
1113               ncorecfm2=ncorecfm2+1
1114            endif
1115         enddo
1116
1117!-----------------------------------------------------------------------
1118!la fraction couverte ne peut pas etre superieure a 1
1119!-----------------------------------------------------------------------
1120!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1121! FH Partie a revisiter.
1122! Il semble qu'etaient codees ici deux optiques dans le cas
1123! F/ (rho *w) > 1
1124! soit limiter la hauteur du thermique en considerant que c'est
1125! la derniere chouche, soit limiter F a rho w.
1126! Dans le second cas, il faut en fait limiter a un peu moins
1127! que ca parce qu'on a des 1 / ( 1 -alpha) un peu plus loin
1128! dans thermcell_main et qu'il semble de toutes facons deraisonable
1129! d'avoir des fractions de 1..
1130! Ci dessous, et dans l'etat actuel, le premier des  deux if est
1131! sans doute inutile.
1132!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1133
1134        do ig=1,ngridmx
1135           if (zw2(ig,l+1).gt.1.e-10) then
1136           zfm=rhobarz(ig,l+1)*zw2(ig,l+1)*alphamax
1137           if ( fm(ig,l+1) .gt. zfm) then
1138              f_old=fm(ig,l+1)
1139              fm(ig,l+1)=zfm
1140              detr(ig,l)=detr(ig,l)+f_old-fm(ig,l+1)
1141              ncorecalpha=ncorecalpha+1
1142           endif
1143           endif
1144
1145        enddo
1146
1147! Fin de la grande boucle sur les niveaux verticaux
1148      enddo
1149
1150!-----------------------------------------------------------------------
1151! On fait en sorte que la quantite totale d'air entraine dans le
1152! panache ne soit pas trop grande comparee a la masse de la maille
1153!-----------------------------------------------------------------------
1154
1155      do l=1,nlayermx-1
1156         do ig=1,ngridmx
1157            eee0=entr(ig,l)
1158            ddd0=detr(ig,l)
1159            eee=entr(ig,l)-masse(ig,l)*fomass_max/ptimestep
1160            ddd=detr(ig,l)-eee
1161            if (eee.gt.0.) then
1162                ncorecfm3=ncorecfm3+1
1163                entr(ig,l)=entr(ig,l)-eee
1164                if ( ddd.gt.0.) then
1165!   l'entrainement est trop fort mais l'exces peut etre compense par une
1166!   diminution du detrainement)
1167                   detr(ig,l)=ddd
1168                else
1169!   l'entrainement est trop fort mais l'exces doit etre compense en partie
1170!   par un entrainement plus fort dans la couche superieure
1171                   if(l.eq.lmax(ig)) then
1172                      detr(ig,l)=fm(ig,l)+entr(ig,l)
1173                   else
1174                      entr(ig,l+1)=entr(ig,l+1)-ddd
1175                      detr(ig,l)=0.
1176                      fm(ig,l+1)=fm(ig,l)+entr(ig,l)
1177                      detr(ig,l)=0.
1178                   endif
1179                endif
1180            endif
1181         enddo
1182      enddo
1183!
1184!              ddd=detr(ig)-entre
1185!on s assure que tout s annule bien en zmax
1186      do ig=1,ngridmx
1187         fm(ig,lmax(ig)+1)=0.
1188         entr(ig,lmax(ig))=0.
1189         detr(ig,lmax(ig))=fm(ig,lmax(ig))+entr(ig,lmax(ig))
1190      enddo
1191
1192!-----------------------------------------------------------------------
1193! Impression du nombre de bidouilles qui ont ete necessaires
1194!-----------------------------------------------------------------------
1195
1196!IM 090508 beg
1197      IF (lwrite) THEN
1198      if (ncorecfm1+ncorecfm2+ncorecfm3+ncorecfm4+ncorecfm5+ncorecalpha > ngridmx/4. ) then
1199         print*,'thermcell warning : large number of corrections'
1200         print*,'PB thermcell : on a du coriger ',ncorecfm1,'x fm1',&
1201     &     ncorecfm2,'x fm2',ncorecfm3,'x fm3 et', &
1202     &     ncorecfm4,'x fm4',ncorecfm5,'x fm5 et', &
1203     &     ncorecfm6,'x fm6', &
1204     &     ncorecfm7,'x fm7', &
1205     &     ncorecfm8,'x fm8', &
1206     &     ncorecalpha,'x alpha'
1207      endif
1208      ENDIF
1209
1210! ===========================================================================
1211! ============= FIN FLUX2 ===================================================
1212! ===========================================================================
1213
1214
1215! ===========================================================================
1216! ============= TRANSPORT ===================================================
1217! ===========================================================================
1218
1219!------------------------------------------------------------------
1220!   calcul du transport vertical
1221!------------------------------------------------------------------
1222
1223! ------------------------------------------------------------------
1224! Transport de teta dans l'updraft : (remplace thermcell_dq)
1225! ------------------------------------------------------------------
1226
1227      zdthladj(:,:)=0.
1228
1229      do ig=1,ngridmx
1230         if(lmax(ig) .gt. 1) then
1231         do k=1,lmax(ig)
1232            zdthladj(ig,k)=(1./masse(ig,k))*(fm(ig,k+1)*ztv(ig,k+1)-    &
1233     &   fm(ig,k)*ztv(ig,k)+fm(ig,k)*ztva(ig,k)-fm(ig,k+1)*ztva(ig,k+1))
1234            if (ztv(ig,k) + ptimestep*zdthladj(ig,k) .le. 0.) then
1235      IF (lwrite) THEN
1236              print*,'Teta<0 in thermcell_dTeta up: qenv .. dq : ', ztv(ig,k),ptimestep*zdthladj(ig,k)
1237      ENDIF
1238              if(ztv(ig,k) .gt. 0.) then
1239              zdthladj(ig,k)=0.
1240              endif
1241            endif
1242         enddo
1243         endif
1244      enddo
1245
1246! ------------------------------------------------------------------
1247! Prescription des proprietes du downdraft
1248! ------------------------------------------------------------------
1249
1250      ztvd(:,:)=ztv(:,:)
1251      fm_down(:,:)=0.
1252      do ig=1,ngridmx
1253         if (lmax(ig) .gt. 1) then
1254         do l=1,lmax(ig)
1255!              if(zlay(ig,l) .le. 0.8*zmax(ig)) then
1256              if(zlay(ig,l) .le. zmax(ig)) then
1257              fm_down(ig,l) =fm(ig,l)* &
1258     &      max(fdfu,-3*max(0.,(zlay(ig,l)/zmax(ig)))-0.9)
1259              endif
1260
1261!             if(zlay(ig,l) .le. 0.06*zmax(ig)) then
1262!          ztvd(ig,l)=ztv(ig,l)*max(0.,(1.+(sqrt((zlay(ig,l)/zmax(ig))/0.122449) - 1.)*(ztva(ig,l)/ztv(ig,l) - 1.)))
1263!             elseif(zlay(ig,l) .le. 0.4*zmax(ig)) then
1264!          ztvd(ig,l)=ztv(ig,l)*max(0.,1.-0.25*(ztva(ig,l)/ztv(ig,l) - 1.))
1265!             elseif(zlay(ig,l) .le. 0.7*zmax(ig)) then
1266!          ztvd(ig,l)=ztv(ig,l)*max(0.,(1.+(((zlay(ig,l)/zmax(ig))-0.7)/1.)*(ztva(ig,l)/ztv(ig,l) - 1.)))
1267!             else
1268!          ztvd(ig,l)=ztv(ig,l)
1269!            endif
1270
1271!            if(zlay(ig,l) .le. 0.6*zmax(ig)) then
1272!          ztvd(ig,l)=ztv(ig,l)*((zlay(ig,l)/zmax(ig))/179.848 + 0.997832)
1273!            elseif(zlay(ig,l) .le. 0.8*zmax(ig)) then
1274!          ztvd(ig,l)=-ztv(ig,l)*(((zlay(ig,l)/zmax(ig))-171.74)/170.94)
1275!             else
1276!          ztvd(ig,l)=ztv(ig,l)
1277!            endif
1278
1279
1280!            if(zlay(ig,l) .le. 0.8*zmax(ig)) then
1281!          ztvd(ig,l)=ztv(ig,l)*((zlay(ig,l)/zmax(ig))/224.81 + 0.997832)
1282!            elseif(zlay(ig,l) .le. zmax(ig)) then
1283!          ztvd(ig,l)=-ztv(ig,l)*(((zlay(ig,l)/zmax(ig))-144.685)/143.885)
1284!             else
1285!          ztvd(ig,l)=ztv(ig,l)
1286!            endif
1287
1288
1289!             if (zbuoy(ig,l) .gt. 0.) then
1290!               ztvd(ig,l)=ztva(ig,l)*0.9998
1291!!               ztvd(ig,l)=ztv(ig,l)*0.997832
1292!!             else
1293!!               if(zlay(ig,l) .le. zmax(ig)) then           
1294!!               ztvd(ig,l)=ztv(ig,l)*((zlay(ig,l)/zmax(ig))/299.7 + 0.997832)
1295!!               endif
1296!             endif
1297
1298            if(zlay(ig,l) .le. zmax(ig)) then           
1299          ztvd(ig,l)=min(ztv(ig,l),ztv(ig,l)*((zlay(ig,l)/zmax(ig))/400. + 0.997832))
1300!          ztvd(ig,l)=min(ztv(ig,l),ztv(ig,l)*((zlay(ig,l)/zmax(ig))/299.7 + 0.997832))
1301             else
1302          ztvd(ig,l)=ztv(ig,l)
1303            endif
1304
1305         enddo
1306         endif
1307      enddo
1308
1309! ------------------------------------------------------------------
1310! Transport de teta dans le downdraft : (remplace thermcell_dq)
1311! ------------------------------------------------------------------
1312
1313       zdthladj_down(:,:)=0.
1314
1315      do ig=1,ngridmx
1316         if(lmax(ig) .gt. 1) then
1317! No downdraft in the very-near surface layer, we begin at k=3
1318 
1319         do k=3,lmax(ig)
1320            zdthladj_down(ig,k)=(1./masse(ig,k))*(fm_down(ig,k+1)*ztv(ig,k+1)- &
1321     & fm_down(ig,k)*ztv(ig,k)+fm_down(ig,k)*ztvd(ig,k)-fm_down(ig,k+1)*ztvd(ig,k+1))
1322            if (ztv(ig,k) + ptimestep*zdthladj_down(ig,k) .le. 0.) then
1323      IF (lwrite) THEN
1324              print*,'q<0 in thermcell_dTeta down: qenv .. dq : ', ztv(ig,k),ptimestep*zdthladj_down(ig,k)
1325      ENDIF
1326              if(ztv(ig,k) .gt. 0.) then
1327              zdthladj(ig,k)=0.
1328              endif
1329            endif
1330         enddo
1331         endif
1332      enddo
1333
1334!------------------------------------------------------------------
1335! Calcul de la fraction de l'ascendance
1336!------------------------------------------------------------------
1337      do ig=1,ngridmx
1338         fraca(ig,1)=0.
1339         fraca(ig,nlayermx+1)=0.
1340      enddo
1341      do l=2,nlayermx
1342         do ig=1,ngridmx
1343            if (zw2(ig,l).gt.1.e-10) then
1344            fraca(ig,l)=fm(ig,l)/(rhobarz(ig,l)*zw2(ig,l))
1345            else
1346            fraca(ig,l)=0.
1347            endif
1348         enddo
1349      enddo
1350
1351
1352
1353! ===========================================================================
1354! ============= DV2 =========================================================
1355! ===========================================================================
1356! ROUTINE OVERIDE : ne prends pas en compte le downdraft
1357! de plus, le gradient de pression horizontal semble tout deregler... A VOIR
1358
1359      if (0 .eq. 1) then
1360
1361!------------------------------------------------------------------
1362!  calcul du transport vertical du moment horizontal
1363!------------------------------------------------------------------
1364
1365! Calcul du transport de V tenant compte d'echange par gradient
1366! de pression horizontal avec l'environnement
1367
1368!   calcul du detrainement
1369!---------------------------
1370
1371      nlarga0=0.
1372
1373      do k=1,nlayermx
1374         do ig=1,ngridmx
1375            detr_dv2(ig,k)=fm(ig,k)-fm(ig,k+1)+entr(ig,k)
1376         enddo
1377      enddo
1378
1379!   calcul de la valeur dans les ascendances
1380      do ig=1,ngridmx
1381         zua(ig,1)=zu(ig,1)
1382         zva(ig,1)=zv(ig,1)
1383         ue(ig,1)=zu(ig,1)
1384         ve(ig,1)=zv(ig,1)
1385      enddo
1386
1387      gamma(1:ngridmx,1)=0.
1388      do k=2,nlayermx
1389         do ig=1,ngridmx
1390            ltherm(ig,k)=(fm(ig,k+1)+detr_dv2(ig,k))*ptimestep > 1.e-5*masse(ig,k)
1391            if(ltherm(ig,k).and.zmax(ig)>0.) then
1392               gamma0(ig,k)=masse(ig,k)  &
1393     &         *sqrt( 0.5*(fraca(ig,k+1)+fraca(ig,k)) )  &
1394     &         *0.5/zmax(ig)  &
1395     &         *1.
1396            else
1397               gamma0(ig,k)=0.
1398            endif
1399            if (ltherm(ig,k).and.zmax(ig)<=0.) nlarga0=nlarga0+1
1400          enddo
1401      enddo
1402
1403      gamma(:,:)=0.
1404
1405      do k=2,nlayermx
1406
1407         do ig=1,ngridmx
1408
1409            if (ltherm(ig,k)) then
1410               dua(ig,k)=zua(ig,k-1)-zu(ig,k-1)
1411               dva(ig,k)=zva(ig,k-1)-zv(ig,k-1)
1412            else
1413               zua(ig,k)=zu(ig,k)
1414               zva(ig,k)=zv(ig,k)
1415               ue(ig,k)=zu(ig,k)
1416               ve(ig,k)=zv(ig,k)
1417            endif
1418         enddo
1419
1420
1421! Debut des iterations
1422!----------------------
1423
1424! AC WARNING : SALE !
1425
1426      do iter=1,5
1427         do ig=1,ngridmx
1428! Pour memoire : calcul prenant en compte la fraction reelle
1429!              zf=0.5*(fraca(ig,k)+fraca(ig,k+1))
1430!              zf2=1./(1.-zf)
1431! Calcul avec fraction infiniement petite
1432               zf=0.
1433               zf2=1.
1434
1435!  la première fois on multiplie le coefficient de freinage
1436!  par le module du vent dans la couche en dessous.
1437!  Mais pourquoi donc ???
1438               if (ltherm(ig,k)) then
1439!   On choisit une relaxation lineaire.
1440!                 gamma(ig,k)=gamma0(ig,k)
1441!   On choisit une relaxation quadratique.
1442                gamma(ig,k)=gamma0(ig,k)*sqrt(dua(ig,k)**2+dva(ig,k)**2)
1443                  zua(ig,k)=(fm(ig,k)*zua(ig,k-1)  &
1444     &               +(zf2*entr(ig,k)+gamma(ig,k))*zu(ig,k))  &
1445     &               /(fm(ig,k+1)+detr_dv2(ig,k)+entr(ig,k)*zf*zf2  &
1446     &                 +gamma(ig,k))
1447                  zva(ig,k)=(fm(ig,k)*zva(ig,k-1)  &
1448     &               +(zf2*entr(ig,k)+gamma(ig,k))*zv(ig,k))  &
1449     &               /(fm(ig,k+1)+detr_dv2(ig,k)+entr(ig,k)*zf*zf2  &
1450     &                 +gamma(ig,k))
1451
1452!                  print*,' OUTPUT DV2 !!!!!!!!!!!!!!!!!!!!',k,zua(ig,k),zva(ig,k),zu(ig,k),zv(ig,k),dua(ig,k),dva(ig,k)
1453                  dua(ig,k)=zua(ig,k)-zu(ig,k)
1454                  dva(ig,k)=zva(ig,k)-zv(ig,k)
1455                  ue(ig,k)=(zu(ig,k)-zf*zua(ig,k))*zf2
1456                  ve(ig,k)=(zv(ig,k)-zf*zva(ig,k))*zf2
1457               endif
1458         enddo
1459! Fin des iterations
1460!--------------------
1461      enddo
1462
1463      enddo ! k=2,nlayermx
1464
1465! Calcul du flux vertical de moment dans l'environnement.
1466!---------------------------------------------------------
1467      do k=2,nlayermx
1468         do ig=1,ngridmx
1469            wud(ig,k)=fm(ig,k)*ue(ig,k)
1470            wvd(ig,k)=fm(ig,k)*ve(ig,k)
1471         enddo
1472      enddo
1473      do ig=1,ngridmx
1474         wud(ig,1)=0.
1475         wud(ig,nlayermx+1)=0.
1476         wvd(ig,1)=0.
1477         wvd(ig,nlayermx+1)=0.
1478      enddo
1479
1480! calcul des tendances.
1481!-----------------------
1482      do k=1,nlayermx
1483         do ig=1,ngridmx
1484            pduadj(ig,k)=((detr_dv2(ig,k)+gamma(ig,k))*zua(ig,k)  &
1485     &               -(entr(ig,k)+gamma(ig,k))*ue(ig,k)  &
1486     &               -wud(ig,k)+wud(ig,k+1))  &
1487     &               /masse(ig,k)
1488            pdvadj(ig,k)=((detr_dv2(ig,k)+gamma(ig,k))*zva(ig,k)  &
1489     &               -(entr(ig,k)+gamma(ig,k))*ve(ig,k)  &
1490     &               -wvd(ig,k)+wvd(ig,k+1))  &
1491     &               /masse(ig,k)
1492         enddo
1493      enddo
1494
1495
1496! Sorties eventuelles.
1497!----------------------
1498
1499!      if (nlarga0>0) then
1500!          print*,'WARNING !!!!!! DANS THERMCELL_DV2 '
1501!      print*,nlarga0,' points pour lesquels laraga=0. dans un thermique'
1502!          print*,'Il faudrait decortiquer ces points'
1503!      endif
1504
1505! ===========================================================================
1506! ============= FIN DV2 =====================================================
1507! ===========================================================================
1508
1509      else
1510
1511!      modname='momentum'
1512!      call thermcell_dqupdown(ngridmx,nlayermx,ptimestep,fm,entr,detr,  &
1513!     &     masse,zu,pduadj,ztvd,fm_down,ztv,modname,lmax)
1514!
1515!      call thermcell_dqupdown(ngridmx,nlayermx,ptimestep,fm,entr,detr,  &
1516!     &     masse,zv,pdvadj,ztvd,fm_down,ztv,modname,lmax)
1517
1518      endif
1519
1520!------------------------------------------------------------------
1521!  calcul du transport vertical de traceurs
1522!------------------------------------------------------------------
1523
1524! We only transport co2 tracer because it is coupled to the scheme through theta_m
1525! The rest is transported outside the sub-timestep loop
1526
1527      if (ico2.ne.0) then
1528!      if (nqmx .ne. 0.) then
1529      do l=1,nlayermx
1530         zdzfull(:,l)=zlev(:,l+1)-zlev(:,l)
1531      enddo
1532
1533      modname='tracer'
1534      call thermcell_dqup(ngridmx,nlayermx,ptimestep     &
1535     &     ,fm,entr,detr,  &
1536     &    masse,pq(:,:,ico2),pdqadj(:,:,ico2),modname,zdzfull)
1537!      endif
1538
1539! Compute the ratio between theta and theta_m
1540     
1541       do l=1,nlayermx
1542          do ig=1,ngridmx
1543             ratiom(ig,l)=1./(A*(pq(ig,l,ico2)+pdqadj(ig,l,ico2)*ptimestep)+B)
1544          enddo
1545       enddo
1546       else
1547          ratiom(:,:)=1.
1548       endif
1549
1550
1551!------------------------------------------------------------------
1552!  incrementation dt
1553!------------------------------------------------------------------
1554
1555      do l=1,nlayermx
1556         do ig=1,ngridmx
1557         pdtadj(ig,l)=(zdthladj(ig,l)+zdthladj_down(ig,l))*zpopsk(ig,l)*ratiom(ig,l)
1558!         pdtadj(ig,l)=zdthladj(ig,l)*zpopsk(ig,l)*ratiom(ig,l)
1559         enddo
1560      enddo
1561
1562!------------------------------------------------------------------
1563!  calcul du transport vertical de la tke
1564!------------------------------------------------------------------
1565
1566!      modname='tke'
1567!      call thermcell_dqupdown(ngridmx,nlayermx,ptimestep,fm,entr,detr,  &
1568!      &      masse,pq2,pdq2adj,ztvd,fm_down,ztv,modname,lmax)
1569
1570! ===========================================================================
1571! ============= FIN TRANSPORT ===============================================
1572! ===========================================================================
1573
1574
1575!------------------------------------------------------------------
1576!   Calculs de diagnostiques pour les sorties
1577!------------------------------------------------------------------
1578! DIAGNOSTIQUE
1579! We compute interface values for teta env and th. The last interface
1580! value does not matter, as the mass flux is 0 there.
1581
1582   
1583      do l=1,nlayermx-1
1584       do ig=1,ngridmx
1585        teta_th_int(ig,l)=0.5*(ztva(ig,l+1)+ztva(ig,l))*ratiom(ig,l)
1586        teta_down_int(ig,l) = 0.5*(ztvd(ig,l+1)+ztvd(ig,l))*ratiom(ig,l)
1587        teta_env_int(ig,l)=0.5*(ztv(ig,l+1)+ztv(ig,l))*ratiom(ig,l)
1588       enddo
1589      enddo
1590      do ig=1,ngridmx
1591       teta_th_int(ig,nlayermx)=teta_th_int(ig,nlayermx-1)
1592       teta_env_int(ig,nlayermx)=teta_env_int(ig,nlayermx-1)
1593       teta_down_int(ig,nlayermx)=teta_down_int(ig,nlayermx-1)
1594      enddo
1595      do l=1,nlayermx
1596       do ig=1,ngridmx
1597        heatFlux(ig,l)=fm(ig,l)*(teta_th_int(ig,l)-teta_env_int(ig,l))/(rhobarz(ig,l))
1598        buoyancyOut(ig,l)=g*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
1599        buoyancyEst(ig,l)=g*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
1600        heatFlux_down(ig,l)=fm_down(ig,l)*(teta_down_int(ig,l)-teta_env_int(ig,l))/rhobarz(ig,l)
1601       enddo
1602      enddo
1603
1604      return
1605      end
Note: See TracBrowser for help on using the repository browser.