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

commits at source.squeak.org commits at source.squeak.org
Thu Dec 10 00:24:01 UTC 2015


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

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

Name: VMMaker.oscog-eem.1569
Author: eem
Time: 9 December 2015, 4:22:18.409 pm
UUID: 3f739d44-3a75-4591-9da7-42e50c358648
Ancestors: VMMaker.oscog-eem.1568

x64 Cogit:
Fix regression in SmallInteger testing in introducing genJump[Is|Not]SmallIntegerValue:scratch:

Add floating-point to SmallFloat conversion, and isSmallFloatValue: testing.  Add RotateLeftCqR, MoveRdR and extend TstCqR to 64-bits to support this.

Add tests for MoveRdR & MoveRRd.

Add a debug facility to halt when generating the Nth abstract instruction (debugOpcodeIndices).

Use smallFloatMantissaBits rathe rthan the magic constant 52.  Make it an <api> method.

Reorder genDoubleArithmetic:preOpCheck: top move the common case SmallInteger/SmallFloat conversion earlier in the method, before the failure code.

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

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genJumpIsSmallIntegerValue:scratch: (in category 'compile abstract instructions') -----
  genJumpIsSmallIntegerValue: aRegister scratch: scratchReg
  	"Generate a test for aRegister containing an integer value in the SmallInteger range, and a jump if so, answering the jump.
  	 c.f. Spur32BitMemoryManager>>isIntegerValue:"
  	<returnTypeC: #'AbstractInstruction *'>
  	^cogit
  		MoveR: aRegister R: scratchReg;
  		ArithmeticShiftRightCq: 1 R: scratchReg;
  		XorR: aRegister R: scratchReg;
+ 		JumpGreaterOrEqual: 0!
- 		JumpLess: 0!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genJumpNotSmallIntegerValue:scratch: (in category 'compile abstract instructions') -----
  genJumpNotSmallIntegerValue: aRegister scratch: scratchReg
  	"Generate a test for aRegister containing an integer value outside the SmallInteger range, and a jump if so, answering the jump.
  	 c.f. Spur32BitMemoryManager>>isIntegerValue:"
  	<returnTypeC: #'AbstractInstruction *'>
  	^cogit
  		MoveR: aRegister R: scratchReg;
  		ArithmeticShiftRightCq: 1 R: scratchReg;
  		XorR: aRegister R: scratchReg;
+ 		JumpLess: 0!
- 		JumpGreaterOrEqual: 0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genAllocFloatValue:into:scratchReg:scratchReg: (in category 'primitive generators') -----
+ genAllocFloatValue: dpreg into: resultReg scratchReg: scratch1 scratchReg: scratch2
+ 	"Override to answer a SmallFloat64 if possible."
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	| jumpFail jumpNotSF jumpMerge |
+ 	<var: #jumpFail type: #'AbstractInstruction *'>
+ 	<var: #jumpNotSF type: #'AbstractInstruction *'>
+ 	<var: #jumpMerge type: #'AbstractInstruction *'>
+ 	cogit MoveRd: dpreg R: scratch2.
+ 	jumpNotSF := self genJumpNotSmallFloatValueBits: scratch2 scratch: scratch1.
+ 	self genConvertBitsToSmallFloatIn: scratch2 scratch: scratch1.
+ 	jumpMerge := cogit Jump: 0.
+ 	jumpNotSF jmpTarget: cogit Label.
+ 	jumpFail := super genAllocFloatValue: dpreg into: resultReg scratchReg: scratch1 scratchReg: scratch2.
+ 	jumpMerge jmpTarget: cogit Label.
+ 	^jumpFail!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genConvertBitsToSmallFloatIn:scratch: (in category 'compile abstract instructions') -----
+ genConvertBitsToSmallFloatIn: reg scratch: scratch
+ 	"Convert the in-SmallFloat64-range floating point value in integer register into a tagged SmallFloat64 oop."
+ 	| jumpZero |
+ 	<var: #jumpZero type: #'AbstractInstruction *'>
+ 	cogit
+ 		RotateLeftCq: 1 R: reg;
+ 		CmpCq: 1 R: reg.
+ 	jumpZero :=
+ 	cogit JumpBelowOrEqual: 0.
+ 	cogit
+ 		SubCq: objectMemory smallFloatExponentOffset << (objectMemory smallFloatMantissaBits + 1) R: reg.
+ 	jumpZero jmpTarget:
+ 	(cogit LogicalShiftLeftCq: self numTagBits R: reg).
+ 	cogit AddCq: objectMemory smallFloatTag R: reg.
+ 	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genJumpIsSmallIntegerValue:scratch: (in category 'compile abstract instructions') -----
  genJumpIsSmallIntegerValue: aRegister scratch: scratchReg
  	"Generate a test for aRegister containing an integer value in the SmallInteger range, and a jump if so, answering the jump.
  	 c.f. Spur64BitMemoryManager>>isIntegerValue:"
  	<returnTypeC: #'AbstractInstruction *'>
  	^cogit
  		MoveR: aRegister R: scratchReg;
  		ArithmeticShiftRightCq: 64 - self numTagBits R: scratchReg;
  		AddCq: 1 R: scratchReg;
  		AndCq: 1 << (self numTagBits + 1) - 1 R: scratchReg; "sign and top numTags bits must be the same"
  		CmpCq: 1 R: scratchReg;
