[Pkg] The Trunk: Chronology-Core-dtl.20.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Jan 4 14:11:08 UTC 2019


David T. Lewis uploaded a new version of Chronology-Core to project The Trunk:
http://source.squeak.org/trunk/Chronology-Core-dtl.20.mcz

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

Name: Chronology-Core-dtl.20
Author: dtl
Time: 1 January 2019, 8:13:58.107101 pm
UUID: 2bffea2b-6a8e-4013-8e86-34347eef905e
Ancestors: Chronology-Core-dtl.19

Bootstrap UTCDateAndTime, step 5 of 5

Update to latest level of Chronology-Core.
See http://www.squeaksource.com/UTCDateAndTime for the original development history, which is a series of update versions beginning with Chronology-Core-cmm.2 and ending with this version.

DateAndTime is now implemented wtih instance 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 uses #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.

=============== Diff against Chronology-Core-dtl.19 ===============

Item was removed:
- ----- Method: DateAndTime>>asLXDateAndTime (in category 'LX-Kernel-Chronology') -----
- asLXDateAndTime
- 
- 	^LXDateAndTime
- 		year: self year
- 		month: self month
- 		day: self dayOfMonth
- 		hour: self hour
- 		minute: self minute
- 		second: self second
- 		nanoSecond: self nanoSecond
- 		offset: self offset!

Item was removed:
- Magnitude subclass: #LXDateAndTime
- 	instanceVariableNames: 'utcMicroseconds localOffsetSeconds'
- 	classVariableNames: 'AutomaticTimezone ClockProvider InitializeFromPrimitive LocalTimeZone PosixEpochJulianDays'
- 	poolDictionaries: 'ChronologyConstants'
- 	category: 'Chronology-Core'!
- 
- !LXDateAndTime 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: LXDateAndTime class>>automaticTimezone (in category 'preferences') -----
- automaticTimezone
- 	"Accessor for the system-wide preference"
- 	
- 	<preference: 'Automatically set local timezone'
- 		category: 'general'
- 		description: 'If enabled, the timezone will automatically be kept in sync with the system''s time (daylight savings changes etc.)'
- 		type: #Boolean>
- 	^AutomaticTimezone ifNil: [ true ]!

Item was removed:
- ----- Method: LXDateAndTime class>>automaticTimezone: (in category 'preferences') -----
- automaticTimezone: aBoolean
- 	"Accessor for the system-wide preference.
- 	Note this gets disabled in localTimeZone: to make that override stick"
- 	
- 	AutomaticTimezone := aBoolean.
- 	aBoolean ifTrue: [self now].		"fetch timezone immediately"!

Item was removed:
- ----- Method: LXDateAndTime 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 removed:
- ----- Method: LXDateAndTime class>>clock (in category 'clock provider') -----
- clock 
- 	 "the provider of real time seconds/milliseconds."
- 
- 	^ ClockProvider !

Item was removed:
- ----- Method: LXDateAndTime class>>clockPrecision (in category 'ansi protocol') -----
- clockPrecision
- 	"One nanosecond precision"
- 
- 	^ Duration seconds: 0 nanoSeconds: 1
- !

Item was removed:
- ----- Method: LXDateAndTime class>>current (in category 'squeak protocol') -----
- current
- 
- 
- 	^ self now!

Item was removed:
- ----- Method: LXDateAndTime class>>date:time: (in category 'squeak protocol') -----
- date: aDate time: aTime
- 
- 	^ self 
- 		year: aDate year
- 		month: aDate monthIndex
- 		day: aDate dayOfMonth 
- 		hour: aTime hour 
- 		minute: aTime minute
- 		second: aTime second
- 		nanoSecond: aTime nanoSecond
- 		offset: aDate start offset!

Item was removed:
- ----- Method: LXDateAndTime class>>daysFromSmalltalkEpochToPosixEpoch (in category 'private') -----
- daysFromSmalltalkEpochToPosixEpoch
- 
- 	^52 * 365 + (17 * 366)!

Item was removed:
- ----- Method: LXDateAndTime class>>epoch (in category 'squeak protocol') -----
- epoch
- 	"Answer a DateAndTime representing the Squeak epoch: 1 January 1901"
- 
- 	^ self utcMicroseconds: self epochOffsetMicros negated offset: 0
- !

Item was removed:
- ----- Method: LXDateAndTime class>>epochOffset (in category 'private') -----
- epochOffset
- 	"Elaspsed seconds from the Smalltalk epoch to the Posix epoch"
- 	^self daysFromSmalltalkEpochToPosixEpoch * SecondsInDay!

Item was removed:
- ----- Method: LXDateAndTime class>>epochOffsetMicros (in category 'private') -----
- epochOffsetMicros
- 	"Elaspsed microseconds from the Smalltalk epoch to the Posix epoch"
- 	^self epochOffset * 1000000!

Item was removed:
- ----- Method: LXDateAndTime class>>fromSeconds: (in category 'smalltalk-80') -----
- fromSeconds: seconds 
- 	"Answer a DateAndTime since the Squeak epoch: 1 January 1901
- 
- 	Squeak traditionally used seconds since the Smalltalk epoch in local time,
- 	which is undefinable. The error was probably caused by some early VM design
- 	choices that have since been corrected. Assume now that the Smalltalk epoch
- 	is defined relative to GMT, and that it may be treated similarly to the Posix
- 	epoch except for a constant offset value.
- 
- 	This implementation differs from earlier Squeak in that it uses seconds relative
- 	to the Smalltalk epoch (not local time), and represents seconds as an arbitrary
- 	precision number rather than an integer."
- 
- 	| s uSec offset |
- 	offset := self localOffsetSeconds.
- 	s := seconds - self epochOffset.
- 	uSec := s * 1000000.
- 	^ self utcMicroseconds: uSec offset: offset
- !

Item was removed:
- ----- Method: LXDateAndTime class>>fromString: (in category 'squeak protocol') -----
- fromString: aString
- 
- 
- 	^ self readFrom: (ReadStream on: aString)!

Item was removed:
- ----- Method: LXDateAndTime class>>fromUnixTime: (in category 'squeak protocol') -----
- fromUnixTime: utcSeconds
- 
- 	^self utcSeconds: utcSeconds offset: 0
- !

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

Item was removed:
- ----- Method: LXDateAndTime class>>julianDayNumber: (in category 'squeak protocol') -----
- julianDayNumber: anInteger 
- 	^ self
- 		julianDayNumber: anInteger
- 		offset: self localOffset!

Item was removed:
- ----- Method: LXDateAndTime class>>julianDayNumber:offset: (in category 'squeak protocol') -----
- julianDayNumber: anInteger offset: aDuration 
- 
- 	^self basicNew
- 		setJdn: anInteger
- 		seconds: 0
- 		nano: 0
- 		offset: aDuration!

