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

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


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

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

Name: VMMaker.oscog-eem.2609
Author: eem
Time: 8 December 2019, 8:41:23.17819 pm
UUID: 0fb74a7b-5bfc-48f0-a4c0-4d56b0f20c62
Ancestors: VMMaker.oscog-eem.2608

A64 fix bugs in LogicalShiftLeftCqR, MoveM16rR, MoveMbrR, MoveXwrRR & cond:br:offset:.

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

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeLogicalShiftLeftCqR (in category 'generate machine code - concretize') -----
  concretizeLogicalShiftLeftCqR
  	"C6.2.17 	ASR (immediate)	C6-785		100100110 (1)
  	 C6.2.177	LSL (immediate)	C6-1075	110100110 (1)
  	 C6.2.180	LSR (immediate)	C6-1081	110100110 (1)"
  	| reg constant |
  	constant := operands at: 0.
  	reg := operands at: 1.
  	self assert: (constant between: 1 and: 63).
  	machineCode
  		at: 0
  		put: 2r1101001101 << 22
+ 			+ (64 - constant << 16)
+ 			+ (63 - constant << 10)
- 			+ (constant << 16)
- 			+ (63 << 10)
  			+ (reg << 5)
  			+ reg.
  	^4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveM16rR (in category 'generate machine code - concretize') -----
  concretizeMoveM16rR
+ 	"C6.2.136	LDRH (immediate)	C6-990"
- 	"C6.2.168	LDURH	C6-1061"
  	| offset destReg srcReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
+ 	(offset between: -2048 and: 2047)
- 	(offset between: -256 and: 255)
  		ifTrue:
  			[machineCode
  				at: 0
+ 				put: 2r0111100101 << 22
+ 					+ ((offset bitAnd: 1 << 12 - 1) << 10)
- 				put: 2r0111100001 << 22
- 					+ ((offset bitAnd: 1 << 9 - 1) << 12)
  					+ (srcReg << 5)
  					+ destReg.
  			^4]
  		ifFalse:
  			[self shouldBeImplemented]!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveMbrR (in category 'generate machine code - concretize') -----
  concretizeMoveMbrR
+ 	"C6.2.134	LDRB (immediate)	C6-985"
- 	"C6.2.167	LDURB	C6-1060"
  	| offset destReg srcReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
+ 	(offset between: -2048 and: 2047)
- 	(offset between: -256 and: 255)
  		ifTrue:
  			[machineCode
  				at: 0
+ 				put: 2r0011100101 << 22
+ 					+ ((offset bitAnd: 1 << 12 - 1) << 10)
- 				put: 2r0011100001 << 22
- 					+ ((offset bitAnd: 1 << 9 - 1) << 12)
  					+ (srcReg << 5)
  					+ destReg.
  			^4]
  		ifFalse:
  			[self shouldBeImplemented]!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveXwrRR (in category 'generate machine code - concretize') -----
  concretizeMoveXwrRR
  	"Xwr - memory word whose address is r * word size away from an address in a register"
  	"C6.2.132	LDR (register)	C6-981"
+ 	| index base dest |
+ 	index := operands at: 0.
+ 	base := operands at: 1.
+ 	dest := operands at: 2.
+ 	self deny: SP = dest.
- 	| destReg srcReg |
- 	srcReg := operands at: 0.
- 	destReg := operands at: 1.
- 	self deny: SP = destReg.
  	machineCode
  		at: 0
  		put: 2r11111000011 << 21
+ 			+ (index << 16)
- 			+ (destReg << 16)
  			+ (UXTX << 13)
+ 			+ (3 << 11)
+ 			+ (base << 5)
+ 			+ dest.
- 			+ (1 << 12)
- 			+ (srcReg << 5)
- 			+ destReg.
  	^4!

Item was changed:
  ----- Method: CogARMv8Compiler>>cond:br:offset: (in category 'generate machine code - support') -----
  cond: cond br: link offset: offset
  	self assert: link = 0.
+ 	self assert: (offset bitAnd: 3) = 0.
  	^2r010101 << 26
+ 	+ ((offset bitAnd: 1 << 19 - 1) << 3)
- 	+ ((offset bitAnd: 1 << 19 - 1) << 5)
  	+ cond!

Item was changed:
  ----- 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."
  		 
  	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 concretizeAddCqR].
