[squeak-dev] The Inbox: Kernel-mtf.527.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Dec 13 22:04:43 UTC 2010


Matthew Fulmer uploaded a new version of Kernel to project The Inbox:
http://source.squeak.org/inbox/Kernel-mtf.527.mcz

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

Name: Kernel-mtf.527
Author: mtf
Time: 13 December 2010, 5:03:32.48 pm
UUID: eee5f8ce-e738-4da7-bd87-64f50998fd53
Ancestors: Kernel-mtf.526

Use FloatMathPlugin for bit-identical floating point operations across machines. Needed by Croquet.

Cherrypicked from Croquet:

Name: Kernel-ar.16
Author: ar
Time: 26 March 2006, 7:01:20 pm
UUID: 99b21c76-119e-5440-aff8-02dfe0ecf377
Ancestors: Kernel-tmp.15

- use FloatMathPlugin primitives for Float

=============== Diff against Kernel-mtf.526 ===============

Item was changed:
  ----- Method: Float>>arcCos (in category 'mathematical functions') -----
  arcCos
  	"Answer the angle in radians."
+ 	<primitive: 'primitiveArcCos' module: 'FloatMathPlugin'>
- 
  	^ Halfpi - self arcSin!

Item was added:
+ ----- Method: Float>>arcCosH (in category 'mathematical functions') -----
+ arcCosH
+ 	<primitive: 'primitiveArcCosH' module: 'FloatMathPlugin'>
+ 	^self primitiveFailed!

Item was changed:
  ----- Method: Float>>arcSin (in category 'mathematical functions') -----
  arcSin
  	"Answer the angle in radians."
+ 	<primitive: 'primitiveArcSin' module: 'FloatMathPlugin'>
- 
  	((self < -1.0) or: [self > 1.0]) ifTrue: [self error: 'Value out of range'].
  	((self = -1.0) or: [self = 1.0])
  		ifTrue: [^ Halfpi * self]
  		ifFalse: [^ (self / (1.0 - (self * self)) sqrt) arcTan]!

Item was added:
+ ----- Method: Float>>arcSinH (in category 'mathematical functions') -----
+ arcSinH
+ 	<primitive: 'primitiveArcSinH' module: 'FloatMathPlugin'>
+ 	^self primitiveFailed!

Item was changed:
  ----- Method: Float>>arcTan (in category 'mathematical functions') -----
  arcTan
  	"Answer the angle in radians.
  	 Optional. See Object documentation whatIsAPrimitive."
+ 	<primitive: 'primitiveArcTan' module: 'FloatMathPlugin'>
+ 	self = self ifFalse:[^self error: 'arcTan is undefined for NaN'].
- 
- 	| theta eps step sinTheta cosTheta |
- 	<primitive: 57>
- 
- 	"Newton-Raphson"
  	self < 0.0 ifTrue: [ ^ 0.0 - (0.0 - self) arcTan ].
+ 	^self primitiveArcTan!
- 
- 	"first guess"
- 	theta := (self * Halfpi) / (self + 1.0).
- 
- 	"iterate"
- 	eps := Halfpi * Epsilon.
- 	step := theta.
- 	[(step * step) > eps] whileTrue: [
- 		sinTheta := theta sin.
- 		cosTheta := theta cos.
- 		step := (sinTheta * cosTheta) - (self * cosTheta * cosTheta).
- 		theta := theta - step].
- 	^ theta!

Item was changed:
  ----- Method: Float>>arcTan: (in category 'mathematical functions') -----
  arcTan: denominator
  	"Answer the angle in radians.
