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

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

Latest thermals adjustments.

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