Skip to content

Commit 3907dc4

Browse files
committed
Make suspension primitives suspend themselves on the stack to allow for normal return condition when returning to a machine code caller
1 parent ea04ea8 commit 3907dc4

File tree

4 files changed

+35
-191
lines changed

4 files changed

+35
-191
lines changed

smalltalksrc/VMMaker/CoInterpreter.class.st

Lines changed: 29 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -4584,44 +4584,42 @@ CoInterpreter >> returnToExecutive: inInterpreter postContextSwitch: switchedCon
45844584
machine code. The instructionPointer tells us where from. If it is above startOfMemory we're
45854585
in the interpreter. If it is below, then we are in machine-code unless it is ceReturnToInterpreterPC,
45864586
in which case we're in a machine-code primitive called from the interpreter."
4587-
<inline: false>
4588-
| cogMethod retValue fullyInInterpreter |
4589-
<var: #cogMethod type: #'CogMethod *'>
45904587

4588+
<inline: false>
4589+
| retValue fullyInInterpreter |
45914590
cogit assertCStackWellAligned.
4592-
(self isMachineCodeFrame: framePointer) ifTrue:
4593-
[self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
4594-
"If returning after a context switch then a result may have to be popped from the stack.
4591+
(self isMachineCodeFrame: framePointer) ifTrue: [
4592+
self
4593+
assertValidExecutionPointe: instructionPointer
4594+
r: framePointer
4595+
s: stackPointer
4596+
imbar: false
4597+
line: #__LINE__.
4598+
"If returning after a context switch then a result may have to be popped from the stack.
45954599
If the process is suspended at a send then the result of the primitive in which the
45964600
process was suspended is still on the stack and must be popped into ReceiverResultReg.
45974601
If not, nothing should be popped and ReceiverResultReg gets the receiver."
4598-
switchedContext
4599-
ifTrue:
4600-
[cogMethod := self mframeCogMethod: framePointer.
4601-
self assert: (instructionPointer asUnsignedInteger > cogit minCogMethodAddress
4602-
and: [instructionPointer asUnsignedInteger < cogit maxCogMethodAddress]).
4603-
(instructionPointer ~= (cogMethod asInteger + cogMethod stackCheckOffset)
4604-
and: [cogit isSendReturnPC: instructionPointer])
4605-
ifTrue:
4606-
[self assert: (objectMemory addressCouldBeOop: self stackTop).
4607-
retValue := self popStack]
4608-
ifFalse:
4609-
[retValue := self mframeReceiver: framePointer]]
4610-
ifFalse: [retValue := self mframeReceiver: framePointer].
4611-
self push: instructionPointer.
4612-
self push: retValue.
4613-
self callEnilopmart: #ceEnterCogCodePopReceiverReg.
4614-
self unreachable].
4602+
retValue := self mframeReceiver: framePointer.
4603+
self push: instructionPointer.
4604+
self push: retValue.
4605+
self callEnilopmart: #ceEnterCogCodePopReceiverReg.
4606+
self unreachable ].
46154607
self setMethod: (self iframeMethod: framePointer).
46164608
fullyInInterpreter := inInterpreter.
4617-
instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
4618-
[instructionPointer := (self iframeSavedIP: framePointer) asUnsignedInteger.
4619-
fullyInInterpreter := false].
4620-
self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: #'__LINE__'.
4621-
fullyInInterpreter ifFalse:
4622-
[self siglong: reenterInterpreter jmp: ReturnToInterpreter.
4623-
self unreachable].
4624-
^nil
4609+
instructionPointer = cogit ceReturnToInterpreterPC ifTrue: [
4610+
instructionPointer := (self iframeSavedIP: framePointer)
4611+
asUnsignedInteger.
4612+
fullyInInterpreter := false ].
4613+
self
4614+
assertValidExecutionPointe: instructionPointer
4615+
r: framePointer
4616+
s: stackPointer
4617+
imbar: true
4618+
line: #__LINE__.
4619+
fullyInInterpreter ifFalse: [
4620+
self siglong: reenterInterpreter jmp: ReturnToInterpreter.
4621+
self unreachable ].
4622+
^ nil
46254623
]
46264624

