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

commits at source.squeak.org commits at source.squeak.org
Thu Jan 9 19:33:01 UTC 2020


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

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

Name: VMMaker.oscog-eem.2654
Author: eem
Time: 9 January 2020, 11:32:44.761732 am
UUID: 962eb13d-1670-4dbd-a3a0-24e2496fd34a
Ancestors: VMMaker.oscog-eem.2653

CoInterpreter:
Fix a major policy violation.  To make doits fast I had made CoInterpreter>>executeNewMethod always JIT.  But executeNewMethod is used in many more places than primitiveExecuteMethod[ArgsArray], which meant that methods were being over-eagerly jitted (such as in perform:).  The Cog policy is only to jit on second use, or several loop iterations, except for executeMewthod, where we need eager jitting to have jit speed doit performance.

So introduce executeNewMethodJitting, using it in primitiveExecuteMethod[ArgsArray] to do what it says, and revert executeNewMethod to not jit (if the method is already jitted it will of course run the jit version).

Rename activateCoggedNewMethod: to the more comprehensible activateNewCogMethod:inInterpreter:, requiring all clients to pass in the newMethod methodHeader, which is the pointer to the cogMethod.

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

Item was removed:
- ----- Method: CoInterpreter>>activateCoggedNewMethod: (in category 'message sending') -----
- activateCoggedNewMethod: inInterpreter
- 	"Activate newMethod when newMethod has been cogged, i.e. create a machine-code frame and (re)enter machine-code."
- 	| methodHeader cogMethod rcvr numTemps switched |
- 	<var: #cogMethod type: #'CogMethod *'>
- 
- 	methodHeader := self rawHeaderOf: newMethod.
- 	self assert: (self isCogMethodReference: methodHeader).
- 
- 	cogMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
- 	methodHeader := cogMethod methodHeader.
- 	rcvr := self stackValue: cogMethod cmNumArgs. "could new rcvr be set at point of send?"
- 	self push: instructionPointer.
- 	cogMethod stackCheckOffset = 0 ifTrue:
- 		["frameless method; nothing to activate..."
- 		 cogit numRegArgs > 0 ifTrue: "dont use and: so as to get Slang to inline cogit numRegArgs > 0"
- 			[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
- 				[self callRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr]].
- 		 self push: cogMethod asInteger + cogit noCheckEntryOffset.
- 		 self push: rcvr.
- 		 cogit ceCallCogCodePopReceiverReg.
- 		 self error: 'should not be reached'].
- 	self push: framePointer.
- 	framePointer := stackPointer.
- 	self push: cogMethod asInteger.
- 	self push: objectMemory nilObject. "FxThisContext field"
- 	self push: rcvr.
- 
- 	"clear remaining temps to nil"
- 	numTemps := self temporaryCountOfMethodHeader: methodHeader.
- 	cogMethod cmNumArgs + 1 to: numTemps do:
- 		[:i | self push: objectMemory nilObject].
- 
- 	((self methodHeaderHasPrimitive: methodHeader)
- 	 and: [primFailCode ~= 0]) ifTrue:
- 		[self reapAndResetErrorCodeTo: stackPointer header: methodHeader].
- 
- 	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
- 	stackPointer >= stackLimit ifTrue:
- 		[self assert: cogMethod stackCheckOffset > cogit noCheckEntryOffset.
- 		 self push: cogMethod asInteger + cogMethod stackCheckOffset.
- 		 self push: rcvr.
- 		 cogit ceEnterCogCodePopReceiverReg.
- 		 self error: 'should not be reached'].
- 	instructionPointer := cogMethod asInteger + cogMethod stackCheckOffset.
- 	switched := self handleStackOverflowOrEventAllowContextSwitch: (self canContextSwitchIfActivating: newMethod header: methodHeader).
- 	self returnToExecutive: inInterpreter postContextSwitch: switched!

