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

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


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

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

Name: Chronology-Core-dtl.19
Author: dtl
Time: 1 January 2019, 8:12:58.333297 pm
UUID: fc3bb329-7dbb-4947-8428-c092e32ab067
Ancestors: Chronology-Core-dtl.18

Resume using DateAndTime instead of LXDateAndTime.

Change instance creation to create DateAndTime instances instead of LXDateAndTime.
In the postScript, have LXDateAndTime instances become DateAndTime.

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

Item was changed:
  SharedPool subclass: #ChronologyConstants
+ 	instanceVariableNames: ''
- 	instanceVariableNames: 'seconds offset jdn nanos'
  	classVariableNames: 'DayNames DaysInMonth MicrosecondsInDay MonthNames NanosInMillisecond NanosInSecond OneDay SecondsInDay SecondsInHour SecondsInMinute SqueakEpoch Zero'
  	poolDictionaries: ''
  	category: 'Chronology-Core'!
  
  !ChronologyConstants commentStamp: 'brp 3/12/2004 14:34' prior: 0!
  ChronologyConstants is a SharedPool for the constants used by the Kernel-Chronology classes.!

Item was removed:
- ServiceProvider subclass: #ChronologyCoreServiceProvider
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Chronology-Core'!

Item was removed:
- ----- Method: ChronologyCoreServiceProvider class>>initialize (in category 'initialization') -----
- initialize 
- 	ServiceRegistry current buildProvider: self new!

Item was changed:
  ----- Method: Date class>>readFrom: (in category 'squeak protocol') -----
  readFrom: aStream 
  	"Read a Date from the stream in any of the forms:  
  		<day> <month> <year>		(15 April 1982; 15-APR-82; 15.4.82; 15APR82)  
  		<month> <day> <year>		(April 15, 1982; 4/15/82)
  		<year>-<month>-<day>			(1982-04-15) (ISO8601)"
+ 	| ymd |
+ 	ymd := self readYearMonthDayFrom: aStream.
- 	| day month year parsedNumber prefix |
- 	aStream peek = $-
- 		ifTrue: [prefix := -1]
- 		ifFalse: [prefix := 1].
- 	[aStream peek isAlphaNumeric]
- 		whileFalse: [aStream skip: 1].
- 	aStream peek isDigit
- 		ifTrue: [
- 			parsedNumber := (Integer readFrom: aStream) * prefix.
- 			(parsedNumber < 0 or: [parsedNumber > 31])
- 				ifTrue: [year := parsedNumber]].
- 	[aStream peek isAlphaNumeric]
- 		whileFalse: [aStream skip: 1].
- 	aStream peek isLetter
- 		ifTrue: ["MM-DD-YY or DD-MM-YY or YY-MM-DD"
- 			month := WriteStream on: (String new: 10).
- 			[aStream peek isLetter]
- 				whileTrue: [month nextPut: aStream next].
- 			month := month contents.
- 			[aStream peek isAlphaNumeric]
- 				whileFalse: [aStream skip: 1].
- 			parsedNumber isNil
- 				ifTrue: ["MM DD YY"
- 					day := Integer readFrom: aStream]
- 				ifFalse: [
- 					year isNil
- 						ifTrue: ["DD MM YY"
- 							day := parsedNumber]]]
- 		ifFalse: ["MM-DD-YY or DD-MM-YY or YY-MM-DD"
- 			year isNil 
- 				ifTrue: ["MM-DD-YY or DD-MM-YY"
- 					parsedNumber > 12
- 						ifTrue: ["DD-MM-YY"
- 							day := parsedNumber.
- 							month := Month nameOfMonth: (Integer readFrom: aStream)]
- 						ifFalse: ["MM-DD-YY"
- 							month := Month nameOfMonth: parsedNumber.
- 							day := Integer readFrom: aStream]]
- 				ifFalse: ["YY-MM-DD"
- 					month := Month nameOfMonth: (Integer readFrom: aStream)]].
- 	[aStream peek isAlphaNumeric]
- 		whileFalse: [aStream skip: 1].
- 	year isNil
- 		ifTrue: [year := Integer readFrom: aStream]
- 		ifFalse: [day := Integer readFrom: aStream].
- 	(year < 100 and: [year >= 0]) 
- 		ifTrue: [
- 			year < 69 
- 				ifTrue: [	year := 2000 + year]
- 				ifFalse: [year := 1900 + year]].
- 
  	^ self
+ 		year: ymd first
+ 		month: ymd second
+ 		day: ymd third
- 		year: year
- 		month: month
- 		day: day
  !

Item was changed:
  ----- Method: DateAndTime 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 |
- 	^ LXDateAndTime fromSeconds: seconds
- 
- 	"| s uSec offset |
  	offset := self localOffsetSeconds.
  	s := seconds - self epochOffset.
  	uSec := s * 1000000.
+ 	^ self utcMicroseconds: uSec offset: offset
- 	^ self utcMicroseconds: uSec offset: offset"
  !

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

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
- 	^LXDateAndTime now.
- 
- 	"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 ]
- 			^ self utcMicroseconds: timeArray first offset: self localOffsetSeconds ]"
  !

Item was removed:
- ----- Method: DateAndTime class>>now:offset: (in category 'squeak protocol') -----
- now: clockValue offset: aDuration
- 
- 	| seconds nanos |
- 	"Ensure that consecutive sends of this method return increasing values, by adding small values to the nanosecond part of the created object. The next few lines are assumed to be executed atomically - having no suspension points."
- 	((LastClockValue ifNil: [ 0 ]) digitCompare: clockValue) = 0
- 		ifTrue: [ NanoOffset := NanoOffset + 1 ]
- 		ifFalse: [ NanoOffset := 0 ].
- 	LastClockValue := clockValue.
- 	nanos := clockValue \\ 1000000 * 1000 + NanoOffset.
- 	seconds := clockValue // 1000000.
- 	^self basicNew
- 		setJdn: seconds // SecondsInDay + SqueakEpoch
- 		seconds: seconds \\ SecondsInDay
- 		nano: nanos
- 		offset: aDuration!

Item was removed:
- ----- Method: DateAndTime class>>setLocalOffsetAutomatically: (in category 'squeak protocol') -----
- setLocalOffsetAutomatically: aDuration
- 	"Set the duration we are offset from UTC (done automatically in #now)"
- 	LocalTimeZone := (TimeZone offset: aDuration name: 'Local Time' abbreviation: 'LT').
- !

Item was changed:
  ----- Method: DateAndTime 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 |
- 	^ LXDateAndTime year: year month: month day: day hour: hour minute: minute second: second nanoSecond: nanoCount offset: offset
- 
- 	"| 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!
- 	^ self utcMicroseconds: utcMicros offset: offsetSeconds"!

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

Item was removed:
- ----- Method: DateAndTime>>hasSmallerTicksThan: (in category 'private') -----
- hasSmallerTicksThan: aDateAndTime
- 	
- 	^ jdn < aDateAndTime julianDayNumber or:
- 		[ jdn > aDateAndTime julianDayNumber
- 			ifTrue: [ false ]
- 			ifFalse:
- 				[ seconds < aDateAndTime secondsSinceMidnight or:
- 					[ seconds > aDateAndTime secondsSinceMidnight
- 						ifTrue: [ false ]
- 						ifFalse: [ nanos < aDateAndTime nanoSecond ] ] ] ]!

Item was removed:
- ----- Method: DateAndTime>>noTimezone (in category 'private') -----
- noTimezone
- 	^offset == nil!

Item was removed:
- ----- Method: DateAndTime>>primOffset: (in category 'private') -----
- primOffset: aDuration
- 	offset := aDuration!

Item was added:
+ ----- Method: Duration class>>readDayHourMinuteSecondNanaFrom: (in category 'squeak protocol') -----
+ readDayHourMinuteSecondNanaFrom: aStream
+ 	"Formatted as per ANSI 5.8.2.16: [-]D:HH:MM:SS[.S]"
+ 
+ 	| sign days hours minutes seconds nanos nanosBuffer |
+ 	sign := (aStream peekFor: $-) ifTrue: [-1] ifFalse: [1].
+ 	days := (aStream upTo: $:) asInteger sign: sign.
+ 	hours := (aStream upTo: $:) asInteger sign: sign.
+ 	minutes := (aStream upTo: $:) asInteger sign: sign.
+ 	seconds := (aStream upTo: $.) asInteger sign: sign.
+ 	nanosBuffer := '000000000' copy.
+ 	nanos := WriteStream on: nanosBuffer.
+ 	[aStream atEnd not and: [aStream peek isDigit]]
+ 		whileTrue: [nanos nextPut: aStream next].
+ 		
+ 	^ { days . hours . minutes . seconds .nanosBuffer asInteger sign: sign }
+ 
+ 	"	'0:00:00:00' asDuration
+ 		'0:00:00:00.000000001' asDuration
+ 		'0:00:00:00.999999999' asDuration
+ 		'0:00:00:00.100000000' asDuration
+ 		'0:00:00:00.001 ' asDuration
+ 		'0:00:00:00.1' asDuration
+ 		'0:00:00:01 ' asDuration
+ 		'0:12:45:45' asDuration
+ 		'1:00:00:00' asDuration
+ 		'365:00:00:00' asDuration
+ 		'-7:09:12:06.10' asDuration
+ 		'+0:01:02:3' asDuration
+  	"!

