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

commits at source.squeak.org commits at source.squeak.org
Tue Nov 3 21:51:09 UTC 2015


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

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

Name: VMMaker.oscog-eem.1505
Author: eem
Time: 3 November 2015, 1:48:54.159 pm
UUID: 4cd041e4-27ee-474f-b71c-f5230ed35af2
Ancestors: VMMaker.oscog-eem.1504

Cogit:
Clarify whether byte reads zero-extend by introducing CogAbstractInstruction>>byteReadsZeroExtend.  Make sure the x86 does zero-extend and take the easy route with x64 having it not zero-extend.  Leaving the ARM to Tim (thanks!!).

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

Item was added:
+ ----- Method: CogAbstractInstruction>>byteReadsZeroExtend (in category 'testing') -----
+ byteReadsZeroExtend
+ 	"Answer if a byte read, via MoveAbR, MoveMbrR, or MoveXbrRR zero-extends
+ 	 into the full register, or merely affects the least significant 8 bits of the
+ 	 the register.  By default the code generator assumes that byte reads
+ 	 to not zero extend.  Note that byte reads /must not/ sign extend."
+ 	^false!

Item was added:
+ ----- Method: CogIA32Compiler>>byteReadsZeroExtend (in category 'testing') -----
+ byteReadsZeroExtend
+ 	"Answer if a byte read, via MoveAbR, MoveMbrR, or MoveXbrRR zero-extends
+ 	 into the full register, or merely affects the least significant 8 bits of the
+ 	 the register.  By default the code generator assumes that byte reads
+ 	 to not zero extend.  Note that byte reads /must not/ sign extend.
+ 	 On x86 we always use movzbl"
+ 	^true!

Item was changed:
  ----- Method: CogIA32Compiler>>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]		-> [^(self concreteRegister: (operands at: 1)) = ESP
  										ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [5] ifFalse: [8]]
  										ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]].
  		[LFENCE]				-> [^3].
  		[MFENCE]				-> [^3].
  		[SFENCE]				-> [^3].
  		[LOCK]					-> [^1].
  		[XCHGAwR]				-> [^6].
  		[XCHGMwrR]			-> [^(self concreteRegister: (operands at: 1)) = ESP
  										ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]
  										ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [3] ifFalse: [6]]].
  		[XCHGRR]				-> [^((self concreteRegister: (operands at: 0)) = EAX
  									   or: [(self concreteRegister: (operands at: 1)) = EAX])
  										ifTrue: [1]
  										ifFalse: [2]].
  		"Control"
  		[CallFull]					-> [^5].
  		[Call]						-> [^5].
  		[JumpR]						-> [^2].
  		[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]			-> [^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: [2] ifFalse: [5]].
  		[MoveCwR]		-> [^5].
  		[MoveRR]		-> [^2].
  		[MoveRdRd]		-> [^4].
  		[MoveAwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[MoveRAw]		-> [^(self concreteRegister: (operands at: 0)) = EAX ifTrue: [5] ifFalse: [6]].
+ 		[MoveAbR]		-> [^7].
- 		[MoveAbR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[MoveRAb]		-> [^(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)) ~= EBP])
  												ifTrue: [2]
  												ifFalse: [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 concreteRegister: (operands at: 1)) = ESP
  								ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [5] ifFalse: [8]]
  								ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]].
  		[MoveRMbr]		-> [^(self concreteRegister: (operands at: 2)) = ESP
  								ifTrue: [7]
  								ifFalse: [(self isQuick: (operands at: 1)) ifTrue: [3] ifFalse: [6]]].
  		[MoveM16rR]	-> [^(self concreteRegister: (operands at: 1)) = ESP
  								ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [5] ifFalse: [8]]
  								ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]].
  		[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)) ~= EBP])
  												ifTrue: [2]
  												ifFalse: [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 changed:
  ----- Method: CogIA32Compiler>>concretizeMoveAbR (in category 'generate machine code') -----
  concretizeMoveAbR
+ 	"N.B. we zero-extend because we state byteReadsZeroExtend."
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| addressOperand reg |
  	addressOperand := operands at: 0.
  	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	reg := self concreteRegister: (operands at: 1).
- 	reg = EAX ifTrue:
- 		[machineCode
- 			at: 0 put: 16rA0;
- 			at: 1 put: (addressOperand bitAnd: 16rFF);
- 			at: 2 put: (addressOperand >> 8 bitAnd: 16rFF);
- 			at: 3 put: (addressOperand >> 16 bitAnd: 16rFF);
- 			at: 4 put: (addressOperand >> 24 bitAnd: 16rFF).
- 			^machineCodeSize := 5].
  	machineCode
+ 		at: 0 put: 16r0F;
+ 		at: 1 put: 16rB6;
+ 		at: 2 put: (self mod: ModRegInd RM: 5 RO: reg);
+ 		at: 3 put: (addressOperand bitAnd: 16rFF);
+ 		at: 4 put: (addressOperand >> 8 bitAnd: 16rFF);
+ 		at: 5 put: (addressOperand >> 16 bitAnd: 16rFF);
+ 		at: 6 put: (addressOperand >> 24 bitAnd: 16rFF).
+ 	^machineCodeSize := 7!
- 		at: 0 put: 16r8A;
- 		at: 1 put: (self mod: ModRegInd RM: 5 RO: reg);
- 		at: 2 put: (addressOperand bitAnd: 16rFF);
- 		at: 3 put: (addressOperand >> 8 bitAnd: 16rFF);
- 		at: 4 put: (addressOperand >> 16 bitAnd: 16rFF);
- 		at: 5 put: (addressOperand >> 24 bitAnd: 16rFF).
- 	^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveMbrR (in category 'generate machine code') -----
  concretizeMoveMbrR
+ 	"N.B. we zero-extend because we state byteReadsZeroExtend."
- 	"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).
  	srcReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16r0f;
  				at: 1 put: 16rb6;
  				at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 3 put: (offset bitAnd: 16rFF).
  			 ^machineCodeSize := 4].
  		machineCode
  			at: 0 put: 16r0f;
  			at: 1 put: 16rb6;
  			at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			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].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16r0f;
  			at: 1 put: 16rb6;
  			at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 4 put: (offset bitAnd: 16rFF).
  		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r0f;
  		at: 1 put: 16rb6;
  		at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  		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 changed:
  ----- Method: CogIA32Compiler>>concretizeMoveXbrRR (in category 'generate machine code') -----
  concretizeMoveXbrRR
