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

commits at source.squeak.org commits at source.squeak.org
Fri Feb 7 01:38:51 UTC 2014


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

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

Name: VMMaker.oscog-eem.611
Author: eem
Time: 6 February 2014, 5:34:59.528 pm
UUID: 83908c61-3751-4074-b6e6-e5283e45f50f
Ancestors: VMMaker.oscog-eem.610

Fix slip in StackInterpreter>>postBecomeAction:.  Must follow
receivers after every become (even if become effects flags are 0)
since e.g. a becommed string can be the receiver in a super send,
and so, because super sends don't trap, must be unforwarded.

Add some asserts to catch this error in *activateNewMethod &
slowPrimitiveResponse.

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

Item was changed:
  ----- Method: CoInterpreter>>activateNewMethod (in category 'message sending') -----
  activateNewMethod
  	| methodHeader numArgs numTemps rcvr errorCode inInterpreter switched |
  
  	methodHeader := self headerOf: newMethod.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  	numArgs := self argumentCountOfMethodHeader: methodHeader.
  
  	rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
+ 	self assert: (objectMemory isOopForwarded: rcvr) not.
  
  	"Because this is an uncogged method we need to continue via the interpreter.
  	 We could have been reached either from the interpreter, in which case we
  	 should simply return, or from a machine code frame or from a compiled
  	 primitive.  In these latter two cases we must longjmp back to the interpreter.
  	 The instructionPointer tells us which path we took.
  	 If the sender was an interpreter frame but called through a (failing) primitive
  	 then make sure we restore the saved instruction pointer and avoid pushing
  	 ceReturnToInterpreterPC which is only valid between an interpreter caller
  	 frame and a machine code callee frame."
  	(inInterpreter := instructionPointer >= objectMemory startOfMemory) ifFalse:
  		[instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
  			[instructionPointer := self iframeSavedIP: framePointer]].
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: newMethod.
  	self setMethod: newMethod methodHeader: methodHeader.
  	self push: objectMemory nilObject. "FxThisContext field"
  	self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
  	self push: 0. "FoxIFSavedIP"
  	self push: rcvr.
  
  	"clear remaining temps to nil"
  	numArgs+1 to: numTemps do:
  		[:i | self push: objectMemory nilObject].
  
  	instructionPointer := (self initialPCForHeader: methodHeader method: newMethod) - 1.
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
  		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  		 instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader).
  		 primFailCode ~= 0 ifTrue:
  			[(objectMemory byteAt: instructionPointer + 1)
  			  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
  			 primFailCode := 0]].
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	switched := true.
  	stackPointer < stackLimit ifTrue:
  		[switched := self handleStackOverflowOrEventAllowContextSwitch:
  							(self canContextSwitchIfActivating: newMethod header: methodHeader)].
  	self returnToExecutive: inInterpreter postContextSwitch: switched!

Item was changed:
  ----- Method: CoInterpreter>>internalActivateNewMethod (in category 'message sending') -----
  internalActivateNewMethod
  	| methodHeader numTemps rcvr errorCode switched |
  	<inline: true>
  
  	methodHeader := self rawHeaderOf: newMethod.
  	self assert: (self isCogMethodReference: methodHeader) not.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  
  	rcvr := self internalStackValue: argumentCount. "could new rcvr be set at point of send?"
+ 	self assert: (objectMemory isOopForwarded: rcvr) not.
  
  	self internalPush: localIP.
  	self internalPush: localFP.
  	localFP := localSP.
  	self internalPush: newMethod.
  	self setMethod: newMethod methodHeader: methodHeader.
  	self internalPush: objectMemory nilObject. "FxThisContext field"
  	self internalPush: (self
  						encodeFrameFieldHasContext: false
  						isBlock: false
  						numArgs: (self argumentCountOfMethodHeader: methodHeader)).
  	self internalPush: 0. "FoxIFSavedIP"
  	self internalPush: rcvr.
  
  	"Initialize temps..."
  	argumentCount + 1 to: numTemps do:
  		[:i | self internalPush: objectMemory nilObject].
  
  	"-1 to account for pre-increment in fetchNextBytecode"
  	localIP := self pointerForOop: (self initialPCForHeader: methodHeader method: newMethod) - 1.
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
  		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  		 localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
  		 primFailCode ~= 0 ifTrue:
  			[(objectMemory byteAt: localIP + 1)
  			  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self internalStackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
  			 primFailCode := 0]].
  
  	self assert: (self frameNumArgs: localFP) == argumentCount.
  	self assert: (self frameIsBlockActivation: localFP) not.
  	self assert: (self frameHasContext: localFP) not.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	localSP < stackLimit ifTrue:
  		[self externalizeIPandSP.
  		 switched := self handleStackOverflowOrEventAllowContextSwitch:
  						(self canContextSwitchIfActivating: newMethod header: methodHeader).
  		 self returnToExecutive: true postContextSwitch: switched.
  		 self internalizeIPandSP]!

