Skip to content

Commit

Permalink
Merge pull request #425 from pharo-project/backport-367
Browse files Browse the repository at this point in the history
The store error code bytecode is skipped in both interpreted and compiled execution
  • Loading branch information
tesonep committed May 30, 2022
2 parents eda1de4 + d626262 commit faea2cb
Show file tree
Hide file tree
Showing 6 changed files with 1,053 additions and 851 deletions.
34 changes: 14 additions & 20 deletions smalltalksrc/VMMaker/CoInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -533,7 +533,7 @@ CoInterpreter >> activateCoggedNewMethod: inInterpreter [

((self methodHeaderHasPrimitive: methodHeader)
and: [primFailCode ~= 0]) ifTrue:
[self reapAndResetErrorCodeTo: stackPointer header: methodHeader].
[self reapAndResetErrorCodeTo: framePointer header: methodHeader].

"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
stackPointer >= stackLimit ifTrue:
Expand Down Expand Up @@ -769,8 +769,10 @@ CoInterpreter >> activateNewMethod [
["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
with a long store temp. Strictly no need to skip the store because it's effectively a noop."
instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader).
primFailCode ~= 0 ifTrue:
[self reapAndResetErrorCodeTo: stackPointer header: methodHeader]].
primFailCode ~= 0 ifTrue: [ | shouldSkipStoreBytecode |
shouldSkipStoreBytecode := self reapAndResetErrorCodeTo: framePointer header: methodHeader.
shouldSkipStoreBytecode ifTrue: [
instructionPointer := instructionPointer + (self sizeOfLongStoreTempBytecode: methodHeader) ] ] ].

"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
switched := true.
Expand Down Expand Up @@ -1775,7 +1777,7 @@ CoInterpreter >> ceReapAndResetErrorCodeFor: cogMethod [
<var: #cogMethod type: #'CogMethod *'>
self assert: primFailCode ~= 0.
newMethod := cogMethod methodObject.
self reapAndResetErrorCodeTo: stackPointer + objectMemory wordSize
self reapAndResetErrorCodeTo: framePointer
header: cogMethod methodHeader
]

Expand Down Expand Up @@ -4115,8 +4117,10 @@ CoInterpreter >> internalActivateNewMethod [
["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
with a long store temp. Strictly no need to skip the store because it's effectively a noop."
localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
primFailCode ~= 0 ifTrue:
[self reapAndResetErrorCodeTo: localSP header: methodHeader]].
primFailCode ~= 0 ifTrue: [ | shouldSkipStoreBytecode |
shouldSkipStoreBytecode := self reapAndResetErrorCodeTo: localFP header: methodHeader.
shouldSkipStoreBytecode ifTrue: [
localIP := localIP + (self sizeOfLongStoreTempBytecode: methodHeader) ] ] ].

self assert: (self frameNumArgs: localFP) = argumentCount.
self assert: (self frameIsBlockActivation: localFP) not.
Expand Down Expand Up @@ -4405,8 +4409,10 @@ CoInterpreter >> justActivateNewMethod: mustBeInterpreterFrame [
with a long store temp. Strictly no need to skip the store because it's effectively a noop."
cogMethod ifNil:
[instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader)].
primFailCode ~= 0 ifTrue:
[self reapAndResetErrorCodeTo: stackPointer header: methodHeader]].
primFailCode ~= 0 ifTrue: [ | shouldSkipStoreBytecode |
shouldSkipStoreBytecode := self reapAndResetErrorCodeTo: framePointer header: methodHeader.
(cogMethod isNil and: [shouldSkipStoreBytecode]) ifTrue: [
instructionPointer := instructionPointer + (self sizeOfLongStoreTempBytecode: methodHeader) ] ] ]..

^methodHeader
]
Expand Down Expand Up @@ -5624,18 +5630,6 @@ CoInterpreter >> primErrTable [
^objectMemory splObj: PrimErrTableIndex
]

