/[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.30 - (show annotations) (download)
Wed Jan 3 00:29:59 2007 UTC (17 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint60, checkpoint61, checkpoint62, checkpoint58x_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58y_post, checkpoint58v_post, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.29: +15 -13 lines
do not apply dumAtLast to snap-shot output (since they are not filled-in)

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

  ViewVC Help
Powered by ViewVC 1.1.22