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

commits at source.squeak.org commits at source.squeak.org
Thu Sep 24 01:35:56 UTC 2015


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

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

Name: VMMaker.oscog-eem.1466
Author: eem
Time: 23 September 2015, 6:33:07.031 pm
UUID: 52d92b43-041a-4a50-af5d-965ade697d40
Ancestors: VMMaker.oscog-eem.1465

x64:
Implement RetN.
Implement var-base relative addressing for MoveRAw/AwR.
Revise upwards the max machine code size (for MoveRAw/AwR).
Implement some of the calling convention machinery.
Hence hit the first problem (in genPassReg:asArgument:).  The Cogit assumes the C argument registers are distinct from the other abstract registers, but on x64 these are rdi, rsi, rdx & rcx, all of which we like to use (for Arg1Reg, Arg0Reg, ReceiverResultReg & ClassReg respectively).  So it's probably time to revise the abstract to concrete register mapping to avoid the conflict.  But I want to sleep on it first.

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

Item was changed:
  ----- Method: CoInterpreter>>varBaseAddress (in category 'cog jit support') -----
  varBaseAddress
  	<api>
  	<returnTypeC: #usqInt>
+ 	^self cCode: [(self addressOf: stackPointer) asUnsignedInteger - 16r40]
- 	^self cCode: [(self addressOf: stackPointer) asUnsignedInteger - 16r42]
  		inSmalltalk: [cogit fakeVarBaseAddress]!

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: [2] ifFalse: [3]].
  		[LogicalShiftRightCqR]		-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]].
  		[ArithmeticShiftRightCqR]	-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]]."
  		[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]]].
