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

commits at source.squeak.org commits at source.squeak.org
Sun May 10 02:13:12 UTC 2015


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

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

Name: VMMaker.oscog-rmacnak.1294
Author: rmacnak
Time: 9 May 2015, 7:11:51.94 pm
UUID: 30c9bb7e-e2bc-4d98-8dfe-c357139ee75f
Ancestors: VMMaker.oscog-eem.1293

Thread lookup rule through from bytecodes to internalFindNewMethod.

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

Item was removed:
- ----- Method: CoInterpreter>>commonSend (in category 'message sending') -----
- commonSend
- 	"Send a message, starting lookup with the receiver's class."
- 	"Assume: messageSelector and argumentCount have been set, and that 
- 	the receiver and arguments have been pushed onto the stack,"
- 	"Note: This method is inlined into the interpreter dispatch loop."
- 	<sharedCodeNamed: 'commonSend' inCase: #singleExtendedSendBytecode>
- 	self sendBreakpoint: messageSelector receiver: (self internalStackValue: argumentCount).
- 	cogit recordSendTrace ifTrue:
- 		[self recordTrace: (objectMemory classForClassTag: lkupClassTag)
- 			thing: messageSelector
- 			source: TraceIsFromInterpreter.
- 		cogit printOnTrace ifTrue:
- 			[self printActivationNameForSelector: messageSelector
- 				startClass: (objectMemory classForClassTag: lkupClassTag); cr]].
- 	self internalFindNewMethod.
- 	self internalExecuteNewMethod.
- 	self fetchNextBytecode!

Item was added:
+ ----- Method: CoInterpreter>>commonSend: (in category 'message sending') -----
+ commonSend: lookupRule
+ 	"Send a message, starting lookup with the receiver's class."
+ 	"Assume: messageSelector and argumentCount have been set, and that 
+ 	the receiver and arguments have been pushed onto the stack,"
+ 	"Note: This method is inlined into the interpreter dispatch loop."
+ 	self sendBreakpoint: messageSelector receiver: (self internalStackValue: argumentCount).
+ 	cogit recordSendTrace ifTrue:
+ 		[self recordTrace: (objectMemory classForClassTag: lkupClassTag)
+ 			thing: messageSelector
+ 			source: TraceIsFromInterpreter.
+ 		cogit printOnTrace ifTrue:
+ 			[self printActivationNameForSelector: messageSelector
+ 				startClass: (objectMemory classForClassTag: lkupClassTag); cr]].
+ 	self internalFindNewMethod: lookupRule.
+ 	self internalExecuteNewMethod.
+ 	self fetchNextBytecode!

