/[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.7 by edhill, Tue Jul 6 03:55:53 2004 UTC revision 1.9 by jmc, Sun Feb 6 23:19:02 2005 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "DIAG_OPTIONS.h"  #include "DIAG_OPTIONS.h"
5    
6        subroutine diagnostics_write (myThid, myIter)        SUBROUTINE DIAGNOSTICS_WRITE ( myTime, myIter, myThid )
7  C***********************************************************************  C***********************************************************************
8  C  Purpose  C  Purpose
9  C  -------  C  -------
# Line 11  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
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    
34          IF ( myIter.NE.nIter0 ) THEN
35            myItM1 = myIter - 1
36    
37  C***********************************************************************  C***********************************************************************
38  C***   Check to see if its time for Diagnostic Output                ***  C***   Check to see IF its time for Diagnostic Output                ***
39  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  
40    
41        return          DO n = 1,nlists
42        end            IF ( freq(n).LT.0 ) THEN
43                dump2fileNow = MOD(myItM1,-freq(n)) .EQ. INT(-freq(n)/2)
44    C--     write snap-shot with suffix = myIter to be consistent with
45    C       time-average diagnostics (e.g., freq=-1 & freq=1):
46    c           wrIter = myIter
47    C--     write snap-shot with suffix = myIter-1 to be consistent with
48    C       state-variable time-step:
49                wrIter = myItM1
50              ELSE
51                dump2fileNow = MOD(myIter,freq(n)) .EQ. 0
52                wrIter = myIter
53              ENDIF
54              IF ( dump2fileNow ) THEN
55                CALL DIAGNOSTICS_OUT(n,wrIter,myThid)
56              ENDIF
57            ENDDO
58    
59    C-      wait for everyone before setting arrays to zero:
60            _BARRIER
61            DO n = 1,nlists
62              IF ( freq(n).LT.0 ) THEN
63                dump2fileNow = MOD(myItM1,-freq(n)) .EQ. INT(-freq(n)/2)
64              ELSE
65                dump2fileNow = MOD(myIter,freq(n)) .EQ. 0
66              ENDIF
67              IF ( dump2fileNow ) CALL CLRINDX(n,myThid)
68            ENDDO
69    
70    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
71          ENDIF
72    
73          RETURN
74          END

Legend:
Removed from v.1.7  
changed lines
  Added in v.1.9

  ViewVC Help
Powered by ViewVC 1.1.22