[squeak-dev] The Inbox: Chronology-Core-dtl.18.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Dec 21 02:21:02 UTC 2018


A new version of Chronology-Core was added to project The Inbox:
http://source.squeak.org/inbox/Chronology-Core-dtl.18.mcz

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

Name: Chronology-Core-dtl.18
Author: dtl
Time: 15 December 2018, 6:45:56.065957 pm
UUID: c30315ee-999e-4ac0-90f0-7b6150d0caa8
Ancestors: Chronology-Core-dtl.17

Bootstrap UTCDateAndTime, step 3 of 5

DateAndTime and TimeStamp are now inactive, having been replaced by LXDateAndTime and LXTimeStamp. Load copies of the reimplemented LXDateAndTime and LXTimeStamp, renamed as DateAndTime and TimeStamp, to replace the original implementations of DateAndTime now.

At this point, DateAndTime is an inactive copy of LXDateAndTime. The next update will activate the new DateAndTime implementation.

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

Item was changed:
  Magnitude subclass: #DateAndTime
+ 	instanceVariableNames: 'utcMicroseconds localOffsetSeconds'
+ 	classVariableNames: 'ClockProvider DaysSinceEpoch LastMilliSeconds LastTick LastTickSemaphore LocalTimeZone MilliSecondOffset OffsetsAreValid'
- 	instanceVariableNames: 'seconds offset jdn nanos'
- 	classVariableNames: 'AutomaticTimezone ClockProvider LastClockValue LocalTimeZone NanoOffset'
  	poolDictionaries: 'ChronologyConstants'
  	category: 'Chronology-Core'!
  
+ !DateAndTime commentStamp: 'brp 5/13/2003 08:07' prior: 0!
- !DateAndTime commentStamp: 'bf 2/18/2016 16:20' prior: 0!
  I represent a point in UTC time as defined by ISO 8601. I have zero duration.
  
  
  My implementation uses three SmallIntegers
   and a Duration:
  jdn		- julian day number.
  seconds	- number of seconds since midnight.
  nanos	- the number of nanoseconds since the second.
  
+ offset	- duration from UTC.
- offset	- duration from UTC (possibly nil if no timezone information)
  
  The nanosecond attribute is almost always zero but it defined for full ISO compliance and is suitable for timestamping.
  !

Item was added:
+ ----- Method: DateAndTime class>>daysFromSmalltalkEpochToPosixEpoch (in category 'DTL') -----
+ daysFromSmalltalkEpochToPosixEpoch
+ 
+ 	^52 * 365 + (17 * 366)!

Item was changed:
  ----- Method: DateAndTime class>>epoch (in category 'squeak protocol') -----
  epoch
  	"Answer a DateAndTime representing the Squeak epoch: 1 January 1901"
  
+ 	| uSec |
+ 	self flag: #FIXME. "see comment in fromSeconds: "
+ 	uSec := self epochOffsetMicros negated.
+ 	^ self utcMicroseconds: uSec offset: self localOffsetSeconds
+ 
+ 
+ "
+ 	^ self julianDayNumber: SqueakEpoch
+ "!
- 	^ self julianDayNumber: SqueakEpoch!

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

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

Item was added:
+ ----- Method: DateAndTime class>>localOffsetSeconds (in category 'DTL') -----
+ localOffsetSeconds
+ 	^self localOffset asSeconds!

Item was changed:
  ----- Method: DateAndTime class>>now (in category 'ansi protocol') -----
+ now 
+ 	"^ self nowWithOffset: self localOffset"
+ 	^LXDateAndTime now!
- now
- 
- 	^LXDateAndTime now.
- "	[ | timeArray |
- 	timeArray := self primPosixMicrosecondClockWithOffset.
- 	^ self utcMicroseconds: timeArray first offset: timeArray second]
- 		on: Error
- 		do: [ ""Use old style primitive support""
- 			^self nowWithOffset: self localOffset]"!

Item was added:
+ ----- Method: DateAndTime class>>posixEpoch (in category 'DTL') -----
+ posixEpoch
+ 	"Answer a DateAndTime representing the Posix epoch"
+ 
+ 	^ self julianDayNumber: self posixEpochJulianDays !

