Double dispatching and Point

Travis or Kerrin Griggs tkc at bmi.net
Sun Feb 1 03:45:50 UTC 1998


OK Squeak-easies,

Here's the changes to make Squeak use double dispatching for it's math stuff. The first
two files, MathDD1.cs and MathDD2.cs change the 4 basic math ops for the three basic
Number types. File them in in order. The first adds the DD methods, the second changes
the math selectors to use them.

The other three files do the same for Point. They add the DD for Point and integrate it
with the changes made in the Math* files. They also do their best to make Point as
protocol possible with Number as reasonable. At the same time, I tried to hunt down any
messages that made Point act as if it were at the "top" of any sort of numerical
coercion hierarchy.

Finally, I have a question. In doing this, I found that the by the time I was done with
Point, it would have been much easier to make Point a subclass of Number. I could
probably get rid of quite a few messages that way as well. Is there a good reason not to
make Point a subclass of Number? If one were to create a filein that made these changes,
how would one do it? That is, for the most part, the filein would redefine Point (with
Number as its super) and then get rid of a whole bunch of methods. Can the change sorter
be used to put together a filein that instead of adding/changing methods, actually
removes them, or do I have to put that together myself?

Travis Griggs

BTW: These changes have been submitted to UIUC

'From Squeak 1.3 of Jan 16, 1998 on 28 January 1998 at 12:15:46 am'!

!Number methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:51'!
zeroDivideError
	^self error: 'Cannot divide by zero'! !


!Float methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:56'!
differenceFromFloat: aFloat
	^self primitiveFailed! !

!Float methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:56'!
differenceFromFraction: aFraction
	^aFraction asFloat - self! !

!Float methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:56'!
differenceFromInteger: anInteger
	^anInteger asFloat - self! !

!Float methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 09:06'!
productFromFloat: aFloat
	^self primitiveFailed! !

!Float methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 09:06'!
productFromFraction: aFraction
	^aFraction asFloat * self! !

!Float methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 09:06'!
productFromInteger: anInteger
	^anInteger asFloat * self! !

!Float methodsFor: 'arithmetic-DD' stamp: 'TAG 1/27/98 23:36'!
quotientFromFloat: aFloat 
	^self = 0.0
		ifTrue: [self zeroDivideError]
		ifFalse: [self primitiveFailed]! !

!Float methodsFor: 'arithmetic-DD' stamp: 'TAG 1/27/98 23:48'!
quotientFromFraction: aFraction
	^aFraction asFloat / self! !

!Float methodsFor: 'arithmetic-DD' stamp: 'TAG 1/28/98 09:14'!
quotientFromInteger: anInteger
	^anInteger asFloat / self! !

!Float methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 09:07'!
sumFromFloat: aFloat
	^self primitiveFailed! !

!Float methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 09:07'!
sumFromFraction: aFraction
	^aFraction asFloat + self! !

!Float methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 09:07'!
sumFromInteger: anInteger
	^anInteger asFloat + self! !


!Fraction methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:43'!
differenceFromFloat: aFloat
	^aFloat - self asFloat! !

!Fraction methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 09:10'!
differenceFromFraction: aFraction
	^aFraction numerator * denominator - (numerator * aFraction denominator) / (aFraction denominator * denominator)! !

!Fraction methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 09:10'!
differenceFromInteger: anInteger
	^anInteger * denominator - numerator / denominator! !

!Fraction methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:49'!
productFromFloat: aFloat
	^aFloat * self asFloat! !

!Fraction methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 09:12'!
productFromFraction: aFraction
	^aFraction numerator * numerator / (aFraction denominator * denominator)! !

!Fraction methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 09:12'!
productFromInteger: anInteger
	^anInteger * numerator / denominator! !

!Fraction methodsFor: 'arithmetic-DD' stamp: 'TAG 1/27/98 23:36'!
quotientFromFloat: aFloat
	^aFloat / self asFloat! !

!Fraction methodsFor: 'arithmetic-DD' stamp: 'TAG 1/27/98 23:38'!
quotientFromFraction: aFraction
	^aFraction numerator * denominator / (aFraction denominator * numerator)! !

!Fraction methodsFor: 'arithmetic-DD' stamp: 'TAG 1/27/98 23:37'!
quotientFromInteger: anInteger 
	^anInteger * denominator / numerator! !

!Fraction methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:54'!
sumFromFloat: aFloat
	^aFloat + self asFloat! !

!Fraction methodsFor: 'arithmetic-DD' stamp: 'TAG 1/27/98 23:44'!
sumFromFraction: aFraction
	^aFraction numerator * denominator + (numerator * aFraction denominator) / (aFraction denominator * denominator)! !

