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

Last change on this file since 939 was 938, checked in by lmdzadmin, 17 years ago

Enleve prints par defaut
IM

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