Item was added:
+ ----- Method: DateAndTime class>>primPosixMicrosecondClockWithOffset (in category 'DTL') -----
+ primPosixMicrosecondClockWithOffset
+ 	"Answer an array with UTC microseconds since the Posix epoch and the
+ 	current seconds offset from GMT in the local time zone."
+ 
+ 	<primitive: 'primitiveUtcWithOffset'>
+ 
+ 	^self primitiveFailed!

Item was changed:
  ----- Method: DateAndTime class>>tomorrow (in category 'squeak protocol') -----
  tomorrow
  
+ 	^ self today asDate next asLXDateAndTime
- 	^ self today asDate next asDateAndTime
  !

Item was added:
+ ----- Method: DateAndTime class>>utcMicroseconds:offset: (in category 'DTL') -----
+ utcMicroseconds: microsecondsSincePosixEpoch offset: offsetSeconds
+ 
+ 	^super new
+ 		utcMicroseconds: microsecondsSincePosixEpoch
+ 		offset: offsetSeconds!

Item was changed:
  ----- Method: DateAndTime class>>yesterday (in category 'squeak protocol') -----
  yesterday
  
+ 	^ self today asDate previous asLXDateAndTime!
- 	^ self today asDate previous asDateAndTime!

Item was changed:
  ----- Method: DateAndTime>>+ (in category 'ansi protocol') -----
  + operand
  	"operand conforms to protocol Duration"
  
+ 	^ self class
+ 		utcMicroseconds: operand asDuration asNanoSeconds / 1000 + utcMicroseconds
+ 		offset: localOffsetSeconds
- 	| ticks |
-  	ticks := self ticks + (operand asDuration ticks) .
- 
- 	^ self class basicNew
- 		ticks: ticks
- 		offset: self offset; 
- 		yourself
  !

Item was changed:
  ----- Method: DateAndTime>>- (in category 'ansi protocol') -----
  - operand
  	"operand conforms to protocol DateAndTime or protocol Duration"
  
