Skip to content

Commit

Permalink
Moving state to the memoryMap structure
Browse files Browse the repository at this point in the history
  • Loading branch information
tesonep committed Jan 14, 2022
1 parent 2f14e6b commit 4932ebd
Show file tree
Hide file tree
Showing 12 changed files with 114 additions and 96 deletions.
6 changes: 3 additions & 3 deletions smalltalksrc/VMMaker/Spur32BitCoMemoryManager.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -79,9 +79,9 @@ Spur32BitCoMemoryManager >> checkMemoryMap [
self assert: (self isOldObject: newSpaceStart) not.
self assert: (self isOldObject: newSpaceLimit - self wordSize) not.
self assert: (self isYoungObject: newSpaceLimit) not.
self assert: (self isYoungObject: oldSpaceStart) not.
self assert: (self isYoungObject: memoryMap oldSpaceStart) not.
self assert: (self isYoungObject: endOfMemory) not.
self assert: (self isOldObject: oldSpaceStart).
self assert: (self isOldObject: memoryMap oldSpaceStart).
self assert: (self isOldObject: endOfMemory).

"we would like the following to be true, but we either choose one boundary check for
Expand Down Expand Up @@ -151,7 +151,7 @@ Spur32BitCoMemoryManager >> headerWhileForwardingOf: aCompiledMethodObjOop [
Spur32BitCoMemoryManager >> initializeFreeSpaceForFacadeFrom: base to: limit [
"c.f. initializeFreeSpacePostLoad: freeListObj."
| freeListObj freeBytes |
newSpaceLimit := oldSpaceStart := freeStart := base.
memoryMap oldSpaceStart: (newSpaceLimit := freeStart := base).
endOfMemory := limit.
scavengeThreshold := limit * 3 // 4.
segmentManager initSegmentForInImageCompilationFrom: base to: limit.
Expand Down
6 changes: 3 additions & 3 deletions smalltalksrc/VMMaker/Spur64BitCoMemoryManager.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -79,9 +79,9 @@ Spur64BitCoMemoryManager >> checkMemoryMap [
self assert: (self isOldObject: newSpaceStart) not.
self assert: (self isOldObject: newSpaceLimit - self wordSize) not.
self assert: (self isYoungObject: newSpaceLimit) not.
self assert: (self isYoungObject: oldSpaceStart) not.
self assert: (self isYoungObject: memoryMap oldSpaceStart) not.
self assert: (self isYoungObject: endOfMemory) not.
self assert: (self isOldObject: oldSpaceStart).
self assert: (self isOldObject: memoryMap oldSpaceStart).
self assert: (self isOldObject: endOfMemory).

"we would like the following to be true, but we either choose one boundary check for
Expand Down Expand Up @@ -158,7 +158,7 @@ Spur64BitCoMemoryManager >> headerWhileForwardingOf: aCompiledMethodObjOop [
Spur64BitCoMemoryManager >> initializeFreeSpaceForFacadeFrom: base to: limit [
"c.f. initializeFreeSpacePostLoad: freeListObj."
| freeListObj freeBytes |
newSpaceLimit := oldSpaceStart := freeStart := base.
memoryMap oldSpaceStart: (newSpaceLimit := freeStart := base).
endOfMemory := limit.
scavengeThreshold := limit * 3 // 4.
segmentManager initSegmentForInImageCompilationFrom: base to: limit.
Expand Down
5 changes: 0 additions & 5 deletions smalltalksrc/VMMaker/Spur64BitMMLECoSimulator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -73,11 +73,6 @@ Spur64BitMMLECoSimulator >> coInterpreter: aCoInterpreter cogit: aCogit [
compactor coInterpreter: aCoInterpreter
]

{ #category : #'simulation only' }
Spur64BitMMLECoSimulator >> cogCodeBase [
^ memory initialAddress + Cogit guardPageSize
]

{ #category : #'debug support' }
Spur64BitMMLECoSimulator >> eek [
self halt
Expand Down
14 changes: 0 additions & 14 deletions smalltalksrc/VMMaker/Spur64BitMMLECoSimulatorFor64Bits.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -53,20 +53,6 @@ Spur64BitMMLECoSimulatorFor64Bits >> long32At: byteAddress put: a32BitValue [
^a32BitValue
]

{ #category : #'memory access' }
Spur64BitMMLECoSimulatorFor64Bits >> long64At: byteAddress [
"memory is a DoubleWordArray, a 64-bit indexable array of bits"
byteAddress \\ 8 ~= 0 ifTrue: [self unalignedAccessError].
^memory at: byteAddress // 8 + 1
]

{ #category : #'memory access' }
Spur64BitMMLECoSimulatorFor64Bits >> long64At: byteAddress put: a64BitValue [
"memory is a DoubleWordArray, a 64-bit indexable array of bits"
byteAddress \\ 8 ~= 0 ifTrue: [self unalignedAccessError].
^memory at: byteAddress // 8 + 1 put: a64BitValue
]

{ #category : #simulation }
Spur64BitMMLECoSimulatorFor64Bits >> memoryClass [
"Answer the class to use for the memory inst var in simulation.
Expand Down
14 changes: 0 additions & 14 deletions smalltalksrc/VMMaker/Spur64BitMMLESimulatorFor64Bits.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -56,20 +56,6 @@ Spur64BitMMLESimulatorFor64Bits >> long32At: byteAddress put: a32BitValue [
^a32BitValue
]

{ #category : #'memory access' }
Spur64BitMMLESimulatorFor64Bits >> long64At: byteAddress [
"memory is a DoubleWordArray, a 64-bit indexable array of bits"
byteAddress \\ 8 ~= 0 ifTrue: [self unalignedAccessError].
^memory at: byteAddress // 8 + 1
]

{ #category : #'memory access' }
Spur64BitMMLESimulatorFor64Bits >> long64At: byteAddress put: a64BitValue [
"memory is a DoubleWordArray, a 64-bit indexable array of bits"
byteAddress \\ 8 ~= 0 ifTrue: [self unalignedAccessError].
^memory at: byteAddress // 8 + 1 put: a64BitValue
]

{ #category : #simulation }
Spur64BitMMLESimulatorFor64Bits >> memoryClass [
"Answer the class to use for the memory inst var in simulation.
Expand Down
10 changes: 6 additions & 4 deletions smalltalksrc/VMMaker/SpurImageReader.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,7 @@ SpurImageReader >> loadImageFromFile: f withHeader: header [
interpreter ensureImageFormatIsUpToDate: header swapBytes.

"compute difference between old and new memory base addresses"
bytesToShift := objectMemory oldSpaceStart - header oldBaseAddr.
bytesToShift := objectMemory getMemoryMap oldSpaceStart - header oldBaseAddr.

interpreter initializeInterpreter: bytesToShift "adjusts all oops to new location"
]
Expand Down Expand Up @@ -216,6 +216,8 @@ SpurImageReader >> readImageFromFile: f StartingAt: headerStart [

| header |

objectMemory initializeMemoryMap.

header := self readHeaderFrom: f startingAt: headerStart.

objectMemory specialObjectsOop: header initialSpecialObjectsOop.
Expand Down Expand Up @@ -255,9 +257,9 @@ SpurImageReader >> readSegmentsFromImageFile: f header: aHeader [
"segment sizes include the two-header-word bridge at the end of each segment."
totalBytesRead := 0.
oldBase := aHeader oldBaseAddr.
newBase := objectMemory oldSpaceStart.
newBase := objectMemory getMemoryMap oldSpaceStart.
nextSegmentSize := aHeader firstSegSize.
bridgehead := aHeader firstSegSize + objectMemory oldSpaceStart
bridgehead := aHeader firstSegSize + objectMemory getMemoryMap oldSpaceStart
- objectMemory bridgeSize.

[
Expand Down Expand Up @@ -291,7 +293,7 @@ SpurImageReader >> readSegmentsFromImageFile: f header: aHeader [
bridgehead := bridgehead - objectMemory bridgeSize + nextSegmentSize ].

"newBase should point just past the last bridge. all others should have been eliminated."
self assert: newBase - objectMemory oldSpaceStart = (totalBytesRead
self assert: newBase - objectMemory getMemoryMap oldSpaceStart = (totalBytesRead
- (segmentManager numSegments * objectMemory bridgeSize)).

"Segments has correct swizzle values, so it can be used to swizzle objects"
Expand Down
84 changes: 43 additions & 41 deletions smalltalksrc/VMMaker/SpurMemoryManager.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -547,14 +547,13 @@ Class {
'scavenger',
'segmentManager',
'compactor',
'memory',
'freeStart',
'memoryMap',
'freeOldSpaceStart',
'scavengeThreshold',
'newSpaceStart',
'newSpaceLimit',
'edenBytes',
'oldSpaceStart',
'nilObj',
'falseObj',
'trueObj',
Expand Down Expand Up @@ -656,7 +655,7 @@ Class {
{ #category : #translation }
SpurMemoryManager class >> ancilliaryClasses [
"Answer any extra classes to be included in the translation."
^{ SpurGenerationScavenger. SpurScavengeLogRecord. SpurSegmentManager. SpurSegmentInfo },
^{ SpurGenerationScavenger. SpurScavengeLogRecord. SpurSegmentManager. SpurSegmentInfo. VMMemoryMap },
self compactorClass classesForTranslation,
SpurNewSpaceSpace withAllSubclasses

Expand Down Expand Up @@ -712,8 +711,8 @@ SpurMemoryManager class >> compactorClass [

{ #category : #translation }
SpurMemoryManager class >> declareCVarsIn: aCCodeGenerator [
self declareCAsOop: #( memory freeStart scavengeThreshold newSpaceStart newSpaceLimit pastSpaceStart
lowSpaceThreshold freeOldSpaceStart oldSpaceStart endOfMemory)
self declareCAsOop: #(freeStart scavengeThreshold newSpaceStart newSpaceLimit pastSpaceStart
lowSpaceThreshold freeOldSpaceStart endOfMemory)
in: aCCodeGenerator.
self declareCAsUSqLong: (self allInstVarNames select: [:ivn| ivn endsWith: 'Usecs']), #(statAllocatedBytes)
in: aCCodeGenerator.
Expand All @@ -734,7 +733,10 @@ SpurMemoryManager class >> declareCVarsIn: aCCodeGenerator [
declareC: 'sqInt remapBuffer[RemapBufferSize + 1 /* ', (RemapBufferSize + 1) printString, ' */]'.
aCCodeGenerator
var: #extraRoots
declareC: 'sqInt *extraRoots[ExtraRootsSize + 1 /* ', (ExtraRootsSize + 1) printString, ' */]'
declareC: 'sqInt *extraRoots[ExtraRootsSize + 1 /* ', (ExtraRootsSize + 1) printString, ' */]'.

aCCodeGenerator
var: #memoryMap type: #'VMMemoryMap *'
]

{ #category : #'api characterization' }
Expand Down Expand Up @@ -1390,7 +1392,7 @@ SpurMemoryManager >> adjustAllOopsBy: bytesToShift [
self countNumClassPagesPreSwizzle: bytesToShift.
(bytesToShift ~= 0
or: [segmentManager numSegments > 1]) ifTrue:
[obj := self objectStartingAt: oldSpaceStart.
[obj := self objectStartingAt: memoryMap oldSpaceStart.
[self oop: obj isLessThan: freeOldSpaceStart] whileTrue:
[classIndex := self classIndexOf: obj.
classIndex >= self isForwardedObjectClassIndexPun
Expand Down Expand Up @@ -1984,7 +1986,7 @@ SpurMemoryManager >> allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceByt
initialAddress: initialAddress
]
{ #category : #asd }
{ #category : #initialization }
SpurMemoryManager >> allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceBytes stackSize: stackBytes codeSize: codeBytes methodCacheSize: methodCacheSize primitiveTraceLogSize: primitiveLogSize rumpCStackSize: rumpCStackSize initialAddress: initialAddress [
"Intialize the receiver for bootsraping an image.
Expand All @@ -1993,7 +1995,7 @@ SpurMemoryManager >> allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceByt
will be set to sane values."
<doNotGenerate>
| allocatedMemory newSpaceStartOffset |
| allocatedMemory newSpaceStartOffset allocatedAddress |
self assert: (memoryBytes \\ self allocationUnit = 0 and: [
newSpaceBytes \\ self allocationUnit = 0 and: [
Expand All @@ -2008,14 +2010,17 @@ SpurMemoryManager >> allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceByt
memoryManager := SlangMemoryManager new.
memoryManager wordSize: self wordSize ].
memory := self
allocatedAddress := self
allocateMemoryOfSize: allocatedMemory
initialAddress: initialAddress.
self assert: allocatedAddress = initialAddress.
newSpaceStart := initialAddress + newSpaceStartOffset.
endOfMemory := freeOldSpaceStart := initialAddress + allocatedMemory.
"leave newSpace empty for the bootstrap"
freeStart := newSpaceBytes + newSpaceStart.
oldSpaceStart := newSpaceLimit := newSpaceBytes + newSpaceStart.
memoryMap oldSpaceStart: (newSpaceLimit := newSpaceBytes + newSpaceStart).
scavengeThreshold := allocatedMemory. "i.e. /don't/ scavenge."
scavenger := SpurGenerationScavenger simulatorClass new.
scavenger manager: self.
Expand Down Expand Up @@ -3375,10 +3380,10 @@ SpurMemoryManager >> checkMemoryMap [
self assert: (self isOldObject: newSpaceStart) not.
self assert: (self isOldObject: newSpaceLimit - self wordSize) not.
self assert: (self isYoungObject: newSpaceLimit) not.
self assert: (self isYoungObject: oldSpaceStart) not.
self assert: (self isYoungObject: memoryMap oldSpaceStart) not.
self assert: (self isYoungObject: endOfMemory) not.
self assert: (self isOldObject: newSpaceLimit).
self assert: (self isOldObject: oldSpaceStart).
self assert: (self isOldObject: memoryMap oldSpaceStart).
self assert: (self isOldObject: endOfMemory)
]
Expand Down Expand Up @@ -4186,7 +4191,7 @@ SpurMemoryManager >> countNumClassPagesPreSwizzle: bytesToShift [
"Compute the used size of the class table before swizzling. Needed to
initialize the classTableBitmap which is populated during adjustAllOopsBy:"
| firstObj classTableRoot nilObjPreSwizzle |
firstObj := self objectStartingAt: oldSpaceStart. "a.k.a. nilObj"
firstObj := self objectStartingAt: memoryMap oldSpaceStart. "a.k.a. nilObj"
"first five objects are nilObj, falseObj, trueObj, freeListsObj, classTableRootObj"
classTableRoot := self noInlineObjectAfter:
(self noInlineObjectAfter:
Expand All @@ -4196,7 +4201,7 @@ SpurMemoryManager >> countNumClassPagesPreSwizzle: bytesToShift [
limit: endOfMemory)
limit: endOfMemory)
limit: endOfMemory.
nilObjPreSwizzle := oldSpaceStart - bytesToShift.
nilObjPreSwizzle := memoryMap oldSpaceStart - bytesToShift.
numClassTablePages := self numSlotsOf: classTableRoot.
self assert: numClassTablePages = (self classTableRootSlots + self hiddenRootSlots).
2 to: numClassTablePages - 1 do:
Expand Down Expand Up @@ -4919,7 +4924,7 @@ SpurMemoryManager >> fireAllUnscannedEphemerons [
{ #category : #'object enumeration' }
SpurMemoryManager >> firstAccessibleObject [
<inline: false>
self assert: nilObj = oldSpaceStart.
self assert: nilObj = memoryMap oldSpaceStart.
"flush newSpace to settle the enumeration."
self flushNewSpace.
^nilObj
Expand Down Expand Up @@ -5714,6 +5719,12 @@ SpurMemoryManager >> getMaxOldSpaceSize [
]
{ #category : #accessing }
SpurMemoryManager >> getMemoryMap [
^ memoryMap
]
{ #category : #'simulation only' }
SpurMemoryManager >> getStackPointer [
"hack around the CoInterpreter/ObjectMemory split refactoring"
Expand Down Expand Up @@ -6313,7 +6324,7 @@ SpurMemoryManager >> initialize [
scavenger := SpurGenerationScavenger simulatorClass new manager: self; yourself.
segmentManager := SpurSegmentManager simulatorClass new manager: self; yourself.
compactor := self class compactorClass simulatorClass new manager: self; yourself.
"We can also initialize here anything that is only for simulation."
heapMap := CogCheck32BitHeapMap new.
Expand Down Expand Up @@ -6404,6 +6415,16 @@ 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 @@ -6447,7 +6468,7 @@ SpurMemoryManager >> initializeObjectMemory: bytesToShift [
"In Cog we insist that nil, true & false are next to each other (Cogit generates tighter
conditional branch code as a result). In addition, Spur places the free lists and
class table root page immediately following them."
self assert: nilObj = oldSpaceStart.
self assert: nilObj = memoryMap oldSpaceStart.
self assert: falseObj = (self oldSpaceObjectAfter: nilObj).
self assert: trueObj = (self oldSpaceObjectAfter: falseObj).
freeListObj := self oldSpaceObjectAfter: trueObj.
Expand Down Expand Up @@ -7106,7 +7127,7 @@ SpurMemoryManager >> isInOldSpace: address [
<api>
^self
oop: address
isGreaterThanOrEqualTo: oldSpaceStart
isGreaterThanOrEqualTo: memoryMap oldSpaceStart
andLessThan: endOfMemory
]
Expand Down Expand Up @@ -7299,7 +7320,7 @@ SpurMemoryManager >> isOldObject: objOop [
<api>
"Answer if obj is old. Require that obj is non-immediate."
self assert: (self isNonImmediate: objOop).
^self oop: objOop isGreaterThanOrEqualTo: oldSpaceStart
^self oop: objOop isGreaterThanOrEqualTo: memoryMap oldSpaceStart
]
{ #category : #'object testing' }
Expand Down Expand Up @@ -8510,19 +8531,6 @@ SpurMemoryManager >> memmove: destAddress _: sourceAddress _: bytes [
[:i| self long32At: dst + i put: (self long32At: src + i)]]
]
{ #category : #accessing }
SpurMemoryManager >> memory [
<cmacro: '() GIV(memory)'>
^memory
]
{ #category : #accessing }
SpurMemoryManager >> memory: aValue [
^memory := aValue
]
{ #category : #accessing }
SpurMemoryManager >> memoryActiveProcess [
Expand Down Expand Up @@ -9467,12 +9475,6 @@ SpurMemoryManager >> oldSpaceSize [
^segmentManager totalBytesInSegments
]
{ #category : #accessing }
SpurMemoryManager >> oldSpaceStart [
<cmacro: '() GIV(oldSpaceStart)'>
^oldSpaceStart
]
{ #category : #'become implementation' }
SpurMemoryManager >> outOfPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag [
<inline: #never> "in an effort to fix a compiler bug with two-way become post r3427"
Expand Down Expand Up @@ -10698,7 +10700,7 @@ SpurMemoryManager >> reverseBytesIn32BitWordsIn: segmentWordArray [
{ #category : #snapshot }
SpurMemoryManager >> reverseBytesInMemory [
self reverseBytesFrom: oldSpaceStart to: endOfMemory
self reverseBytesFrom: memoryMap oldSpaceStart to: endOfMemory
]
{ #category : #scavenger }
Expand Down Expand Up @@ -10993,7 +10995,7 @@ SpurMemoryManager >> setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory:
freeStart := scavenger eden start.
pastSpaceStart := scavenger pastSpace start.
oldSpaceStart := newSpaceLimit.
memoryMap oldSpaceStart: newSpaceLimit.
freeOldSpaceStart := memEnd.
endOfMemory := memLimit.
Expand Down

0 comments on commit 4932ebd

Please sign in to comment.