[squeak-dev] The Inbox: Kernel-cbc.871.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Sep 19 06:18:22 UTC 2014


A new version of Kernel was added to project The Inbox:
http://source.squeak.org/inbox/Kernel-cbc.871.mcz

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

Name: Kernel-cbc.871
Author: cbc
Time: 18 September 2014, 11:15:40.731 pm
UUID: db75fc86-1341-8542-86df-8d6f5eb21d44
Ancestors: Kernel-cbc.870

Added support for chaining durations (such as 1 month + 1 day).
Also fixed GenericYear handling of leap years - there were corner cases where it failed to work correctly - now fixed.
No comments yet - will be in next commit.

=============== Diff against Kernel-cbc.870 ===============

Item was changed:
  ----- Method: DateAndTime>>+ (in category 'ansi protocol') -----
+ + aDuration
+ 	"aDuration is one of: Duration, GenericDuration, GenericMonth, or GenericYear."
+ 	^aDuration addToDateTime: self
- + operand
- 	"operand conforms to protocol Duration, or a Generic Month/Year"
- 	^operand addToDateTime: self
  !

Item was changed:
  ----- Method: DateAndTime>>- (in category 'ansi protocol') -----
  - operand
+ 	"operand is one of: Duration, GenericDuration, GenericMonth, or GenericYear; or a DateAndTime or Timespan."
+ 	^operand subtractFromDateTime: self
- 	"operand conforms to protocol DateAndTime or protocol Duration"
- 
- 	^ (operand respondsTo: #asDateAndTime)
- 		ifTrue: 
- 			[ | 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 added:
+ ----- Method: DateAndTime>>addToDuration: (in category 'ansi protocol') -----
+ addToDuration: aDuration
+ 	^Duration nanoSeconds: (self asNanoSeconds + aDuration asNanoSeconds)
+ !

Item was added:
+ ----- Method: DateAndTime>>subtractFromDateTime: (in category 'ansi protocol') -----
+ subtractFromDateTime: aDateAndTime
+ 	| lticks rticks |
+ 	lticks := aDateAndTime asLocal ticks.
+ 	rticks := self asLocal ticks.
+ 	^Duration
+ 		seconds: (SecondsInDay * (lticks first - rticks first)) + 
+ 					(lticks second - rticks second)
+ 		nanoSeconds: (lticks third - rticks third)!

Item was added:
+ ----- Method: DateAndTime>>subtractFromDuration: (in category 'ansi protocol') -----
+ subtractFromDuration: aDuration
+ 	^Duration nanoSeconds: (aDuration asNanoSeconds - self asNanoSeconds)!

Item was changed:
  ----- Method: Duration>>+ (in category 'ansi protocol') -----
  + operand
+ 	"operand is a type of Duration"
+ 	^operand addToDuration: self
+ !
- 
- 	"operand is a Duration" 	^ self class nanoSeconds: (self asNanoSeconds + operand asNanoSeconds)!

Item was changed:
  ----- Method: Duration>>- (in category 'ansi protocol') -----
  - operand
+ 	"operand is a type of Duration"
+ 	^operand subtractFromDuration: self
+ !
- 	"operand is a Duration" 	^ self + operand negated!

Item was added:
+ ----- Method: Duration>>addToDuration: (in category 'ansi protocol') -----
+ addToDuration: aDuration
+ 	^self class nanoSeconds: (self asNanoSeconds + aDuration asNanoSeconds)
+ !

Item was added:
+ ----- Method: Duration>>subtractFromDateTime: (in category 'ansi protocol') -----
+ subtractFromDateTime: aDateAndTime
+ 	^self copy negated addToDateTime: aDateAndTime!

Item was added:
+ ----- Method: Duration>>subtractFromDuration: (in category 'ansi protocol') -----
+ subtractFromDuration: aDuration
+ 	^self class nanoSeconds: (aDuration asNanoSeconds - self asNanoSeconds)
+ !

Item was added:
+ Object subclass: #GenericDuration
+ 	instanceVariableNames: 'sequence'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Chronology'!

Item was added:
+ ----- Method: GenericDuration>>+ (in category 'ansii protocol') -----
+ + aDuration
+ 	"aDuration is one of the families of Duration.  Not that if it isn't, it will fail, but only when addng to a DateAndTime or Timespan, not before!!"
+ 	aDuration class = self class
+ 		ifTrue: [sequence addAll: aDuration sequence]
+ 		ifFalse: [sequence addLast: { #+. #-. aDuration. }]
+ 	!

Item was added:
+ ----- Method: GenericDuration>>- (in category 'ansii protocol') -----
+ - aDuration
+ 	"aDuration is one of the families of Duration.  Not that if it isn't, it will fail, but only when addng to a DateAndTime or Timespan, not before!!"
+ 	aDuration class = self class
+ 		ifTrue: [sequence addAll: (aDuration sequence collect: [:s| s copy swap: 1 with: 2])]
+ 		ifFalse: [sequence addLast: { #-. #+. aDuration. }]!

Item was added:
+ ----- Method: GenericDuration>>= (in category 'ansii protocol') -----
+ = aGenericDuration
+ 	^aGenericDuration hasSameSequence: sequence!

Item was added:
+ ----- Method: GenericDuration>>addToDateTime: (in category 'ansii protocol') -----
+ addToDateTime: aDateAndTime
+ 	^sequence inject: aDateAndTime into: [:result :message|
+ 		result perform: message first with: message last
+ 		]!

Item was added:
+ ----- Method: GenericDuration>>addToDuration: (in category 'ansii protocol') -----
+ addToDuration: aDuration
+ 	sequence addFirst: { #+. #-. aDuration. }!

Item was added:
+ ----- Method: GenericDuration>>hasSameSequence: (in category 'ansii protocol') -----
+ hasSameSequence: testSequence
+ 	^sequence hasEqualElements: testSequence!

Item was added:
+ ----- Method: GenericDuration>>initialize (in category 'initialize-release') -----
+ initialize
+ 	sequence := OrderedCollection new.!

Item was added:
+ ----- Method: GenericDuration>>printOn: (in category 'squeak protocol') -----
+ printOn: stream
+ 	sequence do: [:msg| msg printOn: stream] separatedBy: [stream space]!

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

Item was added:
+ ----- Method: GenericDuration>>subtractFromDateTime: (in category 'ansii protocol') -----
+ subtractFromDateTime: aDateAndTime
+ 	^sequence inject: aDateAndTime into: [:result :message|
+ 		result perform: message second with: message last
+ 		]!

Item was added:
+ ----- Method: GenericDuration>>subtractFromDuration: (in category 'ansii protocol') -----
+ subtractFromDuration: aDuration
+ 	sequence do: [:s| s swap: 1 with: 2].
+ 	sequence addFirst: { #+. #-. aDuration. }!

Item was added:
+ ----- Method: GenericMonth>>+ (in category 'ansiProtocol') -----
+ + aDuration
+ 	"aDuration is one of the families of Duration.  Not that if it isn't, it will fail, but only when addng to a DateAndTime or Timespan, not before!!"
+ 	^GenericDuration new + self + aDuration!

Item was added:
+ ----- Method: GenericMonth>>- (in category 'ansiProtocol') -----
+ - aDuration
+ 	"aDuration is one of the families of Duration.  Not that if it isn't, it will fail, but only when addng to a DateAndTime or Timespan, not before!!"
+ 	^GenericDuration new + self - aDuration!

Item was added:
+ ----- Method: GenericMonth>>= (in category 'ansiProtocol') -----
+ = aGenericMonth
+ 	^aGenericMonth class = GenericMonth
+ 		and: [aGenericMonth number = number]!

Item was added:
+ ----- Method: GenericMonth>>addToDuration: (in category 'ansiProtocol') -----
+ addToDuration: aDuration
+ 	^GenericDuration new + aDuration + self
+ !

Item was added:
+ ----- Method: GenericMonth>>printOn: (in category 'squeak protocol') -----
+ printOn: stream
+ 	stream nextPutAll: number asString; nextPutAll: ' month'.
+ 	number abs = 1 ifFalse: [stream nextPut: $s].!

Item was added:
+ ----- Method: GenericMonth>>subtractFromDateTime: (in category 'ansiProtocol') -----
+ subtractFromDateTime: aDateAndTime
+ 	^self copy negated addToDateTime: aDateAndTime
+ !

Item was added:
+ ----- Method: GenericMonth>>subtractFromDuration: (in category 'ansiProtocol') -----
+ subtractFromDuration: aDuration
+ 	^GenericDuration new + aDuration - self!

Item was added:
+ ----- Method: GenericYear>>+ (in category 'ansiProtocol') -----
+ + aDuration
+ 	"aDuration is one of the families of Duration.  Not that if it isn't, it will fail, but only when addng to a DateAndTime or Timespan, not before!!"
+ 	^GenericDuration new + self + aDuration!

Item was added:
+ ----- Method: GenericYear>>- (in category 'ansiProtocol') -----
+ - aDuration
+ 	"aDuration is one of the families of Duration.  Not that if it isn't, it will fail, but only when addng to a DateAndTime or Timespan, not before!!"
+ 	^GenericDuration new + self - aDuration!

Item was added:
+ ----- Method: GenericYear>>= (in category 'ansiProtocol') -----
+ = aGenericYear
+ 	^aGenericYear class = GenericYear
+ 		and: [aGenericYear number = number]!

Item was changed:
  ----- Method: GenericYear>>addToDateTime: (in category 'ansiProtocol') -----
  addToDateTime: aDateAndTime
  	| next |
  	number < 0 ifTrue: [^self addNegativeToDateTime: aDateAndTime].
  	^(1 to: number) inject: aDateAndTime into: [:end :mnth|
+ 		next := end + ((end isLeapYear and: [end month > 2])
+ 			ifTrue: [end daysInYear - 1] "We've already factored in the extra leap year"
+ 			ifFalse: [end daysInYear] "either not a leap year, or we need the extra day"
+ 			) days.
+ 		"if we are now in a leap year, we may need to already factor in the extra day"
+ 		(next month > 2 and: [next isLeapYear and: [end dayOfMonth ~= next dayOfMonth]]) ifTrue: [next := next + 1 days].
+ 		"If we have leaped out of a leap year, and we were on Feb 29th, we need to back up to Feb 28th"
+ 		next month > end month ifTrue: [next := next - next dayOfMonth days].
- 		next := end + end daysInYear days.
- 		next month = end month
- 			ifFalse: [next := next - next dayOfMonth days].
  		next
  		].
  !

Item was added:
+ ----- Method: GenericYear>>addToDuration: (in category 'ansiProtocol') -----
+ addToDuration: aDuration
+ 	^GenericDuration new + aDuration + self
+ !

Item was added:
+ ----- Method: GenericYear>>printOn: (in category 'squeak protocol') -----
+ printOn: stream
+ 	stream nextPutAll: number asString; nextPutAll: ' year'.
+ 	number abs = 1 ifFalse: [stream nextPut: $s].!

Item was added:
+ ----- Method: GenericYear>>subtractFromDateTime: (in category 'ansiProtocol') -----
+ subtractFromDateTime: aDateAndTime
+ 	^self copy negated addToDateTime: aDateAndTime!

Item was added:
+ ----- Method: GenericYear>>subtractFromDuration: (in category 'ansiProtocol') -----
+ subtractFromDuration: aDuration
+ 	^GenericDuration new + aDuration - self!

Item was added:
+ ----- Method: Time>>addToDuration: (in category 'ansi protocol') -----
+ addToDuration: aDuration
+ 	^Duration nanoSeconds: (self asNanoSeconds + aDuration asNanoSeconds)
+ !

Item was added:
+ ----- Method: Time>>subtractFromDuration: (in category 'ansi protocol') -----
+ subtractFromDuration: aDuration
+ 	^Duration nanoSeconds: (aDuration asNanoSeconds - self asNanoSeconds)!

Item was changed:
  ----- Method: Timespan>>+ (in category 'ansi protocol') -----
+ + aDuration
+ 	"aDuration is one of: Duration, GenericDuration, GenericMonth, or GenericYear."
+ 	^self class starting: (aDuration addToDateTime: self start) duration: self duration
+ !
- + operand
- 	"operand conforms to protocol Duration"
- 	
- 
- 	^ self class starting: (self start + operand) duration: self duration!

Item was changed:
  ----- Method: Timespan>>- (in category 'ansi protocol') -----
  - operand
+ 	| result |
+ 	"operand is one of: Duration, GenericDuration, GenericMonth, or GenericYear; or a DateAndTime or Timespan."
+ 	result := operand subtractFromDateTime: self start.
+ 	^result class = DateAndTime
+ 		ifTrue: [ self class starting: result duration: self duration]
+ 		ifFalse: [result]
- 	"operand conforms to protocol DateAndTime or protocol Duration"
- 
- 	^ (operand respondsTo: #asDateAndTime)
- 
- 	 	ifTrue: [ self start - operand ]
- 	
- 	ifFalse: [ self + (operand negated) ]
  !

Item was changed:
  ----- Method: Timespan>>addToDateTime: (in category 'squeak protocol') -----
  addToDateTime: aDateAndTime
+ 	^start addToDateTime: aDateAndTime
- 	^duration addToDateTime: aDateAndTime
  !

Item was added:
+ ----- Method: Timespan>>subtractFromDateTime: (in category 'squeak protocol') -----
+ subtractFromDateTime: aDateAndTime
+ 	^start subtractFromDateTime: aDateAndTime!



More information about the Squeak-dev mailing list