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

commits at source.squeak.org commits at source.squeak.org
Wed Aug 26 04:07:17 UTC 2015


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

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

Name: VMMaker.oscog-rmacnak.1444
Author: rmacnak
Time: 25 August 2015, 9:05:48.306 pm
UUID: 2ffc3ab7-87d2-43b1-b719-6d4cf96765b5
Ancestors: VMMaker.oscog-rmacnak.1443

Fix bug from refactoring in VMMaker.oscog-eem.1438 - lookupProtected:startingAt:rule: should return the actual lookup rule, not 0.

Fix bug in MNU for cogged dynamic super sends - should start looking for #doesNotUnderstand: in the superclass not the receiver class. Unify MNU lookup between absent and present receiver sends as a result.

Rename local variable lookupClass to currentClass in a few places to avoid confusion with instance variable lkupClass.

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

Item was changed:
  ----- Method: CoInterpreter>>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.
  	localAbsentReceiverOrZero := 0.
  	methodMixin := self methodClassOf: method.
  	methodMixinApplication := self
  		findApplicationOfTargetMixin: methodMixin
  		startingAtBehavior: (objectMemory fetchClassOf: localAbsentReceiver).
+ 	lkupClass := self superclassOf: methodMixinApplication. "MNU lookup starts here."
- 	lkupClass := self superclassOf: methodMixinApplication. "For use by MNU"
  	^self lookupProtectedNoMNU: messageSelector startingAt: lkupClass rule: LookupRuleDynamicSuper!

Item was changed:
  ----- Method: CoInterpreter>>lookupImplicitReceiverSendNoMNU: (in category 'message sending') -----
  lookupImplicitReceiverSendNoMNU: methodReceiver
  	"Do the full lookup for an implicit receiver send.
  	IN: messageSelector
  	IN: argumentCount
  	OUT: localAbsentReceiver
  	OUT: localAbsentReceiverOrZero
  	OUT: newMethod
  	OUT: primitiveIndex
  	RESULT: 0 or SelectorDoesNotUnderstand"
  
  	| candidateReceiver candidateMixin candidateMixinApplication dictionary found |
  	messageSelector := objectMemory followMaybeForwarded: messageSelector.
  	candidateReceiver := methodReceiver.
  	self deny: (objectMemory isForwarded: method).
  	candidateMixin := self methodClassOf: method.
  	localAbsentReceiverOrZero := 0.
  	[self deny: (objectMemory isForwarded: candidateMixin).
  	self deny: (objectMemory isForwarded: candidateReceiver).
  	candidateMixinApplication := self
  		findApplicationOfTargetMixin: candidateMixin
  		startingAtBehavior: (objectMemory fetchClassOf: candidateReceiver).
  	self deny: (candidateMixinApplication = 0).
  	self deny: (candidateMixinApplication = objectMemory nilObject).
  	self deny: (objectMemory isForwarded: candidateMixinApplication).
  	self assert: (self addressCouldBeClassObj: candidateMixinApplication).
  	dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: candidateMixinApplication.
  	found := self lookupMethodInDictionary: dictionary.
  	found ifTrue:
  		[localAbsentReceiver := candidateReceiver.
  		^self lookupLexicalNoMNU: messageSelector from: candidateMixin rule: LookupRuleImplicit].
  	candidateMixin := objectMemory followObjField: EnclosingMixinIndex ofObject: candidateMixin.
  	self deny: (objectMemory isForwarded: candidateMixin).
  	candidateMixin = objectMemory nilObject]
  		whileFalse:
  			[localAbsentReceiverOrZero := candidateReceiver := objectMemory followObjField: EnclosingObjectIndex ofObject: candidateMixinApplication].
  	"There is no lexically visible method, so the implicit receiver is the method receiver."
  	localAbsentReceiverOrZero := 0.
  	localAbsentReceiver := methodReceiver.
