Skip to content

Commit

Permalink
Make ephemeron scanning more optimal by firing many ephemerons in a s…
Browse files Browse the repository at this point in the history
…ingle run
  • Loading branch information
guillep committed Sep 13, 2023
1 parent 2dc24ce commit 27556c3
Show file tree
Hide file tree
Showing 3 changed files with 178 additions and 11 deletions.
48 changes: 37 additions & 11 deletions smalltalksrc/VMMaker/SpurMemoryManager.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -8473,20 +8473,46 @@ SpurMemoryManager >> markAllUnscannedEphemerons [
The wrinkle is that doing so may add more ephemerons to the set.
So we remove the first element, by overwriting it with the last element,
and decrementing the top, and then markAndTrace its contents."

"self assert: (self noUnscannedEphemerons) not."

| nextOffsetToScan lastOffsetToScan |
self assert: self allUnscannedEphemeronsAreActive.
[unscannedEphemerons top > unscannedEphemerons start] whileTrue:
[| ephemeron key lastptr |
ephemeron := self longAt: unscannedEphemerons start.
lastptr := unscannedEphemerons top - self bytesPerOop.
lastptr > unscannedEphemerons start ifTrue:
[self longAt: unscannedEphemerons start put: (self longAt: lastptr)].
unscannedEphemerons top: lastptr.
key := self followedKeyOfMaybeFiredEphemeron: ephemeron.
self setIsMarkedOf: ephemeron to: false. "to get it to be fully scanned in markAndTrace:"
self
nextOffsetToScan := unscannedEphemerons start.
lastOffsetToScan := unscannedEphemerons top.
[ lastOffsetToScan > nextOffsetToScan ] whileTrue: [
| ephemeron key lastptr |
ephemeron := self longAt: nextOffsetToScan.

key := self followedKeyOfMaybeFiredEphemeron: ephemeron.
self setIsMarkedOf: ephemeron to: false. "to get it to be fully scanned in markAndTrace:"
self
markAndTrace: key;
markAndTrace: ephemeron]
markAndTrace: ephemeron.

"Now we compact the array to ensure that all elements between start and top are valid objects.
We move the last element in the list to the start.
We could have moved a newly discovered ephemeron or an ephemeron we already had. See below"
lastptr := unscannedEphemerons top - self bytesPerOop.
lastptr > nextOffsetToScan ifTrue: [
self longAt: nextOffsetToScan put: (self longAt: lastptr) ].

"New ephemerons are above the lastOffsetToScan.
If we find new ephemerons, we need to move the nextOffsetToScan up. Otherwise, move the lastOffsetToScan down.
The invariant are that:
- the objects originally in the array will always be between nextOffsetToScan and lastOffsetToScan
- both the differences lastOffsetToScan-nextOffsetToScan and unscannedEphemerons top - unscannedEphemerons start go down by one in each iteration."
unscannedEphemerons top > lastOffsetToScan
ifTrue: [
"New ephemeron was moved down, move nextOffsetToScan up"
nextOffsetToScan := nextOffsetToScan + self bytesPerOop ]
ifFalse: [
"Old ephemeron was moved down, move lastOffsetToScan down"
lastOffsetToScan := lastOffsetToScan - self bytesPerOop
].
"Then move the top of the full array down by one element"
unscannedEphemerons top: lastptr.
].
]

