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

commits at source.squeak.org commits at source.squeak.org
Mon Feb 2 01:17:55 UTC 2015


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

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

Name: VMMaker.oscog-eem.1035
Author: eem
Time: 1 February 2015, 5:16:35.867 pm
UUID: 33a34378-0618-40c7-8fbb-c467fb40fc57
Ancestors: VMMaker.oscog-eem.1034

Newspeak:
Refactor the absent receiver shuffling in the
interpreter to get more common code.

Spur: comment more carefully the receiver and
supersend forwarding invariants, and therefore
eliminate internalForwardedReceiver.

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

Item was removed:
- ----- Method: CoInterpreter>>internalFollowedReceiver (in category 'internal interpreter access') -----
- internalFollowedReceiver
- 	<inline: true>
- 	| rcvr |
- 	rcvr := stackPages longAt: localFP + FoxIFReceiver.
- 	(objectMemory isOopForwarded: rcvr) ifTrue:
- 		[rcvr := objectMemory followForwarded: rcvr.
- 		 stackPages longAt: localFP + FoxIFReceiver put: rcvr].
- 	^rcvr!

Item was changed:
  InterpreterPrimitives subclass: #StackInterpreter
+ 	instanceVariableNames: 'currentBytecode bytecodeSetSelector localFP localIP localSP stackLimit stackPage stackPages method instructionPointer stackPointer framePointer localReturnValue localAbsentReceiver extA extB primitiveFunctionPointer methodCache 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'
- 	instanceVariableNames: 'currentBytecode bytecodeSetSelector localFP localIP localSP stackLimit stackPage stackPages method instructionPointer stackPointer framePointer localReturnValue extA extB primitiveFunctionPointer methodCache 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: 'AltBytecodeEncoderClassName AltLongStoreBytecode AlternateHeaderHasPrimFlag AlternateHeaderIsOptimizedFlag AlternateHeaderNumLiteralsMask AtCacheEntries AtCacheFixedFields AtCacheFmt AtCacheMask AtCacheOop AtCacheSize AtCacheTotalSize AtPutBase BytecodeEncoderClassName BytecodeTable CacheProbeMax 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 VMMethodCacheConstants VMObjectIndices VMSpurObjectRepresentationConstants VMSqueakClassIndices VMSqueakV3BytecodeConstants 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'].
  	"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: #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].
  	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 added:
+ ----- Method: StackInterpreter>>commonSendAbsent (in category 'send bytecodes') -----
+ commonSendAbsent
+ 	"Send an absent receiver message, shuffling arguments and inserting the absent
+ 	 receiver for the send.  Assume: messageSelector and argumentCount have been
+ 	 set, and that the arguments but not the receiver have been pushed onto the stack,"
+ 	"Note: This method is inlined into the interpreter dispatch loop."
+ 	"160-175	1010 i i i i		Send To Absent Implicit Receiver Literal Selector #iiii With 0 Arguments"
+ 	"240		11110000	i i i i i j j j	Send To Absent Implicit Receiver Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
+ 	<sharedCodeInCase: #extSendAbsentImplicitBytecode>
+ 	self shuffleArgumentsAndStoreAbsentReceiver: localAbsentReceiver.
+ 	lkupClassTag := objectMemory fetchClassTagOf: localAbsentReceiver.
+ 	self assert: (objectMemory classForClassTag: lkupClassTag) ~= objectMemory nilObject.
+ 	self commonSend!

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

Item was changed:
  ----- Method: StackInterpreter>>dynamicSuperSendBytecode (in category 'send bytecodes') -----
  dynamicSuperSendBytecode
  "Send a message to self, starting lookup in the superclass of the method application of the currently executing method's mixin."
  "Assume: messageSelector and argumentCount have been set, and that the receiver and arguments have been pushed onto the stack," 
  "WE WANT THE RECEIVER PUSHED IMPLICITLY, BUT IT IS NOT - SO FAR"
  "Note: This method is inlined into the interpreter dispatch loop."
  	| rcvr mClassMixin mixinApplication |
  	<inline: true>
  	argumentCount := self fetchByte.
  	messageSelector := self literal: self fetchByte.
+ 	"To maintain the invariant that all receivers are unforwarded we need an explicit
+ 	 read barrier in the super send cases."
+ 	self ensureReceiverUnforwarded.
  	rcvr := self internalStackValue: argumentCount.
  	mClassMixin := self methodClassOf: method.
  	mixinApplication := self 
+ 							findApplicationOfTargetMixin: mClassMixin
+ 							startingAtBehavior: (objectMemory fetchClassOf: rcvr).
- 		findApplicationOfTargetMixin: mClassMixin
- 		startingAtBehavior: (objectMemory fetchClassOf: rcvr).
  	lkupClassTag := objectMemory classTagForClass: (self superclassOf: mixinApplication).
  	self commonSend!

