/[MITgcm]/MITgcm_contrib/heimbach/OpenAD/code_heat_transport/monitor.F
ViewVC logotype

Contents of /MITgcm_contrib/heimbach/OpenAD/code_heat_transport/monitor.F

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


Revision 1.1 - (show annotations) (download)
Tue Nov 20 17:31:21 2007 UTC (17 years, 8 months ago) by utke
Branch: MAIN
CVS Tags: HEAD
enable monitor

1 C $Header: /u/gcmpack/MITgcm/pkg/monitor/monitor.F,v 1.43 2007/10/15 13:51:12 jmc Exp $
2 C $Name: $
3
4 #include "MONITOR_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP
8 C !ROUTINE: MONITOR
9
10 C !INTERFACE:
11 SUBROUTINE MONITOR(
12 I myIter, myTime, myThid )
13
14 C !DESCRIPTION:
15 C Monitor key dynamical variables: calculate over the full domain
16 C some simple statistics (e.g., min,max,average) and write them.
17
18 C !USES:
19 IMPLICIT NONE
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #include "GRID.h"
24 #include "DYNVARS.h"
25 #include "FFIELDS.h"
26 #include "MONITOR.h"
27 #ifdef ALLOW_MNC
28 # include "MNC_PARAMS.h"
29 #endif
30
31 C !INPUT PARAMETERS:
32 INTEGER myIter
33 _RL myTime
34 INTEGER myThid
35 CEOP
36
37 C === Functions ====
38 LOGICAL DIFFERENT_MULTIPLE
39 EXTERNAL DIFFERENT_MULTIPLE
40 LOGICAL MASTER_CPU_IO
41 EXTERNAL MASTER_CPU_IO
42
43 C !LOCAL VARIABLES:
44 CHARACTER*(MAX_LEN_MBUF) msgBuf
45 _RL dT
46 _RL statsTemp(6)
47 _RS thickFacC(Nr), thickFacF(Nr)
48 _RL copyBuff4(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
49 _RL copyBuff5(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
50 INTEGER k
51
52 IF ( DIFFERENT_MULTIPLE(monitorFreq,myTime,deltaTClock) ) THEN
53
54 IF ( MASTER_CPU_IO(myThid) ) THEN
55 C-- only the master thread is allowed to switch On/Off mon_write_stdout
56 C & mon_write_mnc (since it's the only thread that uses those flags):
57
58 IF (monitor_stdio) THEN
59 mon_write_stdout = .TRUE.
60 ELSE
61 mon_write_stdout = .FALSE.
62 ENDIF
63 mon_write_mnc = .FALSE.
64 #ifdef ALLOW_MNC
65 IF (useMNC .AND. monitor_mnc) THEN
66 DO k = 1,MAX_LEN_MBUF
67 mon_fname(k:k) = ' '
68 ENDDO
69 mon_fname(1:7) = 'monitor'
70 CALL MNC_CW_APPEND_VNAME(
71 & 'T', '-_-_--__-__t', 0,0, myThid)
72 CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
73 CALL MNC_CW_RL_W_S(
74 & 'D',mon_fname,1,1,'T', myTime, myThid)
75 CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
76 mon_write_mnc = .TRUE.
77 ENDIF
78 #endif /* ALLOW_MNC */
79
80 C Dynamics field monitor start
81 IF ( mon_write_stdout ) THEN
82 WRITE(msgBuf,'(2A)') '// ==========================',
83 & '============================='
84 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
85 WRITE(msgBuf,'(A)')
86 & '// Begin MONITOR dynamic field statistics'
87 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
88 WRITE(msgBuf,'(2A)') '// ==========================',
89 & '============================='
90 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
91 ENDIF
92
93 C-- endif master cpu io
94 ENDIF
95
96 C- Set mass weighted thickness factor
97 DO k=1,Nr
98 thickFacC(k) = drF(k)*deepFac2C(k)*rhoFacC(k)
99 thickFacF(k) = drC(k)*deepFac2F(k)*rhoFacF(k)
100 ENDDO
101
102 C Print the time to make grepping the stdout easier
103 CALL MON_SET_PREF('time',myThid)
104 CALL MON_OUT_I( '_tsnumber', myIter,mon_string_none,myThid)
105 CALL MON_OUT_RL('_secondsf', myTime,mon_string_none,myThid)
106
107 C Print the basic statistics of model state variables
108 CALL MON_SET_PREF('dynstat',myThid)
109 copyBuff4=EtaN%v
110 CALL MON_PRINTSTATS_RL(1,copyBuff4,'_eta',
111 & maskH,maskH,rA ,drF,myThid)
112 copyBuff5=uVel%v
113 CALL MON_PRINTSTATS_RL(Nr,copyBuff5,'_uvel',
114 & maskW,hFacW,rAw,thickFacC,myThid)
115 copyBuff5=vVel%v
116 CALL MON_PRINTSTATS_RL(Nr,copyBuff5,'_vvel',
117 & maskS,hFacS,rAs,thickFacC,myThid)
118 copyBuff5=wVel%v
119 CALL MON_PRINTSTATS_RL(Nr,copyBuff5,'_wvel',
120 & maskC,maskC,rA ,thickFacF,myThid)
121 copyBuff5=theta%v
122 CALL MON_WRITESTATS_RL(Nr,copyBuff5,'_theta',
123 & maskC,hFacC,rA ,thickFacC,
124 & statsTemp, myThid)
125 copyBuff5=salt%v
126 CALL MON_PRINTSTATS_RL(Nr,copyBuff5,'_salt',
127 & maskC,hFacC,rA ,thickFacC,myThid)
128 IF ( nSx.EQ.1 .AND. nSy.EQ.1 .AND. fluidIsWater ) THEN
129 C- print stats only if nSx=nSy=1 since otherwise stats are wrong
130 k = 1
131 IF ( usingPCoords ) k = Nr
132 copyBuff5=theta(1-Olx:,1-Oly:,k:,1:,1:)%v
133 CALL MON_PRINTSTATS_RL(1,copyBuff5,'_sst',
134 & maskH,maskH,rA ,drF,myThid)
135 copyBuff5=salt(1-Olx:,1-Oly:,k:,1:,1:)%v
136 CALL MON_PRINTSTATS_RL(1, copyBuff5,'_sss',
137 & maskH,maskH,rA ,drF,myThid)
138 ENDIF
139
140 C Print the basic statistics of external forcing
141 IF ( fluidIsWater ) THEN
142 CALL MON_SET_PREF('extforcing',myThid)
143 CALL MON_PRINTSTATS_RL(1,Qnet,'_qnet',
144 & maskH,maskH,rA ,drF,myThid)
145 CALL MON_PRINTSTATS_RL(1,Qsw,'_qsw',
146 & maskH,maskH,rA ,drF,myThid)
147 CALL MON_PRINTSTATS_RL(1,EmPmR,'_empmr',
148 & maskH,maskH,rA ,drF,myThid)
149 IF ( nSx.EQ.1 .AND. nSy.EQ.1 .AND. usingZCoords ) THEN
150 C- print stats only if nSx=nSy=1 since otherwise stats are wrong
151 CALL MON_PRINTSTATS_RL(1,fu,'_fu',
152 & maskW,maskW,rAw,drF,myThid)
153 CALL MON_PRINTSTATS_RL(1,fv,'_fv',
154 & maskS,maskS,rAs,drF,myThid)
155 ENDIF
156 ENDIF
157
158 C Print the numerical stablility parameters for current state
159 CALL MON_SET_PREF('advcfl',myThid)
160 dT=MAX(dTtracerLev(1),deltaTmom)
161 CALL MON_ADVCFL('_uvel',uVel,recip_dxc,dT,myThid)
162 CALL MON_ADVCFL('_vvel',vVel,recip_dyc,dT,myThid)
163 CALL MON_ADVCFLW('_wvel',wVel,recip_drc,dT,myThid)
164 CALL MON_ADVCFLW2('_W_hf',wVel,recip_hFacC,
165 & recip_drC,dT,myThid)
166
167 C Print stats for KE
168 CALL MON_KE(myIter, myThid)
169
170 C Print stats for (relative,absolute) Vorticity AND Pot.Vort.
171 CALL MON_VORT3(myIter, myThid)
172
173 C Print stats for surface correction terms (Linear Free-Surf)
174 CALL MON_SURFCOR(myThid)
175
176 C Check that solution is within reasonable bounds
177 CALL MON_SOLUTION( statsTemp, myTime, myIter, myThid )
178
179 C Dynamics field monitor finish
180 IF ( MASTER_CPU_IO(myThid) ) THEN
181 C-- only the master thread is allowed to switch On/Off mon_write_stdout
182 C & mon_write_mnc (since it's the only thread that uses those flags):
183
184 IF ( mon_write_stdout ) THEN
185 WRITE(msgBuf,'(2A)') '// ==========================',
186 & '============================='
187 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
188 WRITE(msgBuf,'(A)')
189 & '// End MONITOR dynamic field statistics'
190 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
191 WRITE(msgBuf,'(2A)') '// ==========================',
192 & '============================='
193 CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
194 ENDIF
195
196 mon_write_stdout = .FALSE.
197 mon_write_mnc = .FALSE.
198
199 C-- endif master cpu io
200 ENDIF
201
202 C endif different multiple
203 ENDIF
204
205 RETURN
206 END

  ViewVC Help
Powered by ViewVC 1.1.22