source: LMDZ4/trunk/libf/phylmd/thermcell_main.F90 @ 879

Last change on this file since 879 was 879, checked in by Laurent Fairhead, 18 years ago

Suite de la bascule vers une physique avec thermiques, nouvelle convection, poche froide ...
LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 22.5 KB
RevLine 
[878]1!
2! $Header$
3!
4      SUBROUTINE thermcell_main(ngrid,nlay,ptimestep  &
5     &                  ,pplay,pplev,pphi,debut  &
6     &                  ,pu,pv,pt,po  &
7     &                  ,pduadj,pdvadj,pdtadj,pdoadj  &
8     &                  ,fm0,entr0,zqla,lmax  &
9     &                  ,ratqscth,ratqsdiff,zqsatth  &
[879]10     &                  ,r_aspect,l_mix,w2di,tho &
11     &                  ,Ale_bl,Alp_bl,lalim_conv,wght_th)
[878]12
13      IMPLICIT NONE
14
15!=======================================================================
16!   Auteurs: Frederic Hourdin, Catherine Rio, Anne Mathieu
17!   Version du 09.02.07
18!   Calcul du transport vertical dans la couche limite en presence
19!   de "thermiques" explicitement representes avec processus nuageux
20!
21!   Réécriture à partir d'un listing papier à Habas, le 14/02/00
22!
23!   le thermique est supposé homogène et dissipé par mélange avec
24!   son environnement. la longueur l_mix contrôle l'efficacité du
25!   mélange
26!
27!   Le calcul du transport des différentes espèces se fait en prenant
28!   en compte:
29!     1. un flux de masse montant
30!     2. un flux de masse descendant
31!     3. un entrainement
32!     4. un detrainement
33!
34!=======================================================================
35
36!-----------------------------------------------------------------------
37!   declarations:
38!   -------------
39
40#include "dimensions.h"
41#include "dimphy.h"
42#include "YOMCST.h"
43#include "YOETHF.h"
44#include "FCTTRE.h"
45
46!   arguments:
47!   ----------
48
49      INTEGER ngrid,nlay,w2di,tho
50      real ptimestep,l_mix,r_aspect
51      REAL pt(ngrid,nlay),pdtadj(ngrid,nlay)
52      REAL pu(ngrid,nlay),pduadj(ngrid,nlay)
53      REAL pv(ngrid,nlay),pdvadj(ngrid,nlay)
54      REAL po(ngrid,nlay),pdoadj(ngrid,nlay)
55      REAL pplay(ngrid,nlay),pplev(ngrid,nlay+1)
56      real pphi(ngrid,nlay)
57
58!   local:
59!   ------
60
[879]61      integer,save :: igout=1521
[878]62      integer,save :: lunout=6
[879]63      integer,save :: lev_out=1
[878]64
65      INTEGER ig,k,l,ll
66      real zsortie1d(klon)
67      INTEGER lmax(klon),lmin(klon),lalim(klon)
68      INTEGER lmix(klon)
69      real linter(klon)
70      real zmix(klon)
71      real zmax(klon),zw2(klon,klev+1),ztva(klon,klev)
72      real zmax_sec(klon)
73      real w_est(klon,klev+1)
74!on garde le zmax du pas de temps precedent
75      real zmax0(klon)
76      save zmax0
77
78      real zlev(klon,klev+1),zlay(klon,klev)
79      real deltaz(klon,klev)
80      REAL zh(klon,klev),zdhadj(klon,klev)
81      real zthl(klon,klev),zdthladj(klon,klev)
82      REAL ztv(klon,klev)
83      real zu(klon,klev),zv(klon,klev),zo(klon,klev)
84      real zl(klon,klev)
85      real zsortie(klon,klev)
86      real zva(klon,klev)
87      real zua(klon,klev)
88      real zoa(klon,klev)
89
90      real zta(klon,klev)
91      real zha(klon,klev)
92      real fraca(klon,klev+1)
93      real zf,zf2
94      real thetath2(klon,klev),wth2(klon,klev),wth3(klon,klev)
95      real q2(klon,klev)
96      common/comtherm/thetath2,wth2
97   
98      real ratqscth(klon,klev)
99      real var
100      real vardiff
101      real ratqsdiff(klon,klev)
102      integer isplit,nsplit
103      parameter (nsplit=10)
104      data isplit/0/
105      save isplit
106
107      logical sorties
108      real rho(klon,klev),rhobarz(klon,klev+1),masse(klon,klev)
109      real zpspsk(klon,klev)
110
111      real wmax(klon)
112      real wmax_sec(klon)
113      real fm0(klon,klev+1),entr0(klon,klev),detr(klon,klev)
114      real detr0(klon,klev)
115      real fm(klon,klev+1),entr(klon,klev)
116
117      real ztla(klon,klev),zqla(klon,klev),zqta(klon,klev)
118!niveau de condensation
[879]119      integer nivcon(klon)
[878]120      real zcon(klon)
121      REAL CHI
122      real zcon2(klon)
123      real pcon(klon)
124      real zqsat(klon,klev)
125      real zqsatth(klon,klev)
126
127      real f_star(klon,klev+1),entr_star(klon,klev)
128      real detr_star(klon,klev)
129      real alim_star_tot(klon),alim_star2(klon)
130      real alim_star(klon,klev)
131      real f(klon), f0(klon)
132      save f0
133      real zlevinter(klon)
134      logical debut
135       real seuil
136
137!
[879]138      !nouvelles variables pour la convection
139      real Ale_bl(klon)
140      real Alp_bl(klon)
141      real alp_int(klon)
142      real ale_int(klon)
143      integer n_int(klon)
144      real fm_tot(klon)
145      real wght_th(klon,klev)
146      integer lalim_conv(klon)
147      logical therm
148      save therm
[878]149
150      character*2 str2
151      character*10 str10
152
153      EXTERNAL SCOPY
154!
155
156!-----------------------------------------------------------------------
157!   initialisation:
158!   ---------------
159!
160
161      seuil=0.25
162
163      if (lev_out.ge.1) print*,'thermcell_main V4'
164
165       sorties=.true.
166      IF(ngrid.NE.klon) THEN
167         PRINT*
168         PRINT*,'STOP dans convadj'
169         PRINT*,'ngrid    =',ngrid
170         PRINT*,'klon  =',klon
171      ENDIF
172!
173!Initialisation
174!
175      do ig=1,klon     
176      if ((debut).or.((.not.debut).and.(f0(ig).lt.1.e-10))) then
177            f0(ig)=1.e-5
178            zmax0(ig)=40.
[879]179            therm=.false.
[878]180      endif
181      enddo
182
183
184
185!-----------------------------------------------------------------------
186! Calcul de T,q,ql a partir de Tl et qT dans l environnement
187!   --------------------------------------------------------------------
188!
189      CALL thermcell_env(ngrid,nlay,po,pt,pu,pv,pplay,  &
190     &           pplev,zo,zh,zl,ztv,zthl,zu,zv,zpspsk,zqsat,lev_out)
191       
192      if (lev_out.ge.1) print*,'thermcell_main apres thermcell_env'
193
194!------------------------------------------------------------------------
195!                       --------------------
196!
197!
198!                       + + + + + + + + + + +
199!
200!
201!  wa, fraca, wd, fracd --------------------   zlev(2), rhobarz
202!  wh,wt,wo ...
203!
204!                       + + + + + + + + + + +  zh,zu,zv,zo,rho
205!
206!
207!                       --------------------   zlev(1)
208!                       \\\\\\\\\\\\\\\\\\\\
209!
210!
211
212!-----------------------------------------------------------------------
213!   Calcul des altitudes des couches
214!-----------------------------------------------------------------------
215
216      do l=2,nlay
217         zlev(:,l)=0.5*(pphi(:,l)+pphi(:,l-1))/RG
218      enddo
219         zlev(:,1)=0.
220         zlev(:,nlay+1)=(2.*pphi(:,klev)-pphi(:,klev-1))/RG
221      do l=1,nlay
222         zlay(:,l)=pphi(:,l)/RG
223      enddo
224!calcul de l epaisseur des couches
225      do l=1,nlay
226         deltaz(:,l)=zlev(:,l+1)-zlev(:,l)
227      enddo
228
229!     print*,'2 OK convect8'
230!-----------------------------------------------------------------------
231!   Calcul des densites
232!-----------------------------------------------------------------------
233
234      do l=1,nlay
235         rho(:,l)=pplay(:,l)/(zpspsk(:,l)*RD*ztv(:,l))
236      enddo
237
238      do l=2,nlay
239         rhobarz(:,l)=0.5*(rho(:,l)+rho(:,l-1))
240      enddo
241
242!calcul de la masse
243      do l=1,nlay
244         masse(:,l)=(pplev(:,l)-pplev(:,l+1))/RG
245      enddo
246
247      if (lev_out.ge.1) print*,'thermcell_main apres initialisation'
248
249!------------------------------------------------------------------
250!
251!             /|\
252!    --------  |  F_k+1 -------   
253!                              ----> D_k
254!             /|\              <---- E_k , A_k
255!    --------  |  F_k ---------
256!                              ----> D_k-1
257!                              <---- E_k-1 , A_k-1
258!
259!
260!
261!
262!
263!    ---------------------------
264!
265!    ----- F_lmax+1=0 ----------         \
266!            lmax     (zmax)              |
267!    ---------------------------          |
268!                                         |
269!    ---------------------------          |
270!                                         |
271!    ---------------------------          |
272!                                         |
273!    ---------------------------          |
274!                                         |
275!    ---------------------------          |
276!                                         |  E
277!    ---------------------------          |  D
278!                                         |
279!    ---------------------------          |
280!                                         |
281!    ---------------------------  \       |
282!            lalim                 |      |
283!    ---------------------------   |      |
284!                                  |      |
285!    ---------------------------   |      |
286!                                  | A    |
287!    ---------------------------   |      |
288!                                  |      |
289!    ---------------------------   |      |
290!    lmin  (=1 pour le moment)     |      |
291!    ----- F_lmin=0 ------------  /      /
292!
293!    ---------------------------
294!    //////////////////////////
295!
296!
297!=============================================================================
298!  Calculs initiaux ne faisant pas intervenir les changements de phase
299!=============================================================================
300
301!------------------------------------------------------------------
302!  1. alim_star est le profil vertical de l'alimentation à la base du
303!     panache thermique, calculé à partir de la flotabilité de l'air sec
304!  2. lmin et lalim sont les indices inferieurs et superieurs de alim_star
305!------------------------------------------------------------------
306!
307      entr_star=0. ; detr_star=0. ; alim_star=0. ; alim_star_tot=0.
308      CALL thermcell_init(ngrid,nlay,ztv,zlev,  &
309     &                    lalim,lmin,alim_star,alim_star_tot,lev_out)
310
311call test_ltherm(ngrid,nlay,pplev,pplay,lmin,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_init lmin  ')
312call test_ltherm(ngrid,nlay,pplev,pplay,lalim,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_init lalim ')
313
314
315      if (lev_out.ge.1) print*,'thermcell_main apres thermcell_init'
316      if (lev_out.ge.10) then
317         write(lunout,*) 'Dans thermcell_main 1'
318         write(lunout,*) 'lmin ',lmin(igout)
319         write(lunout,*) 'lalim ',lalim(igout)
320         write(lunout,*) ' ig l alim_star thetav'
321         write(lunout,'(i6,i4,2e15.5)') (igout,l,alim_star(igout,l) &
322     &   ,ztv(igout,l),l=1,lalim(igout)+4)
323      endif
324
[879]325      do ig=1,klon
326      if (alim_star(ig,1).gt.1.e-10) then
327         therm=.true.
328      endif
329      enddo
[878]330!-----------------------------------------------------------------------------
331!  3. wmax_sec et zmax_sec sont les vitesses et altitudes maximum d'un
332!     panache sec conservatif (e=d=0) alimente selon alim_star
333!     Il s'agit d'un calcul de type CAPE
334!     zmax_sec est utilisé pour déterminer la géométrie du thermique.
335!------------------------------------------------------------------------------
336!
337      CALL thermcell_dry(ngrid,nlay,zlev,pphi,ztv,alim_star,  &
338     &                      lalim,lmin,zmax_sec,wmax_sec,lev_out)
339
340call test_ltherm(ngrid,nlay,pplev,pplay,lmin,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_dry  lmin  ')
341call test_ltherm(ngrid,nlay,pplev,pplay,lalim,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_dry  lalim ')
342
343      if (lev_out.ge.1) print*,'thermcell_main apres thermcell_dry'
344      if (lev_out.ge.10) then
345         write(lunout,*) 'Dans thermcell_main 1b'
346         write(lunout,*) 'lmin ',lmin(igout)
347         write(lunout,*) 'lalim ',lalim(igout)
348         write(lunout,*) ' ig l alim_star entr_star detr_star f_star '
349         write(lunout,'(i6,i4,e15.5)') (igout,l,alim_star(igout,l) &
350     &    ,l=1,lalim(igout)+4)
351      endif
352
353
354
355!---------------------------------------------------------------------------------
356!calcul du melange et des variables dans le thermique
357!--------------------------------------------------------------------------------
358!
359      CALL thermcell_plume(ngrid,nlay,ztv,zthl,po,zl,rhobarz,  &
360     &           zlev,pplev,pphi,zpspsk,l_mix,r_aspect,alim_star,  &
361     &           lalim,zmax_sec,f0,detr_star,entr_star,f_star,ztva,  &
362     &           ztla,zqla,zqta,zha,zw2,zqsatth,lmix,linter,lev_out)
363      call test_ltherm(ngrid,nlay,pplev,pplay,lalim,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_plum lalim ')
364      call test_ltherm(ngrid,nlay,pplev,pplay,lmix ,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_plum lmix  ')
365
366      if (lev_out.ge.1) print*,'thermcell_main apres thermcell_plume'
367      if (lev_out.ge.10) then
368         write(lunout,*) 'Dans thermcell_main 2'
369         write(lunout,*) 'lmin ',lmin(igout)
370         write(lunout,*) 'lalim ',lalim(igout)
371         write(lunout,*) ' ig l alim_star entr_star detr_star f_star '
372         write(lunout,'(i6,i4,4e15.5)') (igout,l,alim_star(igout,l),entr_star(igout,l),detr_star(igout,l) &
373     &    ,f_star(igout,l+1),l=1,nint(linter(igout))+5)
374      endif
375
376!-------------------------------------------------------------------------------
377! Calcul des caracteristiques du thermique:zmax,zmix,wmax
378!-------------------------------------------------------------------------------
379!
380      CALL thermcell_height(ngrid,nlay,lalim,lmin,linter,lmix,zw2,  &
381     &           zlev,lmax,zmax,zmax0,zmix,wmax,lev_out)
382
383
384      call test_ltherm(ngrid,nlay,pplev,pplay,lalim,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_heig lalim ')
385      call test_ltherm(ngrid,nlay,pplev,pplay,lmin ,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_heig lmin  ')
386      call test_ltherm(ngrid,nlay,pplev,pplay,lmix ,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_heig lmix  ')
387      call test_ltherm(ngrid,nlay,pplev,pplay,lmax ,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_heig lmax  ')
388
389      if (lev_out.ge.1) print*,'thermcell_main apres thermcell_height'
390
391!-------------------------------------------------------------------------------
392! Fermeture,determination de f
393!-------------------------------------------------------------------------------
394
395      CALL thermcell_closure(ngrid,nlay,r_aspect,ptimestep,rho,  &
396     &   zlev,lalim,alim_star,zmax_sec,wmax_sec,zmax,wmax,f,f0,lev_out)
397
398      if(lev_out.ge.1)print*,'thermcell_closure apres thermcell_closure'
399
400!-------------------------------------------------------------------------------
401!deduction des flux
402!-------------------------------------------------------------------------------
403
404      CALL thermcell_flux(ngrid,nlay,ptimestep,masse, &
405     &       lalim,lmax,alim_star,  &
406     &       entr_star,detr_star,f,rhobarz,zlev,zw2,fm,entr,  &
407     &       detr,zqla,zmax,lev_out,lunout,igout)
408
409      if (lev_out.ge.1) print*,'thermcell_main apres thermcell_flux'
410      call test_ltherm(ngrid,nlay,pplev,pplay,lalim,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_flux lalim ')
411      call test_ltherm(ngrid,nlay,pplev,pplay,lmax ,seuil,ztv,po,ztva,zqla,f_star,zw2,'thermcell_flux lmax  ')
412
413!c------------------------------------------------------------------
414!   calcul du transport vertical
415!------------------------------------------------------------------
416
417      if (w2di.eq.1) then
418         fm0=fm0+ptimestep*(fm-fm0)/float(tho)
419         entr0=entr0+ptimestep*(entr-entr0)/float(tho)
420      else
421         fm0=fm
422         entr0=entr
423         detr0=detr
424      endif
425
426      call thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,masse,  &
427     &                    zthl,zdthladj,zta,lev_out)
428      call thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,masse,  &
429     &                   po,pdoadj,zoa,lev_out)
430
431      if (1.eq.0) then
432
433! Calcul du transport de V tenant compte d'echange par gradient
434! de pression horizontal avec l'environnement
435
436         call thermcell_dv2(ngrid,nlay,ptimestep,fm0,entr0,masse  &
437     &    ,fraca,zmax  &
438     &    ,zu,zv,pduadj,pdvadj,zua,zva,lev_out)
439      else
440
441! calcul purement conservatif pour le transport de V
442         call thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,masse  &
443     &    ,zu,pduadj,zua,lev_out)
444         call thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,masse  &
445     &    ,zv,pdvadj,zva,lev_out)
446      endif
447
448!     print*,'13 OK convect8'
449      do l=1,nlay
450         do ig=1,ngrid
451           pdtadj(ig,l)=zdthladj(ig,l)*zpspsk(ig,l) 
452         enddo
453      enddo
454
455      print*,'14 OK convect8'
456!------------------------------------------------------------------
457!   Calculs de diagnostiques pour les sorties
458!------------------------------------------------------------------
459!calcul de fraca pour les sorties
460     
461      if (sorties) then
462      do ig=1,klon
463         fraca(ig,1)=0.
464      enddo
465      do l=2,nlay
466         do ig=1,klon
467            if (zw2(ig,l).gt.1.e-10) then
468            fraca(ig,l)=fm(ig,l)/(rhobarz(ig,l)*zw2(ig,l))
469            else
470            fraca(ig,l)=0.
471            endif
472         enddo
473      enddo
474     
475      print*,'14a OK convect8'
476! calcul du niveau de condensation
477! initialisation
478      do ig=1,ngrid
[879]479         nivcon(ig)=0
[878]480         zcon(ig)=0.
481      enddo
482!nouveau calcul
483      do ig=1,ngrid
484      CHI=zh(ig,1)/(1669.0-122.0*zo(ig,1)/zqsat(ig,1)-zh(ig,1))
485      pcon(ig)=pplay(ig,1)*(zo(ig,1)/zqsat(ig,1))**CHI
486      enddo
487      do k=1,nlay
488         do ig=1,ngrid
489         if ((pcon(ig).le.pplay(ig,k))  &
490     &      .and.(pcon(ig).gt.pplay(ig,k+1))) then
491            zcon2(ig)=zlay(ig,k)-(pcon(ig)-pplay(ig,k))/(RG*rho(ig,k))/100.
492         endif
493         enddo
494      enddo
495      print*,'14b OK convect8'
496      do k=nlay,1,-1
497         do ig=1,ngrid
498            if (zqla(ig,k).gt.1e-10) then
499               nivcon(ig)=k
500               zcon(ig)=zlev(ig,k)
501            endif
502         enddo
503      enddo
504      print*,'14c OK convect8'
505!calcul des moments
506!initialisation
507      do l=1,nlay
508         do ig=1,ngrid
509            q2(ig,l)=0.
510            wth2(ig,l)=0.
511            wth3(ig,l)=0.
512            ratqscth(ig,l)=0.
513            ratqsdiff(ig,l)=0.
514         enddo
515      enddo     
516      print*,'14d OK convect8'
517      do l=1,nlay
518         do ig=1,ngrid
519            zf=fraca(ig,l)
520            zf2=zf/(1.-zf)
521            thetath2(ig,l)=zf2*(zha(ig,l)-zh(ig,l)/zpspsk(ig,l))**2
522            wth2(ig,l)=zf2*(zw2(ig,l))**2
523!           print*,'wth2=',wth2(ig,l)
524            wth3(ig,l)=zf2*(1-2.*fraca(ig,l))/(1-fraca(ig,l))  &
525     &                *zw2(ig,l)*zw2(ig,l)*zw2(ig,l)
526            q2(ig,l)=zf2*(zqta(ig,l)*1000.-po(ig,l)*1000.)**2
527!test: on calcul q2/po=ratqsc
528            ratqscth(ig,l)=sqrt(max(q2(ig,l),1.e-6)/(po(ig,l)*1000.))
529         enddo
530      enddo
[879]531!calcul de ale_bl et alp_bl
532!pour le calcul d'une valeur intégrée entre la surface et lmax
533      do ig=1,ngrid
534      alp_int(ig)=0.
535      ale_int(ig)=0.
536      n_int(ig)=0
537      enddo
538      do ig=1,ngrid
539!      do l=nivcon(ig),lmax(ig)
540      do l=1,lmax(ig)
541      alp_int(ig)=alp_int(ig)+0.5*rhobarz(ig,l)*wth3(ig,l)
542      ale_int(ig)=ale_int(ig)+0.5*zw2(ig,l)**2
543      n_int(ig)=n_int(ig)+1
544      enddo
545      enddo
546!      print*,'avant calcul ale et alp'
547!calcul de ALE et ALP pour la convection
548      do ig=1,ngrid
549!      Alp_bl(ig)=0.5*rhobarz(ig,lmix_bis(ig))*wth3(ig,lmix(ig))
550!          Alp_bl(ig)=0.5*rhobarz(ig,nivcon(ig))*wth3(ig,nivcon(ig))
551!      Alp_bl(ig)=0.5*rhobarz(ig,lmix(ig))*wth3(ig,lmix(ig))
552!     &           *0.1
553!valeur integree de alp_bl * 0.5:
554       if (n_int(ig).gt.0) then
555       Alp_bl(ig)=0.5*alp_int(ig)/n_int(ig)
556!       if (Alp_bl(ig).lt.0.) then
557!       Alp_bl(ig)=0.
558       endif
559!       endif
560!         write(18,*),'rhobarz,wth3,Alp',rhobarz(ig,nivcon(ig)),
561!     s               wth3(ig,nivcon(ig)),Alp_bl(ig)
562!            write(18,*),'ALP_BL',Alp_bl(ig),lmix(ig)
563!      Ale_bl(ig)=0.5*zw2(ig,lmix_bis(ig))**2
564!      if (nivcon(ig).eq.1) then
565!       Ale_bl(ig)=0.
566!       else
567!valeur max de ale_bl:
568       Ale_bl(ig)=0.5*zw2(ig,lmix(ig))**2
569!     & /2.
570!     & *0.1
571!        Ale_bl(ig)=0.5*zw2(ig,lmix_bis(ig))**2
572!       if (n_int(ig).gt.0) then
573!       Ale_bl(ig)=ale_int(ig)/n_int(ig)
574!        Ale_bl(ig)=4.
575!       endif
576!       endif
577!            Ale_bl(ig)=0.5*wth2(ig,lmix_bis(ig))
578!          Ale_bl(ig)=wth2(ig,nivcon(ig))
579!          write(19,*),'wth2,ALE_BL',wth2(ig,nivcon(ig)),Ale_bl(ig)
580      enddo
581!test:calcul de la ponderation des couches pour KE
582!initialisations
583!      print*,'ponderation'
584      do ig=1,ngrid
585           fm_tot(ig)=0.
586      enddo
587       do ig=1,ngrid
588        do k=1,klev
589           wght_th(ig,k)=1.
590        enddo
591       enddo
592       do ig=1,ngrid
593!         lalim_conv(ig)=lmix_bis(ig)
594!la hauteur de la couche alim_conv = hauteur couche alim_therm
595         lalim_conv(ig)=lalim(ig)
596!         zentr(ig)=zlev(ig,lalim(ig))
597      enddo
598      do ig=1,ngrid
599        do k=1,lalim_conv(ig)
600           fm_tot(ig)=fm_tot(ig)+fm(ig,k)
601        enddo
602      enddo
603      do ig=1,ngrid
604        do k=1,lalim_conv(ig)
605           if (fm_tot(ig).gt.1.e-10) then
606!           wght_th(ig,k)=fm(ig,k)/fm_tot(ig)
607           endif
608!on pondere chaque couche par a*
609             if (alim_star(ig,k).gt.1.e-10) then
610             wght_th(ig,k)=alim_star(ig,k)
611             else
612             wght_th(ig,k)=1.
613             endif
614        enddo
615      enddo
616!      print*,'apres wght_th'
617!test pour prolonger la convection
618      do ig=1,ngrid
619      if ((alim_star(ig,1).lt.1.e-10).and.(therm)) then
620      lalim_conv(ig)=1
621      wght_th(ig,1)=1.
622!      print*,'lalim_conv ok',lalim_conv(ig),wght_th(ig,1)
623      endif
624      enddo
625
[878]626!calcul du ratqscdiff
627      print*,'14e OK convect8'
628      var=0.
629      vardiff=0.
630      ratqsdiff(:,:)=0.
631      do ig=1,ngrid
632         do l=1,lalim(ig)
633            var=var+alim_star(ig,l)*zqta(ig,l)*1000.
634         enddo
635      enddo
636      print*,'14f OK convect8'
637      do ig=1,ngrid
638          do l=1,lalim(ig)
639          zf=fraca(ig,l)
640          zf2=zf/(1.-zf)
641          vardiff=vardiff+alim_star(ig,l)  &
642     &           *(zqta(ig,l)*1000.-var)**2
643!         ratqsdiff=ratqsdiff+alim_star(ig,l)*
644!     s          (zqta(ig,l)*1000.-po(ig,l)*1000.)**2
645          enddo
646      enddo
647      print*,'14g OK convect8'
648      do l=1,nlay
649         do ig=1,ngrid
650            ratqsdiff(ig,l)=sqrt(vardiff)/(po(ig,l)*1000.)   
651!           write(11,*)'ratqsdiff=',ratqsdiff(ig,l)
652         enddo
653      enddo
654!--------------------------------------------------------------------   
655!
656!ecriture des fichiers sortie
657!     print*,'15 OK convect8'
658
659      isplit=isplit+1       
660
661
662#ifdef und
663      if (lev_out.ge.1) print*,'thermcell_main sorties 1D'
664#include "thermcell_out1d.h"
665#endif
666
667
668! #define troisD
669      if (lev_out.ge.1) print*,'thermcell_main sorties 3D'
670#ifdef troisD
671#include "thermcell_out3d.h"
672#endif
673
674      endif
675
676      if (lev_out.ge.1) print*,'thermcell_main FIN  OK'
677
678      return
679      end
680
681!-----------------------------------------------------------------------------
682
683      subroutine test_ltherm(klon,klev,pplev,pplay,long,seuil,ztv,po,ztva,zqla,f_star,zw2,comment)
684
685      integer klon,klev
686      real pplev(klon,klev+1),pplay(klon,klev)
687      real ztv(klon,klev)
688      real po(klon,klev)
689      real ztva(klon,klev)
690      real zqla(klon,klev)
691      real f_star(klon,klev)
692      real zw2(klon,klev)
693      integer long(klon)
694      real seuil
695      character*21 comment
696
[879]697      print*,'WARNING !!! TEST ',comment
698      return
699
[878]700!  test sur la hauteur des thermiques ...
701         do i=1,klon
702            if (pplay(i,long(i)).lt.seuil*pplev(i,1)) then
703               print*,'WARNING ',comment,' au point ',i,' K= ',long(i)
704               print*,'  K  P(MB)  THV(K)     Qenv(g/kg)THVA        QLA(g/kg)   F*        W2'
705               do k=1,klev
706                  write(6,'(i3,7f10.3)') k,pplay(i,k),ztv(i,k),1000*po(i,k),ztva(i,k),1000*zqla(i,k),f_star(i,k),zw2(i,k)
707               enddo
708!              stop
709            endif
710         enddo
711
712
713      return
714      end
715
Note: See TracBrowser for help on using the repository browser.