/[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.3 - (hide annotations) (download)
Wed Apr 7 23:40:34 2004 UTC (20 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint53d_post, checkpoint54a_pre, checkpoint54e_post, checkpoint54a_post, checkpoint53c_post, checkpoint53b_post, checkpoint54b_post, checkpoint53b_pre, checkpoint54d_post, checkpoint52m_post, checkpoint53a_post, checkpoint54, checkpoint53, checkpoint53g_post, checkpoint53f_post, checkpoint53d_pre, checkpoint54c_post
Changes since 1.2: +13 -5 lines
major changes in pkg/thsice: allows atmospheric model (AIM) to use thsice.
- split thsice_therm.F in 2 S/R: thsice_solve4temp.F & thsice_calc_thickn.F
- move most of the ocean & bulk_force interface in thsice_main.F
- add a "slab ocean" component to be used with atmospheric model

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_monitor.F,v 1.2 2004/03/03 14:16:41 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     _BEGIN_MASTER(myThid)
69     WRITE(msgBuf,'(A)')
70     &'// ======================================================='
71     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
72     WRITE(msgBuf,'(A)') '// Begin MONITOR Therm.SeaIce statistics'
73     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
74     WRITE(msgBuf,'(A)')
75     &'// ======================================================='
76     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
77     _END_MASTER(myThid)
78    
79     CALL MON_SET_PREF('thSI_',myThid)
80     CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)
81    
82     C-- Ice area and Ice thickness :
83 jmc 1.2 CALL MON_STATS_LATBND_RL(
84     I 1, 1, 1, 2, yBand,
85 jmc 1.1 I iceheight, iceMask, maskH, rA, yC, locDr,
86     O theMin, theMax, theMean, theVar, theVol,
87     I myThid )
88     theVolG= theVol(1)+theVol(2)
89     theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
90     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
91    
92     mon_var='Ice_Area'
93     CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
94     CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
95     CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
96     mon_var='IceH_ave'
97     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
98     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
99     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
100     mon_var='IceH_max'
101     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
102     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
103    
104     C-- Snow thickness :
105 jmc 1.2 CALL MON_STATS_LATBND_RL(
106     I 1, 1, 1, 2, yBand,
107 jmc 1.1 I snowheight, iceMask, maskH, rA, yC, locDr,
108     O theMin, theMax, theMean, theVar, theVol,
109     I myThid )
110     theVolG= theVol(1)+theVol(2)
111     theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
112     theEnergy = -rhos*Lfresh*theMeanG
113     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
114    
115     mon_var='SnwH_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='SnwH_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-- Total Energy :
124     CALL MON_STATS_RL(
125     I 1, Qice1, iceMask, iceheight, rA, locDr,
126     O theMin0,theMax0,theMean1,theSD,theDel2,theVolG,
127     I myThid )
128     CALL MON_STATS_RL(
129     I 1, Qice2, iceMask, iceheight, rA, locDr,
130     O theMin0,theMax0,theMean2,theSD,theDel2,theVolG,
131     I myThid )
132     theEnergy = theEnergy -rhoi*(theMean1+theMean2)*theVolG/2
133     mon_var='TotEnerg'
134     CALL MON_OUT_RL(mon_var, theEnergy, mon_sufx(0), myThid)
135    
136     C-- Surface Temp. :
137 jmc 1.2 CALL MON_STATS_LATBND_RL(
138     I 1, 1, 1, 2, yBand,
139 jmc 1.1 I Tsrf, iceMask, maskH, rA, yC, locDr,
140     O theMin, theMax, theMean, theVar, theVol,
141     I myThid )
142     theVolG= theVol(1)+theVol(2)
143     theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
144     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
145    
146     mon_var='Tsrf_ave'
147     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
148     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
149     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
150     mon_var='Tsrf_min'
151     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
152     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
153     mon_var='Tsrf_max'
154     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
155     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
156    
157     C-- 1rst level (volume-mean) Temp. :
158 jmc 1.2 CALL MON_STATS_LATBND_RL(
159     I 1, 1, 1, 2, yBand,
160 jmc 1.1 I Tice1, iceMask, iceheight, 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     c mon_var='IceVolum'
168     c CALL MON_OUT_RL(mon_var, theVolG , mon_sufx(0), myThid)
169     c CALL MON_OUT_RL(mon_var, theVol(1), mon_sufx(1), myThid)
170     c CALL MON_OUT_RL(mon_var, theVol(2), mon_sufx(2), myThid)
171     mon_var='Tic1_ave'
172     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
173     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
174     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
175     mon_var='Tic1_min'
176     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
177     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
178     mon_var='Tic1_max'
179     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
180     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
181    
182     C-- 2nd level (volume-mean) Temp. :
183 jmc 1.2 CALL MON_STATS_LATBND_RL(
184     I 1, 1, 1, 2, yBand,
185 jmc 1.1 I Tice2, iceMask, iceheight, rA, yC, locDr,
186     O theMin, theMax, theMean, theVar, theVol,
187     I myThid )
188     theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
189     IF (theVolG.GT.0.) theMeanG = theMeanG / theVolG
190    
191     mon_var='Tic2_ave'
192     CALL MON_OUT_RL(mon_var,theMeanG , mon_sufx(0), myThid)
193     CALL MON_OUT_RL(mon_var,theMean(1), mon_sufx(1), myThid)
194     CALL MON_OUT_RL(mon_var,theMean(2), mon_sufx(2), myThid)
195     mon_var='Tic2_min'
196     CALL MON_OUT_RL(mon_var, theMin(1), mon_sufx(1), myThid)
197     CALL MON_OUT_RL(mon_var, theMin(2), mon_sufx(2), myThid)
198     mon_var='Tic2_max'
199     CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
200     CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
201    
202     _BEGIN_MASTER(myThid)
203     WRITE(msgBuf,'(A)')
204     &'// ======================================================='
205     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
206     WRITE(msgBuf,'(A)') '// End MONITOR Therm.SeaIce statistics'
207     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
208     WRITE(msgBuf,'(A)')
209     &'// ======================================================='
210     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
211     _END_MASTER(myThid)
212    
213     ENDIF
214    
215     #endif /* ALLOW_MONITOR */
216     #endif /* ALLOW_THSICE */
217    
218     RETURN
219     END

  ViewVC Help
Powered by ViewVC 1.1.22