Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
81 changes: 44 additions & 37 deletions smalltalksrc/VMMaker/SpurMemoryManager.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -8315,7 +8315,6 @@ SpurMemoryManager >> markInactiveEphemerons [

{ #category : #'gc - global' }
SpurMemoryManager >> markLoopFrom: objOop [

"Scan objOop and all objects on the mark stack, until the mark stack is empty.
N.B. When the incremental GC is written this will probably be refactored as
markLoopFrom: objOop while: aBlock"
Expand All @@ -8326,61 +8325,66 @@ SpurMemoryManager >> markLoopFrom: objOop [
objToScan := objOop.
"To avoid overflowing the mark stack when we encounter large objects, we
push the obj, then its numStrongSlots, and then index the object from the stack."
[
[
(self isImmediate: objToScan)
ifTrue: [ scanLargeObject := true ]
ifFalse: [
numStrongSlots := ((self isEphemeron: objToScan) and: [ self isMarked: (self keyOfEphemeron: objToScan) ])
ifTrue: [ self numSlotsOf: objToScan ]
ifFalse: [ self numStrongSlotsOfInephemeral: objToScan ].
numStrongSlots := ((self isEphemeron: objToScan) and: [
| key |
(self isImmediate:
(key := self keyOfEphemeron: objToScan)) or: [
self isMarked: key ] ])
ifTrue: [ self numSlotsOf: objToScan ]
ifFalse: [
self numStrongSlotsOfInephemeral: objToScan ].
scanLargeObject := numStrongSlots > self traceImmediatelySlotLimit ].
scanLargeObject
ifTrue: [ "scanning a large object. scan until hitting an unmarked object, then switch to it, if any."
(self isImmediate: objToScan)
ifTrue: [
ifTrue: [
index := self integerValueOf: objToScan.
objToScan := self topOfObjStack: markStack ]
ifFalse: [
ifFalse: [
index := numStrongSlots.
self markAndTraceClassOf: objToScan ].
[ index > 0 ] whileTrue: [
[ index > 0 ] whileTrue: [
index := index - 1.
field := self fetchPointer: index ofObject: objToScan.
(self isNonImmediate: field) ifTrue: [
(self isNonImmediate: field) ifTrue: [
(self isForwarded: field) ifTrue: [ "fixFollowedField: is /not/ inlined"
field := self
fixFollowedField: index
ofObject: objToScan
withInitialValue: field ].
(self markAndShouldScan: field) ifTrue: [
index > 0 ifTrue: [
(self topOfObjStack: markStack) ~= objToScan ifTrue: [
(self markAndShouldScan: field) ifTrue: [
index > 0 ifTrue: [
(self topOfObjStack: markStack) ~= objToScan ifTrue: [
self push: objToScan onObjStack: markStack ].
self push: (self integerObjectOf: index) onObjStack: markStack ].
objToScan := field.
index := -1 ] ] ].
index >= 0 ifTrue: [ "if loop terminated without finding an unmarked referent, switch to top of stack."
objToScan := self popObjStack: markStack.
objToScan = objOop ifTrue: [
objToScan = objOop ifTrue: [
objToScan := self popObjStack: markStack ] ] ]
ifFalse: [ "scanning a small object. scan, marking, pushing unmarked referents, then switch to the top of the stack."
index := numStrongSlots.
self markAndTraceClassOf: objToScan.
[ index > 0 ] whileTrue: [
[ index > 0 ] whileTrue: [
index := index - 1.
field := self fetchPointer: index ofObject: objToScan.
(self isNonImmediate: field) ifTrue: [
(self isNonImmediate: field) ifTrue: [
(self isForwarded: field) ifTrue: [ "fixFollowedField: is /not/ inlined"
field := self
fixFollowedField: index
ofObject: objToScan
withInitialValue: field ].
(self markAndShouldScan: field) ifTrue: [
(self markAndShouldScan: field) ifTrue: [
self push: field onObjStack: markStack.
((self rawNumSlotsOf: field) > self traceImmediatelySlotLimit
and: [
((self rawNumSlotsOf: field) > self traceImmediatelySlotLimit
and: [
(numStrongSlots := self numStrongSlotsOfInephemeral: field)
> self traceImmediatelySlotLimit ]) ifTrue: [
> self traceImmediatelySlotLimit ]) ifTrue: [
self
push: (self integerObjectOf: numStrongSlots)
onObjStack: markStack ] ] ] ].
Expand Down Expand Up @@ -9252,30 +9256,33 @@ SpurMemoryManager >> numStrongSlotsOfInephemeral: objOop [
"Answer the number of strong pointer fields in the given object,
which is expected not to be an active ephemeron.
Works with CompiledMethods, as well as ordinary objects."

<inline: true>
| fmt numSlots contextSize numLiterals header |
| fmt numSlots contextSize numLiterals header |
fmt := self formatOf: objOop.
self assert: (fmt ~= self ephemeronFormat or: [self isMarked: (self keyOfEphemeron: objOop)]).
fmt <= self lastPointerFormat ifTrue:
[numSlots := self numSlotsOf: objOop.
fmt <= self arrayFormat ifTrue:
[^numSlots].
fmt = self indexablePointersFormat ifTrue:
[(self isContextNonImm: objOop) ifTrue:
[coInterpreter setTraceFlagOnContextsFramesPageIfNeeded: objOop.
"contexts end at the stack pointer"
contextSize := coInterpreter fetchStackPointerOf: objOop.
^CtxtTempFrameStart + contextSize].
^numSlots].
fmt = self weakArrayFormat ifTrue:
[^self fixedFieldsOfClass: (self fetchClassOfNonImm: objOop)]].
fmt = self forwardedFormat ifTrue: [^1].
fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
self assert: (fmt ~= self ephemeronFormat or: [
| key |
(self isImmediate: (key := self keyOfEphemeron: objOop)) or: [
self isMarked: key ] ]).
fmt <= self lastPointerFormat ifTrue: [
numSlots := self numSlotsOf: objOop.
fmt <= self arrayFormat ifTrue: [ ^ numSlots ].
fmt = self indexablePointersFormat ifTrue: [
(self isContextNonImm: objOop) ifTrue: [
coInterpreter setTraceFlagOnContextsFramesPageIfNeeded: objOop.
"contexts end at the stack pointer"
contextSize := coInterpreter fetchStackPointerOf: objOop.
^ CtxtTempFrameStart + contextSize ].
^ numSlots ].
fmt = self weakArrayFormat ifTrue: [
^ self fixedFieldsOfClass: (self fetchClassOfNonImm: objOop) ] ].
fmt = self forwardedFormat ifTrue: [ ^ 1 ].
fmt < self firstCompiledMethodFormat ifTrue: [ ^ 0 ]. "no pointers"

"CompiledMethod: contains both pointers and bytes"
header := self methodHeaderOf: objOop.
numLiterals := self literalCountOfMethodHeader: header.
^numLiterals + LiteralStart
^ numLiterals + LiteralStart
]

{ #category : #'object access' }
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -416,6 +416,24 @@ VMSpurOldSpaceGarbageCollectorTest >> testEphemeronOverflowUnscannedEphemeronQue
equals: numberJustOverLimit
]

{ #category : #tests }
VMSpurOldSpaceGarbageCollectorTest >> testEphemeronWithImmediateKeyShouldNotFail [

| ephemeron1 key |
ephemeron1 := self newEphemeronObjectWithSlots: 5.
self keepObjectInVMVariable1: ephemeron1.
key := memory integerObjectOf: 15.
memory storePointer: 0 ofObject: ephemeron1 withValue: key.

memory setCheckForLeaks: 63. "all"
memory fullGC.

self
assert:
(memory fetchInteger: 0 ofObject: self keptObjectInVMVariable1)
equals: 15
]
Comment on lines +420 to +435
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Why here the assertion says just 15 instead of key? @guillep

Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I did a fetchInteger:, to make sure the same value is there.
What would be the most readable?
I think in any case we will need a comment, right?

Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Ahhhh okkkkk. I don't think that a comment is needed, I just need to learn how to read 😅

Maybe having storeInteger: also would help with the symmetry.


{ #category : #tests }
VMSpurOldSpaceGarbageCollectorTest >> testGrowOldSpace [

Expand Down