/[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.24 by edhill, Wed Jul 6 02:13:52 2005 UTC revision 1.37 by jmc, Fri Jun 8 15:01:19 2012 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 (
7         I                               modelEnd,
8         I                               myTime, myIter, myThid )
9  C***********************************************************************  C***********************************************************************
10  C  Purpose  C  Purpose
11  C  -------  C  -------
# Line 11  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     myTime :: Current time of simulation ( s )  C     modelEnd :: true if call at end of model run.
17  C     myIter :: Current Iteration Number  C     myTime   :: Current time of simulation ( s )
18  C     myThid :: my Thread Id number  C     myIter   :: Current Iteration Number
19    C     myThid   :: my Thread Id number
20  C***********************************************************************  C***********************************************************************
21         IMPLICIT NONE         IMPLICIT NONE
22    #include "EEPARAMS.h"
23  #include "SIZE.h"  #include "SIZE.h"
24  #include "DIAGNOSTICS_SIZE.h"  #include "DIAGNOSTICS_SIZE.h"
 #include "DIAGNOSTICS.h"  
 #include "EEPARAMS.h"  
25  #include "PARAMS.h"  #include "PARAMS.h"
26    #include "DIAGNOSTICS.h"
27    
28  C     !INPUT PARAMETERS:  C     !INPUT PARAMETERS:
29          LOGICAL modelEnd
30        _RL     myTime        _RL     myTime
31        INTEGER myIter, myThid        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        INTEGER   myItM1, wrIter
45        LOGICAL   dump2fileNow, write2file        LOGICAL   dump2fileNow, write2file
46        _RL       phiSec, freqSec, wrTime        _RL       phiSec, freqSec, wrTime
 #ifdef ALLOW_CAL  
       INTEGER thisdate(4), prevdate(4)  
 #endif  
47  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
48        logical alarm2        CHARACTER *9 tagname
       character *9 tagname  
49  #endif  #endif
50    
       LOGICAL  DIFF_PHASE_MULTIPLE  
       EXTERNAL DIFF_PHASE_MULTIPLE  
   
51        IF ( myIter.NE.nIter0 ) THEN        IF ( myIter.NE.nIter0 ) THEN
52          myItM1 = myIter - 1          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***********************************************************************
57    
 #ifdef ALLOW_CAL  
         IF ( calendarDumps ) THEN  
 C-    Determine calendar dates for this and previous time step.  
            call cal_GetDate(myiter  ,mytime            ,thisdate,mythid)  
            call cal_GetDate(myiter-1,mytime-deltaTClock,prevdate,mythid)  
         ENDIF  
 #endif  
   
58          write2file = .FALSE.          write2file = .FALSE.
59          DO n = 1,nlists          DO n = 1,nlists
60            freqSec = freq(n)            freqSec = freq(n)
# Line 71  c           wrTime = myTime Line 68  c           wrTime = myTime
68  C--     write snap-shot with suffix = myIter-1 to be consistent with  C--     write snap-shot with suffix = myIter-1 to be consistent with
69  C       state-variable time-step:  C       state-variable time-step:
70              wrIter = myItM1              wrIter = myItM1
71              wrTime = myTime - deltaTclock              wrTime = myTime - deltaTClock
72            ELSE            ELSE
73              wrIter = myIter              wrIter = myIter
74              wrTime = myTime              wrTime = myTime
75            ENDIF            ENDIF
76            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
77       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTClock )
78  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
79           if( useFIZHI) then            IF ( useFIZHI ) THEN
80            write(tagname,'(A,I2.2)')'diagtag',n             WRITE(tagname,'(A,I2.2)')'diagtag',n
81            dump2fileNow = alarm2(tagname)             dump2fileNow = ALARM2(tagname)
          endif  
 #endif  
   
 #ifdef ALLOW_CAL  
           IF ( calendarDumps .AND. (  
      &     ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.  
      &     ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN  
 C--   Convert approximate months (30-31 days) and years (360-372 days)  
 C     to exact calendar months and years.  
            dump2fileNow = .FALSE.  
 C-    Monthly freqSec:  
            IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.  
      &        (thisdate(1)-prevdate(1)).GT.50   ) dump2fileNow = .TRUE.  
 C-    Yearly  freqSec:  
            IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.  
      &        (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.  
82            ENDIF            ENDIF
83  #endif  #endif
84    #ifdef ALLOW_CAL
85            IF ( dump2fileNow .OR.            IF ( useCAL ) THEN
86       &        (myTime.EQ.endTime .AND. dumpatlast) ) THEN              CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
87         U                          dump2fileNow,
88         I                          wrTime, myIter, 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.              write2file = .TRUE.
95              CALL DIAGNOSTICS_OUT(n,wrIter,myTime,myThid)              CALL DIAGNOSTICS_OUT(n,wrTime,wrIter,myThid)
96            ENDIF            ENDIF
97          ENDDO          ENDDO
98    
99  C---   Check to see IF its time for Statistics Diag. Output  C---   Check to see if its time for Statistics Diag. Output
100    
101          DO n = 1,diagSt_nbLists          DO n = 1,diagSt_nbLists
102            freqSec = diagSt_freq(n)            freqSec = diagSt_freq(n)
# Line 122  c           wrTime = myTime Line 110  c           wrTime = myTime
110  C--     write snap-shot with suffix = myIter-1 to be consistent with  C--     write snap-shot with suffix = myIter-1 to be consistent with
111  C       state-variable time-step:  C       state-variable time-step:
112              wrIter = myItM1              wrIter = myItM1
113              wrTime = myTime - deltaTclock              wrTime = myTime - deltaTClock
114            ELSE            ELSE
115              wrIter = myIter              wrIter = myIter
116              wrTime = myTime              wrTime = myTime
117            ENDIF            ENDIF
118            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
119       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTClock )
120  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
121           if( useFIZHI) then            IF ( useFIZHI ) THEN
122            write(tagname,'(A,I2.2)')'diagStg',n             WRITE(tagname,'(A,I2.2)')'diagStg',n
123            dump2fileNow = alarm2(tagname)             dump2fileNow = ALARM2(tagname)
124           endif            ENDIF
125  #endif  #endif
126    #ifdef ALLOW_CAL
127            IF ( dump2fileNow .OR.            IF ( useCAL ) THEN
128       &        (myTime.EQ.endTime .AND. dumpatlast) ) THEN              CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
129         U                          dump2fileNow,
130         I                          wrTime, myIter, 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.              write2file = .TRUE.
137              CALL DIAGSTATS_OUTPUT(n,wrIter,myTime,myThid)              CALL DIAGSTATS_OUTPUT(n,wrTime,wrIter,myThid)
138            ENDIF            ENDIF
139          ENDDO          ENDDO
140    
141  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
142    
143          IF ( write2file ) THEN          IF ( write2file ) THEN
144            IF ( debugLevel.GE.debLevB ) THEN            IF ( debugLevel.GE.debLevC ) THEN
145              CALL DIAGNOSTICS_SUMMARY( myTime, myIter, myThid )              CALL DIAGNOSTICS_SUMMARY( myTime, myIter, myThid )
146            ENDIF            ENDIF
147  C-      wait for everyone before setting arrays to zero:  C-      wait for everyone before setting arrays to zero:
148            _BARRIER            _BARRIER
149          ENDIF          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:  C--     Clear storage space:
156    
# Line 160  C--     Clear storage space: Line 159  C--     Clear storage space:
159            phiSec = phase(n)            phiSec = phase(n)
160    
161            wrTime = myTime            wrTime = myTime
162            IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock            IF ( freqSec.LT.0. ) wrTime = myTime - deltaTClock
163            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
164       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTClock )
165  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
166            if( useFIZHI) then            IF ( useFIZHI ) THEN
167             write(tagname,'(A,I2.2)')'diagtag',n             WRITE(tagname,'(A,I2.2)')'diagtag',n
168             dump2fileNow = alarm2(tagname)             dump2fileNow = ALARM2(tagname)
           endif  
 #endif  
   
 #ifdef ALLOW_CAL  
           IF ( calendarDumps .AND. (  
      &     ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.  
      &     ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN  
 C--   Convert approximate months (30-31 days) and years (360-372 days)  
 C     to exact calendar months and years.  
            dump2fileNow = .FALSE.  
 C-    Monthly freqSec:  
            IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.  
      &        (thisdate(1)-prevdate(1)).GT.50   ) dump2fileNow = .TRUE.  
 C-    Yearly  freqSec:  
            IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.  
      &        (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.  
169            ENDIF            ENDIF
170  #endif  #endif
171    #ifdef ALLOW_CAL
172            IF ( dump2fileNow .OR.            IF ( useCAL ) THEN
173       &        (myTime.EQ.endTime .AND. dumpatlast)              CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
174       &       ) CALL DIAGNOSTICS_CLEAR(n,myThid)       U                          dump2fileNow,
175         I                          wrTime, myIter, myThid )
176              ENDIF
177    #endif /* ALLOW_CAL */
178              IF ( dumpAtLast .AND. modelEnd
179         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
180              IF ( dump2fileNow ) CALL DIAGNOSTICS_CLEAR(n,myThid)
181          ENDDO          ENDDO
182    
183          DO n = 1,diagSt_nbLists          DO n = 1,diagSt_nbLists
184            freqSec = diagSt_freq(n)            freqSec = diagSt_freq(n)
185            phiSec = diagSt_phase(n)            phiSec = diagSt_phase(n)
186            wrTime = myTime            wrTime = myTime
187            IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock            IF ( freqSec.LT.0. ) wrTime = myTime - deltaTClock
188            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
189       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTClock )
190  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
191           if( useFIZHI) then            IF ( useFIZHI ) THEN
192            write(tagname,'(A,I2.2)')'diagStg',n             WRITE(tagname,'(A,I2.2)')'diagStg',n
193            dump2fileNow = alarm2(tagname)             dump2fileNow = ALARM2(tagname)
194           endif            ENDIF
195  #endif  #endif
196            IF ( dump2fileNow .OR.  #ifdef ALLOW_CAL
197       &        (myTime.EQ.endTime .AND. dumpatlast)            IF ( useCAL ) THEN
198       &       ) CALL DIAGSTATS_CLEAR( n, myThid )              CALL CAL_TIME2DUMP( phiSec, freqSec, deltaTClock,
199         U                          dump2fileNow,
200         I                          wrTime, myIter, myThid )
201              ENDIF
202    #endif /* ALLOW_CAL */
203              IF ( dumpAtLast .AND. modelEnd
204         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
205              IF ( dump2fileNow ) CALL DIAGSTATS_CLEAR( n, myThid )
206          ENDDO          ENDDO
207    
208  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

Legend:
Removed from v.1.24  
changed lines
  Added in v.1.37

  ViewVC Help
Powered by ViewVC 1.1.22