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

commits at source.squeak.org commits at source.squeak.org
Mon Dec 9 05:04:56 UTC 2019


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

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

Name: VMMaker.oscog-eem.2610
Author: eem
Time: 8 December 2019, 9:04:37.440523 pm
UUID: fc46f0b9-0842-4d46-88b0-98097a972574
Ancestors: VMMaker.oscog-eem.2609

A64 several parts of the ABI-compliant call glue filled out.

Eliminate duplication in genLoadCStackPointers, genSaveStackPointers, genSaveRegs:.  These can all be implemented in CogAbstractInstruction.

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

Item was removed:
- ----- Method: CogARMCompiler>>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)."
- 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
- 	cogit MoveAw: cogit cFramePointerAddress R: FPReg.
- 	^0!

Item was changed:
  ----- Method: CogARMCompiler>>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:
- 		numArgs > 0 ifTrue:
  			[cogit PushR: Arg0Reg.
  			 numArgs > 1 ifTrue:
  				[cogit PushR: Arg1Reg]]]!

Item was removed:
- ----- Method: CogARMCompiler>>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."
- 	cogit MoveR: FPReg Aw: cogit framePointerAddress.
- 	cogit MoveR: SPReg Aw: cogit stackPointerAddress.
- 	^0!

Item was changed:
  CogAbstractInstruction subclass: #CogARMv8Compiler
  	instanceVariableNames: ''
+ 	classVariableNames: 'AL AddOpcode AndOpcode CArg0Reg CArg1Reg CArg2Reg CArg3Reg 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 XZR XorOpcode'
- 	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 XZR XorOpcode'
  	poolDictionaries: 'ARMv8A64Opcodes'
  	category: 'VMMaker-JIT'!
  
  !CogARMv8Compiler commentStamp: 'eem 12/3/2019 08:45' 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.!

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]].
  
  	SP := XZR := R31.
  	LR := R30.
  	FP := R29.
  
+ 	CArg0Reg := R0.
+ 	CArg1Reg := R1.
+ 	CArg2Reg := R2.
+ 	CArg3Reg := R3.
+ 
  	"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!

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>>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>>genSaveRegs: (in category 'abi') -----
+ genSaveRegs: regMask
+ 	"Save the registers in regMask for a call into the C run-time from a trampoline."
+ 	R17 to: R0 by: -1 do:
+ 		[:reg|
+ 		 (regMask anyMask: (cogit registerMaskFor: reg)) ifTrue:
+ 			[cogit PushR: reg]].
+ 	^0!

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 changed:
  ----- 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 isPossiblyShiftableImm12: (operands at: 0) 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]].
  		[CmpCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
  		[OrCqR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
  		[SubCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|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].
  		[OrCwR]		-> [^true].
  		[SubCwR]		-> [^true].
  		[XorCwR]		-> [^true].
  		"[LoadEffectiveAddressMwrR]
  						-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]]."
  		"Data Movement"						
+ 		[MoveCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
- 		"[MoveCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [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 is12BitValue: (operands at: 1) ifTrue: [:u :i| false] ifFalse: [true]].
  		[MoveM64rRd]	-> [^self is12BitValue: (operands at: 0) ifTrue: [:u :i| false] ifFalse: [true]]."
  		[PushCw]		-> [^(self inCurrentCompilation: (operands at: 0)) not].
  		"[PushCq]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]]."
  		[PrefetchAw] 	-> [^(self isAddressRelativeToVarBase: (operands at: 0)) not].
  		}
  		otherwise: [self assert: false].
  	^false "to keep C compiler quiet"
  !

Item was changed:
  ----- Method: CogAbstractInstruction>>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)."
+ 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
+ 	cogit MoveAw: cogit cFramePointerAddress R: FPReg.
+ 	^0!
- 	self subclassResponsibility!

Item was added:
+ ----- Method: CogAbstractInstruction>>genSaveRegs: (in category 'abi') -----
+ genSaveRegs: regMask
+ 	"Save the registers in regMask for a call into the C run-time from a trampoline"
+ 	self subclassResponsibility!

Item was changed:
  ----- Method: CogAbstractInstruction>>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."
+ 	cogit MoveR: FPReg Aw: cogit framePointerAddress.
+ 	cogit MoveR: SPReg Aw: cogit stackPointerAddress.
+ 	^0!
- 	self subclassResponsibility!

Item was removed:
- ----- Method: CogIA32Compiler>>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)."
- 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
- 	cogit MoveAw: cogit cFramePointerAddress R: FPReg.
- 	^0!

Item was removed:
- ----- Method: CogIA32Compiler>>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."
- 	cogit MoveR: FPReg Aw: cogit framePointerAddress.
- 	cogit MoveR: SPReg Aw: cogit stackPointerAddress.
- 	^0!

Item was removed:
- ----- Method: CogMIPSELCompiler>>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)."
- 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
- 	cogit MoveAw: cogit cFramePointerAddress R: FPReg.
- 	^0!

Item was removed:
- ----- Method: CogMIPSELCompiler>>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."
- 	cogit MoveR: FPReg Aw: cogit framePointerAddress.
- 	cogit MoveR: SPReg Aw: cogit stackPointerAddress.
- 	^0!

Item was removed:
- ----- Method: CogX64Compiler>>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)."
- 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
- 	cogit MoveAw: cogit cFramePointerAddress R: FPReg.
- 	^0!

Item was removed:
- ----- Method: CogX64Compiler>>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."
- 	cogit MoveR: FPReg Aw: cogit framePointerAddress.
- 	cogit MoveR: SPReg Aw: cogit stackPointerAddress.
- 	^0!



More information about the Vm-dev mailing list