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

commits at source.squeak.org commits at source.squeak.org
Thu Dec 8 18:35:48 UTC 2022


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

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

Name: VMMaker.oscog.seperateMarking-eem.3281
Author: eem
Time: 8 December 2022, 10:35:27.618989 am
UUID: 563eefa5-7e25-41a0-b95c-71a70fec2569
Ancestors: VMMaker.oscog.seperateMarking-eem.3279, VMMaker.oscog-eem.3280

Merge VMMaker.oscog-eem.3280 & VMMaker.oscog-eem.3276

=============== Diff against VMMaker.oscog.seperateMarking-eem.3279 ===============

Item was changed:
  ----- Method: ClipboardExtendedPlugin>>ioAddClipboardData:data:dataFormat: (in category 'io') -----
  ioAddClipboardData: clipboard data: data dataFormat: format
  	| dataLength |
+ 	self primitive: 'ioAddClipboardData' parameters: #(Unsigned WordsOrBytes Oop).
- 	self primitive: 'ioAddClipboardData' parameters: #(Unsigned ByteArray Oop).
  
  	dataLength := interpreterProxy byteSizeOf: data cPtrAsOop.
  	(interpreterProxy isIntegerObject: format)
  		ifTrue:
  			[self
  				sqPasteboardPutItemFlavor: clipboard asVoidPointer
  				data: data length: dataLength
  				formatType: (interpreterProxy integerValueOf: format)]
  		ifFalse:
  			[(interpreterProxy isBytes: format)
  				ifTrue:
  					[self
  						sqPasteboardPutItemFlavor: clipboard asVoidPointer
  						data: data length: dataLength
  						formatType: (interpreterProxy firstIndexableField: format)
  						formatLength: (interpreterProxy byteSizeOf: format)]
  				ifFalse:
  					[interpreterProxy primitiveFailFor: PrimErrBadArgument]]!

Item was changed:
  ----- Method: ClipboardExtendedPlugin>>ioGetClipboardFormat:formatNumber: (in category 'io') -----
+ ioGetClipboardFormat: clipboard formatNumber: formatNumber
- ioGetClipboardFormat: clipboard formatNumber: formatNumber 
  	<var: #clipboardAddress type: #'usqIntptr_t'>
  	self primitive: 'ioGetClipboardFormat' parameters: #(Unsigned SmallInteger).
  	^(self sqPasteboardGetItemCount: clipboard asVoidPointer) > 0
  		ifTrue: [self sqPasteboardCopyItemFlavors: clipboard asVoidPointer itemNumber: formatNumber]
  		ifFalse: [interpreterProxy nilObject]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveObjectsAccessibleFromRoots (in category 'image segment in/out') -----
+ primitiveObjectsAccessibleFromRoots
+ 	"This primitive is called from Squeak as...
+ 		arrayOfRoots uniquelyAccessibleObjects"
+ 
+ 	"This primitive answers an array of the receiver and every object in its proper tree of subParts (ie, that is not refered to from anywhere else outside the tree)."
+ 	"This primitive could be used to implement the primitiveStoreImageSegment segment, thanks to a suggestion from Igor Stassenko. Currently it is
+ 	 used only to debug that primitive."
+ 
+ 	| arrayOfRoots result |
+ 	arrayOfRoots := self stackTop.
+ 
+ 	"Essential type checks"
+ 	(objectMemory isArray: arrayOfRoots)				"Must be indexable pointers"
+ 		ifFalse: [^self primitiveFail].
+ 
+ 	result := objectMemory objectsAccessibleFromRoots: arrayOfRoots.
+ 	(objectMemory hasSpurMemoryManagerAPI
+ 	 and: [(objectMemory isIntegerObject: result)
+ 	 and: [(objectMemory integerValueOf: result) = PrimErrNoMemory]]) ifTrue:
+ 		[objectMemory fullGC.
+ 		 arrayOfRoots := self stackTop.
+ 		 result := objectMemory objectsAccessibleFromRoots: arrayOfRoots].
+ 	(objectMemory isIntegerObject: result)
+ 		ifTrue: [self primitiveFailFor: (objectMemory integerValueOf: result)]
+ 		ifFalse: [self methodReturnValue: result]!

Item was added:
+ ----- Method: ObjectMemory>>objectsAccessibleFromRoots: (in category 'image segment in/out') -----
+ objectsAccessibleFromRoots: arrayOfRoots
+ 	^self integerObjectOf: PrimErrUnsupported!

Item was added:
+ ----- Method: SpurMemoryManager>>objectsAccessibleFromRoots: (in category 'image segment in/out') -----
+ objectsAccessibleFromRoots: arrayOfRootsArg
+ 	"This primitive is called from Squeak as...
+ 		arrayOfRoots uniquelyAccessibleObjects
+ 
+ 	This primitive answers an array of the receiver and every object in its proper tree of subParts (ie, that is not refered to from anywhere else outside the tree).
+ 
+ 	 The primitive can fail for the following reasons with the specified failure codes:
+ 		PrimErrNoMemory:			additional allocations failed"
+ 
+ 	<inline: false>
+ 	| arrayOfRoots arrayOfObjects |
+ 	<var: 'segAddr' type: #usqInt>
+ 
+ 	self runLeakCheckerFor: GCCheckImageSegment.
+ 
+ 	"First scavenge to collect any new space garbage that refers to the graph."
+ 	self scavengingGC.
+ 	arrayOfRoots := self updatePostScavenge: arrayOfRootsArg.
+ 	
+ 	"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:
+ 		[^self integerObjectOf: 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:
+ 			[^self integerObjectOf: PrimErrNeedCompaction].
+ 		 ^self integerObjectOf: PrimErrNoMemory].
+ 
+ 	self assert: self allObjectsUnmarked. "work to be done when the incremental GC is written"
+ 	self deny: (self forwardersIn: arrayOfObjects).
+ 
+ 	^arrayOfObjects!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)



More information about the Vm-dev mailing list