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

commits at source.squeak.org commits at source.squeak.org
Mon Dec 2 05:39:57 UTC 2019


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

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

Name: VMMaker.oscog-eem.2599
Author: eem
Time: 1 December 2019, 9:39:41.329223 pm
UUID: 4857615d-4183-4b1c-bdb9-6c710c344702
Ancestors: VMMaker.oscog-eem.2598

More work for CogARMv8Compiler.  Add register assignments.  Add concretizeMoveRR & concretizeRetN.  Hence the first run-time routine is now generated.

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

Item was changed:
  ----- Method: CogARMCompiler>>initialize (in category 'generate machine code') -----
  initialize
  	"This method intializes the Smalltalk instance.  The C instance is merely a struct and doesn't need initialization."
  	<doNotGenerate>
  	operands := CArrayAccessor on: (Array new: NumOperands).
+ 	machineCode := CArrayAccessor on: (WordArray new: self machineCodeWords)!
- 	machineCode := CArrayAccessor on: (Array new: self machineCodeWords)!

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'
- 	classVariableNames: 'AL CC CS 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 GE GT HI LE LS LT MI NE 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 VC VS'
  	poolDictionaries: 'ARMv8A64Opcodes'
  	category: 'VMMaker-JIT'!
  
  !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!

Item was changed:
  ----- 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 R31 (named XZR in ARM doc) 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 either the PC or SP; a big difference. See ARMARM DDI0487 C1.2.5. wrt to both issues.
  	
  	We will 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"
  	#(	(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)
  		(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)) do:
  		[:classVarNames|
  		 classVarNames doWithIndex:
  			[:k :v|
  			CogARMv8Compiler classPool at: k put: v - 1]].
  	
  	"Condition Codes. Note that cc=16rF is mapped back to AL in AARCH64. Generally it shouldn't be used"
  	"Perhaps have these in the ARMv8A64Opcodes pool?"
  	EQ := 0.
  	NE := 1.
  	CS := 2.
  	CC := 3.
  	MI := 4.
  	PL := 5.
  	VS := 6.
  	VC := 7.
  	HI := 8.
  	LS := 9.
  	GE := 10.
  	LT := 11.
  	GT := 12.
  	LE := 13.
+ 	AL := 14.
+ 
+ 	"Extension Methods "
+ 	UXTB := 2r000.
+ 	UXTH := 2r001.
+ 	UXTW := 2r010.
+ 	UXTX := 2r011.	"a.k.a. LSL"
+ 	SXTB := 2r100.
+ 	SXTH := 2r101.
+ 	SXTW := 2r110.
+ 	SXTX := 2r111!
- 	AL := 14.!

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."
+ 
+ 	super initializeAbstractRegisters.
+ 
+ 	"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
+ 	"
+ 
+ 	CallerSavedRegisterMask := (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).
+ 
+ 	TempReg			:= R0.
+ 	ClassReg			:= R4.
+ 	ReceiverResultReg	:= R5.
+ 	SendNumArgsReg	:= R6.
+ 	Arg0Reg			:= R7.
+ 	Arg1Reg			:= R8.
+ 						"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.
+ 	VarBaseReg			:= R27.	
+ 	RISCTempReg		:= R28.	
+ 	FPReg		:= FP	:= R29.
+ 	LinkReg	:= LR	:= R30.
+ 	SPReg		:= SP	:= R31.
+ 
+ 	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 changed:
  ----- Method: CogARMv8Compiler class>>machineCodeDeclaration (in category 'translation') -----
  machineCodeDeclaration
  	"Answer the declaration for the machineCode array.
+ 	 ARM instructions are 32-bits in length."
- 	 AARCH64 instructions are 32-bits in length."
  	^{#'unsigned int'. '[', self basicNew machineCodeWords printString, ']'}!

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>>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:  [2r10010001000000000000000000000000 + (srcReg << 5) + destReg]
+ 				ifFalse: [2r10101010000000000000001111100000 + (srcReg << 16) + destReg]).
+ 	^machineCodeSize := 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: 2r11010110010111110000000000000000 + (LR << 5).
+ 		^machineCodeSize := 4].
+ 
+ 	"C6.2.4 ADD (immediate) p761"
+ 	machineCode
+ 		at: 0 put: (self addrn: SP rd: SP imm: offset shiftBy12: false);
+ 		at: 4 put: 2r11010110010111110000000000000000 + (LR << 5).
+ 	^machineCodeSize := 8!

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."
+ 	<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 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>>initialize (in category 'generate machine code') -----
+ initialize
+ 	"This method intializes the Smalltalk instance.  The C instance is merely a struct and doesn't need initialization."
+ 	<doNotGenerate>
+ 	operands := CArrayAccessor on: (Array new: NumOperands).
+ 	machineCode := CArrayAccessor on: (WordArray new: self machineCodeWords)!

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  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 changed:
  ----- Method: CogARMv8Compiler>>machineCodeBytes (in category 'generate machine code') -----
  machineCodeBytes
  	"Answer the maximum number of bytes of machine code generated for any abstract instruction.
- 	 e.g. CmpCwR =>
- 			mov R3, #<addressByte1>, 12
- 			orr R3, R3, #<addressByte2>, 8
- 			orr R3, R3, #<addressByte3>, 4
- 			orr R3, R3, #<addressByte4>, 0
- 			cmp R?, R3
  	Likely to be quite different for AARCH64"
+ 	^12!
- 	^20!

Item was changed:
  ----- Method: CogARMv8Compiler>>machineCodeWords (in category 'generate machine code') -----
  machineCodeWords
  	"Answer the maximum number of words of machine code generated for any abstract instruction.
- 	 e.g. CmpCwR =>
- 			mov R3, #<addressByte1>, 12
- 			orr R3, R3, #<addressByte2>, 8
- 			orr R3, R3, #<addressByte3>, 4
- 			orr R3, R3, #<addressByte4>, 0
- 			cmp R?, R3
  	Likely to be quite different for AARCH64"
+ 	^self machineCodeBytes // 4!
- 	^self machineCodeBytes// 4!

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|
+ 		objectMemory long32At: targetAddress + j put: (machineCode at: j // 4)]!

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



More information about the Vm-dev mailing list