+ 	 Optional. See Object documentation whatIsAPrimitive."
+ 	| result |
+ 	<primitive: 'primitiveArcTan2' module: 'FloatMathPlugin'>
+ 	(self = 0.0) ifTrue: [ 
+ 		(denominator > 0.0) 
+ 			ifTrue: [ result := 0 ]
+ 			ifFalse: [ result := Pi ]
+ 	] ifFalse: [
+ 		(denominator = 0.0) ifTrue: [ 
+ 			(self > 0.0) 
+ 				ifTrue: [ result := Halfpi ]
+ 				ifFalse: [ result := Halfpi negated ]
+ 		] ifFalse: [ 
+ 			(denominator > 0) 
+ 				ifTrue: [ result := (self / denominator) arcTan ]
+ 				ifFalse: [ result := ((self / denominator) arcTan) + Pi ]
+ 		].
+ 	].
+ 	^ result.!
- 	 Optional. See Object documentation whatIsAPrimitive.
- 	Implementation note: use sign in order to catch cases of negativeZero"
- 
- 	^self = 0.0
- 		ifTrue: [denominator sign >= 0
- 			ifTrue: [ 0 ]
- 			ifFalse: [ self sign >= 0
- 				ifTrue: [ Pi ]
- 				ifFalse: [ Pi negated ]]]
- 		ifFalse: [denominator = 0.0
- 			ifTrue: [self > 0.0
- 				ifTrue: [ Halfpi ]
- 				ifFalse: [ Halfpi negated ]]
- 			ifFalse: [denominator > 0
- 				ifTrue: [ (self / denominator) arcTan ]
- 				ifFalse: [self > 0
- 					ifTrue: [ ((self / denominator) arcTan) + Pi ]
- 					ifFalse: [ ((self / denominator) arcTan) - Pi ]]]]!

Item was added:
+ ----- Method: Float>>arcTanH (in category 'mathematical functions') -----
+ arcTanH
+ 	<primitive: 'primitiveArcTanH' module: 'FloatMathPlugin'>
+ 	^self primitiveFailed!

Item was changed:
  ----- Method: Float>>cos (in category 'mathematical functions') -----
  cos
  	"Answer the cosine of the receiver taken as an angle in radians."
+ 	<primitive: 'primitiveCos' module: 'FloatMathPlugin'>
+ 	self = self ifFalse:[^self error: 'cos is undefined for NaN'].
+ 	self abs = Float infinity ifTrue:[^self error: 'cos is undefined for Infinity'].
- 
  	^ (self + Halfpi) sin!

Item was added:
+ ----- Method: Float>>cosH (in category 'mathematical functions') -----
+ cosH
+ 	"Answer the cosine of the receiver taken as an angle in radians."
+ 	<primitive: 'primitiveCosH' module: 'FloatMathPlugin'>
+ 	^self primitiveFailed!

Item was changed:
  ----- Method: Float>>exp (in category 'mathematical functions') -----
  exp
  	"Answer E raised to the receiver power.
  	 Optional. See Object documentation whatIsAPrimitive." 
  
+ 	<primitive: 'primitiveExp' module: 'FloatMathPlugin'>
+ 	self = self ifFalse:[^self error: 'exp is undefined for NaN'].
+ 	"For now, fall back to the Squeak version of exp if FloatMathPlugin is absent"
+ 	^self primitiveExp!
- 	| base fract correction delta div |
- 	<primitive: 59>
- 
- 	"Taylor series"
- 	"check the special cases"
- 	self < 0.0 ifTrue: [^ (self negated exp) reciprocal].
- 	self = 0.0 ifTrue: [^ 1].
- 	self abs > MaxValLn ifTrue: [self error: 'exp overflow'].
- 
- 	"get first approximation by raising e to integer power"
- 	base := E raisedToInteger: (self truncated).
- 
- 	"now compute the correction with a short Taylor series"
- 	"fract will be 0..1, so correction will be 1..E"
- 	"in the worst case, convergance time is logarithmic with 1/Epsilon"
- 	fract := self fractionPart.
- 	fract = 0.0 ifTrue: [ ^ base ].  "no correction required"
- 
- 	correction := 1.0 + fract.
- 	delta := fract * fract / 2.0.
- 	div := 2.0.
- 	[delta > Epsilon] whileTrue: [
- 		correction := correction + delta.
- 		div := div + 1.0.
- 		delta := delta * fract / div].
- 	correction := correction + delta.
- 	^ base * correction!