Item was removed:
- ----- Method: CoInterpreter>>internalFindNewMethod (in category 'message sending') -----
- internalFindNewMethod
- 	"Find the compiled method to be run when the current messageSelector is
- 	 sent to the given class, setting the values of newMethod and primitiveIndex."
- 	| ok |
- 	<inline: true>
- 	ok := self inlineLookupInMethodCacheSel: messageSelector classTag: lkupClassTag.
- 	ok	ifTrue:
- 			[self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
- 		ifFalse:
- 			[self externalizeIPandSP.
- 			 ((objectMemory isOopForwarded: messageSelector)
- 			  or: [objectMemory isForwardedClassTag: lkupClassTag]) ifTrue:
- 				[(objectMemory isOopForwarded: messageSelector) ifTrue:
- 					[messageSelector := self handleForwardedSelectorFaultFor: messageSelector].
- 				 (objectMemory isForwardedClassTag: lkupClassTag) ifTrue:
- 					[lkupClassTag := self handleForwardedSendFaultForTag: lkupClassTag].
- 				(self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag) ifTrue:
- 					[^self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]].
- 			 lkupClass := objectMemory classForClassTag: lkupClassTag.
- 			self lookupMethodInClass: lkupClass.
- 			self internalizeIPandSP.
- 			self addNewMethodToCache: lkupClass]!

Item was added:
+ ----- Method: CoInterpreter>>internalFindNewMethod: (in category 'message sending') -----
+ internalFindNewMethod: lookupRule
+ 	"Find the compiled method to be run when the current messageSelector is
+ 	 sent to the given class, setting the values of newMethod and primitiveIndex."
+ 	| ok |
+ 	<inline: true>
+ 	ok := self inlineLookupInMethodCacheSel: messageSelector classTag: lkupClassTag.
+ 	ok	ifTrue:
+ 			[self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
+ 		ifFalse:
+ 			[self externalizeIPandSP.
+ 			 ((objectMemory isOopForwarded: messageSelector)
+ 			  or: [objectMemory isForwardedClassTag: lkupClassTag]) ifTrue:
+ 				[(objectMemory isOopForwarded: messageSelector) ifTrue:
+ 					[messageSelector := self handleForwardedSelectorFaultFor: messageSelector].
+ 				 (objectMemory isForwardedClassTag: lkupClassTag) ifTrue:
+ 					[lkupClassTag := self handleForwardedSendFaultForTag: lkupClassTag].
+ 				(self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag) ifTrue:
+ 					[^self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]].
+ 			 lkupClass := objectMemory classForClassTag: lkupClassTag.
+ 			self lookupMethodInClass: lkupClass.
+ 			self internalizeIPandSP.
+ 			self addNewMethodToCache: lkupClass]!

Item was removed:
- ----- Method: CogVMSimulator>>internalFindNewMethod (in category 'testing') -----
- internalFindNewMethod
- "
- 	| cName |
- 	traceOn ifTrue:
- 		[cName := (self sizeBitsOf: class) = 16r20
- 			ifTrue: ['class ' , (self nameOfClass: (self fetchPointer: 6 ofObject: class))]
- 			ifFalse: [(self nameOfClass: class)].
- 		self cr; print: cName , '>>' , (self stringOf: messageSelector)].
- "
- 	messageSelector = (objectMemory splObj: SelectorDoesNotUnderstand) ifTrue: [self halt].
- 
- 	self logSend: messageSelector.
- "
- 	(sendCount > 1000 and: [sendCount\\10 = 0]) ifTrue:
- 		[Transcript print: sendCount; space.
- 		self validate].
- "
- "
- 	(sendCount > 100150) ifTrue:
- 		[self qvalidate.
- 		messageQueue == nil ifTrue: [messageQueue := OrderedCollection new].
- 		messageQueue addLast: (self stringOf: messageSelector)].
- "
- 	^super internalFindNewMethod!

Item was added:
+ ----- Method: CogVMSimulator>>internalFindNewMethod: (in category 'testing') -----
+ internalFindNewMethod: lookupRule
+ "
+ 	| cName |
+ 	traceOn ifTrue:
+ 		[cName := (self sizeBitsOf: class) = 16r20
+ 			ifTrue: ['class ' , (self nameOfClass: (self fetchPointer: 6 ofObject: class))]
+ 			ifFalse: [(self nameOfClass: class)].
+ 		self cr; print: cName , '>>' , (self stringOf: messageSelector)].
+ "
+ 	messageSelector = (objectMemory splObj: SelectorDoesNotUnderstand) ifTrue: [self halt].
+ 
+ 	self logSend: messageSelector.
+ "
+ 	(sendCount > 1000 and: [sendCount\\10 = 0]) ifTrue:
+ 		[Transcript print: sendCount; space.
+ 		self validate].
+ "
+ "
+ 	(sendCount > 100150) ifTrue:
+ 		[self qvalidate.
+ 		messageQueue == nil ifTrue: [messageQueue := OrderedCollection new].
+ 		messageQueue addLast: (self stringOf: messageSelector)].
+ "
+ 	^super internalFindNewMethod: lookupRule!

Item was changed:
  ----- Method: StackInterpreter class>>initializeCaches (in category 'initialization') -----
  initializeCaches
  
  	| atCacheEntrySize |
  	MethodCacheEntries := 1024. 
  	MethodCacheSelector := 1.
  	MethodCacheClass := 2.
  	MethodCacheMethod := 3.
  	MethodCachePrimFunction := 4.
  	MethodCacheEntrySize := 4.  "Must be power of two for masking scheme."
  	MethodCacheMask := (MethodCacheEntries - 1) * MethodCacheEntrySize.
  	MethodCacheSize := MethodCacheEntries * MethodCacheEntrySize.
  	CacheProbeMax := 3.
  
  	AtCacheEntries := 8.  "Must be a power of two"
  	AtCacheOop := 1.
  	AtCacheSize := 2.
  	AtCacheFmt := 3.
  	AtCacheFixedFields := 4.
  	atCacheEntrySize := 4.  "Must be power of two for masking scheme."
  	AtCacheMask := (AtCacheEntries-1) * atCacheEntrySize.
  	AtPutBase := AtCacheEntries * atCacheEntrySize.
  	AtCacheTotalSize := AtCacheEntries * atCacheEntrySize * 2.
+ 
+ 	"LookupRuleOuter is [0, 255], with the value being the lexical depth. Note that an
+ 	 outer send to lexical depth 0 is equivalent to a self send. Implicit receiver and
+ 	 outer sends are encoded as adjacent values to allow a quick range check to
+ 	 determine whether the absent receiver might differ from the method receiver.
+ 	 Note also Smalltalk super sends use ordinary send lookup rules."
+ 	LookupRuleSelf := 0.
+ 	LookupRuleImplicit := 256.
+ 	LookupRuleDynamicSuper := 257.
+ 	LookupRuleOrdinary := 258.
+ 	LookupRuleMNU := 259.
  !

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimAt (in category 'common selector sends') -----
  bytecodePrimAt
  	"BytecodePrimAt will only succeed if the receiver is in the atCache.
  	 Otherwise it will fail so that the more general primitiveAt will put it in the
  	 cache after validating that message lookup results in a primitive response.
  	 Override to insert in the at: cache here.  This is necessary since once there
  	 is a compiled at: primitive method (which doesn't use the at: cache) the only
  	 way something can get installed in the atCache is here."
  	| index rcvr result atIx |
  	index := self internalStackTop.
  	rcvr := self internalStackValue: 1.
  	((objectMemory isNonImmediate: rcvr)
  	 and: [objectMemory isIntegerObject: index]) ifTrue:
  		[atIx := rcvr bitAnd: AtCacheMask.  "Index into atCache = 4N, for N = 0 ... 7"
  		(atCache at: atIx+AtCacheOop) ~= rcvr ifTrue:
  			[lkupClassTag := objectMemory fetchClassTagOfNonImm: rcvr.
  			 messageSelector := self specialSelector: 16.
  			 (self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag) ifFalse:
  				[argumentCount := 1.
+ 				 ^self commonSend: LookupRuleOrdinary].
- 				 ^self commonSend].
  			 primitiveFunctionPointer == #primitiveAt
  				ifTrue: [self install: rcvr inAtCache: atCache at: atIx string: false]
  				ifFalse:
  					[primitiveFunctionPointer == #primitiveStringAt
  						ifTrue: [self install: rcvr inAtCache: atCache at: atIx string: true]
  						ifFalse:
  							[argumentCount := 1.
+ 							 ^self commonSend: LookupRuleOrdinary]]].
- 							 ^self commonSend]]].
  		 self successful ifTrue:
  			[result := self commonVariable: rcvr at: (objectMemory integerValueOf: index) cacheIndex: atIx].
  		 self successful ifTrue:
  			[self fetchNextBytecode.
  			 ^self internalPop: 2 thenPush: result].
  		 self initPrimCall].
  
  	messageSelector := self specialSelector: 16.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimAtPut (in category 'common selector sends') -----
  bytecodePrimAtPut
  	"BytecodePrimAtPut will only succeed if the receiver is in the atCache.
  	Otherwise it will fail so that the more general primitiveAtPut will put it in the
  	cache after validating that message lookup results in a primitive response.
  	 Override to insert in the atCache here.  This is necessary since once there
  	 is a compiled at:[put:] primitive method (which doesn't use the at: cache) the
  	 only way something can get installed in the atCache is here."
  	| index rcvr atIx value |
  	value := self internalStackTop.
  	index := self internalStackValue: 1.
  	rcvr := self internalStackValue: 2.
  	((objectMemory isNonImmediate: rcvr)
  	 and: [objectMemory isIntegerObject: index]) ifTrue:
  		[atIx := (rcvr bitAnd: AtCacheMask) + AtPutBase.  "Index into atPutCache"
  		 (atCache at: atIx+AtCacheOop) ~= rcvr ifTrue:
  			[lkupClassTag := objectMemory fetchClassTagOfNonImm: rcvr.
  			 messageSelector := self specialSelector: 17.
  			 (self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag) ifFalse:
  				[argumentCount := 2.
+ 				 ^self commonSend: LookupRuleOrdinary].
- 				 ^self commonSend].
  			 primitiveFunctionPointer == #primitiveAtPut
  				ifTrue: [self install: rcvr inAtCache: atCache at: atIx string: false]
  				ifFalse:
  					[primitiveFunctionPointer == #primitiveStringAtPut
  						ifTrue: [self install: rcvr inAtCache: atCache at: atIx string: true]
  						ifFalse:
  							[argumentCount := 2.
+ 							 ^self commonSend: LookupRuleOrdinary]]].
- 							 ^self commonSend]]].
  		 self successful ifTrue:
  			[self commonVariable: rcvr at: (objectMemory integerValueOf: index) put: value cacheIndex: atIx].
  		 self successful ifTrue:
  			[self fetchNextBytecode.
  			 ^self internalPop: 3 thenPush: value].
  		 self initPrimCall].
  
  	messageSelector := self specialSelector: 17.
  	argumentCount := 2.
  	self normalSend!

