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

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

Enleve bogues du 1d pour thermcell_main.F90 et pour "first" appel pour yamada4.F
FH/IM

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 22.9 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
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
61      integer,save :: igout=1
62      integer,save :: lunout=6
63      integer,save :: lev_out=10
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
119      integer nivcon(klon)
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!
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!v1d     logical therm
148!v1d     save therm
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.
179!v1d        therm=.false.
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
325      do ig=1,klon
326!v1d     if (alim_star(ig,1).gt.1.e-10) then
327!v1d     therm=.true.
328!v1d     endif
329      enddo
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!------------------------------------------------------------------
432! Calcul de la fraction de l'ascendance
433!------------------------------------------------------------------
434      do ig=1,klon
435         fraca(ig,1)=0.
436         fraca(ig,nlay+1)=0.
437      enddo
438      do l=2,nlay
439         do ig=1,klon
440            if (zw2(ig,l).gt.1.e-10) then
441            fraca(ig,l)=fm(ig,l)/(rhobarz(ig,l)*zw2(ig,l))
442            else
443            fraca(ig,l)=0.
444            endif
445         enddo
446      enddo
447     
448!------------------------------------------------------------------
449!  calcul du transport vertical du moment horizontal
450!------------------------------------------------------------------
451
452      if (1.eq.1) then
453
454
455! Calcul du transport de V tenant compte d'echange par gradient
456! de pression horizontal avec l'environnement
457
458         call thermcell_dv2(ngrid,nlay,ptimestep,fm0,entr0,masse  &
459     &    ,fraca,zmax  &
460     &    ,zu,zv,pduadj,pdvadj,zua,zva,igout,lev_out)
461      else
462
463! calcul purement conservatif pour le transport de V
464         call thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,masse  &
465     &    ,zu,pduadj,zua,lev_out)
466         call thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,masse  &
467     &    ,zv,pdvadj,zva,lev_out)
468      endif
469
470!     print*,'13 OK convect8'
471      do l=1,nlay
472         do ig=1,ngrid
473           pdtadj(ig,l)=zdthladj(ig,l)*zpspsk(ig,l) 
474         enddo
475      enddo
476
477      print*,'14 OK convect8'
478!------------------------------------------------------------------
479!   Calculs de diagnostiques pour les sorties
480!------------------------------------------------------------------
481!calcul de fraca pour les sorties
482     
483      if (sorties) then
484      print*,'14a OK convect8'
485! calcul du niveau de condensation
486! initialisation
487      do ig=1,ngrid
488         nivcon(ig)=0
489         zcon(ig)=0.
490      enddo
491!nouveau calcul
492      do ig=1,ngrid
493      CHI=zh(ig,1)/(1669.0-122.0*zo(ig,1)/zqsat(ig,1)-zh(ig,1))
494      pcon(ig)=pplay(ig,1)*(zo(ig,1)/zqsat(ig,1))**CHI
495      enddo
496      do k=1,nlay
497         do ig=1,ngrid
498         if ((pcon(ig).le.pplay(ig,k))  &
499     &      .and.(pcon(ig).gt.pplay(ig,k+1))) then
500            zcon2(ig)=zlay(ig,k)-(pcon(ig)-pplay(ig,k))/(RG*rho(ig,k))/100.
501         endif
502         enddo
503      enddo
504      print*,'14b OK convect8'
505      do k=nlay,1,-1
506         do ig=1,ngrid
507            if (zqla(ig,k).gt.1e-10) then
508               nivcon(ig)=k
509               zcon(ig)=zlev(ig,k)
510            endif
511         enddo
512      enddo
513      print*,'14c OK convect8'
514!calcul des moments
515!initialisation
516      do l=1,nlay
517         do ig=1,ngrid
518            q2(ig,l)=0.
519            wth2(ig,l)=0.
520            wth3(ig,l)=0.
521            ratqscth(ig,l)=0.
522            ratqsdiff(ig,l)=0.
523         enddo
524      enddo     
525      print*,'14d OK convect8'
526      do l=1,nlay
527         do ig=1,ngrid
528            zf=fraca(ig,l)
529            zf2=zf/(1.-zf)
530            thetath2(ig,l)=zf2*(zha(ig,l)-zh(ig,l)/zpspsk(ig,l))**2
531            wth2(ig,l)=zf2*(zw2(ig,l))**2
532!           print*,'wth2=',wth2(ig,l)
533            wth3(ig,l)=zf2*(1-2.*fraca(ig,l))/(1-fraca(ig,l))  &
534     &                *zw2(ig,l)*zw2(ig,l)*zw2(ig,l)
535            q2(ig,l)=zf2*(zqta(ig,l)*1000.-po(ig,l)*1000.)**2
536!test: on calcul q2/po=ratqsc
537            ratqscth(ig,l)=sqrt(max(q2(ig,l),1.e-6)/(po(ig,l)*1000.))
538         enddo
539      enddo
540!calcul de ale_bl et alp_bl
541!pour le calcul d'une valeur intégrée entre la surface et lmax
542      do ig=1,ngrid
543      alp_int(ig)=0.
544      ale_int(ig)=0.
545      n_int(ig)=0
546      enddo
547      do ig=1,ngrid
548!      do l=nivcon(ig),lmax(ig)
549      do l=1,lmax(ig)
550      alp_int(ig)=alp_int(ig)+0.5*rhobarz(ig,l)*wth3(ig,l)
551      ale_int(ig)=ale_int(ig)+0.5*zw2(ig,l)**2
552      n_int(ig)=n_int(ig)+1
553      enddo
554      enddo
555!      print*,'avant calcul ale et alp'
556!calcul de ALE et ALP pour la convection
557      do ig=1,ngrid
558!      Alp_bl(ig)=0.5*rhobarz(ig,lmix_bis(ig))*wth3(ig,lmix(ig))
559!          Alp_bl(ig)=0.5*rhobarz(ig,nivcon(ig))*wth3(ig,nivcon(ig))
560!      Alp_bl(ig)=0.5*rhobarz(ig,lmix(ig))*wth3(ig,lmix(ig))
561!     &           *0.1
562!valeur integree de alp_bl * 0.5:
563       if (n_int(ig).gt.0) then
564       Alp_bl(ig)=0.5*alp_int(ig)/n_int(ig)
565!       if (Alp_bl(ig).lt.0.) then
566!       Alp_bl(ig)=0.
567       endif
568!       endif
569!         write(18,*),'rhobarz,wth3,Alp',rhobarz(ig,nivcon(ig)),
570!     s               wth3(ig,nivcon(ig)),Alp_bl(ig)
571!            write(18,*),'ALP_BL',Alp_bl(ig),lmix(ig)
572!      Ale_bl(ig)=0.5*zw2(ig,lmix_bis(ig))**2
573!      if (nivcon(ig).eq.1) then
574!       Ale_bl(ig)=0.
575!       else
576!valeur max de ale_bl:
577       Ale_bl(ig)=0.5*zw2(ig,lmix(ig))**2
578!     & /2.
579!     & *0.1
580!        Ale_bl(ig)=0.5*zw2(ig,lmix_bis(ig))**2
581!       if (n_int(ig).gt.0) then
582!       Ale_bl(ig)=ale_int(ig)/n_int(ig)
583!        Ale_bl(ig)=4.
584!       endif
585!       endif
586!            Ale_bl(ig)=0.5*wth2(ig,lmix_bis(ig))
587!          Ale_bl(ig)=wth2(ig,nivcon(ig))
588!          write(19,*),'wth2,ALE_BL',wth2(ig,nivcon(ig)),Ale_bl(ig)
589      enddo
590!test:calcul de la ponderation des couches pour KE
591!initialisations
592!      print*,'ponderation'
593      do ig=1,ngrid
594           fm_tot(ig)=0.
595      enddo
596       do ig=1,ngrid
597        do k=1,klev
598           wght_th(ig,k)=1.
599        enddo
600       enddo
601       do ig=1,ngrid
602!         lalim_conv(ig)=lmix_bis(ig)
603!la hauteur de la couche alim_conv = hauteur couche alim_therm
604         lalim_conv(ig)=lalim(ig)
605!         zentr(ig)=zlev(ig,lalim(ig))
606      enddo
607      do ig=1,ngrid
608        do k=1,lalim_conv(ig)
609           fm_tot(ig)=fm_tot(ig)+fm(ig,k)
610        enddo
611      enddo
612      do ig=1,ngrid
613        do k=1,lalim_conv(ig)
614           if (fm_tot(ig).gt.1.e-10) then
615!           wght_th(ig,k)=fm(ig,k)/fm_tot(ig)
616           endif
617!on pondere chaque couche par a*
618             if (alim_star(ig,k).gt.1.e-10) then
619             wght_th(ig,k)=alim_star(ig,k)
620             else
621             wght_th(ig,k)=1.
622             endif
623        enddo
624      enddo
625!      print*,'apres wght_th'
626!test pour prolonger la convection
627      do ig=1,ngrid
628!v1d  if ((alim_star(ig,1).lt.1.e-10).and.(therm)) then
629      if ((alim_star(ig,1).lt.1.e-10)) then
630      lalim_conv(ig)=1
631      wght_th(ig,1)=1.
632!      print*,'lalim_conv ok',lalim_conv(ig),wght_th(ig,1)
633      endif
634      enddo
635
636!calcul du ratqscdiff
637      print*,'14e OK convect8'
638      var=0.
639      vardiff=0.
640      ratqsdiff(:,:)=0.
641      do ig=1,ngrid
642         do l=1,lalim(ig)
643            var=var+alim_star(ig,l)*zqta(ig,l)*1000.
644         enddo
645      enddo
646      print*,'14f OK convect8'
647      do ig=1,ngrid
648          do l=1,lalim(ig)
649          zf=fraca(ig,l)
650          zf2=zf/(1.-zf)
651          vardiff=vardiff+alim_star(ig,l)  &
652     &           *(zqta(ig,l)*1000.-var)**2
653!         ratqsdiff=ratqsdiff+alim_star(ig,l)*
654!     s          (zqta(ig,l)*1000.-po(ig,l)*1000.)**2
655          enddo
656      enddo
657      print*,'14g OK convect8'
658      do l=1,nlay
659         do ig=1,ngrid
660            ratqsdiff(ig,l)=sqrt(vardiff)/(po(ig,l)*1000.)   
661!           write(11,*)'ratqsdiff=',ratqsdiff(ig,l)
662         enddo
663      enddo
664!--------------------------------------------------------------------   
665!
666!ecriture des fichiers sortie
667!     print*,'15 OK convect8'
668
669      isplit=isplit+1       
670
671
672#ifdef und
673      if (lev_out.ge.1) print*,'thermcell_main sorties 1D'
674#include "thermcell_out1d.h"
675#endif
676
677
678! #define troisD
679      if (lev_out.ge.1) print*,'thermcell_main sorties 3D'
680#ifdef troisD
681#include "thermcell_out3d.h"
682#endif
683
684      endif
685
686      if (lev_out.ge.1) print*,'thermcell_main FIN  OK'
687
688      return
689      end
690
691!-----------------------------------------------------------------------------
692
693      subroutine test_ltherm(klon,klev,pplev,pplay,long,seuil,ztv,po,ztva,zqla,f_star,zw2,comment)
694
695      integer klon,klev
696      real pplev(klon,klev+1),pplay(klon,klev)
697      real ztv(klon,klev)
698      real po(klon,klev)
699      real ztva(klon,klev)
700      real zqla(klon,klev)
701      real f_star(klon,klev)
702      real zw2(klon,klev)
703      integer long(klon)
704      real seuil
705      character*21 comment
706
707      print*,'WARNING !!! TEST ',comment
708      return
709
710!  test sur la hauteur des thermiques ...
711         do i=1,klon
712            if (pplay(i,long(i)).lt.seuil*pplev(i,1)) then
713               print*,'WARNING ',comment,' au point ',i,' K= ',long(i)
714               print*,'  K  P(MB)  THV(K)     Qenv(g/kg)THVA        QLA(g/kg)   F*        W2'
715               do k=1,klev
716                  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)
717               enddo
718!              stop
719            endif
720         enddo
721
722
723      return
724      end
725
Note: See TracBrowser for help on using the repository browser.