/[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.6 by edhill, Wed May 5 00:39:21 2004 UTC revision 1.13 by molod, Fri May 13 18:32:46 2005 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4        subroutine diagnostics_write (myThid, myIter)  #include "DIAG_OPTIONS.h"
5    
6          SUBROUTINE DIAGNOSTICS_WRITE ( myTime, myIter, myThid )
7  C***********************************************************************  C***********************************************************************
8  C  Purpose  C  Purpose
9  C  -------  C  -------
# Line 9  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        _RL     myTime
29          INTEGER myIter, myThid
30    
31  c Local variables  c Local variables
32  c ===============  c ===============
33        integer   n        INTEGER   n
34          INTEGER   myItM1, wrIter
35          LOGICAL   dump2fileNow
36          INTEGER thisdate(4), prevdate(4)
37          _RL     freqSec
38          integer realfreq,nsecf2,yymmdd,hhmmss
39    
40          IF ( myIter.NE.nIter0 ) THEN
41            myItM1 = myIter - 1
42    
43  C***********************************************************************  C***********************************************************************
44  C***   Check to see if its time for Diagnostic Output                ***  C***   Check to see IF its time for Diagnostic Output                ***
45  C***********************************************************************  C***********************************************************************
       do n=1,nlists  
       if ( myIter.ne.niter0) then  
        if ( mod(myIter,freq(n)).eq.0 ) then  
         call diagout(myThid,myIter,n)  
         call clrindx(myThid,n)  
        endif  
       endif  
       enddo  
46    
47        return  #ifdef ALLOW_CAL
48        end          IF ( calendarDumps ) THEN
49    C-    Determine calendar dates for this and previous time step.
50               call cal_GetDate(myiter  ,mytime            ,thisdate,mythid)
51               call cal_GetDate(myiter-1,mytime-deltaTClock,prevdate,mythid)
52            ENDIF
53    #endif
54    
55            DO n = 1,nlists
56             realfreq = freq(n)
57    #ifdef ALLOW_FIZHI
58             if( useFIZHI) then
59              yymmdd = int(freq(n))
60              hhmmss = int((freq(n) - int(freq(n)))*1.e6)
61              realfreq = nsecf2(hhmmss,yymmdd,nymd) / deltaTclock
62             endif
63    #endif
64    
65              IF ( realfreq.LT.0 ) THEN
66                dump2fileNow = MOD(myItM1,-realfreq) .EQ. INT(-realfreq/2)
67    C--     write snap-shot with suffix = myIter to be consistent with
68    C       time-average diagnostics (e.g., freq=-1 & freq=1):
69    c           wrIter = myIter
70    C--     write snap-shot with suffix = myIter-1 to be consistent with
71    C       state-variable time-step:
72                wrIter = myItM1
73              ELSE
74                dump2fileNow = MOD(myIter,realfreq) .EQ. 0
75                wrIter = myIter
76              ENDIF
77    
78    #ifdef ALLOW_CAL
79              freqSec = realfreq * deltaTClock
80              IF ( calendarDumps .AND. (
81         &     ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.
82         &     ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN
83    C--   Convert approximate months (30-31 days) and years (360-372 days)
84    C     to exact calendar months and years.
85               dump2fileNow = .FALSE.
86    C-    Monthly freqSec:
87               IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.
88         &        (thisdate(1)-prevdate(1)).GT.50   ) dump2fileNow = .TRUE.
89    C-    Yearly  freqSec:
90               IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.
91         &        (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.
92              ENDIF
93    #endif
94    
95              IF ( dump2fileNow ) THEN
96                CALL DIAGNOSTICS_OUT(n,wrIter,myThid)
97              ENDIF
98            ENDDO
99    
100    C-      wait for everyone before setting arrays to zero:
101            _BARRIER
102            DO n = 1,nlists
103             realfreq = freq(n)
104    #ifdef ALLOW_FIZHI
105             if( useFIZHI) then
106              yymmdd = int(freq(n))
107              hhmmss = int((freq(n) - int(freq(n)))*1.e6)
108              realfreq = nsecf2(hhmmss,yymmdd,nymd) / deltaTclock
109             endif
110    #endif
111              IF ( realfreq.LT.0 ) THEN
112                dump2fileNow = MOD(myItM1,-realfreq) .EQ. INT(-realfreq/2)
113              ELSE
114                dump2fileNow = MOD(myIter,realfreq) .EQ. 0
115              ENDIF
116              IF ( dump2fileNow ) CALL CLRINDX(n,myThid)
117            ENDDO
118    
119    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
120          ENDIF
121    
122          RETURN
123          END

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

  ViewVC Help
Powered by ViewVC 1.1.22