/[MITgcm]/MITgcm/pkg/thsice/thsice_monitor.F
ViewVC logotype

Contents of /MITgcm/pkg/thsice/thsice_monitor.F

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


Revision 1.12 - (show annotations) (download)
Fri Jun 23 00:50:22 2006 UTC (17 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58n_post, checkpoint58o_post, checkpoint58k_post, checkpoint58p_post, checkpoint58m_post
Changes since 1.11: +75 -49 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 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_monitor.F,v 1.11 2005/11/04 01:34:35 jmc Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: THSICE_MONITOR
8 C !INTERFACE
9 SUBROUTINE THSICE_MONITOR( myTime, myIter, myThid )
10
11 C !DESCRIPTION:
12 C Do ICE global and Hemispheric monitor output
13
14 C !USES:
15 IMPLICIT NONE
16
17 C === Global variables ===
18 #include "SIZE.h"
19 #include "EEPARAMS.h"
20 #include "EESUPPORT.h"
21 #include "PARAMS.h"
22 #include "GRID.h"
23 #include "THSICE_PARAMS.h"
24 #include "THSICE_VARS.h"
25 #ifdef ALLOW_MONITOR
26 # include "MONITOR.h"
27 #endif
28
29 C !INPUT/OUTPUT PARAMETERS:
30 C == Routine arguments ==
31 C myTime - Current time of simulation ( s )
32 C myIter - Iteration number
33 C myThid - Number of this instance of INI_FORCING
34 _RL myTime
35 INTEGER myIter
36 INTEGER myThid
37 CEOP
38
39 #ifdef ALLOW_THSICE
40 #ifdef ALLOW_MONITOR
41
42 C == Local variables ==
43 LOGICAL DIFFERENT_MULTIPLE
44 EXTERNAL DIFFERENT_MULTIPLE
45 CHARACTER*(MAX_LEN_MBUF) msgBuf
46 CHARACTER*10 mon_var
47 CHARACTER*2 mon_sufx(0:2)
48 _RS yBand(2), locDr(1)
49 _RL theMin(2), theMax(2)
50 _RL theMean(2), theVar(2), theVol(2)
51 _RL theMeanG, theVolG
52 _RL theMean1, theMean2, theEnergy
53 _RL theMin0, theMax0, theSD, theDel2
54 #ifdef ALLOW_MNC
55 INTEGER k
56 #endif
57
58 DATA yBand / 0. , 0. /
59 DATA locDr / 1. /
60 DATA mon_sufx / '_G' , '_S' , '_N' /
61
62 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
63
64 IF (
65 & DIFFERENT_MULTIPLE(thSIce_monFreq,myTime,deltaTclock)
66 & .OR. myIter.EQ.nIter0 ) THEN
67
68 #ifdef ALLOW_USE_MPI
69 IF ( .NOT.useSingleCPUIO .OR. mpiMyId.EQ.0 ) THEN
70 #endif /* ALLOW_USE_MPI */
71 _BEGIN_MASTER(myThid)
72 C-- only the master thread is allowed to switch On/Off mon_write_stdout
73 C & mon_write_mnc (since it's the only thread that uses those flags):
74
75 IF ( thSIce_mon_stdio ) THEN
76 mon_write_stdout = .TRUE.
77 ELSE
78 mon_write_stdout = .FALSE.
79 ENDIF
80 mon_write_mnc = .FALSE.
81 #ifdef ALLOW_MNC
82 IF (useMNC .AND. thSIce_mon_mnc) THEN
83 DO k = 1,MAX_LEN_MBUF
84 mon_fname(k:k) = ' '
85 ENDDO
86 mon_fname(1:12) = 'monitor_sice'
87 CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
88 CALL MNC_CW_I_W_S(
89 & 'I',mon_fname,1,1,'iter', myIter, myThid)
90 CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
91 CALL MNC_CW_RL_W_S(
92 & 'D',mon_fname,1,1,'T', myTime, myThid)
93 mon_write_mnc = .TRUE.
94 ENDIF
95 #endif /* ALLOW_MNC */
96
97 IF (mon_write_stdout) THEN
98 WRITE(msgBuf,'(2A)') '// ==========================',
99 & '============================='
100 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
101 WRITE(msgBuf,'(A)')
102 & '// Begin MONITOR Therm.SeaIce statistics'
103 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
104 WRITE(msgBuf,'(2A)') '// ==========================',
105 & '============================='
106 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
107 ENDIF
108
109 _END_MASTER(myThid)
110 #ifdef ALLOW_USE_MPI
111 ENDIF
112 #endif /* ALLOW_USE_MPI */
113
114 CALL MON_SET_PREF('thSI_',myThid)
115 CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)
116
117 C-- Ice area and Ice thickness :
118 CALL MON_STATS_LATBND_RL(
119 I 1, 1, 1, 2, yBand,
120 I iceheight, iceMask, maskH, rA, yC, locDr,
121 O theMin, theMax, theMean, theVar, theVol,
122 I myThid )
123 theVolG= theVol(1)+theVol(2)
124 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
125 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
126
127 mon_var='Ice_Area'
128 CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
129 CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
130 CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
131 mon_var='IceH_ave'
132 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
133 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
134 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
135 mon_var='IceH_max'
136 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
137 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
138
139 C-- Snow thickness :
140 CALL MON_STATS_LATBND_RL(
141 I 1, 1, 1, 2, yBand,
142 I snowheight, iceMask, maskH, rA, yC, locDr,
143 O theMin, theMax, theMean, theVar, theVol,
144 I myThid )
145 theVolG= theVol(1)+theVol(2)
146 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
147 theEnergy = -rhos*Lfresh*theMeanG
148 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
149
150 mon_var='SnwH_ave'
151 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
152 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
153 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), 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
158 C-- Total Energy :
159 CALL MON_STATS_RL(
160 I 1, Qice1, iceMask, iceheight, rA, locDr,
161 O theMin0,theMax0,theMean1,theSD,theDel2,theVolG,
162 I myThid )
163 CALL MON_STATS_RL(
164 I 1, Qice2, iceMask, iceheight, rA, locDr,
165 O theMin0,theMax0,theMean2,theSD,theDel2,theVolG,
166 I myThid )
167 theEnergy = theEnergy -rhoi*(theMean1+theMean2)*theVolG/2
168 mon_var='TotEnerg'
169 CALL MON_OUT_RL(mon_var, theEnergy, mon_sufx(0), myThid)
170
171 C-- Surface Temp. :
172 CALL MON_STATS_LATBND_RL(
173 I 1, 1, 1, 2, yBand,
174 I Tsrf, iceMask, maskH, rA, yC, locDr,
175 O theMin, theMax, theMean, theVar, theVol,
176 I myThid )
177 theVolG= theVol(1)+theVol(2)
178 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
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 mon_var='Tsrf_min'
186 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
187 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
188 mon_var='Tsrf_max'
189 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
190 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
191
192 C-- 1rst level (volume-mean) Temp. :
193 CALL MON_STATS_LATBND_RL(
194 I 1, 1, 1, 2, yBand,
195 I Tice1, iceMask, iceheight, rA, yC, locDr,
196 O theMin, theMax, theMean, theVar, theVol,
197 I myThid )
198 theVolG = theVol(1)+theVol(2)
199 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
200 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
201
202 c mon_var='IceVolum'
203 c CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
204 c CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
205 c CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
206 mon_var='Tic1_ave'
207 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
208 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
209 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
210 mon_var='Tic1_min'
211 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
212 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
213 mon_var='Tic1_max'
214 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
215 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
216
217 C-- 2nd level (volume-mean) Temp. :
218 CALL MON_STATS_LATBND_RL(
219 I 1, 1, 1, 2, yBand,
220 I Tice2, iceMask, iceheight, rA, yC, locDr,
221 O theMin, theMax, theMean, theVar, theVol,
222 I myThid )
223 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
224 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
225
226 mon_var='Tic2_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 mon_var='Tic2_min'
231 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
232 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
233 mon_var='Tic2_max'
234 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
235 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
236
237 #ifdef ALLOW_USE_MPI
238 IF ( .NOT.useSingleCPUIO .OR. mpiMyId.EQ.0 ) THEN
239 #endif /* ALLOW_USE_MPI */
240 _BEGIN_MASTER(myThid)
241 C-- only the master thread is allowed to switch On/Off mon_write_stdout
242 C & mon_write_mnc (since it's the only thread that uses those flags):
243
244 IF (mon_write_stdout) THEN
245 WRITE(msgBuf,'(2A)') '// ==========================',
246 & '============================='
247 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
248 WRITE(msgBuf,'(A)')
249 & '// End MONITOR Therm.SeaIce statistics'
250 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
251 WRITE(msgBuf,'(2A)') '// ==========================',
252 & '============================='
253 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
254 ENDIF
255
256 mon_write_stdout = .FALSE.
257 mon_write_mnc = .FALSE.
258
259 _END_MASTER(myThid)
260 #ifdef ALLOW_USE_MPI
261 ENDIF
262 #endif /* ALLOW_USE_MPI */
263
264 C endif different multiple
265 ENDIF
266
267 #endif /* ALLOW_MONITOR */
268 #endif /* ALLOW_THSICE */
269
270 RETURN
271 END

  ViewVC Help
Powered by ViewVC 1.1.22