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

commits at source.squeak.org commits at source.squeak.org
Mon Sep 21 18:22:03 UTC 2015


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

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

Name: VMMaker.oscog-eem.1457
Author: eem
Time: 21 September 2015, 11:19:30.886 am
UUID: eb386c95-4dfd-464c-ac8f-d48208f11177
Ancestors: VMMaker.oscog-eem.1456

Add enough to get the simple conmditional jump test to work on the x64 alien.

Refactor assertSaneJumpTarget: up into AbstractInstructionTests.

Improve a comment or two.

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

Item was added:
+ ----- Method: AbstractInstructionTests>>assertSaneJumpTarget: (in category 'cogit compatibility') -----
+ assertSaneJumpTarget: jumpTarget
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
+ 
+ 	self assert: (self addressIsInInstructions: jumpTarget)!

Item was changed:
  ----- Method: AbstractInstructionTests>>runBinaryConditionalJumps: (in category 'running') -----
  runBinaryConditionalJumps: assertPrintBar
  	"self defaultTester runBinaryConditionalJumps: false"
  	| mask reg1 reg2 reg3 |
  	mask := (1 << self processor bitsInWord) - 1.
  	self concreteCompilerClass dataRegistersWithAccessorsDo:
  		[:n :get :set|
  		n = 0 ifTrue: [reg1 := get].
  		n = 1 ifTrue: [reg2 := set].
  		n = 2 ifTrue: [reg3 := set]].
  	#(	(JumpAbove > unsigned)			(JumpBelowOrEqual <= unsigned)
  		(JumpBelow < unsigned)			(JumpAboveOrEqual >= unsigned)
  		(JumpGreater > signed)			(JumpLessOrEqual <= signed)
  		(JumpLess < signed)				(JumpGreaterOrEqual >= signed)
  		(JumpZero = signed)				(JumpNonZero ~= signed)) do:
  		[:triple|
  		[:opName :relation :signednessOrResult| | opcode jumpNotTaken jumpTaken nop memory bogus |
  		self resetGen.
  		opcode := CogRTLOpcodes classPool at: opName.
  		self gen: CmpRR operand: 2 operand: 1.
  		jumpTaken := self gen: opcode.
  		self gen: MoveCqR operand: 0 operand: 0.
  		jumpNotTaken := self gen: Jump.
  		jumpTaken jmpTarget: (self gen: MoveCqR operand: 1 operand: 0).
  		jumpNotTaken jmpTarget: (nop := self gen: Nop).
  		memory := self generateInstructions.
  		"self processor disassembleFrom: 0 to: memory size in: memory on: Transcript"
  		bogus := false.
  		self pairs: (-2 to: 2)  do:
  			[:a :b| | taken |
  			self processor
  				reset;
+ 				perform: reg2 with: a signedIntToLong64;
+ 				perform: reg3 with: b signedIntToLong64.
- 				perform: reg2 with: a signedIntToLong;
- 				perform: reg3 with: b signedIntToLong.
  			[self processor singleStepIn: memory.
  			 self processor pc ~= nop address] whileTrue.
  			taken := (self processor perform: reg1) = 1.
  			assertPrintBar
  				ifTrue:
  					[self assert: taken = (signednessOrResult == #unsigned
  											ifTrue: [(a bitAnd: mask) perform: relation with: (b bitAnd: mask)]
  											ifFalse: [a perform: relation with: b])]
  				ifFalse:
  					[Transcript
  						nextPutAll: reg2; nextPut: $(; print: a; nextPutAll: ') '; nextPutAll: relation; space;
  						nextPutAll: reg3; nextPut: $(; print: b; nextPutAll: ') = ';
  						print: taken; cr; flush.
  					 taken = (signednessOrResult == #unsigned
  											ifTrue: [(a bitAnd: mask) perform: relation with: (b bitAnd: mask)]
  											ifFalse: [a perform: relation with: b]) ifFalse:
  						[bogus := true]]].
  			 bogus ifTrue:
  				[self processor printRegistersOn: Transcript.
  				 Transcript show: (self processor disassembleInstructionAt: jumpTaken address In: memory); cr]]
  					valueWithArguments: triple]!

Item was removed:
- ----- Method: CogARMCompilerTests>>assertSaneJumpTarget: (in category 'cogit compiler compatibility') -----
- assertSaneJumpTarget: jumpTarget
- 	<var: #jumpTarget type: #'AbstractInstruction *'>
- 
- 	self assert: (self addressIsInInstructions: jumpTarget)!

Item was changed:
  ----- Method: CogIA32Compiler>>mod:RM:RO: (in category 'encoding') -----
  mod: mod RM: regMode RO: regOpcode
+ 	"See ModR/M byte & opcode syntax
+ 	 In addition to the notation shown above in 'Mnemonic Syntax' on page 43,
+ 	 the following notation indicates the size and type of operands in the syntax of an instruction opcode:
+ 		/digit	Indicates that the ModRM byte specifies only one register or memory (r/m) operand.
+ 				The digit is specified by the ModRM reg field and is used as an instruction-opcode extension.
+ 				Valid digit values range from 0 to 7.
+ 		/r		Indicates that the ModRM byte specifies both a register operand and a reg/mem (register or memory) operand."
  	^mod << 6 + (regOpcode << 3) + regMode!

Item was removed:
- ----- Method: CogIA32CompilerTests>>assertSaneJumpTarget: (in category 'cogit compatibility') -----
- assertSaneJumpTarget: jumpTarget
- 	<var: #jumpTarget type: #'AbstractInstruction *'>
- 
- 	self assert: (self addressIsInInstructions: jumpTarget)!

Item was added:
+ ----- Method: CogInLineLiteralsX64Compiler>>isPCDependent (in category 'testing') -----
+ isPCDependent
+ 	"Answer if the receiver is a pc-dependent instruction."
+ 	^self isJump or: [opcode = AlignmentNops]!

Item was added:
+ ----- Method: CogInLineLiteralsX64Compiler>>sizePCDependentInstructionAt: (in category 'generate machine code') -----
+ sizePCDependentInstructionAt: eventualAbsoluteAddress
+ 	"Size a jump and set its address.  The target may be another instruction
+ 	 or an absolute address.  On entry the address inst var holds our virtual
+ 	 address. On exit address is set to eventualAbsoluteAddress, which is
+ 	 where this instruction will be output.  The span of a jump to a following
+ 	 instruction is therefore between that instruction's address and this
+ 	 instruction's address ((which are both still their virtual addresses), but the
+ 	 span of a jump to a preceeding instruction or to an absolute address is
+ 	 between that instruction's address (which by now is its eventual absolute
+ 	 address) or absolute address and eventualAbsoluteAddress."
+ 
+ 	| target maximumSpan abstractInstruction |
+ 	<var: #abstractInstruction type: #'AbstractInstruction *'>
+ 	opcode = AlignmentNops ifTrue:
+ 		[| alignment |
+ 		 address := eventualAbsoluteAddress.
+ 		 alignment := operands at: 0.
+ 		 ^machineCodeSize := (eventualAbsoluteAddress + (alignment - 1) bitAnd: alignment negated)
+ 							   - eventualAbsoluteAddress].
+ 	self assert: self isJump.
+ 	target := operands at: 0.
+ 	abstractInstruction := cogit cCoerceSimple: target to: #'AbstractInstruction *'.
+ 	(self isAnInstruction: abstractInstruction)
+ 		ifTrue:
+ 			[maximumSpan := abstractInstruction address
+ 							- (((cogit abstractInstruction: self follows: abstractInstruction)
+ 								ifTrue: [eventualAbsoluteAddress]
+ 								ifFalse: [address]) + 2)]
+ 		ifFalse:
+ 			[maximumSpan := target - (eventualAbsoluteAddress + 2)].
+ 	address := eventualAbsoluteAddress.
+ 	^machineCodeSize := opcode >= FirstShortJump
+ 							ifTrue:
+ 								[(self isQuick: maximumSpan)
+ 									ifTrue: [2]
+ 									ifFalse: [opcode = Jump
+ 												ifTrue: [5]
+ 												ifFalse: [6]]]
+ 							ifFalse:
+ 								[opcode caseOf:
+ 									{	[JumpLong]	->	[5].
+ 										[JumpFull]	->	[12].
+ 										[Call]		->	[5].
+ 										[CallFull]	->	[12] }]!

Item was added:
+ ----- Method: CogOutOfLineLiteralsX64Compiler>>isPCDependent (in category 'testing') -----
+ isPCDependent
+ 	"Answer if the receiver is a pc-dependent instruction.  With out-of-line literals any instruction
+ 	 that refers to a literal depends on the address of the literal, so add them in addition to the jumps."
+ 	^self isJump
+ 	  or: [opcode = AlignmentNops
+ 	  or: [opcode ~= Literal and: [dependent notNil and: [dependent opcode = Literal]]]]!

Item was changed:
  ----- Method: CogRTLOpcodes class>>initialize (in category 'class initialization') -----
  initialize
  	"Abstract opcodes are a compound of a one word operation specifier and zero or more operand type specifiers.
  	 e.g. MoveRR is the Move opcode with two register operand specifiers and defines a move register to
  	 register instruction from operand 0 to operand 1.  The word and register size is assumed to be either 32-bits on
  	 a 32-bit architecture or 64-bits on a 64-bit architecture.  The abstract machine is mostly a 2 address machine
  	 with the odd three address instruction added to better exploit RISCs.
  			(self initialize)
  	The operand specifiers are
  		R		- general purpose register
  		Rd		- double-precision floating-point register
  		Cq		- a `quick' constant that can be encoded in the minimum space possible.
  		Cw		- a constant with word size where word is the default operand size for the Smalltalk VM, 32-bits
  				  for a 32-bit VM, 64-bits for a 64-bit VM.  The generated constant must occupy the default number
  				  of bits.  This allows e.g. a garbage collector to update the value without invalidating the code.
  		C32	- a constant with 32 bit size.  The generated constant must occupy 32 bits.
  		C64	- a constant with 64 bit size.  The generated constant must occupy 64 bits.
  		Aw		- memory word at an absolute address
  		Ab		- memory byte at an absolute address
  		Mwr	- memory word whose address is at a constant offset from an address in a register
  		Mbr		- memory byte whose address is at a constant offset from an address in a register (zero-extended on read)
  		M16r	- memory 16-bit halfword whose address is at a constant offset from an address in a register
  		M32r	- memory 32-bit halfword whose address is at a constant offset from an address in a register
  		M64r	- memory 64-bit doubleword whose address is at a constant offset from an address in a register
  		XbrR	- memory word whose address is r * byte size away from an address in a register
  		X16rR	- memory word whose address is r * (2 bytes size) away from an address in a register
  		XwrR	- memory word whose address is r * word size away from an address in a register
  		XowrR	- memory word whose address is (r * word size) + o away from an address in a register (scaled indexed)
  
  	An alternative would be to decouple opcodes from operands, e.g.
  		Move := 1. Add := 2. Sub := 3...
  		RegisterOperand := 1. ConstantQuickOperand := 2. ConstantWordOperand := 3...
  	But not all combinations make sense and even fewer are used so we stick with the simple compound approach.
  
  	The assumption is that comparison and arithmetic instructions set condition codes and that move instructions
  	leave the condition codes unaffected.  In particular LoadEffectiveAddressMwrR does not set condition codes
  	although it can be used to do arithmetic.
  
  	Not all of the definitions in opcodeDefinitions below are implemented.  In particular we do not implement the
  	 XowrR scaled index addressing mode since it requires 4 operands.
  
  	Note that there are no generic division instructions defined, but a processor may define some.
  
  	Branch/Call ranges.  Jump[Cond] can be generated as short as possible.  Call/Jump[Cond]Long must be generated
  	in the same number of bytes irrespective of displacement since their targets may be updated, but they need only
  	span 16Mb, the maximum size of the code zone.  This allows e.g. ARM to use single-word call and jump instructions
  	for most calls and jumps.  CallFull/JumpFull must also be generated in the same number of bytes irrespective of
  	displacement for the same reason, but they must be able to span the full (32-bit or 64-bit) address space because
+ 	they are used to call code in the C runtime, which may be distant from the code zone.  CallFull/JumpFull are allowed
+ 	to use the cResultRegister as a scratch if required (e.g. on x64 where there is no direct 64-bit call or jump)."
- 	they are used to call code in the C runtime, which may be distant from the code zone."
  
  	| opcodeNames refs |
  	self flag: 'GPRegMin and GPRegMax are poorly thought-out and should instead defer to the backEnd for allocateable registers.'.
  	"A small fixed set of abstract registers are defined and used in code generation
  	 for Smalltalk code, and executes on stack pages in the stack zone.
  	 These are mapped to processor-specific registers by concreteRegister:"
  	FPReg := -1.	"A frame pointer is used for Smalltalk frames."
  	SPReg := -2.
  	ReceiverResultReg := GPRegMax := -3. "The receiver at point of send, and return value from a send"
  	TempReg := -4.
  	ClassReg := -5.							"The inline send cache class tag is in this register, loaded at the send site"
  	SendNumArgsReg := -6.				"Sends > 2 args set the arg count in this reg"
  	Arg0Reg := -7.							"In the StackToregisterMappingCogit 1 & 2 arg sends marshall into these registers."
  	Arg1Reg := GPRegMin := -8.
  
  	"Floating-point registers"
  	DPFPReg0 := -9.
  	DPFPReg1 := -10.
  	DPFPReg2 := -11.
  	DPFPReg3 := -12.
  	DPFPReg4 := -13.
  	DPFPReg5 := -14.
  	DPFPReg6 := -15.
  	DPFPReg7 := -16.
  
  	"RISC-specific"
  	LinkReg := -17.
  	RISCTempReg := -18.
  	PCReg := -19.
  	VarBaseReg := -20. "If useful, points to base of interpreter variables."
  
  	opcodeNames := #("Noops & Pseudo Ops"
  						Label
  						Literal			"a word-sized literal"
  						AlignmentNops
  						FillBytesFrom	"output operand 0's worth of bytes from the address in operand 1"
  						Fill8				"output a byte's worth of bytes with operand 0"
  						Fill16			"output two byte's worth of bytes with operand 0"
  						Fill32			"output four byte's worth of bytes with operand 0"
  						FillFromWord	"output BytesPerWord's worth of bytes with operand 0 + operand 1"
  						Nop
  
  						"Control"
  						Call					"call within the code zone"
  						CallFull				"call anywhere within the full address space"
  						RetN
  						JumpR				"Not a regular jump, i.e. not pc dependent."
  						Stop				"Halt the processor"
  
  						"N.B.  Jumps are contiguous.  Long and Full jumps are contigiuous within them.  See FirstJump et al below"
  						JumpFull			"Jump anywhere within the address space"
  						JumpLong			"Jump anywhere within the 16mb code zone."
  						JumpLongZero			"a.k.a. JumpLongEqual"
  						JumpLongNonZero		"a.k.a. JumpLongNotEqual"
  						Jump				"short jumps; can be encoded in as few bytes as possible; will not be disturbed by GC or relocation."
  						JumpZero				"a.k.a. JumpEqual"
  						JumpNonZero			"a.k.a. JumpNotEqual"
  						JumpNegative
  						JumpNonNegative
  						JumpOverflow
  						JumpNoOverflow
  						JumpCarry
  						JumpNoCarry
  						JumpLess			"signed"
  						JumpGreaterOrEqual
  						JumpGreater
  						JumpLessOrEqual
  						JumpBelow			"unsigned"
  						JumpAboveOrEqual
  						JumpAbove
  						JumpBelowOrEqual
  
  						JumpFPEqual
  						JumpFPNotEqual
  						JumpFPLess
  						JumpFPLessOrEqual
  						JumpFPGreater
  						JumpFPGreaterOrEqual
  						JumpFPOrdered
  						JumpFPUnordered
  
  						"Data Movement; destination is always last operand"
  						MoveRR
  						MoveAwR
  						MoveRAw
  						MoveAbR
  						MoveRAb
  						MoveMwrR MoveRMwr MoveXwrRR MoveRXwrR MoveXowrR MoveRXowr
  						MoveM16rR MoveRM16r MoveX16rRR MoveRX16rR
  						MoveM32rR MoveRM32r MoveX32rRR MoveRX32rR
  						MoveMbrR MoveRMbr MoveXbrRR MoveRXbrR
  						MoveCqR MoveCwR MoveC32R MoveC64R
  						MoveRdRd MoveM64rRd MoveRdM64r
  						PopR PushR PushCq PushCw
  						PrefetchAw
  
  						"Arithmetic; destination is always last operand except Cmp; CmpXR is SubRX with no update of result"
  						LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR "Variants of add/multiply"
  						NegateR "2's complement negation"
  						ArithmeticShiftRightCqR ArithmeticShiftRightRR
  						LogicalShiftRightCqR LogicalShiftRightRR
  						LogicalShiftLeftCqR LogicalShiftLeftRR
  
  						CmpRR AddRR SubRR AndRR OrRR XorRR MulRR
  						CmpCqR AddCqR SubCqR AndCqR OrCqR TstCqR XorCqR MulCqR
  						CmpCwR AddCwR SubCwR AndCwR OrCwR XorCwR MulCwR
  
  						AndCqRR
  
  						CmpRdRd AddRdRd SubRdRd MulRdRd DivRdRd SqrtRd
  
  						"Conversion"
  						ConvertRRd
  
  						LastRTLCode).
  
  	"Magic auto declaration. Add to the classPool any new variables and nuke any obsolete ones, and assign values"
  	"Find the variables directly referenced by this method"
  	refs := (thisContext method literals select: [:l| l isVariableBinding and: [classPool includesKey: l key]]) collect:
  				[:ea| ea key].
  	"Move to Undeclared any opcodes in classPool not in opcodes or this method."
  	(classPool keys reject: [:k| (opcodeNames includes: k) or: [refs includes: k]]) do:
  		[:k|
  		Undeclared declare: k from: classPool].
  	"Declare as class variables and number elements of opcodeArray above"
  	opcodeNames withIndexDo:
  		[:classVarName :value|
  		self classPool
  			declare: classVarName from: Undeclared;
  			at: classVarName put: value].
  
  	"For CogAbstractInstruction>>isJump etc..."
  	FirstJump := JumpFull.
  	LastJump := JumpFPUnordered.
  	FirstShortJump := Jump.
  
  	"And now initialize the backends; they add their own opcodes and hence these must be reinitialized."
  	(Smalltalk classNamed: #CogAbstractInstruction) ifNotNil:
  		[:cogAbstractInstruction| cogAbstractInstruction allSubclasses do: [:sc| sc initialize]]!

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]					-> [^1].
  		[IDIVR]					-> [^2].
  		[IMULRR]				-> [^3].
  		[CPUID]					-> [^2].
  		[CMPXCHGAwR]			-> [^7].
  		[CMPXCHGMwrR]		-> [^8].
  		[LFENCE]				-> [^3].
  		[MFENCE]				-> [^3].
  		[SFENCE]				-> [^3].
  		[LOCK]					-> [^1].
  		[XCHGAwR]				-> [^6].
  		[XCHGMwrR]			-> [^7].
  		[XCHGRR]				-> [^2]."
  		"Control"
+ 		[CallFull]					-> [^12].
- 		[CallFull]					-> [^5].
  		[Call]						-> [^5].
  		[JumpR]						-> [^2].
+ 		[JumpFull]					-> [self resolveJumpTarget. ^12].
- 		[JumpFull]					-> [self resolveJumpTarget. ^5].
  		[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 isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[AndCqR]		-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[CmpCqR]		-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[OrCqR]			-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[SubCqR]		-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[TstCqR]		-> [^((self isQuick: (operands at: 0)) and: [(self concreteRegister: (operands at: 1)) < 4])
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[AddCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[AndCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[CmpCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[OrCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[SubCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
+ 		[XorCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]]."
+ 		[AddRR]			-> [^3].
+ 		[AndRR]			-> [^3].
+ 		[CmpRR]		-> [^3].
+ 		[OrRR]			-> [^3].
+ 		[XorRR]			-> [^3].
+ 		[SubRR]			-> [^3].
+ 		[NegateR]		-> [^3].
+ 		"[LoadEffectiveAddressMwrR]
- 		[XorCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
- 		[AddRR]			-> [^2].
- 		[AndRR]			-> [^2].
- 		[CmpRR]		-> [^2].
- 		[OrRR]			-> [^2].
- 		[XorRR]			-> [^2].
- 		[SubRR]			-> [^2].
- 		[NegateR]		-> [^2].
- 		[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].
- 		"[MoveCqR]		-> [^(operands at: 0) = 0 ifTrue: [2] ifFalse: [5]].
- 		[MoveCwR]		-> [^5].
- 		[MoveRR]		-> [^2].
  		[MoveRdRd]		-> [^4].
+ 		"[MoveAwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
- 		[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: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											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: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											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]			-> [^1].
  		[PushR]			-> [^1].
  		[PushCq]		-> [^(self isQuick: (operands at: 0)) ifTrue: [2] ifFalse: [5]].
  		[PushCw]		-> [^5].
  		[PrefetchAw]	-> [^self hasSSEInstructions ifTrue: [7] ifFalse: [0]]."
  		"Conversion"
  		"[ConvertRRd]	-> [^4]" }.
  	^0 "to keep C compiler quiet"!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeCmpRR (in category 'generate machine code') -----
+ concretizeCmpRR
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| regLHS regRHS |
+ 	"CmpRR RHS LHS computes LHS - RHS, i.e. apparently reversed.  You have to think subtract."
+ 	regRHS := self concreteRegister: (operands at: 0).
+ 	regLHS := self concreteRegister: (operands at: 1).
+ 	machineCode
+ 		at: 0 put: (self rexR: regLHS x: 0 b: regRHS);
+ 		at: 1 put: 16r39;
+ 		at: 2 put: (self mod: ModReg RM: regLHS RO: regRHS).
+ 	^machineCodeSize := 3!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeConditionalJump: (in category 'generate machine code') -----
+ concretizeConditionalJump: conditionCode
+ 	"Will get inlined into concretizeAt: switch."
+ 	"Sizing/generating jumps.
+ 		Jump targets can be to absolute addresses or other abstract instructions.
+ 		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
+ 		Otherwise instructions must have a machineCodeSize which must be kept to."
+ 	<inline: true>
+ 	| offset |
+ 	offset := self computeJumpTargetOffsetPlus: 2.
+ 	(machineCodeSize = 0 "size not determined because no sizeJump pass; generating initial trampolines"
+ 		ifTrue: [self isQuick: offset]
+ 		ifFalse: [machineCodeSize = 2]) ifTrue:
+ 		[machineCode
+ 			at: 0 put: 16r70 + conditionCode;
+ 			at: 1 put: (offset bitAnd: 16rFF).
+ 		 ^machineCodeSize := 2].
+ 	^self concretizeConditionalJumpLong: conditionCode!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeJump (in category 'generate machine code') -----
+ concretizeJump
+ 	"Will get inlined into concretizeAt: switch."
+ 	"Sizing/generating jumps.
+ 		Jump targets can be to absolute addresses or other abstract instructions.
+ 		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
+ 		Otherwise instructions must have a machineCodeSize which must be kept to."
+ 	<inline: true>
+ 	| jumpTarget offset |
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
+ 	jumpTarget := cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'.
+ 	cogit assertSaneJumpTarget: jumpTarget.
+ 	(self isAnInstruction: jumpTarget) ifTrue:
+ 		[jumpTarget := cogit cCoerceSimple: jumpTarget address to: #'AbstractInstruction *'].
+ 	self assert: jumpTarget ~= 0.
+ 	offset := jumpTarget signedIntFromLong - (address + 2) signedIntFromLong.
+ 	(machineCodeSize = 0 "size not determined because no sizeJump pass; generating initial trampolines"
+ 		ifTrue: [self isQuick: offset]
+ 		ifFalse: [machineCodeSize = 2]) ifTrue:
+ 		[machineCode
+ 			at: 0 put: 16rEB;
+ 			at: 1 put: (offset bitAnd: 16rFF).
+ 		 ^machineCodeSize := 2].
+ 	offset := jumpTarget signedIntFromLong - (address + 5) signedIntFromLong.
+ 	machineCode
+ 		at: 0 put: 16rE9;
+ 		at: 1 put: (offset bitAnd: 16rFF);
+ 		at: 2 put: (offset >> 8 bitAnd: 16rFF);
+ 		at: 3 put: (offset >> 16 bitAnd: 16rFF);
+ 		at: 4 put: (offset >> 24 bitAnd: 16rFF).
+ 	^machineCodeSize := 5!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeMoveCqR (in category 'generate machine code') -----
+ concretizeMoveCqR
+ 	"Will get inlined into concretizeAt: switch.
+ 	 On x64 we can short-cut mov 0, reg using xor, and use 32-bit displacement, signed or unsigned, if possible."
+ 	<inline: true>
+ 	| value reg |
+ 	value := operands at: 0.
+ 	(self is32BitSignedImmediate: value) ifFalse:
+ 		[^self concretizeMoveCwR].
+ 	reg := self concreteRegister: (operands at: 1).
+ 	machineCode at: 0 put: (self rexR: reg x: 0 b: reg).
+ 	value = 0 ifTrue:
+ 		[machineCode
+ 			at: 1 put: 16r31;
+ 			at: 2 put: (self mod: ModReg RM: reg RO: reg).
+ 		^machineCodeSize := 3].
+ 	machineCode
+ 		at: 1 put: 16rC7;
+ 		at: 2 put: (self mod: ModReg RM: reg RO: reg);
+ 		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>>concretizeMoveCwR (in category 'generate machine code') -----
+ concretizeMoveCwR
+ 	"Will get inlined into concretizeAt: switch.
+ 	 Note that for quick constants, xor reg,reg, movq r8 may be shorter.
+ 	 We don't consider it worthwhile for other  than 0."
+ 	<inline: true>
+ 	| value reg |
+ 	value := operands at: 0.
+ 	reg := self concreteRegister: (operands at: 1).
+ 	machineCode
+ 		at: 0 put: (self rexR: reg x: 0 b: reg);
+ 		at: 1 put: 16rB8 + (reg bitAnd: 7);
+ 		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);
+ 		at: 6 put: (value >> 32 bitAnd: 16rFF);
+ 		at: 7 put: (value >> 40 bitAnd: 16rFF);
+ 		at: 8 put: (value >> 48 bitAnd: 16rFF);
+ 		at: 9 put: (value >> 56 bitAnd: 16rFF).
+ 	^machineCodeSize := 10!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeNop (in category 'generate machine code') -----
+ concretizeNop
+ 	<inline: true>
+ 	machineCode at: 0 put: 16r90.
+ 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogX64Compiler>>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."
  	<returnTypeC: #void>
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]				-> [^self concretizeLabel].
  		[AlignmentNops]	-> [^self concretizeAlignmentNops].
  		[Fill16]				-> [^self concretizeFill16].
  		[Fill32]				-> [^self concretizeFill32].
  		[FillFromWord]		-> [^self concretizeFillFromWord].
  		[Nop]				-> [^self concretizeNop].
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^self concretizeCDQ].
  		[IDIVR]					-> [^self concretizeIDIVR].
  		[IMULRR]				-> [^self concretizeMulRR].
  		[CPUID]					-> [^self concretizeCPUID].
  		[CMPXCHGAwR]			-> [^self concretizeCMPXCHGAwR].
  		[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR].
  		[LFENCE]				-> [^self concretizeFENCE: 5].
  		[MFENCE]				-> [^self concretizeFENCE: 6].
  		[SFENCE]				-> [^self concretizeFENCE: 7].
  		[LOCK]					-> [^self concretizeLOCK].
  		[XCHGAwR]				-> [^self concretizeXCHGAwR].
  		[XCHGMwrR]			-> [^self concretizeXCHGMwrR].
  		[XCHGRR]				-> [^self concretizeXCHGRR].
  		"Control"
  		[Call]					-> [^self concretizeCall].
+ 		[CallFull]				-> [^self concretizeCallFull].
- 		[CallFull]				-> [^self concretizeCall].
  		[JumpR]					-> [^self concretizeJumpR].
+ 		[JumpFull]				-> [^self concretizeJumpFull].
- 		[JumpFull]				-> [^self concretizeJumpLong].
  		[JumpLong]				-> [^self concretizeJumpLong].
  		[JumpLongZero]		-> [^self concretizeConditionalJump: 16r4].
  		[JumpLongNonZero]	-> [^self concretizeConditionalJump: 16r5].
  		[Jump]					-> [^self concretizeJump].
  		"Table B-1 Intel® 64 and IA-32 Architectures Software Developer's Manual Volume 1: Basic Architecture"
  		[JumpZero]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpNonZero]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpNegative]			-> [^self concretizeConditionalJump: 16r8].
  		[JumpNonNegative]		-> [^self concretizeConditionalJump: 16r9].
  		[JumpOverflow]			-> [^self concretizeConditionalJump: 16r0].
  		[JumpNoOverflow]		-> [^self concretizeConditionalJump: 16r1].
  		[JumpCarry]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpNoCarry]			-> [^self concretizeConditionalJump: 16r3].
  		[JumpLess]				-> [^self concretizeConditionalJump: 16rC].
  		[JumpGreaterOrEqual]	-> [^self concretizeConditionalJump: 16rD].
  		[JumpGreater]			-> [^self concretizeConditionalJump: 16rF].
  		[JumpLessOrEqual]		-> [^self concretizeConditionalJump: 16rE].
  		[JumpBelow]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpAboveOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpAbove]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpBelowOrEqual]	-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPEqual]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpFPNotEqual]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpFPLess]				-> [^self concretizeConditionalJump: 16r2].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpFPGreater]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpFPLessOrEqual]		-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPOrdered]			-> [^self concretizeConditionalJump: 16rB].
  		[JumpFPUnordered]			-> [^self concretizeConditionalJump: 16rA].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeAddCqR].
  		[AddCwR]					-> [^self concretizeAddCwR].
  		[AddRR]						-> [^self concretizeAddRR].
  		[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58].
  		[AndCqR]					-> [^self concretizeAndCqR].
  		[AndCwR]					-> [^self concretizeAndCwR].
  		[AndRR]						-> [^self concretizeAndRR].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[CmpCqR]					-> [^self concretizeCmpCqR].
  		[CmpCwR]					-> [^self concretizeCmpCwR].
  		[CmpRR]					-> [^self concretizeCmpRR].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
  		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59].
  		[OrCqR]						-> [^self concretizeOrCqR].
  		[OrCwR]					-> [^self concretizeOrCwR].
  		[OrRR]						-> [^self concretizeOrRR].
  		[SubCqR]					-> [^self concretizeSubCqR].
  		[SubCwR]					-> [^self concretizeSubCwR].
  		[SubRR]						-> [^self concretizeSubRR].
  		[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C].
  		[SqrtRd]						-> [^self concretizeSqrtRd].
  		[XorCwR]						-> [^self concretizeXorCwR].
  		[XorRR]							-> [^self concretizeXorRR].
  		[NegateR]						-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]			-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeMoveRR].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeMoveRMbr].
  		[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] }!

Item was added:
+ ----- Method: CogX64Compiler>>is32BitSignedImmediate: (in category 'testing') -----
+ is32BitSignedImmediate: a64BitUnsignedOperand
+ 	^(a64BitUnsignedOperand >> 31) signedIntFromLong between: -1 and: 0!

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. movq $0x12345678ABCDEF0, %rax; jmp *%rax => 48 B8 F0 DE BC 9A 78 56 34 12 FF E0"
+ 	^12!
- 	 e.g. lock movsd  0x400(%rsp),%xmm4 => f0 f2 0f 10 a4 24 00 04 00 00"
- 	^10!

Item was added:
+ ----- Method: Integer>>signedInt64FromLong (in category '*VMMaker-interpreter simulator') -----
+ signedInt64FromLong
+ 	"Self is a signed or unsigned 32-bit integer"
+ 
+ 	| sign |
+ 	self < 0 ifTrue: [^self].
+ 	sign := self bitAnd: 16r8000000000000000.
+ 	sign = 0 ifTrue: [^ self].
+ 	^ self - sign - sign!

Item was added:
+ ----- Method: Integer>>signedIntToLong64 (in category '*VMMaker-interpreter simulator') -----
+ signedIntToLong64
+ 	"Produces a 64-bit value in twos-comp form.  Sorry no error checking"
+ 
+ 	self >= 0
+ 		ifTrue: [^ self]
+ 		ifFalse: [^ self + 16r8000000000000000 + 16r8000000000000000]
+ !



More information about the Vm-dev mailing list