/[MITgcm]/MITgcm/pkg/timeave/timeave_statvars.F
ViewVC logotype

Contents of /MITgcm/pkg/timeave/timeave_statvars.F

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


Revision 1.3 - (show annotations) (download)
Thu Jan 3 16:25:44 2002 UTC (22 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint44e_post, checkpoint46g_pre, checkpoint46f_post, checkpoint44f_post, checkpoint46b_post, checkpoint43a-release1mods, chkpt44d_post, checkpoint44e_pre, checkpoint46d_pre, release1-branch_tutorials, checkpoint45d_post, chkpt44a_post, checkpoint44h_pre, checkpoint46a_post, chkpt44c_pre, checkpoint45a_post, checkpoint44g_post, checkpoint46e_pre, checkpoint45b_post, checkpoint46b_pre, release1-branch-end, release1_final_v1, checkpoint46c_pre, checkpoint46, checkpoint44b_post, checkpoint46a_pre, checkpoint45c_post, checkpoint44h_post, chkpt44a_pre, checkpoint46c_post, checkpoint46e_post, checkpoint44b_pre, checkpoint44, checkpoint45, chkpt44c_post, checkpoint44f_pre, checkpoint46d_post, release1-branch_branchpoint
Branch point for: release1_final, release1-branch
Changes since 1.2: +68 -19 lines
change heat transport diagnostic (UTtave & VTtave):
 hFactor is now included in UTtave and VTtave output file and
 can be directly used to compute heat transport.
add new time average diagnostics :
 * Eta**2
 * wVel*Theta
 * volume transport hFac*U, hFac*V (only with NONLIN_FRSURF).

Note: since wVel and Theta are not updated synchronously in the model,
 WTtave output must be used with some cautious.

1 C $Header: /u/gcmpack/models/MITgcmUV/pkg/timeave/timeave_statvars.F,v 1.2 2001/05/29 14:01:40 adcroft Exp $
2 C $Name: $
3 #include "CPP_OPTIONS.h"
4
5 SUBROUTINE TIMEAVE_STATVARS(
6 I myTime, myIter, bi, bj, myThid)
7 C /==========================================================\
8 C | SUBROUTINE TIMEAVE_STATVARS |
9 C | o Time averaging routine for eta, U, V, W, T, S, UT, VT |
10 C | in model main time-stepping |
11 C \==========================================================/
12 IMPLICIT NONE
13
14 C == Global variables ===
15 #include "SIZE.h"
16 #include "EEPARAMS.h"
17 #include "PARAMS.h"
18 #include "DYNVARS.h"
19 #include "GRID.h"
20 #include "TIMEAVE_STATV.h"
21
22 LOGICAL DIFFERENT_MULTIPLE
23 EXTERNAL DIFFERENT_MULTIPLE
24
25 C == Routine arguments ==
26 C myThid - Thread number for this instance of the routine.
27 C myIter - Iteration number
28 C myTime - Current time of simulation ( s )
29 INTEGER myThid
30 INTEGER myIter, bi, bj
31 _RL myTime
32
33 #ifdef ALLOW_TIMEAVE
34
35 C == Local variables ==
36 INTEGER K
37 _RL DDTT
38
39 C- Initialize fields for the first call ever
40 IF ( myIter .EQ. nIter0 ) THEN
41 CALL TIMEAVE_RESET(etatave, 1, bi, bj, myThid)
42 CALL TIMEAVE_RESET(thetatave, Nr, bi, bj, myThid)
43 CALL TIMEAVE_RESET(salttave, Nr, bi, bj, myThid)
44 CALL TIMEAVE_RESET(uVeltave, Nr, bi, bj, myThid)
45 CALL TIMEAVE_RESET(vVeltave, Nr, bi, bj, myThid)
46 CALL TIMEAVE_RESET(wVeltave, Nr, bi, bj, myThid)
47
48 CALL TIMEAVE_RESET(Eta2tave, 1, bi, bj, myThid)
49 CALL TIMEAVE_RESET(TTtave, Nr, bi, bj, myThid)
50 CALL TIMEAVE_RESET(UUtave, Nr, bi, bj, myThid)
51 CALL TIMEAVE_RESET(VVtave, Nr, bi, bj, myThid)
52 c CALL TIMEAVE_RESET(KEtave, Nr, bi, bj, myThid)
53 CALL TIMEAVE_RESET(UTtave, Nr, bi, bj, myThid)
54 CALL TIMEAVE_RESET(VTtave, Nr, bi, bj, myThid)
55 CALL TIMEAVE_RESET(WTtave, Nr, bi, bj, myThid)
56 CALL TIMEAVE_RESET(phiHydtave,Nr, bi, bj, myThid)
57 CALL TIMEAVE_RESET(ConvectCountTave,Nr,bi,bj,myThid)
58 #ifdef NONLIN_FRSURF
59 CALL TIMEAVE_RESET(hUtave, Nr, bi, bj, myThid)
60 CALL TIMEAVE_RESET(hVtave, Nr, bi, bj, myThid)
61 c CALL TIMEAVE_RESET(hFacCtave, Nr, bi, bj, myThid)
62 c CALL TIMEAVE_RESET(hFacWtave, Nr, bi, bj, myThid)
63 c CALL TIMEAVE_RESET(hFacStave, Nr, bi, bj, myThid)
64 #endif /* NONLIN_FRSURF */
65 DO K=1,Nr
66 TimeAve_half(k,bi,bj)=0.
67 TimeAve_full(k,bi,bj)=0.
68 ENDDO
69 ENDIF
70
71 C-- Cumulate state-variables with Half or Full time step :
72 IF ( myIter .EQ. nIter0 .OR.
73 & DIFFERENT_MULTIPLE(taveFreq, myTime, myTime-deltaTClock)) THEN
74 DDTT=0.5*deltaTclock
75 ELSE
76 DDTT=deltaTclock
77 ENDIF
78
79 C- Time Averages of single fields (no hFactor)
80 CALL TIMEAVE_CUMULATE(etatave, etaN, 1 , DDTT, bi, bj, myThid)
81 CALL TIMEAVE_CUMULATE(thetatave,theta, Nr, DDTT, bi, bj, myThid)
82 CALL TIMEAVE_CUMULATE(salttave, salt, Nr, DDTT, bi, bj, myThid)
83 CALL TIMEAVE_CUMULATE(uVeltave, uVel, Nr, DDTT, bi, bj, myThid)
84 CALL TIMEAVE_CUMULATE(vVeltave, vVel, Nr, DDTT, bi, bj, myThid)
85
86 C- Time Averages of "double" fields (no hFactor)
87 CALL TIMEAVE_CUMUL_2V(Eta2tave, etaN,etaN, 1, 0,
88 & DDTT, bi, bj, myThid)
89 CALL TIMEAVE_CUMUL_2V(TTtave, theta,theta, Nr, 0,
90 & DDTT, bi, bj, myThid)
91 CALL TIMEAVE_CUMUL_2V(UUtave, uVel, uVel, Nr, 0,
92 & DDTT, bi, bj, myThid)
93 CALL TIMEAVE_CUMUL_2V(VVtave, vVel, vVel, Nr, 0,
94 & DDTT, bi, bj, myThid)
95 c CALL TIMEAVE_CUMUL_KE(KEtave, uVel, vVel, Nr,
96 c & DDTT, bi, bj, myThid)
97
98 #ifdef NONLIN_FRSURF
99
100 c CALL TIMEAVE_CUMUL_FC(hFacCtave,hFacC, Nr, DDTT, bi, bj, myThid)
101 c CALL TIMEAVE_CUMUL_FC(hFacWtave,hFacW, Nr, DDTT, bi, bj, myThid)
102 c CALL TIMEAVE_CUMUL_FC(hFacStave,hFacS, Nr, DDTT, bi, bj, myThid)
103
104 C- Time Averages of single fields (* hFactor)
105 CALL TIMEAVE_CUMUL_1VFC(hUtave, uVel, hFacW, Nr,
106 & DDTT, bi, bj, myThid)
107 CALL TIMEAVE_CUMUL_1VFC(hVtave, vVel, hFacS, Nr,
108 & DDTT, bi, bj, myThid)
109
110 #endif /* NONLIN_FRSURF */
111
112 C- Time Averages of "double" fields (* hFactor)
113 CALL TIMEAVE_CUMUL_2VFC(UTtave, theta, uVel, hFacW, Nr, 1,
114 & DDTT, bi, bj, myThid)
115 CALL TIMEAVE_CUMUL_2VFC(VTtave, theta, vVel, hFacS, Nr, 2,
116 & DDTT, bi, bj, myThid)
117
118 C- Time Averages of "double" fields (no hFactor)
119 c CALL TIMEAVE_CUMUL_2V(UTtave, theta, uVel, Nr, 1,
120 c & DDTT, bi, bj, myThid)
121 c CALL TIMEAVE_CUMUL_2V(VTtave, theta, vVel, Nr, 2,
122 c & DDTT, bi, bj, myThid)
123
124
125 C- Keep record of how much time has been integrated over
126 DO K=1,Nr
127 TimeAve_half(k,bi,bj)=TimeAve_half(k,bi,bj)+DDTT
128 ENDDO
129
130 C- CAUTIOUS : wVel and theta are not synchronously updated during the model
131 C time-stepping, so that the time-average diagnostic of the cross product
132 C W*Theta is not perfectly accurate.
133
134 C- Time Averages of "intermediate" fields (no hFactor)
135 IF ( myIter .NE. nIter0 ) THEN
136 CALL TIMEAVE_CUMULATE(wVeltave, wVel, Nr, deltaTclock,
137 & bi, bj, myThid)
138 CALL TIMEAVE_CUMUL_2V(WTtave, theta, wVel, Nr, 3,
139 & deltaTclock, bi, bj, myThid)
140 DO K=1,Nr
141 TimeAve_full(k,bi,bj)=TimeAve_full(k,bi,bj)+deltaTclock
142 ENDDO
143 ENDIF
144
145 #endif /* ALLOW_TIMEAVE */
146
147 RETURN
148 END

  ViewVC Help
Powered by ViewVC 1.1.22