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

commits at source.squeak.org commits at source.squeak.org
Fri Mar 6 23:49:11 UTC 2015


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

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

Name: Kernel-cbc.910
Author: cbc
Time: 6 March 2015, 3:48:56.226 pm
UUID: 6af9b576-3666-7444-ad16-9b84461a4dd0
Ancestors: Kernel-mt.909, Kernel-cbc.872

Changes to support adding months and years to a DateAndTime, such as:
DateAndTime now + 2 months
and
DateAndTimeNow - 5 years

This requires retro-fitting the + and - in DateAndTime to a double dispatch system, and requires changes in Collections as well (to support + and - with String representations).

Added support for chaining durations (such as 1 month + 1 day).

=============== Diff against Kernel-mt.909 ===============

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"
- 
- 	| ticks |
-  	ticks := self ticks + (operand asDuration ticks) .
- 
- 	^ self class basicNew
- 		ticks: ticks
- 		offset: self offset; 
- 		yourself
  !

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>>addToDateTime: (in category 'ansi protocol') -----
+ addToDateTime: aDateAndTime
+ 	^self asDuration addToDateTime: aDateAndTime
+ !

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>>addToDateTime: (in category 'ansi protocol') -----
+ addToDateTime: aDateAndTime
+ 	| ticks |
+  	ticks := self ticks + (aDateAndTime ticks) .
+ 	^ aDateAndTime class basicNew
+ 		ticks: ticks
+ 		offset: aDateAndTime offset; 
+ 		yourself
+ !

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'!
+ 
+ !GenericDuration commentStamp: 'cbc 9/21/2014 22:07' prior: 0!
+ The GenericDuration class exists to support simple DateAndTime arithmetic (also including Timespan, such as Date).  This class supports chains of different duration arthmetic with each other, such as:
+    1 year + 2 months + 3 days + 4 hours + 5 minuts + 6 seconds + 7 nanoSeconds
+ Instances of GenericDuration should be created by adding (or subtracting)2 or more durations with each other, including other instances of GenericDuration.
+ 
+ You cannot ask a GenericDuration how long it is.  This is a nonsensical question if a year or month is involved, as those are only resolvable once it is place into relationship to an actual date.
+ 
+ GenericDuration are associate, but not commutative.  That is
+    1 month + 31 days ~= 31 days + 1 month
+ but
+    ((1 month + 1 year) + 31 days) = (1 month + (1 year + 31 days))
+ !

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 addAllLast: aDuration sequence]
+ 		ifFalse: [sequence addLast: aDuration copy]
+ 	!

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 addAllLast: (aDuration sequence collect: [:s| s copy negated])]
+ 		ifFalse: [sequence addLast: aDuration copy negated]!

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 :duration | result + duration ]!

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

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

Item was added:
+ ----- Method: GenericDuration>>hash (in category 'ansii protocol') -----
+ hash
+ 	^(sequence collect: #hash) sum hash!

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 nextPutAll: ' + ']!

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 :duration | result + duration copy negated ]!

Item was added:
+ ----- Method: GenericDuration>>subtractFromDuration: (in category 'ansii protocol') -----
+ subtractFromDuration: aDuration
+ 	sequence addFirst: aDuration copy negated!

