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

commits at source.squeak.org commits at source.squeak.org
Wed Jul 21 17:03:13 UTC 2021


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

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

Name: VMMaker.oscog-eem.2991
Author: eem
Time: 21 July 2021, 10:03:03.546862 am
UUID: e1f9918c-198c-4551-9400-d6bfdcf693c7
Ancestors: VMMaker.oscog-eem.2990

CogARMv8Compiler: avoid using an out-of-line literal in immediate offset stores if the offset fits within an ADDS or SUBS.

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

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeAddCqRDest: (in category 'generate machine code - concretize') -----
  concretizeAddCqRDest: destReg
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| constant srcReg offset |
  	<var: #constant type: #sqInt>
  	constant := (operands at: 0) signedIntFromLong64.
  	srcReg := operands at: 1.
  
  	self isPossiblyShiftableImm12: constant
  		ifTrue:
  			[:shift|
  			"C6.2.4		ADD (immediate)	C6-761
  			 C6.2.8		ADDS (immediate)	C6-769"
  			machineCode
  				at: 0
  				put: (srcReg = SP
  						ifTrue:  [2r100100010 "ADD"]
  						ifFalse: [2r101100010 "ADDS"]) << 23
  					+ (shift ifTrue: [constant >> 2 + (1 << 22)] ifFalse: [constant << 10])
  					+ (srcReg << 5)
  					+ destReg.
  			^4]
  		ifFalse: [].
  	self isPossiblyShiftableImm12: constant negated
  		ifTrue:
  			[:shift|
  			"C6.2.308		SUB (immediate)	C6-1311
  			 C6.2.314		SUBS (immediate)	C6-1321"
  			machineCode
  				at: 0
  				put: (srcReg = SP
  						ifTrue:  [2r110100010 "SUB"]
  						ifFalse: [2r111100010 "SUBS"]) << 23
  					+ (shift ifTrue: [constant negated >> 2 + (1 << 22)] ifFalse: [constant negated << 10])
  					+ (srcReg << 5)
+ 					+ destReg.
- 					+destReg.
  			^4]
  		ifFalse: [].
  	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
  	"cogit processor disassembleInstructionAt: 4 In: machineCode object"
  	offset := self emitMoveCw: constant intoR: RISCTempReg at: 0.
  	"C6.2.7		ADDS (extended register)		C6-766"
  	machineCode
  				at: offset // 4
  				put: 2r10101011001 << 21
  					+ (RISCTempReg << 16)
  					+ (SXTX << 13)
  					+ (srcReg << 5)
  					+ destReg.
  	^offset + 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>emitSt:rn:rt:imm:shiftBy12: (in category 'generate machine code - support') -----
  emitSt: unitSizeLog2MinusOne rn: baseReg rt: sourceReg imm: offset shiftBy12: shiftBy12
  	"C6.2.273	STR (immediate)	C6-1239
  	 C6.2.274	STR (register)		C6-1242
  	 C6.2.275	STRB (immediate)	C6-1244"
  
  	| unitSize instrBytes |
  	unitSize := 1 << unitSizeLog2MinusOne.
  	self deny: SP = sourceReg.
  	self deny: baseReg = sourceReg.
  	"Unsigned offset, C6-1240"
  	(offset \\ unitSize = 0
  	 and: [offset / unitSize between: 0 and: 1 << 12 - 1]) ifTrue:
  		[machineCode
  			at: 0
  			put: unitSizeLog2MinusOne << 30
  				+ (2r11100100 << 22)
  				+ (offset << (10 - unitSizeLog2MinusOne))
  				+ (baseReg << 5)
  				+ sourceReg.
  		 ^4].
  	(offset between: -256 and: 255) ifTrue: "Unscaled signed 9-bit offset, C6-1244"
  		[machineCode
  			at: 0
  			put: unitSizeLog2MinusOne << 30
  				+ (2r111000000 << 21)
  				+ ((offset bitAnd: 511) << 12)
  				+ (baseReg << 5)
  				+ sourceReg.
  		 ^4].