+ 		JumpLessOrEqual: 0!
- 		JumpGreaterOrEqual: 0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genJumpNotSmallFloatValueBits:scratch: (in category 'compile abstract instructions') -----
+ genJumpNotSmallFloatValueBits: reg scratch: exponent
+ 	"Generate a test to check that the integer register contains a floating point value within the SmallFloat64 range,
+ 	 and answer the jump.  c.f. Spur64BitMemoryManager>>isSmallFloatValue:"
+ 	| jumpFail jumpTest jumpMinExponent jumpMaxExponent jumpZeroMantissa |
+ 	<var: #jumpFail type: #'AbstractInstruction *'>
+ 	<var: #jumpTest type: #'AbstractInstruction *'>
+ 	<var: #jumpMinExponent type: #'AbstractInstruction *'>
+ 	<var: #jumpMaxExponent type: #'AbstractInstruction *'>
+ 	<var: #jumpZeroMantissa type: #'AbstractInstruction *'>
+ 	cogit MoveR: reg R: exponent;
+ 		LogicalShiftRightCq: objectMemory smallFloatMantissaBits R: exponent;
+ 		AndCq: 16r7FF R: exponent;  "ieee double precision mantissa is 11 bits"
+ 		CmpCq: objectMemory smallFloatExponentOffset R: exponent.
+ 	jumpMinExponent := cogit JumpLessOrEqual: 0.
+ 	cogit CmpCq: 255 + objectMemory smallFloatExponentOffset R: exponent. "SmallFloat exponent is 8 bits"
+ 	jumpMaxExponent := cogit JumpLessOrEqual: 0.
+ 	jumpFail :=
+ 	cogit Jump: 0.
+ 	jumpMinExponent jmpTarget:
+ 	(cogit TstCq: 1 << objectMemory smallFloatMantissaBits - 1 R: reg). "test mantissa bits"
+ 	jumpZeroMantissa := cogit JumpZero: 0.
+ 	cogit CmpCq: objectMemory smallFloatExponentOffset R: exponent.
+ 	jumpTest :=
+ 	cogit Jump: 0.
+ 	jumpZeroMantissa jmpTarget:
+ 	(cogit CmpCq: 0 R: exponent).
+ 	jumpTest jmpTarget:
+ 	(cogit JumpNonZero: jumpFail).
+ 	jumpMaxExponent jmpTarget: cogit Label.
+ 	^jumpFail!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genJumpNotSmallIntegerValue:scratch: (in category 'compile abstract instructions') -----
  genJumpNotSmallIntegerValue: aRegister scratch: scratchReg
  	"Generate a test for aRegister containing an integer value outside the SmallInteger range, and a jump if so, answering the jump.
  	 c.f. Spur64BitMemoryManager>>isIntegerValue:"
  	<returnTypeC: #'AbstractInstruction *'>
  	^cogit
  		MoveR: aRegister R: scratchReg;
  		ArithmeticShiftRightCq: 64 - self numTagBits R: scratchReg;
  		AddCq: 1 R: scratchReg;
  		AndCq: 1 << (self numTagBits + 1) - 1 R: scratchReg; "sign and top numTags bits must be the same"
  		CmpCq: 1 R: scratchReg;