Item was changed:
  ----- Method: Float>>fractionPart (in category 'truncation and round off') -----
  fractionPart
  	"Primitive. Answer a Float whose value is the difference between the 
  	receiver and the receiver's asInteger value. Optional. See Object 
  	documentation whatIsAPrimitive."
+ 	<primitive: 'primitiveFractionalPart' module: 'FloatMathPlugin'>
- 
- 	<primitive: 52>
  	^self - self truncated asFloat!

Item was added:
+ ----- Method: Float>>hypot: (in category 'mathematical functions') -----
+ hypot: arg
+ 	"hypot(x,y) returns sqrt(x^2+y^2) with error less  than 1 ulps"
+ 	<primitive: 'primitiveHypot' module: 'FloatMathPlugin'>
+ 	arg isFloat ifFalse:[^self hypot: arg asFloat].
+ 	^self primitiveFailed!

Item was changed:
  ----- Method: Float>>ln (in category 'mathematical functions') -----
  ln
  	"Answer the natural logarithm of the receiver.
  	 Optional. See Object documentation whatIsAPrimitive."
+ 	<primitive: 'primitiveLogN' module: 'FloatMathPlugin'>
+ 	self <= 0.0 ifTrue: [^self error: 'ln is only defined for x > 0.0'].
+ 	^self primitiveLn!
- 
- 	| expt n mant x div pow delta sum eps |
- 	<primitive: 58>
- 
- 	"Taylor series"
- 	self <= 0.0 ifTrue: [self error: 'ln is only defined for x > 0.0'].
- 
- 	"get a rough estimate from binary exponent"
- 	expt := self exponent.
- 	n := Ln2 * expt.
- 	mant := self timesTwoPower: 0 - expt.
- 
- 	"compute fine correction from mantinssa in Taylor series"
- 	"mant is in the range [0..2]"
- 	"we unroll the loop to avoid use of abs"
- 	x := mant - 1.0.
- 	div := 1.0.
- 	pow := delta := sum := x.
- 	x := x negated.  "x <= 0"
- 	eps := Epsilon * (n abs + 1.0).
- 	[delta > eps] whileTrue: [
- 		"pass one: delta is positive"
- 		div := div + 1.0.
- 		pow := pow * x.
- 		delta := pow / div.
- 		sum := sum + delta.
- 		"pass two: delta is negative"
- 		div := div + 1.0.
- 		pow := pow * x.
- 		delta := pow / div.
- 		sum := sum + delta].
- 
- 	^ n + sum
- 
- 	"2.718284 ln 1.0"!

Item was changed:
  ----- Method: Float>>log (in category 'mathematical functions') -----
  log
  	"Answer the base 10 logarithm of the receiver."
+ 	<primitive: 'primitiveLog10' module: 'FloatMathPlugin'>
- 
  	^ self ln / Ln10!

Item was added:
+ ----- Method: Float>>primitiveArcTan (in category 'primitives') -----
+ primitiveArcTan
+ 	"Answer the angle in radians.
+ 	 Optional. See Object documentation whatIsAPrimitive."
+ 
+ 	| theta eps step sinTheta cosTheta |
+ 	<primitive: 57>
+ 
+ 	"Newton-Raphson"
+ 	self < 0.0 ifTrue: [ ^ 0.0 - (0.0 - self) arcTan ].
+ 
+ 	"first guess"
+ 	theta := (self * Halfpi) / (self + 1.0).
+ 
+ 	"iterate"
+ 	eps := Halfpi * Epsilon.
+ 	step := theta.
+ 	[(step * step) > eps] whileTrue: [
+ 		sinTheta := theta sin.
+ 		cosTheta := theta cos.
+ 		step := (sinTheta * cosTheta) - (self * cosTheta * cosTheta).
+ 		theta := theta - step].
+ 	^ theta!