Item was removed:
- ----- Method: LXDateAndTime class>>localOffset (in category 'squeak protocol') -----
- localOffset
- 	"Answer the duration we are offset from UTC"
- 
- 	^ Duration seconds: self localOffsetSeconds
- !

Item was removed:
- ----- Method: LXDateAndTime class>>localOffset: (in category 'squeak protocol') -----
- localOffset: aDuration
- 	"Override the local time zone (for testing). This disables the #automaticTimezone: preference"
- 	self localTimeZone: (TimeZone offset: aDuration name: 'Local Time (override)' abbreviation: 'LTO').
- !

Item was removed:
- ----- Method: LXDateAndTime class>>localOffsetSeconds (in category 'private') -----
- localOffsetSeconds
- 
- 	self automaticTimezone
- 		ifTrue: [ ^Time posixMicrosecondClockWithOffset second ]
- 		ifFalse: [ ^self localTimeZone offset asSeconds ]!

Item was removed:
- ----- Method: LXDateAndTime class>>localTimeZone (in category 'accessing') -----
- localTimeZone
- 	"Answer the local time zone"
- 
- 	^ LocalTimeZone ifNil: [ LocalTimeZone := TimeZone default ]
- 
- !

Item was removed:
- ----- Method: LXDateAndTime class>>localTimeZone: (in category 'accessing') -----
- localTimeZone: aTimeZone
- 	"Set the local time zone"
- 	"
- 	DateAndTime localTimeZone: (TimeZone offset:  0 hours name: 'Universal Time' abbreviation: 'UTC').
- 	DateAndTime localTimeZone: (TimeZone offset: -8 hours name: 'Pacific Standard Time' abbreviation: 'PST').
- 	"
- 	LocalTimeZone := aTimeZone.
- 	self automaticTimezone: (aTimeZone abbreviation = 'LT')!

Item was removed:
- ----- Method: LXDateAndTime class>>midnight (in category 'squeak protocol') -----
- midnight
- 
- 	^ self now midnight!

Item was removed:
- ----- Method: LXDateAndTime class>>milliSecondsSinceMidnight (in category 'squeak protocol') -----
- milliSecondsSinceMidnight
- 	^Time milliSecondsSinceMidnight!

Item was removed:
- ----- Method: LXDateAndTime class>>millisecondClockValue (in category 'smalltalk-80') -----
- millisecondClockValue
- 
- 	^ self clock millisecondClockValue!

Item was removed:
- ----- Method: LXDateAndTime class>>new (in category 'squeak protocol') -----
- new
- 	"Answer a DateAndTime representing the Squeak epoch: 1 January 1901"
- 
- 	^ self utcMicroseconds: self epochOffsetMicros negated offset: 0
- 
- !

Item was removed:
- ----- Method: LXDateAndTime class>>noon (in category 'squeak protocol') -----
- noon
- 
- 	^ self now noon
- !

Item was removed:
- ----- Method: LXDateAndTime 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: [ InitializeFromPrimitive
- 			ifTrue: [ ^ self basicNew initializeFromPrimitive ]
- 			ifFalse: [ | timeArray |
- 				timeArray := Time posixMicrosecondClockWithOffset.
- 				^ self utcMicroseconds: timeArray first offset: timeArray second ] ]
- 		ifFalse: [ | timeArray |
- 			timeArray := Time posixMicrosecondClockWithOffset.
- 			^ self utcMicroseconds: timeArray first offset: self localOffsetSeconds ]
- !

Item was removed:
- ----- Method: LXDateAndTime class>>nowAtOffset: (in category 'squeak protocol') -----
- nowAtOffset: offsetDuration
- 	"Answers the local time at places with the specified offsetDuration timezone."
- 	"local time Chicago (CST)"
- 	"DateAndTime nowAtOffset: -6 hours"
- 
- 	^ self utcMicroseconds: Time posixMicrosecondClockWithOffset first offset: offsetDuration asSeconds
- !

Item was removed:
- ----- Method: LXDateAndTime class>>nowWithOffset: (in category 'squeak protocol') -----
- nowWithOffset: aDuration
- 	"Answer time now as reported by #primitiveUtcWithOffset. If the primitive is not
- 	available, answer the Posix epoch with time zone offset aDuration."
- 
- 	| timeArray |
- 	timeArray := Time posixMicrosecondClockWithOffset.
- 	^ self utcMicroseconds: timeArray first offset: aDuration asSeconds
- !

Item was removed:
- ----- Method: LXDateAndTime class>>readFrom: (in category 'squeak protocol') -----
- readFrom: aStream
- 
- 	| 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 := aStream next.
- 				ch = $+ ifTrue: [ch := Character space].
- 				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 
-  	"!

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

Item was removed:
- ----- Method: LXDateAndTime class>>today (in category 'squeak protocol') -----
- today
- 
- 	^ self midnight!

Item was removed:
- ----- Method: LXDateAndTime class>>tomorrow (in category 'squeak protocol') -----
- tomorrow
- 
- 	^ self today asDate next asLXDateAndTime
- !

Item was removed:
- ----- Method: LXDateAndTime class>>totalSeconds (in category 'smalltalk-80') -----
- totalSeconds
- 
- 	^ self clock totalSeconds!

Item was removed:
- ----- Method: LXDateAndTime class>>unixEpoch (in category 'squeak protocol') -----
- unixEpoch
- 	"Answer a DateAndTime representing the Unix epoch (1 January 1970, midnight UTC)"
- 
- 	^ self basicNew
- 		ticks: #(2440588 0 0) offset: Duration zero;
- 		yourself.
- !

Item was removed:
- ----- Method: LXDateAndTime class>>utcMicroseconds:offset: (in category 'instance creation') -----
- utcMicroseconds: microsecondsSincePosixEpoch offset: secondsFromGMT
- 
- 	^super new
- 		utcMicroseconds: microsecondsSincePosixEpoch
- 		offset: secondsFromGMT!

Item was removed:
- ----- Method: LXDateAndTime class>>utcMicrosecondsForYear:month:day:hour:minute:second:nanoSecond:offsetSeconds: (in category 'private') -----
- utcMicrosecondsForYear: year month: month day: day hour: hour minute: minute second: second nanoSecond: nanoCount  offsetSeconds: offsetSeconds
- 
- 	| monthIndex daysInMonth p q r s julianDayNumber posixDays seconds utcSeconds |
- 
- 	monthIndex := month isInteger ifTrue: [month] ifFalse: [Month indexOfMonth: month].
- 	daysInMonth := Month
- 		daysInMonth: monthIndex
- 		forYear: year.
- 	day < 1 ifTrue: [self error: 'day may not be zero or negative'].
- 	day > daysInMonth ifTrue: [self error: 'day is after month ends']. 	
- 	
- 	p := (monthIndex - 14) quo: 12.
- 	q := year + 4800 + p.
- 	r := monthIndex - 2 - (12 * p).
- 	s := (year + 4900 + p) quo: 100.
- 
- 	julianDayNumber :=
-  		( (1461 * q) quo: 4 ) +
- 			( (367 * r) quo: 12 ) -
-  				( (3 * s) quo: 4 ) +
-  					( day - 32075 ).
- 
- 	posixDays := julianDayNumber - PosixEpochJulianDays.
- 	seconds := hour * 60 + minute * 60 + second - offsetSeconds.
- 	utcSeconds := seconds + (posixDays * 24 * 3600).
- 	^ utcSeconds * 1000000 + (nanoCount / 1000)
- !

