The Inbox: Chronology-Core-dtl.20.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Inbox: Chronology-Core-dtl.20.mcz

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

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

Name: Chronology-Core-dtl.20
Author: dtl
Time: 19 December 2018, 4:34:31.493987 pm
UUID: 6b0c69bf-2dc2-4708-8fd8-f3aedbdf410c
Ancestors: Chronology-Core-dtl.19

Bootstrap UTCDateAndTime, step 5 of 5

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

DateAndTime is now implemented wtih instance variables utcMicroseconds and localOffsetSeconds. This represents time magnitude as elapsed microseconds since the Posix epoch, with localOffsetSeconds representing local offset from UTC. The magnitude is used for comparison and duration calculations, and the local offset is used for displaying this magnitude in the context of a local time zone. The implementation ignores leap seconds, which are adjustments made to maintain earth rotational clock time in synchronization with elapsed seconds.

DateAndTime class>>now uses #primitiveUtcWithOffset to obtain current time in UTC microseconds with current local offset in seconds. The primitive provides an atomic query for UTC time and local offset as measured by the OS platform. If primitiveUtcWithOffset is not available, the traditional implementation is used, which relies on a primitive for microseconds in the local time zone and derives UTC based on the TimeZone setting.

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

Item was 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 changed:
  Timespan subclass: #Date
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: 'ChronologyConstants'
  category: 'Chronology-Core'!
 
+ !Date commentStamp: 'cmm 6/28/2016 21:36' prior: 0!
+ Instances of Date are Timespans with duration of 1 day.  As with all Chronology Timespan sub-instances, Dates can be instantiated as position values which compare equally to any other instance of the same Date, irregardless of the timezone in which either is created.
- !Date commentStamp: 'cmm 2/3/2012 17:30' prior: 0!
- Instances of Date are Timespans with duration of 1 day.
 