Item was removed:
- ----- Method: StackInterpreter>>commonSend (in category 'send bytecodes') -----
- commonSend
- 	"Send a message, starting lookup with the receiver's class."
- 	"Assume: messageSelector and argumentCount have been set, and that 
- 	the receiver and arguments have been pushed onto the stack,"
- 	"Note: This method is inlined into the interpreter dispatch loop."
- 	<sharedCodeInCase: #singleExtendedSendBytecode>
- 	self sendBreakpoint: messageSelector receiver: (self internalStackValue: argumentCount).
- 	self printSends ifTrue:
- 		[self printActivationNameForSelector: messageSelector startClass: (objectMemory classForClassTag: lkupClassTag); cr].
- 	self internalFindNewMethod.
- 	self internalExecuteNewMethod.
- 	self fetchNextBytecode!

Item was added:
+ ----- Method: StackInterpreter>>commonSend: (in category 'send bytecodes') -----
+ commonSend: lookupRule
+ 	"Send a message, starting lookup with the receiver's class."
+ 	"Assume: messageSelector and argumentCount have been set, and that 
+ 	the receiver and arguments have been pushed onto the stack,"
+ 	"Note: This method is inlined into the interpreter dispatch loop."
+ 	"<sharedCodeInCase: #singleExtendedSendBytecode>"
+ 	self sendBreakpoint: messageSelector receiver: (self internalStackValue: argumentCount).
+ 	self printSends ifTrue:
+ 		[self printActivationNameForSelector: messageSelector startClass: (objectMemory classForClassTag: lkupClassTag); cr].
+ 	self internalFindNewMethod: lookupRule.
+ 	self internalExecuteNewMethod.
+ 	self fetchNextBytecode!

