Skip to content

Commit

Permalink
Adding VMMemoryMap configuration
Browse files Browse the repository at this point in the history
  • Loading branch information
tesonep committed Jan 28, 2022
1 parent 1a89716 commit 055008a
Show file tree
Hide file tree
Showing 21 changed files with 378 additions and 263 deletions.
3 changes: 2 additions & 1 deletion smalltalksrc/Slang/CCodeGenerator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -3434,7 +3434,8 @@ CCodeGenerator >> isNode: aNode constantValueWithinRangeOfType: aType [
{ #category : #'C code generator' }
CCodeGenerator >> isNonArgumentImplicitReceiverVariableName: aString [
^ (self typeOfVariable: aString) == #implicit
^ (currentMethod definingClass implicitVariables includes: aString)
or: [ (self typeOfVariable: aString) == #implicit ]
]
{ #category : #'type inference' }
Expand Down
6 changes: 6 additions & 0 deletions smalltalksrc/Slang/SlangClass.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,12 @@ SlangClass class >> defineAtCompileTime: anObject [
^ false
]

{ #category : #translation }
SlangClass class >> implicitVariables [

^ #()
]

{ #category : #translation }
SlangClass class >> isStructClass [
"The various VMStructType classes override this."
Expand Down
2 changes: 1 addition & 1 deletion smalltalksrc/VMMaker/AbstractImageAccess.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -138,7 +138,7 @@ AbstractImageAccess >> interpreter: anObject [
{ #category : #reading }
AbstractImageAccess >> loadHeaderToMemory: header [

objectMemory initializeMemoryMap.
objectMemory createMemoryMap.

objectMemory specialObjectsOop: header initialSpecialObjectsOop.
objectMemory lastHash: header hdrLastHash.
Expand Down
19 changes: 8 additions & 11 deletions smalltalksrc/VMMaker/CoInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -683,37 +683,34 @@ CoInterpreter >> allocateJITMemory: desiredSize _: desiredPosition [
CoInterpreter >> allocateMemoryForImage: f withHeader: header [

<var: #f type: #sqImageFile>
<var: #header type: #'SpurImageHeaderStruct'>

<var: #header type: #SpurImageHeaderStruct>
| cogCodeBase desiredPositionOfHeap |

cogCodeSize := desiredCogCodeSize ~= 0
ifTrue: [ desiredCogCodeSize ]
ifFalse: [
header hdrCogCodeSize = 0
ifTrue: [ cogit defaultCogCodeSize ]
ifFalse: [ header hdrCogCodeSize ] ].

cogCodeSize := cogCodeSize min: cogit maxCogCodeSize.

cogCodeBase := self
allocateJITMemory: cogCodeSize
desiredPosition: header oldBaseAddr - cogCodeSize.

"We want to avoid the swizzle in case the allocation of the code space is much below in the address space than the requested one"
desiredPositionOfHeap := cogCodeBase + cogCodeSize max: header oldBaseAddr.
desiredPositionOfHeap := cogCodeBase + cogCodeSize max:
header oldBaseAddr.

self allocateMemoryForImageHeader: header desiredStartingAddress: desiredPositionOfHeap.

self allocateHeapMemoryForImage: f withHeader: header desiredStartingAddress: desiredPositionOfHeap.

imageReader loadImageFromFile: f withHeader: header.

self beforeCodeZoneInitialization.

cogit
initializeCodeZoneFrom: cogCodeBase
upTo: cogCodeBase + cogCodeSize.


upTo: cogCodeBase + cogCodeSize
]

{ #category : #'cog jit support' }
Expand Down
5 changes: 0 additions & 5 deletions smalltalksrc/VMMaker/CogVMSimulator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1283,11 +1283,6 @@ CogVMSimulator >> instVar: index ofContext: aMarriedContext put: anOop [
^super instVar: index ofContext: aMarriedContext put: anOop
]

{ #category : #'interpreter shell' }
CogVMSimulator >> insufficientMemoryAvailableError [
self error: 'Failed to allocate memory for the heap'
]

{ #category : #'interpreter shell' }
CogVMSimulator >> insufficientMemorySpecifiedError [
self error: 'Insufficient memory for this image'
Expand Down
4 changes: 2 additions & 2 deletions smalltalksrc/VMMaker/ComposedImageWriter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,8 @@ ComposedImageWriter >> writeImageSegments: imageFileName [

| total |
self assert:
(objectMemory endOfMemory = segmentManager lastSegment segLimit
or: [ objectMemory endOfMemory + objectMemory bridgeSize = segmentManager lastSegment segLimit ]).
(objectMemory getMemoryMap oldSpaceEnd = segmentManager lastSegment segLimit
or: [ objectMemory getMemoryMap oldSpaceEnd + objectMemory bridgeSize = segmentManager lastSegment segLimit ]).

self assert: segmentManager firstSegmentBytes > 0.

Expand Down
26 changes: 0 additions & 26 deletions smalltalksrc/VMMaker/Spur32BitCoMemoryManager.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -147,32 +147,6 @@ Spur32BitCoMemoryManager >> headerWhileForwardingOf: aCompiledMethodObjOop [
^self baseHeader: aCompiledMethodObjOop
]

{ #category : #'simulation only' }
Spur32BitCoMemoryManager >> initializeFreeSpaceForFacadeFrom: base to: limit [
"c.f. initializeFreeSpacePostLoad: freeListObj."
| freeListObj freeBytes |

memoryMap newSpaceEnd: (freeStart := base).
memoryMap oldSpaceStart: memoryMap newSpaceEnd.
memoryMap oldSpaceEnd: limit.

scavengeThreshold := limit * 3 // 4.
segmentManager initSegmentForInImageCompilationFrom: base to: limit.
freeListObj := self allocateSlots: self numFreeLists
format: self wordIndexableFormat
classIndex: self wordSizeClassIndexPun.
freeLists := self firstIndexableField: freeListObj.
freeListsMask := 0.
0 to: self numFreeLists - 1 do:
[:i|
(freeLists at: i) ~= 0 ifTrue:
[freeListsMask := freeListsMask bitOr: (1 << i).
freeLists at: i put: (segmentManager swizzleObj: (freeLists at: i))]].
freeBytes := segmentManager lastSegment segLimit - self bridgeSize - freeStart.
freeLists at: 0 put: (self initFreeChunkWithBytes: freeBytes at: freeStart).
totalFreeOldSpace := freeBytes
]

{ #category : #'class table' }
Spur32BitCoMemoryManager >> isForwardedClassIndex: maybeClassIndex [
"A lenient tester of forwarded class indices for inline cache management in the Cogit."
Expand Down
13 changes: 2 additions & 11 deletions smalltalksrc/VMMaker/Spur32BitMMLECoSimulator.class.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
Class {
#name : #Spur32BitMMLECoSimulator,
#superclass : #Spur32BitCoMemoryManager,
#traits : 'TVMSpurMemoryManagerSimulator',
#classTraits : 'TVMSpurMemoryManagerSimulator classTrait',
#instVars : [
'parent',
'bootstrapping'
Expand Down Expand Up @@ -344,17 +346,6 @@ Spur32BitMMLECoSimulator >> setIsMarkedOf: objOop to: aBoolean [
[self halt]"
]

{ #category : #'debug support' }
Spur32BitMMLECoSimulator >> setUpForUseByFacade: aCurrentImageCoInterpreterFacade [
"Make sure that eden etc are initialized, so that methods can be printed.
This is really to make addressCouldBeObj: et al work."
<doNotGenerate>
self edenBytes: 0.
self setHeapBase: self freeStart
memoryLimit: memoryMap oldSpaceEnd
endOfMemory: memoryMap oldSpaceEnd
]

{ #category : #'memory access' }
Spur32BitMMLECoSimulator >> shortAt: byteAddress [
"Return the half-word at byteAddress which must be even."
Expand Down
2 changes: 2 additions & 0 deletions smalltalksrc/VMMaker/Spur32BitMMLESimulator.class.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
Class {
#name : #Spur32BitMMLESimulator,
#superclass : #Spur32BitMemoryManager,
#traits : 'TVMSpurMemoryManagerSimulator',
#classTraits : 'TVMSpurMemoryManagerSimulator classTrait',
#instVars : [
'parent',
'bootstrapping'
Expand Down
35 changes: 0 additions & 35 deletions smalltalksrc/VMMaker/Spur64BitCoMemoryManager.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -154,30 +154,6 @@ Spur64BitCoMemoryManager >> headerWhileForwardingOf: aCompiledMethodObjOop [
^self baseHeader: aCompiledMethodObjOop
]

{ #category : #'simulation only' }
Spur64BitCoMemoryManager >> initializeFreeSpaceForFacadeFrom: base to: limit [
"c.f. initializeFreeSpacePostLoad: freeListObj."
| freeListObj freeBytes |
memoryMap newSpaceEnd: (freeStart := base).
memoryMap oldSpaceStart: memoryMap newSpaceEnd.
memoryMap oldSpaceEnd: limit.
scavengeThreshold := limit * 3 // 4.
segmentManager initSegmentForInImageCompilationFrom: base to: limit.
freeListObj := self allocateSlots: self numFreeLists
format: self wordIndexableFormat
classIndex: self wordSizeClassIndexPun.
freeLists := self firstIndexableField: freeListObj.
freeListsMask := 0.
0 to: self numFreeLists - 1 do:
[:i|
(freeLists at: i) ~= 0 ifTrue:
[freeListsMask := freeListsMask bitOr: (1 << i).
freeLists at: i put: (segmentManager swizzleObj: (freeLists at: i))]].
freeBytes := segmentManager lastSegment segLimit - self bridgeSize - freeStart.
freeLists at: 0 put: (self initFreeChunkWithBytes: freeBytes at: freeStart).
totalFreeOldSpace := freeBytes
]

{ #category : #'class table' }
Spur64BitCoMemoryManager >> isForwardedClassIndex: maybeClassIndex [
"A lenient tester of forwarded class indices for inline cache management in the Cogit."
Expand Down Expand Up @@ -296,17 +272,6 @@ Spur64BitCoMemoryManager >> scavengeThresholdAddress [
inSmalltalk: [cogit simulatedReadWriteVariableAddress: #getScavengeThreshold in: self]
]

{ #category : #'debug support' }
Spur64BitCoMemoryManager >> setUpForUseByFacade: aCurrentImageCoInterpreterFacade [
"Make sure that eden etc are initialized, so that methods can be printed.
This is really to make addressCouldBeObj: et al work."
<doNotGenerate>
self edenBytes: 0.
self setHeapBase: self freeStart
memoryLimit: memoryMap oldSpaceEnd
endOfMemory: memoryMap oldSpaceEnd
]

{ #category : #'trampoline support' }
Spur64BitCoMemoryManager >> specialObjectsArrayAddress [
<api>
Expand Down
2 changes: 2 additions & 0 deletions smalltalksrc/VMMaker/Spur64BitMMLECoSimulator.class.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
Class {
#name : #Spur64BitMMLECoSimulator,
#superclass : #Spur64BitCoMemoryManager,
#traits : 'TVMSpurMemoryManagerSimulator',
#classTraits : 'TVMSpurMemoryManagerSimulator classTrait',
#instVars : [
'parent',
'bootstrapping'
Expand Down
2 changes: 2 additions & 0 deletions smalltalksrc/VMMaker/Spur64BitMMLESimulator.class.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
Class {
#name : #Spur64BitMMLESimulator,
#superclass : #Spur64BitMemoryManager,
#traits : 'TVMSpurMemoryManagerSimulator',
#classTraits : 'TVMSpurMemoryManagerSimulator classTrait',
#instVars : [
'parent',
'bootstrapping'
Expand Down
107 changes: 31 additions & 76 deletions smalltalksrc/VMMaker/SpurMemoryManager.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -652,7 +652,8 @@ Class {
{ #category : #translation }
SpurMemoryManager class >> ancilliaryClasses [
"Answer any extra classes to be included in the translation."
^{ SpurGenerationScavenger. SpurScavengeLogRecord. SpurSegmentManager. SpurSegmentInfo. VMMemoryMap },
^{ SpurGenerationScavenger. SpurScavengeLogRecord. SpurSegmentManager. SpurSegmentInfo. VMMemoryMap.
VMMemoryMapConfiguration. VMMemoryMapConfiguration forWordsize: self objectMemoryClass wordSize },
self compactorClass classesForTranslation,
SpurNewSpaceSpace withAllSubclasses

Expand Down Expand Up @@ -1948,41 +1949,6 @@ SpurMemoryManager >> allocateMemoryOfSize: memoryBytes initialAddress: initialAd
^ memoryManager allocate: memoryBytes desiredPosition: initialAddress
]
{ #category : #'spur bootstrap' }
SpurMemoryManager >> allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceBytes stackSize: stackBytes codeSize: codeBytes [
"Intialize the receiver for bootsraping an image.
Set up a large oldSpace and an empty newSpace and set-up freeStart and scavengeThreshold
to allocate in oldSpace. Later on (in initializePostBootstrap) freeStart and scavengeThreshold
will be set to sane values."
<doNotGenerate>
self
allocateMemoryOfSize: memoryBytes
newSpaceSize: newSpaceBytes
stackSize: stackBytes
codeSize: codeBytes
initialAddress: 0
]
{ #category : #'spur bootstrap' }
SpurMemoryManager >> allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceBytes stackSize: stackBytes codeSize: codeBytes initialAddress: initialAddress [
"Intialize the receiver for bootsraping an image.
Set up a large oldSpace and an empty newSpace and set-up freeStart and scavengeThreshold
to allocate in oldSpace. Later on (in initializePostBootstrap) freeStart and scavengeThreshold
will be set to sane values."
<doNotGenerate>
self
allocateMemoryOfSize: memoryBytes
newSpaceSize: newSpaceBytes
stackSize: stackBytes
codeSize: codeBytes
methodCacheSize: 0
primitiveTraceLogSize: 0
rumpCStackSize: 0
initialAddress: initialAddress
]
{ #category : #initialization }
SpurMemoryManager >> allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceBytes stackSize: stackBytes codeSize: codeBytes methodCacheSize: methodCacheSize primitiveTraceLogSize: primitiveLogSize rumpCStackSize: rumpCStackSize initialAddress: initialAddress [
Expand Down Expand Up @@ -4203,6 +4169,18 @@ SpurMemoryManager >> countNumClassPagesPreSwizzle: bytesToShift [
]
{ #category : #initialization }
SpurMemoryManager >> createMemoryMap [
self
cCode: [ memoryMap := self cCoerce: (self malloc: (self sizeof: VMMemoryMap)) to: #'VMMemoryMap *']
inSmalltalk: [
memoryMap := VMMemoryMap new.
memoryMap memoryManager: memoryManager ].
memoryMap initializeMemoryMap.
]
{ #category : #'allocation accounting' }
SpurMemoryManager >> currentAllocatedBytes [
"Compute the current allocated bytes since last set.
Expand Down Expand Up @@ -6374,6 +6352,23 @@ SpurMemoryManager >> initializeFreeSpacePostLoad: freeListObj [
freeLists at: i put: (segmentManager swizzleObj: (freeLists at: i))]]
]
{ #category : #snapshot }
SpurMemoryManager >> initializeFromMemoryMap [
| reserve |
reserve := coInterpreter interpreterAllocationReserveBytes.
scavenger newSpaceStart: memoryMap newSpaceStart
newSpaceBytes: memoryMap newSpaceEnd - memoryMap newSpaceStart
survivorBytes: memoryMap newSpaceEnd - memoryMap newSpaceStart - reserve // self scavengerDenominator.
freeStart := scavenger eden start.
pastSpaceStart := scavenger pastSpace start.
freeOldSpaceStart := memoryMap oldSpaceEnd.
]
{ #category : #allocation }
SpurMemoryManager >> initializeHeaderOfStartAddress: startAddress numSlots: numSlots format: formatField classIndex: classIndex pinned: isPinned [
Expand All @@ -6397,16 +6392,6 @@ SpurMemoryManager >> initializeMarkStack [
self ensureRoomOnObjStackAt: MarkStackRootIndex
]
{ #category : #initialization }
SpurMemoryManager >> initializeMemoryMap [
self
cCode: [ memoryMap := self cCoerce: (self malloc: (self sizeof: VMMemoryMap)) to: #'VMMemoryMap *']
inSmalltalk: [
memoryMap := VMMemoryMap new.
memoryMap memoryManager: memoryManager ]
]
{ #category : #'gc - scavenging' }
SpurMemoryManager >> initializeNewSpaceVariables [
<inline: #never>
Expand Down Expand Up @@ -10942,36 +10927,6 @@ SpurMemoryManager >> setHashBitsOf: objOop to: hash [
put: ((self long32At: objOop + 4) bitClear: self identityHashHalfWordMask) + hash
]
{ #category : #snapshot }
SpurMemoryManager >> setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd [
"Set the dimensions of the heap, answering the start of oldSpace. edenBytes holds the desired ``size of eden''
which is actually the total size of new space minus the reserve. edenBytes is then divided up between eden
and the two survivor spaces, where each survivor space is a scavengerDenominator (one seventh) of the total."
"Transcript
cr; nextPutAll: 'heapBase: '; print: baseOfHeap; nextPut: $/; nextPutAll: baseOfHeap hex;
nextPutAll: ' memLimit '; print: memLimit; nextPut: $/; nextPutAll: memLimit hex;
nextPutAll: ' memEnd '; print: memEnd; nextPut: $/; nextPutAll: memEnd hex; cr; flush."
"This is more than a little counter-intuitive. Eden must include interpreterAllocationReserveBytes."
<inline: #never>
| reserve |
reserve := coInterpreter interpreterAllocationReserveBytes.
memoryMap newSpaceStart: baseOfHeap.
memoryMap newSpaceEnd: baseOfHeap + edenBytes + reserve.
scavenger newSpaceStart: memoryMap newSpaceStart
newSpaceBytes: memoryMap newSpaceEnd - memoryMap newSpaceStart
survivorBytes: memoryMap newSpaceEnd - memoryMap newSpaceStart - reserve // self scavengerDenominator.
freeStart := scavenger eden start.
pastSpaceStart := scavenger pastSpace start.
memoryMap oldSpaceStart: memoryMap newSpaceEnd.
freeOldSpaceStart := memEnd.
memoryMap oldSpaceEnd: memLimit.
^baseOfHeap
]
{ #category : #accessing }
SpurMemoryManager >> setHeapGrowthToSizeGCRatio: aDouble [
<var: #aDouble type: #double>
Expand Down

0 comments on commit 055008a

Please sign in to comment.