/[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.8 by molod, Tue May 17 00:22:00 2005 UTC revision 1.16 by jmc, Tue Feb 5 15:31:19 2008 UTC
# Line 28  C     !USES: Line 28  C     !USES:
28  #include "PARAMS.h"  #include "PARAMS.h"
29  #include "DIAGNOSTICS_SIZE.h"  #include "DIAGNOSTICS_SIZE.h"
30  #include "DIAGNOSTICS.h"  #include "DIAGNOSTICS.h"
 #ifdef ALLOW_FIZHI  
 #include "chronos.h"  
 #endif  
31    
32  C     !INPUT PARAMETERS:  C     !INPUT PARAMETERS:
33  C     myTime     :: current Time of simulation ( s )  C     myTime     :: current Time of simulation ( s )
# Line 44  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 j, m, n        INTEGER m, n, nd
47          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
53          INTEGER dBugUnit
54  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
55        integer mmdd,hhmmss,nsecf2        LOGICAL alarm2, alarm2next
56        logical alarm2        CHARACTER *9 tagname
       character *9 tagname  
57  #endif  #endif
58    
59        LOGICAL  DIFF_PHASE_MULTIPLE        LOGICAL  DIFF_PHASE_MULTIPLE
60        EXTERNAL DIFF_PHASE_MULTIPLE        EXTERNAL DIFF_PHASE_MULTIPLE
61    
       _BEGIN_MASTER(myThid)  
   
62  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  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  c     newIter = 1 + myIter
68        DO n = 1,nlists        DO n = 1,nlists
69    
# Line 73  C--    Select diagnostics list that uses Line 75  C--    Select diagnostics list that uses
75          time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,          time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
76       &                                       myTime, deltaTclock )       &                                       myTime, deltaTclock )
77  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
78          if( useFIZHI) then          IF ( useFIZHI ) THEN
79           mmdd = int(freq(n))           WRITE(tagname,'(A,I2.2)')'diagtag',n
80           hhmmss = int((freq(n) - int(freq(n)))*1.e6)           time4SnapShot = alarm2next(tagname,deltaT)
81           freqSec = nsecf2(hhmmss,mmdd,nymd)          ENDIF
          write(tagname,'(A,I2.2)')'diagtag',n  
          time4SnapShot = alarm2(tagname)  
         endif  
82  #endif  #endif
83    
84          IF ( time4SnapShot ) THEN          DO bj=myByLo(myThid), myByHi(myThid)
85  C--     switch ON diagnostics of output-stream # n           DO bi=myBxLo(myThid), myBxHi(myThid)
86            DO m=1,nActive(n)            IF ( time4SnapShot ) THEN
87              j = jdiag(m,n)  C--       switch ON diagnostics of output-stream # n
88  c           IF (ndiag(j).NE.0) WRITE(0,*) myIter,j,ndiag(j),' ->',0              DO m=1,nActive(n)
89              ndiag(j) = 0  c             nd = jdiag(m,n)
90            ENDDO  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          ELSE
116  C--     switch OFF diagnostics of output-stream # n            nInterval = 1 + INT( -xInterval/FLOAT(averageCycle(n)) )
117            DO m=1,nActive(n)            nInterval = nInterval*averageCycle(n) + INT(xInterval) - 1
             j = jdiag(m,n)  
 c           IF (ndiag(j).NE.-1) WRITE(0,*) myIter,j,ndiag(j),' ->',-1  
             ndiag(j) = -1  
           ENDDO  
118          ENDIF          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         ENDIF
143    
144        ENDDO        ENDDO
145    
146  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
147    
148        _END_MASTER(myThid)        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  C-jmc: do we need a "BARRIER" at this point ?          DO bj=myByLo(myThid), myByHi(myThid)
168  c     _BARRIER           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        RETURN
204        END        END

Legend:
Removed from v.1.8  
changed lines
  Added in v.1.16

  ViewVC Help
Powered by ViewVC 1.1.22