/[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.9 by jmc, Sun Feb 6 23:19:02 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:
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          _RL       phiSec, freqSec, wrTime
35    #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
# Line 38  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            write2file = .FALSE.
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
68              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
69         &                                        wrTime, deltaTclock )
70    #ifdef ALLOW_FIZHI
71              IF( useFIZHI) THEN
72               write(tagname,'(A,I2.2)')'diagtag',n
73               dump2fileNow = alarm2(tagname)
74            ENDIF            ENDIF
75            IF ( dump2fileNow ) THEN  #endif
76              CALL DIAGNOSTICS_OUT(n,wrIter,myThid)  #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 ( 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-      wait for everyone before setting arrays to zero:  C---   Check to see IF its time for Statistics Diag. Output
91          _BARRIER  
92          DO n = 1,nlists          DO n = 1,diagSt_nbLists
93            IF ( freq(n).LT.0 ) THEN            freqSec = diagSt_freq(n)
94              dump2fileNow = MOD(myItM1,-freq(n)) .EQ. INT(-freq(n)/2)            phiSec = diagSt_phase(n)
95    
96              IF ( freqSec.LT.0. ) THEN
97    C--     write snap-shot with suffix = myIter to be consistent with
98    C       time-average diagnostics (e.g., freq=-1 & freq=1):
99    c           wrIter = myIter
100    c           wrTime = myTime
101    C--     write snap-shot with suffix = myIter-1 to be consistent with
102    C       state-variable time-step:
103                wrIter = myItM1
104                wrTime = myTime - deltaTclock
105            ELSE            ELSE
106              dump2fileNow = MOD(myIter,freq(n)) .EQ. 0              wrIter = myIter
107                wrTime = myTime
108              ENDIF
109              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
110         &                                        wrTime, deltaTclock )
111    #ifdef ALLOW_FIZHI
112              IF( useFIZHI) THEN
113               write(tagname,'(A,I2.2)')'diagStg',n
114               dump2fileNow = alarm2(tagname)
115              ENDIF
116    #endif
117              IF ( dump2fileNow .OR.
118         &        (myTime.EQ.endTime .AND. dumpatlast) ) THEN
119                write2file = .TRUE.
120                CALL DIAGSTATS_OUTPUT(n,wrTime,wrIter,myThid)
121              ENDIF
122            ENDDO
123    
124    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
125    
126            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:
135    
136            DO n = 1,nlists
137              freqSec = freq(n)
138              phiSec = phase(n)
139    
140              wrTime = myTime
141              IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
142              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
143         &                                        wrTime, deltaTclock )
144    #ifdef ALLOW_FIZHI
145              IF( useFIZHI) THEN
146               write(tagname,'(A,I2.2)')'diagtag',n
147               dump2fileNow = alarm2(tagname)
148              ENDIF
149    #endif
150    #ifdef ALLOW_CAL
151              IF ( useCAL ) THEN
152                CALL CAL_TIME2DUMP( freqSec, deltaTClock,
153         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
161    
162            DO n = 1,diagSt_nbLists
163              freqSec = diagSt_freq(n)
164              phiSec = diagSt_phase(n)
165              wrTime = myTime
166              IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
167              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
168         &                                        wrTime, deltaTclock )
169    #ifdef ALLOW_FIZHI
170              IF( useFIZHI) THEN
171               write(tagname,'(A,I2.2)')'diagStg',n
172               dump2fileNow = alarm2(tagname)
173            ENDIF            ENDIF
174            IF ( dump2fileNow ) CALL CLRINDX(n,myThid)  #endif
175              IF ( dump2fileNow .OR.
176         &        (myTime.EQ.endTime .AND. dumpatlast)
177         &       ) 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.9  
changed lines
  Added in v.1.28

  ViewVC Help
Powered by ViewVC 1.1.22