Skip to content

Commit

Permalink
Fixing tests to correctly use the memory map of the VM
Browse files Browse the repository at this point in the history
  • Loading branch information
tesonep committed Apr 29, 2022
1 parent e76b5fa commit 0c18ab1
Show file tree
Hide file tree
Showing 21 changed files with 217 additions and 139 deletions.
2 changes: 1 addition & 1 deletion smalltalksrc/Slang/SlangMemoryManager.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -207,7 +207,7 @@ SlangMemoryManager >> regionsDo: aFullBlockClosure [
{ #category : #allocating }
SlangMemoryManager >> registerNewRegion: newMemoryRegion size: desiredSize address: allocatedAddress [

allocatedAddress to: allocatedAddress + desiredSize by: self pageSize do: [
allocatedAddress to: (allocatedAddress + desiredSize - 1) by: self pageSize do: [
:pageAddress | "Index regions by the high bits of the address"
memoryMap at: pageAddress >> 12 put: newMemoryRegion ]
]
Expand Down
1 change: 1 addition & 0 deletions smalltalksrc/VMMaker/Cogit.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -7993,6 +7993,7 @@ Cogit >> generateCogMethod: selector [
<returnTypeC: #'CogMethod *'>
| codeSize headerSize mapSize totalSize startAddress result method |
<var: #method type: #'CogMethod *'>
headerSize := self sizeof: CogMethod.
methodLabel address: methodZone freeStart.
self computeMaximumSizes.
Expand Down
42 changes: 16 additions & 26 deletions smalltalksrc/VMMaker/SpurMemoryManager.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1979,56 +1979,46 @@ SpurMemoryManager >> allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceByt
will be set to sane values."
<doNotGenerate>
| allocatedMemory newSpaceStartOffset allocatedAddress vmMemoryConf |
| vmMemoryConf |
self assert: (memoryBytes \\ self allocationUnit = 0 and: [
newSpaceBytes \\ self allocationUnit = 0 and: [
codeBytes \\ self allocationUnit = 0 and: [
initialAddress \\ self allocationUnit = 0 ] ] ]).
newSpaceStartOffset := codeBytes + stackBytes
+ methodCacheSize + primitiveLogSize
+ rumpCStackSize.
allocatedMemory := newSpaceStartOffset + newSpaceBytes + memoryBytes.
memoryManager ifNil: [
memoryManager := SlangMemoryManager new.
memoryManager wordSize: self wordSize ].
allocatedAddress := self
allocateMemoryOfSize: allocatedMemory
initialAddress: initialAddress.
self assert: allocatedAddress = initialAddress.
coInterpreter movePrimTraceLogToMemoryAt: (memoryManager allocate: primitiveLogSize).
memoryMap
allocationReserve: coInterpreter interpreterAllocationReserveBytes;
initialOldSpaceSize: memoryBytes;
initialNewSpaceSize: newSpaceBytes;
initialHeadroom: 0;
initialCodeZoneSize: codeBytes;
initialPermSpaceSize: permSpaceSize;
allocateHeap.
memoryMap newSpaceStart: initialAddress + newSpaceStartOffset.
memoryMap newSpaceEnd: newSpaceBytes + memoryMap newSpaceStart.
memoryMap oldSpaceStart: memoryMap newSpaceEnd.
memoryMap setOldSpaceEnd: (freeOldSpaceStart := initialAddress + allocatedMemory).
"leave newSpace empty for the bootstrap"
freeStart := newSpaceBytes + memoryMap newSpaceStart.
scavengeThreshold := allocatedMemory. "i.e. /don't/ scavenge."
scavengeThreshold := memoryMap newSpaceStart.
scavenger := SpurGenerationScavenger simulatorClass new.
scavenger manager: self.
scavenger rememberedSet: newSpaceRememberedSet.
scavenger
newSpaceStart: memoryMap newSpaceStart
newSpaceBytes: newSpaceBytes
survivorBytes: newSpaceBytes // self scavengerDenominator.
compactor := self class compactorClass simulatorClass new
manager: self;
yourself.
vmMemoryConf := (VMMemoryMapConfiguration forWordsize: self wordSize) new.
permSpaceSize isZero
ifTrue: [
memoryMap permSpaceStart: vmMemoryConf permSpaceInitialAddress.
memoryMap permSpaceEnd: vmMemoryConf permSpaceInitialAddress]
ifFalse: [
memoryMap permSpaceStart: (self allocateMemoryOfSize: permSpaceSize initialAddress: vmMemoryConf permSpaceInitialAddress).
memoryMap permSpaceEnd: memoryMap permSpaceStart + permSpaceSize ].
permSpaceFreeStart := memoryMap permSpaceStart
]
Expand Down Expand Up @@ -6572,7 +6562,7 @@ SpurMemoryManager >> initializeOldSpaceFirstFree: startOfFreeOldSpace [
SpurMemoryManager >> initializePostBootstrap [
"The heap has just been bootstrapped into a modified newSpace occupying all of memory
above newSpace (and the codeZone). Put things back to some kind of normalcy."
freeOldSpaceStart := freeStart.
freeOldSpaceStart := self getMemoryMap oldSpaceStart.
freeStart := scavenger eden start.
pastSpaceStart := scavenger pastSpace start.
scavengeThreshold := scavenger eden limit
Expand Down
75 changes: 64 additions & 11 deletions smalltalksrc/VMMaker/VMMemoryMap.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,8 @@ Class {
'stackPagesEnd',
'initialPermSpaceSize',
'minPermSpaceSize',
'objectMemory'
'objectMemory',
'spaceMaskToUse'
],
#pools : [
'VMBasicConstants'
Expand Down Expand Up @@ -78,6 +79,11 @@ VMMemoryMap >> allocateCodeZone [
initialCodeZoneSize = 0 ifTrue: [ ^ self ].
self codeZoneStart: (self allocateJITMemory: initialCodeZoneSize _: memoryMapConfiguration codeZoneInitialAddress).
self codeZoneStart ifNil: [ self insufficientMemoryAvailableError ].

self codeZoneStart = memoryMapConfiguration codeZoneInitialAddress
ifFalse: [
self logError: 'Could not allocate codeZone in the expected place (%p), got %p' _: self codeZoneStart _: memoryMapConfiguration codeZoneInitialAddress.
self error: 'Error allocating' ].

self codeZoneEnd: codeZoneStart + initialCodeZoneSize.
]
Expand Down Expand Up @@ -117,6 +123,11 @@ VMMemoryMap >> allocateNewObjectsSpace [

self newSpaceStart ifNil: [ self insufficientMemoryAvailableError ].

self newSpaceStart = memoryMapConfiguration newSpaceInitialAddress
ifFalse: [
self logError: 'Could not allocate newSpace in the expected place (%p), got %p' _: self newSpaceStart _: memoryMapConfiguration newSpaceInitialAddress.
self error: 'Error allocating' ].

self newSpaceEnd: self newSpaceStart + newSpaceSizeToAllocate.
]

Expand All @@ -131,6 +142,13 @@ VMMemoryMap >> allocateOldObjectsSpace [

self oldSpaceStart ifNil: [ self insufficientMemoryAvailableError ].

self oldSpaceStart = memoryMapConfiguration oldSpaceInitialAddress
ifFalse: [
self logError: 'Could not allocate oldSpace in the expected place (%p), got %p' _: self oldSpaceStart _: memoryMapConfiguration oldSpaceInitialAddress.
self error: 'Error allocating' ].

self oldSpaceMask: (self oldSpaceStart bitAnd: self spaceMaskToUse).

self setOldSpaceEnd: self oldSpaceStart + sizeToAllocate
]

Expand All @@ -150,6 +168,11 @@ VMMemoryMap >> allocatePermObjectsSpace [

self permSpaceStart ifNil: [ self insufficientMemoryAvailableError ].

self permSpaceStart = memoryMapConfiguration permSpaceInitialAddress
ifFalse: [
self logError: 'Could not allocate permSpace in the expected place (%p), got %p' _: self permSpaceStart _: memoryMapConfiguration permSpaceInitialAddress.
self error: 'Error allocating' ].

self permSpaceEnd: self permSpaceStart + minSize.
objectMemory setPermSpaceFreeStart: self permSpaceStart
]
Expand Down Expand Up @@ -182,6 +205,11 @@ VMMemoryMap >> allocateStackPages: initialStackSize [

self stackPagesStart ifNil: [ self insufficientMemoryAvailableError ].

self stackPagesStart = memoryMapConfiguration stackPagesInitialAddress
ifFalse: [
self logError: 'Could not allocate stack in the expected place (%p), got %p' _: self stackPagesStart _: memoryMapConfiguration stackPagesInitialAddress.
self error: 'Error allocating' ].

self stackPagesEnd: self stackPagesStart + sizeToRequest.

self memset: self stackPagesStart _: 0 _: sizeToRequest.
Expand Down Expand Up @@ -233,15 +261,15 @@ VMMemoryMap >> codeZoneStart: anInteger [
VMMemoryMap >> doCheckMemoryMap [

self assert: (self isYoungObject: self newSpaceStart).
self assert: (self isYoungObject: self newSpaceEnd - memoryMapConfiguration wordSize).
self assert: (self isYoungObject: self newSpaceEnd - memoryMapConfiguration confWordSize).
self assert: (self isOldObject: self newSpaceStart) not.
self assert: (self isOldObject: self newSpaceEnd - memoryMapConfiguration wordSize) not.
self assert: (self isOldObject: self newSpaceEnd - memoryMapConfiguration confWordSize) not.
self assert: (self isYoungObject: self newSpaceEnd) not.
self assert: (self isYoungObject: self oldSpaceStart) not.
self assert: (self isYoungObject: self oldSpaceEnd) not.
self assert: (self isOldObject: self oldSpaceStart).
self assert: (self isOldObject: self oldSpaceEnd - memoryMapConfiguration wordSize).
self assert: (self isOldObject: self oldSpaceEnd) not.
self assert: (self isOldObject: self oldSpaceEnd - memoryMapConfiguration confWordSize).
self assert: (self isOldObject: self oldSpaceEnd).

]

Expand Down Expand Up @@ -367,9 +395,11 @@ VMMemoryMap >> initializeMemoryMap [
permSpaceStart := 0.
permSpaceEnd := 0.

self cCode: [ ] inSmalltalk: [
self simulationOnly: [
memoryMapConfiguration := (VMMemoryMapConfiguration forWordsize:
self class objectMemoryClass wordSize) new ]
self class objectMemoryClass wordSize) new ].

spaceMaskToUse := memoryMapConfiguration calculateMaskToUse.
]

{ #category : #private }
Expand All @@ -381,11 +411,10 @@ VMMemoryMap >> insufficientMemoryAvailableError [

{ #category : #'testing objects' }
VMMemoryMap >> isOldObject: anOop [

<api>
self flag:#todo.
"^ anOop allMask: oldSpaceMask "
^ oldSpaceStart <= anOop and: [ anOop < oldSpaceEnd ]

^ anOop allMask: oldSpaceMask
]

{ #category : #'testing objects' }
Expand Down Expand Up @@ -423,7 +452,7 @@ VMMemoryMap >> memset: startAddress _: value _: size [

<doNotGenerate>

startAddress to: startAddress + size - 1 by: memoryMapConfiguration wordSize do: [ :address |
startAddress to: startAddress + size - 1 by: memoryMapConfiguration confWordSize do: [ :address |
memoryManager longAt: address put: value ]

]
Expand Down Expand Up @@ -476,6 +505,18 @@ VMMemoryMap >> oldSpaceEnd [
^ oldSpaceEnd
]

{ #category : #accessing }
VMMemoryMap >> oldSpaceMask [

^ oldSpaceMask
]

{ #category : #accessing }
VMMemoryMap >> oldSpaceMask: anObject [

oldSpaceMask := anObject
]

{ #category : #accessing }
VMMemoryMap >> oldSpaceStart [

Expand Down Expand Up @@ -544,6 +585,18 @@ VMMemoryMap >> setOldSpaceEnd: anInteger [

]

{ #category : #accessing }
VMMemoryMap >> spaceMaskToUse [

^ spaceMaskToUse
]

{ #category : #accessing }
VMMemoryMap >> spaceMaskToUse: anObject [

spaceMaskToUse := anObject
]

{ #category : #accessing }
VMMemoryMap >> stackPagesEnd [

Expand Down
31 changes: 25 additions & 6 deletions smalltalksrc/VMMaker/VMMemoryMapConfiguration.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -18,12 +18,37 @@ VMMemoryMapConfiguration class >> isAbstract [
^ self == VMMemoryMapConfiguration
]

{ #category : #'initial addresses' }
VMMemoryMapConfiguration >> calculateMaskToUse [

| newSpaceFirst newSpaceLast newSpaceMask oldSpaceFirst oldSpaceLast oldSpaceMask maskToUse |

newSpaceFirst := self newSpaceInitialAddress.
newSpaceLast := self oldSpaceInitialAddress - 1.
newSpaceMask := (newSpaceLast - newSpaceFirst) bitXor: (1 << (self confWordSize * 8)) - 1.

oldSpaceFirst := self oldSpaceInitialAddress.
oldSpaceLast := self permSpaceInitialAddress - 1.
oldSpaceMask := (oldSpaceLast - oldSpaceFirst) bitXor: (1 << (self confWordSize * 8)) - 1.

maskToUse := newSpaceMask bitAnd: oldSpaceMask.
maskToUse = 0 ifTrue: [ self error: 'Could not calculate mask to use to identify new/old/perm objects' ].

^ maskToUse
]

{ #category : #'initial addresses' }
VMMemoryMapConfiguration >> codeZoneInitialAddress [

^ self subclassResponsibility
]

{ #category : #accessing }
VMMemoryMapConfiguration >> confWordSize [

^ self subclassResponsibility
]

{ #category : #'initial addresses' }
VMMemoryMapConfiguration >> newSpaceInitialAddress [

Expand All @@ -47,9 +72,3 @@ VMMemoryMapConfiguration >> stackPagesInitialAddress [

^ self subclassResponsibility
]

{ #category : #accessing }
VMMemoryMapConfiguration >> wordSize [

^ self subclassResponsibility
]
14 changes: 8 additions & 6 deletions smalltalksrc/VMMaker/VMMemoryMapConfigurationFor32Bits.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,14 @@ VMMemoryMapConfigurationFor32Bits >> codeZoneInitialAddress [
^ 16r10000000 "(256 MB)"
]

{ #category : #accessing }
VMMemoryMapConfigurationFor32Bits >> confWordSize [

<inline: true>

^ 4
]

{ #category : #'initial addresses' }
VMMemoryMapConfigurationFor32Bits >> newSpaceInitialAddress [

Expand All @@ -33,9 +41,3 @@ VMMemoryMapConfigurationFor32Bits >> stackPagesInitialAddress [

^ 16r0F000000 "(240 MB)"
]

{ #category : #accessing }
VMMemoryMapConfigurationFor32Bits >> wordSize [
<doNotGenerate>
^ 4
]
24 changes: 13 additions & 11 deletions smalltalksrc/VMMaker/VMMemoryMapConfigurationFor64Bits.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -7,23 +7,31 @@ Class {
{ #category : #'initial addresses' }
VMMemoryMapConfigurationFor64Bits >> codeZoneInitialAddress [

self cppIf: WIN32 ifTrue: [ ^ 16r440000000 "17GB" ].
"self cppIf: WIN32 ifTrue: [ ^ 16r440000000 ""17GB"" ]."

^ 16r240000000 "9GB"
]

{ #category : #accessing }
VMMemoryMapConfigurationFor64Bits >> confWordSize [

<inline: true>

^ 8
]

{ #category : #'initial addresses' }
VMMemoryMapConfigurationFor64Bits >> newSpaceInitialAddress [

self cppIf: WIN32 ifTrue: [ ^ 16r480000000 "18GB" ].

" self cppIf: WIN32 ifTrue: [ ^ 16r480000000 ""18GB"" ]."
^ 16r280000000 "10GB"
]

{ #category : #'initial addresses' }
VMMemoryMapConfigurationFor64Bits >> oldSpaceInitialAddress [

self cppIf: WIN32 ifTrue: [ ^ 16r4C0000000 "19GB" ].
"self cppIf: WIN32 ifTrue: [ ^ 16r4C0000000 ""19GB"" ]."

^ 16r10000000000 "1024GB"
]
Expand All @@ -37,13 +45,7 @@ VMMemoryMapConfigurationFor64Bits >> permSpaceInitialAddress [
{ #category : #'initial addresses' }
VMMemoryMapConfigurationFor64Bits >> stackPagesInitialAddress [

self cppIf: WIN32 ifTrue: [ ^ 16r400000000 "16GB" ].
"self cppIf: WIN32 ifTrue: [ ^ 16r400000000 ""16GB"" ]."

^ 16r200000000 "8GB"
]

{ #category : #accessing }
VMMemoryMapConfigurationFor64Bits >> wordSize [
<doNotGenerate>
^ 8
]

0 comments on commit 0c18ab1

Please sign in to comment.