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

commits at source.squeak.org commits at source.squeak.org
Thu Jun 4 20:00:31 UTC 2015


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

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

Name: VMMaker.oscog-eem.1339
Author: eem
Time: 4 June 2015, 12:58:10.572 pm
UUID: 022ddfcc-a8f6-422b-8a81-edffae18ebe6
Ancestors: VMMaker.oscog-cb.1338

Spur Cogit:
Fix Spur block performance now that we follow
forwarded receivers in blocks.  Scan blocks for
inst var usage, only unforwarding in the prologue of
blocks that actually refer to inst vars.  In a test Spur
Squeak image only 12.5% of blocks do refer to
inst vars.  So this is definitely a win.

Add a special purpose store check trampoline to
store check the updated receiver.  Make sure it's
only called if the eceiuver is updated.

Rationalize computing the number of trampolines.

Add state to CogBytecodeDescriptor, CogBlockStart
and CogBlockMethod to track block inst var usage.

=============== Diff against VMMaker.oscog-cb.1338 ===============

Item was changed:
  VMStructType subclass: #CogBlockMethod
+ 	instanceVariableNames: 'objectHeader homeOffset startpc padToWord cmNumArgs cmType cmRefersToYoung cpicHasMNUCase cmUsageCount cmUsesPenultimateLit cbUsesInstVars cmUnusedFlags stackCheckOffset'
- 	instanceVariableNames: 'objectHeader homeOffset startpc padToWord cmNumArgs cmType cmRefersToYoung cpicHasMNUCase cmUsageCount cmUsesPenultimateLit cmUnusedFlags stackCheckOffset'
  	classVariableNames: ''
  	poolDictionaries: 'CogMethodConstants VMBasicConstants'
  	category: 'VMMaker-JIT'!
  
+ !CogBlockMethod commentStamp: 'eem 6/4/2015 09:06' prior: 0!
- !CogBlockMethod commentStamp: 'eem 8/19/2014 17:07' prior: 0!
  I am the rump method header for a block method embedded in a full CogMethod.  I am the superclass of CogMethod, which is a Cog method header proper.  Instances of both classes have the same second word.  The homeOffset and startpc fields are overlaid on the objectHeader in a CogMethod.  See Cogit class>>structureOfACogMethod for more information.  In C I look like
  
  	typedef struct {
  		unsigned short	homeOffset;
  		unsigned short	startpc;
+ 	#if SpurVM
+ 		unsigned int	padToWord;
+ 	#endif
- 
  		unsigned		cmNumArgs : 8;
  		unsigned		cmType : 3;
  		unsigned		cmRefersToYoung : 1;
+ 		unsigned		cpicHasMNUCase : 1;
- 		unsigned		cmIsUnlinked : 1;
  		unsigned		cmUsageCount : 3;
+ 		unsigned		cmUsesPenultimateLit : 1;
+ 		unsigned		cbUsesInstVars : 1;
+ 		unsigned		cmUnusedFlags : 2;
+ 		unsigned		stackCheckOffset : 12;
+ 	 } CogBlockMethod;
- 		unsigned		stackCheckOffset : 16;
- 	} CogBlockMethod;
  
