VM Maker: VMMaker.oscog-eem.2819.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker.oscog-eem.2819.mcz

commits-2
 
Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2819.mcz

==================== Summary ====================

Name: VMMaker.oscog-eem.2819
Author: eem
Time: 24 September 2020, 11:00:39.141595 pm
UUID: 0d2e74ed-d411-42ae-a202-d2ca9865a0ad
Ancestors: VMMaker.oscog-eem.2818

Spur: Bridging new and old space.

Dela with the issue of pastSpace being just a 64-bit word shy of eden.  This needs a one word bridge, which is not somehting the system is designed for at all.  However, we can hack one in to a special enumerator used only for the bridged new and old spae enumerators, objectAfterMaybeSlimBridge:limit:. hackSlimBridgeTo:at: creates a one word overflow header recognised by objectAfterMaybeSlimBridge:limit:.  The slkim bridge overflow header has a slot count of either 0 or 1.  And so, placed in the last word of past space it is able to point either to the first word of eden (the first object in eden having a one word header) or to the second word of eden (the first object in eden having an overflow header).

Avoid recursion in assert checking by adding objectInPastSpaceBefore: which is used only to locate the object before a slim bridge.

Slim bridge is a pun, a return to my youth: https://www.wwt.org.uk/wetland-centres/slimbridge#

=============== Diff against VMMaker.oscog-eem.2818 ===============

Item was added:
+ ----- Method: Spur32BitMemoryManager>>hackSlimBridgeTo:at: (in category 'object enumeration-private') -----
+ hackSlimBridgeTo: firstEdenObject at: lastWordInPastSpace
+ "This is a horrible hack for getting to the first object in eden if pastSpace is almost full.
+ If there is only one (64-bit) word at the end of pastSpace there is no room for a full
+ bridge, but there is room for this hack."
+ self flag: #endianness.
+ self assert: lastWordInPastSpace = pastSpaceStart.
+ self assert: lastWordInPastSpace + self baseHeaderSize = scavenger eden start.
+ self longAt: lastWordInPastSpace
+ put: (firstEdenObject = scavenger eden start ifTrue: [0] ifFalse: [1]).
+ self longAt: lastWordInPastSpace + 4 put: self numSlotsMask << self numSlotsHalfShift!

Item was changed:
+ ----- Method: Spur32BitMemoryManager>>initSegmentBridgeWithBytes:at: (in category 'object enumeration') -----
- ----- Method: Spur32BitMemoryManager>>initSegmentBridgeWithBytes:at: (in category 'segments') -----
  initSegmentBridgeWithBytes: numBytes at: address
  <var: #numBytes type: #usqLong>
  | numSlots |
  "Must have room for a double header or a short object with the forwarding slot (16 bytes either way)."
  self assert: (numBytes \\ self allocationUnit = 0
  and: [numBytes >= (self baseHeaderSize + self baseHeaderSize)]).
  numSlots := numBytes - self baseHeaderSize - self baseHeaderSize >> self shiftForWord.
  self flag: #endianness.
  numSlots = 0
  ifTrue: "short bridge for adjacent segments"
  [self longAt: address put: (1 << self pinnedBitShift)
  + (self wordIndexableFormat << self formatShift)
  + self segmentBridgePun;
  longAt: address + 4 put: (1 << self markedBitHalfShift)]
  ifFalse: "long bridge"
  [self longAt: address put: numSlots;
  longAt: address + 4 put: self numSlotsMask << self numSlotsHalfShift;
  longAt: address + 8 put: (1 << self pinnedBitShift)
  + (self wordIndexableFormat << self formatShift)
  + self segmentBridgePun;
  longAt: address + 12 put: self numSlotsMask << self numSlotsHalfShift
  + (1 << self markedBitHalfShift)]!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>objectAfterMaybeSlimBridge:limit: (in category 'object enumeration-private') -----
