source: LMDZ4/trunk/libf/phylmd/thermcell.F @ 940

Last change on this file since 940 was 940, checked in by Laurent Fairhead, 16 years ago

On remplace le fichier include dimphy.h par le module dimphy.F90i pour etre
coherent avec le partout
LF

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 38.9 KB
Line 
1      SUBROUTINE calcul_sec(ngrid,nlay,ptimestep
2     s                  ,pplay,pplev,pphi,zlev
3     s                  ,pu,pv,pt,po
4     s                  ,zmax,wmax,zw2,lmix
5c    s                  ,pu_therm,pv_therm
6     s                  ,r_aspect,l_mix,w2di,tho)
7
8      USE dimphy
9      IMPLICIT NONE
10
11c=======================================================================
12c
13c   Calcul du transport verticale dans la couche limite en presence
14c   de "thermiques" explicitement representes
15c
16c   Réécriture à partir d'un listing papier à Habas, le 14/02/00
17c
18c   le thermique est supposé homogène et dissipé par mélange avec
19c   son environnement. la longueur l_mix contrôle l'efficacité du
20c   mélange
21c
22c   Le calcul du transport des différentes espèces se fait en prenant
23c   en compte:
24c     1. un flux de masse montant
25c     2. un flux de masse descendant
26c     3. un entrainement
27c     4. un detrainement
28c
29c=======================================================================
30
31c-----------------------------------------------------------------------
32c   declarations:
33c   -------------
34
35#include "dimensions.h"
36cccc#include "dimphy.h"
37#include "YOMCST.h"
38
39c   arguments:
40c   ----------
41
42      INTEGER ngrid,nlay,w2di,tho
43      real ptimestep,l_mix,r_aspect
44      REAL pt(ngrid,nlay),pdtadj(ngrid,nlay)
45      REAL pu(ngrid,nlay),pduadj(ngrid,nlay)
46      REAL pv(ngrid,nlay),pdvadj(ngrid,nlay)
47      REAL po(ngrid,nlay),pdoadj(ngrid,nlay)
48      REAL pplay(ngrid,nlay),pplev(ngrid,nlay+1)
49      real pphi(ngrid,nlay)
50
51      integer idetr
52      save idetr
53      data idetr/3/
54
55c   local:
56c   ------
57
58      INTEGER ig,k,l,lmaxa(klon),lmix(klon)
59      real zsortie1d(klon)
60c CR: on remplace lmax(klon,klev+1)
61      INTEGER lmax(klon),lmin(klon),lentr(klon)
62      real linter(klon)
63      real zmix(klon), fracazmix(klon)
64c RC
65      real zmax(klon),zw,zw2(klon,klev+1),ztva(klon,klev)
66
67      real zlev(klon,klev+1),zlay(klon,klev)
68      REAL zh(klon,klev),zdhadj(klon,klev)
69      REAL ztv(klon,klev)
70      real zu(klon,klev),zv(klon,klev),zo(klon,klev)
71      REAL wh(klon,klev+1)
72      real wu(klon,klev+1),wv(klon,klev+1),wo(klon,klev+1)
73      real zla(klon,klev+1)
74      real zwa(klon,klev+1)
75      real zld(klon,klev+1)
76!      real zwd(klon,klev+1)
77      real zsortie(klon,klev)
78      real zva(klon,klev)
79      real zua(klon,klev)
80      real zoa(klon,klev)
81
82      real zha(klon,klev)
83      real wa_moy(klon,klev+1)
84      real fraca(klon,klev+1)
85      real fracc(klon,klev+1)
86      real zf,zf2
87      real thetath2(klon,klev),wth2(klon,klev)
88!      common/comtherm/thetath2,wth2
89
90      real count_time
91!      integer isplit,nsplit
92      integer isplit,nsplit,ialt
93      parameter (nsplit=10)
94      data isplit/0/
95      save isplit
96
97      logical sorties
98      real rho(klon,klev),rhobarz(klon,klev+1),masse(klon,klev)
99      real zpspsk(klon,klev)
100
101c     real wmax(klon,klev),wmaxa(klon)
102      real wmax(klon),wmaxa(klon)
103      real wa(klon,klev,klev+1)
104      real wd(klon,klev+1)
105      real larg_part(klon,klev,klev+1)
106      real fracd(klon,klev+1)
107      real xxx(klon,klev+1)
108      real larg_cons(klon,klev+1)
109      real larg_detr(klon,klev+1)
110      real fm0(klon,klev+1),entr0(klon,klev),detr(klon,klev)
111      real pu_therm(klon,klev),pv_therm(klon,klev)
112      real fm(klon,klev+1),entr(klon,klev)
113      real fmc(klon,klev+1)
114 
115cCR:nouvelles variables
116      real f_star(klon,klev+1),entr_star(klon,klev)
117      real entr_star_tot(klon),entr_star2(klon)
118      real zalim(klon)
119      integer lalim(klon)
120      real norme(klon)
121      real f(klon), f0(klon)
122      real zlevinter(klon)
123      logical therm
124      logical first
125      data first /.false./
126      save first
127cRC
128
129      character*2 str2
130      character*10 str10
131
132!      LOGICAL vtest(klon),down
133
134      EXTERNAL SCOPY
135
136      integer ncorrec
137      save ncorrec
138      data ncorrec/0/
139     
140c
141c-----------------------------------------------------------------------
142c   initialisation:
143c   ---------------
144c
145       sorties=.true.
146      IF(ngrid.NE.klon) THEN
147         PRINT*
148         PRINT*,'STOP dans convadj'
149         PRINT*,'ngrid    =',ngrid
150         PRINT*,'klon  =',klon
151      ENDIF
152c
153c-----------------------------------------------------------------------
154c   incrementation eventuelle de tendances precedentes:
155c   ---------------------------------------------------
156
157c       print*,'0 OK convect8'
158
159      DO 1010 l=1,nlay
160         DO 1015 ig=1,ngrid
161            zpspsk(ig,l)=(pplay(ig,l)/pplev(ig,1))**RKAPPA
162            zh(ig,l)=pt(ig,l)/zpspsk(ig,l)
163            zu(ig,l)=pu(ig,l)
164            zv(ig,l)=pv(ig,l)
165            zo(ig,l)=po(ig,l)
166            ztv(ig,l)=zh(ig,l)*(1.+0.61*zo(ig,l))
1671015     CONTINUE
1681010  CONTINUE
169
170c       print*,'1 OK convect8'
171c                       --------------------
172c
173c
174c                       + + + + + + + + + + +
175c
176c
177c  wa, fraca, wd, fracd --------------------   zlev(2), rhobarz
178c  wh,wt,wo ...
179c
180c                       + + + + + + + + + + +  zh,zu,zv,zo,rho
181c
182c
183c                       --------------------   zlev(1)
184c                       \\\\\\\\\\\\\\\\\\\\
185c
186c
187
188c-----------------------------------------------------------------------
189c   Calcul des altitudes des couches
190c-----------------------------------------------------------------------
191
192      do l=2,nlay
193         do ig=1,ngrid
194            zlev(ig,l)=0.5*(pphi(ig,l)+pphi(ig,l-1))/RG
195         enddo
196      enddo
197      do ig=1,ngrid
198         zlev(ig,1)=0.
199         zlev(ig,nlay+1)=(2.*pphi(ig,klev)-pphi(ig,klev-1))/RG
200      enddo
201      do l=1,nlay
202         do ig=1,ngrid
203            zlay(ig,l)=pphi(ig,l)/RG
204         enddo
205      enddo
206
207c      print*,'2 OK convect8'
208c-----------------------------------------------------------------------
209c   Calcul des densites
210c-----------------------------------------------------------------------
211
212      do l=1,nlay
213         do ig=1,ngrid
214            rho(ig,l)=pplay(ig,l)/(zpspsk(ig,l)*RD*zh(ig,l))
215         enddo
216      enddo
217
218      do l=2,nlay
219         do ig=1,ngrid
220            rhobarz(ig,l)=0.5*(rho(ig,l)+rho(ig,l-1))
221         enddo
222      enddo
223
224      do k=1,nlay
225         do l=1,nlay+1
226            do ig=1,ngrid
227               wa(ig,k,l)=0.
228            enddo
229         enddo
230      enddo
231
232c      print*,'3 OK convect8'
233c------------------------------------------------------------------
234c   Calcul de w2, quarre de w a partir de la cape
235c   a partir de w2, on calcule wa, vitesse de l'ascendance
236c
237c   ATTENTION: Dans cette version, pour cause d'economie de memoire,
238c   w2 est stoke dans wa
239c
240c   ATTENTION: dans convect8, on n'utilise le calcule des wa
241c   independants par couches que pour calculer l'entrainement
242c   a la base et la hauteur max de l'ascendance.
243c
244c   Indicages:
245c   l'ascendance provenant du niveau k traverse l'interface l avec
246c   une vitesse wa(k,l).
247c
248c                       --------------------
249c
250c                       + + + + + + + + + +
251c
252c  wa(k,l)   ----       --------------------    l
253c             /\
254c            /||\       + + + + + + + + + +
255c             ||
256c             ||        --------------------
257c             ||
258c             ||        + + + + + + + + + +
259c             ||
260c             ||        --------------------
261c             ||__
262c             |___      + + + + + + + + + +     k
263c
264c                       --------------------
265c
266c
267c
268c------------------------------------------------------------------
269
270cCR: ponderation entrainement des couches instables
271cdef des entr_star tels que entr=f*entr_star     
272      do l=1,klev
273         do ig=1,ngrid
274            entr_star(ig,l)=0.
275         enddo
276      enddo
277c determination de la longueur de la couche d entrainement
278      do ig=1,ngrid
279         lentr(ig)=1
280      enddo
281
282con ne considere que les premieres couches instables
283      therm=.false.
284      do k=nlay-2,1,-1
285         do ig=1,ngrid
286            if (ztv(ig,k).gt.ztv(ig,k+1).and.
287     s          ztv(ig,k+1).le.ztv(ig,k+2)) then
288               lentr(ig)=k+1
289               therm=.true.
290            endif
291          enddo
292      enddo
293climitation de la valeur du lentr
294c      do ig=1,ngrid
295c         lentr(ig)=min(5,lentr(ig))
296c      enddo
297c determination du lmin: couche d ou provient le thermique
298      do ig=1,ngrid
299         lmin(ig)=1
300      enddo
301      do ig=1,ngrid
302         do l=nlay,2,-1
303            if (ztv(ig,l-1).gt.ztv(ig,l)) then
304               lmin(ig)=l-1
305            endif
306         enddo
307      enddo
308cinitialisations
309      do ig=1,ngrid
310         zalim(ig)=0.
311         norme(ig)=0.
312         lalim(ig)=1
313      enddo
314      do k=1,klev-1
315         do ig=1,ngrid
316       zalim(ig)=zalim(ig)+zlev(ig,k)*MAX(0.,(ztv(ig,k)-ztv(ig,k+1))
317     s          /(zlev(ig,k+1)-zlev(ig,k)))
318c     s         *(zlev(ig,k+1)-zlev(ig,k))
319       norme(ig)=norme(ig)+MAX(0.,(ztv(ig,k)-ztv(ig,k+1))
320     s          /(zlev(ig,k+1)-zlev(ig,k)))
321c    s          *(zlev(ig,k+1)-zlev(ig,k))
322         enddo
323       enddo
324       do ig=1,ngrid
325          if (norme(ig).gt.1.e-10) then
326             zalim(ig)=max(10.*zalim(ig)/norme(ig),zlev(ig,2))
327c             zalim(ig)=min(zalim(ig),zlev(ig,lentr(ig)))
328          endif
329       enddo
330cdétermination du lalim correspondant
331      do k=1,klev-1
332         do ig=1,ngrid
333      if ((zalim(ig).gt.zlev(ig,k)).and.(zalim(ig).le.zlev(ig,k+1)))
334     s   then
335         lalim(ig)=k
336      endif
337         enddo
338      enddo
339c
340c definition de l'entrainement des couches
341      do l=1,klev-1
342         do ig=1,ngrid
343            if (ztv(ig,l).gt.ztv(ig,l+1).and.
344     s          l.ge.lmin(ig).and.l.lt.lentr(ig)) then
345                 entr_star(ig,l)=MAX((ztv(ig,l)-ztv(ig,l+1)),0.)
346c     s                           *(zlev(ig,l+1)-zlev(ig,l))
347     s                           *sqrt(zlev(ig,l+1))
348cautre def
349c                entr_star(ig,l)=zlev(ig,l+1)*(1.-(zlev(ig,l+1)
350c     s                         /zlev(ig,lentr(ig)+2)))**(3./2.)
351            endif
352         enddo
353      enddo
354cnouveau test
355c      if (therm) then
356      do l=1,klev-1
357         do ig=1,ngrid
358            if (ztv(ig,l).gt.ztv(ig,l+1).and.
359     s          l.ge.lmin(ig).and.l.le.lalim(ig)
360     s          .and.zalim(ig).gt.1.e-10) then
361c            if (l.le.lentr(ig)) then
362c               entr_star(ig,l)=zlev(ig,l+1)*(1.-(zlev(ig,l+1)
363c     s                         /zalim(ig)))**(3./2.)
364c               write(10,*)zlev(ig,l),entr_star(ig,l)
365            endif
366         enddo
367      enddo
368c      endif
369c pas de thermique si couche 1 stable
370      do ig=1,ngrid
371         if (lmin(ig).gt.5) then
372            do l=1,klev
373               entr_star(ig,l)=0.
374            enddo
375         endif
376      enddo
377c calcul de l entrainement total
378      do ig=1,ngrid
379         entr_star_tot(ig)=0.
380      enddo
381      do ig=1,ngrid
382         do k=1,klev
383            entr_star_tot(ig)=entr_star_tot(ig)+entr_star(ig,k)
384         enddo
385      enddo
386c Calcul entrainement normalise
387      do ig=1,ngrid
388         if (entr_star_tot(ig).gt.1.e-10) then
389c         do l=1,lentr(ig)
390          do l=1,klev
391cdef possibles pour entr_star: zdthetadz, dthetadz, zdtheta
392            entr_star(ig,l)=entr_star(ig,l)/entr_star_tot(ig)
393         enddo
394         endif
395      enddo
396c
397c      print*,'fin calcul entr_star'
398      do k=1,klev
399         do ig=1,ngrid
400            ztva(ig,k)=ztv(ig,k)
401         enddo
402      enddo
403cRC
404c      print*,'7 OK convect8'
405      do k=1,klev+1
406         do ig=1,ngrid
407            zw2(ig,k)=0.
408            fmc(ig,k)=0.
409cCR
410            f_star(ig,k)=0.
411cRC
412            larg_cons(ig,k)=0.
413            larg_detr(ig,k)=0.
414            wa_moy(ig,k)=0.
415         enddo
416      enddo
417
418c      print*,'8 OK convect8'
419      do ig=1,ngrid
420         linter(ig)=1.
421         lmaxa(ig)=1
422         lmix(ig)=1
423         wmaxa(ig)=0.
424      enddo
425
426cCR:
427      do l=1,nlay-2
428         do ig=1,ngrid
429            if (ztv(ig,l).gt.ztv(ig,l+1)
430     s         .and.entr_star(ig,l).gt.1.e-10
431     s         .and.zw2(ig,l).lt.1e-10) then
432               f_star(ig,l+1)=entr_star(ig,l)
433ctest:calcul de dteta
434               zw2(ig,l+1)=2.*RG*(ztv(ig,l)-ztv(ig,l+1))/ztv(ig,l+1)
435     s                     *(zlev(ig,l+1)-zlev(ig,l))
436     s                     *0.4*pphi(ig,l)/(pphi(ig,l+1)-pphi(ig,l))
437               larg_detr(ig,l)=0.
438            else if ((zw2(ig,l).ge.1e-10).and.
439     s               (f_star(ig,l)+entr_star(ig,l).gt.1.e-10)) then
440               f_star(ig,l+1)=f_star(ig,l)+entr_star(ig,l)
441               ztva(ig,l)=(f_star(ig,l)*ztva(ig,l-1)+entr_star(ig,l)
442     s                    *ztv(ig,l))/f_star(ig,l+1)
443               zw2(ig,l+1)=zw2(ig,l)*(f_star(ig,l)/f_star(ig,l+1))**2+
444     s                     2.*RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
445     s                     *(zlev(ig,l+1)-zlev(ig,l))
446            endif
447c determination de zmax continu par interpolation lineaire
448            if (zw2(ig,l+1).lt.0.) then
449ctest
450               if (abs(zw2(ig,l+1)-zw2(ig,l)).lt.1e-10) then
451c                  print*,'pb linter'
452               endif
453               linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))
454     s           -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
455               zw2(ig,l+1)=0.
456               lmaxa(ig)=l
457            else
458               if (zw2(ig,l+1).lt.0.) then
459c                  print*,'pb1 zw2<0'
460               endif
461               wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
462            endif
463            if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
464c   lmix est le niveau de la couche ou w (wa_moy) est maximum
465               lmix(ig)=l+1
466               wmaxa(ig)=wa_moy(ig,l+1)
467            endif
468         enddo
469      enddo
470c      print*,'fin calcul zw2'
471c
472c Calcul de la couche correspondant a la hauteur du thermique
473      do ig=1,ngrid
474         lmax(ig)=lentr(ig)
475c         lmax(ig)=lalim(ig)
476      enddo
477      do ig=1,ngrid
478         do l=nlay,lentr(ig)+1,-1
479c         do l=nlay,lalim(ig)+1,-1
480            if (zw2(ig,l).le.1.e-10) then
481               lmax(ig)=l-1
482            endif
483         enddo
484      enddo
485c pas de thermique si couche 1 stable
486      do ig=1,ngrid
487         if (lmin(ig).gt.5) then
488            lmax(ig)=1
489            lmin(ig)=1
490            lentr(ig)=1
491            lalim(ig)=1
492         endif
493      enddo
494c   
495c Determination de zw2 max
496      do ig=1,ngrid
497         wmax(ig)=0.
498      enddo
499
500      do l=1,nlay
501         do ig=1,ngrid
502            if (l.le.lmax(ig)) then
503                if (zw2(ig,l).lt.0.)then
504c                  print*,'pb2 zw2<0'
505                endif
506                zw2(ig,l)=sqrt(zw2(ig,l))
507                wmax(ig)=max(wmax(ig),zw2(ig,l))
508            else
509                 zw2(ig,l)=0.
510            endif
511          enddo
512      enddo
513
514c   Longueur caracteristique correspondant a la hauteur des thermiques.
515      do  ig=1,ngrid
516         zmax(ig)=0.
517         zlevinter(ig)=zlev(ig,1)
518      enddo
519      do  ig=1,ngrid
520c calcul de zlevinter
521          zlevinter(ig)=(zlev(ig,lmax(ig)+1)-zlev(ig,lmax(ig)))*
522     s    linter(ig)+zlev(ig,lmax(ig))-lmax(ig)*(zlev(ig,lmax(ig)+1)
523     s    -zlev(ig,lmax(ig)))
524       zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,lmin(ig)))
525      enddo
526      do ig=1,ngrid
527c      write(8,*)zmax(ig),lmax(ig),lentr(ig),lmin(ig)
528      enddo
529con stoppe après les calculs de zmax et wmax
530      RETURN
531
532c      print*,'avant fermeture'
533c Fermeture,determination de f
534cAttention! entrainement normalisé ou pas?
535      do ig=1,ngrid
536         entr_star2(ig)=0.
537      enddo
538      do ig=1,ngrid
539         if (entr_star_tot(ig).LT.1.e-10) then
540            f(ig)=0.
541         else
542             do k=lmin(ig),lentr(ig)
543c             do k=lmin(ig),lalim(ig)
544                entr_star2(ig)=entr_star2(ig)+entr_star(ig,k)**2
545     s                    /(rho(ig,k)*(zlev(ig,k+1)-zlev(ig,k)))
546             enddo
547c Nouvelle fermeture
548             f(ig)=wmax(ig)/(max(500.,zmax(ig))*r_aspect
549     s             *entr_star2(ig))
550c     s            *entr_star_tot(ig)
551ctest
552c             if (first) then
553             f(ig)=f(ig)+(f0(ig)-f(ig))*exp(-ptimestep/zmax(ig)
554     s             *wmax(ig))
555c             endif
556         endif
557         f0(ig)=f(ig)
558c         first=.true.
559      enddo
560c      print*,'apres fermeture'
561con stoppe après la fermeture
562      RETURN
563c Calcul de l'entrainement
564       do k=1,klev
565         do ig=1,ngrid
566            entr(ig,k)=f(ig)*entr_star(ig,k)
567         enddo
568      enddo
569con stoppe après le calcul de entr
570c      RETURN
571cCR:test pour entrainer moins que la masse
572c       do ig=1,ngrid
573c          do l=1,lentr(ig)
574c             if ((entr(ig,l)*ptimestep).gt.(0.9*masse(ig,l))) then
575c                entr(ig,l+1)=entr(ig,l+1)+entr(ig,l)
576c     s                       -0.9*masse(ig,l)/ptimestep
577c                entr(ig,l)=0.9*masse(ig,l)/ptimestep
578c             endif
579c          enddo
580c       enddo
581cCR: fin test
582c Calcul des flux
583      do ig=1,ngrid
584         do l=1,lmax(ig)-1
585            fmc(ig,l+1)=fmc(ig,l)+entr(ig,l)
586         enddo
587      enddo
588
589cRC
590
591
592c      print*,'9 OK convect8'
593c     print*,'WA1 ',wa_moy
594
595c   determination de l'indice du debut de la mixed layer ou w decroit
596
597c   calcul de la largeur de chaque ascendance dans le cas conservatif.
598c   dans ce cas simple, on suppose que la largeur de l'ascendance provenant
599c   d'une couche est égale à la hauteur de la couche alimentante.
600c   La vitesse maximale dans l'ascendance est aussi prise comme estimation
601c   de la vitesse d'entrainement horizontal dans la couche alimentante.
602
603      do l=2,nlay
604         do ig=1,ngrid
605            if (l.le.lmaxa(ig)) then
606               zw=max(wa_moy(ig,l),1.e-10)
607               larg_cons(ig,l)=zmax(ig)*r_aspect
608     s         *fmc(ig,l)/(rhobarz(ig,l)*zw)
609            endif
610         enddo
611      enddo
612
613      do l=2,nlay
614         do ig=1,ngrid
615            if (l.le.lmaxa(ig)) then
616c              if (idetr.eq.0) then
617c  cette option est finalement en dur.
618                  if ((l_mix*zlev(ig,l)).lt.0.)then
619c                   print*,'pb l_mix*zlev<0'
620                  endif
621cCR: test: nouvelle def de lambda
622c                  larg_detr(ig,l)=sqrt(l_mix*zlev(ig,l))
623                  if (zw2(ig,l).gt.1.e-10) then
624                  larg_detr(ig,l)=sqrt((l_mix/zw2(ig,l))*zlev(ig,l))
625                  else
626                  larg_detr(ig,l)=sqrt(l_mix*zlev(ig,l))
627                  endif
628cRC
629c              else if (idetr.eq.1) then
630c                 larg_detr(ig,l)=larg_cons(ig,l)
631c    s            *sqrt(l_mix*zlev(ig,l))/larg_cons(ig,lmix(ig))
632c              else if (idetr.eq.2) then
633c                 larg_detr(ig,l)=sqrt(l_mix*zlev(ig,l))
634c    s            *sqrt(wa_moy(ig,l))
635c              else if (idetr.eq.4) then
636c                 larg_detr(ig,l)=sqrt(l_mix*zlev(ig,l))
637c    s            *wa_moy(ig,l)
638c              endif
639            endif
640         enddo
641       enddo
642
643c      print*,'10 OK convect8'
644c     print*,'WA2 ',wa_moy
645c   calcul de la fraction de la maille concernée par l'ascendance en tenant
646c   compte de l'epluchage du thermique.
647c
648cCR def de  zmix continu (profil parabolique des vitesses)
649      do ig=1,ngrid
650           if (lmix(ig).gt.1.) then
651c test
652              if (((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig)))
653     s        *((zlev(ig,lmix(ig)))-(zlev(ig,lmix(ig)+1)))
654     s        -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1))
655     s        *((zlev(ig,lmix(ig)-1))-(zlev(ig,lmix(ig))))).gt.1e-10)
656     s        then
657c             
658            zmix(ig)=((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig)))
659     s        *((zlev(ig,lmix(ig)))**2-(zlev(ig,lmix(ig)+1))**2)
660     s        -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1))
661     s        *((zlev(ig,lmix(ig)-1))**2-(zlev(ig,lmix(ig)))**2))
662     s        /(2.*((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig)))
663     s        *((zlev(ig,lmix(ig)))-(zlev(ig,lmix(ig)+1)))
664     s        -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1))
665     s        *((zlev(ig,lmix(ig)-1))-(zlev(ig,lmix(ig))))))
666            else
667            zmix(ig)=zlev(ig,lmix(ig))
668c            print*,'pb zmix'
669            endif
670         else
671         zmix(ig)=0.
672         endif
673ctest
674         if ((zmax(ig)-zmix(ig)).lt.0.) then
675            zmix(ig)=0.99*zmax(ig)
676c            print*,'pb zmix>zmax'
677         endif
678      enddo
679c
680c calcul du nouveau lmix correspondant
681      do ig=1,ngrid
682         do l=1,klev
683            if (zmix(ig).ge.zlev(ig,l).and.
684     s          zmix(ig).lt.zlev(ig,l+1)) then
685              lmix(ig)=l
686             endif
687          enddo
688      enddo
689c
690      do l=2,nlay
691         do ig=1,ngrid
692            if(larg_cons(ig,l).gt.1.) then
693c     print*,ig,l,lmix(ig),lmaxa(ig),larg_cons(ig,l),'  KKK'
694               fraca(ig,l)=(larg_cons(ig,l)-larg_detr(ig,l))
695     s            /(r_aspect*zmax(ig))
696c test
697               fraca(ig,l)=max(fraca(ig,l),0.)
698               fraca(ig,l)=min(fraca(ig,l),0.5)
699               fracd(ig,l)=1.-fraca(ig,l)
700               fracc(ig,l)=larg_cons(ig,l)/(r_aspect*zmax(ig))
701            else
702c              wa_moy(ig,l)=0.
703               fraca(ig,l)=0.
704               fracc(ig,l)=0.
705               fracd(ig,l)=1.
706            endif
707         enddo
708      enddo                 
709cCR: calcul de fracazmix
710       do ig=1,ngrid
711          fracazmix(ig)=(fraca(ig,lmix(ig)+1)-fraca(ig,lmix(ig)))/
712     s     (zlev(ig,lmix(ig)+1)-zlev(ig,lmix(ig)))*zmix(ig)
713     s    +fraca(ig,lmix(ig))-zlev(ig,lmix(ig))*(fraca(ig,lmix(ig)+1)
714     s    -fraca(ig,lmix(ig)))/(zlev(ig,lmix(ig)+1)-zlev(ig,lmix(ig)))
715       enddo
716c
717       do l=2,nlay
718          do ig=1,ngrid
719             if(larg_cons(ig,l).gt.1.) then
720               if (l.gt.lmix(ig)) then
721ctest
722                 if (zmax(ig)-zmix(ig).lt.1.e-10) then
723c                   print*,'pb xxx'
724                   xxx(ig,l)=(lmaxa(ig)+1.-l)/(lmaxa(ig)+1.-lmix(ig))
725                 else
726                 xxx(ig,l)=(zmax(ig)-zlev(ig,l))/(zmax(ig)-zmix(ig))
727                 endif
728           if (idetr.eq.0) then
729               fraca(ig,l)=fracazmix(ig)
730           else if (idetr.eq.1) then
731               fraca(ig,l)=fracazmix(ig)*xxx(ig,l)
732           else if (idetr.eq.2) then
733               fraca(ig,l)=fracazmix(ig)*(1.-(1.-xxx(ig,l))**2)
734           else
735               fraca(ig,l)=fracazmix(ig)*xxx(ig,l)**2
736           endif
737c     print*,ig,l,lmix(ig),lmaxa(ig),xxx(ig,l),'LLLLLLL'
738               fraca(ig,l)=max(fraca(ig,l),0.)
739               fraca(ig,l)=min(fraca(ig,l),0.5)
740               fracd(ig,l)=1.-fraca(ig,l)
741               fracc(ig,l)=larg_cons(ig,l)/(r_aspect*zmax(ig))
742             endif
743            endif
744         enddo
745      enddo
746     
747c      print*,'fin calcul fraca'
748c      print*,'11 OK convect8'
749c     print*,'Ea3 ',wa_moy
750c------------------------------------------------------------------
751c   Calcul de fracd, wd
752c   somme wa - wd = 0
753c------------------------------------------------------------------
754
755
756      do ig=1,ngrid
757         fm(ig,1)=0.
758         fm(ig,nlay+1)=0.
759      enddo
760
761      do l=2,nlay
762           do ig=1,ngrid
763              fm(ig,l)=fraca(ig,l)*wa_moy(ig,l)*rhobarz(ig,l)
764cCR:test
765              if (entr(ig,l-1).lt.1e-10.and.fm(ig,l).gt.fm(ig,l-1)
766     s            .and.l.gt.lmix(ig)) then
767                 fm(ig,l)=fm(ig,l-1)
768c                 write(1,*)'ajustement fm, l',l
769              endif
770c              write(1,*)'ig,l,fm(ig,l)',ig,l,fm(ig,l)
771cRC
772           enddo
773         do ig=1,ngrid
774            if(fracd(ig,l).lt.0.1) then
775               stop'fracd trop petit'
776            else
777c    vitesse descendante "diagnostique"
778               wd(ig,l)=fm(ig,l)/(fracd(ig,l)*rhobarz(ig,l))
779            endif
780         enddo
781      enddo
782
783      do l=1,nlay
784         do ig=1,ngrid
785c           masse(ig,l)=rho(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
786            masse(ig,l)=(pplev(ig,l)-pplev(ig,l+1))/RG
787         enddo
788      enddo
789
790c      print*,'12 OK convect8'
791c     print*,'WA4 ',wa_moy
792cc------------------------------------------------------------------
793c   calcul du transport vertical
794c------------------------------------------------------------------
795
796      go to 4444
797c     print*,'XXXXXXXXXXXXXXX ptimestep= ',ptimestep
798      do l=2,nlay-1
799         do ig=1,ngrid
800            if(fm(ig,l+1)*ptimestep.gt.masse(ig,l)
801     s      .and.fm(ig,l+1)*ptimestep.gt.masse(ig,l+1)) then
802c     print*,'WARN!!! FM>M ig=',ig,' l=',l,'  FM='
803c    s         ,fm(ig,l+1)*ptimestep
804c    s         ,'   M=',masse(ig,l),masse(ig,l+1)
805             endif
806         enddo
807      enddo
808
809      do l=1,nlay
810         do ig=1,ngrid
811            if(entr(ig,l)*ptimestep.gt.masse(ig,l)) then
812c     print*,'WARN!!! E>M ig=',ig,' l=',l,'  E=='
813c    s         ,entr(ig,l)*ptimestep
814c    s         ,'   M=',masse(ig,l)
815             endif
816         enddo
817      enddo
818
819      do l=1,nlay
820         do ig=1,ngrid
821            if(.not.fm(ig,l).ge.0..or..not.fm(ig,l).le.10.) then
822c     print*,'WARN!!! fm exagere ig=',ig,'   l=',l
823c    s         ,'   FM=',fm(ig,l)
824            endif
825            if(.not.masse(ig,l).ge.1.e-10
826     s         .or..not.masse(ig,l).le.1.e4) then
827c     print*,'WARN!!! masse exagere ig=',ig,'   l=',l
828c    s         ,'   M=',masse(ig,l)
829c     print*,'rho(ig,l),pplay(ig,l),zpspsk(ig,l),RD,zh(ig,l)',
830c    s                 rho(ig,l),pplay(ig,l),zpspsk(ig,l),RD,zh(ig,l)
831c     print*,'zlev(ig,l+1),zlev(ig,l)'
832c    s                ,zlev(ig,l+1),zlev(ig,l)
833c     print*,'pphi(ig,l-1),pphi(ig,l),pphi(ig,l+1)'
834c    s                ,pphi(ig,l-1),pphi(ig,l),pphi(ig,l+1)
835            endif
836            if(.not.entr(ig,l).ge.0..or..not.entr(ig,l).le.10.) then
837c     print*,'WARN!!! entr exagere ig=',ig,'   l=',l
838c    s         ,'   E=',entr(ig,l)
839            endif
840         enddo
841      enddo
842
8434444   continue
844
845cCR:redefinition du entr
846       do l=1,nlay
847         do ig=1,ngrid
848            detr(ig,l)=fm(ig,l)+entr(ig,l)-fm(ig,l+1)
849            if (detr(ig,l).lt.0.) then
850c                entr(ig,l)=entr(ig,l)-detr(ig,l)
851                fm(ig,l+1)=fm(ig,l)+entr(ig,l)
852                detr(ig,l)=0.
853c     print*,'WARNING !!! detrainement negatif ',ig,l
854            endif
855         enddo
856      enddo
857cRC
858      if (w2di.eq.1) then
859         fm0=fm0+ptimestep*(fm-fm0)/float(tho)
860         entr0=entr0+ptimestep*(entr-entr0)/float(tho)
861      else
862         fm0=fm
863         entr0=entr
864      endif
865
866      if (1.eq.1) then
867         call dqthermcell(ngrid,nlay,ptimestep,fm0,entr0,masse
868     .    ,zh,zdhadj,zha)
869         call dqthermcell(ngrid,nlay,ptimestep,fm0,entr0,masse
870     .    ,zo,pdoadj,zoa)
871      else
872         call dqthermcell2(ngrid,nlay,ptimestep,fm0,entr0,masse,fraca
873     .    ,zh,zdhadj,zha)
874         call dqthermcell2(ngrid,nlay,ptimestep,fm0,entr0,masse,fraca
875     .    ,zo,pdoadj,zoa)
876      endif
877
878      if (1.eq.0) then
879         call dvthermcell2(ngrid,nlay,ptimestep,fm0,entr0,masse
880     .    ,fraca,zmax
881     .    ,zu,zv,pduadj,pdvadj,zua,zva)
882      else
883         call dqthermcell(ngrid,nlay,ptimestep,fm0,entr0,masse
884     .    ,zu,pduadj,zua)
885         call dqthermcell(ngrid,nlay,ptimestep,fm0,entr0,masse
886     .    ,zv,pdvadj,zva)
887      endif
888
889      do l=1,nlay
890         do ig=1,ngrid
891            zf=0.5*(fracc(ig,l)+fracc(ig,l+1))
892            zf2=zf/(1.-zf)
893            thetath2(ig,l)=zf2*(zha(ig,l)-zh(ig,l))**2
894            wth2(ig,l)=zf2*(0.5*(wa_moy(ig,l)+wa_moy(ig,l+1)))**2
895         enddo
896      enddo
897
898
899
900c     print*,'13 OK convect8'
901c     print*,'WA5 ',wa_moy
902      do l=1,nlay
903         do ig=1,ngrid
904            pdtadj(ig,l)=zdhadj(ig,l)*zpspsk(ig,l)
905         enddo
906      enddo
907
908
909c     do l=1,nlay
910c        do ig=1,ngrid
911c           if(abs(pdtadj(ig,l))*86400..gt.500.) then
912c     print*,'WARN!!! ig=',ig,'  l=',l
913c    s         ,'   pdtadj=',pdtadj(ig,l)
914c           endif
915c           if(abs(pdoadj(ig,l))*86400..gt.1.) then
916c     print*,'WARN!!! ig=',ig,'  l=',l
917c    s         ,'   pdoadj=',pdoadj(ig,l)
918c           endif
919c        enddo
920c      enddo
921
922c      print*,'14 OK convect8'
923c------------------------------------------------------------------
924c   Calculs pour les sorties
925c------------------------------------------------------------------
926
927      if(sorties) then
928      do l=1,nlay
929         do ig=1,ngrid
930            zla(ig,l)=(1.-fracd(ig,l))*zmax(ig)
931            zld(ig,l)=fracd(ig,l)*zmax(ig)
932            if(1.-fracd(ig,l).gt.1.e-10)
933     s      zwa(ig,l)=wd(ig,l)*fracd(ig,l)/(1.-fracd(ig,l))
934         enddo
935      enddo
936
937cdeja fait
938c      do l=1,nlay
939c         do ig=1,ngrid
940c            detr(ig,l)=fm(ig,l)+entr(ig,l)-fm(ig,l+1)
941c            if (detr(ig,l).lt.0.) then
942c                entr(ig,l)=entr(ig,l)-detr(ig,l)
943c                detr(ig,l)=0.
944c     print*,'WARNING !!! detrainement negatif ',ig,l
945c            endif
946c         enddo
947c      enddo
948
949c     print*,'15 OK convect8'
950
951      isplit=isplit+1
952
953
954c #define und
955        goto 123
956#ifdef und
957      CALL writeg1d(1,nlay,wd,'wd      ','wd      ')
958      CALL writeg1d(1,nlay,zwa,'wa      ','wa      ')
959      CALL writeg1d(1,nlay,fracd,'fracd      ','fracd      ')
960      CALL writeg1d(1,nlay,fraca,'fraca      ','fraca      ')
961      CALL writeg1d(1,nlay,wa_moy,'wam         ','wam         ')
962      CALL writeg1d(1,nlay,zla,'la      ','la      ')
963      CALL writeg1d(1,nlay,zld,'ld      ','ld      ')
964      CALL writeg1d(1,nlay,pt,'pt      ','pt      ')
965      CALL writeg1d(1,nlay,zh,'zh      ','zh      ')
966      CALL writeg1d(1,nlay,zha,'zha      ','zha      ')
967      CALL writeg1d(1,nlay,zu,'zu      ','zu      ')
968      CALL writeg1d(1,nlay,zv,'zv      ','zv      ')
969      CALL writeg1d(1,nlay,zo,'zo      ','zo      ')
970      CALL writeg1d(1,nlay,wh,'wh      ','wh      ')
971      CALL writeg1d(1,nlay,wu,'wu      ','wu      ')
972      CALL writeg1d(1,nlay,wv,'wv      ','wv      ')
973      CALL writeg1d(1,nlay,wo,'w15uo     ','wXo     ')
974      CALL writeg1d(1,nlay,zdhadj,'zdhadj      ','zdhadj      ')
975      CALL writeg1d(1,nlay,pduadj,'pduadj      ','pduadj      ')
976      CALL writeg1d(1,nlay,pdvadj,'pdvadj      ','pdvadj      ')
977      CALL writeg1d(1,nlay,pdoadj,'pdoadj      ','pdoadj      ')
978      CALL writeg1d(1,nlay,entr  ,'entr        ','entr        ')
979      CALL writeg1d(1,nlay,detr  ,'detr        ','detr        ')
980      CALL writeg1d(1,nlay,fm    ,'fm          ','fm          ')
981
982      CALL writeg1d(1,nlay,pdtadj,'pdtadj    ','pdtadj    ')
983      CALL writeg1d(1,nlay,pplay,'pplay     ','pplay     ')
984      CALL writeg1d(1,nlay,pplev,'pplev     ','pplev     ')
985
986c   recalcul des flux en diagnostique...
987c     print*,'PAS DE TEMPS ',ptimestep
988       call dt2F(pplev,pplay,pt,pdtadj,wh)
989      CALL writeg1d(1,nlay,wh,'wh2     ','wh2     ')
990#endif
991123   continue
992#define troisD
993#ifdef troisD
994c       if (sorties) then
995c      print*,'Debut des wrgradsfi'
996
997c      print*,'16 OK convect8'
998         call wrgradsfi(1,nlay,wd,'wd        ','wd        ')
999         call wrgradsfi(1,nlay,zwa,'wa        ','wa        ')
1000         call wrgradsfi(1,nlay,fracd,'fracd     ','fracd     ')
1001         call wrgradsfi(1,nlay,fraca,'fraca     ','fraca     ')
1002         call wrgradsfi(1,nlay,xxx,'xxx       ','xxx       ')
1003         call wrgradsfi(1,nlay,wa_moy,'wam       ','wam       ')
1004c      print*,'WA6 ',wa_moy
1005         call wrgradsfi(1,nlay,zla,'la        ','la        ')
1006         call wrgradsfi(1,nlay,zld,'ld        ','ld        ')
1007         call wrgradsfi(1,nlay,pt,'pt        ','pt        ')
1008         call wrgradsfi(1,nlay,zh,'zh        ','zh        ')
1009         call wrgradsfi(1,nlay,zha,'zha        ','zha        ')
1010         call wrgradsfi(1,nlay,zua,'zua        ','zua        ')
1011         call wrgradsfi(1,nlay,zva,'zva        ','zva        ')
1012         call wrgradsfi(1,nlay,zu,'zu        ','zu        ')
1013         call wrgradsfi(1,nlay,zv,'zv        ','zv        ')
1014         call wrgradsfi(1,nlay,zo,'zo        ','zo        ')
1015         call wrgradsfi(1,nlay,wh,'wh        ','wh        ')
1016         call wrgradsfi(1,nlay,wu,'wu        ','wu        ')
1017         call wrgradsfi(1,nlay,wv,'wv        ','wv        ')
1018         call wrgradsfi(1,nlay,wo,'wo        ','wo        ')
1019         call wrgradsfi(1,1,zmax,'zmax      ','zmax      ')
1020         call wrgradsfi(1,nlay,zdhadj,'zdhadj    ','zdhadj    ')
1021         call wrgradsfi(1,nlay,pduadj,'pduadj    ','pduadj    ')
1022         call wrgradsfi(1,nlay,pdvadj,'pdvadj    ','pdvadj    ')
1023         call wrgradsfi(1,nlay,pdoadj,'pdoadj    ','pdoadj    ')
1024         call wrgradsfi(1,nlay,entr,'entr      ','entr      ')
1025         call wrgradsfi(1,nlay,detr,'detr      ','detr      ')
1026         call wrgradsfi(1,nlay,fm,'fm        ','fm        ')
1027         call wrgradsfi(1,nlay,fmc,'fmc       ','fmc       ')
1028         call wrgradsfi(1,nlay,zw2,'zw2       ','zw2       ')
1029         call wrgradsfi(1,nlay,ztva,'ztva      ','ztva      ')
1030         call wrgradsfi(1,nlay,ztv,'ztv       ','ztv       ')
1031
1032         call wrgradsfi(1,nlay,zo,'zo        ','zo        ')
1033         call wrgradsfi(1,nlay,larg_cons,'Lc        ','Lc        ')
1034         call wrgradsfi(1,nlay,larg_detr,'Ldetr     ','Ldetr     ')
1035
1036cCR:nouveaux diagnostiques
1037      call wrgradsfi(1,nlay,entr_star  ,'entr_star   ','entr_star   ')     
1038      call wrgradsfi(1,nlay,f_star    ,'f_star   ','f_star   ')
1039      call wrgradsfi(1,1,zmax,'zmax      ','zmax      ')
1040      call wrgradsfi(1,1,zmix,'zmix      ','zmix      ')
1041      zsortie1d(:)=lmax(:)
1042      call wrgradsfi(1,1,zsortie1d,'lmax      ','lmax      ')
1043      call wrgradsfi(1,1,wmax,'wmax      ','wmax      ')
1044      zsortie1d(:)=lmix(:)
1045      call wrgradsfi(1,1,zsortie1d,'lmix      ','lmix      ')
1046      zsortie1d(:)=lentr(:)
1047      call wrgradsfi(1,1,zsortie1d,'lentr      ','lentr     ')
1048
1049c      print*,'17 OK convect8'
1050
1051         do k=1,klev/10
1052            write(str2,'(i2.2)') k
1053            str10='wa'//str2
1054            do l=1,nlay
1055               do ig=1,ngrid
1056                  zsortie(ig,l)=wa(ig,k,l)
1057               enddo
1058            enddo   
1059            CALL wrgradsfi(1,nlay,zsortie,str10,str10)
1060            do l=1,nlay
1061               do ig=1,ngrid
1062                  zsortie(ig,l)=larg_part(ig,k,l)
1063               enddo
1064            enddo
1065            str10='la'//str2
1066            CALL wrgradsfi(1,nlay,zsortie,str10,str10)
1067         enddo
1068
1069
1070c     print*,'18 OK convect8'
1071c      endif
1072c      print*,'Fin des wrgradsfi'
1073#endif
1074
1075      endif
1076
1077c     if(wa_moy(1,4).gt.1.e-10) stop
1078
1079c      print*,'19 OK convect8'
1080      return
1081      end
1082
1083      SUBROUTINE fermeture_seche(ngrid,nlay
1084     s                ,pplay,pplev,pphi,zlev,rhobarz,f0,zpspsk
1085     s                ,alim_star,zh,zo,lentr,lmin,nu_min,nu_max,r_aspect
1086     s                ,zmax,wmax)
1087
1088      USE dimphy
1089      IMPLICIT NONE
1090
1091#include "dimensions.h"
1092cccc#include "dimphy.h"
1093#include "YOMCST.h"
1094
1095      INTEGER ngrid,nlay
1096      REAL pplay(ngrid,nlay),pplev(ngrid,nlay+1)
1097      real pphi(ngrid,nlay)
1098      real zlev(klon,klev+1)
1099      real alim_star(klon,klev)
1100      real f0(klon)
1101      integer lentr(klon)
1102      integer lmin(klon)
1103      real zmax(klon)
1104      real wmax(klon)
1105      real nu_min
1106      real nu_max
1107      real r_aspect
1108      real rhobarz(klon,klev+1)
1109      REAL zh(klon,klev)
1110      real zo(klon,klev)
1111      real zpspsk(klon,klev)
1112
1113      integer ig,l
1114
1115      real f_star(klon,klev+1)
1116      real detr_star(klon,klev)
1117      real entr_star(klon,klev)
1118      real zw2(klon,klev+1)
1119      real linter(klon)
1120      integer lmix(klon)
1121      integer lmax(klon)
1122      real zlevinter(klon)
1123      real wa_moy(klon,klev+1)
1124      real wmaxa(klon)
1125      REAL ztv(klon,klev)
1126      REAL ztva(klon,klev)
1127      real nu(klon,klev)
1128!      real zmax0_sec(klon)
1129!      save zmax0_sec
1130       REAL, SAVE, ALLOCATABLE :: zmax0_sec(:)
1131c$OMP THREADPRIVATE(zmax0_sec)
1132      logical, save :: first = .true.
1133
1134      if (first) then
1135        allocate(zmax0_sec(klon))
1136        first=.false.
1137      endif
1138
1139      do l=1,nlay
1140         do ig=1,ngrid
1141      ztv(ig,l)=zh(ig,l)/zpspsk(ig,l)
1142      ztv(ig,l)=ztv(ig,l)*(1.+RETV*zo(ig,l))
1143         enddo
1144      enddo
1145      do l=1,nlay-2
1146         do ig=1,ngrid
1147            if (ztv(ig,l).gt.ztv(ig,l+1)
1148     s         .and.alim_star(ig,l).gt.1.e-10
1149     s         .and.zw2(ig,l).lt.1e-10) then
1150               f_star(ig,l+1)=alim_star(ig,l)
1151ctest:calcul de dteta
1152               zw2(ig,l+1)=2.*RG*(ztv(ig,l)-ztv(ig,l+1))/ztv(ig,l+1)
1153     s                     *(zlev(ig,l+1)-zlev(ig,l))
1154     s                     *0.4*pphi(ig,l)/(pphi(ig,l+1)-pphi(ig,l))
1155            else if ((zw2(ig,l).ge.1e-10).and.
1156     s         (f_star(ig,l)+alim_star(ig,l)).gt.1.e-10) then
1157cestimation du detrainement a partir de la geometrie du pas precedent
1158ctests sur la definition du detr
1159             nu(ig,l)=(nu_min+nu_max)/2.
1160     s         *(1.-(nu_max-nu_min)/(nu_max+nu_min)
1161     s  *tanh((((ztva(ig,l-1)-ztv(ig,l))/ztv(ig,l))/0.0005)))
1162         
1163             detr_star(ig,l)=rhobarz(ig,l)
1164     s                      *sqrt(zw2(ig,l))
1165     s                       /(r_aspect*zmax0_sec(ig))*
1166c     s                       /(r_aspect*zmax0(ig))*
1167     s                      (sqrt(nu(ig,l)*zlev(ig,l+1)
1168     s                /sqrt(zw2(ig,l)))
1169     s                     -sqrt(nu(ig,l)*zlev(ig,l)
1170     s                /sqrt(zw2(ig,l))))
1171         detr_star(ig,l)=detr_star(ig,l)/f0(ig)
1172         if ((detr_star(ig,l)).gt.f_star(ig,l)) then
1173              detr_star(ig,l)=f_star(ig,l)
1174         endif
1175         entr_star(ig,l)=0.9*detr_star(ig,l)
1176             if ((l.lt.lentr(ig))) then
1177                 entr_star(ig,l)=0.
1178c                 detr_star(ig,l)=0.
1179             endif
1180c           print*,'ok detr_star'
1181cprise en compte du detrainement dans le calcul du flux
1182             f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)
1183     s                      -detr_star(ig,l)
1184ctest sur le signe de f_star
1185       if ((f_star(ig,l+1)+detr_star(ig,l)).gt.1.e-10) then
1186cAM on melange Tl et qt du thermique
1187          ztva(ig,l)=(f_star(ig,l)*ztva(ig,l-1)+(entr_star(ig,l)
1188     s                    +alim_star(ig,l))
1189     s                    *ztv(ig,l))/(f_star(ig,l+1)+detr_star(ig,l))
1190               zw2(ig,l+1)=zw2(ig,l)*(f_star(ig,l)
1191     s                     /(f_star(ig,l+1)+detr_star(ig,l)))**2+
1192     s                     2.*RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)
1193     s                     *(zlev(ig,l+1)-zlev(ig,l))
1194            endif
1195        endif
1196c
1197            if (zw2(ig,l+1).lt.0.) then
1198               linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))
1199     s           -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
1200               zw2(ig,l+1)=0.
1201c              print*,'linter=',linter(ig)
1202            else
1203               wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
1204            endif
1205            if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
1206c   lmix est le niveau de la couche ou w (wa_moy) est maximum
1207               lmix(ig)=l+1
1208               wmaxa(ig)=wa_moy(ig,l+1)
1209            endif
1210         enddo
1211      enddo
1212c     print*,'fin calcul zw2'
1213c
1214c Calcul de la couche correspondant a la hauteur du thermique
1215      do ig=1,ngrid
1216         lmax(ig)=lentr(ig)
1217      enddo
1218      do ig=1,ngrid
1219         do l=nlay,lentr(ig)+1,-1
1220            if (zw2(ig,l).le.1.e-10) then
1221               lmax(ig)=l-1
1222            endif
1223         enddo
1224      enddo
1225c pas de thermique si couche 1 stable
1226      do ig=1,ngrid
1227         if (lmin(ig).gt.1) then
1228            lmax(ig)=1
1229             lmin(ig)=1
1230             lentr(ig)=1
1231         endif
1232      enddo
1233c   
1234c Determination de zw2 max
1235      do ig=1,ngrid
1236         wmax(ig)=0.
1237      enddo
1238
1239      do l=1,nlay
1240         do ig=1,ngrid
1241            if (l.le.lmax(ig)) then
1242                if (zw2(ig,l).lt.0.)then
1243c                 print*,'pb2 zw2<0'
1244                endif
1245                zw2(ig,l)=sqrt(zw2(ig,l))
1246                wmax(ig)=max(wmax(ig),zw2(ig,l))
1247            else
1248                 zw2(ig,l)=0.
1249            endif
1250          enddo
1251      enddo
1252
1253c   Longueur caracteristique correspondant a la hauteur des thermiques.
1254      do  ig=1,ngrid
1255         zmax(ig)=0.
1256         zlevinter(ig)=zlev(ig,1)
1257      enddo
1258      do  ig=1,ngrid
1259c calcul de zlevinter
1260          zlevinter(ig)=(zlev(ig,lmax(ig)+1)-zlev(ig,lmax(ig)))*
1261     s    linter(ig)+zlev(ig,lmax(ig))-lmax(ig)*(zlev(ig,lmax(ig)+1)
1262     s    -zlev(ig,lmax(ig)))
1263cpour le cas ou on prend tjs lmin=1
1264c       zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,lmin(ig)))
1265       zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,1))
1266       zmax0_sec(ig)=zmax(ig)
1267      enddo
1268       
1269      RETURN
1270      END
Note: See TracBrowser for help on using the repository browser.