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

commits at source.squeak.org commits at source.squeak.org
Mon Jun 22 00:27:11 UTC 2015


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

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

Name: VMMaker.oscog-rmacnak.1372
Author: rmacnak
Time: 21 June 2015, 5:25:31.325 pm
UUID: addc4f0f-0a6b-4594-b946-a7f8af54d6a4
Ancestors: VMMaker.oscog-eem.1371

Enforce Newspeak access control in the interpreter, and enable it in Stack VMs. Disable in Cog VMs to avoid partial enforcement. Should be eliminated by Slang from Squeak VMs.

Add a separate global lookup cache for non-ordinary sends.

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

Item was removed:
- ----- Method: CoInterpreter>>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."
- 	<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: LookupRuleOrdinary.
- 	self internalExecuteNewMethod.
- 	self fetchNextBytecode!

Item was removed:
- ----- 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 added:
+ ----- Method: CoInterpreter>>commonSendOrdinary (in category 'send bytecodes') -----
+ commonSendOrdinary
+ 	"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: 'commonSendOrdinary' 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 internalFindNewMethodOrdinary.
+ 	self internalExecuteNewMethod.
+ 	self fetchNextBytecode!

Item was removed:
- ----- 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 added:
+ ----- 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 lookupMethodInClass: lkupClass.
+ 			self internalizeIPandSP.
+ 			self addNewMethodToCache: lkupClass]!

Item was changed:
  ----- Method: CogVMSimulator>>initialize (in category 'initialization') -----
  initialize
  	"Initialize the CogVMSimulator when running the interpreter inside Smalltalk.  The
  	 primary responsibility of this method is to allocate Smalltalk Arrays for variables
  	 that will be declared as statically-allocated global arrays in the translated code."
  	super initialize.
  
  	transcript := Transcript.
  
  	objectMemory ifNil:
  		[objectMemory := self class objectMemoryClass simulatorClass new].
  	cogit ifNil:
  		[cogit := self class cogitClass new setInterpreter: self].
  	objectMemory coInterpreter: self cogit: cogit.
  
  	cogit numRegArgs > 0 ifTrue:
  		[debugStackDepthDictionary := Dictionary new].
  
  	cogThreadManager ifNotNil:
  		[super initialize].
  
  	"Note: we must initialize ConstMinusOne & HasBeenReturnedFromMCPC differently
  	 for simulation, due to the fact that the simulator works only with +ve 32-bit values"
  	ConstMinusOne := objectMemory integerObjectOf: -1.
  	HasBeenReturnedFromMCPC := objectMemory integerObjectOf: -1.
  	cogMethodZone := cogit methodZone. "Because Slang can't remove intermediate implicit receivers (cogit methodZone foo doesn't reduce to foo())"
  	enableCog := true.
  
  	methodCache := Array new: MethodCacheSize.
+ 	nsMethodCache := Array new: NSMethodCacheSize.
  	atCache := Array new: AtCacheTotalSize.
  	self flushMethodCache.
  	cogCompiledCodeCompactionCalledFor := false.
  	gcSemaphoreIndex := 0.
  	externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  	externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  	externalPrimitiveTableFirstFreeIndex := 0.
  	primitiveTable := self class primitiveTable copy.
  	mappedPluginEntries := OrderedCollection new.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[primitiveAccessorDepthTable := Array new: primitiveTable size.
  			 pluginList := {}.
  			 self loadNewPlugin: '']
  		ifFalse:
  			[pluginList := {'' -> self }].
  	desiredNumStackPages := desiredEdenBytes := desiredCogCodeSize := 0.
  	"This is initialized on loading the image, but convenient for testing stack page values..."
  	numStackPages := self defaultNumStackPages. 
  	startMicroseconds := Time totalSeconds * 1000000.
  	maxLiteralCountForCompile := MaxLiteralCountForCompile.
  	minBackwardJumpCountForCompile := MinBackwardJumpCountForCompile.
  	flagInterpretedMethods := false.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := lastPollCount := sendCount := lookupCount := 0.
  	quitBlock := [^ self].
  	traceOn := true.
  	printSends := printFrameAtEachStep := printBytecodeAtEachStep := false.
  	myBitBlt := BitBltSimulator new setInterpreter: self.
  	displayForm := fakeForm := 'Display has not yet been installed' asDisplayText form.
  	suppressHeartbeatFlag := deferSmash := deferredSmash := false.
  	systemAttributes := Dictionary new.
  	primTraceLog := CArrayAccessor on: (Array new: 256 withAll: 0).
  	primTraceLogIndex := 0.
  	traceLog := CArrayAccessor on: (Array new: TraceBufferSize withAll: 0).
  	traceLogIndex := 0.
  	traceSources := TraceSources.
  	statCodeCompactionCount := 0.
  	statCodeCompactionUsecs := 0.
  	extSemTabSize := 256!

Item was removed:
- ----- 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 added:
+ ----- Method: CogVMSimulator>>internalFindNewMethodOrdinary (in category 'testing') -----
+ internalFindNewMethodOrdinary
+ "
+ 	| 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 internalFindNewMethodOrdinary!

Item was changed:
  InterpreterPrimitives subclass: #StackInterpreter
