[squeak-dev] The Trunk: Chronology-Core-mt.70.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Jul 5 07:01:25 UTC 2021


Marcel Taeumel uploaded a new version of Chronology-Core to project The Trunk:
http://source.squeak.org/trunk/Chronology-Core-mt.70.mcz

==================== Summary ====================

Name: Chronology-Core-mt.70
Author: mt
Time: 5 July 2021, 9:01:22.838745 am
UUID: 5450e237-fb63-c04b-90d0-94e40ef57fa4
Ancestors: Chronology-Core-mt.69, Chronology-Core-dtl.68

Merges latest fixes from Chronology-Core-dtl.68, after the update bug was fixed in (the kind of branch'd) Chronology-Core-mt.69.

=============== Diff against Chronology-Core-mt.69 ===============

Item was changed:
  Magnitude subclass: #DateAndTime
  	instanceVariableNames: 'utcMicroseconds localOffsetSeconds'
+ 	classVariableNames: 'AutomaticTimezone ClockProvider LocalTimeZone PosixEpochJulianDays'
- 	classVariableNames: 'AutomaticTimezone ClockProvider InitializeFromPrimitive LocalTimeZone PosixEpochJulianDays'
  	poolDictionaries: 'ChronologyConstants'
  	category: 'Chronology-Core'!
  
  !DateAndTime commentStamp: 'dtl 3/12/2016 10:32' prior: 0!
  I represent a point in UTC time as defined by ISO 8601. I have zero duration.
  
  My implementation uses variables utcMicroseconds and localOffsetSeconds. This represents time magnitude as elapsed microseconds since the Posix epoch, with localOffsetSeconds representing local offset from UTC. The magnitude is used for comparison and duration calculations, and the local offset is used for displaying this magnitude in the context of a local time zone.
  
  The implementation ignores leap seconds, which are adjustments made to maintain earth rotational clock time in synchronization with elapsed seconds.
  
  DateAndTime class>>now will use #primitiveUtcWithOffset to obtain current time in UTC microseconds with current local offset in seconds. The primitive provides an atomic query for UTC time and local offset as measured by the OS platform.  If primitiveUtcWithOffset is not available, the traditional implementation is used, which relies on a primitive for microseconds in the local time zone and derives UTC based on the TimeZone setting.
  !

Item was removed:
- ----- Method: DateAndTime class>>canInitializeFromPrimitive (in category 'system startup') -----
- canInitializeFromPrimitive
- 	"Some implementations of primitiveUtcWithOffset do not support passing the
- 	DateAndTime instance as a parameter to the primitive."
- 
- 	^self  basicNew initializeFromPrimitive utcMicroseconds notNil!

Item was changed:
  ----- Method: DateAndTime class>>initialize (in category 'initialize-release') -----
  initialize
  
  	ClockProvider := Time.
+ 	PosixEpochJulianDays := 2440588.!
- 	PosixEpochJulianDays := 2440588.
- 	InitializeFromPrimitive := self canInitializeFromPrimitive.
- 	Smalltalk addToStartUpList: self.
- 	self startUp: true
- !

Item was changed:
  ----- Method: DateAndTime class>>now (in category 'ansi protocol') -----
  now
  	"Answer time now as reported by #primitiveUtcWithOffset. If the primitive is not
  	available, answer the Posix epoch GMT."
  
  	self automaticTimezone
  		ifTrue: [ ^ self basicNew initializeFromPrimitive ]
  		ifFalse: [ | timeArray |
  			timeArray := Time posixMicrosecondClockWithOffset.
  			^ self utcMicroseconds: timeArray first offset: self localOffsetSeconds ]
  !

Item was changed:
  ----- Method: DateAndTime class>>readFrom: (in category 'squeak protocol') -----
  readFrom: aStream
  
+ 	| yearMonthDay hourMinuteSecondNano offsetSeconds |
- 	| offsetSeconds ch yearMonthDay hourMinuteSecondNano offset |
  
  	yearMonthDay := Date readYearMonthDayFrom: aStream.
  	[aStream peek isDigit]
  		whileFalse: [aStream next].
  	hourMinuteSecondNano := Time readHourMinuteSecondNanoFrom: aStream.
  	(aStream atEnd or: [('+-Z' includes: aStream peek) not])
  		ifTrue: [ self flag: #FIXME.
  				"Different unit tests have conflicting opinions as to whether the
  				current local offset should be used as a default. However, the current
  				local offset cannot be correct due to DST (offset is itself a function
  				of the point in time). Nevertheless, this is a reasonable default considering
  				that the offset would have been explicitly part of the date string if it
  				was a matter of concern. Unit tests will require updates to match this
  				assumption."
  				"offsetSeconds := 0"
  				offsetSeconds := self localOffsetSeconds]
  		ifFalse: [(aStream peekFor: $Z)
  			ifTrue: [offsetSeconds := 0]
+ 			ifFalse: [ | ch offsetString offset |
- 			ifFalse: [
  				ch := aStream next.
  				ch = $+ ifTrue: [ch := Character space].
+ 				offsetString := aStream upToEnd.
+ 				(offsetString atLast: 3 ifAbsent: ['']) = $:
+ 					ifFalse: [offsetString := (offsetString allButLast: 2) , ':' , (offsetString last: 2)].
+ 				offset := Duration fromString: ch asString, '0:', offsetString, ':0'.
- 				offset := Duration fromString: ch asString, '0:', aStream upToEnd, ':0'.
  				offsetSeconds := offset asSeconds]].
  	^ self
  		year: yearMonthDay first
  		month: yearMonthDay second
  		day: yearMonthDay third
  		hour: hourMinuteSecondNano first
  		minute: hourMinuteSecondNano second
  		second: hourMinuteSecondNano third
  		nanoSecond: hourMinuteSecondNano fourth
  		offsetSeconds: offsetSeconds
  
  
  	"	'-1199-01-05T20:33:14.321-05:00' asDateAndTime
  		' 2002-05-16T17:20:45.1+01:01' asDateAndTime
  
  		' 2002-05-16T17:20:45.02+01:01' asDateAndTime
  
  		' 2002-05-16T17:20:45.003+01:01' asDateAndTime
  
  		' 2002-05-16T17:20:45.0004+01:01' asDateAndTime
    		' 2002-05-16T17:20:45.00005' asDateAndTime
  		' 2002-05-16T17:20:45.000006+01:01' asDateAndTime
  
  		' 2002-05-16T17:20:45.0000007+01:01' asDateAndTime
  		' 2002-05-16T17:20:45.00000008-01:01' asDateAndTime   
  		' 2002-05-16T17:20:45.000000009+01:01' asDateAndTime  
  		' 2002-05-16T17:20:45.0000000001+01:01' asDateAndTime  
  
   		' 2002-05-16T17:20' asDateAndTime
  		' 2002-05-16T17:20:45' asDateAndTime
  		' 2002-05-16T17:20:45+01:57' asDateAndTime
   		' 2002-05-16T17:20:45-02:34' asDateAndTime
   		' 2002-05-16T17:20:45+00:00' asDateAndTime
  		' 1997-04-26T01:02:03+01:02:3' asDateAndTime 
+ 		
+ 		' 1970-01-01T00:00:00.000+0000' asDateAndTime
   	"!

Item was removed:
- ----- Method: DateAndTime class>>startUp: (in category 'system startup') -----
- startUp: startingAfresh
- 	"Set local timezone"
- 	startingAfresh
- 		ifTrue: [InitializeFromPrimitive := self canInitializeFromPrimitive.
- 			Time initialize. "set LastClockTick to 0".
- 			self now]!

Item was changed:
  ----- Method: Time class>>posixMicrosecondClockWithOffset (in category 'clock') -----
  posixMicrosecondClockWithOffset
  	"Answer an array with local microseconds since the Posix epoch and the
  	current seconds offset from GMT in the local time zone."
  
  	| array posixUtcValue |
+ 	array := self primPosixMicrosecondClockWithOffset: (Array new: 2).
- 	array := self primPosixMicrosecondClockWithOffset.
  	posixUtcValue := array at: 1.
  	(self updateTimeZoneCacheAt: posixUtcValue) ifTrue: [ "Time zone may have changed: fetch again."
  		self primPosixMicrosecondClockWithOffset: array.
  		posixUtcValue := array at: 1 ].
  	ClockPolicy caseOf: {
  		[#acceptPlatformTime] -> [^ array] .
  		[#monotonicAllowDuplicates] -> [
  			posixUtcValue > LastClockTick
  				ifTrue: [LastClockTick := posixUtcValue]
  				ifFalse: [array at: 1 put: LastClockTick]] .
  		[#monotonicForceMicrosecondIncrement] -> [
  			posixUtcValue > LastClockTick
  				ifTrue: [LastClockTick := posixUtcValue]
  				ifFalse: [LastClockTick := LastClockTick + 1. "add one microsecond"
  					array at: 1 put: LastClockTick]] .
  		[#monotonicForceNanosecondIncrement] -> [
  			posixUtcValue > LastClockTick
  				ifTrue: [LastClockTick := posixUtcValue]
  				ifFalse: [LastClockTick := LastClockTick + (1 / 1000). "add one nanosecond"
  					array at: 1 put: LastClockTick]]
  	} otherwise: [].
  	^array!

Item was removed:
- ----- Method: Time class>>primPosixMicrosecondClockWithOffset (in category 'private') -----
- primPosixMicrosecondClockWithOffset
- 	"Answer an array with UTC microseconds since the Posix epoch and the
- 	current seconds offset from GMT in the local time zone. If the primitive is
- 	not available, then answer the time and offset of Posix epoch GMT. This enables
- 	the image to continue running in the absence of #primitiveUtcWithOffset, thus
- 	avoiding the need to fallback code based on the earlier local microsecond clock
- 	mechanism."
- 
- 	<primitive: 'primitiveUtcWithOffset'>
- 	^{0. 0}!

Item was changed:
+ ----- Method: Time class>>primPosixMicrosecondClockWithOffset: (in category 'clock') -----
- ----- Method: Time class>>primPosixMicrosecondClockWithOffset: (in category 'private') -----
  primPosixMicrosecondClockWithOffset: arrayOrObjectWithTwoSlots
  	"Answer an array with UTC microseconds since the Posix epoch and the
  	current seconds offset from GMT in the local time zone. If the primitive is
  	not available, then answer the time and offset of Posix epoch GMT. This enables
  	the image to continue running in the absence of #primitiveUtcWithOffset, thus
  	avoiding the need to fallback code based on the earlier local microsecond clock
  	mechanism.
  
  	The parameter may be a two element array, or an object whose first two instance
  	variables are expected to be UTC microseconds and seconds offset from GMT."
  
  	<primitive: 'primitiveUtcWithOffset'>
  
  	(arrayOrObjectWithTwoSlots instVarAt: 1)
  		ifNil: [arrayOrObjectWithTwoSlots instVarAt: 1 put: 0].
  	(arrayOrObjectWithTwoSlots instVarAt: 2)
  		ifNil: [arrayOrObjectWithTwoSlots instVarAt: 2 put: 0]!

Item was changed:
+ (PackageInfo named: 'Chronology-Core') postscript: 'Smalltalk removeFromStartUpList: DateAndTime'!
- (PackageInfo named: 'Chronology-Core') postscript: '"Make sure UpdateVMTimeZoneCacheAt of Time is initialized."
- Time classPool at: #UpdateVMTimeZoneCacheAt put: 0.
- "Separated Time''s startup duties from DateAndTime."
- Smalltalk addToStartUpList: Time before: DateAndTime'!



More information about the Squeak-dev mailing list