+ 		JumpGreater: 0!
- 		JumpLess: 0!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>genJumpIsSmallIntegerValue:scratch: (in category 'compile abstract instructions') -----
  genJumpIsSmallIntegerValue: aRegister scratch: scratchReg
  	"Generate a test for aRegister containing an integer value in the SmallInteger range, and a jump if so, answering the jump.
  	 c.f. ObjectMemory>>isIntegerValue:"
  	<returnTypeC: #'AbstractInstruction *'>
  	^cogit
  		MoveR: aRegister R: scratchReg;
  		ArithmeticShiftRightCq: 1 R: scratchReg;
  		XorR: aRegister R: scratchReg;
+ 		JumpGreaterOrEqual: 0!
- 		JumpLess: 0!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>genJumpNotSmallIntegerValue:scratch: (in category 'compile abstract instructions') -----
  genJumpNotSmallIntegerValue: aRegister scratch: scratchReg
  	"Generate a test for aRegister containing an integer value outside the SmallInteger range, and a jump if so, answering the jump.
  	 c.f. ObjectMemory>>isIntegerValue:"
  	<returnTypeC: #'AbstractInstruction *'>
  	^cogit
  		MoveR: aRegister R: scratchReg;
  		ArithmeticShiftRightCq: 1 R: scratchReg;
  		XorR: aRegister R: scratchReg;
+ 		JumpLess: 0!
- 		JumpGreaterOrEqual: 0!

Item was changed:
  SharedPool subclass: #CogRTLOpcodes
  	instanceVariableNames: ''
+ 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCqRR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call CallFull ClassReg CmpC32R CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpFull JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg Literal LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRRd MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdR MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCq PushCw PushR RISCTempReg ReceiverResultReg RetN RotateLeftCqR RotateRightCqR SPReg Scratch0Reg Scratch1Reg Scratch2Reg Scratch3Reg Scratch4Reg Scratch5Reg Scratch6Reg Scratch7Reg SendNumArgsReg SqrtRd Stop SubCqR SubCwR SubRR SubRdRd TempReg TstCqR VarBaseReg XorCqR XorCwR XorRR'
- 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCqRR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call CallFull ClassReg CmpC32R CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpFull JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg Literal LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRRd MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdR MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCq PushCw PushR RISCTempReg ReceiverResultReg RetN RotateRightCqR SPReg Scratch0Reg Scratch1Reg Scratch2Reg Scratch3Reg Scratch4Reg Scratch5Reg Scratch6Reg Scratch7Reg SendNumArgsReg SqrtRd Stop SubCqR SubCwR SubRR SubRdRd TempReg TstCqR VarBaseReg XorCqR XorCwR XorRR'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogRTLOpcodes commentStamp: '<historical>' prior: 0!
  I am a pool for the Register-Transfer-Language to which Cog compiles.  I define unique integer values for all RTL opcodes and abstract registers.  See CogAbstractInstruction for instances of instructions with the opcodes that I define.!

Item was changed:
  ----- Method: CogRTLOpcodes class>>initialize (in category 'class initialization') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: CogX64Compiler>>computeMaximumSize (in category 'generate machine code') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRRd (in category 'generate machine code') -----
+ concretizeMoveRRd
+ 	<inline: true>
- concretizeMoveRRd	<inline: true>
  	| srcReg destReg |
  	srcReg := self concreteRegister: (operands at: 0).
  	destReg := self concreteDPFPRegister: (operands at: 1).
  	machineCode
  		at: 0 put: 16r66;
  		at: 1 put: (self rexR: destReg x: 0 b: srcReg);
  		at: 2 put: 16r0f;
  		at: 3 put: 16r6e;
  		at: 4 put: (self mod: ModReg RM: srcReg RO: destReg).
  	^machineCodeSize := 5!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeMoveRdR (in category 'generate machine code') -----
