source: LMDZ5/branches/testing/libf/phylmd/thermcell_height.F90 @ 2056

Last change on this file since 2056 was 2056, checked in by Laurent Fairhead, 10 years ago

Merged trunk changes r1997:2055 into testing branch

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.7 KB
Line 
1      SUBROUTINE thermcell_height(ngrid,nlay,lalim,lmin,linter,lmix,  &
2     &           zw2,zlev,lmax,zmax,zmax0,zmix,wmax,lev_out)                           
3
4!-----------------------------------------------------------------------------
5!thermcell_height: calcul des caracteristiques du thermique: zmax,wmax,zmix
6!-----------------------------------------------------------------------------
7      IMPLICIT NONE
8#include "iniprint.h"
9#include "thermcell.h"
10
11      INTEGER ig,l
12      INTEGER ngrid,nlay
13      INTEGER lalim(ngrid),lmin(ngrid)
14      INTEGER lmix(ngrid)
15      REAL linter(ngrid)
16      integer lev_out                           ! niveau pour les print
17
18      REAL zw2(ngrid,nlay+1)
19      REAL zlev(ngrid,nlay+1)
20
21      REAL wmax(ngrid)
22      INTEGER lmax(ngrid)
23      REAL zmax(ngrid)
24      REAL zmax0(ngrid)
25      REAL zmix(ngrid)
26      REAL num(ngrid)
27      REAL denom(ngrid)
28
29      REAL zlevinter(ngrid)
30
31!calcul de la hauteur max du thermique
32      do ig=1,ngrid
33         lmax(ig)=lalim(ig)
34      enddo
35      do ig=1,ngrid
36         do l=nlay,lalim(ig)+1,-1
37            if (zw2(ig,l).le.1.e-10) then
38               lmax(ig)=l-1
39            endif
40         enddo
41      enddo
42
43! On traite le cas particulier qu'il faudrait éviter ou le thermique
44! atteind le haut du modele ...
45      do ig=1,ngrid
46      if ( zw2(ig,nlay) > 1.e-10 ) then
47          print*,'WARNING !!!!! W2 thermiques non nul derniere couche '
48          lmax(ig)=nlay
49      endif
50      enddo
51
52! pas de thermique si couche 1 stable
53      do ig=1,ngrid
54         if (lmin(ig).gt.1) then
55             lmax(ig)=1
56             lmin(ig)=1
57             lalim(ig)=1
58         endif
59      enddo
60!   
61! Determination de zw2 max
62      do ig=1,ngrid
63         wmax(ig)=0.
64      enddo
65
66      do l=1,nlay
67         do ig=1,ngrid
68            if (l.le.lmax(ig)) then
69                if (zw2(ig,l).lt.0.)then
70                  print*,'pb2 zw2<0'
71                endif
72                zw2(ig,l)=sqrt(zw2(ig,l))
73                wmax(ig)=max(wmax(ig),zw2(ig,l))
74            else
75                 zw2(ig,l)=0.
76            endif
77          enddo
78      enddo
79
80!   Longueur caracteristique correspondant a la hauteur des thermiques.
81      do  ig=1,ngrid
82         zmax(ig)=0.
83         zlevinter(ig)=zlev(ig,1)
84      enddo
85
86!     if (iflag_thermals_ed.ge.1) then
87      if (1==0) then
88!CR:date de quand le calcul du zmax continu etait buggue
89         num(:)=0.
90         denom(:)=0.
91         do ig=1,ngrid
92          do l=1,nlay
93             num(ig)=num(ig)+zw2(ig,l)*zlev(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
94             denom(ig)=denom(ig)+zw2(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
95          enddo
96       enddo
97       do ig=1,ngrid
98       if (denom(ig).gt.1.e-10) then
99          zmax(ig)=2.*num(ig)/denom(ig)
100          zmax0(ig)=zmax(ig)
101       endif
102       enddo
103 
104      else
105!CR:Calcul de zmax continu via le linter     
106      do  ig=1,ngrid
107! calcul de zlevinter
108          zlevinter(ig)=(zlev(ig,lmax(ig)+1)-zlev(ig,lmax(ig)))*  &
109     &    linter(ig)+zlev(ig,lmax(ig))-lmax(ig)*(zlev(ig,lmax(ig)+1)  &
110     &    -zlev(ig,lmax(ig)))
111!pour le cas ou on prend tjs lmin=1
112!       zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,lmin(ig)))
113       zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,1))
114       zmax0(ig)=zmax(ig)
115      enddo
116
117
118      endif
119!endif iflag_thermals_ed
120!
121! def de  zmix continu (profil parabolique des vitesses)
122      do ig=1,ngrid
123           if (lmix(ig).gt.1) then
124! test
125              if (((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig)))  &
126     &        *((zlev(ig,lmix(ig)))-(zlev(ig,lmix(ig)+1)))  &
127     &        -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1))  &
128     &        *((zlev(ig,lmix(ig)-1))-(zlev(ig,lmix(ig))))).gt.1e-10)  &
129     &        then
130!             
131            zmix(ig)=((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig)))  &
132     &        *((zlev(ig,lmix(ig)))**2-(zlev(ig,lmix(ig)+1))**2)  &
133     &        -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1))  &
134     &        *((zlev(ig,lmix(ig)-1))**2-(zlev(ig,lmix(ig)))**2))  &
135     &        /(2.*((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig)))  &
136     &        *((zlev(ig,lmix(ig)))-(zlev(ig,lmix(ig)+1)))  &
137     &        -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1))  &
138     &        *((zlev(ig,lmix(ig)-1))-(zlev(ig,lmix(ig))))))
139              else
140              zmix(ig)=zlev(ig,lmix(ig))
141              print*,'pb zmix'
142              endif
143          else
144              zmix(ig)=0.
145          endif
146!test
147         if ((zmax(ig)-zmix(ig)).le.0.) then
148            zmix(ig)=0.9*zmax(ig)
149!            print*,'pb zmix>zmax'
150         endif
151      enddo
152!
153! calcul du nouveau lmix correspondant
154      do ig=1,ngrid
155         do l=1,nlay
156            if (zmix(ig).ge.zlev(ig,l).and.  &
157     &          zmix(ig).lt.zlev(ig,l+1)) then
158              lmix(ig)=l
159             endif
160          enddo
161      enddo
162!
163      return
164      end
Note: See TracBrowser for help on using the repository browser.