Item was added:
+ ----- Method: StackInterpreter>>ensureReceiverUnforwarded (in category 'send bytecodes') -----
+ ensureReceiverUnforwarded
+ 	"To maintain the invariant that all receivers are unforwarded we need an explicit
+ 	 read barrier in the super send cases."
+ 	(objectMemory isOopForwarded: (self internalStackValue: argumentCount)) ifTrue:
+ 		[self internalStackValue: argumentCount
+ 			put: (objectMemory followForwarded: (self internalStackValue: argumentCount))]!

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 depth absentReceiver |
  	byte := self fetchByte.
  	messageSelector := self literal: (byte >> 3) + (extA << 5).
  	extA := 0.
  	argumentCount := (byte bitAnd: 7) + (extB << 3).
  	extB := 0.
  	depth := self fetchByte.
+ 	localAbsentReceiver := self 
- 	absentReceiver := self 
  							enclosingObjectAt: depth
  							withObject: self receiver 
  							withMixin: (self methodClassOf: method).
+ 	self commonSendAbsent!
- 	self shuffleArgumentsAndStoreAbsentReceiver: absentReceiver.
- 	lkupClassTag := objectMemory classTagForClass: (objectMemory fetchClassOf: absentReceiver).
- 	self commonSend!

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

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

Item was removed:
- ----- Method: StackInterpreter>>internalFollowedReceiver (in category 'internal interpreter access') -----
- internalFollowedReceiver
- 	<inline: true>
- 	| rcvr |
- 	rcvr := stackPages longAt: localFP + FoxReceiver.
- 	(objectMemory isOopForwarded: rcvr) ifTrue:
- 		[rcvr := objectMemory followForwarded: rcvr.
- 		 stackPages longAt: localFP + FoxReceiver put: rcvr].
- 	^rcvr!

Item was changed:
  ----- Method: StackInterpreter>>pushImplicitReceiverBytecode (in category 'stack bytecodes') -----
  pushImplicitReceiverBytecode
  	"This bytecode is used to implement outer sends in NS2/NS3. The
  	 bytecode takes as an argument the literal offset of a selector. It
  	 effectively finds the nearest lexically-enclosing implementation of
  	 that selector by searching up the static chain of the receiver,
  	 starting at the current method."
+ 	| selector |
- 	| selector followedReceiver |
  	selector := self literal: self fetchByte.
  	self fetchNextBytecode.
- 	followedReceiver := self internalFollowedReceiver.
  	self internalPush: (self
+ 						implicitReceiverFor: self receiver
- 						implicitReceiverFor: followedReceiver
  						mixin: (self methodClassOf: method)
  						implementing: selector)!

Item was changed:
  ----- Method: StackInterpreter>>spurPostBecomeAction: (in category 'object memory support') -----
  spurPostBecomeAction: theBecomeEffectsFlags
  	"Insulate the stack zone from the effects of a become.
  	 All receivers must be unfollowed for two reasons:
  		1. inst var access is direct with no read barrier
  		2. super sends (always to the receiver) have no class check and so don't trap
  		   for forwarded receivers.  This is an issue for primitives that assume their receiver
  		   is valid and don't validate.
+ 	 Super sends require an explicit check to ensure receivers in super sends are unforwarded.
+ 	 e.g. super doSomethingWith: (self become: other) forwards the receiver self pushed on the
+ 	 stack.  So we could avoid following non-pointer receivers.  But this is too tricky,  Instead, we
+ 	 always follow receivers.
  	 Methods must be unfollowed since bytecode access is direct with no read barrier.
  	 But this only needs to be done if the becomeEffectsFlags indicate that a
  	 CompiledMethod was becommed.
  	 The scheduler state must be followed, but only if the becomeEffectsFlags indicate
  	 that a pointer object was becommed."
  	<option: #SpurObjectMemory>
  	<inline: false> "For VM profiling"
  	self followForwardingPointersInStackZone: theBecomeEffectsFlags.
  	theBecomeEffectsFlags ~= 0 ifTrue:
  		[(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  			[self followForwardedMethodsInMethodCache.
  			 self followForwardedMethodsInMethodZone]. "for CoInterpreter"
  		 (theBecomeEffectsFlags anyMask: BecameActiveClassFlag) ifTrue:
  			[self flushBecommedClassesInMethodCache.
  			 self flushBecommedClassesInMethodZone]. "for CoInterpreter"
  		 self followForwardingPointersInScheduler.
  		 self followForwardingPointersInSpecialObjectsArray.
  		 self followForwardingPointersInProfileState]!

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



More information about the Vm-dev mailing list