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

commits at source.squeak.org commits at source.squeak.org
Tue Dec 3 17:40:43 UTC 2019


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

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

Name: VMMaker.oscog-eem.2601
Author: eem
Time: 3 December 2019, 9:40:27.524843 am
UUID: 16ee0b79-1d3a-4ee9-9de4-89d2da8176cd
Ancestors: VMMaker.oscog-eem.2600

More work for CogARMv8Compiler.  Add concretizeCmpCqR & concretizeMoveMwrR.  Fix pc-relative louteral loading in moveCw:intoR:. Now four instructions into generating ceDereferenceSelectorIndex.

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

Item was changed:
  CogAbstractInstruction subclass: #CogARMv8Compiler
  	instanceVariableNames: ''
  	classVariableNames: 'AL AddOpcode AndOpcode CC CS CmpOpcode 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 EQ FP GE GT HI LE LR LS LT MI NE OrOpcode 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 SP SXTB SXTH SXTW SXTX SubOpcode UXTB UXTH UXTW UXTX VC VS XorOpcode'
  	poolDictionaries: 'ARMv8A64Opcodes'
  	category: 'VMMaker-JIT'!
  
+ !CogARMv8Compiler commentStamp: 'eem 12/3/2019 08:45' prior: 0!
- !CogARMv8Compiler commentStamp: 'eem 11/25/2019 16:30' 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.!
- https://developer.arm.com/docs/ddi0487/latest/arm-architecture-reference-manual-armv8-for-armv8-a-architecture-profile!

Item was changed:
  ----- 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 bytecode compiler's long branch
  	 limits which are exceeded when each case jumps around the otherwise."
  
  	opcode
  		caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]						-> [^0].
  		[Literal]						-> [^8].
  		[AlignmentNops]			-> [^(operands at: 0) - 4].
  		[Fill32]						-> [^4].
  		[Nop]						-> [^4].
  		"Control"
  		[Call]						-> [^4].
  		[CallFull]					-> [^8].
  		[JumpR]					-> [^4].
  		[Jump]						-> [^4].
  		[JumpFull]					-> [^8].
  		[JumpLong]				-> [^4].
  		[JumpZero]					-> [^4].
  		[JumpNonZero]				-> [^4].
  		[JumpNegative]				-> [^4].
  		[JumpNonNegative]			-> [^4].
  		[JumpOverflow]				-> [^4].
  		[JumpNoOverflow]			-> [^4].
  		[JumpCarry]				-> [^4].
  		[JumpNoCarry]				-> [^4].
  		[JumpLess]					-> [^4].
  		[JumpGreaterOrEqual]		-> [^4].
  		[JumpGreater]				-> [^4].
  		[JumpLessOrEqual]			-> [^4].
  		[JumpBelow]				-> [^4].
  		[JumpAboveOrEqual]		-> [^4].
  		[JumpAbove]				-> [^4].
  		[JumpBelowOrEqual]		-> [^4].
  		[JumpLongZero]			-> [^4].
  		[JumpLongNonZero]		-> [^4].
  		[JumpFPEqual]				-> [^8].
  		[JumpFPNotEqual]			-> [^8].
  		[JumpFPLess]				-> [^8].
  		[JumpFPGreaterOrEqual]	-> [^8].
  		[JumpFPGreater]			-> [^8].
  		[JumpFPLessOrEqual]		-> [^8].
  		[JumpFPOrdered]			-> [^8].
  		[JumpFPUnordered]		-> [^8].
  		[RetN]						-> [^(operands at: 0) = 0 ifTrue: [4] ifFalse: [8]].
  		[Stop]						-> [^4].
  
  		"Arithmetic"
  		[AddCqR]					-> [^8].
  		[AndCqR]					-> [^8].
  		[AndCqRR]					-> [^8].
  		[CmpCqR]					-> [^8].
  		[OrCqR]					-> [^8].
  		[SubCqR]					-> [^8].
  		[TstCqR]					-> [^8].
  		[XorCqR]					-> [^8].
  		[AddCwR]					-> [^8].
  		[AndCwR]					-> [^8].
  		[CmpCwR]					-> [^8].
  		[OrCwR]					-> [^8].
  		[SubCwR]					-> [^8].
  		[XorCwR]					-> [^8].
  		[AddRR]					-> [^4].
  		[AndRR]					-> [^4].
  		[CmpRR]					-> [^4].
  		[OrRR]						-> [^4].
  		[XorRR]						-> [^4].
  		[SubRR]					-> [^4].
  		[NegateR]					-> [^4].
  		[LoadEffectiveAddressMwrR]-> [^8 halt]. "I think this is likely 4"
  
  		[LogicalShiftLeftCqR]		-> [^4].
  		[LogicalShiftRightCqR]		-> [^4].
  		[ArithmeticShiftRightCqR]	-> [^4].
  		[LogicalShiftLeftRR]			-> [^4].
  		[LogicalShiftRightRR]		-> [^4].
  		[ArithmeticShiftRightRR]	-> [^4].
  		[AddRdRd]					-> [^4].
  		[CmpRdRd]					-> [^4].
  		[SubRdRd]					-> [^4].
  		[MulRdRd]					-> [^4].
  		[DivRdRd]					-> [^4].
  		[SqrtRd]					-> [^4].
  		[ClzRR]						-> [^4].
  		"Data Movement"						
  		[MoveCqR]				-> [^4].
  		[MoveCwR]				-> [^4].
  		[MoveRR]				-> [^4].
  		[MoveRdRd]			-> [^4].
