source: LMDZ4/trunk/libf/phylmd/thermcell_env.F90 @ 946

Last change on this file since 946 was 938, checked in by lmdzadmin, 17 years ago

Enleve prints par defaut
IM

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.1 KB
Line 
1      SUBROUTINE thermcell_env(ngrid,nlay,po,pt,pu,pv,pplay,  &
2     &           pplev,zo,zh,zl,ztv,zthl,zu,zv,zpspsk,zqsat,lev_out)
3
4!--------------------------------------------------------------
5!thermcell_env: calcule les caracteristiques de l environnement
6!necessaires au calcul des proprietes dans le thermique
7!--------------------------------------------------------------
8
9      IMPLICIT NONE
10
11#include "YOMCST.h"
12#include "YOETHF.h"
13#include "FCTTRE.h"     
14#include "iniprint.h"
15
16      INTEGER ngrid,nlay
17      REAL po(ngrid,nlay)
18      REAL pt(ngrid,nlay)
19      REAL pu(ngrid,nlay)
20      REAL pv(ngrid,nlay)
21      REAL pplay(ngrid,nlay)
22      REAL pplev(ngrid,nlay+1)
23      integer lev_out                           ! niveau pour les print
24
25      REAL zo(ngrid,nlay)
26      REAL zl(ngrid,nlay)
27      REAL zh(ngrid,nlay)
28      REAL ztv(ngrid,nlay)
29      REAL zthl(ngrid,nlay)
30      REAL zpspsk(ngrid,nlay)
31      REAL zu(ngrid,nlay)
32      REAL zv(ngrid,nlay)
33      REAL zqsat(ngrid,nlay)
34
35      INTEGER ig,l,ll
36
37      real zcor,zdelta,zcvm5,qlbef
38      real Tbef,qsatbef
39      real dqsat_dT,DT,num,denom
40      REAL RLvCp,DDT0
41      PARAMETER (DDT0=.01)
42      LOGICAL Zsat
43
44      Zsat=.false.
45!
46! Pr Tprec=Tl calcul de qsat
47! Si qsat>qT T=Tl, q=qT
48! Sinon DDT=(-Tprec+Tl+RLVCP (qT-qsat(T')) / (1+RLVCP dqsat/dt)
49! On cherche DDT < DDT0
50!
51! calcul des caracteristiques de l environnement
52       DO  ll=1,nlay
53         DO ig=1,ngrid
54            zo(ig,ll)=po(ig,ll)
55            zl(ig,ll)=0.
56            zh(ig,ll)=pt(ig,ll)
57            zqsat(ig,ll)=0.
58         EndDO
59       EndDO
60!
61!
62!recherche de saturation dans l environnement
63       DO ll=1,nlay
64! les points insatures sont definitifs
65         DO ig=1,ngrid
66            Tbef=pt(ig,ll)
67            zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
68            qsatbef= R2ES * FOEEW(Tbef,zdelta)/pplev(ig,ll)
69            qsatbef=MIN(0.5,qsatbef)
70            zcor=1./(1.-retv*qsatbef)
71            qsatbef=qsatbef*zcor
72            Zsat = (max(0.,po(ig,ll)-qsatbef) .gt. 1.e-10)
73            if (Zsat) then
74            qlbef=max(0.,po(ig,ll)-qsatbef)
75! si sature: ql est surestime, d'ou la sous-relax
76            DT = 0.5*RLvCp*qlbef
77! on pourra enchainer 2 ou 3 calculs sans Do while
78            do while (abs(DT).gt.DDT0)
79! il faut verifier si c,a conserve quand on repasse en insature ...
80              Tbef=Tbef+DT
81              zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
82              qsatbef= R2ES * FOEEW(Tbef,zdelta)/pplev(ig,ll)
83              qsatbef=MIN(0.5,qsatbef)
84              zcor=1./(1.-retv*qsatbef)
85              qsatbef=qsatbef*zcor
86! on veut le signe de qlbef
87              qlbef=po(ig,ll)-qsatbef
88!          dqsat_dT
89              zdelta=MAX(0.,SIGN(1.,RTT-Tbef))
90              zcvm5=R5LES*(1.-zdelta) + R5IES*zdelta
91              zcor=1./(1.-retv*qsatbef)
92              dqsat_dT=FOEDE(Tbef,zdelta,zcvm5,qsatbef,zcor)
93              num=-Tbef+pt(ig,ll)+RLvCp*qlbef
94              denom=1.+RLvCp*dqsat_dT
95              if (denom.lt.1.e-10) then
96                  print*,'pb denom'
97              endif
98              DT=num/denom
99            enddo
100! on ecrit de maniere conservative (sat ou non)
101            zl(ig,ll) = max(0.,qlbef)
102!          T = Tl +Lv/Cp ql
103            zh(ig,ll) = pt(ig,ll)+RLvCp*zl(ig,ll)
104            zo(ig,ll) = po(ig,ll)-zl(ig,ll)
105           endif
106!on ecrit zqsat
107            zqsat(ig,ll)=qsatbef     
108         EndDO
109       EndDO
110!
111!
112!-----------------------------------------------------------------------
113!   incrementation eventuelle de tendances precedentes:
114!   ---------------------------------------------------
115
116      if (prt_level.ge.1) print*,'0 OK convect8'
117
118      DO 1010 l=1,nlay
119         DO 1015 ig=1,ngrid
120             zpspsk(ig,l)=(pplay(ig,l)/100000.)**RKAPPA
121             zu(ig,l)=pu(ig,l)
122             zv(ig,l)=pv(ig,l)
123!attention zh est maintenant le profil de T et plus le profil de theta !
124!
125!   T-> Theta
126            ztv(ig,l)=zh(ig,l)/zpspsk(ig,l)
127!Theta_v
128            ztv(ig,l)=ztv(ig,l)*(1.+RETV*(zo(ig,l))  &
129     &           -zl(ig,l))
130!Thetal
131            zthl(ig,l)=pt(ig,l)/zpspsk(ig,l)
132!           
1331015     CONTINUE
1341010  CONTINUE
135 
136      RETURN
137      END
Note: See TracBrowser for help on using the repository browser.