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

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

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


Revision 1.24 - (hide annotations) (download)
Wed Jul 6 02:13:52 2005 UTC (18 years, 10 months ago) by edhill
Branch: MAIN
Changes since 1.23: +2 -2 lines
 o add mnc output capability to diagnostics/diagstat and update
   our cvsignore files for the ACSII output generated

1 edhill 1.24 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_write.F,v 1.23 2005/06/26 16:51:49 jmc Exp $
2 edhill 1.6 C $Name: $
3    
4 edhill 1.7 #include "DIAG_OPTIONS.h"
5    
6 jmc 1.23 SUBROUTINE DIAGNOSTICS_WRITE ( myTime, myIter, myThid )
7 molod 1.1 C***********************************************************************
8     C Purpose
9     C -------
10 molod 1.2 C Output sequence for the (multiple) diagnostics output files
11 molod 1.1 C
12     C Arguments Description
13     C ----------------------
14 jmc 1.9 C myTime :: Current time of simulation ( s )
15     C myIter :: Current Iteration Number
16 jmc 1.23 C myThid :: my Thread Id number
17 molod 1.1 C***********************************************************************
18 jmc 1.8 IMPLICIT NONE
19 molod 1.1 #include "SIZE.h"
20 jmc 1.8 #include "DIAGNOSTICS_SIZE.h"
21     #include "DIAGNOSTICS.h"
22 molod 1.4 #include "EEPARAMS.h"
23     #include "PARAMS.h"
24 molod 1.1
25 jmc 1.14 C !INPUT PARAMETERS:
26 jmc 1.9 _RL myTime
27 jmc 1.8 INTEGER myIter, myThid
28 molod 1.1
29     c Local variables
30     c ===============
31 jmc 1.8 INTEGER n
32 jmc 1.9 INTEGER myItM1, wrIter
33 jmc 1.23 LOGICAL dump2fileNow, write2file
34 jmc 1.14 _RL phiSec, freqSec, wrTime
35     #ifdef ALLOW_CAL
36 dimitri 1.10 INTEGER thisdate(4), prevdate(4)
37 jmc 1.14 #endif
38     #ifdef ALLOW_FIZHI
39 molod 1.16 logical alarm2
40 molod 1.15 character *9 tagname
41 jmc 1.14 #endif
42    
43     LOGICAL DIFF_PHASE_MULTIPLE
44     EXTERNAL DIFF_PHASE_MULTIPLE
45 jmc 1.8
46 jmc 1.9 IF ( myIter.NE.nIter0 ) THEN
47     myItM1 = myIter - 1
48 molod 1.1
49     C***********************************************************************
50 jmc 1.8 C*** Check to see IF its time for Diagnostic Output ***
51 molod 1.1 C***********************************************************************
52    
53 dimitri 1.10 #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 jmc 1.23 write2file = .FALSE.
62 jmc 1.8 DO n = 1,nlists
63 jmc 1.14 freqSec = freq(n)
64     phiSec = phase(n)
65 molod 1.12
66 jmc 1.14 IF ( freqSec.LT.0. ) THEN
67 jmc 1.23 C-- write snap-shot with suffix = myIter to be consistent with
68 jmc 1.9 C time-average diagnostics (e.g., freq=-1 & freq=1):
69     c wrIter = myIter
70 jmc 1.14 c wrTime = myTime
71 jmc 1.9 C-- write snap-shot with suffix = myIter-1 to be consistent with
72     C state-variable time-step:
73     wrIter = myItM1
74 jmc 1.14 wrTime = myTime - deltaTclock
75 jmc 1.9 ELSE
76     wrIter = myIter
77 jmc 1.14 wrTime = myTime
78 jmc 1.9 ENDIF
79 jmc 1.23 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
80 jmc 1.14 & wrTime, deltaTclock )
81 molod 1.15 #ifdef ALLOW_FIZHI
82     if( useFIZHI) then
83     write(tagname,'(A,I2.2)')'diagtag',n
84     dump2fileNow = alarm2(tagname)
85     endif
86     #endif
87 dimitri 1.10
88     #ifdef ALLOW_CAL
89     IF ( calendarDumps .AND. (
90     & ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.
91 dimitri 1.11 & ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN
92 dimitri 1.10 C-- Convert approximate months (30-31 days) and years (360-372 days)
93     C to exact calendar months and years.
94 dimitri 1.11 dump2fileNow = .FALSE.
95 dimitri 1.10 C- Monthly freqSec:
96     IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.
97 dimitri 1.11 & (thisdate(1)-prevdate(1)).GT.50 ) dump2fileNow = .TRUE.
98 dimitri 1.10 C- Yearly freqSec:
99     IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.
100 dimitri 1.11 & (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.
101 dimitri 1.10 ENDIF
102     #endif
103    
104 jmc 1.23 IF ( dump2fileNow .OR.
105     & (myTime.EQ.endTime .AND. dumpatlast) ) THEN
106     write2file = .TRUE.
107 edhill 1.20 CALL DIAGNOSTICS_OUT(n,wrIter,myTime,myThid)
108 jmc 1.8 ENDIF
109     ENDDO
110    
111 jmc 1.23 C--- Check to see IF its time for Statistics Diag. Output
112 jmc 1.17
113     DO n = 1,diagSt_nbLists
114     freqSec = diagSt_freq(n)
115     phiSec = diagSt_phase(n)
116    
117     IF ( freqSec.LT.0. ) THEN
118 jmc 1.23 C-- write snap-shot with suffix = myIter to be consistent with
119 jmc 1.17 C time-average diagnostics (e.g., freq=-1 & freq=1):
120     c wrIter = myIter
121     c wrTime = myTime
122     C-- write snap-shot with suffix = myIter-1 to be consistent with
123     C state-variable time-step:
124     wrIter = myItM1
125     wrTime = myTime - deltaTclock
126     ELSE
127     wrIter = myIter
128     wrTime = myTime
129     ENDIF
130 jmc 1.23 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
131 jmc 1.17 & wrTime, deltaTclock )
132 jmc 1.18 #ifdef ALLOW_FIZHI
133     if( useFIZHI) then
134     write(tagname,'(A,I2.2)')'diagStg',n
135     dump2fileNow = alarm2(tagname)
136     endif
137     #endif
138    
139 jmc 1.23 IF ( dump2fileNow .OR.
140     & (myTime.EQ.endTime .AND. dumpatlast) ) THEN
141     write2file = .TRUE.
142 edhill 1.24 CALL DIAGSTATS_OUTPUT(n,wrIter,myTime,myThid)
143 jmc 1.17 ENDIF
144     ENDDO
145    
146     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
147 jmc 1.23
148     IF ( write2file ) THEN
149     IF ( debugLevel.GE.debLevB ) THEN
150     CALL DIAGNOSTICS_SUMMARY( myTime, myIter, myThid )
151     ENDIF
152     C- wait for everyone before setting arrays to zero:
153     _BARRIER
154     ENDIF
155 jmc 1.17
156     C-- Clear storage space:
157    
158 jmc 1.8 DO n = 1,nlists
159 jmc 1.14 freqSec = freq(n)
160     phiSec = phase(n)
161 jmc 1.17
162 jmc 1.14 wrTime = myTime
163     IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
164 jmc 1.23 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
165 jmc 1.14 & wrTime, deltaTclock )
166 molod 1.15 #ifdef ALLOW_FIZHI
167     if( useFIZHI) then
168     write(tagname,'(A,I2.2)')'diagtag',n
169     dump2fileNow = alarm2(tagname)
170     endif
171     #endif
172 dimitri 1.19
173     #ifdef ALLOW_CAL
174     IF ( calendarDumps .AND. (
175     & ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.
176     & ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN
177     C-- Convert approximate months (30-31 days) and years (360-372 days)
178     C to exact calendar months and years.
179     dump2fileNow = .FALSE.
180     C- Monthly freqSec:
181     IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.
182     & (thisdate(1)-prevdate(1)).GT.50 ) dump2fileNow = .TRUE.
183     C- Yearly freqSec:
184     IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.
185     & (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.
186     ENDIF
187     #endif
188    
189 jmc 1.23 IF ( dump2fileNow .OR.
190     & (myTime.EQ.endTime .AND. dumpatlast)
191     & ) CALL DIAGNOSTICS_CLEAR(n,myThid)
192 jmc 1.8 ENDDO
193    
194 jmc 1.17 DO n = 1,diagSt_nbLists
195     freqSec = diagSt_freq(n)
196     phiSec = diagSt_phase(n)
197     wrTime = myTime
198     IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
199 jmc 1.23 dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
200 jmc 1.17 & wrTime, deltaTclock )
201 jmc 1.18 #ifdef ALLOW_FIZHI
202     if( useFIZHI) then
203     write(tagname,'(A,I2.2)')'diagStg',n
204     dump2fileNow = alarm2(tagname)
205     endif
206     #endif
207 jmc 1.23 IF ( dump2fileNow .OR.
208     & (myTime.EQ.endTime .AND. dumpatlast)
209     & ) CALL DIAGSTATS_CLEAR( n, myThid )
210 jmc 1.17 ENDDO
211    
212 jmc 1.8 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
213     ENDIF
214    
215 jmc 1.23 RETURN
216 jmc 1.8 END

  ViewVC Help
Powered by ViewVC 1.1.22