+ concretizeMoveRdR
+ 	<inline: true>
+ 	| srcReg destReg |
+ 	srcReg := self concreteDPFPRegister: (operands at: 0).
+ 	destReg := self concreteRegister: (operands at: 1).
+ 	machineCode
+ 		at: 0 put: 16r66;
+ 		at: 1 put: (self rexR: srcReg x: 0 b: destReg);
+ 		at: 2 put: 16r0f;
+ 		at: 3 put: 16r7e;
+ 		at: 4 put: (self mod: ModReg RM: destReg RO: srcReg).
+ 	^machineCodeSize := 5!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeTstCqR (in category 'generate machine code') -----
  concretizeTstCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| 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: 16rF6;
  			at: 2 put: (self mod: ModReg RM: reg RO: 0);
  			at: 3 put: (value bitAnd: 16rFF).
  		 ^machineCodeSize := 4].
+ 	
+ 	(self isSignExtendedFourByteValue: value) ifTrue:
+ 		[reg = RAX ifTrue:
+ 			[machineCode
+ 				at: 1 put: 16rA9;
+ 				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: 16rF7;
+ 			at: 2 put: (self mod: ModReg RM: reg RO: 0);
+ 			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: 16r85!
- 	self assert: value >> 32 = 0.
- 	reg = RAX ifTrue:
- 		[machineCode
- 			at: 1 put: 16rA9;
- 			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: 16rF7;
- 		at: 2 put: (self mod: ModReg RM: reg RO: 0);
- 		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 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].
  		[JumpR]					-> [^self concretizeJumpR].
  		[JumpFull]				-> [^self concretizeJumpFull].
  		[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 concretizeArithCqRWithRO: 0 raxOpcode: 15r05].
  		[AddCwR]					-> [^self concretizeArithCwR: 16r03].
  		[AddRR]						-> [^self concretizeOpRR: 16r03].
  		[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58].
  		[AndCqR]					-> [^self concretizeArithCqRWithRO: 4 raxOpcode: 16r25].
  		[AndCwR]					-> [^self concretizeArithCwR: 16r23].
  		[AndRR]						-> [^self concretizeOpRR: 16r23].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[CmpCqR]					-> [^self concretizeArithCqRWithRO: 7 raxOpcode: 16r3D].
  		[CmpCwR]					-> [^self concretizeArithCwR: 16r39].
  		[CmpC32R]					-> [^self concretizeCmpC32R].
  		[CmpRR]					-> [^self concretizeReverseOpRR: 16r39].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
  		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59].
  		[OrCqR]						-> [^self concretizeArithCqRWithRO: 1 raxOpcode: 16r0D].
  		[OrCwR]					-> [^self concretizeArithCwR: 16r0B].
  		[OrRR]						-> [^self concretizeOpRR: 16r0B].
  		[SubCqR]					-> [^self concretizeArithCqRWithRO: 5 raxOpcode: 16r2D].
  		[SubCwR]					-> [^self concretizeArithCwR: 16r2B].
  		[SubRR]						-> [^self concretizeOpRR: 16r2B].
  		[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C].
  		[SqrtRd]					-> [^self concretizeSqrtRd].
  		[XorCwR]					-> [^self concretizeArithCwR: 16r33].
  		[XorRR]						-> [^self concretizeOpRR: 16r33].
  		[NegateR]					-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
+ 		[RotateLeftCqR]				-> [^self concretizeShiftCqRegOpcode: 0].
  		[RotateRightCqR]				-> [^self concretizeShiftCqRegOpcode: 1].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeShiftCqRegOpcode: 7].
  		[LogicalShiftRightCqR]			-> [^self concretizeShiftCqRegOpcode: 5].
  		[LogicalShiftLeftCqR]			-> [^self concretizeShiftCqRegOpcode: 4].
  		[ArithmeticShiftRightRR]			-> [^self concretizeShiftRegRegOpcode: 7].
  		[LogicalShiftLeftRR]				-> [^self concretizeShiftRegRegOpcode: 4].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveC32R]		-> [^self concretizeMoveC32R].
  		[MoveRR]			-> [^self concretizeReverseOpRR: 16r89].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveAbR]			-> [^self concretizeMoveAbR].
  		[MoveRAb]			-> [^self concretizeMoveRAb].
  		[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].
  		[MoveX32rRR]		-> [^self concretizeMoveX32rRR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[MoveRdR]			-> [^self concretizeMoveRdR].
  		[MoveRRd]			-> [^self concretizeMoveRRd].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd] }!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveRRd (in category 'tests') -----
