[squeak-dev] DoubleWordArray broken in Pharo

Levente Uzonyi leves at caesar.elte.hu
Sat Mar 28 16:12:43 UTC 2020


Hi Robert

On Sat, 28 Mar 2020, Robert wrote:

>
> On 3/28/20 10:16 AM, Levente Uzonyi wrote:
>> Hi Robert,
>>
>> No, it's not a VM bug. My analysis I sent to you earlier is correct. It's
>> that in Pharo DoubleWordArray is a variableWordSubclass instead of a
>> variableDoubleWordSubclass. The latter is not available in Pharo.
>> Here's the link to the issue they created based on my analysis you sent
>> to them: https://github.com/pharo-project/pharo/issues/5956
>
> Alright, I shared this analysis with Pharo's Discord channel. I must
> have missed the discussion of the #variableDoubleWordSubclass:.
>
>> In theory, yes, it would be possible to rewrite SHA-512 and its related
>> hash functions to avoid using DoubleWordArray, but I see no value in doing
>> that.
>
> The value would be Crypto operational in Pharo. And all that follows

Fixing DoubleWordArray in Pharo alone won't make the packages operational. 
Pharo is a moving target and it keeps breaking stuff all the time.

> from that (ParrotTalk, SSL, SSH, Signal, Raven). Is it possible for you
> to make these changes, please? I see this as more likely than Pharo
> accommodating #variableDoubleWordSubclass:. And other Smalltalks...

I've attached a changeset. If you load it before the Cryptography 
packages, CryptographyHashing will work in Pharo 8 and in the current 
Pharo 9 alpha. Some tests will fail, because random strings are generated 
with the Random class, which is different in Squeak and Pharo but still,
everything will work.


Levente

>
> k, r
>
>> Pharo simply failed to properly integrate DoubleWordArray. It's there but
>> it's disfunctional. Just wait until they fix it.
>>
>>
>> Levente
>>
>> P.S.: This is pretty much off topic on squeak-dev.
>>
>> On Sat, 28 Mar 2020, Robert wrote:
>>
>>> Hey Levente,
>>>
>>> I dug a little deeper into the Pharo issue with Cryptography and it IS a VM issue, I think. Primitive 61 is failing in DoubleWordArray>>#at:put:. Pharo seems totally uninterested in fixing this so I wanted to ask you, is there any way Cryptography can avoid reliance on DoubleWordArray?
>>>
>>> Kindly,
>>> Robert
>>>
>>>
> -- 
> Kindly,
> Robert
>
>
>
-------------- next part --------------
!ByteArray methodsFor: 'accessing' stamp: 'Anonymous 3/28/2020 16:07'!
unsignedLong64At: index put: value bigEndian: bigEndian
	"Store a 64-bit unsigned integer quantity starting from the given byte index"
	
	| i j |
	value isLarge ifTrue: [
		i := value digitLength.
		bigEndian ifFalse: [
			self
				replaceFrom: index
					to: index + i - 1
					with: value 
					startingAt: 1;
				replaceFrom: index + i
					to: index + 7
					with: #[0 0 0 0 0 0 0 0]
					startingAt: 1.
			^value ].
		j := index + 8.
		i <= 7 ifTrue: [
			self
				replaceFrom: index
				to: j - i - 1
				with: #[0 0 0 0 0 0 0 0]
				startingAt: 1 ].
		[ 1 <= i ] whileTrue: [
			self at: j - i put: (value digitAt: i).
			i := i - 1 ].
		^value ].
	bigEndian ifFalse: [
		j := index - 1.
		i := value.
		[ 1 <= i ] whileTrue: [
			self at: (j := j + 1) put: (i bitAnd: 16rFF).
			i := i bitShift: -8 ].
		self replaceFrom: j + 1
			to: index + 7
			with: #[0 0 0 0 0 0 0 0]
			startingAt: 1.
		^value ].
	j := index + 8.
	i := value.
	[ 1 <= i ] whileTrue: [
		self at: (j := j - 1) put: (i bitAnd: 16rFF).
		i := i bitShift: -8 ].
	self replaceFrom: index
		to: j - 1
		with: #[0 0 0 0 0 0 0 0]
		startingAt: 1.
	^value! !

!SmallInteger methodsFor: 'accessing' stamp: 'ul 3/28/2020 16:16'!
digitAt: n 
	"Answer the value of an apparent byte-indexable field in the receiver,
	 analogous. to the large integers, which are organized as bytes."

	n = 1 ifTrue: "Negate carefully in case the receiver is SmallInteger minVal"
		[self < 0 ifTrue:
			[^-256 - self bitAnd: 255].
		 ^self bitAnd: 255].
	self < 0 ifTrue:
		[^(-256 - self bitShift: -8) + 1 digitAt: n - 1].
	^(self bitShift: 8 - (n bitShift: 3)) bitAnd: 255! !

!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ul 3/28/2020 16:01'!
digitLength
	"Answer the number of indexable fields in the receiver. This value is the 
	 same as the largest legal subscript. Included so that a SmallInteger can 
	 behave like a LargePositiveInteger or LargeNegativeInteger."

	| value length |
	length := 1.
	(value := self) < -255
		ifTrue:
			[length := 2.
			value := (-256 - self bitShift: -8) + 1 "carefully negate SmallInteger minVal"].
	[value > 255] whileTrue:
		[value := value bitShift: -8.
		 length := length + 1].
	^length! !

!LargeInteger methodsFor: 'as yet unclassified' stamp: 'ul 3/28/2020 16:01'!
digitLength
	"Primitive. Answer the number of indexable fields in the receiver. This 
	value is the same as the largest legal subscript. Essential. See Object 
	documentation whatIsAPrimitive."

	<primitive: 62>
	self primitiveFailed! !

!LargeInteger methodsFor: 'accessing' stamp: 'ul 3/28/2020 16:17'!
digitAt: index 
	"Primitive. Answer the value of an indexable field in the receiver.   LargePositiveInteger uses bytes of base two number, and each is a 'digit' base 256.  Fail if the argument (the index) is not an Integer or is out of bounds. Essential.  See Object documentation whatIsAPrimitive."

	<primitive: 60>
	self digitLength < index
		ifTrue: [^0]
		ifFalse: [^super at: index]! !

!Class methodsFor: 'subclass creation - variableWord' stamp: 'ul 3/28/2020 15:44'!
variableDoubleWordSubclass: className instanceVariableNames: instVarNameList classVariableNames: classVarNames package: cat

	^ self
		variableDoubleWordSubclass: className
		instanceVariableNames: instVarNameList
		classVariableNames: classVarNames
		poolDictionaries: ''
		package: cat! !

!Class methodsFor: 'subclass creation - variableWord' stamp: 'ul 3/28/2020 15:43'!
variableDoubleWordSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s package: cat

	^ self classInstaller
		make: [ :builder | 
			builder
				superclass: self;
				name: t;
				layoutClass: DoubleWordLayout;
				slots: f asSlotCollection;
				sharedVariablesFromString: d;
				sharedPools: s;
				category: cat;
				environment: self environment ]! !

ArrayedCollection variableDoubleWordSubclass: #DoubleWordArray
	instanceVariableNames: ''
	classVariableNames: ''
	package: 'Collections-Native-Base'!


More information about the Squeak-dev mailing list