+ 	lkupClass := objectMemory fetchClassOf: methodReceiver. "MNU lookup starts here."
- 	lkupClass := objectMemory fetchClassOf: methodReceiver. "For use by MNU"
  	^self lookupProtectedNoMNU: messageSelector startingAt: lkupClass rule: LookupRuleImplicit.!

Item was changed:
  ----- Method: CoInterpreter>>lookupLexicalNoMNU:from:rule: (in category 'message sending') -----
  lookupLexicalNoMNU: selector from: mixin rule: rule
  	"A shared part of the lookup for implicit receiver sends that found a lexically visible
  	method, and self and outer sends."
  	| receiverClass mixinApplication dictionary found |
  	receiverClass := objectMemory fetchClassOf: localAbsentReceiver.
+ 	lkupClass := receiverClass. "MNU lookup starts here."
- 	lkupClass := receiverClass. "For use by MNU"
  	mixinApplication := self findApplicationOfTargetMixin: mixin startingAtBehavior: receiverClass.
  	dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: mixinApplication.
  	found := self lookupMethodInDictionary: dictionary.
  	(found and: [(self isPrivateMethod: newMethod)]) ifTrue:
  		[^0].
  	^self lookupProtectedNoMNU: selector startingAt: receiverClass rule: rule!

Item was changed:
  ----- Method: CoInterpreter>>lookupProtectedNoMNU:startingAt:rule: (in category 'message sending') -----
  lookupProtectedNoMNU: selector startingAt: mixinApplication rule: rule
  	"A shared part of the lookup for self, outer or implicit receiver sends that did not find a
  	private lexically visible method, and (Newspeak) super sends."
+ 	| currentClass dictionary found |
+ 	currentClass := mixinApplication.
+ 	[currentClass = objectMemory nilObject] whileFalse:
+ 		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
- 	| lookupClass dictionary found |
- 	lookupClass := mixinApplication.
- 	[lookupClass = objectMemory nilObject] whileFalse:
- 		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: lookupClass.
  		found := self lookupMethodInDictionary: dictionary.
  		(found and: [(self isPrivateMethod: newMethod) not]) ifTrue:
  			[^0].
+ 		currentClass := self superclassOf: currentClass].
- 		lookupClass := self superclassOf: lookupClass].
  	^SelectorDoesNotUnderstand!

Item was removed:
- ----- Method: StackInterpreter>>lookupDnuAbsent (in category 'message sending') -----
- lookupDnuAbsent
- 	"An absent receiver send lookup failed. Replace the arguments on the stack with
- 	 a Message and lookup #doesNotUndestand:.
- 	IN: lkupClass
- 	IN: messageSelector
- 	IN: argumentCount
- 	OUT: newMethod
- 	OUT: primitiveIndex
- 	RESULT: LookupRuleMNU"
- 
- 	| currentClass dictionary found |
- 	self createActualMessageTo: lkupClass.
- 	lkupClass := objectMemory fetchClassOf: localAbsentReceiver.
- 	messageSelector := objectMemory splObj: SelectorDoesNotUnderstand.
- 	currentClass := lkupClass.
- 	[currentClass ~= objectMemory nilObject] whileTrue:
- 		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
- 		found := self lookupMethodInDictionary: dictionary.
- 		found ifTrue: [^LookupRuleMNU].
- 		currentClass := self superclassOf: currentClass].
- 
- 	self error: 'Recursive not understood error encountered'
- !

