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

commits at source.squeak.org commits at source.squeak.org
Wed Oct 7 01:31:19 UTC 2015


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

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

Name: VMMaker.oscog-eem.1491
Author: eem
Time: 6 October 2015, 6:29:21.907 pm
UUID: 05ac8927-326d-4bb1-bb66-99d4615fd7fa
Ancestors: VMMaker.oscog-eem.1490

x64 Cogit:
Refactor the gen[NS]Send: machinery to take selector indices instead of selector oops, to allow the x64/Spur64 JIT to use 32-bit in-line caches that hold selector indices, not selector oops.  Scheme is commented in genLoadInlineCache:.

Still required is PIC support (CmpC32R).

Fix the use of 80 as a constant in the special selector machinewry.  This should be firstSpecialSelectorBytecodeOffset.  Add [Alt]NumSpecialSelectors for range checking special selector indices, which are negative.


Nuke an obsolete method.

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

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveCwR (in category 'generate machine code') -----
  concretizeMoveCwR
+ 	"Will get inlined into concretizeAt: switch."
- 	"Will get inlined into concretizeAt: switch.
- 	 Note that for quick constants, xor reg,reg, movq r8 may be shorter.
- 	 We don't consider it worthwhile for other  than 0."
  	<inline: true>
  	| value |
  	value := operands at: 0.
  	machineCode
  		at: 0 put: 16rB8 + (self concreteRegister: (operands at: 1));
  		at: 1 put: (value bitAnd: 16rFF);
  		at: 2 put: (value >> 8 bitAnd: 16rFF);
  		at: 3 put: (value >> 16 bitAnd: 16rFF);
  		at: 4 put: (value >> 24 bitAnd: 16rFF).
  	^machineCodeSize := 5!

Item was added:
+ ----- Method: CogIA32CompilerForTests class>>byteRegistersWithNamesDo: (in category 'test support') -----
+ byteRegistersWithNamesDo: aBinaryBlock
+ 	(self registers first: 4)
+ 		with: #('%al' '%cl' '%dl' '%bl')
+ 		do: aBinaryBlock!

Item was changed:
  ----- Method: CogIA32CompilerTests>>testMoveRMbr (in category 'tests') -----
  testMoveRMbr
  	"self new testMoveRMbr"
+ 	CogIA32CompilerForTests byteRegistersWithNamesDo:
- 	CogIA32CompilerForTests registersWithNamesDo:
  		[:sreg :srname|
  		CogIA32CompilerForTests registersWithNamesDo:
  			[:dreg :drname|
  			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
  				[:offset| | inst len |
  				inst := self gen: MoveRMbr operand: sreg operand: offset operand: dreg.
  				len := inst concretizeAt: 0.
  				self processor
  					disassembleInstructionAt: 0
  					In: inst machineCode object
  					into: [:str :sz| | plainJane herIntended |
  						plainJane := self strip: str.
  						herIntended := 'movb ', srname, ', 0x', (offset hex allButFirst: 3), '(', drname, ')'.
  						self assert: (plainJane match: herIntended).
  						self assert: len = sz]]]]!