- 		"[MoveAwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
- 		[MoveRAw]		-> [^(self concreteRegister: (operands at: 0)) = EAX ifTrue: [5] ifFalse: [6]]."
  		[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: [4]
  											ifFalse: [7])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveRMbr]		-> [^((self isQuick: (operands at: 1))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[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)) ~= ESP.
  							^(self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[MoveRXwrR]	-> [self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
  							^(self concreteRegister: (operands at: 2)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]]."
  		[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 added:
+ ----- Method: CogX64Compiler>>concretizeMoveAwR (in category 'generate machine code') -----
+ concretizeMoveAwR
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| addressOperand reg offset save0 save1 |
+ 	addressOperand := operands at: 0.
+ 	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
+ 		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
+ 	(self isAddressRelativeToVarBase: addressOperand) ifTrue:
+ 		[save0 := operands at: 0.
+ 		 save1 := operands at: 1.
+ 		 operands
+ 			at: 0 put: addressOperand - cogit varBaseAddress;
+ 			at: 1 put: VarBaseReg;
+ 			at: 2 put: save1.
+ 		 self concretizeMoveMwrR.
+ 		 operands
+ 			at: 0 put: save0;
+ 			at: 1 put: save1;
+ 			at: 2 put: 0.
+ 		^machineCodeSize].
+ 	reg := self concreteRegister: (operands at: 1).
+ 	reg = RAX
+ 		ifTrue: [offset := 0]
+ 		ifFalse:
+ 			[machineCode
+ 				at: 0 put: (self rexR: 0 x: 0 b: reg);
+ 				at: 1 put: 16r90 + (reg \\ 8).
+ 			 offset := 2].
+ 	machineCode
+ 		at: 0 + offset put: 16r48;
+ 		at: 1 + offset put: 16rA1;
+ 		at: 2 + offset put: (addressOperand bitAnd: 16rFF);
+ 		at: 3 + offset put: (addressOperand >> 8 bitAnd: 16rFF);
+ 		at: 4 + offset put: (addressOperand >> 16 bitAnd: 16rFF);
+ 		at: 5 + offset put: (addressOperand >> 24 bitAnd: 16rFF);
+ 		at: 6 + offset put: (addressOperand >> 32 bitAnd: 16rFF);
+ 		at: 7 + offset put: (addressOperand >> 40 bitAnd: 16rFF);
+ 		at: 8 + offset put: (addressOperand >> 48 bitAnd: 16rFF);
+ 		at: 9 + offset put: (addressOperand >> 56 bitAnd: 16rFF).
+ 	reg = RAX ifTrue:
+ 		[^machineCodeSize := 10].
+ 	machineCode
+ 		at: 12 put: (machineCode at: 0);
+ 		at: 13 put: (machineCode at: 1).
+ 	^machineCodeSize := 14!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeMoveRAw (in category 'generate machine code') -----
+ concretizeMoveRAw
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| addressOperand reg offset save1 |
+ 	reg := self concreteRegister: (operands at: 0).
+ 	addressOperand := operands at: 1.
+ 	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
+ 		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
+ 	(self isAddressRelativeToVarBase: addressOperand) ifTrue:
+ 		[save1 := operands at: 1.
+ 		 operands
+ 			at: 1 put: addressOperand - cogit varBaseAddress;
+ 			at: 2 put: VarBaseReg.
+ 		 self concretizeMoveRMwr.
+ 		 operands
+ 			at: 1 put: save1;
+ 			at: 2 put: 0.
+ 		^machineCodeSize].
+ 	reg = RAX
+ 		ifTrue: [offset := 0]
+ 		ifFalse:
+ 			[machineCode
+ 				at: 0 put: (self rexR: 0 x: 0 b: reg);
+ 				at: 1 put: 16r90 + (reg \\ 8).
+ 			 offset := 2].
+ 	machineCode
+ 		at: 0 + offset put: 16r48;
+ 		at: 1 + offset put: 16rA3;
+ 		at: 2 + offset put: (addressOperand bitAnd: 16rFF);
+ 		at: 3 + offset put: (addressOperand >> 8 bitAnd: 16rFF);
+ 		at: 4 + offset put: (addressOperand >> 16 bitAnd: 16rFF);
+ 		at: 5 + offset put: (addressOperand >> 24 bitAnd: 16rFF);
+ 		at: 6 + offset put: (addressOperand >> 32 bitAnd: 16rFF);
+ 		at: 7 + offset put: (addressOperand >> 40 bitAnd: 16rFF);
+ 		at: 8 + offset put: (addressOperand >> 48 bitAnd: 16rFF);
+ 		at: 9 + offset put: (addressOperand >> 56 bitAnd: 16rFF).
+ 	reg = RAX ifTrue:
+ 		[^machineCodeSize := 10].
+ 	machineCode
+ 		at: 12 put: (machineCode at: 0);
+ 		at: 13 put: (machineCode at: 1).
+ 	^machineCodeSize := 14!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeRetN (in category 'generate machine code') -----
+ concretizeRetN
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| offset |
+ 	offset := operands at: 0.
+ 	offset = 0 ifTrue:
+ 		[machineCode at: 0 put: 16rC3.
+ 		^machineCodeSize := 1].
+ 	machineCode
+ 		at: 0 put: 16rC2;
+ 		at: 1 put: (offset bitAnd: 16rFF);
+ 		at: 2 put: (offset >> 8).
+ 	^machineCodeSize := 3!

Item was added:
+ ----- Method: CogX64Compiler>>fullCallsAreRelative (in category 'abi') -----
+ fullCallsAreRelative
+ 	^false!

Item was added:
+ ----- Method: CogX64Compiler>>genGetLeafCallStackPointerFunction (in category 'assertions') -----
+ genGetLeafCallStackPointerFunction
+ 	cogit
+ 		MoveR: RSP R: RAX;
+ 		RetN: 0!

Item was added:
+ ----- Method: CogX64Compiler>>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)."
+ 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
+ 	cogit MoveAw: cogit cFramePointerAddress R: FPReg.
+ 	^0!

Item was added:
+ ----- Method: CogX64Compiler>>genLoadStackPointers (in category 'smalltalk calling convention') -----
+ genLoadStackPointers
+ 	"Switch back to the Smalltalk stack. Assign SPReg first
+ 	 because typically it is used immediately afterwards."
+ 	cogit MoveAw: cogit stackPointerAddress R: SPReg.
+ 	cogit MoveAw: cogit framePointerAddress R: FPReg.
+ 	^0!

Item was added:
+ ----- Method: CogX64Compiler>>genPassConst:asArgument: (in category 'abi') -----
+ genPassConst: constant asArgument: zeroRelativeArgIndex
+ 	zeroRelativeArgIndex caseOf: {
+ 		[0] -> [cogit MoveCq: constant R: RDI].
+ 		[1] -> [cogit MoveCq: constant R: RSI].
+ 		[2] -> [cogit MoveCq: constant R: RDX].
+ 		[3] -> [cogit MoveCq: constant R: RCX].}.
+ 	^0!

Item was added:
+ ----- Method: CogX64Compiler>>genPassReg:asArgument: (in category 'abi') -----
+ genPassReg: abstractRegister asArgument: zeroRelativeArgIndex
+ 	zeroRelativeArgIndex caseOf: {
+ 		[0] -> [cogit MoveR: abstractRegister R: RDI].
+ 		[1] -> [cogit MoveR: abstractRegister R: RSI].
+ 		[2] -> [cogit MoveR: abstractRegister R: RDX].
+ 		[3] -> [cogit MoveR: abstractRegister R: RCX].}.
+ 	^0!

Item was added:
+ ----- Method: CogX64Compiler>>genPushRegisterArgsForNumArgs:scratchReg: (in category 'smalltalk calling convention') -----
+ genPushRegisterArgsForNumArgs: numArgs scratchReg: scratchReg
+ 	"Ensure that the register args are pushed before the retpc for arity <= self numRegArgs.  This
+ 	 isn't as clumsy on a RISC.  But putting the receiver and args above the return address
+ 	 means the CoInterpreter has a single machine-code frame format which saves us a lot of work.
+ 	 N.B. Take great care to /not/ smash TempReg, which is used in directed send marshalling.
+ 	 We could use XCHG to swap the ReceiverResultReg and top-of-stack return address, pushing the
+ 	 the ret pc (now in ReceiverResultReg) later, but XCHG is very slow.  We can use SendNumArgsReg
+ 	 because it is only live in sends of arity >= (NumSendTrampolines - 1)."
+ 	self assert: cogit numRegArgs < (NumSendTrampolines - 1).
+ 	numArgs <= cogit numRegArgs ifTrue:
+ 		[self assert: cogit numRegArgs <= 2.
+ 		 false "these two variants show the same performance on Intel Core i7, but the second one may be shorter."
+ 			ifTrue:
+ 				[cogit MoveMw: 0 r: SPReg R: scratchReg. "Save return pc"
+ 				 numArgs > 0 ifTrue:
+ 					[cogit PushR: Arg0Reg.
+ 					 numArgs > 1 ifTrue:
+ 						[cogit PushR: Arg1Reg]].
+ 				 cogit PushR: scratchReg.
+ 				 cogit MoveR: ReceiverResultReg Mw: objectMemory wordSize * (1 + numArgs) r: SPReg]
+ 			ifFalse:
+ 				["a.k.a.
+ 					cogit gen: XCHGMwrR operand: 0 operand: SPReg operand: ReceiverResultReg.
+ 				  but XCHG is slow."
+ 				 cogit MoveMw: 0 r: SPReg R: scratchReg. "Save return pc"
+ 				 cogit MoveR: ReceiverResultReg Mw: 0 r: SPReg.
+ 				 numArgs > 0 ifTrue:
+ 					[cogit PushR: Arg0Reg.
+ 					 numArgs > 1 ifTrue:
+ 						[cogit PushR: Arg1Reg]].
+ 				 cogit PushR: scratchReg]] "Restore return address"!

Item was added:
+ ----- Method: CogX64Compiler>>genSaveStackPointers (in category 'smalltalk calling convention') -----
+ genSaveStackPointers
+ 	"Save the frame and stack pointer registers to the framePointer
+ 	 and stackPointer variables.  Used to save the machine code frame
+ 	 for use by the run-time when calling into the CoInterpreter run-time."
+ 	cogit MoveR: FPReg Aw: cogit framePointerAddress.
+ 	cogit MoveR: SPReg Aw: cogit stackPointerAddress.
+ 	^0!

Item was added:
+ ----- Method: CogX64Compiler>>hasLinkRegister (in category 'testing') -----
+ hasLinkRegister
+ 	^false!

Item was added:
+ ----- Method: CogX64Compiler>>isAddressRelativeToVarBase: (in category 'testing') -----
+ isAddressRelativeToVarBase: varAddress
+ 	<inline: true>
+ 	<var: #varAddress type: #usqInt>
+ 	"Support for addressing variables off the dedicated VarBaseReg.  Allow for 16k of variables.
+ 	 The x64 supports 32-bit offsets, but we choose not to address everything from VarBaseReg."
+ 	^varAddress notNil
+ 	  and: [varAddress >= cogit varBaseAddress
+ 	  and: [varAddress - cogit varBaseAddress < (1 << 14)]]!

Item was added:
+ ----- Method: CogX64Compiler>>leafCallStackPointerDelta (in category 'abi') -----
+ leafCallStackPointerDelta
+ 	"Answer the delta from the stack pointer after a call to the stack pointer
+ 	 immediately prior to the call.  This is used to compute the stack pointer
+ 	 immediately prior to  call from within a leaf routine, which in turn is used
+ 	 to capture the c stack pointer to use in trampolines back into the C run-time."
+ 	^8!

Item was changed:
  ----- Method: CogX64Compiler>>machineCodeBytes (in category 'generate machine code') -----
  machineCodeBytes
  	"Answer the maximum number of bytes of machine code generated for any abstract instruction.
+ 	 e.g. xchg %rdx, %rax; movq $0x12345678ABCDEF0, %(rax); xchg %rdx, %rax => 48 92 48 A3 F0 DE BC 9A 78 56 34 12 48 92"
+ 	^14!
- 	 e.g. movq $0x12345678ABCDEF0, %rax; jmp *%rax => 48 B8 F0 DE BC 9A 78 56 34 12 FF E0"
- 	^12!

Item was added:
+ ----- Method: CogX64Compiler>>nopsFrom:to: (in category 'generate machine code') -----
+ nopsFrom: startAddr to: endAddr
+ 	startAddr to: endAddr do:
+ 		[:p| objectMemory byteAt: p put: 16r90]!

Item was changed:
  ----- Method: CogX64CompilerTests>>testMoveAwR (in category 'tests') -----
  testMoveAwR
  	"self new testMoveAwR"
  	self concreteCompilerClass registersWithNamesDo:
  		[:reg :regname|
+ 		#(16r555555 16rAAAAAA 16r5A5A5A5A5A5A) do:
+ 			[:addr| | inst len totalsz |
- 		#(16r555555 16rAAAAAA) do:
- 			[:addr| | inst len |
  			inst := self gen: MoveAwR operand: addr operand: reg.
  			len := inst concretizeAt: 0.
+ 			totalsz := 0.
+ 			regname ~= '%rax' ifTrue:
+ 				[self processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended |
+ 						plainJane := self strip: str.
+ 						herIntended := 'xchgq %rax, ', regname.
+ 						self assert: (plainJane match: herIntended).
+ 						totalsz := sz]].
  			self processor
+ 				disassembleInstructionAt: totalsz
- 				disassembleInstructionAt: 0
  				In: inst machineCode object
  				into: [:str :sz| | plainJane herIntended |
- 					"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
  					plainJane := self strip: str.
+ 					herIntended := 'movq 0x', (addr printStringBase: 16 length: 16 padded: true), ', %rax'.
- 					herIntended := 'movl 0x', (addr hex allButFirst: 3), ', ', regname.
  					self assert: (plainJane match: herIntended).
+ 					totalsz := totalsz + sz].
+ 			regname ~= '%rax' ifTrue:
+ 				[self processor
+ 					disassembleInstructionAt: totalsz
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended |
+ 						plainJane := self strip: str.
+ 						herIntended := 'xchgq %rax, ', regname.
+ 						self assert: (plainJane match: herIntended).
+ 						totalsz := totalsz + sz]].
+ 			self assert: len = totalsz]]!
- 					self assert: len = sz]]]!

