[squeak-dev] The Trunk: Kernel-nice.652.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Apr 26 17:02:32 UTC 2012


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

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

Name: Kernel-nice.652
Author: nice
Time: 5 November 2011, 12:54:57.688 am
UUID: 6588c880-ca5d-4c3d-a39b-b75588ce0263
Ancestors: Kernel-laza.649

PURPOSE:

Any Float now prints with the minimal number of digits that describes it unambiguously.
This way, every two different Float will have a different printed representation.
More over, every Float can be reconstructed from its printed representation with #readFrom:.

	self assert: ([:f | f isNaN or: [(Float readFrom: f printString) = f]] value: Float someInstance).

Note that Float nan, Float infinity and Float infinity negated still print as 'NaN' 'Infinity' and '-Infinity' which are compatible with #readFrom:.

RATIONALE:

the old behaviour was obscuring our data like for example:
       0.1 successor printString = 0.1 printString.
       1.0e-100 printString = '9.99999999999999e-101'.

The old behaviour was returning many digits without any guaranty of exactness which is useless.

The old behaviour was faster (x4) but this is less relevant than exactness.
Similar or better speed should be obtained by controlling number of printed digits if we can afford inexactness.

IMPLEMENTATION:

The essential change was to use #absPrintExactlyOn:base: in #printOn:base:
Side note: this is really a bad name, because it prints the shortest base-representation, not the exact one.
Anyway, we can only print the exact one in even bases.
For example, the exact representation of 0.1 in base 10 is:
	0.1 asFraction asScaledDecimal = 0.1000000000000000055511151231257827021181583404541015625s55.

The second change was to marginally fast-up #absPrintExactlyOn:base: main loop by avoiding a #not send and piping decimal point test.
Avoiding the #not makes the intention a tiny bit clearer.
Also of few formatting has been performed in the last lines.

REJECTED CHANGES:

It is possible to move self > 0.0 before self isNaN to statistically reduce the number of tests performed.
This works because Float nan > 0.0 = false.
But this speed-up is quite marginal.

