/[MITgcm]/MITgcm/pkg/sbo/sbo_diags.F
ViewVC logotype

Annotation of /MITgcm/pkg/sbo/sbo_diags.F

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


Revision 1.3 - (hide annotations) (download)
Thu Oct 2 14:42:17 2003 UTC (21 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint51j_post, checkpoint51h_pre, checkpoint51g_post, checkpoint51f_post, checkpoint51i_pre
Changes since 1.2: +2 -2 lines
Added CPP style comments to #endif ALLOW_
 #endif ALLOW_  -> #endif /* ALLOW_ */

1 dimitri 1.2 C $Header:
2    
3     #include "SBO_OPTIONS.h"
4    
5     SUBROUTINE SBO_DIAGS( myCurrentTime, myIter, myThid )
6     C /==========================================================\
7     C | SUBROUTINE SBO_DIAGS |
8     C | o Do SBO diagnostic output. |
9     C \==========================================================/
10     IMPLICIT NONE
11    
12     C === Global variables ===
13     #include "SIZE.h"
14     #include "EEPARAMS.h"
15     #include "PARAMS.h"
16     #include "SBO.h"
17    
18     C == Routine arguments ==
19     C myCurrentTime - Current time of simulation ( s )
20     C myIter - Iteration number
21     C myThid - Number of this instance of INI_FORCING
22     _RL myCurrentTime
23     INTEGER myIter
24     INTEGER myThid
25    
26     #ifdef ALLOW_SBO
27    
28     c == Local variables ==
29     c bi, bj - loop counters
30     c sbo_diag - vector of SBO diagnostics contains:
31     c model time (s), xoamc, yoamc, zoamc,
32     c xoamp, yoamp, zoamp, mass, xcom, ycom, zcom
33     INTEGER bi, bj
34     Real*8 sbo_diag(11)
35     LOGICAL DIFFERENT_MULTIPLE
36     EXTERNAL DIFFERENT_MULTIPLE
37     _RL DDTT
38     CHARACTER*(MAX_LEN_MBUF) suff
39     character*(8) fName
40     integer narr
41     integer irecord, k
42    
43     C-----------------------------------------------------------------
44     C Save angular momentum and mass variables at every time step
45     C-----------------------------------------------------------------
46    
47     sbo_diag(1) = myCurrentTime
48     sbo_diag(2) = xoamc
49     sbo_diag(3) = yoamc
50     sbo_diag(4) = zoamc
51     sbo_diag(5) = xoamp
52     sbo_diag(6) = yoamp
53     sbo_diag(7) = zoamp
54     sbo_diag(8) = mass
55     sbo_diag(9) = xcom
56     sbo_diag(10) = ycom
57     sbo_diag(11) = zcom
58    
59     fName = 'SBO_DIAG'
60     narr = 11
61     irecord = myCurrentTime/deltaTClock
62    
63     CALL SBO_WRITEVECTOR(
64     I fName,
65     I narr,
66     I sbo_diag,
67     I irecord,
68     I myIter,
69     I myThid )
70    
71     #ifdef ALLOW_TIMEAVE
72    
73     C-----------------------------------------------------------------
74     C Save time-averaged bottom pressure at sbo_taveFreq intervals
75     C-----------------------------------------------------------------
76    
77     C Initialize averages to zero
78     IF ( myIter.EQ.nIter0 ) THEN
79     DO bj = myByLo(myThid), myByHi(myThid)
80     DO bi = myBxLo(myThid), myBxHi(myThid)
81     CALL TIMEAVE_RESET(OBPtave,1,bi,bj,myThid)
82     DO k=1,Nr
83     sbo_TimeAve(k,bi,bj)=0.
84     ENDDO
85     ENDDO
86     ENDDO
87     ENDIF
88    
89     C Time Average SBO fields
90     IF ( myIter .EQ. nIter0 .OR.
91     & DIFFERENT_MULTIPLE
92     & (sbo_taveFreq,myCurrentTime,myCurrentTime-deltaTClock) )
93     & THEN
94     DDTT=0.5*deltaTclock
95     ELSE
96     DDTT=deltaTclock
97     ENDIF
98     DO bj = myByLo(myThid), myByHi(myThid)
99     DO bi = myBxLo(myThid), myBxHi(myThid)
100     CALL TIMEAVE_CUMULATE(
101     & obp,OBPtave,1,DDTT,bi,bj,myThid)
102    
103     C Keep record of how much time has been integrated over
104     DO k=1,Nr
105     sbo_TimeAve(k,bi,bj)=sbo_TimeAve(k,bi,bj)+DDTT
106     ENDDO
107     ENDDO
108     ENDDO
109    
110     C Dump files and restart average computation if needed
111     IF ( myIter.NE.nIter0 .AND.
112     & DIFFERENT_MULTIPLE(sbo_taveFreq,myCurrentTime,
113     & myCurrentTime-deltaTClock)
114     & ) THEN
115    
116     C Normalize by integrated time
117     DO bj = myByLo(myThid), myByHi(myThid)
118     DO bi = myBxLo(myThid), myBxHi(myThid)
119     CALL TIMEAVE_NORMALIZ(OBPtave,sbo_timeave,1,bi,bj,myThid)
120     ENDDO
121     ENDDO
122    
123     WRITE(suff,'(I10.10)') myIter
124    
125     CALL WRITE_FLD_XY_RL('OBPtave',suff,OBPtave,
126     & myIter,myThid)
127    
128     C Reset averages to zero
129     DO bj = myByLo(myThid), myByHi(myThid)
130     DO bi = myBxLo(myThid), myBxHi(myThid)
131     CALL TIMEAVE_RESET(OBPtave,1,bi,bj,myThid)
132     DO k=1,Nr
133     sbo_TimeAve(k,bi,bj)=0.
134     ENDDO
135     ENDDO
136     ENDDO
137    
138     C Time Average SBO fields
139     DDTT=0.5*deltaTclock
140     DO bj = myByLo(myThid), myByHi(myThid)
141     DO bi = myBxLo(myThid), myBxHi(myThid)
142     CALL TIMEAVE_CUMULATE(
143     & obp,OBPtave,1,DDTT,bi,bj,myThid)
144    
145     C Keep record of how much time has been integrated over
146     DO k=1,Nr
147     sbo_TimeAve(k,bi,bj)=sbo_TimeAve(k,bi,bj)+DDTT
148     ENDDO
149     ENDDO
150     ENDDO
151     ENDIF
152    
153 adcroft 1.3 #endif /* ALLOW_TIMEAVE */
154 dimitri 1.2
155 adcroft 1.3 #endif /* ALLOW_SBO */
156 dimitri 1.2
157     RETURN
158     END

  ViewVC Help
Powered by ViewVC 1.1.22