[ENH][UPDATE] Time functions

Lex Spoon lex at cc.gatech.edu
Thu Dec 2 11:09:03 UTC 1999


This looks like a great start at a system which incorporates timezone
handling.  However, there seems to be no way to automatically switch
from EST to EDT, which a full system should be able to do.  Also, as you
mention, there is no access to existing timezone databases.  Finally, we
should probably let the VM specify a default timezone, perhaps by name;
many OS's already have this information stored away somewhere, and it
would be a shame to make people set their timezone separately in the OS
and in Squeak.


Lex


"David T. Lewis" <lewis at mail.msen.com> wrote:
> 
> --tKW2IUtsqtDRztdT
> Content-Type: text/plain; charset=us-ascii
> 
> This replaces the change set I posted a couple of days ago.
> 
> Class PointInTime knows how to convert to and from Smalltalk time, and
> TimeZone knows how to obtain the offset between UTC and local time.
> Together, they provide a framework for mapping the local time in
> Smalltalk (Time and Date) to a location-independent PointInTime
> representation.
> 
> Class PointInTime now uses 01-Jan-1970 as the origin on its timeline.
> 
> PointInTimeNow represents the current time on the absolute timeline.
> Its single instance is updated by a process loop, but it is intended
> to be hooked into the VM so as to be updated by the system clock.
> 
> Class WallClock demonstrates the mapping of Date and Time to PointInTimeNow.
> 
> Class TimePlugin contains the pluggable primitives.
> 
> There is not yet any connection to a timezone database, but TimeZone can
> query the operating system to learn about the local timezone.
> 
> Dave
> 
> 
> --tKW2IUtsqtDRztdT
> Content-Type: text/plain; charset=us-ascii
> Content-Disposition: attachment; filename="Time.30Nov1057pm.cs"
> 
> 'From Squeak2.6 of 11 October 1999 [latest update: #1559] on 30 November 1999 at 10:57:39 pm'!
> "Change Set:		Time
> Date:			30 November 1999
> Author:			David T. Lewis
> 
> Pluggable primitives and supporting Smalltalk classes to demonstrate one
> way to handle timezones on a computer which already understands them.
> An important aspect is class PointInTime, which represents a point on an
> absolute (timezone independent) timeline, using units of seconds in a
> Smalltalk Float representation.
> 
> This was built on a unix-like operating system. I don't know whether the
> plugin can be built on other systems, but I'm sure with a bit of hacking
> that at least a useful subset of the methods can be built on other systems.
> 
> Load this change set into your image, then generate the source for the
> pluggable primitive by executing:
> 
> 	TimePlugin translateDoInlining: true
> 
> Build the plugin (on Unix, just add it to a subdirectory in your source
> tree, reconfigure, and make plugins). Put the shared library
> TimeFunctions.so in the directory with your other plugins, and
> everything should be fine.
> 
> I do not know how much tweaking will be required to make this
> work on a Windows machine, so please let me (lewis at mail.msen.com)
> know if you try it. Thanks."!
> 
> Object subclass: #PointInTime
> 	instanceVariableNames: 'absoluteTime '
> 	classVariableNames: ''
> 	poolDictionaries: ''
> 	category: 'Time'!
> PointInTime subclass: #PointInTimeNow
> 	instanceVariableNames: 'updateProcess '
> 	classVariableNames: 'ThisInstant '
> 	poolDictionaries: ''
> 	category: 'Time'!
> InterpreterPlugin subclass: #TimePlugin
> 	instanceVariableNames: ''
> 	classVariableNames: ''
> 	poolDictionaries: ''
> 	category: 'Time'!
> Object subclass: #TimeZone
> 	instanceVariableNames: 'timeZoneName secondaryTimeZoneName daylightSavingsInEffect currentLocalOffset '
> 	classVariableNames: 'DefaultDaylightSavingsInEffect DefaultLocalOffsetSeconds DefaultSecondaryTimeZoneName DefaultTimeZoneName '
> 	poolDictionaries: ''
> 	category: 'Time'!
> Object subclass: #WallClock
> 	instanceVariableNames: 'now timeZone date time '
> 	classVariableNames: ''
> 	poolDictionaries: ''
> 	category: 'Time'!
> 
> !PointInTime commentStamp: 'dtl 11/30/1999 21:18' prior: 0!
> I represent a single point on an infinite time line. My origin is arbitrarily
> chosen to be the first instant of the day of January 1, 1970, UTC. My unit
> of measure is the second, which I represent as a Float.
> 
> A Float has sufficient precision to represent a millisecond clock for thousands
> of years, and can represent a microsecond clock for about the next hundred
> years. In the event that a microsecond clock is required for Squeak in the
> twenty-second century or later, the possible solutions are:
> 
> 1) Shift the origin of time forward a couple hundred years. Simple to do, and
>    generates good consulting revenues for the decendents of present day Y2k
>    consultants.
> 2) Change to a higher precision representation of absoluteTime. If we are all
>    using longer word length computers in another hundred years, this is a
>    no-brainer.
> 3) Use a LongPositiveInteger representation. This is awkward to implement in
>    primitives, and is not as good for conveying the notion of a point on an
>    infinite continuum, so I do not encourage this approach. - dtl
> !
> 
> !PointInTime methodsFor: 'initialize-release' stamp: 'dtl 11/25/1999 23:00'!
> initialize
> 
> 	self update: self
> ! !
> 
> !PointInTime methodsFor: 'accessing' stamp: 'dtl 11/25/1999 22:59'!
> absoluteTime
> 
> 	^ absoluteTime! !
> 
> !PointInTime methodsFor: 'accessing' stamp: 'dtl 11/26/1999 15:17'!
> absoluteTime: aNumber
> 
> 	absoluteTime _ aNumber! !
> 
> !PointInTime methodsFor: 'converting' stamp: 'dtl 11/30/1999 22:45'!
> asLocalSmalltalkSeconds
> 	"Answer the number of seconds since January 1, 1901 in the local time zone. This
> 	number is suitable for creating instances of Time and Date."
> 
> 	^ self asSmalltalkSecondsForTimeZone: TimeZone here
> ! !
> 
> !PointInTime methodsFor: 'converting' stamp: 'dtl 11/30/1999 22:21'!
> asSmalltalkSecondsForTimeZone: aTimeZone
> 	"Answer the number of seconds since January 1, 1901 in aTimeZone. This
> 	number is suitable for creating instances of Time and Date."
> 
> 	self absoluteTime ifNil: [^ nil].
> 	^ self absoluteTime asInteger + self class posixOffset - (aTimeZone localOffsetSecondsAt: self)
> ! !
> 
> !PointInTime methodsFor: 'printing' stamp: 'dtl 11/26/1999 15:36'!
> printOn: aStream
> 
> 	super printOn: aStream.
> 	aStream nextPutAll: ' at '.
> 	absoluteTime printOn: aStream.
> 	aStream nextPutAll: ' seconds'
> ! !
> 
> !PointInTime methodsFor: 'updating' stamp: 'dtl 11/28/1999 19:36'!
> update: aParameter
> 
> 	absoluteTime _ self primPosixTimeMicrosecondResolution! !
> 
> !PointInTime methodsFor: 'primitives' stamp: 'dtl 11/28/1999 19:35'!
> primPosixTime
> 	"Number of seconds, expressed as a float, since the origin of time for
> 	unix-like systems."
> 
> 	<primitive: 'primitivePosixTime' module: 'TimeFunctions'>
> 	^ nil! !
> 
> !PointInTime methodsFor: 'primitives' stamp: 'dtl 11/27/1999 01:08'!
> primPosixTimeAndLocalOffset
> 	"Array of two integers, with number of seconds since the origin of time for
> 	unix-like systems, and the local offset for the time zone in effect for this system."
> 
> 	<primitive: 'primitivePosixTimeAndLocalOffset' module: 'TimeFunctions'>
> 	^ nil! !
> 
> !PointInTime methodsFor: 'primitives' stamp: 'dtl 11/27/1999 12:50'!
> primPosixTimeMicrosecondResolution
> 	"Number of seconds, expressed as a float, since the origin of time for
> 	unix-like systems."
> 
> 	<primitive: 'primitivePosixTimeMicrosecondResolution' module: 'TimeFunctions'>
> 	^ nil! !
> 
> 
> !PointInTime class methodsFor: 'instance creation' stamp: 'dtl 11/30/1999 20:24'!
> date: aDate time: aTime timeZone: aTimeZone
> 	"Answer a PointInTime corresponding to the aDate and aTime in the
> 	context of aTimeZone."
> 
> 	"PointInTime date: (Date fromString: '23.11.1999') time: (Time fromSeconds:  1700) timeZone: TimeZone here"
> 
> 	"PointInTime date: (Date fromSeconds: 3121286400) time: (Time fromSeconds:  1700) timeZone: TimeZone here"
> 
> 	| s |
> 	s _ aDate asSeconds + aTime asSeconds - (aTimeZone localOffsetSecondsForDate: aDate time: aTime).
> 	^ self fromSmalltalkSeconds: s! !
> 
> !PointInTime class methodsFor: 'instance creation' stamp: 'dtl 11/30/1999 22:44'!
> fromPosixSeconds: seconds
> 	"Answer aPointInTime at a number of seconds after 1-Jan-1970 UTC"
> 
> 	"PointInTime fromPosixSeconds: ((Date today asSeconds) + (Time now asSeconds) + 14400)"
> 
> 	^ super new absoluteTime: seconds asFloat
> ! !
> 
> !PointInTime class methodsFor: 'instance creation' stamp: 'dtl 11/30/1999 22:44'!
> fromSmalltalkSeconds: seconds
> 	"Answer aPointInTime at a number of seconds after 1-Jan-1901 UTC"
> 
> 	"PointInTime fromSmalltalkSeconds: Time totalSeconds"
> 
> 	^ super new absoluteTime: (seconds - self posixOffset) asFloat
> ! !
> 
> !PointInTime class methodsFor: 'instance creation' stamp: 'dtl 11/30/1999 21:04'!
> fromSmalltalkSeconds: seconds inTimeZone: aTimeZone
> 	"Answer aPointInTime at a number of seconds after 1-Jan-1901 in aTimeZone. The
> 	time zone offset is calculated as of aPointInTime, which may not be the same
> 	offset as is currently in effect for aTimeZone."
> 
> 	"PointInTime fromSmalltalkSeconds: Time totalSeconds inTimeZone: TimeZone here"
> 
> 	| approximateTime offset time newOffset |
> 	(1 to: 10) do: [:e |	"Loop until convergence, or exit with error"
> 		approximateTime _ PointInTime fromSmalltalkSeconds:
> 			(seconds + (aTimeZone currentLocalOffset)).
> 		offset _ aTimeZone localOffsetSecondsAt: approximateTime.
> 		time _ PointInTime fromSmalltalkSeconds: (seconds + offset).
> 		newOffset _ aTimeZone localOffsetSecondsAt: time.
> 		(newOffset = offset) ifTrue: [^ time]].
> 	self error: 'algorithm does not converge'.
> 	^ nil
> 
> ! !
> 
> !PointInTime class methodsFor: 'instance creation' stamp: 'dtl 11/26/1999 15:14'!
> now
> 	"PointInTime now"
> 
> 	| now |
> 	now _ super new.
> 	^ now update: now
> ! !
> 
> !PointInTime class methodsFor: 'testing' stamp: 'dtl 11/30/1999 21:07'!
> testFromSmalltalkSeconds
> 	"Answer 'OK' if PointInTime>>fromSmalltalkSeconds gives the right result, plus
> 	or minus one second to allow for clock updates while this test is running."
> 
> 	"PointInTime testFromSmalltalkSeconds"
> 
> 	| t1 t2 |
> 	t1 _ Time totalSeconds.
> 	t2 _ (PointInTime fromSmalltalkSeconds: t1 inTimeZone: TimeZone here) asLocalSmalltalkSeconds.
> 	((t1 - t2) between: -1 and: 1)
> 		ifTrue: [^ 'OK']
> 		ifFalse: [^ 'Failed']! !
> 
> !PointInTime class methodsFor: 'testing' stamp: 'dtl 11/30/1999 22:56'!
> testLocalSeconds
> 	"Answer 'OK' if PointInTime>>now>>asLocalSeconds gives the right result, plus
> 	or minus one second to allow for clock updates while this test is running."
> 
> 	"PointInTime testLocalSeconds"
> 
> 	| now |
> 	now _ PointInTime now asLocalSmalltalkSeconds.
> 	(now notNil and: [((Time totalSeconds - now) between: -1 and: 1)])
> 		ifTrue: [^ 'OK']
> 		ifFalse: [^ 'Failed']! !
> 
> !PointInTime class methodsFor: 'private' stamp: 'dtl 11/29/1999 23:27'!
> posixOffset
> 	"Logic is lifted from Ian's Unix support code.
> 	Squeak epoc	h is Jan 1, 1901.  Unix epoch is Jan 1, 1970: 17 leap years
>      and 52 non-leap years later than Squeak."
> 
> 	"52 * 365 + (17 * 366) * 24 * 60 * 60"
> 
> 	^ 2177452800! !
> 
> 
> !PointInTimeNow commentStamp: 'dtl 11/27/1999 16:48' prior: 0!
> I represent the current point in time, as reported by the underlying hardware
> or operating system. There is only one instance of me in the system.
> 
> My update mechanism is a hack. A better way is to hook to the system clock
> for automatic updates. See comment in my updateFromSystemClock method.!
> 
> !PointInTimeNow methodsFor: 'initialize-release' stamp: 'dtl 11/27/1999 14:05'!
> initialize
> 
> 	super initialize.
> 	self addDependent: self.
> 	self updateFromSystemClock! !
> 
> !PointInTimeNow methodsFor: 'initialize-release' stamp: 'dtl 11/27/1999 14:05'!
> release
> 
> 	super release.
> 	self removeDependent: self! !
> 
> !PointInTimeNow methodsFor: 'system clock' stamp: 'dtl 11/26/1999 15:52'!
> terminateProcess
> 
> 	updateProcess ifNotNil: [updateProcess terminate].
> ! !
> 
> !PointInTimeNow methodsFor: 'system clock' stamp: 'dtl 11/27/1999 14:04'!
> updateFromSystemClock
> 
> 	"FIXME: Add a hook here to update the time automagically. That requires
> 	messing with the VM support code, so for the time being this is just a placeholder.
> 	Get rid of the instance variable and the update process when the automagic version
> 	is done."
> 
> 	self terminateProcess.
> 	updateProcess _ [[true] whileTrue: [
> 		(Delay forMilliseconds: 200) wait.
> 		self changed: self]] forkAt: Processor userInterruptPriority
> 	! !
> 
> 
> !PointInTimeNow class methodsFor: 'instance creation' stamp: 'dtl 11/26/1999 12:55'!
> new
> 
> 	self notify: 'use PointInTimeNow>>thisInstant to access my single instance'! !
> 
> !PointInTimeNow class methodsFor: 'instance creation' stamp: 'dtl 11/26/1999 15:40'!
> thisInstant
> 	"PointInTimeNow thisInstant"
> 
> 	ThisInstant ifNil: [ThisInstant _ super new initialize].
> 	^ ThisInstant! !
> 
> !PointInTimeNow class methodsFor: 'initialize-release' stamp: 'dtl 11/26/1999 15:53'!
> initialize
> 	"PointInTimeNow initialize"
> 
> 	ThisInstant ifNotNil: [
> 		ThisInstant terminateProcess.
> 		ThisInstant _ nil]! !
> 
> 
> !TimePlugin commentStamp: 'dtl 11/26/1999 16:00' prior: 0!
> I contain source code for pluggable primitives for time functions.!
> 
> !TimePlugin reorganize!
> ('primitives - time' primitivePosixTime primitivePosixTimeAndLocalOffset primitivePosixTimeMicrosecondResolution)
> ('primitives - timezone' primitiveGetDaylightFlag primitiveGetDaylightFlagAt primitiveGetTimeZone primitiveGetTimeZoneAt primitiveGetTimeZoneName primitiveGetTimeZoneSecondaryName primitiveLocalOffsetSeconds primitiveLocalOffsetSecondsAt)
> !
> 
> 
> !TimePlugin methodsFor: 'primitives - time' stamp: 'dtl 11/28/1999 19:05'!
> primitivePosixTime
> 	"Answer Posix time in seconds expressed as a Float."
> 
> 	| dt |
> 	self var: #dt declareC: 'double dt'.
> 	dt _ self cCode: '(double) time(NULL)'.
> 	interpreterProxy pop: 1; pushFloat: dt! !
> 
> !TimePlugin methodsFor: 'primitives - time' stamp: 'dtl 11/28/1999 19:22'!
> primitivePosixTimeAndLocalOffset
> 	"Answer an array with the Posix time and the current local offset, with
> 	Posix time expressed as a Float, and local offset expressed as an Integer.
> 	The two values are obtained simultaneously."
> 
> 	| t timeStruct result timezone |
> 	self var: #t declareC: 'time_t t'.
> 	self var: #timeStruct declareC: 'struct tm *timeStruct'.
> 	self var: #timezone declareC: 'extern long int timezone'.
> 
> 	t _ self cCode: 'time(NULL)'.
> 	timeStruct _ self cCode: 'localtime(&t)'.
> 	"External variable timezone is set as side effect of localtime(3)"
> 
> 	result _ interpreterProxy
> 			instantiateClass: interpreterProxy classArray
> 			indexableSize: 2.	
> 	interpreterProxy stObject: result at: 1 put: (interpreterProxy floatObjectOf: t).
> 	interpreterProxy stObject: result at: 2 put: (interpreterProxy integerObjectOf: timezone).
> 	interpreterProxy pop: 1; push: result
> 
> ! !
> 
> !TimePlugin methodsFor: 'primitives - time' stamp: 'dtl 11/28/1999 19:43'!
> primitivePosixTimeMicrosecondResolution
> 	"Answer Posix time as a float with microsecond precision, limited of course
> 	by the capability of the hardware. Use a gettimeofday() call to get current
> 	time. This may not be supported on some systems."
> 
> 	| tv |
> 	self var: #tv declareC: 'struct timeval tv'.
> 	interpreterProxy pop: 1.
> 	(self cCode: 'gettimeofday(&tv, NULL)')
> 		ifTrue: [interpreterProxy push: interpreterProxy nilObject]
> 		ifFalse: [interpreterProxy pushFloat: (self cCode: 'tv.tv_usec / 1000000.0 + tv.tv_sec')]
> ! !
> 
> !TimePlugin methodsFor: 'primitives - timezone' stamp: 'dtl 11/28/1999 19:18'!
> primitiveGetDaylightFlag
> 	"Answer the daylight savings time flag at the present time"
> 
> 	| t daylight |
> 	self var: #t declareC: 'time_t t'.
> 	t _ self cCode: 'time(NULL)'.
> 	self cCode: 'localtime(&t)'.
> 	"External variable daylight is set as side effect of localtime(3)"
> 	interpreterProxy pop: 1; pushBool: (daylight ~= 0)! !
> 
> !TimePlugin methodsFor: 'primitives - timezone' stamp: 'dtl 11/28/1999 20:44'!
> primitiveGetDaylightFlagAt
> 	"Answer the daylight savings time flag for a Posix time expressed as a Float."
> 
> 	| t daylight |
> 	self var: #t declareC: 'time_t t'.
> 	t _ self popFloat.	"Coersce to time_t."
> 	self cCode: 'localtime(&t)'.
> 	"External variable daylight is set as side effect of localtime(3)"
> 	interpreterProxy pop: 1; pushBool: (daylight ~= 0)! !
> 
> !TimePlugin methodsFor: 'primitives - timezone' stamp: 'dtl 11/29/1999 21:48'!
> primitiveGetTimeZone
> 	"Answer a four element array of two time zone names (primary and secondary),
> 	daylight savings time flag, and seconds offset from UTC."
> 
> 	| t timeStruct tz strOop1 strPtr1 strOop2 strPtr2 daylight timezone |
> 	self var: #t declareC: 'time_t t'.
> 	self var: #timeStruct declareC: 'struct tm *timeStruct'.
> 	self var: #strPtr1 declareC: 'char * strPtr1'.
> 	self var: #strPtr2 declareC: 'char * strPtr2'.
> 
> 	"Get timezone information from the operating system."
> 	t _ self cCode: 'time(NULL)'.
> 	timeStruct _ self cCode: 'localtime(&t)'.
> 	"External variable tzname[] is set as side effect of localtime(3)"
> 
> 	"Instantiate an array of two strings."
> 	tz _ interpreterProxy
> 			instantiateClass: interpreterProxy classArray
> 			indexableSize: 4.	
> 	strOop1 _ interpreterProxy
> 			instantiateClass: interpreterProxy classString
> 			indexableSize: (self cCode: 'strlen(tzname[0])').
> 	strOop2 _ interpreterProxy
> 			instantiateClass: interpreterProxy classString
> 			indexableSize: (self cCode: 'strlen(tzname[1])').
> 	interpreterProxy stObject: tz at: 1 put: strOop1.
> 	interpreterProxy stObject: tz at: 2 put: strOop2.
> 	strPtr1 _ interpreterProxy arrayValueOf: strOop1.
> 	strPtr2 _ interpreterProxy arrayValueOf: strOop2.
> 
> 	"Copy the time zone names into the strings."
> 	self cCode: 'strcpy(strPtr1, tzname[0])'.
> 	self cCode: 'strcpy(strPtr2, tzname[1])'.
> 
> 	"Daylight savings time flag, a boolean."
> 	(daylight ~= 0)
> 		ifTrue: [interpreterProxy stObject: tz at: 3 put: interpreterProxy trueObject]
> 		ifFalse: [interpreterProxy stObject: tz at: 3 put: interpreterProxy falseObject].
> 
> 	"Seconds offset from UTC."
> 	interpreterProxy stObject: tz at: 4 put: (interpreterProxy integerObjectOf: timezone).
> 
> 	"Answer the results array."
> 	interpreterProxy pop: 1; push: tz
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> ! !
> 
> !TimePlugin methodsFor: 'primitives - timezone' stamp: 'dtl 11/29/1999 21:51'!
> primitiveGetTimeZoneAt
> 	"Answer a four element array of two time zone names (primary and secondary),
> 	daylight savings time flag, and seconds offset from UTC. The values are obtained
> 	relative to the given Posix time, which is passed as a Float."
> 
> 	| t timeStruct tz strOop1 strPtr1 strOop2 strPtr2 daylight timezone |
> 	self var: #t declareC: 'time_t t'.
> 	self var: #timeStruct declareC: 'struct tm *timeStruct'.
> 	self var: #strPtr1 declareC: 'char * strPtr1'.
> 	self var: #strPtr2 declareC: 'char * strPtr2'.
> 
> 	"Get timezone information from the operating system."
> 	t _ self popFloat.	"Coersce to time_t."
> 	timeStruct _ self cCode: 'localtime(&t)'.
> 	"External variable tzname[] is set as side effect of localtime(3)"
> 
> 	"Instantiate an array of two strings."
> 	tz _ interpreterProxy
> 			instantiateClass: interpreterProxy classArray
> 			indexableSize: 4.	
> 	strOop1 _ interpreterProxy
> 			instantiateClass: interpreterProxy classString
> 			indexableSize: (self cCode: 'strlen(tzname[0])').
> 	strOop2 _ interpreterProxy
> 			instantiateClass: interpreterProxy classString
> 			indexableSize: (self cCode: 'strlen(tzname[1])').
> 	interpreterProxy stObject: tz at: 1 put: strOop1.
> 	interpreterProxy stObject: tz at: 2 put: strOop2.
> 	strPtr1 _ interpreterProxy arrayValueOf: strOop1.
> 	strPtr2 _ interpreterProxy arrayValueOf: strOop2.
> 
> 	"Copy the time zone names into the strings."
> 	self cCode: 'strcpy(strPtr1, tzname[0])'.
> 	self cCode: 'strcpy(strPtr2, tzname[1])'.
> 
> 	"Daylight savings time flag, a boolean."
> 	(daylight ~= 0)
> 		ifTrue: [interpreterProxy stObject: tz at: 3 put: interpreterProxy trueObject]
> 		ifFalse: [interpreterProxy stObject: tz at: 3 put: interpreterProxy falseObject].
> 
> 	"Seconds offset from UTC."
> 	interpreterProxy stObject: tz at: 4 put: (interpreterProxy integerObjectOf: timezone).
> 
> 	"Answer the results array."
> 	interpreterProxy pop: 1; push: tz
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> ! !
> 
> !TimePlugin methodsFor: 'primitives - timezone' stamp: 'dtl 11/27/1999 01:23'!
> primitiveGetTimeZoneName
> 	"Answer the name of this time zone."
> 
> 	| t timeStruct tz tzPtr |
> 	self var: #t declareC: 'time_t t'.
> 	self var: #timeStruct declareC: 'struct tm *timeStruct'.
> 	self var: #tzPtr declareC: 'char * tzPtr'.
> 
> 	t _ self cCode: 'time(NULL)'.
> 	timeStruct _ self cCode: 'localtime(&t)'.
> 	"External variable tzname[] is set as side effect of localtime(3)"
> 
> 	tz _ interpreterProxy
> 			instantiateClass: interpreterProxy classString
> 			indexableSize: (self cCode: 'strlen(tzname[0])').
> 	tzPtr _ interpreterProxy arrayValueOf: tz.
> 
> 	self cCode: 'strcpy(tzPtr, tzname[0])'.
> 	interpreterProxy pop: 1; push: tz
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> ! !
> 
> !TimePlugin methodsFor: 'primitives - timezone' stamp: 'dtl 11/27/1999 01:24'!
> primitiveGetTimeZoneSecondaryName
> 	"Answer the name of this time zone."
> 
> 	| t timeStruct tz tzPtr |
> 	self var: #t declareC: 'time_t t'.
> 	self var: #timeStruct declareC: 'struct tm *timeStruct'.
> 	self var: #tzPtr declareC: 'char * tzPtr'.
> 
> 	t _ self cCode: 'time(NULL)'.
> 	timeStruct _ self cCode: 'localtime(&t)'.
> 	"External variable tzname[] is set as side effect of localtime(3)"
> 
> 	tz _ interpreterProxy
> 			instantiateClass: interpreterProxy classString
> 			indexableSize: (self cCode: 'strlen(tzname[1])').
> 	tzPtr _ interpreterProxy arrayValueOf: tz.
> 
> 	self cCode: 'strcpy(tzPtr, tzname[1])'.
> 	interpreterProxy pop: 1; push: tz
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> 
> ! !
> 
> !TimePlugin methodsFor: 'primitives - timezone' stamp: 'dtl 11/28/1999 19:12'!
> primitiveLocalOffsetSeconds
> 
> 	| t timezone |
> 	self var: #t declareC: 'time_t t'.
> 	self var: #timezone declareC: 'extern long int timezone'.
> 	t _ self cCode: 'time(NULL)'.
> 	self cCode: 'localtime(&t)'.
> 	"External variable timezone is set as side effect of localtime(3)"
> 	interpreterProxy pop: 1.
> 	interpreterProxy pushInteger: timezone
> 
> 
> ! !
> 
> !TimePlugin methodsFor: 'primitives - timezone' stamp: 'dtl 11/28/1999 21:04'!
> primitiveLocalOffsetSecondsAt
> 	"Answer the local offset in seconds for a Posix time expressed as a Float.
> 	For a given time zone, the offset may change as a function of absolute
> 	time, for example if daylight savings time is in effect."
> 
> 	| t timezone |
> 	self var: #t declareC: 'time_t t'.
> 	self var: #timeStruct declareC: 'struct tm *timeStruct'.
> 	self var: #timezone declareC: 'extern long int timezone'.
> 	t _ self popFloat.	"Coersce to time_t."
> 	self cCode: 'localtime(&t)'.
> 	interpreterProxy pop: 1; pushInteger: timezone
> ! !
> 
> 
> !TimePlugin class methodsFor: 'class initialization' stamp: 'dtl 11/27/1999 12:46'!
> declareCVarsIn: cg
> 
> 	cg addHeaderFile: '<unistd.h>'.
> 	cg addHeaderFile: '<sys/utsname.h>'.
> 	cg addHeaderFile: '<sys/time.h>
> /* D T Lewis 1999 - TimeFunctions.c translated from class TimePlugin */'.
> ! !
> 
> !TimePlugin class methodsFor: 'translation' stamp: 'dtl 11/26/1999 13:31'!
> moduleName
> 
> 	^ 'TimeFunctions'! !
> 
> !TimePlugin class methodsFor: 'translation' stamp: 'dtl 11/25/1999 23:15'!
> translate: fileName doInlining: inlineFlag
> 
> 	"This is a convenience method which simply documents that the C source code file
> 	may be generated as shown below."
> 
> 	"TimePlugin translate: TimePlugin moduleName,'.c' doInlining: true"
> 
> 	^ super translate: fileName doInlining: inlineFlag! !
> 
> !TimePlugin class methodsFor: 'translation' stamp: 'dtl 11/25/1999 23:16'!
> translateDoInlining: inlineFlag
> 
> 	"Translate to C source code file."
> 
> 	"TimePlugin translateDoInlining: true"
> 
> 	^ super translate: TimePlugin moduleName,'.c' doInlining: inlineFlag! !
> 
> !TimeZone commentStamp: 'dtl 11/30/1999 21:39' prior: 0!
> I represent a time zone for a location in the world. I know how to
> do a coordinate transformation between a PointInTime (a point on
> an infinite time line) and the local time line as might be used
> by a wall clock or by the Time and Date classes.
> 
> The coordinate transformation is not necessarily a continuous function,
> because it embodies rules for setting local clock forward and back in
> accordance with daylight savings time conventions and other calendar
> oddities.
> 
> I am not yet smart enough to make use of a time zone database, but I
> do at least have enough sense to make inquiries to the operating system
> to see if it can tell me where I am and how my timezone rules should
> behave.!
> 
> !TimeZone methodsFor: 'initialize-release' stamp: 'dtl 11/28/1999 18:23'!
> initialize
> 
> 	self setTimeZoneName.
> 	self setSecondaryTimeZoneName.
> 	self setCurrentLocalOffset.
> 	self setDaylightSavingsInEffect
> 
> 
> 
> 	! !
> 
> !TimeZone methodsFor: 'accessing' stamp: 'dtl 11/28/1999 18:23'!
> currentLocalOffset
> 	"Always update from the primitive if possible."
> 
> 	^ currentLocalOffset _ self setCurrentLocalOffset
> 
> ! !
> 
> !TimeZone methodsFor: 'accessing' stamp: 'dtl 11/28/1999 18:25'!
> currentLocalOffset: anInteger
> 	"Number of seconds offset from UTC at the present time. Note that
> 	value changes as a function of the current time, for example when
> 	daylight savings time takes effect."
> 
> 	currentLocalOffset _ anInteger
> 
> ! !
> 
> !TimeZone methodsFor: 'accessing' stamp: 'dtl 11/28/1999 10:59'!
> daylightSavingsInEffect
> 	"Always update from the primitive if possible."
> 
> 	^ daylightSavingsInEffect _ self setDaylightSavingsInEffect
> ! !
> 
> !TimeZone methodsFor: 'accessing' stamp: 'dtl 11/25/1999 21:59'!
> daylightSavingsInEffect: aBoolean
> 
> 	daylightSavingsInEffect _ aBoolean! !
> 
> !TimeZone methodsFor: 'accessing' stamp: 'dtl 11/25/1999 22:11'!
> secondaryTimeZoneName
> 
> 	^ secondaryTimeZoneName! !
> 
> !TimeZone methodsFor: 'accessing' stamp: 'dtl 11/25/1999 22:11'!
> secondaryTimeZoneName: aSymbol
> 
> 	secondaryTimeZoneName _ aSymbol! !
> 
> !TimeZone methodsFor: 'accessing' stamp: 'dtl 11/25/1999 22:12'!
> timeZoneName
> 
> 	^ timeZoneName! !
> 
> !TimeZone methodsFor: 'accessing' stamp: 'dtl 11/25/1999 22:12'!
> timeZoneName: aSymbol
> 
> 	timeZoneName _ aSymbol! !
> 
> !TimeZone methodsFor: 'offsets from UTC' stamp: 'dtl 11/30/1999 22:23'!
> localOffsetSecondsAt: aPointInTime
> 	"Answer the offset from UTC in this time zone as of aPointInTime"
> 
> 	| t |
> 	t _ aPointInTime absoluteTime.
> 	t ifNil: [^ nil].
> 	^ self primLocalOffsetSecondsAt: t! !
> 
> !TimeZone methodsFor: 'offsets from UTC' stamp: 'dtl 11/30/1999 21:02'!
> localOffsetSecondsForDate: aDate time: aTime
> 	"Answer the offset from UTC in this time zone as of aDate and aTime, where
> 	aDate and aTime are in the context of this time zone."
> 
> 	"TimeZone here localOffsetSecondsForDate: Date today time: Time now"
> 
> 	| seconds t |
> 	seconds _ aDate asSeconds + aTime asSeconds.
> 	t _ PointInTime fromSmalltalkSeconds: seconds inTimeZone: self.
> 	^ self localOffsetSecondsAt: t
> ! !
> 
> !TimeZone methodsFor: 'printing' stamp: 'dtl 11/27/1999 16:07'!
> printOn: aStream
> 
> 	super printOn: aStream.
> 	timeZoneName ifNotNil: [
> 		aStream nextPut: $ .
> 		timeZoneName do: [:e | aStream nextPut: e]].
> 	secondaryTimeZoneName ifNotNil: [
> 		aStream nextPut: $ .
> 		secondaryTimeZoneName do: [:e | aStream nextPut: e]]
> ! !
> 
> !TimeZone methodsFor: 'private' stamp: 'dtl 11/28/1999 18:23'!
> setCurrentLocalOffset
> 
> 	| offset |
> 	offset _ self primLocalOffsetSeconds.
> 	offset notNil
> 		ifTrue: [^ currentLocalOffset _ offset]
> 		ifFalse: [^ currentLocalOffset _ DefaultLocalOffsetSeconds]
> ! !
> 
> !TimeZone methodsFor: 'private' stamp: 'dtl 11/28/1999 11:10'!
> setDaylightSavingsInEffect
> 
> 	| dst |
> 	dst _ self primGetDaylightFlag.
> 	dst notNil
> 		ifTrue: [^ daylightSavingsInEffect _ dst]
> 		ifFalse: [^ daylightSavingsInEffect _ DefaultDaylightSavingsInEffect]
> ! !
> 
> !TimeZone methodsFor: 'private' stamp: 'dtl 11/28/1999 21:10'!
> setSecondaryTimeZoneName
> 
> 	| tz |
> 	tz _ self primGetTimeZoneSecondaryName.
> 	tz notNil
> 		ifTrue: [^ secondaryTimeZoneName _ tz]
> 		ifFalse: [^ secondaryTimeZoneName _ DefaultSecondaryTimeZoneName]! !
> 
> !TimeZone methodsFor: 'private' stamp: 'dtl 11/28/1999 21:09'!
> setTimeZoneName
> 
> 	| tz |
> 	tz _ self primGetTimeZoneName.
> 	tz notNil
> 		ifTrue: [^ timeZoneName _ tz]
> 		ifFalse: [^ timeZoneName _ DefaultTimeZoneName]! !
> 
> !TimeZone methodsFor: 'primitives' stamp: 'dtl 11/30/1999 21:56'!
> primGetDaylightFlag
> 	"Answer true if daylight savings is in effect"
> 
> 	<primitive: 'primitiveGetDaylightFlag' module: 'TimeFunctions'>
> 	^ DefaultDaylightSavingsInEffect! !
> 
> !TimeZone methodsFor: 'primitives' stamp: 'dtl 11/30/1999 21:56'!
> primGetDaylightFlagAt: aPosixTimeExpressedAsFloat
> 	"Answer true if daylight savings is in effect"
> 
> 	<primitive: 'primitiveGetDaylightFlagAt' module: 'TimeFunctions'>
> 	^ DefaultDaylightSavingsInEffect! !
> 
> !TimeZone methodsFor: 'primitives' stamp: 'dtl 11/30/1999 21:28'!
> primGetTimeZone
> 	"Answer a four element array of two time zone names (primary and secondary),
> 	daylight savings time flag, and seconds offset from UTC, for the current
> 	time zone at the present time."
> 
> 	<primitive: 'primitiveGetTimeZone' module: 'TimeFunctions'>
> 	^ nil! !
> 
> !TimeZone methodsFor: 'primitives' stamp: 'dtl 11/30/1999 21:28'!
> primGetTimeZoneAt: aPosixTimeExpressedAsFloat
> 	"Answer a four element array of two time zone names (primary and secondary),
> 	daylight savings time flag, and seconds offset from UTC, for the current
> 	time zone at the indicated time."
> 
> 	<primitive: 'primitiveGetTimeZoneAt' module: 'TimeFunctions'>
> 	^ nil! !
> 
> !TimeZone methodsFor: 'primitives' stamp: 'dtl 11/30/1999 21:57'!
> primGetTimeZoneName
> 	"Answer time zone name"
> 
> 	<primitive: 'primitiveGetTimeZoneName' module: 'TimeFunctions'>
> 	^ DefaultTimeZoneName! !
> 
> !TimeZone methodsFor: 'primitives' stamp: 'dtl 11/30/1999 21:57'!
> primGetTimeZoneSecondaryName
> 	"Answer secondary time zone name"
> 
> 	<primitive: 'primitiveGetTimeZoneSecondaryName' module: 'TimeFunctions'>
> 	^ DefaultSecondaryTimeZoneName! !
> 
> !TimeZone methodsFor: 'primitives' stamp: 'dtl 11/30/1999 21:57'!
> primLocalOffsetSeconds
> 
> 	<primitive: 'primitiveLocalOffsetSeconds' module: 'TimeFunctions'>
> 	^ DefaultLocalOffsetSeconds! !
> 
> !TimeZone methodsFor: 'primitives' stamp: 'dtl 11/28/1999 18:36'!
> primLocalOffsetSecondsAt: aFloat
> 
> 	<primitive: 'primitiveLocalOffsetSecondsAt' module: 'TimeFunctions'>
> 	^ DefaultLocalOffsetSeconds! !
> 
> 
> !TimeZone class methodsFor: 'instance creation' stamp: 'dtl 11/30/1999 22:46'!
> here
> 	"Answer an instance representing the timezone at this location."
> 
> 	"TimeZone here"
> 
> 	^ super new initialize! !
> 
> !TimeZone class methodsFor: 'initialize-release' stamp: 'dtl 11/28/1999 21:12'!
> initialize
> 
> 	"Eastern Standard Time, Detroit, Michigan, USA"
> 
> 	"TimeZone initialize"
> 
> 	DefaultLocalOffsetSeconds _ 18000.
> 	DefaultTimeZoneName _ #EST.
> 	DefaultSecondaryTimeZoneName _ #DST.
> 	DefaultDaylightSavingsInEffect _ true! !
> 
> 
> !WallClock commentStamp: 'dtl 11/27/1999 16:53' prior: 0!
> I am a demonstration of how to relate PointInTimeNow to the Squeak Time and
> Date classes by means of a TimeZone.
> 
> I know how to watch the singleton instance of PointInTimeNow, and to update
> the current date and time accordingly. Watch me in an inspector and check to
> see if the time conversion methods are working correctly. My date and time
> should be the same as those answered by Time class>>now and Date class>>today.!
> 
> !WallClock methodsFor: 'initialize-release' stamp: 'dtl 11/27/1999 15:57'!
> initialize
> 
> 	timeZone _ TimeZone here.
> 	now _ PointInTimeNow thisInstant.
> 	now addDependent: self! !
> 
> !WallClock methodsFor: 'initialize-release' stamp: 'dtl 11/27/1999 13:58'!
> release
> 
> 	now ifNotNil: [
> 		now removeDependent: self.
> 		now _ nil]! !
> 
> !WallClock methodsFor: 'accessing' stamp: 'dtl 11/27/1999 13:55'!
> date
> 
> 	^ date! !
> 
> !WallClock methodsFor: 'accessing' stamp: 'dtl 11/27/1999 13:53'!
> now
> 
> 	^ now! !
> 
> !WallClock methodsFor: 'accessing' stamp: 'dtl 11/27/1999 13:55'!
> time
> 
> 	^ time! !
> 
> !WallClock methodsFor: 'accessing' stamp: 'dtl 11/27/1999 15:57'!
> timeZone
> 
> 	^ timeZone! !
> 
> !WallClock methodsFor: 'printing' stamp: 'dtl 11/27/1999 23:49'!
> printOn: aStream
> 
> 	| abs |
> 	abs _ now absoluteTime.
> 	aStream nextPutAll: 'a '.
> 	abs ifNil: [aStream nextPutAll: 'bogus '].
> 	self class printOn: aStream.
> 	aStream nextPutAll: ' with date '.
> 	date printOn: aStream.
> 	aStream nextPutAll: ' and time '.
> 	time printOn: aStream.
> 	timeZone ifNotNil: [
> 		aStream nextPutAll: ' '.
> 		timeZone timeZoneName do: [:e | aStream nextPut: e]].
> 	aStream nextPutAll: ' from absoluteTime '.
> 	abs isNil
> 		ifTrue: [aStream nextPutAll: '(unavailable - pluggable primitives not yet built - using class defaults)']
> 		ifFalse: [aStream nextPutAll: abs asInteger asStringWithCommas.
> 				aStream nextPutAll: ' ('.
> 				abs printOn: aStream.
> 				aStream nextPutAll: ')']! !
> 
> !WallClock methodsFor: 'updating' stamp: 'dtl 11/30/1999 22:28'!
> update: aParameter
> 
> 	| s |
> 	s _ self now asSmalltalkSecondsForTimeZone: self timeZone.
> 	s ifNotNil: [date _ Date fromSeconds: s.
> 			    time _ Time fromSeconds: (s - (date asSeconds))]
> ! !
> 
> 
> !WallClock class methodsFor: 'instance creation' stamp: 'dtl 11/27/1999 13:51'!
> new
> 	"WallClock new inspect"
> 
> 	^ super new initialize! !
> 
> 
> PointInTime removeSelector: #asLocalSecondsForTimeZone:!
> PointInTime removeSelector: #primAbsoluteTime!
> PointInTime removeSelector: #timeZone:!
> PointInTime removeSelector: #asLocalSmalltalkSecondsForTimeZone:!
> PointInTime removeSelector: #posixOffset!
> PointInTime removeSelector: #smalltalkSeconds!
> PointInTime removeSelector: #asLocalSeconds!
> PointInTime removeSelector: #asSeconds!
> PointInTime removeSelector: #asSmalltalkSeconds!
> PointInTime removeSelector: #timeZone!
> PointInTime removeSelector: #timezone:!
> PointInTime removeSelector: #primLocalOffsetSeconds!
> PointInTime removeSelector: #primLocalOffsetHousr!
> PointInTime removeSelector: #primAbsoluteTimeAsFloat!
> PointInTime removeSelector: #primLocalOffsetHours!
> PointInTime removeSelector: #primAbsoluteTimeAsFloatMicrosecondResolution!
> PointInTime removeSelector: #posixOffsetAsFloat!
> PointInTime removeSelector: #timezone!
> PointInTime class removeSelector: #testConversions!
> PointInTime class removeSelector: #fromSeconds:!
> PointInTime class removeSelector: #testFromSeconds!
> PointInTime class removeSelector: #fromSeconds:inTimeZone:!
> PointInTimeNow initialize!
> TimePlugin removeSelector: #posixTimeWithMicrosecondResolution!
> TimePlugin removeSelector: #primitiveGetTzName!
> TimePlugin removeSelector: #primitiveAbsoluteTimeAsFloat!
> TimePlugin removeSelector: #primitiveGetTimeZoneSecontdaryName!
> TimePlugin removeSelector: #primitivePosixTimeWithMicrosecondResolution!
> TimePlugin removeSelector: #primitiveAbsoluteTimeAsFloatMicrosecondResolution!
> TimePlugin removeSelector: #posixOffset!
> TimePlugin removeSelector: #posixTime!
> TimePlugin removeSelector: #primitiveAbsoluteTimaAndLocalOffset!
> TimePlugin removeSelector: #posixTimeWithMillisecondResolution!
> TimePlugin removeSelector: #primitiveLocalOffsetHours!
> TimePlugin removeSelector: #smalltalkTimeMicrosecondResolution!
> TimePlugin removeSelector: #posixTimeAsInteger!
> TimePlugin removeSelector: #localOffsetSeconds!
> TimePlugin removeSelector: #posixTimeMicrosecondResolution!
> TimePlugin removeSelector: #smalltalkTime!
> TimePlugin removeSelector: #primitiveGetdaylightFlag!
> TimePlugin removeSelector: #primitiveAbsoluteTimeAndLocalOffset!
> TimePlugin removeSelector: #primitiveAbsoluteTime!
> TimePlugin removeSelector: #isDaylightSavings!
> TimeZone removeSelector: #daylightSavingsTimeInEffect:!
> TimeZone removeSelector: #localOffsetSeconds!
> TimeZone removeSelector: #localOffset:!
> TimeZone removeSelector: #primLocalOffsetHours!
> TimeZone removeSelector: #daylightSavingsTimeInEffect!
> TimeZone removeSelector: #primGetTimezoneSecondaryName!
> TimeZone removeSelector: #localOffsetHours!
> TimeZone removeSelector: #timezoneName!
> TimeZone removeSelector: #setLocalOffset!
> TimeZone removeSelector: #secondaryTimezoneName:!
> TimeZone removeSelector: #localOffsetSecondsForDate:time:timeZone:!
> TimeZone removeSelector: #primGetTimezone!
> TimeZone removeSelector: #timezoneName:!
> TimeZone removeSelector: #primGetTimezone:!
> TimeZone removeSelector: #localOffsetSecondsForDate:atTime:!
> TimeZone removeSelector: #locateOffsetSecondsAt:!
> TimeZone removeSelector: #secondaryTimezoneName!
> TimeZone removeSelector: #localOffset!
> TimeZone initialize!
> "Postscript:
> Bring up an inspector on a WallClock to demonstrate how the time functions
> work. The WallClock will not work correctly until the plugin is compiled."
> 
> WallClock new inspect.
> !
> 
> 
> --tKW2IUtsqtDRztdT--





More information about the Squeak-dev mailing list