Item was removed:
- ----- Method: StackInterpreter>>commonSendAbsent (in category 'send bytecodes') -----
- commonSendAbsent
- 	"Send an absent receiver message, shuffling arguments and inserting the absent
- 	 receiver for the send.  Assume: messageSelector and argumentCount have been
- 	 set, and that the arguments but not the receiver have been pushed onto the stack,"
- 	"Note: This method is inlined into the interpreter dispatch loop."
- 	"160-175	1010 i i i i				Send To Absent Implicit Receiver Literal Selector #iiii With 0 Arguments"
- 	"240		11110000	i i i i i j j j	Send To Absent Implicit Receiver Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
- 	"245		 11110101 i i i i i j j j	Send To Self Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
- 	"254		 11111110 i i i i i j j j	kkkkkkkk Send To Enclosing Object at Depth kkkkkkkk Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
- 	<sharedCodeInCase: #extSendAbsentImplicitBytecode>
- 	self shuffleArgumentsAndStoreAbsentReceiver: localAbsentReceiver.
- 	lkupClassTag := objectMemory fetchClassTagOf: localAbsentReceiver.
- 	self assert: (objectMemory classForClassTag: lkupClassTag) ~= objectMemory nilObject.
- 	CheckPrivacyViolations ifTrue:
-             [isPrivateSend := true].
- 	self commonSend!

