The Inbox: Chronology-Core-dtl.19.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.19.mcz

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

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

Name: Chronology-Core-dtl.19
Author: dtl
Time: 15 December 2018, 6:47:29.647762 pm
UUID: 501afcd3-0158-4b5b-a9b2-2f284fd760a3
Ancestors: Chronology-Core-dtl.18

Bootstrap UTCDateAndTime, step 4 of 5

Resume using DateAndTime instead of LXDateAndTime.

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

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

Item was changed:
  ----- Method: DateAndTime 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
+ !
- ^ LXDateAndTime fromSeconds: seconds
- " | integerSeconds nanos |
- integerSeconds := seconds truncated.
- integerSeconds = seconds
- ifTrue: [nanos := 0]
- ifFalse: [nanos := (seconds - integerSeconds * NanosInSecond) asInteger].
- ^ self basicNew
- ticks: (Array
- with: SqueakEpoch
- with: integerSeconds
- with: nanos)
- offset: self localOffset"!

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

Item was changed:
  ----- Method: DateAndTime 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]!
- now
- "^ self nowWithOffset: self localOffset"
- ^LXDateAndTime now!

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

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"
 
+ | monthIndex daysInMonth p q r s julianDayNumber |
- ^ LXDateAndTime year: year month: month day: day hour: hour minute: minute second: second nanoSecond: nanoCount offset: offset
- " | 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
- seconds: hour * 60 + minute * 60 + second
  nano: nanoCount
  offset: offset;
+ yourself!
- yourself"!

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

Item was changed:
  ----- Method: DateAndTime>>- (in category 'ansi protocol') -----
  - operand
  "operand conforms to protocol DateAndTime or protocol Duration"
 
+ ^ (operand respondsTo: #asDateAndTime)
- ^ (operand respondsTo: #asLXDateAndTime)
  ifTrue:
  [ | lticks rticks |
  lticks := self asLocal ticks.
 
+ rticks := operand asDateAndTime 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 changed:
  ----- Method: DateAndTime>>< (in category 'ansi protocol') -----
  < comparand
  "comparand conforms to protocol DateAndTime,
  or can be converted into something that conforms."
 
+ ^utcMicroseconds < comparand asDateAndTime utcMicroseconds
- utcMicroseconds ifNil: [^true]. self flag: #FIXME. "dtl transitional hack"
- ^utcMicroseconds < comparand asLXDateAndTime utcMicroseconds
  !

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 isKindOf: self class)
+ or: [aDateAndTimeOrTimeStamp isKindOf: DateAndTime orOf: TimeStamp])
- or: [aDateAndTimeOrTimeStamp isKindOf: LXDateAndTime orOf: TimeStamp])
  ifFalse: [ ^ false ].
  ^utcMicroseconds = aDateAndTimeOrTimeStamp utcMicroseconds!

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

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

Item was changed:
  ----- 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.
+
- self startUp: true
  !

Item was removed:
- ----- Method: Time class>>primPosixMicrosecondClockWithOffsetStoredIn: (in category 'LX-Kernel-Chronology') -----
- primPosixMicrosecondClockWithOffsetStoredIn: resultArray
- "Answer an array with UTC microseconds since the Posix epoch and the
- current seconds offset from GMT in the local time zone, supplying a two
- element result array that will be populated in the primitive."
-
- <primitive: 'primitiveUtcWithOffset'>
- ^#(0 0)!

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

Item was changed:
+ (PackageInfo named: 'Chronology-Core') postscript: '"Convert all instances of LXDateAndTime and LXTimeStamp to the equivalent DateAndTime and TimeStamp."
- (PackageInfo named: 'Chronology-Core') postscript: '"Convert all instances of DateAndTime and TimeStamp to the equivalent LXDateAndTime and LXTimeStamp."
 
  | oldInstances newInstances |
  Smalltalk garbageCollect.
+ oldInstances := LXDateAndTime allInstances, LXTimeStamp allInstances.
- oldInstances := DateAndTime allInstances, TimeStamp allInstances.
  newInstances := oldInstances collect: [ :each |
+         each class == LXDateAndTime
+                 ifTrue: [ each asDateAndTime ]
+                 ifFalse: [ each asTimeStamp ] ].
-         each class == DateAndTime
-                 ifTrue: [ each asLXDateAndTime ]
-                 ifFalse: [ each asLXTimeStamp ] ].
  oldInstances elementsForwardIdentityTo: newInstances.
  Smalltalk garbageCollect.
 
  "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 ].
- Smalltalk at: #ObjectHistory ifPresent: [ :cls | cls current restartMarkProcess ].
  '!