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

commits at source.squeak.org commits at source.squeak.org
Fri Jan 8 07:03:00 UTC 2021


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

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

Name: VMMaker.oscog-eem.2930
Author: eem
Time: 7 January 2021, 11:02:49.506067 pm
UUID: 3755defc-b655-43b4-bb4e-467bae846680
Ancestors: VMMaker.oscog-eem.2929

Time to bring the ARMv8 work back into Cog/VMMaker under full MIT.

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

Item was added:
+ CogAbstractInstruction subclass: #CogARMv8Compiler
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'AL ArithmeticAdd ArithmeticAddS ArithmeticSub ArithmeticSubS CASAL CArg0Reg CArg1Reg CArg2Reg CArg3Reg CArg4Reg CArg5Reg CArg6Reg CBNZ CBZ CC CCMPNE CLREX CS CSET D0 D1 D10 D11 D12 D13 D14 D15 D16 D17 D18 D19 D2 D20 D21 D22 D23 D24 D25 D26 D27 D28 D29 D3 D30 D31 D4 D5 D6 D7 D8 D9 DC DC_CISW DC_CIVAC DC_CSW DC_CVAC DC_CVAU DC_ISW DC_IVAC DC_ZVA DMB DSB DSB_ALL DSB_ALLSY DSB_ISH DSB_NSH DSB_OSH DSB_READS DSB_SY DSB_WRITES DivRRR EQ FP GE GT HI IC IC_IALLU IC_IALLUIS IC_IVAU ISB LDAXR LE LR LS LT LogicalAnd LogicalAndS LogicalOr LogicalXor MI MRS_CTR_EL0 MRS_ID_AA64ISAR0_EL1 MSubRRR MoveAwRR MoveRRAw MulOverflowRRR MulRRR NE NativePopRR NativePushRR PL R0 R1 R10 R11 R12 R13 R14 R15 R16 R17 R18 R19 R2 R20 R21 R22 R23 R24 R25 R26 R27 R28 R29 R3 R30 R31 R4 R5 R6 R7 R8 R9 SMULHRRR SP STLR STLXR SXTB SXTH SXTW SXTX UXTB UXTH UXTW UXTX VC VS XZR'
+ 	poolDictionaries: 'ARMv8A64Opcodes'
+ 	category: 'VMMaker-JIT'!
+ CogARMv8Compiler class
+ 	instanceVariableNames: 'ctrEl0 idISAR0'!
+ 
+ !CogARMv8Compiler commentStamp: 'eem 1/7/2021 23:01' prior: 0!
+ I generate ARMv8 machine code instructions from CogAbstractInstructions with CogRTLOpcodes.
+ Here in "Arm ARM" refers to
+ 	Arm® Architecture Reference Manual
+ 	Armv8, for Armv8-A architecture profile
+ https://developer.arm.com/docs/ddi0487/latest/arm-architecture-reference-manual-armv8-for-armv8-a-architecture-profile
+ 
+ Some things to know about ARMv8 instructions:
+ Whether 31 in a register field implies the zero register or the SP register(s) depends on the specific instruction.
+ 
+ C3.2.1 Load/Store register
+ If a Load instruction specifies writeback and the register being loaded is also the base register,
+ then behavior is CONSTRAINED UNPREDICTABLE and one of the following behaviors must occur:
+ - The instruction is treated as UNDEFINED.
+ - The instruction is treated as a NOP.
+ - The instruction performs the load using the specified addressing mode and the base register
+   becomes UNKNOWN.  In addition, if an exception occurs during the execution of such an
+   instruction, the base address might be corrupted so that the instruction cannot be repeated.
+ If a Store instruction performs a writeback and the register that is stored is also the base register,
+ then behavior is CONSTRAINED UNPREDICTABLE and one of the following behaviors must occur:
+ - The instruction is treated as UNDEFINED.
+ - The instruction is treated as a NOP.
+ - The instruction performs the store to the designated register using the specified addressing
+   mode, but the value stored is UNKNOWN.!
+ CogARMv8Compiler class
+ 	instanceVariableNames: 'ctrEl0 idISAR0'!

Item was added:
+ ----- Method: CogARMv8Compiler class>>ISA (in category 'translation') -----
+ ISA
+ 	"Answer the name of the ISA the receiver implements."
+ 	^#ARMv8!

Item was added:
+ ----- Method: CogARMv8Compiler class>>VarBaseReg (in category 'accessing') -----
+ VarBaseReg
+ 	"Answer the number of the reg we use to hold the base address of CoInterpreter variables"
+ 	^VarBaseReg!

Item was added:
+ ----- Method: CogARMv8Compiler class>>ctrEl0 (in category 'accessing') -----
+ ctrEl0
+ 	^ctrEl0!

Item was added:
+ ----- Method: CogARMv8Compiler class>>declareCVarsIn: (in category 'translation') -----
+ declareCVarsIn: aCCodeGenerator
+ 	aCCodeGenerator
+ 		declareVar: 'ctrEl0' type: #usqIntptr_t;
+ 		declareVar: 'idISAR0' type: #usqIntptr_t!

Item was added:
+ ----- Method: CogARMv8Compiler class>>idISAR0 (in category 'accessing') -----
+ idISAR0
+ 	^idISAR0!

Item was added:
+ ----- Method: CogARMv8Compiler class>>identifyingPredefinedMacros (in category 'translation') -----
+ identifyingPredefinedMacros
+ 	^#('__arm64__' '__aarch64__' '__ARM_ARCH_ISA_A64' '__ARM_ARCH >= 8' 'ARM64' 'ARMv8') "The last two are probably bogus..."!

Item was added:
+ ----- Method: CogARMv8Compiler class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"Initialize various ARM64 instruction-related constants."
+ 	"self initialize"
+ 
+ 	"main registers; a minor complication in reading the doc.
+ 	ARM refer to the 64bit registers as X0...30 and use R0...30 to refer to the 32bit lower halves.
+ 	They also use a whole suite of names for the floating point/SIMD registers. See ARMARM DDI0487 B1.2.1 etc for the gory details.
+ 	Note that R30 (yes, yes, X30) is used as the link register and as such is not really a general purpose register. 
+ 	Also note that 31 in a general register field means R31, and that in most of these instructions R31 is the zero
+ 	register named XZR in ARM doc.  but in the rest of these instructions R31 the effective SP register.
+ 	XZR is a pseudo-register that always reads as 0 and writes to /dev/null.
+ 	And note that unlike the ARM32, there is no general purpose register for the PC; a big difference.
+ 	See ARMARM DDI0487 C1.2.5. wrt to both the lack of a PC register and the XZR/SP distinction."
+ 	
+ 	"and initialize most sets of variables that run from 0 to N - 1..."
+ 	#(	"General registers, 0 to 31. We stick with R0...30 to refer to the 64 bit general regs and D0...31 (note the extra reg here!!) for the FP/SIMD regs"
+ 		(R0 R1 R2 R3 R4 R5 R6 R7 R8 R9 R10 R11 R12 R13 R14 R15 R16 R17 R18 R19 R20 R21 R22 R23 R24 R25 R26 R27 R28 R29 R30 R31)
+ 		"Floating-point registers, 0 to 31"
+ 		(D0 D1 D2 D3 D4 D5 D6 D7 D8 D9 D10 D11 D12 D13 D14 D15 D16 D17 D18 D19 D20 D21 D22 D23 D24 D25 D26 D27 D28 D29 D30 D31)
+ 		"C argument registers, 0 to 6"
+ 		(CArg0Reg CArg1Reg CArg2Reg CArg3Reg CArg4Reg CArg5Reg CArg6Reg)
+ 		"Condition Codes 0 to 16. Note that cc=16rF is mapped back to AL in AARCH64. Generally it shouldn't be used."
+ 		(EQ NE CS CC MI PL VS VC HI LS GE LT GT LE AL)
+ 		"Logical Op Codes"
+ 		(LogicalAnd LogicalOr LogicalXor LogicalAndS)
+ 		"Arithmetic Opcodes"
+ 		"ADD (shifted register) on page C6-763			10001011
+ 		 ADDS (shifted register) on page C6-771		10101011
+ 		 CMN (shifted register) on page C6-854			10101011	Rd=XZR
+ 		 SUB (shifted register) on page C6-1313		11001011
+ 		 SUBS (shifted register) on page C6-1323		11101011
+ 		 CMP (shifted register) on page C6-860			11101011	Rd=XZR
+ 		 NEG (shifted register) on page C6-1114		11001011	Rn=XZR
+ 		 NEGS					on page C6-1116		11101011	Rn=XZR"
+ 		(ArithmeticAdd ArithmeticAddS ArithmeticSub ArithmeticSubS)
+ 		"Extension Methods "
+ 		(UXTB UXTH UXTW UXTX "a.k.a. LSL" SXTB SXTH SXTW SXTX)) do:
+ 		[:classVarNames|
+ 		 classVarNames doWithIndex:
+ 			[:k :v|
+ 			CogARMv8Compiler classPool at: k put: v - 1]].
+ 
+ 	SP := XZR := R31.
+ 	LR := R30.
+ 	FP := R29.
+ 
+ 	"DC variant selectors; see concretizeDataCacheControl"
+ 	DC_CISW := 13.
+ 	DC_CIVAC := 14.
+ 	DC_CSW := 15.
+ 	DC_CVAC := 16.
+ 	DC_CVAU := 19.
+ 	DC_ISW := 26.
+ 	DC_IVAC := 27.
+ 	DC_ZVA := 28.
+ 
+ 	"IC variant selectors; see concretizeInstructionCacheControl"
+ 	IC_IALLU := 0.
+ 	IC_IALLUIS := 1.
+ 	IC_IVAU := 2.
+ 
+ 	"DSB domains and types	C6.2.81 DSB	C6-891"
+ 	DSB_OSH := 0.		"Domain_OuterSharable"
+ 	DSB_NSH := 1.		"Domain_NonSharable"
+ 	DSB_ISH := 2.		"Domain_InnerSharable"
+ 	DSB_SY := 3.		"Domain_FullSystem"
+ 
+ 	DSB_ALLSY := 0.	"Types_All; domain = Domain_FullSystem"
+ 	DSB_READS := 1.	"Types_Reads"
+ 	DSB_WRITES := 2.	"Types_Writes"
+ 	DSB_ALL := 3.		"Types_All; domain ~= Domain_FullSystem"
+ 
+ 	"Specific instructions"
+ 	self
+ 		initializeSpecificOpcodes: #(MulRRR MulOverflowRRR SMULHRRR DivRRR MSubRRR "N.B. ARMv8 has MSUBRRRR but we only support three operands"
+ 									MoveAwRR MoveRRAw NativePushRR NativePopRR "these map to ldp/stp"
+ 									"Cache control and memory barrier"
+ 									"B2.3.7		Memory barriers	B2-124"
+ 									DC IC DMB DSB ISB MRS_CTR_EL0 MRS_ID_AA64ISAR0_EL1
+ 									CASAL CBNZ CBZ CCMPNE CSET CLREX LDAXR STLXR STLR)
+ 		in: thisContext method!

Item was added:
+ ----- Method: CogARMv8Compiler class>>initializeAbstractRegisters (in category 'class initialization') -----
+ initializeAbstractRegisters
+ 	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
+ 
+ 	"See Table 3-1 Register Usage in AArch64 SMC32, HVC32, SMC64, and HVC64 calls in
+ 	 SMC CALLING CONVENTION
+ 	 System Software on ARM® Platforms Document number: ARM DEN 0028B
+ 	 http://infocenter.arm.com/help/topic/com.arm.doc.den0028b/ARM_DEN0028B_SMC_Calling_Convention.pdf"
+ 
+ 	TempReg			:= R0.
+ 	ClassReg			:= R4.
+ 	ReceiverResultReg	:= R5.
+ 	SendNumArgsReg	:= R6.
+ 	Arg0Reg			:= R7.
+ 	Arg1Reg			:= R8.
+ 	RISCTempReg		:= R9.
+ 	SPReg				:= R16."we cannot easily use the native SP for SPReg because of the typical
+ 								 16-byte alignment restriction, enforced if the SA0 bit is set in SCTLR_EL1."
+ 						"X18/R18 is the Platform register; leave it be"
+ 	Extra0Reg			:= R19. "R18 through R28 are callee saved"
+ 	Extra1Reg			:= R20.
+ 	Extra2Reg			:= R21.
+ 	Extra3Reg			:= R22.
+ 	Extra4Reg			:= R23.
+ 	Extra5Reg			:= R24.
+ 	Extra6Reg			:= R25.
+ 	Extra7Reg			:= R26.
+ 	Extra8Reg			:= R27.
+ 	VarBaseReg			:= R28.	
+ 	FPReg				:= FP.	"a.k.a. R29"
+ 	LinkReg			:= LR.	"a.k.a. R30"
+ 	NativeSPReg		:= SP.	"a.k.a. R31; we cannot easily use the native SP for SPReg because of the typical
+ 								 16-byte alignment restriction, enforced if the SA0 bit is set in SCTLR_EL1."
+ 
+ 	ABICalleeSavedRegisterMask := (self registerMaskFor: 19 and: 20 and: 21 and: 22 and: 23)
+ 									 + (self registerMaskFor: 24 and: 25 and: 26 and: 27 and: 28).
+ 	ABICallerSavedRegisterMask := ((self registerMaskFor: 0 and: 1 and: 2 and: 3 and: 4 and: 5 and: 6 and: 7 and: 8 and: 9)
+ 									+ (self registerMaskFor: 10 and: 11 and: 12 and: 13 and: 14 and: 15 and: 16 and: 17)).
+ 	CallerSavedRegisterMask := ABICallerSavedRegisterMask
+ 									bitAnd: (self registerMaskFor: ClassReg and: ReceiverResultReg and: SendNumArgsReg and: Arg0Reg and: Arg1Reg).
+ 
+ 	NumRegisters := 32.
+ 
+ 	DPFPReg0			:= D0.
+ 	DPFPReg1			:= D1.
+ 	DPFPReg2			:= D2.
+ 	DPFPReg3			:= D3.
+ 	DPFPReg4			:= D4.
+ 	DPFPReg5			:= D5.
+ 	DPFPReg6			:= D6.
+ 	DPFPReg7			:= D7.
+ 	DPFPReg8			:= D8.
+ 	DPFPReg9			:= D9.
+ 	DPFPReg10			:= D10.
+ 	DPFPReg11			:= D11.
+ 	DPFPReg12			:= D12.
+ 	DPFPReg13			:= D13.
+ 	DPFPReg14			:= D14.
+ 	DPFPReg15			:= D15.
+ 
+ 	NumFloatRegisters := 32!

Item was added:
+ ----- Method: CogARMv8Compiler class>>literalsManagerClass (in category 'accessing class hierarchy') -----
+ literalsManagerClass
+ 	^OutOfLineLiteralsManagerFor64Bits!

