Skip to content

Commit

Permalink
Merge pull request #304 from tesonep/fix-asFloat-when-no-more-memory
Browse files Browse the repository at this point in the history
Primitive asFloat should fail and callback to the C function.
  • Loading branch information
guillep authored Jul 6, 2021
2 parents 7de247b + 097af98 commit ea8a3bf
Show file tree
Hide file tree
Showing 5 changed files with 64 additions and 14 deletions.
6 changes: 6 additions & 0 deletions smalltalksrc/VMMaker-Tools/Integer.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,12 @@ Integer >> aarch64Disassembled [
^ self disassembleWith: LLVMARMDisassembler aarch64
]

{ #category : #'*VMMaker-Tools' }
Integer >> armv7Disassembled [

^ self disassembleWith: LLVMARMDisassembler armv7
]

{ #category : #'*VMMaker-Tools' }
Integer >> disassembleWith: aLLVMDisassembler [

Expand Down
13 changes: 0 additions & 13 deletions smalltalksrc/VMMaker/CogARMv8Compiler.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -3705,19 +3705,6 @@ VCVTW. regB, regA - ARM_ARM v7 DDI10406.pdf pp. A8-576-8"
^(2r11101110101110000000101111000000 bitOr: srcReg ) bitOr: regB<<12
]

{ #category : #'ARM convenience instructions' }
CogARMv8Compiler >> fstd: fpReg rn: addrReg plus: u imm: immediate8bitValue [
"FSTD or VSTR instruction to move a value to address in an ARM addrReg +/- offset<<2 from an fpu double fpReg
FSTD fpReg, addrReg, #offset - ARM_ARM v5 DDI 01001.pdf pp. C4-101
VSTR.64 fpReg, addrReg, #offset - ARM_ARM v7 DDI10406 pp. A8-780-1"
<inline: true>
"Note that
offset is <<2 to make byte address
u =1 -> addrReg + offset<<2
u=0 -> addrReg - offset<<2"
^(((2r11101101000000000000101100000000 bitOr:(addrReg <<16)) bitOr: fpReg<<12) bitOr: u<<23) bitOr: immediate8bitValue
]

{ #category : #'ARM convenience instructions' }
CogARMv8Compiler >> fsubd: destReg with: srcReg [
"FSUBD or VSUB instruction to subtract double srcReg from double destREg and stick result in double destReg
Expand Down
6 changes: 5 additions & 1 deletion smalltalksrc/VMMaker/CogObjectRepresentation.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -516,7 +516,11 @@ CogObjectRepresentation >> genPrimitiveAsFloat [
cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
cogit genPrimReturn.
jumpFailAlloc jmpTarget: cogit Label.
^ CompletePrimitive

"This primitive is not complete. If the eden is full, it will fail.
We need to handle that in the C primitive or in the image.
We decided to handle it in the C primitive. "
^ 0
]

{ #category : #'primitive generators' }
Expand Down
40 changes: 40 additions & 0 deletions smalltalksrc/VMMakerTests/VMJittedBoxFloatPrimitivesTest.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,40 @@
Class {
#name : #VMJittedBoxFloatPrimitivesTest,
#superclass : #VMJittedPrimitivesTest,
#pools : [
'CogRTLOpcodes'
],
#category : #'VMMakerTests-JitTests'
}

{ #category : #tests }
VMJittedBoxFloatPrimitivesTest >> testAsFloat [

cogit receiverTags: memory smallIntegerTag.

self compile: [ cogit objectRepresentation genPrimitiveAsFloat ].

self executePrimitiveWithReceiver: (self memory integerObjectOf: 27).

self
assert: (memory floatValueOf: machineSimulator receiverRegisterValue)
equals: 27.0
]

{ #category : #tests }
VMJittedBoxFloatPrimitivesTest >> testAsFloatWhenThereIsNotSpaceFailsPrimitive [

| stop |
cogit receiverTags: memory smallIntegerTag.

memory freeStart: memory scavengeThreshold.

self compile: [
cogit objectRepresentation genPrimitiveAsFloat.
stop := cogit Stop ].

self prepareStackForSendReceiver: (self memory integerObjectOf: 27) arguments: #().
self runFrom: initialAddress until: stop address.
self assert: machineSimulator instructionPointerValue equals: stop address

]
13 changes: 13 additions & 0 deletions smalltalksrc/VMMakerTests/VMJittedPrimitivesTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,19 @@ VMJittedPrimitivesTest class >> isAbstract [
^ self == VMJittedPrimitivesTest
]

{ #category : #helpers }
VMJittedPrimitivesTest >> executePrimitiveWithReceiver: receiverOop [

"Simulate a primitive execution having an object as receiver and a single argument
- the receiver goes to the receiver register
- the argument should be pushed to the stack
If we are in a system without a link register, we need to push the caller IP to the stack to simulate a call"

self prepareStackForSendReceiver: receiverOop arguments: #().
self runUntilReturn.

]

{ #category : #helpers }
VMJittedPrimitivesTest >> executePrimitiveWithReceiver: receiverOop withArgument: argumentOop [

Expand Down

0 comments on commit ea8a3bf

Please sign in to comment.