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

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

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


Revision 1.13 - (hide annotations) (download)
Mon Dec 21 00:15:57 2009 UTC (14 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a
Changes since 1.12: +9 -9 lines
- use new S/R version for statistics with mask & volume;
- use interior masks (instead of maskH, <- to be remove).

1 jmc 1.13 C $Header: /u/gcmpack/MITgcm/pkg/land/land_monitor.F,v 1.12 2009/09/02 21:42:43 jmc Exp $
2 jmc 1.1 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 edhill 1.3 C !DESCRIPTION:
12     C Do land global and Hemispheric diagnostic
13 jmc 1.10
14 jmc 1.1 C !USES:
15     IMPLICIT NONE
16     #include "LAND_SIZE.h"
17     #include "EEPARAMS.h"
18     #include "PARAMS.h"
19     #include "GRID.h"
20     #include "LAND_PARAMS.h"
21     #include "LAND_VARS.h"
22     #ifdef ALLOW_MONITOR
23 jmc 1.10 # include "MONITOR.h"
24 jmc 1.1 #endif
25    
26     C !INPUT/OUTPUT PARAMETERS:
27     C land_frc :: land fraction [0-1]
28     C myTime :: Current time of simulation ( s )
29     C myIter :: Iteration number
30     C myThid :: Number of this instance of INI_FORCING
31     _RS land_frc(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
32     _RL myTime
33     INTEGER myIter
34     INTEGER myThid
35     CEOP
36    
37     #ifdef ALLOW_LAND
38     #ifdef ALLOW_MONITOR
39    
40 jmc 1.11 C === Functions ====
41 jmc 1.9 LOGICAL DIFFERENT_MULTIPLE
42     EXTERNAL DIFFERENT_MULTIPLE
43 jmc 1.11 LOGICAL MASTER_CPU_IO
44     EXTERNAL MASTER_CPU_IO
45 jmc 1.1
46     C == Local variables ==
47     C nLatBnd :: Number of latitude bands
48 jmc 1.13 C msgBuf :: Informational/error message buffer
49 jmc 1.1 C mon_var :: Variable sufix name
50     C mon_sufx :: Latitude band sufix
51     C n, k :: loop counter
52     C yBand :: latitude separation
53 jmc 1.10 C locDr :: thickness (= 1. here)
54 jmc 1.1 C theMin :: lat. band minimum value
55     C theMax :: lat. band maximum value
56     C theMean :: lat. band mean value
57     C theVar :: lat. band variance
58     C theVol :: lat. band volume (or area if locDr=1.)
59     C theMeanG :: global mean value
60 jmc 1.10 C theVarG :: global variance
61 jmc 1.1 C theVolG :: global volume (or area if locDr=1.)
62     C theEng :: lat. band energy content
63     C theEnergy :: total energy
64     INTEGER nLatBnd
65     PARAMETER ( nLatBnd = 3 )
66     CHARACTER*(MAX_LEN_MBUF) msgBuf
67     CHARACTER*10 mon_var
68     CHARACTER*2 mon_sufx(0:nLatBnd)
69     INTEGER n, k
70     _RS yBand(nLatBnd), locDr(land_nLev)
71     _RL theMin(nLatBnd), theMax(nLatBnd)
72     _RL theMean(nLatBnd), theVar(nLatBnd), theVol(nLatBnd)
73 jmc 1.13 _RL theMeanG, theVolG
74 jmc 1.1 _RL theEng(nLatBnd), theEnergy
75    
76     DATA yBand / 0. , -24. , 24. /
77     DATA mon_sufx / '_G' , '_S' , '_T' , '_N' /
78    
79     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
80    
81 jmc 1.10 IF ( DIFFERENT_MULTIPLE(land_monFreq,myTime,deltaTClock)
82 jmc 1.1 & .OR. myIter.EQ.nIter0 ) THEN
83    
84 jmc 1.11 IF ( MASTER_CPU_IO(myThid) ) THEN
85 jmc 1.10 C-- only the master thread is allowed to switch On/Off mon_write_stdout
86     C & mon_write_mnc (since it's the only thread that uses those flags):
87    
88     IF ( land_mon_stdio ) THEN
89     mon_write_stdout = .TRUE.
90     ELSE
91     mon_write_stdout = .FALSE.
92     ENDIF
93     mon_write_mnc = .FALSE.
94     #ifdef ALLOW_MNC
95     IF ( useMNC .AND. land_mon_mnc ) THEN
96     DO k = 1,MAX_LEN_MBUF
97     mon_fname(k:k) = ' '
98     ENDDO
99     mon_fname(1:12) = 'monitor_land'
100     CALL MNC_CW_APPEND_VNAME(
101     & 'T', '-_-_--__-__t', 0,0, myThid)
102     CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
103     CALL MNC_CW_I_W_S(
104     & 'I',mon_fname,1,1,'T', myIter, myThid)
105     CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
106     mon_write_mnc = .TRUE.
107     ENDIF
108     #endif /* ALLOW_MNC */
109    
110     IF ( mon_write_stdout ) THEN
111     WRITE(msgBuf,'(2A)') '// ===========================',
112     & '============================'
113     CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
114     WRITE(msgBuf,'(A)') '// Begin MONITOR Land statistics'
115     CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
116     WRITE(msgBuf,'(2A)') '// ===========================',
117     & '============================'
118     CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
119     ENDIF
120    
121 jmc 1.11 C-- endif master cpu io
122 edhill 1.3 ENDIF
123 jmc 1.1
124     CALL MON_SET_PREF('land_',myThid)
125     CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)
126 jmc 1.10
127 jmc 1.12 DO k=1,land_nLev
128     locDr(k)= 1.
129     ENDDO
130    
131 jmc 1.1 C-- Snow thickness :
132     CALL MON_STATS_LATBND_RL(
133     I 1, 1, 1, nLatBnd, yBand,
134 jmc 1.13 I land_hSnow, land_frc, maskInC, rA, yC, locDr,
135 jmc 1.1 O theMin, theMax, theMean, theVar, theVol,
136     I myThid )
137     theVolG = 0.
138     theMeanG= 0.
139     DO n=1,nLatBnd
140     theVolG = theVolG + theVol(n)
141     theMeanG = theMeanG + theMean(n)*theVol(n)
142     theEng(n)= -land_rhoSnow*land_Lfreez*theMean(n)*theVol(n)
143     ENDDO
144     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
145    
146     mon_var='SnwH_ave'
147     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
148     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
149     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
150     CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
151     mon_var='SnwH_max'
152     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
153     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
154     CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
155    
156     IF ( myIter.EQ.1+nIter0 ) THEN
157     _BEGIN_MASTER(myThid)
158     WRITE(msgBuf,'(A,1PE16.9,A,0P9F7.2)') '%MON LAND : Area=',
159     & theVolG, ' ; Lat sep=', (yBand(n),n=2,nLatBnd)
160     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
161 jmc 1.10 WRITE(msgBuf,'(A,1P9E16.9)') '%MON LAND : LatA=',
162 jmc 1.1 & (theVol(n),n=1,nLatBnd)
163     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
164     _END_MASTER(myThid)
165     ENDIF
166    
167     C-- Surface Temp. :
168     CALL MON_STATS_LATBND_RL(
169     I 1, 1, 1, nLatBnd, yBand,
170 jmc 1.13 I land_skinT, land_frc, maskInC, rA, yC, locDr,
171 jmc 1.1 O theMin, theMax, theMean, theVar, theVol,
172     I myThid )
173     theVolG = 0.
174     theMeanG= 0.
175     DO n=1,nLatBnd
176     theVolG = theVolG + theVol(n)
177     theMeanG = theMeanG + theMean(n)*theVol(n)
178     ENDDO
179     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
180    
181     mon_var='Tsrf_ave'
182     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
183     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
184     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
185     CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
186     mon_var='Tsrf_min'
187     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
188     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
189     CALL MON_OUT_RL(mon_var, theMin(3), mon_sufx(3), myThid)
190     mon_var='Tsrf_max'
191     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
192     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
193     CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
194    
195     C-- 1rst level (volume-mean) Temp. :
196     CALL MON_STATS_LATBND_RL(
197     I land_nLev, 1, 1, nLatBnd, yBand,
198 jmc 1.13 I land_groundT, land_frc, maskInC, rA, yC, locDr,
199 jmc 1.1 O theMin, theMax, theMean, theVar, theVol,
200     I myThid )
201     theVolG = 0.
202     theMeanG= 0.
203     DO n=1,nLatBnd
204     theVolG = theVolG + theVol(n)
205     theMeanG = theMeanG + theMean(n)*theVol(n)
206     ENDDO
207     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
208    
209     mon_var='Tgr1_ave'
210     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
211     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
212     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
213     CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
214     mon_var='Tgr1_min'
215     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
216     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
217     CALL MON_OUT_RL(mon_var, theMin(3), mon_sufx(3), myThid)
218     mon_var='Tgr1_max'
219     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
220     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
221     CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
222 jmc 1.10
223 jmc 1.1 C-- 2nd level (volume-mean) Temp. :
224     CALL MON_STATS_LATBND_RL(
225     I land_nLev, 1, 2, nLatBnd, yBand,
226 jmc 1.13 I land_groundT, land_frc, maskInC, rA, yC, locDr,
227 jmc 1.1 O theMin, theMax, theMean, theVar, theVol,
228     I myThid )
229     theVolG = 0.
230     theMeanG= 0.
231     DO n=1,nLatBnd
232     theVolG = theVolG + theVol(n)
233     theMeanG = theMeanG + theMean(n)*theVol(n)
234     ENDDO
235     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
236    
237     mon_var='Tgr2_ave'
238     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
239     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
240     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
241     CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
242     mon_var='Tgr2_min'
243     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
244     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
245     CALL MON_OUT_RL(mon_var, theMin(3), mon_sufx(3), myThid)
246     mon_var='Tgr2_max'
247     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
248     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
249     CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
250 jmc 1.10
251 jmc 1.12 C-- Total Energy :
252     DO k=1,land_nLev
253     locDr(k)= land_dzF(k)
254     ENDDO
255     CALL MON_STATS_LATBND_RL(
256     I land_nLev, 1, 0, nLatBnd, yBand,
257 jmc 1.13 I land_enthalp, land_frc, maskInC, rA, yC, locDr,
258 jmc 1.12 O theMin, theMax, theMean, theVar, theVol,
259     I myThid )
260     theEnergy = 0.
261     DO n=1,nLatBnd
262     theEng(n) = theEng(n) + theMean(n)*theVol(n)
263     theEnergy = theEnergy + theEng(n)
264     ENDDO
265     mon_var='TotEnerg'
266     CALL MON_OUT_RL(mon_var,theEnergy, mon_sufx(0), myThid)
267     CALL MON_OUT_RL(mon_var,theEng(1), mon_sufx(1), myThid)
268     CALL MON_OUT_RL(mon_var,theEng(2), mon_sufx(2), myThid)
269     CALL MON_OUT_RL(mon_var,theEng(3), mon_sufx(3), myThid)
270    
271 jmc 1.1 C-- Soil water content (level 1+2):
272     CALL MON_STATS_LATBND_RL(
273     I land_nLev, 1, 0, nLatBnd, yBand,
274 jmc 1.13 I land_groundW, land_frc, maskInC, rA, yC, locDr,
275 jmc 1.1 O theMin, theMax, theMean, theVar, theVol,
276     I myThid )
277     theVolG = 0.
278     theMeanG= 0.
279     DO n=1,nLatBnd
280     theVolG = theVolG + theVol(n)
281     theMeanG = theMeanG + theMean(n)*theVol(n)
282     ENDDO
283     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
284    
285     mon_var='grdW_ave'
286     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
287     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
288     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
289     CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
290     mon_var='grdW_min'
291     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
292     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
293     CALL MON_OUT_RL(mon_var, theMin(3), mon_sufx(3), myThid)
294     c mon_var='grdW_max'
295     c CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
296     c CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
297     c CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
298 jmc 1.10
299 jmc 1.11 IF ( MASTER_CPU_IO(myThid) ) THEN
300 jmc 1.10 C-- only the master thread is allowed to switch On/Off mon_write_stdout
301     C & mon_write_mnc (since it's the only thread that uses those flags):
302    
303     IF (mon_write_stdout) THEN
304     WRITE(msgBuf,'(2A)') '// ===========================',
305     & '============================'
306     CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
307     WRITE(msgBuf,'(A)') '// End MONITOR Land statistics'
308     CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
309     WRITE(msgBuf,'(2A)') '// ===========================',
310     & '============================'
311     CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
312     ENDIF
313    
314     mon_write_stdout = .FALSE.
315     mon_write_mnc = .FALSE.
316    
317 jmc 1.11 C-- endif master cpu io
318 edhill 1.3 ENDIF
319 jmc 1.2
320 jmc 1.10 C endif different multiple
321 jmc 1.1 ENDIF
322    
323     #endif /* ALLOW_MONITOR */
324     #endif /* ALLOW_LAND */
325 jmc 1.10
326 jmc 1.1 RETURN
327     END

  ViewVC Help
Powered by ViewVC 1.1.22