/[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.22 - (show annotations) (download)
Tue Jun 14 23:06:15 2005 UTC (18 years, 10 months ago) by molod
Branch: MAIN
CVS Tags: checkpoint57i_post
Changes since 1.21: +9 -5 lines
Add diagnostics flag for output at last time step

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_write.F,v 1.21 2005/06/14 22:30:02 molod 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 "SIZE.h"
20 #include "DIAGNOSTICS_SIZE.h"
21 #include "DIAGNOSTICS.h"
22 #include "EEPARAMS.h"
23 #include "PARAMS.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
34 _RL phiSec, freqSec, wrTime
35 #ifdef ALLOW_CAL
36 INTEGER thisdate(4), prevdate(4)
37 #endif
38 #ifdef ALLOW_FIZHI
39 logical alarm2
40 character *9 tagname
41 #endif
42
43 LOGICAL DIFF_PHASE_MULTIPLE
44 EXTERNAL DIFF_PHASE_MULTIPLE
45
46 IF ( myIter.NE.nIter0 ) THEN
47 myItM1 = myIter - 1
48
49 C***********************************************************************
50 C*** Check to see IF its time for Diagnostic Output ***
51 C***********************************************************************
52
53 #ifdef ALLOW_CAL
54 IF ( calendarDumps ) THEN
55 C- Determine calendar dates for this and previous time step.
56 call cal_GetDate(myiter ,mytime ,thisdate,mythid)
57 call cal_GetDate(myiter-1,mytime-deltaTClock,prevdate,mythid)
58 ENDIF
59 #endif
60
61 DO n = 1,nlists
62 freqSec = freq(n)
63 phiSec = phase(n)
64
65 IF ( freqSec.LT.0. ) THEN
66 C-- write snap-shot with suffix = myIter to be consistent with
67 C time-average diagnostics (e.g., freq=-1 & freq=1):
68 c wrIter = myIter
69 c wrTime = myTime
70 C-- write snap-shot with suffix = myIter-1 to be consistent with
71 C state-variable time-step:
72 wrIter = myItM1
73 wrTime = myTime - deltaTclock
74 ELSE
75 wrIter = myIter
76 wrTime = myTime
77 ENDIF
78 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
79 & wrTime, deltaTclock )
80 #ifdef ALLOW_FIZHI
81 if( useFIZHI) then
82 write(tagname,'(A,I2.2)')'diagtag',n
83 dump2fileNow = alarm2(tagname)
84 endif
85 #endif
86
87 #ifdef ALLOW_CAL
88 IF ( calendarDumps .AND. (
89 & ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.
90 & ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN
91 C-- Convert approximate months (30-31 days) and years (360-372 days)
92 C to exact calendar months and years.
93 dump2fileNow = .FALSE.
94 C- Monthly freqSec:
95 IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.
96 & (thisdate(1)-prevdate(1)).GT.50 ) dump2fileNow = .TRUE.
97 C- Yearly freqSec:
98 IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.
99 & (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.
100 ENDIF
101 #endif
102
103 IF ( dump2fileNow .or. ((myIter.eq.nIter0+nTimeSteps).and.
104 . dumpatlast) ) THEN
105 CALL DIAGNOSTICS_OUT(n,wrIter,myTime,myThid)
106 ENDIF
107 ENDDO
108
109 C--- Check to see IF its time for Statistics Diag. Output
110
111 DO n = 1,diagSt_nbLists
112 freqSec = diagSt_freq(n)
113 phiSec = diagSt_phase(n)
114
115 IF ( freqSec.LT.0. ) THEN
116 C-- write snap-shot with suffix = myIter to be consistent with
117 C time-average diagnostics (e.g., freq=-1 & freq=1):
118 c wrIter = myIter
119 c wrTime = myTime
120 C-- write snap-shot with suffix = myIter-1 to be consistent with
121 C state-variable time-step:
122 wrIter = myItM1
123 wrTime = myTime - deltaTclock
124 ELSE
125 wrIter = myIter
126 wrTime = myTime
127 ENDIF
128 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
129 & wrTime, deltaTclock )
130 #ifdef ALLOW_FIZHI
131 if( useFIZHI) then
132 write(tagname,'(A,I2.2)')'diagStg',n
133 dump2fileNow = alarm2(tagname)
134 endif
135 #endif
136
137 IF ( dump2fileNow .or. ((myIter.eq.nIter0+nTimeSteps).and.
138 . dumpatlast) ) THEN
139 CALL DIAGSTATS_OUTPUT(n,wrIter,myThid)
140 ENDIF
141 ENDDO
142
143 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
144 C- wait for everyone before setting arrays to zero:
145 _BARRIER
146
147 C-- Clear storage space:
148
149 DO n = 1,nlists
150 freqSec = freq(n)
151 phiSec = phase(n)
152
153 wrTime = myTime
154 IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
155 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
156 & wrTime, deltaTclock )
157 #ifdef ALLOW_FIZHI
158 if( useFIZHI) then
159 write(tagname,'(A,I2.2)')'diagtag',n
160 dump2fileNow = alarm2(tagname)
161 endif
162 #endif
163
164 #ifdef ALLOW_CAL
165 IF ( calendarDumps .AND. (
166 & ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.
167 & ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN
168 C-- Convert approximate months (30-31 days) and years (360-372 days)
169 C to exact calendar months and years.
170 dump2fileNow = .FALSE.
171 C- Monthly freqSec:
172 IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.
173 & (thisdate(1)-prevdate(1)).GT.50 ) dump2fileNow = .TRUE.
174 C- Yearly freqSec:
175 IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.
176 & (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.
177 ENDIF
178 #endif
179
180 IF ( dump2fileNow .or. ((myIter.eq.nIter0+nTimeSteps).and.
181 . dumpatlast) )
182 . CALL CLRINDX(n,myThid)
183 ENDDO
184
185 DO n = 1,diagSt_nbLists
186 freqSec = diagSt_freq(n)
187 phiSec = diagSt_phase(n)
188 wrTime = myTime
189 IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
190 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
191 & wrTime, deltaTclock )
192 #ifdef ALLOW_FIZHI
193 if( useFIZHI) then
194 write(tagname,'(A,I2.2)')'diagStg',n
195 dump2fileNow = alarm2(tagname)
196 endif
197 #endif
198 IF ( dump2fileNow .or. ((myIter.eq.nIter0+nTimeSteps).and.
199 . dumpatlast) )
200 . CALL DIAGSTATS_CLEAR(n,myThid)
201 ENDDO
202
203 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
204 ENDIF
205
206 RETURN
207 END

  ViewVC Help
Powered by ViewVC 1.1.22