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

commits at source.squeak.org commits at source.squeak.org
Thu Jun 11 01:13:02 UTC 2015


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

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

Name: VMMaker.oscog-eem.1346
Author: eem
Time: 10 June 2015, 6:11:01.157 pm
UUID: 899ace24-f7ff-42f5-9652-f95e532a1bb8
Ancestors: VMMaker.oscog-eem.1345

Cogit:
Move annotations into instructions, where they sit
more naturally anyway.  But doing so makes it trivial
to move annotations from the instructions referencing
out-of-line literals to the literals themselves.
Hence nuke CogInstructionAnnotation.

Update usesOutOfLineLiteral to reflect the changes
in computeMaximumSizes & dispatchConcretize to
be accurate in identifying insttructions that use oolls

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

Item was changed:
  ----- Method: CogARMCompiler class>>filteredInstVarNames (in category 'translation') -----
  filteredInstVarNames
  	"Edit such that conditionOrNil is amongst the char size vars opcode machineCodeSize and maxSize."
  	^(super filteredInstVarNames copyWithout: 'conditionOrNil')
+ 		copyReplaceFrom: 5 to: 4 with: #('conditionOrNil')!
- 		copyReplaceFrom: 4 to: 3 with: #('conditionOrNil')!

Item was removed:
- ----- Method: CogARMCompiler class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
- instVarNamesAndTypesForTranslationDo: aBinaryBlock
- 	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in an AbstractInstruction struct."
- 	"{CogAbstractInstruction. CogIA32Compiler. CogARMCompiler} do:
- 		[:c| Transcript print: c; cr. c printTypedefOn: Transcript]"
- 	(self filteredInstVarNames copyWithout: 'machineCode'), #('machineCode') do:
- 		[:ivn|
- 		ivn ~= 'bcpc' ifTrue:
- 			[aBinaryBlock
- 				value: ivn
- 				value: (ivn caseOf: {
- 							['address']			-> [#'unsigned long'].
- 							['machineCode']	-> [{#'unsigned long'. '[', self basicNew machineCodeWords printString, ']'}].
- 							['operands']		-> [{#'unsigned long'. '[', NumOperands, ']'}].
- 							['dependent']		-> ['struct _AbstractInstruction *']}
- 						otherwise:
- 							[#'unsigned char'])]]!

Item was added:
+ ----- Method: CogARMCompiler class>>machineCodeDeclaration (in category 'translation') -----
+ machineCodeDeclaration
+ 	"Answer the declaration for the machineCode array."
+ 	^{#'unsigned long'. '[', self basicNew machineCodeWords printString, ']'}!

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]]].
- 											[self rotateable8bitImmediate: (operands at: 0)
- 												ifTrue: [:r :i| 4]
- 												ifFalse:
- 													[| val invVal |
- 													invVal := (val := operands at: 0) < 0 ifTrue: [-1 - val] ifFalse: [val bitInvert32].
- 													self rotateable8bitImmediate: invVal
- 														ifTrue: [:r :i| 4]
- 														ifFalse: [self literalLoadInstructionBytes]]]].
  		[MoveCwR]				-> [^self literalLoadInstructionBytes = 4
  										ifTrue: [self literalLoadInstructionBytes]
  										ifFalse:
  											[((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: (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 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]]].
- 											[self rotateable8bitImmediate: (operands at: 0)
- 												ifTrue: [:r :i| 8]
- 												ifFalse:
- 													[| val invVal |
- 													invVal := (val := operands at: 0) < 0 ifTrue: [-1 - val] ifFalse: [val bitInvert32].
- 													self rotateable8bitImmediate: invVal
- 														ifTrue: [:r :i| 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>>concretizePushCq (in category 'generate machine code - concretize') -----
  concretizePushCq
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
+ 	| word instrOffset |
- 	| word instrOffset|
  	word := operands at: 0.
  	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]).
- 		rotateable8bitImmediate: word 
- 		ifTrue: [:rot :immediate |
- 			self machineCodeAt: 0 put: (self mov: ConcreteIPReg imm: immediate ror: rot).
  			instrOffset := 4]
+ 		ifFalse:
+ 			[instrOffset := self moveCw: word intoR: ConcreteIPReg].
- 		ifFalse:[|invVal|
- 			word <0
- 				ifTrue:[invVal := -1 - word]
- 				ifFalse:[invVal := word bitInvert32].
- 			self rotateable8bitImmediate: invVal
- 				ifTrue: [ :rot :immediate |
- 					self machineCodeAt: 0 put: (self mvn: ConcreteIPReg imm: immediate ror: rot).
- 					instrOffset := 4]
- 				ifFalse: [instrOffset := self moveCw: word intoR: ConcreteIPReg]].
  	self machineCodeAt: instrOffset put: (self pushR: ConcreteIPReg).
  	^machineCodeSize := instrOffset + 4!

Item was changed:
  VMStructType subclass: #CogAbstractInstruction
+ 	instanceVariableNames: 'opcode machineCodeSize maxSize annotation machineCode operands address dependent cogit objectMemory bcpc'
- 	instanceVariableNames: 'opcode machineCodeSize maxSize machineCode operands address dependent cogit objectMemory bcpc'
  	classVariableNames: 'NumOperands'
  	poolDictionaries: 'CogCompilationConstants CogRTLOpcodes'
  	category: 'VMMaker-JIT'!
  
  !CogAbstractInstruction commentStamp: 'eem 4/21/2015 09:12' prior: 0!
  I am an abstract instruction generated by the Cogit.  I am subsequently concretized to machine code for the current processor.  A sequence of concretized CogAbstractInstructions are concatenated to form the code for a CogMethod.  I am an abstract class.  My concrete subclasses concretize to the machine code of a specific processor.
  
  Instance Variables
  	address:			<Integer>
  	bcpc:				<Integer>
  	cogit:				<Cogit>
  	dependent:			<AbstractInstruction|nil>
  	machineCode:		<CArray on: (ByteArray|Array)>
  	machineCodeSize:	<Integer>
  	maxSize:			<Integer>
  	objectMemory:		<NewCoObjectMemory|SpurCoMemoryManager etc>
  	opcode:			<Integer>
  	operands:			<CArray on: Array>
  
  address
  	- the address at which the instruction will be generated
  
  bcpc
  	- the bytecode pc for which the instruction was generated; simulation only
  
  cogit
  	- the Cogit assembling the receiver; simulation only
  
  dependent
  	- a reference to another instruction which depends on the receiver, if any; in C this is a pointer
  
  machineCode
  	- the array of machine code the receiver generates when concretized
  
  machineCodeSize
  	- the size of machineCode in bytes
  
  maxSize
  	- the maximum size of machine code that the current instruction will generate, in bytes
  
  objectMemory
  	- the memory manager for the system; simulation only
  
  opcode
  	- the opcode for the receiver which defines which abstract opcode it represents; see CogRTLOpcodes class>>initialize and CogAbstractInstruction subclass initialize methods
  
  operands
  	- the array containing any operands the instruction may have; the opcode defines implicitly how many operands are consdered!

Item was changed:
  ----- Method: CogAbstractInstruction class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in an AbstractInstruction struct."
  	"{CogAbstractInstruction. CogIA32Compiler. CogARMCompiler} do:
  		[:c| Transcript print: c; cr. c printTypedefOn: Transcript]"
- 	| machineCodeBytes |
- 	machineCodeBytes := self ==  CogAbstractInstruction
- 								ifTrue: [0]
- 								ifFalse: [self basicNew machineCodeBytes].
  	(self filteredInstVarNames copyWithout: 'machineCode'), #('machineCode') do:
  		[:ivn|
  		ivn ~= 'bcpc' ifTrue:
  			[aBinaryBlock
  				value: ivn
  				value: (ivn caseOf: {
  							['address']			-> [#'unsigned long'].
+ 							['machineCode']	-> [self machineCodeDeclaration].
- 							['machineCode']	-> [{#'unsigned char'. '[', machineCodeBytes printString, ']'}].
  							['operands']		-> [{#'unsigned long'. '[', NumOperands, ']'}].
  							['dependent']		-> ['struct _AbstractInstruction *']}
  						otherwise:
  							[#'unsigned char'])]]!

Item was added:
+ ----- Method: CogAbstractInstruction class>>machineCodeDeclaration (in category 'translation') -----
+ machineCodeDeclaration
+ 	"Answer a dummy declaration.  Subclasses will override to provgide the real one."
+ 	^#(#'unsigned char' '[4]')!

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

Item was added:
+ ----- Method: CogAbstractInstruction>>annotation: (in category 'accessing') -----
+ annotation: aByte
+ 	^annotation := aByte!

Item was added:
+ ----- Method: CogIA32Compiler class>>machineCodeDeclaration (in category 'translation') -----
+ machineCodeDeclaration
+ 	"Answer the declaration for the machineCode array."
+ 	^{#'unsigned char'. '[', self basicNew machineCodeBytes printString, ']'}!

Item was removed:
- VMStructType subclass: #CogInstructionAnnotation
- 	instanceVariableNames: 'annotation instruction'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-JIT'!
- 
- !CogInstructionAnnotation commentStamp: '<historical>' prior: 0!
- I am an annotation for a specific generated instruction.  I add information such as "this is an instruction corresponding to a bytecode pc", "this is an instruction containing an object reference", etc.!

Item was removed:
- ----- Method: CogInstructionAnnotation class>>byteSizeForSimulator: (in category 'simulation only') -----
- byteSizeForSimulator: aVMClass
- 	"Answer an approximation of the byte size of an AbstractInstruction struct.
- 	 This is for estimating the alloca in allocateOpcodes:bytecodes:ifFail:"
- 	^self instSize * (aVMClass sizeof: #'void *')!

Item was removed:
- ----- Method: CogInstructionAnnotation class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
- instVarNamesAndTypesForTranslationDo: aBinaryBlock
- 	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a CogInstructionAnnotation struct."
- 
- 	self allInstVarNames do:
- 		[:ivn|
- 		aBinaryBlock
- 			value: ivn
- 			value: (ivn = 'instruction'
- 					ifTrue: [#'AbstractInstruction *']
- 					ifFalse: [#sqInt])]!

Item was removed:
- ----- Method: CogInstructionAnnotation class>>structTypeName (in category 'translation') -----
- structTypeName
- 	^self name allButFirst: 3 "Drop initial Cog"!

Item was removed:
- ----- Method: CogInstructionAnnotation>>annotation (in category 'accessing') -----
- annotation
- 	"Answer the value of annotation"
- 
- 	^ annotation!

Item was removed:
- ----- Method: CogInstructionAnnotation>>annotation: (in category 'accessing') -----
- annotation: anObject
- 	"Set the value of annotation"
- 
- 	annotation := anObject!

Item was removed:
- ----- Method: CogInstructionAnnotation>>instruction (in category 'accessing') -----
- instruction
- 	"Answer the value of instruction"
- 	<returnTypeC: #'AbstractInstruction *'>
- 	^instruction!

Item was removed:
- ----- Method: CogInstructionAnnotation>>instruction: (in category 'accessing') -----
- instruction: anObject
- 	"Set the value of instruction"
- 
- 	instruction := anObject!

Item was removed:
- ----- Method: CogInstructionAnnotation>>printStateOn: (in category 'printing') -----
- printStateOn: aStream
- 	<doNotGenerate>
- 	annotation ifNotNil:
- 		[aStream
- 			space; nextPut: $(;
- 			nextPutAll: (Cogit annotationConstantNames at: annotation + 1);
- 			space; print: instruction; nextPut: $)]!

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 changed:
  ----- Method: CogOutOfLineLiteralsARMCompiler>>sizePCDependentInstructionAt: (in category 'generate machine code') -----
  sizePCDependentInstructionAt: eventualAbsoluteAddress
  	"Size a jump and set its address.  The target may be another instruction
  	 or an absolute address.  On entry the address inst var holds our virtual
  	 address. On exit address is set to eventualAbsoluteAddress, which is
  	 where this instruction will be output.  The span of a jump to a following
  	 instruction is therefore between that instruction's address and this
  	 instruction's address ((which are both still their virtual addresses), but the
  	 span of a jump to a preceeding instruction or to an absolute address is
  	 between that instruction's address (which by now is its eventual absolute
  	 address) or absolute address and eventualAbsoluteAddress.
  
+ 	 ARM is simple; the 26-bit call/jump range means no short jumps.  This
+ 	 routine only has to determine the targets of jumps, not determine sizes.
- 	 ARM is simple; the 26-bit call/jump range means no short jumps.  This routine
- 	 only has to determine the targets of jumps, not determine sizes."
  
+ 	 This version also deals with out-of-line literals.  If this is the real literal,
+ 	 update the stand-in in literalsManager with the address (because instructions
+ 	 referring to the literal are referring to the stand-in).  If this is annotated with
+ 	 IsObjectReference transfer the annotation to the stand-in, whence it will be
+ 	 transferred to the real literal, simplifying update of literals."
+ 
  	opcode = AlignmentNops ifTrue:
  		[| alignment |
  		 address := eventualAbsoluteAddress.
  		 alignment := operands at: 0.
  		 ^machineCodeSize := (eventualAbsoluteAddress + (alignment - 1) bitAnd: alignment negated)
  							   - eventualAbsoluteAddress].
  	self assert: (self isJump or: [opcode = Call or: [opcode = CallFull
  				or: [dependent notNil and: [dependent opcode = Literal]]]]).
  	self isJump ifTrue: [self resolveJumpTarget].
  	address := eventualAbsoluteAddress.
+ 	(dependent notNil and: [dependent opcode = Literal]) ifTrue:
+ 		[opcode = Literal ifTrue:
+ 			[dependent address: address].
+ 		 annotation = cogit getIsObjectReference ifTrue:
+ 			[dependent annotation: annotation.
+ 			 annotation := nil]].
- 	(opcode = Literal and: [dependent notNil and: [dependent opcode = Literal]]) ifTrue:
- 		[dependent address: address].
  	^machineCodeSize := maxSize!

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]].
- 		[AndCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
- 		[AndCqRR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
- 		[CmpCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| 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]].
- 		[SubCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| 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]].
- 		[XorCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| 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: (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: (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:
  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 primInvokeLabel 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'
- 	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 primInvokeLabel 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 annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex 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 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>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
  	ProcessorClass ifNil:
  		[Cogit initializeMiscConstants].
  	^{	CogMethodZone.
  		CogBlockStart.
  		CogBytecodeDescriptor.
  		CogBytecodeFixup.
- 		CogInstructionAnnotation.
  		CogPrimitiveDescriptor.
  		CogBlockMethod.
  		CogMethod },
  	(self activeCompilerClass withAllSuperclasses copyUpThrough: CogAbstractInstruction),
  	((options at: #NewspeakVM ifAbsent: [false])
  		ifTrue: [{NewspeakCogMethod. NSSendCache}]
  		ifFalse: [#()])!

Item was changed:
  ----- Method: Cogit>>allocateOpcodes:bytecodes: (in category 'initialization') -----
  allocateOpcodes: numberOfAbstractOpcodes bytecodes: numberOfBytecodes
  	"Allocate the various arrays needed to compile abstract instructions.
  	 This needs to be a macro since the arrays are alloca'ed (stack allocated)
  	 to ensure their being freed when compilation is done.
  	 Notionally we only need as many fixups as there are bytecodes.  But we
  	 reuse fixups to record pc-dependent instructions in generateInstructionsAt:
  	 and so need at least as many as there are abstract opcodes.
  
  	 N.B. We do one single alloca to save embarrassing C optimizers that
  	 generate incorrect code as both gcc and the intel compiler do on x86."
  	<cmacro: '(numberOfAbstractOpcodes,numberOfBytecodes) do { \
  		int opcodeSize = sizeof(AbstractInstruction) * (numAbstractOpcodes = (numberOfAbstractOpcodes)); \
  		int fixupSize = sizeof(BytecodeFixup) * numAbstractOpcodes; \
+ 		abstractOpcodes = alloca(opcodeSize + fixupSize); \
- 		int annotationSize = sizeof(InstructionAnnotation) * ((numAbstractOpcodes + 3) / 4); \
- 		abstractOpcodes = alloca(opcodeSize + fixupSize + annotationSize); \
  		bzero(abstractOpcodes, opcodeSize + fixupSize); \
  		fixups = (void *)((char *)abstractOpcodes + opcodeSize); \
+ 		opcodeIndex = labelCounter = 0; \
- 		annotations = (void *)((char *)fixups + fixupSize); \
- 		opcodeIndex = labelCounter = annotationIndex = 0; \
  } while (0)'>
  	numAbstractOpcodes := numberOfAbstractOpcodes.
  	abstractOpcodes := CArrayAccessor on:
  						((1 to: numAbstractOpcodes) collect:
  							[:ign| CogCompilerClass for: self]).
  	fixups := CArrayAccessor on:
  						((1 to: numAbstractOpcodes) collect:
  							[:ign| self bytecodeFixupClass new]).
+ 	opcodeIndex := labelCounter := 0!
- 	annotations := CArrayAccessor on:
- 						((1 to: numAbstractOpcodes + 3 // 4) collect:
- 							[:ign| CogInstructionAnnotation new]).
- 	opcodeIndex := labelCounter := annotationIndex := 0!

Item was changed:
  ----- Method: Cogit>>allocateOpcodes:bytecodes:ifFail: (in category 'initialization') -----
  allocateOpcodes: numberOfAbstractOpcodes bytecodes: numberOfBytecodes ifFail: failBlock
  	"Allocate the various arrays needed to compile abstract instructions.
  	 This needs to be a macro since the arrays are alloca'ed (stack allocated)
  	 to ensure their being freed when compilation is done.
  	 Notionally we only need as many fixups as there are bytecodes.  But we
  	 reuse fixups to record pc-dependent instructions in generateInstructionsAt:
  	 and so need at least as many as there are abstract opcodes.
  
  	 N.B. We do one single alloca to save embarrassing C optimizers that
  	 generate incorrect code as both gcc and the intel compiler do on x86."
  	<cmacro: '(numberOfAbstractOpcodes,numberOfBytecodes,failBlock) do { \
  		int opcodeSize = sizeof(AbstractInstruction) * (numAbstractOpcodes = (numberOfAbstractOpcodes)); \
  		int fixupSize = sizeof(BytecodeFixup) * numAbstractOpcodes; \
+ 		int allocSize = opcodeSize + fixupSize; \
- 		int annotationSize = sizeof(InstructionAnnotation) * ((numAbstractOpcodes + 3) / 4); \
- 		int allocSize = opcodeSize + fixupSize + annotationSize; \
  		if (allocSize > MaxStackAllocSize) failBlock; \
  		abstractOpcodes = alloca(allocSize); \
  		bzero(abstractOpcodes, opcodeSize + fixupSize); \
  		fixups = (void *)((char *)abstractOpcodes + opcodeSize); \
+ 		opcodeIndex = labelCounter = 0; \
- 		annotations = (void *)((char *)fixups + fixupSize); \
- 		opcodeIndex = labelCounter = annotationIndex = 0; \
  } while (0)'>
+ 	| opcodeSize fixupSize allocSize |
- 	| opcodeSize fixupSize annotationSize allocSize |
  	opcodeSize := (self sizeof: CogAbstractInstruction) * numberOfAbstractOpcodes.
  	fixupSize := (self sizeof: CogBytecodeFixup) * numberOfAbstractOpcodes.
+ 	allocSize := opcodeSize + fixupSize.
- 	annotationSize := (self sizeof: CogInstructionAnnotation) * ((numberOfAbstractOpcodes + 3) / 4).
- 	allocSize := opcodeSize + fixupSize + annotationSize.
  	allocSize > MaxStackAllocSize ifTrue: [^failBlock value].
  	numAbstractOpcodes := numberOfAbstractOpcodes.
  	abstractOpcodes := CArrayAccessor on:
  						((1 to: numAbstractOpcodes) collect:
  							[:ign| CogCompilerClass for: self]).
  	fixups := CArrayAccessor on:
  						((1 to: numAbstractOpcodes) collect:
  							[:ign| self bytecodeFixupClass new]).
+ 	opcodeIndex := labelCounter := 0!
- 	annotations := CArrayAccessor on:
- 						((1 to: numAbstractOpcodes + 3 // 4) collect:
- 							[:ign| CogInstructionAnnotation new]).
- 	opcodeIndex := labelCounter := annotationIndex := 0!

Item was changed:
  ----- Method: Cogit>>annotate:objRef: (in category 'method map') -----
  annotate: abstractInstruction objRef: anOop
  	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	<returnTypeC: #'AbstractInstruction *'>
  	(objectRepresentation shouldAnnotateObjectReference: anOop) ifTrue:
  		[(objectMemory isYoungObject: anOop) ifTrue:
  			[hasYoungReferent := true].
+ 		 abstractInstruction annotation: IsObjectReference].
- 		^self annotate: abstractInstruction with: IsObjectReference].
  	^abstractInstruction!

Item was removed:
- ----- Method: Cogit>>annotate:with: (in category 'method map') -----
- annotate: abstractInstruction with: annotationFlag "<Integer>"
- 	<var: #abstractInstruction type: #'AbstractInstruction *'>
- 	<returnTypeC: #'AbstractInstruction *'>
- 	| annotation |
- 	<var: #annotation type: #'InstructionAnnotation *'>
- 	annotation := self addressOf: (annotations at: annotationIndex).
- 	annotationIndex := annotationIndex + 1.
- 	annotation
- 		instruction: abstractInstruction;
- 		annotation: annotationFlag.
- 	^abstractInstruction!

Item was changed:
  ----- Method: Cogit>>annotateAbsolutePCRef: (in category 'method map') -----
  annotateAbsolutePCRef: abstractInstruction
  	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	<returnTypeC: #'AbstractInstruction *'>
  	<inline: true>
+ 	abstractInstruction annotation: IsAbsPCReference.
+ 	^abstractInstruction!
- 	^self annotate: abstractInstruction with: IsAbsPCReference!

Item was changed:
  ----- Method: Cogit>>annotateBytecode: (in category 'method map') -----
  annotateBytecode: abstractInstruction
  	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	<returnTypeC: #'AbstractInstruction *'>
  	<inline: true>
+ 	abstractInstruction annotation: HasBytecodePC.
+ 	^abstractInstruction!
- 	^self annotate: abstractInstruction with: HasBytecodePC!

Item was changed:
  ----- Method: Cogit>>annotateCall: (in category 'method map') -----
  annotateCall: abstractInstruction
  	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	<returnTypeC: #'AbstractInstruction *'>
  	<inline: true>
+ 	abstractInstruction annotation: IsRelativeCall.
+ 	^abstractInstruction!
- 	^self annotate: abstractInstruction with: IsRelativeCall!

Item was changed:
  ----- Method: Cogit>>annotateNewspeakSend: (in category 'method map') -----
  annotateNewspeakSend: abstractInstruction
  	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	<returnTypeC: #'AbstractInstruction *'>
  	<inline: true>
+ 	abstractInstruction annotation: IsNSSendCall.
+ 	^abstractInstruction!
- 	^self annotate: abstractInstruction with: IsNSSendCall!

Item was changed:
  ----- Method: Cogit>>generateMapAt:start: (in category 'method map') -----
  generateMapAt: addressOrNull start: startAddress
  	"Generate the method map at addressrNull (or compute it if addressOrNull is null).
  	 Answer the length of the map in byes.  Each entry in the map is in two parts.  In the
  	 least signficant bits are a displacement of how far from the start or previous entry,
  	 unless it is an IsAnnotationExtension byte, in which case those bits are the extension.
  	 In the most signficant bits are the type of annotation at the point reached.  A null
  	 byte ends the map."
  	| length location |
+ 	<var: #instruction type: #'AbstractInstruction *'>
- 	<var: #annotation type: #'InstructionAnnotation *'>
  	length := 0.
  	location := startAddress.
+ 	0 to: opcodeIndex - 1 do:
+ 		[:i| | instruction mcpc delta maxDelta mapEntry |
+ 		instruction := self abstractInstructionAt: i.
+ 		instruction annotation ifNotNil:
+ 			[:annotation|
+ 			 self flag: 'if this is moved into e.g. CogAbstractInstruction>>annotationAddress then e.g. a push const can annotate the lit synth instr, not the reg push'.
+ 			 mcpc := instruction address + instruction machineCodeSize.
+ 			 [(delta := mcpc - location / backEnd codeGranularity) > DisplacementMask] whileTrue:
+ 				[maxDelta := (delta min: MaxX2NDisplacement) bitClear: DisplacementMask.
+ 				 self assert: maxDelta >> AnnotationShift <= DisplacementMask.
+ 				 addressOrNull ifNotNil:
+ 					[objectMemory
+ 						byteAt: addressOrNull - length
+ 						put: maxDelta >> AnnotationShift + DisplacementX2N.
+ 					 self traceMap: IsDisplacementX2N
+ 						instruction: instruction
+ 						byte: maxDelta >> AnnotationShift + DisplacementX2N
+ 						at: addressOrNull - length
+ 						for: mcpc].
+ 				 location := location + (maxDelta * backEnd codeGranularity).
+ 				 length := length + 1].
- 	0 to: annotationIndex - 1 do:
- 		[:i| | annotation mcpc delta maxDelta mapEntry |
- 		 annotation := self addressOf: (annotations at: i).
- 		 mcpc := annotation instruction address + annotation instruction machineCodeSize.
- 		 [(delta := mcpc - location / backEnd codeGranularity) > DisplacementMask] whileTrue:
- 			[maxDelta := (delta min: MaxX2NDisplacement) bitClear: DisplacementMask.
- 			 self assert: maxDelta >> AnnotationShift <= DisplacementMask.
  			 addressOrNull ifNotNil:
+ 				[mapEntry := delta + ((annotation min: IsSendCall) << AnnotationShift).
- 				[objectMemory
- 					byteAt: addressOrNull - length
- 					put: maxDelta >> AnnotationShift + DisplacementX2N.
- 				 self traceMap: IsDisplacementX2N
- 					  byte: maxDelta >> AnnotationShift + DisplacementX2N
- 					  at: addressOrNull - length
- 					  for: mcpc].
- 			 location := location + (maxDelta * backEnd codeGranularity).
- 			 length := length + 1].
- 		 addressOrNull ifNotNil:
- 			[mapEntry := delta + ((annotation annotation min: IsSendCall) << AnnotationShift).
- 			 objectMemory byteAt: addressOrNull - length put: mapEntry.
- 			 self traceMap: annotation
- 				  byte: mapEntry
- 				  at: addressOrNull - length
- 				  for: mcpc].
- 		 location := location + (delta * backEnd codeGranularity).
- 		 length := length + 1.
- 		 annotation annotation > IsSendCall ifTrue: "Add the necessary IsAnnotationExtension"
- 			[addressOrNull ifNotNil:
- 				[mapEntry := IsAnnotationExtension << AnnotationShift + (annotation annotation - IsSendCall).
  				 objectMemory byteAt: addressOrNull - length put: mapEntry.
  				 self traceMap: annotation
+ 					instruction: instruction
+ 					byte: mapEntry
+ 					at: addressOrNull - length
+ 					for: mcpc].
+ 			 location := location + (delta * backEnd codeGranularity).
+ 			 length := length + 1.
+ 			 annotation > IsSendCall ifTrue: "Add the necessary IsAnnotationExtension"
+ 				[addressOrNull ifNotNil:
+ 					[mapEntry := IsAnnotationExtension << AnnotationShift + (annotation - IsSendCall).
+ 					 objectMemory byteAt: addressOrNull - length put: mapEntry.
+ 					 self traceMap: annotation
+ 						instruction: instruction
+ 						byte: mapEntry
+ 						at: addressOrNull - length
+ 						for: mcpc].
+ 				 length := length + 1]]].
- 					  byte: mapEntry
- 					  at: addressOrNull - length
- 					  for: mcpc].
- 			 length := length + 1]].
  	addressOrNull ifNotNil:
  		[objectMemory byteAt: addressOrNull - length put: MapEnd.
  		 self traceMap: MapEnd
+ 			instruction: nil
+ 			byte: MapEnd
+ 			at: addressOrNull - length
+ 			for: 0].
- 			  byte: MapEnd
- 			  at: addressOrNull - length
- 			  for: 0].
  	^length + 1!

Item was added:
+ ----- Method: Cogit>>getIsObjectReference (in category 'method map') -----
+ getIsObjectReference
+ 	<cmacro: '() IsObjectReference'>
+ 	^IsObjectReference!

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:
- 	| annotation |
- 	<var: #annotation type: #'InstructionAnnotation *'>
- 	0 to: annotationIndex - 1 do:
- 		[:i|
- 		annotation := self addressOf: (annotations at: i).
- 		annotation 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 address + instruction machineCodeSize) asInteger.
+ 			 runtimeObjectRefIndex := runtimeObjectRefIndex + 1]]!
- 				put: (annotation instruction address + annotation instruction machineCodeSize) asInteger.
- 			 runtimeObjectRefIndex := runtimeObjectRefIndex + 1]].
- 	annotationIndex := 0!

Item was removed:
- ----- Method: Cogit>>traceMap:byte:at:for: (in category 'method map') -----
- traceMap: annotation byte: byte at: address for: mcpc
- 	<cmacro: '(ig,no,re,d) 0'>
- 	| s code bytecode |
- 	(compilationTrace anyMask: 16) ifTrue:
- 		[code := annotation isInteger ifTrue: [annotation] ifFalse: [annotation annotation].
- 		(s := coInterpreter transcript)
- 			ensureCr;
- 			print: code; nextPut: $/; nextPutAll: byte hex; space;
- 			nextPutAll: address hex; space; nextPutAll: mcpc hex; space;
- 			nextPutAll: (AnnotationConstantNames detect: [:name| (Cogit classPool at: name ifAbsent: []) = code]); cr; flush.
- 		(annotation isInteger not
- 		 and: [annotation instruction bcpc isInteger]) ifTrue:
- 			[s tab; print: annotation instruction bcpc; nextPut: $/.
- 			 annotation instruction bcpc printOn: s base: 16.
- 			 s space.
- 			 annotation instruction printStateOn: s.
- 			 s space.
- 			 bytecode := objectMemory fetchByte: annotation instruction bcpc ofObject: methodObj.
- 			 bytecode := bytecode + (self bytecodeSetOffsetForHeader: (objectMemory methodHeaderOf: methodObj)).
- 			 (self generatorAt: bytecode) printStateOn: s.
- 			 s cr; flush]]!

Item was added:
+ ----- Method: Cogit>>traceMap:instruction:byte:at:for: (in category 'method map') -----
+ traceMap: annotation instruction: instruction byte: byte at: address for: mcpc
+ 	<cmacro: '(ig,no,r,e,d) 0'>
+ 	| s bytecode |
+ 	(compilationTrace anyMask: 16) ifTrue:
+ 		[(s := coInterpreter transcript)
+ 			ensureCr;
+ 			print: annotation; nextPut: $/; nextPutAll: byte hex; space;
+ 			nextPutAll: address hex; space; nextPutAll: mcpc hex; space;
+ 			nextPutAll: (AnnotationConstantNames detect: [:name| (Cogit classPool at: name ifAbsent: []) = annotation]); cr; flush.
+ 		(instruction notNil
+ 		 and: [instruction bcpc isInteger]) ifTrue:
+ 			[s tab; print: instruction bcpc; nextPut: $/.
+ 			 instruction bcpc printOn: s base: 16.
+ 			 s space.
+ 			 instruction printStateOn: s.
+ 			 s space.
+ 			 bytecode := objectMemory fetchByte: instruction bcpc ofObject: methodObj.
+ 			 bytecode := bytecode + (self bytecodeSetOffsetForHeader: (objectMemory methodHeaderOf: methodObj)).
+ 			 (self generatorAt: bytecode) printStateOn: s.
+ 			 s cr; flush]]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSend:numArgs:sendTable: (in category 'bytecode generator support') -----
  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 MoveCw: selector R: ClassReg.
+ 	(self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1))) annotation: annotation.
- 	self annotate: (self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1)))
- 		with: annotation.
  	self PushR: ReceiverResultReg.
  	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>compileBlockBodies (in category 'compile abstract instructions') -----
  compileBlockBodies
  	"override to maintain counterIndex when recompiling blocks; sigh."
  	<inline: false>
  	| result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs savedNumTemps
+ 	  initialStackPtr initialOpcodeIndex initialCounterIndex initialIndexOfIRC |
- 	  initialStackPtr initialOpcodeIndex initialAnnotationIndex initialCounterIndex initialIndexOfIRC |
  	<var: #blockStart type: #'BlockStart *'>
  	self assert: blockCount > 0.
  	"scanBlock: in compileBlockEntry: sets both of these appropriately for each block."
  	savedNeedsFrame := needsFrame.
  	savedNumArgs := methodOrBlockNumArgs.
  	savedNumTemps := methodOrBlockNumTemps.
  	inBlock := true.
  	compiledBlocksCount := 0.
  	[compiledBlocksCount < blockCount] whileTrue:
  		[blockStart := self blockStartAt: compiledBlocksCount.
  		 self scanBlock: blockStart.
  		 initialOpcodeIndex := opcodeIndex.
- 		 initialAnnotationIndex := annotationIndex.
  		 initialCounterIndex := counterIndex.
  		 self cppIf: #NewspeakVM ifTrue:
  			[initialIndexOfIRC := indexOfIRC].
  		 [self compileBlockEntry: blockStart.
  		  initialStackPtr := simStackPtr.
  		  (result := self compileAbstractInstructionsFrom: blockStart startpc + (self pushNilSize: methodObj numInitialNils: blockStart numInitialNils)
  						through: blockStart startpc + blockStart span - 1) < 0 ifTrue:
  			[^result].
  		  "If the final simStackPtr is less than the initial simStackPtr then scanBlock: over-
  		   estimated the number of initial nils (because it assumed one or more pushNils to
  		   produce an operand were pushNils to initialize temps.  This is very rare, so
+ 		   compensate by checking, adjusting numInitialNils and recompiling the block body.
+ 		   N.B.  No need to reinitialize the literalsManager because it answers existing literals."
- 		   compensate by checking, adjusting numInitialNils and recompiling the block body."
  		  initialStackPtr = simStackPtr]
  			whileFalse:
  				[self assert: initialStackPtr > simStackPtr.
  				 blockStart numInitialNils: blockStart numInitialNils + simStackPtr - initialStackPtr.
  				 blockStart fakeHeader dependent: nil.
  				 self reinitializeFixupsFrom: blockStart startpc + blockStart numInitialNils
  					through: blockStart startpc + blockStart span - 1.
  				 self cCode: 'bzero(abstractOpcodes + initialOpcodeIndex,
  									(opcodeIndex - initialOpcodeIndex) * sizeof(AbstractInstruction))'
  					inSmalltalk: [initialOpcodeIndex to: opcodeIndex - 1 do:
  									[:i| abstractOpcodes at: i put: (CogCompilerClass for: self)]].
  				 opcodeIndex := initialOpcodeIndex.
- 				 annotationIndex := initialAnnotationIndex.
  				 counterIndex := initialCounterIndex.
  				 self cppIf: #NewspeakVM ifTrue:
  					[indexOfIRC := initialIndexOfIRC]].
  		compiledBlocksCount := compiledBlocksCount + 1].
  	needsFrame := savedNeedsFrame.
  	methodOrBlockNumArgs := savedNumArgs.
  	methodOrBlockNumTemps := savedNumTemps.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>compileBlockBodies (in category 'compile abstract instructions') -----
  compileBlockBodies
  	<inline: false>
  	| result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs savedNumTemps
+ 	  initialStackPtr initialOpcodeIndex initialIndexOfIRC |
- 	  initialStackPtr initialOpcodeIndex initialAnnotationIndex initialIndexOfIRC |
  	<var: #blockStart type: #'BlockStart *'>
  	self assert: blockCount > 0.
  	"scanBlock: in compileBlockEntry: sets both of these appropriately for each block."
  	savedNeedsFrame := needsFrame.
  	savedNumArgs := methodOrBlockNumArgs.
  	savedNumTemps := methodOrBlockNumTemps.
  	inBlock := true.
  	compiledBlocksCount := 0.
  	[compiledBlocksCount < blockCount] whileTrue:
  		[blockStart := self blockStartAt: compiledBlocksCount.
  		 self scanBlock: blockStart.
  		 initialOpcodeIndex := opcodeIndex.
- 		 initialAnnotationIndex := annotationIndex.
  		 self cppIf: #NewspeakVM ifTrue:
  			[initialIndexOfIRC := indexOfIRC].
  		 [self compileBlockEntry: blockStart.
  		  initialStackPtr := simStackPtr.
  		  (result := self compileAbstractInstructionsFrom: blockStart startpc + (self pushNilSize: methodObj numInitialNils: blockStart numInitialNils)
  						through: blockStart startpc + blockStart span - 1) < 0 ifTrue:
  			[^result].
  		  "If the final simStackPtr is less than the initial simStackPtr then scanBlock: over-
  		   estimated the number of initial nils (because it assumed one or more pushNils to
  		   produce an operand were pushNils to initialize temps.  This is very rare, so
+ 		   compensate by checking, adjusting numInitialNils and recompiling the block body.
+ 		   N.B.  No need to reinitialize the literalsManager because it answers existing literals."
- 		   compensate by checking, adjusting numInitialNils and recompiling the block body."
  		  initialStackPtr = simStackPtr]
  			whileFalse:
  				[self assert: initialStackPtr > simStackPtr.
  				 blockStart numInitialNils: blockStart numInitialNils + simStackPtr - initialStackPtr.
  				 blockStart fakeHeader dependent: nil.
  				 self reinitializeFixupsFrom: blockStart startpc + blockStart numInitialNils
  					through: blockStart startpc + blockStart span - 1.
  				 self cCode: 'bzero(abstractOpcodes + initialOpcodeIndex,
  									(opcodeIndex - initialOpcodeIndex) * sizeof(AbstractInstruction))'
  					inSmalltalk: [initialOpcodeIndex to: opcodeIndex - 1 do:
  									[:i| abstractOpcodes at: i put: (CogCompilerClass for: self)]].
  				 opcodeIndex := initialOpcodeIndex.
- 				 annotationIndex := initialAnnotationIndex.
  				 self cppIf: #NewspeakVM ifTrue:
  					[indexOfIRC := initialIndexOfIRC]].
  		compiledBlocksCount := compiledBlocksCount + 1].
  	needsFrame := savedNeedsFrame.
  	methodOrBlockNumArgs := savedNumArgs.
  	methodOrBlockNumTemps := savedNumTemps.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genMarshalledSend:numArgs:sendTable: (in category 'bytecode generator support') -----
  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 MoveCw: selector R: ClassReg.
+ 	(self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1))) annotation: annotation.
- 	self annotate: (self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1)))
- 		with: annotation.
  	optStatus isReceiverResultRegLive: false.
  	^self ssPushRegister: ReceiverResultReg!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>prevInstIsPCAnnotated (in category 'testing') -----
  prevInstIsPCAnnotated
+ 	| prevIndex prevInst |
- 	| annotation prevIndex prevInst |
- 	<var: #annotation type: #'InstructionAnnotation *'>
  	<var: #prevInst type: #'AbstractInstruction *'>
+ 	opcodeIndex > 0 ifFalse:
- 	annotationIndex > 0 ifFalse:
  		[^false].
- 	annotation := self addressOf: (annotations at: annotationIndex - 1).
- 	(self isPCMappedAnnotation: annotation annotation) ifFalse:
- 		[^false].
  	prevIndex := opcodeIndex - 1.
  	[prevIndex <= 0 ifTrue: [^false].
  	 prevInst := self abstractInstructionAt: prevIndex.
+ 	 (self isPCMappedAnnotation: (prevInst annotation ifNil: [0])) ifTrue:
- 	 annotation instruction = prevInst ifTrue:
  		[^true].
  	 prevInst opcode = Label]
  		whileTrue:
  			[prevIndex := prevIndex - 1].
  	^false!



More information about the Vm-dev mailing list