source: dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/thermcell_env.F90 @ 3817

Last change on this file since 3817 was 3817, checked in by millour, 10 years ago

Further cleanup and removal of references to iniprint.h.
Also added bench testcase 48x36x19.
EM

File size: 2.4 KB
Line 
1      SUBROUTINE thermcell_env(ngrid,nlay,po,pt,pu,pv,pplay,  &
2     &           pplev,zo,zh,zl,ztv,zthl,zu,zv,zpspsk,pqsat,lev_out)
3
4!--------------------------------------------------------------
5!thermcell_env: calcule les caracteristiques de l environnement
6!necessaires au calcul des proprietes dans le thermique
7!--------------------------------------------------------------
8      USE inifis_mod, ONLY: prt_level
9      IMPLICIT NONE
10
11#include "YOMCST.h"
12#include "YOETHF.h"
13#include "FCTTRE.h"     
14
15      INTEGER ngrid,nlay
16      REAL po(ngrid,nlay)
17      REAL pt(ngrid,nlay)
18      REAL pu(ngrid,nlay)
19      REAL pv(ngrid,nlay)
20      REAL pplay(ngrid,nlay)
21      REAL pplev(ngrid,nlay+1)
22      integer lev_out                           ! niveau pour les print
23
24      REAL zo(ngrid,nlay)
25      REAL zl(ngrid,nlay)
26      REAL zh(ngrid,nlay)
27      REAL ztv(ngrid,nlay)
28      REAL zthl(ngrid,nlay)
29      REAL zpspsk(ngrid,nlay)
30      REAL zu(ngrid,nlay)
31      REAL zv(ngrid,nlay)
32      REAL pqsat(ngrid,nlay)
33
34      INTEGER ig,ll
35
36      real dqsat_dT
37      real RLvCp
38
39logical mask(ngrid,nlay)
40
41
42!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
43! Initialisations :
44!------------------
45
46mask(:,:)=.true.
47RLvCp = RLVTT/RCPD
48
49!
50! calcul des caracteristiques de l environnement
51       DO  ll=1,nlay
52         DO ig=1,ngrid
53            zo(ig,ll)=po(ig,ll)
54            zl(ig,ll)=0.
55            zh(ig,ll)=pt(ig,ll)
56         EndDO
57       EndDO
58!
59!
60! Condensation :
61!---------------
62! Calcul de l'humidite a saturation et de la condensation
63
64call thermcell_qsat(ngrid*nlay,mask,pplev,pt,po,pqsat)
65DO ll=1,nlay
66   DO ig=1,ngrid
67      zl(ig,ll) = max(0.,po(ig,ll)-pqsat(ig,ll))
68      zh(ig,ll) = pt(ig,ll)+RLvCp*zl(ig,ll)         !   T = Tl + Lv/Cp ql
69      zo(ig,ll) = po(ig,ll)-zl(ig,ll)
70   ENDDO
71ENDDO
72!
73!
74!-----------------------------------------------------------------------
75
76      if (prt_level.ge.1) print*,'0 OK convect8'
77
78      DO ll=1,nlay
79         DO ig=1,ngrid
80             zpspsk(ig,ll)=(pplay(ig,ll)/100000.)**RKAPPA
81             zu(ig,ll)=pu(ig,ll)
82             zv(ig,ll)=pv(ig,ll)
83!attention zh est maintenant le profil de T et plus le profil de theta !
84! Quelle horreur ! A eviter.
85!
86!   T-> Theta
87            ztv(ig,ll)=zh(ig,ll)/zpspsk(ig,ll)
88!Theta_v
89            ztv(ig,ll)=ztv(ig,ll)*(1.+RETV*(zo(ig,ll))-zl(ig,ll))
90!Thetal
91            zthl(ig,ll)=pt(ig,ll)/zpspsk(ig,ll)
92!           
93         ENDDO
94      ENDDO
95 
96      RETURN
97      END
Note: See TracBrowser for help on using the repository browser.