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

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

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

revision 1.6 by edhill, Wed May 5 00:39:21 2004 UTC revision 1.25 by jmc, Thu Jul 7 13:14:56 2005 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4        subroutine diagnostics_write (myThid, myIter)  #include "DIAG_OPTIONS.h"
5    
6          SUBROUTINE DIAGNOSTICS_WRITE ( myTime, myIter, myThid )
7  C***********************************************************************  C***********************************************************************
8  C  Purpose  C  Purpose
9  C  -------  C  -------
# Line 9  C    Output sequence for the (multiple) Line 11  C    Output sequence for the (multiple)
11  C  C
12  C  Arguments  Description  C  Arguments  Description
13  C  ----------------------  C  ----------------------
14  C     myIter ..... Current Iteration Number  C     myTime :: Current time of simulation ( s )
15  C     myThid ..... Current Process(or)  C     myIter :: Current Iteration Number
16    C     myThid :: my Thread Id number
17  C***********************************************************************  C***********************************************************************
18         implicit none         IMPLICIT NONE
 #include "CPP_OPTIONS.h"  
19  #include "SIZE.h"  #include "SIZE.h"
20  #include "diagnostics_SIZE.h"  #include "DIAGNOSTICS_SIZE.h"
21  #include "diagnostics.h"  #include "DIAGNOSTICS.h"
22  #include "EEPARAMS.h"  #include "EEPARAMS.h"
23  #include "PARAMS.h"  #include "PARAMS.h"
24    
25        integer myThid, myIter  C     !INPUT PARAMETERS:
26          _RL     myTime
27          INTEGER myIter, myThid
28    
29  c Local variables  c Local variables
30  c ===============  c ===============
31        integer   n        INTEGER   n
32          INTEGER   myItM1, wrIter
33          LOGICAL   dump2fileNow, write2file
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***********************************************************************  C***********************************************************************
50  C***   Check to see if its time for Diagnostic Output                ***  C***   Check to see IF its time for Diagnostic Output                ***
51  C***********************************************************************  C***********************************************************************
       do n=1,nlists  
       if ( myIter.ne.niter0) then  
        if ( mod(myIter,freq(n)).eq.0 ) then  
         call diagout(myThid,myIter,n)  
         call clrindx(myThid,n)  
        endif  
       endif  
       enddo  
52    
53        return  #ifdef ALLOW_CAL
54        end          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            write2file = .FALSE.
62            DO n = 1,nlists
63              freqSec = freq(n)
64              phiSec = phase(n)
65    
66              IF ( freqSec.LT.0. ) THEN
67    C--     write snap-shot with suffix = myIter to be consistent with
68    C       time-average diagnostics (e.g., freq=-1 & freq=1):
69    c           wrIter = myIter
70    c           wrTime = myTime
71    C--     write snap-shot with suffix = myIter-1 to be consistent with
72    C       state-variable time-step:
73                wrIter = myItM1
74                wrTime = myTime - deltaTclock
75              ELSE
76                wrIter = myIter
77                wrTime = myTime
78              ENDIF
79              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
80         &                                        wrTime, deltaTclock )
81    #ifdef ALLOW_FIZHI
82             if( useFIZHI) then
83              write(tagname,'(A,I2.2)')'diagtag',n
84              dump2fileNow = alarm2(tagname)
85             endif
86    #endif
87    
88    #ifdef ALLOW_CAL
89              IF ( calendarDumps .AND. (
90         &     ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.
91         &     ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN
92    C--   Convert approximate months (30-31 days) and years (360-372 days)
93    C     to exact calendar months and years.
94               dump2fileNow = .FALSE.
95    C-    Monthly freqSec:
96               IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.
97         &        (thisdate(1)-prevdate(1)).GT.50   ) dump2fileNow = .TRUE.
98    C-    Yearly  freqSec:
99               IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.
100         &        (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.
101              ENDIF
102    #endif
103    
104              IF ( dump2fileNow .OR.
105         &        (myTime.EQ.endTime .AND. dumpatlast) ) THEN
106                write2file = .TRUE.
107                CALL DIAGNOSTICS_OUT(n,wrIter,myTime,myThid)
108              ENDIF
109            ENDDO
110    
111    C---   Check to see IF its time for Statistics Diag. Output
112    
113            DO n = 1,diagSt_nbLists
114              freqSec = diagSt_freq(n)
115              phiSec = diagSt_phase(n)
116    
117              IF ( freqSec.LT.0. ) THEN
118    C--     write snap-shot with suffix = myIter to be consistent with
119    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              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
131         &                                        wrTime, deltaTclock )
132    #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              IF ( dump2fileNow .OR.
140         &        (myTime.EQ.endTime .AND. dumpatlast) ) THEN
141                write2file = .TRUE.
142                CALL DIAGSTATS_OUTPUT(n,myTime,wrIter,myThid)
143              ENDIF
144            ENDDO
145    
146    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
147    
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    
156    C--     Clear storage space:
157    
158            DO n = 1,nlists
159              freqSec = freq(n)
160              phiSec = phase(n)
161    
162              wrTime = myTime
163              IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
164              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
165         &                                        wrTime, deltaTclock )
166    #ifdef ALLOW_FIZHI
167              if( useFIZHI) then
168               write(tagname,'(A,I2.2)')'diagtag',n
169               dump2fileNow = alarm2(tagname)
170              endif
171    #endif
172    
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              IF ( dump2fileNow .OR.
190         &        (myTime.EQ.endTime .AND. dumpatlast)
191         &       ) CALL DIAGNOSTICS_CLEAR(n,myThid)
192            ENDDO
193    
194            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              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
200         &                                        wrTime, deltaTclock )
201    #ifdef ALLOW_FIZHI
202             if( useFIZHI) then
203              write(tagname,'(A,I2.2)')'diagStg',n
204              dump2fileNow = alarm2(tagname)
205             endif
206    #endif
207              IF ( dump2fileNow .OR.
208         &        (myTime.EQ.endTime .AND. dumpatlast)
209         &       ) CALL DIAGSTATS_CLEAR( n, myThid )
210            ENDDO
211    
212    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
213          ENDIF
214    
215          RETURN
216          END

Legend:
Removed from v.1.6  
changed lines
  Added in v.1.25

  ViewVC Help
Powered by ViewVC 1.1.22