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

commits at source.squeak.org commits at source.squeak.org
Sat Jun 20 18:24:19 UTC 2015


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

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

Name: VMMaker.oscog-eem.1368
Author: eem
Time: 20 June 2015, 11:22:19.253 am
UUID: 413094c9-bc1b-430f-8e41-34a0438291c5
Ancestors: VMMaker.oscog-eem.1367

Add explicit read barriers to primitives which
access an argument as the receiver (i.e. the
mirror primitives).  Don't check if the actual
receiver is used.  Simplify failure where
appropriate because the primitives will be retried.

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

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveAdoptInstance (in category 'object access primitives') -----
  primitiveAdoptInstance
  	"Primitive. Change the class of the argument to make it an instance of the receiver
  	 given that the format of the receiver matches the format of the argument's class.
  	 Fail if receiver or argument are SmallIntegers, or the receiver is an instance of a
  	 compact class and the argument isn't, or when the argument's class is compact and
  	 the receiver isn't, or when the format of the receiver is different from the format of
  	 the argument's class, or when the arguments class is fixed and the receiver's size
  	 differs from the size that an instance of the argument's class should have."
  	| rcvr arg err |
  
+ 	arg := self stackTop.
+ 	rcvr := self stackValue: 1.
+ 	((objectMemory isImmediate: arg)
+ 	 or: [argumentCount > 1
+ 		and: [(objectMemory isImmediate: rcvr)
+ 			or: [(self objCouldBeClassObj: rcvr) not]]]) ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadArgument].
- 	arg := self stackObjectValue: 0.
- 	rcvr := self stackObjectValue: 1.
- 	self successful ifFalse:[^nil].
  
  	err := objectMemory changeClassOf: arg to: rcvr.
  	err = 0
  		ifTrue: ["Flush at cache because rcvr's class has changed."
  				self flushAtCache.
  				self pop: self methodArgumentCount]
  		ifFalse: [self primitiveFailFor: err].
  	^nil!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveAllInstances (in category 'object access primitives') -----
  primitiveAllInstances
  	"Answer an array of all instances of the receiver that exist
  	 when the primitive is called, excluding any that may be
  	 garbage collected as a side effect of allocating the result array."
  
  	<export: true>
  	| result |
+ 	self cppIf: NewspeakVM
+ 		ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 			[(argumentCount < 1
+ 			  or: [(objectMemory isNonImmediate: self stackTop)
+ 				  and: [self objCouldBeClassObj: self stackTop]]) ifFalse:
+ 				[self primitiveFailFor: PrimErrBadArgument]].
  	result := objectMemory allInstancesOf: self stackTop.
  	(objectMemory isIntegerObject: result) ifTrue:
  		[objectMemory growToAccomodateContainerWithNumSlots: (objectMemory integerValueOf: result).
  		 result := objectMemory allInstancesOf: self stackTop.
  		 (objectMemory isIntegerObject: result) ifTrue:
  			[^self primitiveFailFor: PrimErrNoMemory]].
  	self pop: argumentCount+1 thenPush: result!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveBehaviorHash (in category 'object access primitives') -----
  primitiveBehaviorHash
  	| hashOrError |
+ 	argumentCount > 0
+ 		ifTrue:
+ 			[((objectMemory isNonImmediate: self stackTop)
+ 			  and: [self addressCouldBeClassObj: self stackTop]) ifFalse:
+ 				[^self primitiveFailFor: PrimErrBadArgument]]
+ 		ifFalse:
+ 			[self assert: ((objectMemory isNonImmediate: self stackTop)
+ 						  and: [self addressCouldBeClassObj: self stackTop])].
- 	self assert: ((objectMemory isNonImmediate: self stackTop)
- 				 and: [self addressCouldBeClassObj: self stackTop]).
  	hashOrError := objectMemory ensureBehaviorHash: self stackTop.
  	hashOrError >= 0
  		ifTrue: [self pop: argumentCount + 1 thenPushInteger: hashOrError]
  		ifFalse: [self primitiveFailFor: hashOrError negated]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveClass (in category 'object access primitives') -----
  primitiveClass
  	| instance |
  	instance := self stackTop.
