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

commits at source.squeak.org commits at source.squeak.org
Mon Aug 2 06:22:44 UTC 2021


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

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

Name: VMMaker.oscog-eem.3012
Author: eem
Time: 1 August 2021, 11:22:35.709916 pm
UUID: b743cd66-0506-49a9-a445-95d97e2ab623
Ancestors: VMMaker.oscog-eem.3011

Cogit: Fix a Slang slip with CogARMv8Compiler>>computeMaximumSize.  USe SP rather than NativeSPReg within CogARMv8Compiler, as NativeSPReg is really for the outside world (the Cogit's world).

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

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 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]					-> ["N.B. For three operand logical ops only support AndCqRR with a NativeSPReg target, used for alignment purposes."
+ 										^self isImmNImmSImmREncodableBitmask: (operands at: 0)
+ 												ifTrue: [:n :imms :immr| (operands at: 2) = SP ifTrue: [8] ifFalse: [4]]
+ 												ifFalse:[(operands at: 2) = SP ifTrue: [12] ifFalse: [8]]].
- 										^(self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|4] ifFalse:[8])
- 										+ ((operands at: 2) = NativeSPReg ifTrue: [4] ifFalse: [0])].
  		[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 isImm12orImm9offset: (operands at: 0)) ifTrue: [4] ifFalse: [8]].
  		[MoveRMwr]			-> [^(self isImm12orImm9offset: (operands at: 1)) ifTrue: [4] ifFalse: [8]].
  		[MoveM32rR]			-> [^(self isImm12orImm9offset: (operands at: 0)) ifTrue: [4] ifFalse: [8]].
  		[MoveRM32r]			-> [^(self isImm12orImm9offset: (operands at: 1)) ifTrue: [4] ifFalse: [8]].
  		[MoveM16rR]			-> [^(self isImm12orImm9offset: (operands at: 0)) ifTrue: [4] ifFalse: [8]].
  		[MoveRM16r]			-> [^(self isImm12orImm9offset: (operands at: 1)) ifTrue: [4] ifFalse: [8]].
  		[MoveMbrR]			-> [^(self isImm12orImm9offset: (operands at: 0)) ifTrue: [4] ifFalse: [8]].
  		[MoveRMbr]			-> [^(self isImm12orImm9offset: (operands at: 1)) ifTrue: [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 changed:
  ----- 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 effectiveDestReg offset |
  	constant := operands at: 0.
  	srcReg := operands at: 1.
  	"N.B. For three operand logical ops only support AndCq: const R: reg R: NativeSPReg, which is used for alignment."
+ 	effectiveDestReg := (opcode = AndCqRR and: [destReg = SP]) ifTrue: [RISCTempReg] ifFalse: [destReg].
- 	effectiveDestReg := (opcode = AndCqRR and: [destReg = NativeSPReg]) ifTrue: [RISCTempReg] ifFalse: [destReg].
  	self isImmNImmSImmREncodableBitmask: constant
  		ifTrue:
  			[:n :imms :immr|
  			 machineCode
  				at: 0
  				put: 2r1001001 << 25
  					+ (op << 29)
  					+ (n << 22)
  					+ (immr << 16)
  					+ (imms << 10)
  					+ (srcReg << 5)
  					+ effectiveDestReg.
  			 offset := 4]
  		ifFalse:
  			[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)
  					+ effectiveDestReg.
  			offset := offset + 4].
+ 	(opcode = AndCqRR and: [destReg = SP]) ifFalse:
- 	(opcode = AndCqRR and: [destReg = NativeSPReg]) ifFalse:
  		[^offset].
  	machineCode at: offset // 4 put: (self movern: effectiveDestReg rd: 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 changed:
  ----- 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: SP rd: SP imm: offset shiftBy12: false);
- 		at: 0 put: (self addrn: NativeSPReg rd: NativeSPReg imm: offset shiftBy12: false);
  		at: 1 put: 2r1101011001 << 22
  				+ (XZR << 16)
  				+ (LR << 5).
  	^8!

Item was changed:
  ----- 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: SP
+ 			operand: FP.
- 			operand: NativeSPReg
- 			operand: FPReg.
  		 ^0].
  
  	^super genLoadCStackPointers!

Item was changed:
  ----- Method: CogARMv8Compiler>>genLoadNativeSPRegWithAlignedSPReg (in category 'smalltalk calling convention') -----
  genLoadNativeSPRegWithAlignedSPReg
+ 	cogit AndCq: (objectMemory wordSize * 2 - 1) bitInvert R: SPReg R: SP!
- 	cogit AndCq: (objectMemory wordSize * 2 - 1) bitInvert R: SPReg R: NativeSPReg!



More information about the Vm-dev mailing list