+ 	"N.B. we zero-extend because we state byteReadsZeroExtend."
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| index base dest |
  	index := self concreteRegister: (operands at: 0).
  	base := self concreteRegister: (operands at: 1).
  	dest := self concreteRegister: (operands at: 2).
  	base ~= EBP ifTrue:
  		[machineCode
  			at: 0 put: 16r0F;
  			at: 1 put: 16rB6;
  			at: 2 put: (self mod: ModRegInd RM: 4 RO: dest);
  			at: 3 put: (self s: SIB1 i: index b: base).
  		 ^machineCodeSize := 4].
  	machineCode
  			at: 0 put: 16r0F;
  			at: 1 put: 16rB6;
  		at: 2 put: (self mod: ModRegRegDisp8 RM: 4 RO: dest);
  		at: 3 put: (self s: SIB1 i: index b: base);
  		at: 4 put: 0.
  	 ^machineCodeSize := 5!

Item was changed:
  ----- Method: CogIA32CompilerTests>>testMoveAbR (in category 'tests') -----
  testMoveAbR
  	"self new testMoveAbR"
+ 	CogIA32CompilerForTests registersWithNamesDo:
- 	CogIA32CompilerForTests byteRegistersWithNamesDo:
  		[:reg :regname|
  		#(16r555555 16rAAAAAA) do:
  			[:addr| | inst len |
  			inst := self gen: MoveAbR operand: addr operand: reg.
  			len := inst concretizeAt: 0.
+ 			self assert: inst byteReadsZeroExtend.
  			self processor
  				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 := 'movzbl 0x', (addr hex allButFirst: 3), ', ', regname.
- 					herIntended := 'movb 0x', (addr hex allButFirst: 3), ', ', regname.
  					self assert: (plainJane match: herIntended).
  					self assert: len = sz]]]!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genNoPopCreateClosureAt:numArgs:numCopied:contextNumArgs:large:inBlock: (in category 'bytecode generator support') -----
  genNoPopCreateClosureAt: bcpc numArgs: numArgs numCopied: numCopied contextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock
  	"Create a closure with the given startpc, numArgs and numCopied
  	 within a context with ctxtNumArgs, large if isLargeCtxt that is in a
  	 block if isInBlock.  Do /not/ initialize the copied values."
