/[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.2 by molod, Thu Feb 26 02:21:18 2004 UTC revision 1.15 by molod, Mon May 16 23:41:32 2005 UTC
# Line 1  Line 1 
1        subroutine diagnostics_write (myThid, myIter)  C $Header$
2    C $Name$
3    
4    #include "DIAG_OPTIONS.h"
5    
6          SUBROUTINE DIAGNOSTICS_WRITE ( myTime, myIter, myThid )
7  C***********************************************************************  C***********************************************************************
8  C  Purpose  C  Purpose
9  C  -------  C  -------
# Line 6  C    Output sequence for the (multiple) Line 11  C    Output sequence for the (multiple)
11  C  C
12  C  Arguments  Description  C  Arguments  Description
13  C  ----------------------  C  ----------------------
14  C     myIter ..... Current Iteration Number  C     myTime :: Current time of simulation ( s )
15  C     myThid ..... Current Process(or)  C     myIter :: Current Iteration Number
16    C     myThid :: my thread Id number
17  C***********************************************************************  C***********************************************************************
18         implicit none         IMPLICIT NONE
 #include "CPP_OPTIONS.h"  
19  #include "SIZE.h"  #include "SIZE.h"
20  #include "fizhi_SIZE.h"  #include "DIAGNOSTICS_SIZE.h"
21  #include "diagnostics_SIZE.h"  #include "DIAGNOSTICS.h"
22  #include "diagnostics.h"  #include "EEPARAMS.h"
23    #include "PARAMS.h"
24    #ifdef ALLOW_FIZHI
25    #include "chronos.h"
26    #endif
27    
28        integer myThid, myIter  C     !INPUT PARAMETERS:
29          _RL     myTime
30          INTEGER myIter, myThid
31    
32  c Local variables  c Local variables
33  c ===============  c ===============
34        integer   n        INTEGER   n
35          INTEGER   myItM1, wrIter
36          LOGICAL   dump2fileNow
37          _RL       phiSec, freqSec, wrTime
38    #ifdef ALLOW_CAL
39          INTEGER thisdate(4), prevdate(4)
40    #endif
41    #ifdef ALLOW_FIZHI
42          integer nsecf2,mmdd,hhmmss,alarm2
43          character *9 tagname
44    #endif
45    
46          LOGICAL  DIFF_PHASE_MULTIPLE
47          EXTERNAL DIFF_PHASE_MULTIPLE
48    
49          IF ( myIter.NE.nIter0 ) THEN
50            myItM1 = myIter - 1
51    
52  C***********************************************************************  C***********************************************************************
53  C***   Check to see if its time for Diagnostic Output                ***  C***   Check to see IF its time for Diagnostic Output                ***
54  C***********************************************************************  C***********************************************************************
       do n=1,nlists  
       if ( mod(freq(n),myIter).eq.0 ) then  
        call diagout(myThid,n)  
        call clrindx(myThid,n)  
       endif  
       enddo  
55    
56        return  #ifdef ALLOW_CAL
57        end          IF ( calendarDumps ) THEN
58    C-    Determine calendar dates for this and previous time step.
59               call cal_GetDate(myiter  ,mytime            ,thisdate,mythid)
60               call cal_GetDate(myiter-1,mytime-deltaTClock,prevdate,mythid)
61            ENDIF
62    #endif
63    
64            DO n = 1,nlists
65              freqSec = freq(n)
66              phiSec = phase(n)
67    #ifdef ALLOW_FIZHI
68             if( useFIZHI) then
69              mmdd = int(freq(n))
70              hhmmss = int((freq(n) - int(freq(n)))*1.e6)
71              freqSec = nsecf2(hhmmss,mmdd,nymd)
72             endif
73    #endif
74    
75              IF ( freqSec.LT.0. ) THEN
76    C--     write snap-shot with suffix = myIter to be consistent with
77    C       time-average diagnostics (e.g., freq=-1 & freq=1):
78    c           wrIter = myIter
79    c           wrTime = myTime
80    C--     write snap-shot with suffix = myIter-1 to be consistent with
81    C       state-variable time-step:
82                wrIter = myItM1
83                wrTime = myTime - deltaTclock
84              ELSE
85                wrIter = myIter
86                wrTime = myTime
87              ENDIF
88              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
89         &                                        wrTime, deltaTclock )
90    #ifdef ALLOW_FIZHI
91             if( useFIZHI) then
92              write(tagname,'(A,I2.2)')'diagtag',n
93              dump2fileNow = alarm2(tagname)
94             endif
95    #endif
96    
97    #ifdef ALLOW_CAL
98              IF ( calendarDumps .AND. (
99         &     ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.
100         &     ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN
101    C--   Convert approximate months (30-31 days) and years (360-372 days)
102    C     to exact calendar months and years.
103               dump2fileNow = .FALSE.
104    C-    Monthly freqSec:
105               IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.
106         &        (thisdate(1)-prevdate(1)).GT.50   ) dump2fileNow = .TRUE.
107    C-    Yearly  freqSec:
108               IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.
109         &        (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.
110              ENDIF
111    #endif
112    
113              IF ( dump2fileNow ) THEN
114                CALL DIAGNOSTICS_OUT(n,wrIter,myThid)
115              ENDIF
116            ENDDO
117    
118    C-      wait for everyone before setting arrays to zero:
119            _BARRIER
120            DO n = 1,nlists
121              freqSec = freq(n)
122              phiSec = phase(n)
123    #ifdef ALLOW_FIZHI
124             if( useFIZHI) then
125              mmdd = int(freq(n))
126              hhmmss = int((freq(n) - int(freq(n)))*1.e6)
127              freqSec = nsecf2(hhmmss,mmdd,nymd)
128             endif
129    #endif
130              wrTime = myTime
131              IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
132              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
133         &                                        wrTime, deltaTclock )
134    #ifdef ALLOW_FIZHI
135              if( useFIZHI) then
136               write(tagname,'(A,I2.2)')'diagtag',n
137               dump2fileNow = alarm2(tagname)
138              endif
139    #endif
140              IF ( dump2fileNow ) CALL CLRINDX(n,myThid)
141            ENDDO
142    
143    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
144          ENDIF
145    
146          RETURN
147          END

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.15

  ViewVC Help
Powered by ViewVC 1.1.22