/[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.8 - (show annotations) (download)
Mon Oct 23 15:11:40 2006 UTC (17 years, 6 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58x_post, checkpoint58t_post, checkpoint59d, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post
Changes since 1.7: +12 -1 lines
Adding HSNOW to seaice_monitor.

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_monitor.F,v 1.7 2006/10/18 16:08:13 jmc 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_I_W_S(
70 & 'I',mon_fname,1,1,'T', myIter, 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 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_uice',
106 & maskW,maskW,rAw,drF,myThid)
107 #else
108 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_uice',
109 & UVM,UVM,rAz,drF,myThid)
110 #endif
111 DO bj=myByLo(myThid),myByHi(myThid)
112 DO bi=myBxLo(myThid),myBxHi(myThid)
113 DO J=1-OLy,sNy+OLy
114 DO I=1-OLx,sNx+OLx
115 TMP_DIAG(i,j,bi,bj)=VICE(i,j,1,bi,bj)
116 ENDDO
117 ENDDO
118 ENDDO
119 ENDDO
120 #ifdef SEAICE_CGRID
121 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_vice',
122 & maskS,maskS,rAs,drF,myThid)
123 #else
124 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_vice',
125 & UVM,UVM,rAz,drF,myThid)
126 #endif
127 DO bj=myByLo(myThid),myByHi(myThid)
128 DO bi=myBxLo(myThid),myBxHi(myThid)
129 DO J=1-OLy,sNy+OLy
130 DO I=1-OLx,sNx+OLx
131 TMP_DIAG(i,j,bi,bj)=AREA(i,j,1,bi,bj)
132 ENDDO
133 ENDDO
134 ENDDO
135 ENDDO
136 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_area',
137 & maskH,maskH,rA ,drF,myThid)
138 DO bj=myByLo(myThid),myByHi(myThid)
139 DO bi=myBxLo(myThid),myBxHi(myThid)
140 DO J=1-OLy,sNy+OLy
141 DO I=1-OLx,sNx+OLx
142 TMP_DIAG(i,j,bi,bj)=HEFF(i,j,1,bi,bj)
143 ENDDO
144 ENDDO
145 ENDDO
146 ENDDO
147 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_heff',
148 & maskH,maskH,rA ,drF,myThid)
149 DO bj=myByLo(myThid),myByHi(myThid)
150 DO bi=myBxLo(myThid),myBxHi(myThid)
151 DO J=1-OLy,sNy+OLy
152 DO I=1-OLx,sNx+OLx
153 TMP_DIAG(i,j,bi,bj)=HSNOW(i,j,bi,bj)
154 ENDDO
155 ENDDO
156 ENDDO
157 ENDDO
158 CALL MON_PRINTSTATS_RL(1,TMP_DIAG,'_hsnow',
159 & maskH,maskH,rA ,drF,myThid)
160
161 IF ( MASTER_CPU_IO(myThid) ) THEN
162 C-- only the master thread is allowed to switch On/Off mon_write_stdout
163 C & mon_write_mnc (since it's the only thread that uses those flags):
164
165 IF ( mon_write_stdout ) THEN
166 WRITE(msgBuf,'(2A)') '// ===========================',
167 & '============================'
168 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
169 WRITE(msgBuf,'(A)') '// End MONITOR SEAICE statistics'
170 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
171 WRITE(msgBuf,'(2A)') '// ===========================',
172 & '============================'
173 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
174 ENDIF
175
176 mon_write_stdout = .FALSE.
177 mon_write_mnc = .FALSE.
178
179 C-- endif master cpu io
180 ENDIF
181
182 C endif different multiple
183 ENDIF
184
185 #endif /* ALLOW_MONITOR */
186
187 RETURN
188 END

  ViewVC Help
Powered by ViewVC 1.1.22