[Vm-dev] VM Maker: VMMaker.oscog-rmacnak.1378.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jun 25 03:29:30 UTC 2015


Ryan Macnak uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-rmacnak.1378.mcz

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

Name: VMMaker.oscog-rmacnak.1378
Author: rmacnak
Time: 24 June 2015, 8:28:02.92 pm
UUID: 75a23d0a-2813-46a9-947d-63c53f91f078
Ancestors: VMMaker.oscog-eem.1377

Do proper lookups for self and super send misses from cogged code.

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

Item was changed:
  ----- Method: CoInterpreter>>ceDynamicSuperSend:to:numArgs: (in category 'trampolines') -----
  ceDynamicSuperSend: selector to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked dynamic super send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
  		
  	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
  	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
  	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
  	because we're out of code memory.
  
  	Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	depending on whether the target method is cogged or not."
  	<api>
  	<option: #NewspeakVM>
+ 	| classTag errSelIdx cogMethod |
- 	| classTag errSelIdx cogMethod mClassMixin mixinApplication |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #newCogMethod type: #'CogMethod *'>
+ 
- 	"self printExternalHeadFrame"
- 	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self sendBreakpoint: selector receiver: rcvr.
+ 
+ 	classTag := objectMemory fetchClassTagOf: rcvr.
+ 	messageSelector := selector.
- 	mClassMixin := self mMethodClass.
- 	mixinApplication := self 
- 							findApplicationOfTargetMixin: mClassMixin
- 							startingAtBehavior: (objectMemory fetchClassOf: rcvr).
- 	self assert: (objectMemory lengthOf: mixinApplication) > (InstanceSpecificationIndex + 1).
- 	classTag := objectMemory classTagForClass: (self superclassOf: mixinApplication).
  	argumentCount := numArgs.