+ However, like the other Timespan subInstances, there are rare cases where it may be desirable to use instances of Date to represent a particular 1-day span of time at a particular locality on the globe.  All Timespans, including Dates, may specify a particular timezone offset for this purpose.!
- Their default creation assumes a start of midnight of UTC to provide the fast, globalized Dates out of the box.  The legacy behavior that creates Timezone-sensitive Dates can be used by sending #localizedDates.
- !

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 added:
+ ----- Method: Date class>>readYearMonthDayFrom: (in category 'squeak protocol') -----
+ readYearMonthDayFrom: aStream
+ "Read Date information 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)"
+ | day month year parsedNumber prefix monthIndex |
+ 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.
+ monthIndex := Integer readFrom: aStream.
+ "month := Month nameOfMonth: (Integer readFrom: aStream)"]
+ ifFalse: ["MM-DD-YY"
+ monthIndex := parsedNumber.
+ "month := Month nameOfMonth: parsedNumber."
+ day := Integer readFrom: aStream]]
+ ifFalse: ["YY-MM-DD"
+ monthIndex := Integer readFrom: aStream.
+ "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]].
+
+ monthIndex ifNil: [monthIndex := Month indexOfMonth: month].
+ ^ { year . monthIndex . day }
+ !

Item was added:
+ ----- Method: Date>>@ (in category 'squeak protocol') -----
+ @ aTime
+ ^ DateAndTime
+ date: self
+ time: aTime!

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

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

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

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

Item was changed:
+ ----- Method: DateAndTime class>>daysFromSmalltalkEpochToPosixEpoch (in category 'private') -----
- ----- 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"
 
+ ^ self utcMicroseconds: self epochOffsetMicros negated offset: 0
+ !
- | uSec |
- self flag: #FIXME. "see comment in fromSeconds: "
- uSec := self epochOffsetMicros negated.
- ^ self utcMicroseconds: uSec offset: self localOffsetSeconds
-
-
- "
- ^ self julianDayNumber: SqueakEpoch
- "!

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

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

Item was changed:
  ----- Method: DateAndTime class>>fromSeconds: (in category 'smalltalk-80') -----
  fromSeconds: seconds
+ "Answer a DateAndTime since the Squeak epoch: 1 January 1901
- "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.
- "dtl - Implemented for compatibiity with Squeak, but this is probably wrong"
 
+ 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 |
- self flag: #FIXME. "local versus UTC? what should we set the offset to?"
  offset := self localOffsetSeconds.
+ s := seconds - self epochOffset.
- s := seconds - self epochOffset - offset..
  uSec := s * 1000000.
  ^ self utcMicroseconds: uSec offset: offset
  !

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

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

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

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

Item was changed:
  ----- Method: DateAndTime class>>localOffset: (in category 'squeak protocol') -----
  localOffset: aDuration
+ "Override the local time zone (for testing). This disables the #automaticTimezone: preference"
+ self localTimeZone: (TimeZone offset: aDuration name: 'Local Time (override)' abbreviation: 'LTO').
- "Set the duration we are offset from UTC (done automatically in #now)"
- self localTimeZone: (TimeZone offset: aDuration name: 'Local Time' abbreviation: 'LT').
  !

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

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

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

Item was changed:
  ----- Method: DateAndTime class>>now (in category 'ansi protocol') -----
  now
+ "Answer time now as reported by #primitiveUtcWithOffset. If the primitive is not
+ available, answer the Posix epoch GMT."
 
+ self automaticTimezone
+ ifTrue: [ 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 ]
+ !
- [ | 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 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 added:
+ ----- Method: DateAndTime class>>nowAtOffset: (in category 'squeak protocol') -----
+ nowAtOffset: offsetDuration
+ "Answers the local time at places with the specified offsetDuration timezone."
+ "local time Chicago (CST)"
+ "DateAndTime nowAtOffset: -6 hours"
+
+ ^ self utcMicroseconds: Time posixMicrosecondClockWithOffset first offset: offsetDuration asSeconds
+ !

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

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

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

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

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

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

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

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 |
+ 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!
- | monthIndex daysInMonth p q r s julianDayNumber |
-
- monthIndex := month isInteger ifTrue: [month] ifFalse: [Month indexOfMonth: month].
- daysInMonth := Month
- daysInMonth: monthIndex
- forYear: year.
- day < 1 ifTrue: [self error: 'day may not be zero or negative'].
- day > daysInMonth ifTrue: [self error: 'day is after month ends'].
-
- p := (monthIndex - 14) quo: 12.
- q := year + 4800 + p.
- r := monthIndex - 2 - (12 * p).
- s := (year + 4900 + p) quo: 100.
-
- julianDayNumber :=
-   ( (1461 * q) quo: 4 ) +
- ( (367 * r) quo: 12 ) -
-   ( (3 * s) quo: 4 ) +
-   ( day - 32075 ).
-
- ^self basicNew
- setJdn: julianDayNumber
- seconds: hour * 60 + minute * 60 + second - offset asSeconds
- nano: nanoCount
- offset: offset;
- yourself!

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

Item was changed:
  ----- Method: DateAndTime>>- (in category 'ansi protocol') -----
  - operand
  "operand conforms to protocol DateAndTime or protocol Duration"
 
  ^ (operand respondsTo: #asDateAndTime)
  ifTrue:
+ [ | micros |
+ micros := utcMicroseconds - operand asDateAndTime utcMicroseconds.
+ Duration seconds: micros // 1000000 nanoSeconds: micros \\ 1000000 * 1000]
+ ifFalse:
+ [ self + (operand negated) ]
- [ | lticks rticks |
- lticks := self 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') -----
  = aDateAndTimeOrTimeStamp
  "Equal if the absolute time values match, regardless of local time transform"
  self == aDateAndTimeOrTimeStamp ifTrue: [ ^ true ].
+ ^aDateAndTimeOrTimeStamp species == DateAndTime
+ and: [ utcMicroseconds = aDateAndTimeOrTimeStamp utcMicroseconds ]!
- ((aDateAndTimeOrTimeStamp isKindOf: self class)
- or: [aDateAndTimeOrTimeStamp isKindOf: DateAndTime orOf: TimeStamp])
- ifFalse: [ ^ false ].
- ^utcMicroseconds = aDateAndTimeOrTimeStamp utcMicroseconds!

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

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

Item was removed:
- ----- Method: DateAndTime>>asLXDateAndTime (in category 'squeak protocol') -----
- asLXDateAndTime
-
- ^ LXDateAndTime utcMicroseconds: utcMicroseconds offset: localOffsetSeconds!

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

Item was changed:
+ ----- Method: DateAndTime>>asPosixSeconds (in category 'converting') -----
- ----- Method: DateAndTime>>asPosixSeconds (in category 'transitional - temporary') -----
  asPosixSeconds
 
+ ^utcMicroseconds / 1000000
+ !
- ^ (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. See asExactSeconds
+ to retain full precision of the duration in seconds."
- "Return the number of seconds since the Squeak epoch"
 
+ "Squeak traditionally used seconds since the Smalltalk epoch in local time,
+ which is undefinable. The error was probably caused by some early VM design
+ choices that have since been corrected. Assume now that the Smalltalk epoch
+ is defined relative to GMT, and that it may be treated similarly to the Posix
+ epoch except for a constant offset value.
- self flag: #FIXME. "is this whole seconds or partial? UTC or local?"
 
+ This implementation differs from earlier Squeak in that it uses seconds relative
+ to the Smalltalk epoch (not local time), and represents seconds as an arbitrary
+ precision number rather than an integer."
+
+ ^ utcMicroseconds // 1000000 + self class epochOffset
- ^ utcMicroseconds / 1000000 + self class epochOffset
  !

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

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

Item was removed:
- ----- Method: DateAndTime>>hasEqualTicks: (in category 'private') -----
- hasEqualTicks: aDateAndTime
-
- ^ (self julianDayNumber = aDateAndTime julianDayNumber)
- and: [ (self getSeconds = aDateAndTime secondsSinceMidnight)
- and: [ self nanoSecond = 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 changed:
  ----- Method: DateAndTime>>hash (in category 'ansi protocol') -----
  hash
+ ^utcMicroseconds hash!
- | totalSeconds |
- totalSeconds := self getSeconds - self offsetSeconds.
- ^ ((totalSeconds // 86400 + self julianDayNumber) hashMultiply bitXor: totalSeconds \\
- 86400) bitXor: self nanoSecond!

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

Item was added:
+ ----- Method: DateAndTime>>initializeFromPrimitive (in category 'initialize-release') -----
+ initializeFromPrimitive
+
+ Time posixMicrosecondClockWithOffset: self!

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

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

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

Item was 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
+ seconds: localOffsetSeconds
- seconds: 0
  nano: 0
+ localOffsetSeconds: localOffsetSeconds.!
- offset: self offset!

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

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

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."
 
+ | newOffset newMicros |
+ self flag: #FIXME. "check the definition of this and of #utcOffset:"
+ newOffset := anOffset asDuration asSeconds.
+ newMicros := localOffsetSeconds - newOffset * 1000000 + utcMicroseconds.
+ ^ self class utcMicroseconds: newMicros offset: newOffset
- ^ self class utcMicroseconds: utcMicroseconds offset: anOffset asDuration asSeconds
  !

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: DateAndTime>>primOffset: (in category 'private') -----
- primOffset: aDuration
- offset := aDuration!

Item was changed:
  ----- Method: DateAndTime>>printHMSOn: (in category 'squeak protocol') -----
  printHMSOn: aStream
  "Print just hh:mm:ss"
+
+ | seconds |
+ seconds := self getSeconds.
+ seconds // 3600 printOn: aStream base: 10 length: 2 padded: true.
+ aStream nextPut: $:.
+ seconds \\ 3600 // 60 printOn: aStream base: 10 length: 2 padded: true.
+ aStream nextPut: $:.
+ seconds \\ 60 printOn: aStream base: 10 length: 2 padded: true!
- aStream
- nextPutAll: (self hour asString padded: #left to: 2 with: $0);
- nextPut: $:;
- nextPutAll: (self minute asString padded: #left to: 2 with: $0);
- nextPut: $:;
- nextPutAll: (self second asString padded: #left to: 2 with: $0).
- !

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)
  "
 
+ | nanos offsetSeconds |
  self printYMDOn: aStream withLeadingSpace: printLeadingSpaceToo.
  aStream nextPut: $T.
  self printHMSOn: aStream.
+ (nanos := utcMicroseconds \\ 1000000 * 1000) = 0 ifFalse: [
+ | length |
+ aStream nextPut: $..
+ length := 9.
+ [ nanos \\ 10 = 0 ] whileTrue: [
+ nanos := nanos // 10.
+ length := length - 1 ].
+ nanos printOn: aStream base: 10 length: length padded: true ].
+ "Print offset"
+ aStream nextPut: (localOffsetSeconds >= 0 ifTrue: [ $+ ] ifFalse: [ $- ]).
+ offsetSeconds := localOffsetSeconds abs.
+ offsetSeconds // 3600 printOn: aStream base: 10 length: 2 padded: true.
+ aStream nextPut: $:.
+ offsetSeconds \\ 3600 // 60 printOn: aStream base: 10 length: 2 padded: true.
+ (offsetSeconds := offsetSeconds \\ 60) = 0 ifFalse: [
+ aStream
- 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: $:;
+ print: offsetSeconds ]!
- nextPutAll: (self offset seconds abs truncated asString) ].
- !

Item was changed:
  ----- Method: DateAndTime>>printYMDOn:withLeadingSpace: (in category 'squeak protocol') -----
  printYMDOn: aStream withLeadingSpace: printLeadingSpaceToo
  "Print just the year, month, and day on aStream.
 
  If printLeadingSpaceToo is true, then print as:
  ' YYYY-MM-DD' (if the year is positive) or '-YYYY-MM-DD' (if the year is negative)
  otherwise print as:
  'YYYY-MM-DD' or '-YYYY-MM-DD' "
 
+ self dayMonthYearDo: [ :day :month :year |
+ year negative
+ ifTrue: [ aStream nextPut: $- ]
+ ifFalse: [ printLeadingSpaceToo ifTrue: [ aStream space ] ].
+ year abs printOn: aStream base: 10 length: 4 padded: true.
+ aStream nextPut: $-.
+ month printOn: aStream base: 10 length: 2 padded: true.
+ aStream nextPut: $-.
+ day printOn: aStream base: 10 length: 2 padded: true ]!
- | year month day |
- self dayMonthYearDo: [ :d :m :y | year := y. month := m. day := d ].
- year negative
- ifTrue: [ aStream nextPut: $- ]
- ifFalse: [ printLeadingSpaceToo ifTrue: [ aStream space ]].
- aStream
- nextPutAll: (year abs asString padded: #left to: 4 with: $0);
- nextPut: $-;
- nextPutAll: (month asString padded: #left to: 2 with: $0);
- nextPut: $-;
- nextPutAll: (day asString padded: #left to: 2 with: $0)
- !

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

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

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

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

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

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

Item was 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.
  nanos := ticks at: 3.
+ localOffsetSeconds := utcOffset ifNil: [0] ifNotNil: [utcOffset asSeconds].
+ utcMicroseconds := self microsecondsFromDay: jdn seconds: s nanos: nanos offset: localOffsetSeconds.
- localOffsetSeconds := utcOffset asSeconds.
- utcMicroseconds := self posixMicrosecondsJdn: jdn seconds: s nanos: nanos offset: localOffsetSeconds.
  !

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

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

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

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

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:
- Magnitude subclass: #LXDateAndTime
- instanceVariableNames: 'utcMicroseconds localOffsetSeconds'
- classVariableNames: 'ClockProvider DaysSinceEpoch LastMilliSeconds LastTick LastTickSemaphore LocalTimeZone MilliSecondOffset OffsetsAreValid'
- poolDictionaries: 'ChronologyConstants'
- category: 'Chronology-Core'!
-
- !LXDateAndTime commentStamp: 'dtl 3/31/2014 19:49' prior: 0!
- I represent a point in UTC time as defined by ISO 8601. I have zero duration.
-
- My magnitude represents the elapsed time since (or before) the Posix epoch.
-
- I have a local offset for presenting my date and time in the context of a local time zone. This offset is independent of my magnitude.
-
- My implementation ignores leap seconds, which are adjustments made to maintain earth rotational clock time in synchronization with elapsed seconds.!

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

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

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

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

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

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

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

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

Item was removed:
- ----- Method: LXDateAndTime class>>fromSeconds: (in category 'smalltalk-80') -----
- fromSeconds: seconds
- "Answer a DateAndTime since the Squeak epoch: 1 January 1901"
-
- "dtl - Implemented for compatibiity with Squeak, but this is probably wrong"
-
- | s uSec offset |
- self flag: #FIXME. "local versus UTC? what should we set the offset to?"
- offset := self localOffsetSeconds.
- s := seconds - self epochOffset - offset..
- uSec := s * 1000000.
- ^ self utcMicroseconds: uSec offset: offset
- !

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

Item was removed:
- ----- Method: LXDateAndTime class>>initialize (in category 'initialize-release') -----
- initialize
- | oldInstances newInstances |
-
- super initialize.
-
- ClockProvider := Time.
- LastTickSemaphore := Semaphore forMutualExclusion.
- LastMilliSeconds := 0.
- LastTick := 0.
- Smalltalk addToStartUpList: self.
- self startUp: true.
-
- "Postscript:
- Convert all instances of LXDateAndTime and LXTimeStamp to the equivalent DateAndTime and TimeStamp."
-
- Smalltalk garbageCollect.
- oldInstances := LXDateAndTime allInstances, LXTimeStamp allInstances.
- newInstances := oldInstances collect: [ :each |
- each class == LXDateAndTime
- ifTrue: [ each asDateAndTime ]
- ifFalse: [ each asTimeStamp ] ].
- oldInstances elementsForwardIdentityTo: newInstances.
- Smalltalk garbageCollect.
-
- !

Item was removed:
- ----- Method: LXDateAndTime class>>initializeOffsets (in category 'initialize-release') -----
- initializeOffsets
- | durationSinceEpoch secondsSinceMidnight nowSecs |
- LastTick := 0.
- nowSecs := self clock secondsWhenClockTicks.
- LastMilliSeconds := self millisecondClockValue.
- durationSinceEpoch := Duration
- days: SqueakEpoch
- hours: 0
- minutes: 0
- seconds: nowSecs.
- DaysSinceEpoch := durationSinceEpoch days.
- secondsSinceMidnight := (durationSinceEpoch -
- (Duration
- days: DaysSinceEpoch
- hours: 0
- minutes: 0
- seconds: 0)) asSeconds.
- MilliSecondOffset := secondsSinceMidnight * 1000 - LastMilliSeconds!

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

Item was removed:
- ----- Method: LXDateAndTime class>>julianDayNumber:offset: (in category 'squeak protocol') -----
- julianDayNumber: anInteger offset: aDuration
- ^ self basicNew
- ticks: anInteger days ticks
- offset: aDuration ;
- yourself!

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

Item was removed:
- ----- Method: LXDateAndTime class>>localOffsetSeconds (in category 'DTL') -----
- localOffsetSeconds
- ^self localOffset asSeconds!

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

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

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

Item was removed:
- ----- Method: LXDateAndTime class>>milliSecondsSinceMidnight (in category 'squeak protocol') -----
- milliSecondsSinceMidnight
- | msm msClock |
-
- "This is usually only during system startup..."
- self waitForOffsets.
-
- msClock := self millisecondClockValue.
- msClock < LastMilliSeconds ifTrue: [ "rolled over"
- MilliSecondOffset := MilliSecondOffset + (SmallInteger maxVal // 2) + 1 ].
- LastMilliSeconds := msClock.
- [
- msm := msClock + MilliSecondOffset.
- msm >= 86400000 ] whileTrue: [
- "next day"
- LastTick := -1.
- DaysSinceEpoch := DaysSinceEpoch + 1.
- MilliSecondOffset := MilliSecondOffset - 86400000 ].
- "day rolled over sanity check"
- (LastTick = -1 and: [
- (Duration
- days: SqueakEpoch
- hours: 0
- minutes: 0
- seconds: self clock totalSeconds) days ~= DaysSinceEpoch ]) ifTrue: [
- self initializeOffsets.
- ^ self milliSecondsSinceMidnight ].
- ^ msm.!

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

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

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

Item was removed:
- ----- Method: LXDateAndTime class>>now (in category 'ansi protocol') -----
- now
-
- [ | 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 removed:
- ----- Method: LXDateAndTime class>>nowWithOffset: (in category 'squeak protocol') -----
- nowWithOffset: aDuration
- | nanoTicks msm |
- nanoTicks := (msm := self milliSecondsSinceMidnight) * 1000000.
- "The following usually only executes at system startup."
- ^ LastTick < nanoTicks
- ifTrue:
- [ LastTick := nanoTicks.
- self waitForOffsets.
- self basicNew
- setJdn: DaysSinceEpoch
- seconds: msm // 1000
- nano: msm \\ 1000 * 1000000
- offset: aDuration ]
- ifFalse:
- [ LastTickSemaphore critical:
- [ LastTick := LastTick + 1.
- self waitForOffsets.
- self basicNew
- setJdn: DaysSinceEpoch
- seconds: LastTick // 1000000000
- nano: LastTick \\ 1000000000
- offset: aDuration ] ]
- "
- [ 10000 timesRepeat: [ self now. ] ] timeToRun / 10000.0 .
-
- If calls to DateAndTime-c-#now are within a single millisecond the semaphore code
- to ensure that (self now <= self now) slows things down considerably by a factor of about 20.
-
- The actual speed of a single call to DateAndTime-now in milliseconds is
- demonstrated by the unguarded method below.
-
- [ 100000 timesRepeat: [ self todayAtMilliSeconds: (self milliSecondsSinceMidnight) ] ] timeToRun / 100000.0 .  0.00494 0.00481 0.00492 0.00495
-  
- "!

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

Item was removed:
- ----- Method: LXDateAndTime 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 removed:
- ----- Method: LXDateAndTime class>>readFrom: (in category 'squeak protocol') -----
- readFrom: aStream
-
- | offset date time ch |
-
- date := Date readFrom: aStream.
- [aStream peek isDigit]
- whileFalse: [aStream next].
- time := Time readFrom: aStream.
- (aStream atEnd or: [('+-Z' includes: aStream peek) not])
- ifTrue: [offset := self localOffset]
- ifFalse: [(aStream peekFor: $Z)
- ifTrue: [offset := Duration zero]
- ifFalse: [
- ch := aStream next.
- ch = $+ ifTrue: [ch := Character space].
- offset := Duration fromString: ch asString, '0:', aStream upToEnd, ':0']].
- ^ self
- year: date year
- month: date monthIndex
- day: date dayOfMonth
- hour: time hour
- minute: time minute
- second: time second
- nanoSecond: time nanoSecond
- offset: offset
-
-
- " '-1199-01-05T20:33:14.321-05:00' asDateAndTime
- ' 2002-05-16T17:20:45.1+01:01' asDateAndTime
-
- ' 2002-05-16T17:20:45.02+01:01' asDateAndTime
-
- ' 2002-05-16T17:20:45.003+01:01' asDateAndTime
-
- ' 2002-05-16T17:20:45.0004+01:01' asDateAndTime
-   ' 2002-05-16T17:20:45.00005' asDateAndTime
- ' 2002-05-16T17:20:45.000006+01:01' asDateAndTime
-
- ' 2002-05-16T17:20:45.0000007+01:01' asDateAndTime
- ' 2002-05-16T17:20:45.00000008-01:01' asDateAndTime  
- ' 2002-05-16T17:20:45.000000009+01:01' asDateAndTime  
- ' 2002-05-16T17:20:45.0000000001+01:01' asDateAndTime  
-
-   ' 2002-05-16T17:20' asDateAndTime
- ' 2002-05-16T17:20:45' asDateAndTime
- ' 2002-05-16T17:20:45+01:57' asDateAndTime
-   ' 2002-05-16T17:20:45-02:34' asDateAndTime
-   ' 2002-05-16T17:20:45+00:00' asDateAndTime
- ' 1997-04-26T01:02:03+01:02:3' asDateAndTime
-   "!

Item was removed:
- ----- Method: LXDateAndTime class>>startUp: (in category 'initialize-release') -----
- startUp: resuming
- resuming ifFalse: [ ^ self ].
- "Time initializeMillisecondClockMask."
- OffsetsAreValid := false.
- [
- self initializeOffsets.
- OffsetsAreValid := true
- ] forkAt: Processor userInterruptPriority.!

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

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

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

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

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

Item was removed:
- ----- Method: LXDateAndTime class>>waitForOffsets (in category 'initialize-release') -----
- waitForOffsets
- OffsetsAreValid ifFalse: [
- [
- (Delay forSeconds: 1) wait.
- OffsetsAreValid
- ] whileFalse
- ]!

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

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

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

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

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

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

Item was removed:
- ----- Method: LXDateAndTime class>>year:month:day:hour:minute:second:nanoSecond:offset: (in category 'squeak protocol') -----
- year: year month: month day: day hour: hour minute: minute second: second nanoSecond: nanoCount offset: offset
- "Return a DateAndTime"
-
- | monthIndex daysInMonth p q r s julianDayNumber |
-
- monthIndex := month isInteger ifTrue: [month] ifFalse: [Month indexOfMonth: month].
- daysInMonth := Month
- daysInMonth: monthIndex
- forYear: year.
- day < 1 ifTrue: [self error: 'day may not be zero or negative'].
- day > daysInMonth ifTrue: [self error: 'day is after month ends'].
-
- p := (monthIndex - 14) quo: 12.
- q := year + 4800 + p.
- r := monthIndex - 2 - (12 * p).
- s := (year + 4900 + p) quo: 100.
-
- julianDayNumber :=
-   ( (1461 * q) quo: 4 ) +
- ( (367 * r) quo: 12 ) -
-   ( (3 * s) quo: 4 ) +
-   ( day - 32075 ).
-
- ^self basicNew
- setJdn: julianDayNumber
- seconds: hour * 60 + minute * 60 + second - offset asSeconds
- nano: nanoCount
- offset: offset;
- yourself!

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

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

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

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

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

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

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

Item was removed:
- ----- Method: LXDateAndTime>>asDateAndTime (in category 'squeak protocol') -----
- asDateAndTime
-
- ^DateAndTime utcMicroseconds: utcMicroseconds offset: localOffsetSeconds
- !

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

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

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

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

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

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

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

Item was removed:
- ----- Method: LXDateAndTime>>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
- !

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Item was removed:
- ----- Method: LXDateAndTime>>getSeconds (in category '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 removed:
- ----- Method: LXDateAndTime>>hasEqualTicks: (in category 'private') -----
- hasEqualTicks: aDateAndTime
-
- ^ (self julianDayNumber = aDateAndTime julianDayNumber)
- and: [ (self getSeconds = aDateAndTime secondsSinceMidnight)
- and: [ self nanoSecond = aDateAndTime nanoSecond ] ]
-
- !

Item was removed:
- ----- Method: LXDateAndTime>>hash (in category 'ansi protocol') -----
- hash
- | totalSeconds |
- totalSeconds := self getSeconds - self offsetSeconds.
- ^ ((totalSeconds // 86400 + self julianDayNumber) hashMultiply bitXor: totalSeconds \\
- 86400) bitXor: self nanoSecond!

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Item was removed:
- ----- Method: LXDateAndTime>>offset: (in category 'ansi protocol') -----
- offset: anOffset
-
- "Answer a <DateAndTime> equivalent to the receiver but with its local time
- being offset from UTC by offset."
-
- ^ self class utcMicroseconds: utcMicroseconds offset: anOffset asDuration asSeconds
- !

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

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

Item was removed:
- ----- Method: LXDateAndTime>>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 removed:
- ----- Method: LXDateAndTime>>printHMSOn: (in category 'squeak protocol') -----
- printHMSOn: aStream
- "Print just hh:mm:ss"
- aStream
- nextPutAll: (self hour asString padded: #left to: 2 with: $0);
- nextPut: $:;
- nextPutAll: (self minute asString padded: #left to: 2 with: $0);
- nextPut: $:;
- nextPutAll: (self second asString padded: #left to: 2 with: $0).
- !

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

Item was removed:
- ----- Method: LXDateAndTime>>printOn:withLeadingSpace: (in category 'squeak protocol') -----
- printOn: aStream withLeadingSpace: printLeadingSpaceToo
- "Print as per ISO 8601 sections 5.3.3 and 5.4.1.
- If printLeadingSpaceToo is false, prints either:
- 'YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for positive years) or '-YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for negative years)
- If printLeadingSpaceToo is true, prints either:
- ' YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for positive years) or '-YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for negative years)
- "
-
- 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 removed:
- ----- Method: LXDateAndTime>>printYMDOn: (in category 'squeak protocol') -----
- printYMDOn: aStream
- "Print just YYYY-MM-DD part.
- If the year is negative, prints out '-YYYY-MM-DD'."
-
- ^self printYMDOn: aStream withLeadingSpace: false.
- !

Item was removed:
- ----- Method: LXDateAndTime>>printYMDOn:withLeadingSpace: (in category 'squeak protocol') -----
- printYMDOn: aStream withLeadingSpace: printLeadingSpaceToo
- "Print just the year, month, and day on aStream.
-
- If printLeadingSpaceToo is true, then print as:
- ' YYYY-MM-DD' (if the year is positive) or '-YYYY-MM-DD' (if the year is negative)
- otherwise print as:
- 'YYYY-MM-DD' or '-YYYY-MM-DD' "
-
- | year month day |
- self dayMonthYearDo: [ :d :m :y | year := y. month := m. day := d ].
- year negative
- ifTrue: [ aStream nextPut: $- ]
- ifFalse: [ printLeadingSpaceToo ifTrue: [ aStream space ]].
- aStream
- nextPutAll: (year abs asString padded: #left to: 4 with: $0);
- nextPut: $-;
- nextPutAll: (month asString padded: #left to: 2 with: $0);
- nextPut: $-;
- nextPutAll: (day asString padded: #left to: 2 with: $0)
- !

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

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

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

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

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

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

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

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

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

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

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

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

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

Item was removed:
- ----- Method: LXDateAndTime>>utcOffset: (in category 'squeak protocol') -----
- utcOffset: anOffset
-
- "Answer a <DateAndTime> equivalent to the receiver but offset from UTC by anOffset"
-
- | equiv |
- equiv := self + (anOffset asDuration - self offset).
- ^ equiv ticks: (equiv ticks) offset: anOffset asDuration; yourself!

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

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

Item was removed:
- ----- Method: LXTimeStamp class>>current (in category 'squeak protocol') -----
- current
-
- | 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: LXTimeStamp class>>now (in category 'ansi protocol') -----
- now
- "Answer the current date and time as a TimeStamp."
-
- ^self current!

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

Item was removed:
- ----- Method: LXTimeStamp>>asLXDateAndTime (in category 'transitional') -----
- asLXDateAndTime
- "Answer the receiver as an instance of DateAndTime."
-
- ^ LXDateAndTime utcMicroseconds: utcMicroseconds offset: self offsetSeconds
- !

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

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

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

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

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

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

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

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

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

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

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

Item was removed:
- Object subclass: #NameOfSubclass
- instanceVariableNames: ''
- classVariableNames: ''
- poolDictionaries: ''
- category: 'Chronology-Core'!

Item was changed:
  Magnitude subclass: #Time
  instanceVariableNames: 'seconds nanos'
+ classVariableNames: 'ClockPolicy LastClockTick'
- classVariableNames: ''
  poolDictionaries: 'ChronologyConstants'
  category: 'Chronology-Core'!
 
  !Time commentStamp: 'dew 10/23/2004 17:58' prior: 0!
  This represents a particular point in time during any given day.  For example, '5:19:45 pm'.
 
  If you need a point in time on a particular day, use DateAndTime.  If you need a duration of time, use Duration.
  !

Item was added:
+ ----- Method: Time class>>clockPolicy: (in category 'class initialization') -----
+ clockPolicy: aSymbol
+ "When sequencial calls are made to DateAndTime now, it may be desirable to
+ force the system clock to be monotonic, and it may be desirable for the clock
+ to appear to be strictly increasing with no repeat values. The ClockPolicy
+ identifies which of several possible strategies to use.
+
+ Allowable values are
+ #acceptPlatformTime
+ #monotonicAllowDuplicates
+ #monotonicForceMicrosecondIncrement
+ #monotonicForceNanosecondIncrement "
+
+ ClockPolicy := aSymbol!

Item was added:
+ ----- Method: Time class>>initialize (in category 'class initialization') -----
+ initialize
+ "Time initialize"
+
+ "Initialize at startup time to protect for the case of an image saved with bad LastClockTick"
+ LastClockTick := 0.
+
+ "self clockPolicy: #acceptPlatformTime."
+ self clockPolicy: #monotonicAllowDuplicates.
+ "self clockPolicy: #monotonicForceMicrosecondIncrement."
+ "self clockPolicy: #monotonicForceNanosecondIncrement."
+ !

Item was changed:
  ----- Method: Time class>>localMicrosecondClock (in category 'clock') -----
  localMicrosecondClock
  "Answer the local microseconds since the Smalltalk epoch (January 1st 1901, the start of the 20th century).
+ The value is derived from the current UTC wallclock time and the image's current notion of time zone."
+ ^self utcMicrosecondClock + (DateAndTime localOffset asSeconds * 1000000)!
- The value is derived from the Posix epoch with a constant offset corresponding to elapsed microseconds
- between the two epochs according to RFC 868, and with an offset duration corresponding to the current
- offset of local time from UTC."
- <primitive: 241>
- ^0!

Item was added:
+ ----- Method: Time class>>localMicrosecondClockPrimitive (in category 'clock') -----
+ localMicrosecondClockPrimitive
+ "Answer the local microseconds since the Smalltalk epoch (January 1st 1901, the start of the 20th century).
+ The value is derived from the Posix epoch with a constant offset corresponding to elapsed microseconds
+ between the two epochs according to RFC 868, and with an offset duration corresponding to the current
+ offset of local time from UTC."
+ <primitive: 241>
+ ^0!

Item was changed:
  ----- 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.
- result := self primPosixMicrosecondClockWithOffset.
  "DateAndTime unixEpoch asSeconds"
  result at: 1 put: result first + ((2177452800 + result second) * 1000000).
  ^result!

Item was changed:
  ----- Method: Time class>>millisecondClockValue (in category 'general inquiries') -----
  millisecondClockValue
  "Answer the value of the millisecond clock."
 
+ ^self utcMicrosecondClock // 1000!
- ^self localMicrosecondClock // 1000!

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

Item was added:
+ ----- Method: Time class>>posixMicrosecondClockWithOffset: (in category 'clock') -----
+ posixMicrosecondClockWithOffset: aDateAndTime
+ "Initialize aDateAndTime initialized with local microseconds since the Posix
+ epoch and the current seconds offset from GMT in the local time zone."
+
+
+ | utcValue |
+ self primPosixMicrosecondClockWithOffset: aDateAndTime.
+ aDateAndTime utcMicroseconds ifNil: [ ^aDateAndTime]. "primitive failed"
+ ClockPolicy caseOf: {
+ [#acceptPlatformTime] -> [^ aDateAndTime] .
+ [#monotonicAllowDuplicates] -> [
+ utcValue := aDateAndTime utcMicroseconds.
+ utcValue > LastClockTick
+ ifTrue: [LastClockTick := utcValue]
+ ifFalse: [aDateAndTime utcMicroseconds: LastClockTick]] .
+ [#monotonicForceMicrosecondIncrement] -> [
+ utcValue := aDateAndTime utcMicroseconds.
+ utcValue > LastClockTick
+ ifTrue: [LastClockTick := utcValue]
+ ifFalse: [LastClockTick := LastClockTick + 1. "add one microsecond"
+ aDateAndTime utcMicroseconds: LastClockTick]] .
+ [#monotonicForceNanosecondIncrement] -> [
+ utcValue := aDateAndTime utcMicroseconds.
+ utcValue > LastClockTick
+ ifTrue: [LastClockTick := utcValue]
+ ifFalse: [LastClockTick := LastClockTick + (1 / 1000). "add one nanosecond"
+ aDateAndTime utcMicroseconds: LastClockTick]]
+ } otherwise: [].
+ ^aDateAndTime
+ !

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 added:
+ ----- Method: Time class>>primPosixMicrosecondClockWithOffset: (in category 'private') -----
+ primPosixMicrosecondClockWithOffset: arrayOrObjectWithTwoSlots
+ "Answer an array with UTC microseconds since the Posix epoch and the
+ current seconds offset from GMT in the local time zone. If the primitive is
+ not available, then answer the time and offset of Posix epoch GMT. This enables
+ the image to continue running in the absence of #primitiveUtcWithOffset, thus
+ avoiding the need to fallback code based on the earlier local microsecond clock
+ mechanism.
+
+ The parameter may be a two element array, or an object whose first two instance
+ variables are expected to be UTC microseconds and seconds offset from GMT."
+
+ <primitive: 'primitiveUtcWithOffset'>
+ ^{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 added:
+ ----- Method: Time class>>readHourMinuteSecondNanoFrom: (in category 'smalltalk-80') -----
+ readHourMinuteSecondNanoFrom: 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"
+
+ | 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 ]].
+ ^ { hour . minute . second . nanosBuffer asInteger }
+
+ "Time readFrom: (ReadStream on: '2:23:09 pm')"!

Item was changed:
  ----- Method: Time>>print24:showSeconds:on: (in category 'printing') -----
  print24: hr24 showSeconds: showSeconds on: aStream
  "Format is 'hh:mm:ss' or 'h:mm:ss am'  or, if showSeconds is false, 'hh:mm' or 'h:mm am'"
 
+ ^self print24: hr24 showSeconds: showSeconds showSubseconds: false on: aStream !
- | h m s |
- h := self hour. m := self minute. s := self second.
- hr24
- ifTrue:
- [ h < 10 ifTrue: [ aStream nextPutAll: '0' ].
- h printOn: aStream ]
- ifFalse:
- [ h > 12
- ifTrue: [h - 12 printOn: aStream]
- ifFalse:
- [h < 1
- ifTrue: [ 12 printOn: aStream ]
- ifFalse: [ h printOn: aStream ]]].
-
- aStream nextPutAll: (m < 10 ifTrue: [':0'] ifFalse: [':']).
- m printOn: aStream.
-
- showSeconds ifTrue:
- [ aStream nextPutAll: (s < 10 ifTrue: [':0'] ifFalse: [':']).
- self nanoSecond = 0
- ifTrue: [s asInteger printOn: aStream]
- ifFalse: [s asInteger * NanosInSecond + self nanoSecond asInteger
- printOn: aStream asFixedPoint: NanosInSecond]].
-
- hr24 ifFalse:
- [ aStream nextPutAll: (h < 12 ifTrue: [' am'] ifFalse: [' pm']) ].
- !

Item was added:
+ ----- Method: Time>>print24:showSeconds:showSubseconds:on: (in category 'printing') -----
+ print24: hr24 showSeconds: showSeconds showSubseconds: showSubseconds on: aStream
+ "Format is 'hh:mm:ss' or 'h:mm:ss am'  or, if showSeconds is false, 'hh:mm' or 'h:mm am'.
+ If showSubseconds is true and our nanoSeconds are not zero, a decimal point and subseconds are added"
+
+ | h m s |
+ h := self hour. m := self minute. s := self second.
+ hr24
+ ifTrue:
+ [ h < 10 ifTrue: [ aStream nextPutAll: '0' ].
+ h printOn: aStream ]
+ ifFalse:
+ [ h > 12
+ ifTrue: [h - 12 printOn: aStream]
+ ifFalse:
+ [h < 1
+ ifTrue: [ 12 printOn: aStream ]
+ ifFalse: [ h printOn: aStream ]]].
+
+ aStream nextPutAll: (m < 10 ifTrue: [':0'] ifFalse: [':']).
+ m printOn: aStream.
+
+ showSeconds ifTrue:
+ [ aStream nextPutAll: (s < 10 ifTrue: [':0'] ifFalse: [':']).
+ (showSubseconds not or: [self nanoSecond = 0])
+ ifTrue: [s asInteger printOn: aStream]
+ ifFalse: [s asInteger * NanosInSecond + self nanoSecond asInteger
+ printOn: aStream asFixedPoint: NanosInSecond]].
+
+ hr24 ifFalse:
+ [ aStream nextPutAll: (h < 12 ifTrue: [' am'] ifFalse: [' pm']) ].
+ !

Item was changed:
  ----- Method: Time>>printOn: (in category 'printing') -----
  printOn: aStream
 
  self print24: false
  showSeconds: (self seconds ~= 0
  or: [self nanoSecond ~= 0])
+ showSubseconds: self nanoSecond ~= 0
  on: aStream!

Item was changed:
  ----- Method: TimeStamp class>>current (in category 'squeak protocol') -----
  current
 
+ ^self now!
- | 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>>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 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 noTimezone or: [ comparand noTimezone ])
- ifTrue: [ self start hasEqualTicks: comparand start ]
- ifFalse: [ self start = comparand start ])
  and: [ self duration = comparand duration ] ]
  .!

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

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

Item was changed:
+ (PackageInfo named: 'Chronology-Core') postscript: 'DateAndTime startUp: true.
+ HashedCollection rehashAll.
- (PackageInfo named: 'Chronology-Core') postscript: '"Convert all instances of LXDateAndTime and LXTimeStamp to the equivalent DateAndTime and TimeStamp."
-
- | oldInstances newInstances |
- Smalltalk garbageCollect.
- oldInstances := LXDateAndTime allInstances, LXTimeStamp allInstances.
- newInstances := oldInstances collect: [ :each |
-         each class == LXDateAndTime
-                 ifTrue: [ each asDateAndTime ]
-                 ifFalse: [ each asTimeStamp ] ].
- oldInstances elementsForwardIdentityTo: newInstances.
- Smalltalk garbageCollect.
-
- "Ensure that the object history mark process uses DateAndTime>>floor rather than an earlier implementation that relied on a named instance variable."
-
- Smalltalk at: #ObjectHistory ifPresent: [ :cls | cls current perform: #restartMarkProcess ].
  '!