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

Legend:
Removed from v.1.11  
changed lines
  Added in v.1.30

  ViewVC Help
Powered by ViewVC 1.1.22