Item was added:
+ ----- Method: Float>>primitiveExp (in category 'primitives') -----
+ primitiveExp
+ 	"Answer E raised to the receiver power.
+ 	 Optional. See Object documentation whatIsAPrimitive." 
+ 
+ 	| base fract correction delta div |
+ 	<primitive: 59>
+ 
+ 	"Taylor series"
+ 	"check the special cases"
+ 	self < 0.0 ifTrue: [^ (self negated exp) reciprocal].
+ 	self = 0.0 ifTrue: [^ 1].
+ 	self abs > MaxValLn ifTrue: [self error: 'exp overflow'].
+ 
+ 	"get first approximation by raising e to integer power"
+ 	base := E raisedToInteger: (self truncated).
+ 
+ 	"now compute the correction with a short Taylor series"
+ 	"fract will be 0..1, so correction will be 1..E"
+ 	"in the worst case, convergance time is logarithmic with 1/Epsilon"
+ 	fract := self fractionPart.
+ 	fract = 0.0 ifTrue: [ ^ base ].  "no correction required"
+ 
+ 	correction := 1.0 + fract.
+ 	delta := fract * fract / 2.0.
+ 	div := 2.0.
+ 	[delta > Epsilon] whileTrue: [
+ 		correction := correction + delta.
+ 		div := div + 1.0.
+ 		delta := delta * fract / div].
+ 	correction := correction + delta.
+ 	^ base * correction!

Item was added:
+ ----- Method: Float>>primitiveFractionPart (in category 'primitives') -----
+ primitiveFractionPart
+ 	"Primitive. Answer a Float whose value is the difference between the 
+ 	receiver and the receiver's asInteger value. Optional. See Object 
+ 	documentation whatIsAPrimitive."
+ 
+ 	<primitive: 52>
+ 	^self - self truncated asFloat!

Item was added:
+ ----- Method: Float>>primitiveLn (in category 'primitives') -----
+ primitiveLn
+ 	"Answer the natural logarithm of the receiver.
+ 	 Optional. See Object documentation whatIsAPrimitive."
+ 
+ 	| expt n mant x div pow delta sum eps |
+ 	<primitive: 58>
+ 
+ 	"Taylor series"
+ 	self <= 0.0 ifTrue: [self error: 'ln is only defined for x > 0.0'].
+ 
+ 	"get a rough estimate from binary exponent"
+ 	expt := self exponent.
+ 	n := Ln2 * expt.
+ 	mant := self timesTwoPower: 0 - expt.
+ 
+ 	"compute fine correction from mantinssa in Taylor series"
+ 	"mant is in the range [0..2]"
+ 	"we unroll the loop to avoid use of abs"
+ 	x := mant - 1.0.
+ 	div := 1.0.
+ 	pow := delta := sum := x.
+ 	x := x negated.  "x <= 0"
+ 	eps := Epsilon * (n abs + 1.0).
+ 	[delta > eps] whileTrue: [
+ 		"pass one: delta is positive"
+ 		div := div + 1.0.
+ 		pow := pow * x.
+ 		delta := pow / div.
+ 		sum := sum + delta.
+ 		"pass two: delta is negative"
+ 		div := div + 1.0.
+ 		pow := pow * x.
+ 		delta := pow / div.
+ 		sum := sum + delta].
+ 
+ 	^ n + sum
+ 
+ 	"2.718284 ln 1.0"!

