source: LMDZ6/trunk/libf/phylmdiso/thermcell_env.F90 @ 3927

Last change on this file since 3927 was 3927, checked in by Laurent Fairhead, 3 years ago

Initial import of the physics wih isotopes from Camille Risi
CR

File size: 5.3 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#ifdef ISO
4     &            ,xtpo,xtzo,xtzl &
5#endif     
6     &   )
7
8!--------------------------------------------------------------
9!thermcell_env: calcule les caracteristiques de l environnement
10!necessaires au calcul des proprietes dans le thermique
11!--------------------------------------------------------------
12
13      USE print_control_mod, ONLY: prt_level
14#ifdef ISO
15  USE infotrac_phy, ONLY : ntraciso
16  USE isotopes_mod, ONLY: pxtice,pxtmelt,iso_eau,iso_HDO
17  USE isotopes_routines_mod, ONLY: condiso_liq_ice_vectall
18#ifdef ISOVERIF
19  USE isotopes_verif_mod, ONLY: iso_verif_egalite, &
20        iso_verif_aberrant_encadre,iso_verif_noNaN
21#endif
22#ifdef ISOTRAC
23  USE isotopes_routines_mod, ONLY: condiso_liq_ice_vectall_trac
24#ifdef ISOVERIF
25  USE isotopes_verif_mod, ONLY: iso_verif_traceur
26#endif
27#endif
28#endif
29      IMPLICIT NONE
30
31#include "YOMCST.h"
32#include "YOETHF.h"
33#include "FCTTRE.h"     
34
35      INTEGER ngrid,nlay
36      REAL po(ngrid,nlay)
37      REAL pt(ngrid,nlay)
38      REAL pu(ngrid,nlay)
39      REAL pv(ngrid,nlay)
40      REAL pplay(ngrid,nlay)
41      REAL pplev(ngrid,nlay+1)
42      integer lev_out                           ! niveau pour les print
43
44      REAL zo(ngrid,nlay)
45      REAL zl(ngrid,nlay)
46      REAL zh(ngrid,nlay)
47      REAL ztv(ngrid,nlay)
48      REAL zthl(ngrid,nlay)
49      REAL zpspsk(ngrid,nlay)
50      REAL zu(ngrid,nlay)
51      REAL zv(ngrid,nlay)
52      REAL pqsat(ngrid,nlay)
53
54      INTEGER ig,ll
55
56      real dqsat_dT
57      real RLvCp
58
59logical mask(ngrid,nlay)
60
61#ifdef ISO
62      REAL xtpo(ntraciso,ngrid,nlay)
63      REAL xtzo(ntraciso,ngrid,nlay)
64      REAL xtzl(ntraciso,ngrid,nlay)
65      integer ixt
66      real zxtliq(ntraciso,ngrid),zxtice(ntraciso,ngrid)
67      real zfice(ngrid)
68      REAL zxtl(ntraciso,ngrid,nlay)
69#endif
70
71
72!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
73! Initialisations :
74!------------------
75
76mask(:,:)=.true.
77RLvCp = RLVTT/RCPD
78
79!
80! calcul des caracteristiques de l environnement
81       DO  ll=1,nlay
82         DO ig=1,ngrid
83            zo(ig,ll)=po(ig,ll)
84            zl(ig,ll)=0.
85            zh(ig,ll)=pt(ig,ll)
86#ifdef ISO
87            do ixt=1,ntraciso
88              xtzo(ixt,ig,ll)=xtpo(ixt,ig,ll)
89              xtzl(ixt,ig,ll)=0.
90            enddo   !do ixt=1,ntraciso
91#endif
92         EndDO
93       EndDO
94!
95!
96! Condensation :
97!---------------
98! Calcul de l'humidite a saturation et de la condensation
99
100call thermcell_qsat(ngrid*nlay,mask,pplev,pt,po,pqsat)
101DO ll=1,nlay
102   DO ig=1,ngrid
103      zl(ig,ll) = max(0.,po(ig,ll)-pqsat(ig,ll))
104      zh(ig,ll) = pt(ig,ll)+RLvCp*zl(ig,ll)         !   T = Tl + Lv/Cp ql
105      zo(ig,ll) = po(ig,ll)-zl(ig,ll)
106   ENDDO
107ENDDO
108
109
110
111#ifdef ISO
112#ifdef ISOVERIF
113   write(*,*) 'thermcell_env 94: avant condiso_liq_ice_vectall'
114   DO ll=1,nlay
115    do ig=1,ngrid
116       call iso_verif_noNaN(po(ig,ll), &
117       & 'thermcell_env 99')
118       do ixt=1,ntraciso         
119         call iso_verif_noNaN(xtpo(ixt,ig,ll), &
120       &        'thermcell_env 103')
121       enddo !do ixt=1,ntraciso   
122       if (iso_eau.gt.0) then
123         call iso_verif_egalite(xtpo(iso_eau,ig,ll),po(ig,ll), &
124         & 'thermcell_env 100')
125       endif
126    enddo !do ig=1,ngrid
127   enddo !DO ll=1,nlay
128#endif     
129 DO ll=1,nlay
130  do ig=1,ngrid
131        zfice(ig)=1.0-(pt(ig,ll)-pxtice)/(pxtmelt-pxtice)
132        zfice(ig) = MIN(MAX(zfice(ig),0.0),1.0)
133  enddo  !do ig=1,ngrid
134
135
136  call condiso_liq_ice_vectall(xtpo(1,1,ll),po(1,ll),zl(1,ll),pt(1,ll),zfice, &
137     &            zxtice,zxtliq,ngrid)
138#ifdef ISOTRAC
139  call condiso_liq_ice_vectall_trac(xtpo(1,1,ll),po(1,ll),zl(1,ll), &
140     &            pt(1,ll),zfice,zxtice,zxtliq,ngrid)
141#ifdef ISOVERIF
142  do ig=1,ngrid           
143      call iso_verif_traceur(xtpo(1,ig,ll),'thermcell_env 102')
144      call iso_verif_traceur(zxtliq(1,ig),'thermcell_env 103')
145      call iso_verif_traceur(zxtice(1,ig),'thermcell_env 104')
146  enddo !do ig=1,ngrid
147#endif
148#endif
149  do ig=1,ngrid
150     do ixt=1,ntraciso                 
151       zxtl(ixt,ig,ll)=zxtice(ixt,ig)+zxtliq(ixt,ig)
152       xtzo(ixt,ig,ll) = xtpo(ixt,ig,ll)-zxtl(ixt,ig,ll)
153     enddo ! do ixt=1,ntraciso 
154#ifdef ISOVERIF
155     if (iso_eau.gt.0) then
156       call iso_verif_egalite(zxtl(iso_eau,ig,ll),zl(ig,ll), &
157       & 'thermcell_env 120')
158       call iso_verif_egalite(xtzo(iso_eau,ig,ll),zo(ig,ll), &
159       & 'thermcell_env 136')
160     endif
161      if (iso_HDO.gt.0) then
162      call iso_verif_aberrant_encadre( &
163       &          xtzo(iso_HDO,ig,ll)/zo(ig,ll), &
164       &          'thermcell_env 141')
165      endif     
166#endif     
167  enddo ! do ig=1,ngrid
168enddo !DO ll=1,nlay
169#endif
170
171!
172!
173!-----------------------------------------------------------------------
174
175      if (prt_level.ge.1) print*,'0 OK convect8'
176
177      DO ll=1,nlay
178         DO ig=1,ngrid
179             zpspsk(ig,ll)=(pplay(ig,ll)/100000.)**RKAPPA
180             zu(ig,ll)=pu(ig,ll)
181             zv(ig,ll)=pv(ig,ll)
182!attention zh est maintenant le profil de T et plus le profil de theta !
183! Quelle horreur ! A eviter.
184!
185!   T-> Theta
186            ztv(ig,ll)=zh(ig,ll)/zpspsk(ig,ll)
187!Theta_v
188            ztv(ig,ll)=ztv(ig,ll)*(1.+RETV*(zo(ig,ll))-zl(ig,ll))
189!Thetal
190            zthl(ig,ll)=pt(ig,ll)/zpspsk(ig,ll)
191!           
192         ENDDO
193      ENDDO
194 
195      RETURN
196      END
Note: See TracBrowser for help on using the repository browser.