/[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.6 - (show annotations) (download)
Sat Dec 18 02:18:56 2004 UTC (19 years, 5 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57d_post, checkpoint57b_post, checkpoint57c_pre, checkpoint57e_post, checkpoint57f_pre, eckpoint57e_pre, checkpoint57c_post
Changes since 1.5: +3 -3 lines
o more CF compliance: convert all MNC 'iter' variables to 'T' so that it
  becomes the coordinate variable for the 'T' dimension

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_monitor.F,v 1.5 2004/12/17 04:59:48 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: \bv
12 C *==========================================================*
13 C | S/R THSICE_MONITOR
14 C | o Do ICE global & Hemispheric diagnostic
15 C *==========================================================*
16 C *==========================================================*
17 C \ev
18
19 C !USES:
20 IMPLICIT NONE
21
22 C === Global variables ===
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "PARAMS.h"
26 #include "GRID.h"
27 #include "THSICE_PARAMS.h"
28 #include "THSICE_VARS.h"
29 #ifdef ALLOW_MONITOR
30 #include "MONITOR.h"
31 #endif
32
33 C !INPUT/OUTPUT PARAMETERS:
34 C == Routine arguments ==
35 C myTime - Current time of simulation ( s )
36 C myIter - Iteration number
37 C myThid - Number of this instance of INI_FORCING
38 _RL myTime
39 INTEGER myIter
40 INTEGER myThid
41 CEOP
42
43 #ifdef ALLOW_THSICE
44 #ifdef ALLOW_MONITOR
45
46 C == Local variables ==
47 LOGICAL DIFFERENT_MULTIPLE
48 EXTERNAL DIFFERENT_MULTIPLE
49 CHARACTER*(MAX_LEN_MBUF) msgBuf
50 CHARACTER*10 mon_var
51 CHARACTER*2 mon_sufx(0:2)
52 INTEGER k
53 _RS yBand(2), locDr(1)
54 _RL theMin(2), theMax(2)
55 _RL theMean(2), theVar(2), theVol(2)
56 _RL theMeanG, theVarG, theVolG
57 _RL theMean0, theMean1, theMean2, theEnergy
58 _RL theMin0, theMax0, theSD, theDel2
59
60 DATA yBand / 0. , 0. /
61 DATA locDr / 1. /
62 DATA mon_sufx / '_G' , '_S' , '_N' /
63
64 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
65
66 IF ( DIFFERENT_MULTIPLE(thSIce_monFreq,myTime,myTime-deltaTclock)
67 & .OR. myIter.EQ.nIter0 ) THEN
68
69 mon_write_stdout = .FALSE.
70 mon_write_mnc = .FALSE.
71 IF ( thSIce_mon_stdio ) mon_write_stdout = .TRUE.
72
73 #ifdef ALLOW_MNC
74 IF (useMNC .AND. thSIce_mon_mnc) THEN
75 DO k = 1,MAX_LEN_MBUF
76 mon_fname(k:k) = ' '
77 ENDDO
78 mon_fname(1:12) = 'monitor_sice'
79 CALL MNC_CW_APPEND_VNAME(
80 & 'T', '-_-_--__-__t', 0,0, myThid)
81 CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
82 CALL MNC_CW_I_W_S(
83 & 'I',mon_fname,1,1,'T', myIter, myThid)
84 CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
85 mon_write_mnc = .TRUE.
86 ENDIF
87 #endif /* ALLOW_MNC */
88
89 IF (mon_write_stdout) THEN
90 _BEGIN_MASTER(myThid)
91 WRITE(msgBuf,'(A)')
92 & '// ======================================================='
93 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
94 WRITE(msgBuf,'(A)') '// Begin MONITOR Therm.SeaIce statistics'
95 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
96 WRITE(msgBuf,'(A)')
97 & '// ======================================================='
98 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
99 _END_MASTER(myThid)
100 ENDIF
101
102 CALL MON_SET_PREF('thSI_',myThid)
103 CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)
104
105 C-- Ice area and Ice thickness :
106 CALL MON_STATS_LATBND_RL(
107 I 1, 1, 1, 2, yBand,
108 I iceheight, iceMask, maskH, rA, yC, locDr,
109 O theMin, theMax, theMean, theVar, theVol,
110 I myThid )
111 theVolG= theVol(1)+theVol(2)
112 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
113 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
114
115 mon_var='Ice_Area'
116 CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
117 CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
118 CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
119 mon_var='IceH_ave'
120 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
121 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
122 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
123 mon_var='IceH_max'
124 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
125 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
126
127 C-- Snow thickness :
128 CALL MON_STATS_LATBND_RL(
129 I 1, 1, 1, 2, yBand,
130 I snowheight, iceMask, maskH, rA, yC, locDr,
131 O theMin, theMax, theMean, theVar, theVol,
132 I myThid )
133 theVolG= theVol(1)+theVol(2)
134 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
135 theEnergy = -rhos*Lfresh*theMeanG
136 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
137
138 mon_var='SnwH_ave'
139 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
140 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
141 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
142 mon_var='SnwH_max'
143 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
144 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
145
146 C-- Total Energy :
147 CALL MON_STATS_RL(
148 I 1, Qice1, iceMask, iceheight, rA, locDr,
149 O theMin0,theMax0,theMean1,theSD,theDel2,theVolG,
150 I myThid )
151 CALL MON_STATS_RL(
152 I 1, Qice2, iceMask, iceheight, rA, locDr,
153 O theMin0,theMax0,theMean2,theSD,theDel2,theVolG,
154 I myThid )
155 theEnergy = theEnergy -rhoi*(theMean1+theMean2)*theVolG/2
156 mon_var='TotEnerg'
157 CALL MON_OUT_RL(mon_var, theEnergy, mon_sufx(0), myThid)
158
159 C-- Surface Temp. :
160 CALL MON_STATS_LATBND_RL(
161 I 1, 1, 1, 2, yBand,
162 I Tsrf, iceMask, maskH, rA, yC, locDr,
163 O theMin, theMax, theMean, theVar, theVol,
164 I myThid )
165 theVolG= theVol(1)+theVol(2)
166 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
167 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
168
169 mon_var='Tsrf_ave'
170 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
171 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
172 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
173 mon_var='Tsrf_min'
174 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
175 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
176 mon_var='Tsrf_max'
177 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
178 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
179
180 C-- 1rst level (volume-mean) Temp. :
181 CALL MON_STATS_LATBND_RL(
182 I 1, 1, 1, 2, yBand,
183 I Tice1, iceMask, iceheight, rA, yC, locDr,
184 O theMin, theMax, theMean, theVar, theVol,
185 I myThid )
186 theVolG = theVol(1)+theVol(2)
187 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
188 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
189
190 c mon_var='IceVolum'
191 c CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
192 c CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
193 c CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
194 mon_var='Tic1_ave'
195 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
196 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
197 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
198 mon_var='Tic1_min'
199 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
200 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
201 mon_var='Tic1_max'
202 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
203 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
204
205 C-- 2nd level (volume-mean) Temp. :
206 CALL MON_STATS_LATBND_RL(
207 I 1, 1, 1, 2, yBand,
208 I Tice2, iceMask, iceheight, rA, yC, locDr,
209 O theMin, theMax, theMean, theVar, theVol,
210 I myThid )
211 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
212 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
213
214 mon_var='Tic2_ave'
215 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
216 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
217 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
218 mon_var='Tic2_min'
219 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
220 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
221 mon_var='Tic2_max'
222 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
223 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
224
225 IF (mon_write_stdout) THEN
226 _BEGIN_MASTER(myThid)
227 WRITE(msgBuf,'(A)')
228 & '// ======================================================='
229 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
230 WRITE(msgBuf,'(A)') '// End MONITOR Therm.SeaIce statistics'
231 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
232 WRITE(msgBuf,'(A)')
233 & '// ======================================================='
234 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
235 _END_MASTER(myThid)
236 ENDIF
237
238 mon_write_stdout = .FALSE.
239 mon_write_mnc = .FALSE.
240
241 ENDIF
242
243 #endif /* ALLOW_MONITOR */
244 #endif /* ALLOW_THSICE */
245
246 RETURN
247 END

  ViewVC Help
Powered by ViewVC 1.1.22