!Fraction methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:54'!
sumFromInteger: anInteger
	^self primitiveFailed! !


!Integer methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:43'!
differenceFromFloat: aFloat
	^aFloat - self asFloat! !

!Integer methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:52'!
differenceFromFraction: aFraction
	^aFraction numerator - (self * aFraction denominator) / aFraction denominator! !

!Integer methodsFor: 'arithmetic-DD' stamp: 'TAG 1/28/98 08:33'!
differenceFromInteger: anInteger 
	^self negative == anInteger negative
		ifTrue: [self digitSubtract: anInteger]
		ifFalse: [(self digitAdd: anInteger) normalize]! !

!Integer methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:49'!
productFromFloat: aFloat
	^aFloat * self asFloat! !

!Integer methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:49'!
productFromFraction: aFraction
	^aFraction numerator * self / aFraction denominator! !

!Integer methodsFor: 'arithmetic-DD' stamp: 'TAG 1/28/98 08:34'!
productFromInteger: anInteger 
	^self digitMultiply: anInteger neg: self negative ~~ anInteger negative! !

!Integer methodsFor: 'arithmetic-DD' stamp: 'TAG 1/27/98 23:36'!
quotientFromFloat: aFloat
	^aFloat / self asFloat! !

!Integer methodsFor: 'arithmetic-DD' stamp: 'TAG 1/27/98 23:38'!
quotientFromFraction: aFraction
	^aFraction numerator / (aFraction denominator * self)! !

!Integer methodsFor: 'arithmetic-DD' stamp: 'TAG 1/28/98 09:12'!
quotientFromInteger: anInteger 
	| quoRem |
	^self = 0
		ifTrue: [self zeroDivideError]
		ifFalse: [
quoRem _ self digitDiv: anInteger 
								neg: self negative ~~ anInteger negative.
				(quoRem at: 2) = 0
					ifTrue: [(quoRem at: 1) normalize]
					ifFalse: [(Fraction numerator: anInteger denominator: self) reduced]]! !

!Integer methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:54'!
sumFromFloat: aFloat
	^aFloat + self asFloat! !

!Integer methodsFor: 'arithmetic-DD' stamp: 'TAG 1/23/98 07:54'!
sumFromFraction: aFraction
	^aFraction numerator + (self * aFraction numerator) / aFraction denominator! !

!Integer methodsFor: 'arithmetic-DD' stamp: 'TAG 1/28/98 08:32'!
sumFromInteger: anInteger 
	^self negative == anInteger negative
		ifTrue: [(self digitAdd: anInteger) normalize]
		ifFalse: [self digitSubtract: anInteger]! !



'From Squeak 1.3 of Jan 16, 1998 on 30 January 1998 at 12:53:38 am'!

!Float methodsFor: 'arithmetic' stamp: 'TAG 1/27/98 23:57'!
* aNumber 
	"Primitive. Answer the result of multiplying the receiver by aNumber.
	Fail if the argument is not a Float. Essential. See Object documentation
	whatIsAPrimitive."

	<primitive: 49>
	"get the argument to actually carry out the operation since it can tune the operation based on my type, if it's the same class then the primitive failure is raised there"
	^aNumber productFromFloat: self! !

!Float methodsFor: 'arithmetic' stamp: 'TAG 1/27/98 23:57'!
+ aNumber 
	"Primitive. Answer the sum of the receiver and aNumber. Essential.
	Fail if the argument is not a Float. See Object documentation
	whatIsAPrimitive."

	<primitive: 41>
	"get the argument to actually carry out the operation since it can tune the operation based on my type, if it's the same class then the primitive failure is raised there"
	^aNumber sumFromFloat: self! !

!Float methodsFor: 'arithmetic' stamp: 'TAG 1/27/98 23:57'!
- aNumber 
	"Primitive. Answer the difference between the receiver and aNumber.
	Fail if the argument is not a Float. Essential. See Object documentation
	whatIsAPrimitive."

	<primitive: 42>
	"get the argument to actually carry out the operation since it can tune the operation based on my type, if it's the same class then the primitive failure is raised there"
	^aNumber differenceFromFloat: self! !

!Float methodsFor: 'arithmetic' stamp: 'TAG 1/27/98 23:58'!
/ aNumber 
	"Primitive. Answer the result of dividing receiver by aNumber.
	Fail if the argument is not a Float. Essential. See Object documentation
	whatIsAPrimitive."

	<primitive: 50>
	"get the argument to actually carry out the operation since it can tune the operation based on my type, if it's the same class then the primitive failure is raised there, as well as zero divide detection"
	^aNumber quotientFromFloat: self! !


!Fraction methodsFor: 'arithmetic' stamp: 'TAG 1/27/98 23:40'!
* aNumber
	"get the argument to actually carry out the operation since it can tune the operation based on my type"
	^aNumber productFromFraction: self! !

