/[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.11 by dimitri, Sun Feb 20 19:41:11 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    
25        integer myThid, myIter        _RL     myTime
26          INTEGER myIter, myThid
27    
28  c Local variables  c Local variables
29  c ===============  c ===============
30        integer   n        INTEGER   n
31          INTEGER   myItM1, wrIter
32          LOGICAL   dump2fileNow
33          INTEGER thisdate(4), prevdate(4)
34          _RL     freqSec
35    
36          IF ( myIter.NE.nIter0 ) THEN
37            myItM1 = myIter - 1
38    
39  C***********************************************************************  C***********************************************************************
40  C***   Check to see if its time for Diagnostic Output                ***  C***   Check to see IF its time for Diagnostic Output                ***
41  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  
42    
43        return  #ifdef ALLOW_CAL
44        end          IF ( calendarDumps ) THEN
45    C-    Determine calendar dates for this and previous time step.
46               call cal_GetDate(myiter  ,mytime            ,thisdate,mythid)
47               call cal_GetDate(myiter-1,mytime-deltaTClock,prevdate,mythid)
48            ENDIF
49    #endif
50    
51            DO n = 1,nlists
52              IF ( freq(n).LT.0 ) THEN
53                dump2fileNow = MOD(myItM1,-freq(n)) .EQ. INT(-freq(n)/2)
54    C--     write snap-shot with suffix = myIter to be consistent with
55    C       time-average diagnostics (e.g., freq=-1 & freq=1):
56    c           wrIter = myIter
57    C--     write snap-shot with suffix = myIter-1 to be consistent with
58    C       state-variable time-step:
59                wrIter = myItM1
60              ELSE
61                dump2fileNow = MOD(myIter,freq(n)) .EQ. 0
62                wrIter = myIter
63              ENDIF
64    
65    #ifdef ALLOW_CAL
66              freqSec = freq(n) * deltaTClock
67              IF ( calendarDumps .AND. (
68         &     ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.
69         &     ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN
70    C--   Convert approximate months (30-31 days) and years (360-372 days)
71    C     to exact calendar months and years.
72               dump2fileNow = .FALSE.
73    C-    Monthly freqSec:
74               IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.
75         &        (thisdate(1)-prevdate(1)).GT.50   ) dump2fileNow = .TRUE.
76    C-    Yearly  freqSec:
77               IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.
78         &        (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.
79              ENDIF
80    #endif
81    
82              IF ( dump2fileNow ) THEN
83                CALL DIAGNOSTICS_OUT(n,wrIter,myThid)
84              ENDIF
85            ENDDO
86    
87    C-      wait for everyone before setting arrays to zero:
88            _BARRIER
89            DO n = 1,nlists
90              IF ( freq(n).LT.0 ) THEN
91                dump2fileNow = MOD(myItM1,-freq(n)) .EQ. INT(-freq(n)/2)
92              ELSE
93                dump2fileNow = MOD(myIter,freq(n)) .EQ. 0
94              ENDIF
95              IF ( dump2fileNow ) CALL CLRINDX(n,myThid)
96            ENDDO
97    
98    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
99          ENDIF
100    
101          RETURN
102          END

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

  ViewVC Help
Powered by ViewVC 1.1.22