source: LMDZ6/trunk/libf/phylmd/lmdz_thermcell_plume.f90 @ 5895

Last change on this file since 5895 was 5895, checked in by fhourdin, 14 hours ago

Nouvelles version des panaches thermiques.
Exploratoire.

File size: 18.4 KB
Line 
1MODULE lmdz_thermcell_plume
2!
3! $Id: lmdz_thermcell_plume.f90 5854 2025-10-10 14:00:56Z fhourdin $
4!
5CONTAINS
6
7      SUBROUTINE thermcell_plume(itap,ngrid,nlay,ptimestep,ztv,zthl,po,zl,rhobarz,  &
8     &           zlev,pplev,pphi,zpspsk,alim_star,alim_star_tot,  &
9     &           lalim,f0,zmax0,detr_star,entr_star,f_star,csc,ztva,  &
10     &           ztla,zqla,zqta,zha,zw2,w_est,ztva_est,zqsatth,lmix,lmix_bis,linter &
11    &           ,lev_out,lunout1,igout)
12!     &           ,lev_out,lunout1,igout,zbuoy,zbuoyjam)
13!--------------------------------------------------------------------------
14!thermcell_plume: calcule les valeurs de qt, thetal et w dans l ascendance
15!--------------------------------------------------------------------------
16
17       USE lmdz_thermcell_ini, ONLY: prt_level,fact_thermals_ed_dz,iflag_thermals_ed,RLvCP,RETV,RG
18       USE lmdz_thermcell_ini, ONLY: fact_epsilon, betalpha, afact, fact_shell
19       USE lmdz_thermcell_ini, ONLY: detr_min, entr_min, detr_q_coef, detr_q_power
20       USE lmdz_thermcell_ini, ONLY: mix0, thermals_flag_alim
21       USE lmdz_thermcell_alim, ONLY : thermcell_alim
22       USE lmdz_thermcell_qsat, ONLY : thermcell_qsat
23
24
25       IMPLICIT NONE
26
27      integer,intent(in) :: itap,lev_out,lunout1,igout,ngrid,nlay
28      real,intent(in) :: ptimestep
29      real,intent(in),dimension(ngrid,nlay) :: ztv
30      real,intent(in),dimension(ngrid,nlay) :: zthl
31      real,intent(in),dimension(ngrid,nlay) :: po
32      real,intent(in),dimension(ngrid,nlay) :: zl
33      real,intent(in),dimension(ngrid,nlay) :: rhobarz
34      real,intent(in),dimension(ngrid,nlay+1) :: zlev
35      real,intent(in),dimension(ngrid,nlay+1) :: pplev
36      real,intent(in),dimension(ngrid,nlay) :: pphi
37      real,intent(in),dimension(ngrid,nlay) :: zpspsk
38      real,intent(in),dimension(ngrid) :: f0,zmax0
39
40      integer,intent(out) :: lalim(ngrid)
41      real,intent(out),dimension(ngrid,nlay) :: alim_star
42      real,intent(out),dimension(ngrid) :: alim_star_tot
43      real,intent(out),dimension(ngrid,nlay) :: detr_star
44      real,intent(out),dimension(ngrid,nlay) :: entr_star
45      real,intent(out),dimension(ngrid,nlay+1) :: f_star
46      real,intent(out),dimension(ngrid,nlay) :: csc
47      real,intent(out),dimension(ngrid,nlay) :: ztva
48      real,intent(out),dimension(ngrid,nlay) :: ztla
49      real,intent(out),dimension(ngrid,nlay) :: zqla
50      real,intent(out),dimension(ngrid,nlay) :: zqta
51      real,intent(out),dimension(ngrid,nlay) :: zha
52      real,intent(out),dimension(ngrid,nlay+1) :: zw2
53      real,intent(out),dimension(ngrid,nlay+1) :: w_est
54      real,intent(out),dimension(ngrid,nlay) :: ztva_est
55      real,intent(out),dimension(ngrid,nlay) :: zqsatth
56      integer,intent(out),dimension(ngrid) :: lmix
57      integer,intent(out),dimension(ngrid) :: lmix_bis
58      real,intent(out),dimension(ngrid) :: linter
59
60      REAL zdw2,zdw2bis
61      REAL zw2modif
62      REAL zw2fact,zw2factbis
63      REAL,dimension(ngrid,nlay) :: zeps
64
65      REAL, dimension(ngrid) ::    wmaxa
66
67      INTEGER ig,l,k,lt,it,lm
68      integer nbpb
69
70      real,dimension(ngrid,nlay) :: detr
71      real,dimension(ngrid,nlay) :: entr
72      real,dimension(ngrid,nlay+1) :: wa_moy
73      real,dimension(ngrid,nlay) :: ztv_est
74      real,dimension(ngrid) :: ztemp,zqsat
75      real,dimension(ngrid,nlay) :: zqla_est
76      real,dimension(ngrid,nlay) :: zta_est
77
78      real,dimension(ngrid,nlay) :: zbuoy,gamma,zdqt
79      real zdz,zalpha,zw2m
80      real,dimension(ngrid,nlay) :: zbuoyjam,zdqtjam
81      real zbuoybis,zdz2,zdz3,lmel,entrbis,zdzbis
82      real, dimension(ngrid) :: d_temp
83      real ztv1,ztv2,factinv,zinv,zlmel
84      real zlmelup,zlmeldwn,zlt,zltdwn,zltup
85      real atv1,atv2,btv1,btv2
86      real ztv_est1,ztv_est2
87      real zcor,zdelta,zcvm5,qlbef
88      real zbetalpha, coefzlmel
89      real eps
90      logical Zsat
91      LOGICAL,dimension(ngrid) :: active,activetmp
92      REAL fact_gamma,fact_gamma2,fact_epsilon2
93      REAL coefc
94      REAL,dimension(ngrid,nlay) :: c2
95
96      real, dimension(ngrid,nlay) :: z_detr_q,z_cld_radius
97      real, dimension(ngrid) :: z_cld_radius_base,z_cld_base_height,z_alpha_base
98
99      integer choice_ed_main,choice_ed_dq
100
101      z_cld_base_height(:)=0.
102
103      if (ngrid==1) print*,'THERMCELL PLUME Modifie 2025/11/11'
104
105! ---------------------------------------------------------------
106!  Controling entrainment and detrainment
107!     iflag_thermals_ed=1XY
108!     choice_ed_main=X
109!     choice_ed_dq=Y
110!     X=0 et Y=0 <=> thermcell_plume_6A
111      choice_ed_main=(iflag_thermals_ed-100)/10
112      choice_ed_dq=(iflag_thermals_ed-100)-10*choice_ed_main
113! ---------------------------------------------------------------
114 
115
116      zbetalpha=betalpha/(1.+betalpha)
117
118
119! Initialisations des variables r?elles
120Zsat=.false.
121if (1==1) then
122      ztva(:,:)=ztv(:,:)
123      ztva_est(:,:)=ztva(:,:)
124      ztv_est(:,:)=ztv(:,:)
125      ztla(:,:)=zthl(:,:)
126      zqta(:,:)=po(:,:)
127      zqla(:,:)=0.
128      zha(:,:) = ztva(:,:)
129else
130      ztva(:,:)=0.
131      ztv_est(:,:)=0.
132      ztva_est(:,:)=0.
133      ztla(:,:)=0.
134      zqta(:,:)=0.
135      zha(:,:) =0.
136endif
137
138      zqla_est(:,:)=0.
139      zqsatth(:,:)=0.
140      zqla(:,:)=0.
141      detr_star(:,:)=0.
142      entr_star(:,:)=0.
143      alim_star(:,:)=0.
144      alim_star_tot(:)=0.
145      csc(:,:)=0.
146      detr(:,:)=0.
147      entr(:,:)=0.
148      zw2(:,:)=0.
149      zbuoy(:,:)=0.
150      zbuoyjam(:,:)=0.
151      gamma(:,:)=0.
152      zeps(:,:)=0.
153      w_est(:,:)=0.
154      f_star(:,:)=0.
155      wa_moy(:,:)=0.
156      linter(:)=1.
157!     linter(:)=1.
158! Initialisation des variables entieres
159      lmix(:)=1
160      lmix_bis(:)=2
161      wmaxa(:)=0.
162
163! Initialisation a 0  en cas de sortie dans replay
164      zqsat(:)=0.
165      zta_est(:,:)=0.
166      zdqt(:,:)=0.
167      zdqtjam(:,:)=0.
168      c2(:,:)=0.
169
170
171!-------------------------------------------------------------------------
172! On ne considere comme actif que les colonnes dont les deux premieres
173! couches sont instables.
174!-------------------------------------------------------------------------
175
176      active(:)=ztv(:,1)>ztv(:,2)
177      d_temp(:)=0. ! Pour activer un contraste de temperature a la base
178                   ! du panache
179!  Cet appel pourrait être fait avant thermcell_plume dans thermcell_main
180      CALL thermcell_alim(thermals_flag_alim,ngrid,nlay,ztv,d_temp,zlev,alim_star,lalim)
181
182!------------------------------------------------------------------------------
183! Calcul dans la premiere couche
184! On decide dans cette version que le thermique n'est actif que si la premiere
185! couche est instable.
186! Pourrait etre change si on veut que le thermiques puisse se d??clencher
187! dans une couche l>1
188!------------------------------------------------------------------------------
189do ig=1,ngrid
190! Le panache va prendre au debut les caracteristiques de l'air contenu
191! dans cette couche.
192    if (active(ig)) then
193    ztla(ig,1)=zthl(ig,1)
194    zqta(ig,1)=po(ig,1)
195    zqla(ig,1)=zl(ig,1)
196!cr: attention, prise en compte de f*(1)=1
197    f_star(ig,2)=alim_star(ig,1)
198    zw2(ig,2)=2.*RG*(ztv(ig,1)-ztv(ig,2))/ztv(ig,2)  &
199&                     *(zlev(ig,2)-zlev(ig,1))  &
200&                     *0.4*pphi(ig,1)/(pphi(ig,2)-pphi(ig,1))
201    w_est(ig,2)=zw2(ig,2)
202    endif
203enddo
204!
205
206!==============================================================================
207!boucle de calcul de la vitesse verticale dans le thermique
208!==============================================================================
209do l=2,nlay-1
210!==============================================================================
211
212
213! On decide si le thermique est encore actif ou non
214! AFaire : Il faut sans doute ajouter entr_star a alim_star dans ce test
215    do ig=1,ngrid
216       active(ig)=active(ig) &
217&                 .and. zw2(ig,l)>1.e-10 &
218&                 .and. f_star(ig,l)+alim_star(ig,l)>1.e-10
219    enddo
220
221
222
223!---------------------------------------------------------------------------
224! calcul des proprietes thermodynamiques et de la vitesse de la couche l
225! sans tenir compte du detrainement et de l'entrainement dans cette
226! couche
227! C'est a dire qu'on suppose
228! ztla(l)=ztla(l-1) et zqta(l)=zqta(l-1)
229! Ici encore, on doit pouvoir ajouter entr_star (qui peut etre calculer
230! avant) a l'alimentation pour avoir un calcul plus propre
231!---------------------------------------------------------------------------
232
233   ztemp(:)=zpspsk(:,l)*ztla(:,l-1)
234   call thermcell_qsat(ngrid, 1, active,pplev(:,l),ztemp,zqta(:,l-1),zqsat(:))
235    do ig=1,ngrid
236!       print*,'active',active(ig),ig,l
237       if(active(ig)) then
238        zqla_est(ig,l)=max(0.,zqta(ig,l-1)-zqsat(ig))
239        ztva_est(ig,l) = ztla(ig,l-1)*zpspsk(ig,l)+RLvCp*zqla_est(ig,l)
240        zta_est(ig,l)=ztva_est(ig,l)
241        ztva_est(ig,l) = ztva_est(ig,l)/zpspsk(ig,l)
242        ztva_est(ig,l) = ztva_est(ig,l)*(1.+RETV*(zqta(ig,l-1)-zqla_est(ig,l)))
243 
244
245!Modif AJAM
246
247        zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
248        zdz=zlev(ig,l+1)-zlev(ig,l)         
249        lmel=fact_thermals_ed_dz*zlev(ig,l)
250!        lmel=0.09*zlev(ig,l)
251        zlmel=zlev(ig,l)+lmel
252        zlmelup=zlmel+(zdz/2)
253        zlmeldwn=zlmel-(zdz/2)
254
255        lt=l+1
256        zlt=zlev(ig,lt)
257        zdz3=zlev(ig,lt+1)-zlt
258        zltdwn=zlt-zdz3/2
259        zltup=zlt+zdz3/2
260         
261!=========================================================================
262! 3. Calcul de la flotabilite modifie par melange avec l'air au dessus
263!=========================================================================
264
265        lt=l+1
266        zlt=zlev(ig,lt)
267        zdz2=zlev(ig,lt)-zlev(ig,l)
268
269        do while (lmel.gt.zdz2)
270          lt=lt+1
271          zlt=zlev(ig,lt)
272          zdz2=zlt-zlev(ig,l)
273        enddo
274        zdz3=zlev(ig,lt+1)-zlt
275        zltdwn=zlev(ig,lt)-zdz3/2
276        zlmelup=zlmel+(zdz/2)
277        coefzlmel=Min(1.,(zlmelup-zltdwn)/zdz)
278        zbuoyjam(ig,l)=1.*RG*(coefzlmel*(ztva_est(ig,l)- &
279    &   ztv(ig,lt))/ztv(ig,lt)+(1.-coefzlmel)*(ztva_est(ig,l)- &
280    &   ztv(ig,lt-1))/ztv(ig,lt-1))+0.*zbuoy(ig,l)
281
282!------------------------------------------------
283!AJAM:nouveau calcul de w? 
284!------------------------------------------------
285        zdz=zlev(ig,l+1)-zlev(ig,l)
286        zdzbis=zlev(ig,l)-zlev(ig,l-1)
287        zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
288
289        zw2fact=fact_epsilon*2.*zdz/(1.+betalpha)
290        zw2factbis=fact_epsilon*2.*zdzbis/(1.+betalpha)
291        zdw2=afact*zbuoy(ig,l)/fact_epsilon
292        zdw2bis=afact*zbuoy(ig,l-1)/fact_epsilon
293        lm=Max(1,l-2)
294        w_est(ig,l+1)=Max(0.0001,exp(-zw2fact)*(w_est(ig,l)-zdw2)+zdw2)
295
296
297       endif
298    enddo
299
300
301!-------------------------------------------------
302! 4. calcul des taux d'entrainement et de detrainement
303!-------------------------------------------------
304
305     do ig=1,ngrid
306        if (active(ig)) then
307
308!          zw2m=max(0.5*(w_est(ig,l)+w_est(ig,l+1)),0.1)
309          zw2m=w_est(ig,l+1)
310!          zw2m=zw2(ig,l)
311          zdz=zlev(ig,l+1)-zlev(ig,l)
312          zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
313!          zbuoybis=zbuoy(ig,l)+RG*0.1/300.
314          zbuoybis=zbuoy(ig,l)
315          zalpha=f0(ig)*f_star(ig,l)/sqrt(w_est(ig,l+1))/rhobarz(ig,l)
316          zdqt(ig,l)=max(zqta(ig,l-1)-po(ig,l),0.)/po(ig,l)
317
318         
319         
320! detr_q_coef = thermals_detr_q_coef lu dans les .def
321! vrai flux de masse : f0*fstar
322! equation de conservation de la masse s'écrit : f*(k+1) - f*(k) = e*(k) - d*(k)
323! e=f0 e* / dz
324
325          if ( choice_ed_dq == 0 )  then
326
327              z_detr_q(ig,l)=detr_q_coef*(zdqt(ig,l)/zw2m)**detr_q_power
328
329          elseif ( choice_ed_dq == 1 )  then
330
331              ! Tant que la couche du dessous n'est pas condensée, on ne tient pas
332              ! compte du détrainement en q
333              ! FH V1 : if ( zqla(ig,l-1) > 0. ) then
334              if ( zqla_est(ig,l) > 0. ) then
335                  if ( z_cld_base_height(ig) == 0. ) then
336                       ! Cloud base : height and fraction
337                       z_cld_base_height(ig)=zlev(ig,l) ! z at cloud base
338                       z_alpha_base(ig)=zalpha
339                  endif
340                  ! Cloud radius. At cloud base = cloud_height / 2. Cloud_height=zmax0-z_cld_base_height
341                  !    With min value dz of the layer
342                  ! FH V1 : z_cld_radius(ig,l)=sqrt(zalpha/z_alpha_base(ig))*0.5*(max(zmax0(ig)-z_cld_base_height(ig),zlev(ig,l+1)-zlev(ig,l)))
343                  z_cld_radius(ig,l)=0.5*(max(zmax0(ig)-z_cld_base_height(ig),zlev(ig,l+1)-zlev(ig,l)))
344                  z_detr_q(ig,l)=detr_q_coef*(zdqt(ig,l)/zw2m)**detr_q_power*2./z_cld_radius(ig,l)
345              else
346                  z_detr_q(ig,l)=0.
347              endif
348
349          else
350
351              print*,'choice_ed_dq=',choice_ed_dq,' non prevu'
352              stop
353
354          endif
355
356! zbetalpha = B1 / ( 1 + B1 )
357! afact     = A1
358! zbuoyjam  = B
359! zw2m      = w2
360! z_detr_q  = terme de détrainement de Delta q
361
362          if ( choice_ed_main == 0 ) then
363
364              detr_star(ig,l)=f_star(ig,l)*zdz             &
365    &         *( mix0 * 0.1 / (zalpha+0.001)               &
366    &         + MAX(detr_min, -afact*zbetalpha*zbuoyjam(ig,l)/zw2m   &
367    &         + z_detr_q(ig,l)) )
368
369              zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
370              entr_star(ig,l)=f_star(ig,l)*zdz* (         &
371    &           mix0 * 0.1 / (zalpha+0.001)               &
372    &         + zbetalpha*MAX(entr_min,                   &
373    &         afact*zbuoyjam(ig,l)/zw2m - fact_epsilon))
374
375          elseif ( choice_ed_main == 1 ) then
376
377              detr_star(ig,l)=f_star(ig,l)*zdz                 &
378    &         *( mix0 * 0.1 / (zalpha+0.001)                   &
379    &         + detr_min                                       &
380    &         + MAX(-afact*zbetalpha*zbuoyjam(ig,l)/zw2m,0.)   &
381    &         + z_detr_q(ig,l) )
382
383              zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l)
384              entr_star(ig,l)=f_star(ig,l)*zdz* (              &
385    &           mix0 * 0.1 / (zalpha+0.001)                    &
386    &         + entr_min                                       &
387    &         + zbetalpha*MAX(0.,                              &
388    &         afact*zbuoyjam(ig,l)/zw2m - fact_epsilon))
389
390
391          else
392              print*,'choice_ed_dq=',choice_ed_dq,' non prevu'
393              stop
394          endif
395
396
397         
398! En dessous de lalim, on prend le max de alim_star et entr_star pour
399! alim_star et 0 sinon
400        if (l.lt.lalim(ig)) then
401          alim_star(ig,l)=max(alim_star(ig,l),entr_star(ig,l))
402          entr_star(ig,l)=0.
403        endif
404!        if (l.lt.lalim(ig).and.alim_star(ig,l)>alim_star(ig,l-1)) then
405!          alim_star(ig,l)=entrbis
406!        endif
407
408!        print*,'alim0',zlev(ig,l),entr_star(ig,l),detr_star(ig,l),zw2m,zbuoy(ig,l),f_star(ig,l)
409! Calcul du flux montant normalise
410      f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)  &
411     &              -detr_star(ig,l)
412
413      endif
414   enddo
415
416
417!============================================================================
418! 5. calcul de la vitesse verticale en melangeant Tl et qt du thermique
419!===========================================================================
420
421   activetmp(:)=active(:) .and. f_star(:,l+1)>1.e-10
422   do ig=1,ngrid
423       if (activetmp(ig)) then
424           Zsat=.false.
425           ztla(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+  &
426     &            (alim_star(ig,l)+entr_star(ig,l))*zthl(ig,l))  &
427     &            /(f_star(ig,l+1)+detr_star(ig,l))
428           zqta(ig,l)=(f_star(ig,l)*zqta(ig,l-1)+  &
429     &            (alim_star(ig,l)+entr_star(ig,l))*po(ig,l))  &
430     &            /(f_star(ig,l+1)+detr_star(ig,l))
431
432        endif
433    enddo
434
435   ztemp(:)=zpspsk(:,l)*ztla(:,l)
436   call thermcell_qsat(ngrid, 1, activetmp,pplev(:,l),ztemp,zqta(:,l),zqsatth(:,l))
437   do ig=1,ngrid
438      if (activetmp(ig)) then
439! on ecrit de maniere conservative (sat ou non)
440!          T = Tl +Lv/Cp ql
441           zqla(ig,l)=max(0.,zqta(ig,l)-zqsatth(ig,l))
442           ztva(ig,l) = ztla(ig,l)*zpspsk(ig,l)+RLvCp*zqla(ig,l)
443           ztva(ig,l) = ztva(ig,l)/zpspsk(ig,l)
444!on rajoute le calcul de zha pour diagnostiques (temp potentielle)
445           zha(ig,l) = ztva(ig,l)
446           ztva(ig,l) = ztva(ig,l)*(1.+RETV*(zqta(ig,l)-zqla(ig,l)))
447           zbuoy(ig,l)=RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
448           zdz=zlev(ig,l+1)-zlev(ig,l)
449           zdzbis=zlev(ig,l)-zlev(ig,l-1)
450           zeps(ig,l)=(entr_star(ig,l)+alim_star(ig,l))/(f_star(ig,l)*zdz)
451           zw2fact=fact_epsilon*2.*zdz/(1.+betalpha)
452           zw2factbis=fact_epsilon*2.*zdzbis/(1.+betalpha)
453           zdw2= afact*zbuoy(ig,l)/(fact_epsilon)
454           zdw2bis= afact*zbuoy(ig,l-1)/(fact_epsilon)
455           zw2(ig,l+1)=Max(0.0001,exp(-zw2fact)*(zw2(ig,l)-zdw2)+zdw2)
456      endif
457   enddo
458
459        if (prt_level.ge.20) print*,'coucou calcul detr 460: ig, l',ig, l
460!
461!===========================================================================
462! 6. initialisations pour le calcul de la hauteur du thermique, de l'inversion et de la vitesse verticale max
463!===========================================================================
464
465   nbpb=0
466   do ig=1,ngrid
467            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
468                nbpb=nbpb+1
469                zw2(ig,l+1)=0.
470                linter(ig)=l+1
471            endif
472
473        if (zw2(ig,l+1).lt.0.) then
474           linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
475     &               -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
476           zw2(ig,l+1)=0.
477!+CR:04/05/12:correction calcul linter pour calcul de zmax continu
478        elseif (f_star(ig,l+1).lt.0.) then
479           linter(ig)=(l*(f_star(ig,l+1)-f_star(ig,l))  &
480     &               -f_star(ig,l))/(f_star(ig,l+1)-f_star(ig,l))
481           zw2(ig,l+1)=0.
482!fin CR:04/05/12
483        endif
484
485           wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
486
487        if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
488!   lmix est le niveau de la couche ou w (wa_moy) est maximum
489!on rajoute le calcul de lmix_bis
490            if (zqla(ig,l).lt.1.e-10) then
491               lmix_bis(ig)=l+1
492            endif
493            lmix(ig)=l+1
494            wmaxa(ig)=wa_moy(ig,l+1)
495        endif
496   enddo
497
498   if (nbpb>0) then
499   print*,'WARNING on tombe ',nbpb,' x sur un pb pour l=',l,' dans thermcell_plume'
500   endif
501
502!=========================================================================
503! FIN DE LA BOUCLE VERTICALE
504      enddo
505!=========================================================================
506
507!on recalcule alim_star_tot
508       do ig=1,ngrid
509          alim_star_tot(ig)=0.
510       enddo
511       do ig=1,ngrid
512          do l=1,lalim(ig)-1
513          alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l)
514          enddo
515       enddo
516       
517
518        if (prt_level.ge.20) print*,'coucou calcul detr 470: ig, l', ig, l
519
520 RETURN
521     END SUBROUTINE thermcell_plume
522END MODULE lmdz_thermcell_plume
Note: See TracBrowser for help on using the repository browser.