Item was changed:
  ----- Method: CoInterpreter>>justActivateNewMethod (in category 'message sending') -----
  justActivateNewMethod
  	| methodHeader activateCogMethod cogMethod numArgs numTemps rcvr errorCode initialIP |
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #initialIP type: #usqInt>
  	<inline: true>
  	methodHeader := self rawHeaderOf: newMethod.
  	(activateCogMethod := self isCogMethodReference: methodHeader) ifTrue:
  		[cogMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
  		 methodHeader := cogMethod methodHeader].
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  	numArgs := self argumentCountOfMethodHeader: methodHeader.
  
  	rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
+ 	self assert: (objectMemory isOopForwarded: rcvr) not.
  
  	(activateCogMethod
  	and: [instructionPointer >= objectMemory startOfMemory]) ifTrue:
  		[self iframeSavedIP: framePointer put: instructionPointer.
  		 instructionPointer := cogit ceReturnToInterpreterPC].
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	initialIP := self initialPCForHeader: methodHeader method: newMethod.
  	activateCogMethod
  		ifTrue:
  			[self push: cogMethod asUnsignedInteger.
  			 self push: objectMemory nilObject. "FoxThisContext field"
  			 instructionPointer := cogMethod asUnsignedInteger + cogMethod stackCheckOffset]
  		ifFalse:
  			[self push: newMethod.
  			 self setMethod: newMethod methodHeader: methodHeader.
  			 self push: objectMemory nilObject. "FoxThisContext field"
  			 self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
  			 self push: 0. "FoxIFSavedIP"
  			 instructionPointer := initialIP - 1].
  	self push: rcvr.
  
  	"clear remaining temps to nil"
  	numArgs+1 to: numTemps do:
  		[:i | self push: objectMemory nilObject].
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
  		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  		 initialIP := initialIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
  		activateCogMethod ifFalse:
  			[instructionPointer := initialIP].
  		 primFailCode ~= 0 ifTrue:
  			[(objectMemory byteAt: initialIP + 1)
  			  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
  			 primFailCode := 0]].
  
  	^methodHeader!

Item was changed:
  ----- Method: StackInterpreter>>internalActivateNewMethod (in category 'message sending') -----
  internalActivateNewMethod
  	| methodHeader numTemps rcvr errorCode |
  	<inline: true>
  
  	methodHeader := self headerOf: newMethod.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  
  	rcvr := self internalStackValue: argumentCount. "could new rcvr be set at point of send?"
+ 	self assert: (objectMemory isOopForwarded: rcvr) not.
  
  	self internalPush: localIP.
  	self internalPush: localFP.
  	localFP := localSP.
  	self internalPush: newMethod.
  	self setMethod: newMethod methodHeader: methodHeader.
  	self internalPush: (self
  						encodeFrameFieldHasContext: false
  						isBlock: false
  						numArgs: (self argumentCountOfMethodHeader: methodHeader)).
  	self internalPush: objectMemory nilObject. "FxThisContext field"
  	self internalPush: rcvr.
  
  	"Initialize temps..."
  	argumentCount + 1 to: numTemps do:
  		[:i | self internalPush: objectMemory nilObject].
  
  	"-1 to account for pre-increment in fetchNextBytecode"
  	localIP := self pointerForOop: (self initialPCForHeader: methodHeader method: newMethod) - 1.
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
  		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  		 localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
  		 primFailCode ~= 0 ifTrue:
  			[(objectMemory byteAt: localIP + 1)
  			  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self internalStackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
  			 primFailCode := 0]].
  
  	self assert: (self frameNumArgs: localFP) == argumentCount.
  	self assert: (self frameIsBlockActivation: localFP) not.
  	self assert: (self frameHasContext: localFP) not.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	localSP < stackLimit ifTrue:
  		[self externalizeIPandSP.
  		 self handleStackOverflowOrEventAllowContextSwitch: (self canContextSwitchIfActivating: newMethod header: methodHeader).
  		 self internalizeIPandSP]!