+ 	method := (self mframeHomeMethod: framePointer) methodObject.
+ 
+ 	(self
+ 		inlineLookupInNSMethodCacheSel: messageSelector
+ 		classTag: classTag
+ 		method: method
+ 		lookupRule: LookupRuleDynamicSuper)
+ 			ifTrue:
+ 				["check for coggability because method is in the cache"
+ 				self
+ 					ifAppropriateCompileToNativeCode: newMethod
+ 					selector: selector]
+ 			ifFalse:
+ 				[(objectMemory isOopForwarded: selector) ifTrue:
+ 					[self
+ 						ceDynamicSuperSend: (self handleForwardedSelectorFaultFor: selector)
+ 						to: rcvr
+ 						numArgs: numArgs.
+ 					self unreachable].
+ 				 (objectMemory isForwardedClassTag: classTag) ifTrue:
+ 					[self
+ 						ceDynamicSuperSend: selector
+ 						to: (self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc")
+ 						numArgs: numArgs.
+ 					self unreachable].
+ 				lkupClassTag := classTag.
+ 				errSelIdx := self lookupDynamicSuperSendNoMNU: rcvr.
+ 				errSelIdx ~= 0 ifTrue:
+ 					[self assert: errSelIdx == SelectorDoesNotUnderstand.
+ 					self handleMNU: errSelIdx 
+ 						InMachineCodeTo: rcvr
+ 						classForMessage: (objectMemory classForClassTag: classTag).
+ 					self unreachable].
+ 				self addNewMethodToNSCache: LookupRuleSelf].
+ 
- 	(self lookupInMethodCacheSel: selector classTag: classTag)
- 		ifTrue:"check for coggability because method is in the cache"
- 			[self
- 				ifAppropriateCompileToNativeCode: newMethod
- 				selector: selector]
- 		ifFalse:
- 			[(objectMemory isOopForwarded: selector) ifTrue:
- 				[^self
- 					ceDynamicSuperSend: (self handleForwardedSelectorFaultFor: selector)
- 					to: rcvr
- 					numArgs: numArgs].
- 			 (objectMemory isForwardedClassTag: classTag) ifTrue:
- 				[^self
- 					ceDynamicSuperSend: selector
- 					to: (self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc")
- 					numArgs: numArgs].
- 			 messageSelector := selector.
- 			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
- 				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: (objectMemory classForClassTag: classTag).
- 				self assert: false "NOTREACHED"]].
  	"Method found and has a cog method.  Attempt to link to it."
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[cogMethod := self cogMethodOf: newMethod.
  		 cogMethod selector = objectMemory nilObject
  			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
  			ifFalse:
  				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the correct
  				  selector.  If not, try and compile a new method with the correct selector."
  				 cogMethod selector ~= selector ifTrue:
  					[(cogit cog: newMethod selector: selector) ifNotNil:
  						[:newCogMethod| cogMethod := newCogMethod]]].
  		 cogMethod selector = selector ifTrue:
  			[cogit
  				linkSendAt: (stackPages longAt: stackPointer)
  				in: (self mframeHomeMethod: framePointer)
  				to: cogMethod
  				offset: cogit entryOffset
  				receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
+ 		 self unreachable].
- 		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
+ 	self interpretMethodFromMachineCode.
+ 	self unreachable.!
- 	^self interpretMethodFromMachineCode
- 	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceSelfSend:to:numArgs: (in category 'trampolines') -----
  ceSelfSend: selector to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked self send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
  		
  	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
  	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
  	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
  	because we're out of code memory.
  
  	Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	depending on whether the target method is cogged or not."
  	<api>
  	<option: #NewspeakVM>
  	| classTag errSelIdx cogMethod |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #newCogMethod type: #'CogMethod *'>
+ 
- 	"self printExternalHeadFrame"
- 	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self sendBreakpoint: selector receiver: rcvr.
+ 
  	classTag := objectMemory fetchClassTagOf: rcvr.
+ 	messageSelector := selector.
  	argumentCount := numArgs.
+ 	method := (self mframeHomeMethod: framePointer) methodObject.
+ 
+ 	(self
+ 		inlineLookupInNSMethodCacheSel: messageSelector
+ 		classTag: classTag
+ 		method: method
+ 		lookupRule: LookupRuleSelf)
+ 			ifTrue:
+ 				["check for coggability because method is in the cache"
+ 				self
+ 					ifAppropriateCompileToNativeCode: newMethod
+ 					selector: selector]
+ 			ifFalse:
+ 				[(objectMemory isOopForwarded: selector) ifTrue:
+ 					[self
+ 						ceSelfSend: (self handleForwardedSelectorFaultFor: selector)
+ 						to: rcvr
+ 						numArgs: numArgs.
+ 					self unreachable].
+ 			 	(objectMemory isForwardedClassTag: classTag) ifTrue:
+ 					[self
+ 						ceSelfSend: selector
+ 						to: (self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc")
+ 						numArgs: numArgs.
+ 					self unreachable].
+ 				lkupClassTag := classTag.
+ 				errSelIdx := self lookupOuterSendNoMNU: rcvr depth: 0.
+ 				errSelIdx ~= 0 ifTrue:
+ 					[self assert: errSelIdx == SelectorDoesNotUnderstand.
+ 					self handleMNU: errSelIdx 
+ 						InMachineCodeTo: rcvr
+ 						classForMessage: (objectMemory classForClassTag: classTag).
+ 					self unreachable].
+ 				self addNewMethodToNSCache: LookupRuleSelf].
+ 
- 	(self lookupInMethodCacheSel: selector classTag: classTag)
- 		ifTrue:"check for coggability because method is in the cache"
- 			[self
- 				ifAppropriateCompileToNativeCode: newMethod
- 				selector: selector]
- 		ifFalse:
- 			[(objectMemory isOopForwarded: selector) ifTrue:
- 				[^self
- 					ceSelfSend: (self handleForwardedSelectorFaultFor: selector)
- 					to: rcvr
- 					numArgs: numArgs].
- 			 (objectMemory isForwardedClassTag: classTag) ifTrue:
- 				[^self
- 					ceSelfSend: selector
- 					to: (self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc")
- 					numArgs: numArgs].
- 			 messageSelector := selector.
- 			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
- 				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: (objectMemory classForClassTag: classTag).
- 				self assert: false "NOTREACHED"]].
  	"Method found and has a cog method.  Attempt to link to it."
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[cogMethod := self cogMethodOf: newMethod.
  		 cogMethod selector = objectMemory nilObject
  			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
  			ifFalse:
  				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the correct
  				  selector.  If not, try and compile a new method with the correct selector."
  				 cogMethod selector ~= selector ifTrue:
  					[(cogit cog: newMethod selector: selector) ifNotNil:
  						[:newCogMethod| cogMethod := newCogMethod]]].
  		 cogMethod selector = selector ifTrue:
  			[cogit
  				linkSendAt: (stackPages longAt: stackPointer)
  				in: (self mframeHomeMethod: framePointer)
  				to: cogMethod
  				offset: cogit entryOffset
  				receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
+ 		 self unreachable].
- 		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
+ 	self interpretMethodFromMachineCode.
+ 	self unreachable.!
- 	^self interpretMethodFromMachineCode
- 	"NOTREACHED"!

Item was removed:
- ----- Method: CoInterpreter>>unreachable (in category 'cog jit support') -----
- unreachable
- 	self error: 'UNREACHABLE'.!

Item was changed:
  ----- Method: Cogit>>ceSICMiss: (in category 'in-line cacheing') -----
  ceSICMiss: receiver
  	"An in-line cache check in a method has failed.  The failing entry check has jumped
  	 to the ceMethodAbort abort call at the start of the method which has called this routine.
  	 If possible allocate a closed PIC for the current and existing classes.
  	 The stack looks like:
  			receiver
  			args
  			sender return address
  	  sp=>	ceMethodAbort call return address
  	 So we can find the method that did the failing entry check at
  		ceMethodAbort call return address - missOffset
  	 and we can find the send site from the outer return address."
  	<api>
  	| pic innerReturn outerReturn entryPoint targetMethod newTargetMethodOrNil errorSelectorOrNil cacheTag extent result |
  	<var: #pic type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #callerMethod type: #'CogMethod *'>
  	"Whether we can relink to a PIC or not we need to pop off the inner return and identify the target method."
  	innerReturn := coInterpreter popStack asUnsignedInteger.
  	targetMethod := self cCoerceSimple: innerReturn - missOffset to: #'CogMethod *'.
  	(objectMemory isOopForwarded: receiver) ifTrue:
  		[^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	outerReturn := coInterpreter stackTop asUnsignedInteger.
  	self assert: (outerReturn between: methodZoneBase and: methodZone freeStart).
  	entryPoint := backEnd callTargetFromReturnAddress: outerReturn.
  
  	self assert: targetMethod selector ~= objectMemory nilObject.
  	self cppIf: NewspeakVM ifTrue:
  		[| callerMethod annotation |
  		 self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
  		 callerMethod := coInterpreter mframeHomeMethod: coInterpreter getFramePointer.
  		 self assert: (outerReturn
  						between: callerMethod asUnsignedInteger + cmNoCheckEntryOffset
  						and: callerMethod asUnsignedInteger + callerMethod blockSize).
  		 annotation := self annotationForMcpc: outerReturn in: callerMethod.
  		 self assert: annotation >= IsSendCall.
  		 "Avoid the effort of implementing PICs for the relatively high dynamic frequency
  		  self send and simply rebind the send site (for now)."
  		 annotation = IsNSSelfSend ifTrue:
+ 			[coInterpreter
- 			[^coInterpreter
  				ceSelfSend: targetMethod selector
  				to: receiver
+ 				numArgs: targetMethod cmNumArgs.
+ 			self unreachable].
- 				numArgs: targetMethod cmNumArgs].
  		 "Avoid the effort of implementing PICs for the relatively low dynamic frequency
  		  dynamic super send and simply rebind the send site."
  		 annotation = IsNSDynamicSuperSend ifTrue:
+ 			[coInterpreter
- 			[^coInterpreter
  				ceDynamicSuperSend: targetMethod selector
  				to: receiver
+ 				numArgs: targetMethod cmNumArgs.
+ 			self unreachable]].
- 				numArgs: targetMethod cmNumArgs]].
  	self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
  
  	self lookup: targetMethod selector
  		for: receiver
  		methodAndErrorSelectorInto:
  			[:method :errsel|
  			newTargetMethodOrNil := method.
  			errorSelectorOrNil := errsel].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  	((errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [(backEnd inlineCacheTagAt: outerReturn) = self picAbortDiscriminatorValue
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]]) ifTrue:
  		[result := self patchToOpenPICFor: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
  		 ^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	"See if an Open PIC is already available."
  	pic := methodZone openPICWithSelector: targetMethod selector.
  	pic isNil ifTrue:
  		["otherwise attempt to create a closed PIC for the two cases."
  		 pic := self cogPICSelector: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					Case0Method: targetMethod
  					Case1Method: newTargetMethodOrNil
  					tag: cacheTag
  					isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
  		 (pic asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory.
  			  Continue as if this is an unlinked send."
  			 pic asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  		 processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize].
  	"Relink the send site to the pic.  If to an open PIC then reset the cache tag to the selector,
  	 for the benefit of the cacheTag assert check in checkIfValidObjectRef:pc:cogMethod:."
  	extent := pic cmType = CMOpenPIC
  				ifTrue:
  					[backEnd
  						rewriteInlineCacheAt: outerReturn
  						tag: targetMethod selector
  						target: pic asInteger + cmEntryOffset]
  				ifFalse:
  					[backEnd
  						rewriteCallAt: outerReturn
  						target: pic asInteger + cmEntryOffset].
  	processor flushICacheFrom: outerReturn asUnsignedInteger - extent to: outerReturn asUnsignedInteger.
  	"Jump back into the pic at its entry in case this is an MNU (newTargetMethodOrNil is nil)"
  	coInterpreter
  		executeCogPIC: pic
  		fromLinkedSendWithReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

Item was added:
+ ----- Method: StackInterpreter>>lookupDynamicSuperSendNoMNU: (in category 'message sending') -----
+ lookupDynamicSuperSendNoMNU: methodReceiver
+ 	"Do the full lookup for a Newspeak super send.
+ 	IN: messageSelector
+ 	IN: argumentCount
+ 	OUT: localAbsentReceiver
+ 	OUT: newMethod
+ 	OUT: primitiveIndex
+ 	RESULT: 0 or SelectorDoesNotUnderstand"
+ 
+ 	| methodMixin methodMixinApplication |
+ 	localAbsentReceiver := methodReceiver.
+ 	methodMixin := self methodClassOf: method.
+ 	methodMixinApplication := self
+ 		findApplicationOfTargetMixin: methodMixin
+ 		startingAtBehavior: (objectMemory fetchClassOf: localAbsentReceiver).
+ 	lkupClass := self superclassOf: methodMixinApplication. "For use by MNU"
+ 	^self lookupProtectedNoMNU: messageSelector startingAt: lkupClass rule: LookupRuleDynamicSuper!

Item was added:
+ ----- Method: VMClass>>unreachable (in category 'debug support') -----
+ unreachable
+ 	self error: 'UNREACHABLE'!



More information about the Vm-dev mailing list