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

commits at source.squeak.org commits at source.squeak.org
Tue Jul 26 23:23:19 UTC 2022


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

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

Name: VMMaker.oscog.seperateMarking-eem.3223
Author: eem
Time: 26 July 2022, 4:23:03.599542 pm
UUID: 683d584f-0293-49e3-8fc7-b045d8d09a88
Ancestors: VMMaker.oscog.seperateMarking-WoC.3222

Nuke the older named primitiveNewPinnedInOldSpace & primitiveNewWithArgUninitialized.  Categorize all the instantiation primitives under "instantiation primitives".

=============== Diff against VMMaker.oscog.seperateMarking-WoC.3222 ===============

Item was changed:
  SystemOrganization addCategory: #'VMMaker-Building'!
  SystemOrganization addCategory: #'VMMaker-Interpreter'!
  SystemOrganization addCategory: #'VMMaker-InterpreterSimulation'!
  SystemOrganization addCategory: #'VMMaker-JIT'!
  SystemOrganization addCategory: #'VMMaker-JITSimulation'!
  SystemOrganization addCategory: #'VMMaker-Multithreading'!
  SystemOrganization addCategory: #'VMMaker-Plugins'!
  SystemOrganization addCategory: #'VMMaker-Plugins-FFI'!
  SystemOrganization addCategory: #'VMMaker-Plugins-IOS'!
  SystemOrganization addCategory: #'VMMaker-PostProcessing'!
  SystemOrganization addCategory: #'VMMaker-SmartSyntaxPlugins'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManager'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManagerSimulation'!
+ SystemOrganization addCategory: #'VMMaker-V3MemoryManager'!
  SystemOrganization addCategory: #'VMMaker-Support'!
  SystemOrganization addCategory: #'VMMaker-Tests'!
  SystemOrganization addCategory: #'VMMaker-Translation to C'!
  SystemOrganization addCategory: #'VMMaker-Utilities'!