+ objectAfterMaybeSlimBridge: objOop limit: limit
+ "Object parsing.
+ 1. all objects have at least a word following the header, for a forwarding pointer.
+ 2. objects with an overflow size have a preceding word with a saturated numSlots.  If the word
+   following an object doesn't have a saturated numSlots field it must be a single-header object.
+   If the word following does have a saturated numSlots it must be the overflow size word.
+ This variation on objectAfter:limit: allows for a single (64-bit) word bridge which may be needed
+ to bridge from an almost full pastSpace to eden.  It is ony used in the flat enumerators that use
+ startAddressForBridgedHeapEnumeration and enumerate over pastSpace, eden and oldSpace
+ in that order.  Note that the order for allObjects, and allInstances enumerates over oldSpace first.
+
+ This hack is cheap.  It increases the size of the objectAfter code, but saves two extra copies of
+ the inner loop, since the inner loop now enumerates over all of pastSpace, eden and oldSpace.
+ The test for a slim bridge is only performed if applied to an overflow header, and typically only
+ 1 in 400 objects have overflow headers in 32-bits, 1 in 500 in 64-bits."
+ <inline: true>
+ | followingWordAddress followingWord |
+ followingWordAddress := self addressAfter: objOop.
+ (self oop: followingWordAddress isGreaterThanOrEqualTo: limit) ifTrue:
+ [^limit].
+ self flag: #endianness.
+ followingWord := self longAt: followingWordAddress + 4.
+ ^followingWord >> self numSlotsHalfShift = self numSlotsMask
+ ifTrue: [1 = (self longAt: followingWordAddress) "i.e. the raw overflow slots in the overflow word"
+ ifTrue: [followingWordAddress + self baseHeaderSize + self baseHeaderSize]
+ ifFalse: [followingWordAddress + self baseHeaderSize]]
+ ifFalse: [followingWordAddress]!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>hackSlimBridgeTo:at: (in category 'object enumeration-private') -----
+ hackSlimBridgeTo: firstEdenObject at: lastWordInPastSpace
+ "This is a horrible hack for getting to the first object in eden if pastSpace is almost full.
+ If there is only one (64-bit) word at the end of pastSpace there is no room for a full
+ bridge, but there is room for this hack."
+ self assert: lastWordInPastSpace = pastSpaceStart.
+ self assert: lastWordInPastSpace + self baseHeaderSize = scavenger eden start.
+ self longAt: lastWordInPastSpace
+ put: (firstEdenObject = scavenger eden start
+ ifTrue: [self numSlotsMask << self numSlotsFullShift]
+ ifFalse: [self numSlotsMask << self numSlotsFullShift + 1])!

Item was changed:
+ ----- Method: Spur64BitMemoryManager>>initSegmentBridgeWithBytes:at: (in category 'object enumeration') -----
- ----- Method: Spur64BitMemoryManager>>initSegmentBridgeWithBytes:at: (in category 'segments') -----
  initSegmentBridgeWithBytes: numBytes at: address
  <var: #numBytes type: #usqLong>
  | numSlots |
  "Must have room for a double header or a short object with the forwarding slot (16 bytes either way)."
  self assert: (numBytes \\ self allocationUnit = 0
  and: [numBytes >= (self baseHeaderSize + self baseHeaderSize)]).
  numSlots := numBytes - self baseHeaderSize - self baseHeaderSize >> self shiftForWord.
  numSlots = 0
  ifTrue: "short bridge for adjacent segments"
  [self longAt: address
  put:    (1 << self pinnedBitShift)
  + (1 << self markedBitFullShift)
  + (self wordIndexableFormat << self formatShift)
  + self segmentBridgePun]
  ifFalse: "long bridge"
  [self longAt: address
  put: self numSlotsMask << self numSlotsFullShift + numSlots;
  longAt: address + self baseHeaderSize
  put: (self numSlotsMask << self numSlotsFullShift)
  + (1 << self pinnedBitShift)
  + (1 << self markedBitFullShift)
  + (self wordIndexableFormat << self formatShift)
  + self segmentBridgePun]!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>objectAfterMaybeSlimBridge:limit: (in category 'object enumeration-private') -----
+ objectAfterMaybeSlimBridge: objOop limit: limit
+ "Object parsing.
+ 1. all objects have at least a word following the header, for a forwarding pointer.
+ 2. objects with an overflow size have a preceding word with a saturated numSlots.  If the word
+   following an object doesn't have a saturated numSlots field it must be a single-header object.
+   If the word following does have a saturated numSlots it must be the overflow size word.
+ This variation on objectAfter:limit: allows for a single (64-bit) word bridge which may be needed
+ to bridge from an almost full pastSpace to eden.  It is ony used in the flat enumerators that use
+ startAddressForBridgedHeapEnumeration and enumerate over pastSpace, eden and oldSpace
+ in that order.  Note that the order for allObjects, and allInstances enumerates over oldSpace first.
+
+ This hack is cheap.  It increases the size of the objectAfter code, but saves two extra copies of
+ the inner loop, since the inner loop now enumerates over all of pastSpace, eden and oldSpace.
+ The test for a slim bridge is only performed if applied to an overflow header, and typically only
+ 1 in 400 objects have overflow headers in 32-bits, 1 in 500 in 64-bits."
+ <inline: true>
+ | followingWordAddress followingWord |
+ followingWordAddress := self addressAfter: objOop.
+ (self oop: followingWordAddress isGreaterThanOrEqualTo: limit) ifTrue:
+ [^limit].
+ self flag: #endianness.
+ followingWord := self longAt: followingWordAddress.
+ ^followingWord >> self numSlotsFullShift = self numSlotsMask
+ ifTrue:
+ [(followingWord bitAnd: 16rFFFFFFFFFFFFFF) = 1
+ ifTrue: [followingWordAddress + self baseHeaderSize + self baseHeaderSize]
+ ifFalse: [followingWordAddress + self baseHeaderSize]]
+ ifFalse: [followingWordAddress]!

