/[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.4 - (hide annotations) (download)
Wed Sep 8 02:07:48 2004 UTC (19 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint55c_post, checkpoint55d_pre, checkpoint55j_post, checkpoint56b_post, checkpoint55h_post, checkpoint55b_post, checkpoint56c_post, checkpoint55, checkpoint57a_post, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, checkpoint55e_post, checkpoint55a_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.3: +5 -1 lines
set mon_write_stdout=TRUE to get the monitor written out

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_monitor.F,v 1.3 2004/04/07 23:40:34 jmc 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     C !DESCRIPTION: \bv
12 jmc 1.1 C *==========================================================*
13 jmc 1.3 C | S/R THSICE_MONITOR
14 jmc 1.1 C | o Do ICE global & Hemispheric diagnostic
15     C *==========================================================*
16     C *==========================================================*
17 jmc 1.3 C \ev
18    
19     C !USES:
20 jmc 1.1 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 jmc 1.3 #include "THSICE_VARS.h"
29 jmc 1.1 #ifdef ALLOW_MONITOR
30     #include "MONITOR.h"
31     #endif
32    
33 jmc 1.3 C !INPUT/OUTPUT PARAMETERS:
34 jmc 1.1 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 jmc 1.3 CEOP
42 jmc 1.1
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     _RS yBand(2), locDr(1)
53     _RL theMin(2), theMax(2)
54     _RL theMean(2), theVar(2), theVol(2)
55     _RL theMeanG, theVarG, theVolG
56     _RL theMean0, theMean1, theMean2, theEnergy
57     _RL theMin0, theMax0, theSD, theDel2
58    
59     DATA yBand / 0. , 0. /
60     DATA locDr / 1. /
61     DATA mon_sufx / '_G' , '_S' , '_N' /
62    
63     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
64    
65     IF ( DIFFERENT_MULTIPLE(thSIce_monFreq,myTime,myTime-deltaTclock)
66     & .OR. myIter.EQ.nIter0 ) THEN
67    
68 jmc 1.4 mon_write_stdout = .TRUE.
69    
70 jmc 1.1 _BEGIN_MASTER(myThid)
71     WRITE(msgBuf,'(A)')
72     &'// ======================================================='
73     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
74     WRITE(msgBuf,'(A)') '// Begin MONITOR Therm.SeaIce statistics'
75     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
76     WRITE(msgBuf,'(A)')
77     &'// ======================================================='
78     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
79     _END_MASTER(myThid)
80    
81     CALL MON_SET_PREF('thSI_',myThid)
82     CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)
83    
84     C-- Ice area and Ice thickness :
85 jmc 1.2 CALL MON_STATS_LATBND_RL(
86     I 1, 1, 1, 2, yBand,
87 jmc 1.1 I iceheight, iceMask, maskH, rA, yC, locDr,
88     O theMin, theMax, theMean, theVar, theVol,
89     I myThid )
90     theVolG= theVol(1)+theVol(2)
91     theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
92     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
93    
94     mon_var='Ice_Area'
95     CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
96     CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
97     CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
98     mon_var='IceH_ave'
99     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
100     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
101     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
102     mon_var='IceH_max'
103     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
104     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
105    
106     C-- Snow thickness :
107 jmc 1.2 CALL MON_STATS_LATBND_RL(
108     I 1, 1, 1, 2, yBand,
109 jmc 1.1 I snowheight, 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     theEnergy = -rhos*Lfresh*theMeanG
115     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
116    
117     mon_var='SnwH_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='SnwH_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-- Total Energy :
126     CALL MON_STATS_RL(
127     I 1, Qice1, iceMask, iceheight, rA, locDr,
128     O theMin0,theMax0,theMean1,theSD,theDel2,theVolG,
129     I myThid )
130     CALL MON_STATS_RL(
131     I 1, Qice2, iceMask, iceheight, rA, locDr,
132     O theMin0,theMax0,theMean2,theSD,theDel2,theVolG,
133     I myThid )
134     theEnergy = theEnergy -rhoi*(theMean1+theMean2)*theVolG/2
135     mon_var='TotEnerg'
136     CALL MON_OUT_RL(mon_var, theEnergy, mon_sufx(0), myThid)
137    
138     C-- Surface Temp. :
139 jmc 1.2 CALL MON_STATS_LATBND_RL(
140     I 1, 1, 1, 2, yBand,
141 jmc 1.1 I Tsrf, iceMask, maskH, rA, yC, locDr,
142     O theMin, theMax, theMean, theVar, theVol,
143     I myThid )
144     theVolG= theVol(1)+theVol(2)
145     theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
146     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
147    
148     mon_var='Tsrf_ave'
149     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
150     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
151     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
152     mon_var='Tsrf_min'
153     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
154     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
155     mon_var='Tsrf_max'
156     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
157     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
158    
159     C-- 1rst level (volume-mean) Temp. :
160 jmc 1.2 CALL MON_STATS_LATBND_RL(
161     I 1, 1, 1, 2, yBand,
162 jmc 1.1 I Tice1, iceMask, iceheight, 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     c mon_var='IceVolum'
170     c CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
171     c CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
172     c CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
173     mon_var='Tic1_ave'
174     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
175     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
176     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
177     mon_var='Tic1_min'
178     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
179     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
180     mon_var='Tic1_max'
181     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
182     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
183    
184     C-- 2nd level (volume-mean) Temp. :
185 jmc 1.2 CALL MON_STATS_LATBND_RL(
186     I 1, 1, 1, 2, yBand,
187 jmc 1.1 I Tice2, iceMask, iceheight, rA, yC, locDr,
188     O theMin, theMax, theMean, theVar, theVol,
189     I myThid )
190     theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
191     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
192    
193     mon_var='Tic2_ave'
194     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
195     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
196     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
197     mon_var='Tic2_min'
198     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
199     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
200     mon_var='Tic2_max'
201     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
202     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
203    
204     _BEGIN_MASTER(myThid)
205     WRITE(msgBuf,'(A)')
206     &'// ======================================================='
207     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
208     WRITE(msgBuf,'(A)') '// End MONITOR Therm.SeaIce statistics'
209     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
210     WRITE(msgBuf,'(A)')
211     &'// ======================================================='
212     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
213     _END_MASTER(myThid)
214    
215 jmc 1.4 mon_write_stdout = .FALSE.
216    
217 jmc 1.1 ENDIF
218    
219     #endif /* ALLOW_MONITOR */
220     #endif /* ALLOW_THSICE */
221    
222     RETURN
223     END

  ViewVC Help
Powered by ViewVC 1.1.22