{ #category : #'cog jit support' }
CoInterpreter >> primFailCode [
<doNotGenerate>
^primFailCode
]

{ #category : #'cog jit support' }
CoInterpreter >> primFailCode: anInteger [
<doNotGenerate>
primFailCode := anInteger
]

{ #category : #'trampoline support' }
CoInterpreter >> primFailCodeAddress [
<api>
Expand Down
43 changes: 32 additions & 11 deletions smalltalksrc/VMMaker/StackInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -8513,8 +8513,10 @@ StackInterpreter >> internalActivateNewMethod [
["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
with a long store temp. Strictly no need to skip the store because it's effectively a noop."
localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
primFailCode ~= 0 ifTrue:
[self reapAndResetErrorCodeTo: localSP header: methodHeader]].
primFailCode ~= 0 ifTrue: [ | shouldSkipStoreBytecode |
shouldSkipStoreBytecode := self reapAndResetErrorCodeTo: localFP header: methodHeader.
shouldSkipStoreBytecode ifTrue: [
localIP := localIP + (self sizeOfLongStoreTempBytecode: methodHeader) ] ] ].

self assert: (self frameNumArgs: localFP) = argumentCount.
self assert: (self frameIsBlockActivation: localFP) not.
Expand Down Expand Up @@ -9356,8 +9358,10 @@ StackInterpreter >> justActivateNewMethod: mustBeInterpreterFrame [
["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
with a long store temp. Strictly no need to skip the store because it's effectively a noop."
instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader).
primFailCode ~= 0 ifTrue:
[self reapAndResetErrorCodeTo: stackPointer header: methodHeader]].
primFailCode ~= 0 ifTrue: [ | shouldSkipStoreBytecode |
shouldSkipStoreBytecode := self reapAndResetErrorCodeTo: framePointer header: methodHeader.
shouldSkipStoreBytecode ifTrue: [
instructionPointer := instructionPointer + (self sizeOfLongStoreTempBytecode: methodHeader) ] ] ].

^methodHeader
]
Expand Down Expand Up @@ -11574,6 +11578,12 @@ StackInterpreter >> primFailCode [
^ primFailCode
]

{ #category : #'cog jit support' }
StackInterpreter >> primFailCode: anInteger [
<doNotGenerate>
primFailCode := anInteger
]

{ #category : #'primitive support' }
StackInterpreter >> primitiveAccessorDepthForExternalPrimitiveMethod: methodObj [
^objectMemory integerValueOf:
Expand Down Expand Up @@ -13669,18 +13679,29 @@ StackInterpreter >> readableFormat: imageVersion [
]

{ #category : #'primitive support' }
StackInterpreter >> reapAndResetErrorCodeTo: theSP header: methodHeader [
StackInterpreter >> reapAndResetErrorCodeTo: theFP header: methodHeader [

"Assuming the primFailCode is non-zero, check if the method consumes the error code
and if so, assign it through theSP. Then zero the primFailCode. This is infrequent code,
so keep it out of the common path."
and if so, assign it through theFP into the correct temporary variable.
Then zero the primFailCode. This is infrequent code, so keep it out of the common path."

<var: 'theSP' type: #'char *'>
<inline: #never>
| initialPC |
self assert: primFailCode ~= 0.
initialPC := (self initialIPForHeader: methodHeader method: newMethod) + (self sizeOfCallPrimitiveBytecode: methodHeader).
(objectMemory byteAt: initialPC) = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
[stackPages longAtPointer: theSP put: self getErrorObjectFromPrimFailCode].
primFailCode := 0
initialPC := (self initialIPForHeader: methodHeader method: newMethod)
+ (self sizeOfCallPrimitiveBytecode: methodHeader).
(objectMemory byteAt: initialPC)
= (self longStoreBytecodeForHeader: methodHeader) ifTrue: [
| temporaryIndex |
temporaryIndex := objectMemory byteAt: initialPC + 1.
self
temporary: temporaryIndex
in: theFP
put: self getErrorObjectFromPrimFailCode.
^ true].
primFailCode := 0.
^ false
]

{ #category : #'internal interpreter access' }
Expand Down
6 changes: 6 additions & 0 deletions smalltalksrc/VMMaker/StackInterpreterSimulator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1284,6 +1284,12 @@ StackInterpreterSimulator >> localFP [
^localFP
]

{ #category : #'spur bootstrap' }
StackInterpreterSimulator >> localFP: anFP [

^ localFP := anFP
]

{ #category : #'spur bootstrap' }
StackInterpreterSimulator >> localIP [
^localIP
Expand Down

0 comments on commit faea2cb

Please sign in to comment.