source: LMDZ6/branches/Amaury_dev/libf/phylmd/lmdz_thermcell_dry.F90

Last change on this file was 5158, checked in by abarral, 3 months ago

Add missing klon on strataer_emiss_mod.F90
Correct various missing explicit declarations
Replace tabs by spaces (tabs are not part of the fortran charset)
Continue cleaning modules
Removed unused arguments and variables

  • 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
RevLine 
[4590]1MODULE lmdz_thermcell_dry
[5099]2
[1403]3! $Id: lmdz_thermcell_dry.F90 5158 2024-08-02 12:12:03Z fairhead $
[5099]4
[4590]5CONTAINS
6
[878]7       SUBROUTINE thermcell_dry(ngrid,nlay,zlev,pphi,ztv,alim_star,  &
[5087]8                              lalim,lmin,zmax,wmax)
[878]9
10!--------------------------------------------------------------------------
11!thermcell_dry: calcul de zmax et wmax du thermique sec
[1403]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.
[878]18!--------------------------------------------------------------------------
[4590]19       USE lmdz_thermcell_ini, ONLY: prt_level, RG
[878]20       IMPLICIT NONE
21
[5117]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
[878]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)
[1403]35      CHARACTER (LEN=20) :: modname='thermcell_dry'
36      CHARACTER (LEN=80) :: abort_message
[4094]37       INTEGER l,ig
[878]38
39!initialisations
[5158]40       DO ig=1,ngrid
41          DO l=1,nlay+1
[878]42             zw2(ig,l)=0.
43             wa_moy(ig,l)=0.
44          enddo
45       enddo
[5158]46       DO ig=1,ngrid
47          DO l=1,nlay
[878]48             ztva(ig,l)=ztv(ig,l)
49          enddo
50       enddo
[5158]51       DO ig=1,ngrid
[878]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.
[5158]60       DO l=1,nlay
[878]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
[5158]73       DO l=1,nlay-2
74         DO ig=1,ngrid
[5117]75            IF (l==lmin(ig).AND.lalim(ig)>1) THEN
[878]76!------------------------------------------------------------------------
77!  Calcul de la vitesse en haut de la premiere couche instable.
78!  Premiere couche du panache thermique
79!------------------------------------------------------------------------
[1403]80
[878]81               zw2(ig,l+1)=2.*RG*(ztv(ig,l)-ztv(ig,l+1))/ztv(ig,l+1)  &
[5087]82                       *(zlev(ig,l+1)-zlev(ig,l))  &
83                       *0.4*pphi(ig,l)/(pphi(ig,l+1)-pphi(ig,l))
[878]84
85!------------------------------------------------------------------------
86! Tant que la vitesse en bas de la couche et la somme du flux de masse
87! et de l'entrainement (c'est a dire le flux de masse en haut) sont
88! positifs, on calcul
89! 1. le flux de masse en haut  f_star(ig,l+1)
90! 2. la temperature potentielle virtuelle dans la couche ztva(ig,l)
[5093]91! 3. la vitesse au carré en haut zw2(ig,l+1)
[878]92!------------------------------------------------------------------------
93
[5117]94            ELSE IF (zw2(ig,l)>=1e-10) THEN
[878]95               ztva(ig,l)=(f_star(ig,l)*ztva(ig,l-1)+alim_star(ig,l)  &
[5087]96                      *ztv(ig,l))/f_star(ig,l+1)
[878]97               zw2(ig,l+1)=zw2(ig,l)*(f_star(ig,l)/f_star(ig,l+1))**2+  &
[5087]98                       2.*RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l)  &
99                       *(zlev(ig,l+1)-zlev(ig,l))
[878]100            endif
101! determination de zmax continu par interpolation lineaire
102!------------------------------------------------------------------------
103
[5117]104            IF (zw2(ig,l+1)>0. .AND. zw2(ig,l+1)<1.e-10) THEN
[5105]105!               stop 'On tombe sur le cas particulier de thermcell_dry'
[5103]106!               PRINT*,'On tombe sur le cas particulier de thermcell_dry'
[878]107                zw2(ig,l+1)=0.
108                linter(ig)=l+1
109                lmax(ig)=l
110            endif
111
[5117]112            IF (zw2(ig,l+1)<0.) THEN
[878]113               linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l))  &
[5087]114             -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l))
[878]115               zw2(ig,l+1)=0.
116               lmax(ig)=l
[1998]117!            endif
118!CR:zmax continu 06/05/12: calcul de linter quand le thermique est stoppe par le detrainement
[5116]119            elseif (f_star(ig,l+1)<0.) THEN
[1998]120               linter(ig)=(l*(f_star(ig,l+1)-f_star(ig,l))  &
[5087]121             -f_star(ig,l))/(f_star(ig,l+1)-f_star(ig,l))
[1998]122               zw2(ig,l+1)=0.
123               lmax(ig)=l
[878]124            endif
[1998]125!CRfin
[878]126               wa_moy(ig,l+1)=sqrt(zw2(ig,l+1))
127
[5117]128            IF (wa_moy(ig,l+1)>wmaxa(ig)) THEN
[878]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
[5117]135       IF (prt_level>=1) PRINT*,'fin calcul zw2'
[5099]136
[878]137! Determination de zw2 max
[5158]138      DO ig=1,ngrid
[878]139         wmax(ig)=0.
140      enddo
141
[5158]142      DO l=1,nlay
143         DO ig=1,ngrid
[5117]144            IF (l<=lmax(ig)) THEN
[878]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.
[5158]154      DO  ig=1,ngrid
[878]155         zmax(ig)=0.
156         zlevinter(ig)=zlev(ig,1)
157      enddo
[5158]158      DO  ig=1,ngrid
[878]159! calcul de zlevinter
160          zlevinter(ig)=zlev(ig,lmax(ig)) + &
[5087]161      (linter(ig)-lmax(ig))*(zlev(ig,lmax(ig)+1)-zlev(ig,lmax(ig)))
[878]162           zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,lmin(ig)))
163      enddo
164
[4094]165 RETURN
[878]166      END
[4590]167END MODULE lmdz_thermcell_dry
Note: See TracBrowser for help on using the repository browser.