Item was added:
+ Object subclass: #GenericMonth
+ 	instanceVariableNames: 'number'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Chronology'!
+ 
+ !GenericMonth commentStamp: 'cbc 9/21/2014 22:01' prior: 0!
+ The GenericMonth class exists to support simple DateAndTime arithmetic with months (also including Timespan, such as Date).  This class is the mechanism behind:
+     DateAndTime now + 3 months
+ Instances of this class should be created by sending #month or #months to an integer (other types of number result in unspecified results).
+ (note that sending #month to any number will result in either exactly 1 month or -1 month, ignoring the actual number you send it too.)
+ 
+ Thse are the rules about what a 'month' is:
+ 1: If you add a month, you want the result to be in the next calendar month, never the following one.
+ 2: If you add a month, you want the same day of the month if possible, and if not (becaue the next month has less days), then the closest that you can get to it.
+ 4: If you add more than 1 month, you want to end up in the right calendar month that you would expect, and as close to the starting day of the month as you can.
+ 3: If you subtract a month, you want it in the previous calendar month, and as close to the starting day of the month as you can get.
+ 
+ So, adding 1 month to August 31 would give September 30th; adding 2 months to August 31 would give October 31st.  And adding 1 month to September 30th would give October 30th.
+ 
+ 
+ !

Item was added:
+ ----- Method: GenericMonth class>>months: (in category 'as yet unclassified') -----
+ months: aNumber
+ 	^self new number: aNumber!

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>>addNegativeToDateTime: (in category 'ansiProtocol') -----
+ addNegativeToDateTime: aDateAndTime
+ 	| next |
+ 	next := (1 to: number abs) inject: aDateAndTime into: [:end :mnth|
+ 		end - end dayOfMonth days.
+ 		].
+ 	^next - (next dayOfMonth - aDateAndTime dayOfMonth max: 0) days!

Item was added:
+ ----- Method: GenericMonth>>addToDateTime: (in category 'ansiProtocol') -----
+ addToDateTime: aDateAndTime
+ 	| next |
+ 	number < 0 ifTrue: [^self addNegativeToDateTime: aDateAndTime].
+ 	next := (1 to: number) inject: aDateAndTime into: [:end :mnth|
+ 		next := end + end daysInMonth days.
+ 		next dayOfMonth < end dayOfMonth
+ 			ifTrue: [next := next - next dayOfMonth days].
+ 		next
+ 		].
+ 	^next + ((next daysInMonth min: aDateAndTime dayOfMonth) - next dayOfMonth) days!

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

Item was added:
+ ----- Method: GenericMonth>>hash (in category 'ansiProtocol') -----
+ hash
+ 	^number hash!

Item was added:
+ ----- Method: GenericMonth>>negated (in category 'accessing') -----
+ negated
+ 	number := number negated!

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

Item was added:
+ ----- Method: GenericMonth>>number: (in category 'accessing') -----
+ number: anObject
+ 
+ 	number := anObject!

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:
+ Object subclass: #GenericYear
+ 	instanceVariableNames: 'number'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Chronology'!
+ 
+ !GenericYear commentStamp: 'cbc 9/21/2014 22:00' prior: 0!
+ The GenericYear class exists to support simple DateAndTime arithmetic with years (also including Timespan, such as Date).  This class is the mechanism behind:
+     DateAndTime now + 3 years
+ Instances of this class should be created by sending #year or #years to an integer (other types of number result in unspecified results).
+ (note that sending #year to any number will result in either exactly 1 year or -1 year, ignoring the actual number you send it too.)
+ 
+ Thse are the rules about what a 'year' is:
+ 1: If you add a year, you want the result to be in the next year, never the following one; it needs to end up in the same month as the starting month; and it needs to be the same day of the month if possible as the starting date, and if not (becaue the next years month has less days such as leap year to non-leap year), then the closest that you can get to it.
+ 4: If you add more than 1 year, you want to end up in the right year, same calendar month that you would expect, and as close to the starting day of the month as you can.
+ 3: If you subtract a year, you want it in the previous year and same calendar month, and as close to the starting day of the month as you can get.!

Item was added:
+ ----- Method: GenericYear class>>years: (in category 'as yet unclassified') -----
+ years: aNumber
+ 	^self new number: aNumber!

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 added:
+ ----- Method: GenericYear>>addNegativeToDateTime: (in category 'ansiProtocol') -----
+ addNegativeToDateTime: aDateAndTime
+ 	| next |
+ 	next := (1 to: number abs) inject: aDateAndTime into: [:end :mnth|
+ 		end - end dayOfYear days.
+ 		].
+ 	next := next - (next month - aDateAndTime month) months.
+ 	^next - (next dayOfMonth - aDateAndTime dayOfMonth max: 0) days!

Item was added:
+ ----- 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].
+ 		"If we have leeped out of a leap year, and we were on Mar 1st, we need to increment by 1 to get back where we should be"
+ 		next month < end month ifTrue: [next := next + 1 day].
+ 		next
+ 		].
+ !

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

Item was added:
+ ----- Method: GenericYear>>hash (in category 'ansiProtocol') -----
+ hash
+ 	^number hash!

Item was added:
+ ----- Method: GenericYear>>negated (in category 'accessing') -----
+ negated
+ 	number := number negated!

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

Item was added:
+ ----- Method: GenericYear>>number: (in category 'accessing') -----
+ number: anObject
+ 
+ 	number := anObject!

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 changed:
  ----- Method: Month>>previous (in category 'squeak protocol') -----
  previous
  
  
+ 	^ self class starting: (self start - 1 month)!
- 	^ self class starting: (self start - 1)!

Item was added:
+ ----- Method: Number>>addToDateTime: (in category 'arithmetic') -----
+ addToDateTime: aDateAndTime
+ 	"Utilized when adjusting DateAndTimes.  Such as:
+ 		DateAndTime now + 2
+ 	Not expected to be used outside of that system.
+ 	Note, also, that this keeps the long-standing tradition that we are adding nanoseconds to the DateAndTime."
+ 	^self asDuration addToDateTime: aDateAndTime
+ !

Item was added:
+ ----- Method: Number>>month (in category 'converting') -----
+ month
+ 
+ 	^ self sign months!

Item was added:
+ ----- Method: Number>>months (in category 'converting') -----
+ months
+ 
+ 	^ GenericMonth months: self!

Item was added:
+ ----- Method: Number>>subtractFromDateTime: (in category 'arithmetic') -----
+ subtractFromDateTime: aDateAndTime
+ 	"Utilized when adjusting DateAndTimes.  Such as:
+ 		DateAndTime now - 2
+ 	Not expected to be used outside of that system.
+ 	Note, also, that this keeps the long-standing tradition that we are subtracting nanoseconds to the DateAndTime."
+ 	^self asDuration subtractFromDateTime: aDateAndTime
+ !

Item was added:
+ ----- Method: Number>>year (in category 'converting') -----
+ year
+ 
+ 	^ self sign years!

Item was added:
+ ----- Method: Number>>years (in category 'converting') -----
+ years
+ 
+ 	^ GenericYear years: self!

Item was added:
+ ----- Method: Time>>addToDateTime: (in category 'squeak protocol') -----
+ addToDateTime: aDateAndTime
+ 	^self asDuration addToDateTime: aDateAndTime
+ !

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

Item was added:
+ ----- Method: Time>>subtractFromDateTime: (in category 'squeak protocol') -----
+ subtractFromDateTime: aDateAndTime
+ 	^self asDuration subtractFromDateTime: aDateAndTime
+ !

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 added:
+ ----- Method: Timespan>>addToDateTime: (in category 'squeak protocol') -----
+ 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