/[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.28 by jmc, Mon Mar 20 15:15:39 2006 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 "EEPARAMS.h"
20  #include "SIZE.h"  #include "SIZE.h"
21  #include "DIAGNOSTICS_SIZE.h"  #include "DIAGNOSTICS_SIZE.h"
 #include "DIAGNOSTICS.h"  
 #include "EEPARAMS.h"  
22  #include "PARAMS.h"  #include "PARAMS.h"
23    #include "DIAGNOSTICS.h"
24    
25  C     !INPUT PARAMETERS:  C     !INPUT PARAMETERS:
26        _RL     myTime        _RL     myTime
# 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
 #ifdef ALLOW_CAL  
       INTEGER thisdate(4), prevdate(4)  
 #endif  
35  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
36        logical alarm2        logical alarm2
37        character *9 tagname        character *9 tagname
# Line 50  C*************************************** Line 47  C***************************************
47  C***   Check to see IF its time for Diagnostic Output                ***  C***   Check to see IF its time for Diagnostic Output                ***
48  C***********************************************************************  C***********************************************************************
49    
50  #ifdef ALLOW_CAL          write2file = .FALSE.
         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  
   
51          DO n = 1,nlists          DO n = 1,nlists
52            freqSec = freq(n)            freqSec = freq(n)
53            phiSec = phase(n)            phiSec = phase(n)
54    
55            IF ( freqSec.LT.0. ) THEN            IF ( freqSec.LT.0. ) THEN
56  C--     write snap-shot with suffix = myIter to be consistent with  C--     write snap-shot with suffix = myIter to be consistent with
57  C       time-average diagnostics (e.g., freq=-1 & freq=1):  C       time-average diagnostics (e.g., freq=-1 & freq=1):
58  c           wrIter = myIter  c           wrIter = myIter
59  c           wrTime = myTime  c           wrTime = myTime
# Line 75  C       state-variable time-step: Line 65  C       state-variable time-step:
65              wrIter = myIter              wrIter = myIter
66              wrTime = myTime              wrTime = myTime
67            ENDIF            ENDIF
68            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
69       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTclock )
70  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
71           if( useFIZHI) then            IF( useFIZHI) THEN
72            write(tagname,'(A,I2.2)')'diagtag',n             write(tagname,'(A,I2.2)')'diagtag',n
73            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.  
74            ENDIF            ENDIF
75  #endif  #endif
76    #ifdef ALLOW_CAL
77            IF ( dump2fileNow .or. ((myIter.eq.nIter0+nTimeSteps).and.            IF ( useCAL ) THEN
78       .                                                dumpatlast) ) THEN              CALL CAL_TIME2DUMP( freqSec, deltaTClock,
79              CALL DIAGNOSTICS_OUT(n,wrIter,myTime,myThid)       U                          dump2fileNow,
80         I                          myTime, myIter, myThid )
81              ENDIF
82    #endif /* ALLOW_CAL */
83              IF ( dump2fileNow .OR.
84         &        (myTime.EQ.endTime .AND. dumpatlast) ) THEN
85                write2file = .TRUE.
86                CALL DIAGNOSTICS_OUT(n,wrIter,wrTime,myThid)
87            ENDIF            ENDIF
88          ENDDO          ENDDO
89    
90  C---   Check to see IF its time for Statistics Diag. Output  C---   Check to see IF its time for Statistics Diag. Output
91    
92          DO n = 1,diagSt_nbLists          DO n = 1,diagSt_nbLists
93            freqSec = diagSt_freq(n)            freqSec = diagSt_freq(n)
94            phiSec = diagSt_phase(n)            phiSec = diagSt_phase(n)
95    
96            IF ( freqSec.LT.0. ) THEN            IF ( freqSec.LT.0. ) THEN
97  C--     write snap-shot with suffix = myIter to be consistent with  C--     write snap-shot with suffix = myIter to be consistent with
98  C       time-average diagnostics (e.g., freq=-1 & freq=1):  C       time-average diagnostics (e.g., freq=-1 & freq=1):
99  c           wrIter = myIter  c           wrIter = myIter
100  c           wrTime = myTime  c           wrTime = myTime
# Line 125  C       state-variable time-step: Line 106  C       state-variable time-step:
106              wrIter = myIter              wrIter = myIter
107              wrTime = myTime              wrTime = myTime
108            ENDIF            ENDIF
109            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
110       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTclock )
111  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
112           if( useFIZHI) then            IF( useFIZHI) THEN
113            write(tagname,'(A,I2.2)')'diagStg',n             write(tagname,'(A,I2.2)')'diagStg',n
114            dump2fileNow = alarm2(tagname)             dump2fileNow = alarm2(tagname)
115           endif            ENDIF
116  #endif  #endif
117              IF ( dump2fileNow .OR.
118            IF ( dump2fileNow .or. ((myIter.eq.nIter0+nTimeSteps).and.       &        (myTime.EQ.endTime .AND. dumpatlast) ) THEN
119       .                                                dumpatlast) ) THEN              write2file = .TRUE.
120              CALL DIAGSTATS_OUTPUT(n,wrIter,myThid)              CALL DIAGSTATS_OUTPUT(n,wrTime,wrIter,myThid)
121            ENDIF            ENDIF
122          ENDDO          ENDDO
123    
124  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
125  C-      wait for everyone before setting arrays to zero:  
126          _BARRIER          IF ( write2file ) THEN
127              IF ( debugLevel.GE.debLevB ) THEN
128                CALL DIAGNOSTICS_SUMMARY( myTime, myIter, myThid )
129              ENDIF
130    C-      wait for everyone before setting arrays to zero:
131              _BARRIER
132            ENDIF
133    
134  C--     Clear storage space:  C--     Clear storage space:
135    
# Line 152  C--     Clear storage space: Line 139  C--     Clear storage space:
139    
140            wrTime = myTime            wrTime = myTime
141            IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock            IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
142            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
143       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTclock )
144  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
145            if( useFIZHI) then            IF( useFIZHI) THEN
146             write(tagname,'(A,I2.2)')'diagtag',n             write(tagname,'(A,I2.2)')'diagtag',n
147             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.  
148            ENDIF            ENDIF
149  #endif  #endif
150    #ifdef ALLOW_CAL
151            IF ( dump2fileNow .or. ((myIter.eq.nIter0+nTimeSteps).and.            IF ( useCAL ) THEN
152       .                                                dumpatlast) )              CALL CAL_TIME2DUMP( freqSec, deltaTClock,
153       .                             CALL CLRINDX(n,myThid)       U                          dump2fileNow,
154         I                          myTime, myIter, myThid )
155              ENDIF
156    #endif /* ALLOW_CAL */
157              IF ( dump2fileNow .OR.
158         &        (myTime.EQ.endTime .AND. dumpatlast)
159         &       ) CALL DIAGNOSTICS_CLEAR(n,myThid)
160          ENDDO          ENDDO
161    
162          DO n = 1,diagSt_nbLists          DO n = 1,diagSt_nbLists
# Line 187  C-    Yearly  freqSec: Line 164  C-    Yearly  freqSec:
164            phiSec = diagSt_phase(n)            phiSec = diagSt_phase(n)
165            wrTime = myTime            wrTime = myTime
166            IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock            IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
167            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
168       &                                        wrTime, deltaTclock )       &                                        wrTime, deltaTclock )
169  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
170           if( useFIZHI) then            IF( useFIZHI) THEN
171            write(tagname,'(A,I2.2)')'diagStg',n             write(tagname,'(A,I2.2)')'diagStg',n
172            dump2fileNow = alarm2(tagname)             dump2fileNow = alarm2(tagname)
173           endif            ENDIF
174  #endif  #endif
175            IF ( dump2fileNow .or. ((myIter.eq.nIter0+nTimeSteps).and.            IF ( dump2fileNow .OR.
176       .                                                dumpatlast) )       &        (myTime.EQ.endTime .AND. dumpatlast)
177       .                             CALL DIAGSTATS_CLEAR(n,myThid)       &       ) CALL DIAGSTATS_CLEAR( n, myThid )
178          ENDDO          ENDDO
179    
180  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
181        ENDIF        ENDIF
182    
183        RETURN        RETURN
184        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.22