{ #category : #'gc - global' }
Expand Down
11 changes: 11 additions & 0 deletions smalltalksrc/VMMakerTests/VMSpurMemoryManagerTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -579,6 +579,17 @@ VMSpurMemoryManagerTest >> newOldByteObjectOfSize: byteSize [
^ oop
]

{ #category : #helpers }
VMSpurMemoryManagerTest >> newOldEphemeronObject [

"In pharo Ephemerons have 3 slots"

^ self
newOldSpaceObjectWithSlots: 3
format: memory ephemeronFormat
classIndex: (memory ensureBehaviorHash: ourEphemeronClass)
]

{ #category : #'helpers - objects' }
VMSpurMemoryManagerTest >> newOldSpaceArrayWithSlots: slots [

Expand Down
130 changes: 130 additions & 0 deletions smalltalksrc/VMMakerTests/VMSpurOldSpaceGarbageCollectorTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -283,6 +283,136 @@ VMSpurOldSpaceGarbageCollectorTest >> testArrayOfPermanentObjectsPointingToOldOb
self assert: (originalHashes at: i) equals: (memory hashBitsOf: (memory fetchPointer: i - 1 ofObject: permArray))]
]

{ #category : #ephemerons }
VMSpurOldSpaceGarbageCollectorTest >> testChainOfFirableEphemerons [

"This test creates a set of ephemerons on the old space that should be fired because their key is not referenced.
However, the only strong reference to an ephemeron is in another ephemeron.
Since all ephemerons depend on different keys, all should be fired at the same time."

| mourned previousEphemeron ephemerons |
self createEphemeronClass.
previousEphemeron := memory nilObject.
ephemerons := 3.
1 to: ephemerons do: [ :i | | ephemeronKey ephemeronObjectOop |
ephemeronKey := self newZeroSizedObject.
"An ephemeron with 3 slots"
ephemeronObjectOop := self newOldEphemeronObject.
memory
storePointer: 0 "key"
ofObject: ephemeronObjectOop
withValue: ephemeronKey.
memory
storePointer: 1 "value"
ofObject: ephemeronObjectOop
withValue: previousEphemeron.
previousEphemeron := ephemeronObjectOop.
].

"Force the first ephemeron in the chain to not be collected by putting it in an intepreter register"
self keepObjectInVMVariable1: previousEphemeron.

self assert: memory validObjStacks.
memory unscannedEphemeronsQueueInitialSize: ephemerons.
memory fullGC.

mourned := 0.
[ memory dequeueMourner notNil ] whileTrue: [ mourned := mourned + 1 ].
self
assert: mourned
equals: ephemerons
]

{ #category : #ephemerons }
VMSpurOldSpaceGarbageCollectorTest >> testChainOfFirableEphemeronsWithNonFirableHead [

"This test creates a set of ephemerons on the old space that should be fired because their key is not referenced.
The only strong reference to an ephemeron is in another ephemeron.
However, the head of the list is an ephemeron with a referenced key!
Since all other ephemerons depend on different keys, all should be fired at the same time."

| mourned previousEphemeron nonFirableEphemeron |
self createEphemeronClass.
previousEphemeron := memory nilObject.
1 to: 5 do: [ :i | | ephemeronKey ephemeronObjectOop |
ephemeronKey := self newZeroSizedObject.
ephemeronObjectOop := self newOldEphemeronObject.
memory
storePointer: 0 "key"
ofObject: ephemeronObjectOop
withValue: ephemeronKey.
memory
storePointer: 1 "value"
ofObject: ephemeronObjectOop
withValue: previousEphemeron.
previousEphemeron := ephemeronObjectOop.
].

nonFirableEphemeron := self newOldEphemeronObject.
memory
storePointer: 0 "key"
ofObject: nonFirableEphemeron
withValue: memory nilObject.
memory
storePointer: 1 "value"
ofObject: nonFirableEphemeron
withValue: previousEphemeron.

"Force the first ephemeron in the chain to not be collected by putting it in an intepreter register"
self keepObjectInVMVariable1: nonFirableEphemeron.

self assert: memory validObjStacks.
memory unscannedEphemeronsQueueInitialSize: 5.
memory fullGC.

mourned := 0.
[ memory dequeueMourner notNil ] whileTrue: [ mourned := mourned + 1 ].
self
assert: mourned
equals: 5
]

{ #category : #ephemerons }
VMSpurOldSpaceGarbageCollectorTest >> testChainOfFirableEphemeronsWithOldKeys [

"This test creates a set of ephemerons on the old space that should be fired because their key is not referenced.
However, the only strong reference to an ephemeron is in another ephemeron.
Since all ephemerons depend on different keys, all should be fired at the same time."

| mourned previousEphemeron ephemerons |
self createEphemeronClass.
previousEphemeron := memory nilObject.
ephemerons := 3.
1 to: ephemerons do: [ :i | | ephemeronKey ephemeronObjectOop |
ephemeronKey := self newOldSpaceObjectWithSlots: 0.
"An ephemeron with 3 slots"
ephemeronObjectOop := self newOldEphemeronObject.
memory
storePointer: 0 "key"
ofObject: ephemeronObjectOop
withValue: ephemeronKey.
memory
storePointer: 1 "value"
ofObject: ephemeronObjectOop
withValue: previousEphemeron.
previousEphemeron := ephemeronObjectOop.
].

"Force the first ephemeron in the chain to not be collected by putting it in an intepreter register"
self keepObjectInVMVariable1: previousEphemeron.

self assert: memory validObjStacks.
memory unscannedEphemeronsQueueInitialSize: ephemerons.
memory fullGC.

mourned := 0.
[ memory dequeueMourner notNil ] whileTrue: [ mourned := mourned + 1 ].
self
assert: mourned
equals: ephemerons
]

{ #category : #ephemerons }
VMSpurOldSpaceGarbageCollectorTest >> testCompactEphemeronQueuePass1 [

Expand Down

0 comments on commit 27556c3

Please sign in to comment.