/[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.8 - (hide annotations) (download)
Mon May 22 14:25:46 2006 UTC (18 years, 1 month ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58m_post, checkpoint58r_post, checkpoint58g_post, checkpoint58n_post, checkpoint58h_post, checkpoint58j_post, checkpoint58f_post, checkpoint58i_post, checkpoint58o_post, checkpoint58k_post, checkpoint58u_post, checkpoint58s_post, checkpoint58p_post, checkpoint58t_post, checkpoint58q_post
Changes since 1.7: +6 -5 lines
o replace SBO EOS by EOS actually used by the model
o add global mean bottom pressure to output

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

  ViewVC Help
Powered by ViewVC 1.1.22