/[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.19 - (show annotations) (download)
Mon Sep 3 19:41:14 2012 UTC (11 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63s, checkpoint64, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.18: +4 -4 lines
comment out unused variable

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

  ViewVC Help
Powered by ViewVC 1.1.22