Item was added:
+ ----- Method: CoInterpreter>>activateNewCogMethod:inInterpreter: (in category 'message sending') -----
+ activateNewCogMethod: cogMethod inInterpreter: inInterpreter
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	"Activate newMethod when newMethod has been cogged, i.e. create a machine-code frame and (re)enter machine-code."
+ 	| methodHeader rcvr numTemps switched |
+ 	self assert: (self rawHeaderOf: newMethod) = cogMethod asInteger.
+ 	methodHeader := cogMethod methodHeader.
+ 	rcvr := self stackValue: cogMethod cmNumArgs. "could new rcvr be set at point of send?"
+ 	self push: instructionPointer.
+ 	cogMethod stackCheckOffset = 0 ifTrue:
+ 		["frameless method; nothing to activate..."
+ 		 cogit numRegArgs > 0 ifTrue: "dont use and: so as to get Slang to inline cogit numRegArgs > 0"
+ 			[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
+ 				[self callRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr]].
+ 		 self push: cogMethod asInteger + cogit noCheckEntryOffset.
+ 		 self push: rcvr.
+ 		 cogit ceCallCogCodePopReceiverReg.
+ 		 self error: 'should not be reached'].
+ 	self push: framePointer.
+ 	framePointer := stackPointer.
+ 	self push: cogMethod asInteger.
+ 	self push: objectMemory nilObject. "FxThisContext field"
+ 	self push: rcvr.
+ 
+ 	"clear remaining temps to nil"
+ 	numTemps := self temporaryCountOfMethodHeader: methodHeader.
+ 	cogMethod cmNumArgs + 1 to: numTemps do:
+ 		[:i | self push: objectMemory nilObject].
+ 
+ 	((self methodHeaderHasPrimitive: methodHeader)
+ 	 and: [primFailCode ~= 0]) ifTrue:
+ 		[self reapAndResetErrorCodeTo: stackPointer header: methodHeader].
+ 
+ 	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
+ 	stackPointer >= stackLimit ifTrue:
+ 		[self assert: cogMethod stackCheckOffset > cogit noCheckEntryOffset.
+ 		 self push: cogMethod asInteger + cogMethod stackCheckOffset.
+ 		 self push: rcvr.
+ 		 cogit ceEnterCogCodePopReceiverReg.
+ 		 self error: 'should not be reached'].
+ 	instructionPointer := cogMethod asInteger + cogMethod stackCheckOffset.
+ 	switched := self handleStackOverflowOrEventAllowContextSwitch: (self canContextSwitchIfActivating: newMethod header: methodHeader).
+ 	self returnToExecutive: inInterpreter postContextSwitch: switched!

Item was changed:
  ----- Method: CoInterpreter>>ceActivateFailingPrimitiveMethod: (in category 'enilopmarts') -----
  ceActivateFailingPrimitiveMethod: aPrimitiveMethod
  	"An external call or FFI primitive has failed.  Build the frame and
  	 activate as appropriate.  Enter either the interpreter or machine
  	 code depending on whether aPrimitiveMethod has been or is still
  	 cogged.  Note that we could always interpret but want the efficiency
  	 of executing machine code if it is available."
  	<api>
  	| methodHeader result |
  	self assert: primFailCode ~= 0.
  	self assert: newMethod = aPrimitiveMethod.
  	"If we're on Spur, retry the primitive, if appropriate,
  	 returning if successful after retry."
  	objectMemory hasSpurMemoryManagerAPI ifTrue:
  		[self retryPrimitiveOnFailure.
  		 self successful ifTrue:
  			[result := self stackTop.
  			 self stackTopPut: instructionPointer.
  			 self push: result.
  			 cogit ceEnterCogCodePopReceiverReg]].
  	methodHeader := self rawHeaderOf: aPrimitiveMethod.
  	(self isCogMethodReference: methodHeader)