+ 	"If the offset fits in an add or subtract immediate then do an
+ 	 add into RISCTempReg, avoiding using an out-of-line literal..."
+ 	(self isPossiblyShiftableNegatableImm12: offset) ifTrue:
+ 		[self isPossiblyShiftableImm12: offset
+ 			ifTrue:
+ 				[:shift| "C6.2.8		ADDS (immediate)	C6-769"
+ 				machineCode
+ 					at: 0
+ 					put: 2r101100010 << 23
+ 						+ (shift ifTrue: [offset >> 2 + (1 << 22)] ifFalse: [offset << 10])
+ 						+ (baseReg << 5)
+ 						+ RISCTempReg]
+ 			ifFalse:
+ 				[self isPossiblyShiftableImm12: offset negated
+ 					ifTrue:
+ 						[:shift| "C6.2.314		SUBS (immediate)	C6-1321"
+ 						machineCode
+ 							at: 0
+ 							put: 2r111100010 "SUBS" << 23
+ 								+ (shift ifTrue: [offset negated >> 2 + (1 << 22)] ifFalse: [offset negated << 10])
+ 								+ (baseReg << 5)
+ 								+ RISCTempReg]
+ 					ifFalse: [self error: 'cannot happen']].
+ 		machineCode
+ 			at: 1
+ 			put: unitSizeLog2MinusOne << 30
+ 				+ (2r111000001 << 21)
+ 				+ (XZR << 16)
+ 				+ (UXTX << 13)
+ 				+ (1 << 11)
+ 				+ (RISCTempReg << 5)
+ 				+ sourceReg.
+ 		^8].
  	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
  	"cogit processor disassembleInstructionAt: 4 In: machineCode object"
  	instrBytes := self emitMoveCw: offset intoR: RISCTempReg at: 0.
  	self assert: instrBytes = 4.
  	machineCode
  		at: 1
  		put: unitSizeLog2MinusOne << 30
  			+ (2r111000001 << 21)
  			+ (RISCTempReg << 16)
  			+ (UXTX << 13)
  			+ (1 << 11)
  			+ (baseReg << 5)
  			+ sourceReg.
  	^8!

Item was added:
+ ----- Method: CogARMv8Compiler>>isPossiblyShiftableNegatableImm12: (in category 'generate machine code - support') -----
+ isPossiblyShiftableNegatableImm12: immediate
+ 	<inline: #always>
+ 	^(immediate between: -1 << 12 and: 1 << 12 - 1)
+ 	 or: [(immediate noMask: 1 << 12 - 1)
+ 		 and: [immediate >>> 12 between: -1 << 12 and: 1 << 12 - 1]]!

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 isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
  								ifTrue: [:ign|false] ifFalse: [true]].
  		[AddCqRR]		-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
  								ifTrue: [:ign|false] ifFalse: [true]].
  		[SubCqR]		-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
  								ifTrue: [:ign|false] ifFalse: [true]].
  		[CmpCqR]		-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
  								ifTrue: [:ign|false] ifFalse: [true]].
  		[LoadEffectiveAddressMwrR]
  						-> [^self isPossiblyShiftableImm12: (operands at: 0) signedIntFromLong64
  								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]].
  		[OrCqRR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
  		[OrCqR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|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].
  		[CmpC32R]		-> [^true].
  		[OrCwR]		-> [^true].
  		[SubCwR]		-> [^true].
  		[XorCwR]		-> [^true].
  		"Data Movement"						
  		[MoveCqR]		-> [self isPossiblyShiftableImm12: (operands at: 0)
  								ifTrue: [:shift12| ^false] ifFalse:[].
  							^self isImmNImmSImmREncodableBitmask: (operands at: 0)
  								ifTrue: [:n :imms :immr|false] ifFalse: [true]].
  		[MoveC32R]	-> [^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 isImm12orImm9offset: (operands at: 0)) not].
- 		[MoveRMwr]	-> [^(self isImm12orImm9offset: (operands at: 1)) not].
  		[MoveMbrR]	-> [^(self isImm12orImm9offset: (operands at: 0)) not].
- 		[MoveRMbr]	-> [^(self isImm12orImm9offset: (operands at: 1)) not].
  		[MoveM16rR]	-> [^(self isImm12orImm9offset: (operands at: 0)) not].
+ 		[MoveRMwr]	-> [^self isPossiblyShiftableNegatableImm12: (operands at: 1) ifTrue: [:shift12| false] ifFalse: [true]].
+ 		[MoveRMbr]	-> [^self isPossiblyShiftableNegatableImm12: (operands at: 1) ifTrue: [:shift12| false] ifFalse: [true]].
+ 		[MoveRM16r]	-> [^self isPossiblyShiftableNegatableImm12: (operands at: 1) ifTrue: [:shift12| false] ifFalse: [true]].
- 		[MoveRM16r]	-> [^(self isImm12orImm9offset: (operands at: 1)) not].
  		[MoveRdM64r]	-> [^(self isUnsigned12BitMultipleOf8: (operands at: 1)) not].
  		[MoveM64rRd]	-> [^(self isUnsigned12BitMultipleOf8: (operands at: 0)) not].
  		[PushCw]		-> [^(self inCurrentCompilation: (operands at: 0)) not].
  		[PushCq]		-> [^((operands at: 0) between: -256 and: 255) not].
  		[PrefetchAw] 	-> [^(self isAddressRelativeToVarBase: (operands at: 0)) not].
  		}
  		otherwise: [self assert: false].
  	^false "to keep C compiler quiet"
  !



More information about the Vm-dev mailing list