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

commits at source.squeak.org commits at source.squeak.org
Sun Nov 24 15:49:40 UTC 2019


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

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

Name: VMMaker.oscog-eem.2590
Author: eem
Time: 24 November 2019, 7:49:27.903788 am
UUID: f58fa0fe-e844-47b7-9889-0db0484adc5d
Ancestors: VMMaker.oscog-eem.2589

Add the compiler for the ARMv8 A64 backend.

Correct a typo.  Add Integer>>binary as a convenience.

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

Item was added:
+ CogAbstractInstruction subclass: #CogARMv8Compiler
+ 	instanceVariableNames: ''
+ 	classVariableNames: '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 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'
+ 	poolDictionaries: 'ARMv8A64Opcodes'
+ 	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: CogARMv8Compiler class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"self initialize"
+ 
+ 	#(	(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]]!

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

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 changed:
  ----- Method: CogRTLOpcodes class>>initialize (in category 'class initialization') -----
  initialize
  	"Abstract opcodes are a compound of a one word operation specifier and zero or more operand type specifiers.
  	 The assembler is in Cogit protocol abstract instructions and uses `at&t' syntax, assigning to the register on the
  	 right. e.g. MoveRR is the Move opcode with two register operand specifiers and defines a move register to
  	 register instruction from operand 0 to operand 1.  The word and register size is assumed to be either 32-bits
  	 on a 32-bit architecture or 64-bits on a 64-bit architecture.  The abstract machine is mostly a 2 address machine
  	 with the odd three address instruction added to better exploit RISCs.
  			(self initialize)
  	The operand specifiers are
  		R		- general purpose register
  		Rs		- single-precision floating-point register
  		Rd		- double-precision floating-point register
  		Cq		- a `quick' constant that can be encoded in the minimum space possible.
  		Cw		- a constant with word size where word is the default operand size for the Smalltalk VM, 32-bits
  				  for a 32-bit VM, 64-bits for a 64-bit VM.  The generated constant must occupy the default number
  				  of bits.  This allows e.g. a garbage collector to update the value without invalidating the code.
  		C32	- a constant with 32 bit size.  The generated constant must occupy 32 bits.
  		C64	- a constant with 64 bit size.  The generated constant must occupy 64 bits.
  		Aw		- memory word (32-bits for a 32-bit VM, 64-bits for a 64-bit VM) at an absolute address
  				  See note about MoveAwR and MoveRAw in the opcodeNames literal array below!!!!
  		Ab		- memory byte at an absolute address
  		A32	- memory 32-bit halfword at an absolute address
  		Mwr	- memory word whose address is at a constant offset from an address in a register
  		Mbr		- memory byte whose address is at a constant offset from an address in a register (zero-extended on read)
  		M16r	- memory 16-bit halfword whose address is at a constant offset from an address in a register
  		M32r	- memory 32-bit halfword whose address is at a constant offset from an address in a register
  		M64r	- memory 64-bit doubleword whose address is at a constant offset from an address in a register
  		Xbr		- memory byte whose address is r * byte size away from an address in a register
  		X16r	- memory 16-bit halfword whose address is r * (2 bytes size) away from an address in a register
  		X32r	- memory 32-bit halfword whose address is r * (4 bytes size) away from an address in a register (64-bit ISAs only)
  		Xwr		- memory word whose address is r * word size away from an address in a register
  		Xowr	- memory word whose address is o + (r * word size) away from an address in a register (scaled indexed)
  
  	An alternative would be to decouple opcodes from operands, e.g.
  		Move := 1. Add := 2. Sub := 3...
  		RegisterOperand := 1. ConstantQuickOperand := 2. ConstantWordOperand := 3...
  	But not all combinations make sense and even fewer are used so we stick with the simple compound approach.
  
  	The assumption is that comparison and arithmetic instructions set condition codes and that move instructions
  	leave the condition codes unaffected.  In particular LoadEffectiveAddressMwrR does not set condition codes
  	although it can be used to do arithmetic.  On processors such as MIPS this distinction is invalid; there are no
  	condition codes.  So the backend is allowed to collapse operation, branch pairs to internal instruction definitions
  	(see senders and implementors of noteFollowingConditionalBranch:). 
  
  	Not all of the definitions in opcodeDefinitions below are implemented.  In particular we do not implement the
  	XowrR scaled index addressing mode since it requires 4 operands.
  
