source: LMDZ6/trunk/libf/phylmd/lmdz_thermcell_height.F90 @ 4843

Last change on this file since 4843 was 4843, checked in by crio, 3 months ago

Nouvelle formulation du strig et correction thermiques montent trop haut

  • 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: 5.2 KB
Line 
1MODULE lmdz_thermcell_height
2CONTAINS
3
4      SUBROUTINE thermcell_height(ngrid,nlay,lalim,lmin,linter,lcong,lintercong,lmix,  &
5     &           zw2,zlev,lmax,zmax,zmax0,zmix,wmax,zcong)
6      IMPLICIT NONE
7
8!-----------------------------------------------------------------------------
9!thermcell_height: calcul des caracteristiques du thermique: zmax,wmax,zmix
10!-----------------------------------------------------------------------------
11
12! arguments
13
14! Entree
15      integer, intent(in) :: ngrid,nlay
16      real, intent(in), dimension(ngrid) :: linter,lintercong
17      real, intent(in), dimension(ngrid,nlay+1) :: zlev
18! Sortie
19      real, intent(out), dimension(ngrid) :: wmax,zmax,zmax0,zmix,zcong
20      integer, intent(out), dimension(ngrid) :: lmax,lcong
21! Les deux
22     integer, intent(inout), dimension(ngrid) :: lmix,lalim,lmin
23     real, intent(inout), dimension(ngrid,nlay+1) :: zw2
24
25! local
26     real, dimension(ngrid) :: num,denom,zlevinter,zlevintercong
27     integer ig,l
28
29!calcul de la hauteur max du thermique
30      do ig=1,ngrid
31         lmax(ig)=lalim(ig)
32      enddo
33      do ig=1,ngrid
34         do l=nlay,lalim(ig)+1,-1
35            if (zw2(ig,l).le.1.e-10) then
36               lmax(ig)=l-1
37            endif
38         enddo
39      enddo
40
41! On traite le cas particulier qu'il faudrait éviter ou le thermique
42! atteind le haut du modele ...
43      do ig=1,ngrid
44      if ( zw2(ig,nlay) > 1.e-10 ) then
45          print*,'WARNING !!!!! W2 thermiques non nul derniere couche '
46          lmax(ig)=nlay
47      endif
48      enddo
49
50! pas de thermique si couche 1 stable
51      do ig=1,ngrid
52         if (lmin(ig).gt.1) then
53             lmax(ig)=1
54             lmin(ig)=1
55             lalim(ig)=1
56         endif
57      enddo
58!   
59! Determination de zw2 max
60      do ig=1,ngrid
61         wmax(ig)=0.
62      enddo
63
64      do l=1,nlay
65         do ig=1,ngrid
66            if (l.le.lmax(ig)) then
67                if (zw2(ig,l).lt.0.)then
68                  print*,'pb2 zw2<0'
69                endif
70                zw2(ig,l)=sqrt(zw2(ig,l))
71                wmax(ig)=max(wmax(ig),zw2(ig,l))
72            else
73                 zw2(ig,l)=0.
74            endif
75          enddo
76      enddo
77
78!   Longueur caracteristique correspondant a la hauteur des thermiques.
79      do  ig=1,ngrid
80         zmax(ig)=0.
81         zlevinter(ig)=zlev(ig,1)
82      enddo
83
84!     if (iflag_thermals_ed.ge.1) then
85      if (1==0) then
86!CR:date de quand le calcul du zmax continu etait buggue
87         num(:)=0.
88         denom(:)=0.
89         do ig=1,ngrid
90          do l=1,nlay
91             num(ig)=num(ig)+zw2(ig,l)*zlev(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
92             denom(ig)=denom(ig)+zw2(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
93          enddo
94       enddo
95       do ig=1,ngrid
96       if (denom(ig).gt.1.e-10) then
97          zmax(ig)=2.*num(ig)/denom(ig)
98          zmax0(ig)=zmax(ig)
99       endif
100       enddo
101 
102      else
103!CR:Calcul de zmax continu via le linter     
104      do  ig=1,ngrid
105! calcul de zlevinter
106          zlevinter(ig)=(zlev(ig,lmax(ig)+1)-zlev(ig,lmax(ig)))*  &
107     &    linter(ig)+zlev(ig,lmax(ig))-lmax(ig)*(zlev(ig,lmax(ig)+1)  &
108     &    -zlev(ig,lmax(ig)))
109!pour le cas ou on prend tjs lmin=1
110!       zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,lmin(ig)))
111       zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,1))
112       zmax0(ig)=zmax(ig)
113      enddo
114
115!CR:calcul du zcong
116      do  ig=1,ngrid
117! calcul de zlevintercong
118         zlevintercong(ig)=(zlev(ig,lcong(ig)+1)-zlev(ig,lcong(ig)))*  &
119     &    lintercong(ig)+zlev(ig,lcong(ig))-lcong(ig)*(zlev(ig,lcong(ig)+1)  &
120     &    -zlev(ig,lcong(ig)))
121         zcong(ig)=zlevintercong(ig)-zlev(ig,1)
122!         print*,"calcul zcong",lcong(ig),lintercong(ig),zlevintercong(ig),zcong(ig)
123      enddo
124
125      endif
126!endif iflag_thermals_ed
127!
128! def de  zmix continu (profil parabolique des vitesses)
129      do ig=1,ngrid
130           if (lmix(ig).gt.1) then
131! test
132              if (((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig)))  &
133     &        *((zlev(ig,lmix(ig)))-(zlev(ig,lmix(ig)+1)))  &
134     &        -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1))  &
135     &        *((zlev(ig,lmix(ig)-1))-(zlev(ig,lmix(ig))))).gt.1e-10)  &
136     &        then
137!             
138            zmix(ig)=((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig)))  &
139     &        *((zlev(ig,lmix(ig)))**2-(zlev(ig,lmix(ig)+1))**2)  &
140     &        -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1))  &
141     &        *((zlev(ig,lmix(ig)-1))**2-(zlev(ig,lmix(ig)))**2))  &
142     &        /(2.*((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig)))  &
143     &        *((zlev(ig,lmix(ig)))-(zlev(ig,lmix(ig)+1)))  &
144     &        -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1))  &
145     &        *((zlev(ig,lmix(ig)-1))-(zlev(ig,lmix(ig))))))
146              else
147              zmix(ig)=zlev(ig,lmix(ig))
148              print*,'pb zmix'
149              endif
150          else
151              zmix(ig)=0.
152          endif
153!test
154         if ((zmax(ig)-zmix(ig)).le.0.) then
155            zmix(ig)=0.9*zmax(ig)
156!            print*,'pb zmix>zmax'
157         endif
158      enddo
159!
160! calcul du nouveau lmix correspondant
161      do ig=1,ngrid
162         do l=1,nlay
163            if (zmix(ig).ge.zlev(ig,l).and.  &
164     &          zmix(ig).lt.zlev(ig,l+1)) then
165              lmix(ig)=l
166             endif
167          enddo
168      enddo
169!
170 RETURN
171      end
172END MODULE lmdz_thermcell_height
Note: See TracBrowser for help on using the repository browser.