/[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.13 - (show annotations) (download)
Tue Oct 17 18:22:33 2006 UTC (17 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58x_post, checkpoint58t_post, checkpoint58q_post, checkpoint59e, checkpoint59d, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post
Changes since 1.12: +10 -17 lines
use function "MASTER_CPU_IO" to hide EESUPPORT.h from TAF.

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_monitor.F,v 1.12 2006/06/23 00:50:22 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 "PARAMS.h"
21 #include "GRID.h"
22 #include "THSICE_PARAMS.h"
23 #include "THSICE_VARS.h"
24 #ifdef ALLOW_MONITOR
25 # include "MONITOR.h"
26 #endif
27
28 C !INPUT/OUTPUT PARAMETERS:
29 C == Routine arguments ==
30 C myTime - Current time of simulation ( s )
31 C myIter - Iteration number
32 C myThid - Number of this instance of INI_FORCING
33 _RL myTime
34 INTEGER myIter
35 INTEGER myThid
36 CEOP
37
38 #ifdef ALLOW_THSICE
39 #ifdef ALLOW_MONITOR
40
41 C === Functions ====
42 LOGICAL DIFFERENT_MULTIPLE
43 EXTERNAL DIFFERENT_MULTIPLE
44 LOGICAL MASTER_CPU_IO
45 EXTERNAL MASTER_CPU_IO
46
47 C == Local variables ==
48 CHARACTER*(MAX_LEN_MBUF) msgBuf
49 CHARACTER*10 mon_var
50 CHARACTER*2 mon_sufx(0:2)
51 _RS yBand(2), locDr(1)
52 _RL theMin(2), theMax(2)
53 _RL theMean(2), theVar(2), theVol(2)
54 _RL theMeanG, theVolG
55 _RL theMean1, theMean2, theEnergy
56 _RL theMin0, theMax0, theSD, theDel2
57 #ifdef ALLOW_MNC
58 INTEGER k
59 #endif
60
61 DATA yBand / 0. , 0. /
62 DATA locDr / 1. /
63 DATA mon_sufx / '_G' , '_S' , '_N' /
64
65 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
66
67 IF (
68 & DIFFERENT_MULTIPLE(thSIce_monFreq,myTime,deltaTclock)
69 & .OR. myIter.EQ.nIter0 ) THEN
70
71 IF ( MASTER_CPU_IO(myThid) ) THEN
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 C-- endif master cpu io
110 ENDIF
111
112 CALL MON_SET_PREF('thSI_',myThid)
113 CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)
114
115 C-- Ice area and Ice thickness :
116 CALL MON_STATS_LATBND_RL(
117 I 1, 1, 1, 2, yBand,
118 I iceheight, iceMask, maskH, rA, yC, locDr,
119 O theMin, theMax, theMean, theVar, theVol,
120 I myThid )
121 theVolG= theVol(1)+theVol(2)
122 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
123 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
124
125 mon_var='Ice_Area'
126 CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
127 CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
128 CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
129 mon_var='IceH_ave'
130 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
131 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
132 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
133 mon_var='IceH_max'
134 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
135 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
136
137 C-- Snow thickness :
138 CALL MON_STATS_LATBND_RL(
139 I 1, 1, 1, 2, yBand,
140 I snowheight, iceMask, maskH, rA, yC, locDr,
141 O theMin, theMax, theMean, theVar, theVol,
142 I myThid )
143 theVolG= theVol(1)+theVol(2)
144 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
145 theEnergy = -rhos*Lfresh*theMeanG
146 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
147
148 mon_var='SnwH_ave'
149 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
150 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
151 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
152 mon_var='SnwH_max'
153 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
154 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
155
156 C-- Total Energy :
157 CALL MON_STATS_RL(
158 I 1, Qice1, iceMask, iceheight, rA, locDr,
159 O theMin0,theMax0,theMean1,theSD,theDel2,theVolG,
160 I myThid )
161 CALL MON_STATS_RL(
162 I 1, Qice2, iceMask, iceheight, rA, locDr,
163 O theMin0,theMax0,theMean2,theSD,theDel2,theVolG,
164 I myThid )
165 theEnergy = theEnergy -rhoi*(theMean1+theMean2)*theVolG/2
166 mon_var='TotEnerg'
167 CALL MON_OUT_RL(mon_var, theEnergy, mon_sufx(0), myThid)
168
169 C-- Surface Temp. :
170 CALL MON_STATS_LATBND_RL(
171 I 1, 1, 1, 2, yBand,
172 I Tsrf, iceMask, maskH, rA, yC, locDr,
173 O theMin, theMax, theMean, theVar, theVol,
174 I myThid )
175 theVolG= theVol(1)+theVol(2)
176 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
177 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
178
179 mon_var='Tsrf_ave'
180 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
181 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
182 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
183 mon_var='Tsrf_min'
184 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
185 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
186 mon_var='Tsrf_max'
187 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
188 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
189
190 C-- 1rst level (volume-mean) Temp. :
191 CALL MON_STATS_LATBND_RL(
192 I 1, 1, 1, 2, yBand,
193 I Tice1, iceMask, iceheight, rA, yC, locDr,
194 O theMin, theMax, theMean, theVar, theVol,
195 I myThid )
196 theVolG = theVol(1)+theVol(2)
197 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
198 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
199
200 c mon_var='IceVolum'
201 c CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
202 c CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
203 c CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
204 mon_var='Tic1_ave'
205 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
206 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
207 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
208 mon_var='Tic1_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 mon_var='Tic1_max'
212 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
213 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
214
215 C-- 2nd level (volume-mean) Temp. :
216 CALL MON_STATS_LATBND_RL(
217 I 1, 1, 1, 2, yBand,
218 I Tice2, iceMask, iceheight, rA, yC, locDr,
219 O theMin, theMax, theMean, theVar, theVol,
220 I myThid )
221 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
222 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
223
224 mon_var='Tic2_ave'
225 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
226 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
227 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
228 mon_var='Tic2_min'
229 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
230 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
231 mon_var='Tic2_max'
232 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
233 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
234
235 IF ( MASTER_CPU_IO(myThid) ) THEN
236 C-- only the master thread is allowed to switch On/Off mon_write_stdout
237 C & mon_write_mnc (since it's the only thread that uses those flags):
238
239 IF (mon_write_stdout) THEN
240 WRITE(msgBuf,'(2A)') '// ==========================',
241 & '============================='
242 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
243 WRITE(msgBuf,'(A)')
244 & '// End MONITOR Therm.SeaIce statistics'
245 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
246 WRITE(msgBuf,'(2A)') '// ==========================',
247 & '============================='
248 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
249 ENDIF
250
251 mon_write_stdout = .FALSE.
252 mon_write_mnc = .FALSE.
253
254 C-- endif master cpu io
255 ENDIF
256
257 C endif different multiple
258 ENDIF
259
260 #endif /* ALLOW_MONITOR */
261 #endif /* ALLOW_THSICE */
262
263 RETURN
264 END

  ViewVC Help
Powered by ViewVC 1.1.22