/[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.13 by molod, Fri May 13 18:32:46 2005 UTC revision 1.31 by jmc, Fri Jan 8 19:44:05 2010 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  #ifdef ALLOW_FIZHI  #include "DIAGNOSTICS.h"
 #include "chronos.h"  
 #endif  
27    
28    C     !INPUT PARAMETERS:
29          LOGICAL modelEnd
30        _RL     myTime        _RL     myTime
31        INTEGER myIter, myThid        INTEGER myIter, myThid
32    
# Line 32  c Local variables Line 34  c Local variables
34  c ===============  c ===============
35        INTEGER   n        INTEGER   n
36        INTEGER   myItM1, wrIter        INTEGER   myItM1, wrIter
37        LOGICAL   dump2fileNow        LOGICAL   dump2fileNow, write2file
38        INTEGER thisdate(4), prevdate(4)        _RL       phiSec, freqSec, wrTime
39        _RL     freqSec  #ifdef ALLOW_FIZHI
40        integer realfreq,nsecf2,yymmdd,hhmmss        LOGICAL alarm2
41          CHARACTER *9 tagname
42    #endif
43    
44          LOGICAL  DIFF_PHASE_MULTIPLE
45          EXTERNAL DIFF_PHASE_MULTIPLE
46    
47        IF ( myIter.NE.nIter0 ) THEN        IF ( myIter.NE.nIter0 ) THEN
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    
54  #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  
   
55          DO n = 1,nlists          DO n = 1,nlists
56           realfreq = freq(n)            freqSec = freq(n)
57              phiSec = phase(n)
58    
59              IF ( freqSec.LT.0. ) THEN
60    C--     write snap-shot with suffix = myIter to be consistent with
61    C       time-average diagnostics (e.g., freq=-1 & freq=1):
62    c           wrIter = myIter
63    c           wrTime = myTime
64    C--     write snap-shot with suffix = myIter-1 to be consistent with
65    C       state-variable time-step:
66                wrIter = myItM1
67                wrTime = myTime - deltaTclock
68              ELSE
69                wrIter = myIter
70                wrTime = myTime
71              ENDIF
72              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
73         &                                        wrTime, deltaTclock )
74  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
75           if( useFIZHI) then            IF ( useFIZHI ) THEN
76            yymmdd = int(freq(n))             WRITE(tagname,'(A,I2.2)')'diagtag',n
77            hhmmss = int((freq(n) - int(freq(n)))*1.e6)             dump2fileNow = alarm2(tagname)
78            realfreq = nsecf2(hhmmss,yymmdd,nymd) / deltaTclock            ENDIF
          endif  
79  #endif  #endif
80    #ifdef ALLOW_CAL
81              IF ( useCAL ) THEN
82                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.
91                CALL DIAGNOSTICS_OUT(n,wrIter,wrTime,myThid)
92              ENDIF
93            ENDDO
94    
95            IF ( realfreq.LT.0 ) THEN  C---   Check to see if its time for Statistics Diag. Output
96              dump2fileNow = MOD(myItM1,-realfreq) .EQ. INT(-realfreq/2)  
97  C--     write snap-shot with suffix = myIter to be consistent with          DO n = 1,diagSt_nbLists
98              freqSec = diagSt_freq(n)
99              phiSec = diagSt_phase(n)
100    
101              IF ( freqSec.LT.0. ) THEN
102    C--     write snap-shot with suffix = myIter to be consistent with
103  C       time-average diagnostics (e.g., freq=-1 & freq=1):  C       time-average diagnostics (e.g., freq=-1 & freq=1):
104  c           wrIter = myIter  c           wrIter = myIter
105    c           wrTime = myTime
106  C--     write snap-shot with suffix = myIter-1 to be consistent with  C--     write snap-shot with suffix = myIter-1 to be consistent with
107  C       state-variable time-step:  C       state-variable time-step:
108              wrIter = myItM1              wrIter = myItM1
109                wrTime = myTime - deltaTclock
110            ELSE            ELSE
             dump2fileNow = MOD(myIter,realfreq) .EQ. 0  