+ 		ifTrue: [self activateNewCogMethod: (self cCoerceSimple: methodHeader to: #'CogMethod *') inInterpreter: false]
- 		ifTrue: [self activateCoggedNewMethod: false]
  		ifFalse: [self activateNewMethod]!

Item was changed:
  ----- Method: CoInterpreter>>executeNewMethod (in category 'message sending') -----
  executeNewMethod
  	"Execute newMethod - either primitiveFunctionPointer must be set directly
  	 (i.e. from primitiveExecuteMethod et al), or it would have been set probing
+ 	 the method cache (i.e. primitivePerform et al)."
- 	 the method cache (i.e. primitivePerform et al).
- 	 Eagerly compile it if appropriate so that doits are fast."
  	| methodHeader inInterpreter |
  	inInterpreter := instructionPointer >= objectMemory startOfMemory.
  	primitiveFunctionPointer ~= 0 ifTrue:
  		[self isPrimitiveFunctionPointerAnIndex ifTrue:
  			[self externalQuickPrimitiveResponse.
  			 self return: self popStack toExecutive: inInterpreter.
  			 ^nil].
  		 "slowPrimitiveResponse may of course context-switch.  If so we must reenter the
  		  new process appopriately, returning only if we've reached here directly from the
  		  interpreter and have found an interpreter frame.  The instructionPointer tells us
  		  from whence we came."
  		 self slowPrimitiveResponse ifTrue:
  			[self return: self popStack toExecutive: inInterpreter.
  			 ^nil]].
- 	"Eagerly compile it if appropriate so that doits are fast."
  	methodHeader := self rawHeaderOf: newMethod.
- 	(self isCogMethodReference: methodHeader) ifFalse:
- 		[(self methodWithHeaderShouldBeCogged: methodHeader)
- 			ifTrue:
- 				[cogit cog: newMethod selector: objectMemory nilObject.
- 				 methodHeader := self rawHeaderOf: newMethod]
- 			ifFalse: [self maybeFlagMethodAsInterpreted: newMethod]].
  	"if not primitive, or primitive failed, activate the method"
  	(self isCogMethodReference: methodHeader)
  		ifTrue:
  			[instructionPointer asUnsignedInteger >= objectMemory startOfMemory ifTrue:
  				[self iframeSavedIP: framePointer put: instructionPointer asInteger.
  				 instructionPointer := cogit ceReturnToInterpreterPC].
+ 			self activateNewCogMethod: (self cCoerceSimple: methodHeader to: #'CogMethod *') inInterpreter: inInterpreter]
- 			self activateCoggedNewMethod: inInterpreter]
  		ifFalse:
  			[self activateNewMethod]!

Item was added:
+ ----- Method: CoInterpreter>>executeNewMethodJitting (in category 'message sending') -----
+ executeNewMethodJitting
+ 	"Execute newMethod - either primitiveFunctionPointer must be set directly
+ 	 (i.e. from primitiveExecuteMethod et al), or it would have been set probing
+ 	 the method cache (i.e. primitivePerform et al).
+ 	 Eagerly compile it if appropriate so that doits are fast."
+ 	| methodHeader inInterpreter |
+ 	inInterpreter := instructionPointer >= objectMemory startOfMemory.
+ 	primitiveFunctionPointer ~= 0 ifTrue:
+ 		[self isPrimitiveFunctionPointerAnIndex ifTrue:
+ 			[self externalQuickPrimitiveResponse.
+ 			 self return: self popStack toExecutive: inInterpreter.
+ 			 ^nil].
+ 		 "slowPrimitiveResponse may of course context-switch.  If so we must reenter the
+ 		  new process appopriately, returning only if we've reached here directly from the
+ 		  interpreter and have found an interpreter frame.  The instructionPointer tells us
+ 		  from whence we came."
+ 		 self slowPrimitiveResponse ifTrue:
+ 			[self return: self popStack toExecutive: inInterpreter.
+ 			 ^nil]].
+ 	"Eagerly compile it if appropriate so that doits are fast."
+ 	methodHeader := self rawHeaderOf: newMethod.
+ 	(self isCogMethodReference: methodHeader) ifFalse:
+ 		[(self methodWithHeaderShouldBeCogged: methodHeader)
+ 			ifTrue:
+ 				[cogit cog: newMethod selector: objectMemory nilObject.
+ 				 methodHeader := self rawHeaderOf: newMethod]
+ 			ifFalse: [self maybeFlagMethodAsInterpreted: newMethod]].
+ 	"if not primitive, or primitive failed, activate the method"
+ 	(self isCogMethodReference: methodHeader)
+ 		ifTrue:
+ 			[instructionPointer asUnsignedInteger >= objectMemory startOfMemory ifTrue:
+ 				[self iframeSavedIP: framePointer put: instructionPointer asInteger.
+ 				 instructionPointer := cogit ceReturnToInterpreterPC].
+ 			self activateNewCogMethod: (self cCoerceSimple: methodHeader to: #'CogMethod *') inInterpreter: inInterpreter]
+ 		ifFalse:
+ 			[self activateNewMethod]!

Item was changed:
  ----- Method: CoInterpreter>>internalExecuteNewMethod (in category 'message sending') -----
  internalExecuteNewMethod
  	<inline: true>
  	"For interpreter performance and to ease the objectAsMethod implementation eagerly
  	 evaluate the primtiive, i.e. if the method is cogged and has a primitive /do not/ evaluate
  	 the machine code primitive, just evaluate primitiveFunctionPointer directly."
+ 	| succeeded methodHeader |
  	primitiveFunctionPointer ~= 0 ifTrue:
+ 		[self isPrimitiveFunctionPointerAnIndex ifTrue:
- 		[| succeeded |
- 		 self isPrimitiveFunctionPointerAnIndex ifTrue:
  			[^self internalQuickPrimitiveResponse].
  		 "slowPrimitiveResponse may of course context-switch.  If so we must reenter the
  		  new process appropriately, returning only if we've found an interpreter frame."
  		 self externalizeIPandSP.
  		 succeeded := self slowPrimitiveResponse.
  		 instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
  			[instructionPointer := self iframeSavedIP: framePointer].
  		 self internalizeIPandSP.
  		 succeeded ifTrue:
  			[self return: self popStack toExecutive: true.
  			 self browserPluginReturnIfNeeded.
  			^nil]].
+ 	methodHeader := self rawHeaderOf: newMethod.
  	"if not primitive, or primitive failed, activate the method"
+ 	(self isCogMethodReference: methodHeader) ifFalse:
+ 		[^self internalActivateNewMethod].
+ 	self iframeSavedIP: localFP put: localIP asInteger.
+ 	instructionPointer := cogit ceReturnToInterpreterPC.
+ 	self externalizeFPandSP.
+ 	"THis may cintext switch and hence return..."
+ 	self activateNewCogMethod: (self cCoerceSimple: methodHeader to: #'CogMethod *') inInterpreter: true.
+ 	"Hence this si reachable..."
+ 	self internalizeIPandSP!
- 	(self methodHasCogMethod: newMethod)
- 		ifTrue: [self iframeSavedIP: localFP put: localIP asInteger.
- 				instructionPointer := cogit ceReturnToInterpreterPC.
- 				self externalizeFPandSP.
- 				self activateCoggedNewMethod: true.
- 				self internalizeIPandSP]
- 		ifFalse: [self internalActivateNewMethod]!

Item was added:
+ ----- Method: CoInterpreter>>primitiveExecuteMethod (in category 'control primitives') -----
+ primitiveExecuteMethod
+ 	"receiver, args, then method are on top of stack. Execute method against receiver and args.
+ 	 Set primitiveFunctionPointer because no cache lookup has been done for the method, and
+ 	 hence primitiveFunctionPointer is stale."
+ 	| methodArgument primitiveIndex |
+ 	methodArgument := self stackTop.
+ 	(objectMemory isOopCompiledMethod: methodArgument) ifFalse:
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	argumentCount - 1 = (self argumentCountOf: methodArgument) ifFalse:
+ 		[^self primitiveFailFor: PrimErrBadNumArgs].
+ 	newMethod := self popStack.
+ 	primitiveIndex := self primitiveIndexOf: newMethod.
+ 	primitiveFunctionPointer := self functionPointerFor: primitiveIndex inClass: nil.
+ 	argumentCount := argumentCount - 1.
+ 	self executeNewMethodJitting.
+ 	"Recursive xeq affects primErrorCode"
+ 	self initPrimCall!

Item was added:
+ ----- Method: CoInterpreter>>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 := 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:
+ 								VMMirror>>ifFail:object:with:executeMethod: et al"
+ 		[rcvr := self stackValue: 2.
+ 		 (argumentCount > 4
+ 		  or: [objectMemory isOopForwarded: rcvr]) ifTrue:
+ 			[^self primitiveFailFor: PrimErrUnsupported].
+ 		self stackValue: argumentCount put: rcvr]. "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 executeNewMethodJitting.
+ 	"Recursive xeq affects primErrorCode"
+ 	self initPrimCall!



More information about the Vm-dev mailing list