[Pkg] The Trunk: Kernel-bf.997.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Feb 19 00:28:12 UTC 2016


Bert Freudenberg uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-bf.997.mcz

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

Name: Kernel-bf.997
Author: bf
Time: 18 February 2016, 4:27:40.07581 pm
UUID: 90f6486d-dd3a-4d00-847a-67eda6da3d44
Ancestors: Kernel-bf.996

Make testRematerializedDateComparison pass.

=============== Diff against Kernel-bf.996 ===============

Item was changed:
  Magnitude subclass: #DateAndTime
  	instanceVariableNames: 'seconds offset jdn nanos'
  	classVariableNames: 'AutomaticTimezone ClockProvider LastClockValue LocalTimeZone NanoOffset'
  	poolDictionaries: 'ChronologyConstants'
  	category: 'Kernel-Chronology'!
  
+ !DateAndTime commentStamp: 'bf 2/18/2016 16:20' 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 three SmallIntegers
   and a Duration:
  jdn		- julian day number.
  seconds	- number of seconds since midnight.
  nanos	- the number of nanoseconds since the second.
  
+ offset	- duration from UTC (possibly nil if no timezone information)
- 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>>< (in category 'ansi protocol') -----
  < comparand 
  	"comparand conforms to protocol DateAndTime,
  	or can be converted into something that conforms."
  	| lvalue rvalue comparandAsDateAndTime |
+ 	comparandAsDateAndTime _ comparand asDateAndTime.
+ 	self offset = comparandAsDateAndTime offset
- 	comparandAsDateAndTime := comparand asDateAndTime.
- 	offset = comparandAsDateAndTime offset
  		ifTrue:
+ 			[ lvalue _ self.
+ 			rvalue _ comparandAsDateAndTime ]
- 			[ lvalue := self.
- 			rvalue := comparandAsDateAndTime ]
  		ifFalse:
+ 			[ lvalue _ self asUTC.
+ 			rvalue _ comparandAsDateAndTime asUTC ].
- 			[ lvalue := self asUTC.
- 			rvalue := comparandAsDateAndTime asUTC ].
  	^ lvalue julianDayNumber < rvalue julianDayNumber or:
  		[ lvalue julianDayNumber > rvalue julianDayNumber
  			ifTrue: [ false ]
  			ifFalse:
  				[ lvalue secondsSinceMidnight < rvalue secondsSinceMidnight or:
  					[ lvalue secondsSinceMidnight > rvalue secondsSinceMidnight
  						ifTrue: [ false ]
  						ifFalse: [ lvalue nanoSecond < rvalue nanoSecond ] ] ] ]!

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

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

Item was removed:
- ----- Method: DateAndTime>>ignoreTimezone (in category 'private') -----
- ignoreTimezone
- 	"For polymorphism with Timespan"
- 	^false!

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

Item was changed:
  ----- Method: DateAndTime>>offset (in category 'ansi protocol') -----
  offset
  
+ 	^ offset ifNil: [Duration zero]!
- 	^ offset!

Item was changed:
  ----- Method: DateAndTime>>offset: (in category 'ansi protocol') -----
  offset: anOffset
  
  	"Answer a <DateAndTime> equivalent to the receiver but with its local time 
  	being offset from UTC by offset."
  
  	^ self class basicNew 
+ 		ticks: self ticks offset: (anOffset ifNotNil: [anOffset asDuration]);
- 		ticks: self ticks offset: anOffset asDuration;
  		yourself!

Item was changed:
  ----- Method: DateAndTime>>printOn:withLeadingSpace: (in category 'squeak protocol') -----
  printOn: aStream withLeadingSpace: printLeadingSpaceToo
  	"Print as per ISO 8601 sections 5.3.3 and 5.4.1.
  	If printLeadingSpaceToo is false, prints either:
  		'YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for positive years) or '-YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for negative years)
  	If printLeadingSpaceToo is true, prints either:
  		' YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for positive years) or '-YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for negative years)
  	"
  
  	self printYMDOn: aStream withLeadingSpace: printLeadingSpaceToo.
  	aStream nextPut: $T.
  	self printHMSOn: aStream.
  	self nanoSecond ~= 0 ifTrue:
  		[ | z ps |
+ 		ps _ self nanoSecond printString padded: #left to: 9 with: $0.
+ 		z _ ps findLast: [ :c | c asciiValue > $0 asciiValue ].
- 		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: (offset positive ifTrue: [$+] ifFalse: [$-]);
- 		nextPutAll: (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:
- 		nextPutAll: (offset minutes abs asString padded: #left to: 2 with: $0).
- 	offset seconds = 0 ifFalse:
  		[ aStream
  			nextPut: $:;
+ 			nextPutAll: (self offset seconds abs truncated asString) ].
- 			nextPutAll: (offset seconds abs truncated asString) ].
  !

Item was changed:
  ----- Method: Timespan class>>defaultOffset (in category 'configuring') -----
  defaultOffset
+ 	"Timespans created in the context of an offset will start in that offset.  When no context is available, the defaultOffset for Timespans must be nil.  For example, two ways to make a Date for today:
+ 	Date today.  'start is midnight without offset.  Will compare successfully to other Date today results.'
+ 	DateAndTime now asDate.  'In this case, the start is midnight of the local time-zone.  It can only compare equally to Dates of its time-zone or Dates without timezone.'"
+ 	^ nil!
- 	"Timespans created in the context of an offset will start in that offset.  When no context is available, the defaultOffset for Timespans must be zero.  For example, two ways to make a Date for today:
- 	Date today.  'start is midnight at offset zero.  Will compare successfully to other Date today results.'
- 	DateAndTime now asDate.  'In this case, the start is midnight of the local time-zone.  It can only compare equally to Dates of its time-zone.'"
- 	^ Duration zero!

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

Item was removed:
- ----- Method: Timespan>>ignoreTimezone (in category 'private') -----
- ignoreTimezone
- 	^ start offset == self class defaultOffset!

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



More information about the Packages mailing list