Item was removed:
- ----- Method: LXDateAndTime class>>utcSeconds:offset: (in category 'instance creation') -----
- utcSeconds: secondsSincePosixEpoch offset: secondsFromGMT
- 
- 	^self
- 		utcMicroseconds: secondsSincePosixEpoch * 1000000
- 		offset: secondsFromGMT!

Item was removed:
- ----- Method: LXDateAndTime class>>year:day: (in category 'squeak protocol') -----
- year: year day: dayOfYear
- 	"Return a DateAndTime"
- 
- 	^ self
- 		year: year
- 		day: dayOfYear
- 		hour: 0
- 		minute: 0
- 		second: 0
- !

Item was removed:
- ----- Method: LXDateAndTime class>>year:day:hour:minute:second: (in category 'ansi protocol') -----
- year: year day: dayOfYear hour: hour minute: minute second: second
- 
- 	^ self
- 		year: year
- 		day: dayOfYear
- 		hour: hour
- 		minute: minute
- 		second: second
- 		offset: self localOffset
- !

Item was removed:
- ----- Method: LXDateAndTime class>>year:day:hour:minute:second:offset: (in category 'ansi protocol') -----
- year: year day: dayOfYear hour: hour minute: minute second: second offset: offset 
- 	"Return a DataAndTime"
- 
- 	| y d |
- 	y := self
- 		year: year
- 		month: 1
- 		day: 1
- 		hour: hour
- 		minute: minute
- 		second: second
- 		nanoSecond: 0
- 		offset: offset.
- 
- 	d := Duration days: (dayOfYear - 1).
- 
- 	^ y + d
- !

Item was removed:
- ----- Method: LXDateAndTime class>>year:month:day: (in category 'squeak protocol') -----
- year: year month: month day: day
- 	"Return a DateAndTime, midnight local time"
- 	
- 	^self
-  		year: year
-  		month: month
-  		day: day
-  		hour: 0
- 		minute: 0
- !

Item was removed:
- ----- Method: LXDateAndTime class>>year:month:day:hour:minute: (in category 'squeak protocol') -----
- year: year month: month day: day hour: hour minute: minute
- 	"Return a DateAndTime"
- 
- 	^self
-  		year: year
-  		month: month
-  		day: day
-  		hour: hour
- 		minute: minute
- 		second: 0
- !

Item was removed:
- ----- Method: LXDateAndTime class>>year:month:day:hour:minute:second: (in category 'ansi protocol') -----
- year: year month: month day: day hour: hour minute: minute second: second
- 	"Return a DateAndTime"
- 
- 	^ self
- 		year: year
- 		month: month
- 		day: day
- 		hour: hour
- 		minute: minute
- 		second: second
- 		offset: self localOffset!

Item was removed:
- ----- Method: LXDateAndTime class>>year:month:day:hour:minute:second:nanoSecond:offset: (in category 'squeak protocol') -----
- year: year month: month day: day hour: hour minute: minute second: second nanoSecond: nanoCount offset: offset
- 	"Return a DateAndTime"
- 
- 	| offsetSeconds utcMicros |
- 	offsetSeconds := offset asSeconds.
- 	utcMicros := self
- 				utcMicrosecondsForYear: year
- 				month: month
- 				day: day
- 				hour: hour
- 				minute: minute
- 				second: second
- 				nanoSecond: nanoCount
- 				offsetSeconds: offsetSeconds.
- 	^ self utcMicroseconds: utcMicros offset: offsetSeconds!

Item was removed:
- ----- Method: LXDateAndTime class>>year:month:day:hour:minute:second:nanoSecond:offsetSeconds: (in category 'squeak protocol') -----
- year: year month: month day: day hour: hour minute: minute second: second nanoSecond: nanoCount offsetSeconds: offsetSeconds
- 	"Return a DateAndTime"
- 
- 	| utcMicros |
- 	utcMicros := self
- 				utcMicrosecondsForYear: year
- 				month: month
- 				day: day
- 				hour: hour
- 				minute: minute
- 				second: second
- 				nanoSecond: nanoCount
- 				offsetSeconds: offsetSeconds.
- 	^ self utcMicroseconds: utcMicros offset: offsetSeconds!

Item was removed:
- ----- Method: LXDateAndTime class>>year:month:day:hour:minute:second:offset: (in category 'ansi protocol') -----
- year: year month: month day: day hour: hour minute: minute second: second offset: offset
- 
- 	^ self
- 		year: year
- 		month: month
- 		day: day
- 		hour: hour
- 		minute: minute
- 		second: second
- 		nanoSecond: 0
- 		offset: offset!

Item was removed:
- ----- Method: LXDateAndTime class>>yesterday (in category 'squeak protocol') -----
- yesterday
- 
- 	^ self today asDate previous asLXDateAndTime!

Item was removed:
- ----- Method: LXDateAndTime>>+ (in category 'ansi protocol') -----
- + operand
- 	"operand conforms to protocol Duration"
- 
- 	^ self class
- 		utcMicroseconds: operand asDuration asNanoSeconds / 1000 + utcMicroseconds
- 		offset: localOffsetSeconds
- !

