/[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.4 by molod, Thu Feb 26 22:49:39 2004 UTC revision 1.16 by molod, Tue May 17 00:22:00 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 "diagnostics_SIZE.h"  #include "DIAGNOSTICS_SIZE.h"
21  #include "diagnostics.h"  #include "DIAGNOSTICS.h"
22  #include "EEPARAMS.h"  #include "EEPARAMS.h"
23  #include "PARAMS.h"  #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
43          logical alarm2
44          character *9 tagname
45    #endif
46    
47          LOGICAL  DIFF_PHASE_MULTIPLE
48          EXTERNAL DIFF_PHASE_MULTIPLE
49    
50          IF ( myIter.NE.nIter0 ) THEN
51            myItM1 = myIter - 1
52    
53  C***********************************************************************  C***********************************************************************
54  C***   Check to see if its time for Diagnostic Output                ***  C***   Check to see IF its time for Diagnostic Output                ***
55  C***********************************************************************  C***********************************************************************
       do n=1,nlists  
       if ( mod(freq(n),myIter).eq.0 .and. myIter.ne.niter0) then  
        call diagout(myThid,myIter,n)  
        call clrindx(myThid,n)  
       endif  
       enddo  
56    
57        return  #ifdef ALLOW_CAL
58        end          IF ( calendarDumps ) THEN
59    C-    Determine calendar dates for this and previous time step.
60               call cal_GetDate(myiter  ,mytime            ,thisdate,mythid)
61               call cal_GetDate(myiter-1,mytime-deltaTClock,prevdate,mythid)
62            ENDIF
63    #endif
64    
65            DO n = 1,nlists
66              freqSec = freq(n)
67              phiSec = phase(n)
68    #ifdef ALLOW_FIZHI
69             if( useFIZHI) then
70              mmdd = int(freq(n))
71              hhmmss = int((freq(n) - int(freq(n)))*1.e6)
72              freqSec = nsecf2(hhmmss,mmdd,nymd)
73             endif
74    #endif
75    
76              IF ( freqSec.LT.0. ) THEN
77    C--     write snap-shot with suffix = myIter to be consistent with
78    C       time-average diagnostics (e.g., freq=-1 & freq=1):
79    c           wrIter = myIter
80    c           wrTime = myTime
81    C--     write snap-shot with suffix = myIter-1 to be consistent with
82    C       state-variable time-step:
83                wrIter = myItM1
84                wrTime = myTime - deltaTclock
85              ELSE
86                wrIter = myIter
87                wrTime = myTime
88              ENDIF
89              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
90         &                                        wrTime, deltaTclock )
91    #ifdef ALLOW_FIZHI
92             if( useFIZHI) then
93              write(tagname,'(A,I2.2)')'diagtag',n
94              dump2fileNow = alarm2(tagname)
95             endif
96    #endif
97    
98    #ifdef ALLOW_CAL
99              IF ( calendarDumps .AND. (
100         &     ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.
101         &     ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN
102    C--   Convert approximate months (30-31 days) and years (360-372 days)
103    C     to exact calendar months and years.
104               dump2fileNow = .FALSE.
105    C-    Monthly freqSec:
106               IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.
107         &        (thisdate(1)-prevdate(1)).GT.50   ) dump2fileNow = .TRUE.
108    C-    Yearly  freqSec:
109               IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.
110         &        (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.
111              ENDIF
112    #endif
113    
114              IF ( dump2fileNow ) THEN
115                CALL DIAGNOSTICS_OUT(n,wrIter,myThid)
116              ENDIF
117            ENDDO
118    
119    C-      wait for everyone before setting arrays to zero:
120            _BARRIER
121            DO n = 1,nlists
122              freqSec = freq(n)
123              phiSec = phase(n)
124    #ifdef ALLOW_FIZHI
125             if( useFIZHI) then
126              mmdd = int(freq(n))
127              hhmmss = int((freq(n) - int(freq(n)))*1.e6)
128              freqSec = nsecf2(hhmmss,mmdd,nymd)
129             endif
130    #endif
131              wrTime = myTime
132              IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
133              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
134         &                                        wrTime, deltaTclock )
135    #ifdef ALLOW_FIZHI
136              if( useFIZHI) then
137               write(tagname,'(A,I2.2)')'diagtag',n
138               dump2fileNow = alarm2(tagname)
139              endif
140    #endif
141              IF ( dump2fileNow ) CALL CLRINDX(n,myThid)
142            ENDDO
143    
144    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
145          ENDIF
146    
147          RETURN
148          END

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.16

  ViewVC Help
Powered by ViewVC 1.1.22