/[MITgcm]/MITgcm/pkg/ecco/cost_averagesflags.F
ViewVC logotype

Annotation of /MITgcm/pkg/ecco/cost_averagesflags.F

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


Revision 1.3 - (hide annotations) (download)
Fri Jul 7 22:53:36 2006 UTC (17 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58r_post, checkpoint58n_post, checkpoint58q_post, checkpoint58o_post, checkpoint58s_post, checkpoint58p_post, checkpoint58m_post
Changes since 1.2: +67 -3 lines
o cost_averagesflags now returns year indices in addition to day, month
o sflux balance is performed on annual basis
  (sflxumm, sfluxmm2, bal_sfluxmm)
o for SSH anomaly, separate more cleanly contrib from T/P, ERS, GFO,
  including separate counting and multipliers

1 heimbach 1.3 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_averagesflags.F,v 1.2 2004/10/11 16:38:53 heimbach Exp $
2 heimbach 1.1
3     #include "COST_CPPOPTIONS.h"
4    
5    
6     subroutine cost_AveragesFlags(
7     I myiter,
8     I mytime,
9     I mythid,
10     O first,
11 heimbach 1.3 O last,
12 heimbach 1.1 O startofday,
13     O startofmonth,
14 heimbach 1.3 O startofyear,
15 heimbach 1.1 O inday,
16     O inmonth,
17 heimbach 1.3 O inyear,
18 heimbach 1.1 O endofday,
19     O endofmonth,
20 heimbach 1.3 O endofyear,
21 heimbach 1.1 O sum1day,
22     O dayrec,
23     O sum1mon,
24 heimbach 1.3 O monrec,
25     O sum1year,
26     O yearrec
27 heimbach 1.1 & )
28    
29     c ==================================================================
30     c SUBROUTINE cost_AveragesFlags
31     c ==================================================================
32     c
33     c o Get flags for the daily and monthly time averaging.
34     c
35     c started: Christian Eckert eckert@mit.edu 24-Feb-2000
36     c
37     c - Introduced in order to create a package for the
38     c MITgcmUV.
39     c
40     c changed:
41     c
42     c ==================================================================
43     c SUBROUTINE cost_AveragesFlags
44     c ==================================================================
45    
46     implicit none
47    
48     c == global variables ==
49    
50     #include "EEPARAMS.h"
51     #include "SIZE.h"
52    
53     #include "cal.h"
54    
55     c == routine arguments ==
56    
57     integer myiter
58     _RL mytime
59     integer mythid
60     logical first
61     logical startofday
62     logical startofmonth
63 heimbach 1.3 logical startofyear
64 heimbach 1.1 logical inday
65     logical inmonth
66 heimbach 1.3 logical inyear
67 heimbach 1.1 logical last
68     logical endofday
69     logical endofmonth
70 heimbach 1.3 logical endofyear
71 heimbach 1.1 integer sum1day
72     integer dayrec
73     integer sum1mon
74     integer monrec
75 heimbach 1.3 integer sum1year
76     integer yearrec
77 heimbach 1.1
78     c == local variables ==
79    
80     integer mydate(4)
81     integer nextdate(4)
82     integer prevdate(4)
83     integer timediff(4)
84     integer datediff(4)
85     integer targetdate(4)
86     integer targetdate1
87     integer targetdate2
88     integer mydateday
89     integer mydatemonth
90 heimbach 1.3 integer mydateyear
91 heimbach 1.1 integer nextdateday
92     integer nextdatemonth
93 heimbach 1.3 integer nextdateyear
94 heimbach 1.1 integer prevdateday
95     integer prevdatemonth
96 heimbach 1.3 integer prevdateyear
97 heimbach 1.1
98     logical equal
99    
100     c == external functions ==
101    
102     logical cal_CompDates
103     external cal_CompDates
104    
105     integer cal_NumInts
106     external cal_NumInts
107    
108     c == end of interface ==
109    
110     c-- First, get some dates.
111     call cal_GetDate( myiter, mytime, mydate, mythid )
112     call cal_GetDate( myiter+1, mytime+modelstep, nextdate, mythid )
113    
114     call cal_TimeInterval( -modelstep, 'secs', timediff, mythid )
115     call cal_AddTime( mydate, timediff, prevdate, mythid )
116    
117     ce print*,' time average flags: mydate = ', mydate
118     ce print*,' time average flags: nextdate = ', nextdate
119     ce print*,' time average flags: prevdate = ', prevdate
120    
121     c-- Where are we with respect to the calendar?
122    
123     c-- The very first model step?
124     equal = cal_CompDates(modelstartdate,mydate,mythid)
125     if ( equal ) then
126     first = .true.
127     dayrec = 0
128     monrec = 0
129 heimbach 1.3 yearrec = 0
130 heimbach 1.1 else
131     first = .false.
132     endif
133    
134     c-- The very last model step?
135     equal = cal_CompDates(modelenddate,mydate,mythid)
136     if ( equal ) then
137     last = .true.
138     else
139     last = .false.
140     endif
141    
142     c-- Start of a calendar day?
143     mydateday = mod(mydate(1),100)
144     prevdateday = mod(prevdate(1),100)
145     if ( mydateday .ne. prevdateday ) then
146     startofday = .true.
147     else
148     startofday = .false.
149     endif
150    
151     c-- End of a calendar day?
152     mydateday = mod(mydate(1),100)
153     nextdateday = mod(nextdate(1),100)
154     if ( mydateday .ne. nextdateday ) then
155     endofday = .true.
156     else
157     endofday = .false.
158     endif
159    
160     c-- In a calendar day? As coded here, inday can not be true
161     c-- for either the first or the last timestep in the day.
162     c-- So the cases are mutually exclusive.
163     if ( ( mydateday .eq. prevdateday ) .and.
164     & ( mydateday .eq. nextdateday ) ) then
165     inday = .true.
166     else
167     inday = .false.
168     endif
169    
170     c-- Determine sum1day and dayrec explicitly.
171     if ( last .or. endofday ) then
172     if ( mydate(1) .eq. modelstartdate(1) ) then
173     call cal_CopyDate( modelstartdate, targetdate, mythid )
174     dayrec = 1
175     else
176     targetdate(1) = mydate(1)
177     targetdate(2) = 0
178     targetdate(3) = mydate(3)
179     targetdate(4) = mydate(4)
180     call cal_TimePassed( modelstartdate, targetdate, datediff,
181     & mythid )
182     if ( datediff(2) .eq. 0) then
183     dayrec = datediff(1) + 1
184     else
185     dayrec = datediff(1) + 2
186     endif
187     endif
188     call cal_TimeInterval( modelstep, 'secs', timediff, mythid )
189    
190     sum1day =
191     & cal_NumInts( targetdate, mydate, timediff, mythid ) + 1
192     else
193     sum1day = 0
194     endif
195    
196     c-- Start of a calendar month?
197     mydatemonth = mod(mydate(1)/100,100)
198     prevdatemonth = mod(prevdate(1)/100,100)
199     if ( mydatemonth .ne. prevdatemonth ) then
200     startofmonth = .true.
201     else
202     startofmonth = .false.
203     endif
204    
205     c-- End of a calendar month?
206     mydatemonth = mod(mydate(1)/100,100)
207     nextdatemonth = mod(nextdate(1)/100,100)
208     if ( mydatemonth .ne. nextdatemonth ) then
209     endofmonth = .true.
210     else
211     endofmonth = .false.
212     endif
213    
214     c-- In a calendar month? As coded here, inmonth can not be true
215     c-- for either the first or the last timestep in the month.
216     c-- So the cases are mutually exclusive.
217     if ( ( mydatemonth .eq. prevdatemonth ) .and.
218     & ( mydatemonth .eq. nextdatemonth ) ) then
219     inmonth = .true.
220     else
221     inmonth = .false.
222     endif
223    
224     c-- Determine sum1mon and monrec explicitly.
225     if ( last .or. endofmonth ) then
226     if ( (mydate(1)/100)*100 .eq. (modelstartdate(1)/100)*100 ) then
227     call cal_CopyDate( modelstartdate, targetdate, mythid )
228     monrec = 1
229     else
230     targetdate1 = (mydate(1)/100)*100+1
231     targetdate2 = 0
232     call cal_FullDate( targetdate1, targetdate2, targetdate,
233     & mythid )
234     if ( mydate(1)/10000 .eq. modelstartdate(1)/10000 ) then
235     monrec = mod( mydate(1)/100, 100 )
236     & - mod( modelstartdate(1)/100, 100 ) + 1
237     else
238     monrec = mod( mydate(1)/100, 100 )
239     & + nmonthyear - mod(modelstartdate(1)/100,100) + 1
240     & + ( mydate(1)/10000 - modelstartdate(1)/10000 - 1)*
241     & nmonthyear
242     endif
243     endif
244     call cal_TimeInterval( modelstep, 'secs', timediff, mythid )
245    
246     sum1mon =
247     & cal_NumInts( targetdate, mydate, timediff, mythid ) + 1
248     else
249     sum1mon = 0
250     endif
251    
252 heimbach 1.3 c-- Start of a Year?
253     mydateyear = int(mydate(1)/10000)
254     prevdateyear = int(prevdate(1)/10000)
255     if ( mydateyear .ne. prevdateyear ) then
256     startofyear = .true.
257     else
258     startofyear = .false.
259     endif
260    
261     c-- End of a Year?
262     mydateyear = int(mydate(1)/10000)
263     nextdateyear = int(nextdate(1)/10000)
264     if ( mydateyear .ne. nextdateyear ) then
265     endofyear = .true.
266     else
267     endofyear = .false.
268     endif
269    
270     c-- In a calendar year? As coded here, inyear can not be true
271     c-- for either the first or the last timestep in the year.
272     c-- So the cases are mutually exclusive.
273     if ( ( mydateyear .eq. prevdateyear ) .and.
274     & ( mydateyear .eq. nextdateyear ) ) then
275     inyear = .true.
276     else
277     inyear = .false.
278     endif
279    
280     c-- Determine sum1year and yearrec explicitly.
281     if ( last .or. endofyear ) then
282     if ( (mydate(1)/10000)*100 .eq.
283     & (modelstartdate(1)/10000)*100 ) then
284     call cal_CopyDate( modelstartdate, targetdate, mythid )
285     yearrec = 1
286     else
287     targetdate1 = (mydate(1)/10000)*100+1
288     targetdate2 = 0
289     call cal_FullDate( targetdate1, targetdate2, targetdate,
290     & mythid )
291     yearrec = mydate(1)/10000 - modelstartdate(1)/10000 + 1
292     endif
293     c
294     call cal_TimeInterval( modelstep, 'secs', timediff, mythid )
295    
296     sum1year =
297     & cal_NumInts( targetdate, mydate, timediff, mythid ) + 1
298     else
299     sum1year = 0
300     endif
301    
302 heimbach 1.1 end

  ViewVC Help
Powered by ViewVC 1.1.22