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

commits at source.squeak.org commits at source.squeak.org
Thu Sep 12 04:47:56 UTC 2013


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

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

Name: VMMaker.oscog-eem.373
Author: eem
Time: 11 September 2013, 9:43:14.115 pm
UUID: b7535476-3c27-4058-9641-dcb2f73d1664
Ancestors: VMMaker.oscog-eem.372

Fix slip in addNewMethodToCache:.

Add the forwarding check to message lookup failure.

Simplify ceDynamicSuperSend: by going back a bit.

Comment typos.

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

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>
  	| class canLinkCacheTag errSelIdx cogMethod mClassMixin mixinApplication |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #newCogMethod type: #'CogMethod *'>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: ((objectMemory isIntegerObject: rcvr) or: [objectMemory addressCouldBeObj: rcvr]).
  	self sendBreak: selector + BaseHeaderSize
  		point: (objectMemory lengthOf: selector)
  		receiver: rcvr.
  	mClassMixin := self mMethodClass.
  	mixinApplication := self 
  							findApplicationOfTargetMixin: mClassMixin
  							startingAtBehavior: (objectMemory fetchClassOf: rcvr).
  	self assert: (objectMemory lengthOf: mixinApplication) > (InstanceSpecificationIndex + 1).
  	lkupClass := self superclassOf: mixinApplication.
+ 	lkupClassTag := self classTagForClass: lkupClass.
+ 	class := objectMemory fetchClassOf: rcvr. "what about the read barrier??"
- 	class := objectMemory fetchClassOf: rcvr.
  	canLinkCacheTag := (objectMemory isYoungObject: class) not or: [cogit canLinkToYoungClasses].
  	"We set the messageSelector and lkupClass for executeMethod below since things
  	 like the at cache read messageSelector and lkupClass and so they cannot be left stale."
  	messageSelector := selector.
+ 	lkupClass := self superclassOf: mixinApplication.
- 	lkupClassTag := objectMemory classTagForClass: (self superclassOf: mixinApplication).
  	argumentCount := numArgs.
