[ENH] timezones and celeste

Lex Spoon lex at cc.gatech.edu
Tue Dec 7 04:44:49 UTC 1999


Okay, here is an up-to-date changeset for local vs. UTC time, and a patch
to Celeste to make use of it.  This works great with David Lewis's time
plugin, with two caveats:

	1. You need to compile the plugin into time.so
	2. I changed it to report the timezone diff as (local - utc) instead of
(utc - local).  Unix and RFC 822 seem to disagree here


Hopefully this message will have a proper date stamp :)  Anyway, 
if it looks okay to everyone, this should be safe to file in; there is
a default to assume you live in England if your VM doesn't support
the needed primitive.


Lex


=========== Time.cs ===========================================
'From Squeak2.7alpha of 25 October 1999 [latest update: #1671] on 6
December 1999 at 11:43:14 pm'!
"Change Set:		Time
Date:			1 December 1999
Author:			Lex Spoon

adds a primitive to distinguish local time from global time"!


!Time commentStamp: 'ls 12/6/1999 22:56' prior: 0!
I represent the time of day.

Two primitives, localSecondsClock and utcSecondsClock, return a time encoded as:

	days*86400 + hours*3600 + minutes*60 + seconds

For UTC time, this is close to the number of seconds since the beginning of Jan 1, 1901, as of December 1999, although it is off by <60 leap seconds.!

!Time class methodsFor: 'general inquiries' stamp: 'ls 12/1/1999 22:39'!
dateAndTimeNow
	"Answer a two-element Array of (Date today, Time now) in local time"
	^self localDateAndTimeNow! !

!Time class methodsFor: 'general inquiries' stamp: 'ls 12/6/1999 22:45'!
dateAndTimeNowWithOffset
	"Answer a three-element Array of (Date today, Time now, offset from UTC)"
	| secondsCount offset secondsWithOffset |
	secondsWithOffset _ self localSecondsClockWithOffset.
	secondsCount _ secondsWithOffset first.
	offset _ secondsWithOffset second.

	^(self dateAndTimeFromSeconds: secondsCount) copyWith: offset! !

!Time class methodsFor: 'general inquiries' stamp: 'ls 12/1/1999 22:37'!
localDateAndTimeNow
	"Answer a two-element Array of (Date today, Time now) in local time"

	| secondCount |
	secondCount _ self localSecondsClock.
	^self dateAndTimeFromSeconds: secondCount! !

!Time class methodsFor: 'general inquiries' stamp: 'ls 12/6/1999 22:54'!
localSecondsClock
	"return the local time, encoded into a single integer (see class comment)"
	^self localSecondsClockWithOffset at: 1! !

!Time class methodsFor: 'general inquiries' stamp: 'ls 12/6/1999 23:29'!
localSecondsClockWithOffset
	"return the local time along with its offset from UTC"
	|ans|
	ans _ Array new: 2.
	self primLocalSecondsClockWithOffset: ans.
	^ans! !

!Time class methodsFor: 'general inquiries' stamp: 'ls 12/1/1999 22:39'!
utcDateAndTimeNow
	"Answer a two-element Array of (Date today, Time now) in UTC time"
	| secondCount |
	secondCount _ self utcSecondsClock.
	^self dateAndTimeFromSeconds: secondCount! !

!Time class methodsFor: 'general inquiries' stamp: 'ls 12/6/1999 23:31'!
utcSecondsClock
	"return the date and time in UTC, encoded as an integer (see class comment)"

	| clockWithOffset |
	clockWithOffset _ self localSecondsClockWithOffset.
	^clockWithOffset first - clockWithOffset second! !

!Time class methodsFor: 'private' stamp: 'ls 12/6/1999 23:16'!
primLocalSecondsClockWithOffset: array
	"calculate the local time, and its ofset from UTC"
	<primitive: 'primitiveLocalSecondsClockWithOffset' module: 'time'>

	"if failed, assume UTC time  (modify this if you want it to assume some other time zone by default"
	array at: 1 put: self primSecondsClock.
	array at: 2 put: 0.! !




========================== Celeste-time.cs ========================================
'From Squeak2.7alpha of 25 October 1999 [latest update: #1671] on 6
December 1999 at 11:44:00 pm'!
"Change Set:		Celeste-time
Date:			6 December 1999
Author:			Lex Spoon

Add a timezone offset to the Date: stamp, so that the time part of the
stamp becomes useful"!


!MailMessage class methodsFor: 'utilities' stamp: 'ls 12/6/1999 23:38'!
dateStampNow
	| timeWithOffset seconds offset date time absOffset offsetHours offsetMinutes |
	"Return the current date and time formatted as a email Date: line"
	"The result conforms to RFC822 with a long year, e.g.  'Thu, 18 Feb 1999 20:38:51 -0400'"

	^String streamContents: [ :str |
		"grab the time and date"
		timeWithOffset _ Time localSecondsClockWithOffset.
		seconds _ timeWithOffset first.
		offset _ timeWithOffset second // 60.   "offset in minuteus"
		date _ Date fromSeconds: seconds.
		time _ Time fromSeconds: seconds \\ 86400.

		"print the date"
		str nextPutAll: (date weekday copyFrom: 1 to: 3).
		str nextPutAll:  ', '.
		date printOn: str format: #(1 2 3 $  2 1 1).
		str space.

		"print the time"	
		time print24: true on: str.
		str space.

		"print the offset from UTC"
		offset < 0
			ifTrue: [ str nextPut: $- ]
			ifFalse: [ str nextPut: $+ ].
		absOffset _ offset abs.
		offsetHours _ absOffset // 60.
		offsetMinutes _ absOffset \\ 60.
		offsetHours < 10 ifTrue: [ str nextPut: $0 ].
		offsetHours printOn: str.
		offsetMinutes < 10 ifTrue: [ str nextPut: $0 ].
		offsetMinutes printOn: str
	].! !





More information about the Squeak-dev mailing list