+ 	instanceVariableNames: 'currentBytecode bytecodeSetSelector localFP localIP localSP stackLimit stackPage stackPages method instructionPointer stackPointer framePointer localReturnValue localAbsentReceiver localAbsentReceiverOrZero extA extB primitiveFunctionPointer methodCache nsMethodCache atCache lkupClassTag lkupClass methodDictLinearSearchLimit highestRunnableProcessPriority nextWakeupUsecs nextPollUsecs inIOProcessEvents interruptKeycode interruptPending savedWindowSize imageHeaderFlags fullScreenFlag deferDisplayUpdates pendingFinalizationSignals extraVMMemory interpreterProxy showSurfaceFn primitiveTable primitiveAccessorDepthTable externalPrimitiveTable externalPrimitiveTableFirstFreeIndex overflowedPage extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth suspendedCallbacks suspendedMethods numStackPages desiredNumStackPages desiredEdenBytes classNameIndex thisClassIndex metaclassNumSlots interruptCheckChain suppressHeartbeatFlag breakSelector breakSelectorLength longRunningPrimitiveCheckMethod longRunningPrimitiveCheckSemaphore longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs longRunningPrimitiveGCUsecs longRunningPrimitiveCheckSequenceNumber longRunningPrimitiveSignalUndelivered checkAllocFiller tempOop tempOop2 theUnknownShort the2ndUnknownShort imageFloatsBigEndian maxExtSemTabSizeSet lastMethodCacheProbeWrite gcSemaphoreIndex classByteArrayCompactIndex statForceInterruptCheck statStackOverflow statStackPageDivorce statCheckForEvents statProcessSwitch statIOProcessEvents statPendingFinalizationSignals'
+ 	classVariableNames: 'AccessModifierPrivate AccessModifierProtected AccessModifierPublic AltBytecodeEncoderClassName AltLongStoreBytecode AlternateHeaderHasPrimFlag AlternateHeaderIsOptimizedFlag AlternateHeaderNumLiteralsMask AtCacheEntries AtCacheFixedFields AtCacheFmt AtCacheMask AtCacheOop AtCacheSize AtCacheTotalSize AtPutBase BytecodeEncoderClassName BytecodeTable CacheProbeMax DirBadPath DirEntryFound DirNoMoreEntries DumpStackOnLowSpace EnclosingMixinIndex EnclosingObjectIndex EnforceAccessControl FailImbalancedPrimitives LongStoreBytecode MaxExternalPrimitiveTableSize MaxJumpBuf MaxPrimitiveIndex MaxQuickPrimitiveIndex MethodHeaderArgCountShift MethodHeaderFlagBitPosition MethodHeaderTempCountShift MixinIndex PrimitiveExternalCallIndex PrimitiveTable StackPageReachedButUntraced StackPageTraceInvalid StackPageTraced StackPageUnreached V3PrimitiveBitsMask'
- 	instanceVariableNames: 'currentBytecode bytecodeSetSelector localFP localIP localSP stackLimit stackPage stackPages method instructionPointer stackPointer framePointer localReturnValue localAbsentReceiver extA extB primitiveFunctionPointer methodCache atCache isPrivateSend lkupClassTag lkupClass methodDictLinearSearchLimit highestRunnableProcessPriority nextWakeupUsecs nextPollUsecs inIOProcessEvents interruptKeycode interruptPending savedWindowSize imageHeaderFlags fullScreenFlag deferDisplayUpdates pendingFinalizationSignals extraVMMemory interpreterProxy showSurfaceFn primitiveTable primitiveAccessorDepthTable externalPrimitiveTable externalPrimitiveTableFirstFreeIndex overflowedPage extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth suspendedCallbacks suspendedMethods numStackPages desiredNumStackPages desiredEdenBytes classNameIndex thisClassIndex metaclassNumSlots interruptCheckChain suppressHeartbeatFlag breakSelector breakSelectorLength longRunningPrimitiveCheckMethod longRunningPrimitiveCheckSemaphore longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs longRunningPrimitiveGCUsecs longRunningPrimitiveCheckSequenceNumber longRunningPrimitiveSignalUndelivered checkAllocFiller tempOop tempOop2 theUnknownShort the2ndUnknownShort imageFloatsBigEndian maxExtSemTabSizeSet lastMethodCacheProbeWrite gcSemaphoreIndex classByteArrayCompactIndex statForceInterruptCheck statStackOverflow statStackPageDivorce statCheckForEvents statProcessSwitch statIOProcessEvents statPendingFinalizationSignals'
- 	classVariableNames: 'AccessModifierPrivate AccessModifierProtected AccessModifierPublic AltBytecodeEncoderClassName AltLongStoreBytecode AlternateHeaderHasPrimFlag AlternateHeaderIsOptimizedFlag AlternateHeaderNumLiteralsMask AtCacheEntries AtCacheFixedFields AtCacheFmt AtCacheMask AtCacheOop AtCacheSize AtCacheTotalSize AtPutBase BytecodeEncoderClassName BytecodeTable CacheProbeMax CheckPrivacyViolations DirBadPath DirEntryFound DirNoMoreEntries DumpStackOnLowSpace EnclosingMixinIndex EnclosingObjectIndex FailImbalancedPrimitives LongStoreBytecode MaxExternalPrimitiveTableSize MaxJumpBuf MaxPrimitiveIndex MaxQuickPrimitiveIndex MethodHeaderArgCountShift MethodHeaderFlagBitPosition MethodHeaderTempCountShift MixinIndex PrimitiveExternalCallIndex PrimitiveTable StackPageReachedButUntraced StackPageTraceInvalid StackPageTraced StackPageUnreached V3PrimitiveBitsMask'
  	poolDictionaries: 'VMBasicConstants VMBytecodeConstants VMMethodCacheConstants VMObjectIndices VMSpurObjectRepresentationConstants VMSqueakClassIndices VMStackFrameOffsets'
  	category: 'VMMaker-Interpreter'!
  
  !StackInterpreter commentStamp: 'eem 12/5/2014 11:32' prior: 0!
  This class is a complete implementation of the Smalltalk-80 virtual machine, derived originally from the Blue Book specification but quite different in some areas.  This VM supports Closures but *not* old-style BlockContexts.
  
  It has been modernized with 32-bit pointers, better management of Contexts (see next item), and attention to variable use that allows the CCodeGenerator (qv) to keep, eg, the instruction pointer and stack pointer in registers as well as keeping most simple variables in a global array that seems to improve performance for most platforms.
  
  The VM does not use Contexts directly.  Instead Contexts serve as proxies for a more conventional stack format that is invisible to the image.  There is considerable explanation at http://www.mirandabanda.org/cogblog/2009/01/14/under-cover-contexts-and-the-big-frame-up.  The VM maintains a fixed-size stack zone divided into pages, each page being capable of holding several method/block activations.  A send establishes a new frame in the current stack page, a return returns to the previous frame.  This eliminates allocation/deallocation of contexts and the moving of receiver and arguments from caller to callee on each send/return.  Contexts are created lazily when an activation needs a context (creating a block, explicit use of thisContext, access to sender when sender is a frame, or linking of stack pages together).  Contexts are either conventional and heap-resident ("single") or "married" and serve as proxies for their corresponding frame or "widowed", meaning that their spouse frame has been returned from (died).  A married context is specially marked (more details in the code) and refers to its frame.  Likewise a married frame is specially marked and refers to its context.
  
  In addition to SmallInteger arithmetic and Floats, the VM supports logic on 32-bit PositiveLargeIntegers, thus allowing it to simulate itself much more effectively than would otherwise be the case.
  
  StackInterpreter and subclasses support multiple memory managers.  Currently there are two.  NewMemoryManager is a slightly refined version of ObjectMemory, and is the memory manager and garbage collector for the original Squeak object representation as described in "Back to the Future The Story of Squeak, A Practical Smalltalk Written in Itself", see http://ftp.squeak.org/docs/OOPSLA.Squeak.html.  Spur is a faster, more regular object representation that is designed for more performance and functionality, and to have a common header format for both 32-bit and 64-bit versions.  You can read about it in SpurMemoryManager's class comment.  There is also a video of a presentation at ESUG 2014 (https://www.youtube.com/watch?v=k0nBNS1aHZ4), along with slides (http://www.slideshare.net/esug/spur-a-new-object-representation-for-cog?related=1).!

