/[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.10 - (hide annotations) (download)
Fri Jun 23 00:50:21 2006 UTC (18 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58n_post, checkpoint58o_post, checkpoint58k_post, checkpoint58p_post, checkpoint58m_post
Changes since 1.9: +82 -63 lines
only the master thread is allowed to switch On/Off mon_write_stdout
and mon_write_mnc (since it's the only thread that uses those flags)

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

  ViewVC Help
Powered by ViewVC 1.1.22