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

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

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


Revision 1.4 - (hide annotations) (download)
Fri May 13 18:32:46 2005 UTC (19 years ago) by molod
Branch: MAIN
Changes since 1.3: +3 -2 lines
Get coding in fizhi case for numbers after the decimal (less than 1 day)

1 molod 1.4 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_switch_onoff.F,v 1.3 2005/05/13 18:22:53 molod Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "DIAG_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7     CBOP 0
8     C !ROUTINE: DIAGNOSTICS_SWITCH_ONOFF
9    
10     C !INTERFACE:
11     SUBROUTINE DIAGNOSTICS_SWITCH_ONOFF( myIter, myThid )
12    
13     C !DESCRIPTION:
14     C-----
15     C Called at the beginning of the time-step,
16     C to switch on/off diagnostics for snap-shot output
17     C-----
18     C during iterations that are multiple of |freq|,
19     C switch ON diagnostics (ndiag>=0) that will become active
20     C and then can be written at the end of the time-step ;
21     C otherwise, put diagnostics in non-active mode (ndiag=-1)
22     C-----
23    
24     C !USES:
25     IMPLICIT NONE
26     #include "SIZE.h"
27     #include "EEPARAMS.h"
28     #include "PARAMS.h"
29     #include "DIAGNOSTICS_SIZE.h"
30     #include "DIAGNOSTICS.h"
31 molod 1.3 #ifdef ALLOW_FIZHI
32     #include "chronos.h"
33     #endif
34 jmc 1.1
35     C !INPUT PARAMETERS:
36     C myIter :: current Iteration number
37     C myThid :: my Thread Id number
38     INTEGER myIter
39     INTEGER myThid
40     CEOP
41    
42     C !LOCAL VARIABLES:
43     C newIter :: future iteration number
44     C j,m,n :: loop index
45     c CHARACTER*(MAX_LEN_MBUF) msgBuf
46     INTEGER newIter
47     INTEGER j, m, n
48 molod 1.3 integer realfreq,yymmdd,hhmmss,nsecf2
49 jmc 1.1
50     _BEGIN_MASTER(myThid)
51    
52     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
53    
54     newIter = 1 + myIter
55     DO n = 1,nlists
56 molod 1.3 realfreq = freq(n)
57     #ifdef ALLOW_FIZHI
58     if( useFIZHI) then
59     yymmdd = int(freq(n))
60 molod 1.4 hhmmss = int((freq(n) - int(freq(n)))*1.e6)
61     realfreq = nsecf2(hhmmss,yymmdd,nymd) / deltaTclock
62 molod 1.3 endif
63     #endif
64    
65     IF ( realfreq.LT.0 ) THEN
66 jmc 1.1 C-- Select diagnostics list that uses instantaneous output
67    
68 molod 1.3 c IF ( MOD(newIter,realfreq).EQ.0 ) THEN
69     IF ( MOD(myIter,-realfreq).EQ.INT(-realfreq/2) ) THEN
70 jmc 1.1 C-- switch ON diagnostics of output-stream # n
71     DO m=1,nActive(n)
72     j = jdiag(m,n)
73     c IF (ndiag(j).NE.0) WRITE(0,*) myIter,j,ndiag(j),' ->',0
74     ndiag(j) = 0
75     ENDDO
76     ELSE
77     C-- switch OFF diagnostics of output-stream # n
78     DO m=1,nActive(n)
79     j = jdiag(m,n)
80     c IF (ndiag(j).NE.-1) WRITE(0,*) myIter,j,ndiag(j),' ->',-1
81     ndiag(j) = -1
82     ENDDO
83     ENDIF
84    
85     ENDIF
86     ENDDO
87    
88     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
89    
90     _END_MASTER(myThid)
91    
92     C-jmc: do we need a "BARRIER" at this point ?
93     c _BARRIER
94    
95     RETURN
96     END

  ViewVC Help
Powered by ViewVC 1.1.22