/[lmdze]/trunk/libf/phylmd/diagetpq.f
ViewVC logotype

Contents of /trunk/libf/phylmd/diagetpq.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 47 - (show annotations)
Fri Jul 1 15:00:48 2011 UTC (12 years, 10 months ago) by guez
File size: 9189 byte(s)
Split "thermcell.f" and "cv3_routines.f".
Removed copies of files that are now in "L_util".
Moved "mva9" and "diagetpq" to their own files.
Unified variable names across procedures.

1 SUBROUTINE diagetpq(airephy,tit,iprt,idiag,idiag2,dtime
2 e ,t,q,ql,qs,u,v,paprs
3 s , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)
4 !
5 ! $Header: /home/cvsroot/LMDZ4/libf/phylmd/diagphy.F,v 1.1.1.1 2004/05/19 12:53:08 lmdzadmin Exp $
6 !
7 C======================================================================
8 C
9 C Purpose:
10 C Calcul la difference d'enthalpie et de masse d'eau entre 2 appels,
11 C et calcul le flux de chaleur et le flux d'eau necessaire a ces
12 C changements. Ces valeurs sont moyennees sur la surface de tout
13 C le globe et sont exprime en W/2 et kg/s/m2
14 C Outil pour diagnostiquer la conservation de l'energie
15 C et de la masse dans la physique. Suppose que les niveau de
16 c pression entre couche ne varie pas entre 2 appels.
17 C
18 C Plusieurs de ces diagnostics peuvent etre fait en parallele: les
19 c bilans sont sauvegardes dans des tableaux indices. On parlera
20 C "d'indice de diagnostic"
21 c
22 C
23 c======================================================================
24 C Arguments:
25 C airephy-------input-R- grid area
26 C tit-----imput-A15- Comment added in PRINT (CHARACTER*15)
27 C iprt----input-I- PRINT level ( <=1 : no PRINT)
28 C idiag---input-I- indice dans lequel sera range les nouveaux
29 C bilans d' entalpie et de masse
30 C idiag2--input-I-les nouveaux bilans d'entalpie et de masse
31 C sont compare au bilan de d'enthalpie de masse de
32 C l'indice numero idiag2
33 C Cas parriculier : si idiag2=0, pas de comparaison, on
34 c sort directement les bilans d'enthalpie et de masse
35 C dtime----input-R- time step (s)
36 c t--------input-R- temperature (K)
37 c q--------input-R- vapeur d'eau (kg/kg)
38 c ql-------input-R- liquid watter (kg/kg)
39 c qs-------input-R- solid watter (kg/kg)
40 c u--------input-R- vitesse u
41 c v--------input-R- vitesse v
42 c paprs----input-R- pression a intercouche (Pa)
43 c
44 C the following total value are computed by UNIT of earth surface
45 C
46 C d_h_vcol--output-R- Heat flux (W/m2) define as the Enthalpy
47 c change (J/m2) during one time step (dtime) for the whole
48 C atmosphere (air, watter vapour, liquid and solid)
49 C d_qt------output-R- total water mass flux (kg/m2/s) defined as the
50 C total watter (kg/m2) change during one time step (dtime),
51 C d_qw------output-R- same, for the watter vapour only (kg/m2/s)
52 C d_ql------output-R- same, for the liquid watter only (kg/m2/s)
53 C d_qs------output-R- same, for the solid watter only (kg/m2/s)
54 C d_ec------output-R- Cinetic Energy Budget (W/m2) for vertical air column
55 C
56 C other (COMMON...)
57 C RCPD, RCPV, ....
58 C
59 C J.L. Dufresne, July 2002
60 c======================================================================
61
62 use dimens_m
63 use dimphy
64 use SUPHEC_M
65 use yoethf_m
66 IMPLICIT NONE
67 C
68 C
69 c Input variables
70 real airephy(klon)
71 CHARACTER*15 tit
72 INTEGER iprt,idiag, idiag2
73 REAL, intent(in):: dtime
74 REAL t(klon,klev), q(klon,klev), ql(klon,klev), qs(klon,klev)
75 REAL u(klon,klev), v(klon,klev)
76 REAL, intent(in):: paprs(klon,klev+1)
77 c Output variables
78 REAL d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec
79 C
80 C Local variables
81 c
82 REAL h_vcol_tot, h_dair_tot, h_qw_tot, h_ql_tot
83 . , h_qs_tot, qw_tot, ql_tot, qs_tot , ec_tot
84 c h_vcol_tot-- total enthalpy of vertical air column
85 C (air with watter vapour, liquid and solid) (J/m2)
86 c h_dair_tot-- total enthalpy of dry air (J/m2)
87 c h_qw_tot---- total enthalpy of watter vapour (J/m2)
88 c h_ql_tot---- total enthalpy of liquid watter (J/m2)
89 c h_qs_tot---- total enthalpy of solid watter (J/m2)
90 c qw_tot------ total mass of watter vapour (kg/m2)
91 c ql_tot------ total mass of liquid watter (kg/m2)
92 c qs_tot------ total mass of solid watter (kg/m2)
93 c ec_tot------ total cinetic energy (kg/m2)
94 C
95 REAL zairm(klon,klev) ! layer air mass (kg/m2)
96 REAL zqw_col(klon)
97 REAL zql_col(klon)
98 REAL zqs_col(klon)
99 REAL zec_col(klon)
100 REAL zh_dair_col(klon)
101 REAL zh_qw_col(klon), zh_ql_col(klon), zh_qs_col(klon)
102 C
103 REAL d_h_dair, d_h_qw, d_h_ql, d_h_qs
104 C
105 REAL airetot, zcpvap, zcwat, zcice
106 C
107 INTEGER i, k
108 C
109 INTEGER ndiag ! max number of diagnostic in parallel
110 PARAMETER (ndiag=10)
111 integer pas(ndiag)
112 save pas
113 data pas/ndiag*0/
114 C
115 REAL h_vcol_pre(ndiag), h_dair_pre(ndiag), h_qw_pre(ndiag)
116 $ , h_ql_pre(ndiag), h_qs_pre(ndiag), qw_pre(ndiag)
117 $ , ql_pre(ndiag), qs_pre(ndiag) , ec_pre(ndiag)
118 SAVE h_vcol_pre, h_dair_pre, h_qw_pre, h_ql_pre
119 $ , h_qs_pre, qw_pre, ql_pre, qs_pre , ec_pre
120
121 c======================================================================
122 C
123 DO k = 1, klev
124 DO i = 1, klon
125 C layer air mass
126 zairm(i,k) = (paprs(i,k)-paprs(i,k+1))/RG
127 ENDDO
128 END DO
129 C
130 C Reset variables
131 DO i = 1, klon
132 zqw_col(i)=0.
133 zql_col(i)=0.
134 zqs_col(i)=0.
135 zec_col(i) = 0.
136 zh_dair_col(i) = 0.
137 zh_qw_col(i) = 0.
138 zh_ql_col(i) = 0.
139 zh_qs_col(i) = 0.
140 ENDDO
141 C
142 zcpvap=RCPV
143 zcwat=RCW
144 zcice=RCS
145 C
146 C Compute vertical sum for each atmospheric column
147 C ================================================
148 DO k = 1, klev
149 DO i = 1, klon
150 C Watter mass
151 zqw_col(i) = zqw_col(i) + q(i,k)*zairm(i,k)
152 zql_col(i) = zql_col(i) + ql(i,k)*zairm(i,k)
153 zqs_col(i) = zqs_col(i) + qs(i,k)*zairm(i,k)
154 C Cinetic Energy
155 zec_col(i) = zec_col(i)
156 $ +0.5*(u(i,k)**2+v(i,k)**2)*zairm(i,k)
157 C Air enthalpy
158 zh_dair_col(i) = zh_dair_col(i)
159 $ + RCPD*(1.-q(i,k)-ql(i,k)-qs(i,k))*zairm(i,k)*t(i,k)
160 zh_qw_col(i) = zh_qw_col(i)
161 $ + zcpvap*q(i,k)*zairm(i,k)*t(i,k)
162 zh_ql_col(i) = zh_ql_col(i)
163 $ + zcwat*ql(i,k)*zairm(i,k)*t(i,k)
164 $ - RLVTT*ql(i,k)*zairm(i,k)
165 zh_qs_col(i) = zh_qs_col(i)
166 $ + zcice*qs(i,k)*zairm(i,k)*t(i,k)
167 $ - RLSTT*qs(i,k)*zairm(i,k)
168
169 END DO
170 ENDDO
171 C
172 C Mean over the planete surface
173 C =============================
174 qw_tot = 0.
175 ql_tot = 0.
176 qs_tot = 0.
177 ec_tot = 0.
178 h_vcol_tot = 0.
179 h_dair_tot = 0.
180 h_qw_tot = 0.
181 h_ql_tot = 0.
182 h_qs_tot = 0.
183 airetot=0.
184 C
185 do i=1,klon
186 qw_tot = qw_tot + zqw_col(i)*airephy(i)
187 ql_tot = ql_tot + zql_col(i)*airephy(i)
188 qs_tot = qs_tot + zqs_col(i)*airephy(i)
189 ec_tot = ec_tot + zec_col(i)*airephy(i)
190 h_dair_tot = h_dair_tot + zh_dair_col(i)*airephy(i)
191 h_qw_tot = h_qw_tot + zh_qw_col(i)*airephy(i)
192 h_ql_tot = h_ql_tot + zh_ql_col(i)*airephy(i)
193 h_qs_tot = h_qs_tot + zh_qs_col(i)*airephy(i)
194 airetot=airetot+airephy(i)
195 END DO
196 C
197 qw_tot = qw_tot/airetot
198 ql_tot = ql_tot/airetot
199 qs_tot = qs_tot/airetot
200 ec_tot = ec_tot/airetot
201 h_dair_tot = h_dair_tot/airetot
202 h_qw_tot = h_qw_tot/airetot
203 h_ql_tot = h_ql_tot/airetot
204 h_qs_tot = h_qs_tot/airetot
205 C
206 h_vcol_tot = h_dair_tot+h_qw_tot+h_ql_tot+h_qs_tot
207 C
208 C Compute the change of the atmospheric state compare to the one
209 C stored in "idiag2", and convert it in flux. THis computation
210 C is performed IF idiag2 /= 0 and IF it is not the first CALL
211 c for "idiag"
212 C ===================================
213 C
214 IF ( (idiag2.gt.0) .and. (pas(idiag2) .ne. 0) ) THEN
215 d_h_vcol = (h_vcol_tot - h_vcol_pre(idiag2) )/dtime
216 d_h_dair = (h_dair_tot- h_dair_pre(idiag2))/dtime
217 d_h_qw = (h_qw_tot - h_qw_pre(idiag2) )/dtime
218 d_h_ql = (h_ql_tot - h_ql_pre(idiag2) )/dtime
219 d_h_qs = (h_qs_tot - h_qs_pre(idiag2) )/dtime
220 d_qw = (qw_tot - qw_pre(idiag2) )/dtime
221 d_ql = (ql_tot - ql_pre(idiag2) )/dtime
222 d_qs = (qs_tot - qs_pre(idiag2) )/dtime
223 d_ec = (ec_tot - ec_pre(idiag2) )/dtime
224 d_qt = d_qw + d_ql + d_qs
225 ELSE
226 d_h_vcol = 0.
227 d_h_dair = 0.
228 d_h_qw = 0.
229 d_h_ql = 0.
230 d_h_qs = 0.
231 d_qw = 0.
232 d_ql = 0.
233 d_qs = 0.
234 d_ec = 0.
235 d_qt = 0.
236 ENDIF
237 C
238 IF (iprt.ge.2) THEN
239 WRITE(6,9000) tit,pas(idiag),d_qt,d_qw,d_ql,d_qs
240 9000 format('Phys. Watter Mass Budget (kg/m2/s)',A15
241 $ ,1i6,10(1pE14.6))
242 WRITE(6,9001) tit,pas(idiag), d_h_vcol
243 9001 format('Phys. Enthalpy Budget (W/m2) ',A15,1i6,10(F8.2))
244 WRITE(6,9002) tit,pas(idiag), d_ec
245 9002 format('Phys. Cinetic Energy Budget (W/m2) ',A15,1i6,10(F8.2))
246 END IF
247 C
248 C Store the new atmospheric state in "idiag"
249 C
250 pas(idiag)=pas(idiag)+1
251 h_vcol_pre(idiag) = h_vcol_tot
252 h_dair_pre(idiag) = h_dair_tot
253 h_qw_pre(idiag) = h_qw_tot
254 h_ql_pre(idiag) = h_ql_tot
255 h_qs_pre(idiag) = h_qs_tot
256 qw_pre(idiag) = qw_tot
257 ql_pre(idiag) = ql_tot
258 qs_pre(idiag) = qs_tot
259 ec_pre (idiag) = ec_tot
260 C
261 RETURN
262 END

  ViewVC Help
Powered by ViewVC 1.1.21