Item was changed:
  ----- Method: SpurMemoryManager>>allEntitiesFrom:do: (in category 'object enumeration-private') -----
  allEntitiesFrom: initialObject do: aBlock
  <inline: true>
  | prevObj prevPrevObj objOop |
  prevPrevObj := prevObj := nil.
  objOop := initialObject.
  self enableObjectEnumerationFrom: initialObject.
  [self assert: objOop \\ self allocationUnit = 0.
  self oop: objOop isLessThan: endOfMemory] whileTrue:
  [self assert: (self long64At: objOop) ~= 0.
  aBlock value: objOop.
  prevPrevObj := prevObj.
  prevObj := objOop.
+ objOop := self objectAfterMaybeSlimBridge: objOop limit: endOfMemory].
- objOop := self objectAfter: objOop limit: endOfMemory].
  self touch: prevPrevObj.
  self touch: prevObj!

Item was changed:
  ----- Method: SpurMemoryManager>>allNewSpaceEntitiesDo: (in category 'object enumeration-private') -----
  allNewSpaceEntitiesDo: aBlock
  "Enumerate all new space objects, including free objects."
  <inline: true>
  | start prevObj prevPrevObj objOop |
  prevPrevObj := prevObj := nil.
  "After a scavenge eden is empty, futureSpace is empty, and all newSpace objects are
   in pastSpace.  Objects are allocated in eden.  So enumerate only pastSpace and eden."
  self assert: (scavenger pastSpace start < scavenger eden start).
  start := self startAddressForBridgedHeapEnumeration.
  start > freeStart ifTrue: [^self].
+ self bridgePastSpaceAndEden.
- self initSegmentBridgeWithBytes: scavenger eden start - pastSpaceStart at: pastSpaceStart.
  objOop := self objectStartingAt: start.
  [self oop: objOop isLessThan: freeStart] whileTrue:
  [aBlock value: objOop.
  prevPrevObj := prevObj.
  prevObj := objOop.
  objOop := self objectAfter: objOop limit: freeStart].
  self touch: prevPrevObj.
  self touch: prevObj!

Item was added:
+ ----- Method: SpurMemoryManager>>bridgeEdenAndOldSpace (in category 'object enumeration-private') -----
+ bridgeEdenAndOldSpace
+ <inline: #always>
+ self initSegmentBridgeWithBytes: oldSpaceStart - freeStart at: freeStart!

Item was added:
+ ----- Method: SpurMemoryManager>>bridgePastSpaceAndEden (in category 'object enumeration-private') -----
+ bridgePastSpaceAndEden
+ <inline: #always>
+ pastSpaceStart < scavenger eden start ifTrue: "past space can be entirely full (!!!!)"
+ [pastSpaceStart + self baseHeaderSize = scavenger eden start
+ ifTrue: "No room for a full bridge (!!!!); use the slim bridge hack"
+ [self hackSlimBridgeTo: (self objectStartingAt: scavenger eden start) at: pastSpaceStart.
+ "And carefully check the assumption"
+ self assert: (self objectAfterMaybeSlimBridge: (self objectInPastSpaceBefore: pastSpaceStart) limit: nilObj)
+ = (self objectStartingAt: scavenger eden start)]
+ ifFalse: "Room for a regular bridge; this is straight-forward"
+ [self initSegmentBridgeWithBytes: scavenger eden start - pastSpaceStart at: pastSpaceStart]]!

Item was added:
+ ----- Method: SpurMemoryManager>>bridgePastSpaceAndOldSpace (in category 'object enumeration-private') -----
+ bridgePastSpaceAndOldSpace
+ <inline: #always>
+ self initSegmentBridgeWithBytes: oldSpaceStart - pastSpaceStart at: pastSpaceStart!

