Skip to content

Commit c610f3e

Browse files
committed
Adding a trampoline in the middle of the FFI calls so we can handle the code compaction and the movements of machine code methods
1 parent a64d876 commit c610f3e

12 files changed

+285
-16
lines changed

smalltalksrc/VMMaker/CogARMCompiler.class.st

Lines changed: 18 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -539,7 +539,8 @@ CogARMCompiler >> computeMaximumSize [
539539
[Fill32] -> [^4].
540540
[Nop] -> [^4].
541541
"Control"
542-
[Call] -> [^4].
542+
[Call] -> [^4].
543+
[CallR] -> [^4].
543544
[CallFull] -> [^self literalLoadInstructionBytes + 4].
544545
[JumpR] -> [^4].
545546
[Jump] -> [^4].
@@ -890,6 +891,15 @@ CogARMCompiler >> concretizeCallFull [
890891
^machineCodeSize := instrOffset + 4
891892
]
892893

894+
{ #category : 'generate machine code - concretize' }
895+
CogARMCompiler >> concretizeCallR [
896+
897+
<inline: true>
898+
899+
self machineCodeAt: 0 put: (self blx: (operands at: 0)).
900+
^ machineCodeSize := 4
901+
]
902+
893903
{ #category : 'generate machine code - concretize' }
894904
CogARMCompiler >> concretizeCmpRdRd [
895905
"Will get inlined into concretizeAt: switch."
@@ -1935,6 +1945,7 @@ CogARMCompiler >> dispatchConcretize [
19351945
"Control"
19361946
[Call] -> [^self concretizeCall]. "call code within code space"
19371947
[CallFull] -> [^self concretizeCallFull]. "call code anywhere in address space"
1948+
[CallR] -> [^self concretizeCallR].
19381949
[JumpR] -> [^self concretizeJumpR].
19391950
[JumpFull] -> [^self concretizeJumpFull]."jump within address space"
19401951
[JumpLong] -> [^self concretizeConditionalJump: AL]."jumps witihn code space"
@@ -3008,6 +3019,12 @@ CogARMCompiler >> nameForRegister: reg [ "<Integer>"
30083019
[default]
30093020
]
30103021

3022+
{ #category : 'testing' }
3023+
CogARMCompiler >> needsFFIFullCallInRegisterTrampoline [
3024+
3025+
^ true
3026+
]
3027+
30113028
{ #category : 'inline cacheing' }
30123029
CogARMCompiler >> numICacheFlushOpcodes [
30133030
"ARM needs to do icache flushing when code is written"

smalltalksrc/VMMaker/CogARMv8Compiler.class.st

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1028,6 +1028,7 @@ CogARMv8Compiler >> computeMaximumSize [
10281028
"Control"
10291029
[Call] -> [^4].
10301030
[CallFull] -> [^self literalLoadInstructionBytes + 4].
1031+
[CallR] -> [^4].
10311032
[JumpR] -> [^4].
10321033
[Jump] -> [^4].
10331034
[JumpFull] -> [^self literalLoadInstructionBytes + 4].
@@ -1618,6 +1619,15 @@ CogARMv8Compiler >> concretizeCallFull [
16181619
^ machineCodeSize := instrOffset + 4
16191620
]
16201621

1622+
{ #category : 'generate machine code - concretize' }
1623+
CogARMv8Compiler >> concretizeCallR [
1624+
1625+
<inline: true>
1626+
1627+
self machineCodeAt: 0 put: (self blr: (operands at: 0)).
1628+
^ machineCodeSize := 4
1629+
]
1630+
16211631
{ #category : 'generate machine code' }
16221632
CogARMv8Compiler >> concretizeCmpC32R [
16231633

@@ -3442,6 +3452,7 @@ CogARMv8Compiler >> dispatchConcretize [
34423452
"Control"
34433453
[Call] -> [^self concretizeCall]. "call code within code space"
34443454
[CallFull] -> [^self concretizeCallFull]. "call code anywhere in address space"
3455+
[CallR] -> [^self concretizeCallR].
34453456
[JumpR] -> [^self concretizeJumpR].
34463457
[JumpFull] -> [^self concretizeJumpFull]."jump within address space"
34473458
[JumpLong] -> [^self concretizeJumpLong]."jumps witihn code space"
@@ -5369,6 +5380,12 @@ CogARMv8Compiler >> nameForRegister: reg [ "<Integer>"
53695380
[default]
53705381
]
53715382

5383+
{ #category : 'testing' }
5384+
CogARMv8Compiler >> needsFFIFullCallInRegisterTrampoline [
5385+
5386+
^ true
5387+
]
5388+
53725389
{ #category : 'assembler' }
53735390
CogARMv8Compiler >> negateSize: is64Bits sourceRegister: sourceRegister sourceRegisterShiftType: immediate2bitShiftType sourceRegisterShift: immediate6bitsShiftValue destinationRegister: destinationRegister [
53745391

smalltalksrc/VMMaker/CogAbstractInstruction.class.st

Lines changed: 10 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -813,16 +813,18 @@ CogAbstractInstruction >> genFFISameThreadCall: anExternalFunctionAddress [
813813
{ #category : 'sameThread callout - optimizations' }
814814
CogAbstractInstruction >> genFFISameThreadCall: anExternalFunctionAddress handlesExtraDoubleArgument: handlesExtraDoubleArgument [
815815

816-
"Change to C Stack, pushing LinkRegistry if needed"
817-
cogit genSmalltalkToCStackSwitch: true.
818-
819-
self prepareStackForFFICall: handlesExtraDoubleArgument.
816+
"This trampoline is used to have a fixed point where all the calls to FFI methods can return.
817+
This is needed because if we do a FFI call that is reentrant in the interpreter, the machine code method that has perform the call might move or disappear.
818+
Producing a crash when returning from the FFI call.
819+
As the affected return address is in the C stack, it will not be handled by the code compaction code.
820+
So, we need a trampoline, so the return IP is in the top of a Machine Code Pharo Stack, and it is correctly patched."
821+
822+
"Check SimpleStackBasedCogit>>#generateSameThreadCalloutTrampolines"
823+
824+
cogit MoveCw: anExternalFunctionAddress R: Extra0Reg.
825+
cogit CallFullRT: (cogit getFFIFullCallInRegisterTrampoline: handlesExtraDoubleArgument).
820826

821-
cogit CallFullRT: anExternalFunctionAddress.
822827

823-
self genLoadStackPointers.
824-
self hasLinkRegister
825-
ifTrue: [cogit PopR: LinkReg].
826828
]
827829

828830
{ #category : 'abstract instructions' }

smalltalksrc/VMMaker/CogIA32Compiler.class.st

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3804,6 +3804,12 @@ CogIA32Compiler >> mod: mod RM: regMode RO: regOpcode [
38043804
^mod << 6 + (regOpcode << 3) + regMode
38053805
]
38063806

3807+
{ #category : 'testing' }
3808+
CogIA32Compiler >> needsFFIFullCallInRegisterTrampoline [
3809+
3810+
^ false
3811+
]
3812+
38073813
{ #category : 'feature detection' }
38083814
CogIA32Compiler >> numCheckFeaturesOpcodes [
38093815
"Answer the number of opcodes required to compile the CPUID call to extract the extended features information."

smalltalksrc/VMMaker/CogX64Compiler.class.st

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4553,6 +4553,12 @@ CogX64Compiler >> nameForRegister: reg [ "<Integer>"
45534553
ifFalse: [default]
45544554
]
45554555

4556+
{ #category : 'testing' }
4557+
CogX64Compiler >> needsFFIFullCallInRegisterTrampoline [
4558+
4559+
^ true
4560+
]
4561+
45564562
{ #category : 'accessing' }
45574563
CogX64Compiler >> numIntRegArgs [
45584564
^SysV ifTrue: [6] ifFalse: [4]

smalltalksrc/VMMaker/Cogit.class.st

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1236,8 +1236,8 @@ Cogit class >> notesAndQueries [
12361236
12371237
{ #category : 'accessing' }
12381238
Cogit class >> numTrampolines [
1239-
^39 "31 + 4 each for self and super sends"
1240-
1239+
^ 41
1240+
12411241
"self withAllSubclasses collect: [:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"
12421242
]
12431243

smalltalksrc/VMMaker/ManifestVMMaker.class.st

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,13 @@ Class {
66
#tag : 'Manifest'
77
}
88

9+
{ #category : 'code-critics' }
10+
ManifestVMMaker class >> ruleBadMessageRule2V1FalsePositive [
11+
12+
<ignoreForCoverage>
13+
^ #(#(#(#RGClassDefinition #(#CogARMv8Compiler)) #'2025-06-18T18:28:03.188809+02:00') )
14+
]
15+
916
{ #category : 'code-critics' }
1017
ManifestVMMaker class >> ruleCodeCruftLeftInMethodsRuleV1FalsePositive [
1118

@@ -24,7 +31,7 @@ ManifestVMMaker class >> ruleExcessiveArgumentsRuleV1FalsePositive [
2431
ManifestVMMaker class >> ruleLongMethodsRuleV1FalsePositive [
2532

2633
<ignoreForCoverage>
27-
^ #(#(#(#RGClassDefinition #(#DruidJIT)) #'2023-04-26T00:25:44.408297+02:00') #(#(#RGMethodDefinition #(#CogObjectRepresentationForSpur #genGetClassObjectOf:into:scratchReg:instRegIsReceiver: #false)) #'2024-03-20T14:24:36.77799+01:00') )
34+
^ #(#(#(#RGClassDefinition #(#DruidJIT)) #'2023-04-26T00:25:44.408297+02:00') #(#(#RGMethodDefinition #(#CogObjectRepresentationForSpur #genGetClassObjectOf:into:scratchReg:instRegIsReceiver: #false)) #'2024-03-20T14:24:36.77799+01:00') #(#(#RGClassDefinition #(#SimpleStackBasedCogit)) #'2025-06-18T18:28:40.088111+02:00') )
2835
]
2936

3037
{ #category : 'code-critics' }
@@ -38,5 +45,5 @@ ManifestVMMaker class >> ruleTempsReadBeforeWrittenRuleV1FalsePositive [
3845
ManifestVMMaker class >> ruleUncommonMessageSendRuleV1FalsePositive [
3946

4047
<ignoreForCoverage>
41-
^ #(#(#(#RGClassDefinition #(#DruidJIT)) #'2023-04-26T00:25:40.525381+02:00') #(#(#RGClassDefinition #(#Cogit)) #'2023-11-14T14:51:46.485495+01:00') #(#(#RGMethodDefinition #(#CogObjectRepresentationForSpur #genGetClassObjectOfClassIndex:into:scratchReg: #false)) #'2024-03-20T12:06:14.044383+01:00') #(#(#RGMethodDefinition #(#CogObjectRepresentationForSpur #genGetClassObjectOf:into:scratchReg:instRegIsReceiver: #false)) #'2024-03-20T12:09:37.299869+01:00') #(#(#RGMethodDefinition #(#CogObjectRepresentation #genPrimitiveFormat #false)) #'2024-03-21T10:01:25.937395+01:00') #(#(#RGClassDefinition #(#StackToRegisterMappingCogit)) #'2024-08-21T15:58:49.593558+02:00') )
48+
^ #(#(#(#RGClassDefinition #(#DruidJIT)) #'2023-04-26T00:25:40.525381+02:00') #(#(#RGClassDefinition #(#Cogit)) #'2023-11-14T14:51:46.485495+01:00') #(#(#RGMethodDefinition #(#CogObjectRepresentationForSpur #genGetClassObjectOfClassIndex:into:scratchReg: #false)) #'2024-03-20T12:06:14.044383+01:00') #(#(#RGMethodDefinition #(#CogObjectRepresentationForSpur #genGetClassObjectOf:into:scratchReg:instRegIsReceiver: #false)) #'2024-03-20T12:09:37.299869+01:00') #(#(#RGMethodDefinition #(#CogObjectRepresentation #genPrimitiveFormat #false)) #'2024-03-21T10:01:25.937395+01:00') #(#(#RGClassDefinition #(#StackToRegisterMappingCogit)) #'2024-08-21T15:58:49.593558+02:00') #(#(#RGClassDefinition #(#SimpleStackBasedCogit)) #'2025-06-18T18:27:45.211828+02:00') #(#(#RGClassDefinition #(#CogAbstractInstruction)) #'2025-06-18T18:28:20.068642+02:00') )
4249
]

smalltalksrc/VMMaker/SimpleStackBasedCogit.class.st

Lines changed: 92 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,9 @@ Class {
1414
'introspectionDataIndex',
1515
'introspectionData',
1616
'ceSameThreadCalloutTrampoline',
17-
'ceFallbackInvalidFFICallTrampoline'
17+
'ceFallbackInvalidFFICallTrampoline',
18+
'ceFFIFullCallInRegisterTrampoline',
19+
'ceFFIFullCallInRegisterTrampolineWithExtraArgument'
1820
],
1921
#pools : [
2022
'VMClassIndices',
@@ -2848,7 +2850,10 @@ SimpleStackBasedCogit >> generateSameThreadCalloutTrampolines [
28482850
genTrampolineFor:
28492851
#ceFallbackInvalidFFICall
28502852
called:
2851-
'ceFallbackInvalidFFICallTrampoline'
2853+
'ceFallbackInvalidFFICallTrampoline'.
2854+
2855+
ceFFIFullCallInRegisterTrampoline := self maybeGenerateFFIFullCallInRegisterTrampoline: false.
2856+
ceFFIFullCallInRegisterTrampolineWithExtraArgument := self maybeGenerateFFIFullCallInRegisterTrampoline: true.
28522857
]
28532858

28542859
{ #category : 'initialization' }
@@ -2873,6 +2878,14 @@ SimpleStackBasedCogit >> generateTracingTrampolines [
28732878
regsToSave: CallerSavedRegisterMask.
28742879
]
28752880

2881+
{ #category : 'accessing' }
2882+
SimpleStackBasedCogit >> getFFIFullCallInRegisterTrampoline: handlesExtraDoubleArgument [
2883+
2884+
^ handlesExtraDoubleArgument
2885+
ifTrue: [ ceFFIFullCallInRegisterTrampolineWithExtraArgument ]
2886+
ifFalse: [ ceFFIFullCallInRegisterTrampoline ]
2887+
]
2888+
28762889
{ #category : 'accessing' }
28772890
SimpleStackBasedCogit >> getFallbackInvalidFFICallTrampoline [
28782891

@@ -2957,6 +2970,83 @@ SimpleStackBasedCogit >> maybeCompileAllocFillerCheck [
29572970
jmpOk jmpTarget: self Label]
29582971
]
29592972

2973+
{ #category : 'initialization' }
2974+
SimpleStackBasedCogit >> maybeGenerateFFIFullCallInRegisterTrampoline: handlesExtraDoubleArgument [
2975+
2976+
"This trampoline is used to have a fixed point where all the calls to FFI methods can return.
2977+
This is needed because if we do a FFI call that is reentrant in the interpreter, the machine code method that has perform the call might move or disappear.
2978+
Producing a crash when returning from the FFI call.
2979+
As the affected return address is in the C stack, it will not be handled by the code compaction code.
2980+
So, we need a trampoline, so the return IP is in the top of a Machine Code Pharo Stack, and it is correctly patched.
2981+
We need two flavors of this trampoline, as Win64 requires to handle the an extra double argument in the stack"
2982+
2983+
| startAddress |
2984+
2985+
<inline: true>
2986+
2987+
backEnd needsFFIFullCallInRegisterTrampoline
2988+
ifFalse: [ ^ 0 ].
2989+
2990+
self allocateOpcodes: 15 bytecodes: 0.
2991+
2992+
"We need to ensure that the Extra0Reg is not in conflict with the registers used for the calling convention"
2993+
backEnd cArg0Register = Extra0Reg ifTrue: [ self error: 'Cannot generate ceFFIFullCallInRegisterTrampoline. Extra0Reg collides with cArg0Register' ].
2994+
backEnd cArg1Register = Extra0Reg ifTrue: [ self error: 'Cannot generate ceFFIFullCallInRegisterTrampoline. Extra0Reg collides with cArg1Register' ].
2995+
backEnd cArg2Register = Extra0Reg ifTrue: [ self error: 'Cannot generate ceFFIFullCallInRegisterTrampoline. Extra0Reg collides with cArg2Register' ].
2996+
backEnd cArg3Register = Extra0Reg ifTrue: [ self error: 'Cannot generate ceFFIFullCallInRegisterTrampoline. Extra0Reg collides with cArg3Register' ].
2997+
2998+
"If we don't have LinkRegister, we need an extra register, that should not conflict with the calling convetion"
2999+
(backEnd hasLinkRegister) ifFalse: [
3000+
backEnd cArg0Register = Extra2Reg ifTrue: [ self error: 'Cannot generate ceFFIFullCallInRegisterTrampoline. Extra2Reg collides with cArg0Register' ].
3001+
backEnd cArg1Register = Extra2Reg ifTrue: [ self error: 'Cannot generate ceFFIFullCallInRegisterTrampoline. Extra2Reg collides with cArg1Register' ].
3002+
backEnd cArg2Register = Extra2Reg ifTrue: [ self error: 'Cannot generate ceFFIFullCallInRegisterTrampoline. Extra2Reg collides with cArg2Register' ].
3003+
backEnd cArg3Register = Extra2Reg ifTrue: [ self error: 'Cannot generate ceFFIFullCallInRegisterTrampoline. Extra2Reg collides with cArg3Register' ]
3004+
].
3005+
3006+
startAddress := methodZoneBase.
3007+
3008+
"We are not pushing the return IP to the stack.
3009+
We need to store it in the instructionPointer variable. If we are coming back into the interpreter in a callback, the ptEnterInterpreterFromCallback
3010+
assumes that the return IP is in the variable, and will put it in the stack so it can be remapped.
3011+
3012+
We need to use an extra register if we don't have LinkReg or PC register"
3013+
3014+
backEnd hasLinkRegister
3015+
ifTrue:
3016+
[self MoveR: LinkReg Aw: coInterpreter instructionPointerAddress]
3017+
ifFalse:
3018+
[self PopR: Extra2Reg. "instruction pointer"
3019+
self MoveR: Extra2Reg Aw: coInterpreter instructionPointerAddress].
3020+
3021+
self genSmalltalkToCStackSwitch: false.
3022+
3023+
backEnd prepareStackForFFICall: handlesExtraDoubleArgument.
3024+
3025+
self CallR: Extra0Reg.
3026+
3027+
backEnd genLoadStackPointers.
3028+
3029+
(backEnd hasLinkRegister)
3030+
ifTrue:
3031+
[backEnd hasPCRegister
3032+
ifTrue: [self MoveAw: coInterpreter instructionPointerAddress R: PCReg]
3033+
ifFalse: [
3034+
self MoveAw: coInterpreter instructionPointerAddress R: LinkReg.
3035+
self RetN: 0]]
3036+
ifFalse: [
3037+
self MoveAw: coInterpreter instructionPointerAddress R: Extra2Reg.
3038+
self PushR: Extra2Reg.
3039+
self RetN: 0].
3040+
3041+
self outputInstructionsForGeneratedRuntimeAt: startAddress.
3042+
3043+
self recordGeneratedRunTime: (handlesExtraDoubleArgument
3044+
ifTrue: [ 'ceFFIFullCallInRegisterTrampolineWithExtraArgument' ]
3045+
ifFalse: [ 'ceFFIFullCallInRegisterTrampoline' ]) address: startAddress.
3046+
3047+
^ startAddress.
3048+
]
3049+
29603050
{ #category : 'trampolines' }
29613051
SimpleStackBasedCogit >> methodAbortTrampolineFor: numArgs [
29623052
^ceMethodAbortTrampoline

smalltalksrc/VMMakerTests/UnicornARMv8Simulator.class.st

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -502,6 +502,12 @@ UnicornARMv8Simulator >> x20 [
502502
^ self readRegister: UcARM64Registers x20
503503
]
504504

505+
{ #category : 'accessing' }
506+
UnicornARMv8Simulator >> x21: anInteger [
507+
508+
^ self writeRegister: UcARM64Registers x21 value: anInteger
509+
]
510+
505511
{ #category : 'accessing-registers-physical' }
506512
UnicornARMv8Simulator >> x22 [
507513

smalltalksrc/VMMakerTests/UnicornProcessor.class.st

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -198,6 +198,12 @@ UnicornProcessor >> r11: anInteger [
198198
machineSimulator r11: anInteger
199199
]
200200

201+
{ #category : 'registers' }
202+
UnicornProcessor >> r12: anInteger [
203+
204+
machineSimulator r12: anInteger
205+
]
206+
201207
{ #category : 'registers' }
202208
UnicornProcessor >> r1: anInteger [
203209

@@ -453,6 +459,12 @@ UnicornProcessor >> x1: anInteger [
453459
machineSimulator x1: anInteger
454460
]
455461

462+
{ #category : 'accessing' }
463+
UnicornProcessor >> x21: anInteger [
464+
465+
machineSimulator x21: anInteger
466+
]
467+
456468
{ #category : 'as yet unclassified' }
457469
UnicornProcessor >> x22: anInteger [
458470

0 commit comments

Comments
 (0)