source: LMDZ6/trunk/libf/phylmd/thermcell_dry.F90 @ 4283

Last change on this file since 4283 was 4094, checked in by fhourdin, 2 years ago

Nettoyage thermiques (suite) et replay1d

  • 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.5 KB
Line 
1!
2! $Id: thermcell_dry.F90 4094 2022-03-14 00:45:50Z jghattas $
3!
4       SUBROUTINE thermcell_dry(ngrid,nlay,zlev,pphi,ztv,alim_star,  &
5     &                            lalim,lmin,zmax,wmax)
6
7!--------------------------------------------------------------------------
8!thermcell_dry: calcul de zmax et wmax du thermique sec
9! Calcul de la vitesse maximum et de la hauteur maximum pour un panache
10! ascendant avec une fonction d'alimentation alim_star et sans changement
11! de phase.
12! Le calcul pourrait etre sans doute simplifier.
13! La temperature potentielle virtuelle dans la panache ascendant est
14! la temperature potentielle virtuelle pondérée par alim_star.
15!--------------------------------------------------------------------------
16       USE thermcell_ini_mod, ONLY: prt_level, RG
17       IMPLICIT NONE
18
19       integer, intent(in) :: ngrid,nlay
20       real, intent(in), dimension(ngrid,nlay+1) :: zlev,pphi,ztv,alim_star
21       integer, intent(in), dimension(ngrid) :: lalim
22       real, intent(out), dimension(ngrid) :: zmax,wmax
23
24!variables locales
25       REAL zw2(ngrid,nlay+1)
26       REAL f_star(ngrid,nlay+1)
27       REAL ztva(ngrid,nlay+1)
28       REAL wmaxa(ngrid)
29       REAL wa_moy(ngrid,nlay+1)
30       REAL linter(ngrid),zlevinter(ngrid)
31       INTEGER lmix(ngrid),lmax(ngrid),lmin(ngrid)
32      CHARACTER (LEN=20) :: modname='thermcell_dry'
33      CHARACTER (LEN=80) :: abort_message
34       INTEGER l,ig
35
36!initialisations
37       do ig=1,ngrid
38          do l=1,nlay+1
39             zw2(ig,l)=0.
40             wa_moy(ig,l)=0.
41          enddo
42       enddo
43       do ig=1,ngrid
44          do l=1,nlay
45             ztva(ig,l)=ztv(ig,l)
46          enddo
47       enddo
48       do ig=1,ngrid
49          wmax(ig)=0.
50          wmaxa(ig)=0.
51       enddo
52!calcul de la vitesse a partir de la CAPE en melangeant thetav
53
54
55! Calcul des F^*, integrale verticale de E^*
56       f_star(:,1)=0.
57       do l=1,nlay
58          f_star(:,l+1)=f_star(:,l)+alim_star(:,l)
59       enddo
60
61! niveau (reel) auquel zw2 s'annule FH :n'etait pas initialise
62       linter(:)=0.
63
64! couche la plus haute concernee par le thermique.
65       lmax(:)=1
66
67! Le niveau linter est une variable continue qui se trouve dans la couche
68! lmax
69
70       do l=1,nlay-2
71         do ig=1,ngrid
72            if (l.eq.lmin(ig).and.lalim(ig).gt.1) then
73
74!------------------------------------------------------------------------
75!  Calcul de la vitesse en haut de la premiere couche instable.
76!  Premiere couche du panache thermique
77!------------------------------------------------------------------------
78
79               zw2(ig,l+1)=2.*RG*(ztv(ig,l)-ztv(ig,l+1))/ztv(ig,l+1)  &
80     &                     *(zlev(ig,l+1)-zlev(ig,l))  &
81     &                     *0.4*pphi(ig,l)/(pphi(ig,l+1)-pphi(ig,l))
82
83!------------------------------------------------------------------------
84! Tant que la vitesse en bas de la couche et la somme du flux de masse
85! et de l'entrainement (c'est a dire le flux de masse en haut) sont
86! positifs, on calcul
87! 1. le flux de masse en haut  f_star(ig,l+1)
88! 2. la temperature potentielle virtuelle dans la couche ztva(ig,l)
89! 3. la vitesse au carré en haut zw2(ig,l+1)
90!------------------------------------------------------------------------
91
92            else if (zw2(ig,l).ge.1e-10) then
93
94               ztva(ig,l)=(f_star(ig,l)*ztva(ig,l-1)+alim_star(ig,l)  &
95     &                    *ztv(ig,l))/f_star(ig,l+1)
96               zw2(ig,l+1)=zw2(ig,l)*(f_star(ig,l)/f_star(ig,l+1))**2+  &
97     &                     2.*RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)  &
98     &                     *(zlev(ig,l+1)-zlev(ig,l))
99            endif
100! determination de zmax continu par interpolation lineaire
101!------------------------------------------------------------------------
102
103            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
104!               stop'On tombe sur le cas particulier de thermcell_dry'
105!               print*,'On tombe sur le cas particulier de thermcell_dry'
106                zw2(ig,l+1)=0.
107                linter(ig)=l+1
108                lmax(ig)=l
109            endif
110
111            if (zw2(ig,l+1).lt.0.) then
112               linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
113     &           -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
114               zw2(ig,l+1)=0.
115               lmax(ig)=l
116!            endif
117!CR:zmax continu 06/05/12: calcul de linter quand le thermique est stoppe par le detrainement
118            elseif (f_star(ig,l+1).lt.0.) then
119               linter(ig)=(l*(f_star(ig,l+1)-f_star(ig,l))  &
120     &           -f_star(ig,l))/(f_star(ig,l+1)-f_star(ig,l))
121               zw2(ig,l+1)=0.
122               lmax(ig)=l
123            endif
124!CRfin
125               wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
126
127            if (wa_moy(ig,l+1).gt.wmaxa(ig)) then
128!   lmix est le niveau de la couche ou w (wa_moy) est maximum
129               lmix(ig)=l+1
130               wmaxa(ig)=wa_moy(ig,l+1)
131            endif
132         enddo
133      enddo
134       if (prt_level.ge.1) print*,'fin calcul zw2'
135!
136! Determination de zw2 max
137      do ig=1,ngrid
138         wmax(ig)=0.
139      enddo
140
141      do l=1,nlay
142         do ig=1,ngrid
143            if (l.le.lmax(ig)) then
144                zw2(ig,l)=sqrt(zw2(ig,l))
145                wmax(ig)=max(wmax(ig),zw2(ig,l))
146            else
147                 zw2(ig,l)=0.
148            endif
149          enddo
150      enddo
151
152!   Longueur caracteristique correspondant a la hauteur des thermiques.
153      do  ig=1,ngrid
154         zmax(ig)=0.
155         zlevinter(ig)=zlev(ig,1)
156      enddo
157      do  ig=1,ngrid
158! calcul de zlevinter
159          zlevinter(ig)=zlev(ig,lmax(ig)) + &
160     &    (linter(ig)-lmax(ig))*(zlev(ig,lmax(ig)+1)-zlev(ig,lmax(ig)))
161           zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,lmin(ig)))
162      enddo
163
164 RETURN
165      END
Note: See TracBrowser for help on using the repository browser.