+ 		[MoveAwR]				-> [^((operands at: 1) ~= SP
+ 										and: [(self isAddressRelativeToVarBase: (operands at: 0))
+ 											   or: [cogit addressIsInCurrentCompilation: (operands at: 0)]])
+ 											ifTrue: [4]
+ 											ifFalse: [8]].
- 		[MoveAwR]				-> [^((self isAddressRelativeToVarBase: (operands at: 0))
- 										and: [(operands at: 1) ~= SP])
- 													ifTrue: [4]
- 													ifFalse: [8]].
  		[MoveRAw]				-> [^((self isAddressRelativeToVarBase: (operands at: 1))
  										and: [(operands at: 0) ~= SP])
+ 											ifTrue: [4]
+ 											ifFalse: [8]].
- 													ifTrue: [4]
- 													ifFalse: [8]].
  		[MoveAbR]				-> [^(self isAddressRelativeToVarBase: (operands at: 0))
+ 											ifTrue: [4]
+ 											ifFalse: [8]].
- 													ifTrue: [4]
- 													ifFalse: [8]].
  		[MoveRAb]				-> [^(self isAddressRelativeToVarBase: (operands at: 1))
+ 											ifTrue: [4]
+ 											ifFalse: [8]].
- 													ifTrue: [4]
- 													ifFalse: [8]].
  		[MoveMwrR]			-> [^self isPossiblyShiftableImm12: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
  		[MoveRMwr]			-> [^self isPossiblyShiftableImm12: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
  		[MoveMbrR]			-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|4] ifFalse:[8]].
  		[MoveRMbr]			-> [^self isPossiblyShiftableImm12: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
  		[MoveM16rR]			-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|4] ifFalse:[8]].
  		[MoveRM16r]			-> [^self isPossiblyShiftableImm12: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
  		[MoveM64rRd]			-> [^8].
  		[MoveRdM64r]			-> [^8].
  		[MoveXbrRR]			-> [^4].
  		[MoveRXbrR]			-> [^4].
  		[MoveXwrRR]			-> [^4].
  		[MoveRXwrR]			-> [^4].
  		[PopR]					-> [^4].
  		[PushR]					-> [^4].
  		[PushCw]				-> [self halt].
  		[PushCq]				-> [self halt].
  		[PrefetchAw] 			-> [self halt].
  		"Conversion"
  		[ConvertRRd]			-> [^8].
  		}.
  	^0 "to keep C compiler quiet"
  !

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCmpCqR (in category 'generate machine code - concretize') -----
+ concretizeCmpCqR
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| constant rn offset |
+ 	constant := operands at: 0.
+ 	rn := operands at: 1.
+ 
+ 	self is6BitSignedImmediate: constant 
+ 		ifTrue:
+ 			[:immediate : negate|
+ 			"C6.2.46	CCMN (immediate)	C6-833
+ 			 C6.2.48	CCMP (immediate)	C6-837"
+ 			machineCode
+ 				at: 0
+ 				put: 2r11111010010000000000100000001111
+ 					+ (AL << 12)
+ 					+ (negate ifTrue: [1 << 30] ifFalse: [0])
+ 					+ (immediate << 16)
+ 					+ (rn << 5).
+ 			^machineCodeSize := 4]
+ 		ifFalse: [].
+ 	offset := self moveCw: constant intoR: RISCTempReg.
+ 	"C6.2.49	CCMP (register)	C6-839"
+ 	machineCode
+ 				at: offset // 4
+ 				put: 2r11111010010000000000000000001111
+ 					+ (AL << 12)
+ 					+ (RISCTempReg << 16)
+ 					+ (rn << 5).
+ 	^machineCodeSize := offset + 4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveMwrR (in category 'generate machine code - concretize') -----
+ concretizeMoveMwrR
+ 	<inline: true>
+ 	| srcReg offset destReg |
+ 	<var: #offset type: #sqInt>
+ 	offset := operands at: 0.
+ 	srcReg := operands at: 1.
+ 	destReg := operands at: 2.
+ 	machineCode
+ 		at: 0
+ 		put: (self ldrn: srcReg rt: destReg imm: offset shiftBy12: false).
+ 	^machineCodeSize := 4!

