/[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.27 by jmc, Mon Jan 23 22:21:15 2006 UTC revision 1.33 by jmc, Mon Jun 6 15:42:58 2011 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"  #include "EEPARAMS.h"
# Line 23  C*************************************** Line 26  C***************************************
26  #include "DIAGNOSTICS.h"  #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    
# Line 32  c =============== Line 36  c ===============
36        INTEGER   myItM1, wrIter        INTEGER   myItM1, wrIter
37        LOGICAL   dump2fileNow, write2file        LOGICAL   dump2fileNow, write2file
38        _RL       phiSec, freqSec, wrTime        _RL       phiSec, freqSec, wrTime
 #ifdef ALLOW_CAL  
       INTEGER thisdate(4), prevdate(4)  
 #endif  
39  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
40        logical alarm2        LOGICAL alarm2
41        character *9 tagname        CHARACTER *9 tagname
42  #endif  #endif
43    
44        LOGICAL  DIFF_PHASE_MULTIPLE        LOGICAL  DIFF_PHASE_MULTIPLE
# Line 47  c =============== Line 48  c ===============
48          myItM1 = myIter - 1          myItM1 = myIter - 1
49    
50  C***********************************************************************  C***********************************************************************
51  C***   Check to see IF its time for Diagnostic Output                ***  C***   Check to see if its time for Diagnostic Output                ***
52  C***********************************************************************  C***********************************************************************
53    
 #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  
   
54          write2file = .FALSE.          write2file = .FALSE.
55          DO n = 1,nlists          DO n = 1,nlists
56            freqSec = freq(n)            freqSec = freq(n)
# Line 79  C       state-variable time-step: Line 72  C       state-variable time-step:
72            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
73       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTclock )
74  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
75           if( useFIZHI) then            IF ( useFIZHI ) THEN
76            write(tagname,'(A,I2.2)')'diagtag',n             WRITE(tagname,'(A,I2.2)')'diagtag',n
77            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.  
78            ENDIF            ENDIF
79  #endif  #endif
80    #ifdef ALLOW_CAL
81            IF ( dump2fileNow .OR.            IF ( useCAL ) THEN
82       &        (myTime.EQ.endTime .AND. dumpatlast) ) THEN              CALL CAL_TIME2DUMP( freqSec, deltaTClock,
83         U                          dump2fileNow,
84         I                          myTime, myIter, myThid )
85              ENDIF
86    #endif /* ALLOW_CAL */
87              IF ( dumpAtLast .AND. modelEnd
88         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
89              IF ( dump2fileNow ) THEN
90              write2file = .TRUE.              write2file = .TRUE.
91              CALL DIAGNOSTICS_OUT(n,wrIter,wrTime,myThid)              CALL DIAGNOSTICS_OUT(n,wrIter,wrTime,myThid)
92            ENDIF            ENDIF
93          ENDDO          ENDDO
94    
95  C---   Check to see IF its time for Statistics Diag. Output  C---   Check to see if its time for Statistics Diag. Output
96    
97          DO n = 1,diagSt_nbLists          DO n = 1,diagSt_nbLists
98            freqSec = diagSt_freq(n)            freqSec = diagSt_freq(n)
# Line 130  C       state-variable time-step: Line 114  C       state-variable time-step:
114            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
115       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTclock )
116  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
117           if( useFIZHI) then            IF ( useFIZHI ) THEN
118            write(tagname,'(A,I2.2)')'diagStg',n             WRITE(tagname,'(A,I2.2)')'diagStg',n
119            dump2fileNow = alarm2(tagname)             dump2fileNow = alarm2(tagname)
120           endif            ENDIF
121  #endif  #endif
122              IF ( dumpAtLast .AND. modelEnd
123            IF ( dump2fileNow .OR.       &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
124       &        (myTime.EQ.endTime .AND. dumpatlast) ) THEN            IF ( dump2fileNow ) THEN
125              write2file = .TRUE.              write2file = .TRUE.
126              CALL DIAGSTATS_OUTPUT(n,wrTime,wrIter,myThid)              CALL DIAGSTATS_OUTPUT(n,wrTime,wrIter,myThid)
127            ENDIF            ENDIF
# Line 146  C       state-variable time-step: Line 130  C       state-variable time-step:
130  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
131    
132          IF ( write2file ) THEN          IF ( write2file ) THEN
133            IF ( debugLevel.GE.debLevB ) THEN            IF ( debugLevel.GE.debLevC ) THEN
134              CALL DIAGNOSTICS_SUMMARY( myTime, myIter, myThid )              CALL DIAGNOSTICS_SUMMARY( myTime, myIter, myThid )
135            ENDIF            ENDIF
136  C-      wait for everyone before setting arrays to zero:  C-      wait for everyone before setting arrays to zero:
137            _BARRIER            _BARRIER
138          ENDIF          ENDIF
139            IF ( modelEnd ) THEN
140    C       Close all Stat-diags output files
141              CALL DIAGSTATS_CLOSE_IO( myThid )
142            ENDIF
143    
144  C--     Clear storage space:  C--     Clear storage space:
145    
# Line 164  C--     Clear storage space: Line 152  C--     Clear storage space:
152            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
153       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTclock )
154  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
155            if( useFIZHI) then            IF ( useFIZHI ) THEN
156             write(tagname,'(A,I2.2)')'diagtag',n             WRITE(tagname,'(A,I2.2)')'diagtag',n
157             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.  
158            ENDIF            ENDIF
159  #endif  #endif
160    #ifdef ALLOW_CAL
161            IF ( dump2fileNow .OR.            IF ( useCAL ) THEN
162       &        (myTime.EQ.endTime .AND. dumpatlast)              CALL CAL_TIME2DUMP( freqSec, deltaTClock,
163       &       ) CALL DIAGNOSTICS_CLEAR(n,myThid)       U                          dump2fileNow,
164         I                          myTime, myIter, myThid )
165              ENDIF
166    #endif /* ALLOW_CAL */
167              IF ( dumpAtLast .AND. modelEnd
168         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
169              IF ( dump2fileNow ) CALL DIAGNOSTICS_CLEAR(n,myThid)
170          ENDDO          ENDDO
171    
172          DO n = 1,diagSt_nbLists          DO n = 1,diagSt_nbLists
# Line 199  C-    Yearly  freqSec: Line 177  C-    Yearly  freqSec:
177            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
178       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTclock )
179  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
180           if( useFIZHI) then            IF ( useFIZHI ) THEN
181            write(tagname,'(A,I2.2)')'diagStg',n             WRITE(tagname,'(A,I2.2)')'diagStg',n
182            dump2fileNow = alarm2(tagname)             dump2fileNow = alarm2(tagname)
183           endif            ENDIF
184  #endif  #endif
185            IF ( dump2fileNow .OR.            IF ( dumpAtLast .AND. modelEnd
186       &        (myTime.EQ.endTime .AND. dumpatlast)       &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
187       &       ) CALL DIAGSTATS_CLEAR( n, myThid )            IF ( dump2fileNow ) CALL DIAGSTATS_CLEAR( n, myThid )
188          ENDDO          ENDDO
189    
190  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

Legend:
Removed from v.1.27  
changed lines
  Added in v.1.33

  ViewVC Help
Powered by ViewVC 1.1.22