/[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.16 - (show annotations) (download)
Tue Feb 5 15:31:19 2008 UTC (16 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59o, checkpoint59n, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62y, checkpoint62x, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.15: +6 -6 lines
minor modifications for many diagnostics:
- modify "available_diagnostics.log" and diagnostics summary (write mate number)
- use wider (integer) format (generally, use I6) to write diagnostics number
- rename numdiags --> numDiags (to differentiate from mdiag)

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_switch_onoff.F,v 1.15 2007/08/21 16:09:31 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 alarm2, alarm2next
56 CHARACTER *9 tagname
57 #endif
58
59 LOGICAL DIFF_PHASE_MULTIPLE
60 EXTERNAL DIFF_PHASE_MULTIPLE
61
62 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
63
64 dBugFlag = debugLevel.GT.debLevB .AND. myThid.EQ.1
65 dBugUnit = errorMessageUnit
66
67 c newIter = 1 + myIter
68 DO n = 1,nlists
69
70 IF ( freq(n).LT.0. ) THEN
71 C-- Select diagnostics list that uses instantaneous output
72
73 freqSec = freq(n)
74 phiSec = phase(n)
75 time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
76 & myTime, deltaTclock )
77 #ifdef ALLOW_FIZHI
78 IF ( useFIZHI ) THEN
79 WRITE(tagname,'(A,I2.2)')'diagtag',n
80 time4SnapShot = alarm2next(tagname,deltaT)
81 ENDIF
82 #endif
83
84 DO bj=myByLo(myThid), myByHi(myThid)
85 DO bi=myBxLo(myThid), myBxHi(myThid)
86 IF ( time4SnapShot ) THEN
87 C-- switch ON diagnostics of output-stream # n
88 DO m=1,nActive(n)
89 c nd = jdiag(m,n)
90 c IF (ndiag(nd).NE.0) WRITE(0,*) myIter,nd,ndiag(nd),' ->',0
91 ip = idiag(m,n)
92 IF (ip.GT.0) ndiag(ip,bi,bj) = 0
93 ENDDO
94 ELSE
95 C-- switch OFF diagnostics of output-stream # n
96 DO m=1,nActive(n)
97 c nd = jdiag(m,n)
98 c IF (ndiag(nd).NE.-1) WRITE(0,*) myIter,nd,ndiag(nd),' ->',-1
99 ip = idiag(m,n)
100 IF (ip.GT.0) ndiag(ip,bi,bj) = -1
101 ENDDO
102 ENDIF
103 ENDDO
104 ENDDO
105
106 C-- list with instantaneous output: end
107 ENDIF
108
109 IF ( averageCycle(n).GT.1 ) THEN
110 C-- Select diagnostics list that uses periodic averaging
111 xInterval = myTime + deltaTclock*0.5 _d 0 - averagePhase(n)
112 xInterval = xInterval / averageFreq(n)
113 IF ( xInterval.GE.0. ) THEN
114 nInterval = INT(xInterval)
115 ELSE
116 nInterval = 1 + INT( -xInterval/FLOAT(averageCycle(n)) )
117 nInterval = nInterval*averageCycle(n) + INT(xInterval) - 1
118 ENDIF
119 nInterval = MOD(nInterval,averageCycle(n))
120
121 C- check future value of pdiag:
122 IF (dBugFlag.AND.pdiag(n,1,1).NE.nInterval)
123 & WRITE(dBugUnit,'(A,I8,3(A,I4),F17.6)')
124 & 'DIAG_SWITCH_ONOFF: at it=', myIter, ', list:', n,
125 & ' switch', pdiag(n,1,1),' ->', nInterval, xInterval
126 IF ( nInterval.LT.0 .OR. nInterval.GE.averageCycle(n) ) THEN
127 WRITE(msgBuf,'(2A,I3,A,I4)') 'DIAGNOSTICS_SWITCH_ONOFF:',
128 & ' error setting pdiag(n=',n,') to:', nInterval
129 CALL PRINT_ERROR( msgBuf , myThid )
130 WRITE(msgBuf,'(2A,I4,A,F17.6)') 'DIAGNOSTICS_SWITCH_ONOFF:',
131 & ' cycle=', averageCycle(n), ', xInt=', xInterval
132 CALL PRINT_ERROR( msgBuf , myThid )
133 STOP 'ABNORMAL END: S/R DIAGNOSTICS_SWITCH_ONOFF'
134 ENDIF
135
136 DO bj=myByLo(myThid), myByHi(myThid)
137 DO bi=myBxLo(myThid), myBxHi(myThid)
138 pdiag(n,bi,bj) = nInterval
139 ENDDO
140 ENDDO
141 C-- list with periodic averaging: end
142 ENDIF
143
144 ENDDO
145
146 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
147
148 DO n = 1,diagSt_nbLists
149
150 IF ( diagSt_freq(n).LT.0. ) THEN
151 C-- Select diagnostics list that uses instantaneous output
152
153 dBugFlag = debugLevel.GT.debLevB
154
155 freqSec = diagSt_freq(n)
156 phiSec = diagSt_phase(n)
157 time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
158 & myTime, deltaTclock )
159
160 #ifdef ALLOW_FIZHI
161 IF ( useFIZHI ) THEN
162 WRITE(tagname,'(A,I2.2)')'diagStg',n
163 time4SnapShot = alarm2next(tagname,deltaT)
164 ENDIF
165 #endif
166
167 DO bj=myByLo(myThid), myByHi(myThid)
168 DO bi=myBxLo(myThid), myBxHi(myThid)
169 dBugFlag = dBugFlag.AND.(bi.EQ.1.AND.bj.EQ.1.AND.myThid.EQ.1)
170 IF ( time4SnapShot ) THEN
171 C-- switch ON diagnostics of output-stream # n
172 DO m=1,diagSt_nbActv(n)
173 iSp = iSdiag(m,n)
174 IF (iSp.GT.0) THEN
175 nd = jSdiag(m,n)
176 IF (dBugFlag.AND.qSdiag(0,0,iSp,bi,bj).NE. 0.)
177 & WRITE(dBugUnit,'(A,I8,A,I6,3A,1PE10.3,A,I3)')
178 & 'DIAG_SWITCH_ONOFF: at it=', myIter, ' diag:', nd,
179 & ' ',cdiag(nd),' :',qSdiag(0,0,iSp,bi,bj),' ->', 0
180 qSdiag(0,0,iSp,bi,bj) = 0.
181 ENDIF
182 ENDDO
183 ELSE
184 C-- switch OFF diagnostics of output-stream # n
185 DO m=1,diagSt_nbActv(n)
186 iSp = iSdiag(m,n)
187 IF (iSp.GT.0) THEN
188 nd = jSdiag(m,n)
189 IF (dBugFlag.AND.qSdiag(0,0,iSp,bi,bj).NE.-1.)
190 & WRITE(dBugUnit,'(A,I8,A,I6,3A,1PE10.3,A,I3)')
191 & 'DIAG_SWITCH_ONOFF: at it=', myIter, ' diag:', nd,
192 & ' ',cdiag(nd),' :',qSdiag(0,0,iSp,bi,bj),' ->', -1
193 qSdiag(0,0,iSp,bi,bj) = -1.
194 ENDIF
195 ENDDO
196 ENDIF
197 ENDDO
198 ENDDO
199
200 ENDIF
201 ENDDO
202
203 RETURN
204 END

  ViewVC Help
Powered by ViewVC 1.1.22