/[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.36 by jmc, Thu Jun 7 17:12:01 2012 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 (
7         I                               modelEnd,
8         I                               myTime, myIter, myThid )
9  C***********************************************************************  C***********************************************************************
10  C  Purpose  C  Purpose
11  C  -------  C  -------
# Line 9  C    Output sequence for the (multiple) Line 13  C    Output sequence for the (multiple)
13  C  C
14  C  Arguments  Description  C  Arguments  Description
15  C  ----------------------  C  ----------------------
16  C     myIter ..... Current Iteration Number  C     modelEnd :: true if call at end of model run.
17  C     myThid ..... Current Process(or)  C     myTime   :: Current time of simulation ( s )
18    C     myIter   :: Current Iteration Number
19    C     myThid   :: my Thread Id number
20  C***********************************************************************  C***********************************************************************
21         implicit none         IMPLICIT NONE
 #include "CPP_OPTIONS.h"  
 #include "SIZE.h"  
 #include "diagnostics_SIZE.h"  
 #include "diagnostics.h"  
22  #include "EEPARAMS.h"  #include "EEPARAMS.h"
23    #include "SIZE.h"
24    #include "DIAGNOSTICS_SIZE.h"
25  #include "PARAMS.h"  #include "PARAMS.h"
26    #include "DIAGNOSTICS.h"
27    
28        integer myThid, myIter  C     !INPUT PARAMETERS:
29          LOGICAL modelEnd
30          _RL     myTime
31          INTEGER myIter, myThid
32    
33    C     !FUNCTIONS:
34          LOGICAL  DIFF_PHASE_MULTIPLE
35          EXTERNAL DIFF_PHASE_MULTIPLE
36    #ifdef ALLOW_FIZHI
37          LOGICAL  ALARM2
38          EXTERNAL ALARM2
39    #endif
40    
41  c Local variables  c Local variables
42  c ===============  c ===============
43        integer   n        INTEGER   n
44          INTEGER   myItM1, wrIter
45          LOGICAL   dump2fileNow, write2file
46          _RL       phiSec, freqSec, wrTime
47    #ifdef ALLOW_FIZHI
48          CHARACTER *9 tagname
49    #endif
50    
51          IF ( myIter.NE.nIter0 ) THEN
52            myItM1 = myIter - 1
53    
54  C***********************************************************************  C***********************************************************************
55  C***   Check to see if its time for Diagnostic Output                ***  C***   Check to see if its time for Diagnostic Output                ***
56  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  
57    
58        return          write2file = .FALSE.
59        end          DO n = 1,nlists
60              freqSec = freq(n)
61              phiSec = phase(n)
62    
63              IF ( freqSec.LT.0. ) THEN
64    C--     write snap-shot with suffix = myIter to be consistent with
65    C       time-average diagnostics (e.g., freq=-1 & freq=1):
66    c           wrIter = myIter
67    c           wrTime = myTime
68    C--     write snap-shot with suffix = myIter-1 to be consistent with
69    C       state-variable time-step:
70                wrIter = myItM1
71                wrTime = myTime - deltaTClock
72              ELSE
73                wrIter = myIter
74                wrTime = myTime
75              ENDIF
76              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
77         &                                        wrTime, deltaTClock )
78    #ifdef ALLOW_FIZHI
79              IF ( useFIZHI ) THEN
80               WRITE(tagname,'(A,I2.2)')'diagtag',n
81               dump2fileNow = ALARM2(tagname)
82              ENDIF
83    #endif
84    #ifdef ALLOW_CAL
85              IF ( useCAL ) THEN
86                CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
87         U                          dump2fileNow,
88         I                          wrTime, wrIter, myThid )
89              ENDIF
90    #endif /* ALLOW_CAL */
91              IF ( dumpAtLast .AND. modelEnd
92         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
93              IF ( dump2fileNow ) THEN
94                write2file = .TRUE.
95                CALL DIAGNOSTICS_OUT(n,wrTime,wrIter,myThid)
96              ENDIF
97            ENDDO
98    
99    C---   Check to see if its time for Statistics Diag. Output
100    
101            DO n = 1,diagSt_nbLists
102              freqSec = diagSt_freq(n)
103              phiSec = diagSt_phase(n)
104    
105              IF ( freqSec.LT.0. ) THEN
106    C--     write snap-shot with suffix = myIter to be consistent with
107    C       time-average diagnostics (e.g., freq=-1 & freq=1):
108    c           wrIter = myIter
109    c           wrTime = myTime
110    C--     write snap-shot with suffix = myIter-1 to be consistent with
111    C       state-variable time-step:
112                wrIter = myItM1
113                wrTime = myTime - deltaTClock
114              ELSE
115                wrIter = myIter
116                wrTime = myTime
117              ENDIF
118              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
119         &                                        wrTime, deltaTClock )
120    #ifdef ALLOW_FIZHI
121              IF ( useFIZHI ) THEN
122               WRITE(tagname,'(A,I2.2)')'diagStg',n
123               dump2fileNow = ALARM2(tagname)
124              ENDIF
125    #endif
126    #ifdef ALLOW_CAL
127              IF ( useCAL ) THEN
128                CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
129         U                          dump2fileNow,
130         I                          wrTime, wrIter, myThid )
131              ENDIF
132    #endif /* ALLOW_CAL */
133              IF ( dumpAtLast .AND. modelEnd
134         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
135              IF ( dump2fileNow ) THEN
136                write2file = .TRUE.
137                CALL DIAGSTATS_OUTPUT(n,wrTime,wrIter,myThid)
138              ENDIF
139            ENDDO
140    
141    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
142    
143            IF ( write2file ) THEN
144              IF ( debugLevel.GE.debLevC ) THEN
145                CALL DIAGNOSTICS_SUMMARY( myTime, myIter, myThid )
146              ENDIF
147    C-      wait for everyone before setting arrays to zero:
148              _BARRIER
149            ENDIF
150            IF ( modelEnd ) THEN
151    C       Close all Stat-diags output files
152              CALL DIAGSTATS_CLOSE_IO( myThid )
153            ENDIF
154    
155    C--     Clear storage space:
156    
157            DO n = 1,nlists
158              freqSec = freq(n)
159              phiSec = phase(n)
160    
161              wrTime = myTime
162              IF ( freqSec.LT.0. ) wrTime = myTime - deltaTClock
163              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
164         &                                        wrTime, deltaTClock )
165    #ifdef ALLOW_FIZHI
166              IF ( useFIZHI ) THEN
167               WRITE(tagname,'(A,I2.2)')'diagtag',n
168               dump2fileNow = ALARM2(tagname)
169              ENDIF
170    #endif
171    #ifdef ALLOW_CAL
172              IF ( useCAL ) THEN
173                wrIter = myIter
174                IF ( freqSec.LT.0. ) wrIter = myItM1
175                CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
176         U                          dump2fileNow,
177         I                          wrTime, wrIter, myThid )
178              ENDIF
179    #endif /* ALLOW_CAL */
180              IF ( dumpAtLast .AND. modelEnd
181         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
182              IF ( dump2fileNow ) CALL DIAGNOSTICS_CLEAR(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    #ifdef ALLOW_CAL
199              IF ( useCAL ) THEN
200                wrIter = myIter
201                IF ( freqSec.LT.0. ) wrIter = myItM1
202                CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
203         U                          dump2fileNow,
204         I                          wrTime, wrIter, myThid )
205              ENDIF
206    #endif /* ALLOW_CAL */
207              IF ( dumpAtLast .AND. modelEnd
208         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
209              IF ( dump2fileNow ) 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.36

  ViewVC Help
Powered by ViewVC 1.1.22