[Pkg] The Trunk: Kernel-nice.635.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Oct 14 19:49:05 UTC 2011


Nicolas Cellier uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-nice.635.mcz

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

Name: Kernel-nice.635
Author: nice
Time: 14 October 2011, 9:48:14.9 pm
UUID: b27ad01f-a82e-460f-8cc5-578ea8a77972
Ancestors: Kernel-nice.634

Integrate great changes Juan made in Cuis:
- make #sqrt exact when possible.
- compute #nthRoot:

=============== Diff against Kernel-nice.634 ===============

Item was added:
+ ----- Method: Float class>>maxExactInteger (in category 'constants') -----
+ maxExactInteger
+ 	"Answer the biggest integer such that it is exactly represented in a float, and all smaller integers also are"
+ 	^1 bitShift: self precision!

Item was added:
+ ----- Method: Float>>nthRoot: (in category 'mathematical functions') -----
+ nthRoot: aPositiveInteger
+ 	"Answer the nth root of the receiver."
+ 	aPositiveInteger = 2 ifTrue: [
+ 		^self sqrt ].
+ 
+ 	(aPositiveInteger isInteger not or: [ aPositiveInteger negative ])
+ 		ifTrue: [^ ArithmeticError signal: 'nth root only defined for positive Integer n.'].
+ 	
+ 	^self negative
+ 		ifTrue: [
+ 			aPositiveInteger odd
+ 				ifTrue: [ (self negated raisedTo: 1.0 / aPositiveInteger) negated ]
+ 				ifFalse: [ ArithmeticError signal: 'Negative numbers don''t have even roots.' ]]
+ 		ifFalse: [ self raisedTo: 1.0 / aPositiveInteger ]!

Item was added:
+ ----- Method: Fraction>>nthRoot: (in category 'mathematical functions') -----
+ nthRoot: aPositiveInteger
+ 	"Answer the nth root of the receiver."
+ 
+ 	| d n |
+ 	n := numerator nthRoot: aPositiveInteger.
+ 	d := denominator nthRoot: aPositiveInteger.
+ 	"The #sqrt method in integer will only answer a Float if there's no exact square root.
+ 	So, we need a float anyway."
+ 	(n isInfinite or: [ d isInfinite ]) ifTrue: [
+ 		^self asFloat nthRoot: aPositiveInteger ].
+ 	^n / d!

Item was added:
+ ----- Method: Fraction>>sqrt (in category 'mathematical functions') -----
+ sqrt
+ 	| d n |
+ 	n := numerator sqrt.
+ 	d := denominator sqrt.
+ 	"The #sqrt method in integer will only answer a Float if there's no exact square root.
+ 	So, we need a float anyway."
+ 	(n isInfinite or: [ d isInfinite ]) ifTrue: [
+ 		^self asFloat sqrt ].
+ 	^n / d!

Item was added:
+ ----- Method: Integer>>nthRoot: (in category 'mathematical functions') -----
+ nthRoot: aPositiveInteger
+ 	"Answer the nth root of the receiver."
+ 
+ 	| selfAsFloat floatResult guess raised higher lower delta |
+ 	selfAsFloat := self asFloat.
+ 	floatResult := selfAsFloat nthRoot: aPositiveInteger.
+ 
+ 	"If we can't do Float arithmetic, currently we can't look for an exact answer"
+ 	floatResult isInfinite ifTrue: [
+ 		^floatResult ].
+ 
+ 	guess := floatResult rounded.
+ 
+ 	"If got an exact answer, answer it."
+ 	raised := guess raisedToInteger: aPositiveInteger.
+ 	raised = self
+ 		ifTrue: [ ^ guess ].
+ 
+ 	"In this case, maybe it failed because we are such a big integer that the Float
+ 	method gets inexact, even if we are a whole square number.
+ 	Note (jmv): The algorithms I found for computing the nthRoot would havily use
+ 	very large fractions. I wrote this one, that doesn't create fractions."
+ 	selfAsFloat abs >= (Float maxExactInteger asFloat raisedToInteger: aPositiveInteger)
+ 		ifTrue: [
+ 			raised > self
+ 				ifTrue: [
+ 					higher := guess.
+ 					delta :=  floatResult predecessor - floatResult.
+ 					[
+ 						floatResult := floatResult + delta.
+ 						lower := floatResult rounded.
+ 						(lower raisedToInteger: aPositiveInteger) > self ] whileTrue: [
+ 							delta := delta * 2.
+ 							higher := lower ] ]
+ 				ifFalse: [
+ 					lower := guess.
+ 					delta :=  floatResult successor - floatResult.
+ 					[
+ 						floatResult := floatResult + delta.
+ 						higher := floatResult rounded.
+ 						(higher raisedToInteger: aPositiveInteger) < self ] whileTrue: [
+ 							delta := delta * 2.
+ 							lower := higher ]].
+ 			[ higher - lower > 1 ] whileTrue: [
+ 				guess := lower + higher // 2.
+ 				raised := guess raisedToInteger: aPositiveInteger.
+ 				raised = self
+ 					ifTrue: [
+ 						^ guess ].
+ 				raised > self
+ 					ifTrue: [ higher := guess ]
+ 					ifFalse: [ lower := guess ]]].
+ 
+ 	"We need an approximate result"
+ 	^floatResult!

