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

commits at source.squeak.org commits at source.squeak.org
Tue Aug 25 06:11:05 UTC 2015


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

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

Name: VMMaker.oscog-rmacnak.1443
Author: rmacnak
Time: 24 August 2015, 11:09:53.273 pm
UUID: fd1228e3-f910-43a8-b648-f197510852c5
Ancestors: VMMaker.oscog-rmacnak.1442

Further fix outer send MNU by not confusing lkupClass and lkupClassTag. Push setting lkupClassTag down to clarify it is for new cache entries.

=============== Diff against VMMaker.oscog-rmacnak.1442 ===============

Item was changed:
  ----- Method: CoInterpreter>>ceDynamicSuperSend:receiver: (in category 'trampolines') -----
  ceDynamicSuperSend: cacheAddress receiver: methodReceiver
  	"A dynamic super send cache missed."
  	| nsSendCache methodReceiverClassTag cogMethod errSelIdx |
  	<api>
  	<option: #NewspeakVM>
  	<inline: false>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	<var: #cogMethod type: #'CogMethod *'>
  
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: methodReceiver).
  	self deny: (objectMemory isOopForwarded: methodReceiver).
  
  	nsSendCache := self cCoerceSimple: cacheAddress to: #'NSSendCache *'.
  	messageSelector := nsSendCache selector.
  	argumentCount := nsSendCache numArgs.
  	method := (self mframeHomeMethod: framePointer) methodObject.
  
  	self assert: (self stackValue: argumentCount + 1 "ret addr") = methodReceiver.
  
  	methodReceiverClassTag := objectMemory fetchClassTagOf: methodReceiver.
  
  	(self
  		inlineLookupInNSMethodCacheSel: messageSelector
  		classTag: methodReceiverClassTag
  		method: method
  		lookupRule: LookupRuleDynamicSuper)
  			ifTrue:
  				[self assert: localAbsentReceiverOrZero = 0.
  				"check for coggability because method is in the cache"
  				self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
  			ifFalse:
  				[self deny: (objectMemory isOopForwarded: messageSelector).
  				self deny: (objectMemory isForwardedClassTag: methodReceiverClassTag).
- 				lkupClassTag := methodReceiverClassTag.
  				errSelIdx := self lookupDynamicSuperSendNoMNU: methodReceiver.
  				errSelIdx ~= 0 ifTrue:
  					[self assert: errSelIdx == SelectorDoesNotUnderstand.
+ 					self assert: localAbsentReceiver == methodReceiver.
  					self handleMNU: errSelIdx 
  						InMachineCodeTo: methodReceiver
+ 						classForMessage: lkupClass.
- 						classForMessage: (objectMemory classForClassTag: methodReceiverClassTag).
  					self unreachable].
+ 				lkupClassTag := methodReceiverClassTag.
  				self addNewMethodToNSCache: LookupRuleDynamicSuper].
  
  	(self maybeMethodHasCogMethod: newMethod) 
  		ifTrue: [
  			cogMethod := self cogMethodOf: newMethod.
  			cogMethod selector = objectMemory nilObject
  				ifTrue: [cogit setSelectorOf: cogMethod to: messageSelector]
  				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 ~= messageSelector ifTrue: [
  							(cogit cog: newMethod selector: messageSelector)
  								ifNotNil: [:newCogMethod | cogMethod := newCogMethod]]].
  			cogMethod selector = messageSelector
  				ifTrue:
  					[cogit
  						linkNSSendCache: nsSendCache 
  						classTag: methodReceiverClassTag
  						enclosingObject: 0
  						target: cogMethod
  						caller: self mframeHomeMethodExport]
  				ifFalse: ["Out of code memory. Fall through to interpret."].
  			instructionPointer := self popStack.
  			self executeNewMethod.
  			self unreachable].
  	instructionPointer := self popStack.
  	self interpretMethodFromMachineCode.
  	self unreachable.!

