Skip to content

Commit

Permalink
Merge pull request #772 from guillep/fix/comparing-different-formats
Browse files Browse the repository at this point in the history
Do not allow comparing objects of different types
  • Loading branch information
guillep committed Apr 29, 2024
2 parents a526528 + fa7a529 commit 17ff0a5
Show file tree
Hide file tree
Showing 3 changed files with 61 additions and 11 deletions.
16 changes: 10 additions & 6 deletions smalltalksrc/VMMaker/StackInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -10889,7 +10889,6 @@ StackInterpreter >> primitiveCompareBytes [

<export: true>
| arg1 arg2 len1 len2 result boolean |

argumentCount < 1 ifTrue: [ ^ self primitiveFail ].

arg1 := self stackValue: 1.
Expand All @@ -10898,13 +10897,18 @@ StackInterpreter >> primitiveCompareBytes [
"Quick identity test to avoid checking object contents when they are the same one\"
arg1 = arg2 ifTrue: [
^ self pop: 2 thenPush: objectMemory trueObject ].


"This primitive only works for objects of the same type e.g., both byte indexable.
This prevents comparison of byte arrays with word arrays"
(objectMemory instSpecOfClass: (objectMemory fetchClassOf: arg1)) ~= (objectMemory instSpecOfClass: (objectMemory fetchClassOf: arg2))
ifTrue: [
self primitiveFail.
^ self ].

"This primitive only works for bytes and words objects.
The check below does not even let pass forwarders.
Below, we assume that the two compared objects are indexable and can be compared."
((objectMemory isWordsOrBytes: arg1) and: [
objectMemory isWordsOrBytes: arg2 ]) ifFalse: [
^ self primitiveFail ].
Since we know by the check before that both arguments are of the same type, we only need to check one of them here"
(objectMemory isWordsOrBytes: arg1) ifFalse: [ ^ self primitiveFail ].

"Two arrays of different lenght can never be equal"
len1 := objectMemory byteSizeOf: arg1.
Expand Down
49 changes: 46 additions & 3 deletions smalltalksrc/VMMakerTests/VMPrimitiveTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1388,9 +1388,11 @@ VMPrimitiveTest >> testPrimitiveCompareBytesWithLastDifferentValue [
{ #category : #'tests - primitiveCompareBytes' }
VMPrimitiveTest >> testPrimitiveCompareBytesWithNonByteArgument [

| array1 size |
| array1 size nilClass |
size := 2.
array1 := self new8BitIndexableOfSize: size.
nilClass := self newClassInOldSpaceWithSlots: 0 instSpec: memory zeroSlotsNonIndexablePointerFormat.
memory setClassIndexOf: memory nilObject to: (memory ensureBehaviorHash: nilClass).

1 to: size do: [ :i |
memory storeByte: i - 1 ofObject: array1 withValue: 0 ].
Expand All @@ -1407,9 +1409,12 @@ VMPrimitiveTest >> testPrimitiveCompareBytesWithNonByteArgument [
{ #category : #'tests - primitiveCompareBytes' }
VMPrimitiveTest >> testPrimitiveCompareBytesWithNonByteReceiver [

| array1 size |
| array1 size nilClass |
size := 2.
array1 := self new8BitIndexableOfSize: size.
nilClass := self newClassInOldSpaceWithSlots: 0 instSpec: memory zeroSlotsNonIndexablePointerFormat.
memory setClassIndexOf: memory nilObject to: (memory ensureBehaviorHash: nilClass).


1 to: size do: [ :i |
memory storeByte: i - 1 ofObject: array1 withValue: 0 ].
Expand All @@ -1426,9 +1431,12 @@ VMPrimitiveTest >> testPrimitiveCompareBytesWithNonByteReceiver [
{ #category : #'tests - primitiveCompareBytes' }
VMPrimitiveTest >> testPrimitiveCompareBytesWithNonByteReceiverShouldLeaveTheSameStack [

| array1 size |
| array1 size nilClass |
size := 2.
array1 := self new8BitIndexableOfSize: size.
nilClass := self newClassInOldSpaceWithSlots: 0 instSpec: memory zeroSlotsNonIndexablePointerFormat.
memory setClassIndexOf: memory nilObject to: (memory ensureBehaviorHash: nilClass).


1 to: size do: [ :i |
memory storeByte: i - 1 ofObject: array1 withValue: 0 ].
Expand Down Expand Up @@ -1464,6 +1472,41 @@ VMPrimitiveTest >> testPrimitiveCompareBytesWithSize [
self assert: interpreter stackTop equals: memory trueObject
]

{ #category : #'tests - primitiveCompareBytes' }
VMPrimitiveTest >> testPrimitiveCompareBytesWithWordArgument [

| array1 array2 size |
size := 1.
"Both will be 8 bytes long"
array1 := self new8BitIndexableOfSize: size * 8.
array2 := self new64BitIndexableOfSize: size.

interpreter push: array1.
interpreter push: array2.

interpreter argumentCount: 1.
interpreter primitiveCompareBytes.

"Should fail because they don't have the same type"
self assert: interpreter failed
]

{ #category : #'tests - primitiveCompareBytes' }
VMPrimitiveTest >> testPrimitiveCompareWordsEmpty [

| array1 array2 |
array1 := self new64BitIndexableOfSize: 0.
array2 := self new64BitIndexableOfSize: 0.

interpreter push: array1.
interpreter push: array2.

interpreter argumentCount: 1.
interpreter primitiveCompareBytes.

self assert: interpreter stackTop equals: memory trueObject
]

{ #category : #'tests - primitiveDiv' }
VMPrimitiveTest >> testPrimitiveDiv [

Expand Down
7 changes: 5 additions & 2 deletions smalltalksrc/VMMakerTests/VMSpurMemoryManagerTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -424,14 +424,17 @@ VMSpurMemoryManagerTest >> newArrayWithSlots: slots classIndex: anIndex [
{ #category : #helpers }
VMSpurMemoryManagerTest >> newBitIndexableOfSize: aSize bytesPerSlot: bytesPerSlot format: format [

| padding numberOfWordSizeSlots desiredByteSize |
| padding numberOfWordSizeSlots desiredByteSize theClass classIndex |
theClass := self newClassInOldSpaceWithSlots: 0 instSpec: format.
classIndex := memory ensureBehaviorHash: theClass.

desiredByteSize := aSize * bytesPerSlot roundUpTo: self wordSize.
numberOfWordSizeSlots := desiredByteSize / self wordSize.
padding := desiredByteSize / bytesPerSlot - aSize.
^ memory
allocateNewSpaceSlots: numberOfWordSizeSlots
format: format + padding
classIndex: self nextOrdinaryClassIndex
classIndex: classIndex
]

{ #category : #asd }
Expand Down

0 comments on commit 17ff0a5

Please sign in to comment.