Skip to content

Commit

Permalink
Refactorings
Browse files Browse the repository at this point in the history
  • Loading branch information
Hernán Morales Durand committed Sep 21, 2023
1 parent 0d089c0 commit a092823
Show file tree
Hide file tree
Showing 2 changed files with 23 additions and 49 deletions.
57 changes: 12 additions & 45 deletions smalltalksrc/VMMaker/StackInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -5410,50 +5410,24 @@ StackInterpreter >> executePrimitiveFromInterpreter: inInterpreter ifFail: aBloc
the machine code primitive, just evaluate primitiveFunctionPointer directly."

primitiveFunctionPointer ~= 0 ifTrue: [
| succeeded |
"slowPrimitiveResponse may of course context-switch.
If so we must reenter the new process appropriately, returning only if we've found an interpreter frame.
The instructionPointer tells us from whence we came."
succeeded := self slowPrimitiveResponse.
succeeded ifTrue: [
self returnToExecutive: inInterpreter.
^ nil ] ].
self slowPrimitiveResponse
ifTrue: [ ^ self returnToExecutive: inInterpreter ] ].

^ aBlock value
]

{ #category : #'primitive support' }
StackInterpreter >> executeQuickPrimitive [

"Invoke a quick primitive.
Called under the assumption that primFunctionPtr has been preloaded"
{ #category : #'message sending' }
StackInterpreter >> executeQuick [

| localPrimIndex |
self assert: self isPrimitiveFunctionPointerAnIndex.
localPrimIndex := self
cCoerceSimple: primitiveFunctionPointer
to: #sqInt.
self assert: (localPrimIndex > 255 and: [ localPrimIndex < 520 ]).
"Quick return inst vars"
localPrimIndex >= 264 ifTrue: [
self stackTopPut: (objectMemory
fetchPointer: localPrimIndex - 264
ofObject: self stackTop).
^ true ].
"Quick return constants"
localPrimIndex = 256 ifTrue: [ ^ true "return self" ].
localPrimIndex = 257 ifTrue: [
self stackTopPut: objectMemory trueObject.
^ true ].
localPrimIndex = 258 ifTrue: [
self stackTopPut: objectMemory falseObject.
^ true ].
localPrimIndex = 259 ifTrue: [
self stackTopPut: objectMemory nilObject.
^ true ].
self stackTopPut:
(objectMemory integerObjectOf: localPrimIndex - 261).
^ true
"primFailCode := 0."
self isPrimitiveFunctionPointerAQuickPrimitive
ifTrue: [ self dispatchFunctionPointer: primitiveFunctionPointer. ^ true ]
ifFalse: [ self isPrimitiveFunctionPointerAnIndex
ifTrue: [ self executeQuickReturn. ^ true ] ].
^ false
]

{ #category : #'primitive support' }
Expand Down Expand Up @@ -14291,15 +14265,8 @@ StackInterpreter >> slowPrimitiveResponse [
<var: #savedStackPointer type: #'char *'>
"self assert: (objectMemory isOopForwarded: (self stackValue: argumentCount)) not."

self isPrimitiveFunctionPointerAQuickPrimitive
ifTrue: [
self dispatchFunctionPointer: primitiveFunctionPointer.
^ true ]
ifFalse: [
self isPrimitiveFunctionPointerAnIndex
ifTrue: [
self executeQuickPrimitive.
^ true ] ].
self executeQuick
ifTrue: [ ^ true ].

self assert: objectMemory remapBufferCount = 0.
FailImbalancedPrimitives ifTrue:
Expand Down
15 changes: 11 additions & 4 deletions smalltalksrc/VMMaker/StackInterpreterPrimitives.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1137,10 +1137,17 @@ StackInterpreterPrimitives >> primitiveDoPrimitiveWithArgs [
[self push: (objectMemory fetchPointer: index - 1 ofObject: argumentArray).
index := index + 1].

self isPrimitiveFunctionPointerAnIndex ifTrue:
[self executeQuickPrimitive.
tempOop2 := 0.
^nil].
"Handle quick executions"
self isPrimitiveFunctionPointerAQuickPrimitive
ifTrue: [
self dispatchFunctionPointer: primitiveFunctionPointer.
tempOop2 := 0.
^ nil ]
ifFalse: [ self isPrimitiveFunctionPointerAnIndex
ifTrue: [ self executeQuickReturn.
tempOop2 := 0.
^ nil ] ].

"We use tempOop instead of pushRemappableOop:/popRemappableOop here because in
the Cogit primitiveEnterCriticalSection, primitiveSignal, primitiveResume et al longjmp back
to either the interpreter or machine code, depending on the process activated. So if we're
Expand Down

0 comments on commit a092823

Please sign in to comment.