+ 	| numSlots byteSize header skip |
- 	| slotSize header skip |
  	<var: #skip type: #'AbstractInstruction *'>
  
  	"First get thisContext into ReceiverResultRega and thence in ClassReg."
  	self genGetActiveContextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock.
  	cogit MoveR: ReceiverResultReg R: ClassReg.
  
+ 	numSlots := ClosureFirstCopiedValueIndex + numCopied.
+ 	byteSize := objectMemory smallObjectBytesForSlots: numSlots.
- 	slotSize := ClosureFirstCopiedValueIndex + numCopied.
  	header := objectMemory
+ 					headerForSlots: numSlots
- 					headerForSlots: slotSize
  					format: objectMemory indexablePointersFormat
  					classIndex: ClassBlockClosureCompactIndex.
  	cogit
  		MoveAw: objectMemory freeStartAddress R: ReceiverResultReg;
  		MoveCq: (self low32BitsOf: header) R: TempReg;
  		MoveR: TempReg Mw: 0 r: ReceiverResultReg;
  		MoveCq: header >> 32 R: TempReg;
  		MoveR: TempReg Mw: 4 r: ReceiverResultReg;
+ 		LoadEffectiveAddressMw: byteSize r: ReceiverResultReg R: TempReg;
- 		MoveR: ReceiverResultReg R: TempReg;
- 		AddCq: (objectMemory smallObjectBytesForSlots: slotSize) R: TempReg;
  		MoveR: TempReg Aw: objectMemory freeStartAddress;
  		CmpCq: objectMemory getScavengeThreshold R: TempReg.
  	skip := cogit JumpBelow: 0.
  	cogit CallRT: ceScheduleScavengeTrampoline.
  	skip jmpTarget: cogit Label.
  
  	cogit
  		MoveR: ClassReg Mw: ClosureOuterContextIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
  		MoveCq: (objectMemory integerObjectOf: bcpc) R: TempReg;
  		MoveR: TempReg Mw: ClosureStartPCIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
  		MoveCq: (objectMemory integerObjectOf: numArgs) R: TempReg;
  		MoveR: TempReg Mw: ClosureNumArgsIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg.
  	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genNoPopCreateClosureAt:numArgs:numCopied:contextNumArgs:large:inBlock: (in category 'bytecode generator support') -----
+ genNoPopCreateClosureAt: bcpc numArgs: numArgs numCopied: numCopied contextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock
+ 	"Create a closure with the given startpc, numArgs and numCopied
+ 	 within a context with ctxtNumArgs, large if isLargeCtxt that is in a
+ 	 block if isInBlock.  Do /not/ initialize the copied values."
+ 	| numSlots byteSize header skip |
+ 	<var: #skip type: #'AbstractInstruction *'>
+ 
+ 	"First get thisContext into ReceiverResultRega and thence in ClassReg."
+ 	self genGetActiveContextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock.
+ 	cogit MoveR: ReceiverResultReg R: ClassReg.
+ 
+ 	numSlots := ClosureFirstCopiedValueIndex + numCopied.
+ 	byteSize := objectMemory smallObjectBytesForSlots: numSlots.
+ 	header := objectMemory
+ 					headerForSlots: numSlots
+ 					format: objectMemory indexablePointersFormat
+ 					classIndex: ClassBlockClosureCompactIndex.
+ 	cogit
+ 		MoveAw: objectMemory freeStartAddress R: ReceiverResultReg;
+ 		MoveCq: header R: TempReg;
+ 		MoveR: TempReg Mw: 0 r: ReceiverResultReg;
+ 		LoadEffectiveAddressMw: byteSize r: ReceiverResultReg R: TempReg;
+ 		MoveR: TempReg Aw: objectMemory freeStartAddress;
+ 		CmpCq: objectMemory getScavengeThreshold R: TempReg.
+ 	skip := cogit JumpBelow: 0.
+ 	cogit CallRT: ceScheduleScavengeTrampoline.
+ 	skip jmpTarget: cogit Label.
+ 
+ 	cogit
+ 		MoveR: ClassReg Mw: ClosureOuterContextIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
+ 		MoveCq: (objectMemory integerObjectOf: bcpc) R: TempReg;
+ 		MoveR: TempReg Mw: ClosureStartPCIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
+ 		MoveCq: (objectMemory integerObjectOf: numArgs) R: TempReg;
+ 		MoveR: TempReg Mw: ClosureNumArgsIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg.
+ 	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genGetRawSlotSizeOfNonImm:into: (in category 'compile abstract instructions') -----
  genGetRawSlotSizeOfNonImm: sourceReg into: destReg
  	"The raw numSlots field is the most significant byte of the 64-bit header word.
  	 MoveMbrR zero-extends."