Item was added:
+ ----- Method: StackInterpreter>>commonSendAbsent: (in category 'send bytecodes') -----
+ commonSendAbsent: lookupRule
+ 	"Send an absent receiver message, shuffling arguments and inserting the absent
+ 	 receiver for the send.  Assume: messageSelector and argumentCount have been
+ 	 set, and that the arguments but not the receiver have been pushed onto the stack,"
+ 	"Note: This method is inlined into the interpreter dispatch loop."
+ 	"160-175	1010 i i i i				Send To Absent Implicit Receiver Literal Selector #iiii With 0 Arguments"
+ 	"240		11110000	i i i i i j j j	Send To Absent Implicit Receiver Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
+ 	"245		 11110101 i i i i i j j j	Send To Self Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
+ 	"254		 11111110 i i i i i j j j	kkkkkkkk Send To Enclosing Object at Depth kkkkkkkk Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
+ 	"<sharedCodeInCase: #extSendAbsentImplicitBytecode>"
+ 	self shuffleArgumentsAndStoreAbsentReceiver: localAbsentReceiver.
+ 	lkupClassTag := objectMemory fetchClassTagOf: localAbsentReceiver.
+ 	self assert: (objectMemory classForClassTag: lkupClassTag) ~= objectMemory nilObject.
+ 	CheckPrivacyViolations ifTrue:
+             [isPrivateSend := true].
+ 	self commonSend: lookupRule!

Item was changed:
  ----- Method: StackInterpreter>>commonSendAbsentImplicit (in category 'send bytecodes') -----
  commonSendAbsentImplicit
  	"Send a message to the implicit receiver for that message."
  	"Assume: messageSelector and argumentCount have been set, and that 
  	the arguments but not the receiver have been pushed onto the stack,"
  	"Note: This method is inlined into the interpreter dispatch loop."
  	"160-175	1010 i i i i		Send To Absent Implicit Receiver Literal Selector #iiii With 0 Arguments"
  	"240		11110000	i i i i i j j j	Send To Absent Implicit Receiver Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	<sharedCodeInCase: #extSendAbsentImplicitBytecode>
  	localAbsentReceiver := self
  								implicitReceiverFor: self receiver
  								mixin: (self methodClassOf: method)
  								implementing: messageSelector.
+ 	self commonSendAbsent: LookupRuleImplicit!
- 	self commonSendAbsent!

Item was changed:
  ----- Method: StackInterpreter>>directedSuperclassSend (in category 'send bytecodes') -----
  directedSuperclassSend
  	"Send a message to self, starting lookup with the superclass of the class on top of stack."
  	"Assume: messageSelector and argumentCount have been set, and that
  	 the receiver and arguments have been pushed onto the stack,"
  	"Note: This method is inlined into the interpreter dispatch loop."
  	<sharedCodeInCase: #extSendSuperBytecode>
  	<option: #SistaVM>
  	| class superclass |
  	class := self internalPopStack.
  	(objectMemory isForwarded: class) ifTrue:
  		[class := objectMemory followForwarded: class].
  	superclass := self superclassOf: class.
  	objectMemory ensureBehaviorHash: superclass.
  	lkupClassTag := objectMemory classTagForClass: superclass.
  	"To maintain the invariant that all receivers are unforwarded we need an explicit
  	 read barrier in the super send cases.  Even though we always follow receivers
  	 on become  e.g. super doSomethingWith: (self become: other) forwards the receiver
  	 self pushed on the stack."
  	self ensureReceiverUnforwarded.
  	self assert: lkupClassTag ~= objectMemory nilObject.
+ 	self commonSend: LookupRuleOrdinary!
- 	self commonSend!

Item was changed:
  ----- Method: StackInterpreter>>extSendAbsentDynamicSuperBytecode (in category 'send bytecodes') -----
  extSendAbsentDynamicSuperBytecode
  	"241		11110001	i i i i i j j j	Send To Dynamic Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	| byte mClassMixin mixinApplication |
  	byte := self fetchByte.
  	messageSelector := self literal: (byte >> 3) + (extA << 5).
  	extA := 0.
  	argumentCount := (byte bitAnd: 7) + (extB << 3).
  	extB := 0.
  	self shuffleArgumentsAndStoreAbsentReceiver: self receiver.
  	mClassMixin := self methodClassOf: method.
  	mixinApplication := self 
  							findApplicationOfTargetMixin: mClassMixin
  							startingAtBehavior: (objectMemory fetchClassOf: self receiver).
  	lkupClassTag := objectMemory classTagForClass: (self superclassOf: mixinApplication).
  	CheckPrivacyViolations ifTrue:
              [isPrivateSend := true].
+ 	self commonSend: LookupRuleDynamicSuper!
- 	self commonSend!

