/[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.13 - (hide annotations) (download)
Fri May 13 18:32:46 2005 UTC (19 years ago) by molod
Branch: MAIN
Changes since 1.12: +5 -3 lines
Get coding in fizhi case for numbers after the decimal (less than 1 day)

1 molod 1.13 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_write.F,v 1.12 2005/05/13 18:22:53 molod 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.12 #ifdef ALLOW_FIZHI
25     #include "chronos.h"
26     #endif
27 molod 1.1
28 jmc 1.9 _RL myTime
29 jmc 1.8 INTEGER myIter, myThid
30 molod 1.1
31     c Local variables
32     c ===============
33 jmc 1.8 INTEGER n
34 jmc 1.9 INTEGER myItM1, wrIter
35     LOGICAL dump2fileNow
36 dimitri 1.10 INTEGER thisdate(4), prevdate(4)
37     _RL freqSec
38 molod 1.12 integer realfreq,nsecf2,yymmdd,hhmmss
39 jmc 1.8
40 jmc 1.9 IF ( myIter.NE.nIter0 ) THEN
41     myItM1 = myIter - 1
42 molod 1.1
43     C***********************************************************************
44 jmc 1.8 C*** Check to see IF its time for Diagnostic Output ***
45 molod 1.1 C***********************************************************************
46    
47 dimitri 1.10 #ifdef ALLOW_CAL
48     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 jmc 1.8 DO n = 1,nlists
56 molod 1.12 realfreq = freq(n)
57     #ifdef ALLOW_FIZHI
58     if( useFIZHI) then
59     yymmdd = int(freq(n))
60 molod 1.13 hhmmss = int((freq(n) - int(freq(n)))*1.e6)
61     realfreq = nsecf2(hhmmss,yymmdd,nymd) / deltaTclock
62 molod 1.12 endif
63     #endif
64    
65     IF ( realfreq.LT.0 ) THEN
66     dump2fileNow = MOD(myItM1,-realfreq) .EQ. INT(-realfreq/2)
67 jmc 1.9 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 molod 1.12 dump2fileNow = MOD(myIter,realfreq) .EQ. 0
75 jmc 1.9 wrIter = myIter
76     ENDIF
77 dimitri 1.10
78     #ifdef ALLOW_CAL
79 molod 1.12 freqSec = realfreq * deltaTClock
80 dimitri 1.10 IF ( calendarDumps .AND. (
81     & ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.
82 dimitri 1.11 & ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN
83 dimitri 1.10 C-- Convert approximate months (30-31 days) and years (360-372 days)
84     C to exact calendar months and years.
85 dimitri 1.11 dump2fileNow = .FALSE.
86 dimitri 1.10 C- Monthly freqSec:
87     IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.
88 dimitri 1.11 & (thisdate(1)-prevdate(1)).GT.50 ) dump2fileNow = .TRUE.
89 dimitri 1.10 C- Yearly freqSec:
90     IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.
91 dimitri 1.11 & (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.
92 dimitri 1.10 ENDIF
93     #endif
94    
95 jmc 1.9 IF ( dump2fileNow ) THEN
96     CALL DIAGNOSTICS_OUT(n,wrIter,myThid)
97 jmc 1.8 ENDIF
98     ENDDO
99    
100     C- wait for everyone before setting arrays to zero:
101     _BARRIER
102     DO n = 1,nlists
103 molod 1.12 realfreq = freq(n)
104     #ifdef ALLOW_FIZHI
105     if( useFIZHI) then
106     yymmdd = int(freq(n))
107 molod 1.13 hhmmss = int((freq(n) - int(freq(n)))*1.e6)
108     realfreq = nsecf2(hhmmss,yymmdd,nymd) / deltaTclock
109 molod 1.12 endif
110     #endif
111     IF ( realfreq.LT.0 ) THEN
112     dump2fileNow = MOD(myItM1,-realfreq) .EQ. INT(-realfreq/2)
113 jmc 1.9 ELSE
114 molod 1.12 dump2fileNow = MOD(myIter,realfreq) .EQ. 0
115 jmc 1.9 ENDIF
116     IF ( dump2fileNow ) CALL CLRINDX(n,myThid)
117 jmc 1.8 ENDDO
118    
119     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
120     ENDIF
121    
122     RETURN
123     END

  ViewVC Help
Powered by ViewVC 1.1.22