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

commits at source.squeak.org commits at source.squeak.org
Thu Feb 12 03:12:24 UTC 2015


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

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

Name: VMMaker.oscog-eem.1057
Author: eem
Time: 11 February 2015, 7:10:52.616 pm
UUID: e81e5238-13d6-428d-8292-2472236402ac
Ancestors: VMMaker.oscog-eem.1056

primitiveDoNamedPrimitiveWithArgs needs to follow
the same convention re primitiveFunctionPointer
as primitiveDoPrimitiveWithArgs et al on failure,
otherwise checkForAndFollowForwardedPrimitiveState
will be fatally confused.

Add an assert to check the range of accessorDepth.

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

Item was changed:
  ----- Method: StackInterpreter>>checkForAndFollowForwardedPrimitiveState (in category 'primitive support') -----
  checkForAndFollowForwardedPrimitiveState
  	"In Spur a primitive may fail due to encountering a forwarder. On failure,
  	 check the accessorDepth for the primitive and if non-negative scan the
  	 args to the depth, following any forwarders.  Answer if any are found so
  	 the prim can be retried.  The primitive index is derived from newMethod.
  	 If the primitive is 118, then primitiveDoPrimitiveWithArgs sets newMethod
  	 to a SmallInteger whose value is the primitive it is evaluating."
  	<option: #SpurObjectMemory>
  	| primIndex accessorDepth found scannedStackFrame |
  	self assert: self failed.
  	found := scannedStackFrame := false.
  	primIndex := (objectMemory isIntegerObject: newMethod)
  					ifTrue: [objectMemory integerValueOf: newMethod]
  					ifFalse:
  						[self assert: argumentCount = (self argumentCountOf: newMethod).
  						 self primitiveIndexOf: newMethod].
  	accessorDepth := primitiveAccessorDepthTable at: primIndex.
  	"For the method-executing primitives, failure could have been in those primitives or the
  	 primitives of the methods they execute.  Find out which failed by seeing what is in effect."
  	((primIndex = 117 and: [primitiveFunctionPointer ~~ #primitiveExternalCall])
  	 or: [primIndex = 218 and: [primitiveFunctionPointer ~~ #primitiveDoNamedPrimitiveWithArgs]])
  		ifTrue:
  			[accessorDepth := self primitiveAccessorDepthForExternalPrimitiveMethod: newMethod]
  		ifFalse:
  			[self assert: (self saneFunctionPointerForFailureOfPrimIndex: primIndex)].
+ 	self assert: (accessorDepth between: -127 and: 127).
  	accessorDepth >= 0 ifTrue:
  		[0 to: argumentCount do:
  			[:index| | oop |
  			oop := self stackValue: index.
  			(objectMemory isNonImmediate: oop) ifTrue:
  				[(objectMemory isForwarded: oop) ifTrue:
  					[self assert: index < argumentCount. "receiver should have been caught at send time."
  					 found := true.
  					 oop := objectMemory followForwarded: oop.
  					 self stackValue: index put: oop.
  					 scannedStackFrame ifFalse:
  						[scannedStackFrame := true.
  						 self
  							followForwardedFrameContents: framePointer
  							stackPointer: stackPointer + (argumentCount + 1 * objectMemory wordSize) "don't repeat effort"]].
  				((objectMemory hasPointerFields: oop)
  				 and: [objectMemory followForwardedObjectFields: oop toDepth: accessorDepth]) ifTrue:
  					[found := true]]]].
  	^found!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveDoNamedPrimitiveWithArgs (in category 'plugin primitives') -----
  primitiveDoNamedPrimitiveWithArgs
  	"Simulate an primitiveExternalCall invocation (e.g. for the Debugger).  Do not cache anything.
  	 e.g. ContextPart>>tryNamedPrimitiveIn: aCompiledMethod for: aReceiver withArgs: arguments"
  	| argumentArray arraySize methodArg methodHeader
  	  moduleName functionName moduleLength functionLength
  	  spec addr primRcvr isArray |
  	<var: #addr declareC: 'void (*addr)()'>
  	argumentArray := self stackTop.
  	methodArg := self stackValue: 2.
  	((objectMemory isArray: argumentArray)
  	 and: [objectMemory isOopCompiledMethod: methodArg]) ifFalse:
  		[^self primitiveFailFor: -2]. "invalid args"
  	arraySize := objectMemory numSlotsOf: argumentArray.
  	(self roomToPushNArgs: arraySize) ifFalse:
  		[^self primitiveFailFor: -2]. "invalid args"
  
  	methodHeader := objectMemory methodHeaderOf: methodArg.
  	(objectMemory literalCountOfMethodHeader: methodHeader) > 2 ifFalse:
  		[^self primitiveFailFor: -3]. "invalid methodArg state"
  	spec := objectMemory fetchPointer: 1 "first literal" ofObject: methodArg.
  	isArray := self isInstanceOfClassArray: spec.
  	(isArray
  	and: [(objectMemory lengthOf: spec) = 4
  	and: [(self primitiveIndexOfMethod: methodArg header: methodHeader) = 117]]) ifFalse:
  		[^self primitiveFailFor: -3]. "invalid methodArg state"
  
  	(self argumentCountOfMethodHeader: methodHeader) = arraySize ifFalse:
  		[^self primitiveFailFor: -2]. "invalid args (Array args wrong size)"
  
  	"The function has not been loaded yet. Fetch module and function name."
  	moduleName := objectMemory fetchPointer: 0 ofObject: spec.
  	moduleName = objectMemory nilObject
  		ifTrue: [moduleLength := 0]
  		ifFalse: [self success: (objectMemory isBytes: moduleName).
  				moduleLength := objectMemory lengthOf: moduleName.
  				self cCode: '' inSmalltalk:
  					[ (#('FloatArrayPlugin' 'Matrix2x3Plugin') includes: (self stringOf: moduleName)) "??"
  						ifTrue: [moduleLength := 0  "Cause all of these to fail"]]].
  	functionName := objectMemory fetchPointer: 1 ofObject: spec.
  	self success: (objectMemory isBytes: functionName).
  	functionLength := objectMemory lengthOf: functionName.
  	self successful ifFalse: [^self primitiveFailFor: -3]. "invalid methodArg state"
  
  	addr := self ioLoadExternalFunction: functionName + objectMemory baseHeaderSize
  				OfLength: functionLength
  				FromModule: moduleName + objectMemory baseHeaderSize
  				OfLength: moduleLength.
  	addr = 0 ifTrue:
  		[^self primitiveFailFor: -1]. "could not find function; answer generic failure (see below)"
  
  	"Cannot fail this primitive from now on.  Can only fail the external primitive."
  	tempOop := objectMemory
  						eeInstantiateClassIndex: ClassArrayCompactIndex
  						format: objectMemory arrayFormat
  						numSlots: (objectMemory hasSpurMemoryManagerAPI
  									ifTrue: [5]
  									ifFalse: [4]).
  	objectMemory
  		storePointerUnchecked: 0 ofObject: tempOop withValue: (argumentArray := self popStack);
  		storePointerUnchecked: 1 ofObject: tempOop withValue: (primRcvr := self popStack);
  		storePointerUnchecked: 2 ofObject: tempOop withValue: self popStack; "the method"
  		storePointerUnchecked: 3 ofObject: tempOop withValue: self popStack. "the context receiver"
  	self push: primRcvr. "replace context receiver with actual receiver"
  	argumentCount := arraySize.
  	1 to: arraySize do:
  		[:index| self push: (objectMemory fetchPointer: index - 1 ofObject: argumentArray)].
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[objectMemory storePointerUnchecked: 4 ofObject: tempOop withValue: newMethod.
  			 newMethod := methodArg.
  			 self callExternalPrimitive: addr. "On Spur, sets primitiveFunctionPointer"
  			 self maybeRetryFailureDueToForwarding.
+ 			 newMethod := objectMemory fetchPointer: 4 ofObject: tempOop]
- 			 newMethod  := objectMemory fetchPointer: 4 ofObject: tempOop]
  		ifFalse:
  			[self callExternalPrimitive: addr].
  	self successful ifFalse: "If primitive failed, then restore state for failure code"
  		[self pop: arraySize + 1.
  		 self push: (objectMemory fetchPointer: 3 ofObject: tempOop).
  		 self push: (objectMemory fetchPointer: 2 ofObject: tempOop).
  		 self push: (objectMemory fetchPointer: 1 ofObject: tempOop).
  		 self push: (objectMemory fetchPointer: 0 ofObject: tempOop).
  		 argumentCount := 3.
+ 		 "Must reset primitiveFunctionPointer for checkForAndFollowForwardedPrimitiveState"
+ 		 objectMemory hasSpurMemoryManagerAPI ifTrue:
+ 			[primitiveFunctionPointer := #primitiveDoNamedPrimitiveWithArgs].
  		 "Hack.  A nil prim error code (primErrorCode = 1) is interpreted by the image
  		  as meaning this primitive is not implemented.  So to pass back nil as an error
  		  code we use -1 to indicate generic failure."
  		 primFailCode = 1 ifTrue:
  			[primFailCode := -1]]!



More information about the Vm-dev mailing list