Skip to content
New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

Improving log of old space limit error reporting #833

Merged
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
13 changes: 8 additions & 5 deletions smalltalksrc/VMMaker/InterpreterPrimitives.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -2017,14 +2017,17 @@ InterpreterPrimitives >> primitiveGreaterThanLargeIntegers [

{ #category : 'memory space primitives' }
InterpreterPrimitives >> primitiveGrowMemoryByAtLeast [

<option: #SpurObjectMemory>
| ammount |
ammount := self stackTop.
(objectMemory isIntegerObject: ammount) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
(objectMemory growOldSpaceByAtLeast: (objectMemory integerValueOf: ammount))
ifNil: [self primitiveFailFor: PrimErrNoMemory]
ifNotNil: [:segSize| self pop: 2 thenPushInteger: segSize]
(objectMemory isIntegerObject: ammount) ifFalse: [
^ self primitiveFailFor: PrimErrBadArgument ].
(objectMemory
growOldSpaceByAtLeast: (objectMemory integerValueOf: ammount)
callingOperation: 'primitiveGrowMemoryByAtLeast - requested by the image')
ifNil: [ self primitiveFailFor: PrimErrNoMemory ]
ifNotNil: [ :segSize | self pop: 2 thenPushInteger: segSize ]
]

{ #category : 'arithmetic integer primitives' }
Expand Down
9 changes: 0 additions & 9 deletions smalltalksrc/VMMaker/Spur32BitMMLECoSimulator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -121,15 +121,6 @@ Spur32BitMMLECoSimulator >> globalGarbageCollect [
^super globalGarbageCollect
]

{ #category : 'growing/shrinking memory' }
Spur32BitMMLECoSimulator >> growOldSpaceByAtLeast: minAmmount [
"Attempt to grow memory by at least minAmmount.
Answer the size of the new segment, or nil if the attempt failed.
Override to not grow during the Spur image bootstrap."
^bootstrapping ifFalse:
[super growOldSpaceByAtLeast: minAmmount]
]

{ #category : 'memory access' }
Spur32BitMMLECoSimulator >> halfWordHighInLong32: long32 [
"Used by Balloon"
Expand Down
9 changes: 0 additions & 9 deletions smalltalksrc/VMMaker/Spur32BitMMLESimulator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -110,15 +110,6 @@ Spur32BitMMLESimulator >> globalGarbageCollect [
^super globalGarbageCollect
]

{ #category : 'growing/shrinking memory' }
Spur32BitMMLESimulator >> growOldSpaceByAtLeast: minAmmount [
"Attempt to grow memory by at least minAmmount.
Answer the size of the new segment, or nil if the attempt failed.
Override to not grow during the Spur image bootstrap."
^bootstrapping ifFalse:
[super growOldSpaceByAtLeast: minAmmount]
]

{ #category : 'memory access' }
Spur32BitMMLESimulator >> halfWordHighInLong32: long32 [
"Used by Balloon"
Expand Down
9 changes: 0 additions & 9 deletions smalltalksrc/VMMaker/Spur64BitMMLECoSimulator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -115,15 +115,6 @@ Spur64BitMMLECoSimulator >> globalGarbageCollect [
^super globalGarbageCollect
]

{ #category : 'growing/shrinking memory' }
Spur64BitMMLECoSimulator >> growOldSpaceByAtLeast: minAmmount [
"Attempt to grow memory by at least minAmmount.
Answer the size of the new segment, or nil if the attempt failed.
Override to not grow during the Spur image bootstrap."
^bootstrapping ifFalse:
[super growOldSpaceByAtLeast: minAmmount]
]

{ #category : 'memory access' }
Spur64BitMMLECoSimulator >> halfWordHighInLong32: long32 [
"Used by Balloon"
Expand Down
9 changes: 0 additions & 9 deletions smalltalksrc/VMMaker/Spur64BitMMLESimulator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -98,15 +98,6 @@ Spur64BitMMLESimulator >> freeLists [
^freeLists
]

{ #category : 'growing/shrinking memory' }
Spur64BitMMLESimulator >> growOldSpaceByAtLeast: minAmmount [
"Attempt to grow memory by at least minAmmount.
Answer the size of the new segment, or nil if the attempt failed.
Override to not grow during the Spur image bootstrap."
^bootstrapping ifFalse:
[super growOldSpaceByAtLeast: minAmmount]
]

{ #category : 'memory access' }
Spur64BitMMLESimulator >> halfWordHighInLong32: long32 [
"Used by Balloon"
Expand Down
69 changes: 41 additions & 28 deletions smalltalksrc/VMMaker/SpurGenerationScavenger.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -341,46 +341,59 @@ SpurGenerationScavenger >> copyToFutureSpace: survivor bytes: bytesInObject [
{ #category : 'scavenger' }
SpurGenerationScavenger >> copyToOldSpace: survivor bytes: bytesInObject format: formatOfSurvivor [
"Copy survivor to oldSpace. Answer the new oop of the object."
<inline: #never> "Should be too infrequent to lower icache density of copyAndForward:"

"Should be too infrequent to lower icache density of copyAndForward:"

<inline: #never>
| nTenures startOfSurvivor newStart newOop growResult |
self assert: (formatOfSurvivor = (manager formatOf: survivor)
and: [((manager isMarked: survivor) not or: [tenureCriterion = MarkOnTenure])
and: [tenureCriterion = TenureToShrinkRT
or: [(manager isPinned: survivor) not
and: [(manager isRemembered: survivor) not]]]]).
self assert: (formatOfSurvivor = (manager formatOf: survivor) and: [
((manager isMarked: survivor) not or: [
tenureCriterion = MarkOnTenure ]) and: [
tenureCriterion = TenureToShrinkRT or: [
(manager isPinned: survivor) not and: [
(manager isRemembered: survivor) not ] ] ] ]).
nTenures := statTenures.
startOfSurvivor := manager startOfObject: survivor.
newStart := manager allocateOldSpaceChunkOfBytes: bytesInObject.
newStart ifNil:
[growResult := manager growOldSpaceByAtLeast: 0. "grow by growHeadroom"
newStart := manager allocateOldSpaceChunkOfBytes: bytesInObject.
newStart ifNil:
[ growResult
ifNil: [ self error: 'Could not allocate new object in the old space. It was not possible to allocate a new memory segment' ]
ifNotNil: [ self error: 'Could not allocate new object in the old space' ]]].

newStart ifNil: [
growResult := manager
growOldSpaceByAtLeast: 0
callingOperation: 'copying objects to OldSpace during GC'. "grow by growHeadroom"
newStart := manager allocateOldSpaceChunkOfBytes: bytesInObject.
newStart ifNil: [
growResult
ifNil: [
self error:
'Could not allocate new object in the old space. It was not possible to allocate a new memory segment' ]
ifNotNil: [
self error: 'Could not allocate new object in the old space' ] ] ].

"manager checkFreeSpace."
manager memcpy: newStart asVoidPointer _: startOfSurvivor asVoidPointer _: bytesInObject.
manager
memcpy: newStart asVoidPointer
_: startOfSurvivor asVoidPointer
_: bytesInObject.
newOop := newStart + (survivor - startOfSurvivor).
tenureCriterion >= (TenureToShrinkRT min: MarkOnTenure) ifTrue:
[tenureCriterion = TenureToShrinkRT ifTrue:
[manager rtRefCountOf: newOop put: 0].
tenureCriterion = MarkOnTenure ifTrue:
[manager setIsMarkedOf: newOop to: true]].
tenureCriterion >= (TenureToShrinkRT min: MarkOnTenure) ifTrue: [
tenureCriterion = TenureToShrinkRT ifTrue: [
manager rtRefCountOf: newOop put: 0 ].
tenureCriterion = MarkOnTenure ifTrue: [
manager setIsMarkedOf: newOop to: true ] ].
statTenures := nTenures + 1.
(manager isAnyPointerFormat: formatOfSurvivor) ifTrue:
["A very quick and dirty scan to find young referents. If we misidentify bytes
(manager isAnyPointerFormat: formatOfSurvivor) ifTrue: [ "A very quick and dirty scan to find young referents. If we misidentify bytes
in a CompiledMethod as young we don't care; it's unlikely, and a subsequent
scan of the rt will filter the object out. But it's good to filter here because
otherwise an attempt to shrink the RT may simply fill it up with new objects,
and here the data is likely in the cache."
manager baseHeaderSize to: bytesInObject - (survivor - startOfSurvivor) - manager wordSize by: manager wordSize do:
[:p| | field |
manager baseHeaderSize to:
bytesInObject - (survivor - startOfSurvivor) - manager wordSize by:
manager wordSize do: [ :p |
| field |
field := manager longAt: survivor + p.
(manager isReallyYoung: field) ifTrue:
[manager getFromOldSpaceRememberedSet remember: newOop.
^newOop]]].
^newOop
(manager isReallyYoung: field) ifTrue: [
manager getFromOldSpaceRememberedSet remember: newOop.
^ newOop ] ] ].
^ newOop
]

{ #category : 'weakness and ephemerality' }
Expand Down
137 changes: 88 additions & 49 deletions smalltalksrc/VMMaker/SpurMemoryManager.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -4685,39 +4685,67 @@ SpurMemoryManager >> ensureRoomOnObjStackAt: objStackRootIndex [
ObjStackNextx. We don't want to shrink objStacks, since they're used
in GC and its good to keep their memory around. So unused pages
created by popping emptying pages are kept on the ObjStackFreex list."

| stackOrNil freeOrNewPage |
stackOrNil := self fetchPointer: objStackRootIndex ofObject: hiddenRootsObj.
(stackOrNil = nilObj
or: [(self fetchPointer: ObjStackTopx ofObject: stackOrNil) >= ObjStackLimit]) ifTrue:
[freeOrNewPage := stackOrNil = nilObj
ifTrue: [0]
ifFalse: [self fetchPointer: ObjStackFreex ofObject: stackOrNil].
freeOrNewPage ~= 0
ifTrue: "the free page list is always on the new page."
[self storePointer: ObjStackFreex ofObjStack: stackOrNil withValue: 0.
self assert: (marking not or: [self isMarked: freeOrNewPage])]
ifFalse:
[freeOrNewPage := self allocateSlotsInOldSpace: ObjStackPageSlots
format: self wordIndexableFormat
classIndex: self wordSizeClassIndexPun.
freeOrNewPage ifNil:
["Allocate a new segment an retry. This is very uncommon. But it happened to me (Clement)."
self growOldSpaceByAtLeast: ObjStackPageSlots.
freeOrNewPage := self allocateSlotsInOldSpace: ObjStackPageSlots
format: self wordIndexableFormat
classIndex: self wordSizeClassIndexPun.
freeOrNewPage ifNil: [self error: 'no memory to allocate or extend obj stack']].
self storePointer: ObjStackFreex ofObjStack: freeOrNewPage withValue: 0.
marking ifTrue: [self setIsMarkedOf: freeOrNewPage to: true]].
self storePointer: ObjStackMyx ofObjStack: freeOrNewPage withValue: objStackRootIndex;
storePointer: ObjStackNextx ofObjStack: freeOrNewPage withValue: (stackOrNil = nilObj ifTrue: [0] ifFalse: [stackOrNil]);
storePointer: ObjStackTopx ofObjStack: freeOrNewPage withValue: 0;
storePointer: objStackRootIndex ofObject: hiddenRootsObj withValue: freeOrNewPage.
self assert: (self isValidObjStackAt: objStackRootIndex).
"Added a new page; now update and answer the relevant cached first page."
stackOrNil := self updateRootOfObjStackAt: objStackRootIndex with: freeOrNewPage].
stackOrNil := self
fetchPointer: objStackRootIndex
ofObject: hiddenRootsObj.
(stackOrNil = nilObj or: [
(self fetchPointer: ObjStackTopx ofObject: stackOrNil)
>= ObjStackLimit ]) ifTrue: [
freeOrNewPage := stackOrNil = nilObj
ifTrue: [ 0 ]
ifFalse: [
self
fetchPointer: ObjStackFreex
ofObject: stackOrNil ].
freeOrNewPage ~= 0
ifTrue: [ "the free page list is always on the new page."
self
storePointer: ObjStackFreex
ofObjStack: stackOrNil
withValue: 0.
self assert: (marking not or: [ self isMarked: freeOrNewPage ]) ]
ifFalse: [
freeOrNewPage := self
allocateSlotsInOldSpace: ObjStackPageSlots
format: self wordIndexableFormat
classIndex: self wordSizeClassIndexPun.
freeOrNewPage ifNil: [ "Allocate a new segment an retry. This is very uncommon. But it happened to me (Clement)."
self
growOldSpaceByAtLeast: ObjStackPageSlots
callingOperation: 'ensuring room on ObjStack'.
freeOrNewPage := self
allocateSlotsInOldSpace: ObjStackPageSlots
format: self wordIndexableFormat
classIndex: self wordSizeClassIndexPun.
freeOrNewPage ifNil: [
self error: 'no memory to allocate or extend obj stack' ] ].
self
storePointer: ObjStackFreex
ofObjStack: freeOrNewPage
withValue: 0.
marking ifTrue: [ self setIsMarkedOf: freeOrNewPage to: true ] ].
self
storePointer: ObjStackMyx
ofObjStack: freeOrNewPage
withValue: objStackRootIndex;
storePointer: ObjStackNextx
ofObjStack: freeOrNewPage
withValue: (stackOrNil = nilObj
ifTrue: [ 0 ]
ifFalse: [ stackOrNil ]);
storePointer: ObjStackTopx ofObjStack: freeOrNewPage withValue: 0;
storePointer: objStackRootIndex
ofObject: hiddenRootsObj
withValue: freeOrNewPage.
self assert: (self isValidObjStackAt: objStackRootIndex).
"Added a new page; now update and answer the relevant cached first page."
stackOrNil := self
updateRootOfObjStackAt: objStackRootIndex
with: freeOrNewPage ].
self assert: (self isValidObjStackAt: objStackRootIndex).
^stackOrNil
^ stackOrNil
]

{ #category : 'interpreter access' }
Expand Down Expand Up @@ -6041,11 +6069,14 @@ SpurMemoryManager >> growHeadroom: aValue [
]

{ #category : 'growing/shrinking memory' }
SpurMemoryManager >> growOldSpaceByAtLeast: minAmmount [
SpurMemoryManager >> growOldSpaceByAtLeast: minAmmount callingOperation: aString [
"Attempt to grow memory by at least minAmmount bytes.
Answer the size of the new segment in bytes, or nil if the attempt failed."
| ammount headroom total start interval |

<var: #segInfo type: #'SpurSegmentInfo *'>
<var: #aString type: #'char *'>

"statGrowMemory counts attempts, not successes."
statGrowMemory := statGrowMemory + 1."we need to include overhead for a new object header plus the segment bridge."
ammount := minAmmount + (self baseHeaderSize * 2 + self bridgeSize).
Expand All @@ -6058,13 +6089,13 @@ SpurMemoryManager >> growOldSpaceByAtLeast: minAmmount [
maxOldSpaceSize > 0 ifTrue:
[total := segmentManager totalBytesInSegments.
total >= maxOldSpaceSize ifTrue:[
self logError: 'Could not allocate more memory. MaxOldSpaceSize reached.'.
self logError: 'Could not allocate more memory while %s. MaxOldSpaceSize reached.' _: aString.
^nil].
headroom := maxOldSpaceSize - total.
headroom < ammount ifTrue:
[headroom < (minAmmount + (self baseHeaderSize * 2 + self bridgeSize)) ifTrue:
[
self logError: 'Required space is bigger than the headroom. Could not allocate'.
self logError: 'Required space is bigger than the headroom while %s. Could not allocate' _: aString.
^nil].
ammount := headroom]].

Expand All @@ -6090,9 +6121,12 @@ SpurMemoryManager >> growToAccomodateContainerWithNumSlots: numSlots [
"Grow memory to accomodate a container (an Array) with numSlots.
Grow by at least the growHeadroom. Supports allInstancesOf: and allObjects.
Answer the size of the new segment in bytes, or nil if the attempt failed."

| delta |
delta := self baseHeaderSize * 2 + (numSlots * self bytesPerOop).
^ self growOldSpaceByAtLeast: (growHeadroom max: delta)
^ self
growOldSpaceByAtLeast: (growHeadroom max: delta)
callingOperation: 'growing to accomodate allObjects / allInstances container'
]

{ #category : 'header access' }
Expand Down Expand Up @@ -8442,13 +8476,15 @@ SpurMemoryManager >> lookupAddress: address [

{ #category : 'free space' }
SpurMemoryManager >> lowSpaceThreshold: threshold [

lowSpaceThreshold := threshold.
"N.B. The threshold > 0 guard eliminates a warning when
self lowSpaceThreshold: 0
is inlined into setSignalLowSpaceFlagAndSaveProcess"
(threshold > 0
and: [totalFreeOldSpace < threshold]) ifTrue:
[self growOldSpaceByAtLeast: threshold - totalFreeOldSpace].
(threshold > 0 and: [ totalFreeOldSpace < threshold ]) ifTrue: [
self
growOldSpaceByAtLeast: threshold - totalFreeOldSpace
callingOperation: 'ensuring enough space after setting lowSpaceThreshold' ].
self assert: totalFreeOldSpace >= lowSpaceThreshold
]

Expand Down Expand Up @@ -12605,17 +12641,20 @@ SpurMemoryManager >> sufficientSpaceAfterGC: numBytes [
| heapSizePostGC |
self assert: numBytes = 0.
self scavengingGCTenuringIf: TenureByAge.
heapSizePostGC := segmentManager totalOldSpaceCapacity - totalFreeOldSpace.
(heapSizePostGC - heapSizeAtPreviousGC) asFloat / heapSizeAtPreviousGC >= heapGrowthToSizeGCRatio ifTrue:
[self fullGC].
[totalFreeOldSpace < growHeadroom
and: [(self growOldSpaceByAtLeast: 0) notNil]] whileTrue:
[totalFreeOldSpace >= growHeadroom ifTrue:
[^true]].
lowSpaceThreshold > totalFreeOldSpace ifTrue: "space is low"
[lowSpaceThreshold := 0. "avoid signalling low space twice"
^false].
^true
heapSizePostGC := segmentManager totalOldSpaceCapacity
- totalFreeOldSpace.
(heapSizePostGC - heapSizeAtPreviousGC) asFloat
/ heapSizeAtPreviousGC >= heapGrowthToSizeGCRatio ifTrue: [
self fullGC ].
[
totalFreeOldSpace < growHeadroom and: [
(self growOldSpaceByAtLeast: 0 callingOperation: 'ensuring sufficient space after GC')
notNil ] ] whileTrue: [
totalFreeOldSpace >= growHeadroom ifTrue: [ ^ true ] ].
lowSpaceThreshold > totalFreeOldSpace ifTrue: [ "space is low"
lowSpaceThreshold := 0. "avoid signalling low space twice"
^ false ].
^ true
]

{ #category : 'allocation' }
Expand Down
16 changes: 10 additions & 6 deletions smalltalksrc/VMMaker/SpurSelectiveCompactor.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -206,18 +206,22 @@ SpurSelectiveCompactor >> findNextSegmentToCompact [
SpurSelectiveCompactor >> findOrAllocateSegmentToFill [
"There was no compacted segments from past GC that we can directly re-use.
We need either to find an empty segment or allocate a new one."

| segIndex |
self findAndSetSegmentToFill.
segmentToFill ifNotNil: [^0].
segmentToFill ifNotNil: [ ^ 0 ].
"No empty segment. We need to allocate a new one"
(manager growOldSpaceByAtLeast: manager growHeadroom) ifNil: ["failed to allocate"^0].
(manager
growOldSpaceByAtLeast: manager growHeadroom
callingOperation: 'finding or allocating segment to fill') ifNil: [ "failed to allocate"
^ 0 ].
"We don't know which segment it is that we've just allocated... So we look for it... This is a bit dumb."
segIndex := self findAndSetSegmentToFill.
"Lilliputian performance hack management... Last lilliputian of new segment is same as prev because no lilliputian in new segment"
self setLastLilliputianChunkAtindex: segIndex to: (self lastLilliputianChunkAtIndex: segIndex - 1).
self assert: segmentToFill ~~ nil.


self
setLastLilliputianChunkAtindex: segIndex
to: (self lastLilliputianChunkAtIndex: segIndex - 1).
self assert: segmentToFill ~~ nil
]

{ #category : 'segment access' }
Expand Down
Loading