Item was removed:
- ----- Method: StackInterpreter>>lookupDnuPresent (in category 'message sending') -----
- lookupDnuPresent
- 	"A present receiver send lookup failed. Replace the arguments on the stack with
- 	 a Message and lookup #doesNotUndestand:.
- 	IN: lkupClass
- 	IN: messageSelector
- 	IN: argumentCount
- 	OUT: newMethod
- 	OUT: primitiveIndex
- 	RESULT: LookupRuleMNU"
- 	<option: #NewspeakVM>
- 	| currentClass dictionary found |
- 	self createActualMessageTo: lkupClass.
- 	messageSelector := objectMemory splObj: SelectorDoesNotUnderstand.
- 	currentClass := lkupClass.
- 	[currentClass ~= objectMemory nilObject] whileTrue:
- 		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
- 		found := self lookupMethodInDictionary: dictionary.
- 		found ifTrue: [^LookupRuleMNU].
- 		currentClass := self superclassOf: currentClass].
- 
- 	self error: 'Recursive not understood error encountered'!

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

Item was changed:
  ----- Method: StackInterpreter>>lookupImplicitReceiverSend (in category 'message sending') -----
  lookupImplicitReceiverSend
  	"Do the full lookup for an implicit receiver send.
  	IN: messageSelector
  	IN: argumentCount
  	OUT: localAbsentReceiver
  	OUT: localAbsentReceiverOrZero
  	OUT: newMethod
  	OUT: primitiveIndex
  	RESULT: LookupRuleImplicit or LookupRuleMNU"
  
  	| methodReceiver candidateReceiver candidateMixin candidateMixinApplication dictionary found |
  	messageSelector := objectMemory followMaybeForwarded: messageSelector.
  	methodReceiver := self receiver.
  	candidateReceiver := methodReceiver.
  	self deny: (objectMemory isForwarded: method).
  	candidateMixin := self methodClassOf: method.
  	localAbsentReceiverOrZero := 0.
  	[self deny: (objectMemory isForwarded: candidateMixin).
  	self deny: (objectMemory isForwarded: candidateReceiver).
  	candidateMixinApplication := self
  		findApplicationOfTargetMixin: candidateMixin
  		startingAtBehavior: (objectMemory fetchClassOf: candidateReceiver).
  	self deny: (candidateMixinApplication = 0).
  	self deny: (candidateMixinApplication = objectMemory nilObject).
  	self deny: (objectMemory isForwarded: candidateMixinApplication).
  	self assert: (self addressCouldBeClassObj: candidateMixinApplication).
  	dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: candidateMixinApplication.
  	found := self lookupMethodInDictionary: dictionary.
  	found ifTrue:
  		[localAbsentReceiver := candidateReceiver.
  		^self lookupLexical: messageSelector from: candidateMixin rule: LookupRuleImplicit].
  	candidateMixin := objectMemory followObjField: EnclosingMixinIndex ofObject: candidateMixin.
  	self deny: (objectMemory isForwarded: candidateMixin).
  	candidateMixin = objectMemory nilObject]
  		whileFalse:
  			[localAbsentReceiverOrZero := candidateReceiver := objectMemory followObjField: EnclosingObjectIndex ofObject: candidateMixinApplication].
  	"There is no lexically visible method, so the implicit receiver is the method receiver."
  	localAbsentReceiverOrZero := 0.
  	localAbsentReceiver := methodReceiver.
+ 	lkupClass := objectMemory fetchClassOf: methodReceiver. "MNU lookup starts here."
- 	lkupClass := objectMemory fetchClassOf: methodReceiver. "For use by MNU"
  	^self lookupProtected: messageSelector startingAt: lkupClass rule: LookupRuleImplicit.!

Item was changed:
  ----- Method: StackInterpreter>>lookupLexical:from:rule: (in category 'message sending') -----
  lookupLexical: selector from: mixin rule: rule
  	"A shared part of the lookup for implicit receiver sends that found a lexically visible
  	method, and self and outer sends."
  	| receiverClass mixinApplication dictionary found |
  	receiverClass := objectMemory fetchClassOf: localAbsentReceiver.
