[Vm-dev] VM Maker: VMMaker.oscog-eem.3187.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jun 9 19:11:47 UTC 2022


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

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

Name: VMMaker.oscog-eem.3187
Author: eem
Time: 9 June 2022, 12:11:34.381091 pm
UUID: 409db813-9691-40ab-8d5b-8960d3b50fbc
Ancestors: VMMaker.oscog-eem.3186

A little less inlining does you good. Don't inline allocateSlots:format:classIndex: in low-frequency primitives.

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

Item was changed:
  ----- Method: SpurMemoryManager>>allocateBytes:classIndex: (in category 'allocation') -----
  allocateBytes: numBytes classIndex: classIndex
  	"Allocate an object of numBytes.  Answer nil if no available memory.
  	 classIndex must be that of a byte class (e.g. ByteString).
  	 The object is *NOT FILLED*."
  	<var: #numBytes type: #usqInt>
+ 	<inline: #always>
  	self assert: (coInterpreter addressCouldBeClassObj: (self classAtIndex: classIndex)).
  	self assert: (self instSpecOfClass: (self classAtIndex: classIndex)) = self firstByteFormat.
  	^self
+ 		noInlineAllocateSlots: (numBytes + self bytesPerOop - 1 // self bytesPerOop)
- 		allocateSlots: (numBytes + self bytesPerOop - 1 // self bytesPerOop)
  		format: (self byteFormatForNumBytes: numBytes)
  		classIndex: classIndex!

Item was changed:
  ----- Method: SpurMemoryManager>>loadImageSegmentFrom:outPointers: (in category 'image segment in/out') -----
  loadImageSegmentFrom: segmentWordArray outPointers: outPointerArray
  	"This primitive is called from Smalltalk as...
  		<imageSegment> loadSegmentFrom: aWordArray outPointers: anArray."
  
  	"This primitive will load a binary image segment created by primitiveStoreImageSegment.
  	 It expects the outPointer array to be of the proper size, and the wordArray to be well formed.
  	 It will return as its value the original array of roots, and the segmentWordArray will become an
  	 array of the loaded objects.  If this primitive should fail, the segmentWordArray will, sadly, have
  	 been reduced to an unrecognizable and unusable jumble.  But what more could you have done
  	 with it anyway?
  
  	 The primitive, if it succeeds, also becomes the segmentWordArray into the array of loaded objects.
  	 This allows fixing up of loaded objects directly, without nextObject, which Spur doesn't support."
  
  	<inline: #never>
  	| segmentLimit segmentStart segVersion errorCode numLoadedObjects loadedObjectsArray |
  
  	segmentLimit := self numSlotsOf: segmentWordArray.
  	(self objectBytesForSlots: segmentLimit) < (self allocationUnit "version info" + self baseHeaderSize "one object header") ifTrue:
  		[^PrimErrBadArgument halt].
  
  	"Verify format.  If the format is wrong, word-swap (since ImageSegment data are 32-bit longs).
  	 If it is still wrong, undo the damage and fail."
  	segVersion := self longAt: segmentWordArray + self baseHeaderSize.
  	(coInterpreter readableFormat: (segVersion bitAnd: 16rFFFFFF "low 3 bytes")) ifFalse:
  		[self reverseBytesIn32BitWordsIn: segmentWordArray.
  		 segVersion := self longAt: segmentWordArray + self baseHeaderSize.
  		 (coInterpreter readableFormat: (segVersion bitAnd: 16rFFFFFF "low 3 bytes")) ifFalse:
  			[self reverseBytesIn32BitWordsIn: segmentWordArray.
  			 ^PrimErrBadArgument halt]].
  
  	segmentStart := segmentWordArray + self baseHeaderSize + self allocationUnit.
  	segmentLimit := segmentLimit * self bytesPerOop + segmentWordArray + self baseHeaderSize.
  
  	"Notionally reverse the Byte type objects if the data is from opposite endian machine.
  	 Test top byte.  $d on the Mac or $s on the PC.  Rest of word is equal.  If Spur is ever
  	 ported to big-endian machines then the segment may have to be byte/word swapped,
  	 but so far it only runs on little-endian machines, so for now just fail if endianness is wrong."
  	self flag: #endianness.
  	(segVersion >> 24 bitAnd: 16rFF) ~= (self imageSegmentVersion >> 24 bitAnd: 16rFF) ifTrue:
  		"Reverse the byte-type objects once"
  		[true
  			ifTrue: [^PrimErrBadArgument halt]
  			ifFalse:
  				[self byteSwapByteObjectsFrom: (self objectStartingAt: segmentStart)
  					to: segmentLimit
  					flipFloatsIf: false]].
  
  	"Avoid having to remember by arranging that there are no young outPointers if segment is in old space."
  	(self isOldObject: segmentWordArray) ifTrue:
  		[errorCode := self ensureNoNewObjectsIn: outPointerArray.
  		 errorCode ~= 0 ifTrue:
  			[^errorCode]].
  
  	"scan through mapping oops and validating class references. Defer entering any
  	 class objects into the class table and/or pinning objects until a second pass."
  	errorCode := self mapOopsAndValidateClassRefsFrom: segmentStart to: segmentLimit outPointers: outPointerArray.
  	errorCode > 0 ifTrue:
  		[^errorCode].
  	numLoadedObjects := errorCode negated.
+ 	loadedObjectsArray := self noInlineAllocateSlots: numLoadedObjects format: self arrayFormat classIndex: ClassArrayCompactIndex.
- 	loadedObjectsArray := self allocateSlots: numLoadedObjects format: self arrayFormat classIndex: ClassArrayCompactIndex.
  	loadedObjectsArray ifNil:
  		[self growOldSpaceByAtLeast: (self largeObjectBytesForSlots: numLoadedObjects).
+ 		 loadedObjectsArray := self noInlineAllocateSlots: numLoadedObjects format: self arrayFormat classIndex: ClassArrayCompactIndex.
- 		 loadedObjectsArray := self allocateSlots: numLoadedObjects format: self arrayFormat classIndex: ClassArrayCompactIndex.
  		 loadedObjectsArray ifNil:
  			[^PrimErrNoMemory halt]].
  
  	"Scan for classes contained in the segment, entering them into the class table.
  	 Classes are at the front, after the root array and have the remembered bit set."
  	errorCode := self enterClassesIntoClassTableFrom: segmentStart to: segmentLimit.
  	errorCode ~= 0 ifTrue:
  		[^errorCode].
  
  	"Make a final pass, assigning class indices and/or pinning pinned objects and collecting the loaded objects in loadedObjectsArray"
  	self assignClassIndicesAndPinFrom: segmentStart to: segmentLimit outPointers: outPointerArray filling: loadedObjectsArray.
  
  	"Evaporate the container, leaving the newly loaded objects in place."
  	(self hasOverflowHeader: segmentWordArray)
  		ifTrue: "N.B. setting the overflow slots to 1 creates a slimbridge in eden, so we also need to delete the overflow slot count in the segment itself"
  			[(self oop: segmentWordArray isLessThan: oldSpaceStart)
  				ifTrue:
  					[self rawOverflowSlotsOf: segmentWordArray put: 0.
  					 self rawNumSlotsOf: segmentWordArray put: 0]
  				ifFalse:
  					[self rawOverflowSlotsOf: segmentWordArray put: self allocationUnit / self bytesPerOop]]
  		ifFalse: [self rawNumSlotsOf: segmentWordArray put: self allocationUnit / self bytesPerOop].
  
  	"Finally forward the segmentWordArray to the loadedObjectsArray"
  	self forward: segmentWordArray to: loadedObjectsArray.
  	
  	self runLeakCheckerFor: GCCheckImageSegment.
  
  	"Answer the first object in the segment because this is what primitiveLoadImageSegment tests for,
  	 even though the real result is the segmentWordArray forwarded to the loadedObjectsArray."
  	^self objectStartingAt: segmentStart!

Item was added:
+ ----- Method: SpurMemoryManager>>noInlineAllocateSlots:format:classIndex: (in category 'allocation') -----
+ noInlineAllocateSlots: numSlots format: formatField classIndex: classIndex
+ 	"Allocate an object with numSlots space.  If there is room beneath scavengeThreshold
+ 	 allocate in newSpace, otherwise alocate in oldSpace.  If there is not room in newSpace
+ 	 and a scavenge is not already scheduled, schedule a scavenge."
+ 	<inline: #never>
+ 	^self allocateSlots: numSlots format: formatField classIndex: classIndex!

Item was changed:
  ----- Method: SpurMemoryManager>>storeImageSegmentInto:outPointers:roots: (in category 'image segment in/out') -----
  storeImageSegmentInto: segmentWordArrayArg outPointers: outPointerArrayArg roots: arrayOfRootsArg
  	"This primitive is called from Squeak as...
  		<imageSegment> storeSegmentFor: arrayOfRoots into: aWordArray outPointers: anArray.
  
  	 This primitive will store a binary image segment (in the same format as objects in the heap) of the
  	 set of objects in arrayOfObjects.  All pointers from within the set to objects outside the set will be
  	 copied into the array of outPointers.  In their place in the image segment will be an oop equal to the
  	 offset in the outPointer array (the first would be 8), but with the high bit set.
  
  	 Since Spur has a class table the load primitive must insert classes that have instances into the
  	 class table.  This primitive marks such classes using the isRemembered bit, which isn't meaningful
  	 as a remembered bit in the segment.
  
  	 The primitive expects the segmentWordArray and outPointerArray to be more than adequately long.
  	 In this case it returns normally, and truncates the two arrays to exactly the right size.
  
  	 The primitive can fail for the following reasons with the specified failure codes:
  		PrimErrGenericError:		the segmentWordArray is too small for the version stamp
  		PrimErrWritePastObject:	the segmentWordArray is too small to contain the reachable objects
  		PrimErrBadIndex:			the outPointerArray is too small
  		PrimErrNoMemory:			additional allocations failed
  		PrimErrLimitExceeded:		there is no room in the hash field to store out pointer indices or class references."
  	<inline: false>
  	| segmentWordArray outPointerArray arrayOfRoots
  	  arrayOfObjects savedFirstFields savedOutHashes segStart segAddr endSeg outIndex numClassesInSegment |
  	<var: 'segAddr' type: #usqInt>
  	((self isObjImmutable: segmentWordArrayArg)
  	 or: [self isObjImmutable: outPointerArrayArg]) ifTrue:
  		[^PrimErrNoModification].
  	"Since segmentWordArrayArg & outPointerArrayArg may get shortened, they can't be pinned."
  	((self isPinned: segmentWordArrayArg)
  	 or: [self isPinned: outPointerArrayArg]) ifTrue:
  		[^PrimErrObjectIsPinned].
  	(self numSlotsOf: outPointerArrayArg) > self maxIdentityHash ifTrue:
  		[^PrimErrLimitExceeded].
  
  	self runLeakCheckerFor: GCCheckImageSegment.
  
  	"First scavenge to collect any new space garbage that refers to the graph."
  	self scavengingGC.
  	segmentWordArray := self updatePostScavenge: segmentWordArrayArg.
  	outPointerArray := self updatePostScavenge: outPointerArrayArg.
  	arrayOfRoots := self updatePostScavenge: arrayOfRootsArg.
  	self deny: (self forwardersIn: outPointerArray).
  	self deny: (self forwardersIn: arrayOfRoots).
  	
  	"Now compute the transitive closure, collecting the sequence of objects to be stored in the arrayOfObjects array.
  	 Included in arrayOfObjects are the arrayOfRoots and all its contents.  All objects have been unmarked."
  	arrayOfObjects := self objectsReachableFromRoots: arrayOfRoots.
  	arrayOfObjects ifNil:
  		[^PrimErrNoMemory].
  	"If objectsReachableFromRoots: answers an integer there is not enough continuous free space in which to allocate the
  	 reachable objects.  If there is sufficient free space then answer an error code to prompt a compacting GC and a retry."
  	(self isIntegerObject: arrayOfObjects) ifTrue:
  		[totalFreeOldSpace - self allocationUnit >= (self integerValueOf: arrayOfObjects) ifTrue:
  			[^PrimErrNeedCompaction].
  		 ^PrimErrNoMemory].
  
  	self assert: self allObjectsUnmarked. "work to be done when the incremental GC is written"
  	self deny: (self forwardersIn: arrayOfObjects).
  
  	"Both to expand the max size of segment and to reduce the length of the
  	 load-time pass that adds classes to the class table, move classes to the
  	 front of arrayOfObjects, leaving the root array as the first element."
  	numClassesInSegment := self moveClassesForwardsIn: arrayOfObjects.
  
  	"The scheme is to copy the objects into segmentWordArray, and then map the oops in segmentWordArray.
  	 Therefore the primitive needs to both map efficiently originals to copies in segmentWordArray and
  	 be able to undo any side-effects if the primitive fails because either segmentWordArray or outPointerArray
  	 is too small.  The mapping is done by having the objects to be stored in arrayOfObjects refer to their mapped
  	 locations through their first field, just like a forwarding pointer, but without becoming a forwarder, saving their
  	 first field in savedFirstFields, and the objects in outPointerArray pointing to their locations in the outPointerArray
  	 through their identityHashes, saved in savedOutHashes.
  	 Since arrayOfObjects and its savedFirstFields, and outPointerArray and its saved hashes, can be enumerated
  	 side-by-side, the hashes can be restored to the originals.  So the first field of the heap object corresponding to
  	 an object in arrayOfObjects is set to its location in segmentWordArray, and the hash of an object in outPointerArray
  	 is set to its index in outPointerArray plus the top hash bit.  Classes in arrayOfObjects have their marked bit set.
  	 Oops in objects in segmentWordArray are therefore mapped by accessing the original oop, and following its first
  	 field. Class indices in segmentWordArray are mapped by fetching the original class, and testing its marked bit.
  	 If marked, the first field is followed to access the class copy in the segment.  Out pointers (objects and classes,
  	 which are unmarked), the object's identityHash is set (eek!!!!) to its index in the outPointerArray. So savedOutHashes
  	 parallels the outPointerArray. The saved hash array is initialized with an out-of-range hash value so that the first
  	 unused entry can be identified."
  
+ 	savedFirstFields := self noInlineAllocateSlots: (self numSlotsOf: arrayOfObjects)
- 	savedFirstFields := self allocateSlots: (self numSlotsOf: arrayOfObjects)
  							format: self wordIndexableFormat
  							classIndex: self wordSizeClassIndexPun.
+ 	savedOutHashes := self noInlineAllocateSlots: (self numSlotsForBytes: (self numSlotsOf: outPointerArray) * 4)
- 	savedOutHashes := self allocateSlots: (self numSlotsForBytes: (self numSlotsOf: outPointerArray) * 4)
  							format: self firstLongFormat
  							classIndex: self thirtyTwoBitLongsClassIndexPun.
  	(savedFirstFields isNil or: [savedOutHashes isNil]) ifTrue:
  		[self freeObject: arrayOfObjects.
  		 (savedFirstFields notNil and: [self isInOldSpace: savedFirstFields]) ifTrue:
  			[self freeObject: savedFirstFields].
  		 (savedOutHashes notNil and: [self isInOldSpace: savedOutHashes]) ifTrue:
  			[self freeObject: savedOutHashes].
  		 ^PrimErrNoMemory].
  
  	self fillObj: savedFirstFields numSlots: (self numSlotsOf: savedFirstFields) with: 0.
  	self fillObj: savedOutHashes numSlots: (self numSlotsOf: savedOutHashes) with: self savedOutHashFillValue.
  
  	segAddr := segmentWordArray + self baseHeaderSize.
  	endSeg := self addressAfter: segmentWordArray.
  
  	"Write a version number for byte order and version check."
  	segAddr >= endSeg ifTrue: [^PrimErrGenericFailure].
  	self long32At: segAddr put: self imageSegmentVersion.
  	self long32At: segAddr + 4 put: self imageSegmentVersion.
  	segStart := segAddr := segAddr + self allocationUnit.
  
  	self assert: arrayOfRoots = (self fetchPointer: 0 ofObject: arrayOfObjects).
  
  	"Copy all reachable objects to the segment, setting the marked bit for all objects (clones) in the segment,
  	 and the remembered bit for all classes (clones) in the segment."
  	0 to: (self numSlotsOf: arrayOfObjects) - 1 do:
  		[:i| | newSegAddrOrError objOop |
  		"Check that classes in the segment are addressable.  Since the top bit of the hash field is used to tag
  		 classes external to the segment, the segment offset must not inadvertently set this bit.  This limit still
  		 allows for a million or more classes."
  		(i = numClassesInSegment
  		 and: [segAddr - segStart / self allocationUnit + self lastClassIndexPun >= TopHashBit]) ifTrue:
  			[^self return: PrimErrLimitExceeded
  					restoringObjectsIn: arrayOfObjects upTo: i savedFirstFields: savedFirstFields].
  		objOop := self fetchPointer: i ofObject: arrayOfObjects.
  		self deny: ((self isImmediate: objOop) or: [self isForwarded: objOop]).
  		newSegAddrOrError := self copyObj: objOop
  									toAddr: segAddr
  									stopAt: endSeg
  									savedFirstFields: savedFirstFields
  									index: i.
  		(self oop: newSegAddrOrError isLessThan: segStart) ifTrue:
  			[^self return: newSegAddrOrError
  					restoringObjectsIn: arrayOfObjects upTo: i savedFirstFields: savedFirstFields].
  		 segAddr := newSegAddrOrError].
  
  	"Check that it can be safely shortened."
  	(endSeg ~= segAddr
  	 and: [endSeg - segAddr < (self baseHeaderSize + self bytesPerOop)]) ifTrue:
  		[^self return: PrimErrWritePastObject
  				restoringObjectsIn: arrayOfObjects upTo: -1 savedFirstFields: savedFirstFields].
  
  	"Now scan, adding out pointers to the outPointersArray; all objects in arrayOfObjects
  	 have their first field pointing to the corresponding copy in segmentWordArray."
  	(outIndex := self mapOopsFrom: segStart
  					to: segAddr
  					outPointers: outPointerArray
  					outHashes: savedOutHashes) < 0 ifTrue: "no room in outPointers; fail"
  		[^self return: PrimErrBadIndex
  				restoringObjectsIn: arrayOfObjects savedFirstFields: savedFirstFields
  				and: outPointerArray savedHashes: savedOutHashes].
  
  	"We're done.  Shorten the results, restore hashes and return."
  	self shorten: segmentWordArray toIndexableSize: segAddr - (segmentWordArray + self baseHeaderSize) / 4.
  	self shorten: outPointerArray toIndexableSize: outIndex.
  	^self return: PrimNoErr
  		restoringObjectsIn: arrayOfObjects savedFirstFields: savedFirstFields
  		and: outPointerArray savedHashes: savedOutHashes!



More information about the Vm-dev mailing list