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

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

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


Revision 1.12 - (hide annotations) (download)
Sun Jun 26 16:51:49 2005 UTC (18 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint57o_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint57v_post, checkpoint57r_post, checkpoint57n_post, checkpoint57p_post, checkpint57u_post, checkpoint57q_post, checkpoint57j_post, checkpoint57l_post
Changes since 1.11: +38 -35 lines
change pointers so that 1 diag. can be used several times (with # freq.)

1 jmc 1.12 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_switch_onoff.F,v 1.11 2005/05/23 19:31:09 molod Exp $
2 jmc 1.1 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 jmc 1.5 SUBROUTINE DIAGNOSTICS_SWITCH_ONOFF( myTime, myIter, myThid )
12 jmc 1.1
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 jmc 1.5 C myTime :: current Time of simulation ( s )
34 jmc 1.1 C myIter :: current Iteration number
35     C myThid :: my Thread Id number
36 jmc 1.6 _RL myTime
37 jmc 1.1 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     c CHARACTER*(MAX_LEN_MBUF) msgBuf
45 jmc 1.5 c INTEGER newIter
46 jmc 1.12 INTEGER m, n, nd
47     INTEGER bi, bj, ip, iSp
48 jmc 1.5 LOGICAL time4SnapShot
49     _RL phiSec, freqSec
50 jmc 1.9 LOGICAL dBugFlag
51 jmc 1.5 #ifdef ALLOW_FIZHI
52 molod 1.11 logical alarm2,alarm2next
53 molod 1.7 character *9 tagname
54 jmc 1.5 #endif
55    
56     LOGICAL DIFF_PHASE_MULTIPLE
57     EXTERNAL DIFF_PHASE_MULTIPLE
58 jmc 1.1
59     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
60    
61 jmc 1.5 c newIter = 1 + myIter
62 jmc 1.1 DO n = 1,nlists
63 jmc 1.5
64     IF ( freq(n).LT.0. ) THEN
65     C-- Select diagnostics list that uses instantaneous output
66    
67     freqSec = freq(n)
68     phiSec = phase(n)
69 molod 1.7 time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
70     & myTime, deltaTclock )
71 molod 1.3 #ifdef ALLOW_FIZHI
72 jmc 1.5 if( useFIZHI) then
73 molod 1.7 write(tagname,'(A,I2.2)')'diagtag',n
74 molod 1.11 time4SnapShot = alarm2next(tagname,deltaT)
75 jmc 1.5 endif
76 molod 1.3 #endif
77    
78 jmc 1.12 DO bj=myByLo(myThid), myByHi(myThid)
79     DO bi=myBxLo(myThid), myBxHi(myThid)
80     IF ( time4SnapShot ) THEN
81     C-- switch ON diagnostics of output-stream # n
82     DO m=1,nActive(n)
83     c nd = jdiag(m,n)
84     c IF (ndiag(nd).NE.0) WRITE(0,*) myIter,nd,ndiag(nd),' ->',0
85     ip = idiag(m,n)
86     IF (ip.GT.0) ndiag(ip,bi,bj) = 0
87     ENDDO
88     ELSE
89     C-- switch OFF diagnostics of output-stream # n
90     DO m=1,nActive(n)
91     c nd = jdiag(m,n)
92     c IF (ndiag(nd).NE.-1) WRITE(0,*) myIter,nd,ndiag(nd),' ->',-1
93     ip = idiag(m,n)
94     IF (ip.GT.0) ndiag(ip,bi,bj) = -1
95     ENDDO
96     ENDIF
97     ENDDO
98     ENDDO
99 jmc 1.1
100     ENDIF
101     ENDDO
102    
103 jmc 1.9 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
104    
105     DO n = 1,diagSt_nbLists
106    
107     IF ( diagSt_freq(n).LT.0. ) THEN
108     C-- Select diagnostics list that uses instantaneous output
109    
110     dBugFlag = debugLevel.GT.debLevB
111    
112     freqSec = diagSt_freq(n)
113     phiSec = diagSt_phase(n)
114     time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
115     & myTime, deltaTclock )
116    
117 jmc 1.10 #ifdef ALLOW_FIZHI
118     if( useFIZHI) then
119     write(tagname,'(A,I2.2)')'diagStg',n
120     time4SnapShot = alarm2(tagname)
121     endif
122     #endif
123    
124 jmc 1.9 DO bj=myByLo(myThid), myByHi(myThid)
125     DO bi=myBxLo(myThid), myBxHi(myThid)
126     dBugFlag = dBugFlag.AND.(bi.EQ.1.AND.bj.EQ.1.AND.myThid.EQ.1)
127     IF ( time4SnapShot ) THEN
128     C-- switch ON diagnostics of output-stream # n
129     DO m=1,diagSt_nbActv(n)
130 jmc 1.12 iSp = iSdiag(m,n)
131     IF (iSp.GT.0) THEN
132     nd = jSdiag(m,n)
133     IF (dBugFlag.AND.qSdiag(0,0,iSp,bi,bj).NE. 0.)
134 jmc 1.9 & WRITE(0,'(I8,I4,3A,1PE10.3,A,I3)') myIter,
135 jmc 1.12 & nd,' ',cdiag(nd),' :',qSdiag(0,0,iSp,bi,bj),' ->', 0
136     qSdiag(0,0,iSp,bi,bj) = 0.
137     ENDIF
138 jmc 1.9 ENDDO
139     ELSE
140     C-- switch OFF diagnostics of output-stream # n
141     DO m=1,diagSt_nbActv(n)
142 jmc 1.12 iSp = iSdiag(m,n)
143     IF (iSp.GT.0) THEN
144     nd = jSdiag(m,n)
145     IF (dBugFlag.AND.qSdiag(0,0,iSp,bi,bj).NE.-1.)
146 jmc 1.9 & WRITE(0,'(I8,I4,3A,1PE10.3,A,I3)') myIter,
147 jmc 1.12 & nd,' ',cdiag(nd),' :',qSdiag(0,0,iSp,bi,bj),' ->',-1
148     qSdiag(0,0,iSp,bi,bj) = -1.
149     ENDIF
150 jmc 1.9 ENDDO
151     ENDIF
152     ENDDO
153     ENDDO
154    
155     ENDIF
156     ENDDO
157    
158 jmc 1.1 RETURN
159     END

  ViewVC Help
Powered by ViewVC 1.1.22