Item was changed:
  ----- Method: StackInterpreter class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	| vmClass |
  	self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses"
  	vmClass := aCCodeGenerator vmClass. "Generate primitiveTable etc based on vmClass, not just StackInterpreter"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h> /* for e.g. alloca */';
  		addHeaderFile:'<setjmp.h>';
  		addHeaderFile:'<wchar.h> /* for wint_t */';
  		addHeaderFile:'"vmCallback.h"';
  		addHeaderFile:'"sqMemoryFence.h"';
  		addHeaderFile:'"dispdbg.h"'.
  	vmClass declareInterpreterVersionIn: aCCodeGenerator defaultName: 'Stack'.
  	aCCodeGenerator
  		var: #interpreterProxy  type: #'struct VirtualMachine*'.
  	aCCodeGenerator
  		declareVar: #sendTrace type: 'volatile int';
  		declareVar: #byteCount type: 'unsigned long'.
  	"These need to be pointers or unsigned."
  	self declareC: #(instructionPointer method newMethod)
  		as: #usqInt
  		in: aCCodeGenerator.
  	"These are all pointers; char * because Slang has no support for C pointer arithmetic."
  	self declareC: #(localIP localSP localFP stackPointer framePointer stackLimit stackMemory breakSelector)
  		as: #'char *'
  		in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #breakSelectorLength
  		declareC: 'sqInt breakSelectorLength = MinSmallInteger'.
  	self declareC: #(stackPage overflowedPage)
  		as: #'StackPage *'
  		in: aCCodeGenerator.
  	aCCodeGenerator removeVariable: 'stackPages'.  "this is an implicit receiver in the translated code."
  	NewspeakVM ifFalse:
