/[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.8 - (hide annotations) (download)
Tue May 17 00:22:00 2005 UTC (18 years, 11 months ago) by molod
Branch: MAIN
CVS Tags: checkpoint57h_done
Changes since 1.7: +3 -2 lines
Get type to agree for strict fortran rules

1 molod 1.8 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_switch_onoff.F,v 1.7 2005/05/16 23:41:32 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 jmc 1.5 SUBROUTINE DIAGNOSTICS_SWITCH_ONOFF( myTime, myIter, myThid )
12 jmc 1.1
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 jmc 1.5 C myTime :: current Time of simulation ( s )
37 jmc 1.1 C myIter :: current Iteration number
38     C myThid :: my Thread Id number
39 jmc 1.6 _RL myTime
40 jmc 1.1 INTEGER myIter
41     INTEGER myThid
42     CEOP
43    
44     C !LOCAL VARIABLES:
45     C newIter :: future iteration number
46     C j,m,n :: loop index
47     c CHARACTER*(MAX_LEN_MBUF) msgBuf
48 jmc 1.5 c INTEGER newIter
49 jmc 1.1 INTEGER j, m, n
50 jmc 1.5 LOGICAL time4SnapShot
51     _RL phiSec, freqSec
52     #ifdef ALLOW_FIZHI
53 molod 1.8 integer mmdd,hhmmss,nsecf2
54     logical alarm2
55 molod 1.7 character *9 tagname
56 jmc 1.5 #endif
57    
58     LOGICAL DIFF_PHASE_MULTIPLE
59     EXTERNAL DIFF_PHASE_MULTIPLE
60 jmc 1.1
61     _BEGIN_MASTER(myThid)
62    
63     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
64    
65 jmc 1.5 c newIter = 1 + myIter
66 jmc 1.1 DO n = 1,nlists
67 jmc 1.5
68     IF ( freq(n).LT.0. ) THEN
69     C-- Select diagnostics list that uses instantaneous output
70    
71     freqSec = freq(n)
72     phiSec = phase(n)
73 molod 1.7 time4SnapShot = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
74     & myTime, deltaTclock )
75 molod 1.3 #ifdef ALLOW_FIZHI
76 jmc 1.5 if( useFIZHI) then
77 molod 1.7 mmdd = int(freq(n))
78 jmc 1.5 hhmmss = int((freq(n) - int(freq(n)))*1.e6)
79 molod 1.7 freqSec = nsecf2(hhmmss,mmdd,nymd)
80     write(tagname,'(A,I2.2)')'diagtag',n
81     time4SnapShot = alarm2(tagname)
82 jmc 1.5 endif
83 molod 1.3 #endif
84    
85 jmc 1.5 IF ( time4SnapShot ) THEN
86 jmc 1.1 C-- switch ON diagnostics of output-stream # n
87     DO m=1,nActive(n)
88     j = jdiag(m,n)
89     c IF (ndiag(j).NE.0) WRITE(0,*) myIter,j,ndiag(j),' ->',0
90     ndiag(j) = 0
91     ENDDO
92     ELSE
93     C-- switch OFF diagnostics of output-stream # n
94     DO m=1,nActive(n)
95     j = jdiag(m,n)
96     c IF (ndiag(j).NE.-1) WRITE(0,*) myIter,j,ndiag(j),' ->',-1
97     ndiag(j) = -1
98     ENDDO
99     ENDIF
100    
101     ENDIF
102     ENDDO
103    
104     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
105    
106     _END_MASTER(myThid)
107    
108     C-jmc: do we need a "BARRIER" at this point ?
109     c _BARRIER
110    
111     RETURN
112     END

  ViewVC Help
Powered by ViewVC 1.1.22