/[MITgcm]/MITgcm/pkg/thsice/thsice_monitor.F
ViewVC logotype

Annotation of /MITgcm/pkg/thsice/thsice_monitor.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.11 - (hide annotations) (download)
Fri Nov 4 01:34:35 2005 UTC (18 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58e_post, checkpoint57y_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58j_post, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint58d_post, checkpoint58c_post, checkpoint58a_post, checkpoint58i_post, checkpoint58g_post, checkpoint57z_post, checkpoint58b_post
Changes since 1.10: +6 -4 lines
remove unused variables (reduces number of compiler warning)

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

  ViewVC Help
Powered by ViewVC 1.1.22