/[MITgcm]/MITgcm/pkg/seaice/seaice_monitor.F
ViewVC logotype

Contents of /MITgcm/pkg/seaice/seaice_monitor.F

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


Revision 1.16 - (show annotations) (download)
Tue Mar 3 14:05:12 2009 UTC (15 years, 3 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61p, checkpoint61q
Changes since 1.15: +3 -3 lines
make coordinate variable T really model time in seconds as promised by units

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_monitor.F,v 1.15 2008/12/17 03:33:30 dimitri Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP
8 C !ROUTINE: SEAICE_MONITOR
9
10 C !INTERFACE:
11 SUBROUTINE SEAICE_MONITOR(
12 I myTime, myIter, myThid )
13
14 C !DESCRIPTION:
15 C Print some statistics about input forcing fields.
16
17 C !USES:
18 IMPLICIT NONE
19 #include "SIZE.h"
20 #include "EEPARAMS.h"
21 #include "PARAMS.h"
22 #include "GRID.h"
23 #include "SEAICE_PARAMS.h"
24 #include "SEAICE.h"
25 #ifdef ALLOW_MONITOR
26 # include "MONITOR.h"
27 #endif
28
29 C !INPUT PARAMETERS:
30 INTEGER myIter
31 _RL myTime
32 INTEGER myThid
33 CEOP
34
35 #ifdef ALLOW_MONITOR
36 C === Functions ====
37 LOGICAL DIFFERENT_MULTIPLE
38 EXTERNAL DIFFERENT_MULTIPLE
39 LOGICAL MASTER_CPU_IO
40 EXTERNAL MASTER_CPU_IO
41
42 C == Local variables ==
43 CHARACTER*(MAX_LEN_MBUF) msgBuf
44 INTEGER i,j,bi,bj
45 _RL TMP_DIAG (1-OLx:sNx+OLx,1-OLy:sNy+OLy, nSx,nSy)
46
47 IF ( DIFFERENT_MULTIPLE(SEAICE_monFreq,myTime,deltaTClock)
48 & ) THEN
49
50 IF ( MASTER_CPU_IO(myThid) ) THEN
51 C-- only the master thread is allowed to switch On/Off mon_write_stdout
52 C & mon_write_mnc (since it's the only thread that uses those flags):
53
54 IF (SEAICE_mon_stdio) THEN
55 mon_write_stdout = .TRUE.
56 ELSE
57 mon_write_stdout = .FALSE.
58 ENDIF
59 mon_write_mnc = .FALSE.
60 #ifdef ALLOW_MNC
61 IF (useMNC .AND. SEAICE_mon_mnc) THEN
62 DO i = 1,MAX_LEN_MBUF
63 mon_fname(i:i) = ' '
64 ENDDO
65 mon_fname(1:14) = 'monitor_seaice'
66 CALL MNC_CW_APPEND_VNAME(
67 & 'T', '-_-_--__-__t', 0,0, myThid)
68 CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
69 CALL MNC_CW_RL_W_S(
70 & 'D',mon_fname,1,1,'T', myTime, myThid)
71 CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
72 mon_write_mnc = .TRUE.
73 ENDIF
74 #endif /* ALLOW_MNC */
75
76 IF ( mon_write_stdout ) THEN
77 WRITE(msgBuf,'(2A)') '// ===========================',
78 & '============================'
79 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
80 WRITE(msgBuf,'(A)') '// Begin MONITOR SEAICE statistics'
81 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
82 WRITE(msgBuf,'(2A)') '// ===========================',
83 & '============================'
84 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
85 ENDIF
86
87 C-- endif master cpu io
88 ENDIF
89
90 CALL MON_SET_PREF('seaice',myThid)
91 CALL MON_OUT_I ('_tsnumber', myIter,mon_string_none,myThid)
92 CALL MON_OUT_RL('_time_sec', myTime,mon_string_none,myThid)
93
94 C Print some statistics about input forcing fields
95 DO bj=myByLo(myThid),myByHi(myThid)
96 DO bi=myBxLo(myThid),myBxHi(myThid)
97 DO J=1-OLy,sNy+OLy
98 DO I=1-OLx,sNx+OLx
99 TMP_DIAG(i,j,bi,bj)=UICE(i,j,1,bi,bj)
100 ENDDO
101 ENDDO
102 ENDDO
103 ENDDO
104 #ifdef SEAICE_CGRID
105 C- print stats only if nSx=nSy=1 since otherwise stats are wrong
106 IF ( nSx.EQ.1 .AND. nSy.EQ.1 )
107 & CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_uice',
108 & maskW,maskW,rAw,drF,myThid)
109 #else
110 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_uice',
111 & UVM,UVM,rAz,drF,myThid)
112 #endif
113 DO bj=myByLo(myThid),myByHi(myThid)
114 DO bi=myBxLo(myThid),myBxHi(myThid)
115 DO J=1-OLy,sNy+OLy
116 DO I=1-OLx,sNx+OLx
117 TMP_DIAG(i,j,bi,bj)=VICE(i,j,1,bi,bj)
118 ENDDO
119 ENDDO
120 ENDDO
121 ENDDO
122 #ifdef SEAICE_CGRID
123 C- print stats only if nSx=nSy=1 since otherwise stats are wrong
124 IF ( nSx.EQ.1 .AND. nSy.EQ.1 )
125 & CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_vice',
126 & maskS,maskS,rAs,drF,myThid)
127 #else
128 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_vice',
129 & UVM,UVM,rAz,drF,myThid)
130 #endif
131 DO bj=myByLo(myThid),myByHi(myThid)
132 DO bi=myBxLo(myThid),myBxHi(myThid)
133 DO J=1-OLy,sNy+OLy
134 DO I=1-OLx,sNx+OLx
135 TMP_DIAG(i,j,bi,bj)=AREA(i,j,1,bi,bj)
136 ENDDO
137 ENDDO
138 ENDDO
139 ENDDO
140 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_area',
141 & maskH,maskH,rA ,drF,myThid)
142 DO bj=myByLo(myThid),myByHi(myThid)
143 DO bi=myBxLo(myThid),myBxHi(myThid)
144 DO J=1-OLy,sNy+OLy
145 DO I=1-OLx,sNx+OLx
146 TMP_DIAG(i,j,bi,bj)=HEFF(i,j,1,bi,bj)
147 ENDDO
148 ENDDO
149 ENDDO
150 ENDDO
151 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_heff',
152 & maskH,maskH,rA ,drF,myThid)
153 DO bj=myByLo(myThid),myByHi(myThid)
154 DO bi=myBxLo(myThid),myBxHi(myThid)
155 DO J=1-OLy,sNy+OLy
156 DO I=1-OLx,sNx+OLx
157 TMP_DIAG(i,j,bi,bj)=HSNOW(i,j,bi,bj)
158 ENDDO
159 ENDDO
160 ENDDO
161 ENDDO
162 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_hsnow',
163 & maskH,maskH,rA ,drF,myThid)
164 #ifdef SEAICE_SALINITY
165 DO bj=myByLo(myThid),myByHi(myThid)
166 DO bi=myBxLo(myThid),myBxHi(myThid)
167 DO J=1-OLy,sNy+OLy
168 DO I=1-OLx,sNx+OLx
169 TMP_DIAG(i,j,bi,bj)=HSALT(i,j,bi,bj)
170 ENDDO
171 ENDDO
172 ENDDO
173 ENDDO
174 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_hsalt',
175 & maskH,maskH,rA ,drF,myThid)
176 #endif /* SEAICE_SALINITY */
177 #ifdef SEAICE_AGE
178 DO bj=myByLo(myThid),myByHi(myThid)
179 DO bi=myBxLo(myThid),myBxHi(myThid)
180 DO J=1-OLy,sNy+OLy
181 DO I=1-OLx,sNx+OLx
182 TMP_DIAG(i,j,bi,bj)=IceAge(i,j,bi,bj)
183 ENDDO
184 ENDDO
185 ENDDO
186 ENDDO
187 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_iceage',
188 & maskH,maskH,rA ,drF,myThid)
189 #endif /* SEAICE_AGE */
190
191 IF ( MASTER_CPU_IO(myThid) ) THEN
192 C-- only the master thread is allowed to switch On/Off mon_write_stdout
193 C & mon_write_mnc (since it's the only thread that uses those flags):
194
195 IF ( mon_write_stdout ) THEN
196 WRITE(msgBuf,'(2A)') '// ===========================',
197 & '============================'
198 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
199 WRITE(msgBuf,'(A)') '// End MONITOR SEAICE statistics'
200 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
201 WRITE(msgBuf,'(2A)') '// ===========================',
202 & '============================'
203 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
204 ENDIF
205
206 mon_write_stdout = .FALSE.
207 mon_write_mnc = .FALSE.
208
209 C-- endif master cpu io
210 ENDIF
211
212 C endif different multiple
213 ENDIF
214
215 #endif /* ALLOW_MONITOR */
216
217 RETURN
218 END

  ViewVC Help
Powered by ViewVC 1.1.22