Item was changed:
  ----- Method: StackInterpreter>>extSendAbsentOuterBytecode (in category 'send bytecodes') -----
  extSendAbsentOuterBytecode
  	"254		  11111110 	i i i i i j j j	kkkkkkkk Send To Enclosing Object at Depth kkkkkkkk Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	| byte depth |
  	byte := self fetchByte.
  	messageSelector := self literal: (byte >> 3) + (extA << 5).
  	extA := 0.
  	argumentCount := (byte bitAnd: 7) + (extB << 3).
  	extB := 0.
  	depth := self fetchByte.
  	localAbsentReceiver := self 
  							enclosingObjectAt: depth
  							withObject: self receiver 
  							withMixin: (self methodClassOf: method).
  	CheckPrivacyViolations ifTrue:
              [isPrivateSend := true].
+ 	self commonSendAbsent: depth!
- 	self commonSendAbsent!

Item was changed:
  ----- Method: StackInterpreter>>extSendAbsentSelfBytecode (in category 'send bytecodes') -----
  extSendAbsentSelfBytecode
  	"245		 11110101 	i i i i i j j j	Send To Self Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	| byte |
  	byte := self fetchByte.
  	messageSelector := self literal: (byte >> 3) + (extA << 5).
  	extA := 0.
  	argumentCount := (byte bitAnd: 7) + (extB << 3).
  	extB := 0.
  	localAbsentReceiver := self receiver.
  	CheckPrivacyViolations ifTrue:
              [isPrivateSend := true].
+ 	self commonSendAbsent: LookupRuleSelf!
- 	self commonSendAbsent!

Item was changed:
  ----- Method: StackInterpreter>>extSendBytecode (in category 'send bytecodes') -----
  extSendBytecode
  	"238		11101110	i i i i i j j j	Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	| byte rcvr |
  	byte := self fetchByte.
  	messageSelector := self literal: (byte >> 3) + (extA << 5).
  	extA := 0.
  	argumentCount := (byte bitAnd: 7) + (extB << 3).
  	extB := 0.
  	rcvr := self internalStackValue: argumentCount.
  	lkupClassTag := objectMemory fetchClassTagOf: rcvr.
  	self assert: (objectMemory classForClassTag: lkupClassTag) ~= objectMemory nilObject.
+ 	self commonSend: LookupRuleOrdinary!
- 	self commonSend!

Item was removed:
- ----- Method: StackInterpreter>>internalFindNewMethod (in category 'message sending') -----
- internalFindNewMethod
- 	"Find the compiled method to be run when the current messageSelector is sent to the class 'lkupClass', setting the values of 'newMethod' and 'primitiveIndex'."
- 	<inline: true>
- 	(self inlineLookupInMethodCacheSel: messageSelector classTag: lkupClassTag) ifFalse:
- 		["entry was not found in the cache; look it up the hard way"
- 		 self externalizeIPandSP.
- 		 ((objectMemory isOopForwarded: messageSelector)
- 		  or: [objectMemory isForwardedClassTag: lkupClassTag]) ifTrue:
- 			[(objectMemory isOopForwarded: messageSelector) ifTrue:
- 				[messageSelector := self handleForwardedSelectorFaultFor: messageSelector].
- 			 (objectMemory isForwardedClassTag: lkupClassTag) ifTrue:
- 				[lkupClassTag := self handleForwardedSendFaultForTag: lkupClassTag].
- 			(self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag) ifTrue:
- 				[^nil]].
- 		 lkupClass := objectMemory classForClassTag: lkupClassTag.
- 		 self lookupMethodInClass: lkupClass.
- 		 self internalizeIPandSP.
- 		 self addNewMethodToCache: lkupClass].
- 	"Clear the flag set in commonSendAbsent and tested in lookupMethodInClass:"
- 	(NewspeakVM and: [CheckPrivacyViolations]) ifTrue:
- 		[isPrivateSend := false].!