Item was changed:
  ----- Method: StackInterpreter>>justActivateNewMethod (in category 'message sending') -----
  justActivateNewMethod
  	| methodHeader numArgs numTemps rcvr errorCode |
  	<inline: true>
  	methodHeader := self headerOf: newMethod.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  	numArgs := self argumentCountOfMethodHeader: methodHeader.
  
  	rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
+ 	self assert: (objectMemory isOopForwarded: rcvr) not.
  
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: newMethod.
  	self setMethod: newMethod methodHeader: methodHeader.
  	self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
  	self push: objectMemory nilObject. "FxThisContext field"
  	self push: rcvr.
  
  	"clear remaining temps to nil"
  	numArgs+1 to: numTemps do:
  		[:i | self push: objectMemory nilObject].
  
  	instructionPointer := (self initialPCForHeader: methodHeader method: newMethod) - 1.
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
  		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  		 instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader).
  		 primFailCode ~= 0 ifTrue:
  			[(objectMemory byteAt: instructionPointer + 1)
  			  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
  			 primFailCode := 0]].
  
  	^methodHeader!

Item was changed:
  ----- Method: StackInterpreter>>postBecomeAction: (in category 'object memory support') -----
  postBecomeAction: theBecomeEffectsFlags
+ 	"Insulate the stack zone from the effects of a become.
+ 	 All receivers must be unfollowed for two reasons:
+ 		1. inst var access is direct with no read barrier
+ 		2. super sends (always to the receiver) have no class check and so don't trap
+ 		   for forwarded receivers.
+ 	 Methods must be unfollowed since bytecode access is direct with no read barrier.
+ 	 But this only needs to be done if the becomeEffectsFlags indicate that a
+ 	 CompiledMethod was becommed.
+ 	 The sceduler state must be followed, but only if the becomeEffectsFlags indicate
+ 	 that a pointer object was becommed."
+ 	self followForwardingPointersInStackZone: theBecomeEffectsFlags.
  	theBecomeEffectsFlags ~= 0 ifTrue:
+ 		[(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
- 		[self followForwardingPointersInStackZone: theBecomeEffectsFlags.
- 		 (theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  			[self followForwardedMethodsInMethodCache.
  			 self followForwardedMethodsInMethodZone]. "for CoInterpreter"
  		 self followForwardingPointersInScheduler]!

Item was changed:
  ----- Method: StackInterpreter>>slowPrimitiveResponse (in category 'primitive support') -----
  slowPrimitiveResponse
  	"Invoke a normal (non-quick) primitive.
  	 Called under the assumption that primFunctionPointer has been preloaded."
  	| nArgs savedFramePointer savedStackPointer |
  	<inline: true>
  	<asmLabel: false>
  	<var: #savedFramePointer type: #'char *'>
  	<var: #savedStackPointer type: #'char *'>
+ 	self assert: (objectMemory isOopForwarded: (self stackValue: argumentCount)) not.
  	FailImbalancedPrimitives ifTrue:
  		[nArgs := argumentCount.
  		 savedStackPointer := stackPointer.
  		 savedFramePointer := framePointer].
  	self initPrimCall.
  	self dispatchFunctionPointer: primitiveFunctionPointer.
  	"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.  Retry the primitive if any are found."
  	(objectMemory hasSpurMemoryManagerAPI
  	 and: [self successful not
  	 and: [(objectMemory isOopCompiledMethod: newMethod)
  	 and: [self checkForAndFollowForwardedPrimitiveState]]]) ifTrue:
  		[self initPrimCall.
  		 self dispatchFunctionPointer: primitiveFunctionPointer].
  	(FailImbalancedPrimitives
  	and: [self successful
  	and: [framePointer = savedFramePointer
  	and: [(self isMachineCodeFrame: framePointer) not]]]) ifTrue:"Don't fail if primitive has done something radical, e.g. perform:"
  		[stackPointer ~= (savedStackPointer + (nArgs * BytesPerWord)) ifTrue:
  			[self flag: 'Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context'.
  			 "This is necessary but insufficient; the result may still have been written to the stack.
  			   At least we'll know something is wrong."
  			 stackPointer := savedStackPointer.
  			 self failUnbalancedPrimitive]].
  	"If we are profiling, take accurate primitive measures"
  	nextProfileTick > 0 ifTrue:
  		[self checkProfileTick: newMethod].
  	^self successful!



More information about the Vm-dev mailing list