source: LMDZ6/trunk/libf/phylmd/diagphy.f90

Last change on this file was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 13.0 KB
Line 
1
2! $Header$
3
4SUBROUTINE diagphy(airephy, tit, iprt, tops, topl, sols, soll, sens, evap, &
5    rain_fall, snow_fall, ts, d_etp_tot, d_qt_tot, d_ec_tot, fs_bound, &
6    fq_bound)
7  ! ======================================================================
8
9  ! Purpose:
10  ! Compute the thermal flux and the watter mass flux at the atmosphere
11  ! boundaries. Print them and also the atmospheric enthalpy change and
12  ! the  atmospheric mass change.
13
14  ! Arguments:
15  ! airephy-------input-R-  grid area
16  ! tit---------input-A15- Comment to be added in PRINT (CHARACTER*15)
17  ! iprt--------input-I-  PRINT level ( <=0 : no PRINT)
18  ! tops(klon)--input-R-  SW rad. at TOA (W/m2), positive up.
19  ! topl(klon)--input-R-  LW rad. at TOA (W/m2), positive down
20  ! sols(klon)--input-R-  Net SW flux above surface (W/m2), positive up
21  ! (i.e. -1 * flux absorbed by the surface)
22  ! soll(klon)--input-R-  Net LW flux above surface (W/m2), positive up
23  ! (i.e. flux emited - flux absorbed by the surface)
24  ! sens(klon)--input-R-  Sensible Flux at surface  (W/m2), positive down
25  ! evap(klon)--input-R-  Evaporation + sublimation watter vapour mass flux
26  ! (kg/m2/s), positive up
27  ! rain_fall(klon)
28  ! --input-R- Liquid  watter mass flux (kg/m2/s), positive down
29  ! snow_fall(klon)
30  ! --input-R- Solid  watter mass flux (kg/m2/s), positive down
31  ! ts(klon)----input-R- Surface temperature (K)
32  ! d_etp_tot---input-R- Heat flux equivalent to atmospheric enthalpy
33  ! change (W/m2)
34  ! d_qt_tot----input-R- Mass flux equivalent to atmospheric watter mass
35  ! change (kg/m2/s)
36  ! d_ec_tot----input-R- Flux equivalent to atmospheric cinetic energy
37  ! change (W/m2)
38
39  ! fs_bound---output-R- Thermal flux at the atmosphere boundaries (W/m2)
40  ! fq_bound---output-R- Watter mass flux at the atmosphere boundaries
41  ! (kg/m2/s)
42
43  ! J.L. Dufresne, July 2002
44  ! Version prise sur
45  ! ~rlmd833/LMDZOR_201102/modipsl/modeles/LMDZ.3.3/libf/phylmd
46  ! le 25 Novembre 2002.
47  ! ======================================================================
48
49USE yoethf_mod_h
50    USE dimphy
51  USE yomcst_mod_h
52IMPLICIT NONE
53
54
55
56  ! Input variables
57  REAL airephy(klon)
58  CHARACTER *15 tit
59  INTEGER iprt
60  REAL tops(klon), topl(klon), sols(klon), soll(klon)
61  REAL sens(klon), evap(klon), rain_fall(klon), snow_fall(klon)
62  REAL ts(klon)
63  REAL d_etp_tot, d_qt_tot, d_ec_tot
64  ! Output variables
65  REAL fs_bound, fq_bound
66
67  ! Local variables
68  REAL stops, stopl, ssols, ssoll
69  REAL ssens, sfront, slat
70  REAL airetot, zcpvap, zcwat, zcice
71  REAL rain_fall_tot, snow_fall_tot, evap_tot
72
73  INTEGER i
74
75  INTEGER pas
76  SAVE pas
77  DATA pas/0/
78  !$OMP THREADPRIVATE(pas)
79
80  pas = pas + 1
81  stops = 0.
82  stopl = 0.
83  ssols = 0.
84  ssoll = 0.
85  ssens = 0.
86  sfront = 0.
87  evap_tot = 0.
88  rain_fall_tot = 0.
89  snow_fall_tot = 0.
90  airetot = 0.
91
92  ! Pour les chaleur specifiques de la vapeur d'eau, de l'eau et de
93  ! la glace, on travaille par difference a la chaleur specifique de l'
94  ! air sec. En effet, comme on travaille a niveau de pression donne,
95  ! toute variation de la masse d'un constituant est totalement
96  ! compense par une variation de masse d'air.
97
98  zcpvap = rcpv - rcpd
99  zcwat = rcw - rcpd
100  zcice = rcs - rcpd
101
102  DO i = 1, klon
103    stops = stops + tops(i)*airephy(i)
104    stopl = stopl + topl(i)*airephy(i)
105    ssols = ssols + sols(i)*airephy(i)
106    ssoll = ssoll + soll(i)*airephy(i)
107    ssens = ssens + sens(i)*airephy(i)
108    sfront = sfront + (evap(i)*zcpvap-rain_fall(i)*zcwat-snow_fall(i)*zcice)* &
109      ts(i)*airephy(i)
110    evap_tot = evap_tot + evap(i)*airephy(i)
111    rain_fall_tot = rain_fall_tot + rain_fall(i)*airephy(i)
112    snow_fall_tot = snow_fall_tot + snow_fall(i)*airephy(i)
113    airetot = airetot + airephy(i)
114  END DO
115  stops = stops/airetot
116  stopl = stopl/airetot
117  ssols = ssols/airetot
118  ssoll = ssoll/airetot
119  ssens = ssens/airetot
120  sfront = sfront/airetot
121  evap_tot = evap_tot/airetot
122  rain_fall_tot = rain_fall_tot/airetot
123  snow_fall_tot = snow_fall_tot/airetot
124
125  slat = rlvtt*rain_fall_tot + rlstt*snow_fall_tot
126  ! Heat flux at atm. boundaries
127  fs_bound = stops - stopl - (ssols+ssoll) + ssens + sfront + slat
128  ! Watter flux at atm. boundaries
129  fq_bound = evap_tot - rain_fall_tot - snow_fall_tot
130
131  IF (iprt>=1) WRITE (6, 6666) tit, pas, fs_bound, d_etp_tot, fq_bound, &
132    d_qt_tot
133
134  IF (iprt>=1) WRITE (6, 6668) tit, pas, d_etp_tot + d_ec_tot - fs_bound, &
135    d_qt_tot - fq_bound
136
137  IF (iprt>=2) WRITE (6, 6667) tit, pas, stops, stopl, ssols, ssoll, ssens, &
138    slat, evap_tot, rain_fall_tot + snow_fall_tot
139
140  RETURN
141
1426666 FORMAT ('Phys. Flux Budget ', A15, 1I6, 2F8.2, 2(1PE13.5))
1436667 FORMAT ('Phys. Boundary Flux ', A15, 1I6, 6F8.2, 2(1PE13.5))
1446668 FORMAT ('Phys. Total Budget ', A15, 1I6, F8.2, 2(1PE13.5))
145
146END SUBROUTINE diagphy
147
148! ======================================================================
149SUBROUTINE diagetpq(airephy, tit, iprt, idiag, idiag2, dtime, t, q, ql, qs, &
150    u, v, paprs, pplay, d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)
151  ! ======================================================================
152
153  ! Purpose:
154  ! Calcul la difference d'enthalpie et de masse d'eau entre 2 appels,
155  ! et calcul le flux de chaleur et le flux d'eau necessaire a ces
156  ! changements. Ces valeurs sont moyennees sur la surface de tout
157  ! le globe et sont exprime en W/2 et kg/s/m2
158  ! Outil pour diagnostiquer la conservation de l'energie
159  ! et de la masse dans la physique. Suppose que les niveau de
160  ! pression entre couche ne varie pas entre 2 appels.
161
162  ! Plusieurs de ces diagnostics peuvent etre fait en parallele: les
163  ! bilans sont sauvegardes dans des tableaux indices. On parlera
164  ! "d'indice de diagnostic"
165
166
167  ! ======================================================================
168  ! Arguments:
169  ! airephy-------input-R-  grid area
170  ! tit-----imput-A15- Comment added in PRINT (CHARACTER*15)
171  ! iprt----input-I-  PRINT level ( <=1 : no PRINT)
172  ! idiag---input-I- indice dans lequel sera range les nouveaux
173  ! bilans d' entalpie et de masse
174  ! idiag2--input-I-les nouveaux bilans d'entalpie et de masse
175  ! sont compare au bilan de d'enthalpie de masse de
176  ! l'indice numero idiag2
177  ! Cas parriculier : si idiag2=0, pas de comparaison, on
178  ! sort directement les bilans d'enthalpie et de masse
179  ! dtime----input-R- time step (s)
180  ! t--------input-R- temperature (K)
181  ! q--------input-R- vapeur d'eau (kg/kg)
182  ! ql-------input-R- liquid watter (kg/kg)
183  ! qs-------input-R- solid watter (kg/kg)
184  ! u--------input-R- vitesse u
185  ! v--------input-R- vitesse v
186  ! paprs----input-R- pression a intercouche (Pa)
187  ! pplay----input-R- pression au milieu de couche (Pa)
188
189  ! the following total value are computed by UNIT of earth surface
190
191  ! d_h_vcol--output-R- Heat flux (W/m2) define as the Enthalpy
192  ! change (J/m2) during one time step (dtime) for the whole
193  ! atmosphere (air, watter vapour, liquid and solid)
194  ! d_qt------output-R- total water mass flux (kg/m2/s) defined as the
195  ! total watter (kg/m2) change during one time step (dtime),
196  ! d_qw------output-R- same, for the watter vapour only (kg/m2/s)
197  ! d_ql------output-R- same, for the liquid watter only (kg/m2/s)
198  ! d_qs------output-R- same, for the solid watter only (kg/m2/s)
199  ! d_ec------output-R- Cinetic Energy Budget (W/m2) for vertical air column
200
201  ! other (COMMON...)
202  ! RCPD, RCPV, ....
203
204  ! J.L. Dufresne, July 2002
205  ! ======================================================================
206
207USE yoethf_mod_h
208    USE dimphy
209  USE yomcst_mod_h
210IMPLICIT NONE
211
212
213
214  ! Input variables
215  REAL airephy(klon)
216  CHARACTER *15 tit
217  INTEGER iprt, idiag, idiag2
218  REAL dtime
219  REAL t(klon, klev), q(klon, klev), ql(klon, klev), qs(klon, klev)
220  REAL u(klon, klev), v(klon, klev)
221  REAL paprs(klon, klev+1), pplay(klon, klev)
222  ! Output variables
223  REAL d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec
224
225  ! Local variables
226
227  REAL h_vcol_tot, h_dair_tot, h_qw_tot, h_ql_tot, h_qs_tot, qw_tot, ql_tot, &
228    qs_tot, ec_tot
229  ! h_vcol_tot--  total enthalpy of vertical air column
230  ! (air with watter vapour, liquid and solid) (J/m2)
231  ! h_dair_tot-- total enthalpy of dry air (J/m2)
232  ! h_qw_tot----  total enthalpy of watter vapour (J/m2)
233  ! h_ql_tot----  total enthalpy of liquid watter (J/m2)
234  ! h_qs_tot----  total enthalpy of solid watter  (J/m2)
235  ! qw_tot------  total mass of watter vapour (kg/m2)
236  ! ql_tot------  total mass of liquid watter (kg/m2)
237  ! qs_tot------  total mass of solid watter (kg/m2)
238  ! ec_tot------  total cinetic energy (kg/m2)
239
240  REAL zairm(klon, klev) ! layer air mass (kg/m2)
241  REAL zqw_col(klon)
242  REAL zql_col(klon)
243  REAL zqs_col(klon)
244  REAL zec_col(klon)
245  REAL zh_dair_col(klon)
246  REAL zh_qw_col(klon), zh_ql_col(klon), zh_qs_col(klon)
247
248  REAL d_h_dair, d_h_qw, d_h_ql, d_h_qs
249
250  REAL airetot, zcpvap, zcwat, zcice
251
252  INTEGER i, k
253
254  INTEGER ndiag ! max number of diagnostic in parallel
255  PARAMETER (ndiag=10)
256  INTEGER pas(ndiag)
257  SAVE pas
258  DATA pas/ndiag*0/
259  !$OMP THREADPRIVATE(pas)
260
261  REAL h_vcol_pre(ndiag), h_dair_pre(ndiag), h_qw_pre(ndiag), &
262    h_ql_pre(ndiag), h_qs_pre(ndiag), qw_pre(ndiag), ql_pre(ndiag), &
263    qs_pre(ndiag), ec_pre(ndiag)
264  SAVE h_vcol_pre, h_dair_pre, h_qw_pre, h_ql_pre, h_qs_pre, qw_pre, ql_pre, &
265    qs_pre, ec_pre
266  !$OMP THREADPRIVATE(h_vcol_pre, h_dair_pre, h_qw_pre, h_ql_pre)
267  !$OMP THREADPRIVATE(h_qs_pre, qw_pre, ql_pre, qs_pre , ec_pre)
268  ! ======================================================================
269
270  DO k = 1, klev
271    DO i = 1, klon
272      ! layer air mass
273      zairm(i, k) = (paprs(i,k)-paprs(i,k+1))/rg
274    END DO
275  END DO
276
277  ! Reset variables
278  DO i = 1, klon
279    zqw_col(i) = 0.
280    zql_col(i) = 0.
281    zqs_col(i) = 0.
282    zec_col(i) = 0.
283    zh_dair_col(i) = 0.
284    zh_qw_col(i) = 0.
285    zh_ql_col(i) = 0.
286    zh_qs_col(i) = 0.
287  END DO
288
289  zcpvap = rcpv
290  zcwat = rcw
291  zcice = rcs
292
293  ! Compute vertical sum for each atmospheric column
294  ! ================================================
295  DO k = 1, klev
296    DO i = 1, klon
297      ! Watter mass
298      zqw_col(i) = zqw_col(i) + q(i, k)*zairm(i, k)
299      zql_col(i) = zql_col(i) + ql(i, k)*zairm(i, k)
300      zqs_col(i) = zqs_col(i) + qs(i, k)*zairm(i, k)
301      ! Cinetic Energy
302      zec_col(i) = zec_col(i) + 0.5*(u(i,k)**2+v(i,k)**2)*zairm(i, k)
303      ! Air enthalpy
304      zh_dair_col(i) = zh_dair_col(i) + rcpd*(1.-q(i,k)-ql(i,k)-qs(i,k))* &
305        zairm(i, k)*t(i, k)
306      zh_qw_col(i) = zh_qw_col(i) + zcpvap*q(i, k)*zairm(i, k)*t(i, k)
307      zh_ql_col(i) = zh_ql_col(i) + zcwat*ql(i, k)*zairm(i, k)*t(i, k) - &
308        rlvtt*ql(i, k)*zairm(i, k)
309      zh_qs_col(i) = zh_qs_col(i) + zcice*qs(i, k)*zairm(i, k)*t(i, k) - &
310        rlstt*qs(i, k)*zairm(i, k)
311
312    END DO
313  END DO
314
315  ! Mean over the planete surface
316  ! =============================
317  qw_tot = 0.
318  ql_tot = 0.
319  qs_tot = 0.
320  ec_tot = 0.
321  h_vcol_tot = 0.
322  h_dair_tot = 0.
323  h_qw_tot = 0.
324  h_ql_tot = 0.
325  h_qs_tot = 0.
326  airetot = 0.
327
328  DO i = 1, klon
329    qw_tot = qw_tot + zqw_col(i)*airephy(i)
330    ql_tot = ql_tot + zql_col(i)*airephy(i)
331    qs_tot = qs_tot + zqs_col(i)*airephy(i)
332    ec_tot = ec_tot + zec_col(i)*airephy(i)
333    h_dair_tot = h_dair_tot + zh_dair_col(i)*airephy(i)
334    h_qw_tot = h_qw_tot + zh_qw_col(i)*airephy(i)
335    h_ql_tot = h_ql_tot + zh_ql_col(i)*airephy(i)
336    h_qs_tot = h_qs_tot + zh_qs_col(i)*airephy(i)
337    airetot = airetot + airephy(i)
338  END DO
339
340  qw_tot = qw_tot/airetot
341  ql_tot = ql_tot/airetot
342  qs_tot = qs_tot/airetot
343  ec_tot = ec_tot/airetot
344  h_dair_tot = h_dair_tot/airetot
345  h_qw_tot = h_qw_tot/airetot
346  h_ql_tot = h_ql_tot/airetot
347  h_qs_tot = h_qs_tot/airetot
348
349  h_vcol_tot = h_dair_tot + h_qw_tot + h_ql_tot + h_qs_tot
350
351  ! Compute the change of the atmospheric state compare to the one
352  ! stored in "idiag2", and convert it in flux. THis computation
353  ! is performed IF idiag2 /= 0 and IF it is not the first CALL
354  ! for "idiag"
355  ! ===================================
356
357  IF ((idiag2>0) .AND. (pas(idiag2)/=0)) THEN
358    d_h_vcol = (h_vcol_tot-h_vcol_pre(idiag2))/dtime
359    d_h_dair = (h_dair_tot-h_dair_pre(idiag2))/dtime
360    d_h_qw = (h_qw_tot-h_qw_pre(idiag2))/dtime
361    d_h_ql = (h_ql_tot-h_ql_pre(idiag2))/dtime
362    d_h_qs = (h_qs_tot-h_qs_pre(idiag2))/dtime
363    d_qw = (qw_tot-qw_pre(idiag2))/dtime
364    d_ql = (ql_tot-ql_pre(idiag2))/dtime
365    d_qs = (qs_tot-qs_pre(idiag2))/dtime
366    d_ec = (ec_tot-ec_pre(idiag2))/dtime
367    d_qt = d_qw + d_ql + d_qs
368  ELSE
369    d_h_vcol = 0.
370    d_h_dair = 0.
371    d_h_qw = 0.
372    d_h_ql = 0.
373    d_h_qs = 0.
374    d_qw = 0.
375    d_ql = 0.
376    d_qs = 0.
377    d_ec = 0.
378    d_qt = 0.
379  END IF
380
381  IF (iprt>=2) THEN
382    WRITE (6, 9000) tit, pas(idiag), d_qt, d_qw, d_ql, d_qs
3839000 FORMAT ('Phys. Watter Mass Budget (kg/m2/s)', A15, 1I6, 10(1PE14.6))
384    WRITE (6, 9001) tit, pas(idiag), d_h_vcol
3859001 FORMAT ('Phys. Enthalpy Budget (W/m2) ', A15, 1I6, 10(F8.2))
386    WRITE (6, 9002) tit, pas(idiag), d_ec
3879002 FORMAT ('Phys. Cinetic Energy Budget (W/m2) ', A15, 1I6, 10(F8.2))
388  END IF
389
390  ! Store the new atmospheric state in "idiag"
391
392  pas(idiag) = pas(idiag) + 1
393  h_vcol_pre(idiag) = h_vcol_tot
394  h_dair_pre(idiag) = h_dair_tot
395  h_qw_pre(idiag) = h_qw_tot
396  h_ql_pre(idiag) = h_ql_tot
397  h_qs_pre(idiag) = h_qs_tot
398  qw_pre(idiag) = qw_tot
399  ql_pre(idiag) = ql_tot
400  qs_pre(idiag) = qs_tot
401  ec_pre(idiag) = ec_tot
402
403  RETURN
404END SUBROUTINE diagetpq
Note: See TracBrowser for help on using the repository browser.