bit shifting

Hans-Martin Mosner hm.mosner at cww.de
Thu Apr 16 19:15:57 UTC 1998


Slowly I'm getting accustomed to correct myself over and over...

Hans-Martin Mosner wrote:
> 
> Let me correct myself:
> (-1 bitShift: 1) = -2   is perfectly right.
> And it's what Squeak 1.31 computes.

.... after I added the bitShift: hack which damages LargeInteger
division...
So Squeak 1.31 out of the box does not do it right.
But do not despair... Here are some fixes for the most pressing
problems:
1. SmallInteger>>bitShift: works as expected, even for negative numbers.
2. Integer>>digitDiv:neg: is correct (and faster)
3. SmallInteger>>highBit is a little faster
4. SmallInteger>>bitAnd: works for negative numbers, too
   (using the notion that the sign bit extends to infinity)

However, there are a lot of other methods which need work. bitOr: and
bitXor: are among them, as well as LargeNegativeInteger bit
manipulation. I don't have the time now to do them all, maybe someone
else can do it?

And maybe someone should write a test suite which tests all combinations
of large & small integers for the various operations.

Hans-Martin

Content-Type: text/plain; charset=us-ascii; x-mac-type="54455854"; x-mac-creator="522A6368"; name="IntegerFix.16Apr857pm.cs"
Content-Transfer-Encoding: 7bit
Content-Description: BBEdit Lite 4.0 Document
Content-Disposition: inline; filename="IntegerFix.16Apr857pm.cs"

'From Squeak 1.31 of Feb 4, 1998 on 16 April 1998 at 8:57:42 pm'!

!Integer methodsFor: 'private' stamp: 'hmm 4/16/98 20:57'!
digitDiv: arg neg: ng 
	"Answer with an array of (quotient, remainder)."
	| quo rem ql d div dh dnh dl q j l hi lo r3 a t r1 r2 |
	l _ self digitLength - arg digitLength + 1.
	l <= 0 ifTrue: [^Array with: 0 with: self].
	d _ 8 - arg lastDigit highBit.
	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 | 
		"quo * arg + rem = self ifFalse: [self halt]."
		"maintain quo*arg+rem=self"
		"Estimate rem/div by dividing the leading to bytes of rem by dh."
		j _ rem digitLength + 1 - k.
		r1 _ rem digitAt: j.
		r1 = dh
			ifTrue: [q _ 255]
			ifFalse: 
				["Compute q = (r1,r2)//dh, t = (r1,r2)\\dh."
				r2 _ (rem digitAt: j - 1).
				t _ (r1 bitShift: 8) + r2.
				q _ t // dh.
				t _ t \\ dh.
				"Next compute (hi,lo) _ q*dnh"
				hi _ q * dnh bitShift: -8.
				lo _ q * dnh 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)"
						q _ q - 1.
						lo _ lo - dnh.
						lo < 0
							ifTrue: 
								[hi _ hi - 1.
								lo _ lo + 256].
						hi >= dh]]
					whileTrue: [hi _ hi - dh]].
		"Subtract q*div from rem"
		l _ j - dl.
		a _ 0.
		1 to: div digitLength do: 
			[:i | 
			t _ a + (rem digitAt: l) - ((div digitAt: i) * q).
			rem digitAt: l put: (t bitAnd: 255).
			a _ t bitShift: -8.
			l _ l + 1].
		a < 0
			ifTrue: 
				["Add div back into rem, decrease q by 1"
				q _ q - 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: q].
	rem _ rem digitRshift: d bytes: 0 lookfirst: dl.
	^Array with: quo with: rem! !


!SmallInteger methodsFor: 'bit manipulation' stamp: 'hmm 4/16/98 20:52'!
bitAnd: arg 
	"Primitive. Answer an Integer whose bits are the logical AND of the
	receiver's bits and those of the argument, arg.
	Negative numbers are interpreted as a 32-bit 2's-complement.
	For operations on negative numbers, an offset is added
	and subtracted where necessary to make the arguments positive.
	Essential.  See Object documentation whatIsAPrimitive."

	| offset |
	<primitive: 14>
	self < 0 ifTrue: [
		^arg < 0
			ifTrue: [
				offset _ 1 bitShift: ((1-self) highBit max: (1-arg) highBit).
				(self + offset bitAnd: arg + offset) - offset]
			ifFalse: [
				offset _ 1 bitShift: (1-self) highBit.
				self + offset bitAnd: arg]].
	^arg bitAnd: self! !

!SmallInteger methodsFor: 'bit manipulation' stamp: 'hmm 3/12/98 19:28'!
bitShift: arg 
	"Primitive. Answer an Integer whose value is the receiver's value shifted
	left by the number of bits indicated by the argument. Negative arguments
	shift right.
	Essential.  See Object documentation whatIsAPrimitive."

	<primitive: 17>
	self < 0 ifTrue: [^ 0 - (0-self bitShift: arg)].
	^ super bitShift: arg! !

!SmallInteger methodsFor: 'bit manipulation' stamp: 'hmm 4/16/98 20:36'!
highBit   "10 highBit 4"
	"Returns the number of the highest 1-bit.  Note that they
	are numbered with 1248 being 1234 -- NOT zero-based.
	Also note that 0 highBit returns 0"
	| shifted bitNo |
	self < 0 ifTrue: [^ (0 - self) highBit].
	shifted _ self.
	bitNo _ 0.
	[shifted < 16] whileFalse:
		[shifted _ shifted bitShift: -4.
		bitNo _ bitNo + 4].
	[shifted = 0] whileFalse:
		[shifted _ shifted bitShift: -1.
		bitNo _ bitNo + 1].
	^ bitNo
! !





More information about the Squeak-dev mailing list