Item was changed:
  ----- Method: SpurMemoryManager>>enableObjectEnumerationFrom: (in category 'object enumeration-private') -----
  enableObjectEnumerationFrom: initialObject
  "We use bridges to stitch segments together to make it appear that the heap is one contiguous space.
  Bridges at the end of oldSpace segments are maintained.  Bridges at the end of pastSpace and eden
+ are temporary, and are established here, depending on the current sizes of pastSpace end eden.
+
+ N.B. this introduces complications.  Either or both pastSpace and eden may be empty, so the
+ bridge from pastSpace may skip eden.  pastSpace may be full, so there may be no bridge at
+ the end of pastSpace.  Most difficult, pastSpace could be one 64-bit word short of full, but normal
+ bridges are two word objects.  To make this work we introduce a hack, objectAfterMaybeSlimBridge:limit:,
+ which uses a fake overflow slot count to get to the start of the next object, which is either one or two
+ words away, depending on whether the first object in eden has a normal or an overflow header."
- are temporary, and are established here, depending on the current sizes of pastSpace end eden."
  <inline: false>
  (self oop: initialObject isLessThan: oldSpaceStart) ifTrue:
  [freeStart > scavenger eden start
  ifTrue:
+ [self bridgeEdenAndOldSpace.
+ self bridgePastSpaceAndEden]
+ ifFalse: "If eden is empty (e.g. at snapshot time), skip it entirely"
+ [self bridgePastSpaceAndOldSpace]]!
- [self initSegmentBridgeWithBytes: oldSpaceStart - freeStart at: freeStart.
- pastSpaceStart < scavenger eden start ifTrue: "past space can be entirely full (!!!!)"
- [self initSegmentBridgeWithBytes: scavenger eden start - pastSpaceStart at: pastSpaceStart]]
- ifFalse:"If eden is empty (e.g. at snapshot time), skip it entirely"
- [self initSegmentBridgeWithBytes: oldSpaceStart - pastSpaceStart at: pastSpaceStart]]!

Item was added:
+ ----- Method: SpurMemoryManager>>hackSlimBridgeTo:at: (in category 'object enumeration-private') -----
+ hackSlimBridgeTo: firstEdenObject at: lastWordInPastSpace
+ "This is a horrible hack for getting to the first object in eden if pastSpace is almost full.
+ If there is only one (64-bit) word at the end of pastSpace there is no room for a full
+ bridge, but there is room for this hack."
+ self subclassResponsibility!

Item was added:
+ ----- Method: SpurMemoryManager>>objectAfterMaybeSlimBridge:limit: (in category 'object enumeration-private') -----
+ objectAfterMaybeSlimBridge: objOop limit: limit
+ "Object parsing.
+ 1. all objects have at least a word following the header, for a forwarding pointer.
+ 2. objects with an overflow size have a preceding word with a saturated numSlots.  If the word
+   following an object doesn't have a saturated numSlots field it must be a single-header object.
+   If the word following does have a saturated numSlots it must be the overflow size word.
+ This variation on objectAfter:limit: allows for a single (64-bit) word bridge which may be needed
+ to bridge from an almost full pastSpace to eden.  It is ony used in the flat enumerators that use
+ startAddressForBridgedHeapEnumeration and enumerate over pastSpace, eden and oldSpace
+ in that order.  Note that the order for allObjects, and allInstances enumerates over oldSpace first.
+
+ This hack is cheap.  It increases the size of the objectAfter code, but saves two extra copies of
+ the inner loop, since the inner loop now enumerates over all of pastSpace, eden and oldSpace.
+ The test for a slim bridge is only performed if applied to an overflow header, and typically only
+ 1 in 400 objects have overflow headers in 32-bits, 1 in 500 in 64-bits."
+ ^self subclassResponsibility!

Item was added:
+ ----- Method: SpurMemoryManager>>objectInPastSpaceBefore: (in category 'object enumeration') -----
+ objectInPastSpaceBefore: objOop
+ "For assertions only... This ends the recursion in setting up the bridged
+ enumerations of new space that need objectBefore: for assertion checking."
+ | prev obj |
+ pastSpaceStart <= scavenger pastSpace start ifTrue:
+ [^nil].
+ prev := nil.
+ obj := self objectStartingAt: scavenger pastSpace start.
+ [self oop: obj isLessThan: pastSpaceStart] whileTrue:
+ [(self oop: obj isGreaterThanOrEqualTo: objOop) ifTrue:
+ [^prev].
+ prev := obj.
+ obj := self objectAfter: obj limit: pastSpaceStart].
+ ^prev!