/[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.19 - (show annotations) (download)
Sun May 22 22:53:36 2005 UTC (18 years, 11 months ago) by dimitri
Branch: MAIN
Changes since 1.18: +18 -1 lines
Bug fix for CalendarDump flag.  Monthly fields were not being reset at
the correct time.  Will move to subroutine in pkg/cal ASAP.  Thank JM
for spotting problem.

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_write.F,v 1.18 2005/05/21 22:33:40 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 "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 ) THEN
104 CALL DIAGNOSTICS_OUT(n,wrIter,myThid)
105 ENDIF
106 ENDDO
107
108 C--- Check to see IF its time for Statistics Diag. Output
109
110 DO n = 1,diagSt_nbLists
111 freqSec = diagSt_freq(n)
112 phiSec = diagSt_phase(n)
113
114 IF ( freqSec.LT.0. ) THEN
115 C-- write snap-shot with suffix = myIter to be consistent with
116 C time-average diagnostics (e.g., freq=-1 & freq=1):
117 c wrIter = myIter
118 c wrTime = myTime
119 C-- write snap-shot with suffix = myIter-1 to be consistent with
120 C state-variable time-step:
121 wrIter = myItM1
122 wrTime = myTime - deltaTclock
123 ELSE
124 wrIter = myIter
125 wrTime = myTime
126 ENDIF
127 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
128 & wrTime, deltaTclock )
129 #ifdef ALLOW_FIZHI
130 if( useFIZHI) then
131 write(tagname,'(A,I2.2)')'diagStg',n
132 dump2fileNow = alarm2(tagname)
133 endif
134 #endif
135
136 IF ( dump2fileNow ) THEN
137 CALL DIAGSTATS_OUTPUT(n,wrIter,myThid)
138 ENDIF
139 ENDDO
140
141 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
142 C- wait for everyone before setting arrays to zero:
143 _BARRIER
144
145 C-- Clear storage space:
146
147 DO n = 1,nlists
148 freqSec = freq(n)
149 phiSec = phase(n)
150
151 wrTime = myTime
152 IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
153 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
154 & wrTime, deltaTclock )
155 #ifdef ALLOW_FIZHI
156 if( useFIZHI) then
157 write(tagname,'(A,I2.2)')'diagtag',n
158 dump2fileNow = alarm2(tagname)
159 endif
160 #endif
161
162 #ifdef ALLOW_CAL
163 IF ( calendarDumps .AND. (
164 & ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.
165 & ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN
166 C-- Convert approximate months (30-31 days) and years (360-372 days)
167 C to exact calendar months and years.
168 dump2fileNow = .FALSE.
169 C- Monthly freqSec:
170 IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.
171 & (thisdate(1)-prevdate(1)).GT.50 ) dump2fileNow = .TRUE.
172 C- Yearly freqSec:
173 IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.
174 & (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.
175 ENDIF
176 #endif
177
178 IF ( dump2fileNow ) CALL CLRINDX(n,myThid)
179 ENDDO
180
181 DO n = 1,diagSt_nbLists
182 freqSec = diagSt_freq(n)
183 phiSec = diagSt_phase(n)
184 wrTime = myTime
185 IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
186 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
187 & wrTime, deltaTclock )
188 #ifdef ALLOW_FIZHI
189 if( useFIZHI) then
190 write(tagname,'(A,I2.2)')'diagStg',n
191 dump2fileNow = alarm2(tagname)
192 endif
193 #endif
194 IF ( dump2fileNow ) CALL DIAGSTATS_CLEAR(n,myThid)
195 ENDDO
196
197 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
198 ENDIF
199
200 RETURN
201 END

  ViewVC Help
Powered by ViewVC 1.1.22