/[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.1 - (hide annotations) (download)
Sun Nov 23 01:20:13 2003 UTC (20 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52e_pre, hrcube4, checkpoint52j_post, checkpoint52e_post, hrcube_1, branch-netcdf, checkpoint52d_pre, checkpoint52k_post, checkpoint52d_post, checkpoint52b_post, checkpoint52f_post, checkpoint52c_post, checkpoint52i_post, checkpoint52j_pre, checkpoint52i_pre, checkpoint52h_pre, checkpoint52f_pre, hrcube_2, hrcube_3
Branch point for: netcdf-sm0
new pkg "thSIce" (replace therm_seaice).

1 jmc 1.1 C $Header: $
2     C $Name: $
3    
4     #include "THSICE_OPTIONS.h"
5    
6     CStartOfInterface
7     SUBROUTINE THSICE_MONITOR( myTime, myIter, myThid )
8     C *==========================================================*
9     C | SUBROUTINE THSICE_MONITOR
10     C | o Do ICE global & Hemispheric diagnostic
11     C *==========================================================*
12     C *==========================================================*
13     IMPLICIT NONE
14    
15     C === Global variables ===
16     #include "SIZE.h"
17     #include "EEPARAMS.h"
18     #include "PARAMS.h"
19     #include "GRID.h"
20     #include "THSICE_PARAMS.h"
21     #include "THSICE.h"
22     #ifdef ALLOW_MONITOR
23     #include "MONITOR.h"
24     #endif
25    
26     C == Routine arguments ==
27     C myTime - Current time of simulation ( s )
28     C myIter - Iteration number
29     C myThid - Number of this instance of INI_FORCING
30     _RL myTime
31     INTEGER myIter
32     INTEGER myThid
33     CEndOfInterface
34    
35     #ifdef ALLOW_THSICE
36     #ifdef ALLOW_MONITOR
37    
38     C == Local variables ==
39     LOGICAL DIFFERENT_MULTIPLE
40     EXTERNAL DIFFERENT_MULTIPLE
41     CHARACTER*(MAX_LEN_MBUF) msgBuf
42     CHARACTER*10 mon_var
43     CHARACTER*2 mon_sufx(0:2)
44     _RS yBand(2), locDr(1)
45     _RL theMin(2), theMax(2)
46     _RL theMean(2), theVar(2), theVol(2)
47     _RL theMeanG, theVarG, theVolG
48     _RL theMean0, theMean1, theMean2, theEnergy
49     _RL theMin0, theMax0, theSD, theDel2
50    
51     DATA yBand / 0. , 0. /
52     DATA locDr / 1. /
53     DATA mon_sufx / '_G' , '_S' , '_N' /
54    
55     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
56    
57     IF ( DIFFERENT_MULTIPLE(thSIce_monFreq,myTime,myTime-deltaTclock)
58     & .OR. myIter.EQ.nIter0 ) THEN
59    
60     _BEGIN_MASTER(myThid)
61     WRITE(msgBuf,'(A)')
62     &'// ======================================================='
63     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
64     WRITE(msgBuf,'(A)') '// Begin MONITOR Therm.SeaIce statistics'
65     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
66     WRITE(msgBuf,'(A)')
67     &'// ======================================================='
68     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
69     _END_MASTER(myThid)
70    
71     CALL MON_SET_PREF('thSI_',myThid)
72     CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)
73    
74     C-- Ice area and Ice thickness :
75     CALL MON_STATS_LATBND_RL(
76     I 1, 2, yBand,
77     I iceheight, iceMask, maskH, rA, yC, locDr,
78     O theMin, theMax, theMean, theVar, theVol,
79     I myThid )
80     theVolG= theVol(1)+theVol(2)
81     theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
82     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
83    
84     mon_var='Ice_Area'
85     CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
86     CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
87     CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
88     mon_var='IceH_ave'
89     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
90     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
91     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
92     mon_var='IceH_max'
93     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
94     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
95    
96     C-- Snow thickness :
97     CALL MON_STATS_LATBND_RL(
98     I 1, 2, yBand,
99     I snowheight, iceMask, maskH, rA, yC, locDr,
100     O theMin, theMax, theMean, theVar, theVol,
101     I myThid )
102     theVolG= theVol(1)+theVol(2)
103     theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
104     theEnergy = -rhos*Lfresh*theMeanG
105     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
106    
107     mon_var='SnwH_ave'
108     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
109     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
110     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
111     mon_var='SnwH_max'
112     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
113     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
114    
115     C-- Total Energy :
116     CALL MON_STATS_RL(
117     I 1, Qice1, iceMask, iceheight, rA, locDr,
118     O theMin0,theMax0,theMean1,theSD,theDel2,theVolG,
119     I myThid )
120     CALL MON_STATS_RL(
121     I 1, Qice2, iceMask, iceheight, rA, locDr,
122     O theMin0,theMax0,theMean2,theSD,theDel2,theVolG,
123     I myThid )
124     theEnergy = theEnergy -rhoi*(theMean1+theMean2)*theVolG/2
125     mon_var='TotEnerg'
126     CALL MON_OUT_RL(mon_var, theEnergy, mon_sufx(0), myThid)
127    
128     C-- Surface Temp. :
129     CALL MON_STATS_LATBND_RL(
130     I 1, 2, yBand,
131     I Tsrf, 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     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
137    
138     mon_var='Tsrf_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='Tsrf_min'
143     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
144     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
145     mon_var='Tsrf_max'
146     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
147     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
148    
149     C-- 1rst level (volume-mean) Temp. :
150     CALL MON_STATS_LATBND_RL(
151     I 1, 2, yBand,
152     I Tice1, iceMask, iceheight, rA, yC, locDr,
153     O theMin, theMax, theMean, theVar, theVol,
154     I myThid )
155     theVolG = theVol(1)+theVol(2)
156     theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
157     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
158    
159     c mon_var='IceVolum'
160     c CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
161     c CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
162     c CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
163     mon_var='Tic1_ave'
164     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
165     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
166     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
167     mon_var='Tic1_min'
168     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
169     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
170     mon_var='Tic1_max'
171     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
172     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
173    
174     C-- 2nd level (volume-mean) Temp. :
175     CALL MON_STATS_LATBND_RL(
176     I 1, 2, yBand,
177     I Tice2, iceMask, iceheight, rA, yC, locDr,
178     O theMin, theMax, theMean, theVar, theVol,
179     I myThid )
180     theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
181     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
182    
183     mon_var='Tic2_ave'
184     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
185     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
186     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
187     mon_var='Tic2_min'
188     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
189     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
190     mon_var='Tic2_max'
191     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
192     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
193    
194     _BEGIN_MASTER(myThid)
195     WRITE(msgBuf,'(A)')
196     &'// ======================================================='
197     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
198     WRITE(msgBuf,'(A)') '// End MONITOR Therm.SeaIce statistics'
199     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
200     WRITE(msgBuf,'(A)')
201     &'// ======================================================='
202     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
203     _END_MASTER(myThid)
204    
205     ENDIF
206    
207     #endif /* ALLOW_MONITOR */
208     #endif /* ALLOW_THSICE */
209    
210     RETURN
211     END

  ViewVC Help
Powered by ViewVC 1.1.22