Item was added:
+ ----- Method: StackInterpreter>>internalFindNewMethod: (in category 'message sending') -----
+ internalFindNewMethod: lookupRule
+ 	"Find the compiled method to be run when the current messageSelector is sent to the class 'lkupClass', setting the values of 'newMethod' and 'primitiveIndex'."
+ 	<inline: true>
+ 	(self inlineLookupInMethodCacheSel: messageSelector classTag: lkupClassTag) ifFalse:
+ 		["entry was not found in the cache; look it up the hard way"
+ 		 self externalizeIPandSP.
+ 		 ((objectMemory isOopForwarded: messageSelector)
+ 		  or: [objectMemory isForwardedClassTag: lkupClassTag]) ifTrue:
+ 			[(objectMemory isOopForwarded: messageSelector) ifTrue:
+ 				[messageSelector := self handleForwardedSelectorFaultFor: messageSelector].
+ 			 (objectMemory isForwardedClassTag: lkupClassTag) ifTrue:
+ 				[lkupClassTag := self handleForwardedSendFaultForTag: lkupClassTag].
+ 			(self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag) ifTrue:
+ 				[^nil]].
+ 		 lkupClass := objectMemory classForClassTag: lkupClassTag.
+ 		 self lookupMethodInClass: lkupClass.
+ 		 self internalizeIPandSP.
+ 		 self addNewMethodToCache: lkupClass].
+ 	"Clear the flag set in commonSendAbsent and tested in lookupMethodInClass:"
+ 	(NewspeakVM and: [CheckPrivacyViolations]) ifTrue:
+ 		[isPrivateSend := false].!

Item was changed:
  ----- Method: StackInterpreter>>normalSend (in category 'send bytecodes') -----
  normalSend
  	"Send a message, starting lookup with the receiver's class."
  	"Assume: messageSelector and argumentCount have been set, and that 
  	the receiver and arguments have been pushed onto the stack,"
  	"Note: This method is inlined into the interpreter dispatch loop."
  	<sharedCodeInCase: #singleExtendedSendBytecode>
  	| rcvr |
  	rcvr := self internalStackValue: argumentCount.
  	lkupClassTag := objectMemory fetchClassTagOf: rcvr.
  	self assert: lkupClassTag ~= objectMemory nilObject.
+ 	self commonSend: LookupRuleOrdinary!
- 	self commonSend!

Item was changed:
  ----- Method: StackInterpreter>>sendLiteralSelector0ArgsBytecode (in category 'send bytecodes') -----
  sendLiteralSelector0ArgsBytecode
  	"Can use any of the first 16 literals for the selector."
  	| rcvr |
  	messageSelector := self literal: (currentBytecode bitAnd: 16rF).
  	argumentCount := 0.
  	rcvr := self internalStackValue: 0.
  	lkupClassTag := objectMemory fetchClassTagOf: rcvr.
  	self assert: lkupClassTag ~= objectMemory nilObject.
+ 	self commonSend: LookupRuleOrdinary!
- 	self commonSend!

Item was changed:
  ----- Method: StackInterpreter>>sendLiteralSelector1ArgBytecode (in category 'send bytecodes') -----
  sendLiteralSelector1ArgBytecode
  	"Can use any of the first 16 literals for the selector."
  	| rcvr |
  	messageSelector := self literal: (currentBytecode bitAnd: 16rF).
  	argumentCount := 1.
  	rcvr := self internalStackValue: 1.
  	lkupClassTag := objectMemory fetchClassTagOf: rcvr.
  	self assert: lkupClassTag ~= objectMemory nilObject.
+ 	self commonSend: LookupRuleOrdinary!
- 	self commonSend!

Item was changed:
  ----- Method: StackInterpreter>>sendLiteralSelector2ArgsBytecode (in category 'send bytecodes') -----
  sendLiteralSelector2ArgsBytecode
  	"Can use any of the first 16 literals for the selector."
  	| rcvr |
  	messageSelector := self literal: (currentBytecode bitAnd: 16rF).
  	argumentCount := 2.
  	rcvr := self internalStackValue: 2.
  	lkupClassTag := objectMemory fetchClassTagOf: rcvr.
  	self assert: lkupClassTag ~= objectMemory nilObject.
+ 	self commonSend: LookupRuleOrdinary!
- 	self commonSend!

Item was changed:
  ----- Method: StackInterpreter>>superclassSend (in category 'send bytecodes') -----
  superclassSend
  	"Send a message to self, starting lookup with the superclass of the class
  	 containing the currently executing method."
  	"Assume: messageSelector and argumentCount have been set, and that
  	 the receiver and arguments have been pushed onto the stack,"
  	"Note: This method is inlined into the interpreter dispatch loop."
  	<sharedCodeInCase: #singleExtendedSuperBytecode>
  	| superclass |
  	superclass := self superclassOf: (self methodClassOf: method).
  	objectMemory ensureBehaviorHash: superclass.
  	lkupClassTag := objectMemory classTagForClass: superclass.
  	"To maintain the invariant that all receivers are unforwarded we need an explicit
  	 read barrier in the super send cases.  Even though we always follow receivers
  	 on become  e.g. super doSomethingWith: (self become: other) forwards the receiver
  	 self pushed on the stack."
  	self ensureReceiverUnforwarded.
  	self assert: lkupClassTag ~= objectMemory nilObject.
