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

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

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

revision 1.13 by molod, Sun Oct 16 18:38:55 2005 UTC revision 1.19 by jmc, Wed Aug 14 00:57:33 2013 UTC
# Line 41  CEOP Line 41  CEOP
41  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
42  C      newIter :: future iteration number  C      newIter :: future iteration number
43  C      j,m,n   :: loop index  C      j,m,n   :: loop index
44  c     CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
45  c     INTEGER newIter  c     INTEGER newIter
46        INTEGER m, n, nd        INTEGER m, n, nd
47        INTEGER bi, bj, ip, iSp        INTEGER bi, bj, ip, iSp
48        LOGICAL time4SnapShot        LOGICAL time4SnapShot
49        _RL     phiSec, freqSec        _RL     phiSec, freqSec
50          INTEGER nInterval
51          _RL     xInterval
52        LOGICAL dBugFlag        LOGICAL dBugFlag
53          INTEGER dBugUnit
54  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
55        logical alarm2,alarm2next        LOGICAL  ALARM2NEXT
56        character *9 tagname        EXTERNAL ALARM2NEXT
57          CHARACTER *9 tagname
58  #endif  #endif
59    
60        LOGICAL  DIFF_PHASE_MULTIPLE        LOGICAL  DIFF_PHASE_MULTIPLE
# Line 58  c     INTEGER newIter Line 62  c     INTEGER newIter
62    
63  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  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            _BEGIN_MASTER(myThid)
71    c       IF ( diag_pkgStatus.NE.10 ) STOP
72            diag_pkgStatus = ready2fillDiags
73            _END_MASTER(myThid)
74    c     ELSEIF
75    c       IF ( diag_pkgStatus.NE.ready2fillDiags ) STOP
76          ENDIF
77    
78  c     newIter = 1 + myIter  c     newIter = 1 + myIter
79        DO n = 1,nlists        DO n = 1,nlists
80    
# Line 67  C--    Select diagnostics list that uses Line 84  C--    Select diagnostics list that uses
84          freqSec = freq(n)          freqSec = freq(n)
85          phiSec = phase(n)          phiSec = phase(n)
86          time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,          time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
87       &                                       myTime, deltaTclock )       &                                       myTime, deltaTClock )
88  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
89          if( useFIZHI) then          IF ( useFIZHI ) THEN
90           write(tagname,'(A,I2.2)')'diagtag',n           WRITE(tagname,'(A,I2.2)')'diagtag',n
91           time4SnapShot = alarm2next(tagname,deltaT)           time4SnapShot = ALARM2NEXT(tagname,deltaT)
92          endif          ENDIF
93  #endif  #endif
94    #ifdef ALLOW_CAL
95            IF ( useCAL ) THEN
96              CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
97         U                        time4SnapShot,
98         I                        myTime, myIter, myThid )
99            ENDIF
100    #endif /* ALLOW_CAL */
101    
102          DO bj=myByLo(myThid), myByHi(myThid)          DO bj=myByLo(myThid), myByHi(myThid)
103           DO bi=myBxLo(myThid), myBxHi(myThid)           DO bi=myBxLo(myThid), myBxHi(myThid)
# Line 97  c             IF (ndiag(nd).NE.-1) WRITE Line 121  c             IF (ndiag(nd).NE.-1) WRITE
121           ENDDO           ENDDO
122          ENDDO          ENDDO
123    
124    C--    list with instantaneous output: end
125           ENDIF
126    
127           IF ( averageCycle(n).GT.1 ) THEN
128    C--    Select diagnostics list that uses periodic averaging
129            xInterval = myTime + deltaTClock*0.5 _d 0 - averagePhase(n)
130            xInterval = xInterval / averageFreq(n)
131            IF ( xInterval.GE.0. ) THEN
132              nInterval = INT(xInterval)
133            ELSE
134              nInterval = 1 + INT( -xInterval/FLOAT(averageCycle(n)) )
135              nInterval = nInterval*averageCycle(n) + INT(xInterval) - 1
136            ENDIF
137            nInterval = MOD(nInterval,averageCycle(n))
138    
139    C-     check future value of pdiag:
140            IF (dBugFlag.AND.pdiag(n,1,1).NE.nInterval)
141         &    WRITE(dBugUnit,'(A,I8,3(A,I4),F17.6)')
142         &     'DIAG_SWITCH_ONOFF: at it=', myIter, ', list:', n,
143         &     ' switch', pdiag(n,1,1),' ->', nInterval, xInterval
144            IF ( nInterval.LT.0 .OR. nInterval.GE.averageCycle(n) ) THEN
145              WRITE(msgBuf,'(2A,I3,A,I4)') 'DIAGNOSTICS_SWITCH_ONOFF:',
146         &       ' error setting pdiag(n=',n,') to:', nInterval
147              CALL PRINT_ERROR( msgBuf , myThid )
148              WRITE(msgBuf,'(2A,I4,A,F17.6)') 'DIAGNOSTICS_SWITCH_ONOFF:',
149         &       ' cycle=', averageCycle(n), ', xInt=', xInterval
150              CALL PRINT_ERROR( msgBuf , myThid )
151              STOP 'ABNORMAL END: S/R DIAGNOSTICS_SWITCH_ONOFF'
152            ENDIF
153    
154            DO bj=myByLo(myThid), myByHi(myThid)
155             DO bi=myBxLo(myThid), myBxHi(myThid)
156               pdiag(n,bi,bj) = nInterval
157             ENDDO
158            ENDDO
159    C--    list with periodic averaging: end
160         ENDIF         ENDIF
161    
162        ENDDO        ENDDO
163    
164  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
# Line 107  C---+----1----+----2----+----3----+----4 Line 168  C---+----1----+----2----+----3----+----4
168         IF ( diagSt_freq(n).LT.0. ) THEN         IF ( diagSt_freq(n).LT.0. ) THEN
169  C--    Select diagnostics list that uses instantaneous output  C--    Select diagnostics list that uses instantaneous output
170    
171          dBugFlag = debugLevel.GT.debLevB          dBugFlag = debugLevel.GE.debLevE
172    
173          freqSec = diagSt_freq(n)          freqSec = diagSt_freq(n)
174          phiSec = diagSt_phase(n)          phiSec = diagSt_phase(n)
175          time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,          time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
176       &                                       myTime, deltaTclock )       &                                       myTime, deltaTClock )
177    
178  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
179          if( useFIZHI) then          IF ( useFIZHI ) THEN
180           write(tagname,'(A,I2.2)')'diagStg',n           WRITE(tagname,'(A,I2.2)')'diagStg',n
181           time4SnapShot = alarm2next(tagname,deltaT)           time4SnapShot = ALARM2NEXT(tagname,deltaT)
182          endif          ENDIF
183  #endif  #endif
184    #ifdef ALLOW_CAL
185            IF ( useCAL ) THEN
186              CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
187         U                        time4SnapShot,
188         I                        myTime, myIter, myThid )
189            ENDIF
190    #endif /* ALLOW_CAL */
191    
192          DO bj=myByLo(myThid), myByHi(myThid)          DO bj=myByLo(myThid), myByHi(myThid)
193           DO bi=myBxLo(myThid), myBxHi(myThid)           DO bi=myBxLo(myThid), myBxHi(myThid)
# Line 131  C--     switch ON diagnostics of output- Line 199  C--     switch ON diagnostics of output-
199               IF (iSp.GT.0) THEN               IF (iSp.GT.0) THEN
200                 nd = jSdiag(m,n)                 nd = jSdiag(m,n)
201                 IF (dBugFlag.AND.qSdiag(0,0,iSp,bi,bj).NE. 0.)                 IF (dBugFlag.AND.qSdiag(0,0,iSp,bi,bj).NE. 0.)
202       &          WRITE(0,'(I8,I4,3A,1PE10.3,A,I3)') myIter,       &          WRITE(dBugUnit,'(A,I8,A,I6,3A,1PE10.3,A,I3)')
203       &           nd,' ',cdiag(nd),' :',qSdiag(0,0,iSp,bi,bj),' ->', 0       &           'DIAG_SWITCH_ONOFF: at it=', myIter, ' diag:', nd,
204         &           ' ',cdiag(nd),' :',qSdiag(0,0,iSp,bi,bj),' ->', 0
205                 qSdiag(0,0,iSp,bi,bj) = 0.                 qSdiag(0,0,iSp,bi,bj) = 0.
206               ENDIF               ENDIF
207              ENDDO              ENDDO
# Line 143  C--     switch OFF diagnostics of output Line 212  C--     switch OFF diagnostics of output
212               IF (iSp.GT.0) THEN               IF (iSp.GT.0) THEN
213                 nd = jSdiag(m,n)                 nd = jSdiag(m,n)
214                 IF (dBugFlag.AND.qSdiag(0,0,iSp,bi,bj).NE.-1.)                 IF (dBugFlag.AND.qSdiag(0,0,iSp,bi,bj).NE.-1.)
215       &          WRITE(0,'(I8,I4,3A,1PE10.3,A,I3)') myIter,       &          WRITE(dBugUnit,'(A,I8,A,I6,3A,1PE10.3,A,I3)')
216       &           nd,' ',cdiag(nd),' :',qSdiag(0,0,iSp,bi,bj),' ->',-1       &           'DIAG_SWITCH_ONOFF: at it=', myIter, ' diag:', nd,
217         &           ' ',cdiag(nd),' :',qSdiag(0,0,iSp,bi,bj),' ->', -1
218                 qSdiag(0,0,iSp,bi,bj) = -1.                 qSdiag(0,0,iSp,bi,bj) = -1.
219               ENDIF               ENDIF
220              ENDDO              ENDDO

Legend:
Removed from v.1.13  
changed lines
  Added in v.1.19

  ViewVC Help
Powered by ViewVC 1.1.22