+ 	lkupClass := receiverClass. "MNU lookup starts here."
- 	lkupClass := receiverClass. "For use by MNU"
  	mixinApplication := self findApplicationOfTargetMixin: mixin startingAtBehavior: receiverClass.
  	dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: mixinApplication.
  	found := self lookupMethodInDictionary: dictionary.
  	(found and: [(self isPrivateMethod: newMethod)]) ifTrue:
  		[^rule].
  	^self lookupProtected: selector startingAt: receiverClass rule: rule
  !

Item was added:
+ ----- Method: StackInterpreter>>lookupMNU (in category 'message sending') -----
+ lookupMNU
+ 	"A send lookup failed. Replace the arguments on the stack with a Message and lookup
+ 	 #doesNotUndestand: starting at lkupClass. Note that MNU lookup ignores access modifiers.
+ 	 This makes it different from an ordinary send of #doesNotUnderstand:, which must only
+ 	 find public methods.
+ 	IN: lkupClass
+ 	IN: messageSelector
+ 	IN: argumentCount
+ 	OUT: newMethod
+ 	OUT: primitiveIndex
+ 	RESULT: LookupRuleMNU"
+ 
+ 	| currentClass dictionary found |
+ 	self createActualMessageTo: lkupClass.
+ 	messageSelector := objectMemory splObj: SelectorDoesNotUnderstand.
+ 	currentClass := lkupClass.
+ 	[currentClass ~= objectMemory nilObject] whileTrue:
+ 		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
+ 		found := self lookupMethodInDictionary: dictionary.
+ 		found ifTrue: [^LookupRuleMNU].
+ 		currentClass := self superclassOf: currentClass].
+ 
+ 	self error: 'Recursive not understood error encountered'
+ !

Item was changed:
  ----- Method: StackInterpreter>>lookupOrdinarySend (in category 'message sending') -----
  lookupOrdinarySend
  	"Do the full lookup for an ordinary send (i.e., a Newspeak or Smalltalk ordinary send or a Smalltalk super send).
  	IN: lkupClass
  	IN: messageSelector
  	IN: argumentCount
  	OUT: newMethod
  	OUT: primitiveIndex
+ 	RESULT: LookupRuleOrdinary or LookupRuleMNU"
- 	RESULT: LookupOrdinary or LookupDNU"
  	<option: #NewspeakVM>
  	| currentClass dictionary found |
  	self assert: (self addressCouldBeClassObj: lkupClass).
  	currentClass := lkupClass.
  	[currentClass ~= objectMemory nilObject] whileTrue:
  		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
  		found := self lookupMethodInDictionary: dictionary.
  		found ifTrue:
  			[(self isPublicMethod: newMethod) ifTrue:
+ 				[^LookupRuleOrdinary].
- 				[^self].
  			(self isProtectedMethod: newMethod) ifTrue:
+ 				[^self lookupMNU]].
- 				[^self lookupDnuPresent]].
  		currentClass := self superclassOf: currentClass].
+ 	^self lookupMNU!
- 	^self lookupDnuPresent!

Item was changed:
  ----- Method: StackInterpreter>>lookupProtected:startingAt:rule: (in category 'message sending') -----
  lookupProtected: selector startingAt: mixinApplication rule: rule
  	"A shared part of the lookup for self, outer or implicit receiver sends that did not find a
  	private lexically visible method, and (Newspeak) super sends."
+ 	| currentClass dictionary found |
+ 	currentClass := mixinApplication.
+ 	[currentClass = objectMemory nilObject] whileFalse:
+ 		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
- 	| lookupClass dictionary found |
- 	lookupClass := mixinApplication.
- 	[lookupClass = objectMemory nilObject] whileFalse:
- 		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: lookupClass.
  		found := self lookupMethodInDictionary: dictionary.
  		(found and: [(self isPrivateMethod: newMethod) not]) ifTrue:
+ 			[^rule].
+ 		currentClass := self superclassOf: currentClass].
+ 	^self lookupMNU!
- 			[^0].
- 		lookupClass := self superclassOf: lookupClass].
- 	^self lookupDnuAbsent!



More information about the Vm-dev mailing list