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

commits at source.squeak.org commits at source.squeak.org
Mon Sep 28 17:25:54 UTC 2015


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

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

Name: VMMaker.oscog-eem.1473
Author: eem
Time: 28 September 2015, 10:23:36.698 am
UUID: b89ffa84-63b0-4e63-803c-2b715ad3f7ef
Ancestors: VMMaker.oscog-eem.1472

x64 Cogit: Get MoveRMbr & MoveMbrR right.

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

Item was changed:
  ----- Method: CogIA32CompilerTests>>testMoveRMbr (in category 'tests') -----
  testMoveRMbr
  	"self new testMoveRMbr"
  	CogIA32CompilerForTests registersWithNamesDo:
+ 		[:sreg :srname|
+ 		CogIA32CompilerForTests registersWithNamesDo:
+ 			[:dreg :drname|
+ 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 				[:offset| | inst len |
+ 				inst := self gen: MoveRMbr operand: sreg operand: offset operand: dreg.
+ 				len := inst concretizeAt: 0.
+ 				self processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended |
+ 						plainJane := self strip: str.
+ 						herIntended := 'movb ', srname, ', 0x', (offset hex allButFirst: 3), '(', drname, ')'.
+ 						self assert: (plainJane match: herIntended).
+ 						self assert: len = sz]]]]!
- 		[:sreg :srname| | brname |
- 		sreg < 4 ifTrue:
- 			[brname := #('%al' '%cl' '%dl' '%bl') at: sreg + 1.
- 			CogIA32CompilerForTests registersWithNamesDo:
- 				[:dreg :drname|
- 				((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
- 					[:offset| | inst len |
- 					inst := self gen: MoveRMbr operand: sreg operand: offset operand: dreg.
- 					len := inst concretizeAt: 0.
- 					self processor
- 						disassembleInstructionAt: 0
- 						In: inst machineCode object
- 						into: [:str :sz| | plainJane herIntended |
- 							plainJane := self strip: str.
- 							herIntended := 'movb ', brname, ', 0x', (offset hex allButFirst: 3), '(', drname, ')'.
- 							self assert: (plainJane match: herIntended).
- 							self assert: len = sz]]]]]!

Item was changed:
  ----- Method: CogX64Compiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Compute the maximum size for each opcode.  This allows jump offsets to
  	 be determined, provided that all backward branches are long branches."
  	"N.B.  The ^N forms are to get around the bytecode compiler's long branch
  	 limits which are exceeded when each case jumps around the otherwise."
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^0].
  		[AlignmentNops]		-> [^(operands at: 0) - 1].
  		[Fill16]					-> [^2].
  		[Fill32]					-> [^4].
  		[FillFromWord]			-> [^4].
  		[Nop]					-> [^1].
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^2].
  		[IDIVR]					-> [^3].
  		[IMULRR]				-> [^4].
  		[CPUID]					-> [^2].
  		[CMPXCHGAwR]			-> [^8].
  		[CMPXCHGMwrR]		-> [^9].
  		[LFENCE]				-> [^3].
  		[MFENCE]				-> [^3].
  		[SFENCE]				-> [^3].
  		[LOCK]					-> [^1].
  		"[XCHGAwR]				-> [^6].
  		[XCHGMwrR]			-> [^7]."
  		[XCHGRR]				-> [^((self concreteRegister: (operands at: 0)) = RAX
  									   or: [(self concreteRegister: (operands at: 1)) = RAX])
  											ifTrue: [2]
  											ifFalse: [3]].
  		"Control"
  		[CallFull]					-> [^12].
  		[Call]						-> [^5].
  		[JumpR]						-> [^2].
  		[JumpFull]					-> [self resolveJumpTarget. ^12].
  		[JumpLong]					-> [self resolveJumpTarget. ^5].
  		[Jump]						-> [self resolveJumpTarget. ^5].
  		[JumpZero]					-> [self resolveJumpTarget. ^6].
  		[JumpNonZero]				-> [self resolveJumpTarget. ^6].
  		[JumpNegative]				-> [self resolveJumpTarget. ^6].
  		[JumpNonNegative]			-> [self resolveJumpTarget. ^6].
  		[JumpOverflow]				-> [self resolveJumpTarget. ^6].
  		[JumpNoOverflow]			-> [self resolveJumpTarget. ^6].
  		[JumpCarry]				-> [self resolveJumpTarget. ^6].
  		[JumpNoCarry]				-> [self resolveJumpTarget. ^6].
  		[JumpLess]					-> [self resolveJumpTarget. ^6].
  		[JumpGreaterOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpGreater]				-> [self resolveJumpTarget. ^6].
  		[JumpLessOrEqual]			-> [self resolveJumpTarget. ^6].
  		[JumpBelow]				-> [self resolveJumpTarget. ^6].
  		[JumpAboveOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpAbove]				-> [self resolveJumpTarget. ^6].
  		[JumpBelowOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpLongZero]			-> [self resolveJumpTarget. ^6].
  		[JumpLongNonZero]		-> [self resolveJumpTarget. ^6].
  		[JumpFPEqual]				-> [self resolveJumpTarget. ^6].
  		[JumpFPNotEqual]			-> [self resolveJumpTarget. ^6].
  		[JumpFPLess]				-> [self resolveJumpTarget. ^6].
  		[JumpFPGreaterOrEqual]	-> [self resolveJumpTarget. ^6].
  		[JumpFPGreater]			-> [self resolveJumpTarget. ^6].
  		[JumpFPLessOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpFPOrdered]			-> [self resolveJumpTarget. ^6].
  		[JumpFPUnordered]			-> [self resolveJumpTarget. ^6].
  		[RetN]						-> [^(operands at: 0) = 0 ifTrue: [1] ifFalse: [3]].
  		[Stop]						-> [^1].
  
  		"Arithmetic"
  		[AddCqR]		-> [^self computeSizeOfArithCqR].
  		[AndCqR]		-> [^self computeSizeOfArithCqR].
  		[CmpCqR]		-> [^self computeSizeOfArithCqR].
  		[OrCqR]			-> [^self computeSizeOfArithCqR].
  		[SubCqR]		-> [^self computeSizeOfArithCqR].
  		[TstCqR]		-> [^self computeSizeOfArithCqR].
  		[AddCwR]		-> [^self computeSizeOfArithCwR].
  		[AndCwR]		-> [^self computeSizeOfArithCwR].
  		[CmpCwR]		-> [^self computeSizeOfArithCwR].
  		[OrCwR]		-> [^self computeSizeOfArithCwR].
  		[SubCwR]		-> [^self computeSizeOfArithCwR].
  		[XorCwR]		-> [^self computeSizeOfArithCwR].
  		[AddRR]			-> [^3].
  		[AndRR]			-> [^3].
  		[CmpRR]		-> [^3].
  		[OrRR]			-> [^3].
  		[XorRR]			-> [^3].
  		[SubRR]			-> [^3].
  		[NegateR]		-> [^3].
  		"[LoadEffectiveAddressMwrR]
  						-> [^((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])]."
  		[LogicalShiftLeftCqR]		-> [^(operands at: 0) = 1 ifTrue: [3] ifFalse: [4]].
  		[LogicalShiftRightCqR]		-> [^(operands at: 0) = 1 ifTrue: [3] ifFalse: [4]].
  		[ArithmeticShiftRightCqR]	-> [^(operands at: 0) = 1 ifTrue: [3] ifFalse: [4]].
  		[LogicalShiftLeftRR]			-> [^self computeShiftRRSize].
  		[LogicalShiftRightRR]		-> [^self computeShiftRRSize].
  		[ArithmeticShiftRightRR]		-> [^self computeShiftRRSize].
  		[AddRdRd]					-> [^4].
  		[CmpRdRd]					-> [^4].
  		[SubRdRd]					-> [^4].
  		[MulRdRd]					-> [^4].
  		[DivRdRd]					-> [^4].
  		[SqrtRd]					-> [^4].
  		"Data Movement"
  		[MoveCqR]		-> [^(operands at: 0) = 0 ifTrue: [3] ifFalse: [(self is32BitSignedImmediate: (operands at: 0)) ifTrue: [7] ifFalse: [10]]].
  		[MoveCwR]		-> [^10].
  		[MoveRR]		-> [^3].
  		[MoveRdRd]		-> [^4].
  		[MoveAwR]		-> [^(self isAddressRelativeToVarBase: (operands at: 0))
  								ifTrue: [7]
  								ifFalse: [(self concreteRegister: (operands at: 1)) = RAX ifTrue: [10] ifFalse: [14]]].
  		[MoveRAw]		-> [^(self isAddressRelativeToVarBase: (operands at: 1))
  								ifTrue: [7]
  								ifFalse: [(self concreteRegister: (operands at: 0)) = RAX ifTrue: [10] ifFalse: [14]]].
  		[MoveRMwr]	-> [^((self isQuick: (operands at: 1))
  									ifTrue: [((operands at: 1) = 0
  											and: [((self concreteRegister: (operands at: 2)) bitAnd: 7) ~= RBP])
  												ifTrue: [3]
  												ifFalse: [4]]
  									ifFalse: [7])
  								+ (((self concreteRegister: (operands at: 2)) bitAnd: 7) = RSP
  									ifTrue: [1]
  									ifFalse: [0])].
  		"[MoveRdM64r]	-> [^((self isQuick: (operands at: 1))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])]."
  		[MoveMbrR]		-> [^((self isQuick: (operands at: 0))
+ 									ifTrue: [((operands at: 0) = 0
+ 											and: [((self concreteRegister: (operands at: 1)) bitAnd: 7) ~= RBP])
+ 												ifTrue: [4]
+ 												ifFalse: [5]]
+ 									ifFalse: [8])
+ 								+ (((self concreteRegister: (operands at: 1)) bitAnd: 7) = RSP
+ 									ifTrue: [1]
+ 									ifFalse: [0])].
+ 		[MoveRMbr]		-> [^((self isQuick: (operands at: 1))
+ 									ifTrue: [((operands at: 1) = 0
+ 											and: [((self concreteRegister: (operands at: 0)) bitAnd: 7) ~= RBP])
+ 												ifTrue: [3]
+ 												ifFalse: [4]]
+ 									ifFalse: [7])
+ 								+ (((self concreteRegister: (operands at: 2)) bitAnd: 7) = RSP
+ 									ifTrue: [1]
+ 									ifFalse: [0])].
- 											ifTrue: [5]
- 											ifFalse: [8])
- 										+ (((self concreteRegister: (operands at: 1)) = RSP
- 											or: [(self concreteRegister: (operands at: 1)) = R12])
- 											ifTrue: [1]
- 											ifFalse: [0])].
- 		[MoveRMbr]		-> [^((self concreteRegister: (operands at: 2)) = RSP
- 							  or: [(self concreteRegister: (operands at: 2)) = R12])
- 								ifTrue: [8]
- 								ifFalse: [(self isQuick: (operands at: 1)) ifTrue: [4] ifFalse: [7]]].
  		"[MoveM16rR]	-> [^((self isQuick: (operands at: 0))
  											ifTrue: [4]
  											ifFalse: [7])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveM64rRd]	-> [^((self isQuick: (operands at: 0))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])]."
  		[MoveMwrR]		-> [^((self isQuick: (operands at: 0))
  									ifTrue: [((operands at: 0) = 0
  											and: [((self concreteRegister: (operands at: 1)) bitAnd: 7) ~= RBP])
  												ifTrue: [3]
  												ifFalse: [4]]
  									ifFalse: [7])
  								+ (((self concreteRegister: (operands at: 1)) bitAnd: 7) = RSP
  									ifTrue: [1]
  									ifFalse: [0])].
  		"[MoveXbrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= ESP.
  							^(self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [5]
  											ifFalse: [4]].
  		[MoveRXbrR]	->	[self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
  							^((self concreteRegister: (operands at: 2)) = EBP
  											ifTrue: [4]
  											ifFalse: [3])
  										+ ((self concreteRegister: (operands at: 0)) >= 4
  											ifTrue: [2]
  											ifFalse: [0])]."
  		[MoveXwrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= RSP.
  							^((self concreteRegister: (operands at: 1)) = RBP
  							   or: [(self concreteRegister: (operands at: 1)) = R13])
  											ifTrue: [5]
  											ifFalse: [4]].
  		[MoveRXwrR]	-> [self assert: (self concreteRegister: (operands at: 1)) ~= RSP.
  							^((self concreteRegister: (operands at: 2)) = RBP
  							   or: [(self concreteRegister: (operands at: 2)) = R13])
  											ifTrue: [5]
  											ifFalse: [4]].
  		[PopR]			-> [^(self concreteRegister: (operands at: 0)) < 8 ifTrue: [1] ifFalse: [2]].
  		[PushR]			-> [^(self concreteRegister: (operands at: 0)) < 8 ifTrue: [1] ifFalse: [2]].
  		[PushCq]		-> [^(self isQuick: (operands at: 0)) ifTrue: [2] ifFalse: [5]].
  		[PushCw]		-> [^self computeSizeOfArithCwR - 1].
  		[PrefetchAw]	-> [^self hasSSEInstructions ifTrue: [12] ifFalse: [0]].
  		"Conversion"
  		"[ConvertRRd]	-> [^4]" }.
  	^0 "to keep C compiler quiet"!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveMbrR (in category 'generate machine code') -----
  concretizeMoveMbrR
  	"N.B. The Cogit compiler makes no assumption about the upper bits being set to zero.
  	 It will clear the register before hand if necessary."
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	destReg := self concreteRegister: (operands at: 2).
  	machineCode
  		at: 0 put: (self rexR: destReg x: 0 b: srcReg);
  		at: 1 put: 16r0f;
  		at: 2 put: 16rb6.
  	(srcReg ~= RSP and: [srcReg ~= R12]) ifTrue:
