/[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.18 - (show annotations) (download)
Wed Sep 2 22:29:15 2009 UTC (14 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61v, checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.17: +5 -1 lines
disable monitor of B-grid uIce,vIce when REAL4_IS_SLOW is undef

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_monitor.F,v 1.17 2009/06/24 08:01:43 mlosch 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
46 IF ( DIFFERENT_MULTIPLE(SEAICE_monFreq,myTime,deltaTClock)
47 & ) THEN
48
49 IF ( MASTER_CPU_IO(myThid) ) THEN
50 C-- only the master thread is allowed to switch On/Off mon_write_stdout
51 C & mon_write_mnc (since it's the only thread that uses those flags):
52
53 IF (SEAICE_mon_stdio) THEN
54 mon_write_stdout = .TRUE.
55 ELSE
56 mon_write_stdout = .FALSE.
57 ENDIF
58 mon_write_mnc = .FALSE.
59 #ifdef ALLOW_MNC
60 IF (useMNC .AND. SEAICE_mon_mnc) THEN
61 DO i = 1,MAX_LEN_MBUF
62 mon_fname(i:i) = ' '
63 ENDDO
64 mon_fname(1:14) = 'monitor_seaice'
65 CALL MNC_CW_APPEND_VNAME(
66 & 'T', '-_-_--__-__t', 0,0, myThid)
67 CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
68 CALL MNC_CW_RL_W_S(
69 & 'D',mon_fname,1,1,'T', myTime, myThid)
70 CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
71 mon_write_mnc = .TRUE.
72 ENDIF
73 #endif /* ALLOW_MNC */
74
75 IF ( mon_write_stdout ) THEN
76 WRITE(msgBuf,'(2A)') '// ===========================',
77 & '============================'
78 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
79 WRITE(msgBuf,'(A)') '// Begin MONITOR SEAICE statistics'
80 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
81 WRITE(msgBuf,'(2A)') '// ===========================',
82 & '============================'
83 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
84 ENDIF
85
86 C-- endif master cpu io
87 ENDIF
88
89 CALL MON_SET_PREF('seaice',myThid)
90 CALL MON_OUT_I ('_tsnumber', myIter,mon_string_none,myThid)
91 CALL MON_OUT_RL('_time_sec', myTime,mon_string_none,myThid)
92
93 C Print some statistics about input forcing fields
94 #ifdef SEAICE_CGRID
95 C- print stats only if nSx=nSy=1 since otherwise stats are wrong
96 IF ( nSx.EQ.1 .AND. nSy.EQ.1 )
97 & CALL MON_PRINTSTATS_RL(1,UICE,'_uice',
98 & maskW,maskW,rAw,drF,myThid)
99 #else
100 # ifdef REAL4_IS_SLOW
101 CALL MON_PRINTSTATS_RL(1,UICE,'_uice',
102 & UVM,UVM,rAz,drF,myThid)
103 # endif
104 #endif
105 #ifdef SEAICE_CGRID
106 C- print stats only if nSx=nSy=1 since otherwise stats are wrong
107 IF ( nSx.EQ.1 .AND. nSy.EQ.1 )
108 & CALL MON_PRINTSTATS_RL(1,VICE,'_vice',
109 & maskS,maskS,rAs,drF,myThid)
110 #else
111 # ifdef REAL4_IS_SLOW
112 CALL MON_PRINTSTATS_RL(1,VICE,'_vice',
113 & UVM,UVM,rAz,drF,myThid)
114 # endif
115 #endif
116 CALL MON_PRINTSTATS_RL(1,AREA,'_area',
117 & maskH,maskH,rA ,drF,myThid)
118 CALL MON_PRINTSTATS_RL(1,HEFF,'_heff',
119 & maskH,maskH,rA ,drF,myThid)
120 CALL MON_PRINTSTATS_RL(1,HSNOW,'_hsnow',
121 & maskH,maskH,rA ,drF,myThid)
122 #ifdef SEAICE_SALINITY
123 CALL MON_PRINTSTATS_RL(1,HSALT,'_hsalt',
124 & maskH,maskH,rA ,drF,myThid)
125 #endif /* SEAICE_SALINITY */
126 #ifdef SEAICE_AGE
127 CALL MON_PRINTSTATS_RL(1,ICEAGE,'_iceage',
128 & maskH,maskH,rA ,drF,myThid)
129 #endif /* SEAICE_AGE */
130
131 IF ( MASTER_CPU_IO(myThid) ) THEN
132 C-- only the master thread is allowed to switch On/Off mon_write_stdout
133 C & mon_write_mnc (since it's the only thread that uses those flags):
134
135 IF ( mon_write_stdout ) THEN
136 WRITE(msgBuf,'(2A)') '// ===========================',
137 & '============================'
138 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
139 WRITE(msgBuf,'(A)') '// End MONITOR SEAICE statistics'
140 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
141 WRITE(msgBuf,'(2A)') '// ===========================',
142 & '============================'
143 CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
144 ENDIF
145
146 mon_write_stdout = .FALSE.
147 mon_write_mnc = .FALSE.
148
149 C-- endif master cpu io
150 ENDIF
151
152 C endif different multiple
153 ENDIF
154
155 #endif /* ALLOW_MONITOR */
156
157 RETURN
158 END

  ViewVC Help
Powered by ViewVC 1.1.22