1"======================================================================
2|
3|   DateTime and Duration Method Definitions
4|
5|
6 ======================================================================"
7
8"======================================================================
9|
10| Copyright 2000, 2001, 2002, 2008, 2009 Free Software Foundation, Inc.
11| Written by Paolo Bonzini.
12|
13| This file is part of the GNU Smalltalk class library.
14|
15| The GNU Smalltalk class library is free software; you can redistribute it
16| and/or modify it under the terms of the GNU Lesser General Public License
17| as published by the Free Software Foundation; either version 2.1, or (at
18| your option) any later version.
19|
20| The GNU Smalltalk class library is distributed in the hope that it will be
21| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
22| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
23| General Public License for more details.
24|
25| You should have received a copy of the GNU Lesser General Public License
26| along with the GNU Smalltalk class library; see the file COPYING.LIB.
27| If not, write to the Free Software Foundation, 59 Temple Place - Suite
28| 330, Boston, MA 02110-1301, USA.
29|
30 ======================================================================"
31
32
33
34Date subclass: DateTime [
35    | seconds offset |
36
37    <category: 'Language-Data types'>
38    <comment: 'My instances represent timestamps.'>
39
40    ClockPrecision := nil.
41
42    DateTime class >> initialize [
43	"Initialize the receiver's class variables"
44
45	<category: 'information'>
46	ClockPrecision := Duration seconds: 1
47    ]
48
49    DateTime class >> clockPrecision [
50	<category: 'information'>
51	^ClockPrecision
52    ]
53
54    DateTime class >> fromSeconds: secs offset: ofs [
55	"Answer a DateTime denoting the given date and time (as seconds
56	 since January 1, 1901 midnight). Set the offset field to ofs (a
57	 Duration)."
58
59	<category: 'instance creation (non-ANSI)'>
60	^self fromDays: 0 seconds: secs offset: ofs
61    ]
62
63    DateTime class >> fromSeconds: secs [
64	"Answer a DateTime denoting the given date and time (as seconds
65	 since January 1, 1901 midnight UTC)."
66
67	<category: 'instance creation (non-ANSI)'>
68	^self fromDays: 0 seconds: secs offset: Duration zero
69    ]
70
71    DateTime class >> fromDays: days seconds: secs [
72	"Answer a DateTime denoting the given date (as days since
73	 January 1, 1901) and time (as seconds since UTC midnight)."
74
75	<category: 'instance creation (non-ANSI)'>
76	^self fromDays: days seconds: secs offset: Duration zero
77    ]
78
79    DateTime class >> fromDays: days seconds: secs offset: ofs [
80	"Answer a DateTime denoting the given date (as days since
81	 January 1, 1901) and time (as seconds since midnight). Set the
82	 offset field to ofs (a Duration)."
83
84	<category: 'instance creation (non-ANSI)'>
85	^(self fromDays: days + (secs // 86400))
86	    setSeconds: secs \\ 86400;
87	    setOffset: ofs
88    ]
89
90    DateTime class >> date: aDate time: aTime offset: ofs [
91	"Answer a DateTime denoting the given date and time. Set the
92	 offset field to ofs (a Duration)."
93
94	<category: 'instance creation (non-ANSI)'>
95	^(self fromDays: aDate days)
96	    setSeconds: aTime asSeconds;
97	    setOffset: ofs
98    ]
99
100    DateTime class >> date: aDate time: aTime [
101	"Answer a DateTime denoting the given date and time. Set the
102	 offset field to ofs (a Duration)."
103
104	<category: 'instance creation (non-ANSI)'>
105	^(self fromDays: aDate days)
106	    setSeconds: aTime asSeconds;
107	    setOffset: Duration zero
108    ]
109
110    DateTime class >> readFrom: aStream [
111	"Parse an instance of the receiver from aStream"
112
113	<category: 'instance creation'>
114        | date time ofs ch |
115        date := super readFrom: aStream.
116        (aStream peekFor: $T) ifFalse: [aStream skipSeparators].
117        time := (aStream atEnd or: [aStream peek isDigit])
118            ifTrue: [Duration readFrom: aStream]
119            ifFalse: [Duration zero].
120        aStream skipSeparators.
121        ch := aStream peek.
122        (ch = $+ or: [ch = $-]) ifFalse: [^date + time].
123        ofs := Duration readFrom: aStream.
124        ^(date + time) setOffset: ofs
125    ]
126
127    DateTime class >> today [
128	"Answer an instance of the receiver referring to midnight of today
129	 in local time."
130
131	<category: 'instance creation'>
132	| t seconds secondsAtMidnight biasNow biasAtMidnight |
133        t := self now.
134        seconds := t asSeconds.
135        secondsAtMidnight := seconds - t seconds.
136        biasAtMidnight := Time timezoneBias: secondsAtMidnight.
137        ^DateTime
138            fromSeconds: secondsAtMidnight
139            offset: (Duration fromSeconds: biasAtMidnight)
140    ]
141
142    DateTime class >> now [
143	"Answer an instance of the receiver referring to the current
144	 date and time."
145
146	<category: 'instance creation'>
147	^self dateAndTimeNow
148    ]
149
150    DateTime class >> year: y month: m day: d hour: h minute: min second: s [
151	"Answer a DateTime denoting the d-th day of the given (as a number)
152	 month and year, setting the time part to the given hour, minute,
153	 and second"
154
155	<category: 'instance creation'>
156	^(super
157	    year: y
158	    month: m
159	    day: d
160	    hour: h
161	    minute: min
162	    second: s) setSeconds: (h * 60 + min) * 60 + s
163    ]
164
165    DateTime class >> year: y day: d hour: h minute: min second: s [
166	"Answer a DateTime denoting the d-th day of the given year, and
167	 setting the time part to the given hour, minute, and second"
168
169	<category: 'instance creation'>
170	^(super
171	    year: y
172	    day: d
173	    hour: h
174	    minute: min
175	    second: s) setSeconds: (h * 60 + min) * 60 + s
176    ]
177
178    DateTime class >> year: y month: m day: d hour: h minute: min second: s offset: ofs [
179	"Answer a DateTime denoting the d-th day of the given (as a number)
180	 month and year. Set the offset field to ofs (a Duration), and
181	 the the time part to the given hour, minute, and second"
182
183	<category: 'instance creation'>
184	^(super
185	    year: y
186	    month: m
187	    day: d
188	    hour: h
189	    minute: min
190	    second: s)
191	    setSeconds: (h * 60 + min) * 60 + s;
192	    setOffset: ofs
193    ]
194
195    DateTime class >> year: y day: d hour: h minute: min second: s offset: ofs [
196	"Answer a DateTime denoting the d-th day of the given year.
197	 Set the offset field to ofs (a Duration), and the time part
198	 to the given hour, minute, and second"
199
200	<category: 'instance creation'>
201	^(super
202	    year: y
203	    day: d
204	    hour: h
205	    minute: min
206	    second: s)
207	    setSeconds: (h * 60 + min) * 60 + s;
208	    setOffset: ofs
209    ]
210
211    < aDateTime [
212	"Answer whether the receiver indicates a date preceding aDate"
213
214	<category: 'testing'>
215	self offset = aDateTime offset ifFalse: [^self asUTC < aDateTime asUTC].
216	^super < aDateTime
217	    or: [super = aDateTime and: [seconds < aDateTime seconds]]
218    ]
219
220    = aDateTime [
221	"Answer whether the receiver indicates the same date as aDate"
222
223	<category: 'testing'>
224	self class == aDateTime class ifFalse: [^false].
225	self offset = aDateTime offset ifFalse: [^self asUTC = aDateTime asUTC].
226	^super = aDateTime and: [seconds = aDateTime seconds]
227    ]
228
229    hash [
230	"Answer an hash value for the receievr"
231
232	<category: 'testing'>
233	^super hash * 37 + (self seconds - self offset seconds)
234    ]
235
236    + aDuration [
237	"Answer a new Date pointing aDuration time past the receiver"
238
239	<category: 'basic'>
240	| newSecs |
241	newSecs := self seconds + (aDuration asSeconds rem: 86400).
242	^newSecs > 86400
243	    ifTrue:
244		[DateTime
245		    fromDays: self days + aDuration days + 1
246		    seconds: newSecs - 86400
247		    offset: self offset]
248	    ifFalse:
249		[DateTime
250		    fromDays: self days + aDuration days
251		    seconds: newSecs
252		    offset: self offset]
253    ]
254
255    - aDateTimeOrDuration [
256	"Answer a new Date pointing dayCount before the receiver"
257
258	<category: 'basic'>
259	| newSecs resultClass |
260	aDateTimeOrDuration class == self class
261	    ifTrue:
262		[self offset = aDateTimeOrDuration offset
263		    ifFalse: [^self asUTC - aDateTimeOrDuration asUTC].
264		resultClass := Duration.
265		newSecs := self seconds - aDateTimeOrDuration seconds]
266	    ifFalse:
267		[resultClass := DateTime.
268		newSecs := self seconds - (aDateTimeOrDuration asSeconds rem: 86400)].
269	^newSecs < 0
270	    ifTrue:
271		[resultClass
272		    fromDays: self days - aDateTimeOrDuration days - 1
273		    seconds: newSecs + 86400
274		    offset: self offset]
275	    ifFalse:
276		[resultClass
277		    fromDays: self days - aDateTimeOrDuration days
278		    seconds: newSecs
279		    offset: self offset]
280    ]
281
282    asSeconds [
283	"Answer the date as the number of seconds from 1/1/1901."
284
285	<category: 'computations'>
286	^super asSeconds + seconds
287    ]
288
289    dayOfWeek [
290	"Answer the day of week of the receiver. Unlike Dates, DateAndTimes
291	 have 1 = Sunday, 7 = Saturday"
292
293	<category: 'computations'>
294	^#(2 3 4 5 6 7 1) at: super dayOfWeek
295    ]
296
297    hour [
298	"Answer the hour in a 24-hour clock"
299
300	<category: 'computations'>
301	^seconds // 3600
302    ]
303
304    hour12 [
305	"Answer the hour in a 12-hour clock"
306
307	<category: 'computations'>
308	| h |
309	h := self hour \\ 12.
310	^h = 0 ifTrue: [12] ifFalse: [h]
311    ]
312
313    hour24 [
314	"Answer the hour in a 24-hour clock"
315
316	<category: 'computations'>
317	^self hour
318    ]
319
320    meridianAbbreviation [
321	"Answer either #AM (for anti-meridian) or #PM (for post-meridian)"
322
323	<category: 'computations'>
324	^self hour < 12 ifTrue: [#AM] ifFalse: [#PM]
325    ]
326
327    minute [
328	"Answer the minute"
329
330	<category: 'computations'>
331	^seconds // 60 \\ 60
332    ]
333
334    second [
335	"Answer the month represented by the receiver"
336
337	<category: 'computations'>
338	^seconds \\ 60
339    ]
340
341    at: anIndex [
342	"Since in the past timestamps were referred to as Arrays containing
343	 a Date and a Time (in this order), this method provides access to
344	 DateTime objects like if they were two-element Arrays."
345
346	<category: 'splitting in dates & times'>
347	anIndex = 1 ifTrue: [^self asDate].
348	anIndex = 2 ifTrue: [^self asTime].
349	SystemExceptions.IndexOutOfRange signalOn: self withIndex: anIndex
350    ]
351
352    asDate [
353	"Answer a Date referring to the same day as the receiver"
354
355	<category: 'splitting in dates & times'>
356	^Date fromDays: self days
357    ]
358
359    asTime [
360	"Answer a Time referring to the same time (from midnight) as the receiver"
361
362	<category: 'splitting in dates & times'>
363	^Time fromSeconds: seconds
364    ]
365
366    asLocal [
367	"Answer the receiver, since DateTime objects store themselves
368	 in Local time"
369
370	<category: 'time zones'>
371        | utcSecs offset |
372	utcSecs := self asSeconds - self offset asSeconds.
373        offset := Time timezoneBias: utcSecs.
374	^DateTime
375            fromSeconds: utcSecs + offset
376            offset: (Duration fromSeconds: offset)
377    ]
378
379    asUTC [
380	"Convert the receiver to UTC time, and answer a new DateTime object."
381
382	<category: 'time zones'>
383	| newSecs |
384	self offset asSeconds = 0 ifTrue: [ ^self ].
385	newSecs := self seconds - self offset asSeconds.
386	^newSecs < 0
387	    ifTrue:
388		[DateTime
389		    fromDays: self days + offset days - 1
390		    seconds: newSecs + 86400
391		    offset: Duration zero]
392	    ifFalse:
393		[DateTime
394		    fromDays: self days + offset days
395		    seconds: newSecs
396		    offset: Duration zero]
397    ]
398
399    offset [
400	"Answer the receiver's offset from UTC to local time (e.g. +3600 seconds
401	 for Central Europe Time, -3600*6 seconds for Eastern Standard Time).
402	 The offset is expressed as a Duration"
403
404	<category: 'time zones'>
405	^offset
406    ]
407
408    offset: anOffset [
409	"Answer a copy of the receiver with the offset from UTC to local time
410	 changed to anOffset (a Duration)."
411
412	<category: 'time zones'>
413	anOffset = offset ifTrue: [^self].
414	^(self copy)
415	    setOffset: anOffset;
416	    yourself
417    ]
418
419    timeZoneAbbreviation [
420	"Answer an abbreviated indication of the receiver's offset, expressed
421	 as `shhmm', where `hh' is the number of hours and `mm' is the number
422	 of minutes between UTC and local time, and `s' can be `+' for the
423	 Eastern hemisphere and `-' for the Western hemisphere."
424
425	<category: 'time zones'>
426	^String
427	    with: (self offset positive ifTrue: [$+] ifFalse: [$-])
428	    with: (self offset hour // 10) digitValue
429	    with: (self offset hour \\ 10) digitValue
430	    with: (self offset minute // 10) digitValue
431	    with: (self offset minute \\ 10) digitValue
432    ]
433
434    timeZoneName [
435	"Answer the time zone name for the receiver (currently, it is
436	 simply `GMT +xxxx', where `xxxx' is the receiver's
437	 #timeZoneAbbreviation)."
438
439	<category: 'time zones'>
440	^'GMT ' , self timeZoneAbbreviation
441    ]
442
443    printOn: aStream [
444	"Print a representation for the receiver on aStream"
445
446	<category: 'printing'>
447	aStream
448	    nextPut: (self year < 0 ifTrue: [$-] ifFalse: [Character space]);
449	    next: 3 - (self year abs log: 10) floor put: $0;
450	    print: self year abs;
451	    nextPut: $-;
452	    next: (self month < 10 ifTrue: [1] ifFalse: [0]) put: $0;
453	    print: self month;
454	    nextPut: $-;
455	    next: (self day < 10 ifTrue: [1] ifFalse: [0]) put: $0;
456	    print: self day;
457	    nextPut: $T;
458	    next: (self hour < 10 ifTrue: [1] ifFalse: [0]) put: $0;
459	    print: self hour;
460	    nextPut: $:;
461	    next: (self minute < 10 ifTrue: [1] ifFalse: [0]) put: $0;
462	    print: self minute;
463	    nextPut: $:;
464	    next: (self second < 10 ifTrue: [1] ifFalse: [0]) put: $0;
465	    print: self second;
466	    nextPut: (self offset negative ifTrue: [$-] ifFalse: [$+]);
467	    next: (self offset hours abs < 10 ifTrue: [1] ifFalse: [0]) put: $0;
468	    print: self offset hours abs;
469	    nextPut: $:;
470	    next: (self offset minutes abs < 10 ifTrue: [1] ifFalse: [0]) put: $0;
471	    print: self offset minutes abs.
472	self offset seconds = 0 ifTrue: [^self].
473	aStream
474	    nextPut: $:;
475	    print: self offset seconds
476    ]
477
478    storeOn: aStream [
479	"Store on aStream Smalltalk code compiling to the receiver"
480
481	<category: 'storing'>
482	aStream
483	    nextPut: $(;
484	    nextPutAll: self class storeString;
485	    nextPutAll: ' year: ';
486	    store: self year;
487	    nextPutAll: ' month: ';
488	    store: self month;
489	    nextPutAll: ' day: ';
490	    store: self day;
491	    nextPutAll: ' hour: ';
492	    store: self hour;
493	    nextPutAll: ' minute: ';
494	    store: self minute;
495	    nextPutAll: ' second: ';
496	    store: self second.
497
498	self offset = Duration zero ifFalse: [
499	    aStream
500		nextPutAll: ' offset: ';
501		store: self offset ].
502
503	aStream
504	    nextPut: $)
505    ]
506
507    setDay: dayOfMonth monthIndex: monthIndex year: yearInteger [
508	"Private - Set the receiver to the given date parts"
509
510	<category: 'private'>
511	seconds := 0.
512	offset := Duration zero.
513	^super
514	    setDay: dayOfMonth
515	    monthIndex: monthIndex
516	    year: yearInteger
517    ]
518
519    setDays: dayCount [
520	"Private - Compute the date parts from the given dayCount and initialize
521	 the receiver"
522
523	<category: 'private'>
524	seconds := 0.
525	offset := Duration zero.
526	^super setDays: dayCount
527    ]
528
529    seconds [
530	<category: 'private'>
531	^seconds
532    ]
533
534    setSeconds: secondsCount [
535	<category: 'private'>
536	seconds := secondsCount
537    ]
538
539    setOffset: offsetDuration [
540	<category: 'private'>
541	offset := offsetDuration
542    ]
543]
544
545
546
547Time subclass: Duration [
548
549    <category: 'Language-Data types'>
550    <comment: 'My instances represent differences between timestamps.'>
551
552    Zero := nil.
553
554    Duration class >> fromDays: days seconds: secs offset: unused [
555	"Answer a duration of `d' days and `secs' seconds.  The last
556	 parameter is unused; this message is available for interoperability
557	 with the DateTime class."
558
559	<category: 'instance creation (non ANSI)'>
560	^self fromSeconds: days * 86400 + secs
561    ]
562
563    Duration class >> milliseconds: msec [
564	"Answer a duration of `msec' milliseconds"
565
566	<category: 'instance creation'>
567	^self fromSeconds: msec / 1000
568    ]
569
570    Duration class >> weeks: w [
571	"Answer a duration of `w' weeks"
572
573	<category: 'instance creation'>
574	^self fromSeconds: w * ##(86400 * 7)
575    ]
576
577    Duration class >> days: d [
578	"Answer a duration of `d' days"
579
580	<category: 'instance creation'>
581	^self fromSeconds: d * 86400
582    ]
583
584    Duration class >> days: d hours: h minutes: m seconds: s [
585	"Answer a duration of `d' days and the given number of hours,
586	 minutes, and seconds."
587
588	<category: 'instance creation'>
589	^self fromSeconds: ((d * 24 + h) * 60 + m) * 60 + s
590    ]
591
592    Duration class >> readFrom: aStream [
593        "Parse an instance of the receiver (hours/minutes/seconds) from
594         aStream"
595
596        <category: 'instance creation'>
597        | sign sec hms i ch ws |
598        hms := {0. 0. 0}.
599        sign := (aStream peekFor: $-)
600            ifTrue: [-1]
601            ifFalse: [aStream peekFor: $+. 1].
602        i := 1.
603        ch := $:.
604        [aStream atEnd not and: [ch isSeparator not and: [
605             ch ~= $+ and: [ch ~= $- and: [
606                 i > 1 ifTrue: [aStream next].
607                 i <= 4 and: [(ch := aStream peek) isDigit]]]]]] whileTrue: [
608            ws := WriteStream on: (String new: 10).
609            [ws nextPut: aStream next.
610             aStream atEnd not and: [(ch := aStream peek) isDigit]] whileTrue.
611            i = 4
612                ifTrue: [
613                    hms := {
614                        (hms at: 1) * 24 + (hms at: 2).
615                        hms at: 3.
616                        ws contents asNumber}]
617                ifFalse: [
618                    hms at: i put: ws contents asNumber].
619	    i := i + 1].
620        sec := ((hms at: 1) * 3600 + ((hms at: 2) * 60) + (hms at: 3)) * sign.
621        ^self fromSeconds: sec
622    ]
623
624    Duration class >> initialize [
625	"Initialize the receiver's instance variables"
626
627	<category: 'instance creation'>
628	Zero := self new
629    ]
630
631    Duration class >> zero [
632	"Answer a duration of zero seconds."
633
634	<category: 'instance creation'>
635	^Zero
636    ]
637
638    * factor [
639	"Answer a Duration that is `factor' times longer than the receiver"
640
641	<category: 'arithmetics'>
642	^Duration fromSeconds: self asSeconds * factor
643    ]
644
645    / factorOrDuration [
646	"If the parameter is a Duration, answer the ratio between the receiver
647	 and factorOrDuration.  Else divide the receiver by factorOrDuration (a
648	 Number) and answer a new Duration that is correspondingly shorter."
649
650	<category: 'arithmetics'>
651	^factorOrDuration isNumber
652	    ifFalse: [self asSeconds / factorOrDuration asSeconds]
653	    ifTrue: [Duration fromSeconds: self asSeconds / factorOrDuration]
654    ]
655
656    + aDuration [
657	"Answer a Duration that is the sum of the receiver and aDuration's
658	 lengths."
659
660	<category: 'arithmetics'>
661	^Duration fromSeconds: self asSeconds + aDuration asSeconds
662    ]
663
664    - aDuration [
665	"Answer a Duration that is the difference of the receiver and aDuration's
666	 lengths."
667
668	<category: 'arithmetics'>
669	^Duration fromSeconds: self asSeconds - aDuration asSeconds
670    ]
671
672    isZero [
673	"Answer whether the receiver correspond to a duration of zero seconds."
674
675	<category: 'arithmetics'>
676	^self asSeconds = 0
677    ]
678
679    abs [
680	"Answer a Duration that is as long as the receiver, but always in
681	 the future."
682
683	<category: 'arithmetics'>
684	^Duration fromSeconds: self asSeconds abs
685    ]
686
687    days [
688	"Answer the number of days in the receiver"
689
690	<category: 'arithmetics'>
691	^self asSeconds quo: 86400
692    ]
693
694    negated [
695	"Answer a Duration that is as long as the receiver, but with past and
696	 future exchanged."
697
698	<category: 'arithmetics'>
699	^Duration fromSeconds: self asSeconds negated
700    ]
701
702    storeOn: aStream [
703	"Store on aStream Smalltalk code compiling to the receiver"
704
705	<category: 'storing'>
706	aStream
707	    nextPut: $(;
708	    nextPutAll: self class storeString;
709	    nextPutAll: ' days: ';
710	    store: self days;
711	    nextPutAll: ' hours: ';
712	    store: self hours;
713	    nextPutAll: ' minutes: ';
714	    store: self minutes;
715	    nextPutAll: ' seconds: ';
716	    store: self seconds;
717	    nextPut: $)
718    ]
719
720    negative [
721	"Answer whether the receiver is in the past."
722
723	<category: 'arithmetics'>
724	^self asSeconds < 0
725    ]
726
727    positive [
728	"Answer whether the receiver is a zero-second duration or is
729	 in the future."
730
731	<category: 'arithmetics'>
732	^self asSeconds >= 0
733    ]
734
735    printOn: aStream [
736	"Print a represention of the receiver on aStream."
737
738	<category: 'arithmetics'>
739	self negative
740	    ifTrue:
741		[aStream
742		    nextPut: $-;
743		    print: self negated.
744		^self].
745	aStream
746	    print: self days;
747	    nextPut: $:;
748	    next: (self hours < 10 ifTrue: [1] ifFalse: [0]) put: $0;
749	    print: self hours;
750	    nextPut: $:;
751	    next: (self minutes < 10 ifTrue: [1] ifFalse: [0]) put: $0;
752	    print: self minutes;
753	    nextPut: $:;
754	    next: (self seconds < 10 ifTrue: [1] ifFalse: [0]) put: $0;
755	    print: self seconds
756    ]
757
758    setSeconds: secs [
759	<category: 'private'>
760	seconds := secs
761    ]
762
763    wait [
764	"Answer a Delay waiting for the amount of time represented
765	 by the receiver and start waiting on it."
766	<category: 'processes'>
767	^(Delay forMilliseconds: self asSeconds * 1000) wait
768    ]
769]
770
771
772
773Eval [
774    Duration initialize
775]
776
777