+ 		[(offset = 0 and: [destReg ~= RBP and: [destReg ~= R13]]) ifTrue:
- 		[(self isQuick: offset) ifTrue:
  			[machineCode
+ 				at: 3 put: (self mod: ModRegInd RM: srcReg RO: destReg).
+ 			 ^machineCodeSize := 4].
+ 		 (self isQuick: offset) ifTrue:
+ 			[machineCode
  				at: 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 4 put: (offset bitAnd: 16rFF).
  			 ^machineCodeSize := 5].
  		machineCode
  			at: 3 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 4 put: (offset bitAnd: 16rFF);
  			at: 5 put: (offset >> 8 bitAnd: 16rFF);
  			at: 6 put: (offset >> 16 bitAnd: 16rFF);
  			at: 7 put: (offset >> 24 bitAnd: 16rFF).
  		^machineCodeSize := 8].
  	"RSP & R12:"
+ 	(offset = 0 and: [destReg ~= RBP and: [destReg ~= R13]]) ifTrue:
+ 		[machineCode
+ 			at: 3 put: (self mod: ModRegInd RM: srcReg RO: destReg);
+ 			at: 4 put: (self s: SIB1 i: 4 b: srcReg).
+ 		 ^machineCodeSize := 5].
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 4 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 5 put: (offset bitAnd: 16rFF).
  		 ^machineCodeSize := 6].
  	machineCode
  		at: 3 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 4 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 5 put: (offset bitAnd: 16rFF);
  		at: 6 put: (offset >> 8 bitAnd: 16rFF);
  		at: 7 put: (offset >> 16 bitAnd: 16rFF);
  		at: 8 put: (offset >> 24 bitAnd: 16rFF).
  	^machineCodeSize := 9!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeMoveRMbr (in category 'generate machine code') -----