!Fraction methodsFor: 'arithmetic' stamp: 'TAG 1/27/98 23:41'!
+ aNumber
	"get the argument to actually carry out the operation since it can tune the operation based on my type"
	^aNumber sumFromFraction: self! !

!Fraction methodsFor: 'arithmetic' stamp: 'TAG 1/27/98 23:46'!
- aNumber
	"get the argument to actually carry out the operation since it can tune the operation based on my type"
	^aNumber differenceFromFraction: self! !

!Fraction methodsFor: 'arithmetic' stamp: 'TAG 1/27/98 23:46'!
/ aNumber
	"get the argument to actually carry out the operation since it can tune the operation based on my type"
	^aNumber quotientFromFraction: self! !


!Integer methodsFor: 'arithmetic' stamp: 'TAG 1/28/98 09:16'!
* aNumber
	"get the argument to actually carry out the operation since it can tune the operation based on my type"
	^aNumber productFromInteger: self! !

!Integer methodsFor: 'arithmetic' stamp: 'TAG 1/28/98 0-10:'!
+ aNumber
	"get the argument to actually carry out the operation since it can tune the operation based on my type"
	^aNumber sumFromInteger: self! !

!Integer methodsFor: 'arithmetic' stamp: 'TAG 1/28/98 09:17'!
- aNumber
	"get the argument to actually carry out the operation since it can tune the operation based on my type"
	^aNumber differenceFromInteger: self! !

!Integer methodsFor: 'arithmetic' stamp: 'TAG 1/28/98 09:15'!
/ aNumber
	"get the argument to actually carry out the operation since it can tune the operation based on my type"
	^aNumber quotientFromInteger: self! !



'From Squeak 1.3 of Jan 16, 1998 on 29 January 1998 at 12:25:34 am'!

!Number methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
differenceFromPoint: aPoint 
	^aPoint x - self @ (aPoint y - self)! !

!Number methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
productFromPoint: aPoint 
	^aPoint x * self @ (aPoint y * self)! !

!Number methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
quotientFromPoint: aPoint 
	^aPoint x / self @ (aPoint y / self)! !

!Number methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
sumFromPoint: aPoint 
	^aPoint x + self @ (aPoint y + self)! !


!Point methodsFor: 'arithmetic' stamp: 'TAG 1/29/98 0-24:'!
negated
	"Answer a point whose x and y coordinates are the negatives of those of the receiver.  6/6/96 sw"

	^ x negated @ y negated! !

!Point methodsFor: 'arithmetic' stamp: 'TAG 1/29/98 0-24:'!
reciprocal
	^x reciprocal @ y reciprocal! !

