/[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.11 - (hide annotations) (download)
Tue Oct 17 18:22:33 2006 UTC (17 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint60, checkpoint61, checkpoint58r_post, checkpoint58x_post, checkpoint58t_post, checkpoint58q_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q
Changes since 1.10: +8 -16 lines
use function "MASTER_CPU_IO" to hide EESUPPORT.h from TAF.

1 jmc 1.11 C $Header: /u/gcmpack/MITgcm/pkg/land/land_monitor.F,v 1.10 2006/06/23 00:50:21 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     C msgBuf :: Informational/error meesage buffer
49     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     _RL theMeanG, theVarG, theVolG
74     _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     DO k=1,land_nLev
85     locDr(k)= 1.
86     ENDDO
87    
88 jmc 1.11 IF ( MASTER_CPU_IO(myThid) ) THEN
89 jmc 1.10 C-- only the master thread is allowed to switch On/Off mon_write_stdout
90     C & mon_write_mnc (since it's the only thread that uses those flags):
91    
92     IF ( land_mon_stdio ) THEN
93     mon_write_stdout = .TRUE.
94     ELSE
95     mon_write_stdout = .FALSE.
96     ENDIF
97     mon_write_mnc = .FALSE.
98     #ifdef ALLOW_MNC
99     IF ( useMNC .AND. land_mon_mnc ) THEN
100     DO k = 1,MAX_LEN_MBUF
101     mon_fname(k:k) = ' '
102     ENDDO
103     mon_fname(1:12) = 'monitor_land'
104     CALL MNC_CW_APPEND_VNAME(
105     & 'T', '-_-_--__-__t', 0,0, myThid)
106     CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
107     CALL MNC_CW_I_W_S(
108     & 'I',mon_fname,1,1,'T', myIter, myThid)
109     CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
110     mon_write_mnc = .TRUE.
111     ENDIF
112     #endif /* ALLOW_MNC */
113    
114     IF ( mon_write_stdout ) THEN
115     WRITE(msgBuf,'(2A)') '// ===========================',
116     & '============================'
117     CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
118     WRITE(msgBuf,'(A)') '// Begin MONITOR Land statistics'
119     CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
120     WRITE(msgBuf,'(2A)') '// ===========================',
121     & '============================'
122     CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
123     ENDIF
124    
125 jmc 1.11 C-- endif master cpu io
126 edhill 1.3 ENDIF
127 jmc 1.1
128     CALL MON_SET_PREF('land_',myThid)
129     CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)
130 jmc 1.10
131 jmc 1.1 C-- Snow thickness :
132     CALL MON_STATS_LATBND_RL(
133     I 1, 1, 1, nLatBnd, yBand,
134     I land_hSnow, land_frc, maskH, rA, yC, locDr,
135     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-- Total Energy :
168     CALL MON_STATS_LATBND_RL(
169     I land_nLev, 1, 0, nLatBnd, yBand,
170     I land_enthalp, land_frc, maskH, rA, yC, land_dzF,
171     O theMin, theMax, theMean, theVar, theVol,
172     I myThid )
173     theEnergy = 0.
174     DO n=1,nLatBnd
175 jmc 1.10 theEng(n) = theEng(n) + theMean(n)*theVol(n)
176 jmc 1.1 theEnergy = theEnergy + theEng(n)
177     ENDDO
178     mon_var='TotEnerg'
179     CALL MON_OUT_RL(mon_var,theEnergy, mon_sufx(0), myThid)
180     CALL MON_OUT_RL(mon_var,theEng(1), mon_sufx(1), myThid)
181     CALL MON_OUT_RL(mon_var,theEng(2), mon_sufx(2), myThid)
182     CALL MON_OUT_RL(mon_var,theEng(3), mon_sufx(3), myThid)
183    
184     C-- Surface Temp. :
185     CALL MON_STATS_LATBND_RL(
186     I 1, 1, 1, nLatBnd, yBand,
187     I land_skinT, land_frc, maskH, rA, yC, locDr,
188     O theMin, theMax, theMean, theVar, theVol,
189     I myThid )
190     theVolG = 0.
191     theMeanG= 0.
192     DO n=1,nLatBnd
193     theVolG = theVolG + theVol(n)
194     theMeanG = theMeanG + theMean(n)*theVol(n)
195     ENDDO
196     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
197    
198     mon_var='Tsrf_ave'
199     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
200     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
201     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
202     CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
203     mon_var='Tsrf_min'
204     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
205     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
206     CALL MON_OUT_RL(mon_var, theMin(3), mon_sufx(3), myThid)
207     mon_var='Tsrf_max'
208     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
209     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
210     CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
211    
212     C-- 1rst level (volume-mean) Temp. :
213     CALL MON_STATS_LATBND_RL(
214     I land_nLev, 1, 1, nLatBnd, yBand,
215     I land_groundT, land_frc, maskH, rA, yC, locDr,
216     O theMin, theMax, theMean, theVar, theVol,
217     I myThid )
218     theVolG = 0.
219     theMeanG= 0.
220     DO n=1,nLatBnd
221     theVolG = theVolG + theVol(n)
222     theMeanG = theMeanG + theMean(n)*theVol(n)
223     ENDDO
224     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
225    
226     mon_var='Tgr1_ave'
227     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
228     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
229     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
230     CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
231     mon_var='Tgr1_min'
232     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
233     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
234     CALL MON_OUT_RL(mon_var, theMin(3), mon_sufx(3), myThid)
235     mon_var='Tgr1_max'
236     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
237     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
238     CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
239 jmc 1.10
240 jmc 1.1 C-- 2nd level (volume-mean) Temp. :
241     CALL MON_STATS_LATBND_RL(
242     I land_nLev, 1, 2, nLatBnd, yBand,
243     I land_groundT, land_frc, maskH, rA, yC, locDr,
244     O theMin, theMax, theMean, theVar, theVol,
245     I myThid )
246     theVolG = 0.
247     theMeanG= 0.
248     DO n=1,nLatBnd
249     theVolG = theVolG + theVol(n)
250     theMeanG = theMeanG + theMean(n)*theVol(n)
251     ENDDO
252     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
253    
254     mon_var='Tgr2_ave'
255     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
256     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
257     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
258     CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
259     mon_var='Tgr2_min'
260     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
261     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
262     CALL MON_OUT_RL(mon_var, theMin(3), mon_sufx(3), myThid)
263     mon_var='Tgr2_max'
264     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
265     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
266     CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
267 jmc 1.10
268 jmc 1.1 C-- Soil water content (level 1+2):
269     CALL MON_STATS_LATBND_RL(
270     I land_nLev, 1, 0, nLatBnd, yBand,
271     I land_groundW, land_frc, maskH, rA, yC, land_dzF,
272     O theMin, theMax, theMean, theVar, theVol,
273     I myThid )
274     theVolG = 0.
275     theMeanG= 0.
276     DO n=1,nLatBnd
277     theVolG = theVolG + theVol(n)
278     theMeanG = theMeanG + theMean(n)*theVol(n)
279     ENDDO
280     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
281    
282     mon_var='grdW_ave'
283     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
284     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
285     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
286     CALL MON_OUT_RL(mon_var,theMean(3), mon_sufx(3), myThid)
287     mon_var='grdW_min'
288     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
289     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
290     CALL MON_OUT_RL(mon_var, theMin(3), mon_sufx(3), myThid)
291     c mon_var='grdW_max'
292     c CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
293     c CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
294     c CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
295 jmc 1.10
296 jmc 1.11 IF ( MASTER_CPU_IO(myThid) ) THEN
297 jmc 1.10 C-- only the master thread is allowed to switch On/Off mon_write_stdout
298     C & mon_write_mnc (since it's the only thread that uses those flags):
299    
300     IF (mon_write_stdout) THEN
301     WRITE(msgBuf,'(2A)') '// ===========================',
302     & '============================'
303     CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
304     WRITE(msgBuf,'(A)') '// End MONITOR Land statistics'
305     CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
306     WRITE(msgBuf,'(2A)') '// ===========================',
307     & '============================'
308     CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
309     ENDIF
310    
311     mon_write_stdout = .FALSE.
312     mon_write_mnc = .FALSE.
313    
314 jmc 1.11 C-- endif master cpu io
315 edhill 1.3 ENDIF
316 jmc 1.2
317 jmc 1.10 C endif different multiple
318 jmc 1.1 ENDIF
319    
320     #endif /* ALLOW_MONITOR */
321     #endif /* ALLOW_LAND */
322 jmc 1.10
323 jmc 1.1 RETURN
324     END

  ViewVC Help
Powered by ViewVC 1.1.22