/[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.22 by molod, Tue Jun 14 23:06:15 2005 UTC revision 1.23 by jmc, Sun Jun 26 16:51:49 2005 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "DIAG_OPTIONS.h"  #include "DIAG_OPTIONS.h"
5    
6        SUBROUTINE DIAGNOSTICS_WRITE ( myTime, myIter, myThid )        SUBROUTINE DIAGNOSTICS_WRITE ( myTime, myIter, myThid )
7  C***********************************************************************  C***********************************************************************
8  C  Purpose  C  Purpose
9  C  -------  C  -------
# Line 13  C  Arguments  Description Line 13  C  Arguments  Description
13  C  ----------------------  C  ----------------------
14  C     myTime :: Current time of simulation ( s )  C     myTime :: Current time of simulation ( s )
15  C     myIter :: Current Iteration Number  C     myIter :: Current Iteration Number
16  C     myThid :: my thread Id number  C     myThid :: my Thread Id number
17  C***********************************************************************  C***********************************************************************
18         IMPLICIT NONE         IMPLICIT NONE
19  #include "SIZE.h"  #include "SIZE.h"
# Line 30  c Local variables Line 30  c Local variables
30  c ===============  c ===============
31        INTEGER   n        INTEGER   n
32        INTEGER   myItM1, wrIter        INTEGER   myItM1, wrIter
33        LOGICAL   dump2fileNow        LOGICAL   dump2fileNow, write2file
34        _RL       phiSec, freqSec, wrTime        _RL       phiSec, freqSec, wrTime
35  #ifdef ALLOW_CAL  #ifdef ALLOW_CAL
36        INTEGER thisdate(4), prevdate(4)        INTEGER thisdate(4), prevdate(4)
# Line 58  C-    Determine calendar dates for this Line 58  C-    Determine calendar dates for this
58          ENDIF          ENDIF
59  #endif  #endif
60    
61            write2file = .FALSE.
62          DO n = 1,nlists          DO n = 1,nlists
63            freqSec = freq(n)            freqSec = freq(n)
64            phiSec = phase(n)            phiSec = phase(n)
65    
66            IF ( freqSec.LT.0. ) THEN            IF ( freqSec.LT.0. ) THEN
67  C--     write snap-shot with suffix = myIter to be consistent with  C--     write snap-shot with suffix = myIter to be consistent with
68  C       time-average diagnostics (e.g., freq=-1 & freq=1):  C       time-average diagnostics (e.g., freq=-1 & freq=1):
69  c           wrIter = myIter  c           wrIter = myIter
70  c           wrTime = myTime  c           wrTime = myTime
# Line 75  C       state-variable time-step: Line 76  C       state-variable time-step:
76              wrIter = myIter              wrIter = myIter
77              wrTime = myTime              wrTime = myTime
78            ENDIF            ENDIF
79            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
80       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTclock )
81  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
82           if( useFIZHI) then           if( useFIZHI) then
# Line 100  C-    Yearly  freqSec: Line 101  C-    Yearly  freqSec:
101            ENDIF            ENDIF
102  #endif  #endif
103    
104            IF ( dump2fileNow .or. ((myIter.eq.nIter0+nTimeSteps).and.            IF ( dump2fileNow .OR.
105       .                                                dumpatlast) ) THEN       &        (myTime.EQ.endTime .AND. dumpatlast) ) THEN
106                write2file = .TRUE.
107              CALL DIAGNOSTICS_OUT(n,wrIter,myTime,myThid)              CALL DIAGNOSTICS_OUT(n,wrIter,myTime,myThid)
108            ENDIF            ENDIF
109          ENDDO          ENDDO
110    
111  C---   Check to see IF its time for Statistics Diag. Output  C---   Check to see IF its time for Statistics Diag. Output
112    
113          DO n = 1,diagSt_nbLists          DO n = 1,diagSt_nbLists
114            freqSec = diagSt_freq(n)            freqSec = diagSt_freq(n)
115            phiSec = diagSt_phase(n)            phiSec = diagSt_phase(n)
116    
117            IF ( freqSec.LT.0. ) THEN            IF ( freqSec.LT.0. ) THEN
118  C--     write snap-shot with suffix = myIter to be consistent with  C--     write snap-shot with suffix = myIter to be consistent with
119  C       time-average diagnostics (e.g., freq=-1 & freq=1):  C       time-average diagnostics (e.g., freq=-1 & freq=1):
120  c           wrIter = myIter  c           wrIter = myIter
121  c           wrTime = myTime  c           wrTime = myTime
# Line 125  C       state-variable time-step: Line 127  C       state-variable time-step:
127              wrIter = myIter              wrIter = myIter
128              wrTime = myTime              wrTime = myTime
129            ENDIF            ENDIF
130            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
131       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTclock )
132  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
133           if( useFIZHI) then           if( useFIZHI) then
# Line 134  C       state-variable time-step: Line 136  C       state-variable time-step:
136           endif           endif
137  #endif  #endif
138    
139            IF ( dump2fileNow .or. ((myIter.eq.nIter0+nTimeSteps).and.            IF ( dump2fileNow .OR.
140       .                                                dumpatlast) ) THEN       &        (myTime.EQ.endTime .AND. dumpatlast) ) THEN
141                write2file = .TRUE.
142              CALL DIAGSTATS_OUTPUT(n,wrIter,myThid)              CALL DIAGSTATS_OUTPUT(n,wrIter,myThid)
143            ENDIF            ENDIF
144          ENDDO          ENDDO
145    
146  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
147  C-      wait for everyone before setting arrays to zero:  
148          _BARRIER          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:  C--     Clear storage space:
157    
# Line 152  C--     Clear storage space: Line 161  C--     Clear storage space:
161    
162            wrTime = myTime            wrTime = myTime
163            IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock            IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
164            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
165       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTclock )
166  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
167            if( useFIZHI) then            if( useFIZHI) then
# Line 177  C-    Yearly  freqSec: Line 186  C-    Yearly  freqSec:
186            ENDIF            ENDIF
187  #endif  #endif
188    
189            IF ( dump2fileNow .or. ((myIter.eq.nIter0+nTimeSteps).and.            IF ( dump2fileNow .OR.
190       .                                                dumpatlast) )       &        (myTime.EQ.endTime .AND. dumpatlast)
191       .                             CALL CLRINDX(n,myThid)       &       ) CALL DIAGNOSTICS_CLEAR(n,myThid)
192          ENDDO          ENDDO
193    
194          DO n = 1,diagSt_nbLists          DO n = 1,diagSt_nbLists
# Line 187  C-    Yearly  freqSec: Line 196  C-    Yearly  freqSec:
196            phiSec = diagSt_phase(n)            phiSec = diagSt_phase(n)
197            wrTime = myTime            wrTime = myTime
198            IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock            IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
199            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
200       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTclock )
201  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
202           if( useFIZHI) then           if( useFIZHI) then
# Line 195  C-    Yearly  freqSec: Line 204  C-    Yearly  freqSec:
204            dump2fileNow = alarm2(tagname)            dump2fileNow = alarm2(tagname)
205           endif           endif
206  #endif  #endif
207            IF ( dump2fileNow .or. ((myIter.eq.nIter0+nTimeSteps).and.            IF ( dump2fileNow .OR.
208       .                                                dumpatlast) )       &        (myTime.EQ.endTime .AND. dumpatlast)
209       .                             CALL DIAGSTATS_CLEAR(n,myThid)       &       ) CALL DIAGSTATS_CLEAR( n, myThid )
210          ENDDO          ENDDO
211    
212  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
213        ENDIF        ENDIF
214    
215        RETURN        RETURN
216        END        END

Legend:
Removed from v.1.22  
changed lines
  Added in v.1.23

  ViewVC Help
Powered by ViewVC 1.1.22