/[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.14 - (show annotations) (download)
Mon Jun 5 18:17:22 2006 UTC (17 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint58q_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58m_post
Changes since 1.13: +51 -10 lines
Implement periodic averaging diagnostics (e.g., mean seasonal cycle,
 mean diurnal cycle)

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

  ViewVC Help
Powered by ViewVC 1.1.22