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

commits at source.squeak.org commits at source.squeak.org
Mon Sep 26 19:27:19 UTC 2011


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

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

Name: Kernel-nice.629
Author: nice
Time: 26 September 2011, 9:26:30.229 pm
UUID: efcd1a80-4b32-4ccf-bdb7-8548ec1f040b
Ancestors: Kernel-nice.628

Define and use #highBitOfByte when we know we operate on byte boundary.
And, oups, remove ===> which crept in trunk (was solely for testing speed).

=============== Diff against Kernel-nice.628 ===============

Item was removed:
- ----- Method: Boolean>>===> (in category 'logical operations') -----
- ===> aBlock
- 	"this is material implication, a ==> b, also known as:
- 			b if a 
- 			a implies b
- 			if a then b
- 			b is a consequence of a
- 			a therefore b (but note: 'it is raining therefore it is cloudy' is implication; 'it is autumn therefore the leaves are falling' is equivalence).
- 		
- 	Here is the truth table for material implication (view in a monospaced font):
- 	
- 	   p   |   q   |   p ==> q
- 	-------|-------|-------------
- 	   T   |   T   |      T
- 	   T   |   F   |      F
- 	   F   |   T   |      T
- 	   F   |   F   |      T
- 	"
- 
- 	^self not or: [aBlock value]!

Item was changed:
  ----- Method: Integer>>digitDiv:neg: (in category 'private') -----
  digitDiv: arg neg: ng 
  	"Answer with an array of (quotient, remainder)."
  	| quo rem ql d div dh dnh dl qhi qlo j l hi lo r3 a t |
  	<primitive: 'primDigitDivNegative' module:'LargeIntegers'>
  	arg = 0 ifTrue: [^ (ZeroDivide dividend: self) signal].
  	"TFEI added this line"
  	l := self digitLength - arg digitLength + 1.
  	l <= 0 ifTrue: [^ Array with: 0 with: self].
  	"shortcut against #highBit"