Item was changed:
  ----- Method: CoInterpreter>>ceImplicitReceiverSend:receiver: (in category 'trampolines') -----
  ceImplicitReceiverSend: cacheAddress receiver: methodReceiver
  	"An implicit receiver send cache missed."
  	| nsSendCache methodReceiverClassTag cogMethod errSelIdx |
  	<api>
  	<option: #NewspeakVM>
  	<inline: false>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	<var: #cogMethod type: #'CogMethod *'>
  
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: methodReceiver).
  	self deny: (objectMemory isOopForwarded: methodReceiver).
  
  	nsSendCache := self cCoerceSimple: cacheAddress to: #'NSSendCache *'.
  	messageSelector := nsSendCache selector.
  	argumentCount := nsSendCache numArgs.
  	method := (self mframeHomeMethod: framePointer) methodObject.
  
  	self assert: (self stackValue: argumentCount + 1 "ret addr") = methodReceiver.
  
  	methodReceiverClassTag := objectMemory fetchClassTagOf: methodReceiver.
  
  	(self
  		inlineLookupInNSMethodCacheSel: messageSelector
  		classTag: methodReceiverClassTag
  		method: method
  		lookupRule: LookupRuleImplicit)
  			ifTrue:
  				[localAbsentReceiverOrZero = 0
  					ifTrue: [localAbsentReceiver := methodReceiver]
  					ifFalse: [localAbsentReceiver := localAbsentReceiverOrZero].
  				"check for coggability because method is in the cache"
  				self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
  			ifFalse:
  				[self deny: (objectMemory isOopForwarded: messageSelector).
  				self deny: (objectMemory isForwardedClassTag: methodReceiverClassTag).
- 				lkupClassTag := methodReceiverClassTag.
  				errSelIdx := self lookupImplicitReceiverSendNoMNU: methodReceiver.
  				errSelIdx ~= 0 ifTrue:
  					[self assert: errSelIdx == SelectorDoesNotUnderstand.
+ 					self assert: localAbsentReceiver == methodReceiver.
  					self handleMNU: errSelIdx 
  						InMachineCodeTo: methodReceiver
+ 						classForMessage: lkupClass.
- 						classForMessage: (objectMemory classForClassTag: methodReceiverClassTag).
  					self unreachable].
+ 				lkupClassTag := methodReceiverClassTag.
  				self addNewMethodToNSCache: LookupRuleImplicit].
  
  	"Fix stacked receiver."
  	self stackValue: argumentCount + 1 "ret addr" put: localAbsentReceiver.
  
  	(self maybeMethodHasCogMethod: newMethod) 
  		ifTrue: [
  			cogMethod := self cogMethodOf: newMethod.
  			cogMethod selector = objectMemory nilObject
  				ifTrue: [cogit setSelectorOf: cogMethod to: messageSelector]
  				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 ~= messageSelector ifTrue: [
  							(cogit cog: newMethod selector: messageSelector)
  								ifNotNil: [:newCogMethod | cogMethod := newCogMethod]]].
  			cogMethod selector = messageSelector
  				ifTrue:
  					[cogit
  						linkNSSendCache: nsSendCache 
  						classTag: methodReceiverClassTag
  						enclosingObject: localAbsentReceiverOrZero
  						target: cogMethod
  						caller: self mframeHomeMethodExport]
  				ifFalse: ["Out of code memory. Fall through to interpret."].
  			instructionPointer := self popStack.
  			self executeNewMethod.
  			self unreachable].
  	instructionPointer := self popStack.
  	self interpretMethodFromMachineCode.
  	self unreachable.!

Item was changed:
  ----- Method: CoInterpreter>>ceOuterSend:receiver: (in category 'trampolines') -----
  ceOuterSend: cacheAddress receiver: methodReceiver
  	"An outer send cache missed."
  	| nsSendCache depth methodReceiverClassTag cogMethod errSelIdx |
  	<api>
  	<option: #NewspeakVM>
  	<inline: false>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	<var: #cogMethod type: #'CogMethod *'>
  
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: methodReceiver).
  	self deny: (objectMemory isOopForwarded: methodReceiver).
  
  	nsSendCache := self cCoerceSimple: cacheAddress to: #'NSSendCache *'.
  	messageSelector := nsSendCache selector.
  	argumentCount := nsSendCache numArgs.
  	depth := nsSendCache depth.
  	method := (self mframeHomeMethod: framePointer) methodObject.
  
  	self assert: (self stackValue: argumentCount + 1 "ret addr") = methodReceiver.
  
  	methodReceiverClassTag := objectMemory fetchClassTagOf: methodReceiver.
  
  	(self
  		inlineLookupInNSMethodCacheSel: messageSelector
  		classTag: methodReceiverClassTag
  		method: method
  		lookupRule: depth)
  			ifTrue:
  				[localAbsentReceiverOrZero = 0
  					ifTrue: [localAbsentReceiver := methodReceiver]
  					ifFalse: [localAbsentReceiver := localAbsentReceiverOrZero].
  				"check for coggability because method is in the cache"
  				self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
  			ifFalse:
  				[self deny: (objectMemory isOopForwarded: messageSelector).
  				self deny: (objectMemory isForwardedClassTag: methodReceiverClassTag).
- 				lkupClassTag := methodReceiverClassTag. "Successful lookup cached under the sender's class"
  				errSelIdx := self lookupOuterSendNoMNU: methodReceiver depth: depth.
  				errSelIdx ~= 0 ifTrue:
  					[self assert: errSelIdx == SelectorDoesNotUnderstand.
  					"Fix stacked receiver."
  					self stackValue: argumentCount + 1 "ret addr" put: localAbsentReceiver.
- 					"Failed lookup continues with the enclosing object's class"
- 					lkupClassTag := objectMemory classForClassTag: localAbsentReceiver.
  					self handleMNU: errSelIdx 
  						InMachineCodeTo: localAbsentReceiver
+ 						classForMessage: lkupClass.
- 						classForMessage: lkupClassTag.
  					self unreachable].
+ 				lkupClassTag := methodReceiverClassTag. "Successful lookup cached under the sender's class"
  				self addNewMethodToNSCache: depth].
  
  	"Fix stacked receiver."
  	self stackValue: argumentCount + 1 "ret addr" put: localAbsentReceiver.
  
  	(self maybeMethodHasCogMethod: newMethod) 
  		ifTrue: [
  			cogMethod := self cogMethodOf: newMethod.
  			cogMethod selector = objectMemory nilObject
  				ifTrue: [cogit setSelectorOf: cogMethod to: messageSelector]
  				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 ~= messageSelector ifTrue: [
  							(cogit cog: newMethod selector: messageSelector)
  								ifNotNil: [:newCogMethod | cogMethod := newCogMethod]]].
  			cogMethod selector = messageSelector
  				ifTrue:
  					[cogit
  						linkNSSendCache: nsSendCache 
  						classTag: methodReceiverClassTag
  						enclosingObject: localAbsentReceiverOrZero
  						target: cogMethod
  						caller: self mframeHomeMethodExport]
  				ifFalse: ["Out of code memory. Fall through to interpret."].
  			instructionPointer := self popStack.
  			self executeNewMethod.
  			self unreachable].
  	instructionPointer := self popStack.
  	self interpretMethodFromMachineCode.
  	self unreachable.!

