/[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.15 by molod, Mon May 16 23:41:32 2005 UTC revision 1.26 by edhill, Tue Sep 6 17:45:19 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 21  C*************************************** Line 21  C***************************************
21  #include "DIAGNOSTICS.h"  #include "DIAGNOSTICS.h"
22  #include "EEPARAMS.h"  #include "EEPARAMS.h"
23  #include "PARAMS.h"  #include "PARAMS.h"
 #ifdef ALLOW_FIZHI  
 #include "chronos.h"  
 #endif  
24    
25  C     !INPUT PARAMETERS:  C     !INPUT PARAMETERS:
26        _RL     myTime        _RL     myTime
# Line 33  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)
37  #endif  #endif
38  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
39        integer nsecf2,mmdd,hhmmss,alarm2        logical alarm2
40        character *9 tagname        character *9 tagname
41  #endif  #endif
42    
# Line 61  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)
 #ifdef ALLOW_FIZHI  
          if( useFIZHI) then  
           mmdd = int(freq(n))  
           hhmmss = int((freq(n) - int(freq(n)))*1.e6)  
           freqSec = nsecf2(hhmmss,mmdd,nymd)  
          endif  
 #endif  
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 85  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 110  C-    Yearly  freqSec: Line 101  C-    Yearly  freqSec:
101            ENDIF            ENDIF
102  #endif  #endif
103    
104            IF ( dump2fileNow ) THEN            IF ( dump2fileNow .OR.
105              CALL DIAGNOSTICS_OUT(n,wrIter,myThid)       &        (myTime.EQ.endTime .AND. dumpatlast) ) THEN
106                write2file = .TRUE.
107                CALL DIAGNOSTICS_OUT(n,wrIter,wrTime,myThid)
108            ENDIF            ENDIF
109          ENDDO          ENDDO
110    
111  C-      wait for everyone before setting arrays to zero:  C---   Check to see IF its time for Statistics Diag. Output
112          _BARRIER  
113          DO n = 1,nlists          DO n = 1,diagSt_nbLists
114            freqSec = freq(n)            freqSec = diagSt_freq(n)
115            phiSec = phase(n)            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  #ifdef ALLOW_FIZHI
133           if( useFIZHI) then           if( useFIZHI) then
134            mmdd = int(freq(n))            write(tagname,'(A,I2.2)')'diagStg',n
135            hhmmss = int((freq(n) - int(freq(n)))*1.e6)            dump2fileNow = alarm2(tagname)
           freqSec = nsecf2(hhmmss,mmdd,nymd)  
136           endif           endif
137  #endif  #endif
138    
139              IF ( dump2fileNow .OR.
140         &        (myTime.EQ.endTime .AND. dumpatlast) ) THEN
141                write2file = .TRUE.
142                CALL DIAGSTATS_OUTPUT(n,wrTime,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            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 137  C-      wait for everyone before setting Line 169  C-      wait for everyone before setting
169             dump2fileNow = alarm2(tagname)             dump2fileNow = alarm2(tagname)
170            endif            endif
171  #endif  #endif
172            IF ( dump2fileNow ) CALL CLRINDX(n,myThid)  
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          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.15  
changed lines
  Added in v.1.26

  ViewVC Help
Powered by ViewVC 1.1.22