Item was added:
+ ----- Method: CogARMv8Compiler class>>machineCodeDeclaration (in category 'translation') -----
+ machineCodeDeclaration
+ 	"Answer the declaration for the machineCode array.
+ 	 ARM instructions are 32-bits in length."
+ 	^{#'unsigned int'. '[', self basicNew machineCodeWords printString, ']'}!

Item was added:
+ ----- Method: CogARMv8Compiler class>>numTrampolines (in category 'trampoline support') -----
+ numTrampolines
+ 	^2 "ceFlushICache, and optionally ceFlushDCache"!

Item was added:
+ ----- Method: CogARMv8Compiler class>>preambleCCode (in category 'translation') -----
+ preambleCCode
+ 	^'#if __APPLE__ && __MACH__ /* Mac OS X */\#include <libkern/OSCacheControl.h>\#endif' withCRs!

Item was added:
+ ----- Method: CogARMv8Compiler class>>printFormatForOpcodeName: (in category 'debug printing') -----
+ printFormatForOpcodeName: opcodeName
+ 	"Answer a sequence of $r, $f or nil for the operands in the opcode, used for printing, where
+ 	 r => integer register, f => floating point register, and nil => numeric or address operand.
+ 	 Subclasses can override to provide a format string for their own private opcodes."
+ 	^opcodeName caseOf: {
+ 		[#CASAL]	-> ['rrr'].
+ 		[#CCMPNE]	-> ['rrc'].
+ 		[#CSET]	-> [#($r nil)].
+ 		[#LDAXR]	-> ['rr'].
+ 		[#STLXR]	-> ['rr'].
+ 		[#STLR]	-> ['rr'] }
+ 		otherwise: [#()]!

Item was added:
+ ----- Method: CogARMv8Compiler class>>specificOpcodes (in category 'class initialization') -----
+ specificOpcodes
+ 	"Answer the processor-specific opcodes for this class.
+ 	 They're all in an Array literal in the initialize method."
+ 	^(self class >> #initialize) literals detect: [:l| l isArray and: [l includes: #MulRR]]!

Item was added:
+ ----- Method: CogARMv8Compiler class>>wordSize (in category 'translation') -----
+ wordSize
+ 	"This is a 64-bit ISA"
+ 	^8!

Item was added:
+ ----- Method: CogARMv8Compiler>>addrn:rd:imm:shiftBy12: (in category 'generate machine code - support') -----
+ addrn: rn rd: rd imm: offset shiftBy12: shiftBy12
+ 	"C6.2.4 ADD (immediate) p761"
+ 	self assert: (offset between: 0 and: 1 << 12 - 1).
+ 	^2r10010001000000000000000000000000
+ 	+ (shiftBy12 ifTrue: [1 << 22] ifFalse: [0]) + (offset << 10) + (rn << 5) + rd!

Item was added:
+ ----- Method: CogARMv8Compiler>>assertCoherentCodeAt:delta: (in category 'debugging') -----
+ assertCoherentCodeAt: codeAddress delta: theCodeToDataDelta
+ 	<inline: #always>
+ 	| codeInstruction dataInstruction |
+ 	codeInstruction := self instructionAt: codeAddress.
+ 	dataInstruction := self instructionAt: codeAddress + theCodeToDataDelta.
+ 	self assert: codeInstruction = dataInstruction!

Item was added:
+ ----- Method: CogARMv8Compiler>>bl: (in category 'generate machine code - support') -----
+ bl: callDistance
+ 	"C6.2.33	BL		C6-812"
+ 	<inline: true>
+ 	self assert: (callDistance noMask: 3).
+ 	^2r100101 << 26 + (callDistance >>> 2 bitAnd: 1 << 26 - 1)!

Item was added:
+ ----- Method: CogARMv8Compiler>>brlink:reg: (in category 'generate machine code - support') -----
+ brlink: link reg: reg
+ 	^2r1101011000011111 << 16
+ 	+ (link ifTrue: [1 << 21] ifFalse: [0])
+ 	+ (reg << 5)!

Item was added:
+ ----- Method: CogARMv8Compiler>>byteReadsZeroExtend (in category 'testing') -----
+ byteReadsZeroExtend
+ 	"Answer if a byte read, via MoveAbR, MoveMbrR, or MoveXbrRR zero-extends
+ 	 into the full register, or merely affects the least significant 8 bits of the
+ 	 the register.  By default the code generator assumes that byte reads
+ 	 to not zero extend.  Note that byte reads /must not/ sign extend."
+ 	^true!

Item was added:
+ ----- Method: CogARMv8Compiler>>callInstructionByteSize (in category 'accessing') -----
+ callInstructionByteSize
+ 	"ARM calls and jumps span +/- 32 mb, more than enough for intra-zone calls and jumps."
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>callTargetFromReturnAddress: (in category 'inline cacheing') -----
+ callTargetFromReturnAddress: mcpc
+ 	| instr |
+ 	instr := self instructionAt: mcpc - 4.
+ 	"C6.2.26 	B		C6-799
+ 	 C6.2.33	BL		C6-812"
+ 	self assert: (instr >> 26 = 2r100101 or: [instr >> 26 = 2r101]).
+ 	^(self
+ 		cCode: [(instr bitAnd: 1 << 26 - 1) << 38]
+ 		inSmalltalk: [(instr bitAnd: 1 << 26 - 1) << 38 bitAnd: 1 << 64 - 1])
+ 			signedIntFromLong64 >>> 36 + (mcpc - 4)!

Item was added:
+ ----- Method: CogARMv8Compiler>>canDivQuoRem (in category 'testing') -----
+ canDivQuoRem
+ 	^true!

Item was added:
+ ----- Method: CogARMv8Compiler>>canMulRR (in category 'testing') -----
+ canMulRR
+ 	^true!

Item was added:
+ ----- Method: CogARMv8Compiler>>canMulRRDetectOverflow (in category 'testing') -----
+ canMulRRDetectOverflow
+ 	"ARMv8's intrinsic integer multiply doesn't set the overflow flag, so we
+ 	 need to generate additional code to implement overflow checking."
+ 	<inline: true>
+ 	^false!

Item was added:
+ ----- Method: CogARMv8Compiler>>canSignExtend (in category 'testing') -----
+ canSignExtend
+ 	"ARMv8 has native SignExtend8RR, SignExtend16RR, & SignExtend32RR."
+ 	<inline: true>
+ 	^true!

Item was added:
+ ----- Method: CogARMv8Compiler>>canZeroExtend (in category 'testing') -----
+ canZeroExtend
+ 	"x64 has native ZeroExtend8RR, ZeroExtend16RR, & ZeroExtend32RR."
+ 	<inline: true>
+ 	^true!

Item was added:
+ ----- Method: CogARMv8Compiler>>cmpC32RTempByteSize (in category 'accessing') -----
+ cmpC32RTempByteSize
+ 	^8!

Item was added:
+ ----- Method: CogARMv8Compiler>>codeGranularity (in category 'accessing') -----
+ codeGranularity
+ 	"Answer the size in bytes of a unit of machine code."
+ 	<inline: true>
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>computeJumpTargetOffset (in category 'generate machine code - support') -----
+ computeJumpTargetOffset
+ 	<inline: true>
+ 	| jumpTarget |
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
+ 	jumpTarget := self jumpTargetAddress.
+ 	^jumpTarget signedIntFromLong64 - address signedIntFromLong64!

Item was added:
+ ----- Method: CogARMv8Compiler>>computeLowBit: (in category 'generate machine code - support') -----
+ computeLowBit: nArg
+ 	" Answer the index of the low order one bit.
+ 		2r00101000 lowBit       (Answers: 4)
+ 		2r-00101000 lowBit      (Answers: 4)
+ 	  This is an implementation of SmallInteger>>lowBit"
+ 
+ 	| n result |
+ 	nArg = 0 ifTrue: [^0].
+ 	n := nArg.
+ 	result := 1.
+ 	[n noMask: 16rFF]
+ 		whileTrue:
+ 			[result := result + 8.
+ 			n := n bitShift: -8].
+ 	(n noMask: 16rF) ifTrue:
+ 		[result := result + 4.
+ 		 n := n bitShift: -4].
+ 	(n noMask: 16r3) ifTrue:
+ 		[result := result + 2.
+ 		 n := n bitShift: -2].
+ 	^(n anyMask: 1)
+ 		ifTrue: [result]
+ 		ifFalse: [result + 1]
+ 
+ 	"| me |
+ 	me := self basicNew.
+ 	(0 to: 65535) reject: [:i| i lowBit = (me lowBit: i)]"!

Item was added:
+ ----- Method: CogARMv8Compiler>>computeMaximumSize (in category 'generate machine code') -----
+ computeMaximumSize
+ 	"Because we don't use Thumb, each ARMv8 instruction has 4 bytes. Several
+ 	 abstract opcodes need more than one instruction. Instructions that refer to
+ 	 constants and/or literals depend on literals being stored out-of-line or encoded
+ 	 in immediate instruction fields (i.e. we only support OutOfLineLiteralsManager.
+ 
+ 	 N.B.  The ^N forms are to get around the old bytecode compiler's long branch
+ 	 limits which are exceeded when each case jumps around the otherwise."
+ 
+ 	opcode
+ 		caseOf: {
+ 		"Noops & Pseudo Ops"
+ 		[Label]						-> [^0].
+ 		[Literal]						-> [^self literalSize].
+ 		[AlignmentNops]			-> [^(operands at: 0) - 4].
+ 		"Control"
+ 		[CallFull]					-> [^8].
+ 		[JumpFull]					-> [^8].
+ 		[JumpLongZero]			-> [^8].
+ 		[JumpLongNonZero]		-> [^8].
+ 		[JumpMulOverflow]			-> [^8].
+ 		[JumpNoMulOverflow]		-> [^8].
+ 		[JumpFPOrdered]			-> [^8].
+ 		[JumpFPUnordered]		-> [^8].
+ 		[RetN]						-> [^(operands at: 0) = 0 ifTrue: [4] ifFalse: [8]].
+ 		[NativeRetN]				-> [^(operands at: 0) = 0 ifTrue: [4] ifFalse: [8]].
+ 
+ 		"Arithmetic"
+ 		[AddCqR]						-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
+ 												ifTrue: [:ign|4] ifFalse: [8]].
+ 		[AddCqRR]						-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
+ 												ifTrue: [:ign|4] ifFalse: [8]].
+ 		[CmpCqR]						-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
+ 												ifTrue: [:ign|4] ifFalse: [8]].
+ 		[SubCqR]						-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
+ 												ifTrue: [:ign|4] ifFalse: [8]].
+ 		[LoadEffectiveAddressMwrR]	-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
+ 												ifTrue: [:ign|4] ifFalse: [8]].
+ 		[AndCqR]					-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|4] ifFalse:[8]].
+ 		[AndCqRR]					-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|4] ifFalse:[8]].
+ 		[OrCqR]					-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|4] ifFalse:[8]].
+ 		[OrCqRR]					-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|4] ifFalse:[8]].
+ 		[TstCqR]					-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|4] ifFalse:[8]].
+ 		[XorCqR]					-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|4] ifFalse:[8]].
+ 		[AddCwR]					-> [^8].
+ 		[AndCwR]					-> [^8].
+ 		[CmpCwR]					-> [^8].
+ 		[CmpC32R]					-> [^8].
+ 		[OrCwR]					-> [^8].
+ 		[SubCwR]					-> [^8].
+ 		[XorCwR]					-> [^8].
+ 		[SubRR]					-> [^(operands at: 0) = SP ifTrue: [8] ifFalse: [4]].
+ 		[SubRRR]					-> [^(operands at: 0) = SP ifTrue: [8] ifFalse: [4]].
+ 
+ 		"ARMv8 Specific Arithmetic"
+ 		[MulOverflowRRR]			-> [^12].
+ 		"Data Movement"						
+ 		[MoveAwR]				-> [^((self isAddressRelativeToVarBase: (operands at: 0))
+ 									    or: [cogit addressIsInCurrentCompilation: (operands at: 0)])
+ 										ifTrue: [(operands at: 1) ~= SP ifTrue: [4] ifFalse: [8]]
+ 										ifFalse: [(operands at: 1) ~= SP ifTrue: [8] ifFalse: [12]]].
+ 		[MoveRAw]				-> [^((self isAddressRelativeToVarBase: (operands at: 1))
+ 									    or: [cogit addressIsInCurrentCompilation: (operands at: 1)])
+ 										ifTrue: [(operands at: 0) ~= SP ifTrue: [4] ifFalse: [8]]
+ 										ifFalse: [(operands at: 0) ~= SP ifTrue: [8] ifFalse: [12]]].
+ 		[MoveAwRR]			-> [self assert: (self isAddressRelativeToVarBase: (operands at: 0)).
+ 									^((operands at: 1) = SP or: [(operands at: 2) = SP])
+ 										ifTrue: [8] ifFalse: [4]].
+ 		[MoveRRAw]			-> [self assert: (self isAddressRelativeToVarBase: (operands at: 2)).
+ 									^((operands at: 0) = SP or: [(operands at: 1) = SP])
+ 										ifTrue: [8] ifFalse: [4]].
+ 		[MoveAbR]				-> [^(self isAddressRelativeToVarBase: (operands at: 0))
+ 											ifTrue: [4]
+ 											ifFalse: [8]].
+ 		[MoveRAb]				-> [^(self isAddressRelativeToVarBase: (operands at: 1))
+ 											ifTrue: [4]
+ 											ifFalse: [8]].
+ 		[MoveMwrR]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|4] ifFalse:[8]].
+ 		[MoveRMwr]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
+ 		[MoveM32rR]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|4] ifFalse:[8]].
+ 		[MoveRM32r]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
+ 		[MoveM16rR]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|4] ifFalse:[8]].
+ 		[MoveRM16r]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
+ 		[MoveMbrR]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|4] ifFalse:[8]].
+ 		[MoveRMbr]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
+ 		[MoveM64rRd]			-> [^(self isUnsigned12BitMultipleOf8: (operands at: 0)) ifTrue: [4] ifFalse: [8]].
+ 		[MoveRdM64r]			-> [^(self isUnsigned12BitMultipleOf8: (operands at: 1)) ifTrue: [4] ifFalse: [8]].
+ 		[PushCw]				-> [^8].
+ 		[PushCq]				-> [^8].
+ 		}
+ 		otherwise: [^4].
+ 	^0 "to keep C compiler quiet"
+ !

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeAddCqRDest: (in category 'generate machine code - concretize') -----
+ concretizeAddCqRDest: destReg
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| constant srcReg offset |
+ 	<var: #constant type: #sqInt>
+ 	constant := (operands at: 0) signedIntFromLong64.
+ 	srcReg := operands at: 1.
+ 
+ 	self isPossiblyShiftableImm12: constant
+ 		ifTrue:
+ 			[:shift|
+ 			"C6.2.4		ADD (immediate)	C6-761
+ 			 C6.2.8		ADDS (immediate)	C6-769"
+ 			machineCode
+ 				at: 0
+ 				put: (srcReg = SP
+ 						ifTrue:  [2r100100010 "ADD"]
+ 						ifFalse: [2r101100010 "ADDS"]) << 23
+ 					+ (shift ifTrue: [constant >> 2 + (1 << 22)] ifFalse: [constant << 10])
+ 					+ (srcReg << 5)
+ 					+ destReg.
+ 			^4]
+ 		ifFalse: [].
+ 	self isPossiblyShiftableImm12: constant negated
+ 		ifTrue:
+ 			[:shift|
+ 			"C6.2.308		SUB (immediate)	C6-1311
+ 			 C6.2.314		SUBS (immediate)	C6-1321"
+ 			machineCode
+ 				at: 0
+ 				put: (srcReg = SP
+ 						ifTrue:  [2r110100010 "SUB"]
+ 						ifFalse: [2r111100010 "SUBS"]) << 23
+ 					+ (shift ifTrue: [constant negated >> 2 + (1 << 22)] ifFalse: [constant negated << 10])
+ 					+ (srcReg << 5)
+ 					+destReg.
+ 			^4]
+ 		ifFalse: [].
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	"cogit processor disassembleInstructionAt: 4 In: machineCode object"
+ 	offset := self emitMoveCw: constant intoR: RISCTempReg at: 0.
+ 	"C6.2.7		ADDS (extended register)		C6-766"
+ 	machineCode
+ 				at: offset // 4
+ 				put: 2r10101011001 << 21
+ 					+ (RISCTempReg << 16)
+ 					+ (SXTX << 13)
+ 					+ (srcReg << 5)
+ 					+ destReg.
+ 	^offset + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeAlignmentNops (in category 'generate machine code - concretize') -----
+ concretizeAlignmentNops
+ 	<inline: true>
+ 	"See outputMachineCodeAt:"
+ 	self assert: machineCodeSize \\ 4 = 0.
+ 	machineCode at: 0 put: NOP.
+ 	^machineCodeSize!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeArithmeticShiftRightCqR (in category 'generate machine code - concretize') -----
+ concretizeArithmeticShiftRightCqR
+ 	<inline: true>
+ 	"C6.2.17 	ASR (immediate)	C6-785		100100110 (1)
+ 	 C6.2.177	LSL (immediate)	C6-1075	110100110 (1)
+ 	 C6.2.180	LSR (immediate)	C6-1081	110100110 (1)"
+ 	| reg constant |
+ 	constant := operands at: 0.
+ 	reg := operands at: 1.
+ 	self assert: (constant between: 1 and: 63).
+ 	machineCode
+ 		at: 0
+ 		put: 2r1001001101 << 22
+ 			+ (constant << 16)
+ 			+ (63 << 10)
+ 			+ (reg << 5)
+ 			+ reg.
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeArithmeticShiftRightCqRR (in category 'generate machine code - concretize') -----
+ concretizeArithmeticShiftRightCqRR
+ 	<inline: true>
+ 	"C6.2.17 	ASR (immediate)	C6-785		100100110 (1)
+ 	 C6.2.177	LSL (immediate)	C6-1075	110100110 (1)
+ 	 C6.2.180	LSR (immediate)	C6-1081	110100110 (1)"
+ 	| constant srcReg  destReg |
+ 	constant := operands at: 0.
+ 	srcReg := operands at: 1.
+ 	destReg := operands at: 2.
+ 	self assert: (constant between: 1 and: 63).
+ 	machineCode
+ 		at: 0
+ 		put: 2r1001001101 << 22
+ 			+ (constant << 16)
+ 			+ (63 << 10)
+ 			+ (srcReg << 5)
+ 			+ destReg.
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCASAL (in category 'generate machine code - concretize processor-specific') -----
+ concretizeCASAL
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| constantReg "Xs" valueReg "Xt" baseReg "Xn" |
+ 	constantReg := operands at: 0.
+ 	valueReg := operands at: 1.
+ 	baseReg := operands at: 2.
+ 	machineCode
+ 		at: 0
+ 		put: 2r11001000111 << 21
+ 			+ (constantReg << 16)
+ 			+ (63 << 10)
+ 			+ (baseReg << 5)
+ 			+ valueReg.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCB (in category 'generate machine code - concretize processor-specific') -----
+ concretizeCB
+ 	"C6.2.44/45 		CBNZ/CBZ 			C6-831..."
+ 	<inline: true>
+ 	| offset reg |
+ 	offset := self computeJumpTargetOffset.
+  	self assert: (offset ~= 0 and: [self isInImmediateBranchRange: offset]).
+ 	reg := operands at: 1.
+ 	machineCode
+ 		at: 0
+ 		put: 2r101101 << 26
+ 			+ (opcode = CBNZ ifTrue: [1 << 24] ifFalse: [0])
+ 			+ ((offset bitAnd: 1 << 21 - 1) << 3)
+ 			+ reg.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCCMPNE (in category 'generate machine code - concretize processor-specific') -----
+ concretizeCCMPNE
+ 	"C6.2.49 CCMP (register)	C6-839"
+ 	<inline: true>
+ 	| rM rN flags |
+ 	rM := operands at: 0.
+ 	rN := operands at: 1.
+ 	flags := operands at: 2.
+ 	machineCode
+ 		at: 0
+ 		put: 2r11111010010 << 21
+ 			+ (rM << 16)
+ 			+ (NE << 12)
+ 			+ (rN << 5)
+ 			+ flags.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCLREX (in category 'generate machine code - concretize processor-specific') -----
+ concretizeCLREX
+ 	"C6.2.54		CLREX 			C6-847"
+ 	<inline: true>
+ 	machineCode
+ 		at: 0
+ 		put: 2r11010101000000110011111101011111.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCSET (in category 'generate machine code - concretize processor-specific') -----
+ concretizeCSET
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| reg condition |
+ 	reg := operands at: 0.
+ 	condition := operands at: 1.
+ 	machineCode
+ 		at: 0
+ 		put: 2r1001101010011111 << 16
+ 			+ ((condition bitXor: 1) "strange, but true" << 12)
+ 			+ (2r111111 << 5)
+ 			+ reg.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCacheControlOp1:CRm:Op2: (in category 'generate machine code - concretize processor-specific') -----
+ concretizeCacheControlOp1: op1 CRm: crm Op2: op2
+ 	<inline: true>
+ 	machineCode
+ 		at: 0
+ 		put: 2r1101010100001 << 19
+ 			+ (op1 << 16)
+ 			+ (2r0111 << 12) "CRn"
+ 			+ (crm << 8)
+ 			+ (op2 << 5)
+ 			+ (operands at: 0).
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4
+ 
+ "Scripture (see DminLine & IminLine below):
+ 
+ D13.2.33	CTR_EL0, Cache Type Register		D13-2912
+ 
+ 	Provides information about the architecture of the caches.
+ 
+ 	AArch64 System register CTR_EL0[31:0] is architecturally mapped to AArch32 System register CTR[31:0].
+ 
+ 	CTR_EL0 is a 64-bit register.
+ 
+ 	DIC, bit [29]
+ 		Instruction cache invalidation requirements for instruction to data coherence. The meaning of this bit is:
+ 			0b0	Instruction cache invalidation to the Point of Unification is required for instruction to data coherence.
+ 			0b1	Instruction cache cleaning to the Point of Unification is not required for instruction to data coherence.
+ 
+ 	IDC, bit [28]
+ 		Data cache clean requirements for instruction to data coherence. The meaning of this bit is:
+ 			0b0	Data cache clean to the Point of Unification is required for instruction to data coherence,
+ 					unless CLIDR.LoC == 0b000 or (CLIDR.LoUIS == 0b000 && CLIDR.LoUU == 0b000).
+ 			0b1 Data cache clean to the Point of Unification is not required for instruction to data coherence.
+ 
+ 	CWG, bits [27:24]
+ 		Cache writeback granule. Log2 of the number of words of the maximum size of memory that can be overwritten as a result of the eviction of a cache entry that has had a memory location in it modified.
+ 		A value of 0b0000 indicates that this register does not provide Cache writeback granule information and either:
+ 			- The architectural maximum of 512 words (2KB) must be assumed.
+ 			- The Cache writeback granule can be determined from maximum cache line size encoded in the Cache Size ID Registers.
+ 		Values greater than 0b1001 are reserved.
+ 		Arm recommends that an implementation that does not support cache write-back implements this field as 0b0001. This applies, for example, to an implementation that supports only write-through caches.
+ 
+ 	ERG, bits [23:20]
+ 		Exclusives reservation granule. Log2 of the number of words of the maximum size of the reservation granule that has been implemented for the Load-Exclusive and Store-Exclusive instructions.
+ 		The use of the value 0b0000 is deprecated.
+ 		The value 0b0001 and values greater than 0b1001 are reserved.
+ 
+ 	DminLine, bits [19:16]
+ 		Log2 of the number of words in the smallest cache line of all the data caches and unified caches that are controlled by the PE.
+ 
+ 	L1Ip, bits [15:14]
+ 		Level 1 instruction cache policy. Indicates the indexing and tagging policy for the L1 instruction cache. Possible values of this field are:
+ 			0b00 VMID aware Physical Index, Physical tag (VPIPT)
+ 			0b01 ASID-tagged Virtual Index, Virtual Tag (AIVIVT)
+ 			0b10 Virtual Index, Physical Tag (VIPT)
+ 			0b11 Physical Index, Physical Tag (PIPT)
+ 		The value 0b01 is reserved in Armv8.
+ 		The value 0b00 is permitted only in an implementation that includes ARMv8.2-VPIPT, otherwise the value is reserved.
+ 
+ 	Bits [13:4] Reserved, RES0.
+ 
+ 	IminLine, bits [3:0]
+ 		Log2 of the number of words in the smallest cache line of all the instruction caches that are controlled by the PE."!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCall (in category 'generate machine code - concretize') -----
+ concretizeCall
+ 	<inline: true>
+ 	| offset |
+ 	offset := ((operands at: 0) - address) signedIntFromLong64.
+ 	self assert: (offset noMask: 3).
+ 	self assert: (self isInImmediateBranchAndLinkRange: offset).
+ 	"C6.2.33	BL		C6-812"
+ 	machineCode at: 0 put: (self bl: offset).
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCallJumpFull: (in category 'generate machine code - concretize') -----
+ concretizeCallJumpFull: link
+ 	"Sizing/generating calls.
+ 		Jump targets can be to absolute addresses or other abstract instructions.
+ 		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
+ 		Otherwise instructions must have a machineCodeSize which must be kept to."
+ 	<inline: true>
+ 	| jumpTarget instrOffset|
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
+ 	jumpTarget := self longJumpTargetAddress.
+ 	instrOffset := self emitMoveCw: jumpTarget asUnsignedInteger intoR: RISCTempReg at: 0.
+ 	machineCode
+ 		at: instrOffset // 4
+ 		put: (self brlink: link reg: RISCTempReg).
+ 	self assert: instrOffset = self literalLoadInstructionBytes.
+ 	^instrOffset + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeClzRR (in category 'generate machine code - concretize') -----
+ concretizeClzRR
+ 	"C6.2.56	CLZ		C6-849"
+ 	<inline: true>
+ 	| maskReg dest  |
+ 	maskReg := operands at: 0.
+ 	dest := operands at: 1.
+ 	machineCode
+ 		at: 0
+ 		put: 2r11011010110000000001 << 12
+ 			+ (maskReg << 5)
+ 			+ dest.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCmpC32R (in category 'generate machine code - concretize') -----
+ concretizeCmpC32R
+ 	<inline: true>
+ 	| constant rn |
+ 	constant := operands at: 0.
+ 	rn := operands at: 1.
+ 
+ 	self assert: (cogit addressIsInCurrentCompilation: dependent address).
+ 	self assert: dependent address \\ 4 = 0.
+ 	self assert: (dependent address - address) abs < (1<<18).
+ 	"C6.2.131	LDR (literal)		C6-979"
+ 	machineCode
+ 		at: 0
+ 		put: 2r00011 << 27
+ 			+ (dependent address - address << 3 "5 - 2")
+ 			+ RISCTempReg.
+ 
+ 	"C6.2.60	CMP (extended register)	C6-856"
+ 	machineCode
+ 		at: 1
+ 		put: 2r01101011001 << 21 "N.B. sf == 0!!!!"
+ 			+ (RISCTempReg << 16)
+ 			+ (UXTX << 13)
+ 			+ (rn << 5)
+ 			+ XZR.
+ 	^8!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCmpCqR (in category 'generate machine code - concretize') -----
+ concretizeCmpCqR
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| constant rn offset |
+ 	<var: #constant type: #sqInt>
+ 	constant := (operands at: 0) signedIntFromLong64.
+ 	rn := operands at: 1.
+ 
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	self isPossiblyShiftableImm12: constant
+ 		ifTrue:
+ 			[:shift|
+ 			"C6.2.61	CMP (immediate)	C6-858
+ 			 C6.2.314	SUBS (immediate)	C6-1321"
+ 			machineCode
+ 				at: 0
+ 				put: 2r111100010 << 23
+ 					+ (shift ifTrue: [constant >> 2 + (1 << 22)] ifFalse: [constant << 10])
+ 					+ (rn << 5)
+ 					+ XZR.
+ 			^4]
+ 		ifFalse: [].
+ 	self isPossiblyShiftableImm12: constant negated
+ 		ifTrue:
+ 			[:shift|
+ 			"C6.2.58	CMN (immediate)	C6-852
+ 			 C6.2.8		ADDS (immediate)	C6-769"
+ 			machineCode
+ 				at: 0
+ 				put: 2r101100010 << 23
+ 					+ (shift ifTrue: [constant negated >> 2 + (1 << 22)] ifFalse: [constant negated << 10])
+ 					+ (rn << 5)
+ 					+ XZR.
+ 			^4]
+ 		ifFalse: [].
+ 	offset := self emitMoveCw: constant intoR: RISCTempReg at: 0.
+ 	"C6.2.60	CMP (extended register)	C6-856"
+ 	machineCode
+ 				at: offset // 4
+ 				put: 2r11101011001 << 21
+ 					+ (RISCTempReg << 16)
+ 					+ (UXTX << 13)
+ 					+ (rn << 5)
+ 					+ XZR.
+ 	^offset + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCmpRdRd (in category 'generate machine code - concretize') -----
+ concretizeCmpRdRd
+ 	"C7.2.59	FCMP	C7-1506"
+ 	<inline: true>
+ 	machineCode
+ 		at: 0
+ 		put: 2r11110011 << 21
+ 		+ ((operands at: 0) << 16)
+ 		+ (1 << 13)
+ 		+ ((operands at: 1) << 5).
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeConditionalJump: (in category 'generate machine code - concretize') -----
+ concretizeConditionalJump: conditionCode
+ 	"Will get inlined into concretizeAt: switch."
+ 	"Sizing/generating jumps.
+ 		Jump targets can be to absolute addresses or other abstract instructions.
+ 		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
+ 		Otherwise instructions must have a machineCodeSize which must be kept to."
+ 	<inline: false>
+ 	| offset |
+ 	offset := self computeJumpTargetOffset.
+  	self assert: (offset ~= 0 and: [self isInImmediateBranchRange: offset]).
+ 	machineCode at: 0 put: (self cond: conditionCode offset: offset). "B offset"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeConditionalLongJump: (in category 'generate machine code - concretize') -----
+ concretizeConditionalLongJump: conditionCode
+ 	"Generate a short conditional branch around a long unconditional jump.
+ 	 C6.2.25	B.cond		C6-798
+ 	 C6.2.26	B			C6-799
+ 	 Note that C6.2.44 CBNZ and C6.2.45 CBZ aren't useful for Closed PIC jumps.
+ 	 They compare against zero and have only a +/-1Mb range."
+ 	<inline: true>
+ 	| offset |
+ 	self assert: (conditionCode = EQ or: [conditionCode = NE]).
+ 	offset := (operands at: 0) - (address + 4).
+ 	self assert: (offset noMask: 3).
+ 	self assert: (offset >>> 2 between: -1 << 26 and: 1 << 26 - 1).
+ 	machineCode
+ 		at: 0
+ 		put: 2r101010 << 25
+ 			+ (2 << 5 "skip next instruction")
+ 			+ (conditionCode = EQ ifTrue: [NE] ifFalse: [EQ]);
+ 		at: 1
+ 		put: 2r101 << 26 + (offset >>> 2 bitAnd: 1 << 26 - 1).
+ 	^8!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeConvertRRd (in category 'generate machine code - concretize') -----
+ concretizeConvertRRd
+ 	"Table C3-67 Floating-point and integer or fixed-point conversion instructions	C3-229
+ 	 SCVTF (scalar, integer) on page C7-1894"
+ 	<inline: true>
+ 	machineCode
+ 		at: 0
+ 		put: 2r1001111001100010 << 16
+ 			+ ((operands at: 0) << 5)
+ 			+ (operands at: 1).
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeConvertRdR (in category 'generate machine code - concretize') -----
+ concretizeConvertRdR
+ 	"Table C3-67 Floating-point and integer or fixed-point conversion instructions	C3-229
+ 	 FCVTZS (scalar, integer) on page C7-1568"
+ 	<inline: true>
+ 	machineCode
+ 		at: 0
+ 		put: 2r1001111001111 << 19
+ 			+ ((operands at: 0) << 5)
+ 			+ (operands at: 1).
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCwRArithmetic:Rd: (in category 'generate machine code - concretize') -----
+ concretizeCwRArithmetic: arithOp Rd: destRegOrXZR
+ 	| instrBytes |
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	"cogit processor disassembleInstructionAt: 4 In: machineCode object"
+ 	instrBytes := self emitMoveCw: (operands at: 0) intoR: RISCTempReg at: 0.
+ 	"ADD (extended register) on page C6-758
+ 	 ADDS (extended register) on page C6-766
+ 	 SUB (extended register) on page C6-1308
+ 	 SUBS (extended register) on page C6-1318"
+ 	machineCode
+ 		at: instrBytes // 4
+ 		put: 2r10001011001 << 21
+ 			+ (arithOp << 29)
+ 			+ (RISCTempReg <<16)
+ 			+ (UXTX << 13)
+ 			+ ((operands at: 1) << 5)
+ 			+ destRegOrXZR.
+ 	^instrBytes + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCwRLogical: (in category 'generate machine code - concretize') -----
+ concretizeCwRLogical: op
+ 	| destReg constant offset |
+ 	constant := operands at: 0.
+ 	destReg := operands at: 1.
+ 	offset := self emitMoveCw: constant intoR: RISCTempReg at: 0.
+ 	"AND	(shifted register) - 64-bit variant on page C6-777
+ 	 BIC	(shifted register) - 64-bit variant on page C6-808
+ 	 ORR	(shifted register) - 64-bit variant on page C6-1127
+ 	 ORN	(shifted register) - 64-bit variant on page C6-1123
+ 	  EOR	(shifted register) - 64-bit variant on page C6-898
+ 	  EON	(shifted register) - 64-bit variant on page C6-894
+ 	  ANDS	(shifted register) - 64-bit variant on page C6-781
+ 	  BICS	(shifted register) - 64-bit variant on page C6-810"
+ 	machineCode
+ 				at: offset // 4
+ 				put: 2r1000101 << 25
+ 					+ (op << 29)
+ 					+ (RISCTempReg << 16)
+ 					+ (destReg << 5)
+ 					+ destReg.
+ 	^offset + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeDataCacheControl (in category 'generate machine code - concretize processor-specific') -----
+ concretizeDataCacheControl
+ 	"Issue a DC CIVAC, CVAC or CVAU
+ 	 C5.3.14	DC CIVAC, Data or unified Cache line Clean and Invalidate by VA to PoC		C5-486
+ 					Clean and Invalidate data cache by address to Point of Coherency.
+ 	 C5.3.16	DC CVAC, Data or unified Cache line Clean by VA to PoC						C5-490
+ 					Clean data cache by address to Point of Coherency.
+ 	 C5.3.19	DC CVAU, Clean data cache by address to Point of Unification				C5-496
+ 					Clean data cache by address to Point of Unification."
+ 
+ 	"(operands at: 0) is the target register, accessed within concretizeCacheControlOp1:CRm:Op2:"
+ 	| cacheOpcode |
+ 	cacheOpcode := (operands at: 1) caseOf: {
+ 						[DC_CIVAC] ->	[2r1110].
+ 						[DC_CVAC] ->	[2r1010].
+ 						[DC_CVAU] ->	[2r1011] }.
+ 	^self concretizeCacheControlOp1: 2r011 CRm: cacheOpcode Op2: 2r001
+ 
+ "Scripture:
+ C5.3.1		DC CGDSW, Data, Allocation Tag or unified Cache line Clean of Data and Allocation Tags by Set/Way					C5-460
+ C5.3.2		DC CGDVAC, Data, Allocation Tag or unified Cache line Clean of Allocation Tags by VA to PoC							C5-462
+ C5.3.3		DC CGDVADP, Data, Allocation Tag or unified Cache line Clean of Allocation Tags by VA to PoDP							C5-464
+ C5.3.4		DC CGDVAP, Data, Allocation Tag or unified Cache line Clean of Data and Allocation Tags by VA to PoP					C5-466
+ C5.3.5		DC CGSW, Data, Allocation Tag or unified Cache line Clean of Allocation Tags by Set/Way								C5-468
+ C5.3.6		DC CGVAC, Data, Allocation Tag or unified Cache line Clean of Allocation Tags by VA to PoC								C5-470
+ C5.3.7		DC CGVADP, Data, Allocation Tag or unified Cache line Clean of Data and Allocation Tags by VA to PoDP					C5-472
+ C5.3.8		DC CGVAP, Data, Allocation Tag or unified Cache line Clean of Allocation Tags by VA to PoP								C5-474
+ C5.3.9		DC CIGDSW, Data, Allocation Tag or unified Cache line Clean and Invalidate of Data and Allocation Tags by Set/Way		C5-476
+ C5.3.10	DC CIGDVAC, Data, Allocation Tag or unified Cache line Clean and Invalidate of Data and Allocation Tags by VA to PoC	C5-478
+ C5.3.11	DC CIGSW, Data, Allocation Tag or unified Cache line Clean and Invalidate of Allocation Tags by Set/Way				C5-480
+ C5.3.12	DC CIGVAC, Data, Allocation Tag or unified Cache line Clean and Invalidate of Allocation Tags by VA to PoC				C5-482
+ C5.3.13	DC CISW, Data or unified Cache line Clean and Invalidate by Set/Way													C5-484
+ C5.3.14	DC CIVAC, Data or unified Cache line Clean and Invalidate by VA to PoC													C5-486
+ C5.3.15	DC CSW, Data or unified Cache line Clean by Set/Way																	C5-488
+ C5.3.16	DC CVAC, Data or unified Cache line Clean by VA to PoC																	C5-490
+ C5.3.17	DC CVADP, Data or unified Cache line Clean by VA to PoDP																C5-492
+ C5.3.18	DC CVAP, Data or unified Cache line Clean by VA to PoP																	C5-494
+ C5.3.19	DC CVAU, Data or unified Cache line Clean by VA to PoU																C5-496
+ C5.3.20	DC GVA, Data Cache set Allocation Tag by VA																			C5-498
+ C5.3.21	DC GZVA, Data Cache set Allocation Tags and Zero by VA																C5-500
+ C5.3.22	DC IGDSW, Data, Allocation Tag or unified Cache line Invalidate of Data and Allocation Tags by Set/Way					C5-502
+ C5.3.23	DC IGDVAC, Data, Allocation Tag or unified Cache line Invalidate of Allocation Tags by VA to PoC							C5-504
+ C5.3.24	DC IGSW, Data, Allocation Tag or unified Cache line Invalidate of Allocation Tags by Set/Way							C5-506
+ C5.3.25	DC IGVAC, Data, Allocation Tag or unified Cache line Invalidate of Allocation Tags by VA to PoC							C5-508
+ C5.3.26	DC ISW, Data or unified Cache line Invalidate by Set/Way																C5-510
+ C5.3.27	DC IVAC, Data or unified Cache line Invalidate by VA to PoC																C5-512
+ C5.3.28	DC ZVA, Data Cache Zero by VA																						C5-514
+ 
+ C6.2.75	DC		C6-883
+ 			1101010100 0 01 op1:3 [0111,CRn:4=7] CRm:4 op2:3 Rt:5
+ 
+ 			DC <dc_op>, <Xt> equivalent to SYS #<op1>. C7, <Cm>, #<op2>, <Xt> = SysOp(op1,0111,CRm,op2) == Sys_DC
+ 			<dc_op>:
+ 				C5.3.27	IVAC		when op1 = 000, CRm = 0110, op2 = 001		Invalidate data cache by address to Point of Coherency.
+ 				C5.3.26	ISW		when op1 = 000, CRm = 0110, op2 = 010		Invalidate data cache by set/way.
+ 				C5.3.15	CSW		when op1 = 000, CRm = 1010, op2 = 010		Clean data cache by set/way.
+ 				C5.3.13	CISW		when op1 = 000, CRm = 1110, op2 = 010		Clean and Invalidate data cache by set/way.
+ 				C5.3.28	ZVA		when op1 = 011, CRm = 0100, op2 = 001		Zero data cache by address. Zeroes a naturally aligned block
+ 																							of N bytes, where the size of N is identified in DCZID_EL0.
+ 				C5.3.16	CVAC		when op1 = 011, CRm = 1010, op2 = 001		Clean data cache by address to Point of Coherency.
+ 				C5.3.19	CVAU		when op1 = 011, CRm = 1011, op2 = 001		Clean data cache by address to Point of Unification.
+ 				C5.3.14	CIVAC		when op1 = 011, CRm = 1110, op2 = 001		Clean and Invalidate data cache by address to Point of Coherency."!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeDataSynchronizationBarrier (in category 'generate machine code - concretize processor-specific') -----
+ concretizeDataSynchronizationBarrier
+ 	"C6.2.81	DSB	C6-891"
+ 	<inline: true>
+ 	| CRm |
+ 	CRm := (operands at: 0) << 2 + (operands at: 1).
+ 	machineCode
+ 		at: 0
+ 		put: 2r11010101000000110011000010011111
+ 			+ (CRm << 8).
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeDivRRR (in category 'generate machine code - concretize processor-specific') -----
+ concretizeDivRRR
+ 	"C6.2.234	SDIV	C6-1174"
+ 	<inline: true>
+ 	"Rd := Rn / Rm"
+ 	"reg3 := reg1 / reg2"
+ 	| reg1 reg2 reg3 |
+ 	reg1 := operands at: 0.
+ 	reg2 := operands at: 1.
+ 	reg3 := operands at: 2.
+ 	machineCode
+ 		at: 0
+ 		put: 2r10011010110 << 21
+ 			+ (reg2 << 16)
+ 			+ (2r000011 << 10)
+ 			+ (reg1 << 5)
+ 			+ reg3.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeFill32 (in category 'generate machine code - concretize') -----
+ concretizeFill32
+ 	"fill with operand 0 according to the processor's endianness"
+ 	<inline: true>
+ 	machineCode at: 0 put: (operands at: 0).
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeInstructionCacheControl (in category 'generate machine code - concretize processor-specific') -----
+ concretizeInstructionCacheControl
+ 	"Issue an IC IVAU	Invalidate instruction cache by address to Point of Unification.
+ 	 C5.3.31	IC IVAU, Instruction Cache line Invalidate by VA to PoU	C5-518"
+ 	"(operands at: 0) is the target register, accessed within concretizeCacheControlOp1:CRm:Op2:"
+ 	"Ho hum, table C5-1 page C5-367 states that IC_IALLU & IC_IALLUIS are available from EL1 or higher,
+ 	 so they are off limits to us."
+ 	<inline: true>
+ 	^true
+ 		ifTrue: [self concretizeCacheControlOp1: 2r011 CRm: 2r0101 Op2: 2r001 "IC_IVAU"]
+ 		ifFalse:
+ 			[(operands at: 1) caseOf: {
+ 				[IC_IALLU] ->	[self concretizeCacheControlOp1: 2r000 CRm: 2r0101 Op2: 2r000].
+ 				[IC_IALLUIS] ->	[self concretizeCacheControlOp1: 2r000 CRm: 2r0001 Op2: 2r000].
+ 				[IC_IVAU] ->	[self concretizeCacheControlOp1: 2r011 CRm: 2r0101 Op2: 2r001] }]
+ 
+ "Scripture:
+ C5.3.29	IC IALLU, Instruction Cache Invalidate All to PoU						C5-516
+ C5.3.30	IC IALLUIS, Instruction Cache Invalidate All to PoU, Inner Shareable		C5-517
+ C5.3.31	IC IVAU, Instruction Cache line Invalidate by VA to PoU					C5-518
+ 
+ C6.2.94	IC		C6-910
+ 			1101010100 0 01 op1:3 [0111,CRn:4=7] CRm:4 op2:3 Rt:5
+ 
+ 			IC <ic_op>, <Xt> equivalent to SYS #<op1>. C7, <Cm>, #<op2>{, <Xt>} = SysOp(op1,0111,CRm,op2) == Sys_IC
+ 
+ 				C5.3.30	IALLUIS		when op1 = 000, CRm = 0001, op2 = 000		Invalidate all instruction caches in Inner Shareable domain to Point of Unification.
+ 				C5.3.29	IALLU		when op1 = 000, CRm = 0101, op2 = 000		Invalidate all instruction caches to Point of Unification.
+ 				C5.3.31	IVAU		when op1 = 011, CRm = 0101, op2 = 001		Invalidate instruction cache by address to Point of Unification."!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeInstructionSynchronizationBarrier (in category 'generate machine code - concretize processor-specific') -----
+ concretizeInstructionSynchronizationBarrier
+ 	"C6.2.96	ISB		C6-912"
+ 	<inline: true>
+ 	| CRm |
+ 	CRm := 2r1111.
+ 	machineCode
+ 		at: 0
+ 		put: 2r11010101000000110011000011011111
+ 			+ (CRm << 8).
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeJumpLong (in category 'generate machine code - concretize') -----
+ concretizeJumpLong
+ 	"C6.2.26 	B		C6-799"
+ 	<inline: true>
+ 	| offset |
+ 	offset := (operands at: 0) - address.
+ 	self assert: (offset noMask: 3).
+ 	self assert: (offset >>> 2 between: -1 << 26 and: 1 << 26 - 1).
+ 	machineCode
+ 		at: 0
+ 		put: 2r101 << 26 + (offset >>> 2 bitAnd: 1 << 26 - 1).
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeJumpR (in category 'generate machine code - concretize') -----
+ concretizeJumpR
+ 	"C6.2.36	BR	C6-816"
+ 	<inline: true>
+ 	machineCode
+ 		at: 0
+ 		put: 2r1101011 << 25
+ 			+ (XZR << 16)
+ 			+ ((operands at: 0) << 5).
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeLDAXR (in category 'generate machine code - concretize') -----
+ concretizeLDAXR
+ 	"C6.2.113		LDAXR		C6-944"
+ 	<inline: true>
+ 	| targetReg addressReg |
+ 	targetReg := operands at: 0.
+ 	addressReg := operands at: 1.
+ 	machineCode
+ 		at: 0
+ 		put: 2r1100100001011111111111 << 10
+ 			+ (addressReg << 5)
+ 			+ targetReg.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeLiteral (in category 'generate machine code - concretize') -----
+ concretizeLiteral
+ 	"Generate an out-of-line literal.  Copy the value and any annotation from the stand-in in the literals manager."
+ 	| literalAsInstruction literal |
+ 	<var: 'literal' type: #usqInt>
+ 	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]).
+ 	dependent annotation ifNotNil:
+ 		[self assert: annotation isNil.
+ 		 annotation := dependent annotation].
+ 	dependent address ifNotNil: [self assert: dependent address = address].
+ 	dependent address: address.
+ 	machineCode at: 0 put: (literal bitAnd: 16rFFFFFFFF).
+ 	self literalSize = 4 ifTrue:
+ 		[^4].
+ 	machineCode at: 1 put: (literal >> 32).
+ 	^8!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeLoadEffectiveAddressMwrR (in category 'generate machine code - concretize') -----
+ concretizeLoadEffectiveAddressMwrR
+ 	| baseReg offset destReg instrBytes |
+ 	<var: #offset type: #sqInt>
+ 	offset := operands at: 0.
+ 	baseReg := operands at: 1.
+ 	destReg := operands at: 2.
+ 	self isPossiblyShiftableImm12: offset
+ 		ifTrue:
+ 			[:shift|
+ 			"C6.2.4		ADD (immediate)	C6-761"
+ 			machineCode
+ 				at: 0
+ 				put: 2r100100010 << 23
+ 					+ (shift ifTrue: [offset >> 2] ifFalse: [offset << 10])
+ 					+ (baseReg << 5)
+ 					+ destReg.
+ 			^4]
+ 		ifFalse: [].
+ 	self isPossiblyShiftableImm12: offset negated
+ 		ifTrue:
+ 			[:shift|
+ 			"C6.2.308		SUB (immediate)	C6-1311"
+ 			machineCode
+ 				at: 0
+ 				put: 2r100100010 << 23
+ 					+ (shift ifTrue: [offset negated >> 2] ifFalse: [offset negated << 10])
+ 					+ (baseReg << 5)
+ 					+ destReg.
+ 			^4]
+ 		ifFalse: [].
+ 	instrBytes := self emitMoveCw: offset intoR: RISCTempReg at: 0.
+ 	"C6.2.3		ADD (extended register) C6-758"
+ 	machineCode
+ 		at: instrBytes // 4
+ 		put: 2r10001011001 << 21
+ 			+ (destReg << 16)
+ 			+ (UXTX << 13)
+ 			+ (RISCTempReg << 5)
+ 			+ destReg.
+ 	^instrBytes + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeLogicalOp:CqRDest: (in category 'generate machine code - concretize') -----
+ concretizeLogicalOp: op CqRDest: destReg
+ 	"AND	(immediate) - 64-bit variant on page C6-775
+ 	 ORR	(immediate) - 64-bit variant on page C6-1125
+ 	 EOR	(immediate) - 64-bit variant on page C6-896
+ 	 ANDS	(immediate) - 64-bit variant on page C6-779
+ 	 C6.2.329	TST (immediate)	C6-1346"
+ 	<inline: false>
+ 	| srcReg constant |
+ 	constant := operands at: 0.
+ 	srcReg := operands at: 1.
+ 	^self isImmNImmSImmREncodableBitmask: constant
+ 		ifTrue:
+ 			[:n :imms :immr|
+ 			 machineCode
+ 				at: 0
+ 				put: 2r1001001 << 25
+ 					+ (op << 29)
+ 					+ (n << 22)
+ 					+ (immr << 16)
+ 					+ (imms << 10)
+ 					+ (srcReg << 5)
+ 					+ destReg.
+ 			 4]
+ 		ifFalse:
+ 			[| offset |
+ 			offset := self emitMoveCw: constant intoR: RISCTempReg at: 0.
+ 			"OPC	N
+ 			 00		0	AND (shifted register) - 64-bit variant on page C6-777
+ 			 00		1	BIC (shifted register) - 64-bit variant on page C6-808
+ 			 01		0	ORR (shifted register) - 64-bit variant on page C6-1127
+ 			 01		1	ORN (shifted register) - 64-bit variant on page C6-1123
+ 			 10		0	EOR (shifted register) - 64-bit variant on page C6-898
+ 			 10		1	EON (shifted register) - 64-bit variant on page C6-894
+ 			 11		0	ANDS (shifted register) - 64-bit variant on page C6-781
+ 			 11		0	BICS (shifted register) - 64-bit variant on page C6-810"
+ 			machineCode
+ 						at: offset // 4
+ 						put: 2r1000101 << 25
+ 							+ (op << 29)
+ 							+ (RISCTempReg << 16)
+ 							+ (srcReg << 5)
+ 							+ destReg.
+ 			offset + 4]
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	"cogit processor disassembleInstructionAt: 4 In: machineCode object"
+ 	"cogit processor disassembleInstructionAt: 8 In: machineCode object"!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeLogicalShiftLeftCqR (in category 'generate machine code - concretize') -----
+ concretizeLogicalShiftLeftCqR
+ 	<inline: true>
+ 	"C6.2.17 	ASR (immediate)	C6-785		100100110 (1)
+ 	 C6.2.177	LSL (immediate)	C6-1075	110100110 (1)
+ 	 C6.2.180	LSR (immediate)	C6-1081	110100110 (1)"
+ 	| reg constant |
+ 	constant := operands at: 0.
+ 	reg := operands at: 1.
+ 	self assert: (constant between: 1 and: 63).
+ 	machineCode
+ 		at: 0
+ 		put: 2r1101001101 << 22
+ 			+ (64 - constant << 16)
+ 			+ (63 - constant << 10)
+ 			+ (reg << 5)
+ 			+ reg.
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeLogicalShiftLeftCqRR (in category 'generate machine code - concretize') -----
+ concretizeLogicalShiftLeftCqRR
+ 	<inline: true>
+ 	"C6.2.17 	ASR (immediate)	C6-785		100100110 (1)
+ 	 C6.2.177	LSL (immediate)	C6-1075	110100110 (1)
+ 	 C6.2.180	LSR (immediate)	C6-1081	110100110 (1)"
+ 	| constant srcReg  destReg |
+ 	constant := operands at: 0.
+ 	srcReg := operands at: 1.
+ 	destReg := operands at: 2.
+ 	self assert: (constant between: 1 and: 63).
+ 	machineCode
+ 		at: 0
+ 		put: 2r1101001101 << 22
+ 			+ (64 - constant << 16)
+ 			+ (63 - constant << 10)
+ 			+ (srcReg << 5)
+ 			+ destReg.
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeLogicalShiftRightCqR (in category 'generate machine code - concretize') -----
+ concretizeLogicalShiftRightCqR
+ 	<inline: true>
+ 	"C6.2.17 	ASR (immediate)	C6-785		100100110 (1)
+ 	 C6.2.177	LSL (immediate)	C6-1075	110100110 (1)
+ 	 C6.2.180	LSR (immediate)	C6-1081	110100110 (1)"
+ 	| reg constant |
+ 	constant := operands at: 0.
+ 	reg := operands at: 1.
+ 	self assert: (constant between: 1 and: 63).
+ 	machineCode
+ 		at: 0
+ 		put: 2r1101001101 << 22
+ 			+ (constant << 16)
+ 			+ (63 << 10)
+ 			+ (reg << 5)
+ 			+ reg.
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeLogicalShiftRightCqRR (in category 'generate machine code - concretize') -----
+ concretizeLogicalShiftRightCqRR
+ 	<inline: true>
+ 	"C6.2.17 	ASR (immediate)	C6-785		100100110 (1)
+ 	 C6.2.177	LSL (immediate)	C6-1075	110100110 (1)
+ 	 C6.2.180	LSR (immediate)	C6-1081	110100110 (1)"
+ 	| constant srcReg  destReg |
+ 	constant := operands at: 0.
+ 	srcReg := operands at: 1.
+ 	destReg := operands at: 2.
+ 	self assert: (constant between: 1 and: 63).
+ 	machineCode
+ 		at: 0
+ 		put: 2r1101001101 << 22
+ 			+ (constant << 16)
+ 			+ (63 << 10)
+ 			+ (srcReg << 5)
+ 			+ destReg.
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMRSOp1:CRn:CRm:Op2: (in category 'generate machine code - concretize processor-specific') -----
+ concretizeMRSOp1: op1 CRn: crn CRm: crm Op2: op2
+ 	"C6.2.192	MRS	C6-1104
+ 	 Move System Register allows the PE to read an AArch64 System register into a general-purpose register."
+ 	<inline: true>
+ 	machineCode
+ 		at: 0
+ 		put: 2r1101010100111 << 19
+ 			+ (op1 << 16)
+ 			+ (crn << 12)
+ 			+ (crm << 8)
+ 			+ (op2 << 5)
+ 			+ (operands at: 0).
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMRS_CTR_EL0 (in category 'generate machine code - concretize processor-specific') -----
+ concretizeMRS_CTR_EL0
+ 	"C6.2.192	MRS	C6-1104
+ 	 Move System Register allows the PE to read an AArch64 System register into a general-purpose register.
+ 	 D12.3 op0==0b11, Moves to and from non-debug System registers, Special-purpose registers		D12-2808
+ 	 Register Accessed	op0		op1		CRn	CRm	op2
+ 	 ...
+ 	 CTR_EL0			3		3		0		0		1"
+ 	<inline: true>
+ 	^self concretizeMRSOp1: 3 CRn: 0 CRm: 0 Op2: 1!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMRS_ID_AA64ISAR0_EL1 (in category 'generate machine code - concretize processor-specific') -----
+ concretizeMRS_ID_AA64ISAR0_EL1
+ 	"C6.2.192	MRS	C6-1104
+ 	 Move System Register allows the PE to read an AArch64 System register into a general-purpose register.
+ 	 D12.3 op0==0b11, Moves to and from non-debug System registers, Special-purpose registers		D12-2808
+ 	 Register Accessed		op0		op1		CRn	CRm	op2
+ 	 ...
+ 	 CTR_EL0				3		3		0		0		1
+ 	 ID_AA64ISAR0_EL1	3		0		0		5		1"
+ 	<inline: true>
+ 	^self concretizeMRSOp1: 0 CRn: 0 CRm: 6 Op2: 0!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMSubRRR (in category 'generate machine code - concretize processor-specific') -----
+ concretizeMSubRRR
+ 	"C6.2.195	MSUB	C6-1109
+ 	 Xd := Xa - (Xn * Xm)"
+ 	<inline: true>
+ 	"rD := rA - (rN * rM)"
+ 	| rN rA rM rD |
+ 	rM := (operands at: 0) >> 5.
+ 	rN := (operands at: 0) bitAnd: 31.
+ 	rA := operands at: 1.
+ 	rD := operands at: 2.
+ 	machineCode
+ 		at: 0
+ 		put: 2r10011011 << 24
+ 			+ (rM << 16)	"Xm"
+ 			+ (1 << 15)
+ 			+ (rA << 10)	"Xa"
+ 			+ (rN << 5)	"Xn"
+ 			+ rD.			"Xd"
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMathRdRd: (in category 'generate machine code - concretize') -----
+ concretizeMathRdRd: floatArithOp
+ 	"C7.2.43	FADD (scalar)	C7-1426"
+ 	"C7.2.91	FDIV (scalar)	C7-1582"
+ 	"C7.2.129	FMUL (scalar)	C7-1664"
+ 	"C7.2.167	FSUB (scalar)	C7-1747"
+ 	<inline: true>
+ 	| srcReg destReg |
+ 	srcReg := operands at: 0.
+ 	destReg := operands at: 1.
+ 	machineCode
+ 		at: 0
+ 		put: 2r11110011 << 21
+ 			+ (srcReg << 16)
+ 			+ (floatArithOp << 10)
+ 			+ (destReg << 5)
+ 			+ destReg.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveAbR (in category 'generate machine code - concretize') -----
+ concretizeMoveAbR
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcAddr destReg instrOffset |
+ 	srcAddr := operands at: 0.
+ 	destReg := operands at: 1.
+ 	self deny: SP = destReg.
+ 	"ldr srcReg, [VarBaseReg, #offset] except that this is illegal for SP/X31"
+ 	(self isAddressRelativeToVarBase: srcAddr) ifTrue:
+ 		[srcAddr < cogit varBaseAddress ifTrue:
+ 			[self shouldBeImplemented.
+ 			 ^4].
+ 		 ^self emitLd: 0 rn: VarBaseReg rt: destReg imm: srcAddr - cogit varBaseAddress shiftBy12: false at: 0].
+ 	instrOffset := self emitMoveCw: srcAddr intoR: RISCTempReg at: 0.
+ 	^self emitLd: 0 rn: RISCTempReg rt: destReg imm: 0 shiftBy12: false at: instrOffset!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveAwR (in category 'generate machine code - concretize') -----
+ concretizeMoveAwR
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcAddr destReg instrOffset |
+ 	srcAddr := operands at: 0.
+ 	destReg := operands at: 1.
+ 	"ldr srcReg, [VarBaseReg, #offset] except that this is illegal for SP/X31"
+ 	(self isAddressRelativeToVarBase: srcAddr) ifTrue:
+ 		[srcAddr < cogit varBaseAddress ifTrue:
+ 			[self shouldBeImplemented.
+ 			 ^4].
+ 		 destReg ~= SP ifTrue:
+ 			[^self emitLd: 3 rn: VarBaseReg rt: destReg imm: srcAddr - cogit varBaseAddress shiftBy12: false at: 0].
+ 		 instrOffset := self emitLd: 3 rn: VarBaseReg rt: RISCTempReg imm: srcAddr - cogit varBaseAddress shiftBy12: false at: 0.
+ 		 machineCode
+ 			at: instrOffset / 4
+ 			put: (self movern: RISCTempReg rd: destReg).
+ 		^instrOffset + 4].
+ 	instrOffset := self emitMoveCw: srcAddr intoR: RISCTempReg at: 0.
+ 	SP ~= destReg ifTrue:
+ 		[^self emitLd: 3 rn: RISCTempReg rt: destReg imm: 0 shiftBy12: false at: instrOffset].
+ 	instrOffset := self emitLd: 3 rn: RISCTempReg rt: RISCTempReg imm: 0 shiftBy12: false at: instrOffset.
+ 	machineCode
+ 		at: instrOffset // 4
+ 		put: (self movern: RISCTempReg rd: destReg).
+ 	^instrOffset + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveAwRR (in category 'generate machine code - concretize processor-specific') -----
+ concretizeMoveAwRR
+ 	"C6.2.128 	LDP		C6-970"
+ 	| pairAddress reg1 reg2 |
+ 	<inline: true>
+ 	pairAddress := operands at: 0.
+ 	reg1 := operands at: 1.
+ 	reg2 := operands at: 2.
+ 	self assert: reg1 ~= reg2.
+ 	self assert: (reg1 ~= RISCTempReg and: [reg2 ~= RISCTempReg]).
+ 	self assert: (self isAddressRelativeToVarBase: pairAddress).
+ 	self assert: pairAddress - cogit varBaseAddress / 8 < (1 << 6).
+ 	reg1 = SP ifTrue: [reg1 := RISCTempReg].
+ 	reg2 = SP ifTrue: [reg2 := RISCTempReg].
+ 	machineCode
+ 		at: 0
+ 		put: 2r1010100101 << 22
+ 			+ (pairAddress - cogit varBaseAddress / 8 << 15)
+ 			+ (reg2 << 10)
+ 			+ (VarBaseReg << 5)
+ 			+ reg1.
+ 	(reg1 ~= RISCTempReg and: [reg2 ~= RISCTempReg]) ifTrue:
+ 		[^4].
+ 	machineCode
+ 		at: 1
+ 		put: (self movern: RISCTempReg rd: SP).
+ 	^8
+ 
+ 	"cogit processor
+ 		disassembleInstructionAt: 0 In: machineCode object;
+ 		disassembleInstructionAt: 4 In: machineCode object"!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveC32R (in category 'generate machine code - concretize') -----
+ concretizeMoveC32R
+ 	<inline: true>
+ 	| constant rn |
+ 	constant := operands at: 0.
+ 	rn := operands at: 1.
+ 
+ 	self assert: (cogit addressIsInCurrentCompilation: dependent address).
+ 	self assert: dependent address \\ 4 = 0.
+ 	self assert: (dependent address - address) < (1 << 20).
+ 	"C6.2.131	LDR (literal)		C6-979
+ 	 C6.2.143	LDRSW (literal)	C6-1008"
+ 	machineCode
+ 		at: 0
+ 		put: 2r10011 << 27
+ 			+ ((dependent address - address  bitAnd: 1 << 21 - 1) << 3 "5 - 2")
+ 			+ rn.
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveCqR (in category 'generate machine code - concretize') -----
+ concretizeMoveCqR
+ 	"C3.3.4		Move (immediate)	C3-215
+ 
+ 	 The Move (immediate) instructions are aliases for a single MOVZ, MOVN, or ORR (immediate with zero register),
+ 	 instruction to load an immediate value into the destination register. An assembler must permit a signed or
+ 	 unsigned immediate, as long as its binary representation can be generated using one of these instructions,
+ 	 and an assembler error results if the immediate cannot be generated in this way. On disassembly, it is
+ 	 unspecified whether the immediate is output as a signed or an unsigned value.
+ 
+ 	 C6.2.191	MOVZ	C6-1102	Move wide with zero moves an optionally-shifted 16-bit immediate value to a register.
+ 	 C6.2.190	MOVN	C6-1100	Move wide with NOT moves the inverse of an optionally-shifted 16-bit immediate value to a register.
+ 	 C6.2.204	ORR (immediate)	C6-1125
+ 										Bitwise OR (immediate) performs a bitwise (inclusive) OR of a register value and an immediate
+ 										register value, and writes the result to the destination register."
+ 
+ 	| constant destReg |
+ 	constant := operands at: 0.
+ 	destReg := operands at: 1.
+ 	destReg ~= SP ifTrue:
+ 		[| lowBit lowBitMod16 mask |
+ 		lowBit := constant > 0
+ 					ifTrue: [self cCode: [self computeLowBit: constant] inSmalltalk: [constant lowBit - 1]]
+ 					ifFalse: [0].
+ 		lowBitMod16 := lowBit // 16 * 16.
+ 		mask := 1 << 16 - 1 << lowBitMod16.
+ 		(constant bitAnd: mask) = constant ifTrue:
+ 			["Use MOVZ"
+ 			 machineCode
+ 				at: 0
+ 				put: 2r110100101 << 23
+ 					+ (lowBitMod16 // 16 << 21)
+ 					+ (constant >> lowBitMod16 << 5)
+ 					+ destReg.
+ 			 ^4].
+ 		lowBit := constant signedIntFromLong64 < -1
+ 					ifTrue: [self cCode: [self computeLowBit: constant bitInvert64] inSmalltalk: [constant bitInvert64 lowBit - 1]]
+ 					ifFalse: [0].
+ 		(constant bitOr: mask) signedIntFromLong64 = -1 ifTrue:
+ 			["Use MOVN"
+ 			 self assert: (constant bitInvert64 >> lowBitMod16) = ((constant bitInvert64 >> lowBitMod16) bitAnd: mask).
+ 			 machineCode
+ 				at: 0
+ 				put: 2r100100101 << 23
+ 					+ (lowBitMod16 // 16 << 21)
+ 					+ (constant bitInvert64 >> lowBitMod16 << 5)
+ 					+ destReg.
+ 			 ^4]].
+ 	^self isImmNImmSImmREncodableBitmask: constant
+ 		ifTrue:
+ 			[:n :imms :immr| "Use ORR"
+ 			machineCode
+ 				at: 0
+ 				put: 2r1011001001 << 22
+ 					+ (immr << 16)
+ 					+ (imms << 10)
+ 					+ (XZR << 5)
+ 					+ destReg.
+ 			4]
+ 		ifFalse: [self emitMoveCw: constant intoR: destReg at: 0]!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveCwR (in category 'generate machine code - concretize') -----
+ concretizeMoveCwR
+ 	<inline: true>
+ 	^self emitMoveCw: (operands at: 0) intoR: (operands at: 1) at: 0!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveM64rRd (in category 'generate machine code - concretize') -----
+ concretizeMoveM64rRd
+ 	"Load/Store Vector on page C3-206.
+ 	 C7.2.184	LDR (immediate, SIMD&FP)	C7-1800"
+ 	<inline: true>
+ 	| rd offset baseReg |
+ 	offset := operands at: 0.
+ 	baseReg := operands at: 1.
+ 	rd := operands at: 2.
+ 	self assert: (offset noMask: 7).
+ 	machineCode
+ 		at: 0
+ 		put: 2r1111110101 << 22
+ 			+ (offset << 7 "10 - 3")
+ 			+ (baseReg << 5)
+ 			+ rd.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveMSrR: (in category 'generate machine code - concretize') -----
+ concretizeMoveMSrR: unitSizeLog2MinusOne
+ 	"Mwr/M32r/M16r/Mbr - memory unit whose address is a constant M away from an address in a register"
+ 	^self emitLd: unitSizeLog2MinusOne
+ 		rn: (operands at: 1)
+ 		rt: (operands at: 2) signedIntFromLong64
+ 		imm: (operands at: 0)
+ 		shiftBy12: false
+ 		at: 0
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveRAb (in category 'generate machine code - concretize') -----
+ concretizeMoveRAb
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcReg destAddr instrOffset |
+ 	srcReg := operands at: 0.
+ 	destAddr := operands at: 1.
+ 	self deny: SP = srcReg.
+ 	(self isAddressRelativeToVarBase: destAddr) ifTrue:
+ 		[destAddr < cogit varBaseAddress ifTrue:
+ 			[self shouldBeImplemented.
+ 			 ^4].
+ 		 machineCode
+ 			at: 0
+ 			put: (self st: 0 rn: VarBaseReg rt: srcReg imm: destAddr - cogit varBaseAddress shiftBy12: false).
+ 		 ^4].
+ 	instrOffset := self emitMoveCw: destAddr intoR: RISCTempReg at: 0.
+ 	machineCode
+ 		at: instrOffset // 4
+ 		put: (self st: 0 rn: RISCTempReg rt: srcReg imm: 0 shiftBy12: false).
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^instrOffset + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveRAw (in category 'generate machine code - concretize') -----
+ concretizeMoveRAw
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcReg destAddr instrOffset |
+ 	srcReg := operands at: 0.
+ 	destAddr := operands at: 1.
+ 	"str srcReg, [VarBaseReg, #offset] except that this is illegal for srcReg = SP/X31"
+ 	(self isAddressRelativeToVarBase: destAddr) ifTrue:
+ 		[destAddr < cogit varBaseAddress ifTrue:
+ 			[self shouldBeImplemented.
+ 			 ^4].
+ 		 srcReg ~= SP ifTrue:
+ 			[machineCode
+ 				at: 0
+ 				put: (self st: 3 rn: VarBaseReg rt: srcReg imm: destAddr - cogit varBaseAddress shiftBy12: false).
+ 			 ^4].
+ 		machineCode
+ 			at: 0
+ 			put: (self movern: srcReg rd: RISCTempReg);
+ 			at: 1
+ 			put: (self st: 3 rn: VarBaseReg rt: RISCTempReg imm: destAddr - cogit varBaseAddress shiftBy12: false).
+ 		^8].
+ 	instrOffset := self emitMoveCw: destAddr intoR: RISCTempReg at: 0.
+ 	SP ~= srcReg ifTrue:
+ 		[machineCode
+ 			at: instrOffset // 4
+ 			put: (self st: 3 rn: RISCTempReg rt: srcReg imm: 0 shiftBy12: false).
+ 		^instrOffset + 4].
+ 	machineCode
+ 		at: instrOffset // 4
+ 		put: (self movern: srcReg rd: CArg1Reg);
+ 		at: instrOffset // 4
+ 		put: (self st: 3 rn: RISCTempReg rt: CArg1Reg imm: 0 shiftBy12: false).
+ 	^instrOffset + 8
+ 	!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveRMSr: (in category 'generate machine code - concretize') -----
+ concretizeMoveRMSr: unitSizeLog2MinusOne
+ 	"Mwr/M32r/M16r/Mbr - memory unit whose address is a constant M away from an address in a register"
+ 	machineCode
+ 		at: 0
+ 		put: (self st: unitSizeLog2MinusOne
+ 				rn: (operands at: 2)
+ 				rt: (operands at: 0)
+ 				imm: (operands at: 1) signedIntFromLong64
+ 				shiftBy12: false).
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveRR (in category 'generate machine code - concretize') -----
+ concretizeMoveRR
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcReg destReg |
+ 	srcReg := operands at: 0.
+ 	destReg := operands at: 1.
+ 	"C6.2.184 MOV (to/from SP) p1089
+ 	 C6.2.188 MOV (register) p1096"
+ 	machineCode
+ 		at: 0
+ 		put: ((srcReg = SP or: [destReg = SP])
+ 				ifTrue:  [2r10010001 << 24
+ 						+ (srcReg << 5)
+ 						+ destReg]
+ 				ifFalse: [2r10101010 << 24
+ 						 + (srcReg << 16)
+ 						 + (XZR << 5)
+ 						 + destReg]).
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveRRAw (in category 'generate machine code - concretize processor-specific') -----
+ concretizeMoveRRAw
+ 	"C6.2.272 	STP		C6-1236"
+ 	<inline: true>
+ 	| pairAddress reg1 reg2 offset |
+ 	reg1 := operands at: 0.
+ 	reg2 := operands at: 1.
+ 	pairAddress := operands at: 2.
+ 	self assert: reg1 ~= reg2.
+ 	self assert: (reg1 ~= RISCTempReg and: [reg2 ~= RISCTempReg]).
+ 	self assert: (self isAddressRelativeToVarBase: pairAddress).
+ 	self assert: pairAddress - cogit varBaseAddress / 8 < (1 << 6).
+ 	reg1 = SP ifTrue: [reg1 := RISCTempReg].
+ 	reg2 = SP ifTrue: [reg2 := RISCTempReg].
+ 	(reg1 = RISCTempReg or: [reg2 = RISCTempReg])
+ 		ifTrue:
+ 			[machineCode
+ 				at: 0
+ 				put: (self movern: SP rd: RISCTempReg).
+ 			 offset := 1]
+ 		ifFalse:
+ 			[offset := 0].
+ 	machineCode
+ 		at: offset
+ 		put: 2r1010100100 << 22
+ 			+ (pairAddress - cogit varBaseAddress / 8 << 15)
+ 			+ (reg2 << 10)
+ 			+ (VarBaseReg << 5)
+ 			+ reg1.
+ 	"cogit processor
+ 		disassembleInstructionAt: 0 In: machineCode object;
+ 		disassembleInstructionAt: 4 In: machineCode object"
+ 	^offset + 1 * 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveRRd (in category 'generate machine code - concretize') -----
+ concretizeMoveRRd
+ 	<inline: true>
+ 	"C7.2.124	FMOV (general)		C7-1651"
+ 	machineCode
+ 		at: 0
+ 		put: 2r1001111001100111 << 16
+ 			+ ((operands at: 0) << 5)
+ 			+ (operands at: 1).
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveRXSrR: (in category 'generate machine code - concretize') -----
+ concretizeMoveRXSrR: unitSizeLog2MinusOne
+ 	"Xwr/X32r/X16r/Xbr - memory unit whose address is r * unit size away from an address in a register"
+ 	"C6.2.274	STR (register)	C6-1242"
+ 	| src index base |
+ 	src := operands at: 0.
+ 	index := operands at: 1.
+ 	base := operands at: 2.
+ 	self deny: (SP = src or: [SP = index]).
+ 	machineCode
+ 		at: 0
+ 		put: unitSizeLog2MinusOne << 30
+ 			+ (2r111000001 << 21)
+ 			+ (index << 16)
+ 			+ (UXTX << 13)
+ 			+ (3 << 11)
+ 			+ (base << 5)
+ 			+ src.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveRXbrR (in category 'generate machine code - concretize') -----
+ concretizeMoveRXbrR
+ 	<inline: true>
+ 	"Xbr - byte in mwemory whose address is r away from an address in a register"
+ 	"C6.2.274	STR (register)	C6-1242"
+ 	| src index base |
+ 	src := operands at: 0.
+ 	index := operands at: 1.
+ 	base := operands at: 2.
+ 	self deny: (SP = src or: [SP = index]).
+ 	machineCode
+ 		at: 0
+ 		put: 2r00111000001 << 21
+ 			+ (index << 16)
+ 			+ (UXTX << 13)
+ 			+ (3 << 11)
+ 			+ (base << 5)
+ 			+ src.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveRdM64r (in category 'generate machine code - concretize') -----
+ concretizeMoveRdM64r
+ 	"Load/Store Vector on page C3-206.
+ 	 C7.2.323	STR (immediate, SIMD&FP)	C7-2114"
+ 	<inline: true>
+ 	| rd offset baseReg |
+ 	rd := operands at: 0.
+ 	offset := operands at: 1.
+ 	baseReg := operands at: 2.
+ 	self assert: (offset noMask: 7).
+ 	machineCode
+ 		at: 0
+ 		put: 2r11111101 << 24
+ 			+ (offset << 7 "10 - 3")
+ 			+ (baseReg << 5)
+ 			+ rd.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveRdR (in category 'generate machine code - concretize') -----
+ concretizeMoveRdR
+ 	<inline: true>
+ 	"C7.2.124	FMOV (general)		C7-1651"
+ 	machineCode
+ 		at: 0
+ 		put: 2r1001111001100110 << 16
+ 			+ ((operands at: 0) << 5)
+ 			+ (operands at: 1).
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveXSrRR: (in category 'generate machine code - concretize') -----
+ concretizeMoveXSrRR: unitSizeLog2MinusOne
+ 	"Xwr/X32r/X16r/Xbr - memory unit whose address is r * unit size away from an address in a register"
+ 	"C6.2.132	LDR (register)	C6-981"
+ 	| index base dest |
+ 	index := operands at: 0.
+ 	base := operands at: 1.
+ 	dest := operands at: 2.
+ 	self deny: SP = dest.
+ 	machineCode
+ 		at: 0
+ 		put: unitSizeLog2MinusOne << 30
+ 			+ (2r111000011 << 21)
+ 			+ (index << 16)
+ 			+ (UXTX << 13)
+ 			+ (3 << 11)
+ 			+ (base << 5)
+ 			+ dest.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMulOverflowJump (in category 'generate machine code - concretize processor-specific') -----
+ concretizeMulOverflowJump
+ 	"Will get inlined into concretizeAt: switch."
+ 	"Sizing/generating jumps.
+ 		Jump targets can be to absolute addresses or other abstract instructions.
+ 		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
+ 		Otherwise instructions must have a machineCodeSize which must be kept to."
+ 	<inline: false>
+ 	| offset |
+ 	offset := self computeJumpTargetOffset - 4. "-4 because the jump is from the second word..."
+  	self assert: (offset ~= 0 and: [self isInImmediateBranchRange: offset]).
+ 	"See concretizeMulOverflowRRR
+ 	 RISCTempReg := RISCTempReg + CArg1Reg/sign.
+ 	 JumpZero/NonZero"
+ 	machineCode
+ 		at: 0
+ 		put: 2r10001011 << 24
+ 			+ (ArithmeticAddS << 29)
+ 			+ (CArg1Reg << 16)
+ 			+ (RISCTempReg << 5)
+ 			+ RISCTempReg;
+ 		at: 1
+ 		put: (self
+ 				cond: (opcode = JumpMulOverflow ifTrue: [NE] ifFalse: [EQ])
+ 				offset: offset). "B offset"
+ 	^8!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMulOverflowRRR (in category 'generate machine code - concretize processor-specific') -----
+ concretizeMulOverflowRRR
+ 	"ARMv8 has no multiply overflow detection.  Instead it is synthesized from the two halves of
+ 	 a 64x64=>128 bit multiply. The upper 64-bits are tested.  The sequence is
+ 		low64 := MUL a,b
+ 		high64 := SMULH a,b
+ 		signBit := low64 >> 63
+ 		high64 := high64 + signBit
+ 	 If high64 is zero after this sequence then the multiply has not overflowed, since
+ 	 high64 is an extension of signBit if no overflow (either 0 or -1) and -1 + 1 = 0.
+ 	 However, since we restrict ourselves to three concrete ARMv8 instructions per abstract instruction
+ 	 we move the last operation of the sequence to concretizeMulOverflowJump
+ 
+ 	 C6.2.196	MUL				C6-1111
+ 	 C6.2.242	SMULH				C6-1184
+ 	 C6.2.180	LSR (immediate)	C6-1081	110100110 (1)"
+ 
+ 	<inline: true>
+ 	| reg1 reg2 reg3 |
+ 	reg1 := operands at: 0.
+ 	reg2 := operands at: 1.
+ 	reg3 := operands at: 2.
+ 	"reg3 := reg1 * reg2"
+ 	machineCode
+ 		at: 0
+ 		put: 2r10011011 << 24
+ 			+ (reg1 << 16)
+ 			+ (XZR << 10)
+ 			+ (reg2 << 5)
+ 			+ reg3.
+ 	"RISCTempReg := high(reg1 * reg2)"
+ 	machineCode
+ 		at: 1
+ 		put: 2r1001101101 << 22
+ 			+ (reg1 << 16)
+ 			+ (XZR << 10)
+ 			+ (reg2 << 5)
+ 			+ RISCTempReg.
+ 	"CArg1Reg := sign(reg3)"
+ 	machineCode
+ 		at: 2
+ 		put: 2r1101001101 << 22
+ 			+ (63 << 16) "constant to shift by"
+ 			+ (63 << 10)
+ 			+ (reg3 << 5)
+ 			+ CArg1Reg. "cuz CArg0Reg == TempReg"
+ 	"RISCTempReg := RISCTempReg + CArg1Reg/sign
+ 	 is in concretizeMulOverflowJump"
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	"cogit processor disassembleInstructionAt: 4 In: machineCode object"
+ 	"cogit processor disassembleInstructionAt: 8 In: machineCode object"
+ 	^12!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMulRRR (in category 'generate machine code - concretize') -----
+ concretizeMulRRR
+ 	"C6.2.196	MUL	C6-1111"
+ 	<inline: true>
+ 	"reg3 := reg1 * reg2"
+ 	| reg1 reg2 reg3 |
+ 	reg1 := operands at: 0.
+ 	reg2 := operands at: 1.
+ 	reg3 := operands at: 2.
+ 	machineCode
+ 		at: 0
+ 		put: 2r10011011 << 24
+ 			+ (reg1 << 16)
+ 			+ (XZR << 10)
+ 			+ (reg2 << 5)
+ 			+ reg3.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeNativePopRR (in category 'generate machine code - concretize processor-specific') -----
+ concretizeNativePopRR
+ 	"C6.2.128 	LDP		C6-970"
+ 	<inline: true>
+ 	| reg1 reg2 |
+ 	reg1 := operands at: 0.
+ 	reg2 := operands at: 1.
+ 	"Post-index"
+ 	machineCode
+ 		at: 0
+ 		put: 2r10101000110000010 << 15
+ 			+ (reg2 << 10)
+ 			+ (SP << 5)
+ 			+ reg1.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeNativePushRR (in category 'generate machine code - concretize processor-specific') -----
+ concretizeNativePushRR
+ 	"C6.2.272 	STP		C6-1236"
+ 	<inline: true>
+ 	| reg1 reg2 |
+ 	reg1 := operands at: 0.
+ 	reg2 := operands at: 1.
+ 	"Pre-index"
+ 	machineCode
+ 		at: 0
+ 		put: 2r10101001101111110 << 15
+ 			+ (reg2 << 10)
+ 			+ (SP << 5)
+ 			+ reg1.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeNativeRetN (in category 'generate machine code - concretize processor-specific') -----
+ concretizeNativeRetN
+ 	"Will get inlined into concretizeAt: switch."
+ 	<var: #offset type: #sqInt>
+ 	<inline: true>
+ 	| offset |
+ 	offset := operands at: 0.
+ 	"C6.2.218 RET p1147"
+ 	offset = 0 ifTrue:
+ 		[machineCode
+ 			at: 0
+ 			put: 2r1101011001 << 22
+ 				+ (XZR << 16)
+ 				+ (LR << 5).
+ 		^4].
+ 
+ 	"C6.2.4 ADD (immediate) p761"
+ 	machineCode
+ 		at: 0 put: (self addrn: NativeSPReg rd: NativeSPReg imm: offset shiftBy12: false);
+ 		at: 1 put: 2r1101011001 << 22
+ 				+ (XZR << 16)
+ 				+ (LR << 5).
+ 	^8!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeNegateR (in category 'generate machine code - concretize') -----
+ concretizeNegateR
+ 	<inline: true>
+ 	"C6.2.309	SUB (shifted register) 1313
+ 	 C6.2.313	SUBS (extended register)	C6-1318"
+ 	| reg |
+ 	reg := operands at: 0.
+ 	self deny: SP = reg.
+ 	machineCode
+ 		at: 0
+ 		put: 2r11001011 << 24
+ 			+ (reg << 16)
+ 			+ (XZR << 5)
+ 			+ reg.
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeNop (in category 'generate machine code - concretize') -----
+ concretizeNop
+ 	<inline: true>
+ 	machineCode at: 0 put: NOP.
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizePopR (in category 'generate machine code - concretize') -----
+ concretizePopR
+ 	<inline: true>
+ 	"C6.2.130	LDR (immediate)	C6-976
+ 	 Post-index"
+ 	| reg |
+ 	reg := operands at: 0.
+ 	self deny: SP = reg.
+ 	machineCode
+ 		at: 0
+ 		put: 2r1111100001 << 22
+ 			+ (8 << 12)
+ 			+ (2r01 << 10)
+ 			+ (SPReg << 5)
+ 			+ reg.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizePrefetchAw (in category 'generate machine code - concretize') -----
+ concretizePrefetchAw
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcAddr |
+ 	srcAddr := operands at: 0.
+ 	(self isAddressRelativeToVarBase: srcAddr) ifTrue:
+ 		[srcAddr < cogit varBaseAddress ifTrue:
+ 			[self shouldBeImplemented.
+ 			 ^4].
+ 		 machineCode
+ 			at: 0
+ 			put: (self prn: VarBaseReg imm: srcAddr - cogit varBaseAddress shiftBy12: false).
+ 		 ^4].
+ 	self halt.
+ 	^0!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizePushCq (in category 'generate machine code - concretize') -----
+ concretizePushCq
+ 	"ARMv8 has no push costant insructions (no store immediate pre-index).
+ 	 Instead load the constant into RISCTempReg and push that."
+ 	<inline: true>
+ 	| instrBytes |
+ 	operands at: 1 put: RISCTempReg.
+ 	instrBytes := self concretizeMoveCqR.
+ 	"C6.2.273	STR (immediate)	Pre-index	C6-1239"
+ 	machineCode
+ 		at: instrBytes // 4
+ 		put: 2r11111 << 27
+ 			+ ((-8 bitAnd: 1 << 9 - 1) << 12)
+ 			+ (2r11 << 10)
+ 			+ (SPReg << 5)
+ 			+ RISCTempReg.
+ 	^instrBytes + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizePushCw (in category 'generate machine code - concretize') -----
+ concretizePushCw
+ 	<inline: true>
+ 	| instrBytes |
+ 	instrBytes := self emitMoveCw: (operands at: 0) intoR: RISCTempReg at: 0.
+ 	"C6.2.273	STR (immediate)	Pre-index	C6-1239"
+ 	machineCode
+ 		at: instrBytes // 4
+ 		put: 2r11111 << 27
+ 			+ ((-8 bitAnd: 1 << 9 - 1) << 12)
+ 			+ (2r11 << 10)
+ 			+ (SPReg << 5)
+ 			+ RISCTempReg.
+ 	^instrBytes + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizePushR (in category 'generate machine code - concretize') -----
+ concretizePushR
+ 	<inline: true>
+ 	"C6.2.273	STR (immediate)	C6-1239
+ 	 Pre-index"
+ 	| reg |
+ 	reg := operands at: 0.
+ 	self deny: SP = reg.
+ 	machineCode
+ 		at: 0
+ 		put: 2r11111 << 27
+ 			+ ((-8 bitAnd: 1 << 9 - 1) << 12)
+ 			+ (2r11 << 10)
+ 			+ (SPReg << 5)
+ 			+ reg.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeRRArithmetic:Rd: (in category 'generate machine code - concretize') -----
+ concretizeRRArithmetic: arithOp Rd: rd
+ 	"rd := regA op regB "
+ 	| regA regB |
+ 	regB := operands at: 0.
+ 	regA := operands at: 1.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	"cogit processor disassembleInstructionAt: 4 In: machineCode object"
+ 	SP = regB ifTrue:	"Arithmetic with the sp; we must use the extended register forms, and negate
+ 						 on subtract because we can't have Rm as SP, Rm = 31 is interoreted as XZR."
+ 		["ADD (extended register) on page C6-758
+ 		  ADDS (extended register) on page C6-766
+ 		  SUB (extended register) on page C6-1308
+ 		  SUBS (extended register) on page C6-1318"
+ 		 machineCode
+ 			at: 0
+ 			put: 2r10001011001 << 21
+ 				+ (arithOp << 29)
+ 				+ (regA << 16)
+ 				+ (UXTX << 13)
+ 				+ (regB << 5)
+ 				+ rd.
+ 		 (arithOp = ArithmeticSub or: [arithOp = ArithmeticSubS]) ifFalse:
+ 			[^4].
+ 		 machineCode
+ 			at: 1
+ 			put: 2r10001011 << 24
+ 				+ (arithOp << 29)
+ 				+ (rd << 16)
+ 				+ (XZR << 5)
+ 				+ rd.
+ 		 ^8].
+ 	SP = regA ifTrue: "Arithmetic with the sp; we must use the extended register forms."
+ 		["ADD (extended register) on page C6-758
+ 		  ADDS (extended register) on page C6-766
+ 		  SUB (extended register) on page C6-1308
+ 		  SUBS (extended register) on page C6-1318
+ 		  CMN (extended register) on page C6-850
+ 		  CMP (extended register) on page C6-856"
+ 		 machineCode
+ 			at: 0
+ 			put: 2r10001011001 << 21
+ 					+ (arithOp << 29)
+ 					+ (regB << 16)
+ 					+ (UXTX << 13)
+ 					+ (regA << 5)
+ 					+ rd.
+ 		 rd ~= XZR ifTrue: [self halt].
+ 		 ^4].
+ 	self assert: (regA ~= SP and: [regB ~= SP]).
+ 	"ADD (shifted register) on page C6-763
+ 	 ADDS (shifted register) on page C6-771
+ 	 CMN (shifted register) on page C6-854
+ 	 CMP (shifted register) on page C6-860
+ 	 SUB (shifted register) on page C6-1313
+ 	 SUBS (shifted register) on page C6-1323"
+ 	 machineCode
+ 		at: 0
+ 		put: 2r10001011 << 24
+ 			+ (arithOp << 29)
+ 			+ (regB << 16)
+ 			+ (regA << 5)
+ 			+ rd.
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeRRLogical: (in category 'generate machine code - concretize') -----
+ concretizeRRLogical: logicalOp
+ 	"AND (shifted register) - 64-bit variant on page C6-777
+ 	 BIC (shifted register) - 64-bit variant on page C6-808
+ 	 ORR (shifted register) - 64-bit variant on page C6-1127
+ 	 ORN (shifted register) - 64-bit variant on page C6-1123
+ 	 EOR (shifted register) - 64-bit variant on page C6-898
+ 	 EON (shifted register) - 64-bit variant on page C6-894
+ 	 ANDS (shifted register) - 64-bit variant on page C6-781
+ 	 BICS (shifted register) - 64-bit variant on page C6-810"
+ 	| destReg srcReg |
+ 	srcReg := operands at: 0.
+ 	destReg := operands at: 1.
+ 	machineCode
+ 		at: 0
+ 		put: 2r1000101 << 25
+ 			+ (logicalOp << 29)
+ 			+ (srcReg << 16)
+ 			+ (destReg << 5)
+ 			+ destReg.
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeRetN (in category 'generate machine code - concretize') -----
+ concretizeRetN
+ 	"Will get inlined into concretizeAt: switch."
+ 	<var: #offset type: #sqInt>
+ 	<inline: true>
+ 	| offset |
+ 	offset := operands at: 0.
+ 	"C6.2.218 RET p1147"
+ 	offset = 0 ifTrue:
+ 		[machineCode
+ 			at: 0
+ 			put: 2r1101011001 << 22
+ 				+ (XZR << 16)
+ 				+ (LR << 5).
+ 		^4].
+ 
+ 	"C6.2.4 ADD (immediate) p761"
+ 	machineCode
+ 		at: 0 put: (self addrn: SPReg rd: SPReg imm: offset shiftBy12: false);
+ 		at: 1 put: 2r1101011001 << 22
+ 				+ (XZR << 16)
+ 				+ (LR << 5).
+ 	^8!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeRotateCqR (in category 'generate machine code - concretize') -----
+ concretizeRotateCqR
+ 	"C6.2.225	ROR (immediate)	C6-1157"
+ 	<inline: true>
+ 	| constant reg |
+ 	constant := operands at: 0.
+ 	reg := operands at: 1.
+ 	self assert: (constant between: 1 and: 63).
+ 	machineCode
+ 		at: 0
+ 		put: 2r1001001111 << 22
+ 			+ (reg << 16)
+ 			+ ((RotateRightCqR = opcode ifTrue: [constant] ifFalse: [64 - constant]) << 10)
+ 			"+ (1 << 10)"
+ 			+ (reg << 5)
+ 			+ reg.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeSTLR (in category 'generate machine code - concretize processor-specific') -----
+ concretizeSTLR
+ 	| valueReg "Xt" baseReg "Xn" |
+ 	valueReg := operands at: 0.
+ 	baseReg := operands at: 1.
+ 	machineCode
+ 		at: 0
+ 		put: 2r1100100010011111111111 << 10
+ 			+ (baseReg << 5)
+ 			+ valueReg.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object '00000000: stlr	x0, [x1]'"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeSTLXR (in category 'generate machine code - concretize') -----
+ concretizeSTLXR
+ 	"C6.2.268		STLXR		C6-1228"
+ 	<inline: true>
+ 	| valueReg addressReg statusReg |
+ 	valueReg := operands at: 0.
+ 	addressReg := operands at: 1.
+ 	statusReg := operands at: 2.
+ 	machineCode
+ 		at: 0
+ 		put: 2r11001 << 27
+ 			+ (statusReg << 16)
+ 			+ (63 << 10)
+ 			+ (addressReg << 5)
+ 			+ valueReg.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeShiftRR: (in category 'generate machine code - concretize') -----
+ concretizeShiftRR: shiftOp
+ 	"C6.2.18 	ASRV	C6-787		(a.k.a	C6.2.16 	ASR (register)	
+ 	 C6.2.178	LSLV	C6-1077	(a.k.a	C6.2.176	LSL (register)	
+ 	 C6.2.181	LSRV	C6-1083	(a.k.a	C6.2.179	LSR (register)"
+ 	<inline: true>
+ 	| shiftedReg shiftCountReg |
+ 	shiftCountReg := operands at: 0.
+ 	shiftedReg := operands at: 1.
+ 	machineCode
+ 		at: 0
+ 		put: 2r10011010110 << 21
+ 			+ (shiftCountReg << 16)
+ 			+ (shiftOp << 10)
+ 			+ (shiftedReg << 5)
+ 			+ shiftedReg.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeSignExtendRR: (in category 'generate machine code - concretize') -----
+ concretizeSignExtendRR: width
+ 	"C6.2.320 	SXTB	C6-1332
+ 	 C6.2.321 	SXTH	C6-1334
+ 	 C6.2.322 	SXTW	C6-1336"
+ 	| rn rd |
+ 	rn := operands at: 0.
+ 	rd := operands at: 1.
+ 	machineCode
+ 		at: 0
+ 		put: 2r1001001101 << 22
+ 			+ (width - 1 << 10)
+ 			+ (rn << 5)
+ 			+ rd.
+ 	^4
+ 
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeSqrtRd (in category 'generate machine code - concretize') -----
+ concretizeSqrtRd
+ 	"C7.2.165	FSQRT (scalar)	C7-1743"
+ 	<inline: true>
+ 	| reg |
+ 	reg := operands at: 0.
+ 	machineCode
+ 		at: 0
+ 		put: 2r111100110000111 << 14
+ 			+ (reg << 5)
+ 			+ reg.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeStop (in category 'generate machine code - concretize') -----
+ concretizeStop
+ 	<inline: true>
+ 	machineCode at: 0 put: self stop.
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeSubCqR (in category 'generate machine code - concretize') -----
+ concretizeSubCqR
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| constant reg offset |
+ 	<var: #constant type: #sqInt>
+ 	constant := (operands at: 0) signedIntFromLong64.
+ 	reg := operands at: 1.
+ 
+ 	self isPossiblyShiftableImm12: constant
+ 		ifTrue:
+ 			[:shift|
+ 			"C6.2.308		SUB (immediate)	C6-1311
+ 			 C6.2.314		SUBS (immediate)	C6-1321"
+ 			machineCode
+ 				at: 0
+ 				put: (reg = SP
+ 						ifTrue:  [2r110100010]
+ 						ifFalse: [2r111100010]) << 23
+ 					+ (shift ifTrue: [constant >> 2 + (1 << 22)] ifFalse: [constant << 10])
+ 					+ (reg << 5)
+ 					+ reg.
+ 			^4]
+ 		ifFalse: [].
+ 	self isPossiblyShiftableImm12: constant negated
+ 		ifTrue:
+ 			[:shift|
+ 			"C6.2.4		ADDS (immediate)	C6-761
+ 			 C6.2.8		ADDS (immediate)	C6-769"
+ 			machineCode
+ 				at: 0
+ 				put: (reg = SP
+ 						ifTrue:  [2r100100010]
+ 						ifFalse: [2r101100010]) << 23
+ 					+ (shift ifTrue: [constant negated >> 2 + (1 << 22)] ifFalse: [constant negated << 10])
+ 					+ (reg << 5)
+ 					+ reg.
+ 			^4]
+ 		ifFalse: [].
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	"cogit processor disassembleInstructionAt: 4 In: machineCode object"
+ 	offset := self emitMoveCw: constant intoR: RISCTempReg at: 0.
+ 	self deny: SP = reg.
+ 	"C6.2.313	SUBS (extended register)		C6-1318"
+ 	machineCode
+ 				at: offset // 4
+ 				put: 2r10001011 << 24
+ 				+ (ArithmeticSubS << 29)
+ 				+ (RISCTempReg << 16)
+ 				+ (reg << 5)
+ 				+ reg.
+ 	^offset + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeXorRdRd (in category 'generate machine code - concretize') -----
+ concretizeXorRdRd
+ 	"C7.2.34	EOR (vector)	C7-1440"
+ 	<inline: true>
+ 	| srcReg destReg |
+ 	srcReg := operands at: 0.
+ 	destReg := operands at: 1.
+ 	machineCode
+ 		at: 0
+ 		put: 2r101110001 << 21
+ 			+ (srcReg << 16)
+ 			+ (2r111 << 10)
+ 			+ (destReg << 5)
+ 			+ destReg.
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeZeroExtendRR: (in category 'generate machine code - concretize') -----
+ concretizeZeroExtendRR: width
+ 	"C6.2.333	UBFX	C6-1353
+ 	 C6.2.341 	UXTB	C6-1364
+ 	 C6.2.342 	UXTH	C6-1366"
+ 	| rn rd |
+ 	rn := operands at: 0.
+ 	rd := operands at: 1.
+ 	machineCode
+ 		at: 0
+ 		put: 2r1101001101 << 22
+ 			+ (width - 1 << 10)
+ 			+ (rn << 5)
+ 			+ rd.
+ 	^4
+ 
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"!

Item was added:
+ ----- Method: CogARMv8Compiler>>cond:offset: (in category 'generate machine code - support') -----
+ cond: cond offset: offset
+ 	"Conditional branch (immediate) C4-257"
+ 	<inline: true>
+ 	self assert: (offset bitAnd: 3) = 0.
+ 	^2r010101 << 26
+ 	+ ((offset bitAnd: 1 << 21 - 1) << 3) "(offset / 4 bitAnd: 1 << 19 - 1) << 5"
+ 	+ cond!

Item was added:
+ ----- Method: CogARMv8Compiler>>countLeadingOnes: (in category 'generate machine code - support') -----
+ countLeadingOnes: anInteger
+ 	| count theInteger |
+ 	anInteger >= 0 ifTrue: [^0].
+ 	theInteger := anInteger.
+ 	count := 0.
+ 	5 to: 0 by: -1 do:
+ 		[:logBase2Shift| | shift |
+ 		shift := 1 << logBase2Shift.
+ 		theInteger >>> shift = -1
+ 			ifTrue: [count := count + shift]
+ 			ifFalse: [theInteger := theInteger >>> shift]].
+ 	^theInteger = -1
+ 		ifTrue: [count + 1]
+ 		ifFalse: [count]
+ 	
+ 
+ 	"self basicNew countLeadingOnes: -16
+ 	((-16 bitAnd: 1 << 64 - 1) binary copyUpTo: $0) occurrencesOf: $1
+ 
+ 	self basicNew countLeadingOnes: -1
+ 	((-1 bitAnd: 1 << 64 - 1) binary copyUpTo: $0) occurrencesOf: $1
+ 
+ 	(-1 to: -64 by: -1)
+ 		select: [:n| (self basicNew countLeadingOnes: n) ~= (((n bitAnd: 1 << 64 - 1) binary copyUpTo: $0) occurrencesOf: $1)]
+ 		thenCollect: [:n| {self basicNew countLeadingOnes: n. (n bitAnd: 1 << 64 - 1) binary}]"!

Item was added:
+ ----- Method: CogARMv8Compiler>>countTrailingOnes: (in category 'generate machine code - support') -----
+ countTrailingOnes: anInteger
+ 	| bits count |
+ 	bits := anInteger.
+ 	count := 0.
+ 	[bits allMask: 16rFFFF] whileTrue:
+ 		[bits := bits bitShift: -16.
+ 		 count := count + 16].
+ 	[bits allMask: 16rFF] whileTrue:
+ 		[bits := bits bitShift: -8.
+ 		 count := count + 8].
+ 	(bits allMask: 16rF) ifTrue:
+ 		[bits := bits bitShift: -4.
+ 		 count := count + 4].
+ 	(bits allMask: 16r3) ifTrue:
+ 		[bits := bits bitShift: -2.
+ 		 count := count + 2].
+ 	 ^(bits allMask: 1) ifTrue: [count + 1] ifFalse: [count]
+ 
+ 	"(-16 to: 16) collect: [:i| {i. self basicNew countTrailingOnes: (i bitAnd: 1 << 64 - 1)}]"!

Item was added:
+ ----- Method: CogARMv8Compiler>>countTrailingZeros: (in category 'generate machine code - support') -----
+ countTrailingZeros: anInteger
+ 	"a.k.a. anInteger lowBit - 1"
+ 	| n result |
+ 	self assert: anInteger ~= 0.
+ 	n := anInteger.
+ 	result := 0.
+ 	[n noMask: 16rFF]
+ 		whileTrue:
+ 			[result := result + 8.
+ 			n := n bitShift: -8].
+ 	(n noMask: 16rF) ifTrue:
+ 		[result := result + 4.
+ 		 n := n bitShift: -4].
+ 	(n noMask: 16r3) ifTrue:
+ 		[result := result + 2.
+ 		 n := n bitShift: -2].
+ 	^(n anyMask: 1)
+ 		ifTrue: [result]
+ 		ifFalse: [result + 1]
+ 
+ 	"| me |
+ 	me := self basicNew.
+ 	(1 to: 65535) reject: [:i| i lowBit - 1 = (me countTrailingZeros: i)]"!

Item was added:
+ ----- Method: CogARMv8Compiler>>ctrEl0 (in category 'feature detection') -----
+ ctrEl0
+ 	<cmacro: '(ign) ctrEl0'>
+ 	"For want of somewhere to put the variable..."
+ 	^self class ctrEl0!

Item was added:
+ ----- Method: CogARMv8Compiler>>decode64Imms:immr: (in category 'generate machine code - support') -----
+ decode64Imms: imms immr: immr
+ 	"See aarch64/instrs/integer/bitmasks/DecodeBitMasks J1-7389.
+ 	 This is a 64-bit version computing the imm mask (wmask) only."
+ 	<returnTypeC: #usqInt>
+ 	| mask |
+ 	<var: 'mask' type: #usqInt>
+ 	self assert: ((imms between: 0 and: 63) and: [immr between: 0 and: 63]).
+ 	"For logical immediates an all-ones value of S is reserved since it would generate a useless all-ones result (many times)"
+ 	imms = 63 ifTrue:
+ 		[^self cCode: [0] inSmalltalk: [#undefined]].
+ 
+ 	mask := 1 << (imms + 1) - 1.
+ 	^immr = 0
+ 		ifTrue: [mask]
+ 		ifFalse: [(mask << (64 - immr) bitAnd: 1 << 64 - 1) + (mask >> immr)]!

Item was added:
+ ----- Method: CogARMv8Compiler>>detectFeatures (in category 'feature detection') -----
+ detectFeatures
+ 	"Do throw-away compilations to read CTR_EL0 & ID_AA64ISAR0_EL1 and initialize ctrEl0 & idISAR0"
+ 	| startAddress getFeatureReg |
+ 	<var: 'getFeatureReg' declareC: 'usqIntptr_t (*getFeatureReg)(void)'>
+ 	startAddress := cogit methodZoneBase.
+ 	cogit allocateOpcodes: 3 bytecodes: 0.
+ 	getFeatureReg := cogit cCoerceSimple: startAddress to: #'usqIntptr_t (*)(void)'.
+ 	"Return the value of CTR_EL0; that's the control register that defines the vital statistics of the processor's caches."
+ 	cogit
+ 		gen: MRS_CTR_EL0 operand: ABIResultReg;
+ 		RetN: 0.
+ 	cogit outputInstructionsForGeneratedRuntimeAt: startAddress.
+ 	cogit resetMethodZoneBase: startAddress.
+ 	self setCtrEl0: (self cCode: 'getFeatureReg()' inSmalltalk: [cogit simulateLeafCallOf: startAddress]).
+ 	cogit zeroOpcodeIndexForNewOpcodes.
+ 	cogit
+ 		gen: MRS_ID_AA64ISAR0_EL1 operand: ABIResultReg;
+ 		RetN: 0.
+ 	cogit outputInstructionsForGeneratedRuntimeAt: startAddress.
+ 	cogit resetMethodZoneBase: startAddress.
+ 	self setIdISAR0: (self cCode: 'getFeatureReg()' inSmalltalk: [cogit simulateLeafCallOf: startAddress])!

Item was added:
+ ----- Method: CogARMv8Compiler>>dispatchConcretize (in category 'generate machine code') -----
+ dispatchConcretize
+ 	"Attempt to generate concrete machine code for the instruction at address.
+ 	 This is the inner dispatch of concretizeAt: actualAddress which exists only
+ 	 to get around the branch size limits in the SqueakV3 (blue book derived)
+ 	 bytecode set."
+ 		 
+ 	opcode caseOf: {
+ 		"Noops & Pseudo Ops"
+ 		[Label]					-> [^self concretizeLabel].
+ 		[Literal]					-> [^self concretizeLiteral].
+ 		[AlignmentNops]		-> [^self concretizeAlignmentNops].
+ 		[Fill32]					-> [^self concretizeFill32].
+ 		[Nop]					-> [^self concretizeNop].
+ 		"Control"
+ 		[Call]						-> [^self concretizeCall]. "call code within code space"
+ 		[CallFull]					-> [^self concretizeCallJumpFull: true]. "call code anywhere in address space"
+ 		[JumpR]					-> [^self concretizeJumpR].
+ 		[JumpFull]					-> [^self concretizeCallJumpFull: false]."jump within address space"
+ 		[JumpLong]				-> [^self concretizeJumpLong]."jump within code space"
+ 		[JumpLongZero]			-> [^self concretizeConditionalLongJump: EQ].
+ 		[JumpLongNonZero]		-> [^self concretizeConditionalLongJump: NE].
+ 		[Jump]						-> [^self concretizeConditionalJump: AL]. "jump within a method, etc"
+ 		[JumpZero]					-> [^self concretizeConditionalJump: EQ].
+ 		[JumpNonZero]				-> [^self concretizeConditionalJump: NE].
+ 		[JumpNegative]				-> [^self concretizeConditionalJump: MI].
+ 		[JumpNonNegative]			-> [^self concretizeConditionalJump: PL].
+ 		[JumpOverflow]				-> [^self concretizeConditionalJump: VS].
+ 		[JumpNoOverflow]			-> [^self concretizeConditionalJump: VC].
+ 		[JumpMulOverflow]			-> [^self concretizeMulOverflowJump].
+ 		[JumpNoMulOverflow]		-> [^self concretizeMulOverflowJump].
+ 		[JumpCarry]				-> [^self concretizeConditionalJump: CS].
+ 		[JumpNoCarry]				-> [^self concretizeConditionalJump: CC].
+ 		[JumpLess]					-> [^self concretizeConditionalJump: LT].
+ 		[JumpGreaterOrEqual]		-> [^self concretizeConditionalJump: GE].
+ 		[JumpGreater]				-> [^self concretizeConditionalJump: GT].
+ 		[JumpLessOrEqual]			-> [^self concretizeConditionalJump: LE].
+ 		[JumpBelow]				-> [^self concretizeConditionalJump: CC]. "unsigned lower"
+ 		[JumpAboveOrEqual]		-> [^self concretizeConditionalJump: CS]. "unsigned greater or equal"
+ 		[JumpAbove]				-> [^self concretizeConditionalJump: HI].
+ 		[JumpBelowOrEqual]		-> [^self concretizeConditionalJump: LS].
+ 		[JumpFPEqual]				-> [^self concretizeConditionalJump: EQ].
+ 		[JumpFPNotEqual]			-> [^self concretizeConditionalJump: NE].
+ 		[JumpFPLess]				-> [^self concretizeConditionalJump: LT].
+ 		[JumpFPGreaterOrEqual]	-> [^self concretizeConditionalJump: GE].
+ 		[JumpFPGreater]			-> [^self concretizeConditionalJump: GT].
+ 		[JumpFPLessOrEqual]		-> [^self concretizeConditionalJump: LE].
+ 		[JumpFPOrdered]			-> [^self concretizeConditionalJump: VC].
+ 		[JumpFPUnordered]		-> [^self concretizeConditionalJump: VS].
+ 		[RetN]						-> [^self concretizeRetN].
+ 		[NativeRetN]				-> [^self concretizeNativeRetN].
+ 		[Stop]						-> [^self concretizeStop].
+ 		"Arithmetic"
+ 		[AddCqR]						-> [^self concretizeAddCqRDest: (operands at: 1)].
+ 		[AddCqRR]						-> [^self concretizeAddCqRDest: (operands at: 2)].
+ 		[AndCqR]						-> [^self concretizeLogicalOp: LogicalAndS CqRDest: (operands at: 1)].
+ 		[AndCqRR]						-> [^self concretizeLogicalOp: LogicalAndS CqRDest: (operands at: 2)].
+ 		[OrCqR]						-> [^self concretizeLogicalOp: LogicalOr CqRDest: (operands at: 1)].
+ 		[OrCqRR]						-> [^self concretizeLogicalOp: LogicalOr CqRDest: (operands at: 2)].
+ 		[CmpCqR]						-> [^self concretizeCmpCqR].
+ 		[SubCqR]						-> [^self concretizeSubCqR].
+ 		[TstCqR]						-> [^self concretizeLogicalOp: LogicalAndS CqRDest: XZR].
+ 		[XorCqR]						-> [^self concretizeLogicalOp: LogicalXor CqRDest: (operands at: 1)].
+ 		[AddCwR]						-> [^self concretizeCwRArithmetic: ArithmeticAddS Rd: (operands at: 1)].
+ 		[AndCwR]						-> [^self concretizeCwRLogical: LogicalAndS].
+ 		[CmpCwR]						-> [^self concretizeCwRArithmetic: ArithmeticSubS Rd: XZR].
+ 		[CmpC32R]						-> [^self concretizeCmpC32R].
+ 		[OrCwR]						-> [^self concretizeCwRLogical: LogicalOr].
+ 		[SubCwR]						-> [^self concretizeCwRArithmetic: ArithmeticSubS Rd: (operands at: 1)].
+ 		[XorCwR]						-> [^self concretizeCwRLogical: LogicalXor].
+ 		[AddRR]						-> [^self concretizeRRArithmetic: ArithmeticAddS Rd: (operands at: 1)].
+ 		[AndRR]						-> [^self concretizeRRLogical: LogicalAndS].
+ 		[CmpRR]						-> [^self concretizeRRArithmetic: ArithmeticSubS Rd: XZR].
+ 		[OrRR]							-> [^self concretizeRRLogical: LogicalOr].
+ 		[SubRR]						-> [^self concretizeRRArithmetic: ArithmeticSubS Rd: (operands at: 1)].
+ 		[XorRR]							-> [^self concretizeRRLogical: LogicalXor].
+ 		[AddRRR]						-> [^self concretizeRRArithmetic: ArithmeticAddS Rd: (operands at: 2)].
+ 		[SubRRR]						-> [^self concretizeRRArithmetic: ArithmeticSubS Rd: (operands at: 2)].
+ 		[AddRdRd]						-> [^self concretizeMathRdRd: 2r1010].
+ 		[CmpRdRd]						-> [^self concretizeCmpRdRd].
+ 		[DivRdRd]						-> [^self concretizeMathRdRd: 2r0110].
+ 		[MulRdRd]						-> [^self concretizeMathRdRd: 2r0010].
+ 		[SubRdRd]						-> [^self concretizeMathRdRd: 2r1110].
+ 		[XorRdRd]						-> [^self concretizeXorRdRd].
+ 		[SqrtRd]						-> [^self concretizeSqrtRd].
+ 		[NegateR]						-> [^self concretizeNegateR].
+ 		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
+ 		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
+ 		[ArithmeticShiftRightCqRR]		-> [^self concretizeArithmeticShiftRightCqRR].
+ 		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
+ 		[LogicalShiftRightCqRR]		-> [^self concretizeLogicalShiftRightCqRR].
+ 		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
+ 		[LogicalShiftLeftCqRR]			-> [^self concretizeLogicalShiftLeftCqRR].
+ 		[ArithmeticShiftRightRR]		-> [^self concretizeShiftRR: 2r001010].
+ 		[LogicalShiftLeftRR]				-> [^self concretizeShiftRR: 2r001000].
+ 		[LogicalShiftRightRR]			-> [^self concretizeShiftRR: 2r001001].
+ 		[RotateRightCqR]				-> [^self concretizeRotateCqR].
+ 		[RotateLeftCqR]				-> [^self concretizeRotateCqR].
+ 		[ClzRR]							-> [^self concretizeClzRR].
+ 		"ARM Specific Arithmetic"
+ 		[MulRRR]						-> [^self concretizeMulRRR].
+ 		[MulOverflowRRR]				-> [^self concretizeMulOverflowRRR].
+ 		[DivRRR]						-> [^self concretizeDivRRR].
+ 		[MSubRRR]						-> [^self concretizeMSubRRR].
+ 		"ARM Specific Cache Control"
+ 		[DC]							-> [^self concretizeDataCacheControl].
+ 		[DSB]							-> [^self concretizeDataSynchronizationBarrier].
+ 		[IC]								-> [^self concretizeInstructionCacheControl].
+ 		[ISB]							-> [^self concretizeInstructionSynchronizationBarrier].
+ 		[MRS_CTR_EL0]					-> [^self concretizeMRS_CTR_EL0].
+ 		[MRS_ID_AA64ISAR0_EL1]		-> [^self concretizeMRS_ID_AA64ISAR0_EL1].
+ 		"Data Movement"
+ 		[MoveCqR]			-> [^self concretizeMoveCqR].
+ 		[MoveCwR]			-> [^self concretizeMoveCwR].
+ 		[MoveC32R]		-> [^self concretizeMoveC32R].
+ 		[MoveRR]			-> [^self concretizeMoveRR].
+ 		[MoveRRd]			-> [^self concretizeMoveRRd].
+ 		[MoveRdR]			-> [^self concretizeMoveRdR].
+ 		[MoveAwR]			-> [^self concretizeMoveAwR].
+ 		[MoveRAw]			-> [^self concretizeMoveRAw].
+ 		[MoveAwRR]		-> [^self concretizeMoveAwRR].
+ 		[MoveRRAw]		-> [^self concretizeMoveRRAw].
+ 		[MoveAbR] 			-> [^self concretizeMoveAbR].
+  		[MoveRAb]			-> [^self concretizeMoveRAb].
+ 		[MoveMwrR]		-> [^self concretizeMoveMSrR: 3].
+ 		[MoveM32rR]		-> [^self concretizeMoveMSrR: 2].
+ 		[MoveM16rR]		-> [^self concretizeMoveMSrR: 1].
+ 		[MoveMbrR]		-> [^self concretizeMoveMSrR: 0].
+ 		[MoveRMwr]		-> [^self concretizeMoveRMSr: 3].
+ 		[MoveRM32r]		-> [^self concretizeMoveRMSr: 2].
+ 		[MoveRM16r]		-> [^self concretizeMoveRMSr: 1].
+ 		[MoveRMbr]		-> [^self concretizeMoveRMSr: 0].
+ 		[MoveXwrRR]		-> [^self concretizeMoveXSrRR: 3].
+ 		[MoveX32rRR]		-> [^self concretizeMoveXSrRR: 2].
+ 		[MoveX16rRR]		-> [^self concretizeMoveXSrRR: 1].
+ 		[MoveXbrRR]		-> [^self concretizeMoveXSrRR: 0].
+ 		[MoveRXwrR]		-> [^self concretizeMoveRXSrR: 3].
+ 		[MoveRX32rR]		-> [^self concretizeMoveRXSrR: 2].
+ 		[MoveRX16rR]		-> [^self concretizeMoveRXSrR: 1].
+ 		[MoveRXbrR]		-> [^self concretizeMoveRXSrR: 0].
+ 		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
+ 		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
+ 		[PopR]				-> [^self concretizePopR].
+ 		[PushR]				-> [^self concretizePushR].
+ 		[NativePopRR]		-> [^self concretizeNativePopRR].
+ 		[NativePushRR]		-> [^self concretizeNativePushRR].
+ 		[PushCq]			-> [^self concretizePushCq].
+ 		[PushCw]			-> [^self concretizePushCw].
+ 		[PrefetchAw]		-> [^self concretizePrefetchAw].
+ 		"Conversion"
+ 		[ConvertRRd]		-> [^self concretizeConvertRRd].
+ 		[ConvertRdR]		-> [^self concretizeConvertRdR].
+ 		"[ConvertRRs]		-> [^self concretizeConvertRRs].
+ 		[ConvertRsR]		-> [^self concretizeConvertRsR].
+ 		[ConvertRsRd]		-> [^self concretizeConvertRsRd].
+ 		[ConvertRdRs]		-> [^self concretizeConvertRdRs]."
+ 			
+ 		[SignExtend8RR]	-> [^self concretizeSignExtendRR: 8].
+ 		[SignExtend16RR]	-> [^self concretizeSignExtendRR: 16].
+ 		[SignExtend32RR]	-> [^self concretizeSignExtendRR: 32].
+ 		
+ 		[ZeroExtend8RR]	-> [^self concretizeZeroExtendRR: 8].
+ 		[ZeroExtend16RR]	-> [^self concretizeZeroExtendRR: 16].
+ 		[ZeroExtend32RR]	-> [^self concretizeZeroExtendRR: 32].
+ 
+ 		"Multi-processing"
+ 		[LDAXR]			-> [^self concretizeLDAXR].
+ 		[STLXR]			-> [^self concretizeSTLXR].
+ 		[CLREX]			-> [^self concretizeCLREX].
+ 		[STLR]				-> [^self concretizeSTLR].
+ 		[CASAL]			-> [^self concretizeCASAL].
+ 		[CCMPNE]			-> [^self concretizeCCMPNE].
+ 		[CSET]				-> [^self concretizeCSET].
+ 		[CBNZ]				-> [^self concretizeCB].
+ 		[CBZ]				-> [^self concretizeCB]. }.
+ 
+ 	^0 "keep Slang happy"!

Item was added:
+ ----- Method: CogARMv8Compiler>>emitLd:rn:rt:imm:shiftBy12:at: (in category 'generate machine code - support') -----
+ emitLd: unitSizeLog2MinusOne rn: baseReg rt: targetReg imm: offset shiftBy12: shiftBy12 at: instrOffset
+ 	"C6.2.130	LDR (immediate)	C6-976
+ 	 C6.2.132	LDR (register)		C6-981
+ 	 C6.2.136	LDRH (immediate)	C6-990
+ 	 C6.2.166	LDUR				C6-1058
+ 	 C6.2.134	LDRB (immediate)	C6-985
+ 	 C6.2.135	LDRB (register)		C6-988"
+ 
+ 	"cogit processor disassembleInstructionAt: instrOffset In: machineCode object"
+ 	| unitSize instrBytes |
+ 	unitSize := 1 << unitSizeLog2MinusOne.
+ 	"Unsigned offset, C6-977"
+ 	(offset \\ unitSize = 0
+ 	 and: [offset / unitSize between: 0 and: 1 << 12 - 1]) ifTrue:
+ 		[machineCode
+ 			at: instrOffset / 4
+ 			put: unitSizeLog2MinusOne << 30
+ 				+ (2r11100101 << 22)
+ 				+ (offset << (10 - unitSizeLog2MinusOne))
+ 				+ (baseReg << 5)
+ 				+ targetReg.
+ 		 ^instrOffset + 4].
+ 	(offset between: -256 and: 255) ifTrue: "Unscaled signed 9-bit offset, C6-1058"
+ 		[machineCode
+ 			at: instrOffset / 4
+ 			put: unitSizeLog2MinusOne << 30
+ 				+ (2r11100001 << 22)
+ 				+ ((offset bitAnd: 511) << 12)
+ 				+ (baseReg << 5)
+ 				+ targetReg.
+ 		 ^instrOffset + 4].
+ 	"C6.2.132	LDR (register)	C6-981"
+ 	instrBytes := self emitMoveCw: offset intoR: RISCTempReg at: instrOffset.
+ 	machineCode
+ 		at: instrBytes // 4
+ 		put: unitSizeLog2MinusOne << 30
+ 			+ (2r111000011 << 21)
+ 			+ (RISCTempReg << 16)
+ 			+ (UXTX << 13)
+ 			+ (1 << 11)
+ 			+ (baseReg << 5)
+ 			+ targetReg.
+ 	^instrBytes + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>emitLdfprn:rt:imm:shiftBy12:at: (in category 'generate machine code - support') -----
+ emitLdfprn: baseReg rt: targetDPReg imm: offset shiftBy12: shiftBy12 at: instrOffset
+ 	"C7.2.184	LDR (immediate, SIMD&FP)	C7-1800
+ 	 C7.2.186	LDR (register, SIMD&FP)	C7-1806"
+ 
+ 	"cogit processor disassembleInstructionAt: instrOffset In: machineCode object"
+ 	| instrBytes |
+ 	"Unsigned offset, C7-1801"
+ 	(offset \\ 8 = 0
+ 	 and: [offset / 8 between: 0 and: 1 << 12 - 1]) ifTrue:
+ 		[machineCode
+ 			at: instrOffset / 4
+ 			put: 2r1111110101 << 22
+ 				+ (offset << 7 "10 - 3")
+ 				+ (baseReg << 5)
+ 				+ targetDPReg.
+ 		 ^instrOffset + 4].
+ 	"No unscaled signed 9-bit offset because there is only post-index and pre-index, see C7-1800"
+ 	"C6.2.132	LDR (register)	C6-981"
+ 	instrBytes := self emitMoveCw: offset intoR: RISCTempReg at: instrOffset.
+ 	"C7.2.186	LDR (register, SIMD&FP)	C7-1806"
+ 	machineCode
+ 		at: instrBytes // 4
+ 		put: 2r11111100011 << 21
+ 			+ (RISCTempReg << 16)
+ 			+ (UXTX << 13)
+ 			+ (1 << 11)
+ 			+ (baseReg << 5)
+ 			+ targetDPReg.
+ 	^instrBytes + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>emitMoveCw:intoR:at: (in category 'generate machine code - support') -----
+ emitMoveCw: constantArg intoR: destReg at: offsetBytes
+ 	"Emit a load of constant into destReg.  Answer the number of bytes of machine code
+ 	 generated. Literals are stored out-of-line; emit a LDR (literal) with the relevant offset."
+ 	 <var: 'constantArg' type: #usqInt>
+ 	| constant |
+ 	 <var: 'constant' type: #usqInt>
+ 	<inline: false>
+ 	self deny: destReg = SP.
+ 	"cogit processor disassembleInstructionAt: offsetBytes // 4 In: machineCode object"
+ 	constant := (self isAnInstruction: (cogit cCoerceSimple: constantArg to: #'AbstractInstruction *'))
+ 					ifTrue: [(cogit cCoerceSimple: constantArg to: #'AbstractInstruction *') address]
+ 					ifFalse: [constantArg].
+ 	((opcode = MoveCwR or: [opcode = PushCw])
+ 	 and: [self inCurrentCompilation: constant]) ifTrue:
+ 		[| aligned unaligned pcRelativeOffset |
+ 		 "C6.2.10 	ADR	C6-773"
+ 		 unaligned := constant bitAnd: 3.
+ 		 aligned := constant - unaligned.
+ 		 pcRelativeOffset := aligned - address asInteger >>> 2.
+ 		 self assert: (pcRelativeOffset between: -1 << 18 and: 1 << 18 - 1).
+ 		 machineCode
+ 			at: offsetBytes // 4
+ 			put: unaligned << 29
+ 				+ (1 << 28)
+ 				+ ((pcRelativeOffset bitAnd: 1 << 19 - 1) << 5)
+ 				+ destReg.
+ 		 ^offsetBytes + 4].
+ 	self assert: (cogit addressIsInCurrentCompilation: dependent address).
+ 	self assert: dependent address \\ 4 = 0.
+ 	self assert: (dependent address - (address + offsetBytes)) abs < (1 << 20).
+ 	"C6.2.131	LDR (literal)		C6-979"
+ 	machineCode
+ 		at: offsetBytes // 4
+ 		put: 2r01011 << 27
+ 			+ ((dependent address - (address + offsetBytes) bitAnd: 1 << 21 - 1) << 3 "5 - 2")
+ 			+ destReg.
+ 	^offsetBytes + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>flushDCacheFrom:to: (in category 'inline cacheing') -----
+ flushDCacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
+ 	"If there is a dual mapped code zone (the normal zone but marked with read/execute, and a
+ 	 read/write zone codeToDataDelta bytes away) then flush the data cache for the corresponding
+ 	 range in the read/write zone and invalidate the data cache for the read/execute zone."
+ 	<cmacro: '(me,startAddress,endAddress) ceFlushDCache(startAddress,endAddress)'>
+ 	^cogit simulateCeFlushDCacheFrom: startAddress to: endAddress!

Item was added:
+ ----- Method: CogARMv8Compiler>>flushICacheFrom:to: (in category 'inline cacheing') -----
+ flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
+ 	"Flush the instruction cache from (startAddress to endAddress].
+ 	 If there is a dual mapped code zone (the normal zone but marked with read/execute, and a
+ 	 read/write zone codeToDataDelta bytes away) then also flush the data cache for the corresp-
+ 	 onding range in the read/write zone and invalidate the data cache for the read/execute zone."
+ 	<cmacro: '(me,startAddress,endAddress) ceFlushICache(startAddress,endAddress)'>
+ 	^cogit simulateCeFlushICacheFrom: startAddress to: endAddress!

Item was added:
+ ----- Method: CogARMv8Compiler>>fullCallsAreRelative (in category 'abi') -----
+ fullCallsAreRelative
+ 	"Answer if CallFull and/or JumpFull are relative and hence need relocating on method
+ 	 compation. If so, they are annotated with IsRelativeCall in methods and relocated in
+ 	 relocateIfCallOrMethodReference:mcpc:delta:"
+ 	^false!

Item was added:
+ ----- Method: CogARMv8Compiler>>genAlignCStackSavingRegisters:numArgs:wordAlignment: (in category 'abi') -----
+ genAlignCStackSavingRegisters: regMask numArgs: numArgs wordAlignment: alignment
+ 	<inline: true>
+ 	"Override to do nothing.  On the ARMv8 the SP has to be aligned correctly,
+ 	 as enforced by the processor on any and all accesses to the SP."
+ 	^0!

Item was added:
+ ----- Method: CogARMv8Compiler>>genDivR:R:Quo:Rem: (in category 'abstract instructions') -----
+ genDivR: regDivisor R: regDividend Quo: regQuotient Rem: regRemainder
+ 	"Divide regDividend by regDivisor storing the quotient in regQuotient and remainder in regRemainder.
+ 		MSUB Multiply-subtract		MSUB	C6-1109
+ 		SDIV Signed divide			SDIV	C6-1174"
+ 	| instr safeRegQuotient |
+ 	"For the MSUB to work we must preserve regDivisor and regDividend for the MSUB;
+ 	 i.e. the DivRRR must not overwrite either regDivisor or regDividend."
+ 	safeRegQuotient := (regQuotient = regDividend or: [regQuotient = regDivisor])
+ 							ifTrue: [RISCTempReg]
+ 							ifFalse: [regQuotient].
+ 	instr := cogit gen: DivRRR operand: regDividend operand: regDivisor operand: safeRegQuotient.
+ 	"MSUB <Xd>, <Xn>, <Xm>, <Xa>, Xd := Xa - (Xn * Xm)"
+ 	"MSUB regRemainder, regQuotient, regDivisor, regQuotient"
+ 	cogit gen: MSubRRR operand: safeRegQuotient << 5 + regDivisor operand: regDividend operand: regRemainder.
+ 	safeRegQuotient ~= regQuotient ifTrue:
+ 		[cogit gen: MoveRR operand: safeRegQuotient operand: regQuotient].
+ 	^instr
+ 	
+ 	"{ 4 \\ 3. 4 // 3. 4 quo: 3. 4 rem: 3 } #(1 1 1 1)
+ 	{ 4 \\ -3. 4 // -3. 4 quo: -3. 4 rem: -3 } #(-2 -2 -1 1)
+ 	{ -4 \\ 3. -4 // 3. -4 quo: 3. -4 rem: 3 } #(2 -2 -1 -1)
+ 	{ -4 \\ -3. -4 // -3. -4 quo: -3. -4 rem: -3 } #(-1 1 1 -1)"!

Item was added:
+ ----- Method: CogARMv8Compiler>>genLoadCStackPointers (in category 'smalltalk calling convention') -----
+ genLoadCStackPointers
+ 	"Load the frame and stack pointer registers with those of the C stack,
+ 	 effecting a switch to the C stack.  Used when machine code calls into
+ 	 the CoInterpreter run-time (e.g. to invoke interpreter primitives).
+ 	 Override to try and use MoveAwRR/ldp"
+ 	cogit cStackPointerAddress + 8 = cogit cFramePointerAddress ifTrue:
+ 		[cogit
+ 			gen: MoveAwRR
+ 			operand: cogit cStackPointerAddress
+ 			operand: NativeSPReg
+ 			operand: FPReg.
+ 		 ^0].
+ 
+ 	^super genLoadCStackPointers!

Item was added:
+ ----- Method: CogARMv8Compiler>>genLoadStackPointers (in category 'smalltalk calling convention') -----
+ genLoadStackPointers
+ 	"Switch back to the Smalltalk stack. Assign SPReg first
+ 	 because typically it is used immediately afterwards.
+ 	 Override to try and use MoveAwRR/ldp"
+ 	cogit stackPointerAddress + 8 = cogit framePointerAddress ifTrue:
+ 		[cogit
+ 			gen: MoveAwRR
+ 			operand: cogit stackPointerAddress
+ 			operand: SPReg
+ 			operand: FPReg.
+ 		 ^0].
+ 	cogit framePointerAddress + 8 = cogit stackPointerAddress ifTrue:
+ 		[cogit
+ 			gen: MoveAwRR
+ 			operand: cogit framePointerAddress
+ 			operand: FPReg
+ 			operand: SPReg.
+ 		 ^0].
+ 	
+ 	^super genLoadStackPointers!

Item was added:
+ ----- Method: CogARMv8Compiler>>genMarshallNArgs:arg:arg:arg:arg: (in category 'abi') -----
+ genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
+ 	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is
+ 	 either a negative number, which encodes a constant, or a non-negative number, that of a register.
+ 
+ 	 Run-time calls have no more than four arguments, so chosen so that on ARM, where in its C ABI the
+ 	 first four integer arguments are passed in registers, all arguments can be passed in registers.  We
+ 	 defer to the back end to generate this code not so much that the back end knows whether it uses
+ 	 the stack or registers to pass arguments (it does, but...). In fact we defer for an extremely evil reason.
+ 	 Doing so allows the x64 (where up to 6 args are passed) to assign the register arguments in an order
+ 	 that allows some of the argument registers to be used for specific abstract registers, specifically
+ 	 ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also it's really nice to keep using the old
+ 	 register assignments the original author has grown accustomed to."
+ 	<inline: true>
+ 	numArgs = 0 ifTrue: [^self].
+ 	"Avoid arg regs being overwritten before they are read."
+ 	numArgs > 1 ifTrue:
+ 		[((cogit isTrampolineArgConstant: regOrConst1) not
+ 		   and: [regOrConst1 = CArg0Reg]) ifTrue:
+ 			[cogit MoveR: regOrConst1 R: Extra0Reg.
+ 			 ^self genMarshallNArgs: numArgs arg: regOrConst0 arg: Extra0Reg arg: regOrConst2 arg: regOrConst3].
+ 		 numArgs > 2 ifTrue:
+ 			[((cogit isTrampolineArgConstant: regOrConst2) not
+ 			   and: [regOrConst2 = CArg0Reg or: [regOrConst2 = CArg1Reg]]) ifTrue:
+ 				[cogit MoveR: regOrConst2 R: Extra1Reg.
+ 				 ^self genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: Extra1Reg arg: regOrConst3].
+ 			 numArgs > 3 ifTrue:
+ 				[((cogit isTrampolineArgConstant: regOrConst3) not
+ 				   and: [regOrConst3 = CArg0Reg or: [regOrConst3 = CArg1Reg or: [regOrConst3 = CArg2Reg]]]) ifTrue:
+ 					[cogit MoveR: regOrConst3 R: Extra2Reg.
+ 					 ^self genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: Extra2Reg]]]].
+ 	(cogit isTrampolineArgConstant: regOrConst0)
+ 		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst0) R: CArg0Reg]
+ 		ifFalse: [cogit MoveR: regOrConst0 R: CArg0Reg].
+ 	numArgs = 1 ifTrue: [^self].
+ 	(cogit isTrampolineArgConstant: regOrConst1)
+ 		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst1) R: CArg1Reg]
+ 		ifFalse: [cogit MoveR: regOrConst1 R: CArg1Reg].
+ 	numArgs = 2 ifTrue: [^self].
+ 	(cogit isTrampolineArgConstant: regOrConst2)
+ 		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: CArg2Reg]
+ 		ifFalse: [cogit MoveR: regOrConst2 R: CArg2Reg].
+ 	numArgs = 3 ifTrue: [^self].
+ 	(cogit isTrampolineArgConstant: regOrConst3)
+ 		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: CArg3Reg]
+ 		ifFalse: [cogit MoveR: regOrConst3 R: CArg3Reg]!

Item was added:
+ ----- Method: CogARMv8Compiler>>genMulOverflowR:R: (in category 'abstract instructions') -----
+ genMulOverflowR: regSource R: regDest
+ 	^cogit gen: MulOverflowRRR operand: regSource operand: regDest operand: regDest!

Item was added:
+ ----- Method: CogARMv8Compiler>>genMulR:R: (in category 'abstract instructions') -----
+ genMulR: regSource R: regDest
+ 	^cogit gen: MulRRR operand: regSource operand: regDest operand: regDest!

Item was added:
+ ----- Method: CogARMv8Compiler>>genPushRegisterArgsForAbortMissNumArgs: (in category 'smalltalk calling convention') -----
+ genPushRegisterArgsForAbortMissNumArgs: numArgs
+ 	"Ensure that the register args are pushed before the outer and
+ 	 inner retpcs at an entry miss for arity <= self numRegArgs.  The
+ 	 outer retpc is that of a call at a send site.  The inner is the call
+ 	 from a method or PIC abort/miss to the trampoline."
+ 
+ 	"Putting the receiver and args above the return address means the
+ 	 CoInterpreter has a single machine-code frame format which saves
+ 	 us a lot of work."
+ 
+ 	"Iff there are register args convert
+ 		sp		->	outerRetpc			(send site retpc)
+ 		linkReg = innerRetpc			(PIC abort/miss retpc)
+ 	 to
+ 		base	->	receiver
+ 					(arg0)
+ 					(arg1)
+ 		sp		->	outerRetpc			(send site retpc)
+ 		sp		->	linkReg/innerRetpc	(PIC abort/miss retpc)"
+ 	numArgs <= cogit numRegArgs ifTrue:
+ 		[self assert: cogit numRegArgs <= 2.
+ 		 cogit MoveMw: 0 r: SPReg R: TempReg. "Save return address"
+ 		 cogit MoveR: ReceiverResultReg Mw: 0 r: SPReg.
+ 		 numArgs > 0 ifTrue:
+ 			[cogit PushR: Arg0Reg.
+ 			 numArgs > 1 ifTrue:
+ 				[cogit PushR: Arg1Reg]].
+ 		cogit PushR: TempReg]. "push back return address"
+ 	cogit PushR: LinkReg!

Item was added:
+ ----- Method: CogARMv8Compiler>>genPushRegisterArgsForNumArgs:scratchReg: (in category 'smalltalk calling convention') -----
+ genPushRegisterArgsForNumArgs: numArgs scratchReg: ignored
+ 	"Ensure that the register args are pushed before the retpc for arity <= self numRegArgs."
+ 	"This is easy on a RISC like ARM because the return address is in the link register.  Putting
+ 	 the receiver and args above the return address means the CoInterpreter has a single
+ 	 machine-code frame format which saves us a lot of work
+ 	NOTA BENE: we do NOT push the return address here, which means it must be dealt with later."
+ 	numArgs <= cogit numRegArgs ifTrue:
+ 		[self assert: cogit numRegArgs <= 2.
+ 		 cogit PushR: ReceiverResultReg.
+ 		 numArgs > 0 ifTrue:
+ 			[cogit PushR: Arg0Reg.
+ 			 numArgs > 1 ifTrue:
+ 				[cogit PushR: Arg1Reg]]]!

Item was added:
+ ----- Method: CogARMv8Compiler>>genRemoveNArgsFromStack: (in category 'abi') -----
+ genRemoveNArgsFromStack: n
+ 	"This is a no-op on ARM64 since the ABI passes up to 6 args in registers and trampolines currently observe that limit, using only 4."
+ 	<inline: true>
+ 	self assert: n <= 6.
+ 	^0!

Item was added:
+ ----- Method: CogARMv8Compiler>>genRestoreRegs: (in category 'abi') -----
+ genRestoreRegs: regMask
+ 	"Restore the registers in regMask as saved by genSaveRegs:.
+ 	 See http://infocenter.arm.com/help/topic/com.arm.doc.den0028b/ARM_DEN0028B_SMC_Calling_Convention.pdf
+ 	 N.B. Alignment is handled by genAlignCStackSavingRegisters:numArgs:wordAlignment:."
+ 	| nRegs pair |
+ 	regMask = 0 ifTrue: [^0].
+ 	self deny: (cogit register: RISCTempReg isInMask: regMask).
+ 	nRegs := 0.
+ 	R1 to: R17 do:
+ 		[:reg|
+ 		 (regMask anyMask: (cogit registerMaskFor: reg)) ifTrue:
+ 			[nRegs := nRegs + 1]].
+ 	pair := nRegs even ifTrue: [NoReg] ifFalse: [RISCTempReg].
+ 	R1 to: R17 do:
+ 		[:reg|
+ 		 (regMask anyMask: (cogit registerMaskFor: reg)) ifTrue:
+ 			[pair = NoReg
+ 				ifTrue: [pair := reg]
+ 				ifFalse:
+ 					[cogit gen: NativePopRR operand: reg operand: pair.
+ 					 pair := NoReg]]].
+ 	self assert: pair = NoReg.
+ 	^0!

Item was added:
+ ----- Method: CogARMv8Compiler>>genSaveRegs: (in category 'abi') -----
+ genSaveRegs: regMask
+ 	"Save the registers in regMask for a call into the C run-time from a trampoline.
+ 	 See http://infocenter.arm.com/help/topic/com.arm.doc.den0028b/ARM_DEN0028B_SMC_Calling_Convention.pdf
+ 	 N.B. Alignment is handled by genAlignCStackSavingRegisters:numArgs:wordAlignment:."
+ 	| pair |
+ 	regMask = 0 ifTrue: [^0].
+ 	self deny: (cogit register: RISCTempReg isInMask: regMask).
+ 	pair := NoReg.
+ 	R17 to: R0 by: -1 do:
+ 		[:reg|
+ 		 (regMask anyMask: (cogit registerMaskFor: reg)) ifTrue:
+ 			[pair = NoReg
+ 				ifTrue: [pair := reg]
+ 				ifFalse:
+ 					[cogit gen: NativePushRR operand: pair operand: reg.
+ 					 pair := NoReg]]].
+ 	pair ~= NoReg ifTrue:
+ 		[cogit gen: NativePushRR operand: pair operand: RISCTempReg].
+ 	^0!

Item was added:
+ ----- Method: CogARMv8Compiler>>genSaveStackPointers (in category 'smalltalk calling convention') -----
+ genSaveStackPointers
+ 	"Save the frame and stack pointer registers to the framePointer
+ 	 and stackPointer variables.  Used to save the machine code frame
+ 	 for use by the run-time when calling into the CoInterpreter run-time.
+ 	 Override to try and use MoveRRAw/stp"
+ 	cogit stackPointerAddress + 8 = cogit framePointerAddress ifTrue:
+ 		[cogit
+ 			gen: MoveRRAw
+ 			operand: SPReg
+ 			operand: FPReg
+ 			operand: cogit stackPointerAddress.
+ 		 ^0].
+ 	
+ 	^super genSaveStackPointers!

Item was added:
+ ----- Method: CogARMv8Compiler>>genSubstituteReturnAddress: (in category 'abstract instructions') -----
+ genSubstituteReturnAddress: retpc
+ 	<inline: true>
+ 	^cogit MoveCw: retpc R: LR!

Item was added:
+ ----- Method: CogARMv8Compiler>>genSubstituteReturnAddressR: (in category 'abstract instructions') -----
+ genSubstituteReturnAddressR: retpcReg
+ 	<inline: true>
+ 	^cogit MoveR: retpcReg R: LR!

Item was added:
+ ----- Method: CogARMv8Compiler>>generalPurposeRegisterMap (in category 'disassembly') -----
+ generalPurposeRegisterMap
+ 	<doNotGenerate>
+ 	"Answer a Dictionary from register getter to register index."
+ 	^Dictionary newFromPairs:
+ 		{	#r0. R0.
+ 			#r1. R1.
+ 			#r2. R2.
+ 			#r3. R3.
+ 			#r4. R4.
+ 			#r5. R5.
+ 			#r6. R6.
+ 			#r7. R7.
+ 			#r8. R8.
+ 			#r9. R9.
+ 			#r10. R10.
+ 			#r11. R11.
+ 			#r12. R12.
+ 			#r13. R13.
+ 			#r14. R14.
+ 			#r15. R15.
+ 			#r16. R16.
+ 			#r17. R17.
+ 			#r18. R18.
+ 			#r19. R19.
+ 			#r20. R20.
+ 			#r21. R21.
+ 			#r22. R22.
+ 			#r23. R23.
+ 			#r24. R24.
+ 			#r25. R25.
+ 			#r26. R26.
+ 			#r27. R27.
+ 			#r28. R28	}!

Item was added:
+ ----- Method: CogARMv8Compiler>>generateDCacheFlush (in category 'inline cacheing') -----
+ generateDCacheFlush
+ 	"Use the DC instruction to implement ceFlushDCache(void *start, void *end); see flushDCacheFrom:to:.
+ 	 If there is a dual mapped zone then clean data via DC_CVAU as address + codeToDataDelta,
+ 	 then invalidate data at address via CIVAC."
+ 
+ 	"D4.4.7		About cache maintenance in AArch64 state													D4-2478
+ 
+ 		Terminology for Clean, Invalidate, and Clean and Invalidate instructions									D4-2479
+ 		...
+ 		-	For instructions operating by VA, the following conceptual points are defined:						D4-2480
+ 		Point of Unification (PoU)							
+ 			The PoU for a PE is the point by which the instruction and data caches and the translation table walks of that
+ 			PE are guaranteed to see the same copy of a memory location. In many cases, the Point of Unification is the
+ 			point in a uniprocessor memory system by which the instruction and data caches and the translation table
+ 			walks have merged.
+ 
+ 			The PoU for an Inner Shareable shareability domain is the point by which the instruction and data caches
+ 			and the translation table walks of all the PEs in that Inner Shareable shareability domain are guaranteed to
+ 			see the same copy of a memory location. Defining this point permits self-modifying software to ensure future
+ 			instruction fetches are associated with the modified version of the software by using the standard correctness
+ 			policy of:
+ 				1. Clean data cache entry by address.
+ 				2. Invalidate instruction cache entry by address.
+ 
+ 		Example code for cache maintenance instructions D4-2490 - D4-2491"
+ 	| ctrEL0 dataCacheMinLineLength mask loop |
+ 	self assert: cogit getCodeToDataDelta ~= 0.
+ 	ctrEL0 := self ctrEl0.
+ 	"See concretizeCacheControlOp1:CRm:Op2: & 
+ 	 http://infocenter.arm.com/help/index.jsp?topic=/com.arm.doc.100403_0200_00_en/lau1443435580346.html
+ 	 DminLine & IminLine are Log2 words; 16 words miniumum"
+ 	(dataCacheMinLineLength := ctrEL0 >> 16 bitAnd: 15) = 0 ifTrue:
+ 		[dataCacheMinLineLength := 4].
+ 	dataCacheMinLineLength := 4 << dataCacheMinLineLength.
+ 	"Mask is large enough to encompass the method zone and has the correct minimum alignment."
+ 	mask := 1 << (cogit coInterpreter highBit: cogit methodZone zoneEnd) - dataCacheMinLineLength.
+ 
+ 	"Since this is used from C code we must use only caller-saved registers.
+ 	 C arg registers 2 & 3 are such a convenient pair of caller-saved registers."
+ 	cogit AndCq: mask R: CArg0Reg R: CArg2Reg. "CArg2Reg = aligned pointer to start of each data cache line"
+ 	cogit AddCq: cogit getCodeToDataDelta R: CArg2Reg R: CArg3Reg.
+ 	loop := cogit Label.
+ 	"see concretizeDataCacheControl"
+ 	cogit gen: DC operand: CArg3Reg operand: DC_CVAU.	"clean (flush) address + codeToDataDelta"
+ 	cogit gen: DC operand: CArg2Reg operand: DC_CIVAC.	"invalidate address"
+ 	cogit
+ 		AddCq: dataCacheMinLineLength R: CArg2Reg;
+ 		AddCq: dataCacheMinLineLength R: CArg3Reg;
+ 		CmpR: CArg1Reg R: CArg2Reg;
+ 		JumpBelowOrEqual: loop.
+ 	cogit RetN: 0!

Item was added:
+ ----- Method: CogARMv8Compiler>>generateICacheFlush (in category 'inline cacheing') -----
+ generateICacheFlush
+ 	"Use DC VAUC, DSB, IC IVAU, and ISB instructions to implement ceFlushICache(void *start, void *end); see flushICacheFrom:to:.
+ 	 One might think that if there is a dual zone then data at address + codeToDataDelta must be cleaned,
+ 	 but this isn't the case.  All we need to do is clean data at address via DC VAUC and instructions via IC IVAU."
+ 
+ 	"B2.2.5		Concurrent modification and execution of instructions											B2-112
+ 
+ 		...to avoid UNPREDICTABLE or CONSTRAINED UNPREDICTABLE behavior, instruction modifications must be explicitly synchronized before they are executed. The required synchronization is as follows:
+ 
+ 		1.	No PE must be executing an instruction when another PE is modifying that instruction.
+ 
+ 		2.	To ensure that the modified instructions are observable, a PE that is writing the instructions must issue the following sequence of instructions and operations:
+ 
+ 			; Coherency example for data and instruction accesses within the same Inner Shareable domain.
+ 			; enter this code with <Wt> containing a new 32-bit instruction, to be held in Cacheable space at a location pointed to by Xn.
+ 
+ 			STR Wt, [Xn]
+ 			DC CVAU, Xn		; Clean data cache by VA to point of unification (PoU)
+ 			DSB ISH			; Ensure visibility of the data cleaned from cache
+ 			IC IVAU, Xn			; Invalidate instruction cache by VA to PoU
+ 			DSB ISH
+ 
+ 			Note
+ 			 -	The DC CVAU operation is not required if the area of memory is either Non-cacheable or Write-Through Cacheable.
+ 			 -	If the contents of physical memory differ between the mappings, changing the mapping of VAs to PAs can cause
+ 				the instructions to be concurrently modified by one PE and executed by another PE. If the modifications affect
+ 				instructions other than those listed as being acceptable for modification, synchronization must be used to avoid
+ 				UNPREDICTABLE or CONSTRAINED UNPREDICTABLE behavior.
+ 
+ 		3.	In a multiprocessor system, the IC IVAU is broadcast to all PEs within the Inner Shareable domain of the PE running this sequence.
+ 			However, when the modified instructions are observable, each PE that is executing the modified instructions must issue the following
+ 			instruction to ensure execution of the modified instructions:
+ 
+ 			ISB					; Synchronize fetched instruction stream"
+ 
+ 	"D4.4.7		About cache maintenance in AArch64 state													D4-2478
+ 
+ 		Terminology for Clean, Invalidate, and Clean and Invalidate instructions									D4-2479
+ 		...
+ 		-	For instructions operating by VA, the following conceptual points are defined:						D4-2480
+ 		Point of Unification (PoU)							
+ 			The PoU for a PE is the point by which the instruction and data caches and the translation table walks of that
+ 			PE are guaranteed to see the same copy of a memory location. In many cases, the Point of Unification is the
+ 			point in a uniprocessor memory system by which the instruction and data caches and the translation table
+ 			walks have merged.
+ 
+ 			The PoU for an Inner Shareable shareability domain is the point by which the instruction and data caches
+ 			and the translation table walks of all the PEs in that Inner Shareable shareability domain are guaranteed to
+ 			see the same copy of a memory location. Defining this point permits self-modifying software to ensure future
+ 			instruction fetches are associated with the modified version of the software by using the standard correctness
+ 			policy of:
+ 				1. Clean data cache entry by address.
+ 				2. Invalidate instruction cache entry by address.
+ 
+ 		Example code for cache maintenance instructions D4-2490 - D4-2491"
+ 	| ctrEL0 dataCacheMinLineLength instrCacheMinLineLength mask loop |
+ 	ctrEL0 := self ctrEl0.
+ 	"See concretizeCacheControlOp1:CRm:Op2: & 
+ 	 http://infocenter.arm.com/help/index.jsp?topic=/com.arm.doc.100403_0200_00_en/lau1443435580346.html"
+ 	(ctrEL0 noMask: 1 << 28) ifTrue: "CTR_EL0.IDC disabled; must clean data cache to point of unification."
+ 		["Since this is used from C code we must use only caller-saved registers.
+ 		  C arg registers 2 & 3 are as such a convenient pair of caller-saved registers."
+ 		 dataCacheMinLineLength := 4 << (ctrEL0 >> 16 bitAnd: 15).
+ 		 "Mask is large enough to encompass the method zone and has the correct minimum alignment."
+ 		 mask := 1 << (cogit coInterpreter highBit: cogit methodZone zoneEnd) - dataCacheMinLineLength.
+ 		 cogit AndCq: mask R: CArg0Reg R: CArg2Reg. "CArg2Reg = aligned pointer to start of each data cache line"
+ 	
+ 		 loop := cogit Label.
+ 		 "see concretizeDataCacheControl"
+ 		 cogit
+ 			gen: DC operand: CArg2Reg operand: DC_CVAU;		"clean (flush) address"
+ 			AddCq: dataCacheMinLineLength R: CArg2Reg;
+ 			CmpR: CArg1Reg R: CArg2Reg;
+ 			JumpBelowOrEqual: loop].
+ 
+ 	cogit gen: DSB operand: DSB_ISH operand: DSB_ALL.		"Ensure visibility of the data cleaned from cache"
+ 
+ 	(ctrEL0 noMask: 1 << 29) ifTrue: "CTR_EL0.DIC disabled; must clean instruction cache to point of unification."
+ 		[instrCacheMinLineLength := 4 << (ctrEL0 bitAnd: 15).
+ 		 "Mask is large enough to encompass the method zone and has the correct minimum alignment."
+ 		 mask := 1 << (cogit coInterpreter highBit: cogit methodZone zoneEnd) - instrCacheMinLineLength.
+ 		 cogit AndCq: mask R: CArg0Reg R: CArg2Reg. "CArg2Reg = aligned pointer to start of each data cache line"
+ 	
+ 		 loop := cogit Label.
+ 		 "see concretizeDataCacheControl"
+ 		 cogit
+ 			gen: IC operand: CArg2Reg operand: IC_IVAU;		"clean (flush) address"
+ 			AddCq: instrCacheMinLineLength R: CArg2Reg;
+ 			CmpR: CArg1Reg R: CArg2Reg;
+ 			JumpBelowOrEqual: loop.
+ 
+ 		 cogit gen: DSB operand: DSB_ISH operand: DSB_ALL].
+ 
+ 	cogit
+ 		gen: ISB;
+ 		RetN: 0!

Item was added:
+ ----- Method: CogARMv8Compiler>>generateLowLevelTryLock: (in category 'multi-threading') -----
+ generateLowLevelTryLock: vmOwnerLockAddress
+ 	"Generate a function that attempts to lock the vmOwnerLock to the argument and answers if it succeeded."
+ 	<inline: true>
+ 	| lockValueReg vmOwnerLockAddressReg br statusReg ldaxr |
+ 	vmOwnerLockAddress = 0 ifTrue:
+ 		[cogit
+ 			MoveCq: 1 R: ABIResultReg;
+ 			RetN: 0.
+ 		 ^self].
+ 
+ 	"spiffy 8.1 version using CASAL..."
+ 	lockValueReg := CArg1Reg. "Holds the value of lock if unlocked (zero), receives the existing value of the lock"
+ 	vmOwnerLockAddressReg := CArg2Reg.
+ 	self hasAtomicInstructions ifTrue:
+ 		[cogit
+ 			MoveCq: 0 R: lockValueReg;
+ 			MoveCq: vmOwnerLockAddress R: vmOwnerLockAddressReg;
+ 			gen: CASAL operand: lockValueReg operand: CArg0Reg operand: vmOwnerLockAddressReg;
+ 			CmpCq: 0 R: lockValueReg;
+ 			gen: CCMPNE operand: ABIResultReg operand: lockValueReg operand: 0 "nzcv all false"; "i.e. if NE to 0, then is it already set to the argument?"
+ 			gen: CSET operand: ABIResultReg operand: EQ;
+ 			RetN: 0.
+ 		 ^self].
+ 
+ 	"frumpy 8.0 version using LDAXR/STLXR"
+ 				cogit MoveCq: vmOwnerLockAddress R: vmOwnerLockAddressReg.
+ 				cogit MoveCq: 0 R: (statusReg := CArg3Reg). "STLXR sets a word status register; clearing the top bits means it's a non-issue"
+ 	ldaxr :=	cogit gen: LDAXR operand: lockValueReg operand: vmOwnerLockAddressReg.
+ 	br :=		cogit gen: CBNZ operand: 0 operand: lockValueReg.
+ 				cogit gen: STLXR operand: CArg0Reg operand: vmOwnerLockAddressReg operand: statusReg.
+ 				cogit gen: CBNZ operand: ldaxr asUnsignedInteger operand: statusReg.
+ 				"Since CArg0Reg is never zero, merely returning answers true"
+ 				cogit RetN: 0.
+ 	br jmpTarget: (cogit gen: CLREX).
+ 				cogit CmpR: ABIResultReg R: lockValueReg.
+ 				cogit gen: CSET operand: ABIResultReg operand: EQ. "i.e. if NE to 0, then is it already set to the argument?"
+ 				cogit RetN: 0.
+ 	 ^self!

Item was added:
+ ----- Method: CogARMv8Compiler>>getDefaultCogCodeSize (in category 'accessing') -----
+ getDefaultCogCodeSize
+ 	"Answer the default number of bytes to allocate for native code at startup.
+ 	 The actual value can be set via vmParameterAt: and/or a preference in the ini file."
+ 	<inline: true>
+ 	^1024 * 1664!

Item was added:
+ ----- Method: CogARMv8Compiler>>hasAtomicInstructions (in category 'feature detection') -----
+ hasAtomicInstructions
+ 	"D13.2.53		ID_AA64ISAR0_EL1, AArch64 Instruction Set Attribute Register 0		D13-3096
+ 
+ 	 The ID_AA64ISAR0_EL1 characteristics are:
+ 	 Purpose
+ 		Provides information about the instructions implemented in AArch64 state.
+ 	 ...
+ 	 Atomic, bits [23:20]
+ 		From ARMv8.1:
+ 		Atomic instructions implemented in AArch64 state. Defined values are:
+ 			0b0000 No Atomic instructions implemented.
+ 			0b0010 LDADD, LDCLR, LDEOR, LDSET, LDSMAX, LDSMIN, LDUMAX, LDUMIN, CAS, CASP, and SWP instructions implemented.
+ 			All other values are reserved.
+ 			ARMv8.1-LSE implements the functionality identified by the value 0b0010.
+ 			From Armv8.1, the only permitted value is 0b0010.
+ 		Otherwise:
+ 			Reserved, RES0."
+ 
+ 	^((self idISAR0 >> 20) bitAnd: 2r1111) = 2r10!

Item was added:
+ ----- Method: CogARMv8Compiler>>hasDoublePrecisionFloatingPointSupport (in category 'testing') -----
+ hasDoublePrecisionFloatingPointSupport
+ 	^true!

Item was added:
+ ----- Method: CogARMv8Compiler>>hasLZCNTInstructions (in category 'testing') -----
+ hasLZCNTInstructions
+ 	^true!

Item was added:
+ ----- Method: CogARMv8Compiler>>hasLinkRegister (in category 'testing') -----
+ hasLinkRegister
+ 	^true "lr"!

Item was added:
+ ----- Method: CogARMv8Compiler>>hasThreeAddressArithmetic (in category 'testing') -----
+ hasThreeAddressArithmetic
+ 	"Answer if the receiver supports three-address arithmetic instructions (currently only AndCqRR)"
+ 	^true!

Item was added:
+ ----- Method: CogARMv8Compiler>>hasVarBaseRegister (in category 'testing') -----
+ hasVarBaseRegister
+ 	"Answer if the processor has a dedicated callee-saved register to point to
+ 	 the base of commonly-accessed variables. On ARMv8 we use R27 for this."
+ 	^true!

Item was added:
+ ----- Method: CogARMv8Compiler>>idISAR0 (in category 'feature detection') -----
+ idISAR0
+ 	<cmacro: '(ign) idISAR0'>
+ 	"For want of somewhere to put the variable..."
+ 	^self class idISAR0!

Item was added:
+ ----- Method: CogARMv8Compiler>>initialFlushICacheFrom:to: (in category 'inline cacheing') -----
+ initialFlushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
+ 	"This must be implemented only if a back end defines any of the following as non-zero:
+ 		numCheckFeaturesOpcodes
+ 		numDCacheFlushOpcodes
+ 		numICacheFlushOpcodes
+ 	 If I or D cache flushing code is jitted (which it will be if num[ID]CacheFlushOpcodes is non-zero) then
+ 	 the ICache must be flushed before the code is used, and that's what this function does."
+ 	<inline: #always>
+ 	self cCode:
+ 			[self cppIf: #__APPLE__ & #__MACH__ ifTrue:
+ 					[cogit sys_dcache_flush: (self cCoerce: startAddress to: #'void *') _: endAddress - startAddress + 1;
+ 						sys_icache_invalidate: (self cCoerce: startAddress to: #'void *') _: endAddress - startAddress + 1]
+ 				cppIf: #__GNUC__ ifTrue:
+ 					[cogit __clear_cache: (self cCoerce: startAddress to: #'char *') _: (self cCoerce: endAddress to: #'char *')]
+ 				ifFalse: [cogit error: 'cache flushing method unknown for this platform']]
+ 		inSmalltalk:
+ 			[cogit processor flushICacheFrom: startAddress to: endAddress]!

Item was added:
+ ----- Method: CogARMv8Compiler>>inlineCacheTagAt: (in category 'inline cacheing') -----
+ inlineCacheTagAt: callSiteReturnAddress
+ 	<inline: true>
+ 	^self instructionAt: (self pcRelativeAddressAt: (callSiteReturnAddress - 8) asUnsignedInteger)!

Item was added:
+ ----- Method: CogARMv8Compiler>>inlineCacheValueForSelector:in: (in category 'inline cacheing') -----
+ inlineCacheValueForSelector: selector in: aCogMethod
+ 	"Answer the value to put in an inline-cache that is being loaded with the selector.
+ 	 Usually this is simply the selector, but in 64-bits the cache is only 32-bits wide and so the
+ 	 cache is loaded with the index of the selector.  Override to use the 64-bit implementation."
+ 	<cmacro: '(backEnd,selector,aCogMethod) indexForSelectorin(selector,aCogMethod)'>
+ 	^cogit indexForSelector: selector in: aCogMethod!

Item was added:
+ ----- Method: CogARMv8Compiler>>instructionAddressBefore: (in category 'inline cacheing') -----
+ instructionAddressBefore: mcpc
+ 	"Answer the instruction address immediately preceding mcpc."
+ 	<inline: true>
+ 	^mcpc - 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>instructionAt: (in category 'accessing') -----
+ instructionAt: pc
+ 	<returnTypeC: #'unsigned int'>
+ 	<inline: true>
+ 	^objectMemory long32At: pc!

Item was added:
+ ----- Method: CogARMv8Compiler>>instructionBeforeAddress: (in category 'inline cacheing') -----
+ instructionBeforeAddress: followingAddress
+ 	"Answer the instruction immediately preceding followingAddress."
+ 	<inline: true>
+ 	^self instructionAt: (self instructionAddressBefore: followingAddress)!

Item was added:
+ ----- Method: CogARMv8Compiler>>instructionIsADR: (in category 'testing') -----
+ instructionIsADR: word
+ 	"C6.2.10 ADR	C6-773"
+ 	^(word >> 24 bitAnd: 2r10011111) = 2r00010000!

Item was added:
+ ----- Method: CogARMv8Compiler>>instructionIsBL: (in category 'generate machine code - support') -----
+ instructionIsBL: word
+ 	<var: 'word' type: #usqInt>
+ 	<inline: true>
+ 	^word >> 26 = 2r100101!

Item was added:
+ ----- Method: CogARMv8Compiler>>instructionIsBLR: (in category 'generate machine code - support') -----
+ instructionIsBLR: word
+ 	<var: 'word' type: #usqInt>
+ 	<inline: true>
+ 	^(word bitOr: 31 << 5) = 2r11010110001111110000001111100000!

Item was added:
+ ----- Method: CogARMv8Compiler>>instructionIsImm26BorBL: (in category 'generate machine code - support') -----
+ instructionIsImm26BorBL: word
+ 	"C6.2.26 	B		C6-799
+ 	 C6.2.33	BL		C6-812"
+ 	<var: 'word' type: #usqInt>
+ 	<inline: true>
+ 	 "BL is 2r100101, B is 2r000101"
+ 	^(word >> 26 bitAnd: 2r11111) = 2r000101!

Item was added:
+ ----- Method: CogARMv8Compiler>>instructionIsLoadStore: (in category 'inline cacheing') -----
+ instructionIsLoadStore: instr
+ 	"C4.1	A64 instruction set encoding on page C4-252"
+ 	^(instr >> 25 bitAnd: 2r101) = 2r100!

Item was added:
+ ----- Method: CogARMv8Compiler>>instructionIsPCRelativeLoad: (in category 'inline cacheing') -----
+ instructionIsPCRelativeLoad: instr
+ 	"C6.2.131	LDR (literal)		C6-979
+ 	 C6.2.143	LDRSW (literal)	C6-1008"
+ 	^(instr >> 24 bitAnd: 2r00111111) = 2r00011000!

Item was added:
+ ----- Method: CogARMv8Compiler>>instructionSizeAt: (in category 'disassembly') -----
+ instructionSizeAt: pc
+ 	"Answer the instruction size at pc.Simple on ARM ;-)"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>inverseForArithOp: (in category 'generate machine code - support') -----
+ inverseForArithOp: arithOp
+ 	"Several of the opcodes are inverses.  Answer the inverse for an opcode if it has one.
+ 	 See Table A3-2 in sec A3.4 Data-processing instructions of the AARM."
+ 	^arithOp caseOf: {
+ 			[ArithmeticAdd]	->	[ArithmeticSub].
+ 			[ArithmeticAddS]	->	[ArithmeticSubS].
+ 			[ArithmeticSub]	->	[ArithmeticAdd].
+ 			[ArithmeticSubS]	->	[ArithmeticAddS] }!

Item was added:
+ ----- Method: CogARMv8Compiler>>is6BitSignedImmediate:ifTrue:ifFalse: (in category 'generate machine code - support') -----
+ is6BitSignedImmediate: constant ifTrue: binaryBlock ifFalse: nullaryBlock
+ 	<inline: #always>
+ 	(constant between: -1 << 5 and: 1 << 5)
+ 		ifTrue:
+ 			[^binaryBlock
+ 				value: constant abs
+ 				value: constant < 0]
+ 		ifFalse: [^nullaryBlock value]!

Item was added:
+ ----- Method: CogARMv8Compiler>>isAddressRelativeToVarBase: (in category 'testing') -----
+ isAddressRelativeToVarBase: varAddress
+ 	<inline: true>
+ 	<var: #varAddress type: #usqInt>
+ 	"Support for addressing variables off the dedicated VarBaseReg"
+ 	^varAddress notNil
+ 	  and: [varAddress
+ 				between: cogit varBaseAddress - (1 << 8)
+ 				and: cogit varBaseAddress + (1 << 12) - 1]!

Item was added:
+ ----- Method: CogARMv8Compiler>>isBigEndian (in category 'testing') -----
+ isBigEndian
+ 	^false!

Item was added:
+ ----- Method: CogARMv8Compiler>>isCallPrecedingReturnPC: (in category 'testing') -----
+ isCallPrecedingReturnPC: mcpc
+ 	"Assuming mcpc is a send return pc answer if the instruction before it is a call (not a CallFull)."
+ 	"There are two types of calls: BL & BLR; BLR is used for CallFull"
+ 	^self instructionIsBL: (self instructionBeforeAddress: mcpc)!

Item was added:
+ ----- Method: CogARMv8Compiler>>isImmNImmSImmREncodableBitmask:ifTrue:ifFalse: (in category 'generate machine code - support') -----
+ isImmNImmSImmREncodableBitmask: constant ifTrue: trinaryBlock "[:n :imms :immr|...]" ifFalse: nullaryBlock
+ 	"See DecodeBitMasks J1-7389.
+ 	 See https://dinfuehr.github.io/blog/encoding-of-immediate-values-on-aarch64/
+ 	 This method is adapted from The LLVM Compiler Infrastructure, AArch64AddressingModes.h processLogicalImmediate"
+ 	<inline: #always>
+ 	| imm size mask numLeadingOnes numTrailingOnes immr n nImms rotateCount |
+ 	<var: 'mask' type: #usqInt>
+ 	<var: 'nImms' type: #usqInt>
+ 	(constant between: -1 and: 0) ifTrue:
+ 		[^nullaryBlock value].
+ 	imm := self cCode: [constant] inSmalltalk: [constant signedIntToLong64].
+  
+ 	"First, determine the element size."
+ 	size := 32.
+ 	[mask := 1 << size - 1.
+ 	 (imm bitAnd: mask) ~= (imm >> size)
+ 			ifTrue: [size := size * 2. false]
+ 			ifFalse: [size > 2]]
+ 		whileTrue: [size := size / 2].
+ 
+ 	"Second, determine the rotation to make the element be: 0^m 1^n."
+ 	mask := 1 << 64 - 1 >> (64 - size).
+ 	imm := imm bitAnd: mask.
+ 
+ 	(self isShiftedMask: imm)
+ 		ifTrue:
+ 			[rotateCount := self countTrailingZeros: imm.
+ 			 numTrailingOnes := self countTrailingOnes: imm >> rotateCount]
+ 		ifFalse:
+ 			[imm := imm bitOr: mask bitInvert64.
+ 			 (self isShiftedMask: imm) ifFalse:
+ 				[^nullaryBlock value].
+ 			 numLeadingOnes := self countLeadingOnes: imm.
+ 			 rotateCount := 64 - numLeadingOnes.
+ 			 numTrailingOnes := numLeadingOnes + (self countTrailingOnes: imm) - (64 - size)].
+ 
+ 	"Encode in Immr the number of RORs it would take to get *from* 0^m 1^n
+ 	 to our target value, where I is the number of RORs to go the opposite direction."
+  
+ 	self assert: size > rotateCount. "rotateCount should be smaller than element size"
+ 	immr := size - rotateCount bitAnd: size - 1.
+ 
+ 	"If size has a 1 in the n'th bit, create a value that has zeroes in bits [0, n] and ones above that."
+ 	nImms := (size - 1) bitInvert64 << 1.
+ 
+ 	"Or the CTO value into the low bits, which must be below the Nth bit mentioned above."
+ 	nImms := nImms bitOr:  numTrailingOnes - 1.
+ 
+ 	"Extract the seventh bit and toggle it to create the N field."
+ 	n := ((nImms >> 6) bitAnd: 1) bitXor: 1.
+ 
+ 	nImms := nImms bitAnd: 16r3F.
+ 
+ 	self assert: (self decode64Imms: nImms immr: immr) = constant signedIntToLong64.
+ 
+ 	^trinaryBlock
+ 		value: n
+ 		value: nImms
+ 		value: immr
+ !

Item was added:
+ ----- Method: CogARMv8Compiler>>isInImmediateBranchAndLinkRange: (in category 'testing') -----
+ isInImmediateBranchAndLinkRange: offset
+ 	"ARM64 calls span +/- 128 mb.
+ 	 C6.2.33 BL		C6-812"
+ 	<var: #offset type: #'sqIntptr_t'>
+ 	self assert: (offset noMask: 3).
+ 	^offset signedIntFromLong64 >>> 27 between: -16r1 and: 0!

Item was added:
+ ----- Method: CogARMv8Compiler>>isInImmediateBranchRange: (in category 'testing') -----
+ isInImmediateBranchRange: offset
+ 	"ARM64 calls and jumps span +/- 1 mb."
+ 	<var: #offset type: #'usqIntptr_t'>
+ 	self assert: (offset noMask: 3).
+ 	^offset signedIntFromLong64 >>> 18 between: -16r1 and: 0!

Item was added:
+ ----- Method: CogARMv8Compiler>>isInImmediateJumpRange: (in category 'generate machine code - support') -----
+ isInImmediateJumpRange: operand
+ 	"ARMv8 calls and jumps span +/- 128 mb, more than enough for intra-zone calls and jumps."
+ 	<var: #operand type: #'usqIntptr_t'>
+ 	self assert: (operand noMask: 3).
+ 	^operand signedIntFromLong between: -1 << 27 and: 1 << 27 - 1!

Item was added:
+ ----- Method: CogARMv8Compiler>>isJump (in category 'testing') -----
+ isJump
+ 	^super isJump or: [opcode between: CBNZ and: CBZ]!

Item was added:
+ ----- Method: CogARMv8Compiler>>isJumpAt: (in category 'testing') -----
+ isJumpAt: pc
+ 	| op0_101_op1MSB |
+ 	"C4.1	A64 instruction set encoding on page C4-252
+ 	 C4.1.3 Branches, Exception Generating and System instructions"
+ 	"cogit processor disassembleInstructionAt: pc In: objectMemory memory"
+ 	op0_101_op1MSB := (self instructionAt: pc) bitShift: -25.
+ 	^op0_101_op1MSB = 2r0101010								"Conditional branch immediate"
+ 	or: [op0_101_op1MSB = 2r1101011							"Unconditional branch (register)"
+ 	or: [(op0_101_op1MSB bitAnd: 2r1111110) = 2r1001010		"Unconditional Branch (immediate)	BL"
+ 	or: [(op0_101_op1MSB bitAnd: 2r1111110) = 2r0001010]]]	"Unconditional branch (immediate) & Compare/Test and branch (immediate)"!

Item was added:
+ ----- Method: CogARMv8Compiler>>isPCDependent (in category 'testing') -----
+ isPCDependent
+ 	"Answer if the receiver is a pc-dependent instruction.  With out-of-line literals any instruction
+ 	 that refers to a literal depends on the address of the literal, so add them in addition to the jumps."
+ 	^self isJump
+ 	  or: [opcode = AlignmentNops
+ 	  or: [opcode ~= Literal and: [dependent notNil and: [dependent opcode = Literal]]]]!

Item was added:
+ ----- Method: CogARMv8Compiler>>isPossiblyShiftableImm12:ifTrue:ifFalse: (in category 'generate machine code - support') -----
+ isPossiblyShiftableImm12: immediate ifTrue: unaryBlock ifFalse: nullaryBlock
+ 	<inline: #always>
+ 	(immediate between: 0 and: 1 << 12 - 1) ifTrue:
+ 		[^unaryBlock value: false].
+ 	((immediate noMask: 1 << 12 - 1)
+ 	 and: [immediate >>> 12 between: 0 and: 1 << 12 - 1]) ifTrue:
+ 		[^unaryBlock value: true].
+ 	^nullaryBlock value!

Item was added:
+ ----- Method: CogARMv8Compiler>>isPossiblyShiftableImm12orImm9:ifTrue:ifFalse: (in category 'generate machine code - support') -----
+ isPossiblyShiftableImm12orImm9: immediate ifTrue: unaryBlock ifFalse: nullaryBlock
+ 	<inline: #always>
+ 	((immediate between: -256 and: 255)
+ 	 or: [immediate between: 0 and: 1 << 12 - 1]) ifTrue:
+ 		[^unaryBlock value: false].
+ 	((immediate noMask: 1 << 12 - 1)
+ 	 and: [immediate >>> 12 between: 0 and: 1 << 12 - 1]) ifTrue:
+ 		[^unaryBlock value: true].
+ 	^nullaryBlock value!

Item was added:
+ ----- Method: CogARMv8Compiler>>isPossiblyShiftableNegatableImm12:ifTrue:ifFalse: (in category 'generate machine code - support') -----
+ isPossiblyShiftableNegatableImm12: immediate ifTrue: unaryBlock ifFalse: nullaryBlock
+ 	<inline: #always>
+ 	(immediate between: -1 << 12 and: 1 << 12 - 1) ifTrue:
+ 		[^unaryBlock value: false].
+ 	((immediate noMask: 1 << 12 - 1)
+ 	 and: [immediate >>> 12 between: -1 << 12 and: 1 << 12 - 1]) ifTrue:
+ 		[^unaryBlock value: true].
+ 	^nullaryBlock value!

Item was added:
+ ----- Method: CogARMv8Compiler>>isSharable (in category 'generate machine code') -----
+ isSharable
+ 	"Hack:  To know if a literal should be unique (not shared) mark the LSB of the second operand."
+ 	<inline: true>
+ 	self assert: opcode = Literal.
+ 	^(operands at: 1) anyMask: 1!

Item was added:
+ ----- Method: CogARMv8Compiler>>isShiftedMask: (in category 'generate machine code - support') -----
+ isShiftedMask: anInteger
+ 	| bits |
+ 	^anInteger ~= 0
+ 	  and: [bits := anInteger - 1 bitOr: anInteger.
+ 		   (bits bitAnd: bits + 1) = 0]!

Item was added:
+ ----- Method: CogARMv8Compiler>>isUnsigned12BitMultipleOf8: (in category 'generate machine code - support') -----
+ isUnsigned12BitMultipleOf8: anInteger
+ 	^anInteger \\ 8 = 0
+ 	  and: [anInteger / 8 between: 0 and: 1 << 12 - 1]!

Item was added:
+ ----- Method: CogARMv8Compiler>>jumpLongByteSize (in category 'accessing') -----
+ jumpLongByteSize
+ "	Branch/Call ranges.  Jump[Cond] can be generated as short as possible.  Call/Jump[Cond]Long must be generated
+ 	in the same number of bytes irrespective of displacement since their targets may be updated, but they need only
+ 	span 16Mb, the maximum size of the code zone.  This allows e.g. ARM to use single-word call and jump instructions
+ 	for most calls and jumps.  CallFull/JumpFull must also be generated in the same number of bytes irrespective of
+ 	displacement for the same reason, but they must be able to span the full (32-bit or 64-bit) address space because
+ 	they are used to call code in the C runtime, which may be distant from the code zone"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>jumpLongConditionalByteSize (in category 'accessing') -----
+ jumpLongConditionalByteSize
+ 	^8!

Item was added:
+ ----- Method: CogARMv8Compiler>>jumpLongTargetBeforeFollowingAddress: (in category 'inline cacheing') -----
+ jumpLongTargetBeforeFollowingAddress: mcpc
+ 	"C6.2.26 	B		C6-799"
+ 	^self callTargetFromReturnAddress: mcpc!

Item was added:
+ ----- Method: CogARMv8Compiler>>jumpTargetPCAt: (in category 'disassembly') -----
+ jumpTargetPCAt: pc
+ 	<returnTypeC: #usqInt>
+ 	| operand word |
+ 	"cogit processor disassembleInstructionAt: pc In: objectMemory memory"
+ 	word := self instructionAt: pc.
+ 	self assert: word >> 26 = 2r10101.
+ 	operand := word >> 5 bitAnd: 16r7FFFF.
+ 	(operand anyMask: 16r40000) ifTrue:
+ 		[operand := operand - 16r80000].
+ 	^self
+ 		cCode: [operand * 4 + pc]
+ 		inSmalltalk: [operand * 4 + pc bitAnd: cogit addressSpaceMask]!

Item was added:
+ ----- Method: CogARMv8Compiler>>leafCallStackPointerDelta (in category 'abi') -----
+ leafCallStackPointerDelta
+ 	"Answer the delta from the stack pointer after a call to the stack pointer
+ 	 immediately prior to the call.  This is used to compute the stack pointer
+ 	 immediately prior to a call from within a leaf routine, which in turn is used
+ 	 to capture the c stack pointer to use in trampolines back into the C run-time."
+ 	"This might actually be false, since directly after a call, lr, fp and variable registers need be pushed onto the stack. It depends on the implementation of call."
+ 	^0!

Item was added:
+ ----- Method: CogARMv8Compiler>>literal32BeforeFollowingAddress: (in category 'inline cacheing') -----
+ literal32BeforeFollowingAddress: followingAddress
+ 	"Answer the 32-bit constant loaded by the instruction sequence just before this address:
+ 	  CmpC32R MoveC32R"
+ 	^self instructionAt:
+ 		(self pcRelativeAddressAt:
+ 			(self instructionAddressBefore:
+ 				((self instructionIsPCRelativeLoad: (self instructionBeforeAddress: followingAddress))
+ 					ifTrue: [followingAddress]
+ 					ifFalse: [followingAddress - 4])))!

Item was added:
+ ----- Method: CogARMv8Compiler>>literalAlignment (in category 'accessing') -----
+ literalAlignment
+ 	"Answer the required alignment for literals embedded in code."
+ 	<inline: true>
+ 	^8!

Item was added:
+ ----- Method: CogARMv8Compiler>>literalBeforeFollowingAddress: (in category 'inline cacheing') -----
+ literalBeforeFollowingAddress: followingAddress
+ 	"Answer the literal referenced by the instruction immediately preceding followingAddress.
+ 	  ArithCwR MoveCwR PushCw"
+ 	^objectMemory longAt:
+ 		(self pcRelativeAddressAt:
+ 			(self instructionAddressBefore:
+ 				((self instructionIsPCRelativeLoad: (self instructionBeforeAddress: followingAddress))
+ 					ifTrue: [followingAddress]
+ 					ifFalse: [followingAddress - 4])))!

Item was added:
+ ----- Method: CogARMv8Compiler>>literalLoadInstructionBytes (in category 'accessing') -----
+ literalLoadInstructionBytes
+ 	"Answer the size of a literal load instruction (which does not include the size of the literal).
+ 	 With out-of-line literals this is always a single LDR instruction that refers to the literal."
+ 	<inline: true>
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>literalOpcodeIndex (in category 'generate machine code') -----
+ literalOpcodeIndex
+ 	"Hack:  To know how far away a literal is from its referencing instruction we store
+ 	 its opcodeIndex, or -1, if as yet unassigned, in the second operand of the literal."
+ 	<inline: true>
+ 	self assert: opcode = Literal.
+ 	^(operands at: 2) asInteger!

Item was added:
+ ----- Method: CogARMv8Compiler>>literalSize (in category 'generate machine code') -----
+ literalSize
+ 	"Hack:  To handle both 32-bit and 64-bit literals, store the literal's size in a field of the second operand."
+ 	<inline: true>
+ 	self assert: opcode = Literal.
+ 	^(operands at: 1) "If not set, default to bytesPerOop"
+ 		ifNil: [objectMemory bytesPerOop]
+ 		ifNotNil: [((operands at: 1) >> 1) bitAnd: 15]!

Item was added:
+ ----- Method: CogARMv8Compiler>>loadLiteralByteSize (in category 'accessing') -----
+ loadLiteralByteSize
+ 	"Answer the byte size of a MoveCwR opcode's corresponding machine code.
+ 	 On ARMv8 this is a single instruction pc-relative register load"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>loadPICLiteralByteSize (in category 'accessing') -----
+ loadPICLiteralByteSize
+ 	"Answer the byte size of a MoveCwR opcode's corresponding machine code
+ 	 when the argument is a PIC.  This is for the self-reference at the end of a
+ 	 closed PIC.  On ARM this is a single instruction pc-relative register load."
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>machineCodeAt: (in category 'accessing') -----
+ machineCodeAt: anOffset
+ 	"read aWord from machineCode, with little endian"
+ 	<inline: true>
+ 	^machineCode at: anOffset // 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>machineCodeAt:put: (in category 'accessing') -----
+ machineCodeAt: anOffset put: aWord
+ 	"add aWord to machineCode, with little endian"
+ 	<inline: true>
+ 	machineCode at: anOffset // 4 put: aWord!

Item was added:
+ ----- Method: CogARMv8Compiler>>machineCodeBytes (in category 'generate machine code') -----
+ machineCodeBytes
+ 	"Answer the maximum number of bytes of machine code generated for any abstract instruction.
+ 	Likely to be quite different for AARCH64"
+ 	^12!

Item was added:
+ ----- Method: CogARMv8Compiler>>machineCodeWords (in category 'generate machine code') -----
+ machineCodeWords
+ 	"Answer the maximum number of words of machine code generated for any abstract instruction.
+ 	Likely to be quite different for AARCH64"
+ 	^self machineCodeBytes // 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>mapEntryAddress (in category 'generate machine code') -----
+ mapEntryAddress
+ 	"Typically map entries apply to the end of an instruction, for two reasons:
+ 	  a)	to cope with literals embedded in variable-length instructions, since, e.g.
+ 		on x86, the literal typically comes at the end of the instruction.
+ 	  b)	in-line cache detection is based on return addresses, which are typically
+ 		to the instruction following a call.
+ 	 But on ARMv8 we use out-of-line literals so the mapEntryAddress of a literal is simply the instruction's address."
+ 	<inline: true>
+ 	^opcode = Literal
+ 		ifTrue: [address]
+ 		ifFalse: [address + machineCodeSize]!

Item was added:
+ ----- Method: CogARMv8Compiler>>movern:rd: (in category 'generate machine code - support') -----
+ movern: srcReg rd: destReg
+ 	^self addrn: srcReg rd: destReg imm: 0 shiftBy12: false!

Item was added:
+ ----- Method: CogARMv8Compiler>>nameForRegister: (in category 'printing') -----
+ nameForRegister: reg "<Integer>"
+ 	<doNotGenerate>
+ 	| default |
+ 	default := super nameForRegister: reg.
+ 	^default last = $?
+ 		ifTrue:
+ 			[reg = 31
+ 				ifTrue:
+ 					['SP/XZR']
+ 				ifFalse:
+ 					[#(LR CArg0Reg CArg1Reg CArg2Reg CArg3Reg)
+ 						detect: [:sym| (thisContext method methodClass classPool at: sym) = reg] 
+ 						ifNone: [default]]]
+ 		ifFalse:
+ 			[default]!

Item was added:
+ ----- Method: CogARMv8Compiler>>noteFollowingConditionalBranch: (in category 'abstract instructions') -----
+ noteFollowingConditionalBranch: branch
+ 	"Morph an Overflow/NoOverflow check after a MulOverflow into an efficient
+ 	 test for overflow, hence avoiding having to set and test the V flag.
+ 	 MulOverflowRRR generates
+ 		mul		Rd,Rm,Rn
+ 		smulh 	RISCTempReg,Rm,Rn
+ 		cmp	RISCTempReg, #0x1
+ 	 so it must be followed by an unsigned conditional jump, Above for Overflow, BelowOrEqual for NoOverflow."
+ 	<var: #branch type: #'AbstractInstruction *'>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	
+ 	(opcode = MulOverflowRRR
+ 	 and: [branch opcode = JumpOverflow or: [branch opcode = JumpNoOverflow]])  ifTrue:
+ 		[branch opcode: (branch opcode = JumpOverflow
+ 							ifTrue: [JumpMulOverflow]
+ 							ifFalse: [JumpNoMulOverflow])].
+ 
+ 	^branch!

Item was added:
+ ----- Method: CogARMv8Compiler>>numDCacheFlushOpcodes (in category 'inline cacheing') -----
+ numDCacheFlushOpcodes
+ 	^cogit getCodeToDataDelta ~= 0 ifTrue: [15] ifFalse: [0]!

Item was added:
+ ----- Method: CogARMv8Compiler>>numICacheFlushOpcodes (in category 'inline cacheing') -----
+ numICacheFlushOpcodes
+ 	^24!

Item was added:
+ ----- Method: CogARMv8Compiler>>numIntRegArgs (in category 'accessing') -----
+ numIntRegArgs
+ 	"See e.g. http://infocenter.arm.com/help/topic/com.arm.doc.den0028b/ARM_DEN0028B_SMC_Calling_Convention.pdf
+ 	 Table 3-1 Register Usage in AArch64 SMC32, HVC32, SMC64, and HVC64 calls"
+ 	^6!

Item was added:
+ ----- Method: CogARMv8Compiler>>numLowLevelLockOpcodes (in category 'multi-threading') -----
+ numLowLevelLockOpcodes
+ 	<inline: #always>
+ 	^14 "12 opcodes in 8.0 LDAXR/STLXR version, plus two words for the vmOwnerLockAddress"!

Item was added:
+ ----- Method: CogARMv8Compiler>>outOfLineLiteralOpcodeLimit (in category 'generate machine code') -----
+ outOfLineLiteralOpcodeLimit
+ 	"The maximum offset in a LDR (literal) is -2^18 to 2^18-1.
+ 	 And this is multiplied by 4 to produce the effective address.
+ 	 This is a huge range; we have no grounds for concern."
+ 	^1 << 18 - 1!

Item was added:
+ ----- Method: CogARMv8Compiler>>outputMachineCodeAt: (in category 'generate machine code') -----
+ outputMachineCodeAt: targetAddress
+ 	"Override to move machine code a word at a time."
+ 	<inline: true>
+ 	0 to: machineCodeSize - 1 by: 4 do:
+ 		[:j|
+ 		cogit codeLong32At: targetAddress + j put: (machineCode at: j // 4)]!

Item was added:
+ ----- Method: CogARMv8Compiler>>padIfPossibleWithStopsFrom:to: (in category 'generate machine code') -----
+ padIfPossibleWithStopsFrom: startAddr to: endAddr
+ 	| nullBytes |
+ 	nullBytes := (endAddr - startAddr + 1) \\ 4.
+ 	self stopsFrom: startAddr to: endAddr - nullBytes.
+ 	endAddr - nullBytes + 1 to: endAddr 
+ 		do: [ :p | cogit codeByteAt: p put: 16rFF]!

Item was added:
+ ----- Method: CogARMv8Compiler>>pcRelativeAddressAt: (in category 'inline cacheing') -----
+ pcRelativeAddressAt: mcpc
+ 	"Extract the address of the adr rX, offset instruction at address mcpc
+ 	 C6.2.131	LDR (literal)		C6-979"
+ 	| instr |
+ 	instr := self instructionAt: mcpc.
+ 	"cogit processor disassembleInstructionAt: mcpc In: objectMemory memory"
+ 	self assert: (self instructionIsPCRelativeLoad: instr).
+ 	^(instr >> 3 bitAnd: 1 << 22 - 4) - (instr >> 2 bitAnd: 1 << 21) + mcpc!

Item was added:
+ ----- Method: CogARMv8Compiler>>printCTR_EL0 (in category 'feature detection') -----
+ printCTR_EL0
+ 	<doNotGenerate>
+ 	^String streamContents:
+ 		[:s| | ctr_el0 fieldPrinter l1ip |
+ 		ctr_el0 := self ctrEl0.
+ 		fieldPrinter := [:name :startBit| | field |
+ 						s nextPutAll: name; nextPutAll: ', ['; print: startBit + 3; nextPut: $,; print: startBit; nextPutAll: ']		log2 words: '.
+ 						s print: (field := ctr_el0 >> startBit bitAnd: 15); nextPutAll: ' ('; print: 8 << field; nextPutAll: ' bytes)'; cr].
+ 		s
+ 			nextPutAll: 'DIC, bit [29]	Instruction cache invalidation requirements for instruction to data coherence. The meaning of this bit is:';
+ 			crtab;
+ 			nextPutAll: ((ctr_el0 noMask: 1 << 29)
+ 							ifTrue: ['0b0 Instruction cache invalidation to the Point of Unification is required for instruction to data coherence.']
+ 							ifFalse: ['0b1 Instruction cache cleaning to the Point of Unification is not required for instruction to data coherence.']);
+ 			cr.
+ 		s
+ 			nextPutAll: 'IDC, bit [28]	Data cache clean requirements for instruction to data coherence. The meaning of this bit is:';
+ 			crtab;
+ 			nextPutAll: ((ctr_el0 noMask: 1 << 28)
+ 							ifTrue: ['0b0 Data cache clean to the Point of Unification is required for instruction to data coherence, unless CLIDR.LoC == 0b000 or (CLIDR.LoUIS == 0b000 && CLIDR.LoUU == 0b000).']
+ 							ifFalse: ['0b1 Data cache clean to the Point of Unification is not required for instruction to data coherence.']);
+ 			cr.
+ 
+ 		fieldPrinter
+ 			value: 'Cache writeback granule' value: 24;
+ 			value: 'Exclusives reservation granule' value: 20;
+ 			value: 'DminLine' value: 16;
+ 			value: 'IminLine' value: 0.
+ 		s
+ 			nextPutAll: 'Level 1 instruction cache policy: '; print: (l1ip := ctr_el0 >> 14 bitAnd: 2); space;
+ 			nextPutAll: (#(	'VMID aware Physical Index, Physical tag (VPIPT)'
+ 							'ASID-tagged Virtual Index, Virtual Tag (AIVIVT)'
+ 							'Virtual Index, Physical Tag (VIPT)'
+ 							'Physical Index, Physical Tag (PIPT)') at: l1ip + 1);
+ 			cr]!

Item was added:
+ ----- Method: CogARMv8Compiler>>prn:imm:shiftBy12: (in category 'generate machine code - support') -----
+ prn: baseReg imm: offset shiftBy12: shiftBy12
+ 	"C6.2.211	PRFM (immediate)	C6-1136"
+ 
+ 	"Unsigned offset, C6-1136"
+ 	"This is the only casde we can make use of so far..."
+ 	self assert: (offset \\ 8 = 0
+ 				 and: [offset / 8 between: 0 and: 1 << 12 - 1]).
+ 	^2r1111100101 << 22
+ 		+ (offset << 7 "10 - 3")
+ 		+ (baseReg << 5)
+ 		+ 0 "prfop = PLD:L1:KEEP"!

Item was added:
+ ----- Method: CogARMv8Compiler>>pushLinkRegisterByteSize (in category 'accessing') -----
+ pushLinkRegisterByteSize
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>relocateCallBeforeReturnPC:by: (in category 'inline cacheing') -----
+ relocateCallBeforeReturnPC: retpc by: delta
+ 	| instr distanceDiv4 |
+ 	"C6.2.26 	B		C6-799
+ 	 C6.2.33	BL		C6-812"
+ 	self assert: delta \\ 4 = 0.
+ 	delta ~= 0 ifTrue:
+ 		[instr := self instructionBeforeAddress: retpc.
+ 		 self assert: (self instructionIsImm26BorBL: instr).
+ 
+ 		 distanceDiv4 := instr bitAnd: 2 << 26 - 1.
+ 		 distanceDiv4 := distanceDiv4 + (delta // 4).
+ 		 cogit
+ 			codeLong32At: (self instructionAddressBefore: retpc)
+ 			put: ((instr bitAnd: 16rFC000000) bitOr: (distanceDiv4 bitAnd: 16r3FFFFFF))]
+ 
+ 	"cogit processor disassembleInstructionAt: (self instructionAddressBefore: retpc) In: objectMemory memory"!

Item was added:
+ ----- Method: CogARMv8Compiler>>relocateMethodReferenceBeforeAddress:by: (in category 'inline cacheing') -----
+ relocateMethodReferenceBeforeAddress: pc by: delta
+ 	"We generate the method address using pc-relative addressing.
+ 	 Simply check that pc-relative addressing is being used. c.f.
+ 	 emitMoveCw:intoR:at:"
+ 	<inline: true>
+ 	self assert: ((self instructionIsADR: (self instructionAt: pc - 4)) "MoveCwR"
+ 			or: [self instructionIsADR: (self instructionAt: pc - 8)]) "PushCwR"
+ 
+ 	"cogit processor disassembleInstructionAt: (self instructionAddressBefore: pc - 4) In: objectMemory memory"
+ 	"cogit processor disassembleInstructionAt: (self instructionAddressBefore: pc) In: objectMemory memory"!

Item was added:
+ ----- Method: CogARMv8Compiler>>rewriteCPICJumpAt:target: (in category 'inline cacheing') -----
+ rewriteCPICJumpAt: addressFollowingJump target: jumpTargetAddr
+ 	"Rewrite a jump instruction to call a different target.  This variant is used to reset the 
+ 	jumps in the prototype CPIC to suit each use,.   
+ 	Answer the extent of the code change which is used to compute the range of the icache to flush."
+ 	<var: #addressFollowingJump type: #usqInt>
+ 	<var: #jumpTargetAddr type: #usqInt>
+ 	<inline: true>
+ 	"cogit processor disassembleInstructionAt: addressFollowingJump - 4 In: objectMemory memory"
+ 	self rewriteImm19JumpBefore: addressFollowingJump target: jumpTargetAddr!

Item was added:
+ ----- Method: CogARMv8Compiler>>rewriteCallAt:target: (in category 'inline cacheing') -----
+ rewriteCallAt: callSiteReturnAddress target: callTargetAddress
+ 	"Rewrite a call instruction to call a different target.  This variant is used to link PICs
+ 	 in ceSendMiss et al, and to rewrite cached primitive calls.   Answer the extent of
+ 	 the code change which is used to compute the range of the icache to flush."
+ 	<var: #callSiteReturnAddress type: #usqInt>
+ 	<var: #callTargetAddress type: #usqInt>
+ 	cogit codeLong32At: callSiteReturnAddress - 4 put: (self bl: callTargetAddress - (callSiteReturnAddress - 4)).
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>rewriteImm19JumpBefore:target: (in category 'inline cacheing') -----
+ rewriteImm19JumpBefore: followingAddress target: targetAddress
+ 	"Rewrite a long jump/call instruction to jump/call to a different target.
+ 	 Answer the extent of the code change which is used to compute the range of the icache to flush.
+ 	 C6.2.25	B.cond		C6-798"
+ 	| mcpc offset instruction instrOpcode |
+ 	"cogit processor disassembleInstructionAt: followingAddress - 4 In: objectMemory memory"
+ 	mcpc := self instructionAddressBefore: followingAddress.
+ 	offset := targetAddress - mcpc.
+ 	instruction := self instructionBeforeAddress: followingAddress.
+ 	instrOpcode := instruction >> 26.
+ 	self assert: instrOpcode = 2r10101.
+ 	cogit
+ 		codeLong32At: mcpc
+ 		put: instrOpcode << 26 + ((offset >>> 2 bitAnd: 1 << 19 - 1) << 5) + (instruction bitAnd: 2r1111).
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>rewriteImm26JumpBefore:target: (in category 'inline cacheing') -----
+ rewriteImm26JumpBefore: followingAddress target: targetAddress
+ 	"Rewrite a long jump/call instruction to jump/call to a different target.
+ 	 Answer the extent of the code change which is used to compute the range of the icache to flush.
+ 	 C6.2.26	B	C6-799
+ 	 C6.2.33 	BL	C6-812"
+ 	| mcpc offset instrOpcode |
+ 	"cogit processor disassembleInstructionAt: followingAddress - 4 In: objectMemory memory"
+ 	mcpc := self instructionAddressBefore: followingAddress.
+ 	offset := targetAddress - mcpc.
+ 	instrOpcode := (self instructionBeforeAddress: followingAddress) >> 26.
+ 	self assert: (instrOpcode = 2r101 or: [instrOpcode = 2r100101]).
+ 	cogit
+ 		codeLong32At: mcpc
+ 		put: instrOpcode << 26 + (offset >>> 2 bitAnd: 1 << 26 - 1).
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>rewriteInlineCacheAt:tag:target: (in category 'inline cacheing') -----
+ rewriteInlineCacheAt: callSiteReturnAddress tag: cacheTag target: callTargetAddress
+ 	"Rewrite an inline cache to call a different target for a new tag.  This variant is used
+ 	 to link unlinked sends in ceSend:to:numArgs: et al.  Answer the extent of the code
+ 	 change which is used to compute the range of the icache to flush.
+ 	 N.B.  On 64-bit platforms the inline cache tag is only 32-bits wide, hence this code
+ 	 is very similar to that for ARM32 CogOutOfLineLiteralsARMCompiler."
+ 	<var: #callSiteReturnAddress type: #usqInt>
+ 	<var: #callTargetAddress type: #usqInt>
+ 	| call callDistance |
+ 	(cogit initialized and: [callTargetAddress < cogit minCallAddress]) ifTrue:
+ 		[self error: 'linking callsite to invalid address'].
+ 	callDistance := (callTargetAddress - (callSiteReturnAddress - 4 "return offset")) signedIntToLong.
+ 	self assert: (self isInImmediateJumpRange: callDistance). "we don't support long call updates here"
+ 	call := self bl: callDistance.
+ 	cogit
+ 		codeLong32At: (self instructionAddressBefore: callSiteReturnAddress) put: call;
+ 		codeLong32At: (self pcRelativeAddressAt: callSiteReturnAddress - 8) put: cacheTag signedIntToLong.
+ 	self assert: (self inlineCacheTagAt: callSiteReturnAddress) signedIntFromLong = cacheTag.
+ 	"self cCode: ''
+ 		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 8 to: (self pcRelativeAddressAt: callSiteReturnAddress - 8)]."
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>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.  RThis cannot happen in 64-bits as cache tags are guaranteed to be 32-bits or less."
+ 	self error: 'should not happen'!

Item was added:
+ ----- Method: CogARMv8Compiler>>rewriteJumpFullAt:target: (in category 'full transfer run-time support') -----
+ rewriteJumpFullAt: callSiteReturnAddress target: callTargetAddress
+ 	"Rewrite a JumpFull instruction to jump to a different target.  This variant is used to rewrite cached primitive calls.
+ 	 Answer the extent of the code change which is used to compute the range of the icache to flush."
+ 	"cogit processor disassembleInstructionAt: callSiteReturnAddress - 8 In: objectMemory memory"
+ 	"cogit processor disassembleInstructionAt: callSiteReturnAddress - 4 In: objectMemory memory"
+ 	cogit
+ 		codeLongAt: (self pcRelativeAddressAt: callSiteReturnAddress - 8)
+ 		put: callTargetAddress.
+ 	^0!

Item was added:
+ ----- Method: CogARMv8Compiler>>rewriteJumpLongAt:target: (in category 'inline cacheing') -----
+ rewriteJumpLongAt: callSiteReturnAddress target: callTargetAddress
+ 	"Rewrite a long jump instruction to jump to a different target.  This variant
+ 	 is used to rewrite cached primitive calls.   Answer the extent of the
+ 	 code change which is used to compute the range of the icache to flush."
+ 	<inline: true>
+ 	^self rewriteImm26JumpBefore: callSiteReturnAddress target: callTargetAddress!

Item was added:
+ ----- Method: CogARMv8Compiler>>roundUpToMethodAlignment: (in category 'method zone and entry point alignment') -----
+ roundUpToMethodAlignment: numBytes
+ 	"Determine the default alignment for the start of a CogMehtod, which in turn
+ 	 determines the size of the mask used to distinguish the checked and unchecked
+ 	 entry-points, used to distinguish normal and super sends on method unlinking.
+ 	 This is implemented here to allow processors with coarse instructions (ARM) to
+ 	 increase the alignment if required."
+ 	<cmacro: '(ignored,numBytes) (((numBytes) + 15) & -16)'> "extra parens to placate gdb :-("
+ 	^numBytes + 15 bitAnd: -16!

Item was added:
+ ----- Method: CogARMv8Compiler>>saveAndRestoreLinkRegAround: (in category 'abi') -----
+ saveAndRestoreLinkRegAround: aBlock
+ 	"If the processor's ABI includes a link register, generate instructions
+ 	 to save and restore it around aBlock, which is assumed to generate code."
+ 	<inline: true>
+ 	| inst |
+ 	inst := cogit PushR: LinkReg.
+ 	aBlock value.
+ 	cogit PopR: LinkReg.
+ 	^inst!

Item was added:
+ ----- Method: CogARMv8Compiler>>saveAndRestoreLinkRegUsingCalleeSavedRegNotLiveAtPointOfSendAround: (in category 'abi') -----
+ saveAndRestoreLinkRegUsingCalleeSavedRegNotLiveAtPointOfSendAround: aBlock
+ 	"Extra7Reg is callee-saved and not live at point of send."
+ 	<inline: #always>
+ 	| inst |
+ 	inst := cogit MoveR: LinkReg R: Extra8Reg.
+ 	aBlock value.
+ 	cogit MoveR: Extra8Reg R: LinkReg!

Item was added:
+ ----- Method: CogARMv8Compiler>>setCtrEl0: (in category 'feature detection') -----
+ setCtrEl0: n
+ 	<cmacro: '(ign,n) ctrEl0 = n'>
+ 	"For want of somewhere to put the variable..."
+ 	self class instVarNamed: 'ctrEl0' put: n!

Item was added:
+ ----- Method: CogARMv8Compiler>>setIdISAR0: (in category 'feature detection') -----
+ setIdISAR0: n
+ 	<cmacro: '(ign,n) idISAR0 = n'>
+ 	"For want of somewhere to put the variable..."
+ 	self class instVarNamed: 'idISAR0' put: n!

Item was added:
+ ----- Method: CogARMv8Compiler>>setLiteralOpcodeIndex: (in category 'generate machine code') -----
+ setLiteralOpcodeIndex: index
+ 	"Hack:  To know how far away a literal is from its referencing instruction we store
+ 	 its opcodeIndex, or -1, if as yet unassigned, in the second operand of the literal."
+ 	<inline: true>
+ 	self assert: opcode = Literal.
+ 	operands at: 2 put: index!

Item was added:
+ ----- Method: CogARMv8Compiler>>setLiteralSize: (in category 'generate machine code - support') -----
+ setLiteralSize: sizeOfLiteral
+ 	"Set the size field.  The only complication is that in Smalltalk (operands at: 1) may be nil."
+ 	operands
+ 		at: 1
+ 		put: ((operands at: 1) ifNil: [0] ifNotNil: [:operand| operand bitClear: 30])
+ 			+ (sizeOfLiteral << 1)!

Item was added:
+ ----- Method: CogARMv8Compiler>>setsConditionCodesFor: (in category 'testing') -----
+ setsConditionCodesFor: aConditionalJumpOpcode
+ 	<inline: false> "to save Slang from having to be a real compiler (it can't inline switches that return)"
+ 	"Answer if the receiver's opcode sets the condition codes correctly for the given conditional jump opcode.
+ 	 ARMv8 appears not to set condition codes at all in its shift instruction(s), which are aliases for
+ 	 SBFM (signed bit field move) and C6.2.332 UBFM.
+ 
+ 	 C6.2.232	SBFM	C6-1170
+ 	 C6.2.332	UBFM	C6-1351"
+ 	<inline: #always>
+ 	^false	"All cases below answer false, so..."
+ 	"^opcode caseOf:
+ 		{	[ArithmeticShiftRightCqR]	->	[false].
+ 			[ArithmeticShiftRightRR]	->	[false].
+ 			[LogicalShiftLeftCqR]		->	[false].
+ 			[LogicalShiftLeftRR]			->	[false].
+ 			[LogicalShiftRightCqR]		->	[false].
+ 			[XorRR]						->	[false].
+ 			[ClzRR]						->	[false]
+ 		}
+ 		otherwise: [self halt: 'unhandled opcode in setsConditionCodesFor:'. false]"!

Item was added:
+ ----- Method: CogARMv8Compiler>>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 preceding 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.
+ 
+ 	 ARMv8 is simple; the 26-bit call/jump range (for a signed 28 bit extent, +/- 128Mb) and
+ 	 19 bit conditional branch range  (for a signed 21 bit extent, +/- 1Mb) 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]].
+ 	^machineCodeSize := maxSize!

Item was added:
+ ----- Method: CogARMv8Compiler>>st:rn:rt:imm:shiftBy12: (in category 'generate machine code - support') -----
+ st: unitSizeLog2MinusOne rn: baseReg rt: targetReg imm: offset shiftBy12: shiftBy12
+ 	"C6.2.273	STR (immediate)	C6-1239
+ 	 C6.2.275	STRB (immediate)	C6-1244"
+ 
+ 	| unitSize |
+ 	unitSize := 1 << unitSizeLog2MinusOne.
+ 	self deny: SP = targetReg.
+ 	self deny: baseReg = targetReg.
+ 	"Unsigned offset, C6-1240"
+ 	(offset \\ unitSize = 0
+ 	 and: [offset / unitSize between: 0 and: 1 << 12 - 1]) ifTrue:
+ 		[^unitSizeLog2MinusOne << 30
+ 		+ (2r11100100 << 22)
+ 		+ (offset << (10 - unitSizeLog2MinusOne))
+ 		+ (baseReg << 5)
+ 		+ targetReg].
+ 	self assert: (offset between: -256 and: 255).
+ 	^unitSizeLog2MinusOne << 30
+ 	  + (2r111000000 << 21)
+ 	  + ((offset bitAnd: 511) << 12)
+ 	  + (baseReg << 5)
+ 	  + targetReg!

Item was added:
+ ----- Method: CogARMv8Compiler>>stop (in category 'encoding') -----
+ stop
+ 	"generate a HLT; C6.2.92 Arm ARM"
+ 	<inline: true>
+ 	^2r11010100010000000000000000000000 "16rD4400000"!

Item was added:
+ ----- Method: CogARMv8Compiler>>stopsFrom:to: (in category 'generate machine code - support') -----
+ stopsFrom: startAddr to: endAddr
+ 	self assert: endAddr - startAddr + 1 \\ 4 = 0.
+ 	startAddr to: endAddr by: 4 do: 
+ 		[:addr | cogit codeLong32At: addr put: self stop]!

Item was added:
+ ----- Method: CogARMv8Compiler>>storeLiteral32:beforeFollowingAddress: (in category 'inline cacheing') -----
+ storeLiteral32: literal beforeFollowingAddress: followingAddress
+ 	"Rewrite the 32-bit literal in the instruction immediately preceding followingAddress."
+ 	cogit
+ 		codeLong32At:
+ 			(self pcRelativeAddressAt:
+ 				(self instructionAddressBefore:
+ 					((self instructionIsPCRelativeLoad: (self instructionBeforeAddress: followingAddress))
+ 						ifTrue: [followingAddress]
+ 						ifFalse: [followingAddress - 4])))
+ 		put: literal!

Item was added:
+ ----- Method: CogARMv8Compiler>>storeLiteral:beforeFollowingAddress: (in category 'inline cacheing') -----
+ storeLiteral: literal beforeFollowingAddress: followingAddress
+ 	"Rewrite the literal in the instruction immediately preceding followingAddress."
+ 	cogit
+ 		codeLongAt:
+ 			(self pcRelativeAddressAt:
+ 				(self instructionAddressBefore:
+ 					((self instructionIsPCRelativeLoad: (self instructionBeforeAddress: followingAddress))
+ 						ifTrue: [followingAddress]
+ 						ifFalse: [followingAddress - 4])))
+ 		put: literal!

Item was added:
+ ----- Method: CogARMv8Compiler>>usesNativeSPReg (in category 'testing') -----
+ usesNativeSPReg
+ 	"Answer if the code model implemented by the receiver uses the native stack pointer for SPReg.
+ 	 Because ARMv8 mandates 16-bit stack pointer alignment when the SA0 bit is set in SCTLR_EL1,
+ 	 and that this choice is common and immutable on typical ARMv8 OS's, we do not use the native
+ 	 stack pointer in Smalltalk machine code."
+ 	^false!

Item was added:
+ ----- Method: CogARMv8Compiler>>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 isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
+ 								ifTrue: [:ign|false] ifFalse: [true]].
+ 		[AddCqRR]		-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
+ 								ifTrue: [:ign|false] ifFalse: [true]].
+ 		[SubCqR]		-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
+ 								ifTrue: [:ign|false] ifFalse: [true]].
+ 		[CmpCqR]		-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
+ 								ifTrue: [:ign|false] ifFalse: [true]].
+ 		[LoadEffectiveAddressMwrR]
+ 						-> [^self isPossiblyShiftableImm12: (operands at: 0) signedIntFromLong64
+ 								ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[AndCqR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
+ 		[AndCqRR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
+ 		[OrCqRR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
+ 		[OrCqR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
+ 		[TstCqR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
+ 		[XorCqR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
+ 		[AddCwR]		-> [^true].
+ 		[AndCwR]		-> [^true].
+ 		[CmpCwR]		-> [^true].
+ 		[CmpC32R]		-> [^true].
+ 		[OrCwR]		-> [^true].
+ 		[SubCwR]		-> [^true].
+ 		[XorCwR]		-> [^true].
+ 		"Data Movement"						
+ 		[MoveCqR]		-> [self isPossiblyShiftableImm12: (operands at: 0)
+ 								ifTrue: [:shift12| ^false] ifFalse:[].
+ 							^self isImmNImmSImmREncodableBitmask: (operands at: 0)
+ 								ifTrue: [:n :imms :immr|false] ifFalse: [true]].
+ 		[MoveC32R]	-> [^true].
+ 		[MoveCwR]		-> [^(self inCurrentCompilation: (operands at: 0)) not].
+ 		[MoveAwR]		-> [^(self isAddressRelativeToVarBase: (operands at: 0)) not].
+ 		[MoveRAw]		-> [^(self isAddressRelativeToVarBase: (operands at: 1)) not].
+ 		[MoveAbR]		-> [^(self isAddressRelativeToVarBase: (operands at: 0)) not].
+ 		[MoveRAb]		-> [^(self isAddressRelativeToVarBase: (operands at: 1)) not].
+ 		[MoveMwrR]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[MoveRMwr]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[MoveMbrR]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[MoveRMbr]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[MoveM16rR]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[MoveRM16r]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|false] ifFalse:[true]].
+ 		[MoveRdM64r]	-> [^(self isUnsigned12BitMultipleOf8: (operands at: 1)) not].
+ 		[MoveM64rRd]	-> [^(self isUnsigned12BitMultipleOf8: (operands at: 0)) not].
+ 		[PushCw]		-> [^(self inCurrentCompilation: (operands at: 0)) not].
+ 		[PushCq]		-> [^((operands at: 0) between: -256 and: 255) not].
+ 		[PrefetchAw] 	-> [^(self isAddressRelativeToVarBase: (operands at: 0)) not].
+ 		}
+ 		otherwise: [self assert: false].
+ 	^false "to keep C compiler quiet"
+ !

Item was added:
+ ----- Method: CogARMv8Compiler>>wantsNearAddressFor: (in category 'simulation') -----
+ wantsNearAddressFor: anObject
+ 	"A hack hook to allow ARM to override the simulated address for the short-cut trampolines"
+ 	<doNotGenerate>
+ 	^anObject == #ceShortCutTraceLinkedSend:
+ 	 or: [anObject == #ceShortCutTraceBlockActivation:
+ 	 or: [anObject == #ceShortCutTraceStore:]]!

Item was added:
+ ----- Method: CogARMv8Compiler>>zoneCallsAreRelative (in category 'inline cacheing') -----
+ zoneCallsAreRelative
+ 	"Answer if Call and JumpLong are relative and hence need to take the caller's
+ 	 relocation delta into account during code compaction, rather than just the
+ 	 callee's delta."
+ 	^true!

Item was added:
+ CogARMv8Compiler subclass: #CogARMv8CompilerForTests
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Tests'!

Item was added:
+ ----- Method: CogARMv8CompilerForTests class>>dataRegistersWithAccessorsGiven:do: (in category 'accessing') -----
+ dataRegistersWithAccessorsGiven: aProcessorSimulator do: aTrinaryBlock
+ 	"We can't use RISCTempReg, because some opcodes may be encoded as multiple instructions using RISCTempReg."
+ 	(0 to: 31) withIndexDo:
+ 		[:reg :i|
+ 		(self isRISCTempRegister: reg) ifFalse:
+ 			[aTrinaryBlock
+ 				value: reg
+ 				value: (aProcessorSimulator registerStateGetters at: i)
+ 				value: (aProcessorSimulator registerStateSetters at: i)]]!

Item was added:
+ ----- Method: CogARMv8CompilerForTests class>>isRISCTempRegister: (in category 'testing') -----
+ isRISCTempRegister: reg
+ 	"For tests to filter-out bogus values left in the RISCTempRegister, if any."
+ 	^reg = R28!

Item was added:
+ ----- Method: CogARMv8CompilerForTests>>concretizeAt: (in category 'generating machine code') -----
+ concretizeAt: actualAddress
+ 	"Override to check maxSize and machineCodeSize"
+ 
+ 	| maxAddress nextAddress |
+ 	maxSize ifNil: [maxSize := self computeMaximumSize].
+ 	maxAddress := actualAddress + maxSize.
+ 	nextAddress := super concretizeAt: actualAddress.
+ 	self assert: (maxSize notNil
+ 				and: [self isPCDependent
+ 						ifTrue: [maxAddress >= nextAddress]
+ 						ifFalse: [maxAddress = nextAddress]]).
+ 	^nextAddress!

Item was added:
+ AbstractInstructionTests subclass: #CogARMv8CompilerTests
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Tests'!

Item was added:
+ ----- Method: CogARMv8CompilerTests>>concreteCompilerClass (in category 'accessing') -----
+ concreteCompilerClass
+ 	^CogARMv8CompilerForTests!

Item was added:
+ ----- Method: CogARMv8CompilerTests>>isaName (in category 'accessing') -----
+ isaName
+ 	^#ARMv8!

Item was added:
+ ----- Method: CogARMv8CompilerTests>>processor (in category 'accessing') -----
+ processor
+ 	processor ifNil:
+ 		[processor := GdbARMv8Alien new].
+ 	^processor!

Item was added:
+ OutOfLineLiteralsManager subclass: #OutOfLineLiteralsManagerFor64Bits
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JIT'!
+ 
+ !OutOfLineLiteralsManagerFor64Bits commentStamp: 'eem 12/17/2019 12:42' prior: 0!
+ OutOfLineLiteralsManagerFor64Bits specializes OutOfLineLiteralsManager to segregate 64-bit and 32-bit literals to achieve correct alignment and more compact code.!

Item was added:
+ ----- Method: OutOfLineLiteralsManagerFor64Bits class>>translationClasses (in category 'translation') -----
+ translationClasses
+ 	^{superclass. self}!

Item was added:
+ ----- Method: OutOfLineLiteralsManagerFor64Bits>>checkLiteral32:forInstruction: (in category 'compile abstract instructions') -----
+ checkLiteral32: literal forInstruction: anInstruction
+ 	<var: #anInstruction type: #'AbstractInstruction *'>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	anInstruction usesOutOfLineLiteral ifTrue:
+ 		[anInstruction dependent: (self locateLiteral: literal size: 4)].
+ 	^anInstruction!

Item was added:
+ ----- Method: OutOfLineLiteralsManagerFor64Bits>>checkLiteral:forInstruction: (in category 'compile abstract instructions') -----
+ checkLiteral: literal forInstruction: anInstruction
+ 	<var: #anInstruction type: #'AbstractInstruction *'>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	anInstruction usesOutOfLineLiteral ifTrue:
+ 		[anInstruction dependent: (self locateLiteral: literal size: objectMemory bytesPerOop)].
+ 	^anInstruction!

Item was added:
+ ----- Method: OutOfLineLiteralsManagerFor64Bits>>dumpLiterals: (in category 'compile abstract instructions') -----
+ dumpLiterals: generateBranchAround
+ 	"Output all pending literal instructions, making the originals dependents on the generated ones
+ 	 so that a later pass will copy the address of each generated literal inst to its original in literals,
+ 	 and hence allow the instruction using the literal to compute the correct address.
+ 
+ 	 Override to segregate 64-bit and 32-bit literals"
+ 	| jump litInst |
+ 
+ 	generateBranchAround ifTrue:
+ 		[jump := cogit Jump: 0].
+ 	"Align and dump the 64-bit literals.
+ 	 We may waste a slot here we could fill with a 32-bit literal, but for now, KISS..."
+ 	cogit backEnd literalAlignment > cogit backEnd codeGranularity ifTrue:
+ 		[cogit gen: AlignmentNops operand: cogit backEnd literalAlignment].
+ 	lastDumpedLiteralIndex to: nextLiteralIndex - 1 do:
+ 		[:i|
+ 		litInst := self literalInstructionAt: i.
+ 		litInst literalSize = 8 ifTrue:
+ 			[(cogit gen: Literal operand: (litInst operands at: 0))
+ 				dependent: litInst;
+ 				setLiteralSize: 8.
+ 			 litInst setLiteralOpcodeIndex: cogit getOpcodeIndex]].
+ 	"Now dump the 32-bit literals"
+ 	lastDumpedLiteralIndex to: nextLiteralIndex - 1 do:
+ 		[:i|
+ 		litInst := self literalInstructionAt: i.
+ 		litInst literalSize = 4 ifTrue:
+ 			[(cogit gen: Literal operand: (litInst operands at: 0))
+ 				dependent: litInst;
+ 				setLiteralSize: 4.
+ 			 litInst setLiteralOpcodeIndex: cogit getOpcodeIndex]].
+ 	generateBranchAround ifTrue:
+ 		[jump jmpTarget: cogit Label].
+ 
+ 	firstOpcodeIndex := cogit getOpcodeIndex.
+ 	lastDumpedLiteralIndex := nextLiteralIndex!

Item was added:
+ ----- Method: OutOfLineLiteralsManagerFor64Bits>>locateLiteral: (in category 'compile abstract instructions') -----
+ locateLiteral: aLiteral
+ 	self shouldNotImplement!

Item was added:
+ ----- Method: OutOfLineLiteralsManagerFor64Bits>>locateLiteral:size: (in category 'compile abstract instructions') -----
+ locateLiteral: aLiteral size: litSize
+ 	"Search for a Literal instruction that is in-range and answer it.  Otherwise
+ 	 allocate a new sharable Literal instruction for the literal and answer it."
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	<inline: false>
+ 	| litInst |
+ 	<var: 'litInst' type: #'AbstractInstruction *'>
+ 	0 to: nextLiteralIndex - 1 do:
+ 		[:i|
+ 		litInst := self literalInstructionAt: i.
+ 		(litInst literalSize = litSize
+ 		 and: [(litInst operands at: 0) = aLiteral
+ 		 and: [litInst isSharable
+ 		 and: [self literalInstructionInRange: litInst]]]) ifTrue:
+ 			[^litInst]].
+ 	nextLiteralIndex >= literalsSize ifTrue:
+ 		[self allocateLiterals: literalsSize + 8].
+ 	litInst := self literalInstructionAt: nextLiteralIndex.
+ 	litInst
+ 		initializeSharableLiteral: aLiteral;
+ 		setLiteralSize: litSize.
+ 	nextLiteralIndex := nextLiteralIndex + 1.
+ 	"Record the opcodeIndex of the first dependent instruction (the first instruction that references an out-of-line literal)"
+ 	firstOpcodeIndex > cogit getOpcodeIndex ifTrue:
+ 		[firstOpcodeIndex := cogit getOpcodeIndex - 1].
+ 	^litInst!



More information about the Vm-dev mailing list