Item was added:
+ ----- Method: Float>>primitiveSin (in category 'primitives') -----
+ primitiveSin
+ 	"Answer the sine of the receiver taken as an angle in radians.
+ 	 Optional. See Object documentation whatIsAPrimitive."
+ 
+ 	| sum delta self2 i |
+ 	<primitive: 56>
+ 
+ 	"Taylor series"
+ 	"normalize to the range [0..Pi/2]"
+ 	self < 0.0 ifTrue: [^ (0.0 - ((0.0 - self) sin))].
+ 	self > Twopi ifTrue: [^ (self \\ Twopi) sin].
+ 	self > Pi ifTrue: [^ (0.0 - (self - Pi) sin)].
+ 	self > Halfpi ifTrue: [^ (Pi - self) sin].
+ 
+ 	"unroll loop to avoid use of abs"
+ 	sum := delta := self.
+ 	self2 := 0.0 - (self * self).
+ 	i := 2.0.
+ 	[delta > Epsilon] whileTrue: [
+ 		"once"
+ 		delta := (delta * self2) / (i * (i + 1.0)).
+ 		i := i + 2.0.
+ 		sum := sum + delta.
+ 		"twice"
+ 		delta := (delta * self2) / (i * (i + 1.0)).
+ 		i := i + 2.0.
+ 		sum := sum + delta].
+ 	^ sum!

Item was added:
+ ----- Method: Float>>primitiveSqrt (in category 'primitives') -----
+ primitiveSqrt
+ 	"Answer the square root of the receiver. 
+ 	 Optional. See Object documentation whatIsAPrimitive."
+ 	| exp guess eps delta |
+ 	<primitive: 55>
+ 	#Numeric.
+ 	"Changed 200/01/19 For ANSI <number> support."
+ 	"Newton-Raphson"
+ 	self <= 0.0
+ 		ifTrue: [self = 0.0
+ 				ifTrue: [^ 0.0]
+ 				ifFalse: ["v Chg"
+ 					^ FloatingPointException signal: 'undefined if less than zero.']].
+ 	"first guess is half the exponent"
+ 	exp := self exponent // 2.
+ 	guess := self timesTwoPower: 0 - exp.
+ 	"get eps value"
+ 	eps := guess * Epsilon.
+ 	eps := eps * eps.
+ 	delta := self - (guess * guess) / (guess * 2.0).
+ 	[delta * delta > eps]
+ 		whileTrue: 
+ 			[guess := guess + delta.
+ 			delta := self - (guess * guess) / (guess * 2.0)].
+ 	^ guess!

Item was added:
+ ----- Method: Float>>primitiveTimesTwoPower: (in category 'primitives') -----
+ primitiveTimesTwoPower: anInteger 
+ 	"Primitive. Answer with the receiver multiplied by 2.0 raised
+ 	to the power of the argument.
+ 	Optional. See Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 54>
+ 
+ 	anInteger < -29 ifTrue: [^ self * (2.0 raisedToInteger: anInteger)].
+ 	anInteger < 0 ifTrue: [^ self / (1 bitShift: (0 - anInteger)) asFloat].
+ 	anInteger < 30 ifTrue: [^ self * (1 bitShift: anInteger) asFloat].
+ 	^ self * (2.0 raisedToInteger: anInteger)!

Item was changed:
  ----- Method: Float>>sin (in category 'mathematical functions') -----
  sin
  	"Answer the sine of the receiver taken as an angle in radians.
  	 Optional. See Object documentation whatIsAPrimitive."
+ 	<primitive: 'primitiveSin' module: 'FloatMathPlugin'>
+ 	self = self ifFalse:[^self error: 'sin is undefined for NaN'].
+ 	self abs = Float infinity ifTrue:[^self error: 'sin is undefined for Infinity'].
+ 	^self primitiveSin!
- 
- 	| sum delta self2 i |
- 	<primitive: 56>
- 
- 	"Taylor series"
- 	"normalize to the range [0..Pi/2]"
- 	self < 0.0 ifTrue: [^ (0.0 - ((0.0 - self) sin))].
- 	self > Twopi ifTrue: [^ (self \\ Twopi) sin].
- 	self > Pi ifTrue: [^ (0.0 - (self - Pi) sin)].
- 	self > Halfpi ifTrue: [^ (Pi - self) sin].
- 
- 	"unroll loop to avoid use of abs"
- 	sum := delta := self.
- 	self2 := 0.0 - (self * self).
- 	i := 2.0.
- 	[delta > Epsilon] whileTrue: [
- 		"once"
- 		delta := (delta * self2) / (i * (i + 1.0)).
- 		i := i + 2.0.
- 		sum := sum + delta.
- 		"twice"
- 		delta := (delta * self2) / (i * (i + 1.0)).
- 		i := i + 2.0.
- 		sum := sum + delta].
- 	^ sum!

