source: LMDZ6/trunk/libf/phylmd/lmdz_thermcell_dry.F90 @ 4678

Last change on this file since 4678 was 4590, checked in by fhourdin, 11 months ago

Passage des thermiques a la nouvelle norme.

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