/[MITgcm]/MITgcm/pkg/diagnostics/diagnostics_switch_onoff.F
ViewVC logotype

Contents of /MITgcm/pkg/diagnostics/diagnostics_switch_onoff.F

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


Revision 1.21 - (show annotations) (download)
Sun Jul 23 00:24:18 2017 UTC (6 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, HEAD
Changes since 1.20: +3 -3 lines
allows for negative "jdiag" (interpret |jdiag| instead)

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_switch_onoff.F,v 1.20 2015/06/02 20:58:22 jmc Exp $
2 C $Name: $
3
4 #include "DIAG_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP 0
8 C !ROUTINE: DIAGNOSTICS_SWITCH_ONOFF
9
10 C !INTERFACE:
11 SUBROUTINE DIAGNOSTICS_SWITCH_ONOFF( myTime, myIter, myThid )
12
13 C !DESCRIPTION:
14 C-----
15 C Called at the beginning of the time-step,
16 C to switch on/off diagnostics for snap-shot output
17 C-----
18 C during iterations that are multiple of |freq|,
19 C switch ON diagnostics (ndiag>=0) that will become active
20 C and then can be written at the end of the time-step ;
21 C otherwise, put diagnostics in non-active mode (ndiag=-1)
22 C-----
23
24 C !USES:
25 IMPLICIT NONE
26 #include "SIZE.h"
27 #include "EEPARAMS.h"
28 #include "PARAMS.h"
29 #include "DIAGNOSTICS_SIZE.h"
30 #include "DIAGNOSTICS.h"
31
32 C !INPUT PARAMETERS:
33 C myTime :: current Time of simulation ( s )
34 C myIter :: current Iteration number
35 C myThid :: my Thread Id number
36 _RL myTime
37 INTEGER myIter
38 INTEGER myThid
39 CEOP
40
41 C !LOCAL VARIABLES:
42 C newIter :: future iteration number
43 C j,m,n :: loop index
44 CHARACTER*(MAX_LEN_MBUF) msgBuf
45 c INTEGER newIter
46 INTEGER m, n, nd
47 INTEGER bi, bj, ip, iSp
48 LOGICAL time4SnapShot
49 _RL phiSec, freqSec
50 INTEGER nInterval
51 _RL xInterval
52 LOGICAL dBugFlag
53 INTEGER dBugUnit
54 #ifdef ALLOW_FIZHI
55 LOGICAL ALARM2NEXT
56 EXTERNAL ALARM2NEXT
57 CHARACTER *9 tagname
58 #endif
59
60 LOGICAL DIFF_PHASE_MULTIPLE
61 EXTERNAL DIFF_PHASE_MULTIPLE
62
63 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
64
65 dBugFlag = debugLevel.GE.debLevE .AND. myThid.EQ.1
66 dBugUnit = errorMessageUnit
67
68 C-- Track diagnostics pkg activation status:
69 IF ( myIter.EQ.nIter0 ) THEN
70 c IF ( diag_pkgStatus.NE.10 ) STOP
71 _BARRIER
72 _BEGIN_MASTER(myThid)
73 diag_pkgStatus = ready2fillDiags
74 _END_MASTER(myThid)
75 _BARRIER
76 c ELSEIF
77 c IF ( diag_pkgStatus.NE.ready2fillDiags ) STOP
78 ENDIF
79
80 c newIter = 1 + myIter
81 DO n = 1,nlists
82
83 IF ( freq(n).LT.0. ) THEN
84 C-- Select diagnostics list that uses instantaneous output
85
86 freqSec = freq(n)
87 phiSec = phase(n)
88 time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
89 & myTime, deltaTClock )
90 #ifdef ALLOW_FIZHI
91 IF ( useFIZHI ) THEN
92 WRITE(tagname,'(A,I2.2)')'diagtag',n
93 time4SnapShot = ALARM2NEXT(tagname,deltaT)
94 ENDIF
95 #endif
96 #ifdef ALLOW_CAL
97 IF ( useCAL ) THEN
98 CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
99 U time4SnapShot,
100 I myTime, myIter, myThid )
101 ENDIF
102 #endif /* ALLOW_CAL */
103
104 DO bj=myByLo(myThid), myByHi(myThid)
105 DO bi=myBxLo(myThid), myBxHi(myThid)
106 IF ( time4SnapShot ) THEN
107 C-- switch ON diagnostics of output-stream # n
108 DO m=1,nActive(n)
109 c nd = ABS(jdiag(m,n))
110 c IF (ndiag(nd).NE.0) WRITE(0,*) myIter,nd,ndiag(nd),' ->',0
111 ip = idiag(m,n)
112 IF (ip.GT.0) ndiag(ip,bi,bj) = 0
113 ENDDO
114 ELSE
115 C-- switch OFF diagnostics of output-stream # n
116 DO m=1,nActive(n)
117 c nd = ABS(jdiag(m,n))
118 c IF (ndiag(nd).NE.-1) WRITE(0,*) myIter,nd,ndiag(nd),' ->',-1
119 ip = idiag(m,n)
120 IF (ip.GT.0) ndiag(ip,bi,bj) = -1
121 ENDDO
122 ENDIF
123 ENDDO
124 ENDDO
125
126 C-- list with instantaneous output: end
127 ENDIF
128
129 IF ( averageCycle(n).GT.1 ) THEN
130 C-- Select diagnostics list that uses periodic averaging
131 xInterval = myTime + deltaTClock*0.5 _d 0 - averagePhase(n)
132 xInterval = xInterval / averageFreq(n)
133 IF ( xInterval.GE.0. ) THEN
134 nInterval = INT(xInterval)
135 ELSE
136 nInterval = 1 + INT( -xInterval/FLOAT(averageCycle(n)) )
137 nInterval = nInterval*averageCycle(n) + INT(xInterval) - 1
138 ENDIF
139 nInterval = MOD(nInterval,averageCycle(n))
140
141 C- check future value of pdiag:
142 IF (dBugFlag.AND.pdiag(n,1,1).NE.nInterval)
143 & WRITE(dBugUnit,'(A,I8,3(A,I4),F17.6)')
144 & 'DIAG_SWITCH_ONOFF: at it=', myIter, ', list:', n,
145 & ' switch', pdiag(n,1,1),' ->', nInterval, xInterval
146 IF ( nInterval.LT.0 .OR. nInterval.GE.averageCycle(n) ) THEN
147 WRITE(msgBuf,'(2A,I3,A,I4)') 'DIAGNOSTICS_SWITCH_ONOFF:',
148 & ' error setting pdiag(n=',n,') to:', nInterval
149 CALL PRINT_ERROR( msgBuf , myThid )
150 WRITE(msgBuf,'(2A,I4,A,F17.6)') 'DIAGNOSTICS_SWITCH_ONOFF:',
151 & ' cycle=', averageCycle(n), ', xInt=', xInterval
152 CALL PRINT_ERROR( msgBuf , myThid )
153 STOP 'ABNORMAL END: S/R DIAGNOSTICS_SWITCH_ONOFF'
154 ENDIF
155
156 DO bj=myByLo(myThid), myByHi(myThid)
157 DO bi=myBxLo(myThid), myBxHi(myThid)
158 pdiag(n,bi,bj) = nInterval
159 ENDDO
160 ENDDO
161 C-- list with periodic averaging: end
162 ENDIF
163
164 ENDDO
165
166 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
167
168 DO n = 1,diagSt_nbLists
169
170 IF ( diagSt_freq(n).LT.0. ) THEN
171 C-- Select diagnostics list that uses instantaneous output
172
173 dBugFlag = debugLevel.GE.debLevE
174
175 freqSec = diagSt_freq(n)
176 phiSec = diagSt_phase(n)
177 time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
178 & myTime, deltaTClock )
179
180 #ifdef ALLOW_FIZHI
181 IF ( useFIZHI ) THEN
182 WRITE(tagname,'(A,I2.2)')'diagStg',n
183 time4SnapShot = ALARM2NEXT(tagname,deltaT)
184 ENDIF
185 #endif
186 #ifdef ALLOW_CAL
187 IF ( useCAL ) THEN
188 CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
189 U time4SnapShot,
190 I myTime, myIter, myThid )
191 ENDIF
192 #endif /* ALLOW_CAL */
193
194 DO bj=myByLo(myThid), myByHi(myThid)
195 DO bi=myBxLo(myThid), myBxHi(myThid)
196 dBugFlag = dBugFlag.AND.(bi.EQ.1.AND.bj.EQ.1.AND.myThid.EQ.1)
197 IF ( time4SnapShot ) THEN
198 C-- switch ON diagnostics of output-stream # n
199 DO m=1,diagSt_nbActv(n)
200 iSp = iSdiag(m,n)
201 IF (iSp.GT.0) THEN
202 nd = jSdiag(m,n)
203 IF (dBugFlag.AND.qSdiag(0,0,iSp,bi,bj).NE. 0.)
204 & WRITE(dBugUnit,'(A,I8,A,I6,3A,1PE10.3,A,I3)')
205 & 'DIAG_SWITCH_ONOFF: at it=', myIter, ' diag:', nd,
206 & ' ',cdiag(nd),' :',qSdiag(0,0,iSp,bi,bj),' ->', 0
207 qSdiag(0,0,iSp,bi,bj) = 0.
208 ENDIF
209 ENDDO
210 ELSE
211 C-- switch OFF diagnostics of output-stream # n
212 DO m=1,diagSt_nbActv(n)
213 iSp = iSdiag(m,n)
214 IF (iSp.GT.0) THEN
215 nd = jSdiag(m,n)
216 IF (dBugFlag.AND.qSdiag(0,0,iSp,bi,bj).NE.-1.)
217 & WRITE(dBugUnit,'(A,I8,A,I6,3A,1PE10.3,A,I3)')
218 & 'DIAG_SWITCH_ONOFF: at it=', myIter, ' diag:', nd,
219 & ' ',cdiag(nd),' :',qSdiag(0,0,iSp,bi,bj),' ->', -1
220 qSdiag(0,0,iSp,bi,bj) = -1.
221 ENDIF
222 ENDDO
223 ENDIF
224 ENDDO
225 ENDDO
226
227 ENDIF
228 ENDDO
229
230 RETURN
231 END

  ViewVC Help
Powered by ViewVC 1.1.22