+ concretizeMoveRMbr
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcReg offset destReg |
+ 	srcReg := self concreteRegister: (operands at: 0).
+ 	offset := operands at: 1.
+ 	destReg := self concreteRegister: (operands at: 2).
+ 	machineCode
+ 		at: 0 put: (self rexR: srcReg x: 0 b: destReg);
+ 		at: 1 put: 16r88.
+ 	(destReg ~= RSP and: [destReg ~= R12]) ifTrue:
+ 		[(offset = 0 and: [destReg ~= RBP and: [destReg ~= R13]]) ifTrue:
+ 			[machineCode
+ 				at: 2 put: (self mod: ModRegInd RM: destReg RO: srcReg).
+ 			 ^machineCodeSize := 3].
+ 		 (self isQuick: offset) ifTrue:
+ 			[machineCode
+ 				at: 2 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
+ 				at: 3 put: (offset bitAnd: 16rFF).
+ 			 ^machineCodeSize := 4].
+ 		machineCode
+ 			at: 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
+ 			at: 3 put: (offset bitAnd: 16rFF);
+ 			at: 4 put: (offset >> 8 bitAnd: 16rFF);
+ 			at: 5 put: (offset >> 16 bitAnd: 16rFF);
+ 			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^machineCodeSize := 7].
+ 	"RSP:"
+ 	offset = 0 ifTrue:
+ 		[machineCode
+ 			at: 2 put: (self mod: ModRegInd RM: destReg RO: srcReg);
+ 			at: 3 put: (self s: SIB1 i: 4 b: destReg).
+ 		 ^machineCodeSize := 4].
+ 	(self isQuick: offset) ifTrue:
+ 		[machineCode
+ 			at: 2 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
+ 			at: 3 put: (self s: SIB1 i: 4 b: destReg);
+ 			at: 4 put: (offset bitAnd: 16rFF).
+ 		 ^machineCodeSize := 5].
+ 	machineCode
+ 		at: 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
+ 		at: 3 put: (self s: SIB1 i: 4 b: destReg);
+ 		at: 4 put: (offset bitAnd: 16rFF);
+ 		at: 5 put: (offset >> 8 bitAnd: 16rFF);
+ 		at: 6 put: (offset >> 16 bitAnd: 16rFF);
+ 		at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^machineCodeSize := 8!

