/[MITgcm]/MITgcm/pkg/land/land_monitor.F
ViewVC logotype

Contents of /MITgcm/pkg/land/land_monitor.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.1 - (show annotations) (download)
Thu Mar 11 14:41:59 2004 UTC (20 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint53d_post, checkpoint54a_pre, checkpoint54e_post, checkpoint54a_post, checkpoint53c_post, checkpoint52l_post, checkpoint54b_post, checkpoint53b_pre, checkpoint54d_post, checkpoint52m_post, checkpoint53a_post, checkpoint54, checkpoint53b_post, checkpoint53, checkpoint53g_post, checkpoint53f_post, checkpoint53d_pre, checkpoint54c_post
new land formulation:
a) use ground enthalpy as prognostic variable to ensure exact
   energy conservation.
b) account for water temperature and for latent heat of freezing
   in all processes (rain, run-off, ground storage)
c) compute surface and ground temperature implicitly.

1 C $Header: $
2 C $Name: $
3
4 #include "LAND_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: LAND_MONITOR
8 C !INTERFACE:
9 SUBROUTINE LAND_MONITOR( land_frc, myTime, myIter, myThid )
10
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | SUBROUTINE LAND_MONITOR
14 C | o Do land global & Hemispheric diagnostic
15 C *==========================================================*
16 C \ev
17
18 C !USES:
19 IMPLICIT NONE
20
21 C === Global variables ===
22 C-- size for MITgcm & Land package :
23 #include "LAND_SIZE.h"
24
25 #include "EEPARAMS.h"
26 #include "PARAMS.h"
27 #include "GRID.h"
28 #include "LAND_PARAMS.h"
29 #include "LAND_VARS.h"
30 #ifdef ALLOW_MONITOR
31 #include "MONITOR.h"
32 #endif
33
34 C !INPUT/OUTPUT PARAMETERS:
35 C == Routine arguments ==
36 C land_frc :: land fraction [0-1]
37 C myTime :: Current time of simulation ( s )
38 C myIter :: Iteration number
39 C myThid :: Number of this instance of INI_FORCING
40 _RS land_frc(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
41 _RL myTime
42 INTEGER myIter
43 INTEGER myThid
44 CEOP
45
46 #ifdef ALLOW_LAND
47 #ifdef ALLOW_MONITOR
48
49 LOGICAL DIFFERENT_MULTIPLE
50 EXTERNAL DIFFERENT_MULTIPLE
51
52 C == Local variables ==
53 C nLatBnd :: Number of latitude bands
54 C msgBuf :: Informational/error meesage buffer
55 C mon_var :: Variable sufix name
56 C mon_sufx :: Latitude band sufix
57 C n, k :: loop counter
58 C yBand :: latitude separation
59 C locDr :: thickness (= 1. here)
60 C theMin :: lat. band minimum value
61 C theMax :: lat. band maximum value
62 C theMean :: lat. band mean value
63 C theVar :: lat. band variance
64 C theVol :: lat. band volume (or area if locDr=1.)
65 C theMeanG :: global mean value
66 C theVarG :: global variance
67 C theVolG :: global volume (or area if locDr=1.)
68 C theEng :: lat. band energy content
69 C theEnergy :: total energy
70 INTEGER nLatBnd
71 PARAMETER ( nLatBnd = 3 )
72 CHARACTER*(MAX_LEN_MBUF) msgBuf
73 CHARACTER*10 mon_var
74 CHARACTER*2 mon_sufx(0:nLatBnd)
75 INTEGER n, k
76 _RS yBand(nLatBnd), locDr(land_nLev)
77 _RL theMin(nLatBnd), theMax(nLatBnd)
78 _RL theMean(nLatBnd), theVar(nLatBnd), theVol(nLatBnd)
79 _RL theMeanG, theVarG, theVolG
80 _RL theEng(nLatBnd), theEnergy
81
82 DATA yBand / 0. , -24. , 24. /
83 DATA mon_sufx / '_G' , '_S' , '_T' , '_N' /
84
85 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
86
87 IF ( DIFFERENT_MULTIPLE(land_monFreq,myTime,myTime-deltaTclock)
88 & .OR. myIter.EQ.nIter0 ) THEN
89
90 DO k=1,land_nLev
91 locDr(k)= 1.
92 ENDDO
93
94 _BEGIN_MASTER(myThid)
95 WRITE(msgBuf,'(A)')
96 &'// ======================================================='
97 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
98 WRITE(msgBuf,'(A)') '// Begin MONITOR Land statistics'
99 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
100 WRITE(msgBuf,'(A)')
101 &'// ======================================================='
102 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
103 _END_MASTER(myThid)
104
105 CALL MON_SET_PREF('land_',myThid)
106 CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)
107
108 C-- Snow thickness :
109 CALL MON_STATS_LATBND_RL(
110 I 1, 1, 1, nLatBnd, yBand,
111 I land_hSnow, land_frc, maskH, rA, yC, locDr,
112 O theMin, theMax, theMean, theVar, theVol,
113 I myThid )
114 theVolG = 0.
115 theMeanG= 0.
116 DO n=1,nLatBnd
117 theVolG = theVolG + theVol(n)
118 theMeanG = theMeanG + theMean(n)*theVol(n)
119 theEng(n)= -land_rhoSnow*land_Lfreez*theMean(n)*theVol(n)
120 ENDDO
121 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
122
123 mon_var='SnwH_ave'
124 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
125 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
126 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
127 CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
128 mon_var='SnwH_max'
129 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
130 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
131 CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
132
133 IF ( myIter.EQ.1+nIter0 ) THEN
134 _BEGIN_MASTER(myThid)
135 WRITE(msgBuf,'(A,1PE16.9,A,0P9F7.2)') '%MON LAND : Area=',
136 & theVolG, ' ; Lat sep=', (yBand(n),n=2,nLatBnd)
137 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
138 WRITE(msgBuf,'(A,1P9E16.9)') '%MON LAND : LatA=',
139 & (theVol(n),n=1,nLatBnd)
140 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
141 _END_MASTER(myThid)
142 ENDIF
143
144 C-- Total Energy :
145 CALL MON_STATS_LATBND_RL(
146 I land_nLev, 1, 0, nLatBnd, yBand,
147 I land_enthalp, land_frc, maskH, rA, yC, land_dzF,
148 O theMin, theMax, theMean, theVar, theVol,
149 I myThid )
150 theEnergy = 0.
151 DO n=1,nLatBnd
152 theEng(n) = theEng(n) + theMean(n)*theVol(n)
153 theEnergy = theEnergy + theEng(n)
154 ENDDO
155 mon_var='TotEnerg'
156 CALL MON_OUT_RL(mon_var,theEnergy, mon_sufx(0), myThid)
157 CALL MON_OUT_RL(mon_var,theEng(1), mon_sufx(1), myThid)
158 CALL MON_OUT_RL(mon_var,theEng(2), mon_sufx(2), myThid)
159 CALL MON_OUT_RL(mon_var,theEng(3), mon_sufx(3), myThid)
160
161 C-- Surface Temp. :
162 CALL MON_STATS_LATBND_RL(
163 I 1, 1, 1, nLatBnd, yBand,
164 I land_skinT, land_frc, maskH, rA, yC, locDr,
165 O theMin, theMax, theMean, theVar, theVol,
166 I myThid )
167 theVolG = 0.
168 theMeanG= 0.
169 DO n=1,nLatBnd
170 theVolG = theVolG + theVol(n)
171 theMeanG = theMeanG + theMean(n)*theVol(n)
172 ENDDO
173 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
174
175 mon_var='Tsrf_ave'
176 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
177 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
178 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
179 CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
180 mon_var='Tsrf_min'
181 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
182 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
183 CALL MON_OUT_RL(mon_var, theMin(3), mon_sufx(3), myThid)
184 mon_var='Tsrf_max'
185 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
186 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
187 CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
188
189 C-- 1rst level (volume-mean) Temp. :
190 CALL MON_STATS_LATBND_RL(
191 I land_nLev, 1, 1, nLatBnd, yBand,
192 I land_groundT, land_frc, maskH, rA, yC, locDr,
193 O theMin, theMax, theMean, theVar, theVol,
194 I myThid )
195 theVolG = 0.
196 theMeanG= 0.
197 DO n=1,nLatBnd
198 theVolG = theVolG + theVol(n)
199 theMeanG = theMeanG + theMean(n)*theVol(n)
200 ENDDO
201 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
202
203 mon_var='Tgr1_ave'
204 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
205 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
206 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
207 CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
208 mon_var='Tgr1_min'
209 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
210 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
211 CALL MON_OUT_RL(mon_var, theMin(3), mon_sufx(3), myThid)
212 mon_var='Tgr1_max'
213 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
214 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
215 CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
216
217 C-- 2nd level (volume-mean) Temp. :
218 CALL MON_STATS_LATBND_RL(
219 I land_nLev, 1, 2, nLatBnd, yBand,
220 I land_groundT, land_frc, maskH, rA, yC, locDr,
221 O theMin, theMax, theMean, theVar, theVol,
222 I myThid )
223 theVolG = 0.
224 theMeanG= 0.
225 DO n=1,nLatBnd
226 theVolG = theVolG + theVol(n)
227 theMeanG = theMeanG + theMean(n)*theVol(n)
228 ENDDO
229 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
230
231 mon_var='Tgr2_ave'
232 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
233 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
234 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
235 CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
236 mon_var='Tgr2_min'
237 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
238 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
239 CALL MON_OUT_RL(mon_var, theMin(3), mon_sufx(3), myThid)
240 mon_var='Tgr2_max'
241 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
242 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
243 CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
244
245 C-- Soil water content (level 1+2):
246 CALL MON_STATS_LATBND_RL(
247 I land_nLev, 1, 0, nLatBnd, yBand,
248 I land_groundW, land_frc, maskH, rA, yC, land_dzF,
249 O theMin, theMax, theMean, theVar, theVol,
250 I myThid )
251 theVolG = 0.
252 theMeanG= 0.
253 DO n=1,nLatBnd
254 theVolG = theVolG + theVol(n)
255 theMeanG = theMeanG + theMean(n)*theVol(n)
256 ENDDO
257 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
258
259 mon_var='grdW_ave'
260 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
261 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
262 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
263 CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
264 mon_var='grdW_min'
265 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
266 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
267 CALL MON_OUT_RL(mon_var, theMin(3), mon_sufx(3), myThid)
268 c mon_var='grdW_max'
269 c CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
270 c CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
271 c CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
272
273 _BEGIN_MASTER(myThid)
274 WRITE(msgBuf,'(A)')
275 &'// ======================================================='
276 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
277 WRITE(msgBuf,'(A)') '// End MONITOR Land statistics'
278 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
279 WRITE(msgBuf,'(A)')
280 &'// ======================================================='
281 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
282 _END_MASTER(myThid)
283
284 ENDIF
285
286 #endif /* ALLOW_MONITOR */
287 #endif /* ALLOW_LAND */
288
289 RETURN
290 END

  ViewVC Help
Powered by ViewVC 1.1.22