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

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

Updated thermals version, that produces quite good overshoots in the inversion region. Series of zmax matches very well the LES and underline one of the weaknesses of convadj. This version will change, as this inversion is only produced in 222 levels. Some resolution tricks must be found for it to work at 32 levels.

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