/[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.9 - (show annotations) (download)
Fri May 20 07:28:50 2005 UTC (18 years, 11 months ago) by jmc
Branch: MAIN
Changes since 1.8: +47 -10 lines
Add new capability: compute & write Global/Regional & per level statistics

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_switch_onoff.F,v 1.8 2005/05/17 00:22:00 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 c CHARACTER*(MAX_LEN_MBUF) msgBuf
45 c INTEGER newIter
46 INTEGER j, m, n
47 INTEGER bi, bj, iSp
48 LOGICAL time4SnapShot
49 _RL phiSec, freqSec
50 LOGICAL dBugFlag
51 #ifdef ALLOW_FIZHI
52 logical alarm2
53 character *9 tagname
54 #endif
55
56 LOGICAL DIFF_PHASE_MULTIPLE
57 EXTERNAL DIFF_PHASE_MULTIPLE
58
59 _BEGIN_MASTER(myThid)
60
61 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
62
63 c newIter = 1 + myIter
64 DO n = 1,nlists
65
66 IF ( freq(n).LT.0. ) THEN
67 C-- Select diagnostics list that uses instantaneous output
68
69 freqSec = freq(n)
70 phiSec = phase(n)
71 time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
72 & myTime, deltaTclock )
73 #ifdef ALLOW_FIZHI
74 if( useFIZHI) then
75 write(tagname,'(A,I2.2)')'diagtag',n
76 time4SnapShot = alarm2(tagname)
77 endif
78 #endif
79
80 IF ( time4SnapShot ) THEN
81 C-- switch ON diagnostics of output-stream # n
82 DO m=1,nActive(n)
83 j = jdiag(m,n)
84 c IF (ndiag(j).NE.0) WRITE(0,*) myIter,j,ndiag(j),' ->',0
85 ndiag(j) = 0
86 ENDDO
87 ELSE
88 C-- switch OFF diagnostics of output-stream # n
89 DO m=1,nActive(n)
90 j = jdiag(m,n)
91 c IF (ndiag(j).NE.-1) WRITE(0,*) myIter,j,ndiag(j),' ->',-1
92 ndiag(j) = -1
93 ENDDO
94 ENDIF
95
96 ENDIF
97 ENDDO
98
99 _END_MASTER(myThid)
100
101 C-jmc: do we need a "BARRIER" at this point ?
102 c _BARRIER
103
104 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
105
106 DO n = 1,diagSt_nbLists
107
108 IF ( diagSt_freq(n).LT.0. ) THEN
109 C-- Select diagnostics list that uses instantaneous output
110
111 dBugFlag = debugLevel.GT.debLevB
112
113 freqSec = diagSt_freq(n)
114 phiSec = diagSt_phase(n)
115 time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
116 & myTime, deltaTclock )
117
118 DO bj=myByLo(myThid), myByHi(myThid)
119 DO bi=myBxLo(myThid), myBxHi(myThid)
120 dBugFlag = dBugFlag.AND.(bi.EQ.1.AND.bj.EQ.1.AND.myThid.EQ.1)
121 IF ( time4SnapShot ) THEN
122 C-- switch ON diagnostics of output-stream # n
123 DO m=1,diagSt_nbActv(n)
124 j = jSdiag(m,n)
125 iSp = iSdiag(j)
126 IF (dBugFlag.AND.qSdiag(0,0,iSp,bi,bj).NE. 0.)
127 & WRITE(0,'(I8,I4,3A,1PE10.3,A,I3)') myIter,
128 & j,' ',cdiag(j),' :',qSdiag(0,0,iSp,bi,bj),' ->', 0
129 qSdiag(0,0,iSp,bi,bj) = 0.
130 ENDDO
131 ELSE
132 C-- switch OFF diagnostics of output-stream # n
133 DO m=1,diagSt_nbActv(n)
134 j = jSdiag(m,n)
135 iSp = iSdiag(j)
136 IF (dBugFlag.AND.qSdiag(0,0,iSp,bi,bj).NE.-1.)
137 & WRITE(0,'(I8,I4,3A,1PE10.3,A,I3)') myIter,
138 & j,' ',cdiag(j),' :',qSdiag(0,0,iSp,bi,bj),' ->',-1
139 qSdiag(0,0,iSp,bi,bj) = -1.
140 ENDDO
141 ENDIF
142 ENDDO
143 ENDDO
144
145 ENDIF
146 ENDDO
147
148 RETURN
149 END

  ViewVC Help
Powered by ViewVC 1.1.22