Item was changed:
  ----- Method: CoInterpreter>>ceSelfSend:receiver: (in category 'trampolines') -----
  ceSelfSend: cacheAddress receiver: methodReceiver
  	"A self send cache missed."
  	| nsSendCache methodReceiverClassTag cogMethod errSelIdx |
  	<api>
  	<option: #NewspeakVM>
  	<inline: false>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	<var: #cogMethod type: #'CogMethod *'>
  
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: methodReceiver).
  	self deny: (objectMemory isOopForwarded: methodReceiver).
  
  	nsSendCache := self cCoerceSimple: cacheAddress to: #'NSSendCache *'.
  	messageSelector := nsSendCache selector.
  	argumentCount := nsSendCache numArgs.
  	method := (self mframeHomeMethod: framePointer) methodObject.
  
  	self assert: (self stackValue: argumentCount + 1 "ret addr") = methodReceiver.
  
  	methodReceiverClassTag := objectMemory fetchClassTagOf: methodReceiver.
  
  	(self
  		inlineLookupInNSMethodCacheSel: messageSelector
  		classTag: methodReceiverClassTag
  		method: method
  		lookupRule: LookupRuleSelf)
  			ifTrue:
  				[self assert: localAbsentReceiverOrZero = 0.
  				"check for coggability because method is in the cache"
  				self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
  			ifFalse:
  				[self deny: (objectMemory isOopForwarded: messageSelector).
  				self deny: (objectMemory isForwardedClassTag: methodReceiverClassTag).
- 				lkupClassTag := methodReceiverClassTag.
  				errSelIdx := self lookupOuterSendNoMNU: methodReceiver depth: 0.
  				errSelIdx ~= 0 ifTrue:
  					[self assert: errSelIdx == SelectorDoesNotUnderstand.
+ 					self assert: localAbsentReceiver == methodReceiver.
  					self handleMNU: errSelIdx 
  						InMachineCodeTo: methodReceiver
+ 						classForMessage: lkupClass.
- 						classForMessage: (objectMemory classForClassTag: methodReceiverClassTag).
  					self unreachable].
+ 				lkupClassTag := methodReceiverClassTag.
  				self addNewMethodToNSCache: LookupRuleSelf].
  
  	(self maybeMethodHasCogMethod: newMethod) 
  		ifTrue: [
  			cogMethod := self cogMethodOf: newMethod.
  			cogMethod selector = objectMemory nilObject
  				ifTrue: [cogit setSelectorOf: cogMethod to: messageSelector]
  				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 ~= messageSelector ifTrue: [
  							(cogit cog: newMethod selector: messageSelector)
  								ifNotNil: [:newCogMethod | cogMethod := newCogMethod]]].
  			cogMethod selector = messageSelector
  				ifTrue:
  					[cogit
  						linkNSSendCache: nsSendCache 
  						classTag: methodReceiverClassTag
  						enclosingObject: 0
  						target: cogMethod
  						caller: self mframeHomeMethodExport]
  				ifFalse: ["Out of code memory. Fall through to interpret."].
  			instructionPointer := self popStack.
  			self executeNewMethod.
  			self unreachable].
  	instructionPointer := self popStack.
  	self interpretMethodFromMachineCode.
  	self unreachable.!



More information about the Vm-dev mailing list