- SystemOrganization addCategory: #'VMMaker-V3MemoryManager'!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitiveClone (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitiveClone (in category 'object access primitives') -----
  primitiveClone
  	"Return a shallow copy of the receiver."
  
  	| rcvr newCopy |
  	rcvr := self stackTop.
  	(objectMemory isImmediate: rcvr)
  		ifTrue:
  			[newCopy := rcvr]
  		ifFalse:
  			[(argumentCount = 0
  			  or: [(objectMemory isForwarded: rcvr) not])
  				ifTrue: [newCopy := objectMemory cloneObject: rcvr]
  				ifFalse: [newCopy := 0].
  			 newCopy = 0 ifTrue: "not enough memory most likely"
  				[^self primitiveFail]].
  	self pop: argumentCount + 1 thenPush: newCopy!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitiveNew (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitiveNew (in category 'object access primitives') -----
  primitiveNew
  	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
  		[(argumentCount < 1
  		  or: [self objCouldBeClassObj: self stackTop]) ifFalse:
  			[^self primitiveFailFor: PrimErrBadArgument]].
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			["Allocate a new fixed-size instance.  Fail if the allocation would leave
  			  less than lowSpaceThreshold bytes free. This *will not* cause a GC :-)"
  			(objectMemory instantiateClass: self stackTop)
  				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
  				ifNil: [self primitiveFailFor: ((objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClass: self stackTop))
  											ifTrue: [PrimErrNoMemory]
  											ifFalse: [PrimErrBadReceiver])]]
  		ifFalse:
  			["Allocate a new fixed-size instance. Fail if the allocation would leave
  			  less than lowSpaceThreshold bytes free. May cause a GC."
  			| spaceOkay |
  			"The following may cause GC!! Use var for result to permit inlining."
  			spaceOkay := objectMemory
  								sufficientSpaceToInstantiate: self stackTop
  								indexableSize: 0.
  			spaceOkay
  				ifTrue:
  					[self
  						pop: argumentCount + 1
  						thenPush: (objectMemory
  									instantiateClass: self stackTop
  									indexableSize: 0)]
  				ifFalse: [self primitiveFailFor: PrimErrNoMemory]]!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitiveNewMethod (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitiveNewMethod (in category 'compiled methods') -----
  primitiveNewMethod
  	| header bytecodeCount class size theMethod literalCount |
  	header := self stackTop.
  	bytecodeCount := self stackValue: 1.
  	((objectMemory isIntegerObject: header)
  	 and: [(objectMemory isIntegerObject: bytecodeCount)
  	 and: [(bytecodeCount := objectMemory integerValueOf: bytecodeCount) >= 0]]) ifFalse:
  		[self primitiveFailFor: PrimErrBadArgument.
  		 ^self].
  	class := self stackValue: 2.
  	literalCount := objectMemory literalCountOfMethodHeader: header.
  	size := literalCount + LiteralStart * objectMemory bytesPerOop + bytecodeCount.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[theMethod := objectMemory instantiateCompiledMethodClass: class indexableSize: size.
  			 theMethod ifNil:
  				[self primitiveFailFor: ((objectMemory isCompiledMethodFormat: (objectMemory instSpecOfClass: class))
  										ifTrue: [PrimErrNoMemory]
  										ifFalse: [PrimErrBadReceiver]).
  				 ^self]]
  		ifFalse:
  			[theMethod := objectMemory instantiateClass: class indexableSize: size].
  	objectMemory storePointerUnchecked: HeaderIndex ofObject: theMethod withValue: header.
  	1 to: literalCount do:
  		[:i | objectMemory storePointerUnchecked: i ofObject: theMethod withValue: objectMemory nilObject].
  	self pop: 3 thenPush: theMethod!

Item was removed:
- ----- Method: InterpreterPrimitives>>primitiveNewPinnedInOldSpace (in category 'object access primitives') -----
- primitiveNewPinnedInOldSpace
- 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
- 		[(argumentCount < 1
- 		  or: [self objCouldBeClassObj: self stackTop]) ifFalse:
- 			[^self primitiveFailFor: PrimErrBadArgument]].
- 	objectMemory hasSpurMemoryManagerAPI
- 		ifTrue:
- 			["Allocate a new fixed-size instance.  Fail if the allocation would leave
- 			  less than lowSpaceThreshold bytes free. This *will not* cause a GC :-)"
- 			(objectMemory instantiateClass: self stackTop)
- 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
- 				ifNil: [self primitiveFailFor: ((objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClass: self stackTop))
- 											ifTrue: [PrimErrNoMemory]
- 											ifFalse: [PrimErrBadReceiver])]]
- 		ifFalse:
- 			["Allocate a new fixed-size instance. Fail if the allocation would leave
- 			  less than lowSpaceThreshold bytes free. May cause a GC."
- 			| spaceOkay |
- 			"The following may cause GC!! Use var for result to permit inlining."
- 			spaceOkay := objectMemory
- 								sufficientSpaceToInstantiate: self stackTop
- 								indexableSize: 0.
- 			spaceOkay
- 				ifTrue:
- 					[self
- 						pop: argumentCount + 1
- 						thenPush: (objectMemory
- 									instantiateClass: self stackTop
- 									indexableSize: 0)]
- 				ifFalse: [self primitiveFailFor: PrimErrNoMemory]]!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitiveNewWithArg (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitiveNewWithArg (in category 'object access primitives') -----
  primitiveNewWithArg
  	"Allocate a new indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free. May cause a GC."
  	| size spaceOkay instSpec |
  	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
  		[(argumentCount < 2
  		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
  			[^self primitiveFailFor: PrimErrBadArgument]].
  	size := self positiveMachineIntegerValueOf: self stackTop.
  	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
  		[^self primitiveFailFor: PrimErrBadArgument].
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[(objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)
  				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
  				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
  					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
  											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
  												ifTrue: [PrimErrNoMemory]
  												ifFalse: [PrimErrBadReceiver])]]
  		ifFalse:
  			[spaceOkay := objectMemory sufficientSpaceToInstantiate: (self stackValue: 1) indexableSize: size.
  			 spaceOkay
  				ifTrue:
  					[self
  						pop: argumentCount + 1
  						thenPush: (objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)]
  				ifFalse:
  					[self primitiveFailFor: PrimErrNoMemory]]!