+ 		[aCCodeGenerator removeVariable: 'localAbsentReceiver'.
+ 		 aCCodeGenerator removeVariable: 'localAbsentReceiverOrZero'].
- 		[aCCodeGenerator removeVariable: 'localAbsentReceiver'].
  	"This defines bytecodeSetSelector as 0 if MULTIPLEBYTECODESETS
  	 is not defined, for the benefit of the interpreter on slow machines."
  	aCCodeGenerator addConstantForBinding: (self bindingOf: #MULTIPLEBYTECODESETS).
  	MULTIPLEBYTECODESETS == false ifTrue:
  		[aCCodeGenerator
  			removeVariable: 'extA';
  			removeVariable: 'extB';
  			removeVariable: 'bytecodeSetSelector'].
  	aCCodeGenerator
  		var: #methodCache
  		declareC: 'long methodCache[MethodCacheSize + 1 /* ', (MethodCacheSize + 1) printString, ' */]'.
  	aCCodeGenerator
+ 		var: #nsMethodCache
+ 		declareC: 'long nsMethodCache[NSMethodCacheSize + 1 /* ', (NSMethodCacheSize + 1) printString, ' */]'.
+ 	aCCodeGenerator
  		var: #atCache
  		declareC: 'sqInt atCache[AtCacheTotalSize + 1 /* ', (AtCacheTotalSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #primitiveTable
  		declareC: 'void (*primitiveTable[MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */])(void) = ', vmClass primitiveTableString.
  	vmClass primitiveTable do:
  		[:symbolOrNot|
  		(symbolOrNot isSymbol
  		 and: [symbolOrNot ~~ #primitiveFail]) ifTrue:
  			[(aCCodeGenerator methodNamed: symbolOrNot) ifNotNil:
  				[:tMethod| tMethod returnType: #void]]].
  	vmClass objectMemoryClass hasSpurMemoryManagerAPI
  		ifTrue:
  			[aCCodeGenerator
  				var: #primitiveAccessorDepthTable
  				type: 'signed char'
  				sizeString: 'MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */'
  				array: vmClass primitiveAccessorDepthTable]
  		ifFalse:
  			[aCCodeGenerator removeVariable: #primitiveAccessorDepthTable].
- 	(NewspeakVM and: [CheckPrivacyViolations]) ifFalse:
- 		[aCCodeGenerator removeVariable: #isPrivateSend].
  	aCCodeGenerator
  		var: #primitiveFunctionPointer
  		declareC: 'void (*primitiveFunctionPointer)()'.
  	aCCodeGenerator
  		var: #externalPrimitiveTable
  		declareC: 'void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* ', (MaxExternalPrimitiveTableSize + 1) printString, ' */])(void)'.
  	aCCodeGenerator var: #showSurfaceFn type: #'void *'.
  	aCCodeGenerator
  		var: #jmpBuf
  		declareC: 'jmp_buf jmpBuf[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #suspendedCallbacks
  		declareC: 'usqInt suspendedCallbacks[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #suspendedMethods
  		declareC: 'usqInt suspendedMethods[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #interruptCheckChain
  		declareC: 'void (*interruptCheckChain)(void) = 0'.
  
  	self declareCAsUSqLong: #(nextPollUsecs nextWakeupUsecs longRunningPrimitiveGCUsecs
  								longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs
  								"these are high-frequency enough that they're overflowing quite quickly on modern hardware"
  								statProcessSwitch statIOProcessEvents statForceInterruptCheck
  								statCheckForEvents statStackOverflow statStackPageDivorce)
  		in: aCCodeGenerator.
  	aCCodeGenerator var: #nextProfileTick type: #sqLong!

Item was changed:
  ----- Method: StackInterpreter class>>initializeCaches (in category 'initialization') -----
  initializeCaches
  
  	| atCacheEntrySize |
+ 	NewspeakVM
+ 		ifTrue: [MethodCacheEntries := 512]
+ 		ifFalse: [MethodCacheEntries := 1024].
- 	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.
  
+ 	NSMethodCacheEntries := 512.
+ 	NSMethodCacheSelector := 1.
+ 	NSMethodCacheClassTag := 2.
+ 	NSMethodCacheCallingMethod := 3.
+ 	NSMethodCacheDepthOrLookupRule := 4.
+ 	NSMethodCacheTargetMethod := 5.
+ 	NSMethodCachePrimFunction := 6.
+ 	NSMethodCacheActualReceiver := 7.
+ 	NSMethodCacheEntrySize := 8.	"Must be power of two for masking scheme."
+ 	NSMethodCacheMask := NSMethodCacheEntries - 1 * NSMethodCacheEntrySize.
+ 	NSMethodCacheSize := NSMethodCacheEntries * NSMethodCacheEntrySize.
+ 
  	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 class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  
  	super initializeMiscConstants.
  	STACKVM := true.
  
  	"These flags function to identify a GC operation, or
  	 to specify what operations the leak checker should be run for."
  	GCModeFull := 1.				"stop-the-world global GC"
  	GCModeNewSpace := 2.		"Spur's scavenge, or V3's incremental"
  	GCModeIncremental := 4.		"incremental global gc (Dijkstra tri-colour marking); as yet unimplemented"
  	GCModeBecome := 8.			"v3 post-become sweeping"
  	GCModeImageSegment := 16.	"just a flag for leak checking image segments"
  
  	StackPageTraceInvalid := -1.
  	StackPageUnreached := 0.
  	StackPageReachedButUntraced := 1.
  	StackPageTraced := 2.
  
  	DumpStackOnLowSpace := 0.
  	PrimitiveExternalCallIndex := 117. "Primitive index for #primitiveExternalCall"
  	MillisecondClockMask := 16r1FFFFFFF.
  	"Note: The external primitive table should actually be dynamically sized but for the sake of inferior platforms (e.g., Mac :-) who cannot allocate memory in any reasonable way, we keep it static (and cross our fingers...)"
  	MaxExternalPrimitiveTableSize := 4096. "entries"
  
  	MaxJumpBuf := 32. "max. callback depth"
  	FailImbalancedPrimitives := initializationOptions at: #FailImbalancedPrimitives ifAbsentPut: [true].
  
+ 	EnforceAccessControl := initializationOptions at: #EnforceAccessControl ifAbsentPut: [false]!
- 	CheckPrivacyViolations := initializationOptions at: #CheckPrivacyViolations ifAbsentPut: [false]!

Item was changed:
  ----- Method: StackInterpreter>>accessModifierOfMethod: (in category 'compiled methods') -----
  accessModifierOfMethod: methodObj
  	<option: #NewspeakVM>
  	^self accessModifierOfMethodHeader: (objectMemory methodHeaderOf: methodObj)!

Item was changed:
  ----- Method: StackInterpreter>>accessModifierOfMethodHeader: (in category 'compiled methods') -----
  accessModifierOfMethodHeader: header
  	<option: #NewspeakVM>
  	"accessModifier bits:
  		 00 public
  		 01 private
  		 10 protected
  		 11 undefined"
+ 	^self cppIf: EnforceAccessControl
+ 		ifTrue: [header >> MethodHeaderFlagBitPosition bitAnd: 3]
+ 		ifFalse: [AccessModifierPublic]!
- 	^header >> MethodHeaderFlagBitPosition bitAnd: 3!

Item was added:
+ ----- Method: StackInterpreter>>addNewMethodToNSCache: (in category 'method lookup cache') -----
+ addNewMethodToNSCache: rule
+ 	<option: #NewspeakVM>
+ 	<inline: false>
+ 	| classObj probe hash primitiveIndex |
+ 	classObj := lkupClass.
+ 	hash := (messageSelector bitXor: lkupClassTag) bitXor: (method bitXor: rule).
+ 	self deny: rule = LookupRuleOrdinary.
+ 
+ 	(objectMemory isOopCompiledMethod: newMethod)
+ 		ifTrue:
+ 			[primitiveIndex := self primitiveIndexOf: newMethod.
+ 			 primitiveFunctionPointer := self functionPointerFor: primitiveIndex inClass: classObj]
+ 		ifFalse:
+ 			[self assert: ((objectMemory isNonImmediate: newMethod)
+ 						  and: [objectMemory isForwarded: newMethod]) not.
+ 			 primitiveFunctionPointer := #primitiveInvokeObjectAsMethod].
+ 
+ 	0 to: CacheProbeMax-1 do:
+ 		[:p | probe := (hash >> p) bitAnd: NSMethodCacheMask.
+ 		(nsMethodCache at: probe + NSMethodCacheSelector) = 0 ifTrue:
+ 			["Found an empty entry -- use it"
+ 			nsMethodCache at: probe + NSMethodCacheSelector put: messageSelector.
+ 			nsMethodCache at: probe + NSMethodCacheClassTag put: lkupClassTag. "(objectMemory classTagForClass: classObj)."
+ 			nsMethodCache at: probe + NSMethodCacheCallingMethod put: method.
+ 			nsMethodCache at: probe + NSMethodCacheDepthOrLookupRule put: rule.
+ 			nsMethodCache at: probe + NSMethodCacheTargetMethod put: newMethod.
+ 			nsMethodCache at: probe + NSMethodCachePrimFunction put: (self cCoerce: primitiveFunctionPointer to: #long).
+ 			nsMethodCache at: probe + NSMethodCacheActualReceiver put: localAbsentReceiverOrZero.
+ 			"lastMethodCacheProbeWrite := probe." "this for primitiveExternalMethod"
+ 			^self]].
+ 
+ 	"OK, we failed to find an entry -- install at the first slot..."
+ 	probe := hash bitAnd: NSMethodCacheMask.  "first probe"
+ 	nsMethodCache at: probe + NSMethodCacheSelector put: messageSelector.
+ 	nsMethodCache at: probe + NSMethodCacheClassTag put: lkupClassTag. "(objectMemory classTagForClass: classObj)."
+ 	nsMethodCache at: probe + NSMethodCacheCallingMethod put: method.
+ 	nsMethodCache at: probe + NSMethodCacheDepthOrLookupRule put: rule.
+ 	nsMethodCache at: probe + NSMethodCacheTargetMethod put: newMethod.
+ 	nsMethodCache at: probe + NSMethodCachePrimFunction put: (self cCoerce: primitiveFunctionPointer to: #long).
+ 	nsMethodCache at: probe + NSMethodCacheActualReceiver put: localAbsentReceiverOrZero.
+ 	"lastMethodCacheProbeWrite := probe. ""this for primitiveExternalMethod"
+ 
+ 	"...and zap the following entries"
+ 	1 to: CacheProbeMax-1 do:
+ 		[:p | probe := (hash >> p) bitAnd: NSMethodCacheMask.
+ 		nsMethodCache at: probe + NSMethodCacheSelector put: 0]!

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 commonSendOrdinary].
- 				 ^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 commonSendOrdinary]]].
- 							 ^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 commonSendOrdinary].
- 				 ^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 commonSendOrdinary]]].
- 							 ^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: LookupRuleOrdinary.
- 	self internalExecuteNewMethod.
- 	self fetchNextBytecode!

Item was removed:
- ----- 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: 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 removed:
- ----- 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!

Item was added:
+ ----- Method: StackInterpreter>>commonSendDynamicSuper (in category 'send bytecodes') -----
+ commonSendDynamicSuper
+ 	"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: #extSendAbsentDynamicSuperBytecode>
+ 	self sendBreakpoint: messageSelector receiver: (self internalStackValue: argumentCount).
+ 	self printSends ifTrue:
+ 		[self printActivationNameForSelector: messageSelector startClass: (objectMemory classForClassTag: lkupClassTag); cr].
+ 	self internalFindNewMethodDynamicSuper.
+ 	self shuffleArgumentsAndStoreAbsentReceiver: localAbsentReceiver.
+ 	self internalExecuteNewMethod.
+ 	self fetchNextBytecode!

Item was added:
+ ----- Method: StackInterpreter>>commonSendImplicitReceiver (in category 'send bytecodes') -----
+ commonSendImplicitReceiver
+ 	"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: #extSendAbsentImplicitBytecode>
+ 	self sendBreakpoint: messageSelector receiver: (self internalStackValue: argumentCount).
+ 	self printSends ifTrue:
+ 		[self printActivationNameForSelector: messageSelector startClass: (objectMemory classForClassTag: lkupClassTag); cr].
+ 	self internalFindNewMethodImplicitReceiver.
+ 	self shuffleArgumentsAndStoreAbsentReceiver: localAbsentReceiver.
+ 	self internalExecuteNewMethod.
+ 	self fetchNextBytecode!

Item was added:
+ ----- Method: StackInterpreter>>commonSendOrdinary (in category 'send bytecodes') -----
+ commonSendOrdinary
+ 	"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 internalFindNewMethodOrdinary.
+ 	self internalExecuteNewMethod.
+ 	self fetchNextBytecode!

Item was added:
+ ----- Method: StackInterpreter>>commonSendOuter: (in category 'send bytecodes') -----
+ commonSendOuter: depth
+ 	"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: #extSendAbsentOuterBytecode>"
+ 	self sendBreakpoint: messageSelector receiver: (self internalStackValue: argumentCount).
+ 	self printSends ifTrue:
+ 		[self printActivationNameForSelector: messageSelector startClass: (objectMemory classForClassTag: lkupClassTag); cr].
+ 	self internalFindNewMethodOuter: depth.
+ 	self shuffleArgumentsAndStoreAbsentReceiver: localAbsentReceiver.
+ 	self internalExecuteNewMethod.
+ 	self fetchNextBytecode!

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 commonSendOrdinary!
- 	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 |
- 	| byte mClassMixin mixinApplication |
  	byte := self fetchByte.
  	messageSelector := self literal: (byte >> 3) + (extA << 5).
  	extA := 0.
  	argumentCount := (byte bitAnd: 7) + (extB << 3).
  	extB := 0.
+ 	self commonSendDynamicSuper!
- 	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!

Item was changed:
  ----- Method: StackInterpreter>>extSendAbsentImplicitBytecode (in category 'send bytecodes') -----
  extSendAbsentImplicitBytecode
  	"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"
  	| byte |
  	byte := self fetchByte.
  	messageSelector := self literal: (byte >> 3) + (extA << 5).
  	extA := 0.
  	argumentCount := (byte bitAnd: 7) + (extB << 3).
  	extB := 0.
+ 	self commonSendImplicitReceiver.!
- 	self commonSendAbsentImplicit!

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.
+ 	self commonSendOuter: depth!
- 	localAbsentReceiver := self 
- 							enclosingObjectAt: depth
- 							withObject: self receiver 
- 							withMixin: (self methodClassOf: method).
- 	CheckPrivacyViolations ifTrue:
-             [isPrivateSend := true].
- 	self commonSendAbsent: depth!

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.
+ 	self commonSendOuter: 0!
- 	localAbsentReceiver := self receiver.
- 	CheckPrivacyViolations ifTrue:
-             [isPrivateSend := true].
- 	self commonSendAbsent: LookupRuleSelf!

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 commonSendOrdinary!
- 	self commonSend!

Item was changed:
  ----- Method: StackInterpreter>>findApplicationOfTargetMixin:startingAtBehavior: (in category 'newspeak bytecode support') -----
  findApplicationOfTargetMixin: targetMixin startingAtBehavior: aBehavior
  	"This is used to implement implicit receiver and enclosing object lookup
  	 for Newspeak. Find the mixin applcation of which aClass is a subclass that
  	 is an application of targetMixin. This is an implementation derived from
  
  	<ContextPart> findApplicationOf: targetMixin startingAt: aBehavior
  	"
  	| mixinApplication mixin |
  	mixinApplication := aBehavior.
  	[mixinApplication = objectMemory nilObject
  	 or: [mixinApplication = targetMixin
+ 	 or: [(mixin := objectMemory followObjField: MixinIndex ofObject: mixinApplication) = targetMixin]]] whileFalse:
+ 		[mixinApplication := objectMemory followObjField: SuperclassIndex ofObject: mixinApplication].
+ 
+ 	mixinApplication = objectMemory nilObject ifTrue: [
+ 		self print: 'looking for '; cr.
+ 		self longPrintOop: targetMixin; cr.
+ 		self print: ' in behavior '; cr.
+ 		self longPrintOop: aBehavior; cr.
+ 	].
+ 
- 	 or: [(mixin := objectMemory fetchPointer: MixinIndex ofObject: mixinApplication) = targetMixin]]] whileFalse:
- 		[mixinApplication := objectMemory fetchPointer: SuperclassIndex ofObject: mixinApplication].
  	^mixinApplication!

Item was changed:
  ----- Method: StackInterpreter>>flushMethodCache (in category 'method lookup cache') -----
  flushMethodCache
  	"Flush the method cache. The method cache is flushed on every programming change and garbage collect."
  
  	1 to: MethodCacheSize do: [ :i | methodCache at: i put: 0 ].
+ 	self cppIf: NewspeakVM 
+ 		ifTrue: [1 to: NSMethodCacheSize do: [ :i | nsMethodCache at: i put: 0 ]].
  	lastMethodCacheProbeWrite := 0. "this for primitiveExternalMethod"
  	self flushAtCache.!

Item was changed:
  ----- Method: StackInterpreter>>flushMethodCacheFrom:to: (in category 'method lookup cache') -----
  flushMethodCacheFrom: memStart to: memEnd 
  	"Flush entries in the method cache only if the oop address is within the given memory range. 
  	This reduces overagressive cache clearing. Note the AtCache is fully flushed, 70% of the time 
  	cache entries live in newspace, new objects die young"
  	| probe |
  	probe := 0.
  	1 to: MethodCacheEntries do: [:i | 
  			(methodCache at: probe + MethodCacheSelector) = 0
  				ifFalse: [((((self oop: (methodCache at: probe + MethodCacheSelector) isGreaterThanOrEqualTo: memStart)
  										and: [self oop: (methodCache at: probe + MethodCacheSelector) isLessThan: memEnd])
  									or: [(self oop: (methodCache at: probe + MethodCacheClass) isGreaterThanOrEqualTo: memStart)
  											and: [self oop: (methodCache at: probe + MethodCacheClass) isLessThan: memEnd]])
  								or: [(self oop: (methodCache at: probe + MethodCacheMethod) isGreaterThanOrEqualTo: memStart)
  										and: [self oop: (methodCache at: probe + MethodCacheMethod) isLessThan: memEnd]])
  						ifTrue: [methodCache at: probe + MethodCacheSelector put: 0]].
  			probe := probe + MethodCacheEntrySize].
+ 	self cppIf: NewspeakVM 
+ 		ifTrue: [1 to: NSMethodCacheSize do: [ :i | nsMethodCache at: i put: 0 ]].
  	self flushAtCache!

Item was changed:
  ----- Method: StackInterpreter>>initialize (in category 'initialization') -----
  initialize
  	"Here we can initialize the variables C initializes to zero.  #initialize methods do /not/ get translated."
  	checkAllocFiller := false. "must preceed initializeObjectMemory:"
  	primFailCode := 0.
  	stackLimit := 0. "This is also the initialization flag for the stack system."
  	stackPage := overflowedPage := 0.
  	extraFramesToMoveOnOverflow := 0.
  	bytecodeSetSelector := 0.
  	highestRunnableProcessPriority := 0.
  	nextProfileTick := 0.
  	nextPollUsecs := 0.
  	nextWakeupUsecs := 0.
  	tempOop := tempOop2 := theUnknownShort := 0.
  	interruptPending := false.
  	inIOProcessEvents := 0.
  	fullScreenFlag := 0.
  	deferDisplayUpdates := false.
  	pendingFinalizationSignals := statPendingFinalizationSignals := 0.
  	globalSessionID := 0.
  	jmpDepth := 0.
  	longRunningPrimitiveStartUsecs := longRunningPrimitiveStopUsecs := 0.
  	maxExtSemTabSizeSet := false.
- 	isPrivateSend := false.
  	statForceInterruptCheck := statStackOverflow := statCheckForEvents :=
  	statProcessSwitch := statIOProcessEvents := statStackPageDivorce := 0!

Item was added:
+ ----- Method: StackInterpreter>>inlineLookupInNSMethodCacheSel:classTag:method:lookupRule: (in category 'method lookup cache') -----
+ inlineLookupInNSMethodCacheSel: selector classTag: classTag method: callingMethod lookupRule: lookupRule
+ 	"Like inlineLookupInMethodCacheSel:classTag:, but the cache is additionally key'd by the calling method and lookupRule/depth and additionally answers localAbsentReceiverOrZero."
+ 
+ 	| hash probe |
+ 	<inline: true>
+ 	hash := (selector bitXor: classTag) bitXor: (callingMethod bitXor: lookupRule).
+ 
+ 	probe := hash bitAnd: NSMethodCacheMask.  "first probe"
+ 	(((((nsMethodCache at: probe + NSMethodCacheSelector) = selector) and:
+ 		[(nsMethodCache at: probe + NSMethodCacheClassTag) = classTag]) and:
+ 		[(nsMethodCache at: probe + NSMethodCacheCallingMethod) = callingMethod]) and:
+ 		[(nsMethodCache at: probe + NSMethodCacheDepthOrLookupRule) = lookupRule]) ifTrue:
+ 			[newMethod := nsMethodCache at: probe + NSMethodCacheTargetMethod.
+ 			primitiveFunctionPointer := self cCoerceSimple: (nsMethodCache at: probe + NSMethodCachePrimFunction)
+ 											to: #'void (*)()'.
+ 			localAbsentReceiverOrZero := nsMethodCache at: probe + NSMethodCacheActualReceiver.
+ 			^true	"found entry in cache; done"].
+ 
+ 	probe := (hash >> 1) bitAnd: NSMethodCacheMask.  "second probe"
+ 	(((((nsMethodCache at: probe + NSMethodCacheSelector) = selector) and:
+ 		[(nsMethodCache at: probe + NSMethodCacheClassTag) = classTag]) and:
+ 		[(nsMethodCache at: probe + NSMethodCacheCallingMethod) = callingMethod]) and:
+ 		[(nsMethodCache at: probe + NSMethodCacheDepthOrLookupRule) = lookupRule]) ifTrue:
+ 			[newMethod := nsMethodCache at: probe + NSMethodCacheTargetMethod.
+ 			primitiveFunctionPointer := self cCoerceSimple: (nsMethodCache at: probe + NSMethodCachePrimFunction)
+ 											to: #'void (*)()'.
+ 			localAbsentReceiverOrZero := nsMethodCache at: probe + NSMethodCacheActualReceiver.
+ 			^true	"found entry in cache; done"].
+ 
+ 	probe := (hash >> 2) bitAnd: NSMethodCacheMask.
+ 	(((((nsMethodCache at: probe + NSMethodCacheSelector) = selector) and:
+ 		[(nsMethodCache at: probe + NSMethodCacheClassTag) = classTag]) and:
+ 		[(nsMethodCache at: probe + NSMethodCacheCallingMethod) = callingMethod]) and:
+ 		[(nsMethodCache at: probe + NSMethodCacheDepthOrLookupRule) = lookupRule]) ifTrue:
+ 			[newMethod := nsMethodCache at: probe + NSMethodCacheTargetMethod.
+ 			primitiveFunctionPointer := self cCoerceSimple: (nsMethodCache at: probe + NSMethodCachePrimFunction)
+ 											to: #'void (*)()'.
+ 			localAbsentReceiverOrZero := nsMethodCache at: probe + NSMethodCacheActualReceiver.
+ 			^true	"found entry in cache; done"].
+ 
+ 	^false!

Item was removed:
- ----- 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 added:
+ ----- Method: StackInterpreter>>internalFindNewMethodDynamicSuper (in category 'message sending') -----
+ internalFindNewMethodDynamicSuper
+ 	"Find the compiled method to be run when the current messageSelector is sent to the superclass of the class where the current method was looked up, setting the values of 'newMethod' and 'primitiveIndex'."
+ 	<inline: true>
+ 	localAbsentReceiver := self receiver.
+ 	self deny: (objectMemory isOopForwarded: localAbsentReceiver).
+ 	lkupClassTag := objectMemory fetchClassTagOf: localAbsentReceiver.
+ 
+ 	(self inlineLookupInNSMethodCacheSel: messageSelector classTag: lkupClassTag method: method lookupRule: LookupRuleDynamicSuper)
+ 	 ifFalse:
+ 		[ | actualLookupRule |
+ 		"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.
+ 		 actualLookupRule := self lookupDynamicSuperSend.
+ 		 self internalizeIPandSP.
+ 		 self addNewMethodToNSCache: actualLookupRule].
+ !

Item was added:
+ ----- Method: StackInterpreter>>internalFindNewMethodImplicitReceiver (in category 'message sending') -----
+ internalFindNewMethodImplicitReceiver
+ 	"Find the compiled method to be run when the for an implicit receiver send of messageSelector, setting the values of 'newMethod' and 'primitiveIndex'."
+ 	<inline: true>
+ 	localAbsentReceiver := self receiver.
+ 	self deny: (objectMemory isOopForwarded: localAbsentReceiver).
+ 	lkupClassTag := objectMemory fetchClassTagOf: localAbsentReceiver.
+ 
+ 	(self inlineLookupInNSMethodCacheSel: messageSelector classTag: lkupClassTag method: method lookupRule: LookupRuleImplicit)
+ 	 ifTrue:
+ 		[localAbsentReceiverOrZero = 0 ifFalse: [localAbsentReceiver := localAbsentReceiverOrZero.]]
+ 	 ifFalse:
+ 		[ | actualLookupRule |
+ 		"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.
+ 		 actualLookupRule := self lookupImplicitReceiverSend.
+ 		 self internalizeIPandSP.
+ 		 self addNewMethodToNSCache: actualLookupRule].
+ !

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

Item was added:
+ ----- Method: StackInterpreter>>internalFindNewMethodOuter: (in category 'message sending') -----
+ internalFindNewMethodOuter: depth
+ 	"Find the compiled method to be run when the current messageSelector is sent to the depth'th enclosing object w/r/t the mixin of the current method, setting the values of 'newMethod' and 'primitiveIndex'."
+ 	<inline: true>
+ 	localAbsentReceiver := self receiver.
+ 	self deny: (objectMemory isOopForwarded: localAbsentReceiver).
+ 	lkupClassTag := objectMemory fetchClassTagOf: localAbsentReceiver.
+ 
+ 	(self inlineLookupInNSMethodCacheSel: messageSelector classTag: lkupClassTag method: method lookupRule: depth)
+ 	 ifTrue:
+ 		[localAbsentReceiverOrZero = 0 ifFalse: [localAbsentReceiver := localAbsentReceiverOrZero.]]
+ 	 ifFalse:
+ 		[ | actualLookupRule |
+ 		"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.
+ 		 actualLookupRule := self lookupOuterSend: depth.
+ 		 self internalizeIPandSP.
+ 		 self addNewMethodToNSCache: actualLookupRule].
+ !

Item was added:
+ ----- 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 added:
+ ----- 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"
+ 
+ 	| 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 added:
+ ----- 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.
+ 	methodMixin := self methodClassOf: method.
+ 	methodMixinApplication := self
+ 		findApplicationOfTargetMixin: methodMixin
+ 		startingAtBehavior: (objectMemory fetchClassOf: localAbsentReceiver).
+ 	lkupClass := self superclassOf: methodMixinApplication. "For use by MNU"
+ 	^self lookupProtected: messageSelector startingAt: lkupClass rule: LookupRuleDynamicSuper!

Item was added:
+ ----- 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. "For use by MNU"
+ 	^self lookupProtected: messageSelector startingAt: lkupClass rule: LookupRuleImplicit.!

Item was added:
+ ----- 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. "For use by MNU"
+ 	mixinApplication := self findApplicationOfTargetMixin: mixin startingAtBehavior: receiverClass.
+ 	dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: mixinApplication.
+ 	found := self lookupMethodInDictionary: dictionary.
+ 	(found and: [(self accessModifierOfMethod: newMethod) = AccessModifierPrivate])
+ 		ifTrue: [^rule].
+ 	^self lookupProtected: selector startingAt: receiverClass rule: rule
+ !

Item was changed:
  ----- Method: StackInterpreter>>lookupMethodInClass: (in category 'message sending') -----
  lookupMethodInClass: class
  	| currentClass dictionary found |
  	<inline: false>
  	self assert: (self addressCouldBeClassObj: class).
  	currentClass := class.
  	[currentClass ~= objectMemory nilObject] whileTrue:
  		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
  		dictionary = objectMemory nilObject ifTrue:
  			["MethodDict pointer is nil (hopefully due a swapped out stub)
  				-- raise exception #cannotInterpret:."
  			self createActualMessageTo: class.
  			messageSelector := objectMemory splObj: SelectorCannotInterpret.
  			self sendBreakpoint: messageSelector receiver: nil.
  			^self lookupMethodInClass: (self superclassOf: currentClass)].
  		found := self lookupMethodInDictionary: dictionary.
+ 		found ifTrue: [^currentClass].
- 		found ifTrue:
- 			[self maybeCheckPrivacyOfNewMethod: currentClass.
- 			 ^currentClass].
  		currentClass := self superclassOf: currentClass].
  
  	"Could not find #doesNotUnderstand: -- unrecoverable error."
  	messageSelector = (objectMemory splObj: SelectorDoesNotUnderstand) ifTrue:
  		[self error: 'Recursive not understood error encountered'].
  
  	"Cound not find a normal message -- raise exception #doesNotUnderstand:"
  	self createActualMessageTo: class.
  	messageSelector := objectMemory splObj: SelectorDoesNotUnderstand.
  	self sendBreak: messageSelector + objectMemory baseHeaderSize
  		point: (objectMemory lengthOf: messageSelector)
  		receiver: nil.
  	^self lookupMethodInClass: class!

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 |
  	<inline: false>
