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

Last change on this file since 936 was 927, checked in by lmdzadmin, 16 years ago

Ajout variables zmax0, f0 dans le startphy.nc FH
IM

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