/[MITgcm]/MITgcm/pkg/diagnostics/diagnostics_write.F
ViewVC logotype

Annotation of /MITgcm/pkg/diagnostics/diagnostics_write.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.11 - (hide annotations) (download)
Sun Feb 20 19:41:11 2005 UTC (19 years, 2 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint57g_post, checkpoint57e_post, checkpoint57g_pre, checkpoint57f_pre, eckpoint57e_pre, checkpoint57f_post, checkpoint57h_pre
Changes since 1.10: +5 -5 lines
bug fix for calendarDumps

1 dimitri 1.11 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_write.F,v 1.10 2005/02/20 11:46:25 dimitri Exp $
2 edhill 1.6 C $Name: $
3    
4 edhill 1.7 #include "DIAG_OPTIONS.h"
5    
6 jmc 1.9 SUBROUTINE DIAGNOSTICS_WRITE ( myTime, myIter, myThid )
7 molod 1.1 C***********************************************************************
8     C Purpose
9     C -------
10 molod 1.2 C Output sequence for the (multiple) diagnostics output files
11 molod 1.1 C
12     C Arguments Description
13     C ----------------------
14 jmc 1.9 C myTime :: Current time of simulation ( s )
15     C myIter :: Current Iteration Number
16     C myThid :: my thread Id number
17 molod 1.1 C***********************************************************************
18 jmc 1.8 IMPLICIT NONE
19 molod 1.1 #include "SIZE.h"
20 jmc 1.8 #include "DIAGNOSTICS_SIZE.h"
21     #include "DIAGNOSTICS.h"
22 molod 1.4 #include "EEPARAMS.h"
23     #include "PARAMS.h"
24 molod 1.1
25 jmc 1.9 _RL myTime
26 jmc 1.8 INTEGER myIter, myThid
27 molod 1.1
28     c Local variables
29     c ===============
30 jmc 1.8 INTEGER n
31 jmc 1.9 INTEGER myItM1, wrIter
32     LOGICAL dump2fileNow
33 dimitri 1.10 INTEGER thisdate(4), prevdate(4)
34     _RL freqSec
35 jmc 1.8
36 jmc 1.9 IF ( myIter.NE.nIter0 ) THEN
37     myItM1 = myIter - 1
38 molod 1.1
39     C***********************************************************************
40 jmc 1.8 C*** Check to see IF its time for Diagnostic Output ***
41 molod 1.1 C***********************************************************************
42    
43 dimitri 1.10 #ifdef ALLOW_CAL
44     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 jmc 1.8 DO n = 1,nlists
52 jmc 1.9 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 dimitri 1.10
65     #ifdef ALLOW_CAL
66     freqSec = freq(n) * deltaTClock
67     IF ( calendarDumps .AND. (
68     & ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.
69 dimitri 1.11 & ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN
70 dimitri 1.10 C-- Convert approximate months (30-31 days) and years (360-372 days)
71     C to exact calendar months and years.
72 dimitri 1.11 dump2fileNow = .FALSE.
73 dimitri 1.10 C- Monthly freqSec:
74     IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.
75 dimitri 1.11 & (thisdate(1)-prevdate(1)).GT.50 ) dump2fileNow = .TRUE.
76 dimitri 1.10 C- Yearly freqSec:
77     IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.
78 dimitri 1.11 & (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.
79 dimitri 1.10 ENDIF
80     #endif
81    
82 jmc 1.9 IF ( dump2fileNow ) THEN
83     CALL DIAGNOSTICS_OUT(n,wrIter,myThid)
84 jmc 1.8 ENDIF
85     ENDDO
86    
87     C- wait for everyone before setting arrays to zero:
88     _BARRIER
89     DO n = 1,nlists
90 jmc 1.9 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 jmc 1.8 ENDDO
97    
98     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
99     ENDIF
100    
101     RETURN
102     END

  ViewVC Help
Powered by ViewVC 1.1.22