+ 	d := 8 - arg lastDigit highBitOfByte.
- 	d := 8 - arg lastDigit highBitOfPositiveReceiver.
  	div := arg digitLshift: d.
  	div := div growto: div digitLength + 1.
  	"shifts so high order word is >=128"
  	rem := self digitLshift: d.
  	rem digitLength = self digitLength ifTrue: [rem := rem growto: self digitLength + 1].
  	"makes a copy and shifts"
  	quo := Integer new: l neg: ng.
  	dl := div digitLength - 1.
  	"Last actual byte of data"
  	ql := l.
  	dh := div digitAt: dl.
  	dnh := dl = 1
  				ifTrue: [0]
  				ifFalse: [div digitAt: dl - 1].
  	1 to: ql do: 
  		[:k | 
  		"maintain quo*arg+rem=self"
  		"Estimate rem/div by dividing the leading to bytes of rem by dh."
  		"The estimate is q = qhi*16+qlo, where qhi and qlo are nibbles."
  		j := rem digitLength + 1 - k.
  		"r1 := rem digitAt: j."
  		(rem digitAt: j)
  			= dh
  			ifTrue: [qhi := qlo := 15
  				"i.e. q=255"]
  			ifFalse: 
  				["Compute q = (r1,r2)//dh, t = (r1,r2)\\dh.  
  				Note that r1,r2 are bytes, not nibbles.  
  				Be careful not to generate intermediate results exceeding 13  
  				bits."
  				"r2 := (rem digitAt: j - 1)."
  				t := ((rem digitAt: j)
  							bitShift: 4)
  							+ ((rem digitAt: j - 1)
  									bitShift: -4).
  				qhi := t // dh.
  				t := (t \\ dh bitShift: 4)
  							+ ((rem digitAt: j - 1)
  									bitAnd: 15).
  				qlo := t // dh.
  				t := t \\ dh.
  				"Next compute (hi,lo) := q*dnh"
  				hi := qhi * dnh.
  				lo := qlo * dnh + ((hi bitAnd: 15)
  								bitShift: 4).
  				hi := (hi bitShift: -4)
  							+ (lo bitShift: -8).
  				lo := lo bitAnd: 255.
  				"Correct overestimate of q.  
  				Max of 2 iterations through loop -- see Knuth vol. 2"
  				r3 := j < 3
  							ifTrue: [0]
  							ifFalse: [rem digitAt: j - 2].
  				[(t < hi
  					or: [t = hi and: [r3 < lo]])
  					and: 
  						["i.e. (t,r3) < (hi,lo)"
  						qlo := qlo - 1.
  						lo := lo - dnh.
  						lo < 0
  							ifTrue: 
  								[hi := hi - 1.
  								lo := lo + 256].
  						hi >= dh]]
  					whileTrue: [hi := hi - dh].
  				qlo < 0
  					ifTrue: 
  						[qhi := qhi - 1.
  						qlo := qlo + 16]].
  		"Subtract q*div from rem"
  		l := j - dl.
  		a := 0.
  		1 to: div digitLength do: 
  			[:i | 
  			hi := (div digitAt: i)
  						* qhi.
  			lo := a + (rem digitAt: l) - ((hi bitAnd: 15)
  							bitShift: 4) - ((div digitAt: i)
  							* qlo).
  			rem digitAt: l put: lo - (lo // 256 * 256).
  			"sign-tolerant form of (lo bitAnd: 255)"
  			a := lo // 256 - (hi bitShift: -4).
  			l := l + 1].
  		a < 0
  			ifTrue: 
  				["Add div back into rem, decrease q by 1"
  				qlo := qlo - 1.
  				l := j - dl.
  				a := 0.
  				1 to: div digitLength do: 
  					[:i | 
  					a := (a bitShift: -8)
  								+ (rem digitAt: l) + (div digitAt: i).
  					rem digitAt: l put: (a bitAnd: 255).
  					l := l + 1]].
  		quo digitAt: quo digitLength + 1 - k put: (qhi bitShift: 4)
  				+ qlo].
  	rem := rem
  				digitRshift: d
  				bytes: 0
  				lookfirst: dl.
  	^ Array with: quo with: rem!

Item was changed:
  ----- Method: LargePositiveInteger>>highBitOfMagnitude (in category 'bit manipulation') -----
  highBitOfMagnitude
  	"Answer the index of the high order bit of the magnitude of the  
  	receiver, or zero if the receiver is zero.  
  	This method is used for LargeNegativeIntegers as well,  
  	since Squeak's LargeIntegers are sign/magnitude."
  	| realLength lastDigit |
  	realLength := self digitLength.
  	[(lastDigit := self digitAt: realLength) = 0]
  		whileTrue: [(realLength := realLength - 1) = 0 ifTrue: [^ 0]].
+ 	^ lastDigit highBitOfByte + (8 * (realLength - 1))!
- 	^ lastDigit highBitOfPositiveReceiver + (8 * (realLength - 1))!

Item was added:
+ ----- Method: SmallInteger>>highBitOfByte (in category 'private') -----
+ highBitOfByte
+ 	"The high bits table can be obtained with:
+ 	(1 to: 8) inject: #[0] into: [:highBits :rank | highBits , (highBits collect: [:e | rank])]."
+ 	^ #[0 1 2 2 3 3 3 3 4 4 4 4 4 4 4 4 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8] at: self + 1!

Item was changed:
  ----- Method: SmallInteger>>highBitOfPositiveReceiver (in category 'private') -----
  highBitOfPositiveReceiver
  	| shifted bitNo |
  	"Answer the index of the high order bit of the receiver, or zero if the 
  	receiver is zero. Receiver has to be positive!!"
  	shifted := self.
  	bitNo := 0.
  	[shifted < 65536]
  		whileFalse: 
  			[shifted := shifted bitShift: -16.
  			bitNo := bitNo + 16].
  	shifted < 256
  		ifFalse: 
  			[shifted := shifted bitShift: -8.
  			bitNo := bitNo + 8].
+ 	^bitNo + shifted highBitOfByte!
- 		
- 	"The high bits table can be obtained with:
- 	(1 to: 8) inject: #[0] into: [:highBits :rank | highBits , (highBits collect: [:e | rank])]."
- 	^bitNo + ( #[0 1 2 2 3 3 3 3 4 4 4 4 4 4 4 4 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8] at: shifted + 1)!




More information about the Squeak-dev mailing list