Item was changed:
  ----- Method: CogIA32CompilerTests>>testMoveXbrRR (in category 'tests') -----
  testMoveXbrRR
  	"self new testMoveXbrRR"
  	CogIA32CompilerForTests registersWithNamesDo:
  		[:idxreg :irname|
+ 		irname ~= '%esp' ifTrue:
+ 			[CogIA32CompilerForTests registersWithNamesDo:
+ 				[:basereg :brname|
+ 				CogIA32CompilerForTests registersWithNamesDo:
+ 					[:dreg :drname|
+ 					((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 						[:offset| | inst len |
+ 						inst := self gen: MoveXbrRR operand: idxreg operand: basereg operand: dreg.
+ 						len := inst concretizeAt: 0.
+ 						self processor
+ 							disassembleInstructionAt: 0
+ 							In: inst machineCode object
+ 							into: [:str :sz| | plainJane herIntended |
+ 								"Convert e.g. '00000000: movzbl %ds:(%eax,%eax,1), %eax : 0F B6 04 00 ' to  'movzbl (%eax,%eax,1)'"
+ 								plainJane := self strip: str.
+ 								herIntended := 'movzbl (', brname, ',', irname, ',1), ',drname.
+ 								self assert: (plainJane match: herIntended).
+ 								self assert: len = sz]]]]]]!
- 			irname ~= '%esp' ifTrue:
- 				[CogIA32CompilerForTests registersWithNamesDo:
- 					[:basereg :brname|
- 					CogIA32CompilerForTests registersWithNamesDo:
- 						[:dreg :drname|
- 						((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
- 							[:offset| | inst len |
- 							inst := self gen: MoveXbrRR operand: idxreg operand: basereg operand: dreg.
- 							len := inst concretizeAt: 0.
- 							self processor
- 								disassembleInstructionAt: 0
- 								In: inst machineCode object
- 								into: [:str :sz| | plainJane herIntended |
- 									"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
- 									plainJane := self strip: str.
- 									herIntended := 'movzbl (', brname, ',', irname, ',1), ',drname.
- 									self assert: (plainJane match: herIntended).
- 									self assert: len = sz]]]]]]!

Item was added:
+ ----- Method: CogInLineLiteralsARMCompiler>>cogit: (in category 'initialization') -----
+ cogit: aCogit
+ 	<doNotGenerate>
+ 	"There is no support for synthesizing 64-bit constants using inline instructions in this code generator."
+ 	self assert: aCogit objectMemory wordSize = 4.
+ 	super cogit: aCogit!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveAtPut: (in category 'primitive generators') -----
  genInnerPrimitiveAtPut: retNoffset
  	"Implement the guts of primitiveAtPut"
  	| formatReg jumpImmediate jumpBadIndex
  	  jumpNotIndexablePointers jumpNotIndexableBits
  	  jumpIsContext jumpIsCompiledMethod jumpIsBytes jumpHasFixedFields
  	  jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds
  	  jumpWordsOutOfBounds jumpBytesOutOfBounds jumpBytesOutOfRange
  	  jumpNonSmallIntegerValue jumpNegative jumpShortsUnsupported jumpNotPointers
  	  |
  	<inline: true>
  	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
  	<var: #jumpIsBytes type: #'AbstractInstruction *'>
  	<var: #jumpNegative type: #'AbstractInstruction *'>
  	<var: #jumpBadIndex type: #'AbstractInstruction *'>
  	<var: #jumpIsContext type: #'AbstractInstruction *'>
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
  	<var: #jumpHasFixedFields type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexableBits type: #'AbstractInstruction *'>
  	<var: #jumpArrayOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpShortsUnsupported type: #'AbstractInstruction *'>
  	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexablePointers type: #'AbstractInstruction *'>
  
  	jumpImmediate := self genJumpImmediate: ReceiverResultReg.
  	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
  	cogit SubCq: 1 R: Arg0Reg. "1-rel => 0-rel"
  
  	"formatReg := self formatOf: ReceiverResultReg"
  	self genGetFormatOf: ReceiverResultReg
  		into: (formatReg := SendNumArgsReg)
  		leastSignificantHalfOfBaseHeaderIntoScratch: nil.
  
  	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
  
  	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
  		  0 = 0 sized objects (UndefinedObject True False et al)
  		  1 = non-indexable objects with inst vars (Point et al)
  		  2 = indexable objects with no inst vars (Array et al)
  		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
  		  4 = weak indexable objects with inst vars (WeakArray et al)
  		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
  		  6 unused, reserved for exotic pointer objects?
  		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
  		  8 unused, reserved for exotic non-pointer objects?
  		  9 (?) 64-bit indexable
  		10 - 11 32-bit indexable
  		12 - 15 16-bit indexable
  		16 - 23 byte indexable
  		24 - 31 compiled method"
  	cogit CmpCq: objectMemory weakArrayFormat R: formatReg.
  	jumpNotPointers := cogit JumpAbove: 0.
  	"optimistic store check; assume index in range (almost always is)."
  	self genStoreCheckReceiverReg: ReceiverResultReg
  		valueReg: Arg1Reg
  		scratchReg: TempReg
  		inFrame: false.
  
  	cogit CmpCq: objectMemory arrayFormat R: formatReg.
  	jumpNotIndexablePointers := cogit JumpBelow: 0.
  	jumpHasFixedFields := cogit JumpNonZero: 0.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpArrayOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
  	cogit MoveR: Arg1Reg Xwr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit RetN: retNoffset.
  
  	jumpHasFixedFields jmpTarget: cogit Label.
  	self genGetClassIndexOfNonImm: ReceiverResultReg into: formatReg.
  	cogit CmpCq: ClassMethodContextCompactIndex R: formatReg.
  	jumpIsContext := cogit JumpZero: 0.
  	"get # fixed fields in formatReg"
  	cogit PushR: ClassReg.
  	self genGetClassObjectOfClassIndex: formatReg into: ClassReg scratchReg: TempReg.
  	self genLoadSlot: InstanceSpecificationIndex sourceReg: ClassReg destReg: formatReg.
  	cogit PopR: ClassReg.
  	self genConvertSmallIntegerToIntegerInReg: formatReg.
  	cogit AndCq: objectMemory fixedFieldsOfClassFormatMask R: formatReg.
  	cogit SubR: formatReg R: ClassReg.
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: formatReg.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpFixedFieldsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddR: formatReg R: Arg0Reg.
  	cogit MoveR: Arg1Reg Xwr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit RetN: retNoffset.
  
  	jumpNotPointers jmpTarget:
  		(cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg).
  	jumpIsCompiledMethod := cogit JumpAboveOrEqual: 0.
  	jumpNonSmallIntegerValue := self genJumpNotSmallInteger: Arg1Reg scratchReg: TempReg.
  					cogit CmpCq: objectMemory firstByteFormat R: formatReg.
  	jumpIsBytes := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
  	jumpShortsUnsupported := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
  	"For now ignore 64-bit indexability."
  	jumpNotIndexableBits := cogit JumpBelow: 0.
  
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	(cogit lastOpcode setsConditionCodesFor: JumpNegative) ifFalse:
- 	(self lastOpcode setsConditionCodesFor: JumpNegative) ifFalse:
  		[self CmpCq: 0 R: ClassReg]. "N.B. FLAGS := ClassReg - 0"
  	jumpNegative := cogit JumpNegative: 0.
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
  	cogit MoveR: TempReg Xwr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit RetN: retNoffset.
  
  	jumpIsBytes jmpTarget:
  		(cogit CmpCq: (objectMemory integerObjectOf: 255) R: Arg1Reg).
  	jumpBytesOutOfRange := cogit JumpAbove: 0.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg.
  	cogit AndCq: objectMemory wordSize - 1 R: formatReg.
  	cogit SubR: formatReg R: ClassReg;
  	CmpR: Arg0Reg R: ClassReg.
  	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
  	cogit AddCq: objectMemory baseHeaderSize R: Arg0Reg.
  	cogit MoveR: TempReg Xbr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit RetN: retNoffset.
  
  	"there are no shorts as yet.  so this is dead code:
  	jumpIsShorts jmpTarget:
  		(cogit CmpCq: (objectMemory integerObjectOf: 65535) R: Arg1Reg).
  	jumpShortsOutOfRange := cogit JumpAbove: 0.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg.
  	cogit AndCq: 1 R: formatReg.
  	cogit SubR: formatReg R: ClassReg;
  	CmpR: Arg0Reg R: ClassReg.
  	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
  	cogit genConvertSmallIntegerToIntegerInReg: TempReg.
  	cogit AddR: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: TempReg M16: objectMemory baseHeaderSize r: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	jumpShortsDone := cogit Jump: 0."
  
  	jumpIsContext jmpTarget: 
  	(jumpNegative jmpTarget:
  	(jumpNotIndexableBits jmpTarget:
  	(jumpBytesOutOfRange jmpTarget:
  	(jumpIsCompiledMethod jmpTarget:
  	(jumpArrayOutOfBounds jmpTarget:
  	(jumpBytesOutOfBounds jmpTarget:
  	(jumpShortsUnsupported jmpTarget:
  	(jumpWordsOutOfBounds jmpTarget:
  	(jumpNotIndexablePointers jmpTarget:
  	(jumpNonSmallIntegerValue jmpTarget:
  	(jumpFixedFieldsOutOfBounds jmpTarget: cogit Label))))))))))).
  
  	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
  	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
  
  	jumpBadIndex jmpTarget: (jumpImmediate jmpTarget: cogit Label).
  
  	^0!

Item was changed:
  SharedPool subclass: #CogRTLOpcodes
  	instanceVariableNames: ''
+ 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCqRR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call CallFull ClassReg CmpC32R CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpFull JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg Literal LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCq PushCw PushR RISCTempReg ReceiverResultReg RetN SPReg Scratch0Reg Scratch1Reg Scratch2Reg Scratch3Reg Scratch4Reg Scratch5Reg Scratch6Reg Scratch7Reg SendNumArgsReg SqrtRd Stop SubCqR SubCwR SubRR SubRdRd TempReg TstCqR VarBaseReg XorCqR XorCwR XorRR'
- 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCqRR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call CallFull ClassReg CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpFull JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg Literal LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCq PushCw PushR RISCTempReg ReceiverResultReg RetN SPReg Scratch0Reg Scratch1Reg Scratch2Reg Scratch3Reg Scratch4Reg Scratch5Reg Scratch6Reg Scratch7Reg SendNumArgsReg SqrtRd Stop SubCqR SubCwR SubRR SubRdRd TempReg TstCqR VarBaseReg XorCqR XorCwR XorRR'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogRTLOpcodes commentStamp: '<historical>' prior: 0!
  I am a pool for the Register-Transfer-Language to which Cog compiles.  I define unique integer values for all RTL opcodes and abstract registers.  See CogAbstractInstruction for instances of instructions with the opcodes that I define.!

Item was changed:
  ----- Method: CogRTLOpcodes class>>initialize (in category 'class initialization') -----
  initialize
  	"Abstract opcodes are a compound of a one word operation specifier and zero or more operand type specifiers.
  	 e.g. MoveRR is the Move opcode with two register operand specifiers and defines a move register to
  	 register instruction from operand 0 to operand 1.  The word and register size is assumed to be either 32-bits on
  	 a 32-bit architecture or 64-bits on a 64-bit architecture.  The abstract machine is mostly a 2 address machine
  	 with the odd three address instruction added to better exploit RISCs.
  			(self initialize)
  	The operand specifiers are
  		R		- general purpose register
  		Rd		- double-precision floating-point register
  		Cq		- a `quick' constant that can be encoded in the minimum space possible.
  		Cw		- a constant with word size where word is the default operand size for the Smalltalk VM, 32-bits
  				  for a 32-bit VM, 64-bits for a 64-bit VM.  The generated constant must occupy the default number
  				  of bits.  This allows e.g. a garbage collector to update the value without invalidating the code.
  		C32	- a constant with 32 bit size.  The generated constant must occupy 32 bits.
  		C64	- a constant with 64 bit size.  The generated constant must occupy 64 bits.
  		Aw		- memory word at an absolute address
  		Ab		- memory byte at an absolute address
  		Mwr	- memory word whose address is at a constant offset from an address in a register
  		Mbr		- memory byte whose address is at a constant offset from an address in a register (zero-extended on read)
  		M16r	- memory 16-bit halfword whose address is at a constant offset from an address in a register
  		M32r	- memory 32-bit halfword whose address is at a constant offset from an address in a register
  		M64r	- memory 64-bit doubleword whose address is at a constant offset from an address in a register
  		XbrR	- memory word whose address is r * byte size away from an address in a register
  		X16rR	- memory word whose address is r * (2 bytes size) away from an address in a register
  		XwrR	- memory word whose address is r * word size away from an address in a register
  		XowrR	- memory word whose address is (r * word size) + o away from an address in a register (scaled indexed)
  
  	An alternative would be to decouple opcodes from operands, e.g.
  		Move := 1. Add := 2. Sub := 3...
  		RegisterOperand := 1. ConstantQuickOperand := 2. ConstantWordOperand := 3...
  	But not all combinations make sense and even fewer are used so we stick with the simple compound approach.
  
  	The assumption is that comparison and arithmetic instructions set condition codes and that move instructions
  	leave the condition codes unaffected.  In particular LoadEffectiveAddressMwrR does not set condition codes
  	although it can be used to do arithmetic.
  
  	Not all of the definitions in opcodeDefinitions below are implemented.  In particular we do not implement the
  	 XowrR scaled index addressing mode since it requires 4 operands.
  
  	Note that there are no generic division instructions defined, but a processor may define some.
  
  	Branch/Call ranges.  Jump[Cond] can be generated as short as possible.  Call/Jump[Cond]Long must be generated
  	in the same number of bytes irrespective of displacement since their targets may be updated, but they need only
  	span 16Mb, the maximum size of the code zone.  This allows e.g. ARM to use single-word call and jump instructions
  	for most calls and jumps.  CallFull/JumpFull must also be generated in the same number of bytes irrespective of
  	displacement for the same reason, but they must be able to span the full (32-bit or 64-bit) address space because
  	they are used to call code in the C runtime, which may be distant from the code zone.  CallFull/JumpFull are allowed
  	to use the cResultRegister as a scratch if required (e.g. on x64 where there is no direct 64-bit call or jump)."
  
  	| opcodeNames refs |
  	"A small fixed set of abstract registers are defined and used in code generation
  	 for Smalltalk code, and executes on stack pages in the stack zone.
  	 These are mapped to processor-specific registers by concreteRegister:"
  	FPReg := -1.	"A frame pointer is used for Smalltalk frames."
  	SPReg := -2.
  	ReceiverResultReg := -3.		"The receiver at point of send, and return value of a send"
  	TempReg := -4.
  	ClassReg := -5.					"The inline send cache class tag is in this register, loaded at the send site"
  	SendNumArgsReg := -6.		"Sends > 2 args set the arg count in this reg"
  	Arg0Reg := -7.					"In the StackToRegisterMappingCogit 1 & 2 arg sends marshall into these registers."
  	Arg1Reg := -8.
  
  	"A small fixed set of abstract scratch registers for register-rich machines (ARM can use 1, x64 can use 6)."
  	Scratch0Reg := -9.
  	Scratch1Reg := -10.
  	Scratch2Reg := -11.
  	Scratch3Reg := -12.
  	Scratch4Reg := -13.
  	Scratch5Reg := -14.
  	Scratch6Reg := -15.
  	Scratch7Reg := -16.
  
  	"RISC-specific registers"
  	LinkReg := -17.
  	RISCTempReg := -18.	"Used to synthesize CISC instructions from multiple RISC instructions."
  	PCReg := -19.
  	VarBaseReg := -20.		"If useful, points to base of interpreter variables."
  
  	"Floating-point registers"
  	DPFPReg0 := -21.
  	DPFPReg1 := -22.
  	DPFPReg2 := -23.
  	DPFPReg3 := -24.
  	DPFPReg4 := -25.
  	DPFPReg5 := -26.
  	DPFPReg6 := -27.
  	DPFPReg7 := -28.
  
  	opcodeNames := #("Noops & Pseudo Ops"
  						Label
  						Literal			"a word-sized literal"
  						AlignmentNops
  						FillBytesFrom	"output operand 0's worth of bytes from the address in operand 1"
  						Fill8				"output a byte's worth of bytes with operand 0"
  						Fill16			"output two byte's worth of bytes with operand 0"
  						Fill32			"output four byte's worth of bytes with operand 0"
  						FillFromWord	"output BytesPerWord's worth of bytes with operand 0 + operand 1"
  						Nop
  
  						"Control"
  						Call					"call within the code zone"
  						CallFull				"call anywhere within the full address space"
  						RetN
  						JumpR				"Not a regular jump, i.e. not pc dependent."
  						Stop				"Halt the processor"
  
  						"N.B.  Jumps are contiguous.  Long and Full jumps are contigiuous within them.  See FirstJump et al below"
  						JumpFull			"Jump anywhere within the address space"
  						JumpLong			"Jump anywhere within the 16mb code zone."
  						JumpLongZero			"a.k.a. JumpLongEqual"
  						JumpLongNonZero		"a.k.a. JumpLongNotEqual"
  						Jump				"short jumps; can be encoded in as few bytes as possible; will not be disturbed by GC or relocation."
  						JumpZero				"a.k.a. JumpEqual"
  						JumpNonZero			"a.k.a. JumpNotEqual"
  						JumpNegative
  						JumpNonNegative
  						JumpOverflow
  						JumpNoOverflow
  						JumpCarry
  						JumpNoCarry
  						JumpLess			"signed"
  						JumpGreaterOrEqual
  						JumpGreater
  						JumpLessOrEqual
  						JumpBelow			"unsigned"
  						JumpAboveOrEqual
  						JumpAbove
  						JumpBelowOrEqual
  
  						JumpFPEqual
  						JumpFPNotEqual
  						JumpFPLess
  						JumpFPLessOrEqual
  						JumpFPGreater
  						JumpFPGreaterOrEqual
  						JumpFPOrdered
  						JumpFPUnordered
  
  						"Data Movement; destination is always last operand"
  						MoveRR
  						MoveAwR
  						MoveRAw
  						MoveAbR
  						MoveRAb
  						MoveMwrR MoveRMwr MoveXwrRR MoveRXwrR MoveXowrR MoveRXowr
  						MoveM16rR MoveRM16r MoveX16rRR MoveRX16rR
  						MoveM32rR MoveRM32r MoveX32rRR MoveRX32rR
  						MoveMbrR MoveRMbr MoveXbrRR MoveRXbrR
  						MoveCqR MoveCwR MoveC32R MoveC64R
  						MoveRdRd MoveM64rRd MoveRdM64r
  						PopR PushR PushCq PushCw
  						PrefetchAw
  
  						"Arithmetic; destination is always last operand except Cmp; CmpXR is SubRX with no update of result"
  						LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR "Variants of add/multiply"
  						NegateR "2's complement negation"
  						ArithmeticShiftRightCqR ArithmeticShiftRightRR
  						LogicalShiftRightCqR LogicalShiftRightRR
  						LogicalShiftLeftCqR LogicalShiftLeftRR
  
  						CmpRR AddRR SubRR AndRR OrRR XorRR
  						CmpCqR AddCqR SubCqR AndCqR OrCqR TstCqR XorCqR
+ 						CmpCwR CmpC32R AddCwR SubCwR AndCwR OrCwR XorCwR
- 						CmpCwR AddCwR SubCwR AndCwR OrCwR XorCwR
  
  						AndCqRR
  
  						CmpRdRd AddRdRd SubRdRd MulRdRd DivRdRd SqrtRd
  
  						"Conversion"
  						ConvertRRd
  
  						LastRTLCode).
  
  	"Magic auto declaration. Add to the classPool any new variables and nuke any obsolete ones, and assign values"
  	"Find the variables directly referenced by this method"
  	refs := (thisContext method literals select: [:l| l isVariableBinding and: [classPool includesKey: l key]]) collect:
  				[:ea| ea key].
  	"Move to Undeclared any opcodes in classPool not in opcodes or this method."
  	(classPool keys reject: [:k| (opcodeNames includes: k) or: [refs includes: k]]) do:
  		[:k|
  		Undeclared declare: k from: classPool].
  	"Declare as class variables and number elements of opcodeArray above"
  	opcodeNames withIndexDo:
  		[:classVarName :value|
  		self classPool
  			declare: classVarName from: Undeclared;
  			at: classVarName put: value].
  
  	"For CogAbstractInstruction>>isJump etc..."
  	FirstJump := JumpFull.
  	LastJump := JumpFPUnordered.
  	FirstShortJump := Jump.
  
  	"And now initialize the backends; they add their own opcodes and hence these must be reinitialized."
  	(Smalltalk classNamed: #CogAbstractInstruction) ifNotNil:
  		[:cogAbstractInstruction| cogAbstractInstruction allSubclasses do: [:sc| sc initialize]]!

Item was changed:
  ----- Method: CogX64Compiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Compute the maximum size for each opcode.  This allows jump offsets to
  	 be determined, provided that all backward branches are long branches."
  	"N.B.  The ^N forms are to get around the bytecode compiler's long branch
  	 limits which are exceeded when each case jumps around the otherwise."
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^0].
  		[AlignmentNops]		-> [^(operands at: 0) - 1].
  		[Fill16]					-> [^2].
  		[Fill32]					-> [^4].
  		[FillFromWord]			-> [^4].
  		[Nop]					-> [^1].
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^2].
  		[IDIVR]					-> [^3].
  		[IMULRR]				-> [^4].
  		[CPUID]					-> [^2].
  		[CMPXCHGAwR]			-> [^8].
  		[CMPXCHGMwrR]		-> [^9].
  		[LFENCE]				-> [^3].
  		[MFENCE]				-> [^3].
  		[SFENCE]				-> [^3].
  		[LOCK]					-> [^1].
  		"[XCHGAwR]				-> [^6].
  		[XCHGMwrR]			-> [^7]."
  		[XCHGRR]				-> [^((self concreteRegister: (operands at: 0)) = RAX
  									   or: [(self concreteRegister: (operands at: 1)) = RAX])
  											ifTrue: [2]
  											ifFalse: [3]].
  		"Control"
  		[CallFull]					-> [^12].
  		[Call]						-> [^5].
  		[JumpR]						-> [^2].
  		[JumpFull]					-> [self resolveJumpTarget. ^12].
  		[JumpLong]					-> [self resolveJumpTarget. ^5].
  		[Jump]						-> [self resolveJumpTarget. ^5].
  		[JumpZero]					-> [self resolveJumpTarget. ^6].
  		[JumpNonZero]				-> [self resolveJumpTarget. ^6].
  		[JumpNegative]				-> [self resolveJumpTarget. ^6].
  		[JumpNonNegative]			-> [self resolveJumpTarget. ^6].
  		[JumpOverflow]				-> [self resolveJumpTarget. ^6].
  		[JumpNoOverflow]			-> [self resolveJumpTarget. ^6].
  		[JumpCarry]				-> [self resolveJumpTarget. ^6].
  		[JumpNoCarry]				-> [self resolveJumpTarget. ^6].
  		[JumpLess]					-> [self resolveJumpTarget. ^6].
  		[JumpGreaterOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpGreater]				-> [self resolveJumpTarget. ^6].
  		[JumpLessOrEqual]			-> [self resolveJumpTarget. ^6].
  		[JumpBelow]				-> [self resolveJumpTarget. ^6].
  		[JumpAboveOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpAbove]				-> [self resolveJumpTarget. ^6].
  		[JumpBelowOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpLongZero]			-> [self resolveJumpTarget. ^6].
  		[JumpLongNonZero]		-> [self resolveJumpTarget. ^6].
  		[JumpFPEqual]				-> [self resolveJumpTarget. ^6].
  		[JumpFPNotEqual]			-> [self resolveJumpTarget. ^6].
  		[JumpFPLess]				-> [self resolveJumpTarget. ^6].
  		[JumpFPGreaterOrEqual]	-> [self resolveJumpTarget. ^6].
  		[JumpFPGreater]			-> [self resolveJumpTarget. ^6].
  		[JumpFPLessOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpFPOrdered]			-> [self resolveJumpTarget. ^6].
  		[JumpFPUnordered]			-> [self resolveJumpTarget. ^6].
  		[RetN]						-> [^(operands at: 0) = 0 ifTrue: [1] ifFalse: [3]].
  		[Stop]						-> [^1].
  
  		"Arithmetic"
  		[AddCqR]		-> [^self computeSizeOfArithCqR].
  		[AndCqR]		-> [^self computeSizeOfArithCqR].
  		[CmpCqR]		-> [^self computeSizeOfArithCqR].
  		[OrCqR]			-> [^self computeSizeOfArithCqR].
  		[SubCqR]		-> [^self computeSizeOfArithCqR].
  		[TstCqR]		-> [^self computeSizeOfArithCqR].
  		[AddCwR]		-> [^self computeSizeOfArithCwR].
  		[AndCwR]		-> [^self computeSizeOfArithCwR].
  		[CmpCwR]		-> [^self computeSizeOfArithCwR].
  		[OrCwR]		-> [^self computeSizeOfArithCwR].
  		[SubCwR]		-> [^self computeSizeOfArithCwR].
  		[XorCwR]		-> [^self computeSizeOfArithCwR].
  		[AddRR]			-> [^3].
  		[AndRR]			-> [^3].
  		[CmpRR]		-> [^3].
  		[OrRR]			-> [^3].
  		[XorRR]			-> [^3].
  		[SubRR]			-> [^3].
  		[NegateR]		-> [^3].
  		"[LoadEffectiveAddressMwrR]
  						-> [^((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])]."
  		[LogicalShiftLeftCqR]		-> [^(operands at: 0) = 1 ifTrue: [3] ifFalse: [4]].
  		[LogicalShiftRightCqR]		-> [^(operands at: 0) = 1 ifTrue: [3] ifFalse: [4]].
  		[ArithmeticShiftRightCqR]	-> [^(operands at: 0) = 1 ifTrue: [3] ifFalse: [4]].
  		[LogicalShiftLeftRR]			-> [^self computeShiftRRSize].
  		[LogicalShiftRightRR]		-> [^self computeShiftRRSize].
  		[ArithmeticShiftRightRR]		-> [^self computeShiftRRSize].
  		[AddRdRd]					-> [^4].
  		[CmpRdRd]					-> [^4].
  		[SubRdRd]					-> [^4].
  		[MulRdRd]					-> [^4].
  		[DivRdRd]					-> [^4].
  		[SqrtRd]					-> [^4].
  		"Data Movement"
+ 		[MoveCqR]		-> [^(operands at: 0) = 0
+ 								ifTrue: [3]
+ 								ifFalse:
+ 									[(self is32BitSignedImmediate: (operands at: 0))
+ 										ifTrue: [7]
+ 										ifFalse: [self moveCwRByteSize]]].
- 		[MoveCqR]		-> [^(operands at: 0) = 0 ifTrue: [3] ifFalse: [(self is32BitSignedImmediate: (operands at: 0)) ifTrue: [7] ifFalse: [self moveCwRByteSize]]].
  		[MoveCwR]		-> [^self moveCwRByteSize].
+ 		[MoveC32R]	-> [^7]. "N.B. Always inlined."
  		[MoveRR]		-> [^3].
  		[MoveRdRd]		-> [^4].
  		[MoveAwR]		-> [^(self isAddressRelativeToVarBase: (operands at: 0))
  								ifTrue: [7]
  								ifFalse: [(self concreteRegister: (operands at: 1)) = RAX ifTrue: [10] ifFalse: [14]]].
  		[MoveRAw]		-> [^(self isAddressRelativeToVarBase: (operands at: 1))
  								ifTrue: [7]
  								ifFalse: [(self concreteRegister: (operands at: 0)) = RAX ifTrue: [10] ifFalse: [14]]].
  		[MoveRMwr]	-> [^((self isQuick: (operands at: 1))
  									ifTrue: [((operands at: 1) = 0
  											and: [((self concreteRegister: (operands at: 2)) bitAnd: 7) ~= RBP])
  												ifTrue: [3]
  												ifFalse: [4]]
  									ifFalse: [7])
  								+ (((self concreteRegister: (operands at: 2)) bitAnd: 7) = RSP
  									ifTrue: [1]
  									ifFalse: [0])].
  		"[MoveRdM64r]	-> [^((self isQuick: (operands at: 1))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])]."
  		[MoveMbrR]		-> [^((self isQuick: (operands at: 0))
  									ifTrue: [((operands at: 0) = 0
  											and: [((self concreteRegister: (operands at: 1)) bitAnd: 7) ~= RBP])
  												ifTrue: [4]
  												ifFalse: [5]]
  									ifFalse: [8])
  								+ (((self concreteRegister: (operands at: 1)) bitAnd: 7) = RSP
  									ifTrue: [1]
  									ifFalse: [0])].
  		[MoveRMbr]		-> [^((self isQuick: (operands at: 1))
  									ifTrue: [((operands at: 1) = 0
  											and: [((self concreteRegister: (operands at: 0)) bitAnd: 7) ~= RBP])
  												ifTrue: [3]
  												ifFalse: [4]]
  									ifFalse: [7])
  								+ (((self concreteRegister: (operands at: 2)) bitAnd: 7) = RSP
  									ifTrue: [1]
  									ifFalse: [0])].
  		[MoveM16rR]	-> [^((self isQuick: (operands at: 0))
  									ifTrue: [((operands at: 0) = 0
  											and: [((self concreteRegister: (operands at: 1)) bitAnd: 7) ~= RBP])
  												ifTrue: [4]
  												ifFalse: [5]]
  									ifFalse: [8])
  								+ (((self concreteRegister: (operands at: 1)) bitAnd: 7) = RSP
  									ifTrue: [1]
  									ifFalse: [0])].
  		"[MoveM64rRd]	-> [^((self isQuick: (operands at: 0))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])]."
  		[MoveMwrR]		-> [^((self isQuick: (operands at: 0))
  									ifTrue: [((operands at: 0) = 0
  											and: [((self concreteRegister: (operands at: 1)) bitAnd: 7) ~= RBP])
  												ifTrue: [3]
  												ifFalse: [4]]
  									ifFalse: [7])
  								+ (((self concreteRegister: (operands at: 1)) bitAnd: 7) = RSP
  									ifTrue: [1]
  									ifFalse: [0])].
+ 		[MoveXbrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= RSP.
+ 							^((self concreteRegister: (operands at: 1)) bitAnd: 7) = RBP
+ 											ifTrue: [6]
+ 											ifFalse: [5]].
+ 		[MoveRXbrR]	->	[self assert: (self concreteRegister: (operands at: 1)) ~= RSP.
+ 							^(((self concreteRegister: (operands at: 0)) < 8
+ 							   and: [(self concreteRegister: (operands at: 1)) < 8
+ 							   and: [(self concreteRegister: (operands at: 2)) < 8]])
+ 								ifTrue: [3]
+ 								ifFalse: [4])
+ 							+ (((self concreteRegister: (operands at: 2)) bitAnd: 7) = RBP
+ 											ifTrue: [1]
+ 											ifFalse: [0])].
- 		"[MoveXbrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= ESP.
- 							^(self concreteRegister: (operands at: 1)) = EBP
- 											ifTrue: [5]
- 											ifFalse: [4]].
- 		[MoveRXbrR]	->	[self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
- 							^((self concreteRegister: (operands at: 2)) = EBP
- 											ifTrue: [4]
- 											ifFalse: [3])
- 										+ ((self concreteRegister: (operands at: 0)) >= 4
- 											ifTrue: [2]
- 											ifFalse: [0])]."
  		[MoveXwrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= RSP.
  							^((self concreteRegister: (operands at: 1)) = RBP
  							   or: [(self concreteRegister: (operands at: 1)) = R13])
  											ifTrue: [5]
  											ifFalse: [4]].
  		[MoveRXwrR]	-> [self assert: (self concreteRegister: (operands at: 1)) ~= RSP.
  							^((self concreteRegister: (operands at: 2)) = RBP
  							   or: [(self concreteRegister: (operands at: 2)) = R13])
  											ifTrue: [5]
  											ifFalse: [4]].
  		[PopR]			-> [^(self concreteRegister: (operands at: 0)) < 8 ifTrue: [1] ifFalse: [2]].
  		[PushR]			-> [^(self concreteRegister: (operands at: 0)) < 8 ifTrue: [1] ifFalse: [2]].
  		[PushCq]		-> [^(self isQuick: (operands at: 0)) ifTrue: [2] ifFalse: [5]].
  		[PushCw]		-> [^self pushCwByteSize].
  		[PrefetchAw]	-> [^self hasSSEInstructions ifTrue: [12] ifFalse: [0]].
  		"Conversion"
  		"[ConvertRRd]	-> [^4]" }.
  	^0 "to keep C compiler quiet"!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeMoveC32R (in category 'generate machine code') -----
+ concretizeMoveC32R
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| value reg |
+ 	value := operands at: 0.
+ 	reg := self concreteRegister: (operands at: 1).
+ 	machineCode
+ 		at: 0 put: (self rexR: 0 x: 0 b: reg);
+ 		at: 1 put: 16rC7;
+ 		at: 2 put: (self mod: ModReg RM: reg RO: 0);
+ 		at: 3 put: (value bitAnd: 16rFF);
+ 		at: 4 put: (value >> 8 bitAnd: 16rFF);
+ 		at: 5 put: (value >> 16 bitAnd: 16rFF);
+ 		at: 6 put: (value >> 24 bitAnd: 16rFF).
+ 	^machineCodeSize := 7!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeMoveRXbrR (in category 'generate machine code') -----
+ concretizeMoveRXbrR
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| index base dest offset |
+ 	index := self concreteRegister: (operands at: 0).
+ 	base := self concreteRegister: (operands at: 1).
+ 	dest := self concreteRegister: (operands at: 2).
+ 	offset := 0.
+ 	(dest >= 8 or: [base >= 8 or: [index >= 8]]) ifTrue:
+ 		[machineCode at: 0 put: (self rexR: dest x: index b: base).
+ 		 offset := 1].
+ 	machineCode
+ 		at: 0 + offset put: 16r88.
+ 	(base ~= RBP and: [base ~= R13]) ifTrue:
+ 		[machineCode
+ 			at: 1 + offset put: (self mod: ModRegInd RM: 4 RO: dest);
+ 			at: 2 + offset put: (self s: SIB1 i: index b: base).
+ 		 ^machineCodeSize := 3 + offset].
+ 	machineCode
+ 		at: 1 + offset put: (self mod: ModRegRegDisp8 RM: 4 RO: dest);
+ 		at: 2 + offset put: (self s: SIB1 i: index b: base);
+ 		at: 3 + offset put: 0.
+ 	 ^machineCodeSize := 4 + offset!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeMoveXbrRR (in category 'generate machine code') -----
+ concretizeMoveXbrRR
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| index base dest |
+ 	index := self concreteRegister: (operands at: 0).
+ 	base := self concreteRegister: (operands at: 1).
+ 	dest := self concreteRegister: (operands at: 2).
+ 	machineCode
+ 		at: 0 put: (self rexR: dest x: index b: base);
+ 		at: 1 put: 16r0F;
+ 		at: 2 put: 16rB6.
+ 	(base ~= RBP and: [base ~= R13]) ifTrue:
+ 		[machineCode
+ 			at: 3 put: (self mod: ModRegInd RM: 4 RO: dest);
+ 			at: 4 put: (self s: SIB1 i: index b: base).
+ 		 ^machineCodeSize := 5].
+ 	machineCode
+ 		at: 3 put: (self mod: ModRegRegDisp8 RM: 4 RO: dest);
+ 		at: 4 put: (self s: SIB1 i: index b: base);
+ 		at: 5 put: 0.
+ 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogX64Compiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  	<returnTypeC: #void>
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]				-> [^self concretizeLabel].
  		[AlignmentNops]	-> [^self concretizeAlignmentNops].
  		[Fill16]				-> [^self concretizeFill16].
  		[Fill32]				-> [^self concretizeFill32].
  		[FillFromWord]		-> [^self concretizeFillFromWord].
  		[Nop]				-> [^self concretizeNop].
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^self concretizeCDQ].
  		[IDIVR]					-> [^self concretizeIDIVR].
  		[IMULRR]				-> [^self concretizeMulRR].
  		[CPUID]					-> [^self concretizeCPUID].
  		[CMPXCHGAwR]			-> [^self concretizeCMPXCHGAwR].
  		[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR].
  		[LFENCE]				-> [^self concretizeFENCE: 5].
  		[MFENCE]				-> [^self concretizeFENCE: 6].
  		[SFENCE]				-> [^self concretizeFENCE: 7].
  		[LOCK]					-> [^self concretizeLOCK].
  		[XCHGAwR]				-> [^self concretizeXCHGAwR].
  		[XCHGMwrR]			-> [^self concretizeXCHGMwrR].
  		[XCHGRR]				-> [^self concretizeXCHGRR].
  		"Control"
  		[Call]					-> [^self concretizeCall].
  		[CallFull]				-> [^self concretizeCallFull].
  		[JumpR]					-> [^self concretizeJumpR].
  		[JumpFull]				-> [^self concretizeJumpFull].
  		[JumpLong]				-> [^self concretizeJumpLong].
  		[JumpLongZero]		-> [^self concretizeConditionalJump: 16r4].
  		[JumpLongNonZero]	-> [^self concretizeConditionalJump: 16r5].
  		[Jump]					-> [^self concretizeJump].
  		"Table B-1 Intel® 64 and IA-32 Architectures Software Developer's Manual Volume 1: Basic Architecture"
  		[JumpZero]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpNonZero]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpNegative]			-> [^self concretizeConditionalJump: 16r8].
  		[JumpNonNegative]		-> [^self concretizeConditionalJump: 16r9].
  		[JumpOverflow]			-> [^self concretizeConditionalJump: 16r0].
  		[JumpNoOverflow]		-> [^self concretizeConditionalJump: 16r1].
  		[JumpCarry]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpNoCarry]			-> [^self concretizeConditionalJump: 16r3].
  		[JumpLess]				-> [^self concretizeConditionalJump: 16rC].
  		[JumpGreaterOrEqual]	-> [^self concretizeConditionalJump: 16rD].
  		[JumpGreater]			-> [^self concretizeConditionalJump: 16rF].
  		[JumpLessOrEqual]		-> [^self concretizeConditionalJump: 16rE].
  		[JumpBelow]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpAboveOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpAbove]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpBelowOrEqual]	-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPEqual]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpFPNotEqual]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpFPLess]				-> [^self concretizeConditionalJump: 16r2].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpFPGreater]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpFPLessOrEqual]		-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPOrdered]			-> [^self concretizeConditionalJump: 16rB].
  		[JumpFPUnordered]			-> [^self concretizeConditionalJump: 16rA].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeArithCqRWithRO: 0 raxOpcode: 15r05].
  		[AddCwR]					-> [^self concretizeArithCwR: 16r03].
  		[AddRR]						-> [^self concretizeAddRR].
  		[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58].
  		[AndCqR]					-> [^self concretizeArithCqRWithRO: 4 raxOpcode: 16r25].
  		[AndCwR]					-> [^self concretizeArithCwR: 16r23].
  		[AndRR]						-> [^self concretizeAndRR].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[CmpCqR]					-> [^self concretizeArithCqRWithRO: 7 raxOpcode: 16r3D].
  		[CmpCwR]					-> [^self concretizeArithCwR: 16r39].
  		[CmpRR]					-> [^self concretizeCmpRR].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
  		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59].
  		[OrCqR]						-> [^self concretizeArithCqRWithRO: 1 raxOpcode: 16r0D].
  		[OrCwR]					-> [^self concretizeArithCwR: 16r0B].
  		[OrRR]						-> [^self concretizeOrRR].
  		[SubCqR]					-> [^self concretizeArithCqRWithRO: 5 raxOpcode: 16r2D].
  		[SubCwR]					-> [^self concretizeArithCwR: 16r2B].
  		[SubRR]						-> [^self concretizeSubRR].
  		[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C].
  		[SqrtRd]					-> [^self concretizeSqrtRd].
  		[XorCwR]					-> [^self concretizeArithCwR: 16r33].
  		[XorRR]						-> [^self concretizeXorRR].
  		[NegateR]					-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeShiftCqRegOpcode: 7].
  		[LogicalShiftRightCqR]			-> [^self concretizeShiftCqRegOpcode: 5].
  		[LogicalShiftLeftCqR]			-> [^self concretizeShiftCqRegOpcode: 4].
  		[ArithmeticShiftRightRR]			-> [^self concretizeShiftRegRegOpcode: 7].
  		[LogicalShiftLeftRR]				-> [^self concretizeShiftRegRegOpcode: 4].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
+ 		[MoveC32R]			-> [^self concretizeMoveC32R].
  		[MoveRR]			-> [^self concretizeMoveRR].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeMoveRMbr].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd] }!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveC32R (in category 'as yet unclassified') -----
+ testMoveC32R
+ 	"self new testMoveMwrR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:reg :rname|
+ 		#(0 64 65536 -64 -65536) do:
+ 			[:offset| | inst len |
+ 			inst := self gen: MoveC32R operand: offset operand: reg.
+ 			len := inst concretizeAt: 0.
+ 			self processor
+ 				disassembleInstructionAt: 0
+ 				In: inst machineCode object
+ 				into: [:str :sz| | plainJane herIntended po |
+ 					plainJane := self strip: str.
+ 					po := offset bitAnd: 1 << self processor bitsInWord - 1.
+ 					herIntended := 'movq $0x', (po printStringBase: 16 length: 16 padded: true), ', ', rname.
+ 					self assert: (plainJane match: herIntended).
+ 					self assert: len = sz]]]!

Item was changed:
  ----- Method: CogX64CompilerTests>>testMoveRMbr (in category 'tests') -----
  testMoveRMbr
  	"self new testMoveRMbr"
+ 	self concreteCompilerClass byteRegistersWithNamesDo:
+ 		[:sreg :srname|
+ 		self concreteCompilerClass registersWithNamesDo:
+ 			[:dreg :drname|
+ 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 				[:offset| | inst len |
+ 				inst := self gen: MoveRMbr operand: sreg operand: offset operand: dreg.
+ 				len := inst concretizeAt: 0.
+ 				self processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended po |
+ 						plainJane := self strip: str.
+ 						po := offset bitAnd: 1 << self processor bitsInWord - 1.
+ 						herIntended := 'movb ', srname, (offset = 0 ifTrue: [', '] ifFalse: [', 0x', (po printStringBase: 16 length: 16 padded: true)]), '(', drname, ')'.
+ 						self assert: (plainJane match: herIntended).
+ 						self assert: len = sz]]]]!
- 	self concreteCompilerClass registersWithNamesDo:
- 		[:sreg :srname| | brname |
- 		sreg < 4 ifTrue:
- 			[brname := #('%al' '%cl' '%dl' '%bl') at: sreg + 1.
- 			self concreteCompilerClass registersWithNamesDo:
- 				[:dreg :drname|
- 				((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
- 					[:offset| | inst len |
- 					inst := self gen: MoveRMbr operand: sreg operand: offset operand: dreg.
- 					len := inst concretizeAt: 0.
- 					self processor
- 						disassembleInstructionAt: 0
- 						In: inst machineCode object
- 						into: [:str :sz| | plainJane herIntended po |
- 							plainJane := self strip: str.
- 							po := offset bitAnd: 1 << self processor bitsInWord - 1.
- 							herIntended := 'movb ', brname, (offset = 0 ifTrue: [', '] ifFalse: [', 0x', (po printStringBase: 16 length: 16 padded: true)]), '(', drname, ')'.
- 							self assert: (plainJane match: herIntended).
- 							self assert: len = sz]]]]]!

Item was changed:
  ----- Method: CogX64CompilerTests>>testMoveXbrRR (in category 'tests') -----
  testMoveXbrRR
  	"self new testMoveXbrRR"
  	self concreteCompilerClass registersWithNamesDo:
  		[:idxreg :irname|
+ 		irname ~= '%rsp' ifTrue:
+ 			[self concreteCompilerClass registersWithNamesDo:
+ 				[:basereg :brname|
+ 				self concreteCompilerClass registersWithNamesDo:
+ 					[:dreg :drname|
+ 					((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 						[:offset| | inst len |
+ 						inst := self gen: MoveXbrRR operand: idxreg operand: basereg operand: dreg.
+ 						len := inst concretizeAt: 0.
+ 						self processor
+ 							disassembleInstructionAt: 0
+ 							In: inst machineCode object
+ 							into: [:str :sz| | plainJane herIntended |
+ 								"Convert e.g. '00000000: movzbq %ds:(%rax,%rax,1), %rax : 48 0F B6 04 00 ' to  'movzbq (%rax,%rax,1), %rax'"
+ 								plainJane := self strip: str.
+ 								herIntended := 'movzbq (', brname, ',', irname, ',1), ',drname.
+ 								self assert: (plainJane match: herIntended).
+ 								self assert: len = sz]]]]]]!
- 			irname ~= '%esp' ifTrue:
- 				[self concreteCompilerClass registersWithNamesDo:
- 					[:basereg :brname|
- 					self concreteCompilerClass registersWithNamesDo:
- 						[:dreg :drname|
- 						((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
- 							[:offset| | inst len |
- 							inst := self gen: MoveXbrRR operand: idxreg operand: basereg operand: dreg.
- 							len := inst concretizeAt: 0.
- 							self processor
- 								disassembleInstructionAt: 0
- 								In: inst machineCode object
- 								into: [:str :sz| | plainJane herIntended |
- 									"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
- 									plainJane := self strip: str.
- 									herIntended := 'movzbl (', brname, ',', irname, ',1), ',drname.
- 									self assert: (plainJane match: herIntended).
- 									self assert: len = sz]]]]]]!

Item was changed:
  CogClass subclass: #Cogit
  	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd literalsManager callerSavedRegMask postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB numIRCs indexOfIRC theIRCs implicitReceiverSendTrampolines nsSendCacheSurrogateClass tempOop'
+ 	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass'
- 	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumTrampolines ProcessorClass'
  	poolDictionaries: 'CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMBytecodeConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 4/6/2015 15:56' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
  
  	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
  
  I have concrete subclasses that implement different levels of optimization:
  	SimpleStackBasedCogit is the simplest code generator.
  
  	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  	to the stack until necessary and implements a register-based calling convention for low-arity sends.
  
  	StackToRegisterMappingCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
  cFramePointer cStackPointer <Integer>
  	the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixup shas one element per byte in methodObj's bytecode
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventually the total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

Item was changed:
  ----- Method: Cogit class>>initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid (in category 'class initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid
  	"SimpleStackBasedCogit initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid"
  	"StackToRegisterMappingCogit initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid"
  
  	| v3Table v4Table |
  	"N.B. Must do it backwards to evaluate AltBlockCreationBytecodeSize & BlockCreationBytecodeSize et al correctly."
  	self initializeBytecodeTableForNewspeakV4.
  	v4Table := generatorTable.
  	AltBlockCreationBytecodeSize := BlockCreationBytecodeSize.
  	AltNSSendIsPCAnnotated := NSSendIsPCAnnotated.
  	AltFirstSpecialSelector := FirstSpecialSelector.
+ 	AltNumSpecialSelectors := NumSpecialSelectors.
  	self initializeBytecodeTableForSqueakV3PlusClosures.
  	v3Table := generatorTable.
  	generatorTable := CArrayAccessor on: v3Table object, v4Table object!

Item was changed:
  ----- Method: Cogit class>>initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid (in category 'class initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid
  	"SimpleStackBasedCogit initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid"
  	"StackToRegisterMappingCogit initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid"
  
  	| v3Table v1Table |
  	"N.B. Must do it backwards to evaluate AltBlockCreationBytecodeSize & BlockCreationBytecodeSize et al correctly."
  	self initializeBytecodeTableForSistaV1.
  	v1Table := generatorTable.
  	AltBlockCreationBytecodeSize := BlockCreationBytecodeSize.
  	AltFirstSpecialSelector := FirstSpecialSelector.
+ 	AltNumSpecialSelectors := NumSpecialSelectors.
  	self initializeBytecodeTableForSqueakV3PlusClosures.
  	v3Table := generatorTable.
  	generatorTable := CArrayAccessor on: v3Table object, v1Table object!

Item was changed:
  ----- Method: Cogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
  	Debug := initializationOptions at: #Debug ifAbsent: [false].
  	(initializationOptions includesKey: #EagerInstructionDecoration)
  		ifTrue:
  			[EagerInstructionDecoration := initializationOptions at: #EagerInstructionDecoration]
  		ifFalse:
  			[EagerInstructionDecoration ifNil:
  				[EagerInstructionDecoration := false]]. "speeds up single stepping but could lose fidelity"
  
  	ProcessorClass := (initializationOptions at: #ISA ifAbsentPut: [#IA32]) caseOf: {
  							[#X64] 		->	[BochsX64Alien].
  							[#IA32] 	->	[BochsIA32Alien].
  							[#ARMv5]	->	[GdbARMAlien]. }.
  	CogCompilerClass := self activeCompilerClass.
+ 	(CogCompilerClass withAllSuperclasses copyUpTo: CogAbstractInstruction) do:
+ 		[:compilerClass| compilerClass initialize].
  	"Our criterion for which methods to JIT is literal count.  The default value is 60 literals or less."
  	MaxLiteralCountForCompile := initializationOptions at: #MaxLiteralCountForCompile ifAbsent: [60].
  	"we special-case 0, 1 & 2 argument sends, N is numArgs >= 3"
  	NumSendTrampolines := 4.
  	"Currently not even the ceImplicitReceiverTrampoline contains object references."
  	NumObjRefsInRuntime := 0.
  
  	NSCSelectorIndex := (NSSendCache instVarNames indexOf: #selector) - 1.
  	NSCNumArgsIndex := (NSSendCache instVarNames indexOf: #numArgs) - 1.
  	NSCClassTagIndex := (NSSendCache instVarNames indexOf: #classTag) - 1.
  	NSCEnclosingObjectIndex := (NSSendCache instVarNames indexOf: #enclosingObject) - 1.
  	NSCTargetIndex := (NSSendCache instVarNames indexOf: #target) - 1.
  	NumOopsPerNSC := NSSendCache instVarNames size.
  
  	"Max size to alloca when compiling.
  	 Mac OS X 10.6.8 segfaults approaching 8Mb.
  	 Linux 2.6.9 segfaults above 11Mb.
  	 WIndows XP segfaults approaching 2Mb."
  	MaxStackAllocSize := 1024 * 1024 * 3 / 2 !

Item was added:
+ ----- Method: Cogit>>CmpC32:R: (in category 'abstract instructions') -----
+ CmpC32: wordConstant R: reg
+ 	"Generate a CmpC32R instruction to compare a 32-bit constant with a
+ 	 register.  If this is a 32-bit platform, simply generate a CmpCwR instruction,
+ 	 to avoid needless duplication in the 32-bit code generators.."
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^self
+ 		gen: (objectMemory wordSize = 8
+ 				ifTrue: [CmpC32R]
+ 				ifFalse: [CmpCwR])
+ 		literal: wordConstant
+ 		operand: reg!

Item was added:
+ ----- Method: Cogit>>MoveC32:R: (in category 'abstract instructions') -----
+ MoveC32: wordConstant R: reg
+ 	"Generate a MoveC32R instruction to move a 32-bit constant into a register.
+ 	 If this is a 32-bit platform, simply generate a MoveCwR instruction, to avoid
+ 	 needless duplication in the 32-bit code generators.."
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^self
+ 		gen: (objectMemory wordSize = 8
+ 				ifTrue: [MoveC32R]
+ 				ifFalse: [MoveCwR])
+ 		literal: wordConstant
+ 		operand: reg!

Item was added:
+ ----- Method: Cogit>>MoveUniqueC32:R: (in category 'abstract instructions') -----
+ MoveUniqueC32: wordConstant R: reg
+ 	"Generate a MoveC32R instruction to move a 32-bit constant into a register.
+ 	 If the backEnd is using out-of-line literals then those for inline caches cannot be shared,
+ 	 and this method ensures the instruction has its own unique label.  If the backEnd is using
+ 	 in-line literals then the literal is unique anyway and this is equivalent to MoveC32:R:.
+ 	 If this is a 32-bit platform, simply generate a MoveCwR instruction, to avoid
+ 	 needless duplication in the 32-bit code generators.."
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^self
+ 		gen: (objectMemory wordSize = 8
+ 				ifTrue: [MoveC32R]
+ 				ifFalse: [MoveCwR])
+ 		uniqueLiteral: wordConstant
+ 		operand: reg!

Item was added:
+ ----- Method: Cogit>>genLoadInlineCache: (in category 'in-line cacheing') -----
+ genLoadInlineCache: selectorIndex
+ 	"The in-line cache for a send is implemented as a constant load into ClassReg.
+ 	 We always use a 32-bit load, even in 64-bits.
+ 
+ 	 In the initial (unlinked) state the in-line cache is notionally loaded with the selector.
+ 	 But since in 64-bits an arbitrary selector oop won't fit in a 32-bit constant load, we
+ 	 instead load the cache with the selector's index, either into the literal frame of the
+ 	 current method, or into the special selector array.  Negative values are 1-relative
+ 	 indices into the special selector array.
+ 
+ 	 When a send is linked, the load of the selector, or selector index, is overwritten with a
+ 	 load of the receiver's class, or class tag.  Hence, the 64-bit VM is currently constrained
+ 	 to use class indices as cache tags.  If out-of-line literals are used, distinct caches /must
+ 	 not/ share acche locations, for if they do, send cacheing will be confused by the sharing.
+ 	 Hence we use the MoveUniqueC32:R: instruction that will not share literal locations."
+ 
+ 	| cacheValue |
+ 	self assert: (selectorIndex < 0
+ 					ifTrue: [selectorIndex negated between: 1 and: self numSpecialSelectors]
+ 					ifFalse: [selectorIndex between: 0 and: (objectMemory literalCountOf: methodObj) - 1]).
+ 
+ 	objectMemory wordSize = 8
+ 		ifTrue:
+ 			[cacheValue := selectorIndex]
+ 		ifFalse:
+ 			[| selector |
+ 			 selector := selectorIndex < 0
+ 							ifTrue: [(coInterpreter specialSelector: -1 - selectorIndex)]
+ 							ifFalse: [self getLiteral: selectorIndex].
+ 			 self assert: (objectMemory addressCouldBeOop: selector).
+ 			 (objectMemory isYoung: selector) ifTrue:
+ 				[hasYoungReferent := true].
+ 			 cacheValue := selector].
+ 
+ 	self MoveUniqueC32: cacheValue R: ClassReg!

Item was changed:
  ----- Method: Cogit>>printMapEntry:mcpc:args: (in category 'disassembly') -----
  printMapEntry: annotation mcpc: mcpc args: tupleOfStreamCodeRangesAndMethod
  	"Print the Map entry's mcpc, its annotation and the corresponding bytecode pc, if any."
  	<doNotGenerate>
  	[:aStream :codeRanges :cogMethod|
  	self startMcpcAndCogMethodForMcpc: mcpc in: cogMethod do:
  		[:startmcpc :subMethod| | name codeRange |
  		"Find the start of the block by searching the code ranges."
  		codeRange := codeRanges detect: [:range| range includes: mcpc].
  		codeRange first = mcpc ifTrue:
  			[aStream nextPutAll: 'startpc: '; print: codeRange startpc; cr].
  		aStream
  			next: 2 put: Character space;
  			nextPutAll: mcpc hex;  space;
  			nextPutAll: (name := self class annotationConstantNames at: annotation + 1);
  			next: 20 - name size put: Character space;
  			nextPut: $(;
  			nextPutAll: (self findMapLocationForMcpc: mcpc inMethod: cogMethod) hex.
  		(self isPCMappedAnnotation: annotation) ifTrue:
  			[aStream
  				nextPutAll: ', bc: ';
  				print: (self bytecodePCFor: mcpc startBcpc: codeRange startpc in: subMethod)].
  		(self isSendAnnotation: annotation) ifTrue:
  			[| sel |
+ 			sel := self selectorForSendAt: mcpc annotation: annotation in: cogMethod methodObject.
- 			sel := self selectorForSendAt: mcpc annotation: annotation.
  			sel isInteger ifTrue:
  				[sel := self lookupAddress: sel].
  			sel isString ifTrue:
  				[aStream space; nextPutAll: sel]].
  		aStream
  			nextPut: $);
  			cr; flush]]
  		valueWithArguments: tupleOfStreamCodeRangesAndMethod.
  	^0!

Item was removed:
- ----- Method: Cogit>>selectorForSendAt:annotation: (in category 'simulation only') -----
- selectorForSendAt: mcpc annotation: annotation
- 	<doNotGenerate>
- 	| entryPoint offset targetMethod selector |
- 	entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
- 	selector := entryPoint > methodZoneBase
- 					ifTrue: "It's a linked send."
- 						[self
- 							offsetAndSendTableFor: entryPoint
- 							annotation: annotation
- 							into: [:off :table| offset := off].
- 						targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
- 						targetMethod selector]
- 					ifFalse:
- 						[backEnd inlineCacheTagAt: mcpc].
- 	^(annotation ~= IsNSSendCall and: [coInterpreter isCurrentImageFacade])
- 		ifTrue: [coInterpreter objectForOop: selector]
- 		ifFalse: [selector]!

Item was added:
+ ----- Method: Cogit>>selectorForSendAt:annotation:in: (in category 'simulation only') -----
+ selectorForSendAt: mcpc annotation: annotation in: aCompiledMethod
+ 	<doNotGenerate>
+ 	| entryPoint offset targetMethod selector |
+ 	entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
+ 	selector := entryPoint > methodZoneBase
+ 					ifTrue: "It's a linked send."
+ 						[self
+ 							offsetAndSendTableFor: entryPoint
+ 							annotation: annotation
+ 							into: [:off :table| offset := off].
+ 						targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
+ 						targetMethod selector]
+ 					ifFalse:
+ 						[objectMemory wordSize = 8
+ 							ifTrue: [self selectorFromSelectorIndex: (backEnd inlineCacheTagAt: mcpc) signedIntToLong
+ 										in: aCompiledMethod]
+ 							ifFalse: [backEnd inlineCacheTagAt: mcpc]].
+ 	^(annotation ~= IsNSSendCall and: [coInterpreter isCurrentImageFacade])
+ 		ifTrue: [coInterpreter objectForOop: selector]
+ 		ifFalse: [selector]!

Item was added:
+ ----- Method: Cogit>>selectorFromSelectorIndex:in: (in category 'in-line cacheing') -----
+ selectorFromSelectorIndex: selectorIndex in: aCompiledMethod
+ 	<inline: true>
+ 	^selectorIndex < 0
+ 		ifTrue: [(coInterpreter specialSelector: -1 - selectorIndex)]
+ 		ifFalse: [coInterpreter literal: selectorIndex ofMethod: aCompiledMethod]!

Item was changed:
  ----- Method: Cogit>>testMcToBcPcMappingForCompiledMethod:cogMethod: (in category 'tests-method map') -----
  testMcToBcPcMappingForCompiledMethod: aCompiledMethod cogMethod: cogMethod
  	<doNotGenerate>
  	| bcMethod subMethods prevMcpc |
  	"self disassembleMethod: cogMethod"
  	"coInterpreter symbolicMethod: cogMethod methodObject"
  	"coInterpreter printOop: cogMethod methodObject"
  	"self printPCMapPairsFor: cogMethod on: Transcript"
  	cogMethod stackCheckOffset = 0 ifTrue: "frameless"
  		[^self].
  	bcMethod := coInterpreter isCurrentImageFacade
  					ifTrue: [coInterpreter objectForOop: cogMethod methodObject]
  					ifFalse: [VMCompiledMethodProxy new
  								for: cogMethod methodObject
  								coInterpreter: coInterpreter
  								objectMemory: objectMemory].
  	subMethods := self subMethodsAsRangesFor: cogMethod.
  	self mapFor: cogMethod do:
  		[:annotation :mcpc| | subMethod subCogMethod bcpc mappedpc |
  		(self isPCMappedAnnotation: annotation) ifTrue:
  			[subMethod := subMethods
  								detect: [:range| range includes: mcpc]
  								ifNone: ["a trailing call ceNonLocalReturnTrampoline's following
  										 pc is the start of a following block or the end of the map"
  										subMethods detect: [:range| range includes: mcpc - 1]].
  			mcpc > subMethod first ifTrue:
  				[bcpc := self
  							bytecodePCFor: mcpc
  							startBcpc: subMethod startpc
  							in: (subCogMethod := subMethod cogMethod).
  				self assert: bcpc ~= 0.
  				mappedpc := self mcPCFor: bcpc startBcpc: subMethod startpc in: subCogMethod.
  				subCogMethod stackCheckOffset = 0
  					ifTrue: [self assert: mappedpc > (subCogMethod address + self noCheckEntryOffset)]
  					ifFalse: [self assert: mappedpc >= (subCogMethod address + subCogMethod stackCheckOffset)].
  				"mcpc = mappedpc is obviously what we want and expect.  prevMcpc = mappedpc hacks
  				 around frame building accessors where the first bytecode is mapped twice, once for the
  				 stack check and once for the context inst var access.  The bytecode pc can only map
  				 back to a single mcpc, the first, so the second map entry will fail without this hack."
  				self assert: (mcpc = mappedpc or: [prevMcpc = mappedpc]).
  				(self isSendAnnotation: annotation) ifTrue:
  					[| mcSelector bcSelector |
+ 					mcSelector := self selectorForSendAt: mcpc annotation: annotation in: aCompiledMethod.
- 					mcSelector := self selectorForSendAt: mcpc annotation: annotation.
  					"sends map to the following pc.  need to find the selector for the previous pc"
  					bcSelector := self selectorForSendBefore: bcpc in: bcMethod.
  					self assert: mcSelector = bcSelector]].
  			 prevMcpc := mcpc].
  		 false "keep scanning"]!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForNewspeakV4 (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"SimpleStackBasedCogit initializeBytecodeTableForNewspeakV4"
  
  	NSSendIsPCAnnotated := false. "IsNSSendCall used by SendAbsentImplicit"
  	FirstSpecialSelector := 80.
+ 	NumSpecialSelectors := 32.
  	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  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 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 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 233 233 genExtStoreLiteralVariableBytecode)
  		(2 234 234 genLongStoreTemporaryVariableBytecode)
  		(2 235 235 genExtStoreAndPopReceiverVariableBytecode isInstVarRef)
  		(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 hasIRC)
  
  		(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 hasIRC)
  
  		(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.
+ 	NumSpecialSelectors := 32.
  	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  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 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 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 241 241 genExtStoreAndPopLiteralVariableBytecode)
  		(2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
  		(2 243 243 genExtStoreReceiverVariableBytecode isInstVarRef)
  		(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.
+ 	NumSpecialSelectors := 32.
  	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  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 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 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isInstVarRef isMapped) "well, maybe inst var ref"
  		(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 changed:
  ----- Method: SimpleStackBasedCogit>>doubleExtendedDoAnythingBytecode (in category 'bytecode generators') -----
  doubleExtendedDoAnythingBytecode
  	"Replaces the Blue Book double-extended send [132], in which the first byte was wasted on 8 bits of argument count. 
  	Here we use 3 bits for the operation sub-type (opType),  and the remaining 5 bits for argument count where needed. 
  	The last byte give access to 256 instVars or literals. 
  	See also secondExtendedSendBytecode"
  	| opType |
  	opType := byte1 >> 5.
  	opType = 0 ifTrue:
+ 		[^self genSend: byte2 numArgs: (byte1 bitAnd: 31)].
- 		[^self genSend: (self getLiteral: byte2) numArgs: (byte1 bitAnd: 31)].
  	opType = 1 ifTrue:
+ 		[^self genSendSuper: byte2 numArgs: (byte1 bitAnd: 31)].
- 		[^self genSendSuper: (self getLiteral: byte2) numArgs: (byte1 bitAnd: 31)].
  	"We need a map entry for this bytecode for correct parsing.
  	 The sends will get an IsSend entry anyway.  The other cases need a
  	 fake one.  We could of course special case the scanning but that's silly."
  	opType caseOf: {
  			[2]	->	[(coInterpreter isReadMediatedContextInstVarIndex: byte2)
  						ifTrue: [self genPushMaybeContextReceiverVariable: byte2]
  						ifFalse: [self genPushReceiverVariable: byte2]].
  			[3]	->	[self genPushLiteralIndex: byte2].
  			[4]	->	[self genPushLiteralVariable: byte2].
  			[7]	->	[self genStorePop: false LiteralVariable: byte2] }
  		otherwise: "5 & 6"
  			[(coInterpreter isWriteMediatedContextInstVarIndex: byte2)
  				ifTrue: [self genStorePop: opType = 6 MaybeContextReceiverVariable: byte2]
  				ifFalse: [self genStorePop: opType = 6 ReceiverVariable: byte2]].
  	"We need a map entry for this bytecode for correct parsing (if the method builds a frame).
  	 We could of course special case the scanning but that's silly."
  	needsFrame ifTrue:
  		[self annotateBytecode: self Label].
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtSendAbsentDynamicSuperBytecode (in category 'bytecode generators') -----
  genExtSendAbsentDynamicSuperBytecode
  	"241		11110001	i i i i i j j j	Send To Absent Dynamic Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	| litIndex nArgs |
  	litIndex := (byte1 >> 3) + (extA << 5).
  	extA := 0.
  	nArgs := (byte1 bitAnd: 7) + (extB << 3).
  	extB := 0.
+ 	^self genSendAbsentDynamicSuper: litIndex numArgs: nArgs!
- 	^self genSendAbsentDynamicSuper: (self getLiteral: litIndex) numArgs: nArgs!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtSendAbsentImplicitBytecode (in category 'bytecode generators') -----
  genExtSendAbsentImplicitBytecode
  	"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"
  	| litIndex nArgs |
  	litIndex := (byte1 >> 3) + (extA << 5).
  	extA := 0.
  	nArgs := (byte1 bitAnd: 7) + (extB << 3).
  	extB := 0.
+ 	^self genSendAbsentImplicit: litIndex numArgs: nArgs!
- 	^self genSendAbsentImplicit: (self getLiteral: litIndex) numArgs: nArgs!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtSendAbsentOuterBytecode (in category 'bytecode generators') -----
  genExtSendAbsentOuterBytecode
  	"254		 11111110	i i i i i j j j kkkkkkkk	Send To Absent Outer Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments at Depth kkkkkkkk "
  	| litIndex nArgs depth |
  	litIndex := (byte1 >> 3) + (extA << 5).
  	extA := 0.
  	nArgs := (byte1 bitAnd: 7) + (extB << 3).
  	extB := 0.
  	depth := byte2.
+ 	^self genSendAbsentOuter: litIndex numArgs: nArgs depth: depth
- 	^self genSendAbsentOuter: (self getLiteral: litIndex) numArgs: nArgs depth: depth
  !

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtSendAbsentSelfBytecode (in category 'bytecode generators') -----
  genExtSendAbsentSelfBytecode
  	"245		11110101	i i i i i j j j	Send To Absent Self Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	| litIndex nArgs |
  	litIndex := (byte1 >> 3) + (extA << 5).
  	extA := 0.
  	nArgs := (byte1 bitAnd: 7) + (extB << 3).
  	extB := 0.
+ 	^self genSendAbsentSelf: litIndex numArgs: nArgs!
- 	^self genSendAbsentSelf: (self getLiteral: litIndex) numArgs: nArgs!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtSendBytecode (in category 'bytecode generators') -----
  genExtSendBytecode
  	"238		11101110	i i i i i j j j	Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	| litIndex nArgs |
  	litIndex := (byte1 >> 3) + (extA << 5).
  	extA := 0.
  	nArgs := (byte1 bitAnd: 7) + (extB << 3).
  	extB := 0.
+ 	^self genSend: litIndex numArgs: nArgs!
- 	^self genSend: (self getLiteral: litIndex) numArgs: nArgs!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtSendSuperBytecode (in category 'bytecode generators') -----
  genExtSendSuperBytecode
  	"239		11101111	i i i i i j j j	Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	| isDirected litIndex nArgs |
  	(isDirected := extB >= 64) ifTrue:
  		[extB := extB bitAnd: 63].
  	litIndex := (byte1 >> 3) + (extA << 5).
  	extA := 0.
  	nArgs := (byte1 bitAnd: 7) + (extB << 3).
  	extB := 0.
  	^isDirected
+ 		ifTrue: [self genSendDirectedSuper: litIndex numArgs: nArgs]
+ 		ifFalse: [self genSendSuper: litIndex numArgs: nArgs]!
- 		ifTrue: [self genSendDirectedSuper: (self getLiteral: litIndex) numArgs: nArgs]
- 		ifFalse: [self genSendSuper: (self getLiteral: litIndex) numArgs: nArgs]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtendedSendBytecode (in category 'bytecode generators') -----
  genExtendedSendBytecode
  	"Can use any of the first 32 literals for the selector and pass up to 7 arguments."
  
+ 	^self genSend: (byte1 bitAnd: 16r1F) numArgs: byte1 >> 5!
- 	^self genSend: (self getLiteral: (byte1 bitAnd: 16r1F)) numArgs: byte1 >> 5!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtendedSuperBytecode (in category 'bytecode generators') -----
  genExtendedSuperBytecode
+ 	^self genSendSuper: (byte1 bitAnd: 16r1F) numArgs: byte1 >> 5!
- 	^self genSendSuper: (self getLiteral: (byte1 bitAnd: 16r1F)) numArgs: byte1 >> 5!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genNSSend:numArgs:depth:sendTable: (in category 'bytecode generators') -----
+ genNSSend: selectorIndex numArgs: numArgs depth: depth sendTable: sendTable
- genNSSend: selector numArgs: numArgs depth: depth sendTable: sendTable
  	<var: #sendTable type: #'sqInt *'>
+ 	| selector nsSendCache |
+ 	self assert: (selectorIndex between: 0 and: (objectMemory literalCountOf: methodObj) - 1).
+ 	selector := self getLiteral: selectorIndex.
+ 	self assert: (objectMemory addressCouldBeOop: selector).	
- 	| nsSendCache |
  	(objectMemory isYoung: selector) ifTrue:
  		[hasYoungReferent := true].
  
  	nsSendCache := theIRCs + (NumOopsPerNSC * objectMemory bytesPerOop * indexOfIRC).
  	indexOfIRC := indexOfIRC + 1.
  	self assert: (objectMemory isInOldSpace: nsSendCache).
  	self initializeNSSendCache: nsSendCache selector: selector numArgs: numArgs depth: depth.
  
  	"This leaves the method receiver on the stack, which might not be the implicit receiver.
  	 But the lookup trampoline will establish the on-stack receiver once it locates it."
  	self marshallAbsentReceiverSendArguments: numArgs.
  
  	"Load the cache last so it is a fixed distance from the call."
  	self MoveUniqueCw: nsSendCache R: SendNumArgsReg.
  	self CallNewspeakSend: (sendTable at: (numArgs min: NumSendTrampolines - 1)).
  
  	self PushR: ReceiverResultReg.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSecondExtendedSendBytecode (in category 'bytecode generators') -----
  genSecondExtendedSendBytecode
  	"Can use any of the first 64 literals for the selector and pass up to 3 arguments."
  
+ 	^self genSend: (byte1 bitAnd: 16r3F) numArgs: byte1 >> 6!
- 	^self genSend: (self getLiteral: (byte1 bitAnd: 16r3F)) numArgs: byte1 >> 6!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSend:numArgs: (in category 'bytecode generator support') -----
+ genSend: selectorIndex numArgs: numArgs
- genSend: selector numArgs: numArgs
  	<inline: true>
+ 	^self genSend: selectorIndex numArgs: numArgs sendTable: ordinarySendTrampolines!
- 	^self genSend: selector numArgs: numArgs sendTable: ordinarySendTrampolines!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSend:numArgs:sendTable: (in category 'bytecode generator support') -----
+ genSend: selectorIndex numArgs: numArgs sendTable: sendTable
- genSend: selector numArgs: numArgs sendTable: sendTable
  	<inline: false>
  	<var: #sendTable type: #'sqInt *'>
  	| annotation |
- 	(objectMemory isYoung: selector) ifTrue:
- 		[hasYoungReferent := true].
  	self assert: needsFrame.
  	annotation := self annotationForSendTable: sendTable.
  	self assert: (numArgs between: 0 and: 255). "say"
- 	self assert: (objectMemory addressCouldBeOop: selector).
  	self MoveMw: numArgs * objectMemory wordSize r: SPReg R: ReceiverResultReg.
  	"Deal with stale super sends; see SpurMemoryManager's class comment."
  	(self annotationIsForUncheckedEntryPoint: annotation) ifTrue:
  		[objectRepresentation genEnsureOopInRegNotForwarded: ReceiverResultReg scratchReg: TempReg].
  	"0 through (NumSendTrampolines - 2) numArgs sends have the arg count implciti in the trampoline.
  	 The last send trampoline (NumSendTrampolines - 1) passes numArgs in SendNumArgsReg."
  	numArgs >= (NumSendTrampolines - 1) ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
  	(BytecodeSetHasDirectedSuperSend
  	 and: [annotation = IsDirectedSuperSend]) ifTrue:
  		[self genMoveConstant: tempOop R: TempReg].
+ 	self genLoadInlineCache: selectorIndex.
- 	self MoveUniqueCw: selector R: ClassReg.
  	(self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1))) annotation: annotation.
  	self PushR: ReceiverResultReg.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentDynamicSuper:numArgs: (in category 'bytecode generators') -----
+ genSendAbsentDynamicSuper: selectorIndex numArgs: numArgs
- genSendAbsentDynamicSuper: selector numArgs: numArgs
  	<inline: false>
  	^self
+ 		genNSSend: selectorIndex
- 		genNSSend: selector
  		numArgs: numArgs
  		depth: LookupRuleDynamicSuper
  		sendTable: dynamicSuperSendTrampolines!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentImplicit0ArgsBytecode (in category 'bytecode generators') -----
  genSendAbsentImplicit0ArgsBytecode
  	"160-175	1010 i i i i		Send To Absent Implicit Receiver Literal Selector #iiii With 0 Arguments."
+ 	^self genSendAbsentImplicit: (byte0 bitAnd: 15) numArgs: 0!
- 	^self genSendAbsentImplicit: (self getLiteral: (byte0 bitAnd: 15)) numArgs: 0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentImplicit:numArgs: (in category 'bytecode generators') -----
+ genSendAbsentImplicit: selectorIndex numArgs: numArgs
- genSendAbsentImplicit: selector numArgs: numArgs
  	<inline: false>
  	^self
+ 		genNSSend: selectorIndex
- 		genNSSend: selector
  		numArgs: numArgs
  		depth: LookupRuleImplicit
  		sendTable: implicitReceiverSendTrampolines!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentOuter:numArgs:depth: (in category 'bytecode generators') -----
+ genSendAbsentOuter: selectorIndex numArgs: numArgs depth: depth
- genSendAbsentOuter: selector numArgs: numArgs depth: depth
  	<inline: false>
  	^self
+ 		genNSSend: selectorIndex
- 		genNSSend: selector
  		numArgs: numArgs
  		depth: depth
  		sendTable: outerSendTrampolines!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentSelf:numArgs: (in category 'bytecode generators') -----
+ genSendAbsentSelf: selectorIndex numArgs: numArgs
- genSendAbsentSelf: selector numArgs: numArgs
  	<inline: false>
  	^self
+ 		genNSSend: selectorIndex
- 		genNSSend: selector
  		numArgs: numArgs
  		depth: LookupRuleSelf
  		sendTable: selfSendTrampolines!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendLiteralSelector0ArgsBytecode (in category 'bytecode generators') -----
  genSendLiteralSelector0ArgsBytecode
+ 	^self genSend: (byte0 bitAnd: 15) numArgs: 0!
- 	^self genSend: (self getLiteral: (byte0 bitAnd: 15)) numArgs: 0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendLiteralSelector1ArgBytecode (in category 'bytecode generators') -----
  genSendLiteralSelector1ArgBytecode
+ 	^self genSend: (byte0 bitAnd: 15) numArgs: 1!
- 	^self genSend: (self getLiteral: (byte0 bitAnd: 15)) numArgs: 1!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendLiteralSelector2ArgsBytecode (in category 'bytecode generators') -----
  genSendLiteralSelector2ArgsBytecode
+ 	^self genSend: (byte0 bitAnd: 15) numArgs: 2!
- 	^self genSend: (self getLiteral: (byte0 bitAnd: 15)) numArgs: 2!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSpecialSelectorSend (in category 'bytecode generators') -----
  genSpecialSelectorSend
+ 	| index numArgs |
- 	| index selector numArgs |
  	index := byte0 - self firstSpecialSelectorBytecodeOffset.
- 	selector := coInterpreter specialSelector: index.
  	numArgs := coInterpreter specialSelectorNumArgs: index.
+ 	^self genSend: index negated - 1 numArgs: numArgs!
- 	^self genSend: selector numArgs: numArgs!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genV4SpecialSelectorSend (in category 'bytecode generators') -----
- genV4SpecialSelectorSend
- 	| index selector numArgs |
- 	index := byte0 - 80.
- 	selector := coInterpreter specialSelector: index.
- 	numArgs := coInterpreter specialSelectorNumArgs: index.
- 	^self genSend: selector numArgs: numArgs!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>numSpecialSelectors (in category 'bytecode generator support') -----
+ numSpecialSelectors
+ 	<inline: true>
+ 	^self cppIf: MULTIPLEBYTECODESETS
+ 		ifTrue: [bytecodeSetOffset = 256 ifTrue: [AltNumSpecialSelectors] ifFalse: [NumSpecialSelectors]]
+ 		ifFalse: [NumSpecialSelectors]!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  	"Override to count inlined branches if followed by a conditional branch.
  	 We borrow the following conditional branch's counter and when about to
  	 inline the comparison we decrement the counter (without writing it back)
  	 and if it trips simply abort the inlining, falling back to the normal send which
  	 will then continue to the conditional branch which will trip and enter the abort."
  	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor
  	  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB annotateInst
+ 	  counterAddress countTripped counterReg index |
- 	  counterAddress countTripped counterReg |
  	<var: #countTripped type: #'AbstractInstruction *'>
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  
  	(coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ self genSpecialSelectorComparisonWithoutCounters ].
  
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := self ssTop type = SSConstant
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (self ssValue: 1) type = SSConstant
  				 and: [objectMemory isIntegerObject: (self ssValue: 1) constant].
  
  	"short-cut the jump if operands are SmallInteger constants."
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[^ self genStaticallyResolvedSpecialSelectorComparison].
  
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  	
  	"Only interested in inlining if followed by a conditional branch."
  	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  		[inlineCAB := argIsInt or: [rcvrIsInt]].
  	inlineCAB ifFalse:
  		[^self genSpecialSelectorSend].
  
  	argIsInt
  		ifTrue:
  			[(self ssValue: 1) popToReg: ReceiverResultReg.
  			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg.
  			 rcvrIsInt ifFalse:
  				[objectRepresentation isSmallIntegerTagNonZero
  					ifTrue: [self AndR: ReceiverResultReg R: TempReg]
  					ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
  	jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  
  	counterReg := self allocateRegNotConflictingWith: (self registerMaskFor: ReceiverResultReg and: Arg0Reg).
  	self 
  		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
  			counterAddress := cAddress. 
  			countTripped := countTripBranch ] 
  		counterReg: counterReg.
  
  	argIsInt
  		ifTrue: [annotateInst
  					ifTrue: [self annotateBytecode: (self CmpCq: argInt R: ReceiverResultReg)]
  					ifFalse: [self CmpCq: argInt R: ReceiverResultReg]]
  		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
  	self gen: (branchDescriptor isBranchTrue
  				ifTrue: [primDescriptor opcode]
  				ifFalse: [self inverseBranchFor: primDescriptor opcode])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  		
  	self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress.
  	
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	countTripped jmpTarget: (jumpNotSmallInts jmpTarget: self Label).
  	
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
+ 	index := byte0 - self firstSpecialSelectorBytecodeOffset.
+ 	^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines!
- 	^self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
- 		numArgs: 1
- 		sendTable: ordinarySendTrampolines!

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.
+ 	NumSpecialSelectors := 32.
  	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  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 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 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 233 233 genExtStoreLiteralVariableBytecode)
  		(2 234 234 genLongStoreTemporaryVariableBytecode)
  		(2 235 235 genExtStoreAndPopReceiverVariableBytecode isInstVarRef)
  		(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 hasIRC)
  
  		(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 hasIRC)
  
  		(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.
+ 	NumSpecialSelectors := 32.
  	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  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   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 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 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 241 241 genExtStoreAndPopLiteralVariableBytecode)
  		(2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
  		(2 243 243 genExtStoreReceiverVariableBytecode isInstVarRef)
  		(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 branch v4:Long:BranchIfNotInstanceOf:Distance:)
  		
  		(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.
+ 	NumSpecialSelectors := 32.
  	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  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 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 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped) "well, maybe inst var ref"
  		(2 133 133 genExtendedSuperBytecode isInstVarRef 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 changed:
  ----- Method: StackToRegisterMappingCogit>>doubleExtendedDoAnythingBytecode (in category 'bytecode generators') -----
  doubleExtendedDoAnythingBytecode
  	"Replaces the Blue Book double-extended send [132], in which the first byte was wasted on 8 bits of argument count. 
  	Here we use 3 bits for the operation sub-type (opType),  and the remaining 5 bits for argument count where needed. 
  	The last byte give access to 256 instVars or literals. 
  	See also secondExtendedSendBytecode"
  	| opType |
  	opType := byte1 >> 5.
  	opType = 0 ifTrue:
+ 		[^self genSend: byte2 numArgs: (byte1 bitAnd: 31)].
- 		[^self genSend: (self getLiteral: byte2) numArgs: (byte1 bitAnd: 31)].
  	opType = 1 ifTrue:
+ 		[^self genSendSuper: byte2 numArgs: (byte1 bitAnd: 31)].
- 		[^self genSendSuper: (self getLiteral: byte2) numArgs: (byte1 bitAnd: 31)].
  	"We need a map entry for this bytecode for correct parsing.
  	 The sends will get an IsSend entry anyway.  The other cases need a
  	 fake one.  We could of course special case the scanning but that's silly."
  	opType caseOf: {
  			[2]	->	[(coInterpreter isReadMediatedContextInstVarIndex: byte2)
  						ifTrue: [self genPushMaybeContextReceiverVariable: byte2]
  						ifFalse: [self genPushReceiverVariable: byte2.
  								self ssTop annotateUse: true.
  								^0]].
  			[3]	->	[self genPushLiteralIndex: byte2.
  					 self ssTop annotateUse: true.
  					 ^0].
  			[4]	->	[self genPushLiteralVariable: byte2.].
  			[7]	->	[self genStorePop: false LiteralVariable: byte2] }
  		otherwise: "5 & 6"
  			[(coInterpreter isWriteMediatedContextInstVarIndex: byte2)
  				ifTrue: [self genStorePop: opType = 6 MaybeContextReceiverVariable: byte2]
  				ifFalse: [self genStorePop: opType = 6 ReceiverVariable: byte2]].
  	"We need a map entry for this bytecode for correct parsing (if the method builds a frame).
  	 We could of course special case the scanning but that's silly (or is it?)."
  	self assert: needsFrame.
  	"genPushMaybeContextInstVar, pushListVar, store & storePop all generate code"
  	self assert: self prevInstIsPCAnnotated not.
  	self annotateBytecode: self Label.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genMarshalledSend:numArgs:sendTable: (in category 'bytecode generator support') -----
+ genMarshalledSend: selectorIndex numArgs: numArgs sendTable: sendTable
- genMarshalledSend: selector numArgs: numArgs sendTable: sendTable
  	<inline: false>
  	<var: #sendTable type: #'sqInt *'>
  	| annotation |
- 	(objectMemory isYoung: selector) ifTrue:
- 		[hasYoungReferent := true].
  	self assert: needsFrame.
  	annotation := self annotationForSendTable: sendTable.
  	"Deal with stale super sends; see SpurMemoryManager's class comment."
  	(self annotationIsForUncheckedEntryPoint: annotation) ifTrue:
  		[objectRepresentation genEnsureOopInRegNotForwarded: ReceiverResultReg scratchReg: TempReg].
  	"0 through (NumSendTrampolines - 2) numArgs sends have the arg count implciti in the trampoline.
  	 The last send trampoline (NumSendTrampolines - 1) passes numArgs in SendNumArgsReg."
  	numArgs >= (NumSendTrampolines - 1) ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
  	(BytecodeSetHasDirectedSuperSend
  	 and: [annotation = IsDirectedSuperSend]) ifTrue:
  		[self genMoveConstant: tempOop R: TempReg].
+ 	self genLoadInlineCache: selectorIndex.
- 	self MoveUniqueCw: selector R: ClassReg.
  	(self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1))) annotation: annotation.
  	optStatus isReceiverResultRegLive: false.
  	^self ssPushRegister: ReceiverResultReg!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genNSSend:numArgs:depth:sendTable: (in category 'bytecode generators') -----
+ genNSSend: selectorIndex numArgs: numArgs depth: depth sendTable: sendTable
- genNSSend: selector numArgs: numArgs depth: depth sendTable: sendTable
  	<var: #sendTable type: #'sqInt *'>
+ 	| selector nsSendCache |
+ 	self assert: (selectorIndex between: 0 and: (objectMemory literalCountOf: methodObj) - 1).
+ 	selector := self getLiteral: selectorIndex.
+ 	self assert: (objectMemory addressCouldBeOop: selector).	
- 	| nsSendCache |
  	(objectMemory isYoung: selector) ifTrue:
  		[hasYoungReferent := true].
  
  	nsSendCache := theIRCs + (NumOopsPerNSC * objectMemory bytesPerOop * indexOfIRC).
  	indexOfIRC := indexOfIRC + 1.
  	self assert: (objectMemory isInOldSpace: nsSendCache).
  	self initializeNSSendCache: nsSendCache selector: selector numArgs: numArgs depth: depth.
  
  	self ssAllocateCallReg: SendNumArgsReg.
  
  	"This may leave the method receiver on the stack, which might not be the implicit receiver.
  	 But the lookup trampoline will establish an on-stack receiver once it locates it."
  	self marshallAbsentReceiverSendArguments: numArgs.
  
  	"Load the cache last so it is a fixed distance from the call."
  	self MoveUniqueCw: nsSendCache R: SendNumArgsReg.
  	self CallNewspeakSend: (sendTable at: (numArgs min: NumSendTrampolines - 1)).
  
  	optStatus isReceiverResultRegLive: false.
  	self ssPushRegister: ReceiverResultReg.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSend:numArgs: (in category 'bytecode generator support') -----
+ genSend: selectorIndex numArgs: numArgs
- genSend: selector numArgs: numArgs
  	self marshallSendArguments: numArgs.
+ 	^self genMarshalledSend: selectorIndex numArgs: numArgs sendTable: ordinarySendTrampolines!
- 	^self genMarshalledSend: selector numArgs: numArgs sendTable: ordinarySendTrampolines!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendDirectedSuper:numArgs: (in category 'bytecode generator support') -----
+ genSendDirectedSuper: selectorIndex numArgs: numArgs
- genSendDirectedSuper: selector numArgs: numArgs
  	self assert: self ssTop type = SSConstant.
  	tempOop := self ssTop constant.
  	self ssPop: 1.
  	self marshallSendArguments: numArgs.
+ 	^self genMarshalledSend: selectorIndex numArgs: numArgs sendTable: directedSuperSendTrampolines!
- 	^self genMarshalledSend: selector numArgs: numArgs sendTable: directedSuperSendTrampolines!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendDynamicSuper:numArgs: (in category 'bytecode generator support') -----
+ genSendDynamicSuper: selectorIndex numArgs: numArgs
- genSendDynamicSuper: selector numArgs: numArgs
  	self marshallSendArguments: numArgs.
+ 	^self genMarshalledSend: selectorIndex numArgs: numArgs sendTable: dynamicSuperSendTrampolines!
- 	^self genMarshalledSend: selector numArgs: numArgs sendTable: dynamicSuperSendTrampolines!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendSuper:numArgs: (in category 'bytecode generator support') -----
+ genSendSuper: selectorIndex numArgs: numArgs
- genSendSuper: selector numArgs: numArgs
  	self marshallSendArguments: numArgs.
+ 	^self genMarshalledSend: selectorIndex numArgs: numArgs sendTable: superSendTrampolines!
- 	^self genMarshalledSend: selector numArgs: numArgs sendTable: superSendTrampolines!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorArithmetic (in category 'bytecode generators') -----
  genSpecialSelectorArithmetic
  	| primDescriptor rcvrIsConst argIsConst rcvrIsInt argIsInt rcvrInt argInt result
+ 	 jumpNotSmallInts jumpContinue annotateInst instToAnnotate index |
- 	 jumpNotSmallInts jumpContinue annotateInst instToAnnotate |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	<var: #jumpContinue type: #'AbstractInstruction *'>
  	<var: #instToAnnotate type: #'AbstractInstruction *'>
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := (argIsConst := self ssTop type = SSConstant)
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (rcvrIsConst := (self ssValue: 1) type = SSConstant)
  				 and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
  
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[rcvrInt := objectMemory integerValueOf: rcvrInt.
  		 argInt := objectMemory integerValueOf: argInt.
  		 primDescriptor opcode caseOf: {
  			[AddRR]	-> [result := rcvrInt + argInt].
  			[SubRR]	-> [result := rcvrInt - argInt].
  			[AndRR]	-> [result := rcvrInt bitAnd: argInt].
  			[OrRR]	-> [result := rcvrInt bitOr: argInt] }.
  		(objectMemory isIntegerValue: result) ifTrue:
  			["Must enter any annotatedConstants into the map"
  			 self annotateBytecodeIfAnnotated: (self ssValue: 1).
  			 self annotateBytecodeIfAnnotated: self ssTop.
  			 "Must annotate the bytecode for correct pc mapping."
  			^self ssPop: 2; ssPushAnnotatedConstant: (objectMemory integerObjectOf: result)].
  		^self genSpecialSelectorSend].
  
  	"If there's any constant involved other than a SmallInteger don't attempt to inline."
  	((rcvrIsConst and: [rcvrIsInt not])
  	 or: [argIsConst and: [argIsInt not]]) ifTrue:
  		[^self genSpecialSelectorSend].
  
  	"If we know nothing about the types then better not to inline as the inline cache and
  	 primitive code is not terribly slow so wasting time on duplicating tag tests is pointless."
  	(argIsInt or: [rcvrIsInt]) ifFalse:
  		[^self genSpecialSelectorSend].
  
  	argIsInt
  		ifTrue:
  			[self ssFlushTo: simStackPtr - 2.
  			 (self ssValue: 1) popToReg: ReceiverResultReg.
  			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg.
  			 rcvrIsInt ifFalse:
  				[objectRepresentation isSmallIntegerTagNonZero
  					ifTrue: [self AndR: ReceiverResultReg R: TempReg]
  					ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
  	jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	primDescriptor opcode caseOf: {
  		[AddRR] -> [argIsInt
  						ifTrue:
  							[instToAnnotate := self AddCq: argInt - ConstZero R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self SubCq: argInt - ConstZero R: ReceiverResultReg]
  						ifFalse:
  							[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ReceiverResultReg.
  							 self AddR: Arg0Reg R: ReceiverResultReg.
  							jumpContinue := self JumpNoOverflow: 0.
  							"overflow; must undo the damage before continuing"
  							 rcvrIsInt
  								ifTrue: [self MoveCq: rcvrInt R: ReceiverResultReg]
  								ifFalse:
  									[self SubR: Arg0Reg R: ReceiverResultReg.
  									 objectRepresentation genSetSmallIntegerTagsIn: ReceiverResultReg]]].
  		[SubRR] -> [argIsInt
  						ifTrue:
  							[instToAnnotate := self SubCq: argInt - ConstZero R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self AddCq: argInt - ConstZero R: ReceiverResultReg]
  						ifFalse:
  							[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: Arg0Reg.
  							 self SubR: Arg0Reg R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self AddR: Arg0Reg R: ReceiverResultReg.
  							 objectRepresentation genSetSmallIntegerTagsIn: Arg0Reg]].
  		[AndRR] -> [argIsInt
  						ifTrue: [instToAnnotate := self AndCq: argInt R: ReceiverResultReg]
  						ifFalse: [self AndR: Arg0Reg R: ReceiverResultReg].
  					jumpContinue := self Jump: 0].
  		[OrRR]	-> [argIsInt
  						ifTrue: [instToAnnotate := self OrCq: argInt R: ReceiverResultReg]
  						ifFalse: [self OrR: Arg0Reg R: ReceiverResultReg].
  					jumpContinue := self Jump: 0] }.
  	jumpNotSmallInts jmpTarget: self Label.
  	argIsInt ifTrue:
  		[annotateInst ifTrue: [self annotateBytecode: instToAnnotate].
  		 self MoveCq: argInt R: Arg0Reg].
+ 	index := byte0 - self firstSpecialSelectorBytecodeOffset.
+ 	self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines.
- 	self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
- 		numArgs: 1
- 		sendTable: ordinarySendTrampolines.
  	jumpContinue jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor
+ 	  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB annotateInst index |
- 	  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB annotateInst |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := self ssTop type = SSConstant
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (self ssValue: 1) type = SSConstant
  				 and: [objectMemory isIntegerObject: (self ssValue: 1) constant].
  
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[^ self genStaticallyResolvedSpecialSelectorComparison].
  
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  
  	"Only interested in inlining if followed by a conditional branch."
  	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  		[inlineCAB := argIsInt or: [rcvrIsInt]].
  	inlineCAB ifFalse:
  		[^self genSpecialSelectorSend].
  
  	argIsInt
  		ifTrue:
  			[(self ssValue: 1) popToReg: ReceiverResultReg.
  			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg.
  			 rcvrIsInt ifFalse:
  				[objectRepresentation isSmallIntegerTagNonZero
  					ifTrue: [self AndR: ReceiverResultReg R: TempReg]
  					ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
  	jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	argIsInt
  		ifTrue: [annotateInst
  					ifTrue: [self annotateBytecode: (self CmpCq: argInt R: ReceiverResultReg)]
  					ifFalse: [self CmpCq: argInt R: ReceiverResultReg]]
  		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
  	self gen: (branchDescriptor isBranchTrue
  				ifTrue: [primDescriptor opcode]
  				ifFalse: [self inverseBranchFor: primDescriptor opcode])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	jumpNotSmallInts jmpTarget: self Label.
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
+ 	index := byte0 - self firstSpecialSelectorBytecodeOffset.
+ 	^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines!
- 	^self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
- 		numArgs: 1
- 		sendTable: ordinarySendTrampolines.!



More information about the Vm-dev mailing list