Item was changed:
  ----- 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."
  	<returnTypeC: #void>
  		 
  	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 concretizeCallFull]. "call code anywhere in address space"
  		[JumpR]					-> [^self concretizeJumpR].
  		[JumpFull]					-> [^self concretizeJumpFull]."jump within address space"
  		[JumpLong]				-> [^self concretizeConditionalJump: AL]."jumps witihn code space"
  		[JumpLongZero]			-> [^self concretizeConditionalJump: EQ].
  		[JumpLongNonZero]		-> [^self concretizeConditionalJump: NE].
  		[Jump]						-> [^self concretizeConditionalJump: AL].
  		[JumpZero]					-> [^self concretizeConditionalJump: EQ].
  		[JumpNonZero]				-> [^self concretizeConditionalJump: NE].
  		[JumpNegative]				-> [^self concretizeConditionalJump: MI].
  		[JumpNonNegative]			-> [^self concretizeConditionalJump: PL].
  		[JumpOverflow]				-> [^self concretizeConditionalJump: VS].
  		[JumpNoOverflow]			-> [^self concretizeConditionalJump: VC].
  		[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 concretizeFPConditionalJump: EQ].
  		[JumpFPNotEqual]			-> [^self concretizeFPConditionalJump: NE].
  		[JumpFPLess]				-> [^self concretizeFPConditionalJump: LT].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeFPConditionalJump: GE].
  		[JumpFPGreater]			-> [^self concretizeFPConditionalJump: GT].
  		[JumpFPLessOrEqual]		-> [^self concretizeFPConditionalJump: LE].
  		[JumpFPOrdered]			-> [^self concretizeFPConditionalJump: VC].
  		[JumpFPUnordered]		-> [^self concretizeFPConditionalJump: VS].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]						-> [^self concretizeNegateableDataOperationCqR: AddOpcode].
  		[AndCqR]						-> [^self concretizeInvertibleDataOperationCqR: AndOpcode].
  		[AndCqRR]						-> [^self concretizeAndCqRR].
+ 		[CmpCqR]						-> [^self concretizeCmpCqR].
- 		[CmpCqR]						-> [^self concretizeNegateableDataOperationCqR: CmpOpcode].
  		[OrCqR]						-> [^self concretizeDataOperationCqR: OrOpcode].
  		[SubCqR]						-> [^self concretizeSubCqR].
  		[TstCqR]						-> [^self concretizeTstCqR].
  		[XorCqR]						-> [^self concretizeInvertibleDataOperationCqR: XorOpcode].
  		[AddCwR]						-> [^self concretizeDataOperationCwR: AddOpcode].
  		[AndCwR]						-> [^self concretizeDataOperationCwR: AndOpcode].
  		[CmpCwR]						-> [^self concretizeDataOperationCwR: CmpOpcode].
  		[OrCwR]						-> [^self concretizeDataOperationCwR: OrOpcode].
  		[SubCwR]						-> [^self concretizeDataOperationCwR: SubOpcode].
  		[XorCwR]						-> [^self concretizeDataOperationCwR: XorOpcode].
  		[AddRR]						-> [^self concretizeDataOperationRR: AddOpcode].
  		[AndRR]						-> [^self concretizeDataOperationRR: AndOpcode].
  		[CmpRR]						-> [^self concretizeDataOperationRR: CmpOpcode].
  		[OrRR]							-> [^self concretizeDataOperationRR: OrOpcode].
  		[SubRR]						-> [^self concretizeDataOperationRR: SubOpcode].
  		[XorRR]							-> [^self concretizeDataOperationRR: XorOpcode].
  		[AddRdRd]						-> [^self concretizeAddRdRd].
  		[CmpRdRd]						-> [^self concretizeCmpRdRd].
  		[DivRdRd]						-> [^self concretizeDivRdRd].
  		[MulRdRd]						-> [^self concretizeMulRdRd].
  		[SubRdRd]						-> [^self concretizeSubRdRd].
  		[SqrtRd]						-> [^self concretizeSqrtRd].
  		[NegateR]						-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]		-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		[LogicalShiftRightRR]			-> [^self concretizeLogicalShiftRightRR].
  		[ClzRR]							-> [^self concretizeClzRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeMoveRR].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveAbR] 			-> [^self concretizeMoveAbR].
   		[MoveRAb]			-> [^self concretizeMoveRAb].
  		[MoveMbrR]		-> [^self concretizeMoveMbrR].
  		[MoveRMbr]		-> [^self concretizeMoveRMbr].
  		[MoveRM16r]		-> [^self concretizeMoveRM16r].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd].
  		[ConvertRdR]		-> [^self concretizeConvertRdR].
  		[ConvertRRs]		-> [^self concretizeConvertRRs].
  		[ConvertRsR]		-> [^self concretizeConvertRsR].
  		[ConvertRsRd]		-> [^self concretizeConvertRsRd].
  		[ConvertRdRs]		-> [^self concretizeConvertRdRs].
  			
  		[SignExtend8RR]	-> [^self concretizeSignExtend8RR].
  		[SignExtend16RR]	-> [^self concretizeSignExtend16RR].
  		[SignExtend32RR]	-> [^self concretizeSignExtend32RR].
  		
  		[ZeroExtend8RR]	-> [^self concretizeZeroExtend8RR].
  		[ZeroExtend16RR]	-> [^self concretizeZeroExtend16RR].
  		[ZeroExtend32RR]	-> [^self concretizeZeroExtend32RR].}!

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>>ldrn:rt:imm:shiftBy12: (in category 'generate machine code - support') -----
+ ldrn: srcReg rt: targetReg imm: offset shiftBy12: shiftBy12
+ 	"C6.2.130	LDR (immediate)	C6-976
+ 	 C6.2.166	LDUR				C6-1058"
+ 
+ 	self deny: srcReg = targetReg.
+ 	"Unsigned offset, C6-1058"
+ 	(offset \\ 8 = 0
+ 	 and: [offset / 8 between: 0 and: 1 << 12 - 1]) ifTrue:
+ 		[^2r1111100101 << 22
+ 		+ (offset << 7 "10 - 3")
+ 		+ (srcReg << 5)
+ 		+ targetReg].
+ 	self assert: (offset between: -256 and: 255).
+ 	"Signed 9-bit offset, C6-976"
+ 	^2r11111000010000000000110000000000
+ 	  + ((offset bitAnd: 511) << 12)
+ 		+ (srcReg << 5)
+ 		+ targetReg!

