Skip to content

Commit

Permalink
- Adding primitive to move to the perm space.
Browse files Browse the repository at this point in the history
- Adding tests
  • Loading branch information
tesonep committed Apr 1, 2022
1 parent 898de44 commit cbabe7e
Show file tree
Hide file tree
Showing 8 changed files with 235 additions and 40 deletions.
61 changes: 58 additions & 3 deletions smalltalksrc/VMMaker/SpurMemoryManager.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1665,7 +1665,8 @@ SpurMemoryManager >> allObjects [
SpurMemoryManager >> allObjectsDo: aBlock [
<inline: true>
self allNewSpaceObjectsDo: aBlock.
self allOldSpaceObjectsDo: aBlock
self allOldSpaceObjectsDo: aBlock.
self allPermSpaceObjectsDo: aBlock.
]
{ #category : #'free space' }
Expand Down Expand Up @@ -1850,6 +1851,19 @@ SpurMemoryManager >> allPastSpaceObjectsDo: aBlock [
aBlock value: objOop]
]
{ #category : #'perm - space' }
SpurMemoryManager >> allPermSpaceObjectsDo: aBlockClosure [
| currentObject |
currentObject := memoryMap permSpaceStart.
[ currentObject = permSpaceFreeStart ]
whileFalse: [
aBlockClosure value: currentObject.
currentObject := self objectAfter: currentObject limit: memoryMap permSpaceEnd ].
]
{ #category : #'weakness and ephemerality' }
SpurMemoryManager >> allStrongSlotsOfWeaklingAreMarked: aWeakling [
"N.B. generateToByDoLimitExpression:negative:on: guards against (unsigned)0 - 1 going +ve"
Expand Down Expand Up @@ -2495,7 +2509,7 @@ SpurMemoryManager >> allocateSlotsInPermSpace: numSlots bytes: totalBytes format
^ newOop
]
{ #category : #allocation }
{ #category : #'perm - space' }
SpurMemoryManager >> allocateSlotsInPermSpace: numSlots format: formatField classIndex: classIndex [
<inline: true>
Expand Down Expand Up @@ -8648,6 +8662,47 @@ SpurMemoryManager >> mournQueue: anOop [
mournQueue := anOop
]
{ #category : #'perm - space' }
SpurMemoryManager >> moveToPermSpace: objOop [
<inline: false>
| numSlots fmt newObj hash |
"Clonning in permSpace"
numSlots := self numSlotsOf: objOop.
fmt := self formatOf: objOop.
(self isPointersFormat: fmt)
ifTrue: [ ^ nil ].
fmt >= self firstCompiledMethodFormat ifTrue: [ ^ nil ].
newObj := self allocateSlotsInPermSpace: numSlots
bytes: (self objectBytesForSlots: numSlots)
format: fmt
classIndex: (self classIndexOf: objOop).
newObj ifNil: [^nil].
0 to: numSlots - 1 do:
[:i|
self storePointerUnchecked: i
ofObject: newObj
withValue: (self fetchPointer: i ofObject: objOop)].
(hash := self rawHashBitsOf: objOop) ~= 0 ifTrue: [self setHashBitsOf: newObj to: hash].
(self isObjImmutable: objOop) ifTrue: [self setIsImmutableOf: newObj to: true].
becomeEffectsFlags := self becomeEffectFlagsFor: objOop.
self forward: objOop to: newObj.
self followSpecialObjectsOop.
coInterpreter postBecomeAction: becomeEffectsFlags.
self postBecomeScanClassTable: becomeEffectsFlags.
becomeEffectsFlags := 0.
^newObj
]
{ #category : #'become implementation' }
SpurMemoryManager >> naiveSwapHeaders: obj1 and: obj2 copyHashFlag: copyHashFlag [
"swap headers, but swapping headers swaps remembered bits and hashes;
Expand Down Expand Up @@ -11662,7 +11717,7 @@ SpurMemoryManager >> storeByte: byteIndex ofObject: oop withValue: valueByte [
SpurMemoryManager >> storeCheckBoundary [
"A renaming for the Cogit, which couldn't make sense of GIV(newSpaceLimit)"
<api>
^memoryMap newSpaceEnd
^memoryMap oldSpaceStart
]
{ #category : #'simulation only' }
Expand Down
6 changes: 4 additions & 2 deletions smalltalksrc/VMMaker/StackInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1149,8 +1149,10 @@ StackInterpreter class >> initializePrimitiveTable [
(88 primitiveSuspend)
(89 primitiveFlushCache)

"Input/Output Primitives (90-109)"
(90 primitiveFail)
"Perm Space primitives"
(90 primitiveMoveToPermSpace)

"Input/Output Primitives (91-109)"
(91 primitiveFail)
(92 primitiveFail)
(93 primitiveFail)
Expand Down
15 changes: 15 additions & 0 deletions smalltalksrc/VMMaker/StackInterpreterPrimitives.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -2888,6 +2888,21 @@ StackInterpreterPrimitives >> primitiveLongRunningPrimitiveSemaphore [
self pop: 1
]

{ #category : #'perm - space' }
StackInterpreterPrimitives >> primitiveMoveToPermSpace [

| rcvr permObject |
rcvr := self stackTop.

(objectMemory isPointers: rcvr)
ifTrue: [ ^ self primitiveFailFor: PrimErrBadReceiver ].

permObject := objectMemory moveToPermSpace: rcvr.
permObject ifNil: [ ^ self primitiveFailFor: PrimErrBadReceiver ].

self pop: argumentCount + 1 thenPush: permObject.
]

{ #category : #'object access primitives' }
StackInterpreterPrimitives >> primitiveObjectPointsTo [
"This primitive is assumed to be fast (see e.g. MethodDictionary>>includesKey:) so make it so.
Expand Down
19 changes: 10 additions & 9 deletions smalltalksrc/VMMakerTests/VMAbstractFFITest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -75,15 +75,6 @@ VMAbstractFFITest >> newExternalAddress: anInteger [
^ anExternalAddress
]

{ #category : #'as yet unclassified' }
VMAbstractFFITest >> newMethodWithBytecodes: aCollection [

^ methodBuilder
newMethod;
bytecodes: aCollection;
buildMethod
]

{ #category : #helpers }
VMAbstractFFITest >> readyProcesses [

Expand All @@ -92,3 +83,13 @@ VMAbstractFFITest >> readyProcesses [
interpreter processesInProcessListDo: [ :e | collection add: e ].
^ collection
]

{ #category : #initialization }
VMAbstractFFITest >> setUp [

super setUp.

interpreter libFFI: LibFFI new.
interpreter libFFI interpreter: interpreter.

]
11 changes: 9 additions & 2 deletions smalltalksrc/VMMakerTests/VMAbstractPrimitiveTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,15 @@ VMAbstractPrimitiveTest >> newArrayWith: aCollection [

]

{ #category : #'as yet unclassified' }
VMAbstractPrimitiveTest >> newMethodWithBytecodes: aCollection [

^ methodBuilder
newMethod;
bytecodes: aCollection;
buildMethod
]

{ #category : #'helpers - frames' }
VMAbstractPrimitiveTest >> newSmallContextReceiver: anOop method: aMethodOop arguments: aCollectionOfArgumentsOop temporaries: aCollectionOfTemporariesOop ip: anIp [

Expand Down Expand Up @@ -135,8 +144,6 @@ VMAbstractPrimitiveTest >> setUp [
page := interpreter makeBaseFrameFor: ctx.
interpreter setStackPageAndLimit: page.
interpreter setStackPointersFromPage: page.
interpreter libFFI: LibFFI new.
interpreter libFFI interpreter: interpreter.

self createActiveProcess.

Expand Down
Original file line number Diff line number Diff line change
@@ -1,22 +1,19 @@
Class {
#name : #VMPermanentSpaceTest,
#name : #VMPermanentSpaceMemoryTest,
#superclass : #VMSpurInitializedOldSpaceTest,
#instVars : [
'byteArrayClassIndex'
],
#category : #'VMMakerTests-MemoryTests'
#category : #'VMMakerTests-PermSpace'
}

{ #category : #running }
VMPermanentSpaceTest >> configureEnvironmentBuilder [
VMPermanentSpaceMemoryTest >> configureEnvironmentBuilder [

super configureEnvironmentBuilder.

environmentBuilder permSpaceSize: 10*1024*1024.
]

{ #category : #'instance creation' }
VMPermanentSpaceTest >> newPermanentByteObjectOfSize: byteSize [
VMPermanentSpaceMemoryTest >> newPermanentByteObjectOfSize: byteSize [

| oop numSlots instSpec |

Expand All @@ -26,7 +23,7 @@ VMPermanentSpaceTest >> newPermanentByteObjectOfSize: byteSize [
oop := memory
allocateSlotsInPermSpace: numSlots
format: instSpec
classIndex: byteArrayClassIndex.
classIndex: (memory ensureBehaviorHash: memory classByteArray).

0 to: byteSize - 1 do: [ :index |
memory storeByte: index ofObject: oop withValue: 0 ].
Expand All @@ -35,21 +32,20 @@ VMPermanentSpaceTest >> newPermanentByteObjectOfSize: byteSize [
]

{ #category : #running }
VMPermanentSpaceTest >> setUp [
VMPermanentSpaceMemoryTest >> setUp [

super setUp.

memory classByteArray: (self newClassInOldSpaceWithSlots: 0 instSpec: (memory byteFormatForNumBytes: 0)).
byteArrayClassIndex := memory ensureBehaviorHash: memory classByteArray.





]

{ #category : #'instance creation' }
VMPermanentSpaceTest >> testMarkingNewSpaceDoesNotMarkPermSpace [
{ #category : #'tests - allocation' }
VMPermanentSpaceMemoryTest >> testMarkingNewSpaceDoesNotMarkPermSpace [

| permanentObject newObject |

Expand All @@ -66,8 +62,8 @@ VMPermanentSpaceTest >> testMarkingNewSpaceDoesNotMarkPermSpace [
self deny: (memory isMarked: permanentObject)
]

{ #category : #'instance creation' }
VMPermanentSpaceTest >> testMarkingOldSpaceDoesNotMarkPermSpace [
{ #category : #'tests - allocation' }
VMPermanentSpaceMemoryTest >> testMarkingOldSpaceDoesNotMarkPermSpace [

| permanentObject oldObject |

Expand All @@ -84,8 +80,45 @@ VMPermanentSpaceTest >> testMarkingOldSpaceDoesNotMarkPermSpace [
self deny: (memory isMarked: permanentObject)
]

{ #category : #'instance creation' }
VMPermanentSpaceTest >> testNewPermanentByteArrayIsCorrectlyAllocated [
{ #category : #'test - moving' }
VMPermanentSpaceMemoryTest >> testMovingOldObjectToPermSpaceIsCorrectlyForwarded [

| permanentObject oldObject rootObject|

rootObject := self newOldSpaceObjectWithSlots: 1.
oldObject := self newOldByteObjectOfSize: 1.

memory storePointer: 0 ofObject: rootObject withValue: oldObject.
self keepObjectInVMVariable1: rootObject.

permanentObject := memory moveToPermSpace: oldObject.

self assert: (memory isForwarded: (memory fetchPointer: 0 ofObject: rootObject)).

memory fullGC.

self deny: (memory isForwarded: (memory fetchPointer: 0 ofObject: rootObject)).
self assert: (memory fetchPointer: 0 ofObject: rootObject) equals: permanentObject.

]

{ #category : #'test - moving' }
VMPermanentSpaceMemoryTest >> testMovingOldObjectToPermSpaceLeavesForwarder [

| permanentObject oldObject |

oldObject := self newOldByteObjectOfSize: 1.
self keepObjectInVMVariable1: oldObject.
self assert: (memory isOldObject: oldObject).

permanentObject := memory moveToPermSpace: oldObject.

self assert: (memory isForwarded: oldObject).

]

{ #category : #'tests - allocation' }
VMPermanentSpaceMemoryTest >> testNewPermanentByteArrayIsCorrectlyAllocated [

| permanentObject |

Expand All @@ -94,8 +127,8 @@ VMPermanentSpaceTest >> testNewPermanentByteArrayIsCorrectlyAllocated [
self assert: permanentObject equals: memory getMemoryMap permSpaceStart
]

{ #category : #'instance creation' }
VMPermanentSpaceTest >> testNewPermanentByteArrayIsNonYoungObject [
{ #category : #'tests - allocation' }
VMPermanentSpaceMemoryTest >> testNewPermanentByteArrayIsNonYoungObject [

| permanentObject |

Expand All @@ -104,8 +137,8 @@ VMPermanentSpaceTest >> testNewPermanentByteArrayIsNonYoungObject [
self deny: (memory isYoungObject: permanentObject)
]

{ #category : #'instance creation' }
VMPermanentSpaceTest >> testNewPermanentByteArrayIsNotAnOldObject [
{ #category : #'tests - allocation' }
VMPermanentSpaceMemoryTest >> testNewPermanentByteArrayIsNotAnOldObject [

| permanentObject |

Expand All @@ -114,8 +147,8 @@ VMPermanentSpaceTest >> testNewPermanentByteArrayIsNotAnOldObject [
self deny: (memory isOldObject: permanentObject)
]

{ #category : #'instance creation' }
VMPermanentSpaceTest >> testNewPermanentByteArrayIsPermanentObject [
{ #category : #'tests - allocation' }
VMPermanentSpaceMemoryTest >> testNewPermanentByteArrayIsPermanentObject [

| permanentObject |

Expand All @@ -124,8 +157,8 @@ VMPermanentSpaceTest >> testNewPermanentByteArrayIsPermanentObject [
self assert: (memory isPermanentObject: permanentObject)
]

{ #category : #'instance creation' }
VMPermanentSpaceTest >> testNextObjectIsReturningAGoodValue [
{ #category : #'tests - allocation' }
VMPermanentSpaceMemoryTest >> testNextObjectIsReturningAGoodValue [

| permanentObject nextObject |

Expand Down

0 comments on commit cbabe7e

Please sign in to comment.