Item was changed:
  ----- Method: CogX64CompilerTests>>testMoveRAw (in category 'tests') -----
  testMoveRAw
  	"self new testMoveRAw"
  	self concreteCompilerClass registersWithNamesDo:
  		[:reg :regname|
+ 		#(16r555555 16rAAAAAA 16r5A5A5A5A5A5A) do:
+ 			[:addr| | inst len totalsz |
- 		#(16r555555 16rAAAAAA) do:
- 			[:addr| | inst len |
  			inst := self gen: MoveRAw operand: reg operand: addr.
  			len := inst concretizeAt: 0.
+ 			totalsz := 0.
+ 			regname ~= '%rax' ifTrue:
+ 				[self processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended |
+ 						plainJane := self strip: str.
+ 						herIntended := 'xchgq %rax, ', regname.
+ 						self assert: (plainJane match: herIntended).
+ 						totalsz := sz]].
  			self processor
+ 				disassembleInstructionAt: totalsz
- 				disassembleInstructionAt: 0
  				In: inst machineCode object
  				into: [:str :sz| | plainJane herIntended |
  					plainJane := self strip: str.
+ 					herIntended := 'movq %rax, 0x', (addr printStringBase: 16 length: 16 padded: true).
- 					herIntended := 'movl ', regname, ', 0x', (addr hex allButFirst: 3).
  					self assert: (plainJane match: herIntended).
+ 					totalsz := totalsz + sz].
+ 			regname ~= '%rax' ifTrue:
+ 				[self processor
+ 					disassembleInstructionAt: totalsz
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended |
+ 						plainJane := self strip: str.
+ 						herIntended := 'xchgq %rax, ', regname.
+ 						self assert: (plainJane match: herIntended).
+ 						totalsz := totalsz + sz]].
+ 			self assert: len = totalsz]]!
- 					self assert: len = sz]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>varBaseAddress (in category 'accessing') -----
+ varBaseAddress
+ 	"Answer a value that should be sufficiently high that var bare relative addressing is never generated."
+ 	^1 << 60!



More information about the Vm-dev mailing list