+ 	(argumentCount > 0
+ 	 and: [objectMemory isOopForwarded: instance])
+ 		ifTrue:
+ 			[self primitiveFail]
+ 		ifFalse:
+ 			[self pop: argumentCount + 1 thenPush: (objectMemory fetchClassOf: instance)]!
- 	argumentCount > 0 ifTrue:
- 		[instance := objectMemory followMaybeForwarded: instance].
- 	self pop: argumentCount + 1 thenPush: (objectMemory fetchClassOf: instance)!

Item was changed:
  ----- 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 isObjectForwarded: rcvr) not])
+ 				ifTrue: [newCopy := objectMemory clone: rcvr]
+ 				ifFalse: [newCopy := 0].
- 			[newCopy := objectMemory clone: rcvr.
  			 newCopy = 0 ifTrue: "not enough memory most likely"
  				[^self primitiveFail]].
  	self pop: argumentCount + 1 thenPush: newCopy!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveIdentical (in category 'object access primitives') -----
  primitiveIdentical
  	"is the receiver/first argument the same object as the (last) argument?.
  	 pop argumentCount because this can be used as a mirror primitive."
  	| thisObject otherObject |
  	otherObject := self stackValue: 1.
  	thisObject := self stackTop.
+ 	((objectMemory isOopForwarded: otherObject)
+ 	 or: [argumentCount > 1
+ 		 and: [objectMemory isOopForwarded: thisObject]])
+ 		ifTrue:
+ 			[self primitiveFailFor: PrimErrBadArgument]
+ 		ifFalse:
+ 			[self pop: argumentCount + 1 thenPushBool: thisObject = otherObject]!
- 	(objectMemory isOopForwarded: otherObject) ifTrue:
- 		[self assert: argumentCount > 1.
- 		 otherObject := objectMemory followForwarded: thisObject].
- 	self assert: (objectMemory isOopForwarded: otherObject) not.
- 	(objectMemory isOopForwarded: thisObject) ifTrue:
- 		[thisObject := objectMemory followForwarded: thisObject].
- 	self pop: argumentCount + 1 thenPushBool: thisObject = otherObject!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveIdentityHash (in category 'object access primitives') -----
  primitiveIdentityHash
  	| thisReceiver |
  	thisReceiver := self stackTop.
+ 	((objectMemory isImmediate: thisReceiver)
+ 	 or: [argumentCount > 0
+ 		 and: [objectMemory isObjectForwarded: thisReceiver]])
- 	(objectMemory isImmediate: thisReceiver)
  		ifTrue: [self primitiveFail]
  		ifFalse: [self pop: argumentCount + 1
  					thenPushInteger: (objectMemory hashBitsOf: thisReceiver)]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveInstVarAt (in category 'object access primitives') -----
  primitiveInstVarAt
  	| index rcvr hdr fmt totalLength fixedFields value |
+ 	index := self stackTop.
- 	index := self stackIntegerValue: 0.
  	rcvr := self stackValue: 1.