+ My instances are not actually used.  The methods exist only as input to Slang.  The simulator uses my surrogates (CogBlockMethodSurrogate32 and CogBlockMethodSurrogate64) to reference CogBlockMethod and CogMethod structures in the code zone.
+ 
+ cbUsesInstVars
+ 	- a flag set to true in blocks that refer to instance variables.
+ 
+ cmNumArgs
+ 	- the byte containing the block or method arg count
+ 
+ cmRefersToYoung
+ 	- a flag set to true in methods which contain a reference to an object in new space
+ 
+ cmType
+ 	- one of CMFree, CMMethod, CMBlock, CMClosedPIC, CMOpenPIC
+ 
+ cmUnusedFlags
+ 	- as yet unused bits
+ 
+ cmUsageCount
+ 	- a count used to identify older methods in code compaction.  The count decays over time, and compaction frees methods with lower usage counts
+ 
+ cmUsesPenultimateLit
+ 	- a flag that states whether the penultimate literal in the corresponding bytecode method is used.  This in turn is used to check that a become of a method does not alter its bytecode.
+ 
+ cpicHasMNUCase
+ 	- a flag that states whether a CMClosedPIC contains one or more MNU cases which are PIC dispatches used to speed-up MNU processing
+ 
+ homeOffset
+ 	- the distance a CMBlock header is away from its enclosing CMMethod header
+ 
+ objectHeader
+ 	- an object header used to fool the garbage collector into thinking that a CMMethod is a normal bits object, so that the first field (the header word) of a bytecoded method can refer directly to a CMMethod without special casing the garbage collector's method scanning code more than it already is.
+ 
+ padToWord
+ 	- a pad that may be necessary to make the homeOffset, startpc, padToWord triple as large as a CMMethod's objectHeader field
+ 
+ stackCheckOffset
+ 	- the distance from the header to the stack limit check in a frame building method or block, used to reenter execution in methods or blocks that have checked for events at what is effectively the first bytecode
+ 
+ startpc
+ 	- the bytecode pc of the start of a CMBlock's bytecode in the bytecode method!
- My instances are not actually used.  The methods exist only as input to Slang.  The simulator uses my surrogates (CogBlockMethodSurrogate32 and CogBlockMethodSurrogate64.!

Item was changed:
  ----- Method: CogBlockMethod class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the
  	 inst vars to include in a CogMethod or CogBlockMethod struct."
  
  	self allInstVarNames do:
  		[:ivn|
  		"Notionally objectHeader is in a union with homeOffset and startpc but
  		 we don't have any convenient support for unions.  So hack, hack, hack, hack."
  		((self == CogBlockMethod
  			ifTrue: [#('objectHeader')]
  			ifFalse: [#('homeOffset' 'startpc' 'padToWord')]) includes: ivn) ifFalse:
  				[aBinaryBlock
  					value: ivn
  					value: (ivn caseOf: {
  								['objectHeader']			-> [self objectMemoryClass baseHeaderSize = 8
  																ifTrue: [#sqLong]
  																ifFalse: [#sqInt]].
  								['cmNumArgs']				-> [#(unsigned ' : 8')].		"SqueakV3 needs only 5 bits"
  								['cmType']					-> [#(unsigned ' : 3')].
  								['cmRefersToYoung']		-> [#(unsigned #Boolean ' : 1')].
  								['cpicHasMNUCase']		-> [#(unsigned #Boolean ' : 1')].
  								['cmUsageCount']			-> [#(unsigned ' : 3')].		"See CMMaxUsageCount in initialize"
  								['cmUsesPenultimateLit']	-> [#(unsigned #Boolean ' : 1')].
+ 								['cbUsesInstVars']			-> [#(unsigned #Boolean ' : 1')].
+ 								['cmUnusedFlags']			-> [#(unsigned ' : 2')].
- 								['cmUnusedFlags']			-> [#(unsigned ' : 3')].
  								['stackCheckOffset']		-> [#(unsigned ' : 12')].		"See MaxStackCheckOffset in initialize. a.k.a. cPICNumCases"
  								['blockSize']				-> [#'unsigned short'].		"See MaxMethodSize in initialize"
  								['blockEntryOffset']			-> [#'unsigned short'].
  								['homeOffset']				-> [#'unsigned short'].
  								['startpc']					-> [#'unsigned short'].
  								['padToWord']				-> [#(#BaseHeaderSize 8 'unsigned int')].
  								['nextMethod']				-> ['struct _CogMethod *'].	"See NewspeakCogMethod"
  								['counters']					-> [#usqInt]}				"See SistaCogMethod"
  							otherwise:
  								[#sqInt])]]!

Item was added:
+ ----- Method: CogBlockMethod>>cbUsesInstVars (in category 'accessing') -----
+ cbUsesInstVars
+ 
+ 	^cbUsesInstVars!

Item was added:
+ ----- Method: CogBlockMethod>>cbUsesInstVars: (in category 'accessing') -----
+ cbUsesInstVars: anObject
+ 
+ 	^cbUsesInstVars := anObject!

Item was added:
+ ----- Method: CogBlockMethodSurrogate32>>cbUsesInstVars (in category 'accessing') -----
+ cbUsesInstVars
+ 	^(((memory unsignedByteAt: address + 3 + baseHeaderSize) bitShift: -1) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- Method: CogBlockMethodSurrogate32>>cbUsesInstVars: (in category 'accessing') -----
+ cbUsesInstVars: aValue
+ 	memory
+ 		unsignedByteAt: address + baseHeaderSize + 3
+ 		put: (((memory unsignedByteAt: address + baseHeaderSize + 3) bitAnd: 16rFD) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 1)).
+ 	^aValue!

Item was added:
+ ----- Method: CogBlockMethodSurrogate64>>cbUsesInstVars (in category 'accessing') -----
+ cbUsesInstVars
+ 	^(((memory unsignedByteAt: address + 3 + baseHeaderSize) bitShift: -1) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- Method: CogBlockMethodSurrogate64>>cbUsesInstVars: (in category 'accessing') -----
+ cbUsesInstVars: aValue
+ 	memory
+ 		unsignedByteAt: address + baseHeaderSize + 3
+ 		put: (((memory unsignedByteAt: address + baseHeaderSize + 3) bitAnd: 16rFD) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 1)).
+ 	^aValue!

Item was changed:
  VMStructType subclass: #CogBlockStart
+ 	instanceVariableNames: 'fakeHeader fillInstruction numArgs numCopied numInitialNils startpc entryLabel stackCheckLabel span hasInstVarRef'
- 	instanceVariableNames: 'fakeHeader fillInstruction numArgs numCopied numInitialNils startpc entryLabel stackCheckLabel span'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogBlockStart commentStamp: '<historical>' prior: 0!
  I am a record of a block, the address of the fake header, the association between the bytecode startpc and the machine code start label, and the block's relevant metrics.!

Item was added:
+ ----- Method: CogBlockStart>>hasInstVarRef (in category 'accessing') -----
+ hasInstVarRef
+ 
+ 	^ hasInstVarRef!

Item was added:
+ ----- Method: CogBlockStart>>hasInstVarRef: (in category 'accessing') -----
+ hasInstVarRef: anObject
+ 
+ 	^hasInstVarRef := anObject!

Item was changed:
  ----- Method: CogBlockStart>>printStateOn: (in category 'printing') -----
  printStateOn: aStream
  	<doNotGenerate> "Smalltalk-side only"
  	aStream
  		space; nextPut: $(;
  		nextPutAll: 'numArgs: '; print: numArgs;
  		nextPutAll: ' numCopied: '; print: numCopied;
  		nextPutAll: ' numInitialNils: '; print: numInitialNils;
+ 		nextPutAll: ' hasInstVarRef: '; print: hasInstVarRef;
  		nextPutAll: ' startpc: '; print: startpc;
  		nextPutAll: ' span: '; print: span;
  		nextPut: $)!

Item was changed:
  VMStructType subclass: #CogBytecodeDescriptor
+ 	instanceVariableNames: 'generator spanFunction needsFrameFunction stackDelta opcode numBytes isBranchTrue isBranchFalse isReturn isBlockCreation isMapped isMappedInBlock isExtension isInstVarRef hasIRC'
- 	instanceVariableNames: 'generator spanFunction needsFrameFunction stackDelta opcode numBytes isBranchTrue isBranchFalse isReturn isBlockCreation isMapped isMappedInBlock isExtension hasIRC'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogBytecodeDescriptor commentStamp: 'eem 11/18/2010 06:32' prior: 0!
  I am an entry in the Cogit's dispatch table for bytecodes.  I hold the routine to call to generate code for the partcular bytecode I represent and the number of bytes the bytecode has.  For eliminating temps in frameless blocks I maintain a stack delta for bytecodes that are valid in a frameless block.  The order of my instance variables is chosen for compact struct packing.!

Item was changed:
  ----- Method: CogBytecodeDescriptor class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a BytecodeDescriptor struct."
  
+ 	"With hasIRC there are 9 flag bits.  Excluding hasIRC in non-Newspeak VMs keeps the descriptor compact."
+ 	(NewspeakVM
+ 		ifTrue: [self instVarNames]
+ 		ifFalse: [self instVarNames copyWithout: 'hasIRC']) do:
- 	self instVarNames do:
  		[:ivn|
  		aBinaryBlock
  			value: ivn
  			value: (ivn caseOf: {
  							['generator']			->	[#('sqInt (*' ')(void)')].
  							['spanFunction']			->	[#('sqInt (*' ')(struct _BytecodeDescriptor *,sqInt,sqInt,sqInt)')].
  							['needsFrameFunction']	->	[#('sqInt (*' ')(sqInt)')].
  							['numBytes']			->	['unsigned char'].
  							['stackDelta']			->	['signed char'].
  							['opcode']				->	['unsigned char'] }
  						otherwise: [#('unsigned' ' : 1')])]!

Item was added:
+ ----- Method: CogBytecodeDescriptor>>isInstVarRef (in category 'accessing') -----
+ isInstVarRef
+ 	"Answer the value of isInstVarRef"
+ 
+ 	^ isInstVarRef!

Item was added:
+ ----- Method: CogBytecodeDescriptor>>isInstVarRef: (in category 'accessing') -----
+ isInstVarRef: anObject
+ 	"Set the value of isInstVarRef"
+ 
+ 	^isInstVarRef := anObject!

Item was added:
+ ----- Method: CogObjectRepresentation class>>numTrampolines (in category 'accessing') -----
+ numTrampolines
+ 	^1!

Item was changed:
  ----- Method: CogObjectRepresentation>>genEnsureOopInRegNotForwarded:scratchReg:updatingSlot:in: (in category 'compile abstract instructions') -----
  genEnsureOopInRegNotForwarded: reg scratchReg: scratch updatingSlot: index in: objReg
  	"Make sure that the oop in reg is not forwarded, updating the slot in objReg with the value."
  	<inline: true>
+ 	self flag: 'not safe unless there''s also a store check!!!!'.
+ 	self assert: false.
  	^self genEnsureOopInRegNotForwarded: reg
  		scratchReg: scratch
  		updatingMw: index * objectMemory wordSize + objectMemory baseHeaderSize
  		r: objReg!

Item was added:
+ ----- Method: CogObjectRepresentation>>maybeNoteDescriptor:blockStart: (in category 'compilation') -----
+ maybeNoteDescriptor: descriptor blockStart: blockStart
+ 	"A hook for the object representation to set state in a blockStart during scanBlock:.
+ 	 By default do nothing.  Subclasses that need to do something special will override."
+ 	<var: #blockStart type: #'BlockStart *'>
+ 	<var: #descriptor type: #'BytecodeDescriptor *'>
+ 	<inline: true>!

Item was changed:
  CogObjectRepresentation subclass: #CogObjectRepresentationForSpur
+ 	instanceVariableNames: 'ceScheduleScavengeTrampoline ceSmallActiveContextInMethodTrampoline ceSmallActiveContextInBlockTrampoline ceLargeActiveContextInMethodTrampoline ceLargeActiveContextInBlockTrampoline ceStoreCheckContextReceiverTrampoline'
- 	instanceVariableNames: 'ceScheduleScavengeTrampoline ceSmallActiveContextInMethodTrampoline ceSmallActiveContextInBlockTrampoline ceLargeActiveContextInMethodTrampoline ceLargeActiveContextInBlockTrampoline'
  	classVariableNames: ''
  	poolDictionaries: 'VMBytecodeConstants VMSqueakClassIndices'
  	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur class>>numTrampolines (in category 'accessing') -----
+ numTrampolines
+ 	^super numTrampolines + 6!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genEnsureOopInRegNotForwarded:scratchReg:updatingMw:r: (in category 'compile abstract instructions') -----
  genEnsureOopInRegNotForwarded: reg scratchReg: scratch updatingMw: offset r: baseReg
  	"Make sure that the oop in reg is not forwarded, and the field reg[offset] is updated
  	 if the object in reg is forwarded.  Use the fact that isForwardedObjectClassIndexPun is
  	 a power of two to save an instruction."
  	| loop imm ok |
  	<var: #ok type: #'AbstractInstruction *'>
  	<var: #imm type: #'AbstractInstruction *'>
  	<var: #loop type: #'AbstractInstruction *'>
+ 	self assert: (reg ~= scratch and: [baseReg ~= scratch]).
- 	self assert: reg ~= scratch.
  	loop := cogit Label.
  	imm := self genJumpImmediate: reg.
  	"notionally
  		self genGetClassIndexOfNonImm: reg into: scratch.
  		cogit CmpCq: objectMemory isForwardedObjectClassIndexPun R: TempReg.
  	 but the following is an instruction shorter:"
  	cogit MoveMw: 0 r: reg R: scratch.
  	cogit
  		AndCq: objectMemory classIndexMask - objectMemory isForwardedObjectClassIndexPun
  		R: scratch.
  	ok := cogit JumpNonZero:  0.
  	self genLoadSlot: 0 sourceReg: reg destReg: reg.
  	cogit MoveR: reg Mw: offset r: baseReg.
  	cogit Jump: loop.
  	ok jmpTarget: (imm jmpTarget: cogit Label).
  	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genEnsureOopInRegNotForwarded:scratchReg:updatingSlot:in: (in category 'compile abstract instructions') -----
+ genEnsureOopInRegNotForwarded: reg scratchReg: scratch updatingSlot: index in: objReg
+ 	"Make sure that the oop in reg is not forwarded, updating the slot in objReg with the value."
+ 	| loop imm ok |
+ 	<var: #ok type: #'AbstractInstruction *'>
+ 	<var: #imm type: #'AbstractInstruction *'>
+ 	<var: #loop type: #'AbstractInstruction *'>
+ 	"Open-code
+ 		self genEnsureOopInRegNotForwarded: reg
+ 			scratchReg: scratch
+ 			updatingMw: index * objectMemory wordSize + objectMemory baseHeaderSize
+ 			r: objReg.
+ 	 to avoid calling the store check unless the receiver is forwarded."
+ 	self assert: (reg ~= scratch and: [objReg ~= scratch]).
+ 	loop := cogit Label.
+ 	imm := self genJumpImmediate: reg.
+ 	"notionally
+ 		self genGetClassIndexOfNonImm: reg into: scratch.
+ 		cogit CmpCq: objectMemory isForwardedObjectClassIndexPun R: TempReg.
+ 	 but the following is an instruction shorter:"
+ 	cogit MoveMw: 0 r: reg R: scratch.
+ 	cogit
+ 		AndCq: objectMemory classIndexMask - objectMemory isForwardedObjectClassIndexPun
+ 		R: scratch.
+ 	ok := cogit JumpNonZero:  0.
+ 	self genLoadSlot: 0 sourceReg: reg destReg: reg.
+ 	cogit MoveR: reg Mw: index * objectMemory wordSize + objectMemory baseHeaderSize r: objReg.
+ 
+ 	"Check that we're meeting the contract of ceStoreCheckContextReceiverTrampoline."
+ 	self assert: (reg = Arg0Reg and: [scratch = TempReg and: [objReg = ReceiverResultReg]]).
+ 	cogit CallRT: ceStoreCheckContextReceiverTrampoline.
+ 
+ 	cogit Jump: loop.
+ 	ok jmpTarget: (imm jmpTarget: cogit Label).
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genStoreCheckContextReceiverTrampoline (in category 'initialization') -----
+ genStoreCheckContextReceiverTrampoline
+ 	<var: #aString type: #'char *'>
+ 	"Create a trampoline to store-check the update of the receiver in a closure's
+ 	 outerContext in compileBlockFrameBuild:."
+ 	| startAddress |
+ 	startAddress := cogit methodZoneBase.
+ 	cogit zeroOpcodeIndex.
+ 	self genStoreCheckReceiverReg: ReceiverResultReg valueReg: Arg0Reg scratchReg: TempReg inFrame: false.
+ 	cogit RetN: 0.
+ 	cogit outputInstructionsForGeneratedRuntimeAt: startAddress.
+ 	cogit recordGeneratedRunTime: 'ceStoreCheckContextReceiver' address: startAddress.
+ 	cogit recordRunTimeObjectReferences.
+ 	^startAddress!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>generateObjectRepresentationTrampolines (in category 'initialization') -----
  generateObjectRepresentationTrampolines
  	"Do the store check.  Answer the argument for the benefit of the code generator;
  	 ReceiverResultReg may be caller-saved and hence smashed by this call.  Answering
  	 it allows the code generator to reload ReceiverResultReg cheaply.
  	 In Spur the only thing we leave to the run-time is adding the receiver to the
  	 remembered set and setting its isRemembered bit."
  	ceStoreCheckTrampoline := cogit
  									genTrampolineFor: #remember:
  									called: 'ceStoreCheckTrampoline'
  									arg: ReceiverResultReg
  									result: cogit returnRegForStoreCheck.
+ 	ceStoreCheckContextReceiverTrampoline := self genStoreCheckContextReceiverTrampoline.
  	ceScheduleScavengeTrampoline := cogit
  											genSafeTrampolineFor: #ceScheduleScavenge
  											called: 'ceScheduleScavengeTrampoline'.
  	ceSmallActiveContextInMethodTrampoline := self genActiveContextTrampolineLarge: false inBlock: false called: 'ceSmallMethodContext'.
  	ceSmallActiveContextInBlockTrampoline := self genActiveContextTrampolineLarge: false inBlock: true called: 'ceSmallBlockContext'.
  	ceLargeActiveContextInMethodTrampoline := self genActiveContextTrampolineLarge: true inBlock: false called: 'ceLargeMethodContext'.
  	ceLargeActiveContextInBlockTrampoline := self genActiveContextTrampolineLarge: true inBlock: true called: 'ceLargeBlockContext'!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>maybeNoteDescriptor:blockStart: (in category 'compilation') -----
+ maybeNoteDescriptor: descriptor blockStart: blockStart
+ 	"Override to note inst var refs in blocks.  Used to avoid checking
+ 	 for forwarded receivers in blocks that don't refer to inst vars."
+ 	<var: #blockStart type: #'BlockStart *'>
+ 	<var: #descriptor type: #'BytecodeDescriptor *'>
+ 	<inline: true>
+ 	descriptor isInstVarRef ifTrue:
+ 		[blockStart hasInstVarRef: true]!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3 class>>numTrampolines (in category 'accessing') -----
+ numTrampolines
+ 	^super numTrampolines + 4!

Item was changed:
  ----- Method: Cogit class>>generatorTableFrom: (in category 'class initialization') -----
  generatorTableFrom: anArray
  	| blockCreationBytecodeSize |
  	generatorTable := CArrayAccessor on: (Array new: 256).
  	anArray do:
  		[:tuple| | descriptor |
  		(descriptor := CogBytecodeDescriptor new)
  						numBytes: tuple first;
  						generator: tuple fourth;
  						isReturn: (tuple includes: #return);
  						isMapped: (tuple includes: #isMapped);
  						isMappedInBlock: (tuple includes: #isMappedInBlock);
  						isBlockCreation: (tuple includes: #block);
  						spanFunction: (((tuple includes: #block) or: [(tuple includes: #branch)]) ifTrue:
  										[tuple detect: [:thing| thing isSymbol and: [thing numArgs = 4]]]);
  						isBranchTrue: (tuple includes: #isBranchTrue);
  						isBranchFalse: (tuple includes: #isBranchFalse);
  						isExtension: (tuple includes: #extension);
+ 						isInstVarRef: (tuple includes: #isInstVarRef);	"for Spur"
+ 						hasIRC: (tuple includes: #hasIRC);			"for Newspeak"
- 						hasIRC: (tuple includes: #hasIRC);
  						yourself.
+ 		"As a hack to cut down on descriptor flags, use opcode to tag unusedBytecode for scanning.
+ 		 Currently descriptors are exactly 16 bytes with all 8 flag bits used (in Newspeak at least 17 bytes,
+ 		 9 flag bits).  As another hack to eliminate a test in scanMethod mark unknowns as extensions."
- 		"As a hack to cut down on descriptor flags, use opcode to tag unusedBytecode for
- 		 scanning. Currently descriptors are exactly 16 bytes with all 8 flag bits used.  As
- 		 another hack to eliminate a test in scanMethod mark unknows as extensions."
  		descriptor generator == #unknownBytecode ifTrue:
  			[descriptor opcode: Nop; isExtension: true].
  		descriptor isBlockCreation ifTrue:
  			[blockCreationBytecodeSize
  				ifNil: [blockCreationBytecodeSize := descriptor numBytes]
  				ifNotNil: [self assert: blockCreationBytecodeSize = descriptor numBytes]].
  		tuple do:
  			[:thing|
  			thing isSymbol ifTrue:
  				[(thing beginsWith: #needsFrame) ifTrue:
  					[descriptor needsFrameFunction: thing].
  				 (CogRTLOpcodes classPool at: thing ifAbsent: []) ifNotNil:
  					[:opcode| descriptor opcode: opcode]]].
  		tuple last isInteger
  			ifTrue: [descriptor stackDelta: tuple last]
  			ifFalse:
  				[descriptor needsFrameFunction ifNotNil:
  					[self error: 'frameless block bytecodes must specify a stack delta']].
  		tuple second to: tuple third do:
  			[:index|
  			generatorTable at: index put: descriptor]].
  	BlockCreationBytecodeSize := blockCreationBytecodeSize.
  	^generatorTable!

Item was added:
+ ----- Method: Cogit class>>initializeNumTrampolines (in category 'class initialization') -----
+ initializeNumTrampolines
+ 	NumTrampolines := self numTrampolines
+ 						+ self objectRepresentationClass numTrampolines
+ 						+ (NewspeakVM ifTrue: [18] ifFalse: [0])
+ 						+ (BytecodeSetHasDirectedSuperSend ifTrue: [4] ifFalse: [0])!

Item was added:
+ ----- Method: Cogit class>>numTrampolines (in category 'accessing') -----
+ numTrampolines
+ 	^35 "27 + 4 each for self and super sends"
+ 
+ 	"self withAllSubclasses collect: [:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"!

Item was changed:
  ----- Method: Cogit class>>structureOfACogMethod (in category 'tests') -----
  structureOfACogMethod
  	"A CogMethod is the machine code for executable code in the Cog VM, and in the simulator these are
  	 instances of CogMethod.  In actuality they are structures in memory in the CogMethodZone..  There
  	 are four real kinds, defined by the cmType field, free space: CMFree, methods: CMMethod, closed
  	 PICs: CMClosedPIC (finite polymorphic inline caches with up to 6 entries), and open PICs: CMOpenPIC
  	 (infinite megamorphicinline caches that probe the first-level method lookup cache).  There is a fifth
  	 kind of method, which is merely a header, for blocks: CMBlock, one which exists only within CMMethods,
  	 and exist only to allow block activations to refer to something that looks like a CogMethod.
  
  	 The blockSize field in a CogMethod is the size in bytes of the entire method, including the header.
  	 Methods are aligned to an 8 byte boundary in the CogMethodZone.  The size is used to iterate over
  	 the methods in the zone.
  
  	 Follwing the header is the abort and entry code.  Starting immediately after the header is the call to
  	 the abort routine called when either a send fails or a stack limit check fails.  Following that is the
  	 checked entry point that checks the receiver is of the right class, and this code ends in the unchecked
  	 entry point.  Following this is either primitive code, followed by frame building code, or frame-building
  	 code, or, for frameless methods, the code for the frameless method.  Following that is the code for the
+ 	 method.  If the method contains blocks  then followng the method code will be a CMBlock header,
- 	 method.  If the mehtrod contains blocks  then followng the method code will be a CMBlock header,
  	 followed by code for the block, for each block, and following this will be the block dispatch code,
+ 	 which is indexed by the blockEntryOffset field in the CogMethod.
- 	 which is pointed to by the blockEntryOffset field in the CogMethod.
  
+ 	 Following either the return in the method, or the block dispatch, is the method map, the meta data which
+ 	 identifies interesting points in the machine code.  The map starts at the end of the structure and is read
+ 	 backwards towards the last instruftion of the method, and is terminated by a null byte.  So the blockSize
+ 	 is used to find the start of the map.  The map reveals where object references, sends and pc-mapping
+ 	 points exist in the machine code.  The map is parsed when garbage collecting to find and update object
+ 	 references, and when unlinking sends for method cache flushing, and to convert between bytecode and
+ 	 machine code pcs by scanning both bytecode and machine code looking for matching points in the map."!
- 	 Following either the return in the method, or the block dispatch, is the meta data which identifies
- 	 intersting points in the machine code.  This meta data starts at the end of the structure and is read
- 	 backwards towards the start of the method, and is terminated by a null byte.  So the blockSize is
- 	 used to find the start of the metadata.  The metadata reveals where object references, sends and
- 	 pc-mapping points exist in the machine code.  The metadata is parsed when garbage collecting to
- 	 find and update object references, and when unlinking sends for method cache flushing.."
- 	 !

Item was changed:
  ----- Method: Cogit>>addBlockStartAt:numArgs:numCopied:span: (in category 'compile abstract instructions') -----
  addBlockStartAt: bcpc numArgs: numArgs numCopied: numCopied span: span
  	"Add a blockStart for an embedded block.  For a binary tree walk block dispatch
  	 blocks must be compiled in pc/depth-first order but are scanned in breadth-first
  	 order, so do an insertion sort (which of course is really a bubble sort because we
  	 have to move everything higher to make room)."
  	<returnTypeC: #'BlockStart *'>
  	| i blockStart |
  	<var: #blockStart type: #'BlockStart *'>
  	blockCount > 0
  		ifTrue:
  			[i := blockCount - 1.
  			 [blockStart := self addressOf: (blockStarts at: i).
  			   blockStart startpc > bcpc
  			   and: [i > 0]] whileTrue:
  				[i := i - 1].
  			 blockCount to: i + 1 by: -1 do:
  				[:j|
  				blockStarts at: j put: (blockStarts at: j - 1)].
  			blockStart := self cCode: [self addressOf: (blockStarts at: i + 1)]
  								inSmalltalk: [blockStarts at: i + 1 put: CogBlockStart new]]
  		ifFalse:
  			[blockStart := self cCode: [self addressOf: (blockStarts at: blockCount)]
  								inSmalltalk: [blockStarts at: blockCount put: CogBlockStart new]].
  	blockCount := blockCount + 1.
  	blockStart
  		startpc: bcpc;
  		numArgs: numArgs;
  		numCopied: numCopied;
  		stackCheckLabel: nil;
+ 		hasInstVarRef: false;
  		span: span.
  	^blockStart!

Item was removed:
- ----- Method: Cogit>>compileBlockFrameBuild: (in category 'compile abstract instructions') -----
- compileBlockFrameBuild: blockStart
- 	self subclassResponsibility!

Item was changed:
  ----- Method: Cogit>>fillInBlockHeadersAt: (in category 'generate machine code') -----
  fillInBlockHeadersAt: startAddress
  	"Fill in the block headers now we know the exact layout of the code."
  	| blockStart blockHeader |
  	<var: #blockStart type: #'BlockStart *'>
  	<var: #blockHeader type: #'CogBlockMethod *'>
  
  	(needsFrame and: [blockCount > 0]) ifFalse:
  		[^nil].
  	blockNoContextSwitchOffset = nil
  		ifTrue: [blockNoContextSwitchOffset := blockEntryLabel address - blockEntryNoContextSwitch address]
  		ifFalse: [self assert: blockNoContextSwitchOffset = (blockEntryLabel address - blockEntryNoContextSwitch address)].
  	0 to: blockCount - 1 do:
  		[:i|
  		blockStart := self blockStartAt: i.
  		blockHeader := self cCoerceSimple: blockStart fakeHeader address
  								to: #'CogBlockMethod *'.
  		blockHeader
  			homeOffset: (blockStart fakeHeader address - startAddress);
  			startpc: blockStart startpc;
  			cmType: CMBlock;
  			cmNumArgs: blockStart numArgs;
+ 			cbUsesInstVars: blockStart hasInstVarRef;
  			stackCheckOffset: (blockStart stackCheckLabel = nil
  								ifTrue: [0]
  								ifFalse: [blockStart stackCheckLabel address - blockStart fakeHeader address])]!

Item was changed:
  ----- Method: Cogit>>printMethodHeader:on: (in category 'disassembly') -----
  printMethodHeader: cogMethod on: aStream
  	<doNotGenerate>
  	self cCode: ''
  		inSmalltalk:
  			[cogMethod isInteger ifTrue:
  				[^self printMethodHeader: (self cogMethodOrBlockSurrogateAt: cogMethod) on: aStream]].
  	aStream ensureCr.
  	cogMethod asInteger printOn: aStream base: 16.
  	aStream crtab.
  	cogMethod cmType = CMMethod ifTrue:
  		[aStream nextPutAll: 'objhdr: '.
  		cogMethod objectHeader printOn: aStream base: 16].
  	cogMethod cmType = CMBlock ifTrue:
  		[aStream nextPutAll: 'homemth: '.
  		cogMethod cmHomeMethod asUnsignedInteger printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'startpc: '; print: cogMethod startpc].
  	aStream
  		crtab; nextPutAll: 'nArgs: ';	print: cogMethod cmNumArgs;
  		tab;    nextPutAll: 'type: ';	print: cogMethod cmType.
  	(cogMethod cmType ~= 0 and: [cogMethod cmType ~= CMBlock]) ifTrue:
  		[aStream crtab; nextPutAll: 'blksiz: '.
  		cogMethod blockSize printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'method: '.
  		cogMethod methodObject printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'mthhdr: '.
  		cogMethod methodHeader printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'selctr: '.
  		cogMethod selector printOn: aStream base: 16.
  		(coInterpreter lookupAddress: cogMethod selector) ifNotNil:
  			[:string| aStream nextPut: $=; nextPutAll: string].
  		aStream crtab; nextPutAll: 'blkentry: '.
  		cogMethod blockEntryOffset printOn: aStream base: 16.
  		cogMethod blockEntryOffset ~= 0 ifTrue:
  			[aStream nextPutAll: ' => '.
  			 cogMethod asInteger + cogMethod blockEntryOffset printOn: aStream base: 16]].
  	cogMethod cmType = CMClosedPIC
  		ifTrue:
  			[aStream crtab; nextPutAll: 'cPICNumCases: '.
  			 cogMethod cPICNumCases printOn: aStream base: 16.]
  		ifFalse:
  			[aStream crtab; nextPutAll: 'stackCheckOffset: '.
  			 cogMethod stackCheckOffset printOn: aStream base: 16.
  			 cogMethod stackCheckOffset > 0 ifTrue:
  				[aStream nextPut: $/.
  				 cogMethod asInteger + cogMethod stackCheckOffset printOn: aStream base: 16].
+ 			cogMethod cmType = CMBlock
+ 				ifTrue:
+ 					[aStream
+ 						crtab;
+ 						nextPutAll: 'cbUsesInstVars ';
+ 						nextPutAll: (cogMethod cbUsesInstVars ifTrue: ['yes'] ifFalse: ['no'])]
+ 				ifFalse:
+ 					[aStream
+ 						crtab;
+ 						nextPutAll: 'cmRefersToYoung: ';
+ 						nextPutAll: (cogMethod cmRefersToYoung ifTrue: ['yes'] ifFalse: ['no'])].
- 			cogMethod cmType ~= CMBlock ifTrue:
- 				[aStream
- 					crtab;
- 					nextPutAll: 'cmRefersToYoung: ';
- 					nextPutAll: (cogMethod cmRefersToYoung ifTrue: ['yes'] ifFalse: ['no'])].
  			cogMethod cmType = CMMethod ifTrue:
  				[([cogMethod nextMethodOrIRCs] on: MessageNotUnderstood do: [:ex| nil]) ifNotNil:
  					[:nmoircs| aStream crtab; nextPutAll: 'nextMethodOrIRCs: '.
  						nmoircs = 0 ifTrue: [aStream print: nmoircs] ifFalse: [coInterpreter printHex: nmoircs]].
  				 ([cogMethod counters] on: MessageNotUnderstood do: [:ex| nil]) ifNotNil:
  					[:cntrs| aStream crtab; nextPutAll: 'counters: '.
  						cntrs = 0 ifTrue: [aStream print: cntrs] ifFalse: [coInterpreter printHex: cntrs]]]].
  	aStream cr; flush!

Item was changed:
  ----- Method: Cogit>>scanBlock: (in category 'compile abstract instructions') -----
  scanBlock: blockStart
  	"Scan the block to determine if the block needs a frame or not"
  	| descriptor pc end framelessStackDelta nExts |
  	<var: #blockStart type: #'BlockStart *'>
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	needsFrame := false.
  	methodOrBlockNumArgs := blockStart numArgs.
  	inBlock := true.
  	pc := blockStart startpc.
  	end := blockStart startpc + blockStart span.
  	framelessStackDelta := nExts := extA := extB := 0.
  	[pc < end] whileTrue:
  		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  		 descriptor := self generatorAt: byte0.
  		 descriptor isExtension ifTrue:
  			[self loadSubsequentBytesForDescriptor: descriptor at: pc.
  			 self perform: descriptor generator].
  		 needsFrame ifFalse:
  			[(descriptor needsFrameFunction isNil
  			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  				ifTrue: [needsFrame := true]
  				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
+ 		 objectRepresentation maybeNoteDescriptor: descriptor blockStart: blockStart.
  		 pc := self nextBytecodePCFor: descriptor at: pc exts: nExts in: methodObj.
  		 descriptor isExtension
  			ifTrue: [nExts := nExts + 1]
  			ifFalse: [nExts := extA := extB := 0]].
  	needsFrame ifFalse:
  		[framelessStackDelta < 0 ifTrue:
  			[self error: 'negative stack delta in block; block contains bogus code or internal error'].
  		 [framelessStackDelta > 0] whileTrue:
  			[descriptor := self generatorAt: (objectMemory fetchByte: blockStart startpc ofObject: methodObj) + bytecodeSetOffset.
  			 descriptor generator ~~ #genPushConstantNilBytecode ifTrue:
  				[self error: 'frameless block doesn''t start with enough pushNils'].
  			 blockStart
  				startpc: blockStart startpc + descriptor numBytes;
  				span: blockStart span - descriptor numBytes.
  			 framelessStackDelta := framelessStackDelta - 1]]!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForNewspeakV4 (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"SimpleStackBasedCogit initializeBytecodeTableForNewspeakV4"
  
  	NSSendIsPCAnnotated := false. "IsNSSendCall used by SendAbsentImplicit"
  	FirstSpecialSelector := 80.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
+ 		(1    0   15 genPushReceiverVariableBytecode isInstVarRef)
- 		(1    0   15 genPushReceiverVariableBytecode)
  		(1  16   31 genPushLiteralVariable16CasesBytecode needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode)
  		(1  76   76 genPushReceiverBytecode)
  		(1  77   77 genExtPushPseudoVariableOrOuterBytecode)
  		(1  78   78 genPushConstantZeroBytecode)
  		(1  79   79 genPushConstantOneBytecode)
  
  		(1   80 101 genSpecialSelectorSend isMapped) "#+ #- #< #> #<= #>= #= #~= #* #/ #\\ #@ #bitShift: #// #bitAnd: #bitOr: #at: #at:put: #size #next #nextPut: #atEnd"
  		(1 102 102 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 103 103 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 104 111 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 112 127 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 128 143 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 144 159 genSendLiteralSelector2ArgsBytecode isMapped)
  		(1 160 175	genSendAbsentImplicit0ArgsBytecode isMapped hasIRC)
  
+ 		(1 176 183 genStoreAndPopReceiverVariableBytecode isInstVarRef needsFrameNever: -1) "N.B. not frameless if immutability"
- 		(1 176 183 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 184 191 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 192 199 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 200 207 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 208 215 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		(1 216 216 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 217 217 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 218 218 genExtReturnTopFromBlock	return needsFrameNever: -1)
  
  		(1 219 219 duplicateTopBytecode			needsFrameNever: 1)
  		(1 220 220 genPopStackBytecode			needsFrameNever: -1)
  		(1 221 221 genExtNopBytecode			needsFrameNever: 0)
  		(1 222 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
+ 		(2 226 226 genExtPushReceiverVariableBytecode isInstVarRef)
- 		(2 226 226 genExtPushReceiverVariableBytecode)
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 230 230 genLongPushTemporaryVariableBytecode)
  		(2 231 231 genPushNewArrayBytecode)
+ 		(2 232 232 genExtStoreReceiverVariableBytecode isInstVarRef)
- 		(2 232 232 genExtStoreReceiverVariableBytecode)
  		(2 233 233 genExtStoreLiteralVariableBytecode)
  		(2 234 234 genLongStoreTemporaryVariableBytecode)
+ 		(2 235 235 genExtStoreAndPopReceiverVariableBytecode isInstVarRef)
- 		(2 235 235 genExtStoreAndPopReceiverVariableBytecode)
  		(2 236 236 genExtStoreAndPopLiteralVariableBytecode)
  		(2 237 237 genLongStoreAndPopTemporaryVariableBytecode)
  
  		(2 238 238 genExtSendBytecode isMapped)
  		(2 239 239 genExtSendSuperBytecode isMapped)
  		(2 240 240 genExtSendAbsentImplicitBytecode isMapped hasIRC)
  		(2 241 241 genExtSendAbsentDynamicSuperBytecode isMapped)
  
  		(2 242 242 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 243 243 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 244 244 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		(2 245 245 genExtSendAbsentSelfBytecode isMapped)
  
  		(2 246 248	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 249 249 genCallPrimitiveBytecode)
  		(3 250 250 genPushRemoteTempLongBytecode)
  		(3 251 251 genStoreRemoteTempLongBytecode)
  		(3 252 252 genStoreAndPopRemoteTempLongBytecode)
  		(3 253 253 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 254 254 genExtSendAbsentOuterBytecode isMapped hasIRC)
  
  		(3 255 255	unknownBytecode))!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForSistaV1 (in category 'class initialization') -----
  initializeBytecodeTableForSistaV1
  	"SimpleStackBasedCogit initializeBytecodeTableForSistaV1"
  
  	BytecodeSetHasDirectedSuperSend := true.
  	FirstSpecialSelector := 96.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		"pushes"
+ 		(1    0   15 genPushReceiverVariableBytecode isInstVarRef)
- 		(1    0   15 genPushReceiverVariableBytecode)
  		(1  16   31 genPushLiteralVariable16CasesBytecode	needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode			needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode)
  		(1  76   76 genPushReceiverBytecode)
  		(1  77   77 genPushConstantTrueBytecode				needsFrameNever: 1)
  		(1  78   78 genPushConstantFalseBytecode			needsFrameNever: 1)
  		(1  79   79 genPushConstantNilBytecode				needsFrameNever: 1)
  		(1  80   80 genPushConstantZeroBytecode				needsFrameNever: 1)
  		(1  81   81 genPushConstantOneBytecode				needsFrameNever: 1)
  		(1  82   82 genExtPushPseudoVariable)
  		(1  83   83 duplicateTopBytecode						needsFrameNever: 1)
  
  		(1  84   87 unknownBytecode)
  
  		"returns"
  		(1  88   88 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  89   89 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  90   90 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  91   91 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  92   92 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1  93   93 genReturnNilFromBlock			return needsFrameNever: -1)
  		(1  94   94 genReturnTopFromBlock		return needsFrameNever: -1)
  		(1  95   95 genExtNopBytecode			needsFrameNever: 0)
  
  		"sends"
  		(1   96 117 genSpecialSelectorSend isMapped) "#+ #- #< #> #<= #>= #= #~= #* #/ #\\ #@ #bitShift: #// #bitAnd: #bitOr: #at: #at:put: #size #next #nextPut: #atEnd"
  		(1 118 118 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 119 119 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 120 127 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 128 143 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 144 159 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 160 175 genSendLiteralSelector2ArgsBytecode isMapped)
  
  		"jumps"
  		(1 176 183 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 184 191 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 192 199 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		"stores"
+ 		(1 200 207 genStoreAndPopReceiverVariableBytecode isInstVarRef needsFrameNever: -1) "N.B. not frameless if immutability"
- 		(1 200 207 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 208 215 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 216 216 genPopStackBytecode needsFrameNever: -1)
  
  		(1 217 217 genUnconditionalTrapBytecode isMapped)
  
  		(1 218 223 unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  
  		"pushes"
+ 		(2 226 226 genExtPushReceiverVariableBytecode isInstVarRef)		"Needs a frame for context inst var access"
- 		(2 226 226 genExtPushReceiverVariableBytecode)		"Needs a frame for context inst var access"
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genLongPushTemporaryVariableBytecode)
  		(2 230 230 genPushClosureTempsBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 233 233 genExtPushCharacterBytecode				needsFrameNever: 1)
  
  		"returns"
  		"sends"
  		(2 234 234 genExtSendBytecode isMapped)
  		(2 235 235 genExtSendSuperBytecode isMapped)
  
  		"sista bytecodes"
  		(2 236 236 unknownBytecode)
  
  		"jumps"
  		(2 237 237 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 238 238 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 239 239 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		"stores"
+ 		(2 240 240 genExtStoreAndPopReceiverVariableBytecode isInstVarRef)
- 		(2 240 240 genExtStoreAndPopReceiverVariableBytecode)
  		(2 241 241 genExtStoreAndPopLiteralVariableBytecode)
  		(2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
+ 		(2 243 243 genExtStoreReceiverVariableBytecode isInstVarRef)
- 		(2 243 243 genExtStoreReceiverVariableBytecode)
  		(2 244 244 genExtStoreLiteralVariableBytecode)
  		(2 245 245 genLongStoreTemporaryVariableBytecode)
  
  		(2 246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 248 248 genCallPrimitiveBytecode)
  		(3 249 249 unknownBytecode) "reserved for Push Float"
  		(3 250 250 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 251 251 genPushRemoteTempLongBytecode)
  		(3 252 252 genStoreRemoteTempLongBytecode)
  		(3 253 253 genStoreAndPopRemoteTempLongBytecode)
  
  		(3 254 254	genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode)
  			
  		(3 255 255	unknownBytecode))!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForSqueakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosures
  	"SimpleStackBasedCogit initializeBytecodeTableForSqueakV3PlusClosures"
  
  	FirstSpecialSelector := 176.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
+ 		(1    0   15 genPushReceiverVariableBytecode isInstVarRef)
- 		(1    0   15 genPushReceiverVariableBytecode)
  		(1  16   31 genPushTemporaryVariableBytecode)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
+ 		(1  96 103 genStoreAndPopReceiverVariableBytecode isInstVarRef needsFrameNever: -1) "N.B. not frameless if immutability"
- 		(1  96 103 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode)
  		(1 113 113 genPushConstantTrueBytecode needsFrameNever: 1)
  		(1 114 114 genPushConstantFalseBytecode needsFrameNever: 1)
  		(1 115 115 genPushConstantNilBytecode needsFrameNever: 1)
  		(1 116 119 genPushQuickIntegerConstantBytecode needsFrameNever: 1)
  		"method returns in blocks need a frame because of nonlocalReturn:through:"
  		(1 120 120 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 121 121 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 122 122 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 123 123 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 124 124 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 125 125 genReturnTopFromBlock		return needsFrameNever: -1)
  
  		(1 126 127 unknownBytecode)
  
+ 		(2 128 128 extendedPushBytecode isInstVarRef) "well, maybe inst var ref"
+ 		(2 129 129 extendedStoreBytecode isInstVarRef) "well, maybe inst var ref"
+ 		(2 130 130 extendedStoreAndPopBytecode isInstVarRef) "well, maybe inst var ref"
- 		(2 128 128 extendedPushBytecode)
- 		(2 129 129 extendedStoreBytecode)
- 		(2 130 130 extendedStoreAndPopBytecode)
  		(2 131 131 genExtendedSendBytecode isMapped)
+ 		(3 132 132 doubleExtendedDoAnythingBytecode isInstVarRef isMapped) "well, maybe inst var ref"
- 		(3 132 132 doubleExtendedDoAnythingBytecode isMapped)
  		(2 133 133 genExtendedSuperBytecode isMapped)
  		(2 134 134 genSecondExtendedSendBytecode isMapped)
  		(1 135 135 genPopStackBytecode needsFrameNever: -1)
  		(1 136 136 duplicateTopBytecode needsFrameNever: 1)
  
  		(1 137 137 genPushActiveContextBytecode)
  		(2 138 138 genPushNewArrayBytecode)),
  
  		((initializationOptions at: #SpurObjectMemory ifAbsent: [false])
  			ifTrue: [#((3 139 139 genCallPrimitiveBytecode))]
  			ifFalse: [#((1 139 139 unknownBytecode))]),
  
  	  #(
  		(3 140 140 genPushRemoteTempLongBytecode)
  		(3 141 141 genStoreRemoteTempLongBytecode)
  		(3 142 142 genStoreAndPopRemoteTempLongBytecode)
  		(4 143 143 genPushClosureCopyCopiedValuesBytecode block v3:Block:Code:Size:)
  
  		(1 144 151 genShortUnconditionalJump			branch v3:ShortForward:Branch:Distance:)
  		(1 152 159 genShortJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:ShortForward:Branch:Distance:)
  		(2 160 163 genLongUnconditionalBackwardJump	branch isMapped "because of interrupt check"
  															v3:Long:Branch:Distance:)
  		(2 164 167 genLongUnconditionalForwardJump		branch v3:Long:Branch:Distance:)
  		(2 168 171 genLongJumpIfTrue					branch isBranchTrue isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  		(2 172 175 genLongJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  
  		(1 176 197 genSpecialSelectorSend isMapped)
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 207 genSpecialSelectorSend isMapped)
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was removed:
- ----- Method: SimpleStackBasedCogit class>>initializeNumTrampolines (in category 'class initialization') -----
- initializeNumTrampolines
- 	NumTrampolines := 42
- 						+ (NewspeakVM ifTrue: [18] ifFalse: [0])
- 						+ (BytecodeSetHasDirectedSuperSend ifTrue: [4] ifFalse: [0])!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileBlockFrameBuild: (in category 'compile abstract instructions') -----
  compileBlockFrameBuild: blockStart
  	"Build a frame for a block activation.  See CoInterpreter class>>initializeFrameIndices.
  	 		closure (in ReceiverResultReg)
  			arg0
  			...
  			argN
  			caller's saved ip/this stackPage (for a base frame)
  	fp->	saved fp
  			method
  			context (uninitialized?)
  			receiver
  			first temp
  			...
  	sp->	Nth temp
  	Avoid use of SendNumArgsReg which is the flag determining whether
  	context switch is allowed on stack-overflow."
  	<var: #blockStart type: #'BlockStart *'>
  	<inline: false>
  	self annotateBytecode: self Label.
  	backEnd hasLinkRegister ifTrue:
  		[self PushR: LinkReg].
  	self PushR: FPReg.
  	self MoveR: SPReg R: FPReg.
+ 	"Think of ClassReg as ClosureReg"
+ 	self MoveR: ReceiverResultReg R: ClassReg.
  	"The block method field must have its MFMethodFlagIsBlockFlag bit set.
  	 We arrange this using a labelOffset.  A hack, but it works."
  	blockStart fakeHeader
  		addDependent: (self annotateAbsolutePCRef:
  			(self PushCw: blockStart fakeHeader asInteger)); "method"
  		setLabelOffset: MFMethodFlagIsBlockFlag.
  	self annotate: (self PushCw: objectMemory nilObject) "context"
  		objRef: objectMemory nilObject.
+ 	"Fetch home receiver from outer context. closure is on stack and initially in ReceiverResultReg.
+ 	 It is safe to use Arg0Reg because reg args are pushed by the value primitives if there are any.".
+ 	blockStart hasInstVarRef
+ 		ifTrue: "Use ReceiverResultReg for Context to agree with store check trampoline"
+ 			[objectRepresentation
+ 				genLoadSlot: ClosureOuterContextIndex
+ 					sourceReg: ClassReg
+ 						destReg: ReceiverResultReg;
+ 				genLoadSlot: ReceiverIndex
+ 					sourceReg: ReceiverResultReg
+ 						destReg: Arg0Reg.
+ 			objectRepresentation
+ 				genEnsureOopInRegNotForwarded: Arg0Reg scratchReg: TempReg updatingSlot: ReceiverIndex in: ReceiverResultReg.
+ 			self MoveR: Arg0Reg R: ReceiverResultReg]
+ 		ifFalse:
+ 			[objectRepresentation
+ 				genLoadSlot: ClosureOuterContextIndex
+ 					sourceReg: ClassReg
+ 						destReg: Arg0Reg;
+ 				genLoadSlot: ReceiverIndex
+ 					sourceReg: Arg0Reg
+ 						destReg: ReceiverResultReg].
+ 	self PushR: ReceiverResultReg. "home receiver"
- 	"fetch home receiver from outer context. closure is on stack and initially in ReceiverResultReg"
- 	objectRepresentation
- 		genLoadSlot: ClosureOuterContextIndex
- 			sourceReg: ReceiverResultReg
- 				destReg: TempReg;
- 		genLoadSlot: ReceiverIndex
- 			sourceReg: TempReg
- 				destReg: ClassReg.
- 	self PushR: ClassReg. "home receiver"
  	"Push copied values; bytecode initializes temporaries"
  	0 to: blockStart numCopied - 1 do:
  		[:i|
  		objectRepresentation
  			genLoadSlot: i + ClosureFirstCopiedValueIndex
+ 			sourceReg: ClassReg
- 			sourceReg: ReceiverResultReg
  			destReg: TempReg.
  		self PushR: TempReg].
- 	self MoveR: ClassReg R: ReceiverResultReg.
  	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
  	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
  	self JumpBelow: stackOverflowCall.
  	blockStart stackCheckLabel: (self annotateBytecode: self Label)!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimitiveClosureValue (in category 'primitive generators') -----
  genPrimitiveClosureValue
  	"Check the argument count.  Fail if wrong.
  	 Get the method from the outerContext and see if it is cogged.  If so, jump to the
  	 block entry or the no-context-switch entry, as appropriate, and we're done.  If not,
  	 invoke the interpreter primitive."
  	| jumpFailNArgs jumpFail1 jumpFail2 jumpFail3 jumpFail4 jumpBCMethod primitiveRoutine result |
+ 	<var: #jumpFail1 type: #'AbstractInstruction *'>
- 	<var: #jumpFail5 type: #'AbstractInstruction *'>
  	<var: #jumpFail2 type: #'AbstractInstruction *'>
  	<var: #jumpFail3 type: #'AbstractInstruction *'>
  	<var: #jumpFail4 type: #'AbstractInstruction *'>
  	<var: #jumpFailNArgs type: #'AbstractInstruction *'>
  	<var: #jumpBCMethod type: #'AbstractInstruction *'>
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)()'>
  	objectRepresentation genLoadSlot: ClosureNumArgsIndex sourceReg: ReceiverResultReg destReg: TempReg.
  	self CmpCq: (objectMemory integerObjectOf: methodOrBlockNumArgs) R: TempReg.
  	jumpFailNArgs := self JumpNonZero: 0.
  	objectRepresentation genLoadSlot: ClosureOuterContextIndex sourceReg: ReceiverResultReg destReg: ClassReg.
  	jumpFail1 := objectRepresentation genJumpImmediate: ClassReg.
  	objectRepresentation genGetCompactClassIndexNonImmOf: ClassReg into: TempReg.
  	objectRepresentation genCmpClassMethodContextCompactIndexR: TempReg.
  	jumpFail2 := self JumpNonZero: 0.
+ 	"We defer unforwarding the receiver to the prologue; scanning blocks
+ 	 for inst var refs and only unforwarding if the block refers to inst vars."
+ 	(false
+ 	 and: [objectRepresentation hasSpurMemoryManagerAPI]) ifTrue:
- 	"This could be deferred to the prologue (compileBlockFrameBuild:) if blocks were
- 	 scanned to see if they referred to the receiver.  But for now this is safe if slow."
- 	objectRepresentation hasSpurMemoryManagerAPI ifTrue:
  		[objectRepresentation
  			genLoadSlot: ReceiverIndex sourceReg: ClassReg destReg: SendNumArgsReg;
  			genEnsureOopInRegNotForwarded: SendNumArgsReg
  			scratchReg: TempReg
  			updatingSlot: ReceiverIndex
  			in: ClassReg].
  	objectRepresentation genLoadSlot: MethodIndex sourceReg: ClassReg destReg: SendNumArgsReg.
  	jumpFail3 := objectRepresentation genJumpImmediate: SendNumArgsReg.
  	objectRepresentation genGetFormatOf: SendNumArgsReg into: TempReg.
  	self CmpCq: objectMemory firstCompiledMethodFormat R: TempReg.
  	jumpFail4 := self JumpLess: 0.
  	objectRepresentation genLoadSlot: HeaderIndex sourceReg: SendNumArgsReg destReg: ClassReg.
  	jumpBCMethod := objectRepresentation genJumpSmallInteger: ClassReg.
  	self MoveM16: (self offset: CogMethod of: #blockEntryOffset) r: ClassReg R: TempReg.
  	self AddR: ClassReg R: TempReg.
  	primitiveRoutine := coInterpreter
  							functionPointerForCompiledMethod: methodObj
  							primitiveIndex: primitiveIndex.
  	primitiveRoutine = #primitiveClosureValueNoContextSwitch ifTrue:
  		[blockNoContextSwitchOffset = nil ifTrue:
  			[^NotFullyInitialized].
  		 self SubCq: blockNoContextSwitchOffset R: TempReg].
  	self JumpR: TempReg.
  	jumpBCMethod jmpTarget: (jumpFail1 jmpTarget: (jumpFail2 jmpTarget: (jumpFail3 jmpTarget: (jumpFail4 jmpTarget: self Label)))).
  	(result := self compileInterpreterPrimitive: primitiveRoutine) < 0 ifTrue:
  		[^result].
  	jumpFailNArgs jmpTarget: self Label.
  	^0!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit class>>initializeNumTrampolines (in category 'class initialization') -----
- initializeNumTrampolines
- 	NumTrampolines := 53
- 						+ (NewspeakVM ifTrue: [18] ifFalse: [0])
- 						+ (BytecodeSetHasDirectedSuperSend ifTrue: [4] ifFalse: [0])!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit class>>numTrampolines (in category 'accessing') -----
+ numTrampolines
+ 	^super numTrampolines + 1
+ 
+ 	"Cogit withAllSubclasses collect: [:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"
+ 	"self instVarNames select: [:ea| ea beginsWith: 'ce']"!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForNewspeakV4 (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"StackToRegisterMappingCogit initializeBytecodeTableForNewspeakV4"
  
  	numPushNilsFunction := #v4:Num:Push:Nils:.
  	pushNilSizeFunction := #v4PushNilSize:numInitialNils:.
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by SendAbsentImplicit"
  	FirstSpecialSelector := 80.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
+ 		(1    0   15 genPushReceiverVariableBytecode isInstVarRef needsFrameNever: 1)
- 		(1    0   15 genPushReceiverVariableBytecode needsFrameNever: 1)
  		(1  16   31 genPushLiteralVariable16CasesBytecode needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  76   76 genPushReceiverBytecode needsFrameNever: 1)
  		(1  77   77 genExtPushPseudoVariableOrOuterBytecode needsFrameIfExtBGT2: 1)
  		(1  78   78 genPushConstantZeroBytecode needsFrameNever: 1)
  		(1  79   79 genPushConstantOneBytecode needsFrameNever: 1)
  
  		(1   80   80 genSpecialSelectorArithmetic isMapped AddRR)
  		(1   81   81 genSpecialSelectorArithmetic isMapped SubRR)
  		(1   82   82 genSpecialSelectorComparison isMapped JumpLess)
  		(1   83   83 genSpecialSelectorComparison isMapped JumpGreater)
  		(1   84   84 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1   85   85 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1   86   86 genSpecialSelectorComparison isMapped JumpZero)
  		(1   87   87 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1   88   93 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1   94   94 genSpecialSelectorArithmetic isMapped AndRR)
  		(1   95   95 genSpecialSelectorArithmetic isMapped OrRR)
  		(1   96 101 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 102 102 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 103 103 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 104 111 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 112 127 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 128 143 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 144 159 genSendLiteralSelector2ArgsBytecode isMapped)
  		(1 160 175	genSendAbsentImplicit0ArgsBytecode isMapped hasIRC)
  
+ 		(1 176 183 genStoreAndPopReceiverVariableBytecode isInstVarRef needsFrameNever: -1) "N.B. not frameless if immutability"
- 		(1 176 183 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 184 191 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 192 199 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 200 207 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 208 215 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		(1 216 216 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 217 217 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 218 218 genExtReturnTopFromBlock	return needsFrameNever: -1)
  
  		(1 219 219 duplicateTopBytecode			needsFrameNever: 1)
  		(1 220 220 genPopStackBytecode			needsFrameNever: -1)
  		(1 221 221 genExtNopBytecode			needsFrameNever: 0)
  		(1 222 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension					needsFrameNever: 0)
  		(2 225 225 extBBytecode extension					needsFrameNever: 0)
+ 		(2 226 226 genExtPushReceiverVariableBytecode isInstVarRef)
- 		(2 226 226 genExtPushReceiverVariableBytecode)
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 230 230 genLongPushTemporaryVariableBytecode)
  		(2 231 231 genPushNewArrayBytecode)
+ 		(2 232 232 genExtStoreReceiverVariableBytecode isInstVarRef)
- 		(2 232 232 genExtStoreReceiverVariableBytecode)
  		(2 233 233 genExtStoreLiteralVariableBytecode)
  		(2 234 234 genLongStoreTemporaryVariableBytecode)
+ 		(2 235 235 genExtStoreAndPopReceiverVariableBytecode isInstVarRef)
- 		(2 235 235 genExtStoreAndPopReceiverVariableBytecode)
  		(2 236 236 genExtStoreAndPopLiteralVariableBytecode)
  		(2 237 237 genLongStoreAndPopTemporaryVariableBytecode)
  
  		(2 238 238 genExtSendBytecode isMapped)
  		(2 239 239 genExtSendSuperBytecode isMapped)
  		(2 240 240 genExtSendAbsentImplicitBytecode isMapped hasIRC)
  		(2 241 241 genExtSendAbsentDynamicSuperBytecode isMapped)
  
  		(2 242 242 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 243 243 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 244 244 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		(2 245 245	genExtSendAbsentSelfBytecode isMapped)
  
  		(2 246 248	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 249 249 genCallPrimitiveBytecode)
  		(3 250 250 genPushRemoteTempLongBytecode)
  		(3 251 251 genStoreRemoteTempLongBytecode)
  		(3 252 252 genStoreAndPopRemoteTempLongBytecode)
  		(3 253 253 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 254 254	genExtSendAbsentOuterBytecode isMapped hasIRC)
  
  		(3 255 255	unknownBytecode))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForSistaV1 (in category 'class initialization') -----
  initializeBytecodeTableForSistaV1
  	"StackToRegisterMappingCogit initializeBytecodeTableForSistaV1"
  
  	numPushNilsFunction := #sistaV1:Num:Push:Nils:.
  	pushNilSizeFunction := #sistaV1PushNilSize:numInitialNils:.
  	BytecodeSetHasDirectedSuperSend := true.
  	FirstSpecialSelector := 96.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		"pushes"
+ 		(1    0   15 genPushReceiverVariableBytecode isInstVarRef		needsFrameNever: 1)
+ 		(1  16   31 genPushLitVarDirSup16CasesBytecode				needsFrameNever: 1)
+ 		(1  32   63 genPushLiteralConstantBytecode					needsFrameNever: 1)
+ 		(1  64   75 genPushTemporaryVariableBytecode				needsFrameIfMod16GENumArgs: 1)
+ 		(1  76   76 genPushReceiverBytecode							needsFrameNever: 1)
+ 		(1  77   77 genPushConstantTrueBytecode						needsFrameNever: 1)
+ 		(1  78   78 genPushConstantFalseBytecode					needsFrameNever: 1)
+ 		(1  79   79 genPushConstantNilBytecode						needsFrameNever: 1)
+ 		(1  80   80 genPushConstantZeroBytecode						needsFrameNever: 1)
+ 		(1  81   81 genPushConstantOneBytecode						needsFrameNever: 1)
- 		(1    0   15 genPushReceiverVariableBytecode			needsFrameNever: 1)
- 		(1  16   31 genPushLitVarDirSup16CasesBytecode	needsFrameNever: 1)
- 		(1  32   63 genPushLiteralConstantBytecode			needsFrameNever: 1)
- 		(1  64   75 genPushTemporaryVariableBytecode		needsFrameIfMod16GENumArgs: 1)
- 		(1  76   76 genPushReceiverBytecode					needsFrameNever: 1)
- 		(1  77   77 genPushConstantTrueBytecode				needsFrameNever: 1)
- 		(1  78   78 genPushConstantFalseBytecode			needsFrameNever: 1)
- 		(1  79   79 genPushConstantNilBytecode				needsFrameNever: 1)
- 		(1  80   80 genPushConstantZeroBytecode				needsFrameNever: 1)
- 		(1  81   81 genPushConstantOneBytecode				needsFrameNever: 1)
  		(1  82   82 genExtPushPseudoVariable)
+ 		(1  83   83 duplicateTopBytecode								needsFrameNever: 1)
- 		(1  83   83 duplicateTopBytecode						needsFrameNever: 1)
  
  		(1  84   87 unknownBytecode)
  
  		"returns"
  		(1  88   88 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  89   89 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  90   90 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  91   91 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  92   92 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1  93   93 genReturnNilFromBlock			return needsFrameNever: -1)
  		(1  94   94 genReturnTopFromBlock		return needsFrameNever: -1)
  		(1  95   95 genExtNopBytecode			needsFrameNever: 0)
  
  		"sends"
  		(1  96   96 genSpecialSelectorArithmetic isMapped AddRR)
  		(1  97   97 genSpecialSelectorArithmetic isMapped SubRR)
  		(1  98   98 genSpecialSelectorComparison isMapped JumpLess)
  		(1  99   99 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 100 100 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 101 101 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 102 102 genSpecialSelectorComparison isMapped JumpZero)
  		(1 103 103 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 104 109 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 110 110 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 111 111 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 112 117 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 118 118 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 119 119 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 120 127 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 128 143 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 144 159 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 160 175 genSendLiteralSelector2ArgsBytecode isMapped)
  
  		"jumps"
  		(1 176 183 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 184 191 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 192 199 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		"stores"
+ 		(1 200 207 genStoreAndPopReceiverVariableBytecode isInstVarRef needsFrameNever: -1) "N.B. not frameless if immutability"
- 		(1 200 207 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 208 215 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 216 216 genPopStackBytecode needsFrameNever: -1)
  
  		(1 217 217 genUnconditionalTrapBytecode isMapped)
  
  		(1 218 223 unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  
  		"pushes"
+ 		(2 226 226 genExtPushReceiverVariableBytecode isInstVarRef)		"Needs a frame for context inst var access"
- 		(2 226 226 genExtPushReceiverVariableBytecode)		"Needs a frame for context inst var access"
  		(2 227 227 genExtPushLitVarDirSupBytecode			needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genLongPushTemporaryVariableBytecode)
  		(2 230 230 genPushClosureTempsBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 233 233 genExtPushCharacterBytecode				needsFrameNever: 1)
  
  		"returns"
  		"sends"
  		(2 234 234 genExtSendBytecode isMapped)
  		(2 235 235 genExtSendSuperBytecode isMapped)
  
  		"sista bytecodes"
  		(2 236 236 unknownBytecode)
  
  		"jumps"
  		(2 237 237 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 238 238 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 239 239 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		"stores"
+ 		(2 240 240 genExtStoreAndPopReceiverVariableBytecode isInstVarRef)
- 		(2 240 240 genExtStoreAndPopReceiverVariableBytecode)
  		(2 241 241 genExtStoreAndPopLiteralVariableBytecode)
  		(2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
+ 		(2 243 243 genExtStoreReceiverVariableBytecode isInstVarRef)
- 		(2 243 243 genExtStoreReceiverVariableBytecode)
  		(2 244 244 genExtStoreLiteralVariableBytecode)
  		(2 245 245 genLongStoreTemporaryVariableBytecode)
  
  		(2 246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 248 248 genCallPrimitiveBytecode)
  		(3 249 249 unknownBytecode) "reserved for Push Float"
  		(3 250 250 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 251 251 genPushRemoteTempLongBytecode)
  		(3 252 252 genStoreRemoteTempLongBytecode)
  		(3 253 253 genStoreAndPopRemoteTempLongBytecode)
  
  		(3 254 254	genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode)
  		
  		(3 255 255	unknownBytecode))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForSqueakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosures
  	"StackToRegisterMappingCogit initializeBytecodeTableForSqueakV3PlusClosures"
  
  	numPushNilsFunction := #v3:Num:Push:Nils:.
  	pushNilSizeFunction := #v3PushNilSize:numInitialNils:.
  	FirstSpecialSelector := 176.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
+ 		(1    0   15 genPushReceiverVariableBytecode isInstVarRef needsFrameNever: 1)
- 		(1    0   15 genPushReceiverVariableBytecode needsFrameNever: 1)
  		(1  16   31 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
+ 		(1  96 103 genStoreAndPopReceiverVariableBytecode isInstVarRef needsFrameNever: -1) "N.B. not frameless if immutability"
- 		(1  96 103 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode needsFrameNever: 1)
  		(1 113 113 genPushConstantTrueBytecode needsFrameNever: 1)
  		(1 114 114 genPushConstantFalseBytecode needsFrameNever: 1)
  		(1 115 115 genPushConstantNilBytecode needsFrameNever: 1)
  		(1 116 119 genPushQuickIntegerConstantBytecode needsFrameNever: 1)
  		"method returns in blocks need a frame because of nonlocalReturn:through:"
  		(1 120 120 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 121 121 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 122 122 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 123 123 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 124 124 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 125 125 genReturnTopFromBlock		return needsFrameNever: -1)
  
  		(1 126 127 unknownBytecode)
  
+ 		(2 128 128 extendedPushBytecode isInstVarRef) "well, maybe inst var ref"
+ 		(2 129 129 extendedStoreBytecode isInstVarRef) "well, maybe inst var ref"
+ 		(2 130 130 extendedStoreAndPopBytecode isInstVarRef) "well, maybe inst var ref"
- 		(2 128 128 extendedPushBytecode)
- 		(2 129 129 extendedStoreBytecode)
- 		(2 130 130 extendedStoreAndPopBytecode)
  		(2 131 131 genExtendedSendBytecode isMapped)
+ 		(3 132 132 doubleExtendedDoAnythingBytecode isMapped) "well, maybe inst var ref"
+ 		(2 133 133 genExtendedSuperBytecode isInstVarRef isMapped)
- 		(3 132 132 doubleExtendedDoAnythingBytecode isMapped)
- 		(2 133 133 genExtendedSuperBytecode isMapped)
  		(2 134 134 genSecondExtendedSendBytecode isMapped)
  		(1 135 135 genPopStackBytecode needsFrameNever: -1)
  		(1 136 136 duplicateTopBytecode needsFrameNever: 1)
  
  		(1 137 137 genPushActiveContextBytecode)
  		(2 138 138 genPushNewArrayBytecode)),
  
  		((initializationOptions at: #SpurObjectMemory ifAbsent: [false])
  			ifTrue: [#((3 139 139 genCallPrimitiveBytecode))]
  			ifFalse: [#((1 139 139 unknownBytecode))]),
  
  	   #(
  		(3 140 140 genPushRemoteTempLongBytecode)
  		(3 141 141 genStoreRemoteTempLongBytecode)
  		(3 142 142 genStoreAndPopRemoteTempLongBytecode)
  		(4 143 143 genPushClosureCopyCopiedValuesBytecode block v3:Block:Code:Size:)
  
  		(1 144 151 genShortUnconditionalJump			branch v3:ShortForward:Branch:Distance:)
  		(1 152 159 genShortJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:ShortForward:Branch:Distance:)
  		(2 160 163 genLongUnconditionalBackwardJump	branch isMapped "because of interrupt check"
  															v3:Long:Branch:Distance:)
  		(2 164 167 genLongUnconditionalForwardJump		branch v3:Long:Branch:Distance:)
  		(2 168 171 genLongJumpIfTrue					branch isBranchTrue isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  		(2 172 175 genLongJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  
  		(1 176 176 genSpecialSelectorArithmetic isMapped AddRR)
  		(1 177 177 genSpecialSelectorArithmetic isMapped SubRR)
  		(1 178 178 genSpecialSelectorComparison isMapped JumpLess)
  		(1 179 179 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 180 180 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 181 181 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 182 182 genSpecialSelectorComparison isMapped JumpZero)
  		(1 183 183 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 184 189 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 190 190 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 191 191 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 192 197 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 207 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was removed:
- ----- Method: StackToRegisterMappingCogit class>>initializeNumTrampolines (in category 'class initialization') -----
- initializeNumTrampolines
- 	NumTrampolines := 52
- 						+ (NewspeakVM ifTrue: [18] ifFalse: [0])
- 						+ (BytecodeSetHasDirectedSuperSend ifTrue: [4] ifFalse: [0])!

Item was added:
+ ----- Method: StackToRegisterMappingCogit class>>numTrampolines (in category 'accessing') -----
+ numTrampolines
+ 	^super numTrampolines + 12 "includes register args aborts"
+ 
+ 	"Cogit withAllSubclasses collect: [:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"
+ 	"self instVarNames select: [:ea| ea beginsWith: 'ce']"!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>addBlockStartAt:numArgs:numCopied:span: (in category 'compile abstract instructions') -----
  addBlockStartAt: bytecodepc numArgs: numArgs numCopied: numCopied span: span
  	"Add a blockStart for an embedded block.  For a binary tree walk block dispatch
  	 blocks must be compiled in pc/depth-first order but are scanned in breadth-first
  	 order, so do an insertion sort (which of course is really a bubble sort because we
  	 have to move everything higher to make room)."
  	<returnTypeC: #'BlockStart *'>
  	| i blockStart |
  	<var: #blockStart type: #'BlockStart *'>
  	"Transcript ensureCr; nextPutAll: 'addBlockStartAt: '; print: bytecodepc; cr; flush."
  	blockCount > 0
  		ifTrue:
  			[i := blockCount - 1.
  			 [blockStart := self addressOf: (blockStarts at: i).
  			  "check for repeat addition during recompilation due to initialNil miscount."
  			  blockStart startpc = bytecodepc ifTrue:
  				[^blockStart].
  			  blockStart startpc > bytecodepc
  			  and: [i > 0]] whileTrue:
  				[i := i - 1].
  			 blockCount to: i + 1 by: -1 do:
  				[:j|
  				blockStarts at: j put: (blockStarts at: j - 1)].
  			blockStart := self cCode: [self addressOf: (blockStarts at: i + 1)]
  								inSmalltalk: [blockStarts at: i + 1 put: CogBlockStart new]]
  		ifFalse:
  			[blockStart := self cCode: [self addressOf: (blockStarts at: blockCount)]
  								inSmalltalk: [blockStarts at: blockCount put: CogBlockStart new]].
  	
  	blockCount := blockCount + 1.
  	blockStart
  		startpc: bytecodepc;
  		numArgs: numArgs;
  		numCopied: numCopied;
  		numInitialNils: 0;
  		stackCheckLabel: nil;
+ 		hasInstVarRef: false;
  		span: span.
  	^blockStart!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>scanBlock: (in category 'compile abstract instructions') -----
  scanBlock: blockStart
  	"Scan the block to determine if the block needs a frame or not"
  	| descriptor pc end framelessStackDelta nExts pushingNils numPushNils |
  	<var: #blockStart type: #'BlockStart *'>
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	needsFrame := false.
  	prevBCDescriptor := nil.
  	methodOrBlockNumArgs := blockStart numArgs.
  	inBlock := true.
  	pc := blockStart startpc.
  	end := blockStart startpc + blockStart span.
  	framelessStackDelta := nExts := extA := extB := 0.
  	pushingNils := true.
  	[pc < end] whileTrue:
  		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  		 descriptor := self generatorAt: byte0.
  		 descriptor isExtension ifTrue:
  			[self loadSubsequentBytesForDescriptor: descriptor at: pc.
  			 self perform: descriptor generator].
  		 needsFrame ifFalse:
  			[(descriptor needsFrameFunction isNil
  			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  				ifTrue: [needsFrame := true]
  				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
+ 		 objectRepresentation maybeNoteDescriptor: descriptor blockStart: blockStart.
  		 (pushingNils
  		  and: [descriptor isExtension not]) ifTrue:
  			["Count the initial number of pushed nils acting as temp initializers.  We can't tell
  			  whether an initial pushNil is an operand reference or a temp initializer, except
  			  when the pushNil is a jump target (has a fixup), which never happens:
  					self systemNavigation browseAllSelect:
  						[:m| | ebc |
  						(ebc := m embeddedBlockClosures
  									select: [:ea| ea decompile statements first isMessage]
  									thenCollect: [:ea| ea decompile statements first selector]) notEmpty
  						and: [(#(whileTrue whileFalse whileTrue: whileFalse:) intersection: ebc) notEmpty]]
  			  or if the bytecode set has a push multiple nils bytecode.  We simply count initial nils.
  			  Rarely we may end up over-estimating.  We will correct by checking the stack depth
  			  at the end of the block in compileBlockBodies."
  			 (numPushNils := self numPushNils: descriptor pc: pc nExts: nExts method: methodObj) > 0
  				ifTrue:
  					[self assert: (descriptor numBytes = 1
  									or: [descriptor generator == #genPushClosureTempsBytecode]).
  					 blockStart numInitialNils: blockStart numInitialNils + numPushNils]
  				ifFalse:
  					[pushingNils := false]].
  		 pc := self nextBytecodePCFor: descriptor at: pc exts: nExts in: methodObj.
  		 descriptor isExtension
  			ifTrue: [nExts := nExts + 1]
  			ifFalse: [nExts := extA := extB := 0].
  		 prevBCDescriptor := descriptor].
  	"It would be nice of this wasn't necessary but alas we need to do the eager
  	 scan for frameless methods so that we don't end up popping too much off
  	 the simulated stack, e.g. for pushNil; returnTopFromBlock methods."
  	needsFrame ifFalse:
  		[self assert: (framelessStackDelta >= 0 and: [blockStart numInitialNils >= framelessStackDelta]).
  		 blockStart numInitialNils: blockStart numInitialNils - framelessStackDelta]!



More information about the Vm-dev mailing list