- 
  	currentClass := class.
  	[currentClass ~= objectMemory nilObject] whileTrue:
  		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
  		 dictionary = objectMemory nilObject ifTrue:
  			[lkupClass := self superclassOf: currentClass.
  			 ^SelectorCannotInterpret].
  		 (self lookupMethodInDictionary: dictionary) ifTrue:
  			[self addNewMethodToCache: class.
  			 ^0].
  		currentClass := self superclassOf: currentClass].
  	lkupClass := class.
  	^SelectorDoesNotUnderstand!

Item was added:
+ ----- 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: LookupOrdinary or LookupDNU"
+ 
+ 	| 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 accessModifierOfMethod: newMethod) == AccessModifierPublic
+ 				ifTrue: [^self].
+ 			(self accessModifierOfMethod: newMethod) == AccessModifierProtected
+ 				ifTrue: [^self lookupDnuPresent]].
+ 		currentClass := self superclassOf: currentClass].
+ 	^self lookupDnuPresent!

Item was added:
+ ----- Method: StackInterpreter>>lookupOuterSend: (in category 'message sending') -----
+ lookupOuterSend: depth
+ 	"Do the full lookup for a self or outer send.
+ 	IN: messageSelector
+ 	IN: argumentCount
+ 	OUT: localAbsentReceiver
+ 	OUT: localAbsentReceiverOrZero
+ 	OUT: newMethod
+ 	OUT: primitiveIndex
+ 	RESULT: [depth] or LookupRuleMNU"
+ 
+ 	| targetMixin count mixinApplication |
+ 	localAbsentReceiver := self receiver.
+ 	localAbsentReceiverOrZero := 0.
+ 	targetMixin := self methodClassOf: method.
+ 	count := 0.
+ 	[count < depth] whileTrue:
+ 		[count := count + 1.
+ 		mixinApplication := self
+ 			findApplicationOfTargetMixin: targetMixin
+ 			startingAtBehavior: (objectMemory fetchClassOf: localAbsentReceiver).
+ 		localAbsentReceiverOrZero := localAbsentReceiver := objectMemory followObjField: EnclosingObjectIndex ofObject: mixinApplication.
+ 		targetMixin := objectMemory followObjField: EnclosingMixinIndex ofObject: targetMixin].
+ 	^self lookupLexical: messageSelector from: targetMixin rule: depth!

