/[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.7 - (show annotations) (download)
Wed Apr 6 18:47:11 2005 UTC (19 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57g_post, checkpoint57g_pre, checkpoint57f_post, checkpoint57h_pre, checkpoint57h_post
Changes since 1.6: +6 -5 lines
use baseTime as time origin ; DIFF_BASE_MULTIPLE replaces DIFFERENT_MULTIPLE

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_monitor.F,v 1.6 2004/12/18 02:18:56 edhill 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 DIFF_BASE_MULTIPLE
48 EXTERNAL DIFF_BASE_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 (
67 & DIFF_BASE_MULTIPLE(baseTime,thSIce_monFreq,myTime,deltaTclock)
68 & .OR. myIter.EQ.nIter0 ) THEN
69
70 mon_write_stdout = .FALSE.
71 mon_write_mnc = .FALSE.
72 IF ( thSIce_mon_stdio ) mon_write_stdout = .TRUE.
73
74 #ifdef ALLOW_MNC
75 IF (useMNC .AND. thSIce_mon_mnc) THEN
76 DO k = 1,MAX_LEN_MBUF
77 mon_fname(k:k) = ' '
78 ENDDO
79 mon_fname(1:12) = 'monitor_sice'
80 CALL MNC_CW_APPEND_VNAME(
81 & 'T', '-_-_--__-__t', 0,0, myThid)
82 CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
83 CALL MNC_CW_I_W_S(
84 & 'I',mon_fname,1,1,'T', myIter, myThid)
85 CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
86 mon_write_mnc = .TRUE.
87 ENDIF
88 #endif /* ALLOW_MNC */
89
90 IF (mon_write_stdout) THEN
91 _BEGIN_MASTER(myThid)
92 WRITE(msgBuf,'(A)')
93 & '// ======================================================='
94 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
95 WRITE(msgBuf,'(A)') '// Begin MONITOR Therm.SeaIce statistics'
96 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
97 WRITE(msgBuf,'(A)')
98 & '// ======================================================='
99 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
100 _END_MASTER(myThid)
101 ENDIF
102
103 CALL MON_SET_PREF('thSI_',myThid)
104 CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)
105
106 C-- Ice area and Ice thickness :
107 CALL MON_STATS_LATBND_RL(
108 I 1, 1, 1, 2, yBand,
109 I iceheight, iceMask, maskH, rA, yC, locDr,
110 O theMin, theMax, theMean, theVar, theVol,
111 I myThid )
112 theVolG= theVol(1)+theVol(2)
113 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
114 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
115
116 mon_var='Ice_Area'
117 CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
118 CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
119 CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
120 mon_var='IceH_ave'
121 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
122 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
123 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
124 mon_var='IceH_max'
125 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
126 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
127
128 C-- Snow thickness :
129 CALL MON_STATS_LATBND_RL(
130 I 1, 1, 1, 2, yBand,
131 I snowheight, iceMask, maskH, 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 theEnergy = -rhos*Lfresh*theMeanG
137 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
138
139 mon_var='SnwH_ave'
140 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
141 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
142 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
143 mon_var='SnwH_max'
144 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
145 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
146
147 C-- Total Energy :
148 CALL MON_STATS_RL(
149 I 1, Qice1, iceMask, iceheight, rA, locDr,
150 O theMin0,theMax0,theMean1,theSD,theDel2,theVolG,
151 I myThid )
152 CALL MON_STATS_RL(
153 I 1, Qice2, iceMask, iceheight, rA, locDr,
154 O theMin0,theMax0,theMean2,theSD,theDel2,theVolG,
155 I myThid )
156 theEnergy = theEnergy -rhoi*(theMean1+theMean2)*theVolG/2
157 mon_var='TotEnerg'
158 CALL MON_OUT_RL(mon_var, theEnergy, mon_sufx(0), myThid)
159
160 C-- Surface Temp. :
161 CALL MON_STATS_LATBND_RL(
162 I 1, 1, 1, 2, yBand,
163 I Tsrf, iceMask, maskH, rA, yC, locDr,
164 O theMin, theMax, theMean, theVar, theVol,
165 I myThid )
166 theVolG= theVol(1)+theVol(2)
167 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
168 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
169
170 mon_var='Tsrf_ave'
171 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
172 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
173 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
174 mon_var='Tsrf_min'
175 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
176 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
177 mon_var='Tsrf_max'
178 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
179 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
180
181 C-- 1rst level (volume-mean) Temp. :
182 CALL MON_STATS_LATBND_RL(
183 I 1, 1, 1, 2, yBand,
184 I Tice1, iceMask, iceheight, rA, yC, locDr,
185 O theMin, theMax, theMean, theVar, theVol,
186 I myThid )
187 theVolG = theVol(1)+theVol(2)
188 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
189 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
190
191 c mon_var='IceVolum'
192 c CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
193 c CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
194 c CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
195 mon_var='Tic1_ave'
196 CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
197 CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
198 CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
199 mon_var='Tic1_min'
200 CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
201 CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
202 mon_var='Tic1_max'
203 CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
204 CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
205
206 C-- 2nd level (volume-mean) Temp. :
207 CALL MON_STATS_LATBND_RL(
208 I 1, 1, 1, 2, yBand,
209 I Tice2, iceMask, iceheight, rA, yC, locDr,
210 O theMin, theMax, theMean, theVar, theVol,
211 I myThid )
212 theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
213 IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
214
215 mon_var='Tic2_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='Tic2_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='Tic2_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 IF (mon_write_stdout) THEN
227 _BEGIN_MASTER(myThid)
228 WRITE(msgBuf,'(A)')
229 & '// ======================================================='
230 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
231 WRITE(msgBuf,'(A)') '// End MONITOR Therm.SeaIce statistics'
232 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
233 WRITE(msgBuf,'(A)')
234 & '// ======================================================='
235 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
236 _END_MASTER(myThid)
237 ENDIF
238
239 mon_write_stdout = .FALSE.
240 mon_write_mnc = .FALSE.
241
242 ENDIF
243
244 #endif /* ALLOW_MONITOR */
245 #endif /* ALLOW_THSICE */
246
247 RETURN
248 END

  ViewVC Help
Powered by ViewVC 1.1.22