+ 	self commonSend: LookupRuleOrdinary!
- 	self commonSend!

Item was removed:
- ----- Method: StackInterpreterSimulator>>internalFindNewMethod (in category 'testing') -----
- internalFindNewMethod
- "
- 	| cName |
- 	traceOn ifTrue:
- 		[cName := (self sizeBitsOf: class) = 16r20
- 			ifTrue: ['class ' , (self nameOfClass: (self fetchPointer: 6 ofObject: class))]
- 			ifFalse: [(self nameOfClass: class)].
- 		self cr; print: cName , '>>' , (self stringOf: messageSelector)].
- "
- 	messageSelector = (objectMemory splObj: SelectorDoesNotUnderstand) ifTrue: [self halt].
- 
- 	sendCount := sendCount + 1.
- 
- 	printSends ifTrue:
- 		[self cr; print: byteCount; space; printStringOf: messageSelector].
- "
- 	(sendCount > 1000 and: [sendCount\\10 = 0]) ifTrue:
- 		[Transcript print: sendCount; space.
- 		self validate].
- "
- "
- 	(sendCount > 100150) ifTrue:
- 		[self qvalidate.
- 		messageQueue == nil ifTrue: [messageQueue := OrderedCollection new].
- 		messageQueue addLast: (self stringOf: messageSelector)].
- "
- 	super internalFindNewMethod!

Item was added:
+ ----- Method: StackInterpreterSimulator>>internalFindNewMethod: (in category 'testing') -----
+ internalFindNewMethod: lookupRule
+ "
+ 	| cName |
+ 	traceOn ifTrue:
+ 		[cName := (self sizeBitsOf: class) = 16r20
+ 			ifTrue: ['class ' , (self nameOfClass: (self fetchPointer: 6 ofObject: class))]
+ 			ifFalse: [(self nameOfClass: class)].
+ 		self cr; print: cName , '>>' , (self stringOf: messageSelector)].
+ "
+ 	messageSelector = (objectMemory splObj: SelectorDoesNotUnderstand) ifTrue: [self halt].
+ 
+ 	sendCount := sendCount + 1.
+ 
+ 	printSends ifTrue:
+ 		[self cr; print: byteCount; space; printStringOf: messageSelector].
+ "
+ 	(sendCount > 1000 and: [sendCount\\10 = 0]) ifTrue:
+ 		[Transcript print: sendCount; space.
+ 		self validate].
+ "
+ "
+ 	(sendCount > 100150) ifTrue:
+ 		[self qvalidate.
+ 		messageQueue == nil ifTrue: [messageQueue := OrderedCollection new].
+ 		messageQueue addLast: (self stringOf: messageSelector)].
+ "
+ 	super internalFindNewMethod: lookupRule!

Item was changed:
  SharedPool subclass: #VMMethodCacheConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'LookupRuleDynamicSuper LookupRuleImplicit LookupRuleMNU LookupRuleOrdinary LookupRuleSelf MethodCacheClass MethodCacheEntries MethodCacheEntrySize MethodCacheMask MethodCacheMethod MethodCachePrim MethodCachePrimFunction MethodCacheSelector MethodCacheSize'
- 	classVariableNames: 'MethodCacheClass MethodCacheEntries MethodCacheEntrySize MethodCacheMask MethodCacheMethod MethodCachePrim MethodCachePrimFunction MethodCacheSelector MethodCacheSize'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!
  
  !VMMethodCacheConstants commentStamp: '<historical>' prior: 0!
  I am a shared pool for the constants that define the first-level method lookup cache.
  
  self ensureClassPool.
  #(#MethodCacheClass #MethodCacheEntries #MethodCacheEntrySize #MethodCacheMask #MethodCacheMethod #MethodCachePrimFunction #MethodCacheSelector #MethodCacheSize) do: [:k|
  	self classPool declare: k from: StackInterpreter classPool]!



More information about the Vm-dev mailing list