Item was added:
+ ----- 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."
+ 	| lookupClass dictionary found |
+ 	lookupClass := mixinApplication.
+ 	[lookupClass = objectMemory nilObject] whileFalse:
+ 		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: lookupClass.
+ 		found := self lookupMethodInDictionary: dictionary.
+ 		(found and: [(self accessModifierOfMethod: newMethod) ~= AccessModifierPrivate])
+ 			ifTrue: [^rule].
+ 		lookupClass := self superclassOf: lookupClass].
+ 	^self lookupDnuAbsent!

Item was removed:
- ----- Method: StackInterpreter>>maybeCheckPrivacyOfNewMethod: (in category 'message sending') -----
- maybeCheckPrivacyOfNewMethod: currentClass
- 	<inline: true>
- 	(NewspeakVM
- 	  and: [CheckPrivacyViolations
- 	  and: [isPrivateSend not
- 	  and: [messageSelector ~= (objectMemory splObj: SelectorDoesNotUnderstand)
- 	  and: [(self accessModifierOfMethod: newMethod) ~= AccessModifierPublic]]]]) ifTrue:
- 		[self print: (self nameOfClass: currentClass); space.
- 		 self printStringOf: (messageSelector); print: ' from '.
- 		 self printStringOf: (self maybeSelectorOfMethod: method); cr]!

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 commonSendOrdinary!
- 	self commonSend!

