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

commits at source.squeak.org commits at source.squeak.org
Fri Jun 26 04:02:56 UTC 2015


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

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

Name: VMMaker.oscog-rmacnak.1382
Author: rmacnak
Time: 25 June 2015, 9:01:41.81 pm
UUID: 21362455-f28a-4718-9285-bc2c42a55fb1
Ancestors: VMMaker.oscog-eem.1381

Distinguish lookup for ordinary sends and for MNU processing in the JIT. Skip private methods and stop on protected methods in ordinary lookup. This should complete Newspeak access control.

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

Item was changed:
  ----- Method: CoInterpreter>>ceCounterTripped: (in category 'cog jit support') -----
  ceCounterTripped: condition
  	"Two things are going on here.  The main one is catching a counter trip and attempting
  	 to send the SelectorCounterTripped selector.  In this case we would like to back-up
  	 the pc to the return address of the send that yields the boolean to be tested, so that
  	 after potential optimization, computation proceeds by retrying the jump.  But we cannot,
  	 since there may be no send, just a pop (as in and: [] and or: [] chains).  In this case we also
  	 want to prevent further callbacks until optimization is complete.  So we nil-out the
  	 SelectorCounterTripped entry in the specialSelectorArray.
  
  	 The minor case is that there is an unlikely  possibility that the cointer tripped but condition
  	 is not a boolean, in which case a mustBeBoolean response should occur."
  	<api>
  	<option: #SistaStackToRegisterMappingCogit>
  	"Send e.g. thisContext conditionalBranchCounterTrippedOn: boolean."
  	| context counterTrippedSelector classTag |
  	(condition = objectMemory falseObject
  	or: [condition = objectMemory trueObject]) ifFalse:
  		[^self ceSendMustBeBoolean: condition].
  
  	counterTrippedSelector := objectMemory maybeSplObj: SelectorCounterTripped.
  	(counterTrippedSelector isNil
  	or: [counterTrippedSelector = objectMemory nilObject]) ifTrue:
  		[cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  		 ^condition].
  
  	classTag := objectMemory
  					classTagForSpecialObjectsIndex: ClassMethodContext
  					compactClassIndex: ClassMethodContextCompactIndex.
  	(self lookupInMethodCacheSel: counterTrippedSelector classTag: classTag) ifFalse:
  	 	[messageSelector := counterTrippedSelector.
+ 		 (self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
- 		 (self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  			[cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  			 ^condition]].
  
  	(primitiveFunctionPointer ~= 0
  	or: [(self argumentCountOf: newMethod) ~= 1]) ifTrue:
  		[cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  		 ^condition].
  
  	objectMemory splObj: SelectorCounterTripped put: objectMemory nilObject.
  	instructionPointer := self popStack.
  	context := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	self push: context.
  	self push: condition.
  	self ifAppropriateCompileToNativeCode: newMethod selector: counterTrippedSelector.
  	self activateNewMethod.
  	"not reached"
  	^true!

Item was changed:
  ----- Method: CoInterpreter>>ceSend:above:to:numArgs: (in category 'trampolines') -----
  ceSend: selector above: startAssociationArg to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked directed super send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
  	startAssociation is an association whose value is the class above which to start the lookup.
  
  	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: #BytecodeSetHasDirectedSuperSend>
  	| startAssociation 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.
  	startAssociation := objectMemory followMaybeForwarded: startAssociationArg.
  	classTag := objectMemory classTagForClass: (self superclassOf: (objectMemory fetchPointer: ValueIndex ofObject: startAssociation)).
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[self deny: (objectMemory isForwardedClassTag: classTag).
  			 (objectMemory isOopForwarded: selector) ifTrue:
  				[^self
  					ceSend: (self handleForwardedSelectorFaultFor: selector)
  					above: startAssociation
  					to: rcvr
  					numArgs: numArgs].
  			 messageSelector := selector.
+ 			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
- 			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  				[(errSelIdx = SelectorDoesNotUnderstand
  				  and: [(cogMethod := cogit cogMNUPICSelector: messageSelector
  											receiver: rcvr
  											methodOperand: (self mnuMethodOrNilFor: rcvr)
  											numArgs: argumentCount) asUnsignedInteger
  						> cogit minCogMethodAddress]) ifTrue:
  						[cogit
  							linkSendAt: (stackPages longAt: stackPointer)
  							in: (self mframeHomeMethod: framePointer)
  							to: cogMethod
  							offset: cogit noCheckEntryOffset
  							receiver: rcvr].
  				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.  The receiver's class may be young.
  	 If the Cogit can't store young classes in inline caches we can link to an open PIC instead."
  	(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 noCheckEntryOffset
  					receiver: rcvr]
  			ifFalse: "If patchToOpenPICFor:.. returns we're out of code memory"
  				[cogit
  					patchToOpenPICFor: selector
  					numArgs: numArgs
  					receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceSend:super:to:numArgs: (in category 'trampolines') -----
  ceSend: selector super: superNormalBar to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked 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>
  	| 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.
  	superNormalBar = 0
  		ifTrue: [classTag := objectMemory fetchClassTagOf: rcvr]
  		ifFalse: [classTag := objectMemory classTagForClass: (self superclassOf: (self methodClassOf: (self frameMethodObject: framePointer)))].
  	argumentCount := numArgs.
  	(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
  					ceSend: (self handleForwardedSelectorFaultFor: selector)
  					super: superNormalBar
  					to: rcvr
  					numArgs: numArgs].
  			 (objectMemory isForwardedClassTag: classTag) ifTrue:
  				[self assert: superNormalBar = 0.
  				^self
  					ceSend: selector
  					super: superNormalBar
  					to: (self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc")
  					numArgs: numArgs].
  			 messageSelector := selector.
+ 			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
- 			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  				[(errSelIdx = SelectorDoesNotUnderstand
  				  and: [(cogMethod := cogit cogMNUPICSelector: messageSelector
  											receiver: rcvr
  											methodOperand: (self mnuMethodOrNilFor: rcvr)
  											numArgs: argumentCount) asUnsignedInteger
  						> cogit minCogMethodAddress]) ifTrue:
  						[cogit
  							linkSendAt: (stackPages longAt: stackPointer)
  							in: (self mframeHomeMethod: framePointer)
  							to: cogMethod
  							offset: (superNormalBar = 0
  									ifTrue: [cogit entryOffset]
  									ifFalse: [cogit noCheckEntryOffset])
  							receiver: rcvr].
  				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.  The receiver's class may be young.
  	 If the Cogit can't store young classes in inline caches we can link to an open PIC instead."
  	(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: (superNormalBar = 0
  								ifTrue: [cogit entryOffset]
  								ifFalse: [cogit noCheckEntryOffset])
  					receiver: rcvr]
  			ifFalse: "If patchToOpenPICFor:.. returns we're out of code memory"
  				[cogit
  					patchToOpenPICFor: selector
  					numArgs: numArgs
  					receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceSendAbort:to:numArgs: (in category 'trampolines') -----
  ceSendAbort: selector to: rcvr numArgs: numArgs
  	"Entry-point for an abort send in a CogMethod (aboutToReturn:through:, cannotReturn: et al).
  	 Try and dispatch the send, but the send may turn into an MNU in which case defer to
  	 handleMNUInMachineCodeTo:... which will dispatch the MNU.
  
  	 Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	 depending on whether the target method is cogged or not."
  	<api>
  	| classTag errSelIdx |
  	<inline: false>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self sendBreakpoint: selector receiver: rcvr.
  	argumentCount := numArgs.
  	classTag := objectMemory fetchClassTagOf: rcvr.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[messageSelector := selector.
+ 			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
- 			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: (objectMemory classForClassTag: classTag).
  				"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>>ceSendFromInLineCacheMiss: (in category 'trampolines') -----
  ceSendFromInLineCacheMiss: cogMethodOrPIC
  	"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),
  	 or when a send has failed due to a forwarded receiver."
  	<api>
  	<var: #cogMethodOrPIC type: #'CogMethod *'>
  	| numArgs rcvr classTag errSelIdx |
  	"self printFrame: stackPage headFP WithSP: stackPage headSP"
  	"self printStringOf: selector"
  	numArgs := cogMethodOrPIC cmNumArgs.
  	rcvr := self stackValue: numArgs + 1. "skip return pc"
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	classTag := objectMemory fetchClassTagOf: rcvr.
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: cogMethodOrPIC selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: cogMethodOrPIC selector]
  		ifFalse:
  			[(objectMemory isOopForwarded: cogMethodOrPIC selector) ifTrue:
  				[self handleForwardedSelectorFaultFor: cogMethodOrPIC selector.
  				 ^self ceSendFromInLineCacheMiss: cogMethodOrPIC].
  			 (objectMemory isForwardedClassTag: classTag) ifTrue:
  				[self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc".
  				 ^self ceSendFromInLineCacheMiss: cogMethodOrPIC].
  			 messageSelector := cogMethodOrPIC selector.
+ 			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
- 			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: (objectMemory classForClassTag: classTag).
  				"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: classTagArg
  	"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 classTag |
- 	| ok class classTag |
  	<inline: false>
  	ok := self lookupInMethodCacheSel: messageSelector classTag: classTagArg.
  	ok	ifTrue:
  			[self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
  		ifFalse:
  			["entry was not found in the cache; perhaps soemthing was forwarded."
  			 classTag := classTagArg.
  			 ((objectMemory isOopForwarded: messageSelector)
  			  or: [objectMemory isForwardedClassTag: classTag]) ifTrue:
  				[(objectMemory isOopForwarded: messageSelector) ifTrue:
  					[messageSelector := self handleForwardedSelectorFaultFor: messageSelector].
  				 (objectMemory isForwardedClassTag: classTag) ifTrue:
  					[classTag := self handleForwardedSendFaultForTag: classTag].
  				ok := self lookupInMethodCacheSel: messageSelector classTag: classTag.
  				ok ifTrue:
  					[^self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]].
  			 "entry was not found in the cache; look it up the hard way "
+ 			 lkupClass := objectMemory classForClassTag: classTag.
+ 			 self cppIf: #NewspeakVM
+ 				ifTrue: [self lookupOrdinarySend]
+ 				ifFalse: [self lookupMethodInClass: lkupClass].
+ 			 self lookupMethodInClass: lkupClass.
+ 			 self addNewMethodToCache: lkupClass]!
- 			 class := objectMemory classForClassTag: classTag.
- 			 self lookupMethodInClass: class.
- 			 self addNewMethodToCache: class]!

Item was changed:
  ----- Method: CoInterpreter>>handleMNU:InMachineCodeTo:classForMessage: (in category 'message sending') -----
  handleMNU: selectorIndex InMachineCodeTo: rcvr classForMessage: classForMessage
  	"A message send from either an open PIC or an unlinked send has not  been
  	 understood.  Create a message and execute the relevant resulting MNU method.
  	 messageSelector is an implicit argument (yuck)."
  	| errSelIdx classForThisMessage |
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	instructionPointer := self popStack.
  	self createActualMessageTo: classForMessage.
  	messageSelector := objectMemory splObj: selectorIndex.
  	(self lookupInMethodCacheSel: messageSelector classTag: (objectMemory classTagForClass: lkupClass))
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: messageSelector]
  		ifFalse:
+ 			[errSelIdx := self lookupMNUInClass: (classForThisMessage := lkupClass).
- 			[errSelIdx := self lookupMethodNoMNUEtcInClass: (classForThisMessage := lkupClass).
  			 errSelIdx ~= 0 ifTrue:
  				[selectorIndex = SelectorDoesNotUnderstand ifTrue:
  					[self error: 'Recursive not understood error encountered'].
  				 self push: instructionPointer.
  				 ^self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: classForThisMessage]].
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[self push: instructionPointer.
  		 self executeCogMethod: (self cogMethodOf: newMethod)
  			 fromUnlinkedSendWithReceiver: rcvr.
  		 "NOTREACHED"
  		 self assert: false].
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>internalFindNewMethodOrdinary (in category 'message sending') -----
  internalFindNewMethodOrdinary
  	"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 cppIf: #NewspeakVM
+ 				ifTrue: [self lookupOrdinarySend]
+ 				ifFalse: [self lookupMethodInClass: lkupClass].
- 			self lookupMethodInClass: lkupClass.
  			self internalizeIPandSP.
  			self addNewMethodToCache: lkupClass]!

Item was removed:
- ----- Method: CoInterpreter>>lookup:receiver: (in category 'cog jit support') -----
- lookup: selector receiver: rcvr
- 	<api>
- 	"Lookup selector in rcvr, without doing MNU processing, and answer either a
- 	 method or an error code if the message was not understood.  Used to populate closed PICs."
- 	| classTag erridx |
- 	"self printFrame: stackPage headFP WithSP: stackPage headSP"
- 	"self printStringOf: selector"
- 	classTag := objectMemory fetchClassTagOf: rcvr.
- 	(self lookupInMethodCacheSel: selector classTag: classTag) ifFalse:
- 		[messageSelector := selector.
- 		 (erridx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
- 			[self assert: erridx <= self maxLookupNoMNUErrorCode.
- 			 ^erridx]].
- 	^newMethod!

Item was added:
+ ----- Method: CoInterpreter>>lookupMNU:receiver: (in category 'cog jit support') -----
+ lookupMNU: selector receiver: rcvr
+ 	<api>
+ 	"Lookup selector in rcvr, without doing MNU processing, and answer either a
+ 	 method or an error code if the message was not understood.  Used to populate closed PICs."
+ 	| classTag inCache erridx |
+ 	"self printFrame: stackPage headFP WithSP: stackPage headSP"
+ 	"self printStringOf: selector"
+ 	classTag := objectMemory fetchClassTagOf: rcvr.
+ 	self cppIf: #NewspeakVM
+ 	  	ifTrue:
+ 			[inCache := (self
+ 				inlineLookupInNSMethodCacheSel: selector
+ 				classTag: classTag
+ 				method: 0
+ 				lookupRule: LookupRuleMNU)]
+ 		ifFalse:
+ 			[inCache := self lookupInMethodCacheSel: selector classTag: classTag].
+ 	inCache ifFalse:
+ 		[messageSelector := selector.
+ 		 erridx := self lookupMNUInClass: (objectMemory classForClassTag: classTag).
+ 		 erridx ~= 0 ifTrue:
+ 			[self assert: erridx <= self maxLookupNoMNUErrorCode.
+ 			 ^erridx]].
+ 	^newMethod!

Item was added:
+ ----- Method: CoInterpreter>>lookupOrdinary:receiver: (in category 'cog jit support') -----
+ lookupOrdinary: selector receiver: rcvr
+ 	<api>
+ 	"Lookup selector in rcvr, without doing MNU processing, and answer either a
+ 	 method or an error code if the message was not understood.  Used to populate closed PICs."
+ 	| classTag erridx |
+ 	"self printFrame: stackPage headFP WithSP: stackPage headSP"
+ 	"self printStringOf: selector"
+ 	classTag := objectMemory fetchClassTagOf: rcvr.
+ 	(self lookupInMethodCacheSel: selector classTag: classTag) ifFalse:
+ 		[messageSelector := selector.
+ 		 (erridx := self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
+ 			[self assert: erridx <= self maxLookupNoMNUErrorCode.
+ 			 ^erridx]].
+ 	^newMethod!

Item was removed:
- ----- Method: CogVMSimulator>>lookupMethodNoMNUEtcInClass: (in category 'callback support') -----
- lookupMethodNoMNUEtcInClass: class
- 	lookupCount := lookupCount + 1.
- 	^super lookupMethodNoMNUEtcInClass: class!

Item was added:
+ ----- Method: CogVMSimulator>>lookupOrdinaryNoMNUEtcInClass: (in category 'callback support') -----
+ lookupOrdinaryNoMNUEtcInClass: class
+ 	lookupCount := lookupCount + 1.
+ 	^super lookupOrdinaryNoMNUEtcInClass: class!

Item was changed:
  ----- Method: Cogit>>lookup:for:methodAndErrorSelectorInto: (in category 'in-line cacheing') -----
  lookup: selector for: receiver methodAndErrorSelectorInto: binaryBlock
  	"Lookup selector in the class of receiver.  If found, evaluate binaryBlock with the
  	 method, cogged if appropriate..  If not found, due to MNU, lookup the DNU selector
  	 and evaluate binaryBlock with the MNU method, cogged if appropriate..  If not found
  	 due to cannot interpret, evaluate binaryBlock with a nil method and the error selector."
  	| methodOrSelectorIndex |
  	<inline: true>
  	methodOrSelectorIndex := coInterpreter
+ 									lookupOrdinary: selector
- 									lookup: selector
  									receiver: receiver.
  	methodOrSelectorIndex asUnsignedInteger > coInterpreter maxLookupNoMNUErrorCode ifTrue:
  		[(objectMemory isOopCompiledMethod: methodOrSelectorIndex) ifFalse:
  			[^binaryBlock value: methodOrSelectorIndex value: SelectorCannotInterpret].
  		 ((coInterpreter methodHasCogMethod: methodOrSelectorIndex) not
  		  and: [coInterpreter methodShouldBeCogged: methodOrSelectorIndex]) ifTrue:
  			["We assume cog:selector: will *not* reclaim the method zone"
  			 self cog: methodOrSelectorIndex selector: selector].
  		^binaryBlock value: methodOrSelectorIndex value: nil].
  	methodOrSelectorIndex = SelectorDoesNotUnderstand ifTrue:
  		[methodOrSelectorIndex := coInterpreter
+ 										lookupMNU: (objectMemory splObj: SelectorDoesNotUnderstand)
- 										lookup: (objectMemory splObj: SelectorDoesNotUnderstand)
  										receiver: receiver.
  		 methodOrSelectorIndex asUnsignedInteger > coInterpreter maxLookupNoMNUErrorCode ifTrue:
  			[self assert: (objectMemory isOopCompiledMethod: methodOrSelectorIndex).
  			 ((coInterpreter methodHasCogMethod: methodOrSelectorIndex) not
  			  and: [coInterpreter methodShouldBeCogged: methodOrSelectorIndex]) ifTrue:
  				["We assume cog:selector: will *not* reclaim the method zone"
  				 self cog: methodOrSelectorIndex selector: (objectMemory splObj: SelectorDoesNotUnderstand)].
  			^binaryBlock value: methodOrSelectorIndex value: SelectorDoesNotUnderstand].
  		^binaryBlock value: nil value: SelectorDoesNotUnderstand].
  	^binaryBlock value: nil value: methodOrSelectorIndex!

Item was changed:
  ----- Method: StackInterpreter>>findNewMethodInClassTag: (in category 'message sending') -----
  findNewMethodInClassTag: classTagArg
  	"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 classTag |
- 	| ok class classTag |
  	<inline: false>
  	ok := self lookupInMethodCacheSel: messageSelector classTag: classTagArg.
  	ok ifFalse: "entry was not found in the cache; look it up the hard way "
  		[classTag := classTagArg.
  		 ((objectMemory isOopForwarded: messageSelector)
  		  or: [objectMemory isForwardedClassTag: classTag]) ifTrue:
  			[(objectMemory isOopForwarded: messageSelector) ifTrue:
  				[messageSelector := self handleForwardedSelectorFaultFor: messageSelector].
  			 (objectMemory isForwardedClassTag: classTag) ifTrue:
  				[classTag := self handleForwardedSendFaultForTag: classTag].
  			ok := self lookupInMethodCacheSel: messageSelector classTag: classTag.
  			ok ifTrue:
  				[^nil]].
+  		 lkupClass := objectMemory classForClassTag: classTag.
+ 		 self cppIf: #NewspeakVM
+ 				ifTrue: [self lookupOrdinarySend]
+ 				ifFalse: [self lookupMethodInClass: lkupClass].
+ 		 self addNewMethodToCache: lkupClass]!
- 		 class := objectMemory classForClassTag: classTag.
- 		 self lookupMethodInClass: class.
- 		 self addNewMethodToCache: class]!

Item was added:
+ ----- Method: StackInterpreter>>lookupMNUInClass: (in category 'message sending') -----
+ lookupMNUInClass: class
+ 	"Lookup messageSelector in class.  Answer 0 on success. Answer the splObj: index
+ 	 for the error selector to use on failure rather than performing MNU processing etc."
+ 	| currentClass dictionary found |
+ 	<inline: false>
+ 	currentClass := class.
+ 	[currentClass ~= objectMemory nilObject] whileTrue:
+ 		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
+ 		 dictionary = objectMemory nilObject ifTrue:
+ 			[lkupClass := self superclassOf: currentClass.
+ 			 ^SelectorCannotInterpret].
+ 		found := self lookupMethodInDictionary: dictionary.
+ 		self cppIf: #NewspeakVM
+ 			ifTrue: [found ifTrue: [lkupClass := class. self addNewMethodToNSCache: LookupRuleMNU. ^0]]
+ 			ifFalse: [found ifTrue: [self addNewMethodToCache: class. ^0]].
+ 		currentClass := self superclassOf: currentClass].
+ 	lkupClass := class.
+ 	^SelectorDoesNotUnderstand!

Item was changed:
  ----- Method: StackInterpreter>>lookupMethodNoMNUEtcInClass: (in category 'message sending') -----
  lookupMethodNoMNUEtcInClass: class
  	"Lookup messageSelector in class.  Answer 0 on success. Answer the splObj: index
  	 for the error selector to use on failure rather than performing MNU processing etc."
+ 	| currentClass dictionary found |
- 	| currentClass dictionary |
  	<inline: false>
  	currentClass := class.
  	[currentClass ~= objectMemory nilObject] whileTrue:
  		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
  		 dictionary = objectMemory nilObject ifTrue:
  			[lkupClass := self superclassOf: currentClass.
  			 ^SelectorCannotInterpret].
+ 		found := self lookupMethodInDictionary: dictionary.
+ 		self cppIf: #NewspeakVM
+ 			ifTrue:
+ 				[found ifTrue:
+ 					[(self accessModifierOfMethod: newMethod) == AccessModifierPublic
+ 						ifTrue: [self addNewMethodToCache: class. ^0].
+ 					(self accessModifierOfMethod: newMethod) == AccessModifierProtected
+ 						ifTrue: [^SelectorDoesNotUnderstand]]]
+ 			ifFalse:
+ 				[found ifTrue: [self addNewMethodToCache: class. ^0]].
- 		 (self lookupMethodInDictionary: dictionary) ifTrue:
- 			[self addNewMethodToCache: class.
- 			 ^0].
  		currentClass := self superclassOf: currentClass].
  	lkupClass := class.
  	^SelectorDoesNotUnderstand!

Item was added:
+ ----- Method: StackInterpreter>>lookupOrdinaryNoMNUEtcInClass: (in category 'message sending') -----
+ lookupOrdinaryNoMNUEtcInClass: class
+ 	"Lookup messageSelector in class.  Answer 0 on success. Answer the splObj: index
+ 	 for the error selector to use on failure rather than performing MNU processing etc."
+ 	| currentClass dictionary found |
+ 	<inline: false>
+ 	currentClass := class.
+ 	[currentClass ~= objectMemory nilObject] whileTrue:
+ 		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
+ 		 dictionary = objectMemory nilObject ifTrue:
+ 			[lkupClass := self superclassOf: currentClass.
+ 			 ^SelectorCannotInterpret].
+ 		found := self lookupMethodInDictionary: dictionary.
+ 		self cppIf: #NewspeakVM
+ 			ifTrue:
+ 				[found ifTrue:
+ 					[(self accessModifierOfMethod: newMethod) == AccessModifierPublic
+ 						ifTrue: [self addNewMethodToCache: class. ^0].
+ 					(self accessModifierOfMethod: newMethod) == AccessModifierProtected
+ 						ifTrue: [^SelectorDoesNotUnderstand]]]
+ 			ifFalse:
+ 				[found ifTrue: [self addNewMethodToCache: class. ^0]].
+ 		currentClass := self superclassOf: currentClass].
+ 	lkupClass := class.
+ 	^SelectorDoesNotUnderstand!

Item was changed:
  ----- Method: StackInterpreter>>sendInvokeCallback:Stack:Registers:Jmpbuf: (in category 'callback support') -----
  sendInvokeCallback: thunkPtr Stack: stackPtr Registers: regsPtr Jmpbuf: jmpBufPtr
  	"Send the 4 argument callback message invokeCallback:stack:registers:jmpbuf:
  	 to Alien class with the supplied args.  The arguments are raw C addresses
  	 and are converted to integer objects on the way."
  	<export: true>
  	| classTag |
  	classTag := self fetchClassTagOfNonImm: (self splObj: ClassAlien).
  	messageSelector := self splObj: SelectorInvokeCallback.
  	argumentCount := 4.
  	(self lookupInMethodCacheSel: messageSelector classTag: classTag) ifFalse:
+ 	 	[(self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
- 	 	[(self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  			[^false]].
  	((self argumentCountOf: newMethod) = 4
  	and: [primitiveFunctionPointer = 0]) ifFalse:
  		[^false].
  	self push: (self splObj: ClassAlien). "receiver"
  	self push: (self positiveMachineIntegerFor: thunkPtr).
  	self push: (self positiveMachineIntegerFor: stackPtr).
  	self push: (self positiveMachineIntegerFor: regsPtr).
  	self push: (self positiveMachineIntegerFor: jmpBufPtr).
  	self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector.
  	self justActivateNewMethod.
  	(self isMachineCodeFrame: framePointer) ifFalse:
  		[self maybeFlagMethodAsInterpreted: newMethod].
  	self externalWriteBackHeadFramePointers.
  	self handleStackOverflow.
  	self enterSmalltalkExecutiveFromCallback.
  	"not reached"
  	^true!

Item was changed:
  ----- Method: StackInterpreter>>sendInvokeCallbackContext: (in category 'callback support') -----
  sendInvokeCallbackContext: vmCallbackContext
  	"Send the calllback message to Alien class with the supplied arg(s).  Use either the
  	 1 arg invokeCallbackContext: or the 4 arg invokeCallback:stack:registers:jmpbuf:
  	 message, depending on what selector is installed in the specialObjectsArray.
  	 Note that if invoking the legacy invokeCallback:stack:registers:jmpbuf: we pass the
  	 vmCallbackContext as the jmpbuf argument (see reestablishContextPriorToCallback:).
  	 The arguments are raw C addresses and are converted to integer objects on the way."
  	<export: true>
  	<var: #vmCallbackContext type: #'VMCallbackContext *'>
  	| classTag |
  	classTag := self fetchClassTagOfNonImm: (self splObj: ClassAlien).
  	messageSelector := self splObj: SelectorInvokeCallback.
  	(self lookupInMethodCacheSel: messageSelector classTag: classTag) ifFalse:
+ 	 	[(self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
- 	 	[(self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  			[^false]].
  	primitiveFunctionPointer ~= 0 ifTrue:
  		[^false].
  	self saveCStackStateForCallbackContext: vmCallbackContext.
  	self push: (self splObj: ClassAlien). "receiver"
  	(self argumentCountOf: newMethod) = 4 ifTrue:
  		[self push: (self positiveMachineIntegerFor: vmCallbackContext thunkp asUnsignedInteger).
  		 self push: (self positiveMachineIntegerFor: vmCallbackContext stackp asUnsignedInteger).
  		 self push: (self positiveMachineIntegerFor: vmCallbackContext intregargsp asUnsignedInteger)].
  	self push: (self positiveMachineIntegerFor: vmCallbackContext asUnsignedInteger).
  	self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector.
  	self justActivateNewMethod.
  	(self isMachineCodeFrame: framePointer) ifFalse:
  		[self maybeFlagMethodAsInterpreted: newMethod].
  	self externalWriteBackHeadFramePointers.
  	self handleStackOverflow.
  	self enterSmalltalkExecutiveFromCallback.
  	"not reached"
  	^true!

Item was removed:
- ----- Method: StackInterpreterSimulator>>lookupMethodNoMNUEtcInClass: (in category 'callback support') -----
- lookupMethodNoMNUEtcInClass: class
- 	lookupCount := lookupCount + 1.
- 	^super lookupMethodNoMNUEtcInClass: class!

Item was added:
+ ----- Method: StackInterpreterSimulator>>lookupOrdinaryNoMNUEtcInClass: (in category 'callback support') -----
+ lookupOrdinaryNoMNUEtcInClass: class
+ 	lookupCount := lookupCount + 1.
+ 	^super lookupOrdinaryNoMNUEtcInClass: class!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurCogVM (in category 'configurations') -----
  generateNewspeakSpurCogVM
  	"No primitives since we can use those for the Cog Newspeak VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(	ObjectMemory Spur32BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
  				NewspeakVM true
+ 				EnforceAccessControl true)
- 				EnforceAccessControl false)
  		to: (FileDirectory default pathFromURI: self sourceTree, '/nsspursrc')
  		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation
  					DeflatePlugin DSAPlugin DropPlugin FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin
  					ImmX11Plugin JPEGReadWriter2Plugin JPEGReaderPlugin LargeIntegersPlugin
  					Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin RePlugin
  					SecurityPlugin SocketPlugin SoundPlugin SqueakSSLPlugin SurfacePlugin
  					UUIDPlugin UnixOSProcessPlugin UnixAioPlugin
  					VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)
  !



More information about the Vm-dev mailing list