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

Last change on this file since 510 was 508, checked in by acolaitis, 14 years ago

Added molar-mass vertical gradient computations in thermals, coupled to the advection scheme for co2 tracer of thermals. As a result, there are now gentle thermals in the polar night (associated with a wstar of about 1.5 m.s-1).

File size: 49.7 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
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
381! --------------------------------------------------------------------------
382! --------------------------------------------------------------------------
383! --------------------------------------------------------------------------
384
385! Initialisation des variables entieres
386      wmaxa(:)=0.
387      lalim(:)=1
388
389!-------------------------------------------------------------------------
390! On ne considere comme actif que les colonnes dont les deux premieres
391! couches sont instables.
392!-------------------------------------------------------------------------
393      activecell(:)=ztv(:,1)>ztv(:,2)
394          do ig=1,ngridmx
395            if (ztv(ig,1)>=(ztv(ig,2))) then
396               alim_star(ig,1)=MAX((ztv(ig,1)-ztv(ig,2)),0.)  &
397     &                       *sqrt(zlev(ig,2))
398!     &                       /sqrt(zlev(ig,2))
399!      &                       *zlev(ig,2)
400               lalim(ig)=2
401               alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,1)
402            endif
403         enddo
404
405       do l=2,nlayermx-1
406!        do l=2,4
407         do ig=1,ngridmx
408           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
409               alim_star(ig,l)=MAX((ztv(ig,l)-ztv(ig,l+1)),0.)  &
410     &                       *sqrt(zlev(ig,l+1))
411!      &                       *zlev(ig,2)
412                lalim(ig)=l+1
413               alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
414           endif
415        enddo
416      enddo
417      do l=1,nlayermx
418         do ig=1,ngridmx
419            if (alim_star_tot(ig) > 1.e-10 ) then
420               alim_star(ig,l)=alim_star(ig,l)/alim_star_tot(ig)
421            endif
422         enddo
423      enddo
424
425      alim_star_tot(:)=1.
426!      if(alim_star(1,1) .ne. 0.) then
427!      print*, 'lalim star' ,lalim(1)
428!      endif
429
430!------------------------------------------------------------------------------
431! Calcul dans la premiere couche
432! On decide dans cette version que le thermique n'est actif que si la premiere
433! couche est instable.
434! Pourrait etre change si on veut que le thermiques puisse se déclencher
435! dans une couche l>1
436!------------------------------------------------------------------------------
437
438      do ig=1,ngridmx
439! Le panache va prendre au debut les caracteristiques de l'air contenu
440! dans cette couche.
441          if (activecell(ig)) then
442          ztla(ig,1)=ztv(ig,1)
443!cr: attention, prise en compte de f*(1)=1 => AC : what ? f*(1) =0. ! (d'ou f*(2)=a*(1)
444! dans un panache conservatif
445          f_star(ig,1)=0.
446         
447          f_star(ig,2)=alim_star(ig,1)
448
449          zw2(ig,2)=2.*g*(ztv(ig,1)-ztv(ig,2))/ztv(ig,2)  &
450      &                     *(zlev(ig,2)-zlev(ig,1))  &
451      &                    *0.4*pphi(ig,1)/(pphi(ig,2)-pphi(ig,1))
452          w_est(ig,2)=zw2(ig,2)
453
454          endif
455      enddo
456
457
458!==============================================================================
459!boucle de calcul de la vitesse verticale dans le thermique
460!==============================================================================
461      do l=2,nlayermx-1
462!==============================================================================
463
464
465! On decide si le thermique est encore actif ou non
466! AFaire : Il faut sans doute ajouter entr_star a alim_star dans ce test
467          do ig=1,ngridmx
468             activecell(ig)=activecell(ig) &
469      &                 .and. zw2(ig,l)>1.e-10 &
470      &                 .and. f_star(ig,l)+alim_star(ig,l)>1.e-10
471          enddo
472
473!---------------------------------------------------------------------------
474! calcul des proprietes thermodynamiques et de la vitesse de la couche l
475! sans tenir compte du detrainement et de l'entrainement dans cette
476! couche
477! C'est a dire qu'on suppose
478! ztla(l)=ztla(l-1)
479! Ici encore, on doit pouvoir ajouter entr_star (qui peut etre calculer
480! avant) a l'alimentation pour avoir un calcul plus propre
481!---------------------------------------------------------------------------
482
483          do ig=1,ngridmx
484             if(activecell(ig)) then
485
486!                if(l .lt. lalim(ig)) then
487!               ztva_est(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
488!     &            alim_star(ig,l)*ztv(ig,l))  &
489!     &            /(f_star(ig,l)+alim_star(ig,l))
490!                else
491                ztva_est(ig,l)=ztla(ig,l-1)
492!                endif
493
494                zdz=zlev(ig,l+1)-zlev(ig,l)
495                zbuoy(ig,l)=g*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
496
497                if (((a1*zbuoy(ig,l)/w_est(ig,l)-b1) .gt. 0.) .and. (w_est(ig,l) .ne. 0.)) then
498                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 &
499     & -2.*zdz*w_est(ig,l)*ae*(a1*zbuoy(ig,l)/w_est(ig,l)-b1)**be)
500                else
501                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)
502                endif
503                if (w_est(ig,l+1).lt.0.) then
504                w_est(ig,l+1)=zw2(ig,l)
505                endif
506             endif
507          enddo
508
509!-------------------------------------------------
510!calcul des taux d'entrainement et de detrainement
511!-------------------------------------------------
512
513      do ig=1,ngridmx
514        if (activecell(ig)) then
515
516          zw2m=w_est(ig,l+1)
517
518          if((a1*(zbuoy(ig,l)/zw2m)-b1) .gt. 0.) then
519          entr_star(ig,l)=f_star(ig,l)*zdz*  &
520!        &   MAX(0.,ae*(a1*(zbuoy(ig,l)/zw2m)-b1)**be)
521         &  MAX(0.,log(1. + 0.027*sqrt(a1*(zbuoy(ig,l)/zw2m)-b1)))
522          else
523          entr_star(ig,l)=0.
524          endif
525
526          if(zbuoy(ig,l) .gt. 0.) then
527             if(l .lt. lalim(ig)) then
528                detr_star(ig,l)=0.
529             else
530
531!                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
532!              &     0.0105*((zbuoy(ig,l)/zw2m)/0.048)**(1./1.7)
533!                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
534!              &     0.0085*((zbuoy(ig,l)/zw2m)/0.05)**(1./1.55)
535
536! last baseline from direct les
537!                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
538!               &     0.065*(2.5*(zbuoy(ig,l)/zw2m))**0.75
539
540! new param from continuity eq with a fit on dfdz
541                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
542!            &  ad
543             &  Max(0., 0.001 - 0.45*zbuoy(ig,l)/zw2m)
544
545!               &     MAX(0.,-0.38*zbuoy(ig,l)/zw2m+0.0005)   !svn baseline
546!                &     MAX(0.,-0.38*zbuoy(ig,l)/zw2m+0.0008)     
547
548!              &     0.014*((zbuoy(ig,l)/zw2m)/0.05)**(1./1.35)
549!                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
550!              &     ((zbuoy(ig,l)/zw2m)/2.222)! + 0.0002)
551
552             endif
553          else
554          detr_star(ig,l)=f_star(ig,l)*zdz*                        &
555!                &     bd*zbuoy(ig,l)/zw2m
556             &  Max(0., 0.001 - 0.45*zbuoy(ig,l)/zw2m)
557
558
559!               &     MAX(0.,-0.38*zbuoy(ig,l)/zw2m+0.0005)      !svn baseline
560
561!              &  *5.*(-afact*zbetalpha*zbuoy(ig,l)/zw2m)
562!              &  *5.*(-afact*zbuoy(ig,l)/zw2m)
563
564! last baseline from direct les
565!               &     0.065*(-2.5*(zbuoy(ig,l)/zw2m))**0.75
566
567! new param from continuity eq with a fit on dfdz
568
569
570          endif
571
572! En dessous de lalim, on prend le max de alim_star et entr_star pour
573! alim_star et 0 sinon
574
575        if (l.lt.lalim(ig)) then
576          alim_star(ig,l)=max(alim_star(ig,l),entr_star(ig,l))
577          entr_star(ig,l)=0.
578        endif
579
580! Calcul du flux montant normalise
581
582      f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
583     &              -detr_star(ig,l)
584
585      endif
586      enddo
587
588
589!----------------------------------------------------------------------------
590!calcul de la vitesse verticale en melangeant Tl et qt du thermique
591!---------------------------------------------------------------------------
592
593      DO tic=0,1  ! internal convergence loop
594      activetmp(:)=activecell(:) .and. f_star(:,l+1)>1.e-10
595      do ig=1,ngridmx
596       if (activetmp(ig)) then
597
598           ztla(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
599     &            (alim_star(ig,l)+entr_star(ig,l))*ztv(ig,l))  &
600     &            /(f_star(ig,l+1)+detr_star(ig,l))
601
602        endif
603      enddo
604
605      activetmp(:)=activetmp(:).and.(abs(ztla(:,l)-ztva(:,l)).gt.0.01)
606
607      do ig=1,ngridmx
608      if (activetmp(ig)) then
609           ztva(ig,l) = ztla(ig,l)
610           zbuoy(ig,l)=g*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
611
612           if (((a1*zbuoy(ig,l)/zw2(ig,l)-b1) .gt. 0.) .and. (zw2(ig,l) .ne. 0.) ) then
613           zw2(ig,l+1)=Max(0.,zw2(ig,l)+2.*zdz*a1*zbuoy(ig,l)-         &
614     & 2.*zdz*zw2(ig,l)*b1-2.*zdz*zw2(ig,l)*ae*(a1*zbuoy(ig,l)/zw2(ig,l)-b1)**be)
615           else
616           zw2(ig,l+1)=Max(0.,zw2(ig,l)+2.*zdz*a1*zbuoy(ig,l)-2.*zdz*zw2(ig,l)*b1)
617           endif
618      endif
619      enddo
620
621! ================ RECOMPUTE ENTR, DETR, and F FROM NEW W2 ===================
622
623
624      do ig=1,ngridmx
625        if (activetmp(ig)) then
626
627          zw2m=zw2(ig,l+1)
628          if(zw2m .gt. 0) then
629          if((a1*(zbuoy(ig,l)/zw2m)-b1) .gt. 0.) then
630          entr_star(ig,l)=f_star(ig,l)*zdz*  &
631        &   MAX(0.,ae*(a1*(zbuoy(ig,l)/zw2m)-b1)**be)
632          else
633          entr_star(ig,l)=0.
634          endif
635
636          if(zbuoy(ig,l) .gt. 0.) then
637             if(l .lt. lalim(ig)) then
638                detr_star(ig,l)=0.
639             else
640                 detr_star(ig,l) = f_star(ig,l)*zdz*              &
641            &  ad
642             endif
643          else
644          detr_star(ig,l)=f_star(ig,l)*zdz*                        &
645                &     bd*zbuoy(ig,l)/zw2m
646          endif
647          else
648          entr_star(ig,l)=0.
649          detr_star(ig,l)=0.
650          endif
651
652! En dessous de lalim, on prend le max de alim_star et entr_star pour
653! alim_star et 0 sinon
654
655        if (l.lt.lalim(ig)) then
656          alim_star(ig,l)=max(alim_star(ig,l),entr_star(ig,l))
657          entr_star(ig,l)=0.
658        endif
659
660! Calcul du flux montant normalise
661
662      f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
663     &              -detr_star(ig,l)
664
665      endif
666      enddo
667
668      ENDDO   ! of tic
669
670!---------------------------------------------------------------------------
671!initialisations pour le calcul de la hauteur du thermique, de l'inversion et de la vitesse verticale max
672!---------------------------------------------------------------------------
673
674      do ig=1,ngridmx
675            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
676             print*,'On tombe sur le cas particulier de thermcell_plume'
677                zw2(ig,l+1)=0.
678                linter(ig)=l+1
679            endif
680
681        if (zw2(ig,l+1).lt.0.) then
682           linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
683     &               -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
684           zw2(ig,l+1)=0.
685        endif
686           wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
687
688        if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
689!   lmix est le niveau de la couche ou w (wa_moy) est maximum
690            wmaxa(ig)=wa_moy(ig,l+1)
691        endif
692      enddo
693
694!=========================================================================
695! FIN DE LA BOUCLE VERTICALE
696      enddo
697!=========================================================================
698
699!on recalcule alim_star_tot
700       do ig=1,ngridmx
701          alim_star_tot(ig)=0.
702       enddo
703       do ig=1,ngridmx
704          do l=1,lalim(ig)-1
705          alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
706          enddo
707       enddo
708
709      do l=1,nlayermx
710         do ig=1,ngridmx
711            if (alim_star_tot(ig) > 1.e-10 ) then
712               alim_star(ig,l)=alim_star(ig,l)/alim_star_tot(ig)
713            endif
714         enddo
715      enddo
716
717! ===========================================================================
718! ================= FIN PLUME ===============================================
719! ===========================================================================
720
721! ===========================================================================
722! ================= HEIGHT ==================================================
723! ===========================================================================
724
725! Attention, w2 est transforme en sa racine carree dans cette routine
726
727!-------------------------------------------------------------------------------
728! Calcul des caracteristiques du thermique:zmax,wmax
729!-------------------------------------------------------------------------------
730
731!calcul de la hauteur max du thermique
732      do ig=1,ngridmx
733         lmax(ig)=lalim(ig)
734      enddo
735      do ig=1,ngridmx
736         do l=nlayermx,lalim(ig)+1,-1
737            if (zw2(ig,l).le.1.e-10) then
738               lmax(ig)=l-1
739            endif
740         enddo
741      enddo
742
743! On traite le cas particulier qu'il faudrait éviter ou le thermique
744! atteind le haut du modele ...
745      do ig=1,ngridmx
746      if ( zw2(ig,nlayermx) > 1.e-10 ) then
747          print*,'WARNING !!!!! W2 thermiques non nul derniere couche '
748          lmax(ig)=nlayermx
749      endif
750      enddo
751
752! pas de thermique si couche 1 stable
753!      do ig=1,ngridmx
754!         if (lmin(ig).gt.1) then
755!             lmax(ig)=1
756!             lmin(ig)=1
757!             lalim(ig)=1
758!         endif
759!      enddo
760!
761! Determination de zw2 max
762      do ig=1,ngridmx
763         wmax(ig)=0.
764      enddo
765
766      do l=1,nlayermx
767         do ig=1,ngridmx
768            if (l.le.lmax(ig)) then
769                if (zw2(ig,l).lt.0.)then
770                  print*,'pb2 zw2<0'
771                endif
772                zw2(ig,l)=sqrt(zw2(ig,l))
773                wmax(ig)=max(wmax(ig),zw2(ig,l))
774            else
775                 zw2(ig,l)=0.
776            endif
777          enddo
778      enddo
779!   Longueur caracteristique correspondant a la hauteur des thermiques.
780      do  ig=1,ngridmx
781         zmax(ig)=0.
782         zlevinter(ig)=zlev(ig,1)
783      enddo
784
785         num(:)=0.
786         denom(:)=0.
787         do ig=1,ngridmx
788          do l=1,nlayermx
789             num(ig)=num(ig)+zw2(ig,l)*zlev(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
790             denom(ig)=denom(ig)+zw2(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
791          enddo
792       enddo
793       do ig=1,ngridmx
794       if (denom(ig).gt.1.e-10) then
795          zmax(ig)=2.*num(ig)/denom(ig)
796       endif
797       enddo
798
799! Attention, w2 est transforme en sa racine carree dans cette routine
800
801! ===========================================================================
802! ================= FIN HEIGHT ==============================================
803! ===========================================================================
804
805! Choix de la fonction d'alimentation utilisee pour la fermeture.
806
807      alim_star_clos(:,:)=entr_star(:,:)+alim_star(:,:)
808
809! ===========================================================================
810! ============= CLOSURE =====================================================
811! ===========================================================================
812
813!-------------------------------------------------------------------------------
814! Fermeture,determination de f
815!-------------------------------------------------------------------------------
816! Appel avec la version seche
817
818      alim_star2(:)=0.
819      alim_star_tot_clos(:)=0.
820      f(:)=0.
821
822! Indice vertical max (max de lalim) atteint par les thermiques sur le domaine
823      llmax=1
824      do ig=1,ngridmx
825         if (lalim(ig)>llmax) llmax=lalim(ig)
826      enddo
827
828
829! Calcul des integrales sur la verticale de alim_star et de
830!   alim_star^2/(rho dz)
831      do k=1,llmax-1
832         do ig=1,ngridmx
833            if (k<lalim(ig)) then
834         alim_star2(ig)=alim_star2(ig)+alim_star_clos(ig,k)*alim_star_clos(ig,k)  &
835      &                    /(rho(ig,k)*(zlev(ig,k+1)-zlev(ig,k)))
836         alim_star_tot_clos(ig)=alim_star_tot_clos(ig)+alim_star_clos(ig,k)
837      endif
838         enddo
839      enddo
840 
841! WARNING : MARS MODIF : we have added 2. : ratio of wmax/vmoy
842! True ratio is 3.5 but wetake into account the vmoy is the one alimentating
843! the thermal, so there are vs=0 into the vmoy... the true vmoy is lower. (a la louche)
844! And r_aspect has been changed from 2 to 1.5 from observations
845      do ig=1,ngridmx
846         if (alim_star2(ig)>1.e-10) then
847!            f(ig)=wmax_sec(ig)*alim_star_tot_clos(ig)/  &
848!      &     (max(500.,zmax_sec(ig))*r_aspect*alim_star2(ig))
849             f(ig)=wmax(ig)*alim_star_tot_clos(ig)/  &
850      &     (max(500.,zmax(ig))*r_aspect*alim_star2(ig))
851
852         endif
853      enddo
854
855! ===========================================================================
856! ============= FIN CLOSURE =================================================
857! ===========================================================================
858
859
860! ===========================================================================
861! ============= FLUX2 =======================================================
862! ===========================================================================
863
864!-------------------------------------------------------------------------------
865!deduction des flux
866!-------------------------------------------------------------------------------
867
868      fomass_max=0.8
869      alphamax=0.5
870
871      ncorecfm1=0
872      ncorecfm2=0
873      ncorecfm3=0
874      ncorecfm4=0
875      ncorecfm5=0
876      ncorecfm6=0
877      ncorecfm7=0
878      ncorecfm8=0
879      ncorecalpha=0
880
881!-------------------------------------------------------------------------
882! Multiplication par le flux de masse issu de la femreture
883!-------------------------------------------------------------------------
884
885      do l=1,nlayermx
886         entr(:,l)=f(:)*(entr_star(:,l)+alim_star(:,l))
887         detr(:,l)=f(:)*detr_star(:,l)
888      enddo
889
890      do l=1,nlayermx
891         do ig=1,ngridmx
892            if (l.lt.lmax(ig)) then
893               fm(ig,l+1)=fm(ig,l)+entr(ig,l)-detr(ig,l)
894            elseif(l.eq.lmax(ig)) then
895               fm(ig,l+1)=0.
896               detr(ig,l)=fm(ig,l)+entr(ig,l)
897            else
898               fm(ig,l+1)=0.
899            endif
900         enddo
901      enddo
902
903! Test provisoire : pour comprendre pourquoi on corrige plein de fois
904! le cas fm6, on commence par regarder une premiere fois avant les
905! autres corrections.
906
907!      do l=1,nlayermx
908!         do ig=1,ngridmx
909!            if (detr(ig,l).gt.fm(ig,l)) then
910!               ncorecfm8=ncorecfm8+1
911!            endif
912!         enddo
913!      enddo
914
915!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
916! FH Version en cours de test;
917! par rapport a thermcell_flux, on fait une grande boucle sur "l"
918! et on modifie le flux avec tous les contr�les appliques d'affilee
919! pour la meme couche
920! Momentanement, on duplique le calcule du flux pour pouvoir comparer
921! les flux avant et apres modif
922!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
923
924      do l=1,nlayermx
925
926         do ig=1,ngridmx
927            if (l.lt.lmax(ig)) then
928               fm(ig,l+1)=fm(ig,l)+entr(ig,l)-detr(ig,l)
929            elseif(l.eq.lmax(ig)) then
930               fm(ig,l+1)=0.
931               detr(ig,l)=fm(ig,l)+entr(ig,l)
932            else
933               fm(ig,l+1)=0.
934            endif
935         enddo
936
937
938!-------------------------------------------------------------------------
939! Verification de la positivite des flux de masse
940!-------------------------------------------------------------------------
941
942         do ig=1,ngridmx
943
944            if (fm(ig,l+1).lt.0.) then
945               if((l+1) .eq. lmax(ig)) then
946               detr(ig,l)=detr(ig,l)+fm(ig,l+1)
947               fm(ig,l+1)=0.
948               entr(ig,l+1)=0.
949               ncorecfm2=ncorecfm2+1
950               else
951          print*,'fm(l+1)<0 : ig, l+1,lmax :',ig,l+1,lmax(ig),fm(ig,l+1)
952               ncorecfm1=ncorecfm1+1
953               fm(ig,l+1)=fm(ig,l)
954               detr(ig,l)=entr(ig,l)
955               endif
956            endif
957
958         enddo
959
960!  Les "optimisations" du flux sont desactivecelles : moins de bidouilles
961!  je considere que celles ci ne sont pas justifiees ou trop delicates
962!  pour MARS, d'apres des observations LES.
963!-------------------------------------------------------------------------
964!Test sur fraca croissant
965!-------------------------------------------------------------------------
966!      if (iflag_thermals_optflux==0) then
967!         do ig=1,ngridmx
968!          if (l.ge.lalim(ig).and.l.le.lmax(ig) &
969!     &    .and.(zw2(ig,l+1).gt.1.e-10).and.(zw2(ig,l).gt.1.e-10) ) then
970!!  zzz est le flux en l+1 a frac constant
971!             zzz=fm(ig,l)*rhobarz(ig,l+1)*zw2(ig,l+1)  &
972!     &                          /(rhobarz(ig,l)*zw2(ig,l))
973!             if (fm(ig,l+1).gt.zzz) then
974!                detr(ig,l)=detr(ig,l)+fm(ig,l+1)-zzz
975!                fm(ig,l+1)=zzz
976!                ncorecfm4=ncorecfm4+1
977!             endif
978!          endif
979!        enddo
980!      endif
981!
982!-------------------------------------------------------------------------
983!test sur flux de masse croissant
984!-------------------------------------------------------------------------
985!      if (iflag_thermals_optflux==0) then
986!         do ig=1,ngridmx
987!            if ((fm(ig,l+1).gt.fm(ig,l)).and.(l.gt.lalim(ig))) then
988!              f_old=fm(ig,l+1)
989!              fm(ig,l+1)=fm(ig,l)
990!              detr(ig,l)=detr(ig,l)+f_old-fm(ig,l+1)
991!               ncorecfm5=ncorecfm5+1
992!            endif
993!         enddo
994!      endif
995!
996!-------------------------------------------------------------------------
997!detr ne peut pas etre superieur a fm
998!-------------------------------------------------------------------------
999
1000         do ig=1,ngridmx
1001            if (detr(ig,l).gt.fm(ig,l)) then
1002               ncorecfm6=ncorecfm6+1
1003               detr(ig,l)=fm(ig,l)
1004               entr(ig,l)=fm(ig,l+1)
1005
1006! Dans le cas ou on est au dessus de la couche d'alimentation et que le
1007! detrainement est plus fort que le flux de masse, on stope le thermique.
1008!            endif
1009
1010            if(l.gt.lmax(ig)) then
1011!            if(l.gt.lalim(ig)) then
1012               detr(ig,l)=0.
1013               fm(ig,l+1)=0.
1014               entr(ig,l)=0.
1015            endif
1016           
1017            endif
1018
1019         enddo
1020
1021!-------------------------------------------------------------------------
1022!fm ne peut pas etre negatif
1023!-------------------------------------------------------------------------
1024
1025         do ig=1,ngridmx
1026            if (fm(ig,l+1).lt.0.) then
1027               detr(ig,l)=detr(ig,l)+fm(ig,l+1)
1028               fm(ig,l+1)=0.
1029               ncorecfm2=ncorecfm2+1
1030            endif
1031         enddo
1032
1033!-----------------------------------------------------------------------
1034!la fraction couverte ne peut pas etre superieure a 1
1035!-----------------------------------------------------------------------
1036!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1037! FH Partie a revisiter.
1038! Il semble qu'etaient codees ici deux optiques dans le cas
1039! F/ (rho *w) > 1
1040! soit limiter la hauteur du thermique en considerant que c'est
1041! la derniere chouche, soit limiter F a rho w.
1042! Dans le second cas, il faut en fait limiter a un peu moins
1043! que ca parce qu'on a des 1 / ( 1 -alpha) un peu plus loin
1044! dans thermcell_main et qu'il semble de toutes facons deraisonable
1045! d'avoir des fractions de 1..
1046! Ci dessous, et dans l'etat actuel, le premier des  deux if est
1047! sans doute inutile.
1048!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1049
1050        do ig=1,ngridmx
1051           if (zw2(ig,l+1).gt.1.e-10) then
1052           zfm=rhobarz(ig,l+1)*zw2(ig,l+1)*alphamax
1053           if ( fm(ig,l+1) .gt. zfm) then
1054              f_old=fm(ig,l+1)
1055              fm(ig,l+1)=zfm
1056              detr(ig,l)=detr(ig,l)+f_old-fm(ig,l+1)
1057              ncorecalpha=ncorecalpha+1
1058           endif
1059           endif
1060
1061        enddo
1062
1063! Fin de la grande boucle sur les niveaux verticaux
1064      enddo
1065
1066!-----------------------------------------------------------------------
1067! On fait en sorte que la quantite totale d'air entraine dans le
1068! panache ne soit pas trop grande comparee a la masse de la maille
1069!-----------------------------------------------------------------------
1070
1071      do l=1,nlayermx-1
1072         do ig=1,ngridmx
1073            eee0=entr(ig,l)
1074            ddd0=detr(ig,l)
1075            eee=entr(ig,l)-masse(ig,l)*fomass_max/ptimestep
1076            ddd=detr(ig,l)-eee
1077            if (eee.gt.0.) then
1078                ncorecfm3=ncorecfm3+1
1079                entr(ig,l)=entr(ig,l)-eee
1080                if ( ddd.gt.0.) then
1081!   l'entrainement est trop fort mais l'exces peut etre compense par une
1082!   diminution du detrainement)
1083                   detr(ig,l)=ddd
1084                else
1085!   l'entrainement est trop fort mais l'exces doit etre compense en partie
1086!   par un entrainement plus fort dans la couche superieure
1087                   if(l.eq.lmax(ig)) then
1088                      detr(ig,l)=fm(ig,l)+entr(ig,l)
1089                   else
1090                      entr(ig,l+1)=entr(ig,l+1)-ddd
1091                      detr(ig,l)=0.
1092                      fm(ig,l+1)=fm(ig,l)+entr(ig,l)
1093                      detr(ig,l)=0.
1094                   endif
1095                endif
1096            endif
1097         enddo
1098      enddo
1099!
1100!              ddd=detr(ig)-entre
1101!on s assure que tout s annule bien en zmax
1102      do ig=1,ngridmx
1103         fm(ig,lmax(ig)+1)=0.
1104         entr(ig,lmax(ig))=0.
1105         detr(ig,lmax(ig))=fm(ig,lmax(ig))+entr(ig,lmax(ig))
1106      enddo
1107
1108!-----------------------------------------------------------------------
1109! Impression du nombre de bidouilles qui ont ete necessaires
1110!-----------------------------------------------------------------------
1111
1112!IM 090508 beg
1113      if (ncorecfm1+ncorecfm2+ncorecfm3+ncorecfm4+ncorecfm5+ncorecalpha > ngridmx/4. ) then
1114         print*,'thermcell warning : large number of corrections'
1115         print*,'PB thermcell : on a du coriger ',ncorecfm1,'x fm1',&
1116     &     ncorecfm2,'x fm2',ncorecfm3,'x fm3 et', &
1117     &     ncorecfm4,'x fm4',ncorecfm5,'x fm5 et', &
1118     &     ncorecfm6,'x fm6', &
1119     &     ncorecfm7,'x fm7', &
1120     &     ncorecfm8,'x fm8', &
1121     &     ncorecalpha,'x alpha'
1122      endif
1123
1124! ===========================================================================
1125! ============= FIN FLUX2 ===================================================
1126! ===========================================================================
1127
1128
1129! ===========================================================================
1130! ============= TRANSPORT ===================================================
1131! ===========================================================================
1132
1133!------------------------------------------------------------------
1134!   calcul du transport vertical
1135!------------------------------------------------------------------
1136
1137! ------------------------------------------------------------------
1138! Transport de teta dans l'updraft : (remplace thermcell_dq)
1139! ------------------------------------------------------------------
1140
1141      zdthladj(:,:)=0.
1142
1143      do ig=1,ngridmx
1144         if(lmax(ig) .gt. 1) then
1145         do k=1,lmax(ig)
1146            zdthladj(ig,k)=(1./masse(ig,k))*(fm(ig,k+1)*ztv(ig,k+1)-    &
1147     &   fm(ig,k)*ztv(ig,k)+fm(ig,k)*ztva(ig,k)-fm(ig,k+1)*ztva(ig,k+1))
1148            if (ztv(ig,k) + ptimestep*zdthladj(ig,k) .le. 0.) then
1149              print*,'Teta<0 in thermcell_dTeta up: qenv .. dq : ', ztv(ig,k),ptimestep*zdthladj(ig,k)
1150              if(ztv(ig,k) .gt. 0.) then
1151              zdthladj(ig,k)=0.
1152              endif
1153            endif
1154         enddo
1155         endif
1156      enddo
1157
1158! ------------------------------------------------------------------
1159! Prescription des proprietes du downdraft
1160! ------------------------------------------------------------------
1161
1162      ztvd(:,:)=ztv(:,:)
1163      fm_down(:,:)=0.
1164      do ig=1,ngridmx
1165         if (lmax(ig) .gt. 1) then
1166         do l=1,lmax(ig)
1167              if(zlay(ig,l) .le. 0.7*zmax(ig)) then
1168              fm_down(ig,l) =fm(ig,l)* &
1169     &      max(fdfu,-3*max(0.,(zlay(ig,l)/zmax(ig)))-0.9)
1170              endif
1171
1172             if(zlay(ig,l) .le. 0.06*zmax(ig)) then
1173          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.)))
1174             elseif(zlay(ig,l) .le. 0.4*zmax(ig)) then
1175          ztvd(ig,l)=ztv(ig,l)*max(0.,1.-0.25*(ztva(ig,l)/ztv(ig,l) - 1.))
1176             elseif(zlay(ig,l) .le. 0.7*zmax(ig)) then
1177          ztvd(ig,l)=ztv(ig,l)*max(0.,(1.+(((zlay(ig,l)/zmax(ig))-0.7)/1.)*(ztva(ig,l)/ztv(ig,l) - 1.)))
1178             else
1179          ztvd(ig,l)=ztv(ig,l)
1180            endif
1181
1182
1183         enddo
1184         endif
1185      enddo
1186
1187! ------------------------------------------------------------------
1188! Transport de teta dans le downdraft : (remplace thermcell_dq)
1189! ------------------------------------------------------------------
1190
1191       zdthladj_down(:,:)=0.
1192
1193      do ig=1,ngridmx
1194         if(lmax(ig) .gt. 1) then
1195! No downdraft in the very-near surface layer, we begin at k=3
1196 
1197         do k=3,lmax(ig)
1198            zdthladj_down(ig,k)=(1./masse(ig,k))*(fm_down(ig,k+1)*ztv(ig,k+1)- &
1199     & fm_down(ig,k)*ztv(ig,k)+fm_down(ig,k)*ztvd(ig,k)-fm_down(ig,k+1)*ztvd(ig,k+1))
1200            if (ztv(ig,k) + ptimestep*zdthladj_down(ig,k) .le. 0.) then
1201              print*,'q<0 in thermcell_dTeta down: qenv .. dq : ', ztv(ig,k),ptimestep*zdthladj_down(ig,k)
1202              if(ztv(ig,k) .gt. 0.) then
1203              zdthladj(ig,k)=0.
1204              endif
1205            endif
1206         enddo
1207         endif
1208      enddo
1209
1210!------------------------------------------------------------------
1211! Calcul de la fraction de l'ascendance
1212!------------------------------------------------------------------
1213      do ig=1,ngridmx
1214         fraca(ig,1)=0.
1215         fraca(ig,nlayermx+1)=0.
1216      enddo
1217      do l=2,nlayermx
1218         do ig=1,ngridmx
1219            if (zw2(ig,l).gt.1.e-10) then
1220            fraca(ig,l)=fm(ig,l)/(rhobarz(ig,l)*zw2(ig,l))
1221            else
1222            fraca(ig,l)=0.
1223            endif
1224         enddo
1225      enddo
1226
1227
1228
1229! ===========================================================================
1230! ============= DV2 =========================================================
1231! ===========================================================================
1232! ROUTINE OVERIDE : ne prends pas en compte le downdraft
1233! de plus, le gradient de pression horizontal semble tout deregler... A VOIR
1234
1235      if (0 .eq. 1) then
1236
1237!------------------------------------------------------------------
1238!  calcul du transport vertical du moment horizontal
1239!------------------------------------------------------------------
1240
1241! Calcul du transport de V tenant compte d'echange par gradient
1242! de pression horizontal avec l'environnement
1243
1244!   calcul du detrainement
1245!---------------------------
1246
1247      nlarga0=0.
1248
1249      do k=1,nlayermx
1250         do ig=1,ngridmx
1251            detr_dv2(ig,k)=fm(ig,k)-fm(ig,k+1)+entr(ig,k)
1252         enddo
1253      enddo
1254
1255!   calcul de la valeur dans les ascendances
1256      do ig=1,ngridmx
1257         zua(ig,1)=zu(ig,1)
1258         zva(ig,1)=zv(ig,1)
1259         ue(ig,1)=zu(ig,1)
1260         ve(ig,1)=zv(ig,1)
1261      enddo
1262
1263      gamma(1:ngridmx,1)=0.
1264      do k=2,nlayermx
1265         do ig=1,ngridmx
1266            ltherm(ig,k)=(fm(ig,k+1)+detr_dv2(ig,k))*ptimestep > 1.e-5*masse(ig,k)
1267            if(ltherm(ig,k).and.zmax(ig)>0.) then
1268               gamma0(ig,k)=masse(ig,k)  &
1269     &         *sqrt( 0.5*(fraca(ig,k+1)+fraca(ig,k)) )  &
1270     &         *0.5/zmax(ig)  &
1271     &         *1.
1272            else
1273               gamma0(ig,k)=0.
1274            endif
1275            if (ltherm(ig,k).and.zmax(ig)<=0.) nlarga0=nlarga0+1
1276          enddo
1277      enddo
1278
1279      gamma(:,:)=0.
1280
1281      do k=2,nlayermx
1282
1283         do ig=1,ngridmx
1284
1285            if (ltherm(ig,k)) then
1286               dua(ig,k)=zua(ig,k-1)-zu(ig,k-1)
1287               dva(ig,k)=zva(ig,k-1)-zv(ig,k-1)
1288            else
1289               zua(ig,k)=zu(ig,k)
1290               zva(ig,k)=zv(ig,k)
1291               ue(ig,k)=zu(ig,k)
1292               ve(ig,k)=zv(ig,k)
1293            endif
1294         enddo
1295
1296
1297! Debut des iterations
1298!----------------------
1299
1300! AC WARNING : SALE !
1301
1302      do iter=1,5
1303         do ig=1,ngridmx
1304! Pour memoire : calcul prenant en compte la fraction reelle
1305!              zf=0.5*(fraca(ig,k)+fraca(ig,k+1))
1306!              zf2=1./(1.-zf)
1307! Calcul avec fraction infiniement petite
1308               zf=0.
1309               zf2=1.
1310
1311!  la première fois on multiplie le coefficient de freinage
1312!  par le module du vent dans la couche en dessous.
1313!  Mais pourquoi donc ???
1314               if (ltherm(ig,k)) then
1315!   On choisit une relaxation lineaire.
1316!                 gamma(ig,k)=gamma0(ig,k)
1317!   On choisit une relaxation quadratique.
1318                gamma(ig,k)=gamma0(ig,k)*sqrt(dua(ig,k)**2+dva(ig,k)**2)
1319                  zua(ig,k)=(fm(ig,k)*zua(ig,k-1)  &
1320     &               +(zf2*entr(ig,k)+gamma(ig,k))*zu(ig,k))  &
1321     &               /(fm(ig,k+1)+detr_dv2(ig,k)+entr(ig,k)*zf*zf2  &
1322     &                 +gamma(ig,k))
1323                  zva(ig,k)=(fm(ig,k)*zva(ig,k-1)  &
1324     &               +(zf2*entr(ig,k)+gamma(ig,k))*zv(ig,k))  &
1325     &               /(fm(ig,k+1)+detr_dv2(ig,k)+entr(ig,k)*zf*zf2  &
1326     &                 +gamma(ig,k))
1327
1328!                  print*,' OUTPUT DV2 !!!!!!!!!!!!!!!!!!!!',k,zua(ig,k),zva(ig,k),zu(ig,k),zv(ig,k),dua(ig,k),dva(ig,k)
1329                  dua(ig,k)=zua(ig,k)-zu(ig,k)
1330                  dva(ig,k)=zva(ig,k)-zv(ig,k)
1331                  ue(ig,k)=(zu(ig,k)-zf*zua(ig,k))*zf2
1332                  ve(ig,k)=(zv(ig,k)-zf*zva(ig,k))*zf2
1333               endif
1334         enddo
1335! Fin des iterations
1336!--------------------
1337      enddo
1338
1339      enddo ! k=2,nlayermx
1340
1341! Calcul du flux vertical de moment dans l'environnement.
1342!---------------------------------------------------------
1343      do k=2,nlayermx
1344         do ig=1,ngridmx
1345            wud(ig,k)=fm(ig,k)*ue(ig,k)
1346            wvd(ig,k)=fm(ig,k)*ve(ig,k)
1347         enddo
1348      enddo
1349      do ig=1,ngridmx
1350         wud(ig,1)=0.
1351         wud(ig,nlayermx+1)=0.
1352         wvd(ig,1)=0.
1353         wvd(ig,nlayermx+1)=0.
1354      enddo
1355
1356! calcul des tendances.
1357!-----------------------
1358      do k=1,nlayermx
1359         do ig=1,ngridmx
1360            pduadj(ig,k)=((detr_dv2(ig,k)+gamma(ig,k))*zua(ig,k)  &
1361     &               -(entr(ig,k)+gamma(ig,k))*ue(ig,k)  &
1362     &               -wud(ig,k)+wud(ig,k+1))  &
1363     &               /masse(ig,k)
1364            pdvadj(ig,k)=((detr_dv2(ig,k)+gamma(ig,k))*zva(ig,k)  &
1365     &               -(entr(ig,k)+gamma(ig,k))*ve(ig,k)  &
1366     &               -wvd(ig,k)+wvd(ig,k+1))  &
1367     &               /masse(ig,k)
1368         enddo
1369      enddo
1370
1371
1372! Sorties eventuelles.
1373!----------------------
1374
1375!      if (nlarga0>0) then
1376!          print*,'WARNING !!!!!! DANS THERMCELL_DV2 '
1377!      print*,nlarga0,' points pour lesquels laraga=0. dans un thermique'
1378!          print*,'Il faudrait decortiquer ces points'
1379!      endif
1380
1381! ===========================================================================
1382! ============= FIN DV2 =====================================================
1383! ===========================================================================
1384
1385      else
1386
1387!      modname='momentum'
1388!      call thermcell_dqupdown(ngridmx,nlayermx,ptimestep,fm,entr,detr,  &
1389!     &     masse,zu,pduadj,ztvd,fm_down,ztv,modname,lmax)
1390!
1391!      call thermcell_dqupdown(ngridmx,nlayermx,ptimestep,fm,entr,detr,  &
1392!     &     masse,zv,pdvadj,ztvd,fm_down,ztv,modname,lmax)
1393
1394      endif
1395
1396!------------------------------------------------------------------
1397!  calcul du transport vertical de traceurs
1398!------------------------------------------------------------------
1399
1400! We only transport co2 tracer because it is coupled to the scheme through theta_m
1401! The rest is transported outside the sub-timestep loop
1402
1403      if (ico2.ne.0) then
1404!      if (nqmx .ne. 0.) then
1405      do l=1,nlayermx
1406         zdzfull(:,l)=zlev(:,l+1)-zlev(:,l)
1407      enddo
1408
1409      modname='tracer'
1410      call thermcell_dqup(ngridmx,nlayermx,ptimestep     &
1411     &     ,fm,entr,detr,  &
1412     &    masse,pq(:,:,ico2),pdqadj(:,:,ico2),modname,zdzfull)
1413!      endif
1414
1415! Compute the ratio between theta and theta_m
1416     
1417       do l=1,nlayermx
1418          do ig=1,ngridmx
1419             ratiom(ig,l)=1./(A*(pq(ig,l,ico2)+pdqadj(ig,l,ico2)*ptimestep)+B)
1420          enddo
1421       enddo
1422       else
1423          ratiom(:,:)=1.
1424       endif
1425
1426
1427!------------------------------------------------------------------
1428!  incrementation dt
1429!------------------------------------------------------------------
1430
1431      do l=1,nlayermx
1432         do ig=1,ngridmx
1433         pdtadj(ig,l)=(zdthladj(ig,l)+zdthladj_down(ig,l))*zpopsk(ig,l)*ratiom(ig,l)
1434         enddo
1435      enddo
1436
1437!------------------------------------------------------------------
1438!  calcul du transport vertical de la tke
1439!------------------------------------------------------------------
1440
1441!      modname='tke'
1442!      call thermcell_dqupdown(ngridmx,nlayermx,ptimestep,fm,entr,detr,  &
1443!      &      masse,pq2,pdq2adj,ztvd,fm_down,ztv,modname,lmax)
1444
1445! ===========================================================================
1446! ============= FIN TRANSPORT ===============================================
1447! ===========================================================================
1448
1449
1450!------------------------------------------------------------------
1451!   Calculs de diagnostiques pour les sorties
1452!------------------------------------------------------------------
1453! DIAGNOSTIQUE
1454! We compute interface values for teta env and th. The last interface
1455! value does not matter, as the mass flux is 0 there.
1456
1457   
1458      do l=1,nlayermx-1
1459       do ig=1,ngridmx
1460        teta_th_int(ig,l)=0.5*(ztva(ig,l+1)+ztva(ig,l))*ratiom(ig,l)
1461        teta_down_int(ig,l) = 0.5*(ztvd(ig,l+1)+ztvd(ig,l))*ratiom(ig,l)
1462        teta_env_int(ig,l)=0.5*(ztv(ig,l+1)+ztv(ig,l))*ratiom(ig,l)
1463       enddo
1464      enddo
1465      do ig=1,ngridmx
1466       teta_th_int(ig,nlayermx)=teta_th_int(ig,nlayermx-1)
1467       teta_env_int(ig,nlayermx)=teta_env_int(ig,nlayermx-1)
1468       teta_down_int(ig,nlayermx)=teta_down_int(ig,nlayermx-1)
1469      enddo
1470      do l=1,nlayermx
1471       do ig=1,ngridmx
1472        heatFlux(ig,l)=fm(ig,l)*(teta_th_int(ig,l)-teta_env_int(ig,l))/(rhobarz(ig,l))
1473        buoyancyOut(ig,l)=g*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
1474        buoyancyEst(ig,l)=g*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
1475        heatFlux_down(ig,l)=fm_down(ig,l)*(teta_down_int(ig,l)-teta_env_int(ig,l))/rhobarz(ig,l)
1476       enddo
1477      enddo
1478
1479      return
1480      end
Note: See TracBrowser for help on using the repository browser.