Similarly (self = Infinity) could replace (self isInfinite) and save another send and also another test (because NegativeInfinity can't happen at this stage).
This would be at the price of a class var reference leak.

It could be more interesting to move this #isInfinite test in #printOn:base: in order to gather print rules for exceptional values.
I didn't to avoid duplicating the test in the two branches > 0.0 and < 0.0.

A far more efficient speed-up would be to optimize LargeInteger arithmetic.
I think there is room, the VM is still using byte operations (thus at most 16 bits).

=============== Diff against Kernel-laza.649 ===============

Item was changed:
  ----- Method: Float>>absPrintExactlyOn:base: (in category 'printing') -----
  absPrintExactlyOn: aStream base: base
  	"Print my value on a stream in the given base.  Assumes that my value is strictly
  	positive; negative numbers, zero, and NaNs have already been handled elsewhere.
  	Based upon the algorithm outlined in:
  	Robert G. Burger and R. Kent Dybvig
  	Printing Floating Point Numbers Quickly and Accurately
  	ACM SIGPLAN 1996 Conference on Programming Language Design and Implementation
  	June 1996.
  	This version guarantees that the printed representation exactly represents my value
  	by using exact integer arithmetic."
  
  	| significand exp baseExpEstimate r s mPlus mMinus scale roundingIncludesLimits d tc1 tc2 fixedFormat decPointCount slowbit shead |
  	self isInfinite ifTrue: [aStream nextPutAll: 'Infinity'. ^ self].
  	significand := self significandAsInteger.
  	roundingIncludesLimits := significand even.
  	exp := (self exponent - 52) max: MinValLogBase2.
  	baseExpEstimate := (self exponent * base asFloat reciprocalLogBase2 - 1.0e-10) ceiling.
  	exp >= 0
  		ifTrue:
  			[significand ~= 16r10000000000000
  				ifTrue:
  					[r := significand bitShift: 1 + exp.
  					s := 2.
  					mPlus := mMinus := 1 bitShift: exp]
  				ifFalse:
  					[r := significand bitShift: 2 + exp.
  					s := 4.
  					mPlus := 2 * (mMinus := 1 bitShift: exp)]]
  		ifFalse:
  			[(exp = MinValLogBase2 or: [significand ~= 16r10000000000000])
  				ifTrue:
  					[r := significand bitShift: 1.
  					s := 1 bitShift: 1 - exp.
  					mPlus := mMinus := 1]
  				ifFalse:
  					[r := significand bitShift: 2.
  					s := 1 bitShift: 2 - exp.
  					mPlus := 2.
  					mMinus := 1]].
  	baseExpEstimate >= 0
  		ifTrue: [s := s * (base raisedToInteger: baseExpEstimate)]
  		ifFalse:
  			[scale := base raisedToInteger: baseExpEstimate negated.
  			r := r * scale.
  			mPlus := mPlus * scale.
  			mMinus := mMinus * scale].
+ 	((r + mPlus >= s) and: [roundingIncludesLimits or: [r + mPlus > s]])
- 	((r + mPlus < s) not and: [roundingIncludesLimits or: [r + mPlus > s]])
  		ifTrue: [baseExpEstimate := baseExpEstimate + 1]
  		ifFalse:
  			[r := r * base.
  			mPlus := mPlus * base.
  			mMinus := mMinus * base].
  	(fixedFormat := baseExpEstimate between: -3 and: 6)
  		ifTrue:
  			[decPointCount := baseExpEstimate.
  			baseExpEstimate <= 0
  				ifTrue: [aStream nextPutAll: ('0.000000' truncateTo: 2 - baseExpEstimate)]]
  		ifFalse:
  			[decPointCount := 1].
  	slowbit := 1 - s lowBit .
  	shead := s bitShift: slowbit.
  	[d := (r bitShift: slowbit) // shead.
  	r := r - (d * s).
+ 	(tc1 := (r <= mMinus) and: [roundingIncludesLimits or: [r < mMinus]]) |
+ 	(tc2 := (r + mPlus >= s) and: [roundingIncludesLimits or: [r + mPlus > s]])] whileFalse:
- 	(tc1 := (r > mMinus) not and: [roundingIncludesLimits or: [r < mMinus]]) |
- 	(tc2 := (r + mPlus < s) not and: [roundingIncludesLimits or: [r + mPlus > s]])] whileFalse:
  		[aStream nextPut: (Character digitValue: d).
  		r := r * base.
  		mPlus := mPlus * base.
  		mMinus := mMinus * base.
+ 		(decPointCount := decPointCount - 1) = 0 ifTrue: [aStream nextPut: $.]].
- 		decPointCount := decPointCount - 1.
- 		decPointCount = 0 ifTrue: [aStream nextPut: $.]].
  	tc2 ifTrue:
  		[(tc1 not or: [r * 2 >= s]) ifTrue: [d := d + 1]].
  	aStream nextPut: (Character digitValue: d).
  	decPointCount > 0
  		ifTrue:
+ 			[decPointCount - 1 to: 1 by: -1 do: [:i | aStream nextPut: $0].
+ 			aStream nextPutAll: '.0'].
+ 	fixedFormat
+ 		ifFalse:
+ 			[aStream nextPut: $e.
+ 			aStream nextPutAll: (baseExpEstimate - 1) printString]!
- 		[decPointCount - 1 to: 1 by: -1 do: [:i | aStream nextPut: $0].
- 		aStream nextPutAll: '.0'].
- 	fixedFormat ifFalse:
- 		[aStream nextPut: $e.
- 		aStream nextPutAll: (baseExpEstimate - 1) printString]!

Item was changed:
  ----- Method: Float>>printOn:base: (in category 'printing') -----
  printOn: aStream base: base
+ 	"Print the receiver with the minimal number of digits that describes it unambiguously.
+ 	This way, every two different Float will have a different printed representation.
+ 	More over, every Float can be reconstructed from its printed representation with #readFrom:." 
- 	"Handle sign, zero, and NaNs; all other values passed to absPrintOn:base:" 
  
  	self isNaN ifTrue: [aStream nextPutAll: 'NaN'. ^ self]. "check for NaN before sign"
  	self > 0.0
+ 		ifTrue: [self absPrintExactlyOn: aStream base: base]
- 		ifTrue: [self absPrintOn: aStream base: base]
  		ifFalse:
  			[self sign = -1
  				ifTrue: [aStream nextPutAll: '-'].
  			self = 0.0
+ 				ifTrue: [aStream nextPutAll: '0.0']
+ 				ifFalse: [self negated absPrintExactlyOn: aStream base: base]]!
- 				ifTrue: [aStream nextPutAll: '0.0'. ^ self]
- 				ifFalse: [self negated absPrintOn: aStream base: base]]!



More information about the Squeak-dev mailing list