Item was changed:
  ----- Method: Duration class>>readFrom: (in category 'squeak protocol') -----
  readFrom: aStream
  	"Formatted as per ANSI 5.8.2.16: [-]D:HH:MM:SS[.S]"
  
+ 	| dayHourMinuteSecondNano |
+ 	dayHourMinuteSecondNano := self readDayHourMinuteSecondNanaFrom: aStream.
- 	| sign days hours minutes seconds nanos nanosBuffer |
- 	sign := (aStream peekFor: $-) ifTrue: [-1] ifFalse: [1].
- 	days := (aStream upTo: $:) asInteger sign: sign.
- 	hours := (aStream upTo: $:) asInteger sign: sign.
- 	minutes := (aStream upTo: $:) asInteger sign: sign.
- 	seconds := (aStream upTo: $.) asInteger sign: sign.
- 	nanosBuffer := '000000000' copy.
- 	nanos := WriteStream on: nanosBuffer.
- 	[aStream atEnd not and: [aStream peek isDigit]]
- 		whileTrue: [nanos nextPut: aStream next].
  		
  	^ self 
+ 		days: dayHourMinuteSecondNano first 
+ 		hours: dayHourMinuteSecondNano second 
+ 		minutes: dayHourMinuteSecondNano third 
+ 		seconds: dayHourMinuteSecondNano fourth 
+ 		nanoSeconds: dayHourMinuteSecondNano fifth
- 		days: days 
- 		hours: hours 
- 		minutes: minutes 
- 		seconds: seconds 
- 		nanoSeconds: (nanosBuffer asInteger sign: sign)
  
  	"	'0:00:00:00' asDuration
  		'0:00:00:00.000000001' asDuration
  		'0:00:00:00.999999999' asDuration
  		'0:00:00:00.100000000' asDuration
  		'0:00:00:00.001 ' asDuration
  		'0:00:00:00.1' asDuration
  		'0:00:00:01 ' asDuration
  		'0:12:45:45' asDuration
  		'1:00:00:00' asDuration
  		'365:00:00:00' asDuration
  		'-7:09:12:06.10' asDuration
  		'+0:01:02:3' asDuration
   	"!

Item was changed:
  ----- Method: Duration class>>seconds: (in category 'ansi protocol') -----
  seconds: seconds
  
+ 	seconds isInteger
+ 		ifTrue: [ ^ self basicNew fullSeconds: seconds ]
+ 		ifFalse: [ ^ self seconds: seconds nanoSeconds: 0 ]
- 	^ self seconds: seconds nanoSeconds: 0
  !

Item was added:
+ ----- Method: Duration>>fullSeconds: (in category 'private') -----
+ fullSeconds: secondCount
+ 	"Private - only used by Duration class"
+ 
+ 	seconds := secondCount.
+ 	nanos := 0.
+ !

Item was removed:
- ----- Method: Duration>>wait (in category 'squeak protocol') -----
- wait
- 	"Convert this duration in a delay and wait once. Return the created delay so that the client can wait on it again if needed.
- 	
- 	Do-it: 3 minutes wait"
- 	
- 	| delay |
- 	delay := self asDelay.
- 	delay wait.
- 	^ delay!

Item was removed:
- TestCase subclass: #LXDateAndTimeConversionTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Chronology-Core'!

Item was removed:
- ----- Method: LXDateAndTimeConversionTest>>testAsSeconds (in category 'testing') -----
- testAsSeconds
- 
- 	| day dt hour lxdt min mo nano offset sec yr expectedSeconds |
- 	yr := 1970.
- 	mo := 12.
- 	day := 2.
- 	hour := 2.
- 	min := 3.
- 	sec := 4.
- 	nano := 5.
- 	offset := 6 hours.
- 	lxdt := LXDateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 	dt := DateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 	self assert: 2206404184 equals: dt asSeconds.
- 	self assert: 2206404184 equals: lxdt asSeconds.
- 
- 	yr := 1969.
- 	lxdt := LXDateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 	dt := DateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 	expectedSeconds := 2206404184 - (365 * 24 * 60 * 60).
- 	self assert: expectedSeconds equals: dt asSeconds.
- 	self assert: expectedSeconds equals: lxdt asSeconds.
- !

Item was removed:
- ----- Method: LXDateAndTimeConversionTest>>testAsSeconds2 (in category 'testing') -----
- testAsSeconds2
- 	"(self selector: #testAsSeconds2) debug"
- 
- 	| day dt hour lxdt min mo nano offset sec |
- 	mo := 12.
- 	day := 2.
- 	hour := 2.
- 	min := 3.
- 	sec := 4.
- 	nano := 5.
- 	offset := 6 hours.
- "	-2000 to: 5000 do: [:yr |"
- 	1970 to: 5000 do: [:yr |
- 		lxdt := LXDateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		dt := DateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		self assert: dt asSeconds equals: lxdt asSeconds].
- !

Item was removed:
- ----- Method: LXDateAndTimeConversionTest>>testDayOfMonth (in category 'testing') -----
- testDayOfMonth
- 	"(self selector: #testDayOfMonth) debug"
- 
- 	| day dt hour lxdt min mo nano offset sec |
- 	mo := 12.
- 	day := 2.
- 	hour := 2.
- 	min := 3.
- 	sec := 4.
- 	nano := 5.
- 	offset := 6 hours.
- 	-1200 to: 3000 do: [:yr |
- 		lxdt := LXDateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		dt := DateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		self assert: dt dayOfMonth equals: lxdt dayOfMonth].
- !

Item was removed:
- ----- Method: LXDateAndTimeConversionTest>>testDayOfWeek (in category 'testing') -----
- testDayOfWeek
- 	"(self selector: #testDayOfWeek) debug"
- 
- 	| day dt hour lxdt min mo nano offset sec |
- 	mo := 12.
- 	day := 2.
- 	hour := 2.
- 	min := 3.
- 	sec := 4.
- 	nano := 5.
- 	offset := 6 hours.
- 	-1200 to: 3000 do: [:yr |
- 		lxdt := LXDateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		dt := DateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		self assert: dt dayOfWeek equals: lxdt dayOfWeek].
- !

Item was removed:
- ----- Method: LXDateAndTimeConversionTest>>testDayOfYear (in category 'testing') -----
- testDayOfYear
- 	"(self selector: #testDayOfYear) debug"
- 
- 	| day dt hour lxdt min mo nano offset sec |
- 	mo := 12.
- 	day := 2.
- 	hour := 2.
- 	min := 3.
- 	sec := 4.
- 	nano := 5.
- 	offset := 6 hours.
- 	-1200 to: 3000 do: [:yr |
- 		lxdt := LXDateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		dt := DateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		self assert: dt dayOfYear equals: lxdt dayOfYear].
- !

Item was removed:
- ----- Method: LXDateAndTimeConversionTest>>testFromString (in category 'testing') -----
- testFromString
- 	"Convert to string then back, verify same date and time. Skip years in the
- 	range 0 to 99 because they are interpreted relative to 2000."
- 
- 	"(LXDateAndTimeConversionTest selector: #testFromString) debug"
- 
- 	| day hour lxdt min mo nano offset sec newLxdt s |
- 	mo := 12.
- 	day := 2.
- 	hour := 2.
- 	min := 3.
- 	sec := 4.
- 	nano := 5.
- 	offset := 6 hours.
- 	(-2000 to: -1) , (100 to: 5000) do: [:yr |
- 		lxdt := LXDateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		s := lxdt asString.
- 		newLxdt := LXDateAndTime fromString: s.
- 		self assert: lxdt equals: newLxdt].
- !

