/[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.9 - (show annotations) (download)
Fri Jun 24 04:36:54 2005 UTC (18 years, 11 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57k_post, checkpoint57j_post
Changes since 1.8: +3 -8 lines
 o mnc-ify the thsice package as requested by Daniel Enderton
   - the monitor--MNC output needs work
   - many attributes need to be added (most are currently blank)
   - does not break testreport (at least on IA32)

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

  ViewVC Help
Powered by ViewVC 1.1.22