Item was removed:
- ----- Method: LXDateAndTime>>- (in category 'ansi protocol') -----
- - operand
- 	"operand conforms to protocol DateAndTime or protocol Duration"
- 
- 	^ (operand respondsTo: #asLXDateAndTime)
- 		ifTrue: 
- 			[ | micros |
- 			micros := utcMicroseconds - operand asLXDateAndTime utcMicroseconds.
- 			Duration seconds: micros // 1000000 nanoSeconds: micros \\ 1000000 * 1000]
- 		ifFalse:
- 			[ self + (operand negated) ]
- !

Item was removed:
- ----- Method: LXDateAndTime>>< (in category 'ansi protocol') -----
- < comparand
- 	"comparand conforms to protocol DateAndTime,
- 	or can be converted into something that conforms."
- 
- 	^utcMicroseconds < comparand asLXDateAndTime utcMicroseconds
- !

Item was removed:
- ----- Method: LXDateAndTime>>= (in category 'ansi protocol') -----
- = aDateAndTimeOrTimeStamp
- 	"Equal if the absolute time values match, regardless of local time transform"
- 	self == aDateAndTimeOrTimeStamp ifTrue: [ ^ true ].
- 	^aDateAndTimeOrTimeStamp species == DateAndTime
- 		and: [ utcMicroseconds = aDateAndTimeOrTimeStamp asLXDateAndTime utcMicroseconds ]!

Item was removed:
- ----- Method: LXDateAndTime>>asChronologySeconds (in category 'converting') -----
- asChronologySeconds
- 	"What #asSeconds answers in prior Chronology-format images."
- 	^ self asSeconds + self offset asSeconds!

Item was removed:
- ----- Method: LXDateAndTime>>asDate (in category 'squeak protocol') -----
- asDate
- 
- 
- 	^ Date starting: self asLXDateAndTime!

Item was removed:
- ----- Method: LXDateAndTime>>asDateAndTime (in category 'squeak protocol') -----
- asDateAndTime
- 	^ DateAndTime
- 		year: self year
- 		month: self month
- 		day: self dayOfMonth
- 		hour: self hour
- 		minute: self minute
- 		second: self second
- 		nanoSecond: self nanoSecond
- 		offset: self offset!

Item was removed:
- ----- Method: LXDateAndTime>>asDuration (in category 'squeak protocol') -----
- asDuration
- 	"Answer the duration since midnight."
- 
- 	^ Duration seconds: self getSeconds nanoSeconds: self nanoSecond
- !

Item was removed:
- ----- Method: LXDateAndTime>>asExactSeconds (in category 'smalltalk-80') -----
- asExactSeconds
- 	"Return the duration in seconds since the Squeak epoch"
- 
- 	"Squeak traditionally used seconds since the Smalltalk epoch in local time,
- 	which is undefinable. The error was probably caused by some early VM design
- 	choices that have since been corrected. Assume now that the Smalltalk epoch
- 	is defined relative to GMT, and that it may be treated similarly to the Posix
- 	epoch except for a constant offset value.
- 
- 	This implementation differs from earlier Squeak in that it uses seconds relative
- 	to the Smalltalk epoch (not local time), and represents seconds as an arbitrary
- 	precision number rather than an integer."
- 
- 	^ utcMicroseconds / 1000000 + self class epochOffset
- !

Item was removed:
- ----- Method: LXDateAndTime>>asLXDateAndTime (in category 'squeak protocol') -----
- asLXDateAndTime
- 
- 	^ self!

Item was removed:
- ----- Method: LXDateAndTime>>asLXTimeStamp (in category 'transitional - temporary') -----
- asLXTimeStamp
- 
- 	^ self as: LXTimeStamp!

Item was removed:
- ----- Method: LXDateAndTime>>asLocal (in category 'ansi protocol') -----
- asLocal
- 	
- 
- 	^ (self offset = self class localOffset)
- 
- 		ifTrue: [self]
- 		ifFalse: [self utcOffset: self class localOffset]!

Item was removed:
- ----- Method: LXDateAndTime>>asMonth (in category 'squeak protocol') -----
- asMonth
- 
- 	^ Month starting: self!

Item was removed:
- ----- Method: LXDateAndTime>>asNanoSeconds (in category 'squeak protocol') -----
- asNanoSeconds
- 	"Answer the number of nanoseconds since midnight"
- 
- 	^ self asDuration asNanoSeconds!

Item was removed:
- ----- Method: LXDateAndTime>>asPosixSeconds (in category 'converting') -----
- asPosixSeconds
- 
- 	^utcMicroseconds / 1000000
- !

Item was removed:
- ----- Method: LXDateAndTime>>asSeconds (in category 'smalltalk-80') -----
- asSeconds
- 	"Return the number of seconds since the Squeak epoch. See asExactSeconds
- 	to retain full precision of the duration in seconds."
- 
- 	"Squeak traditionally used seconds since the Smalltalk epoch in local time,
- 	which is undefinable. The error was probably caused by some early VM design
- 	choices that have since been corrected. Assume now that the Smalltalk epoch
- 	is defined relative to GMT, and that it may be treated similarly to the Posix
- 	epoch except for a constant offset value.
- 
- 	This implementation differs from earlier Squeak in that it uses seconds relative
- 	to the Smalltalk epoch (not local time), and represents seconds as an arbitrary
- 	precision number rather than an integer."
- 
- 	^ utcMicroseconds // 1000000 + self class epochOffset
- !

Item was removed:
- ----- Method: LXDateAndTime>>asTime (in category 'squeak protocol') -----
- asTime
- 
- 
- 	^ Time seconds: self getSeconds nanoSeconds: self nanoSecond
- !

Item was removed:
- ----- Method: LXDateAndTime>>asTimeStamp (in category 'squeak protocol') -----
- asTimeStamp
- 
- 	^ self asLXTimeStamp
- !

Item was removed:
- ----- Method: LXDateAndTime>>asUTC (in category 'ansi protocol') -----
- asUTC
- 
- 	localOffsetSeconds = 0 ifTrue: [ ^self ].
- 	^self copy
- 		utcMicroseconds: utcMicroseconds
- 		offset: 0
- !

Item was removed:
- ----- Method: LXDateAndTime>>asUnixTime (in category 'squeak protocol') -----
- asUnixTime
- 	"answer number of seconds since unix epoch (midnight Jan 1, 1970, UTC)"
- 
- 	^(self - self class unixEpoch) asSeconds!

Item was removed:
- ----- Method: LXDateAndTime>>asWeek (in category 'squeak protocol') -----
- asWeek
- 
- 	^ Week starting: self!

Item was removed:
- ----- Method: LXDateAndTime>>asYear (in category 'squeak protocol') -----
- asYear
- 
- 	^ Year starting: self!

Item was removed:
- ----- Method: LXDateAndTime>>day (in category 'smalltalk-80') -----
- day
- 
- 	^ self dayOfYear
- !

Item was removed:
- ----- Method: LXDateAndTime>>dayMonthYearDo: (in category 'squeak protocol') -----
- dayMonthYearDo: aBlock
- 	"Evaluation the block with three arguments: day month, year."
- 
- 	| l n i j dd mm yyyy |
- 	l := self julianDayNumber + 68569.
- 	n := 4 * l // 146097.
- 	l := l - (146097 * n + 3 // 4).
- 	i := 4000 * (l + 1) // 1461001.
- 	l := l - (1461 * i // 4) + 31.
- 	j := 80 * l // 2447.
- 	dd := l - (2447 * j // 80).
- 	l := j // 11.
- 	mm := j + 2 - (12 * l).
- 	yyyy := 100 * (n - 49) + i + l.
- 
- 	^ aBlock
- 		value: dd
- 		value: mm
- 		value: yyyy!

Item was removed:
- ----- Method: LXDateAndTime>>dayOfMonth (in category 'ansi protocol') -----
- dayOfMonth
- 	"Answer which day of the month is represented by the receiver."
- 
- 	^ self
- 		dayMonthYearDo: [ :d :m :y | d ]
- !

Item was removed:
- ----- Method: LXDateAndTime>>dayOfWeek (in category 'ansi protocol') -----
- dayOfWeek
- 
- 	"Sunday=1, ... , Saturday=7"
- 
- 	^ (self julianDayNumber + 1 rem: 7) + 1
- !

Item was removed:
- ----- Method: LXDateAndTime>>dayOfWeekAbbreviation (in category 'ansi protocol') -----
- dayOfWeekAbbreviation
- 
- 	^ self dayOfWeekName copyFrom: 1 to: 3
- !

Item was removed:
- ----- Method: LXDateAndTime>>dayOfWeekName (in category 'ansi protocol') -----
- dayOfWeekName
- 
- 	^ Week nameOfDay: self dayOfWeek!

Item was removed:
- ----- Method: LXDateAndTime>>dayOfYear (in category 'ansi protocol') -----
- dayOfYear
- 	"This code was contributed by Dan Ingalls. It is equivalent to the terser
- 		^ jdn - (Year year: self year) start julianDayNumber + 1 but much quicker."
- 
- 	^ self dayMonthYearDo:
- 		[ :d :m :y |
- 			| monthStart |
- 			monthStart := #(1 32 60 91 121 152 182 213 244 274 305 335) at: m.
- 			(m > 2 and: [ Year isLeapYear: y ])
- 				ifTrue: [ monthStart + d ]
- 				ifFalse: [ monthStart + d - 1 ]]!

Item was removed:
- ----- Method: LXDateAndTime>>daysInMonth (in category 'smalltalk-80') -----
- daysInMonth
- 	"Answer the number of days in the month represented by the receiver."
- 
- 
- 	^ self asMonth daysInMonth!

Item was removed:
- ----- Method: LXDateAndTime>>daysInYear (in category 'smalltalk-80') -----
- daysInYear
- 
- 	"Answer the number of days in the year represented by the receiver."
- 
- 	^ self asYear daysInYear!

Item was removed:
- ----- Method: LXDateAndTime>>daysLeftInYear (in category 'smalltalk-80') -----
- daysLeftInYear
- 	"Answer the number of days in the year after the date of the receiver."
- 
- 	^ self daysInYear - self dayOfYear!

Item was removed:
- ----- Method: LXDateAndTime>>duration (in category 'squeak protocol') -----
- duration
- 
- 	^ Duration zero!

Item was removed:
- ----- Method: LXDateAndTime>>firstDayOfMonth (in category 'smalltalk-80') -----
- firstDayOfMonth
- 
- 	^ self asMonth start day
- !

Item was removed:
- ----- Method: LXDateAndTime>>floor (in category 'squeak protocol') -----
- floor
- 	"Answer a copy with magnitude rounded down to the nearest whole second"
- 	^self class
- 		utcMicroseconds: utcMicroseconds - (utcMicroseconds \\ 1000000)
- 		offset: localOffsetSeconds!

Item was removed:
- ----- Method: LXDateAndTime>>getSeconds (in category 'accessing') -----
- getSeconds
- 
- 	| posixDays posixSeconds localSeconds |
- 	posixSeconds := utcMicroseconds // 1000000.
- 	localSeconds := posixSeconds + localOffsetSeconds.
- 	localSeconds < 0 ifTrue: [localSeconds := localSeconds \\ SecondsInDay]. "normalize"
- 	posixDays := localSeconds // SecondsInDay.
- 	^localSeconds - (posixDays * SecondsInDay).
- !

Item was removed:
- ----- Method: LXDateAndTime>>hasEqualTicks: (in category 'private') -----
- hasEqualTicks: aDateAndTime
- 	
- 	^ (self julianDayNumber = aDateAndTime julianDayNumber)
- 		and: [ (self secondsSinceMidnight = aDateAndTime secondsSinceMidnight)
- 			and: [ self nanoSecond = aDateAndTime nanoSecond ] ]
- !

Item was removed:
- ----- Method: LXDateAndTime>>hash (in category 'ansi protocol') -----
- hash
- 	^utcMicroseconds hash!

Item was removed:
- ----- Method: LXDateAndTime>>hour (in category 'ansi protocol') -----
- hour
- 
- 	^ self hour24!

Item was removed:
- ----- Method: LXDateAndTime>>hour12 (in category 'ansi protocol') -----
- hour12
- 	"Answer an <integer> between 1 and 12, inclusive, representing the hour 
- 	of the day in the 12-hour clock of the local time of the receiver."
- 	^ self hour24 - 1 \\ 12 + 1
- !

Item was removed:
- ----- Method: LXDateAndTime>>hour24 (in category 'ansi protocol') -----
- hour24
- 
- 	^self getSeconds // 3600!

Item was removed:
- ----- Method: LXDateAndTime>>hours (in category 'smalltalk-80') -----
- hours
- 
- 	^ self hour
- !

Item was removed:
- ----- Method: LXDateAndTime>>initializeFromPrimitive (in category 'initialize-release') -----
- initializeFromPrimitive
- 
- 	Time posixMicrosecondClockWithOffset: self!

Item was removed:
- ----- Method: LXDateAndTime>>isLeapYear (in category 'ansi protocol') -----
- isLeapYear
- 
- 
- 	^ Year isLeapYear: self year
- !

Item was removed:
- ----- Method: LXDateAndTime>>julianDayNumber (in category 'squeak protocol') -----
- julianDayNumber
- 
- 	| posixDays posixSeconds localSeconds negativeDays |
- 	posixSeconds := utcMicroseconds // 1000000.
- 	localSeconds := posixSeconds + localOffsetSeconds.
- 	negativeDays := 0.
- 	localSeconds < 0 ifTrue: [ "normalize"
- 			negativeDays := localSeconds // SecondsInDay.
- 			localSeconds := negativeDays * SecondsInDay + localSeconds].
- 	posixDays := localSeconds // SecondsInDay.
- 	^posixDays + PosixEpochJulianDays - negativeDays.
- !

Item was removed:
- ----- Method: LXDateAndTime>>localOffsetSeconds: (in category 'initialize-release') -----
- localOffsetSeconds: seconds
- 	"Private. Allow value to be modified during initialization in order to support local
- 	timezone preference."
- 
- 	localOffsetSeconds := seconds
- !

Item was removed:
- ----- Method: LXDateAndTime>>makeUTC (in category 'squeak protocol') -----
- makeUTC
- 	"Make the receiver's timezone UTC."
- 	localOffsetSeconds := 0!

Item was removed:
- ----- Method: LXDateAndTime>>meridianAbbreviation (in category 'ansi protocol') -----
- meridianAbbreviation
- 
- 	^ self asTime meridianAbbreviation
- !

Item was removed:
- ----- Method: LXDateAndTime>>microsecondsFromDay:seconds:nanos:offset: (in category 'private') -----
- microsecondsFromDay: jdn seconds: s nanos: n offset: localOffsetSeconds
- 
- 	| days totalSeconds micros |
- 	days := jdn - PosixEpochJulianDays.
- 	totalSeconds := days * 86400 + s - localOffsetSeconds. "n.g. const 86400 is faster than SecondsInDay"
- 	micros := totalSeconds * 1000000.
- 	^micros + (n / 1000)
- !

Item was removed:
- ----- Method: LXDateAndTime>>middleOf: (in category 'squeak protocol') -----
- middleOf: aDuration
- 	"Return a Timespan where the receiver is the middle of the Duration"
- 
- 	| duration |
- 	duration := aDuration asDuration.
- 
- 	^ Timespan starting: (self - (duration / 2)) duration: duration
- !

Item was removed:
- ----- Method: LXDateAndTime>>midnight (in category 'squeak protocol') -----
- midnight
- 	"Answer a DateAndTime starting at midnight of the same timezone offset as the receiver."
- 	^ self class basicNew
- 		setJdn: self julianDayNumber
- 		seconds: localOffsetSeconds
- 		nano: 0
- 		localOffsetSeconds: localOffsetSeconds.!

Item was removed:
- ----- Method: LXDateAndTime>>minute (in category 'ansi protocol') -----
- minute
- 
- 	^self getSeconds // 60 \\ 60!

Item was removed:
- ----- Method: LXDateAndTime>>minutes (in category 'smalltalk-80') -----
- minutes
- 
- 	^ self minute
- !

Item was removed:
- ----- Method: LXDateAndTime>>month (in category 'ansi protocol') -----
- month
- 
- 	^ self 
- 		dayMonthYearDo: [ :d :m :y | m ]
- !

Item was removed:
- ----- Method: LXDateAndTime>>monthAbbreviation (in category 'ansi protocol') -----
- monthAbbreviation
- 
- 
- 	^ self monthName copyFrom: 1 to: 3!

Item was removed:
- ----- Method: LXDateAndTime>>monthIndex (in category 'smalltalk-80') -----
- monthIndex
- 
- 
- 	^ self month!

Item was removed:
- ----- Method: LXDateAndTime>>monthName (in category 'ansi protocol') -----
- monthName
- 
- 
- 	^ Month nameOfMonth: self month!

Item was removed:
- ----- Method: LXDateAndTime>>nanoSecond (in category 'squeak protocol') -----
- nanoSecond
- 
- 	^utcMicroseconds \\ 1000000 * 1000
- !

Item was removed:
- ----- Method: LXDateAndTime>>noTimezone (in category 'private') -----
- noTimezone
- 	^ false!

Item was removed:
- ----- Method: LXDateAndTime>>noon (in category 'squeak protocol') -----
- noon
- 	"Answer a DateAndTime starting at noon"
- 
- 	^ self dayMonthYearDo: 
- 		[ :d :m :y | self class year: y month: m day: d hour: 12 minute: 0 second: 0 ]
- !

Item was removed:
- ----- Method: LXDateAndTime>>normalize:ticks:base: (in category 'private') -----
- normalize: i ticks: ticks base: base
- 
- 	| tick div quo rem |
- 	tick := ticks at: i.
- 	div := tick asInteger digitDiv: base neg: tick negative.
- 	quo := (div at: 1) normalize.
- 	rem := (div at: 2) normalize.
- 	rem < 0 ifTrue: [ quo := quo - 1. rem := base + rem ].
- 	ticks at: (i-1) put: ((ticks at: i-1) + quo).
- 	ticks at: i put: rem
- !

Item was removed:
- ----- Method: LXDateAndTime>>offset (in category 'ansi protocol') -----
- offset
- 
- 	^ Duration seconds: localOffsetSeconds!

Item was removed:
- ----- Method: LXDateAndTime>>offset: (in category 'ansi protocol') -----
- offset: anOffset
- 
- 	"Answer a <DateAndTime> equivalent to the receiver but with its local time 
- 	being offset from UTC by offset."
- 
- 	| newOffset newMicros |
- 	self flag: #FIXME. "check the definition of this and of #utcOffset:"
- 	newOffset := anOffset asDuration asSeconds.
- 	newMicros := localOffsetSeconds - newOffset * 1000000 + utcMicroseconds.
- 	^ self class utcMicroseconds: newMicros offset: newOffset
- !

Item was removed:
- ----- Method: LXDateAndTime>>offsetSeconds (in category 'accessing') -----
- offsetSeconds
- 
- 	^localOffsetSeconds!

Item was removed:
- ----- Method: LXDateAndTime>>posixEpochJulianDays (in category 'initialize-release') -----
- posixEpochJulianDays
- 
- 	^self class daysFromSmalltalkEpochToPosixEpoch + SqueakEpoch!

Item was removed:
- ----- Method: LXDateAndTime>>printHMSOn: (in category 'squeak protocol') -----
- printHMSOn: aStream
- 	"Print just hh:mm:ss"
- 	
- 	| seconds |
- 	seconds := self getSeconds.
- 	seconds // 3600 printOn: aStream base: 10 length: 2 padded: true.
- 	aStream nextPut: $:.
- 	seconds \\ 3600 // 60 printOn: aStream base: 10 length: 2 padded: true.
- 	aStream nextPut: $:.
- 	seconds \\ 60 printOn: aStream base: 10 length: 2 padded: true!

Item was removed:
- ----- Method: LXDateAndTime>>printOn: (in category 'squeak protocol') -----
- printOn: aStream
- 	"Print as per ISO 8601 sections 5.3.3 and 5.4.1.
- 	Prints either:
- 		'YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for positive years) or '-YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for negative years)"
- 
- 	^self printOn: aStream withLeadingSpace: false
- !

Item was removed:
- ----- Method: LXDateAndTime>>printOn:withLeadingSpace: (in category 'squeak protocol') -----
- printOn: aStream withLeadingSpace: printLeadingSpaceToo
- 	"Print as per ISO 8601 sections 5.3.3 and 5.4.1.
- 	If printLeadingSpaceToo is false, prints either:
- 		'YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for positive years) or '-YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for negative years)
- 	If printLeadingSpaceToo is true, prints either:
- 		' YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for positive years) or '-YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for negative years)
- 	"
- 
- 	| nanos offsetSeconds |
- 	self printYMDOn: aStream withLeadingSpace: printLeadingSpaceToo.
- 	aStream nextPut: $T.
- 	self printHMSOn: aStream.
- 	(nanos := utcMicroseconds \\ 1000000 * 1000) = 0 ifFalse: [
- 		| length |
- 		aStream nextPut: $..
- 		length := 9.
- 		[ nanos \\ 10 = 0 ] whileTrue: [
- 			nanos := nanos // 10.
- 			length := length - 1 ].
- 		nanos printOn: aStream base: 10 length: length padded: true ].
- 	"Print offset"
- 	aStream nextPut: (localOffsetSeconds >= 0 ifTrue: [ $+ ] ifFalse: [ $- ]).
- 	offsetSeconds := localOffsetSeconds abs.
- 	offsetSeconds // 3600 printOn: aStream base: 10 length: 2 padded: true.
- 	aStream nextPut: $:.
- 	offsetSeconds \\ 3600 // 60 printOn: aStream base: 10 length: 2 padded: true.
- 	(offsetSeconds := offsetSeconds \\ 60) = 0 ifFalse: [
- 		aStream
- 			nextPut: $:;
- 			print: offsetSeconds ]!

Item was removed:
- ----- Method: LXDateAndTime>>printYMDOn: (in category 'squeak protocol') -----
- printYMDOn: aStream
- 	"Print just YYYY-MM-DD part.
- 	If the year is negative, prints out '-YYYY-MM-DD'."
- 
- 	^self printYMDOn: aStream withLeadingSpace: false.
- !

Item was removed:
- ----- Method: LXDateAndTime>>printYMDOn:withLeadingSpace: (in category 'squeak protocol') -----
- printYMDOn: aStream withLeadingSpace: printLeadingSpaceToo
- 	"Print just the year, month, and day on aStream.
- 
- 	If printLeadingSpaceToo is true, then print as:
- 		' YYYY-MM-DD' (if the year is positive) or '-YYYY-MM-DD' (if the year is negative)
- 	otherwise print as:
- 		'YYYY-MM-DD' or '-YYYY-MM-DD' "
- 
- 	self dayMonthYearDo: [ :day :month :year |
- 		year negative
- 			ifTrue: [ aStream nextPut: $- ]
- 			ifFalse: [ printLeadingSpaceToo ifTrue: [ aStream space ] ].
- 		year abs printOn: aStream base: 10 length: 4 padded: true.
- 		aStream nextPut: $-.
- 		month printOn: aStream base: 10 length: 2 padded: true.
- 		aStream nextPut: $-.
- 		day printOn: aStream base: 10 length: 2 padded: true ]!

Item was removed:
- ----- Method: LXDateAndTime>>readDataFrom:size: (in category 'objects from disk') -----
- readDataFrom: aDataStream size: varsOnDisk
- 	"Fill in the fields of self based on the contents of aDataStream. The serialized
- 	data will have four instance variables, because all instances are serialized in a
- 	cononical format as if having originating from an instance with the traditional
- 	seconds/offset/jdn/nanos instance variables."
-  
- 	| seconds offset jdn nanos |
- 	seconds := aDataStream next.
- 	offset := aDataStream next.
- 	jdn := aDataStream next.
- 	nanos := aDataStream next.
- 	localOffsetSeconds := offset ifNil: [ 0 ] ifNotNil: [ :off | off asSeconds ].
- 	utcMicroseconds := self
- 				microsecondsFromDay: jdn
- 				seconds: seconds
- 				nanos: nanos
- 				offset: localOffsetSeconds.!

Item was removed:
- ----- Method: LXDateAndTime>>second (in category 'ansi protocol') -----
- second
- 
- 	^self getSeconds \\ 60!

Item was removed:
- ----- Method: LXDateAndTime>>seconds (in category 'smalltalk-80') -----
- seconds
- 
- 	^ self second
- !

Item was removed:
- ----- Method: LXDateAndTime>>secondsSinceMidnight (in category 'private') -----
- secondsSinceMidnight
- 
- 	^ self getSeconds!

Item was removed:
- ----- Method: LXDateAndTime>>setJdn:seconds:nano:localOffsetSeconds: (in category 'private') -----
- setJdn: jdn seconds: s nano: n localOffsetSeconds: offset
- 
- 	localOffsetSeconds := offset.
- 	utcMicroseconds := self
- 				microsecondsFromDay: jdn
- 				seconds: s - offset
- 				nanos: n
- 				offset: offset!

Item was removed:
- ----- Method: LXDateAndTime>>setJdn:seconds:nano:offset: (in category 'squeak protocol') -----
- setJdn: jdn seconds: s nano: n offset: o
- 
- 	self setJdn: jdn seconds: s nano: n localOffsetSeconds: o asSeconds.
- !

Item was removed:
- ----- Method: LXDateAndTime>>species (in category 'accessing') -----
- species
- 	^DateAndTime!

Item was removed:
- ----- Method: LXDateAndTime>>storeDataOn: (in category 'objects from disk') -----
- storeDataOn: aDataStream
- 	"Store myself on a DataStream.  Answer self. 
- 	Store 4 variables worth of data, corresponding to the 4 instance variables of the old
- 	DateAndTime implementation, which is to be used as common format for externally
- 	stored instances."
- 
- 	" | dt dt2 |
- 	dt := DateAndTime now.
- 	dt2 := DataStream testWith: dt.
- 	{ dt . dt2 }."
- 
- 	| cntInstVars cntIndexedVars ticks jdn offset seconds nanos |
- 	"Set the instance variable count to 4 to match that of a cononical instance." 
- 	cntInstVars := 4.
- 	cntIndexedVars := self basicSize.
- 	aDataStream
- 		beginInstance: self xxxClass
- 		size: cntInstVars + cntIndexedVars.
- 
- 	"Create the 4 values of the old format DateAndTime"
- 	ticks := self ticks. 	"{days. seconds. nanoSeconds}."
- 	offset := self offset.
- 	jdn := ticks at: 1.
- 	seconds := ticks at: 2.
- 	nanos := ticks at: 3.
- 	aDataStream
- 		nextPut: seconds;
- 		nextPut: offset;
- 		nextPut: jdn;
- 		nextPut: nanos.
- !

Item was removed:
- ----- Method: LXDateAndTime>>ticks (in category 'private') -----
- ticks
- 	"Private - answer an array with our instance variables. Assumed to be UTC "
- 
- 	^ Array with: self julianDayNumber with: self getSeconds with: self nanoSecond
- !

Item was removed:
- ----- Method: LXDateAndTime>>ticks:offset: (in category 'private') -----
- ticks: ticks offset: utcOffset
- 	"ticks is {julianDayNumber. secondCount. nanoSeconds}"
- 
- 	| jdn s nanos |
- 	self normalize: 3 ticks: ticks base: NanosInSecond.
- 	self normalize: 2 ticks: ticks base: SecondsInDay.
- 
- 	jdn	:= ticks at: 1.
- 	s := ticks at: 2.
- 	nanos := ticks at: 3.
- 	localOffsetSeconds := utcOffset ifNil: [0] ifNotNil: [utcOffset asSeconds].
- 	utcMicroseconds := self microsecondsFromDay: jdn seconds: s nanos: nanos offset: localOffsetSeconds.
- !

Item was removed:
- ----- Method: LXDateAndTime>>timeZoneAbbreviation (in category 'ansi protocol') -----
- timeZoneAbbreviation
- 
- 	^ self class localTimeZone abbreviation!

Item was removed:
- ----- Method: LXDateAndTime>>timeZoneName (in category 'ansi protocol') -----
- timeZoneName
- 
- 	^ self class localTimeZone name!

Item was removed:
- ----- Method: LXDateAndTime>>to: (in category 'squeak protocol') -----
- to: anEnd
- 	"Answer a Timespan. anEnd conforms to protocol DateAndTime or protocol Timespan"
- 
- 	^ Timespan starting: self ending: (anEnd asLXDateAndTime)
- !

Item was removed:
- ----- Method: LXDateAndTime>>to:by: (in category 'squeak protocol') -----
- to: anEnd by: aDuration
- 	"Answer a Timespan. anEnd conforms to protocol DateAndTime or protocol Timespan"
- 
- 	^ (Schedule starting: self ending: (anEnd asLXDateAndTime))
- 		schedule: (Array with: aDuration asDuration);
- 		yourself
- !

Item was removed:
- ----- Method: LXDateAndTime>>to:by:do: (in category 'squeak protocol') -----
- to: anEnd by: aDuration do: aBlock
- 	"Answer a Timespan. anEnd conforms to protocol DateAndTime or protocol Timespan"
- 
- 	^ (self to: anEnd by: aDuration) scheduleDo: aBlock!

Item was removed:
- ----- Method: LXDateAndTime>>utcMicroseconds (in category 'accessing') -----
- utcMicroseconds
- 	^utcMicroseconds!

Item was removed:
- ----- Method: LXDateAndTime>>utcMicroseconds: (in category 'initialize-release') -----
- utcMicroseconds: utcValue
- 	"Allow value to be modified during initialization from a primitive in order to support
- 	monotonically increasing clock behavior."
- 	utcMicroseconds := utcValue!

Item was removed:
- ----- Method: LXDateAndTime>>utcMicroseconds:offset: (in category 'initialize-release') -----
- utcMicroseconds: microsecondsSincePosixEpoch offset: tzOffset
- 
- 	utcMicroseconds := microsecondsSincePosixEpoch.
- 	localOffsetSeconds := tzOffset.
- !

Item was removed:
- ----- Method: LXDateAndTime>>utcOffset: (in category 'squeak protocol') -----
- utcOffset: anOffset
- 
- 	"Answer a <DateAndTime> equivalent to the receiver but offset from UTC by anOffset"
- 
- 	self flag: #FIXME. "check the definition of this and of #offset:"
- 	^self utcMicroseconds: utcMicroseconds offset: anOffset asDuration asSeconds
- !

Item was removed:
- ----- Method: LXDateAndTime>>year (in category 'ansi protocol') -----
- year
- 	^ self
- 		dayMonthYearDo: [ :d :m :y | y ]
- !

Item was removed:
- LXDateAndTime subclass: #LXTimeStamp
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Chronology-Core'!
- 
- !LXTimeStamp commentStamp: '<historical>' prior: 0!
- This represents a duration of 0 length that marks a particular point in time.!

Item was removed:
- ----- Method: LXTimeStamp class>>current (in category 'squeak protocol') -----
- current
- 
- 	^self now!

Item was removed:
- ----- Method: LXTimeStamp>>asDateAndTime (in category 'squeak protocol') -----
- asDateAndTime
- 	"Answer the receiver as an instance of DateAndTime."
- 
- 	^ (LXDateAndTime utcMicroseconds: utcMicroseconds offset: localOffsetSeconds)
- 		asDateAndTime!

Item was removed:
- ----- Method: LXTimeStamp>>asTimeStamp (in category 'squeak protocol') -----
- asTimeStamp
- 	"Answer the receiver as an instance of TimeStamp."
- 
- 	^ self asDateAndTime asTimeStamp.!

Item was removed:
- ----- Method: LXTimeStamp>>date (in category 'squeak protocol') -----
- date
- 	"Answer the date of the receiver."
- 
- 	^ self asDate!

Item was removed:
- ----- Method: LXTimeStamp>>dateAndTime (in category 'squeak protocol') -----
- dateAndTime
- 	"Answer a two element Array containing the receiver's date and time."
- 
- 	^ Array with: self date with: self time!

Item was removed:
- ----- Method: LXTimeStamp>>minusDays: (in category 'squeak protocol') -----
- minusDays: anInteger
- 	"Answer a TimeStamp which is anInteger days before the receiver."
- 
- 	^ self - (anInteger days)!

Item was removed:
- ----- Method: LXTimeStamp>>minusSeconds: (in category 'squeak protocol') -----
- minusSeconds: anInteger
- 	"Answer a TimeStamp which is anInteger number of seconds before the receiver."
- 
- 	^ self - (anInteger seconds)!

Item was removed:
- ----- Method: LXTimeStamp>>plusDays: (in category 'squeak protocol') -----
- plusDays: anInteger
- 	"Answer a TimeStamp which is anInteger days after the receiver."
- 
- 	^ self + (anInteger days)!

Item was removed:
- ----- Method: LXTimeStamp>>plusSeconds: (in category 'squeak protocol') -----
- plusSeconds: anInteger
- 	"Answer a TimeStamp which is anInteger number of seconds after the receiver."
- 
- 	^ self + (anInteger seconds)!

Item was removed:
- ----- Method: LXTimeStamp>>printOn: (in category 'squeak protocol') -----
- printOn: aStream 
- 	"Print receiver's date and time on aStream."
- 
- 	aStream 
- 		nextPutAll: self date printString;
- 		space;
- 		nextPutAll: self time printString.!

Item was removed:
- ----- Method: LXTimeStamp>>storeOn: (in category 'squeak protocol') -----
- storeOn: aStream 
- 
- 	aStream 
- 		print: self printString;
- 		nextPutAll: ' asLXTimeStamp'!

Item was removed:
- ----- Method: LXTimeStamp>>time (in category 'squeak protocol') -----
- time
- 	"Answer the time of the receiver."
- 
- 	^ self asTime!

Item was removed:
- ----- Method: String>>asLXDateAndTime (in category '*Chronology-Core') -----
- asLXDateAndTime
- 
- 	"Convert from UTC format" 	^ LXDateAndTime fromString: self!

Item was removed:
- ----- Method: TimeStamp>>asLXTimeStamp (in category 'LX-Kernel-Chronology') -----
- asLXTimeStamp
- 
- 	^self asLXDateAndTime asLXTimeStamp!

Item was removed:
- ----- Method: Timespan>>asLXDateAndTime (in category '*Chronology-Core') -----
- asLXDateAndTime
- 
- 	^ start asLXDateAndTime!

Item was changed:
+ (PackageInfo named: 'Chronology-Core') postscript: 'DateAndTime startUp: true.
+ HashedCollection rehashAll.
- (PackageInfo named: 'Chronology-Core') postscript: '"Convert all instances of LXDateAndTime and LXTimeStamp to the equivalent DateAndTime and TimeStamp."
- 
- | oldInstances newInstances |
- Smalltalk garbageCollect.
- oldInstances := LXDateAndTime allInstances, LXTimeStamp allInstances.
- newInstances := oldInstances collect: [ :each |
-         each class == LXDateAndTime
-                 ifTrue: [ each asDateAndTime ]
-                 ifFalse: [ each asTimeStamp ] ].
- oldInstances elementsForwardIdentityTo: newInstances.
- Smalltalk garbageCollect.
  '!



More information about the Packages mailing list