Item was changed:
  ----- Method: StackInterpreter>>sendAbsentImplicit0ArgsBytecode (in category 'send bytecodes') -----
  sendAbsentImplicit0ArgsBytecode
  	"160-175	1010 i i i i		Send To Absent Implicit Receiver Literal Selector #iiii With 0 Arguments"
  	messageSelector := self literal: (currentBytecode bitAnd: 16rF).
  	argumentCount := 0.
+ 	self commonSendImplicitReceiver!
- 	self commonSendAbsentImplicit!

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 commonSendOrdinary!
- 	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 commonSendOrdinary!
- 	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 commonSendOrdinary!
- 	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 commonSendOrdinary!
- 	self commonSend!

Item was changed:
  ----- Method: StackInterpreterSimulator>>initialize (in category 'initialization') -----
  initialize
  	"Initialize the StackInterpreterSimulator when running the interpreter
  	 inside Smalltalk. The primary responsibility of this method is to allocate
  	 Smalltalk Arrays for variables that will be declared as statically-allocated
  	 global arrays in the translated code."
  	super initialize.
  
  	bootstrapping := false.
  	transcript := Transcript.
  
  	objectMemory ifNil:
  		[objectMemory := self class objectMemoryClass simulatorClass new].
  	objectMemory coInterpreter: self.
  
  	"Note: we must initialize ConstMinusOne differently for simulation,
  		due to the fact that the simulator works only with +ve 32-bit values"
  	ConstMinusOne := objectMemory integerObjectOf: -1.
  
  	methodCache := Array new: MethodCacheSize.