+ 	Not all instructions make sense on all architectures.  MoveRRd and MoveRdR are meaningful only on 64-bit machines.
- 	Not all instructions make sense on all architectures.  MoveRRd and MoveRdR aqre meaningful only on 64-bit machines.
  
  	Note that there are no generic division instructions defined, but a processor may define some.
  
  	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.  CallFull/JumpFull are allowed
  	to use the cResultRegister as a scratch if required (e.g. on x64 where there is no direct 64-bit call or jump).
  
  	Byte reads.  If the concrete compiler class answers true to byteReadsZeroExtend then byte reads must zero-extend
  	the byte read into the destination register.  If not, the other bits of the register should be left undisturbed and the
  	Cogit will add an instruction to zero the register as required.  Under no circumstances should byte reads sign-extend.
  
  	16-bit (and on 64-bits, 32-bit) reads.  These /are/ expected to always zero-extend."
  
  	| opcodeNames refs |
  	opcodeNames := #("Noops & Pseudo Ops"
  						Label
  						Literal			"a word-sized literal"
  						AlignmentNops
  						Fill32			"output four byte's worth of bytes with operand 0"
  						Nop
  
  						"Control"
  						Call					"call within the code zone"
  						CallFull				"call anywhere within the full address space"
  						CallR
  						RetN
  						JumpR				"Not a regular jump, i.e. not pc dependent."
  						Stop				"Halt the processor"
  
  						"N.B.  Jumps are contiguous.  Long and Full jumps are contiguous within them.  See FirstJump et al below"
  						JumpFull			"Jump anywhere within the address space"
  						JumpLong			"Jump anywhere within the 16mb code zone."
  						JumpLongZero			"a.k.a. JumpLongEqual"
  						JumpLongNonZero		"a.k.a. JumpLongNotEqual"
  						Jump				"short jumps; can be encoded in as few bytes as possible; will not be disturbed by GC or relocation."
  						JumpZero				"a.k.a. JumpEqual"
  						JumpNonZero			"a.k.a. JumpNotEqual"
  						JumpNegative
  						JumpNonNegative
  						JumpOverflow
  						JumpNoOverflow
  						JumpCarry
  						JumpNoCarry
  						JumpLess			"signed"
  						JumpGreaterOrEqual
  						JumpGreater
  						JumpLessOrEqual
  						JumpBelow			"unsigned"
  						JumpAboveOrEqual
  						JumpAbove
  						JumpBelowOrEqual
  
  						JumpFPEqual
  						JumpFPNotEqual
  						JumpFPLess
  						JumpFPLessOrEqual
  						JumpFPGreater
  						JumpFPGreaterOrEqual
  						JumpFPOrdered
  						JumpFPUnordered
  
  						"Data Movement; destination is always last operand"
  						MoveRR
  						"N.B. On certain targets (including X64) MoveAwR & MoveRAw may
  						 smash TempReg if the register argument is either FPReg or SPReg!!!!"
  						MoveAwR MoveA32R
  						MoveRAw MoveRA32
  						MoveAbR
  						MoveRAb
  						MoveMwrR MoveRMwr MoveXwrRR MoveRXwrR "MoveXowrR MoveRXowr""Unused"
  						MoveM8rR MoveMs8rR MoveRM8r 
  						MoveM16rR MoveRM16r MoveX16rRR MoveRX16rR
  						MoveM32rR MoveRM32r MoveX32rRR MoveRX32rR
  						MoveMbrR MoveRMbr MoveXbrRR MoveRXbrR
  						MoveCqR MoveCwR MoveC32R "MoveC64R""Not used"
  						MoveRRd MoveRdR MoveRdRd MoveM64rRd MoveRdM64r
  						MoveRsRs MoveM32rRs MoveRsM32r
  						PopR PushR PushCq PushCw
  						PrefetchAw
  
  						"Arithmetic; destination is always last operand except Cmp; CmpXR is SubRX with no update of result"
  						LoadEffectiveAddressMwrR "LoadEffectiveAddressXowrR" "Variants of add/multiply"
  						NegateR "2's complement negation"
  						NotR
  						ArithmeticShiftRightCqR ArithmeticShiftRightRR
  						LogicalShiftRightCqR LogicalShiftRightRR
  						LogicalShiftLeftCqR LogicalShiftLeftRR
  						RotateLeftCqR RotateRightCqR
  
  						CmpRR AddRR SubRR AndRR OrRR XorRR
  						CmpCqR AddCqR SubCqR AndCqR OrCqR TstCqR XorCqR
  						CmpCwR CmpC32R AddCwR SubCwR AndCwR OrCwR XorCwR
  						AddcRR AddcCqR SubbRR SubbCqR
  
  						AndCqRR "Three address ops for RISCs; feel free to add and extend"
  
  						CmpRdRd AddRdRd SubRdRd MulRdRd DivRdRd SqrtRd XorRdRd
  						CmpRsRs AddRsRs SubRsRs MulRsRs DivRsRs SqrtRs XorRsRs
  
  						"Conversion"
  						ConvertRRd ConvertRdR
  						ConvertRsRd ConvertRdRs ConvertRsR ConvertRRs
  
  						SignExtend8RR SignExtend16RR SignExtend32RR
  						ZeroExtend8RR ZeroExtend16RR ZeroExtend32RR
  
  						"Advanced bit manipulation (aritmetic)"
  						ClzRR
  						
  						LastRTLCode).
  
  	"Magic auto declaration. Add to the classPool any new variables and nuke any obsolete ones, and assign values"
  	"Find the variables directly referenced by this method"
  	refs := (thisContext method literals select: [:l| l isVariableBinding and: [classPool includesKey: l key]]) collect:
  				[:ea| ea key].
  	"Move to Undeclared any opcodes in classPool not in opcodes or this method."
  	(classPool keys reject: [:k| (opcodeNames includes: k) or: [refs includes: k]]) do:
  		[:k|
  		Undeclared declare: k from: classPool].
  	"Declare as class variables and number elements of opcodeArray above"
  	opcodeNames withIndexDo:
  		[:classVarName :value|
  		self classPool
  			declare: classVarName from: Undeclared;
  			at: classVarName put: value].
  
  	"For CogAbstractInstruction>>isJump etc..."
  	FirstJump := JumpFull.
  	LastJump := JumpFPUnordered.
  	FirstShortJump := Jump.
  
  	"And now initialize the backends; they add their own opcodes and hence these must be reinitialized."
  	(Smalltalk classNamed: #CogAbstractInstruction) ifNotNil:
  		[:cogAbstractInstruction| cogAbstractInstruction allSubclasses do: [:sc| sc initialize]]!

Item was added:
+ ----- Method: Integer>>binary (in category '*VMMaker-printing') -----
+ binary
+ 	^self printStringRadix: 2!



More information about the Vm-dev mailing list