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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 5 02:56:23 UTC 2015


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

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

Name: VMMaker.oscog-eem.1551
Author: eem
Time: 4 December 2015, 6:54:29.867 pm
UUID: 6888417d-b2bd-4ff5-9dea-d29090173d97
Ancestors: VMMaker.oscog-eem.1550

x64 Cogit: Lift restriction on OpCqR that value must be 32-bits.
  Correct a comment.

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

Item was added:
+ ----- Method: CogInLineLiteralsX64Compiler>>computeSizeOfArithCqR (in category 'generate machine code') -----
+ computeSizeOfArithCqR
+ 	"With CqR we assume constants are 32-bits or less."
+ 	<inline: true>
+ 	(self isQuick: (operands at: 0)) ifTrue:
+ 		[^4].
+ 	(self isSignExtendedFourByteValue: (operands at: 0)) ifTrue:
+ 		[^(self concreteRegister: (operands at: 1)) = RAX
+ 			ifTrue: [6]
+ 			ifFalse: [7]].
+ 	^10 "movabsq" + 3 "r op r"!

Item was changed:
  ----- Method: CogOutOfLineLiteralsX64Compiler>>concreteRegister: (in category 'encoding') -----
  concreteRegister: registerIndex
  	 "Map a possibly abstract register into a concrete one.  Abstract registers
  	  (defined in CogAbstractOpcodes) are all negative.  If registerIndex is
  	 negative assume it is an abstract register.
  
  	[1] Figure 3.4 Register Usage in
  		System V Application Binary Interface
  		AMD64 Architecture Processor Supplement
  
  
  	N.B. RAX RCX & RDX are caller-save (scratch) registers.  Hence we use RCX for class and RDX for
  		receiver/result since these are written in all normal sends."
  
  	^registerIndex
  		caseOf: {
  			[TempReg]				-> [RAX].
  			[ClassReg]				-> [RCX].
  			[ReceiverResultReg]	-> [RDX].
  			[SendNumArgsReg]		-> [R8].
  			[SPReg]					-> [RSP].
  			[FPReg]					-> [RBP].
  			[Arg0Reg]				-> [RDI]. "So as to agree with C ABI arg 0"
  			[Arg1Reg]				-> [RSI]. "So as to agree with C ABI arg 1"
  			[VarBaseReg]			-> [RBX]. "Must be callee saved"
+ 			"No need for a RISCTempReg because out-of-line literal loads imply no need for a special MoveCwR"
- 			"No need for a RISCTempReg because out-of-line literal loads imply
- 			 no need for a special MoveCwR, given movabsq only targets RAX"
  			"[RISCTempReg]		-> [R8]."
  			[Scratch0Reg]			-> [R9].
  			[Scratch1Reg]			-> [R10].
  			[Scratch2Reg]			-> [R11].
  			[Scratch3Reg]			-> [R12].
  			[Scratch4Reg]			-> [R13].
  			[Scratch5Reg]			-> [R14].
  			[Scratch6Reg]			-> [R15] }
  		otherwise:
  			[self assert: (registerIndex between: RAX and: R15).
  			 registerIndex]!

Item was changed:
  ----- Method: CogX64Compiler>>computeSizeOfArithCqR (in category 'generate machine code') -----
  computeSizeOfArithCqR
+ 	self subclassResponsibility!
- 	"With CqR we assume constants are 32-bits or less."
- 	<inline: true>
- 	^(self isQuick: (operands at: 0))
- 		ifTrue: [4]
- 		ifFalse: [(self concreteRegister: (operands at: 1)) = RAX
- 					ifTrue: [6]
- 					ifFalse: [7]]!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeArithCqRWithRO:raxOpcode: (in category 'generate machine code') -----
  concretizeArithCqRWithRO: regOpcode raxOpcode: raxOpcode
  	"Will get inlined into concretizeAt: switch."
  	<inline: false>
  	| value reg |
  	value := operands at: 0.
  	reg := self concreteRegister: (operands at: 1).
  	machineCode
  		at: 0 put: (self rexR: 0 x: 0 b: reg).
  	(self isQuick: value) ifTrue:
  		[machineCode
  			at: 1 put: 16r83;
  			at: 2 put: (self mod: ModReg RM: reg RO: regOpcode);
  			at: 3 put: (value bitAnd: 16rFF).
  		 ^machineCodeSize := 4].
+ 	(self isSignExtendedFourByteValue: value) ifTrue:
+ 		[reg = RAX ifTrue:
+ 			[machineCode
+ 				at: 1 put: raxOpcode;
+ 				at: 2 put: (value bitAnd: 16rFF);
+ 				at: 3 put: (value >> 8 bitAnd: 16rFF);
+ 				at: 4 put: (value >> 16 bitAnd: 16rFF);
+ 				at: 5 put: (value >> 24 bitAnd: 16rFF).
+ 			 ^machineCodeSize := 6].
+ 		machineCode
+ 			at: 1 put: 16r81;
+ 			at: 2 put: (self mod: ModReg RM: reg RO: regOpcode);
+ 			at: 3 put: (value bitAnd: 16rFF);
+ 			at: 4 put: (value >> 8 bitAnd: 16rFF);
+ 			at: 5 put: (value >> 16 bitAnd: 16rFF);
+ 			at: 6 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^machineCodeSize := 7].
+ 	^self concretizeArithCwR: (raxOpcode = 16r3D ifTrue: [16r39] ifFalse: [raxOpcode - 2])!
- 	self assert: value >> 32 = 0.
- 	reg = RAX ifTrue:
- 		[machineCode
- 			at: 1 put: raxOpcode;
- 			at: 2 put: (value bitAnd: 16rFF);
- 			at: 3 put: (value >> 8 bitAnd: 16rFF);
- 			at: 4 put: (value >> 16 bitAnd: 16rFF);
- 			at: 5 put: (value >> 24 bitAnd: 16rFF).
- 		 ^machineCodeSize := 6].
- 	machineCode
- 		at: 1 put: 16r81;
- 		at: 2 put: (self mod: ModReg RM: reg RO: regOpcode);
- 		at: 3 put: (value bitAnd: 16rFF);
- 		at: 4 put: (value >> 8 bitAnd: 16rFF);
- 		at: 5 put: (value >> 16 bitAnd: 16rFF);
- 		at: 6 put: (value >> 24 bitAnd: 16rFF).
- 	 ^machineCodeSize := 7!

Item was added:
+ ----- Method: CogX64Compiler>>isSignExtendedFourByteValue: (in category 'testing') -----
+ isSignExtendedFourByteValue: unsigned64BitValue
+ 	"Top 32 bits all the same as the bottom 32 bits' sign bit  implies we can use a sign-extended 4 byte offset."
+ 	^((self cCode: [unsigned64BitValue >>> 32]
+ 			inSmalltalk: [(unsigned64BitValue >> 32) signedIntFromLong]) + 1 bitXor: 1) = (unsigned64BitValue >> 31 bitAnd: 1)!



More information about the Vm-dev mailing list