[BUG] DSA failure in LargePositiveInteger in #new: <primitive: 71>

Stephan Rudlof sr at evolgo.de
Tue May 30 17:48:22 UTC 2000


Jerry,

I think I have found a possible location of the problem. There is a
subtle difference in the semantics with or without the LargeIntegers
module.

In
Integer>>
bitShift: shiftCount 
	"Answer an Integer whose value (in twos-complement representation) is  
	the receiver's value (in twos-complement representation) shifted left
by 
	 the number of bits indicated by the argument. Negative arguments  
	shift right. Zeros are shifted in from the right in left shifts."
	| rShift |
	<primitive: 'primDigitBitShift' module:'LargeIntegers'>
	shiftCount >= 0 ifTrue: [^ self digitLshift: shiftCount].
	rShift _ 0 - shiftCount.
	^ (self
		digitRshift: (rShift bitAnd: 7)
		bytes: (rShift bitShift: -3)
		lookfirst: self digitLength) normalize

there is no >>normalize after calling >>digitLshift:, because in
Integer>>digitLshift: the result will be created by
	result _ Integer new: len neg: self negative.
; and Integer>>new: chooses the correct representation (LargeInteger or
SmallInteger) automatically.

If the LargeIntegers module is present, a left shift converts the
receiver to a LargeInteger (if necessary) and performs the left shift
*without* a normalization of the result.

I think this should be possible, because if there is a call of

SmallInteger
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. The receiver is interpreted as having 2's-complement
representation.
	Essential.  See Object documentation whatIsAPrimitive."

	<primitive: 17>
	self >= 0 ifTrue: [^ super bitShift: arg].
	^ arg >= 0
		ifTrue: [(self negated bitShift: arg) negated]
		ifFalse: [(self bitInvert bitShift: arg) bitInvert]

Integer>>bitShift: will be called after failing of <primitive: 17> with
a LargePositiveInteger result and if there is a call of

LargePositiveInteger>>
>>bitShift: anInteger 
	"Primitive. Answer an Integer whose value (in twos-complement 
	representation) is the receiver's value (in twos-complement
	representation) shifted left by the number of bits indicated by the
	argument. Negative arguments shift right. Zeros are shifted in from the
	right in left shifts. The sign bit is extended in right shifts.
	Fail if the receiver or result is greater than 32 bits.
	See Object documentation whatIsAPrimitive."
	<primitive: 17>
	^super bitShift: anInteger
the same <primitive: 17> has been called.

Now to <primitive: 17>; it is

Interpreter>>
primitiveBitShift 
	| integerReceiver integerArgument shifted |
	integerArgument _ self popInteger.
	integerReceiver _ self popPos32BitInteger.
	successFlag ifTrue: [
		integerArgument >= 0 ifTrue: [
			"Left shift -- must fail if we lose bits beyond 32"
			self success: integerArgument <= 31.
			shifted _ integerReceiver << integerArgument.
			self success: (shifted >> integerArgument) = integerReceiver.
		] ifFalse: [
			"Right shift -- OK to lose bits"
			self success: integerArgument >= -31.
			shifted _ integerReceiver bitShift: integerArgument.
		].
	].
	successFlag
		ifTrue: [self push: (self positive32BitIntegerFor: shifted)]
		ifFalse: [self unPop: 2]

which for a left shift only should fail (not in all cases though), if
there is a result not fitting in a positive SmallInteger (Note: receiver
is interpreted as positive integer).

So my conclusion is, that the assumption, that Integer>>bitShift: only
will be called if there is a LargeInteger result for left shifts, should
hold.

But I think this isn't true, if there is a violation of the 'normalize'
constraint for all Integers, taken from the class comment of
LargePositiveInteger:
"Care must be taken, when new values are computed, that any result that
COULD BE a SmallInteger IS a SmallInteger (see normalize)."

So I would dig deeper first into
DigitalSignatureAlgorithm>>remainder:mod: to find the error.


Hope this helps,

Stephan

P.S.: I don't have the DSA module ready to run here, but I'm very
interested in every possible bug of the LargeIntegersPlugin: So I've
taken a look into it and explained my assumptions (which could be
wrong...).

JArchibald at aol.com wrote:
> 
> All--
> 
> In attempting to further pursue the strange behavior of primitive plug-ins
> (the possible failure to properly link to a plug-in module when morphic has
> never been used), I decided to run some tests with DSA. This facility uses a
> plug-in module and also does not require the use of morphic facilities, so it
> seemed to be a natural for such tests.
> 
> The simplest test of DSA behavior is just to attempt to generate the keys.
> Among other things, this routine will nicely display its progress on the
> Transcript. When evaluating an expression which does a send to
> DigitalSignatureAlgorithm>>generateKeySet, I was confronted with errors in
> Behavior>>new: which was accompanied by the following back-chain:
> 
> ----------------------------------------------------------------
>     Error: a primitive has failed
> 
> LargePositiveInteger class(Object)>>error:
> LargePositiveInteger class(Object)>>primitiveFailed
> LargePositiveInteger class(Behavior)>>new:
> DigitalSignatureAlgorithm>>remainder:mod:
> DigitalSignatureAlgorithm>>isProbablyPrime:
> DigitalSignatureAlgorithm>>generateSandQ
> DigitalSignatureAlgorithm>>generateQandP
> DigitalSignatureAlgorithm>>generateKeySet
> DigitalSignatureAlgorithm class>>generateKeySet
> UndefinedObject>>DoIt
> ----------------------------------------------------------------
> 
> This test failed every time, although the algorithm clearly pursued different
> twists in the logic (resulting from the use of a random seed). As a result,
> the back-chain is sometimes different, i.e., longer. I got the same results
> in both MVC as well as Morphic projects. An identical error occurs on both
> Mac and Windows platforms. This was run on Squeak2.7 at cs#2210.
> 
> I did have a copy of Squeak2.7 at cs#2005 (i.e., prior to cs#2163) sitting
> around, so I ran the same test there. It _did_ complete successfully.
> 
> Is there a possibility that this has resulted from the new implementation of
> LargeIntegers? If not that, can anyone figure out what it is?
> 
> Cheers,
> Jerry.
> ____________________________
> 
> Jerry L. Archibald
> systemObjectivesIncorporated
> ____________________________
> 
> "Sometimes you feel like a nut,
>  sometimes you are." :-o (this is one of the most remarkable, the famous
> self-palindromic smiley.  :-o is of course OIC)

-- 
Stephan Rudlof (sr at evolgo.de)
   "Genius doesn't work on an assembly line basis.
    You can't simply say, 'Today I will be brilliant.'"
    -- Kirk, "The Ultimate Computer", stardate 4731.3





More information about the Squeak-dev mailing list