Item was removed:
- ----- Method: LXDateAndTimeConversionTest>>testJulianDayNumber (in category 'testing') -----
- testJulianDayNumber
- 	"(self selector: #testJulianDayNumber) debug"
- 
- 	| day dt hour lxdt min mo nano offset sec |
- 	mo := 12.
- 	day := 2.
- 	hour := 2.
- 	min := 3.
- 	sec := 4.
- 	nano := 5.
- 	offset := 6 hours.
- 	-2000 to: 5000 do: [:yr |
- 		lxdt := LXDateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		dt := DateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		self assert: dt julianDayNumber equals: lxdt julianDayNumber].
- !

Item was removed:
- ----- Method: LXDateAndTimeConversionTest>>testMinute (in category 'testing') -----
- testMinute
- 	"(self selector: #testMinute) debug"
- 
- 	| day dt hour lxdt min mo nano offset sec |
- 	mo := 12.
- 	day := 2.
- 	hour := 2.
- 	min := 3.
- 	sec := 4.
- 	nano := 5.
- 	offset := 6 hours.
- 	-2000 to: 5000 do: [:yr |
- 		lxdt := LXDateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		dt := DateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		self assert: dt minute equals: lxdt minute].
- !

Item was removed:
- ----- Method: LXDateAndTimeConversionTest>>testMonth (in category 'testing') -----
- testMonth
- 
- 	| day dt hour lxdt min mo nano offset sec yr |
- 	yr := 1969.
- 	mo := 12.
- 	day := 2.
- 	hour := 2.
- 	min := 3.
- 	sec := 4.
- 	nano := 5.
- 	offset := 6 hours.
- 	lxdt := LXDateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 	dt := DateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 	self assert: 12 equals: dt month.
- 	self assert: 12 equals: lxdt month.
- 
- 	(2105 to: -1105 by: 20)
- 		do: [:year |
- 			1 to: 12 do: [:m |
- 				lxdt := LXDateAndTime 
- 					year: year month: m day: day 
- 					hour: hour minute: min second: sec nanoSecond: nano 
- 					offset: offset.
- 				dt := DateAndTime 
- 					year: year month: m day: day 
- 					hour: hour minute: min second: sec nanoSecond: nano 
- 					offset: offset.
- 				self assert: m equals: dt month.
- 				self assert: m equals: lxdt month]]
- !

Item was removed:
- ----- Method: LXDateAndTimeConversionTest>>testNanoSecond (in category 'testing') -----
- testNanoSecond
- 
- 	| day dt hour lxdt min mo nano offset sec yr |
- 	yr := 1969.
- 	mo := 12.
- 	day := 2.
- 	hour := 2.
- 	min := 3.
- 	sec := 4.
- 	nano := 5.
- 	offset := 6 hours.
- 	lxdt := LXDateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 	dt := DateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 	self assert: 5 equals: dt nanoSecond.
- 	self assert: 5 equals: lxdt nanoSecond.
- 
- 	(2105 to: -1105 by: 20)
- 		do: [:year |
- 			lxdt := LXDateAndTime 
- 				year: year month: mo day: day 
- 				hour: hour minute: min second: sec nanoSecond: nano 
- 				offset: offset.
- 			dt := DateAndTime 
- 				year: year month: mo day: day 
- 				hour: hour minute: min second: sec nanoSecond: nano 
- 				offset: offset.
- 			self assert: 5 equals: dt nanoSecond.
- 			self assert: 5 equals: lxdt nanoSecond]
- 
- !

Item was removed:
- ----- Method: LXDateAndTimeConversionTest>>testSecond (in category 'testing') -----
- testSecond
- 	"(self selector: #testSecond) debug"
- 
- 	| day dt hour lxdt min mo nano offset sec |
- 	mo := 12.
- 	day := 2.
- 	hour := 2.
- 	min := 3.
- 	sec := 4.
- 	nano := 5.
- 	offset := 6 hours.
- 	-2000 to: 5000 do: [:yr |
- 		lxdt := LXDateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		dt := DateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 		self assert: dt second equals: lxdt second].
- !

Item was removed:
- ----- Method: LXDateAndTimeConversionTest>>testYear (in category 'testing') -----
- testYear
- 
- 	| day dt hour lxdt min mo nano offset sec yr |
- 	yr := 1969.
- 	mo := 12.
- 	day := 2.
- 	hour := 2.
- 	min := 3.
- 	sec := 4.
- 	nano := 5.
- 	offset := 6 hours.
- 	lxdt := LXDateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 	dt := DateAndTime 
- 			year: yr month: mo day: day 
- 			hour: hour minute: min second: sec nanoSecond: nano 
- 			offset: offset.
- 	self assert: 1969 equals: dt year.
- 	self assert: 1969 equals: lxdt year.
- 
- 	(2105 to: -1105 by: 20)
- 		do: [:year |
- 			lxdt := LXDateAndTime 
- 				year: year month: mo day: day 
- 				hour: hour minute: min second: sec nanoSecond: nano 
- 				offset: offset.
- 			dt := DateAndTime 
- 				year: year month: mo day: day 
- 				hour: hour minute: min second: sec nanoSecond: nano 
- 				offset: offset.
- 			self assert: year equals: dt year.
- 			self assert: year equals: lxdt year]
- 
- !

