/[MITgcm]/MITgcm/pkg/cal/cal_set.F
ViewVC logotype

Contents of /MITgcm/pkg/cal/cal_set.F

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


Revision 1.10 - (show annotations) (download)
Thu Jun 5 19:38:45 2014 UTC (9 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65o, checkpoint64y, checkpoint64z, HEAD
Changes since 1.9: +58 -53 lines
new calendar type "noLeapYear" for 365 days calendar without any leap year.

1 C $Header: /u/gcmpack/MITgcm/pkg/cal/cal_set.F,v 1.9 2012/04/08 19:17:09 jmc Exp $
2 C $Name: $
3
4 #include "CAL_OPTIONS.h"
5
6 SUBROUTINE CAL_SET(
7 I modstart, modend, modstep,
8 I moditerini, moditerend, modintsteps,
9 I myThid )
10
11 C ==================================================================
12 C SUBROUTINE cal_Set
13 C ==================================================================
14 C
15 C o This routine initialises the calendar according to the user
16 C specifications in "data".
17 C
18 C Purpose: Precalculations for the calendar.
19 C Given the type of calendar that should be used date
20 C arrays and some additional information is returned.
21 C Check for consistency with other specifications such
22 C as modintsteps.
23 C
24 C started: Christian Eckert eckert@mit.edu 30-Jun-1999
25 C changed: Christian Eckert eckert@mit.edu 29-Dec-1999
26 C - restructured the original version in order to have a
27 C better interface to the MITgcmUV.
28 C Christian Eckert eckert@mit.edu 19-Jan-2000
29 C - Changed the role of the routine arguments. Chris Hill
30 C proposed to make the calendar less "invasive". The tool
31 C now assumes that the MITgcmUV already provides an ade-
32 C quate set of time stepping parameters. The calendar
33 C only associates a date with the given starttime of the
34 C numerical model. startdate corresponds to zero start-
35 C time. So, given niter0 or startdate .ne. zero the actual
36 C startdate of the current integration is shifted by the
37 C time interval correponding to niter0, startdate respec-
38 C tively.
39 C Christian Eckert eckert@mit.edu 03-Feb-2000
40 C - Introduced new routine and function names, cal_<NAME>,
41 C for verion 0.1.3.
42 C Christian Eckert eckert@mit.edu 23-Feb-2000
43 C - Corrected the declaration of *modelrundate*
44 C --> integer modelrundate(4)
45 C
46 C ==================================================================
47 C SUBROUTINE cal_Set
48 C ==================================================================
49
50 IMPLICIT NONE
51
52 C == global variables ==
53
54 #include "cal.h"
55
56 C == routine arguments ==
57 C modstart :: start time of the model integration
58 C modend :: end time of the model integration
59 C modstep :: timestep of the numerical model
60 C moditerini :: initial iteration number of the model
61 C moditerend :: last iteration number of the model
62 C modintsteps :: number of timesteps that are to be performed.
63 C myThid :: my Thread Id number
64
65 _RL modstart
66 _RL modend
67 _RL modstep
68 INTEGER moditerini
69 INTEGER moditerend
70 INTEGER modintsteps
71 INTEGER myThid
72
73 C == local variables ==
74 C modelBaseDate :: full date array for startdate_1,startdate_2
75 C (corresponds to model baseTime, iter=0)
76 INTEGER i,j,k
77 INTEGER ierr
78 INTEGER timediff(4)
79 INTEGER iterinitime(4)
80 INTEGER modelBaseDate(4)
81 _RL runtimesecs
82 _RL iterinisecs
83 C == end of interface ==
84
85 _BEGIN_MASTER(myThid)
86
87 C- Initialise some variables.
88 usingNoLeapYearCal = .FALSE.
89 usingGregorianCalendar = .FALSE.
90 usingModelCalendar = .FALSE.
91 usingJulianCalendar = .FALSE.
92
93 C- Set calendar parameters which are independent of the calendar choice:
94 hoursPerDay = 24
95 minutesPerHour = 60
96 minutesPerDay = minutesPerHour*hoursPerDay
97 secondsPerMinute = 60
98 secondsPerHour = secondsPerMinute*minutesPerHour
99 secondsPerDay = secondsPerMinute*minutesPerDay
100
101 C- Select which calendar type to use:
102 IF ( theCalendar .EQ. 'gregorian') THEN
103 usingGregorianCalendar = .TRUE.
104 c ELSE IF ( theCalendar .EQ. 'julian') THEN
105 c usingJulianCalendar = .TRUE.
106 c STOP ' stopped in cal_Set (Julian Calendar).'
107 ELSE IF ( theCalendar .EQ. 'noLeapYear') THEN
108 usingNoLeapYearCal = .TRUE.
109 ELSE IF ( theCalendar .EQ. 'model') THEN
110 usingModelCalendar = .TRUE.
111 c ELSE IF ( theCalendar .EQ. 'none') THEN
112 c usingNoCalendar = .TRUE.
113 c STOP ' stopped in cal_Set (No Calendar).'
114 ELSE
115 ierr = 101
116 CALL cal_PrintError( ierr, myThid )
117 STOP
118 ENDIF
119
120 C- Set calendar parameters according to the calendar type:
121
122 IF ( usingGregorianCalendar .OR. usingNoLeapYearCal ) THEN
123 C The reference date for the Gregorian Calendar.
124 C and its format: ( yymmdd , hhmmss , leap year, weekday )
125 C (1/2) (1 - 7)
126 C The Gregorian calendar starts on Friday, 15 Oct. 1582.
127 refDate(1) = 15821015
128 refDate(2) = 0
129 refDate(3) = 1
130 refDate(4) = 1
131
132 C Number of months per year and other useful numbers.
133 nDaysNoLeap = 365
134 nDaysLeap = 366
135 nMaxDayMonth = 31
136
137 C Number of days per month.
138 C The "magic" number 2773 derives from the sequence: 101010110101
139 C read in reverse and interpreted as a dual number. An
140 C alternative would be to take 2741 with the loop being
141 C executed in reverse order. Accidentially, the latter
142 C is a prime number.
143 k=2773
144 DO i=1,nMonthYear
145 j = MOD(k,2)
146 k = (k-j)/2
147 nDayMonth(i,1) = 30+j
148 nDayMonth(i,2) = 30+j
149 ENDDO
150 nDayMonth(2,1) = 28
151 nDayMonth(2,2) = 29
152
153 C Week days.
154 dayOfWeek(1) = 'FRI'
155 dayOfWeek(2) = 'SAT'
156 dayOfWeek(3) = 'SUN'
157 dayOfWeek(4) = 'MON'
158 dayOfWeek(5) = 'TUE'
159 dayOfWeek(6) = 'WED'
160 dayOfWeek(7) = 'THU'
161 ENDIF
162
163 IF ( usingModelCalendar ) THEN
164 C Assume a model calendar having 12 months with thirty days each.
165 C Reference date is the first day of year 0 at 0am, and model day 1.
166 refDate(1) = 00000101
167 refDate(2) = 0
168 refDate(3) = 1
169 refDate(4) = 1
170
171 C Some useful numbers.
172 nDaysNoLeap = 360
173 nDaysLeap = 360
174 nMaxDayMonth = 30
175 DO i=1,nMonthYear
176 nDayMonth(i,1) = 30
177 nDayMonth(i,2) = 30
178 ENDDO
179
180 C Week days (Model Day 1 - 7).
181 dayOfWeek(1) = 'MD1'
182 dayOfWeek(2) = 'MD2'
183 dayOfWeek(3) = 'MD3'
184 dayOfWeek(4) = 'MD4'
185 dayOfWeek(5) = 'MD5'
186 dayOfWeek(6) = 'MD6'
187 dayOfWeek(7) = 'MD7'
188
189 ENDIF
190
191 C- Record completion of calendar settings: stage 1 = calendar is defined
192 cal_setStatus = 1
193
194 C Map the numerical model parameters. --> common blocks in CALENDAR.h
195 modelStart = modstart
196 modelEnd = modend
197 modelStep = modstep
198 modelIter0 = moditerini
199 modelIterEnd = moditerend
200 modelIntSteps = modintsteps
201
202 C Do first consistency checks
203 C o Time step.
204 IF ( modelStep .LE. 0. ) THEN
205 ierr = 102
206 CALL cal_PrintError( ierr, myThid )
207 STOP ' stopped in cal_Set.'
208 ENDIF
209 IF ( modelStep .LT. 1. ) THEN
210 ierr = 103
211 CALL cal_PrintError( ierr, myThid )
212 STOP ' stopped in cal_Set.'
213 ENDIF
214 IF ( ABS(modelStep - NINT(modelStep)) .GT. 0.000001 ) THEN
215 ierr = 104
216 CALL cal_PrintError( ierr, myThid )
217 STOP ' stopped in cal_Set.'
218 ELSE
219 modelStep = FLOAT(NINT(modelStep))
220 ENDIF
221
222 C- Record completion of calendar settings: stage 2 = numerical model parms
223 cal_setStatus = 2
224
225 C Complete the start date specification to get a full date array.
226 CALL cal_FullDate( startdate_1, startdate_2,
227 & modelBaseDate, myThid )
228
229 C From here on, the final calendar settings are determined by the
230 C following variables:
231 C modelStart, modelStep*modelIntSteps & modelBaseDate
232
233 runtimesecs = modelIntSteps*modelStep
234
235 C Determine the startdate of the integration.
236 c iterinisecs = float(modelIter0)*modelStep
237 C-jmc: above does not work if baseTime <> 0 ; fix it below:
238 iterinisecs = modelStart
239 CALL cal_TimeInterval( iterinisecs, 'secs', iterinitime, myThid )
240 CALL cal_AddTime( modelBaseDate, iterinitime, modelStartDate,
241 & myThid )
242
243 CALL cal_TimeInterval( runtimesecs, 'secs', timediff, myThid )
244 CALL cal_AddTime( modelStartDate, timediff, modelEndDate,
245 & myThid )
246
247 C- Record completion of calendar settings: stage 3 = fully set-up.
248 cal_setStatus = 3
249
250 _END_MASTER(myThid)
251
252 C Everyone else must wait for the parameters to be set
253 _BARRIER
254
255 RETURN
256 END

  ViewVC Help
Powered by ViewVC 1.1.22