+ 		[AndCqR]						-> [^self concretizeAndCqRDest: (operands at: 1)].
+ 		[AndCqRR]						-> [^self concretizeAndCqRDest: (operands at: 2)].
- 		[AndCqR]						-> [^self concretizeInvertibleDataOperationCqR: AndOpcode].
- 		[AndCqRR]						-> [^self concretizeAndCqRDest: (operands at: 1)].
  		[CmpCqR]						-> [^self concretizeCmpCqR].
  		[OrCqR]						-> [^self concretizeDataOperationCqR: OrOpcode].
  		[SubCqR]						-> [^self concretizeSubCqR].
  		[TstCqR]						-> [^self concretizeAndCqRDest: XZR].
  		[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 concretizeAddRR].
  		[AndRR]						-> [^self concretizeDataOperationRR: AndOpcode].
  		[CmpRR]						-> [^self concretizeDataOperationRR: CmpOpcode].
  		[OrRR]							-> [^self concretizeDataOperationRR: OrOpcode].
  		[SubRR]						-> [^self concretizeSubRR].
  		[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] }.
  
  	^0 "keep Slang happy"!

Item was changed:
  ----- Method: CogARMv8Compiler>>isImmNImmSImmREncodableBitmask:ifTrue:ifFalse: (in category 'generate machine code - support') -----
  isImmNImmSImmREncodableBitmask: constant ifTrue: trinaryBlock "[:n :imms :immr|...]" ifFalse: nullaryBlock
  	"See DecodeBitMasks J1-7389.
  	 See https://dinfuehr.github.io/blog/encoding-of-immediate-values-on-aarch64/
  	 This method is adapted from The LLVM Compiler Infrastructure, AArch64AddressingModes.h processLogicalImmediate"
  	<inline: #always>
  	| imm size mask countLeadingOnes countTrailingOnes immr n nImms rotateCount |
  	(constant between: -1 and: 0) ifTrue:
  		[^nullaryBlock value].
+ 	imm := self cCode: [constant] inSmalltalk: [constant signedIntToLong64].
- 	imm := constant.
   
  	"First, determine the element size."
  	size := 32.
  	[mask := 1 << size - 1.
  	 (imm bitAnd: mask) ~= (imm >> size)
  			ifTrue: [size := size * 2. false]
  			ifFalse: [size > 2]]
  		whileTrue: [size := size / 2].
  
  	"Second, determine the rotation to make the element be: 0^m 1^n."
  	mask := 1 << 64 - 1 >> (64 - size).
  	imm := imm bitAnd: mask.
  
  	(self isShiftedMask: imm)
  		ifTrue:
  			[rotateCount := self countTrailingZeros: imm.
  			 countTrailingOnes := self countTrailingOnes: imm >> rotateCount]
  		ifFalse:
  			[imm := imm bitOr: mask bitInvert64.
  			 (self isShiftedMask: imm) ifFalse:
  				[^nullaryBlock value].
  			 countLeadingOnes := self countLeadingOnes: imm.
  			 rotateCount := 64 - countLeadingOnes.
  			 countTrailingOnes := countLeadingOnes + (self countTrailingOnes: imm) - (64 - size)].
  
  	"Encode in Immr the number of RORs it would take to get *from* 0^m 1^n
  	 to our target value, where I is the number of RORs to go the opposite direction."
   
  	self assert: size > rotateCount. "rotateCount should be smaller than element size"
  	immr := size - rotateCount bitAnd: size - 1.
  
  	"If size has a 1 in the n'th bit, create a value that has zeroes in bits [0, n] and ones above that."
  	nImms := (size - 1) bitInvert64 << 1.
  
  	"Or the CTO value into the low bits, which must be below the Nth bit mentioned above."
  	nImms := nImms bitOr:  countTrailingOnes - 1.
  
  	"Extract the seventh bit and toggle it to create the N field."
  	n := ((nImms >> 6) bitAnd: 1) bitXor: 1.
  
  	nImms := nImms bitAnd: 16r3F.
  
+ 	self assert: (self decode64Imms: nImms immr: immr) = constant signedIntToLong64.
- 	self assert: (self decode64Imms: nImms immr: immr) = constant.
  
  	^trinaryBlock
  		value: n
  		value: nImms
  		value: immr
  !

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]].
- 		[AndCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
- 		[AndCqRR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|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]].
- 		[OrCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|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]].
- 		[TstCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
- 		[XorCqR]		-> [^self isPossiblyShiftableImm12: (operands at: 0) ifTrue: [:shift12|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 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"
  !



More information about the Vm-dev mailing list