46274625
{ #category : 'return bytecodes' }

smalltalksrc/VMMaker/CogVMSimulator.class.st

Lines changed: 0 additions & 51 deletions
Original file line numberDiff line numberDiff line change
@@ -1322,34 +1322,6 @@ CogVMSimulator >> primTraceLogSize [
13221322
^PrimTraceLogSize * objectMemory wordSize
13231323
]
13241324

1325-
{ #category : 'debugging traps' }
1326-
CogVMSimulator >> primitiveContextAtPut [
1327-
"| aContext |
1328-
aContext := self stackValue: 2.
1329-
(#(24205456 24205732) includes: aContext) ifTrue:
1330-
[(self checkIsStillMarriedContext: aContext currentFP: framePointer)
1331-
ifTrue: [self printFrame: (self frameOfMarriedContext: aContext)
1332-
WithSP: (self frameOfMarriedContext: aContext) - 48]
1333-
ifFalse: [self printContext: aContext]]."
1334-
^super primitiveContextAtPut
1335-
]
1336-
1337-
{ #category : 'debugging traps' }
1338-
CogVMSimulator >> primitiveDoPrimitiveWithArgs [
1339-
| primIndex |
1340-
primIndex := objectMemory integerValueOf: (self stackValue: 1).
1341-
transcript nextPutAll: 'DO PRIMITIVE: '; print: (self functionPointerFor: primIndex inClass: nil); cr; flush.
1342-
(#(76 "primitiveStoreStackp" 188 189 "eval method") includes: primIndex) ifTrue:
1343-
[self halt].
1344-
^super primitiveDoPrimitiveWithArgs
1345-
]
1346-
1347-
{ #category : 'debugging traps' }
1348-
CogVMSimulator >> primitiveExecuteMethod [
1349-
self halt: thisContext selector.
1350-
^super primitiveExecuteMethod
1351-
]
1352-
13531325
{ #category : 'as yet unclassified' }
13541326
CogVMSimulator >> primitiveFailCount [
13551327
^ primitiveFailCount
@@ -1381,15 +1353,6 @@ CogVMSimulator >> primitiveForceMachineCodeCompaction [
13811353

13821354
]
13831355

1384-
{ #category : 'debugging traps' }
1385-
CogVMSimulator >> primitiveNewWithArg [
1386-
"(objectMemory hasSpurMemoryManagerAPI
1387-
and: [self classNameOf: (self stackValue: 1) Is: 'Bitmap']) ifTrue:
1388-
[self printExternalHeadFrame.
1389-
self halt]."
1390-
^super primitiveNewWithArg
1391-
]
1392-
13931356
{ #category : 'object access primitives' }
13941357
CogVMSimulator >> primitiveObjectAt [
13951358
"self transcript
@@ -1401,12 +1364,6 @@ CogVMSimulator >> primitiveObjectAt [
14011364
^super primitiveObjectAt
14021365
]
14031366

1404-
{ #category : 'debugging traps' }
1405-
CogVMSimulator >> primitiveObjectPointsTo [
1406-
"self halt."
1407-
^super primitiveObjectPointsTo
1408-
]
1409-
14101367
{ #category : 'system control primitives' }
14111368
CogVMSimulator >> primitiveSignalAtMilliseconds [
14121369
super primitiveSignalAtMilliseconds.
@@ -1418,14 +1375,6 @@ CogVMSimulator >> primitiveSignalAtMilliseconds [
14181375
nextPutAll: ' wakeup - now '; print: nextWakeupUsecs - self ioUTCMicroseconds; flush]"
14191376
]
14201377

1421-
{ #category : 'debugging traps' }
1422-
CogVMSimulator >> primitiveStoreStackp [
1423-
"self printContext: (self stackValue: 1).
1424-
self halt."
1425-
"(self stackValue: 1) = 16r1934F80 ifTrue: [self halt]."
1426-
super primitiveStoreStackp
1427-
]
1428-
14291378
{ #category : 'plugin support' }
14301379
CogVMSimulator >> primitiveThatDoNothingWithOneArgument [
14311380

smalltalksrc/VMMaker/Cogit.class.st

Lines changed: 6 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -953,10 +953,10 @@ Cogit class >> initializePrimitiveTable [
953953
"(82 primitiveFail)" "Blue Book: primitiveValueWithArgs"
954954
(83 genPrimitivePerform)
955955
"(84 primitivePerformWithArgs)"
956-
"(85 primitiveSignal)"
957-
"(86 primitiveWait)"
958-
"(87 primitiveResume)"
959-
"(88 primitiveSuspend)"
956+
(85 genNonImplementedPrimitive -1 #maycallback) "primitiveSignal"
957+
(86 genNonImplementedPrimitive -1 #maycallback) "primitiveWait"
958+
(87 genNonImplementedPrimitive -1 #maycallback) "primitiveResume"
959+
(88 genNonImplementedPrimitive -1 #maycallback) "primitiveSuspend"
960960
"(89 primitiveFlushCache)"
961961
962962
"(90 primitiveMousePoint)"
@@ -1004,6 +1004,8 @@ Cogit class >> initializePrimitiveTable [
10041004
(165 genPrimitiveIntegerAt 1) "Signed version of genPrimitiveAt"
10051005
(166 genPrimitiveIntegerAtPut 2) "Signed version of genPrimitiveAtPut"
10061006
1007+
(167 genNonImplementedPrimitive -1 #maycallback) "primitiveYield"
1008+
10071009
(169 genPrimitiveNotIdentical 1)
10081010
10091011
(170 genPrimitiveAsCharacter) "SmallInteger>>asCharacter, Character class>>value:"
@@ -8651,18 +8653,6 @@ Cogit >> isSendAnnotation: annotation [
86518653
^annotation >= IsSendCall
86528654
]
86538655
8654-
{ #category : 'jit - api' }
8655-
Cogit >> isSendReturnPC: retpc [
8656-
<api>
8657-
"Answer if the instruction preceding retpc is a call instruction."
8658-
| target |
8659-
(backEnd isCallPrecedingReturnPC: retpc) ifFalse:
8660-
[^false].
8661-
target := backEnd callTargetFromReturnAddress: retpc.
8662-
^(target between: firstSend and: lastSend)
8663-
or: [target between: methodZoneBase and: methodZone freeStart]
8664-
]
8665-
86668656
{ #category : 'initialization' }
86678657
Cogit >> isTrampolineArgConstant: n [
86688658
"Test for true and false and 0 to N encoded via trampolineArgConstant:"

smalltalksrc/VMMaker/StackInterpreterSimulator.class.st

Lines changed: 0 additions & 93 deletions
Original file line numberDiff line numberDiff line change
@@ -993,18 +993,6 @@ StackInterpreterSimulator >> primitiveAtPut [
993993
^super primitiveAtPut
994994
]
995995

996-
{ #category : 'debugging traps' }
997-
StackInterpreterSimulator >> primitiveContextAt [
998-
"self halt."
999-
^super primitiveContextAt
1000-
]
1001-
1002-
{ #category : 'debugging traps' }
1003-
StackInterpreterSimulator >> primitiveDoPrimitiveWithArgs [
1004-
self halt.
1005-
^super primitiveDoPrimitiveWithArgs
1006-
]
1007-
1008996
{ #category : 'control primitives' }
1009997
StackInterpreterSimulator >> primitiveExecuteMethod [
1010998
self halt: thisContext selector.
@@ -1019,72 +1007,6 @@ StackInterpreterSimulator >> primitiveExecuteMethodArgsArray [
10191007
^super primitiveExecuteMethodArgsArray
10201008
]
10211009

1022-
{ #category : 'debugging traps' }
1023-
StackInterpreterSimulator >> primitiveFailFor: reasonCode [
1024-
"self halt."
1025-
^super primitiveFailFor: reasonCode
1026-
]
1027-
1028-
{ #category : 'debugging traps' }
1029-
StackInterpreterSimulator >> primitiveIdentityHash [
1030-
"| oop |
1031-
oop := self stackTop.
1032-
((objectMemory isBytes: oop)
1033-
and: [(objectMemory lengthOf: oop) = 'smallSelect' size
1034-
and: [(self stringOf: oop) = 'smallSelect']]) ifTrue:
1035-
[self halt]."
1036-
^super primitiveIdentityHash
1037-
]
1038-
1039-
{ #category : 'debugging traps' }
1040-
StackInterpreterSimulator >> primitiveNewWithArg [
1041-
"(objectMemory hasSpurMemoryManagerAPI
1042-
and: [self classNameOf: (self stackValue: 1) Is: 'MethodDictionary']) ifTrue:
1043-
[self halt]."
1044-
"| hash |
1045-
hash := objectMemory rawHashBitsOf: (self stackValue: 1)."
1046-
"| format |
1047-
format := objectMemory instSpecOfClass: (self stackValue: 1)."
1048-
"(objectMemory numSlotsOf: (self stackValue: 1)) = 3 ifTrue:
1049-
[self halt]."
1050-
super primitiveNewWithArg.
1051-
"self successful ifTrue:
1052-
[(Smalltalk at: #Counts ifAbsentPut: [Bag new]) add: format]."
1053-
"(self successful and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
1054-
[(Smalltalk at: #Counts ifAbsentPut: [Bag new]) add: hash]"
1055-
"Smalltalk removeKey: #Counts"
1056-
"Counts sortedCounts collect: [:assoc|
1057-
assoc key -> ((SpurMemoryManager organization listAtCategoryNamed: #'header formats') detect:
1058-
[:f| (SpurMemoryManager basicNew perform: f) = assoc value])]
1059-
{3251->#arrayFormat.
1060-
1685->#firstByteFormat.
1061-
1533->#firstLongFormat.
1062-
110->#weakArrayFormat.
1063-
35->#indexablePointersFormat.
1064-
5->#nonIndexablePointerFormat}"
1065-
"Counts sortedCounts collect: [:assoc|
1066-
assoc value = 0
1067-
ifTrue: [assoc]
1068-
ifFalse: [assoc key -> {(self nameOfClass: (objectMemory classAtIndex: assoc value)).
1069-
(SpurMemoryManager organization listAtCategoryNamed: #'header formats') detect:
1070-
[:f| (objectMemory perform: f)
1071-
= (objectMemory instSpecOfClass: (objectMemory classAtIndex: assoc value))]}]]
1072-
{1062->#('Array' #arrayFormat).
1073-
777->#('Bitmap' #firstLongFormat).
1074-
395->#('Float' #firstLongFormat).
1075-
345->#('ByteString' #firstByteFormat).
1076-
237->#('MatrixTransform2x3' #firstLongFormat).
1077-
233->#('LargePositiveInteger' #firstByteFormat).
1078-
103->#('WordArray' #firstLongFormat).
1079-
58->#('WeakArray' #weakArrayFormat).
1080-
52->#('WeakMessageSend' #weakArrayFormat).
1081-
9->#('MethodContext' #indexablePointersFormat).
1082-
4->#('DirectoryEntry' #nonIndexablePointerFormat).
1083-
3->#('BalloonBuffer' #firstLongFormat).
1084-
1->#('ByteArray' #firstByteFormat).
1085-
1->0}"
1086-
]
1087-
10881010
{ #category : 'object access primitives' }
10891011
StackInterpreterSimulator >> primitiveObjectPointsTo [
10901012
"self halt."
@@ -1108,14 +1030,6 @@ StackInterpreterSimulator >> primitiveVMParameter [
11081030
^super primitiveVMParameter
11091031
]
11101032

1111-
{ #category : 'debugging traps' }
1112-
StackInterpreterSimulator >> primitiveWait [
1113-
"Catch errors before we start the whole morphic error process"
1114-
1115-
"byteCount > 1000000 ifTrue: [self halt]." "Ignore early process activity"
1116-
^ super primitiveWait
1117-
]
1118-
11191033
{ #category : 'debug printing' }
11201034
StackInterpreterSimulator >> print: it [
11211035

@@ -1525,13 +1439,6 @@ StackInterpreterSimulator >> startInSender [
15251439
withValue: (self fetchStackPointerOf: senderContext) + 1
15261440
]
15271441

1528-
{ #category : 'debugging traps' }
1529-
StackInterpreterSimulator >> success: successBoolean [
1530-
"successBoolean ifFalse:
1531-
[self halt]."
1532-
^super success: successBoolean
1533-
]
1534-
15351442
{ #category : 'simulation only' }
15361443
StackInterpreterSimulator >> systemAttributes [
15371444
^systemAttributes

0 commit comments

Comments
 (0)