Skip to content

Commit cf30a2d

Browse files
committed
Fix assertion when suspending a process in a list
1 parent 1854453 commit cf30a2d

File tree

1 file changed

+21
-5
lines changed

1 file changed

+21
-5
lines changed

smalltalksrc/VMMaker/StackInterpreter.class.st

+21-5
Original file line numberDiff line numberDiff line change
@@ -1955,16 +1955,32 @@ StackInterpreter >> addIdleUsecs: idleUsecs [
19551955
StackInterpreter >> addLastLink: proc toList: aList [
19561956
"Add the given process to the end of the given linked list
19571957
and set the backpointer of process to its new list."
1958-
| lastLink |
1958+
| lastLink procList |
1959+
1960+
lastLink := objectMemory
1961+
fetchPointer: LastLinkIndex
1962+
ofObject: aList.
1963+
1964+
"If the process is already in a list two cases may arise"
1965+
procList := objectMemory followField: MyListIndex ofObject: proc.
1966+
procList ~= objectMemory nilObject ifTrue: [
1967+
procList = aList ifTrue: [
1968+
"It it is in the same list we want to put it, remove it so we make sure to install it at the end"
1969+
self removeProcess: proc fromList: aList.
1970+
] ifFalse: [
1971+
"Otherwise, we cannot ensure a correct behavior, fail.
1972+
If the process is already in a list, do not silently move it to another one"
1973+
self error: 'Process is already suspended in a different list'
1974+
]].
1975+
19591976
self deny: (objectMemory isForwarded: proc).
19601977
self deny: (objectMemory isForwarded: aList).
19611978
self assert: (objectMemory fetchPointer: NextLinkIndex ofObject: proc) = objectMemory nilObject.
19621979
(self isEmptyList: aList)
19631980
ifTrue: [objectMemory storePointer: FirstLinkIndex ofObject: aList withValue: proc]
1964-
ifFalse:
1965-
[lastLink := objectMemory fetchPointer: LastLinkIndex ofObject: aList.
1966-
self assert: lastLink ~= proc.
1967-
objectMemory storePointer: NextLinkIndex ofObject: lastLink withValue: proc].
1981+
ifFalse: [
1982+
lastLink := objectMemory fetchPointer: LastLinkIndex ofObject: aList.
1983+
objectMemory storePointer: NextLinkIndex ofObject: lastLink withValue: proc].
19681984
objectMemory storePointer: LastLinkIndex ofObject: aList withValue: proc.
19691985
objectMemory storePointer: MyListIndex ofObject: proc withValue: aList
19701986
]

0 commit comments

Comments
 (0)