Item was changed:
  ----- Method: CogARMv8Compiler>>moveCw:intoR: (in category 'generate machine code - support') -----
  moveCw: constant intoR: destReg
+ 	"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."
- 	"Emit a load of aWord into destReg.  Answer the number of bytes of machine code generated.
- 	 Literals are stored out-of-line; emit a LDR with the relevant offset."
  	 <var: 'constant' type: #usqInt>
  	<inline: true>
+ 	self deny: destReg = SP.
  	self assert: (cogit addressIsInCurrentCompilation: dependent address).
+ 	self assert: dependent address \\ 4 = 0.
+ 	self assert: (dependent address - address) abs < (1<<18).
- 	self assert: (dependent address bitAnd: 3) = 0.
- 	self assert: (dependent address - address) abs < (1<<19).
  	"C6.2.131	LDR (literal)		C6-979"
  	machineCode
  		at: 0
+ 		put: 2r01011 << 27
+ 			+ (dependent address - address << 3 "5 - 2")
+ 			+ destReg.
- 		put: 2r01011000 << 24
- 			+ destReg
- 			+ ((dependent address - (address + 8) bitAnd: 1 << 19 - 1) << 5).
  	^machineCodeSize := 4!

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 changed:
  ----- Method: CogARMv8Compiler>>strn:rt:imm:shiftBy12: (in category 'generate machine code - support') -----
  strn: srcReg rt: targetReg imm: offset shiftBy12: shiftBy12
  	"C6.2.273	STR (immediate)	C6-1239
  	 C6.2.297	STUR				C6-1290"
  
  	self deny: srcReg = SP.
+ 	self deny: srcReg = targetReg.
  	"Unsigned offset, C6-1240"
  	(offset \\ 8 = 0
  	 and: [offset / 8 between: 0 and: 1 << 12 - 1]) ifTrue:
  		[^2r1111100100 << 22
  		+ (offset << 7 "10 - 3")
  		+ (targetReg << 5)
  		+ srcReg].
  	self assert: (offset between: -256 and: 255).
  	^2r11111000000 << 21
  	  + ((offset bitAnd: 511) << 12)
  	  + (targetReg << 5)
  	  + srcReg!

Item was changed:
+ ----- Method: CogOutOfLineLiteralsARMCompiler>>outOfLineLiteralOpcodeLimit (in category 'generate machine code') -----
- ----- Method: CogOutOfLineLiteralsARMCompiler>>outOfLineLiteralOpcodeLimit (in category 'compile abstract instructions') -----
  outOfLineLiteralOpcodeLimit
  	"The maximum offset in a LDR is (1<<12)-1, or (1<<10)-1 instructions.
  	 Be conservative.  The issue is that one abstract instruction can emit
  	 multiple hardware instructions so we assume a 2 to 1 worst case of
  	 hardware instructions to abstract opcodes.."
  	^1 << (12 "12-bit offset field"
  			- 2 "4 bytes per literal"
  			- 1 "2 hardware instructions to 1 abstract opcode") - 1!



More information about the Vm-dev mailing list