Item was removed:
- ----- Method: InterpreterPrimitives>>primitiveNewWithArgUninitialized (in category 'object access primitives') -----
- primitiveNewWithArgUninitialized
- 	"Allocate a new indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free. May cause a GC."
- 	| size spaceOkay instSpec |
- 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
- 		[(argumentCount < 2
- 		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
- 			[^self primitiveFailFor: PrimErrBadArgument]].
- 	size := self positiveMachineIntegerValueOf: self stackTop.
- 	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
- 		[^self primitiveFailFor: PrimErrBadArgument].
- 	objectMemory hasSpurMemoryManagerAPI
- 		ifTrue:
- 			[(objectMemory instantiateUninitializedClass: (self stackValue: 1) indexableSize: size)
- 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
- 				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
- 					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
- 											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
- 												ifTrue: [PrimErrNoMemory]
- 												ifFalse: [PrimErrBadReceiver])]]
- 		ifFalse:
- 			[spaceOkay := objectMemory sufficientSpaceToInstantiate: (self stackValue: 1) indexableSize: size.
- 			 spaceOkay
- 				ifTrue:
- 					[self
- 						pop: argumentCount + 1
- 						thenPush: (objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)]
- 				ifFalse:
- 					[self primitiveFailFor: PrimErrNoMemory]]!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitivePinnedNew (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitivePinnedNew (in category 'object access primitives') -----
  primitivePinnedNew
  	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
  		[(argumentCount < 1
  		  or: [self objCouldBeClassObj: self stackTop]) ifFalse:
  			[^self primitiveFailFor: PrimErrBadArgument]].
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			["Allocate a new fixed-size instance.  Fail if the allocation would leave
  			  less than lowSpaceThreshold bytes free. This *will not* cause a GC :-)"
  			(objectMemory inOldSpaceInstantiatePinnedClass: self stackTop)
  				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
  				ifNil: [self primitiveFailFor: ((objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClass: self stackTop))
  											ifTrue: [PrimErrNoMemory]
  											ifFalse: [PrimErrBadReceiver])]]
  		ifFalse:
  			[self primitiveFailFor: PrimErrUnsupported]!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitivePinnedNewWithArg (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitivePinnedNewWithArg (in category 'object access primitives') -----
  primitivePinnedNewWithArg
  	"Allocate a new pinned indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free."
  	| size instSpec |
  	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
  		[(argumentCount < 2
  		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
  			[^self primitiveFailFor: PrimErrBadArgument]].
  	size := self positiveMachineIntegerValueOf: self stackTop.
  	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
  		[^self primitiveFailFor: PrimErrBadArgument].
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[(objectMemory inOldSpaceInstantiatePinnedClass: (self stackValue: 1) indexableSize: size)
  				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
  				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
  					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
  											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
  												ifTrue: [PrimErrNoMemory]
  												ifFalse: [PrimErrBadReceiver])]]
  		ifFalse:
  			[self primitiveFailFor: PrimErrUnsupported]!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitiveUninitializedNewWithArg (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitiveUninitializedNewWithArg (in category 'object access primitives') -----
  primitiveUninitializedNewWithArg
  	"Allocate a new indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free. May cause a GC."
  	| size instSpec |
  	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
  		[(argumentCount < 2
  		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
  			[^self primitiveFailFor: PrimErrBadArgument]].
  	size := self positiveMachineIntegerValueOf: self stackTop.
  	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
  		[^self primitiveFailFor: PrimErrBadArgument].
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[(objectMemory instantiateUninitializedClass: (self stackValue: 1) indexableSize: size)
  				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
  				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
  					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
  											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
  												ifTrue: [PrimErrNoMemory]
  												ifFalse: [PrimErrBadReceiver])]]
  		ifFalse:
  			[self primitiveFailFor: PrimErrUnsupported]!



More information about the Vm-dev mailing list