!Point methodsFor: 'mathematical functions' stamp: 'TAG 1/29/98 0-24:'!
exp
	^x exp @ y exp!
]style[(19)f1b! !

!Point methodsFor: 'mathematical functions' stamp: 'TAG 1/29/98 0-24:'!
floorLog: aNumber
	^(x floorLog: aNumber) @ (y floorLog: aNumber)!
]style[(65)f1b! !

!Point methodsFor: 'mathematical functions' stamp: 'TAG 1/29/98 0-24:'!
ln
	^x ln @ y ln!
]style[(16)f1b! !

!Point methodsFor: 'mathematical functions' stamp: 'TAG 1/29/98 0-24:'!
log: aNumber
	^(x log: aNumber) @ (y log: aNumber)!
]style[(50)f1b! !

!Point methodsFor: 'mathematical functions' stamp: 'TAG 1/29/98 0-24:'!
raisedTo: aNumber
	"Number compatibility"
	^(x raisedTo: aNumber) @ (y raisedTo: aNumber)!
]style[(41 48)f1b,f1! !

!Point methodsFor: 'mathematical functions' stamp: 'TAG 1/29/98 0-24:'!
raisedToInteger: aNumber
	"Number compatibility"
	^(x raisedToInteger: aNumber) @ (y raisedToInteger: aNumber)!
]style[(48 6 16 15 16 9)f1b,f1,f1b,f1,f1b,f1! !

!Point methodsFor: 'mathematical functions' stamp: 'TAG 1/29/98 0-24:'!
sqrt
	^x sqrt @ y sqrt!
]style[(22)f1b! !

!Point methodsFor: 'mathematical functions' stamp: 'TAG 1/29/98 0-24:'!
squared
	^x squared @ y squared!
]style[(31)f1b! !

!Point methodsFor: 'truncation and round off' stamp: 'TAG 1/29/98 0-24:'!
ceiling
	"return the point where both x and y are the ceiling values of the receiver"
	^x ceiling @ y ceiling!
]style[(109)f1b! !

!Point methodsFor: 'truncation and round off' stamp: 'TAG 1/29/98 0-24:'!
floor
	"return the point where both x and y are the ceiling values of the receiver"
	^x floor @ y floor!
]style[(103)f1b! !

!Point methodsFor: 'truncation and round off' stamp: 'TAG 1/29/98 0-24:'!
roundTo: aNumber 
	"implemented like Number of upwards scalability"

	^(self / aNumber) rounded * aNumber! !

!Point methodsFor: 'truncation and round off' stamp: 'TAG 1/29/98 0-24:'!
truncated
	"Answer a Point that is the receiver's x and y truncated by removing the fractional part."

	^x truncated @ y truncated! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
differenceFromFloat: aFloat
	^aFloat - x @ (aFloat - y)! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
differenceFromFraction: aFraction
	^aFraction - x @ (aFraction - y)!
]style[(33 3 9 8 9 5)f1b,f1,f1b,f1,f1b,f1! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
differenceFromInteger: anInteger
	^anInteger - x @ (anInteger - y)! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
differenceFromPoint: aPoint
	^aPoint x - x @ (aPoint y - y)! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
productFromFloat: aFloat
	^aFloat * x @ (aFloat * y)! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
productFromFraction: aFraction
	^aFraction * x @ (aFraction * y)!
]style[(30 3 9 8 9 5)f1b,f1,f1b,f1,f1b,f1! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
productFromInteger: anInteger
	^anInteger * x @ (anInteger * y)! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
productFromPoint: aPoint
	^aPoint x * x @ (aPoint y * y)! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
quotientFromFloat: aFloat
	^aFloat / x @ (aFloat / y)! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
quotientFromFraction: aFraction
	^aFraction / x @ (aFraction / y)!
]style[(31 3 9 8 9 5)f1b,f1,f1b,f1,f1b,f1! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
quotientFromInteger: anInteger
	^anInteger / x @ (anInteger / y)! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
quotientFromPoint: aPoint
	^aPoint x / x @ (aPoint y / y)! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
sumFromFloat: aFloat
	^aFloat + x @ (aFloat + y)! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
sumFromFraction: aFraction
	^aFraction + x @ (aFraction + y)!
]style[(26 3 9 8 9 5)f1b,f1,f1b,f1,f1b,f1! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
sumFromInteger: anInteger
	^anInteger + x @ (anInteger + y)! !

!Point methodsFor: 'arithmetic-DD' stamp: 'TAG 1/29/98 0-23:'!
sumFromPoint: aPoint
	^aPoint x + x @ (aPoint y + y)! !



'From Squeak 1.3 of Jan 16, 1998 on 29 January 1998 at 12:22:38 am'!

!Point methodsFor: 'arithmetic' stamp: 'TAG 1/29/98 0-24:'!
// scale 
	"reimplemented for upwards scalability"

	^(self / scale) floor! !

!Point methodsFor: 'arithmetic' stamp: 'TAG 1/29/98 0-24:'!
quo: scale 
	"implemented as such for upwards scalability"

	^(self / scale) truncated! !



'From Squeak 1.3 of Jan 16, 1998 on 30 January 1998 at 12:56:18 am'!

!Point methodsFor: 'arithmetic' stamp: 'TAG 1/29/98 0-24:'!
rem: aNumericalThing
	"implemented just like Number, for upwards scalability"

	^self - ((self quo: aNumericalThing) * aNumericalThing)!
]style[(11 89 6 13 6 10)f1b,f1,f1b,f1,f1b,f1! !

!Point methodsFor: 'arithmetic' stamp: 'TAG 1/29/98 0-24:'!
\\ aNumericalThing
	"implemented just like Number, for upwards scalability"

	^self - (self // aNumericalThing * aNumericalThing)!
]style[(18 77 15 3 15 1)f1b,f1,f1b,f1,f1b,f1! !

!Point methodsFor: 'truncation and round off' stamp: 'TAG 1/29/98 0-24:'!
roundTo: aNumericalThing 
	"implemented like Number for compatibility"

	^(self / aNumericalThing) rounded * aNumericalThing!
]style[(24 85 15)f1b,f1,f1b! !

!Point methodsFor: 'truncation and round off' stamp: 'TAG 1/30/98 0-24:'!
roundUpTo: aNumber 
	"same as Number, but for points"

	^(self/aNumber) ceiling * aNumber! !

!Point methodsFor: 'truncation and round off' stamp: 'TAG 1/29/98 0-24:'!
truncateTo: aNumericalThing 
	"implemented just like Number"

	^(self quo: aNumericalThing) * aNumericalThing!
]style[(27 48 15 4 15)f1b,f1,f1b,f1,f1b! !





More information about the Squeak-dev mailing list