+ 	(self lookupInMethodCacheSel: selector classTag: (objectMemory classTagForClass: lkupClass))
- 	(self lookupInMethodCacheSel: selector classTag: lkupClassTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
+ 			[(errSelIdx := self lookupMethodNoMNUEtcInClass: lkupClass) ~= 0 ifTrue:
- 			[lkupClass := objectMemory classTagForClass: lkupClassTag.
- 			(errSelIdx := self lookupMethodNoMNUEtcInClass: lkupClass) ~= 0 ifTrue:
  				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: lkupClass.
  				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
  		 and: [canLinkCacheTag]) ifTrue:
  			[cogit
  				linkSendAt: (stackPages longAt: stackPointer)
  				in: (self mframeHomeMethod: framePointer)
  				to: cogMethod
  				offset: cogit dynSuperEntryOffset
  				receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceSendFromInLineCacheMiss: (in category 'trampolines') -----
  ceSendFromInLineCacheMiss: oPIC
  	"Send from an Open PIC when the first-level method lookup probe has failed,
  	 or to continue when PIC creation has failed (e.g. because we're out of code space)."
  	<api>
  	<var: #oPIC type: #'CogMethod *'>
  	| numArgs rcvr classTag errSelIdx |
  	"self printFrame: stackPage headFP WithSP: stackPage headSP"
  	"self printStringOf: selector"
  	numArgs := oPIC cmNumArgs.
  	rcvr := self stackValue: numArgs + 1. "skip return pc"
  	self assert: ((objectMemory isIntegerObject: rcvr) or: [objectMemory addressCouldBeObj: rcvr]).
  	classTag := objectMemory fetchClassTagOf: rcvr.
  	argumentCount := numArgs.
  	"We set the messageSelector and lkupClass for executeMethod below since things
+ 	 like the at cache read messageSelector and lkupClass and so they cannot be left stale."
- 	 like the at cache read messageSelectorand lkupClass and so they cannot be left stale."
  	messageSelector := oPIC selector.
  	lkupClass := objectMemory classForClassTag: classTag.
  	(self lookupInMethodCacheSel: oPIC selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: oPIC selector]
  		ifFalse:
  			[(errSelIdx := self lookupMethodNoMNUEtcInClass: lkupClass) ~= 0 ifTrue:
  				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: lkupClass.
  				"NOTREACHED"
  				self assert: false]].
  	instructionPointer := self popStack.
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[self executeNewMethod.
  		 self assert: false
  		 "NOTREACHED"].
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>findNewMethodInClassTag: (in category 'message sending') -----
  findNewMethodInClassTag: classTag
  	"Find the compiled method to be run when the current messageSelector is
  	 sent to the given classTag, setting the values of newMethod and primitiveIndex."
  	| ok class |
  	<inline: false>
  	ok := self lookupInMethodCacheSel: messageSelector classTag: classTag.
  	ok	ifTrue:
  			[self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
  		ifFalse:
  			["entry was not found in the cache; look it up the hard way "
  			 class := objectMemory classForClassTag: classTag.
+ 			 objectMemory hasSpurMemoryManagerAPI ifTrue:
+ 			 	[| oop |
+ 				 oop := self stackValue: argumentCount.
+ 				 ((objectMemory isNonImmediate: oop)
+ 				  and: [objectMemory isForwarded: oop]) ifTrue:
+ 					[self stackValue: argumentCount put: (objectMemory followForwarded: oop)]].
  			 self lookupMethodInClass: class.
  			 self addNewMethodToCache: class]!

Item was changed:
  ----- 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 lookupInMethodCacheSel: messageSelector classTag: lkupClassTag.
  	ok	ifTrue:
  			[self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
  		ifFalse:
  			["entry was not found in the cache; look it up the hard way"
  			lkupClass := objectMemory classForClassTag: lkupClassTag.
+ 			objectMemory hasSpurMemoryManagerAPI ifTrue:
+ 				[| oop |
+ 				 oop := self internalStackValue: argumentCount.
+ 				 ((objectMemory isNonImmediate: oop)
+ 				  and: [objectMemory isForwarded: oop]) ifTrue:
+ 					[self internalStackValue: argumentCount put: (objectMemory followForwarded: oop)]].
  			self externalizeIPandSP.
  			self lookupMethodInClass: lkupClass.
  			self internalizeIPandSP.
  			self addNewMethodToCache: lkupClass]!

Item was changed:
  ----- Method: NewObjectMemory>>classTagForSpecialObjectsIndex:compactClassIndex: (in category 'interpreter access') -----
  classTagForSpecialObjectsIndex: splObjIndex compactClassIndex: compactClassIndex
  	"For compatibility with Spur.  Answer the class tag to use to lookup a method in the
+ 	 first-level method lookup cache."
- 	 first-;evel method lookup cache."
  	^self splObj: splObjIndex!

Item was added:
+ ----- Method: SpurMemoryManager>>classTagForSpecialObjectsIndex:compactClassIndex: (in category 'interpreter access') -----
+ classTagForSpecialObjectsIndex: splObjIndex compactClassIndex: compactClassIndex
+ 	"Answer the compactClassIndex to use as a tag in the first-level method lookup cache."
+ 	^compactClassIndex!

Item was changed:
  ----- Method: StackInterpreter>>addNewMethodToCache: (in category 'method lookup cache') -----
  addNewMethodToCache: class
  	"Add the given entry to the method cache.
  	The policy is as follows:
  		Look for an empty entry anywhere in the reprobe chain.
  		If found, install the new entry there.
  		If not found, then install the new entry at the first probe position
  			and delete the entries in the rest of the reprobe chain.
  		This has two useful purposes:
  			If there is active contention over the first slot, the second
  				or third will likely be free for reentry after ejection.
  			Also, flushing is good when reprobe chains are getting full."
  	| probe hash primitiveIndex |
  	<inline: false>
  	hash := messageSelector bitXor: class.  "drop low-order zeros from addresses"
  	(objectMemory isOopCompiledMethod: newMethod)
  		ifTrue:
  			[primitiveIndex := self primitiveIndexOf: newMethod.
  			 primitiveFunctionPointer := self functionPointerFor: primitiveIndex inClass: class]
  		ifFalse:
  			[primitiveFunctionPointer := #primitiveInvokeObjectAsMethod].
  
  	0 to: CacheProbeMax-1 do:
  		[:p | probe := (hash >> p) bitAnd: MethodCacheMask.
  		(methodCache at: probe + MethodCacheSelector) = 0 ifTrue:
  			["Found an empty entry -- use it"
  			methodCache at: probe + MethodCacheSelector put: messageSelector.
  			methodCache at: probe + MethodCacheClass put: (objectMemory classTagForClass: class).
  			methodCache at: probe + MethodCacheMethod put: newMethod.
  			methodCache at: probe + MethodCachePrimFunction put: (self cCoerce: primitiveFunctionPointer to: #long).
  			lastMethodCacheProbeWrite := probe. "this for primitiveExternalMethod"
  			^ nil]].
  
  	"OK, we failed to find an entry -- install at the first slot..."
  	probe := hash bitAnd: MethodCacheMask.  "first probe"
  	methodCache at: probe + MethodCacheSelector put: messageSelector.
+ 	methodCache at: probe + MethodCacheClass put: (objectMemory classTagForClass: class).
- 	methodCache at: probe + MethodCacheClass put: class.
  	methodCache at: probe + MethodCacheMethod put: newMethod.
  	methodCache at: probe + MethodCachePrimFunction put: (self cCoerce: primitiveFunctionPointer to: #long).
  	lastMethodCacheProbeWrite := probe. "this for primitiveExternalMethod"
  
  	"...and zap the following entries"
  	1 to: CacheProbeMax-1 do:
  		[:p | probe := (hash >> p) bitAnd: MethodCacheMask.
  		methodCache at: probe + MethodCacheSelector put: 0]!

Item was changed:
  ----- Method: StackInterpreter>>findNewMethodInClassTag: (in category 'message sending') -----
  findNewMethodInClassTag: classTag
  	"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 class |
  	<inline: false>
  	ok := self lookupInMethodCacheSel: messageSelector classTag: classTag.
  	ok ifFalse: "entry was not found in the cache; look it up the hard way "
  		[class := objectMemory classForClassTag: classTag.
+ 		 objectMemory hasSpurMemoryManagerAPI ifTrue:
+ 		 	[| oop |
+ 			 oop := self stackValue: argumentCount.
+ 			 ((objectMemory isNonImmediate: oop)
+ 			  and: [objectMemory isForwarded: oop]) ifTrue:
+ 				[self stackValue: argumentCount put: (objectMemory followForwarded: oop)]].
  		 self lookupMethodInClass: class.
  		 self addNewMethodToCache: class]!

Item was changed:
  ----- 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'."
  	| ok | 
  	<inline: true>
  	ok := self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag.
  	ok ifFalse: "entry was not found in the cache; look it up the hard way"
  		[lkupClass := objectMemory classForClassTag: lkupClassTag.
+ 		 objectMemory hasSpurMemoryManagerAPI ifTrue:
+ 			[| oop |
+ 			 oop := self internalStackValue: argumentCount.
+ 			 ((objectMemory isNonImmediate: oop)
+ 			  and: [objectMemory isForwarded: oop]) ifTrue:
+ 				[self internalStackValue: argumentCount put: (objectMemory followForwarded: oop)]].
  		 self externalizeIPandSP.
  		 self lookupMethodInClass: lkupClass.
  		 self internalizeIPandSP.
  		 self addNewMethodToCache: lkupClass]!



More information about the Vm-dev mailing list