+ 	((objectMemory isNonIntegerObject: index)
+ 	 or: [argumentCount > 1 "e.g. object:instVarAt:"
+ 		and: [objectMemory isOopForwarded: rcvr]]) ifTrue:
- 	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
+ 	index := objectMemory integerValueOf: index.
  	hdr := self baseHeader: rcvr.
  	fmt := objectMemory formatOfHeader: hdr.
  	totalLength := self lengthOf: rcvr baseHeader: hdr format: fmt.
  	fixedFields := self fixedFieldsOf: rcvr format: fmt length: totalLength.
  	(index >= 1 and: [index <= fixedFields]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	value := self subscript: rcvr with: index format: fmt.
  	self pop: argumentCount + 1 thenPush: value!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveInstVarAtPut (in category 'object access primitives') -----
  primitiveInstVarAtPut
  	| newValue index rcvr hdr fmt totalLength fixedFields |
  	newValue := self stackTop.
+ 	index := self stackValue: 1.
- 	index := self stackIntegerValue: 1.
  	rcvr := self stackValue: 2.
+ 	((objectMemory isNonIntegerObject: index)
+ 	 or: [argumentCount > 2 "e.g. object:instVarAt:put:"
+ 		and: [objectMemory isOopForwarded: rcvr]]) ifTrue:
- 	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
+ 	index := objectMemory integerValueOf: index.
  	hdr := objectMemory baseHeader: rcvr.
  	fmt := objectMemory formatOfHeader: hdr.
  	totalLength := objectMemory lengthOf: rcvr baseHeader: hdr format: fmt.
  	fixedFields := objectMemory fixedFieldsOf: rcvr format: fmt length: totalLength.
  	(index >= 1 and: [index <= fixedFields]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	self subscript: rcvr with: index storing: newValue format: fmt.
  	self pop: argumentCount + 1 thenPush: newValue!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveNew (in category 'object access primitives') -----
  primitiveNew
+ 	self cppIf: NewspeakVM
+ 		ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 			[(argumentCount < 1
+ 			  or: [self addressCouldBeClassObj: 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>>primitivePerformInSuperclass (in category 'control primitives') -----
  primitivePerformInSuperclass
  	| lookupClass rcvr currentClass |
- 	lookupClass := self stackTop.
  	rcvr := self stackValue: 3.
+ 	lookupClass := self stackTop.
+ 	(argumentCount > 3 "e.g. object:perform:withArguments:inClass:"
+ 	 and: [objectMemory isOopForwarded: rcvr]) ifTrue:
+ 		[^self primitiveFail].
  	currentClass := objectMemory fetchClassOf: rcvr.
  	[currentClass ~= lookupClass] whileTrue:
  		[currentClass := self superclassOf: currentClass.
+ 		 currentClass = objectMemory nilObject ifTrue:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
- 		 currentClass = objectMemory nilObject ifTrue: [^self primitiveFailFor: PrimErrBadArgument]].
  
  	self primitiveObject: rcvr "a.k.a. self stackValue: 3"
  		perform: (self stackValue: 2)
  		withArguments: (self stackValue: 1)
  		lookedUpIn: lookupClass "a.k.a. self stackTop"!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSomeInstance (in category 'object access primitives') -----
  primitiveSomeInstance
  	| class instance |
  	class := self stackTop.
+ 	self cppIf: NewspeakVM
+ 		ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 			[(argumentCount < 1
+ 			  or: [(objectMemory isNonImmediate: class)
+ 				  and: [self objCouldBeClassObj: class]]) ifFalse:
+ 				[self primitiveFailFor: PrimErrBadArgument]].
  	instance := objectMemory initialInstanceOf: class.
  	instance
  		ifNil: [self primitiveFail]
  		ifNotNil: [self pop: argumentCount+1 thenPush: instance]!

Item was changed:
  ----- Method: StackInterpreter>>commonAt: (in category 'indexing primitive support') -----
  commonAt: stringy
  	"This code is called if the receiver responds primitively to at:.
  	 N.B. this does *not* use the at cache, instead inlining stObject:at:.
  	 Using the at cache here would require that callers set messageSelector
  	 and lkupClass and that is onerous and error-prone, and in any case,
  	 inlining produces much better performance than using the at cache here."
  	| index rcvr result |
  	<inline: true> "to get it inlined in primitiveAt and primitiveStringAt"
  	self initPrimCall.
  	rcvr := self stackValue: 1.
+ 	index := self stackTop.
  	(objectMemory isImmediate: rcvr) ifTrue:
  		[^self primitiveFailFor: PrimErrInappropriate].
- 	index := self stackTop.
  	"No need to test for large positive integers here.  No object has 1g elements"
+ 	((objectMemory isNonIntegerObject: index)
+ 	 or: [argumentCount > 1 "e.g. object:basicAt:"
+ 		 and: [objectMemory isObjectForwarded: rcvr]]) ifTrue:
- 	(objectMemory isIntegerObject: index) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	index := objectMemory integerValueOf: index.
  	result := self stObject: rcvr at: index.
  	self successful ifTrue:
  		[stringy ifTrue: [result := self characterForAscii: (objectMemory integerValueOf: result)].
  		 self pop: argumentCount+1 thenPush: result]!

Item was changed:
  ----- Method: StackInterpreter>>commonAtPut: (in category 'indexing primitive support') -----
  commonAtPut: stringy
  	"This code is called if the receiver responds primitively to at:Put:.
  	 N.B. this does *not* use the at cache, instead inlining stObject:at:put:.
  	 Using the at cache here would require that callers set messageSelector
  	 and lkupClass and that is onerous and error-prone, and in any case,
  	 inlining produces much better performance than using the at cache here."
  	| value index rcvr |
  	<inline: true> "to get it inlined in primitiveAtPut and primitiveStringAtPut"
- 	value := self stackTop.
  	self initPrimCall.
  	rcvr := self stackValue: 2.
- 	(objectMemory isNonImmediate: rcvr) ifFalse:
- 		[^self primitiveFailFor: PrimErrInappropriate].
  	index := self stackValue: 1.
+ 	value := self stackTop.
+ 	(objectMemory isImmediate: rcvr) ifTrue:
+ 		[^self primitiveFailFor: PrimErrInappropriate].
  	"No need to test for large positive integers here.  No object has 1g elements"
+ 	((objectMemory isNonIntegerObject: index)
+ 	 or: [argumentCount > 2 "e.g. object:basicAt:put:"
+ 		 and: [objectMemory isObjectForwarded: rcvr]]) ifTrue:
- 	(objectMemory isIntegerObject: index) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	index := objectMemory integerValueOf: index.
  	stringy
  		ifTrue: [self stObject: rcvr at: index put: (self asciiOfCharacter: value)]
  		ifFalse: [self stObject: rcvr at: index put: value].
  	self successful ifTrue:
  		[self pop: argumentCount+1 thenPush: value]!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveClone (in category 'object access primitives') -----
  primitiveClone
  	"Return a shallow copy of the receiver.
  	 Special-case non-single contexts (because of context-to-stack mapping).
  	 Can't fail for contexts cuz of image context instantiation code (sigh)."
  
  	| rcvr newCopy |
  	rcvr := self stackTop.
  	(objectMemory isImmediate: rcvr)
  		ifTrue:
  			[newCopy := rcvr]
  		ifFalse:
  			[(objectMemory isContextNonImm: rcvr)
  				ifTrue:
  					[newCopy := self cloneContext: rcvr]
  				ifFalse:
+ 					[(argumentCount = 0
+ 					  or: [(objectMemory isObjectForwarded: rcvr) not])
+ 						ifTrue: [newCopy := objectMemory clone: rcvr]
+ 						ifFalse: [newCopy := 0]].
- 					[newCopy := objectMemory clone: rcvr].
  			newCopy = 0 ifTrue:
  				[^self primitiveFailFor: PrimErrNoMemory]].
  	self pop: argumentCount + 1 thenPush: newCopy!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveExecuteMethodArgsArray (in category 'control primitives') -----
  primitiveExecuteMethodArgsArray
  	"receiver, argsArray, then method are on top of stack.  Execute method against
  	 receiver and args.  Allow for up to two extra arguments (e.g. for mirror primitives).
  	 Set primitiveFunctionPointer because no cache lookup has been done for the
  	 method, and hence primitiveFunctionPointer is stale."
+ 	| methodArgument argCnt rcvr argumentArray primitiveIndex |
- 	| methodArgument argCnt argumentArray primitiveIndex |
  	methodArgument := self stackTop.
  	argumentArray := self stackValue: 1.
  	((objectMemory isOopCompiledMethod: methodArgument)
  	 and: [objectMemory isArray: argumentArray]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	argCnt := self argumentCountOf: methodArgument.
  	argCnt = (objectMemory numSlotsOf: argumentArray) ifFalse:
  		[^self primitiveFailFor: PrimErrBadNumArgs].
  	argumentCount > 2 ifTrue: "CompiledMethod class>>receiver:withArguments:executeMethod:
+ 								SqueakObjectPrimitives class>>receiver:withArguments:apply:
- 								SqueakObjectPrimitives class >> receiver:withArguments:apply:
  								VMMirror>>ifFail:object:with:executeMethod: et al"
  		[argumentCount > 4 ifTrue:
  			[^self primitiveFailFor: PrimErrUnsupported].
+ 		rcvr := self stackValue: 2.
+ 		rcvr := objectMemory followMaybeForwarded: rcvr.
+ 		self stackValue: argumentCount put: rcvr]. "replace actual receiver with desired receiver"
- 		self stackValue: argumentCount put: (self stackValue: 2)]. "replace actual receiver with desired receiver"
  	"and push the actual arguments"
  	self pop: argumentCount.
  	0 to: argCnt - 1 do:
  		[:i|
  		self push: (objectMemory fetchPointer: i ofObject: argumentArray)].
  	newMethod := methodArgument.
  	primitiveIndex := self primitiveIndexOf: newMethod.
  	primitiveFunctionPointer := self functionPointerFor: primitiveIndex inClass: nil.
  	argumentCount := argCnt.
  	self executeNewMethod.
  	"Recursive xeq affects primErrorCode"
  	self initPrimCall!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveInstVarAt (in category 'object access primitives') -----
  primitiveInstVarAt
  	| index rcvr hdr fmt totalLength fixedFields value |
+ 	index := self stackTop.
- 	index := self stackIntegerValue: 0.
  	rcvr := self stackValue: 1.
+ 	((objectMemory isNonIntegerObject: index)
+ 	 or: [argumentCount > 1 "e.g. object:instVarAt:"
+ 		and: [objectMemory isOopForwarded: rcvr]]) ifTrue:
- 	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
+ 	index := objectMemory integerValueOf: index.
  	hdr := objectMemory baseHeader: rcvr.
  	fmt := objectMemory formatOfHeader: hdr.
  	totalLength := objectMemory lengthOf: rcvr baseHeader: hdr format: fmt.
  	fixedFields := objectMemory fixedFieldsOf: rcvr format: fmt length: totalLength.
  	(index >= 1 and: [index <= fixedFields]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	(fmt = objectMemory indexablePointersFormat
  	 and: [objectMemory isContextHeader: hdr])
  		ifTrue: [value := self externalInstVar: index - 1 ofContext: rcvr]
  		ifFalse: [value := self subscript: rcvr with: index format: fmt].
  	self pop: argumentCount + 1 thenPush: value!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveInstVarAtPut (in category 'object access primitives') -----
  primitiveInstVarAtPut
  	| newValue index rcvr hdr fmt totalLength fixedFields |
  	newValue := self stackTop.
+ 	index := self stackValue: 1.
- 	index := self stackIntegerValue: 1.
  	rcvr := self stackValue: 2.
+ 	((objectMemory isNonIntegerObject: index)
+ 	 or: [argumentCount > 2 "e.g. object:instVarAt:put:"
+ 		and: [objectMemory isOopForwarded: rcvr]]) ifTrue:
- 	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
+ 	index := objectMemory integerValueOf: index.
  	hdr := objectMemory baseHeader: rcvr.
  	fmt := objectMemory formatOfHeader: hdr.
  	totalLength := objectMemory lengthOf: rcvr baseHeader: hdr format: fmt.
  	fixedFields := objectMemory fixedFieldsOf: rcvr format: fmt length: totalLength.
  	(index >= 1 and: [index <= fixedFields]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	(fmt = objectMemory indexablePointersFormat
  	 and: [objectMemory isContextHeader: hdr])
  		ifTrue: [self externalInstVar: index - 1 ofContext: rcvr put: newValue]
  		ifFalse: [self subscript: rcvr with: index storing: newValue format: fmt].
  	self pop: argumentCount + 1 thenPush: newValue!



More information about the Vm-dev mailing list