/[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.17 - (show annotations) (download)
Tue Mar 16 00:23:59 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.16: +3 -3 lines
avoid unbalanced quote (single or double) in commented line

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_monitor.F,v 1.16 2009/12/21 00:20:06 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 :: my Thread Id. number
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 locMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
52 _RS yBand(2), locDr(1)
53 _RL theMin(2), theMax(2)
54 _RL theMean(2), theVar(2), theVol(2)
55 _RL theMeanG, theVolG
56 _RL theMean1, theMean2, theEnergy
57 _RL theMin0, theMax0, theSD, theDel2
58 INTEGER i,j,bi,bj
59 #ifdef ALLOW_MNC
60 INTEGER k
61 #endif
62
63 DATA yBand / 0. , 0. /
64 DATA locDr / 1. /
65 DATA mon_sufx / '_G' , '_S' , '_N' /
66
67 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
68
69 IF (
70 & DIFFERENT_MULTIPLE(thSIce_monFreq,myTime,deltaTclock)
71 & .OR. myIter.EQ.nIter0 ) THEN
72
73 IF ( MASTER_CPU_IO(myThid) ) THEN
74 C-- only the master thread is allowed to switch On/Off mon_write_stdout
75 C & mon_write_mnc (since it is the only thread that uses those flags):
76
77 IF ( thSIce_mon_stdio ) THEN
78 mon_write_stdout = .TRUE.
79 ELSE
80 mon_write_stdout = .FALSE.
81 ENDIF
82 mon_write_mnc = .FALSE.
83 #ifdef ALLOW_MNC
84 IF (useMNC .AND. thSIce_mon_mnc) THEN
85 DO k = 1,MAX_LEN_MBUF
86 mon_fname(k:k) = ' '
87 ENDDO
88 mon_fname(1:12) = 'monitor_sice'
89 CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
90 CALL MNC_CW_I_W_S(
91 & 'I',mon_fname,1,1,'iter', myIter, myThid)
92 CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
93 CALL MNC_CW_RL_W_S(
94 & 'D',mon_fname,1,1,'T', myTime, myThid)
95 mon_write_mnc = .TRUE.
96 ENDIF
97 #endif /* ALLOW_MNC */
98
99 IF (mon_write_stdout) THEN
100 WRITE(msgBuf,'(2A)') '// ==========================',
101 & '============================='
102 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
103 WRITE(msgBuf,'(A)')
104 & '// Begin MONITOR Therm.SeaIce statistics'
105 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
106 WRITE(msgBuf,'(2A)') '// ==========================',
107 & '============================='
108 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
109 ENDIF
110
111 C-- endif master cpu io
112 ENDIF
113
114 C-- make a local copy of iceMask into "RS" array:
115 DO bj = myByLo(myThid), myByHi(myThid)
116 DO bi = myBxLo(myThid), myBxHi(myThid)
117 DO j=1-OLy,sNy+OLy
118 DO i=1-OLx,sNx+OLx
119 locMask(i,j,bi,bj) = iceMask(i,j,bi,bj)
120 ENDDO
121 ENDDO
122 ENDDO
123 ENDDO
124
125 CALL MON_SET_PREF('thSI_',myThid)
126 CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)
127
128 C-- Ice area and Ice thickness :
129 CALL MON_STATS_LATBND_RL(
130 I 1, 1, 1, 2, yBand,
131 I iceHeight, locMask, maskInC, rA, yC, locDr,
132 O theMin, theMax, theMean, theVar, theVol,
133 I myThid )
134 theVolG= theVol(1)+theVol(2)
135 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
136 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
137
138 mon_var='Ice_Area'
139 CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
140 CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
141 CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
142 mon_var='IceH_ave'
143 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
144 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
145 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
146 mon_var='IceH_max'
147 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
148 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
149
150 C-- Snow thickness :
151 CALL MON_STATS_LATBND_RL(
152 I 1, 1, 1, 2, yBand,
153 I snowHeight, locMask, maskInC, rA, yC, locDr,
154 O theMin, theMax, theMean, theVar, theVol,
155 I myThid )
156 theVolG= theVol(1)+theVol(2)
157 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
158 theEnergy = -rhos*Lfresh*theMeanG
159 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
160
161 mon_var='SnwH_ave'
162 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
163 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
164 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
165 mon_var='SnwH_max'
166 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
167 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
168
169 C-- Surface Temp. :
170 CALL MON_STATS_LATBND_RL(
171 I 1, 1, 1, 2, yBand,
172 I Tsrf, locMask, maskInC, 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-- make a local copy of iceMask*iceHeight into "RS" array:
191 DO bj = myByLo(myThid), myByHi(myThid)
192 DO bi = myBxLo(myThid), myBxHi(myThid)
193 DO j=1-OLy,sNy+OLy
194 DO i=1-OLx,sNx+OLx
195 locMask(i,j,bi,bj)=iceMask(i,j,bi,bj)*iceHeight(i,j,bi,bj)
196 ENDDO
197 ENDDO
198 ENDDO
199 ENDDO
200
201 C-- 1rst level (volume-mean) Temp. :
202 CALL MON_STATS_LATBND_RL(
203 I 1, 1, 1, 2, yBand,
204 I Tice1, locMask, maskInC, rA, yC, locDr,
205 O theMin, theMax, theMean, theVar, theVol,
206 I myThid )
207 theVolG = theVol(1)+theVol(2)
208 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
209 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
210
211 c mon_var='IceVolum'
212 c CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
213 c CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
214 c CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
215 mon_var='Tic1_ave'
216 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
217 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
218 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
219 mon_var='Tic1_min'
220 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
221 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
222 mon_var='Tic1_max'
223 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
224 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
225
226 C-- 2nd level (volume-mean) Temp. :
227 CALL MON_STATS_LATBND_RL(
228 I 1, 1, 1, 2, yBand,
229 I Tice2, locMask, maskInC, rA, yC, locDr,
230 O theMin, theMax, theMean, theVar, theVol,
231 I myThid )
232 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
233 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
234
235 mon_var='Tic2_ave'
236 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
237 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
238 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
239 mon_var='Tic2_min'
240 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
241 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
242 mon_var='Tic2_max'
243 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
244 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
245
246 C-- Total Energy :
247 CALL MON_CALC_STATS_RL(
248 I 1, Qice1, locMask, maskInC, rA, locDr,
249 O theMin0,theMax0,theMean1,theSD,theDel2,theVolG,
250 I myThid )
251 CALL MON_CALC_STATS_RL(
252 I 1, Qice2, locMask, maskInC, rA, locDr,
253 O theMin0,theMax0,theMean2,theSD,theDel2,theVolG,
254 I myThid )
255 theEnergy = theEnergy -rhoi*(theMean1+theMean2)*theVolG/2
256 mon_var='TotEnerg'
257 CALL MON_OUT_RL(mon_var, theEnergy, mon_sufx(0), myThid)
258
259 IF ( MASTER_CPU_IO(myThid) ) THEN
260 C-- only the master thread is allowed to switch On/Off mon_write_stdout
261 C & mon_write_mnc (since it is the only thread that uses those flags):
262
263 IF (mon_write_stdout) THEN
264 WRITE(msgBuf,'(2A)') '// ==========================',
265 & '============================='
266 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
267 WRITE(msgBuf,'(A)')
268 & '// End MONITOR Therm.SeaIce statistics'
269 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
270 WRITE(msgBuf,'(2A)') '// ==========================',
271 & '============================='
272 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
273 ENDIF
274
275 mon_write_stdout = .FALSE.
276 mon_write_mnc = .FALSE.
277
278 C-- endif master cpu io
279 ENDIF
280
281 C endif different multiple
282 ENDIF
283
284 #endif /* ALLOW_MONITOR */
285 #endif /* ALLOW_THSICE */
286
287 RETURN
288 END

  ViewVC Help
Powered by ViewVC 1.1.22