+ 	cogit backEnd byteReadsZeroExtend ifFalse:
+ 		[self MoveCq: 0 R: destReg].
  	cogit MoveMb: 7 r: sourceReg R: destReg.
  	^0!

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: [4]
  									ifFalse: [7])
  								+ (((self concreteRegister: (operands at: 1)) bitAnd: 7) = RSP
  									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: [self moveCwRByteSize]]].
  		[MoveCwR]		-> [^(self inCurrentCompilation: (operands at: 0))
  								ifTrue: [7]
  								ifFalse: [self moveCwRByteSize]].
  		[MoveC32R]	-> [^7]. "N.B. Always inlined."
  		[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]]].
  		[MoveAbR]		-> [^(self isAddressRelativeToVarBase: (operands at: 0))
  								ifTrue: [7]
  								ifFalse: [(self concreteRegister: (operands at: 1)) = RAX ifTrue: [10] ifFalse: [14]]].
  		[MoveRAb]		-> [^(self isAddressRelativeToVarBase: (operands at: 1))
  								ifTrue: [7]
  								ifFalse: [(self concreteRegister: (operands at: 0)) = RAX ifTrue: [10] ifFalse: [14]]].
  		[MoveRMwr]	-> [self assert: (self is32BitSignedImmediate: (operands at: 1)).
  							^((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 assert: (self is32BitSignedImmediate: (operands at: 0)).
  							^((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])
- 												ifTrue: [4]
- 												ifFalse: [5]]
- 									ifFalse: [8])
  								+ (((self concreteRegister: (operands at: 1)) bitAnd: 7) = RSP
  									ifTrue: [1]
  									ifFalse: [0])].
  		[MoveRMbr]		-> [self assert: (self is32BitSignedImmediate: (operands at: 1)).
  							^((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])].
  		[MoveM16rR]	-> [^((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])].
  		"[MoveM64rRd]	-> [^((self isQuick: (operands at: 0))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])]."
  		[MoveMwrR]		-> [self assert: (self is32BitSignedImmediate: (operands at: 0)).
  								^((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)) ~= RSP.
  							^((self concreteRegister: (operands at: 1)) bitAnd: 7) = RBP
+ 											ifTrue: [5]
+ 											ifFalse: [4]].
- 											ifTrue: [6]
- 											ifFalse: [5]].
  		[MoveRXbrR]	->	[self assert: (self concreteRegister: (operands at: 1)) ~= RSP.
  							^(((self concreteRegister: (operands at: 0)) < 8
  							   and: [(self concreteRegister: (operands at: 1)) < 8
  							   and: [(self concreteRegister: (operands at: 2)) < 8]])
  								ifTrue: [3]
  								ifFalse: [4])
  							+ (((self concreteRegister: (operands at: 2)) bitAnd: 7) = RBP
  											ifTrue: [1]
  											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 inCurrentCompilation: (operands at: 0))
  								ifTrue: [9]
  								ifFalse: [self pushCwByteSize]].
  		[PrefetchAw]	-> [^(self isAddressRelativeToVarBase: (operands at: 0)) ifTrue: [7] ifFalse: [0]].
  		"Conversion"
  		"[ConvertRRd]	-> [^4]" }.
  	^0 "to keep C compiler quiet"!

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

