/[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.34 - (show annotations) (download)
Sat Jun 11 23:29:44 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62z
Changes since 1.33: +2 -2 lines
move MNC code out of diagnostics_out.F into 2 S/R (in diagnostics_mnc_out.F)

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_write.F,v 1.33 2011/06/06 15:42:58 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 Local variables
34 c ===============
35 INTEGER n
36 INTEGER myItM1, wrIter
37 LOGICAL dump2fileNow, write2file
38 _RL phiSec, freqSec, wrTime
39 #ifdef ALLOW_FIZHI
40 LOGICAL alarm2
41 CHARACTER *9 tagname
42 #endif
43
44 LOGICAL DIFF_PHASE_MULTIPLE
45 EXTERNAL DIFF_PHASE_MULTIPLE
46
47 IF ( myIter.NE.nIter0 ) THEN
48 myItM1 = myIter - 1
49
50 C***********************************************************************
51 C*** Check to see if its time for Diagnostic Output ***
52 C***********************************************************************
53
54 write2file = .FALSE.
55 DO n = 1,nlists
56 freqSec = freq(n)
57 phiSec = phase(n)
58
59 IF ( freqSec.LT.0. ) THEN
60 C-- write snap-shot with suffix = myIter to be consistent with
61 C time-average diagnostics (e.g., freq=-1 & freq=1):
62 c wrIter = myIter
63 c wrTime = myTime
64 C-- write snap-shot with suffix = myIter-1 to be consistent with
65 C state-variable time-step:
66 wrIter = myItM1
67 wrTime = myTime - deltaTclock
68 ELSE
69 wrIter = myIter
70 wrTime = myTime
71 ENDIF
72 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
73 & wrTime, deltaTclock )
74 #ifdef ALLOW_FIZHI
75 IF ( useFIZHI ) THEN
76 WRITE(tagname,'(A,I2.2)')'diagtag',n
77 dump2fileNow = alarm2(tagname)
78 ENDIF
79 #endif
80 #ifdef ALLOW_CAL
81 IF ( useCAL ) THEN
82 CALL CAL_TIME2DUMP( freqSec, deltaTClock,
83 U dump2fileNow,
84 I myTime, myIter, myThid )
85 ENDIF
86 #endif /* ALLOW_CAL */
87 IF ( dumpAtLast .AND. modelEnd
88 & .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
89 IF ( dump2fileNow ) THEN
90 write2file = .TRUE.
91 CALL DIAGNOSTICS_OUT(n,wrTime,wrIter,myThid)
92 ENDIF
93 ENDDO
94
95 C--- Check to see if its time for Statistics Diag. Output
96
97 DO n = 1,diagSt_nbLists
98 freqSec = diagSt_freq(n)
99 phiSec = diagSt_phase(n)
100
101 IF ( freqSec.LT.0. ) THEN
102 C-- write snap-shot with suffix = myIter to be consistent with
103 C time-average diagnostics (e.g., freq=-1 & freq=1):
104 c wrIter = myIter
105 c wrTime = myTime
106 C-- write snap-shot with suffix = myIter-1 to be consistent with
107 C state-variable time-step:
108 wrIter = myItM1
109 wrTime = myTime - deltaTclock
110 ELSE
111 wrIter = myIter
112 wrTime = myTime
113 ENDIF
114 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
115 & wrTime, deltaTclock )
116 #ifdef ALLOW_FIZHI
117 IF ( useFIZHI ) THEN
118 WRITE(tagname,'(A,I2.2)')'diagStg',n
119 dump2fileNow = alarm2(tagname)
120 ENDIF
121 #endif
122 IF ( dumpAtLast .AND. modelEnd
123 & .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
124 IF ( dump2fileNow ) THEN
125 write2file = .TRUE.
126 CALL DIAGSTATS_OUTPUT(n,wrTime,wrIter,myThid)
127 ENDIF
128 ENDDO
129
130 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
131
132 IF ( write2file ) THEN
133 IF ( debugLevel.GE.debLevC ) THEN
134 CALL DIAGNOSTICS_SUMMARY( myTime, myIter, myThid )
135 ENDIF
136 C- wait for everyone before setting arrays to zero:
137 _BARRIER
138 ENDIF
139 IF ( modelEnd ) THEN
140 C Close all Stat-diags output files
141 CALL DIAGSTATS_CLOSE_IO( myThid )
142 ENDIF
143
144 C-- Clear storage space:
145
146 DO n = 1,nlists
147 freqSec = freq(n)
148 phiSec = phase(n)
149
150 wrTime = myTime
151 IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
152 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
153 & wrTime, deltaTclock )
154 #ifdef ALLOW_FIZHI
155 IF ( useFIZHI ) THEN
156 WRITE(tagname,'(A,I2.2)')'diagtag',n
157 dump2fileNow = alarm2(tagname)
158 ENDIF
159 #endif
160 #ifdef ALLOW_CAL
161 IF ( useCAL ) THEN
162 CALL CAL_TIME2DUMP( freqSec, deltaTClock,
163 U dump2fileNow,
164 I myTime, myIter, myThid )
165 ENDIF
166 #endif /* ALLOW_CAL */
167 IF ( dumpAtLast .AND. modelEnd
168 & .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
169 IF ( dump2fileNow ) CALL DIAGNOSTICS_CLEAR(n,myThid)
170 ENDDO
171
172 DO n = 1,diagSt_nbLists
173 freqSec = diagSt_freq(n)
174 phiSec = diagSt_phase(n)
175 wrTime = myTime
176 IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
177 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
178 & wrTime, deltaTclock )
179 #ifdef ALLOW_FIZHI
180 IF ( useFIZHI ) THEN
181 WRITE(tagname,'(A,I2.2)')'diagStg',n
182 dump2fileNow = alarm2(tagname)
183 ENDIF
184 #endif
185 IF ( dumpAtLast .AND. modelEnd
186 & .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
187 IF ( dump2fileNow ) CALL DIAGSTATS_CLEAR( n, myThid )
188 ENDDO
189
190 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
191 ENDIF
192
193 RETURN
194 END

  ViewVC Help
Powered by ViewVC 1.1.22