Item was added:
+ ----- Method: Float>>sinH (in category 'mathematical functions') -----
+ sinH
+ 	<primitive: 'primitiveSinH' module: 'FloatMathPlugin'>
+ 	^self primitiveFailed!

Item was changed:
  ----- Method: Float>>sqrt (in category 'mathematical functions') -----
  sqrt
  	"Answer the square root of the receiver. 
  	 Optional. See Object documentation whatIsAPrimitive."
+ 
+ 	"ar 3/26/2006: sqrt is the ONE primitive that we really don't want to use from FloatMathPlugin - it's several times slower and we use it often enough that this can make a noticable difference"
+ 
+ 	<primitive: 55> "instead of: <primitive: 'primitiveSqrt' module: 'FloatMathPlugin'>"
+ 	^self primitiveSqrt!
- 	| exp guess eps delta |
- 	<primitive: 55>
- 	#Numeric.
- 	"Changed 200/01/19 For ANSI <number> support."
- 	"Newton-Raphson"
- 	self <= 0.0
- 		ifTrue: [self = 0.0
- 				ifTrue: [^ 0.0]
- 				ifFalse: ["v Chg"
- 					^ FloatingPointException signal: 'undefined if less than zero.']].
- 	"first guess is half the exponent"
- 	exp := self exponent // 2.
- 	guess := self timesTwoPower: 0 - exp.
- 	"get eps value"
- 	eps := guess * Epsilon.
- 	eps := eps * eps.
- 	delta := self - (guess * guess) / (guess * 2.0).
- 	[delta * delta > eps]
- 		whileTrue: 
- 			[guess := guess + delta.
- 			delta := self - (guess * guess) / (guess * 2.0)].
- 	^ guess!

Item was changed:
  ----- Method: Float>>tan (in category 'mathematical functions') -----
  tan
  	"Answer the tangent of the receiver taken as an angle in radians."
+ 	<primitive: 'primitiveTan' module: 'FloatMathPlugin'>
+ 	self = self ifFalse:[^self error: 'tan is undefined for NaN'].
- 
  	^ self sin / self cos!

Item was added:
+ ----- Method: Float>>tanH (in category 'mathematical functions') -----
+ tanH
+ 	<primitive: 'primitiveTanH' module: 'FloatMathPlugin'>
+ 	^self primitiveFailed!

Item was changed:
  ----- Method: Float>>timesTwoPower: (in category 'mathematical functions') -----
  timesTwoPower: anInteger 
  	"Primitive. Answer with the receiver multiplied by 2.0 raised
  	to the power of the argument.
  	Optional. See Object documentation whatIsAPrimitive."
+ 	<primitive: 'primitiveTimesTwoPower' module: 'FloatMathPlugin'>
+ 	^self primitiveTimesTwoPower: anInteger!
- 
- 	<primitive: 54>
- 
- 	anInteger < -29 ifTrue: [^ self * (2.0 raisedToInteger: anInteger)].
- 	anInteger < 0 ifTrue: [^ self / (1 bitShift: (0 - anInteger)) asFloat].
- 	anInteger < 30 ifTrue: [^ self * (1 bitShift: anInteger) asFloat].
- 	^ self * (2.0 raisedToInteger: anInteger)!

Item was added:
+ ----- Method: Number>>hypot: (in category 'mathematical functions') -----
+ hypot: arg
+ 	"hypot(x,y) returns sqrt(x^2+y^2) with error less  than 1 ulps"
+ 	^self asFloat hypot: arg asFloat!




More information about the Squeak-dev mailing list