Item was changed:
  ----- Method: CogX64CompilerTests>>testMoveMbrR (in category 'tests') -----
  testMoveMbrR
  	"self new testMoveMbrR"
  	self concreteCompilerClass registersWithNamesDo:
  		[:sreg :srname|
+ 		self concreteCompilerClass byteRegistersWithNamesDo:
- 		self concreteCompilerClass registersWithNamesDo:
  			[:dreg :drname|
  			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
  				[:offset| | inst len |
  				inst := self gen: MoveMbrR operand: offset operand: sreg operand: dreg.
+ 				self deny: inst byteReadsZeroExtend.
  				len := inst concretizeAt: 0.
  				self processor
  					disassembleInstructionAt: 0
  					In: inst machineCode object
  					into: [:str :sz| | plainJane herIntended po |
  						po := offset bitAnd: 1 << self processor bitsInWord - 1.
  						plainJane := self strip: str.
+ 						herIntended := 'movb ', (offset = 0 ifTrue: [''] ifFalse: ['0x', (po printStringBase: 16 length: 16 padded: true)]), '(', srname, '), ', drname.
- 						herIntended := 'movzbq ', (offset = 0 ifTrue: [''] ifFalse: ['0x', (po printStringBase: 16 length: 16 padded: true)]), '(', srname, '), ', drname.
  						self assert: (plainJane match: herIntended).
  						self assert: len = sz]]]]!

Item was changed:
  ----- Method: CogX64CompilerTests>>testMoveXbrRR (in category 'tests') -----
  testMoveXbrRR
  	"self new testMoveXbrRR"
  	self concreteCompilerClass registersWithNamesDo:
  		[:idxreg :irname|
  		irname ~= '%rsp' ifTrue:
  			[self concreteCompilerClass registersWithNamesDo:
  				[:basereg :brname|
+ 				self concreteCompilerClass byteRegistersWithNamesDo:
- 				self concreteCompilerClass registersWithNamesDo:
  					[:dreg :drname|
  					((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
  						[:offset| | inst len |
  						inst := self gen: MoveXbrRR operand: idxreg operand: basereg operand: dreg.
+ 						self deny: inst byteReadsZeroExtend.
  						len := inst concretizeAt: 0.
  						self processor
  							disassembleInstructionAt: 0
  							In: inst machineCode object
  							into: [:str :sz| | plainJane herIntended |
  								"Convert e.g. '00000000: movzbq %ds:(%rax,%rax,1), %rax : 48 0F B6 04 00 ' to  'movzbq (%rax,%rax,1), %rax'"
  								plainJane := self strip: str.
+ 								herIntended := 'movb (', brname, ',', irname, ',1), ',drname.
- 								herIntended := 'movzbq (', brname, ',', irname, ',1), ',drname.
  								self assert: (plainJane match: herIntended).
  								self assert: len = sz]]]]]]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genFastPrimTraceUsing:and: (in category 'primitive generators') -----
  genFastPrimTraceUsing: r1 and: r2
  	"Suport for compileInterpreterPrimitive.  Generate inline code so as to record the primitive
  	 trace as fast as possible."
+ 	backEnd byteReadsZeroExtend ifFalse:
+ 		[self MoveCq: 0 R: r2].
  	self MoveAb: coInterpreter primTraceLogIndexAddress R: r2.
  	self MoveR: r2 R: r1.
  	self AddCq: 1 R: r1.
  	self MoveR: r1 Ab: coInterpreter primTraceLogIndexAddress.
  	methodLabel addDependent:
  		(self annotateAbsolutePCRef:
  			(self MoveCw: methodLabel asInteger R: r1)).
  	self MoveMw: (self offset: CogMethod of: #selector) r: r1 R: TempReg.
  	self MoveCw: coInterpreter primTraceLogAddress asInteger R: r1.
  	self MoveR: TempReg Xwr: r2 R: r1!



More information about the Vm-dev mailing list