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

commits at source.squeak.org commits at source.squeak.org
Tue Jun 16 22:30:13 UTC 2015


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

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

Name: VMMaker.oscog-eem.1357
Author: eem
Time: 16 June 2015, 3:27:59.805 pm
UUID: e41e9e44-9282-44ad-9e31-d7a33f325590
Ancestors: VMMaker.oscog-eem.1356

ARM Cogit:
Provide the rest of the literal scanning and
update support required for out-of-line
literals.

Fix Slang translation.

Eliminate compiler warnings.

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

Item was changed:
  ----- Method: CogARMCompiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Because we don't use Thumb, each ARM instruction has 4 bytes. Many
  	 abstract opcodes need more than one instruction. Instructions that refer
  	 to constants and/or literals depend on literals being stored in-line or out-of-line.
  
  	 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].
  		[Literal]					-> [^4].
  		[AlignmentNops]		-> [^(operands at: 0) - 4].
  		[Fill16]					-> [^4].
  		[Fill32]					-> [^4].
  		[FillFromWord]			-> [^4].
  		[Nop]					-> [^4].
  		"Control"
  		[Call]					-> [^4].
  		[CallFull]				-> [^self literalLoadInstructionBytes + 4].
  		[JumpR]					-> [^4].
  		[Jump]					-> [^4].
  		[JumpFull]				-> [^self literalLoadInstructionBytes + 4].
  		[JumpLong]				-> [^4].
  		[JumpZero]				-> [^4].
  		[JumpNonZero]			-> [^4].
  		[JumpNegative]			-> [^4].
  		[JumpNonNegative]		-> [^4].
  		[JumpOverflow]			-> [^4].
  		[JumpNoOverflow]		-> [^4].
  		[JumpCarry]			-> [^4].
  		[JumpNoCarry]			-> [^4].
  		[JumpLess]				-> [^4].
  		[JumpGreaterOrEqual]	-> [^4].
  		[JumpGreater]			-> [^4].
  		[JumpLessOrEqual]		-> [^4].
  		[JumpBelow]			-> [^4].
  		[JumpAboveOrEqual]	-> [^4].
  		[JumpAbove]			-> [^4].
  		[JumpBelowOrEqual]	-> [^4].
  		[JumpLongZero]		-> [^4].
  		[JumpLongNonZero]	-> [^4].
  		[JumpFPEqual]			-> [^8].
  		[JumpFPNotEqual]		-> [^8].
  		[JumpFPLess]			-> [^8].
  		[JumpFPGreaterOrEqual]-> [^8].
  		[JumpFPGreater]		-> [^8].
  		[JumpFPLessOrEqual]	-> [^8].
  		[JumpFPOrdered]		-> [^8].
  		[JumpFPUnordered]		-> [^8].
  		[RetN]					-> [^(operands at: 0) = 0 ifTrue: [4] ifFalse: [8]].
  		[Stop]					-> [^4].
  
  		"Arithmetic"
  		[AddCqR]				-> [^self rotateable8bitSignedImmediate: (operands at: 0)
  										ifTrue: [:r :i :n| 4]
  										ifFalse: [self literalLoadInstructionBytes + 4]].
  		[AndCqR]				-> [^self rotateable8bitBitwiseImmediate: (operands at: 0)
  										ifTrue: [:r :i :n| 4]
  										ifFalse:
  											[self literalLoadInstructionBytes = 4
  												ifTrue: [8]
  												ifFalse:
  													[1 << (operands at: 0) highBit = ((operands at: 0) + 1)
  														ifTrue: [8]
  														ifFalse: [self literalLoadInstructionBytes + 4]]]].
  		[AndCqRR]				-> [^self rotateable8bitBitwiseImmediate: (operands at: 0)
  										ifTrue: [:r :i :n| 4]
  										ifFalse:
  											[self literalLoadInstructionBytes = 4
  												ifTrue: [8]
  												ifFalse:
  													[1 << (operands at: 0) highBit = ((operands at: 0) + 1)
  														ifTrue: [8]
  														ifFalse: [self literalLoadInstructionBytes + 4]]]].
  		[CmpCqR]				-> [^self rotateable8bitSignedImmediate: (operands at: 0)
  											ifTrue: [:r :i :n| 4]
  											ifFalse: [self literalLoadInstructionBytes + 4]].
  		[OrCqR]					-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| 4]
  											ifFalse: [self literalLoadInstructionBytes + 4]].
  		[SubCqR]				-> [^self rotateable8bitSignedImmediate: (operands at: 0)
  											ifTrue: [:r :i :n| 4]
  											ifFalse: [self literalLoadInstructionBytes + 4]].
  		[TstCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| 4]
  											ifFalse: [self literalLoadInstructionBytes + 4]].
  		[XorCqR]				-> [^self rotateable8bitBitwiseImmediate: (operands at: 0)
  										ifTrue: [:r :i :n| 4]
  										ifFalse:
  											[self literalLoadInstructionBytes = 4
  												ifTrue: [8]
  												ifFalse:
  													[1 << (operands at: 0) highBit = ((operands at: 0) + 1)
  														ifTrue: [8]
  														ifFalse: [self literalLoadInstructionBytes + 4]]]].
  		[AddCwR]				-> [^self literalLoadInstructionBytes + 4].
  		[AndCwR]				-> [^self literalLoadInstructionBytes + 4].
  		[CmpCwR]				-> [^self literalLoadInstructionBytes + 4].
  		[OrCwR]				-> [^self literalLoadInstructionBytes + 4].
  		[SubCwR]				-> [^self literalLoadInstructionBytes + 4].
  		[XorCwR]				-> [^self literalLoadInstructionBytes + 4].
  		[AddRR]					-> [^4].
  		[AndRR]					-> [^4].
  		[CmpRR]				-> [^4].
  		[OrRR]					-> [^4].
  		[XorRR]					-> [^4].
  		[SubRR]					-> [^4].
  		[NegateR]				-> [^4].
  		[LoadEffectiveAddressMwrR]
  									-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| 4]
  											ifFalse: [self literalLoadInstructionBytes + 4]].
  
  		[LogicalShiftLeftCqR]		-> [^4].
  		[LogicalShiftRightCqR]		-> [^4].
  		[ArithmeticShiftRightCqR]	-> [^4].
  		[LogicalShiftLeftRR]			-> [^4].
  		[LogicalShiftRightRR]		-> [^4].
  		[ArithmeticShiftRightRR]		-> [^4].
  		[AddRdRd]					-> [^4].
  		[CmpRdRd]					-> [^4].
  		[SubRdRd]					-> [^4].
  		[MulRdRd]					-> [^4].
  		[DivRdRd]					-> [^4].
  		[SqrtRd]					-> [^4].
  		"ARM Specific Arithmetic"
  		[SMULL]				-> [^4].
  		[MSR]					-> [^4].
  		[CMPSMULL]			-> [^4]. "special compare for genMulR:R: usage"
  		"Data Movement"						
  		[MoveCqR]				-> [^self literalLoadInstructionBytes = 4
  										ifTrue: [self literalLoadInstructionBytes]
  										ifFalse:
  											[self rotateable8bitBitwiseImmediate: (operands at: 0)
  												ifTrue: [:r :i :n| 4]
  												ifFalse: [self literalLoadInstructionBytes]]].
  		[MoveCwR]				-> [^self literalLoadInstructionBytes = 4
  										ifTrue: [self literalLoadInstructionBytes]
  										ifFalse:
+ 											[((self isAnInstruction: (cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *')) "i.e. a label, which by definition will be in the current compilation."
- 											[((self isAnInstruction: (operands at: 0)) "i.e. a label, which by definition will be in the current compilation."
  											   or: [cogit addressIsInCurrentCompilation: (operands at: 0)])
  												ifTrue: [4]
  												ifFalse: [self literalLoadInstructionBytes]]].
  		[MoveRR]				-> [^4].
  		[MoveRdRd]				-> [^4].
  		[MoveAwR]				-> [^(self isAddressRelativeToVarBase: (operands at: 0))
  													ifTrue: [4]
  													ifFalse: [self literalLoadInstructionBytes + 4]].
  		[MoveRAw]				-> [^(self isAddressRelativeToVarBase: (operands at: 1))
  													ifTrue: [4]
  													ifFalse: [self literalLoadInstructionBytes + 4]].
  		[MoveRMwr]			-> [^self is12BitValue: (operands at: 1)
  										ifTrue: [:u :i| 4]
  										ifFalse: [self literalLoadInstructionBytes + 4]].
  		[MoveRdM64r]			-> [^self literalLoadInstructionBytes + 4]. 
  		[MoveMbrR]				-> [^self is12BitValue: (operands at: 0)
  										ifTrue: [:u :i| 4]
  										ifFalse: [self literalLoadInstructionBytes + 4]].
  		[MoveRMbr]				-> [^self is12BitValue: (operands at: 1)
  										ifTrue: [:u :i| 4]
  										ifFalse: [self literalLoadInstructionBytes + 4]].
  		[MoveM16rR]			-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| 4]
  											ifFalse: [self literalLoadInstructionBytes + 4]].
  		[MoveM64rRd]			-> [^self literalLoadInstructionBytes + 4].
  		[MoveMwrR]			-> [^self is12BitValue: (operands at: 0)
  										ifTrue: [:u :i| 4]
  										ifFalse: [self literalLoadInstructionBytes + 4]].
  		[MoveXbrRR]			-> [^4].
  		[MoveRXbrR]			-> [^4].
  		[MoveXwrRR]			-> [^4].
  		[MoveRXwrR]			-> [^4].
  		[PopR]					-> [^4].
  		[PushR]					-> [^4].
  		[PushCw]				-> [^self literalLoadInstructionBytes = 4
  										ifTrue: [self literalLoadInstructionBytes + 4]
  										ifFalse:
+ 											[((self isAnInstruction: (cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *')) "i.e. a label, which by definition will be in the current compilation."
- 											[((self isAnInstruction: (operands at: 0)) "i.e. a label, which by definition will be in the current compilation."
  											   or: [cogit addressIsInCurrentCompilation: (operands at: 0)])
  												ifTrue: [8]
  												ifFalse:
  													[self rotateable8bitBitwiseImmediate: (operands at: 0)
  														ifTrue: [:r :i :n| 8]
  														ifFalse: [self literalLoadInstructionBytes + 4]]]].
  		[PushCq]				-> [^self literalLoadInstructionBytes = 4
  										ifTrue: [self literalLoadInstructionBytes + 4]
  										ifFalse:
  											[self rotateable8bitBitwiseImmediate: (operands at: 0)
  												ifTrue: [:r :i :n| 8]
  												ifFalse: [self literalLoadInstructionBytes + 4]]].
  		[PrefetchAw] 			-> [^(self isAddressRelativeToVarBase: (operands at: 0))
  										ifTrue: [4]
  										ifFalse: [self literalLoadInstructionBytes + 4]].
  		"Conversion"
  		[ConvertRRd]			-> [^4].
  		}.
  	^0 "to keep C compiler quiet"
  !

Item was changed:
  ----- Method: CogARMCompiler>>concretizePushCw (in category 'generate machine code - concretize') -----
  concretizePushCw
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| word instrOffset |
  	word := operands at: 0.	
+ 	((self isAnInstruction: (cogit cCoerceSimple: word to: #'AbstractInstruction *'))
- 	((self isAnInstruction: word)
  	 or: [cogit addressIsInCurrentCompilation: word])
  		ifTrue:
  			[instrOffset := self loadCwInto: ConcreteIPReg]
  		ifFalse:
  			[self 
  				rotateable8bitBitwiseImmediate: word 
  				ifTrue:
  					[:rot :immediate :invert|
  					self machineCodeAt: 0
  						put: (invert
  								ifTrue: [self mvn: ConcreteIPReg imm: immediate ror: rot]
  								ifFalse: [self mov: ConcreteIPReg imm: immediate ror: rot]).
  					instrOffset := 4]
  				ifFalse:
  					[instrOffset := self loadCwInto: ConcreteIPReg]].
  	self machineCodeAt: instrOffset put: (self pushR: ConcreteIPReg).
  	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>loadCwInto: (in category 'generate machine code - support') -----
  loadCwInto: destReg
  	"Load the operand into the destination register, answering
  	 the size of the instructions generated to do so."
  	| operand distance |
  	operand := operands at: 0.
+ 	(self isAnInstruction: (cogit cCoerceSimple: operand to: #'AbstractInstruction *')) ifTrue:
- 	(self isAnInstruction: operand) ifTrue:
  		[operand := (cogit cCoerceSimple: operand to: #'AbstractInstruction *') address].
  	"First try and encode as a pc-relative reference..."
  	(cogit addressIsInCurrentCompilation: operand) ifTrue:
  		[distance := operand - (address + 8).
  		 self rotateable8bitSignedImmediate: distance
  		 	ifTrue:
  				[:rot :immediate :negate|
  		 		 self machineCodeAt: 0 put: (negate
  												ifTrue: [self sub: destReg rn: PC imm: immediate ror: rot]
  												ifFalse: [self add: destReg rn: PC imm: immediate ror: rot]).
  		 		^4]
  		 	ifFalse:
+ 		 		[self deny: (self isAnInstruction: (cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'))]].
- 		 		[self deny: (self isAnInstruction: (operands at: 0))]].
  	"If this fails, use the conventional literal load sequence."
  	^self moveCw: operand intoR: destReg!

Item was removed:
- ----- Method: CogARMCompiler>>relocateMethodReferenceBeforeAddress:by: (in category 'inline cacheing') -----
- relocateMethodReferenceBeforeAddress: pc by: delta
- 	"If possible we generate the method address using pc-relative addressing.
- 	 If so we don't need to relocate it in code.  So check if pc-relative code was
- 	 generated, and if not, adjust a long sequence.  There are two cases, a push
- 	 or a register load.  If a push, then there is a register load, but in the instruction
- 	 before."
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: CogARMCompiler>>rewriteInlineCacheTag:at: (in category 'inline cacheing') -----
- rewriteInlineCacheTag: cacheTag at: callSiteReturnAddress
- 	"Rewrite an inline cache with a new tag.  This variant is used
- 	 by the garbage collector."
- 	^self subclassResponsibility!

Item was changed:
  ----- Method: CogOutOfLineLiteralsARMCompiler>>concretizeLiteral (in category 'generate machine code') -----
  concretizeLiteral
  	"Generate an out-of-line literal.  Copy the value and any annotation from the stand-in in the literals manager."
  	| literalAsInstruction literal |
- 	<var: #jumpTarget type: #'AbstractInstruction *'>
  	literalAsInstruction := cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'.
  	literal := (self isAnInstruction: literalAsInstruction)
  				ifTrue: [literalAsInstruction address]
  				ifFalse: [self cCode: [literalAsInstruction asUnsignedInteger]
  							inSmalltalk: [literalAsInstruction]].
  	self assert: (dependent notNil and: [dependent opcode = Literal and: [dependent address = address]]).
  	dependent annotation ifNotNil:
  		[self assert: annotation isNil.
  		 annotation := dependent annotation].
  	self machineCodeAt: 0 put: literal!

Item was added:
+ ----- Method: CogOutOfLineLiteralsARMCompiler>>relocateMethodReferenceBeforeAddress:by: (in category 'inline cacheing') -----
+ relocateMethodReferenceBeforeAddress: pc by: delta
+ 	"If possible we generate the method address using pc-relative addressing.
+ 	 If so we don't need to relocate it in code.  So check if pc-relative code was
+ 	 generated, and if not, adjust a load literal.  There are two cases, a push
+ 	 or a register load.  If a push, then there is a register load, but in the instruction
+ 	 before."
+ 	| pcPreceedingLoad reference litAddr |
+ 	pcPreceedingLoad := (self instructionIsPush: (self instructionBeforeAddress: pc))
+ 							ifTrue: [pc - 4]
+ 							ifFalse: [pc].
+ 	"If the load is not done via pc-relative addressing we have to relocate."
+ 	(self isPCRelativeValueLoad: (self instructionBeforeAddress: pcPreceedingLoad)) ifFalse:
+ 		[litAddr := self pcRelativeAddressAt: pcPreceedingLoad.
+ 		 reference := objectMemory longAt: litAddr.
+ 		 objectMemory longAt: litAddr put: reference + delta]!

Item was added:
+ ----- Method: CogOutOfLineLiteralsARMCompiler>>rewriteInlineCacheTag:at: (in category 'inline cacheing') -----
+ rewriteInlineCacheTag: cacheTag at: callSiteReturnAddress
+ 	"Rewrite an inline cache with a new tag.  This variant is used
+ 	 by the garbage collector."
+ 	<inline: true>
+ 	objectMemory longAt: (self pcRelativeAddressAt: callSiteReturnAddress - 8) put: cacheTag!

Item was changed:
  ----- Method: CogOutOfLineLiteralsARMCompiler>>usesOutOfLineLiteral (in category 'testing') -----
  usesOutOfLineLiteral
  	"Answer if the receiver uses an out-of-line literal.  Needs only
  	 to work for the opcodes created with gen:literal:operand: et al."
  
  	opcode
  		caseOf: {
  		[CallFull]		-> [^true].
  		[JumpFull]		-> [^true].
  		"Arithmetic"
  		[AddCqR]		-> [^self rotateable8bitSignedImmediate: (operands at: 0) ifTrue: [:r :i :n| false] ifFalse: [true]].
  		[AndCqR]		-> [^self rotateable8bitBitwiseImmediate: (operands at: 0)
  								ifTrue: [:r :i :n| false]
  								ifFalse: [1 << (operands at: 0) highBit ~= ((operands at: 0) + 1)]].
  		[AndCqRR]		-> [^self rotateable8bitBitwiseImmediate: (operands at: 0)
  								ifTrue: [:r :i :n| false]
  								ifFalse: [1 << (operands at: 0) highBit ~= ((operands at: 0) + 1)]].
  		[CmpCqR]		-> [^self rotateable8bitSignedImmediate: (operands at: 0) ifTrue: [:r :i :n| false] ifFalse: [true]].
  		[OrCqR]			-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[SubCqR]		-> [^self rotateable8bitSignedImmediate: (operands at: 0) ifTrue: [:r :i :n| false] ifFalse: [true]].
  		[TstCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[XorCqR]		-> [^self rotateable8bitBitwiseImmediate: (operands at: 0) ifTrue: [:r :i :n| false] ifFalse: [true]].
  		[AddCwR]		-> [^true].
  		[AndCwR]		-> [^true].
  		[CmpCwR]		-> [^true].
  		[OrCwR]		-> [^true].
  		[SubCwR]		-> [^true].
  		[XorCwR]		-> [^true].
  		[LoadEffectiveAddressMwrR]
  						-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		"Data Movement"						
  		[MoveCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
+ 		[MoveCwR]		-> [^((self isAnInstruction: (cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *')) "i.e. a label, which by definition will be in the current compilation."
- 		[MoveCwR]		-> [^((self isAnInstruction: (operands at: 0)) "i.e. a label, which by definition will be in the current compilation."
  							  or: [cogit addressIsInCurrentCompilation: (operands at: 0)]) not].
  		[MoveAwR]		-> [^(self isAddressRelativeToVarBase: (operands at: 0)) ifTrue: [false] ifFalse: [true]].
  		[MoveRAw]		-> [^(self isAddressRelativeToVarBase: (operands at: 1)) ifTrue: [false] ifFalse: [true]].
  		[MoveRMwr]	-> [^self is12BitValue: (operands at: 1) ifTrue: [:u :i| false] ifFalse: [true]].
  		[MoveRdM64r]	-> [^self is12BitValue: (operands at: 1) ifTrue: [:u :i| false] ifFalse: [true]]. 
  		[MoveMbrR]		-> [^self is12BitValue: (operands at: 0) ifTrue: [:u :i| false] ifFalse: [true]].
  		[MoveRMbr]		-> [^self is12BitValue: (operands at: 1) ifTrue: [:u :i| false] ifFalse: [true]].
  		[MoveM16rR]	-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[MoveM64rRd]	-> [^self is12BitValue: (operands at: 0) ifTrue: [:u :i| false] ifFalse: [true]].
  		[MoveMwrR]	-> [^self is12BitValue: (operands at: 0) ifTrue: [:u :i| false] ifFalse: [true]].
+ 		[PushCw]		-> [^((self isAnInstruction: (cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *')) "i.e. a label, which by definiion will be in the current compilation."
- 		[PushCw]		-> [^((self isAnInstruction: (operands at: 0)) "i.e. a label, which by definiion will be in the current compilation."
  							  or: [cogit addressIsInCurrentCompilation: (operands at: 0)]) not].
  		[PushCq]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[PrefetchAw] 	-> [^(self isAddressRelativeToVarBase: (operands at: 0)) ifTrue: [false] ifFalse: [true]].
  		}
  		otherwise: [self assert: false].
  	^false "to keep C compiler quiet"
  !

Item was changed:
  ----- Method: Cogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	#(	'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation'
  		'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass' 'nsSendCacheSurrogateClass'
  		'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses'
  		'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters'
  		'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep') do:
  			[:simulationVariableNotNeededForRealVM|
  			aCCodeGenerator removeVariable: simulationVariableNotNeededForRealVM].
  	NewspeakVM ifFalse:
  		[#(	'selfSendTrampolines' 'dynamicSuperSendTrampolines'
  			'implicitReceiverSendTrampolines' 'outerSendTrampolines'
  			'ceEnclosingObjectTrampoline' 'numIRCs' 'indexOfIRC' 'theIRCs') do:
  				[:variableNotNeededInNormalVM|
  				aCCodeGenerator removeVariable: variableNotNeededInNormalVM]].
  	aCCodeGenerator removeConstant: #COGMTVM. "this should be defined at compile time"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h>'; "for e.g. offsetof"
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"dispdbg.h"'; "must preceed cointerp.h & cogit.h otherwise NoDbgRegParms gets screwed up"
  		addHeaderFile:'"cogmethod.h"'.
  	NewspeakVM ifTrue:
  		[aCCodeGenerator addHeaderFile:'"nssendcache.h"'].
  	aCCodeGenerator
  		addHeaderFile:'#if COGMTVM';
  		addHeaderFile:'"cointerpmt.h"';
  		addHeaderFile:'#else';
  		addHeaderFile:'"cointerp.h"';
  		addHeaderFile:'#endif';
  		addHeaderFile:'"cogit.h"'.
  	aCCodeGenerator
  		var: #ceGetSP
  			declareC: 'unsigned long (*ceGetSP)(void)';
  		var: #ceCaptureCStackPointers
  			declareC: 'void (*ceCaptureCStackPointers)(void)';
  		var: #ceEnterCogCodePopReceiverReg
  			declareC: 'void (*ceEnterCogCodePopReceiverReg)(void)';
  		var: #realCEEnterCogCodePopReceiverReg
  			declareC: 'void (*realCEEnterCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverReg
  			declareC: 'void (*ceCallCogCodePopReceiverReg)(void)';
  		var: #realCECallCogCodePopReceiverReg
  			declareC: 'void (*realCECallCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*ceCallCogCodePopReceiverAndClassRegs)(void)';
  		var: #realCECallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*realCECallCogCodePopReceiverAndClassRegs)(void)';
  		var: #ceFlushICache
  			declareC: 'static void (*ceFlushICache)(unsigned long from, unsigned long to)';
  		var: #ceCheckFeaturesFunction
  			declareC: 'static unsigned long (*ceCheckFeaturesFunction)(void)';
  		var: #ceTryLockVMOwner
  			declareC: 'unsigned long (*ceTryLockVMOwner)(void)';
  		var: #ceUnlockVMOwner
  			declareC: 'void (*ceUnlockVMOwner)(void)';
  		var: #postCompileHook
  			declareC: 'void (*postCompileHook)(CogMethod *)';
  		var: #openPICList declareC: 'CogMethod *openPICList = 0';
  		var: #maxMethodBefore type: #'CogBlockMethod *'.
  	aCCodeGenerator
  		declareVar: 'aMethodLabel' type: #'AbstractInstruction'; "Has to come lexicographically before backEnd & methodLabel"
  		var: #backEnd declareC: 'AbstractInstruction * const backEnd = &aMethodLabel';
  		var: #methodLabel declareC: 'AbstractInstruction * const methodLabel = &aMethodLabel'.
  	self declareC: #(abstractOpcodes stackCheckLabel
  					blockEntryLabel blockEntryNoContextSwitch
  					stackOverflowCall sendMiss
  					entry noCheckEntry selfSendEntry dynSuperEntry
  					picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1)
  			as: #'AbstractInstruction *'
  				in: aCCodeGenerator.
  	aCCodeGenerator
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *'.
  	aCCodeGenerator
  		var: #ordinarySendTrampolines
  			declareC: 'sqInt ordinarySendTrampolines[NumSendTrampolines]';
  		var: #superSendTrampolines
  			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]';
  		var: #directedSuperSendTrampolines
  			declareC: 'sqInt directedSuperSendTrampolines[NumSendTrampolines]';
  		var: #selfSendTrampolines
  			declareC: 'sqInt selfSendTrampolines[NumSendTrampolines]';
  		var: #dynamicSuperSendTrampolines
  			declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]';
  		var: #implicitReceiverSendTrampolines
  			declareC: 'sqInt implicitReceiverSendTrampolines[NumSendTrampolines]';
  		var: #outerSendTrampolines
  			declareC: 'sqInt outerSendTrampolines[NumSendTrampolines]';
  		var: #trampolineAddresses
  			declareC: 'static char *trampolineAddresses[NumTrampolines*2]';
  		var: #objectReferencesInRuntime
+ 			declareC: 'static usqInt objectReferencesInRuntime[NumObjRefsInRuntime]';
- 			declareC: 'static sqInt objectReferencesInRuntime[NumObjRefsInRuntime]';
  		var: #labelCounter
  			type: #int;
  		var: #traceFlags
  			declareC: 'int traceFlags = 8 /* prim trace log on by default */';
  		var: #cStackAlignment
  			declareC: 'const int cStackAlignment = STACK_ALIGN_BYTES'.
  	aCCodeGenerator
  		declareVar: #CFramePointer type: #'void *';
  		declareVar: #CStackPointer type: #'void *';
  		declareVar: #minValidCallAddress type: #'unsigned long';
  		declareVar: #debugPrimCallStackOffset type: #'unsigned long'.
  	aCCodeGenerator vmClass generatorTable ifNotNil:
  		[:bytecodeGenTable|
  		aCCodeGenerator
  			var: #generatorTable
  				declareC: 'static BytecodeDescriptor generatorTable[', bytecodeGenTable size, ']',
  							(self tableInitializerFor: bytecodeGenTable
  								in: aCCodeGenerator);
  			var: #primitiveGeneratorTable
  				declareC: 'static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
  							(self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
  								in: aCCodeGenerator)].
  	"In C the abstract opcode names clash with the Smalltak generator syntactic sugar.
  	 Most of the syntactic sugar is inlined, but alas some remains.  Rename the syntactic
  	 sugar to avoid the clash."
  	(self organization listAtCategoryNamed: #'abstract instructions') do:
  		[:s|
  		aCCodeGenerator addSelectorTranslation: s to: 'g', (aCCodeGenerator cFunctionNameFor: s)].
  	aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'!

Item was changed:
  ----- Method: Cogit>>addressIsInCurrentCompilation: (in category 'testing') -----
  addressIsInCurrentCompilation: address
  	^address asUnsignedInteger >= methodLabel address
+ 	  and: [address asUnsignedInteger < (methodLabel address + (1 << 16))]!
- 	  and: [address < (methodLabel address + (1 << 16))]!

Item was changed:
  ----- Method: Cogit>>cPICHasForwardedClass: (in category 'in-line cacheing') -----
  cPICHasForwardedClass: cPIC
  	<var: #cPIC type: #'CogMethod *'>
  	| pc |
  	pc := cPIC asUnsignedInteger
  		+ firstCPICCaseOffset
  		+ cPICCaseSize
  		- backEnd jumpLongConditionalByteSize.
  	2 to: cPIC cPICNumCases do:
  		[:i| | classIndex |
+ 		classIndex := literalsManager classRefInClosedPICAt: pc.
- 		classIndex := backEnd literalBeforeFollowingAddress: pc - backEnd loadLiteralByteSize.
  		(objectMemory isForwardedClassIndex: classIndex) ifTrue:
  			[^true].
  		pc := pc + cPICCaseSize].
  	^false!

Item was changed:
  ----- Method: Cogit>>closedPICRefersToUnmarkedObject: (in category 'garbage collection') -----
  closedPICRefersToUnmarkedObject: cPIC
  	"Answer if the ClosedPIC refers to any unmarked objects or freed/freeable target methods,
  	 applying markAndTraceOrFreeCogMethod:firstVisit: to those targets to determine if freed/freeable."
  	<var: #cPIC type: #'CogMethod *'>
+ 	| pc offsetToLiteral offsetToJump object entryPoint targetMethod |
- 	| pc offsetToLiteral object entryPoint targetMethod |
  	<var: #targetMethod type: #'CogMethod *'>
  	(objectMemory isImmediate: cPIC selector) ifFalse:
  		[(objectMemory isMarked: cPIC selector) ifFalse:
  			[^true]].
  	pc := cPIC asInteger + firstCPICCaseOffset.
  	"First jump is unconditional; subsequent ones are conditional"
  	offsetToLiteral := backEnd jumpLongByteSize.
+ 	offsetToJump := literalsManager literalBytesFollowingJumpInClosedPIC.
  	1 to: cPIC cPICNumCases do:
  		[:i|
  		objectRepresentation inlineCacheTagsMayBeObjects ifTrue:
+ 			[object := literalsManager classRefInClosedPICAt: pc - offsetToLiteral.
- 			[object := backEnd literalBeforeFollowingAddress: pc - offsetToLiteral - backEnd loadLiteralByteSize.
  			 ((objectRepresentation couldBeObject: object)
  			  and: [(objectMemory isMarked: object) not]) ifTrue:
  				[^true]].
+ 		object := literalsManager objRefInClosedPICAt: pc - offsetToLiteral.
- 		object := backEnd literalBeforeFollowingAddress: pc - offsetToLiteral.
  		((objectRepresentation couldBeObject: object)
  		 and: [(objectMemory isMarked: object) not]) ifTrue:
  			[^true].
+ 		entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc - offsetToJump.
- 		entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc.
  		"Find target from jump.  Ignore jumps to the interpret and MNU calls within this PIC"
+ 		self assert: (entryPoint > methodZoneBase and: [entryPoint < methodZone freeStart]).
  		(entryPoint asUnsignedInteger < cPIC asUnsignedInteger
  		 or: [entryPoint asUnsignedInteger > (cPIC asUnsignedInteger + cPIC blockSize) asUnsignedInteger]) ifTrue:
  			[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  			 self assert: (targetMethod cmType = CMMethod
  						or: [targetMethod cmType = CMFree]).
  			 (self markAndTraceOrFreeCogMethod: targetMethod
  				  firstVisit: targetMethod asUnsignedInteger > pc asUnsignedInteger) ifTrue:
  				[^true]].
  		offsetToLiteral := backEnd jumpLongConditionalByteSize.
+ 		offsetToJump := literalsManager literalBytesFollowingBranchInClosedPIC.
  		pc := pc + cPICCaseSize].
  	^false!

Item was changed:
  ----- Method: Cogit>>mapObjectReferencesInClosedPIC: (in category 'garbage collection') -----
  mapObjectReferencesInClosedPIC: cPIC
  	"Remap all object references in the closed PIC.  Answer if any references are young.
  	Set codeModified if any modifications are made."
  	<var: #cPIC type: #'CogMethod *'>
  	| pc refersToYoung |
  	pc := cPIC asInteger + firstCPICCaseOffset.
  	refersToYoung := self updateMaybeObjRefInClosedPICAt: pc - backEnd jumpLongByteSize.
  	pc := pc + cPICCaseSize.
  	2 to: cPIC cPICNumCases do:
  		[:i|
  		objectRepresentation inlineCacheTagsMayBeObjects ifTrue:
+ 			[(self updateMaybeClassRefInClosedPICAt: pc - backEnd jumpLongConditionalByteSize) ifTrue:
- 			[(self updateMaybeClassRefAt: pc - backEnd jumpLongConditionalByteSize) ifTrue:
  				[refersToYoung := true]].
  		(self updateMaybeObjRefInClosedPICAt: pc - backEnd jumpLongConditionalByteSize) ifTrue:
  			[refersToYoung := true].
  		pc := pc + cPICCaseSize].
  	^refersToYoung!

Item was changed:
  ----- Method: Cogit>>mapObjectReferencesInGeneratedRuntime (in category 'garbage collection') -----
  mapObjectReferencesInGeneratedRuntime
  	"Update all references to objects in the generated runtime."
  	0 to: runtimeObjectRefIndex - 1 do:
  		[:i| | mcpc literal mappedLiteral |
  		 mcpc := objectReferencesInRuntime at: i.
+ 		 literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc using: backEnd.
- 		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 mappedLiteral := objectRepresentation remapObject: literal.
  		 mappedLiteral ~= literal ifTrue:
+ 			[literalsManager storeLiteral: mappedLiteral atAnnotatedAddress: mcpc using: backEnd.
- 			[backEnd storeLiteral: mappedLiteral beforeFollowingAddress: mcpc.
  			 codeModified := true]]!

Item was changed:
  ----- Method: Cogit>>markAndTraceObjectReferencesInGeneratedRuntime (in category 'jit - api') -----
  markAndTraceObjectReferencesInGeneratedRuntime
  	"Mark and trace any object references in the generated run-time."
  	0 to: runtimeObjectRefIndex - 1 do:
  		[:i| | mcpc literal |
  		 mcpc := objectReferencesInRuntime at: i.
+ 		 literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc using: backEnd.
- 		 literal := backEnd literalBeforeFollowingAddress: mcpc asUnsignedInteger.
  		 objectRepresentation
  			markAndTraceLiteral: literal
  			in: (self cCoerceSimple: nil to: #'CogMethod *')
  			atpc: mcpc asUnsignedInteger]!

Item was changed:
  ----- Method: Cogit>>recordRunTimeObjectReferences (in category 'initialization') -----
  recordRunTimeObjectReferences
  	<var: #instruction type: #'AbstractInstruction *'>
  	0 to: opcodeIndex - 1 do:
  		[:i| | instruction |
  		instruction := self abstractInstructionAt: i.
  		instruction annotation = IsObjectReference ifTrue:
  			[self assert: runtimeObjectRefIndex < NumObjRefsInRuntime.
  			 self assert: hasYoungReferent not.
  			 hasYoungReferent ifTrue:
  				[self error: 'attempt to generate run-time routine containing young object reference.  Cannot initialize Cogit run-time.'].
  			 objectReferencesInRuntime
  				at: runtimeObjectRefIndex
+ 				put: instruction mapEntryAddress asUnsignedInteger.
- 				put: (instruction address + instruction machineCodeSize) asInteger.
  			 runtimeObjectRefIndex := runtimeObjectRefIndex + 1]]!

Item was changed:
  ----- Method: Cogit>>remapIfObjectRef:pc:hasYoung: (in category 'garbage collection') -----
  remapIfObjectRef: annotation pc: mcpc hasYoung: hasYoungPtr
  	<var: #mcpc type: #'char *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal mappedLiteral |
  		 literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (objectRepresentation couldBeObject: literal) ifTrue:
  			[mappedLiteral := objectRepresentation remapObject: literal.
  			 literal ~= mappedLiteral ifTrue:
  				[literalsManager storeLiteral: mappedLiteral atAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  				 codeModified := true].
  			 (hasYoungPtr ~= 0
  			  and: [objectMemory isYoung: mappedLiteral]) ifTrue:
  				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]].
  
  	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
  		[| nsSendCache oop mappedOop |
+ 		nsSendCache := self nsSendCacheFromReturnAddress: mcpc.
- 		nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  		oop := nsSendCache selector.	
  		mappedOop := objectRepresentation remapObject: oop.
  		oop ~= mappedOop ifTrue:
  			[nsSendCache selector: mappedOop.
  			(hasYoungPtr ~= 0 and: [objectMemory isYoung: mappedOop]) ifTrue:
  				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
  		oop := nsSendCache enclosingObject.	
  		oop ~= 0 ifTrue: [
  			mappedOop := objectRepresentation remapObject: oop.
  			oop ~= mappedOop ifTrue:
  				[nsSendCache enclosingObject: mappedOop.
  				(hasYoungPtr ~= 0 and: [objectMemory isYoung: mappedOop]) ifTrue:
  					[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]].
  		^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | mappedCacheTag |
  			 (tagCouldBeObj
  			  and: [objectRepresentation couldBeObject: cacheTag]) ifTrue:
  				[mappedCacheTag := objectRepresentation remapObject: cacheTag.
  				 cacheTag ~= mappedCacheTag ifTrue:
+ 					[backEnd rewriteInlineCacheTag: mappedCacheTag at: mcpc asUnsignedInteger.
- 					[backEnd rewriteInlineCacheTag: mappedCacheTag at: mcpc asInteger.
  					 codeModified := true].
  				 (hasYoungPtr ~= 0
  				  and: [objectMemory isYoung: mappedCacheTag]) ifTrue:
  					[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
  			hasYoungPtr ~= 0 ifTrue:
  				["Since the unlinking routines may rewrite the cacheTag to the send's selector, and
  				  since they don't have the cogMethod to hand and can't add it to youngReferrers,
  				  the method must remain in youngReferrers if the targetMethod's selector is young."
  				 entryPoint > methodZoneBase ifTrue: "It's a linked send."
  					[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  						[:targetMethod :ignored|
  						 (objectMemory isYoung: targetMethod selector) ifTrue:
  							[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]]].
  	^0 "keep scanning"!

Item was changed:
  VMClass subclass: #InLineLiteralsManager
+ 	instanceVariableNames: 'cogit'
- 	instanceVariableNames: 'cogit backEnd'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !InLineLiteralsManager commentStamp: 'eem 6/7/2015 12:07' prior: 0!
  An InLineLiteralsManager is a dummy class that understands the OutOfLineLiteralsManager API but does nothing.  It is used to allow the Cogits to work with back-ends that generate either in-line or out-of-line literals.!

Item was added:
+ ----- Method: InLineLiteralsManager class>>isNonArgumentImplicitReceiverVariableName: (in category 'translation') -----
+ isNonArgumentImplicitReceiverVariableName: aString
+ 	^Cogit isNonArgumentImplicitReceiverVariableName: aString!

Item was changed:
  ----- Method: InLineLiteralsManager>>classRefInClosedPICAt: (in category 'garbage collection') -----
  classRefInClosedPICAt: mcpc
  	<inline: true>
+ 	^cogit backEnd literalBeforeFollowingAddress: mcpc - cogit backEnd loadLiteralByteSize!
- 	^backEnd literalBeforeFollowingAddress: mcpc - backEnd loadLiteralByteSize!

Item was changed:
  ----- Method: InLineLiteralsManager>>cogit: (in category 'initialization') -----
  cogit: aCogit
  	<doNotGenerate>
+ 	cogit := aCogit!
- 	cogit := aCogit.
- 	backEnd := aCogit backEnd!

Item was added:
+ ----- Method: InLineLiteralsManager>>literalBytesFollowingBranchInClosedPIC (in category 'garbage collection') -----
+ literalBytesFollowingBranchInClosedPIC
+ 	<inline: true>
+ 	^0!

Item was added:
+ ----- Method: InLineLiteralsManager>>literalBytesFollowingJumpInClosedPIC (in category 'garbage collection') -----
+ literalBytesFollowingJumpInClosedPIC
+ 	<inline: true>
+ 	^0!

Item was changed:
  ----- Method: InLineLiteralsManager>>storeClassRef:inClosedPICAt: (in category 'garbage collection') -----
  storeClassRef: classObj inClosedPICAt: address
  	<var: #address type: #usqInt>
  	<inline: true>
+ 	cogit backEnd storeLiteral: classObj beforeFollowingAddress: address - cogit backEnd loadLiteralByteSize!
- 	backEnd storeLiteral: classObj beforeFollowingAddress: address - backEnd loadLiteralByteSize!

Item was changed:
  ----- Method: InLineLiteralsManager>>storeObjRef:inClosedPICAt: (in category 'garbage collection') -----
  storeObjRef: literal inClosedPICAt: address
  	<var: #address type: #usqInt>
  	<inline: true>
+ 	cogit backEnd storeLiteral: literal beforeFollowingAddress: address!
- 	backEnd storeLiteral: literal beforeFollowingAddress: address!

Item was changed:
  VMClass subclass: #OutOfLineLiteralsManager
+ 	instanceVariableNames: 'cogit objectMemory objectRepresentation firstOpcodeIndex nextLiteralIndex lastDumpedLiteralIndex literals literalsSize savedFirstOpcodeIndex savedNextLiteralIndex savedLastDumpedLiteralIndex'
- 	instanceVariableNames: 'cogit objectMemory firstOpcodeIndex nextLiteralIndex lastDumpedLiteralIndex literals literalsSize savedFirstOpcodeIndex savedNextLiteralIndex savedLastDumpedLiteralIndex'
  	classVariableNames: ''
  	poolDictionaries: 'CogCompilationConstants CogRTLOpcodes'
  	category: 'VMMaker-JIT'!
  
  !OutOfLineLiteralsManager commentStamp: 'eem 6/7/2015 12:10' prior: 0!
  An OutOfLineLiteralsManager manages the dumping of literals for backends that wat to keep literals out-of-line, accessed by pc-relative addressing.
  
  Instance Variables
  	cogit:		<Cogit>!

Item was added:
+ ----- Method: OutOfLineLiteralsManager class>>isNonArgumentImplicitReceiverVariableName: (in category 'translation') -----
+ isNonArgumentImplicitReceiverVariableName: aString
+ 	^Cogit isNonArgumentImplicitReceiverVariableName: aString!

Item was changed:
  ----- Method: OutOfLineLiteralsManager>>cogit: (in category 'initialization') -----
  cogit: aCogit
  	<doNotGenerate>
  	cogit := aCogit.
  	objectMemory := aCogit objectMemory.
+ 	objectRepresentation := aCogit objectRepresentation.
  	literalsSize := 0!

Item was added:
+ ----- Method: OutOfLineLiteralsManager>>literalBytesFollowingBranchInClosedPIC (in category 'garbage collection') -----
+ literalBytesFollowingBranchInClosedPIC
+ 	<inline: true>
+ 	"With Spur the class tag is always 32-bits and the literal is bytesPerOop.
+ 	 With V3 the class and literal are both bytesPerOop."
+ 	^objectRepresentation inlineCacheTagsMayBeObjects
+ 		ifTrue: [objectMemory bytesPerOop * 2]
+ 		ifFalse: [objectMemory bytesPerOop + 4]!

Item was added:
+ ----- Method: OutOfLineLiteralsManager>>literalBytesFollowingJumpInClosedPIC (in category 'garbage collection') -----
+ literalBytesFollowingJumpInClosedPIC
+ 	<inline: true>
+ 	^objectMemory bytesPerOop!

Item was changed:
  ----- Method: OutOfLineLiteralsManager>>literalInstructionAt: (in category 'compile abstract instructions') -----
  literalInstructionAt: index
  	<cmacro: '(index) (&literals[index])'>
+ 	<returnTypeC: #'AbstractInstruction *'>
  	^(literals at: index)
  		ifNil: [literals at: index put: (CogCompilerClass for: cogit)]
  		ifNotNil: [:litInst| litInst]!

Item was changed:
  ----- Method: OutOfLineLiteralsManager>>literalInstructionInRange: (in category 'testing') -----
  literalInstructionInRange: litInst
+ 	"A literal is in range if its opcode index is within outOfLineLiteralOpcodeLimit,
+ 	 or if its index has yet to be assigned."
+ 	<var: 'litInst' type: #'AbstractInstruction *'>
- 	"A literal is in range if its opcode index is within outOfLineLiteralOpcodeLimit, or if
- 	 its index has yet to be assigned."
  	| opcodeIdx |
  	opcodeIdx := litInst literalOpcodeIndex.
  	^opcodeIdx asInteger < 0
  	  or: [self assert: cogit getOpcodeIndex >= opcodeIdx.
  		cogit getOpcodeIndex - opcodeIdx < cogit backEnd outOfLineLiteralOpcodeLimit]!



More information about the Vm-dev mailing list