Item was added:
+ ----- Method: CogX64CompilerForTests class>>byteRegistersWithNamesDo: (in category 'test support') -----
+ byteRegistersWithNamesDo: aBinaryBlock
+ 	self registers
+ 		with: #('%al' '%cl' '%dl' '%bl' '%spl' '%bpl' '%sil' '%dil' '%r8b' '%r9b' '%r10b' '%r11b' '%r12b' '%r13b' '%r14b' '%r15b')
+ 		do: aBinaryBlock!

Item was changed:
  ----- Method: CogX64CompilerTests>>testMoveRMbr (in category 'tests') -----
  testMoveRMbr
  	"self new testMoveRMbr"
  	self concreteCompilerClass registersWithNamesDo:
  		[:sreg :srname| | brname |
  		sreg < 4 ifTrue:
  			[brname := #('%al' '%cl' '%dl' '%bl') at: sreg + 1.
  			self concreteCompilerClass registersWithNamesDo:
  				[:dreg :drname|
  				((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
  					[:offset| | inst len |
  					inst := self gen: MoveRMbr operand: sreg operand: offset operand: dreg.
  					len := inst concretizeAt: 0.
  					self processor
  						disassembleInstructionAt: 0
  						In: inst machineCode object
+ 						into: [:str :sz| | plainJane herIntended po |
- 						into: [:str :sz| | plainJane herIntended |
  							plainJane := self strip: str.
+ 							po := offset bitAnd: 1 << self processor bitsInWord - 1.
+ 							herIntended := 'movb ', brname, (offset = 0 ifTrue: [', '] ifFalse: [', 0x', (po printStringBase: 16 length: 16 padded: true)]), '(', drname, ')'.
- 							herIntended := 'movb ', brname, ', 0x', (offset hex allButFirst: 3), '(', drname, ')'.
  							self assert: (plainJane match: herIntended).
  							self assert: len = sz]]]]]!



More information about the Vm-dev mailing list