source: LMDZ5/branches/testing/libf/phylmd/thermcell_dry.F90 @ 1910

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

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