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

Last change on this file since 648 was 648, checked in by emillour, 13 years ago

Mars GCM:

  • some syntax corrections in thermcall_main_mars, vdif_cd, pbl_parameters which cause problems when compiling with some strict compilers (g95, gfortran)
  • added an initialisation of 'varian' in initracer for cases when using conrath dust; because that value can be is used elsewhere (e.g. surfacearea)

JYC+EM

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