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

Contents of /MITgcm/pkg/diagnostics/diagnostics_write.F

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


Revision 1.39 - (show annotations) (download)
Tue Jun 2 20:58:22 2015 UTC (8 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65n, checkpoint65o, checkpoint65m, HEAD
Changes since 1.38: +4 -2 lines
add few _BARRIER around anyupdate of "diag_pkgStatus"

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_write.F,v 1.38 2013/08/14 00:57:33 jmc Exp $
2 C $Name: $
3
4 #include "DIAG_OPTIONS.h"
5
6 SUBROUTINE DIAGNOSTICS_WRITE (
7 I modelEnd,
8 I myTime, myIter, myThid )
9 C***********************************************************************
10 C Purpose
11 C -------
12 C Output sequence for the (multiple) diagnostics output files
13 C
14 C Arguments Description
15 C ----------------------
16 C modelEnd :: true if call at end of model run.
17 C myTime :: Current time of simulation ( s )
18 C myIter :: Current Iteration Number
19 C myThid :: my Thread Id number
20 C***********************************************************************
21 IMPLICIT NONE
22 #include "EEPARAMS.h"
23 #include "SIZE.h"
24 #include "DIAGNOSTICS_SIZE.h"
25 #include "PARAMS.h"
26 #include "DIAGNOSTICS.h"
27
28 C !INPUT PARAMETERS:
29 LOGICAL modelEnd
30 _RL myTime
31 INTEGER myIter, myThid
32
33 C !FUNCTIONS:
34 LOGICAL DIFF_PHASE_MULTIPLE
35 EXTERNAL DIFF_PHASE_MULTIPLE
36 #ifdef ALLOW_FIZHI
37 LOGICAL ALARM2
38 EXTERNAL ALARM2
39 #endif
40
41 c Local variables
42 c ===============
43 INTEGER n
44 INTEGER myItM1, wrIter
45 LOGICAL dump2fileNow, write2file
46 _RL phiSec, freqSec, wrTime
47 #ifdef ALLOW_FIZHI
48 CHARACTER *9 tagname
49 #endif
50
51 IF ( myIter.NE.nIter0 ) THEN
52 myItM1 = myIter - 1
53
54 C***********************************************************************
55 C*** Check to see if its time for Diagnostic Output ***
56 C***********************************************************************
57
58 write2file = .FALSE.
59 DO n = 1,nlists
60 freqSec = freq(n)
61 phiSec = phase(n)
62
63 IF ( freqSec.LT.0. ) THEN
64 C-- write snap-shot with suffix = myIter to be consistent with
65 C time-average diagnostics (e.g., freq=-1 & freq=1):
66 c wrIter = myIter
67 c wrTime = myTime
68 C-- write snap-shot with suffix = myIter-1 to be consistent with
69 C state-variable time-step:
70 wrIter = myItM1
71 wrTime = myTime - deltaTClock
72 ELSE
73 wrIter = myIter
74 wrTime = myTime
75 ENDIF
76 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
77 & wrTime, deltaTClock )
78 #ifdef ALLOW_FIZHI
79 IF ( useFIZHI ) THEN
80 WRITE(tagname,'(A,I2.2)')'diagtag',n
81 dump2fileNow = ALARM2(tagname)
82 ENDIF
83 #endif
84 #ifdef ALLOW_CAL
85 IF ( useCAL ) THEN
86 CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
87 U dump2fileNow,
88 I wrTime, myIter, myThid )
89 ENDIF
90 #endif /* ALLOW_CAL */
91 IF ( dumpAtLast .AND. modelEnd
92 & .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
93 IF ( dump2fileNow ) THEN
94 write2file = .TRUE.
95 CALL DIAGNOSTICS_OUT(n,wrTime,wrIter,myThid)
96 ENDIF
97 ENDDO
98
99 C--- Check to see if its time for Statistics Diag. Output
100
101 DO n = 1,diagSt_nbLists
102 freqSec = diagSt_freq(n)
103 phiSec = diagSt_phase(n)
104
105 IF ( freqSec.LT.0. ) THEN
106 C-- write snap-shot with suffix = myIter to be consistent with
107 C time-average diagnostics (e.g., freq=-1 & freq=1):
108 c wrIter = myIter
109 c wrTime = myTime
110 C-- write snap-shot with suffix = myIter-1 to be consistent with
111 C state-variable time-step:
112 wrIter = myItM1
113 wrTime = myTime - deltaTClock
114 ELSE
115 wrIter = myIter
116 wrTime = myTime
117 ENDIF
118 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
119 & wrTime, deltaTClock )
120 #ifdef ALLOW_FIZHI
121 IF ( useFIZHI ) THEN
122 WRITE(tagname,'(A,I2.2)')'diagStg',n
123 dump2fileNow = ALARM2(tagname)
124 ENDIF
125 #endif
126 #ifdef ALLOW_CAL
127 IF ( useCAL ) THEN
128 CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
129 U dump2fileNow,
130 I wrTime, myIter, myThid )
131 ENDIF
132 #endif /* ALLOW_CAL */
133 IF ( dumpAtLast .AND. modelEnd
134 & .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
135 IF ( dump2fileNow ) THEN
136 write2file = .TRUE.
137 CALL DIAGSTATS_OUTPUT(n,wrTime,wrIter,myThid)
138 ENDIF
139 ENDDO
140
141 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
142
143 IF ( write2file ) THEN
144 IF ( debugLevel.GE.debLevC ) THEN
145 CALL DIAGNOSTICS_SUMMARY( myTime, myIter, myThid )
146 ENDIF
147 C- wait for everyone before setting arrays to zero:
148 _BARRIER
149 ENDIF
150 IF ( modelEnd ) THEN
151 C- Track diagnostics pkg activation status:
152 c IF ( diag_pkgStatus.NE.ready2fillDiags ) STOP
153 _BARRIER
154 _BEGIN_MASTER(myThid)
155 diag_pkgStatus = 99
156 _END_MASTER(myThid)
157 _BARRIER
158 C Close all Stat-diags output files
159 CALL DIAGSTATS_CLOSE_IO( myThid )
160 ENDIF
161
162 C-- Clear storage space:
163
164 DO n = 1,nlists
165 freqSec = freq(n)
166 phiSec = phase(n)
167
168 wrTime = myTime
169 IF ( freqSec.LT.0. ) wrTime = myTime - deltaTClock
170 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
171 & wrTime, deltaTClock )
172 #ifdef ALLOW_FIZHI
173 IF ( useFIZHI ) THEN
174 WRITE(tagname,'(A,I2.2)')'diagtag',n
175 dump2fileNow = ALARM2(tagname)
176 ENDIF
177 #endif
178 #ifdef ALLOW_CAL
179 IF ( useCAL ) THEN
180 CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
181 U dump2fileNow,
182 I wrTime, myIter, myThid )
183 ENDIF
184 #endif /* ALLOW_CAL */
185 IF ( dumpAtLast .AND. modelEnd
186 & .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
187 IF ( dump2fileNow ) CALL DIAGNOSTICS_CLEAR(n,myThid)
188 ENDDO
189
190 DO n = 1,diagSt_nbLists
191 freqSec = diagSt_freq(n)
192 phiSec = diagSt_phase(n)
193 wrTime = myTime
194 IF ( freqSec.LT.0. ) wrTime = myTime - deltaTClock
195 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
196 & wrTime, deltaTClock )
197 #ifdef ALLOW_FIZHI
198 IF ( useFIZHI ) THEN
199 WRITE(tagname,'(A,I2.2)')'diagStg',n
200 dump2fileNow = ALARM2(tagname)
201 ENDIF
202 #endif
203 #ifdef ALLOW_CAL
204 IF ( useCAL ) THEN
205 CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
206 U dump2fileNow,
207 I wrTime, myIter, myThid )
208 ENDIF
209 #endif /* ALLOW_CAL */
210 IF ( dumpAtLast .AND. modelEnd
211 & .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
212 IF ( dump2fileNow ) CALL DIAGSTATS_CLEAR( n, myThid )
213 ENDDO
214
215 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
216 ENDIF
217
218 RETURN
219 END

  ViewVC Help
Powered by ViewVC 1.1.22