+ 	nsMethodCache := Array new: NSMethodCacheSize.
  	atCache := Array new: AtCacheTotalSize.
  	self flushMethodCache.
  	gcSemaphoreIndex := 0.
  	externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  	externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  	externalPrimitiveTableFirstFreeIndex := 0.
  	primitiveTable := self class primitiveTable copy.
  	mappedPluginEntries := OrderedCollection new.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[primitiveAccessorDepthTable := Array new: primitiveTable size.
  			 pluginList := {}.
  			 self loadNewPlugin: '']
  		ifFalse:
  			[pluginList := {'' -> self }].
  	desiredNumStackPages := desiredEdenBytes := 0.
  	"This is initialized on loading the image, but convenient for testing stack page values..."
  	numStackPages := self defaultNumStackPages. 
  	startMicroseconds := Time totalSeconds * 1000000.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := sendCount := lookupCount := 0.
  	quitBlock := [^self].
  	traceOn := true.
  	printSends := printReturns := printFrameAtEachStep := printBytecodeAtEachStep := false.
  	myBitBlt := BitBltSimulator new setInterpreter: self.
  	displayForm := fakeForm := 'Display has not yet been installed' asDisplayText form.
  	eventQueue := SharedQueue new.
  	suppressHeartbeatFlag := false.
  	systemAttributes := Dictionary new.
  	extSemTabSize := 256.
  	disableBooleanCheat := false.
  	assertVEPAES := true. "a flag so the assertValidExecutionPointers can be disabled for simulation speed"!

Item was removed:
- ----- 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 added:
+ ----- Method: StackInterpreterSimulator>>internalFindNewMethodOrdinary (in category 'testing') -----
+ internalFindNewMethodOrdinary
+ "
+ 	| 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 internalFindNewMethodOrdinary!

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 false)
- 				NewspeakVM true)
  		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)
  !

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurStack64VM (in category 'configurations') -----
  generateNewspeakSpurStack64VM
  	"No primitives since we can use those from the Cog VM"
  	^VMMaker
  		generate: StackInterpreter
+ 		with: #( ObjectMemory Spur64BitMemoryManager
- 		with: #(ObjectMemory Spur64BitMemoryManager
  				MULTIPLEBYTECODESETS true
  				NewspeakVM true
  				FailImbalancedPrimitives false
+ 				EnforceAccessControl false)
- 				CheckPrivacyViolations true)
  		to: (FileDirectory default directoryNamed: self sourceTree, '/nsspurstack64src') fullName
  		platformDir: (FileDirectory default directoryNamed: self sourceTree, '/platforms') fullName
  		including: #()!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurStackVM (in category 'configurations') -----
  generateNewspeakSpurStackVM
  	"No primitives since we can use those from the Cog Newspeak VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #(	ObjectMemory Spur32BitMemoryManager
  				MULTIPLEBYTECODESETS true
  				NewspeakVM true
  				FailImbalancedPrimitives false
+ 				EnforceAccessControl true)
- 				CheckPrivacyViolations true)
  		to: (FileDirectory default directoryNamed: self sourceTree, '/nsspurstacksrc') fullName
  		platformDir: (FileDirectory default directoryNamed: self sourceTree, '/platforms') fullName
  		including: #()!

Item was changed:
  SharedPool subclass: #VMMethodCacheConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'LookupRuleDynamicSuper LookupRuleImplicit LookupRuleMNU LookupRuleOrdinary LookupRuleSelf MethodCacheClass MethodCacheEntries MethodCacheEntrySize MethodCacheMask MethodCacheMethod MethodCachePrim MethodCachePrimFunction MethodCacheSelector MethodCacheSize NSMethodCacheActualReceiver NSMethodCacheCallingMethod NSMethodCacheClassTag NSMethodCacheDepthOrLookupRule NSMethodCacheEntries NSMethodCacheEntrySize NSMethodCacheMask NSMethodCachePrimFunction NSMethodCacheSelector NSMethodCacheSize NSMethodCacheTargetMethod'
- 	classVariableNames: 'LookupRuleDynamicSuper LookupRuleImplicit LookupRuleMNU LookupRuleOrdinary LookupRuleSelf 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