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

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

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


Revision 1.3 - (show annotations) (download)
Sat Apr 7 16:21:05 2012 UTC (12 years, 2 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, checkpoint64, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint65o, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, HEAD
Changes since 1.2: +82 -78 lines
stop if called before pkg/cal parameters were set.

1 C $Header: /u/gcmpack/MITgcm/pkg/cal/cal_timepassed.F,v 1.2 2003/10/09 04:19:19 edhill Exp $
2 C $Name: $
3
4 #include "CAL_OPTIONS.h"
5
6 SUBROUTINE CAL_TIMEPASSED(
7 I initialdate,
8 I finaldate,
9 O numdays,
10 I myThid )
11
12 C ==================================================================
13 C SUBROUTINE cal_TimePassed
14 C ==================================================================
15 C
16 C o Calculate the time that passed between initialdate and
17 C finaldate.
18 C
19 C started: Christian Eckert eckert@mit.edu 30-Jun-1999
20 C changed: Christian Eckert eckert@mit.edu 29-Dec-1999
21 C - restructured the original version in order to have a
22 C better interface to the MITgcmUV.
23 C Christian Eckert eckert@mit.edu 03-Feb-2000
24 C - Introduced new routine and function names, cal_<NAME>,
25 C for verion 0.1.3.
26 C
27 C ==================================================================
28 C SUBROUTINE cal_TimePassed
29 C ==================================================================
30
31 IMPLICIT NONE
32
33 C == global variables ==
34 #include "EEPARAMS.h"
35 #include "cal.h"
36
37 C == routine arguments ==
38 INTEGER initialdate(4)
39 INTEGER finaldate(4)
40 INTEGER numdays(4)
41 INTEGER myThid
42
43 C == external ==
44 INTEGER cal_IsLeap
45 EXTERNAL cal_IsLeap
46
47 C == local variables ==
48 INTEGER yi,yf
49 INTEGER mi,mf
50 INTEGER di,df
51 INTEGER si,sf
52 INTEGER li,lf
53 INTEGER wi,wf
54 INTEGER cdi,cdf
55 INTEGER csi,csf
56 INTEGER ndays
57 INTEGER nsecs
58 INTEGER hhmmss
59 INTEGER imon
60 INTEGER iyr
61 INTEGER ierr
62 LOGICAL swap
63 LOGICAL caldates
64 LOGICAL nothingtodo
65 CHARACTER*(MAX_LEN_MBUF) msgBuf
66
67 C == end of interface ==
68
69 IF ( cal_setStatus .LT. 1 ) THEN
70 WRITE( msgBuf,'(2A,4I9)') 'CAL_TIMEPASSED: ', 'initialdate=',
71 & initialdate(1),initialdate(2),initialdate(3),initialdate(4)
72 CALL PRINT_ERROR( msgBuf, myThid )
73 WRITE( msgBuf,'(2A,4I9)') 'CAL_TIMEPASSED: ', 'finaldate=',
74 & finaldate(1),finaldate(2),finaldate(3),finaldate(4)
75 CALL PRINT_ERROR( msgBuf, myThid )
76 WRITE( msgBuf,'(2A,I2,A)') 'CAL_TIMEPASSED: ',
77 & 'called too early (cal_setStatus=',cal_setStatus,' )'
78 CALL PRINT_ERROR( msgBuf, myThid )
79 STOP 'ABNORMAL END: S/R CAL_TIMEPASSED'
80 ENDIF
81
82 nothingtodo = .false.
83
84 C Initialise output.
85 numdays(1) = 0
86 numdays(2) = 0
87 numdays(3) = 0
88 numdays(4) = -1
89
90 if ((initialdate(4) .gt. 0) .eqv.
91 & ( finaldate(4) .gt. 0)) then
92
93 caldates = (initialdate(4) .gt. 0) .and.
94 & ( finaldate(4) .gt. 0)
95
96 C Check relation between initial and final dates.
97 if (initialdate(1) .eq. finaldate(1)) then
98 if (initialdate(2) .eq. finaldate(2)) then
99 nothingtodo = .true.
100 else if (initialdate(2) .gt. finaldate(2)) then
101 swap = .true.
102 else
103 swap = .false.
104 endif
105 else if (initialdate(1) .gt. finaldate(1)) then
106 swap = .true.
107 else
108 swap = .false.
109 endif
110
111 if (.not. nothingtodo) then
112
113 if (swap) then
114 call cal_ConvDate( finaldate,yi,mi,di,si,li,wi,myThid )
115 call cal_ConvDate( initialdate,yf,mf,df,sf,lf,wf,myThid )
116 else
117 call cal_ConvDate( initialdate,yi,mi,di,si,li,wi,myThid )
118 call cal_ConvDate( finaldate,yf,mf,df,sf,lf,wf,myThid )
119 endif
120
121 C Determine the time interval.
122 if (.not. caldates) then
123 ndays = df - di
124 nsecs = sf - si
125 if (nsecs .lt. 0) then
126 nsecs = nsecs + secondsperday
127 ndays = ndays - 1
128 endif
129 ndays = ndays + nsecs/secondsperday
130 nsecs = mod(nsecs,secondsperday)
131 else
132 si = si + (di-1)*secondsperday
133 sf = sf + (df-1)*secondsperday
134 cdi = 0
135 do imon = 1,mod(mi-1,12)
136 cdi = cdi + ndaymonth(imon,li)
137 enddo
138 csi = si
139 cdf = 0
140 do imon = 1,mod(mf-1,12)
141 cdf = cdf + ndaymonth(imon,lf)
142 enddo
143 csf = sf
144
145 if (yi .eq. yf) then
146 ndays = (cdf + csf/secondsperday) -
147 & (cdi + csi/secondsperday)
148 nsecs = (csf - (csf/secondsperday)*secondsperday) -
149 & (csi - (csi/secondsperday)*secondsperday)
150 if (nsecs .lt. 0) then
151 nsecs = nsecs + secondsperday
152 ndays = ndays - 1
153 endif
154 else
155 ndays = (ndaysnoleap - 1) + cal_IsLeap( yi, myThid ) -
156 & cdi - ndaymonth(mi,li)
157 do iyr = yi+1,yf-1
158 ndays = ndays + (ndaysnoleap - 1) +
159 & cal_IsLeap( iyr, myThid )
160 enddo
161 ndays = ndays + cdf
162 csi = ndaymonth(mi,li)*secondsperday - csi
163 nsecs = csi + csf
164 endif
165 endif
166
167 C Convert to calendar format.
168 numdays(1) = ndays + nsecs/secondsperday
169 nsecs = mod(nsecs,secondsperday)
170 hhmmss = nsecs/secondsperminute
171 numdays(2) = hhmmss/minutesperhour*10000 +
172 & mod(hhmmss,minutesperhour)*100 +
173 & mod(nsecs,secondsperminute)
174 if (swap) then
175 numdays(1) = -numdays(1)
176 numdays(2) = -numdays(2)
177 endif
178
179 else
180 C Dates are equal.
181 endif
182
183 else
184
185 ierr = 501
186 call cal_PrintError( ierr, myThid )
187 stop ' stopped in cal_TimePassed'
188
189 endif
190
191 RETURN
192 END

  ViewVC Help
Powered by ViewVC 1.1.22