source: LMDZ5/branches/IPSLCM5A2.1_ISO/libf/phyiso/thermcell_env.F90 @ 3363

Last change on this file since 3363 was 3331, checked in by acozic, 6 years ago

Add modification for isotopes

  • Property svn:executable set to *
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#ifdef ISO
110#ifdef ISOVERIF
111   DO ll=1,nlay
112    do ig=1,ngrid
113       call iso_verif_noNaN(po(ig,ll), &
114       & 'thermcell_env 99')
115       do ixt=1,ntraciso         
116         call iso_verif_noNaN(xtpo(ixt,ig,ll), &
117       &        'thermcell_env 103')
118       enddo !do ixt=1,ntraciso
119    enddo !do ig=1,ngrid
120   enddo !DO ll=1,nlay
121#endif
122#ifdef ISOVERIF
123   write(*,*) 'thermcell_env 94: avant condiso_liq_ice_vectall'
124   DO ll=1,nlay
125    do ig=1,ngrid   
126     if (iso_eau.gt.0) then
127       call iso_verif_egalite(xtpo(iso_eau,ig,ll),po(ig,ll), &
128       & 'thermcell_env 100')
129     endif
130    enddo !do ig=1,ngrid
131   enddo !DO ll=1,nlay
132#endif     
133 DO ll=1,nlay
134  do ig=1,ngrid
135        zfice(ig)=1.0-(pt(ig,ll)-pxtice)/(pxtmelt-pxtice)
136        zfice(ig) = MIN(MAX(zfice(ig),0.0),1.0)
137  enddo  !do ig=1,ngrid
138
139  call condiso_liq_ice_vectall(xtpo(1,1,ll),po(1,ll),zl(1,ll),pt(1,ll),zfice, &
140     &            zxtice,zxtliq,ngrid)
141#ifdef ISOTRAC
142  call condiso_liq_ice_vectall_trac(xtpo(1,1,ll),po(1,ll),zl(1,ll), &
143     &            pt(1,ll),zfice,zxtice,zxtliq,ngrid)
144#ifdef ISOVERIF
145  do ig=1,ngrid           
146      call iso_verif_traceur(xtpo(1,ig,ll),'thermcell_env 102')
147      call iso_verif_traceur(zxtliq(1,ig),'thermcell_env 103')
148      call iso_verif_traceur(zxtice(1,ig),'thermcell_env 104')
149  enddo !do ig=1,ngrid
150#endif
151#endif
152  do ig=1,ngrid
153     do ixt=1,ntraciso                 
154       zxtl(ixt,ig,ll)=zxtice(ixt,ig)+zxtliq(ixt,ig)
155       xtzo(ixt,ig,ll) = xtpo(ixt,ig,ll)-zxtl(ixt,ig,ll)
156     enddo ! do ixt=1,ntraciso 
157#ifdef ISOVERIF
158     if (iso_eau.gt.0) then
159       call iso_verif_egalite(zxtl(iso_eau,ig,ll),zl(ig,ll), &
160       & 'thermcell_env 120')
161       call iso_verif_egalite(xtzo(iso_eau,ig,ll),zo(ig,ll), &
162       & 'thermcell_env 136')
163     endif
164      if (iso_HDO.gt.0) then
165      call iso_verif_aberrant_encadre( &
166       &          xtzo(iso_HDO,ig,ll)/zo(ig,ll), &
167       &          'thermcell_env 141')
168      endif     
169#endif     
170  enddo ! do ig=1,ngrid
171enddo !DO ll=1,nlay
172#endif
173!
174!
175!-----------------------------------------------------------------------
176
177      if (prt_level.ge.1) print*,'0 OK convect8'
178
179      DO ll=1,nlay
180         DO ig=1,ngrid
181             zpspsk(ig,ll)=(pplay(ig,ll)/100000.)**RKAPPA
182             zu(ig,ll)=pu(ig,ll)
183             zv(ig,ll)=pv(ig,ll)
184!attention zh est maintenant le profil de T et plus le profil de theta !
185! Quelle horreur ! A eviter.
186!
187!   T-> Theta
188            ztv(ig,ll)=zh(ig,ll)/zpspsk(ig,ll)
189!Theta_v
190            ztv(ig,ll)=ztv(ig,ll)*(1.+RETV*(zo(ig,ll))-zl(ig,ll))
191!Thetal
192            zthl(ig,ll)=pt(ig,ll)/zpspsk(ig,ll)
193!           
194         ENDDO
195      ENDDO
196 
197      RETURN
198      END
Note: See TracBrowser for help on using the repository browser.