111              wrIter = myIter              wrIter = myIter
112                wrTime = myTime
113            ENDIF            ENDIF
114              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
115  #ifdef ALLOW_CAL       &                                        wrTime, deltaTclock )
116            freqSec = realfreq * deltaTClock  #ifdef ALLOW_FIZHI
117            IF ( calendarDumps .AND. (            IF ( useFIZHI ) THEN
118       &     ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.             WRITE(tagname,'(A,I2.2)')'diagStg',n
119       &     ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN             dump2fileNow = alarm2(tagname)
 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.  
120            ENDIF            ENDIF
121  #endif  #endif
122              IF ( dumpAtLast .AND. modelEnd
123         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
124            IF ( dump2fileNow ) THEN            IF ( dump2fileNow ) THEN
125              CALL DIAGNOSTICS_OUT(n,wrIter,myThid)              write2file = .TRUE.
126                CALL DIAGSTATS_OUTPUT(n,wrTime,wrIter,myThid)
127            ENDIF            ENDIF
128          ENDDO          ENDDO
129    
130  C-      wait for everyone before setting arrays to zero:  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
131          _BARRIER  
132            IF ( write2file ) THEN
133              IF ( debugLevel.GE.debLevB ) THEN
134                CALL DIAGNOSTICS_SUMMARY( myTime, myIter, myThid )
135              ENDIF
136    C-      wait for everyone before setting arrays to zero:
137              _BARRIER
138            ENDIF
139    
140    C--     Clear storage space:
141    
142          DO n = 1,nlists          DO n = 1,nlists
143           realfreq = freq(n)            freqSec = freq(n)
144              phiSec = phase(n)
145    
146              wrTime = myTime
147              IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
148              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
149         &                                        wrTime, deltaTclock )
150  #ifdef ALLOW_FIZHI  #ifdef ALLOW_FIZHI
151           if( useFIZHI) then            IF ( useFIZHI ) THEN
152            yymmdd = int(freq(n))             WRITE(tagname,'(A,I2.2)')'diagtag',n
153            hhmmss = int((freq(n) - int(freq(n)))*1.e6)             dump2fileNow = alarm2(tagname)
154            realfreq = nsecf2(hhmmss,yymmdd,nymd) / deltaTclock            ENDIF
          endif  
155  #endif  #endif
156            IF ( realfreq.LT.0 ) THEN  #ifdef ALLOW_CAL
157              dump2fileNow = MOD(myItM1,-realfreq) .EQ. INT(-realfreq/2)            IF ( useCAL ) THEN
158            ELSE              CALL CAL_TIME2DUMP( freqSec, deltaTClock,
159              dump2fileNow = MOD(myIter,realfreq) .EQ. 0       U                          dump2fileNow,
160         I                          myTime, myIter, myThid )
161              ENDIF
162    #endif /* ALLOW_CAL */
163              IF ( dumpAtLast .AND. modelEnd
164         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
165              IF ( dump2fileNow ) CALL DIAGNOSTICS_CLEAR(n,myThid)
166            ENDDO
167    
168            DO n = 1,diagSt_nbLists
169              freqSec = diagSt_freq(n)
170              phiSec = diagSt_phase(n)
171              wrTime = myTime
172              IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
173              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
174         &                                        wrTime, deltaTclock )
175    #ifdef ALLOW_FIZHI
176              IF ( useFIZHI ) THEN
177               WRITE(tagname,'(A,I2.2)')'diagStg',n
178               dump2fileNow = alarm2(tagname)
179            ENDIF            ENDIF
180            IF ( dump2fileNow ) CALL CLRINDX(n,myThid)  #endif
181              IF ( dumpAtLast .AND. modelEnd
182         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
183              IF ( dump2fileNow ) CALL DIAGSTATS_CLEAR( n, myThid )
184          ENDDO          ENDDO
185    
186  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
187        ENDIF        ENDIF
188    
189        RETURN        RETURN
190        END        END

Legend:
Removed from v.1.13  
changed lines
  Added in v.1.31

  ViewVC Help
Powered by ViewVC 1.1.22