Item was added:
+ ----- Method: Integer>>sqrt (in category 'mathematical functions') -----
+ sqrt
+ 	"Answer the square root of the receiver."
+ 
+ 	| selfAsFloat floatResult guess |
+ 	selfAsFloat := self asFloat.
+ 	floatResult := selfAsFloat sqrt.
+ 
+ 	floatResult isInfinite ifFalse: [
+ 		guess := floatResult truncated.
+ 
+ 		"If got an exact answer, answer it. Otherwise answer float approximate answer."
+ 		guess squared = self
+ 			ifTrue: [ ^ guess ]].
+ 
+ 	"In this case, maybe it failed because we are such a big integer that the Float method becomes
+ 	inexact, even if we are a whole square number. So, try the slower but more general method"
+ 	selfAsFloat >= Float maxExactInteger asFloat squared
+ 		ifTrue: [
+ 			guess := self sqrtFloor.
+ 			guess * guess = self ifTrue: [
+ 				^guess ]].
+ 
+ 	"We need an approximate result"
+ 	^floatResult!

Item was added:
+ ----- Method: LargeNegativeInteger>>sqrt (in category 'mathematical functions') -----
+ sqrt
+ 	"Answer the square root of the receiver."
+ 	^ DomainError signal: 'sqrt undefined for number less than zero.'!

Item was added:
+ ----- Method: LargePositiveInteger>>mightBeASquare (in category 'mathematical functions') -----
+ mightBeASquare
+ 	"In base 16, a square number can end only with 0,1,4 or 9 and
+ 	- in case 0, only 0,1,4,9 can precede it,
+ 	- in case 4, only even numbers can precede it.
+ 	See http://en.wikipedia.org/wiki/Square_number
+ 	So, in hex, the last byte must be one of:
+ 		00
+ 		10
+ 		40
+ 		90
+ 		x1
+ 		e4
+ 		x9
+ 	where x is any hex digit and e is any even digit
+ 	"
+     | lsb |
+     lsb := self digitAt: 1.
+     ^((lsb bitAnd: 7) = 1					"any|1 or any|9"
+         or: [(lsb bitAnd: 31) = 4			"even|4"
+         or: [(lsb bitAnd: 127) = 16			"10 or 90"
+         or: [(lsb bitAnd: 191) = 0]]])		"00 or 40"!

Item was added:
+ ----- Method: LargePositiveInteger>>sqrt (in category 'mathematical functions') -----
+ sqrt
+ 	"If we know for sure no exact solution exists, then just answer the cheap float approximation without wasting time."
+ 	self mightBeASquare ifFalse: [
+ 		^self asFloat sqrt ].
+ 
+ 	"If some exact solution might exist,  call potentially expensive super"
+ 	^super sqrt!

Item was added:
+ ----- Method: Number>>nthRoot: (in category 'mathematical functions') -----
+ nthRoot: aPositiveInteger
+ 	"Answer the nth root of the receiver."
+ 
+ 	self subclassResponsibility!

Item was changed:
  ----- Method: Number>>raisedTo: (in category 'mathematical functions') -----
  raisedTo: aNumber 
  	"Answer the receiver raised to aNumber."
  
+ 	aNumber isInteger ifTrue: [
+ 		"Do the special case of integer power"
- 	aNumber isInteger ifTrue:
- 		["Do the special case of integer power"
  		^ self raisedToInteger: aNumber].
+ 	aNumber isFraction ifTrue: [
+ 		"Special case for fraction power"
+ 		^ (self nthRoot: aNumber denominator) raisedToInteger: aNumber numerator ].
+ 	self < 0 ifTrue: [
+ 		^ ArithmeticError signal: 'Negative numbers can''t be raised to float powers.' ].
- 	self < 0 ifTrue:
- 		[ self error: self printString, ' raised to a non-integer power' ].
  	0 = aNumber ifTrue: [^ self class one].	"Special case of exponent=0"
  	1 = aNumber ifTrue: [^ self].	"Special case of exponent=1"
  	0 = self ifTrue: [				"Special case of self = 0"
  		aNumber < 0
  			ifTrue: [^ (ZeroDivide dividend: self) signal]
  			ifFalse: [^ self]].
  	^ (aNumber * self ln) exp		"Otherwise use logarithms"!

Item was changed:
  ----- Method: Number>>sqrt (in category 'mathematical functions') -----
  sqrt
  	"Answer the square root of the receiver."
  
+ 	self subclassResponsibility!
- 	^self asFloat sqrt!

Item was added:
+ ----- Method: SmallInteger>>sqrt (in category 'mathematical functions') -----
+ sqrt
+ 	self negative ifTrue: [
+ 		^ DomainError signal: 'sqrt undefined for number less than zero.' ].
+ 	^super sqrt!



More information about the Packages mailing list