+ 	^ (operand respondsTo: #asLXDateAndTime)
- 	^ (operand respondsTo: #asDateAndTime)
  		ifTrue: 
  			[ | lticks rticks |
  			lticks := self asLocal ticks.
  	
+ 		rticks := operand asLXDateAndTime asLocal ticks.
- 		rticks := operand asDateAndTime asLocal ticks.
  			Duration
   				seconds: (SecondsInDay *(lticks first - rticks first)) + 
  							(lticks second - rticks second)
   				nanoSeconds: (lticks third - rticks third) ]
  	
  	ifFalse:
  		
   	[ self + (operand negated) ]
  !

Item was changed:
  ----- Method: DateAndTime>>< (in category 'ansi protocol') -----
+ < comparand
- < comparand 
  	"comparand conforms to protocol DateAndTime,
  	or can be converted into something that conforms."
+ 
+ 	utcMicroseconds ifNil: [^true]. self flag: #FIXME. "dtl transitional hack"
+ 	^utcMicroseconds < comparand asLXDateAndTime utcMicroseconds
+ !
- 	| lvalue rvalue comparandAsDateAndTime |
- 	comparandAsDateAndTime _ comparand asDateAndTime.
- 	self offset = comparandAsDateAndTime offset
- 		ifTrue:
- 			[ lvalue := self.
- 			rvalue := comparandAsDateAndTime ]
- 		ifFalse:
- 			[ lvalue := self asUTC.
- 			rvalue := comparandAsDateAndTime asUTC ].
- 	^ lvalue julianDayNumber < rvalue julianDayNumber or:
- 		[ lvalue julianDayNumber > rvalue julianDayNumber
- 			ifTrue: [ false ]
- 			ifFalse:
- 				[ lvalue secondsSinceMidnight < rvalue secondsSinceMidnight or:
- 					[ lvalue secondsSinceMidnight > rvalue secondsSinceMidnight
- 						ifTrue: [ false ]
- 						ifFalse: [ lvalue nanoSecond < rvalue nanoSecond ] ] ] ]!

Item was changed:
  ----- Method: DateAndTime>>= (in category 'ansi protocol') -----
+ = aDateAndTimeOrTimeStamp
+ 	"Equal if the absolute time values match, regardless of local time transform"
- = aDateAndTimeOrTimeStamp 
  	self == aDateAndTimeOrTimeStamp ifTrue: [ ^ true ].
  	((aDateAndTimeOrTimeStamp isKindOf: self class)
+ 		or: [aDateAndTimeOrTimeStamp isKindOf: LXDateAndTime orOf: TimeStamp])
- 		or: [aDateAndTimeOrTimeStamp isKindOf: DateAndTime orOf: TimeStamp])
  			ifFalse: [ ^ false ].
+ 	^utcMicroseconds = aDateAndTimeOrTimeStamp utcMicroseconds!
- 	^ self offset = aDateAndTimeOrTimeStamp offset
- 		ifTrue: [ self hasEqualTicks: aDateAndTimeOrTimeStamp ]
- 		ifFalse: [ self asUTC hasEqualTicks: aDateAndTimeOrTimeStamp asUTC ]!

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

Item was changed:
+ ----- Method: DateAndTime>>asLXDateAndTime (in category 'squeak protocol') -----
- ----- Method: DateAndTime>>asLXDateAndTime (in category 'LX-Kernel-Chronology') -----
  asLXDateAndTime
  
+ 	^ LXDateAndTime utcMicroseconds: utcMicroseconds offset: localOffsetSeconds!
- 	^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 added:
+ ----- Method: DateAndTime>>asLXTimeStamp (in category 'transitional - temporary') -----
+ asLXTimeStamp
+ 
+ 	^ self as: LXTimeStamp!

Item was added:
+ ----- Method: DateAndTime>>asPosixSeconds (in category 'transitional - temporary') -----
+ asPosixSeconds
+ 
+ 	^ (self - (self class posixEpoch offset: self offset)) asSeconds!

Item was changed:
  ----- Method: DateAndTime>>asSeconds (in category 'smalltalk-80') -----
  asSeconds
  	"Return the number of seconds since the Squeak epoch"
+ 
+ 	self flag: #FIXME. "is this whole seconds or partial? UTC or local?"
+ 
+ 	^ utcMicroseconds / 1000000 + self class epochOffset
+ !
- 	^ (self - (self class epoch offset: offset)) asSeconds!

Item was changed:
  ----- Method: DateAndTime>>asTime (in category 'squeak protocol') -----
  asTime
  
  
+ 	^ Time seconds: self getSeconds nanoSeconds: self nanoSecond
- 	^ Time seconds: seconds nanoSeconds: nanos
  !

Item was changed:
  ----- Method: DateAndTime>>asTimeStamp (in category 'squeak protocol') -----
  asTimeStamp
  
+ 	^ self
+ 		asDateAndTime "FIXME LX hack for test support"
+ 		as: TimeStamp!
- 	^ self as: TimeStamp!

Item was changed:
  ----- Method: DateAndTime>>asUTC (in category 'ansi protocol') -----
  asUTC
  
  	^ self offset isZero
  		ifTrue: [self]
  		ifFalse: [self utcOffset: 0]
  !

Item was changed:
  ----- Method: DateAndTime>>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.
- 	l := jdn + 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 changed:
  ----- Method: DateAndTime>>dayOfWeek (in category 'ansi protocol') -----
  dayOfWeek
  
  	"Sunday=1, ... , Saturday=7"
  
+ 	^ (self julianDayNumber + 1 rem: 7) + 1
- 	^ (jdn + 1 rem: 7) + 1
  !

Item was changed:
  ----- Method: DateAndTime>>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!
- 	^self class basicNew
- 		ticks: (self ticks at: 3 put: 0; yourself)
- 		offset: offset.
- !

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

Item was changed:
  ----- Method: DateAndTime>>hasEqualTicks: (in category 'private') -----
  hasEqualTicks: aDateAndTime
  	
+ 	^ (self julianDayNumber = aDateAndTime julianDayNumber)
+ 		and: [ (self getSeconds = aDateAndTime secondsSinceMidnight)
+ 			and: [ self nanoSecond = aDateAndTime nanoSecond ] ]
- 	^ (jdn = aDateAndTime julianDayNumber)
- 		and: [ (seconds = aDateAndTime secondsSinceMidnight)
- 			and: [ nanos = aDateAndTime nanoSecond ] ]
  
  !

Item was changed:
  ----- Method: DateAndTime>>hash (in category 'ansi protocol') -----
  hash
  	| totalSeconds |
+ 	totalSeconds := self getSeconds - self offsetSeconds.
+ 	^ ((totalSeconds // 86400 + self julianDayNumber) hashMultiply bitXor: totalSeconds \\
+ 86400) bitXor: self nanoSecond!
- 	totalSeconds := seconds - self offset asSeconds.
- 	^ ((totalSeconds // 86400 + jdn) hashMultiply bitXor: totalSeconds \\
- 86400) bitXor: nanos!

Item was changed:
  ----- Method: DateAndTime>>hour24 (in category 'ansi protocol') -----
  hour24
  
  
+ 	^ (Duration seconds: self getSeconds) hours!
- 	^ (Duration seconds: seconds) hours!

Item was changed:
  ----- Method: DateAndTime>>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 - 1 * SecondsInDay + localSeconds].
+ 	posixDays := (localSeconds / SecondsInDay) asInteger.
+ 	^posixDays + self posixEpochJulianDays - negativeDays.
+ !
- 
- 	^ jdn!

Item was changed:
  ----- Method: DateAndTime>>makeUTC (in category 'squeak protocol') -----
  makeUTC
  	"Make the receiver's timezone UTC."
+ 	localOffsetSeconds := 0!
- 	self primOffset: Duration zero!

Item was changed:
  ----- Method: DateAndTime>>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
- 		setJdn: jdn
  		seconds: 0
  		nano: 0
+ 		offset: self offset!
- 		offset: offset!

Item was changed:
  ----- Method: DateAndTime>>minute (in category 'ansi protocol') -----
  minute
  
  
+ 	^ (Duration seconds: self getSeconds) minutes!
- 	^ (Duration seconds: seconds) minutes!

Item was changed:
  ----- Method: DateAndTime>>nanoSecond (in category 'squeak protocol') -----
  nanoSecond
  
+ 	^utcMicroseconds \\ 1000000 * 1000
+ !
- 
- 	^ nanos!

Item was changed:
  ----- Method: DateAndTime>>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.
- 	div := tick 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 changed:
  ----- Method: DateAndTime>>offset (in category 'ansi protocol') -----
  offset
  
+ 	^ Duration seconds: localOffsetSeconds!
- 	^ offset ifNil: [Duration zero]!

Item was changed:
  ----- Method: DateAndTime>>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."
  
+ 	^ self class utcMicroseconds: utcMicroseconds offset: anOffset asDuration asSeconds
+ !
- 	^ self class basicNew 
- 		ticks: self ticks offset: (anOffset ifNotNil: [anOffset asDuration]);
- 		yourself!

Item was added:
+ ----- Method: DateAndTime>>offsetSeconds (in category 'transitional - temporary') -----
+ offsetSeconds
+ 
+ 	^localOffsetSeconds ifNil: [localOffsetSeconds := self offset asSeconds]!

Item was added:
+ ----- Method: DateAndTime>>posixEpochJulianDays (in category 'DTL-initializing') -----
+ posixEpochJulianDays
+ 
+ 	^self class daysFromSmalltalkEpochToPosixEpoch + SqueakEpoch!

Item was added:
+ ----- Method: DateAndTime>>posixMicrosecondsJdn:seconds:nanos:offset: (in category 'transitional - temporary') -----
+ posixMicrosecondsJdn: j seconds: s nanos: n offset: o
+ 
+ 	| days totalSeconds micros |
+ 	days := j - self posixEpochJulianDays.
+ 	totalSeconds := days * 24 * 60 * 60 + s.
+ 	micros := totalSeconds * 1000000.
+ 	^micros + (n / 1000)
+ !

Item was changed:
  ----- Method: DateAndTime>>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)
  	"
  
  	self printYMDOn: aStream withLeadingSpace: printLeadingSpaceToo.
  	aStream nextPut: $T.
  	self printHMSOn: aStream.
  	self nanoSecond ~= 0 ifTrue:
  		[ | z ps |
  		ps := self nanoSecond printString padded: #left to: 9 with: $0.
  		z := ps findLast: [ :c | c asciiValue > $0 asciiValue ].
  		(z > 0) ifTrue: [aStream nextPut: $.].
  		ps from: 1 to: z do: [ :c | aStream nextPut: c ] ].
  	aStream
  		nextPut: (self offset positive ifTrue: [$+] ifFalse: [$-]);
  		nextPutAll: (self offset hours abs asString padded: #left to: 2 with: $0);
  		nextPut: $:;
  		nextPutAll: (self offset minutes abs asString padded: #left to: 2 with: $0).
  	self offset seconds = 0 ifFalse:
  		[ aStream
  			nextPut: $:;
  			nextPutAll: (self offset seconds abs truncated asString) ].
  !

Item was changed:
  ----- Method: DateAndTime>>second (in category 'ansi protocol') -----
  second
  
  
+ 	^ (Duration seconds: self getSeconds) seconds!
- 	^ (Duration seconds: seconds) seconds!

Item was changed:
  ----- Method: DateAndTime>>secondsSinceMidnight (in category 'private') -----
  secondsSinceMidnight
  
+ 	^ self getSeconds!
- 	^ seconds!

Item was changed:
  ----- Method: DateAndTime>>setJdn:seconds:nano:offset: (in category 'squeak protocol') -----
+ setJdn: jdn seconds: s nano: n offset: o
- setJdn: j seconds: s nano: n offset: o
  
+ 	localOffsetSeconds :=  o asSeconds.
+ 	utcMicroseconds := self posixMicrosecondsJdn: jdn seconds: s nanos: n offset: localOffsetSeconds.
+ 
- jdn := j.
- seconds := s.
- nanos :=  n.
- offset :=  o
  !

Item was changed:
  ----- Method: DateAndTime>>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
- 	^ Array with: jdn with: seconds with: nanos
  !

Item was changed:
  ----- Method: DateAndTime>>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.
- 	seconds	:= ticks at: 2.
  	nanos := ticks at: 3.
+ 	localOffsetSeconds := utcOffset asSeconds.
+ 	utcMicroseconds := self posixMicrosecondsJdn: jdn seconds: s nanos: nanos offset: localOffsetSeconds.
- 	offset := utcOffset
  !

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

Item was changed:
  ----- Method: DateAndTime>>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 starting: self ending: (anEnd asDateAndTime))
  		schedule: (Array with: aDuration asDuration);
  		yourself
  !

Item was added:
+ ----- Method: DateAndTime>>utcMicroseconds (in category 'transitional - temporary') -----
+ utcMicroseconds
+ 	^utcMicroseconds!

Item was added:
+ ----- Method: DateAndTime>>utcMicroseconds:offset: (in category 'DTL-initializing') -----
+ utcMicroseconds: microsecondsSincePosixEpoch offset: tzOffset
+ 
+ 	utcMicroseconds := microsecondsSincePosixEpoch.
+ 	localOffsetSeconds := tzOffset.
+ !

Item was changed:
  ----- Method: LXDateAndTime>>asDateAndTime (in category 'squeak protocol') -----
  asDateAndTime
  
+ 	^DateAndTime utcMicroseconds: utcMicroseconds offset: localOffsetSeconds
+ !
- 	^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 added:
+ ----- Method: Time class>>primPosixMicrosecondClockWithOffsetStoredIn: (in category 'LX-Kernel-Chronology') -----
+ primPosixMicrosecondClockWithOffsetStoredIn: resultArray
+ 	"Answer an array with UTC microseconds since the Posix epoch and the
+ 	current seconds offset from GMT in the local time zone, supplying a two
+ 	element result array that will be populated in the primitive."
+ 
+ 	<primitive: 'primitiveUtcWithOffset'>
+ 	^#(0 0)!

Item was changed:
  ----- Method: TimeStamp class>>current (in category 'squeak protocol') -----
  current
  
+ 	| ts ticks |
+ 	ts := super now asTimeStamp.
+ 	ticks := ts ticks.
+ 	ticks at: 3 put: 0.
+ 	ts ticks: ticks offset: ts offset.
+ 	^ ts
+ !
- 	^self now!

Item was added:
+ ----- Method: TimeStamp class>>now (in category 'ansi protocol') -----
+ now
+ 	"Answer the current date and time as a TimeStamp."
+ 
+ 	^self current!

Item was changed:
  ----- Method: TimeStamp>>asDateAndTime (in category 'squeak protocol') -----
  asDateAndTime
  	"Answer the receiver as an instance of DateAndTime."
  
+ 	^ DateAndTime utcMicroseconds: utcMicroseconds offset: localOffsetSeconds!
- 	^ DateAndTime new setJdn: jdn seconds: seconds nano: nanos offset: offset!

Item was added:
+ ----- Method: TimeStamp>>asLXDateAndTime (in category 'transitional') -----
+ asLXDateAndTime
+ 	"Answer the receiver as an instance of DateAndTime."
+ 
+ 	utcMicroseconds ifNil: [^LXDateAndTime new].
+ 	^ LXDateAndTime utcMicroseconds: utcMicroseconds offset: self offsetSeconds
+ !

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

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



More information about the Squeak-dev mailing list