+ testMoveRRd
+ 	"self new testMoveRRd"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:sreg :srname|
+ 		self concreteCompilerClass xmmRegistersWithNamesDo:
+ 			[:dreg :drname| | inst len |
+ 			inst := self gen: MoveRRd operand: sreg operand: dreg.
+ 			len := inst concretizeAt: 0.
+ 			self processor
+ 				disassembleInstructionAt: 0
+ 				In: inst machineCode object
+ 				into: [:str :sz| | plainJane herIntended |
+ 					plainJane := self strip: str.
+ 					herIntended := 'movq ', srname, ', ', drname.
+ 					"N.B. bochs 2.3.7 gets many cases wrong, e.g.
+ 						movq %ds:(%rax), %xmm8 : F3 44 0F 7E 00
+ 					 is disassembled as
+ 						rep movq %ds:(%rax), %xmm8 : F3 44 0F 7E 00"
+ 					(plainJane beginsWith: 'rep ') ifTrue:
+ 						[plainJane := plainJane allButFirst: 4].
+ 					self assert: herIntended equals: plainJane.
+ 					self assert: len = sz]]]
+ 
+ "| them it |
+ them := OrderedCollection new.
+ [(it := CogX64CompilerTests new) testMoveRRd]
+ 	on: AssertionFailure, TestResult failure
+ 	do: [:ex| | inst |
+ 		ex class == AssertionFailure
+ 			ifTrue:
+ 				[inst := ex signalerContext receiver.
+ 				it processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| them addLast: (it strip: str)]]
+ 			ifFalse:
+ 				[ResumableTestFailure adoptInstance: ex].
+ 		ex resume].
+ them size"
+ "| them it |
+ them := OrderedCollection new.
+ [(it := CogX64CompilerTests new) testMoveRRd]
+ 	on: TestResult failure
+ 	do: [:ex| | ctxt |
+ 		ctxt := ex signalerContext findContextSuchThat: [:c| c selector == #assert:equals:]..
+ 		them addLast: {ctxt tempAt: 1. ctxt tempAt: 2}.
+ 		ResumableTestFailure adoptInstance: ex.
+ 		ex resume].
+ them size"!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveRdR (in category 'tests') -----
+ testMoveRdR
+ 	"self new testMoveRdR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:dreg :drname|
+ 		self concreteCompilerClass xmmRegistersWithNamesDo:
+ 			[:sreg :srname| | inst len |
+ 			inst := self gen: MoveRdR operand: sreg operand: dreg.
+ 			len := inst concretizeAt: 0.
+ 			self processor
+ 				disassembleInstructionAt: 0
+ 				In: inst machineCode object
+ 				into: [:str :sz| | plainJane herIntended |
+ 					plainJane := self strip: str.
+ 					herIntended := 'movq ', srname, ', ', drname.
+ 					"N.B. bochs 2.3.7 gets many cases wrong, e.g.
+ 						movq %ds:(%rax), %xmm8 : F3 44 0F 7E 00
+ 					 is disassembled as
+ 						rep movq %ds:(%rax), %xmm8 : F3 44 0F 7E 00"
+ 					(plainJane beginsWith: 'rep ') ifTrue:
+ 						[plainJane := plainJane allButFirst: 4].
+ 					self assert: herIntended equals: plainJane.
+ 					self assert: len = sz]]]
+ 
+ "| them it |
+ them := OrderedCollection new.
+ [(it := CogX64CompilerTests new) testMoveRdR]
+ 	on: AssertionFailure, TestResult failure
+ 	do: [:ex| | inst |
+ 		ex class == AssertionFailure
+ 			ifTrue:
+ 				[inst := ex signalerContext receiver.
+ 				it processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| them addLast: (it strip: str)]]
+ 			ifFalse:
+ 				[ResumableTestFailure adoptInstance: ex].
+ 		ex resume].
+ them size"
+ "| them it |
+ them := OrderedCollection new.
+ [(it := CogX64CompilerTests new) testMoveRdR]
+ 	on: TestResult failure
+ 	do: [:ex| | ctxt |
+ 		ctxt := ex signalerContext findContextSuchThat: [:c| c selector == #assert:equals:]..
+ 		them addLast: {ctxt tempAt: 1. ctxt tempAt: 2}.
+ 		ResumableTestFailure adoptInstance: ex.
+ 		ex resume].
+ them size"!

Item was changed:
  CogClass subclass: #Cogit
+ 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd literalsManager callerSavedRegMask postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB tempOop numIRCs indexOfIRC theIRCs implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel maxCPICCases debugOpcodeIndices'
- 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd literalsManager callerSavedRegMask postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB tempOop numIRCs indexOfIRC theIRCs implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel maxCPICCases'
  	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass'
  	poolDictionaries: 'CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMBytecodeConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 4/6/2015 15:56' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
  
  	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
  
  I have concrete subclasses that implement different levels of optimization:
  	SimpleStackBasedCogit is the simplest code generator.
  
  	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  	to the stack until necessary and implements a register-based calling convention for low-arity sends.
  
  	StackToRegisterMappingCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
  cFramePointer cStackPointer <Integer>
  	the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixup shas one element per byte in methodObj's bytecode
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventually the total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

Item was added:
+ ----- Method: Cogit>>RotateLeftCq:R: (in category 'abstract instructions') -----
+ RotateLeftCq: quickConstant R: reg
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^self gen: RotateLeftCqR operand: quickConstant operand: reg!

Item was changed:
  ----- Method: Cogit>>abstractInstructionAt: (in category 'compile abstract instructions') -----
  abstractInstructionAt: index
  	<cmacro: '(index) (&abstractOpcodes[index])'>
+ 	(debugOpcodeIndices includes: index) ifTrue: [self halt].
  	^abstractOpcodes at: index!

Item was changed:
  ----- Method: Cogit>>setInterpreter: (in category 'initialization') -----
  setInterpreter: aCoInterpreter
  	"Initialization of the code generator in the simulator.
  	 These objects already exist in the generated C VM
  	 or are used only in the simulation."
  	<doNotGenerate>
  	coInterpreter := aCoInterpreter.
  	objectMemory := aCoInterpreter objectMemory.
  	threadManager := aCoInterpreter threadManager. "N.B. may be nil"
  	methodZone := CogMethodZone new.
  	objectRepresentation := objectMemory objectRepresentationClass
  								forCogit: self methodZone: methodZone.
  	methodZone setInterpreter: aCoInterpreter
  				objectRepresentation: objectRepresentation
  				cogit: self.
  	generatorTable := self class generatorTable.
  	primitiveGeneratorTable := self class primitiveTable.
  	processor := ProcessorClass new.
  	simulatedAddresses := Dictionary new.
  	simulatedTrampolines := Dictionary new.
  	simulatedVariableGetters := Dictionary new.
  	simulatedVariableSetters := Dictionary new.
  	traceStores := 0.
  	traceFlags := (self class initializationOptions at: #recordPrimTrace ifAbsent: [true])
  					ifTrue: [8] "record prim trace on by default (see Cogit class>>decareCVarsIn:)"
  					ifFalse: [0].
  	debugPrimCallStackOffset := 0.
  	singleStep := printRegisters := printInstructions := clickConfirm := false.
  	breakBlock ifNil: [self breakPC: breakPC].
  	backEnd := CogCompilerClass for: self.
  	methodLabel := CogCompilerClass for: self.
  	(literalsManager := backEnd class literalsManagerClass new) cogit: self.
  	ordinarySendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	superSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	BytecodeSetHasDirectedSuperSend ifTrue:
  		[directedSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].
  	NewspeakVM ifTrue:
  		[selfSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		dynamicSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		implicitReceiverSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		outerSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].
  	"debug metadata"
  	objectReferencesInRuntime := CArrayAccessor on: (Array new: NumObjRefsInRuntime).
  	runtimeObjectRefIndex := 0.
  	"debug metadata"
  	trampolineAddresses := CArrayAccessor on: (Array new: NumTrampolines * 2).
  	trampolineTableIndex := 0.
  
+ 	extA := extB := 0.
+ 
  	compilationTrace ifNil: [compilationTrace := self class initializationOptions at: #compilationTrace ifAbsent: [0]].
+ 	debugOpcodeIndices := self class initializationOptions at: #debugOpcodeIndices ifAbsent: [Set new].!
- 	extA := extB := 0!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>isSmallFloatValue: (in category 'interpreter access') -----
  isSmallFloatValue: aFloat
  	<inline: true>
  	<var: #aFloat type: #double>
  	| exponent rawFloat |
  	rawFloat := self
  					cCode: [(self cCoerce: (self addressOf: aFloat) to: 'sqLong *') at: 0]
  					inSmalltalk: [(aFloat at: 1) << 32 + (aFloat at: 2)].
+ 	exponent := rawFloat >> self smallFloatMantissaBits bitAnd: 16r7FF.
- 	exponent := rawFloat >> 52 bitAnd: 16r7FF.
  	^exponent > self smallFloatExponentOffset
  	 	ifTrue: [exponent <= (255 + self smallFloatExponentOffset)]
  		ifFalse:
+ 			[(rawFloat bitAnd: (1 << self smallFloatMantissaBits - 1)) = 0
- 			[(rawFloat bitAnd: (1 << 52 - 1)) = 0
  				ifTrue: [exponent = 0]
  				ifFalse: [exponent = self smallFloatExponentOffset]]!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>smallFloatMantissaBits (in category 'interpreter access') -----
  smallFloatMantissaBits
+ 	<api>
+ 	<cmacro: '() 52'>
  	^52!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genDoubleArithmetic:preOpCheck: (in category 'primitive generators') -----
  genDoubleArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
  	"Receiver and arg in registers.
  	 Stack looks like
  		return address"
  	<var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
  	| jumpFailClass jumpFailClass2 jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp |
  	<var: #jumpFailClass type: #'AbstractInstruction *'>
  	<var: #jumpFailClass2 type: #'AbstractInstruction *'>
  	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
  	<var: #jumpNonInt type: #'AbstractInstruction *'>
  	<var: #jumpFailCheck type: #'AbstractInstruction *'>
  	<var: #doOp type: #'AbstractInstruction *'>
  	objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
  	self MoveR: Arg0Reg R: ClassReg.
  	jumpImmediate := objectRepresentation genJumpImmediate: Arg0Reg.
  	objectRepresentation genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
  	objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
  	jumpFailClass := self JumpNonZero: 0.
  	objectRepresentation genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
  	doOp := self Label.
  	preOpCheckOrNil ifNotNil:
  		[jumpFailCheck := self perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
  	self gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
  	jumpFailAlloc := objectRepresentation
  						genAllocFloatValue: DPFPReg0
  						into: SendNumArgsReg
  						scratchReg: ClassReg
  						scratchReg: TempReg.
  	self MoveR: SendNumArgsReg R: ReceiverResultReg.
  	self RetN: 0.
+ 	jumpImmediate jmpTarget: self Label.
+ 	objectRepresentation maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: doOp.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratch: TempReg].
+ 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
+ 	self ConvertR: ClassReg Rd: DPFPReg1.
+ 	self Jump: doOp.
  	"We need to push the register args on two paths; this one and the interpreter primitive path.
  	But the interpreter primitive path won't unless regArgsHaveBeenPushed is false."
  	self assert: methodOrBlockNumArgs <= self numRegArgs.
  	jumpFailClass jmpTarget: self Label.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt jmpTarget: jumpFailClass getJmpTarget].
  	preOpCheckOrNil ifNotNil:
  		[jumpFailCheck jmpTarget: jumpFailClass getJmpTarget].
  	backEnd genPushRegisterArgsForNumArgs: methodOrBlockNumArgs scratchReg: SendNumArgsReg.
  	jumpFailClass2 := self Jump: 0.
- 	jumpImmediate jmpTarget: self Label.
- 	objectRepresentation maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: doOp.
- 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratch: TempReg.
- 		 jumpNonInt jmpTarget: jumpFailClass getJmpTarget].
- 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
- 	self ConvertR: ClassReg Rd: DPFPReg1.
- 	self Jump: doOp.
  	jumpFailAlloc jmpTarget: self Label.
  	self compileFallbackToInterpreterPrimitive: 0.
  	jumpFailClass2 jmpTarget: self Label.
  	^0!



More information about the Vm-dev mailing list