Item was removed:
- TestCase subclass: #LXDateAndTimeEpochTest
- 	instanceVariableNames: 'aDateAndTime aDuration aTimeZone localTimeZoneToRestore'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Chronology-Core'!
- 
- !LXDateAndTimeEpochTest commentStamp: 'tlk 1/6/2004 18:27' prior: 0!
- I represent one of several Sunit test Cases intentended to provide complete coverage  for the Chronology set of classes as part of the external testing. The other Chronology sunit test cases are:
-  DateTestCase
-  DateAndTimeLeapTestCase,
-  DurationTestCase,
-  ScheduleTestCase
-  TimeStampTestCase
-  TimespanDoTestCase, 
-  TimespanDoSpanAYearTestCase, 
-  TimespanTestCase, 
-  YearMonthWeekTestCase.  
- These tests attempt to exercise all public and private methods.  Except, they do not explicitly depreciated methods. tlk
- My fixtures are:
- aDateAndTime = January 01, 1901 midnight (the start of the Squeak epoch) with localTimeZone = Grenwhich Meridian (local offset = 0 hours)
- aDuration = 1 day, 2 hours, 3, minutes, 4 seconds and 5 nano seconds.
- aTimeZone =  'Epoch Test Time Zone', 'ETZ' , offset: 12 hours, 15 minutes. !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>setUp (in category 'running') -----
- setUp
-      localTimeZoneToRestore := LXDateAndTime localTimeZone.
- 	aDateAndTime :=  LXDateAndTime localTimeZone: TimeZone default; epoch.
- 	aTimeZone := TimeZone offset: (Duration minutes: 135) name: 'Epoch Test Time Zone' abbreviation: 'ETZ'.
- 	aDuration := Duration days: 1 hours: 2 minutes: 3 seconds: 4 nanoSeconds: 5 !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>tearDown (in category 'running') -----
- tearDown
-      LXDateAndTime localTimeZone: localTimeZoneToRestore.
-      "wish I could remove the time zones I added earlier, tut there is no method for that"
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testAsDate (in category 'testing') -----
- testAsDate
- 	self assert: aDateAndTime asDate =   'January 1, 1901' asDate.
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testAsDateAndTime (in category 'testing') -----
- testAsDateAndTime
- 	self assert: aDateAndTime asLXDateAndTime =  aDateAndTime
- 	
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testAsDuration (in category 'testing') -----
- testAsDuration
- 	self assert: aDateAndTime asDuration =  0 asDuration
- 	
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testAsLocal (in category 'testing') -----
- testAsLocal
- 	self assert: aDateAndTime asLocal =  aDateAndTime.
- 	self assert: aDateAndTime asLocal = (aDateAndTime utcOffset: aDateAndTime class localOffset)
- 	
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testAsMonth (in category 'testing') -----
- testAsMonth
- 	self assert: aDateAndTime asMonth = (Month month: 'January' year: 1901). 
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testAsNanoSeconds (in category 'testing') -----
- testAsNanoSeconds
- 	self assert: aDateAndTime asNanoSeconds =  0 asDuration asNanoSeconds
- 	
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testAsSeconds (in category 'testing') -----
- testAsSeconds
- 	self assert: aDateAndTime asSeconds =  0 asDuration asSeconds
- 	
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testAsTime (in category 'testing') -----
- testAsTime
- 	self assert: aDateAndTime asTime =  Time midnight.
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testAsTimeStamp (in category 'testing') -----
- testAsTimeStamp
- 	self assert: aDateAndTime asTimeStamp =  TimeStamp new.
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testAsUTC (in category 'testing') -----
- testAsUTC
- 	self assert: aDateAndTime asUTC =  aDateAndTime
-           !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testAsWeek (in category 'testing') -----
- testAsWeek
- 	self assert: aDateAndTime asWeek = (Week starting: '12-31-1900' asDate). 
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testAsYear (in category 'testing') -----
- testAsYear
- 	self assert: aDateAndTime asYear =   (Year starting: '01-01-1901' asDate). 
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testCurrent (in category 'testing') -----
- testCurrent
- 	self deny: aDateAndTime =  (LXDateAndTime current).
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testDateTime (in category 'testing') -----
- testDateTime
- 	self assert: aDateAndTime =  (LXDateAndTime date: '01-01-1901' asDate time: '00:00:00' asTime)
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testDay (in category 'testing') -----
- testDay
- 	self assert: aDateAndTime day =   LXDateAndTime new day
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testDayMonthYearDo (in category 'testing') -----
- testDayMonthYearDo
- 	|iterations|
- 	iterations := 0.
- 	self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  iterations := iterations + 1])  = 1.
- 	self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  eachYear])  = 1901.
- 	self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  eachMonth]) = 1.
- 	self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  eachDay]) = 1.
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testDayOfMonth (in category 'testing') -----
- testDayOfMonth
- 	self assert: aDateAndTime dayOfMonth  = 1.
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testDayOfWeek (in category 'testing') -----
- testDayOfWeek
- 	self assert: aDateAndTime dayOfWeek  = 3.
- 	self assert: aDateAndTime dayOfWeekAbbreviation = 'Tue'.
- 	self assert: aDateAndTime dayOfWeekName = 'Tuesday'.
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testDayOfYear (in category 'testing') -----
- testDayOfYear
- 	self assert: aDateAndTime dayOfYear  = 1.
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testDaysInMonth (in category 'testing') -----
- testDaysInMonth
- 	self assert: aDateAndTime daysInMonth  = 31.
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testDaysInYear (in category 'testing') -----
- testDaysInYear
- 	self assert: aDateAndTime daysInYear  = 365.
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testDaysLeftInYear (in category 'testing') -----
- testDaysLeftInYear
- 	self assert: aDateAndTime daysLeftInYear  = 364.
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testDuration (in category 'testing') -----
- testDuration
- 	self assert: aDateAndTime duration  = 0 asDuration.
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testEpoch (in category 'testing') -----
- testEpoch
- 	self assert: aDateAndTime =  '1901-01-01T00:00:00+00:00' asLXDateAndTime
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testFirstDayOfMonth (in category 'testing') -----
- testFirstDayOfMonth
- 	self assert: aDateAndTime firstDayOfMonth =   1
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testFromSeconds (in category 'testing') -----
- testFromSeconds
- 	self assert: aDateAndTime =  (LXDateAndTime fromSeconds: 0).
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testFromString (in category 'testing') -----
- testFromString
- 	self assert: aDateAndTime =  (LXDateAndTime fromString: ' 1901-01-01T00:00:00+00:00').
- 	self assert: aDateAndTime =  (LXDateAndTime fromString: ' 1901-01-01T00:00:00').
- 	self assert: aDateAndTime =  (LXDateAndTime fromString: ' 1901-01-01T00:00').
- 	self assert: aDateAndTime =  (LXDateAndTime fromString: ' 1901-01-01T00:00:00+00:00').
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testHash (in category 'testing') -----
- testHash
- 	self assert: aDateAndTime hash =    LXDateAndTime new hash.
- 	self assert: aDateAndTime hash =     112557138
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testHour (in category 'testing') -----
- testHour
- 	self assert: aDateAndTime hour =    aDateAndTime hour24.
- 	self assert: aDateAndTime hour =    0.
- 	self assert: aDateAndTime hour =    aDateAndTime hours
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testHour12 (in category 'testing') -----
- testHour12
- 	self assert: aDateAndTime hour12  = LXDateAndTime new hour12.
- 	self assert: aDateAndTime hour12  = 12
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testIsLeapYear (in category 'testing') -----
- testIsLeapYear
- 	self deny: aDateAndTime isLeapYear
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testJulianDayNumber (in category 'testing') -----
- testJulianDayNumber
- 	self assert: aDateAndTime =  (LXDateAndTime julianDayNumber: 2415386).
- 	self assert: aDateAndTime julianDayNumber = 2415386.!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testLessThan (in category 'testing') -----
- testLessThan
- 	self assert: aDateAndTime  < (aDateAndTime + '1:00:00:00').
- 	self assert: aDateAndTime + -1 < aDateAndTime.
- 	!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testMeridianAbbreviation (in category 'testing') -----
- testMeridianAbbreviation
- 	self assert: aDateAndTime meridianAbbreviation = 'AM'.
- 	!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testMiddleOf (in category 'testing') -----
- testMiddleOf
- 	self assert: (aDateAndTime middleOf: '2:00:00:00' asDuration) = 
- 	 (Timespan starting: '12-31-1900' asDate duration: 2 days).
- 	
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testMidnight (in category 'testing') -----
- testMidnight
- 	self assert: aDateAndTime midnight =  aDateAndTime
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testMinus (in category 'testing') -----
- testMinus
- 	self assert: aDateAndTime - aDateAndTime =  '0:00:00:00' asDuration.
- 	self assert: aDateAndTime - '0:00:00:00' asDuration = aDateAndTime.
- 	self assert: aDateAndTime - aDuration =  (LXDateAndTime year: 1900 month: 12 day: 30 hour: 21 minute: 56 second: 55 nanoSecond: 999999995 offset: 0 hours ).
- 	" I believe this Failure is a bug in the nanosecond part of (LXDateAndTime >> year:month:day:hour:minute:second:nanoSecond:offset:)" !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testMinute (in category 'testing') -----
- testMinute
- 	self assert: aDateAndTime minute =  0
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testMinutes (in category 'testing') -----
- testMinutes
- 	self assert: aDateAndTime minutes = 0
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testMonth (in category 'testing') -----
- testMonth
- 	self assert: aDateAndTime month  = 1.
- 	self assert: aDateAndTime monthAbbreviation = 'Jan'.
- 	self assert: aDateAndTime monthName = 'January'.
- 	self assert: aDateAndTime monthIndex = 1.!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testNanoSecond (in category 'testing') -----
- testNanoSecond
- 	self assert: aDateAndTime nanoSecond =  0
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testNew (in category 'testing') -----
- testNew
- 	self assert: aDateAndTime =  (LXDateAndTime new).
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testNoon (in category 'testing') -----
- testNoon
- 	self assert: aDateAndTime noon = '1901-01-01T12:00:00+00:00' asLXDateAndTime!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testNow (in category 'testing') -----
- testNow
- 	self deny: aDateAndTime =  (LXDateAndTime now).
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testOffset (in category 'testing') -----
- testOffset
- 	self assert: aDateAndTime offset =  '0:00:00:00' asDuration.
-      self assert: (aDateAndTime offset: '0:12:00:00') =  '1901-01-01T00:00:00+12:00' asLXDateAndTime!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testPlus (in category 'testing') -----
- testPlus
- 	self assert: aDateAndTime + '0:00:00:00' = aDateAndTime.
- 	self assert: aDateAndTime + 0 = aDateAndTime.
- 	self assert: aDateAndTime + aDuration = (LXDateAndTime year: 1901 month: 1 day: 2 hour: 2 minute: 3 second: 4 nanoSecond: 5 offset: 0 hours )
- 	" I believe this is a bug in the nanosecond part of (DateAndTime >> year:month:day:hour:minute:second:nanoSecond:offset:)"
- 	
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testPrintOn (in category 'testing') -----
- testPrintOn
- 	| ref ws |
- 	ref := '1901-01-01T00:00:00+00:00'.
- 	ws := '' writeStream.
- 	aDateAndTime printOn: ws.
- 	self assert: ws contents = ref.
- 	ref  := 'a TimeZone(ETZ)'.
- 	ws := '' writeStream.
- 	aTimeZone printOn:  ws.
- 	self assert: ws contents = ref!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testSecond (in category 'testing') -----
- testSecond
- 	self assert: aDateAndTime second =  0
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testSeconds (in category 'testing') -----
- testSeconds
- 	self assert: aDateAndTime seconds =  0
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testTicks (in category 'testing') -----
- testTicks
- 	self assert: aDateAndTime ticks =  (LXDateAndTime julianDayNumber: 2415386) ticks.
- 	self assert: aDateAndTime ticks = #(2415386 0 0)!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testTicksOffset (in category 'testing') -----
- testTicksOffset
- 	self assert: aDateAndTime =  (aDateAndTime ticks:  #(2415386 0 0) offset: LXDateAndTime localOffset).
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testTo (in category 'testing') -----
- testTo
- 	self assert: (aDateAndTime to: aDateAndTime) = (LXDateAndTime new to: LXDateAndTime new) 
- 	"MessageNotUnderstood: UndefinedObject>>starting:ending:  where UndefinedObject is Timespan "!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testToBy (in category 'testing') -----
- testToBy
- 	self assert: (aDateAndTime to: aDateAndTime + 10 days by: 5 days) = 
- 				(LXDateAndTime new to: LXDateAndTime new + 10 days by: 5 days ) 
- 	"MessageNotUnderstood: UndefinedObject>>starting:ending:  where UndefinedObject is Timespan "!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testToByDo (in category 'testing') -----
- testToByDo
- 	"self assert: (aDateAndTime to: aDateAndTime + 10 days by: 5 days do: []) =  "
- 	"MessageNotUnderstood: UndefinedObject>>starting:ending:  where UndefinedObject is Timespan "!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testToday (in category 'testing') -----
- testToday
- 	self deny: aDateAndTime =  (LXDateAndTime today).
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testTommorrow (in category 'testing') -----
- testTommorrow
- 	self assert: (LXDateAndTime today + 24 hours) =  (LXDateAndTime tomorrow).
- 	self deny: aDateAndTime =  (LXDateAndTime tomorrow).
-      "MessageNotUnderstood: Date class>>starting:"!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testUtcOffset (in category 'testing') -----
- testUtcOffset
-      self assert: (aDateAndTime utcOffset: '0:12:00:00') =  '1901-01-01T12:00:00+12:00' asLXDateAndTime!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testYear (in category 'testing') -----
- testYear
- 	self assert: aDateAndTime year = 1901.
- 	!

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testYearDay (in category 'testing') -----
- testYearDay
- 	self assert: aDateAndTime =  (LXDateAndTime year: 1901 day: 1).
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testYearDayHourMinuteSecond (in category 'testing') -----
- testYearDayHourMinuteSecond
- 	self assert: aDateAndTime =  (LXDateAndTime year: 1901 day: 1 hour: 0 minute: 0 second: 0).
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testYearMonthDay (in category 'testing') -----
- testYearMonthDay
- 	self assert: aDateAndTime =  (LXDateAndTime year: 1901 month: 1 day: 1).
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testYearMonthDayHourMinuteSecond (in category 'testing') -----
- testYearMonthDayHourMinuteSecond
- 	self assert: aDateAndTime =  (LXDateAndTime year: 1901 month: 1 day: 1 hour: 0 minute: 0 second: 0).
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testYearMonthDayHourMinuteSecondNanosSecondOffset (in category 'testing') -----
- testYearMonthDayHourMinuteSecondNanosSecondOffset
- 	self assert: aDateAndTime =  (LXDateAndTime year: 1901 month: 1 day: 1 hour: 0 minute: 0 second: 0 nanoSecond: 0 offset:0 hours ).
- 	self assert: ((LXDateAndTime year: 1 month: 1 day: 1 hour: 0 minute: 0 second: 0 nanoSecond: 0 offset: 0 hours ) +
- 				(Duration days: 1 hours: 2 minutes: 3 seconds: 4  nanoSeconds: 5) ) =  	
- 				(LXDateAndTime year: 1 month: 1 day: 2 hour: 2 minute: 3 second: 4 nanoSecond: 5 offset: 0 hours ) 
- 	" I believe this is a bug in the nanosecond part of (DateAndTime >> year:month:day:hour:minute:second:nanoSecond:offset:)"" I believe this is a bug in the nanosecond part of (DateAndTime >> year:month:day:hour:minute:second:nanoSecond:offset:)"   
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testYesterday (in category 'testing') -----
- testYesterday
- 	self deny: aDateAndTime =  (LXDateAndTime yesterday).
- !

Item was removed:
- ----- Method: LXDateAndTimeEpochTest>>testtimeZone (in category 'testing') -----
- testtimeZone
- 	self assert: aDateAndTime timeZoneName	= 'Universal Time'.
- 	self assert: aDateAndTime timeZoneAbbreviation	=  'UTC'
- !

Item was removed:
- TestCase subclass: #LXDateAndTimeLeapTest
- 	instanceVariableNames: 'aDateAndTime aDuration aTimeZone localTimeZoneToRestore'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Chronology-Core'!
- 
- !LXDateAndTimeLeapTest commentStamp: 'tlk 1/6/2004 17:54' prior: 0!
- I represent one of several Sunit test Cases intentended to provide complete coverage for the Chronology set of classes as part of the external testing. tlk.
- My fixtures are:
- aDateAndTime = February 29, 2004 1:33 PM with offset: 2 hours
- aDuration = 15 days, 14 hours, 13 minutes, 12 seconds and 11 nano seconds.
- aTimeZone =  Grenwhich Meridian (local offset = 0 hours) !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>setUp (in category 'running') -----
- setUp
- 	localTimeZoneToRestore := LXDateAndTime localTimeZone.
- 	LXDateAndTime localTimeZone: TimeZone default.
- 	aDateAndTime := (LXDateAndTime year: 2004 month: 2 day: 29 hour: 13 minute: 33 second: 0 offset: 2 hours).
- 	aTimeZone := TimeZone default.
- 	aDuration := Duration days: 0 hours: 13 minutes: 33 seconds: 0 nanoSeconds: 0
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>tearDown (in category 'running') -----
- tearDown
-      LXDateAndTime localTimeZone: localTimeZoneToRestore.
-      "wish I could remove the time zones I added earlier, tut there is no method for that"
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testAsDate (in category 'testing') -----
- testAsDate
- 	self assert: (aDateAndTime offset: LXDateAndTime localTimeZone offset) asDate = 'February 29, 2004' asDate!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testAsDuration (in category 'testing') -----
- testAsDuration
- 	self assert: aDateAndTime asDuration =  aDuration
- 	
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testAsLocal (in category 'testing') -----
- testAsLocal
- 	self assert: aDateAndTime asLocal =  aDateAndTime.
- 	self assert: aDateAndTime asLocal = (aDateAndTime utcOffset: aDateAndTime class localOffset)
- 	
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testAsMonth (in category 'testing') -----
- testAsMonth
- 	self assert:
- 		(aDateAndTime offset: Month defaultOffset) asMonth =
- 			(Month
- 				month: 'February'
- 				year: 2004)!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testAsNanoSeconds (in category 'testing') -----
- testAsNanoSeconds
- 	self assert: aDateAndTime asNanoSeconds =  aDuration asNanoSeconds.
- 	self assert: aDateAndTime asNanoSeconds = 48780000000000
- 	
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testAsSeconds (in category 'testing') -----
- testAsSeconds
- 	self assert: aDuration asSeconds = 48780.
- 	self assert: aDateAndTime asSeconds = 3255514380!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testAsTime (in category 'testing') -----
- testAsTime
- 	self assert: aDateAndTime asTime = (Time hour: 13 minute: 33 second: 0)
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testAsTimeStamp (in category 'testing') -----
- testAsTimeStamp
- 	self assert: aDateAndTime asTimeStamp =  ((TimeStamp readFrom: '2-29-2004 1:33 pm' readStream) offset: 2 hours).
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testAsUTC (in category 'testing') -----
- testAsUTC
- 	self assert: aDateAndTime asUTC =  aDateAndTime
-           !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testAsWeek (in category 'testing') -----
- testAsWeek
- 	self assert: (aDateAndTime offset: LXDateAndTime localTimeZone offset) asWeek = (Week starting: '02-29-2004' asDate)!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testAsYear (in category 'testing') -----
- testAsYear
- 	| year |
- 	year := (aDateAndTime offset: LXDateAndTime localTimeZone offset) asYear.
- 	self assert: year = (Year starting: '02-29-2004' asDate).
- 	self deny: year = (Year starting: '01-01-2004' asDate)!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testDay (in category 'testing') -----
- testDay
- 	self assert: aDateAndTime day =   60. 
- 	self deny: aDateAndTime day =   29 !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testDayMonthYearDo (in category 'testing') -----
- testDayMonthYearDo
- 	self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  eachYear])  = 2004.
- 	self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  eachMonth]) = 2.
- 	self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  eachDay]) = 29.
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testDayOfMonth (in category 'testing') -----
- testDayOfMonth
- 	self assert: aDateAndTime dayOfMonth  = 29.
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testDayOfWeek (in category 'testing') -----
- testDayOfWeek
- 	self assert: aDateAndTime dayOfWeek  = 1.
- 	self assert: aDateAndTime dayOfWeekAbbreviation = 'Sun'.
- 	self assert: aDateAndTime dayOfWeekName = 'Sunday'.
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testDayOfYear (in category 'testing') -----
- testDayOfYear
- 	self assert: aDateAndTime dayOfYear  = 60.
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testDaysInMonth (in category 'testing') -----
- testDaysInMonth
- 	self assert: aDateAndTime daysInMonth  = 29.
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testDaysInYear (in category 'testing') -----
- testDaysInYear
- 	self assert: aDateAndTime daysInYear  = 366.
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testDaysLeftInYear (in category 'testing') -----
- testDaysLeftInYear
- 	self assert: aDateAndTime daysLeftInYear  = 306.
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testFirstDayOfMonth (in category 'testing') -----
- testFirstDayOfMonth
- 	self deny: aDateAndTime firstDayOfMonth =  1.
- 	self assert: aDateAndTime firstDayOfMonth = 32
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testFromString (in category 'testing') -----
- testFromString
- 	self assert: aDateAndTime =  (LXDateAndTime fromString: ' 2004-02-29T13:33:00+02:00').
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testHash (in category 'testing') -----
- testHash
- 	self assert: aDateAndTime hash =      16256473
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testHour (in category 'testing') -----
- testHour
- 	self assert: aDateAndTime hour =    aDateAndTime hour24.
- 	self assert: aDateAndTime hour =    13.
- 	self assert: aDateAndTime hour =    aDateAndTime hours
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testHour12 (in category 'testing') -----
- testHour12
- 	self assert: aDateAndTime hour12  =   1.
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testIsLeapYear (in category 'testing') -----
- testIsLeapYear
- 	self assert: aDateAndTime isLeapYear
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testLessThan (in category 'testing') -----
- testLessThan
- 	self assert: aDateAndTime  < (aDateAndTime + '1:00:00:00').
- 	self assert: aDateAndTime + -1 < aDateAndTime.
- 	!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testMeridianAbbreviation (in category 'testing') -----
- testMeridianAbbreviation
- 	self assert: aDateAndTime meridianAbbreviation = 'PM'.
- 	!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testMiddleOf (in category 'testing') -----
- testMiddleOf
- 	self assert: (aDateAndTime middleOf: aDuration)  = 
- 	 (Timespan starting: (LXDateAndTime year: 2004 month: 2 day: 29 hour: 6 minute: 46 second: 30 offset: 2 hours)
- 	duration: (Duration days: 0 hours: 13 minutes: 33 seconds: 0 nanoSeconds: 0 ))
- 	!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testMidnight (in category 'testing') -----
- testMidnight
- 	| midnight |
- 	midnight := (aDateAndTime offset: LXDateAndTime localTimeZone offset) midnight.
- 	self assert: midnight = '2004-02-29T00:00:00+00:00' asLXDateAndTime.
- 	self deny: midnight = '2004-02-29T00:00:00+02:00' asLXDateAndTime!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testMinute (in category 'testing') -----
- testMinute
- 	self assert: aDateAndTime minute =  33
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testMinutes (in category 'testing') -----
- testMinutes
- 	self assert: aDateAndTime minutes = 33
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testMonth (in category 'testing') -----
- testMonth
- 	self assert: aDateAndTime month  = 2.
- 	self assert: aDateAndTime monthAbbreviation = 'Feb'.
- 	self assert: aDateAndTime monthName = 'February'.
- 	self assert: aDateAndTime monthIndex = 2.!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testMonthParsing (in category 'testing') -----
- testMonthParsing
- 	self assert:
- 		(Month readFrom: 'Feb 2011' readStream) =
- 			(Month
- 				month: 2
- 				year: 2011)!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testNanoSecond (in category 'testing') -----
- testNanoSecond
- 	self assert: aDateAndTime nanoSecond =  0
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testNoon (in category 'testing') -----
- testNoon
- 	self assert: aDateAndTime noon =  '2004-02-29T12:00:00+00:00' asLXDateAndTime!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testOffset (in category 'testing') -----
- testOffset
- 	self assert: aDateAndTime offset =  '0:02:00:00' asDuration.
-      self assert: (aDateAndTime offset: '0:12:00:00') =  '2004-02-29T13:33:00+12:00' asLXDateAndTime!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testPrintOn (in category 'testing') -----
- testPrintOn
- 	| ref ws |
- 	ref := '2004-02-29T13:33:00+02:00'.
- 	ws := '' writeStream.
- 	aDateAndTime printOn: ws.
- 	self assert: ws contents = ref.
- 	ref  := 'a TimeZone(UTC)'.
- 	ws := '' writeStream.
- 	aTimeZone printOn:  ws.
- 	self assert: ws contents = ref	!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testSecond (in category 'testing') -----
- testSecond
- 	self assert: aDateAndTime second =  0
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testSeconds (in category 'testing') -----
- testSeconds
- 	self assert: aDateAndTime seconds =  0
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testTicks (in category 'testing') -----
- testTicks
- 	self assert: aDateAndTime ticks =  ((LXDateAndTime julianDayNumber: 2453065) + 48780 seconds) ticks.
- 	self assert: aDateAndTime ticks =  #(2453065 48780 0)!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testTicksOffset (in category 'testing') -----
- testTicksOffset
- 	self assert: aDateAndTime =  (aDateAndTime ticks:  #(2453065 48780 0) offset: LXDateAndTime localOffset).
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testUtcOffset (in category 'testing') -----
- testUtcOffset
-      self assert: (aDateAndTime utcOffset: '0:02:00:00') =  '2004-02-29T13:33:00+02:00' asLXDateAndTime!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testYear (in category 'testing') -----
- testYear
- 	self assert: aDateAndTime year = 2004.
- 	!

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testYearDayHourMinuteSecond (in category 'testing') -----
- testYearDayHourMinuteSecond
- 	self assert: aDateAndTime =  ((LXDateAndTime year: 2004 day: 60 hour: 13 minute: 33 second: 0) offset: 2 hours).
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testYearMonthDayHourMinuteSecond (in category 'testing') -----
- testYearMonthDayHourMinuteSecond
- 	self assert: aDateAndTime =  ((LXDateAndTime year: 2004 month: 2 day: 29 hour: 13 minute: 33 second: 0) offset: 2 hours).
- !

Item was removed:
- ----- Method: LXDateAndTimeLeapTest>>testtimeZone (in category 'testing') -----
- testtimeZone
- 	self assert: aDateAndTime timeZoneName	= 'Universal Time'.
- 	self assert: aDateAndTime timeZoneAbbreviation	=  'UTC'
- !

Item was removed:
- ClassTestCase subclass: #LXDateAndTimeTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Chronology-Core'!

Item was removed:
- ----- Method: LXDateAndTimeTest>>classToBeTested (in category 'Coverage') -----
- classToBeTested
- 	^ LXDateAndTime
- !

Item was removed:
- ----- Method: LXDateAndTimeTest>>selectorsToBeIgnored (in category 'Coverage') -----
- selectorsToBeIgnored
- 	| private | 
- 	private := #( #printOn: ).
- 	^ super selectorsToBeIgnored, private
- !

Item was removed:
- ----- Method: LXDateAndTimeTest>>testArithmeticAcrossDateBoundary (in category 'Tests') -----
- testArithmeticAcrossDateBoundary
- 	| t1 t2 |
- 	t1 := '2004-01-07T11:55:00+00:00' asLXDateAndTime. 
- 	t2 := t1 - ( (42900+1) seconds).  
- 	self 
- 		assert: t2 = ('2004-01-06T23:59:59+00:00' asLXDateAndTime)
- 		
- !

Item was removed:
- ----- Method: LXDateAndTimeTest>>testDateTimeDenotation1 (in category 'Tests') -----
- testDateTimeDenotation1
-   "LXDateAndTimeTest new testDateTimeDenotation1"
- 	
- 	 " Detroit is 5 hours behind UTC, this offset to UTC is therefore written with a minus sign. This example tests the correct interpretation of the DateAndTime denotation. "
- 	| twoPmInLondon twoPmUTCInLocalTimeOfDetroit nineAmInDetroit |
- 	twoPmInLondon := LXDateAndTime
- 				year: 2004
- 				month: 11
- 				day: 2
- 				hour: 14
- 				minute: 0
- 				second: 0
- 				offset: 0 hours.
- 	twoPmUTCInLocalTimeOfDetroit := twoPmInLondon utcOffset: -5 hours.
- 	nineAmInDetroit  := '2004-11-02T09:00:00-05:00' asLXDateAndTime.
- 	self assert:  twoPmUTCInLocalTimeOfDetroit = nineAmInDetroit.
- 	
- !

Item was removed:
- ----- Method: LXDateAndTimeTest>>testDateTimeDenotation2 (in category 'Tests') -----
- testDateTimeDenotation2
-   "LXDateAndTimeTest new testDateTimeDenotation2"
- 	
- 	 " Moscow is 3 hours ahead UTC, this offset to UTC is therefore positive. This example tests the correct interpretation of the DateAndTime denotation. "
- 	| lateEveningInLondon lateEveningInLocalTimeOfMoscow
- 	 localMoscowTimeFromDenotation |
- 	lateEveningInLondon := LXDateAndTime
- 				year: 2004
- 				month: 11
- 				day: 30
- 				hour: 23
- 				minute: 30
- 				second: 0
- 				offset: 0 hours.
- 	lateEveningInLocalTimeOfMoscow := lateEveningInLondon utcOffset: 3 hours.
- 	localMoscowTimeFromDenotation  := '2004-12-01T02:30:00+03:00' asLXDateAndTime.
- 	self assert:  lateEveningInLocalTimeOfMoscow = localMoscowTimeFromDenotation.
- 	
- !

Item was removed:
- ----- Method: LXDateAndTimeTest>>testErrorWhenDayIsAfterMonthEnd (in category 'Tests') -----
- testErrorWhenDayIsAfterMonthEnd
- 	self
- 		should:
- 			[LXDateAndTime
- 				year: 2004
- 				month: 2
- 				day: 30]
- 		raise: Error.!

Item was removed:
- ----- Method: LXDateAndTimeTest>>testErrorWhenDayIsBeforeMonthStart (in category 'Tests') -----
- testErrorWhenDayIsBeforeMonthStart
- 	self
- 		should:
- 			[LXDateAndTime
- 				year: 2004
- 				month: 2
- 				day: -1]
- 		raise: Error.
- 	self
- 		should:
- 			[LXDateAndTime
- 				year: 2004
- 				month: 2
- 				day: 0]
- 		raise: Error.!

Item was removed:
- ----- Method: LXDateAndTimeTest>>testFromString (in category 'Tests') -----
- testFromString
- 	| fromString fromStringNoOffset fromStringUTC |
- 	fromString := LXDateAndTime fromString: '-1199-01-05T20:33:14.321-05:00'.
- 	self assert: (fromString printString = '-1199-01-05T20:33:14.321-05:00').
- 	
- 	"if no offset is provided, the local offset should be used"
- 	fromStringNoOffset := LXDateAndTime fromString: '-1199-01-05T20:33:14.321'.
- 	self assert: (fromStringNoOffset offset = LXDateAndTime localOffset).
- 	
- 	"if a string contains the UTC designator Z, the local offset should not be used"
- 	fromStringUTC := LXDateAndTime fromString: '2011-08-26T18:00:03Z'.
- 	self assert: (fromStringUTC printString = '2011-08-26T18:00:03+00:00').!

Item was removed:
- ----- Method: LXDateAndTimeTest>>testHash (in category 'Tests') -----
- testHash
- 	| date0 date1 date2 |
- 	date0 := LXDateAndTime unixEpoch.
- 	date1 := LXDateAndTime new ticks: (date0 + 1 hours) ticks offset: 0 hours.
- 	date2 := LXDateAndTime new ticks: (date0 - 2 hours) ticks offset: -3 hours.
- 	self assert: (date1 = date2) ==> [date1 hash = date2 hash]!

Item was removed:
- ----- Method: LXDateAndTimeTest>>testInstanceCreation (in category 'Tests') -----
- testInstanceCreation
- 	| t |
- 	t := LXDateAndTime 
- 			year: 1 month: 1 day: 2 
- 			hour: 2 minute: 3 second: 4 nanoSecond: 5 
- 			offset: 6 hours.
- 	self 
- 		assert: (t julianDayNumber = 1721427);
- 		assert: (t offset = 6 hours);
- 		assert: (t hour = 2);
- 		assert: (t minute = 3);
- 		assert: (t second = 4);
- 		assert: (t nanoSecond = 5).
- 		
- !

Item was removed:
- ----- Method: LXDateAndTimeTest>>testMonotonicity (in category 'Tests') -----
- testMonotonicity
- 	| t1 t2 t3 t4 |
- 	t1 := LXDateAndTime now.
- 	t2 := LXDateAndTime now.
- 	(Delay forMilliseconds: 1000) wait.
- 	t3 := LXDateAndTime now.
- 	t4 := LXDateAndTime now.
- 	self
- 		assert: (	t1 <= t2);
- 		assert: (	t2 < t3);
- 		assert: (	t3 <= t4).
- !

Item was removed:
- ----- Method: LXDateAndTimeTest>>testPrecision (in category 'Tests') -----
- testPrecision
- 	"Verify that the clock is returning a value with accuracy of better than 1 second.  For now it seems sufficient to get two values and verify they are not the same."
- 	self
- 		assert: (LXDateAndTime now ~= LXDateAndTime now)
- !

Item was removed:
- ----- Method: LXDateAndTimeTest>>testPrintString (in category 'Tests') -----
- testPrintString
- 	"(self new setTestSelector: #testPrintString) debug"
- 	| dt dtNoOffset |
- 	dt :=LXDateAndTime
- 		year: 2004
- 		month: 11
- 		day: 2
- 		hour: 14
- 		minute: 3
- 		second: 5
- 		nanoSecond: 12345
- 		offset: (Duration seconds: (5 * 3600)).
- 	self assert: dt printString = '2004-11-02T14:03:05.000012345+05:00'.
- 	
- 	self assert: ('2002-05-16T17:20:45.1+01:01' asLXDateAndTime printString = '2002-05-16T17:20:45.1+01:01').
- 	self assert:	(' 2002-05-16T17:20:45.02+01:01' asLXDateAndTime printString = '2002-05-16T17:20:45.02+01:01').  
- 	self assert:	('2002-05-16T17:20:45.000000009+01:01' asLXDateAndTime printString =  '2002-05-16T17:20:45.000000009+01:01').
- 	self assert: ('2002-05-16T17:20:45+00:00' asLXDateAndTime printString = '2002-05-16T17:20:45+00:00' ).
- 	self assert: (' 2002-05-16T17:20:45+01:57' asLXDateAndTime printString = '2002-05-16T17:20:45+01:57').
- 	self assert: (' 2002-05-16T17:20:45-02:34' asLXDateAndTime printString = '2002-05-16T17:20:45-02:34').
- 	self assert: ('2002-05-16T17:20:45+00:00' asLXDateAndTime printString = '2002-05-16T17:20:45+00:00').
- 	self assert: ('1997-04-26T01:02:03+01:02:3' asLXDateAndTime printString = '1997-04-26T01:02:03+01:02:3').
- 	"When no offset is provided, the local one is used"
- 	dtNoOffset := '2002-05-16T17:20' asLXDateAndTime.
- 	self assert: (('2002-05-16T17:20:00*' match: dtNoOffset printString) and: [dtNoOffset offset = LXDateAndTime localOffset]).
- !

Item was removed:
- ----- Method: LXDateAndTimeTest>>testReadFrom (in category 'Tests') -----
- testReadFrom
- self assert: ((LXDateAndTime readFrom: '-1199-01-05T20:33:14.321-05:00' readStream) printString = '-1199-01-05T20:33:14.321-05:00').
-  !

Item was removed:
- ----- Method: LXDateAndTimeTest>>testSmalltalk80Accessors (in category 'Tests') -----
- testSmalltalk80Accessors
- 	| t |
- 	t := LXDateAndTime 
- 			year: 1 month: 1 day: 2 
- 			hour: 2 minute: 3 second: 4 nanoSecond: 5 
- 			offset: 6 hours.
- 	self 
- 		assert: (t hours = t hours);
- 		assert: (t minutes = t minute);
- 		assert: (t seconds = t second).
- !

Item was removed:
- ----- Method: LXDateAndTimeTest>>testTimeZoneEquivalence (in category 'Tests') -----
- testTimeZoneEquivalence
-   "LXDateAndTimeTest new testTimeZoneEquivalence"
- 	"When the clock on the wall in Detroit says 9:00am, the clock on the wall
- 	in London says 2:00pm. The Duration difference between the corresponding
- 	DateAndTime values should be zero."
- 	
- 	 " Detroit is 5 hours behind UTC, this offset to UTC is therefore written with a minus sign. This example tests both the correct interpretation of the DateAndTime denotation and correct DateAndTime arithmetics. "
- 	| twoPmInLondon nineAmInDetroit durationDifference |
- 	twoPmInLondon := '2004-11-02T14:00:00+00:00' asLXDateAndTime.
- 	nineAmInDetroit  := '2004-11-02T09:00:00-05:00' asLXDateAndTime.
- 	durationDifference := twoPmInLondon - nineAmInDetroit.
- 	self assert: durationDifference asSeconds = 0.
- 	self assert: twoPmInLondon = nineAmInDetroit
- !

Item was removed:
- ----- Method: LXDateAndTimeTest>>testTimeZoneEquivalence2 (in category 'Tests') -----
- testTimeZoneEquivalence2
-   "LXDateAndTimeTest new testTimeZoneEquivalence2"
- 	"This example demonstates the fact that
-         2004-05-24T22:40:00  UTC  is
-         2004-05-25T01:40:00  in Moscow
-      (Moscow is 3 hours ahead of UTC)  "
- 	| thisMoment thisMomentInMoscow |
-     thisMoment := LXDateAndTime year: 2004 month: 5 day: 24 hour: 22 minute: 40.
-     thisMomentInMoscow := thisMoment utcOffset: 3 hours.
- 	self assert: (thisMoment - thisMomentInMoscow) asSeconds = 0.
- 	self assert: thisMoment = thisMomentInMoscow
- !

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

Item was changed:
  ----- Method: Time class>>condenseBunches: (in category 'general inquiries') -----
  condenseBunches: aCollectionOfSeconds
  	| secArray now out pause prev bunchEnd |
  	"Identify the major intervals in a bunch of numbers.  
  	Each number is a seconds since 1901 that represents a date and time.
  	We want the last event in a bunch.  Return array of seconds for:
  	
  	Every event in the last half hour.
  		Every bunch separated by 30 min in the last 24 hours.
  	
  	Every bunch separated by two hours before that."
  
  	"Time condenseBunches: 
  		(#(20 400 401  20000 20200 20300 40000 45000  200000 201000 202000) 
  			collect: [ :tt | self totalSeconds - tt])
  "
  
+ 	secArray := aCollectionOfSeconds asSortedCollection.
- 	secArray := aCollectionOfSeconds sorted.
  	pause := 1.
  	now := self totalSeconds.
  	out := OrderedCollection new.
  	prev := 0.
  	bunchEnd := nil.
  	secArray reverseDo: [:secs | | ago | "descending"
  		ago := now - secs.
  		ago > (60*30) ifTrue: [pause := "60*30" 1800].
  		ago > (60*60*24) ifTrue: [pause := "60*120" 7200].
  		ago - prev >= pause ifTrue: [out add: bunchEnd.  bunchEnd := secs].
  		prev := ago].
  	out add: bunchEnd.
  	out removeFirst.
  	^ out
  !

Item was added:
+ ----- Method: Time class>>localMicrosecondClockWithOffset (in category 'clock') -----
+ localMicrosecondClockWithOffset
+ 	"Answer an array with local microseconds since the Smalltalk epoch and the
+ 	current seconds offset from GMT in the local time zone."
+ 
+ 	| result |
+ 	result := self posixMicrosecondClockWithOffset.
+ 	"DateAndTime unixEpoch asSeconds"
+ 	result at: 1 put: result first + ((2177452800 + result second) * 1000000).
+ 	^result!

Item was changed:
  ----- 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."
- 	current seconds offset from GMT in the local time zone."
  
  	<primitive: 'primitiveUtcWithOffset'>
  	^{0. 0}!

Item was changed:
  ----- Method: Time class>>readFrom: (in category 'smalltalk-80') -----
  readFrom: aStream
  	"Read a Time from the stream in the form:
  		<hour>:<minute>:<second> <am/pm>
  
  	<minute>, <second> or <am/pm> may be omitted.  e.g. 1:59:30 pm; 8AM; 15:30"
  
+ 	| hourMinuteSecondNano |
+ 	hourMinuteSecondNano := self readHourMinuteSecondNanoFrom: aStream.
- 	| hour minute second ampm nanos nanosBuffer |
- 	hour := Integer readFrom: aStream.
- 	minute := 0.
- 	second := 0.
- 	nanosBuffer := '000000000' copy.
- 	nanos := WriteStream on: nanosBuffer.
- 	(aStream peekFor: $:) 
- 		ifTrue: [
- 			minute := Integer readFrom: aStream.
- 			(aStream peekFor: $:) 
- 				ifTrue: [
- 					second := Integer readFrom: aStream.
- 					(aStream peekFor: $.)
- 						ifTrue: [
- 							[aStream atEnd not and: [aStream peek isDigit]]
- 								whileTrue: [nanos nextPut: aStream next]]]].
- 	aStream skipSeparators.
- 	(aStream atEnd not and: ['PApa' includes: aStream peek]) ifTrue: 
- 		[ampm := aStream next asLowercase.
- 		(ampm = $p and: [hour < 12]) ifTrue: [hour := hour + 12].
- 		(ampm = $a and: [hour = 12]) ifTrue: [hour := 0].
- 		(aStream peekFor: $m) ifFalse: [aStream peekFor: $M ]].
  	^ self 
+ 		hour: hourMinuteSecondNano first 
+ 		minute: hourMinuteSecondNano second 
+ 		second: hourMinuteSecondNano third 
+ 		nanoSecond: hourMinuteSecondNano fourth
- 		hour: hour 
- 		minute: minute 
- 		second: second 
- 		nanoSecond: nanosBuffer asInteger
  
  	"Time readFrom: (ReadStream on: '2:23:09 pm')"!

Item was removed:
- ----- Method: Time class>>utcMicrosecondClockWithOffset (in category 'clock') -----
- utcMicrosecondClockWithOffset
- 	"Answer an array with UTC microseconds since the Smalltalk epoch and the
- 	current seconds offset from UTC in the local time zone."
- 	| offset utc |
- 	utc := self utcMicrosecondClock. 
- 	offset := (self localMicrosecondClockPrimitive - utc) // 1000000.
- 	^{utc. offset}!

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

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

Item was removed:
- ----- Method: TimeStamp 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"
- 
- 	^ LXTimeStamp year: year month: month day: day hour: hour minute: minute second: second nanoSecond: nanoCount offset: offset
- 
- !

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 changed:
  ----- Method: TimeStamp>>asTimeStamp (in category 'squeak protocol') -----
  asTimeStamp
  	"Answer the receiver as an instance of TimeStamp."
  
  	^ self!

Item was changed:
  Magnitude subclass: #Timespan
  	instanceVariableNames: 'start duration'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Chronology-Core'!
  
+ !Timespan commentStamp: 'bf 2/18/2016 14:43' prior: 0!
+ I represent a duration starting on a specific DateAndTime.
+ 
+ If my start has an offset identical to my #defaultOffset then comparisons ignore timezone offset.!
- !Timespan commentStamp: 'cmm 10/17/2018 22:00' prior: 0!
- I represent a duration starting on a specific DateAndTime.!

Item was changed:
  ----- Method: Timespan>>< (in category 'ansi protocol') -----
  < comparand
+ 
+ 	^ self start < comparand!
- 	^(self noTimezone or: [comparand noTimezone])
- 		ifTrue: [self start hasSmallerTicksThan: comparand asDateAndTime]
- 		ifFalse: [self start < comparand asDateAndTime]
- !

Item was changed:
  ----- Method: Timespan>>= (in category 'ansi protocol') -----
  = comparand
+ 	^ self class = comparand class 
+ 		and: [ self start = comparand start
+ 		and: [ self duration = comparand duration ] ]
-     ^ self class = comparand class 
-         and: [(((self noTimezone and: [comparand noTimezone]) or: [self start offset = comparand start offset])
-             ifTrue: [ self start hasEqualTicks: comparand start ]
-             ifFalse: [ self start = comparand start ])
-         and: [ self duration = comparand duration ] ]
  .!

Item was removed:
- ----- Method: Timespan>>beCanonical (in category 'squeak protocol') -----
- beCanonical
- 	"Make the receiver a canonical Date (or Month or Year) instead of a timespan of my duration starting at a specific local time.  Canonical are the most common use of Dates in applications."
- 	self stripTimezone!

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

Item was removed:
- ----- Method: Timespan>>stripTimezone (in category 'squeak protocol') -----
- stripTimezone
- 	"Chronology preserves Timespans that are extracted from DateAndTime's, making Dates, Months and Years in Squeak able to represent a true Timespan of those durations starting at a specific local DateAndTime.  In case a canonical version is needed, make the receiver independent of any Timezone by removing it."
- 	start primOffset: self class defaultOffset!

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



More information about the Packages mailing list