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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 12 19:59:50 UTC 2015


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

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

Name: VMMaker.oscog-eem.1583
Author: eem
Time: 12 December 2015, 11:58:03.582 am
UUID: 7eb04eee-02fd-4ece-8742-c2f9ca00d4a0
Ancestors: VMMaker.oscog-eem.1582

x64 Cogit: get generated cogitX64.c to compile.

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

Item was changed:
  ----- 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 preceding 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.
+ 	opcode >= FirstShortJump
+ 		ifTrue:
+ 			[machineCodeSize := (self isQuick: maximumSpan)
- 	^machineCodeSize := opcode >= FirstShortJump
- 							ifTrue:
- 								[(self isQuick: maximumSpan)
  									ifTrue: [2]
  									ifFalse: [opcode = Jump
+ 												ifTrue: [5]]]
+ 		ifFalse:
+ 			[machineCodeSize := opcode caseOf:
- 												ifTrue: [5]
- 												ifFalse: [6]]]
- 							ifFalse:
- 								[opcode caseOf:
  									{	[JumpLong]				->	[5].
  										[JumpFull]				->	[12].
  										[JumpLongZero]		->	[6].
+ 										[JumpLongNonZero]	->	[6] }].
+ 	^machineCodeSize "Slang can't inline the switch into the ifTrue:ifFalse: correctly"!
- 										[JumpLongNonZero]	->	[6] }]!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genClearAndSetSmallIntegerTagsIn: (in category 'compile abstract instructions') -----
  genClearAndSetSmallIntegerTagsIn: scratchReg
  	"Set the SmallInteger tag bits when the tag bits may be filled with garbage."
  	cogit
+ 		AndCq: -1 - objectMemory tagMask R: scratchReg;
- 		AndCq: -1 - self tagMask R: scratchReg;
  		OrCq: 1 R: scratchReg.
  	^0!

Item was changed:
  ----- 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.
  	 c.f. Spur64BitMemoryManager>>smallFloatObjectOf:"
  	| 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: objectMemory numTagBits R: reg).
- 	(cogit LogicalShiftLeftCq: self numTagBits R: reg).
  	cogit AddCq: objectMemory smallFloatTag R: reg.
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genConvertIntegerToSmallIntegerInReg: (in category 'compile abstract instructions') -----
  genConvertIntegerToSmallIntegerInReg: reg
+ 	cogit LogicalShiftLeftCq: objectMemory numTagBits R: reg.
- 	cogit LogicalShiftLeftCq: self numTagBits R: reg.
  	cogit AddCq: 1 R: reg.
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genConvertSmallIntegerToIntegerInReg: (in category 'compile abstract instructions') -----
  genConvertSmallIntegerToIntegerInReg: reg
+ 	cogit ArithmeticShiftRightCq: objectMemory numTagBits R: reg.
- 	cogit ArithmeticShiftRightCq: self numTagBits R: reg.
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genGetHashFieldNonImmOf:asSmallIntegerInto: (in category 'compile abstract instructions') -----
  genGetHashFieldNonImmOf: instReg asSmallIntegerInto: destReg
  	"Fetch the instance's identity hash into destReg, encoded as a SmallInteger."
  	cogit
  		MoveMw: 0 r: instReg R: destReg;
  		"Shift and mask the field leaving room for the SmallInteger tag."
+ 		LogicalShiftRightCq: objectMemory identityHashFullWordShift - objectMemory numTagBits R: destReg;
- 		LogicalShiftRightCq: objectMemory identityHashFullWordShift - self numTagBits R: destReg;
  		AndCq: objectMemory identityHashHalfWordMask << objectMemory numTagBits R: destReg;
  		AddCq: objectMemory smallIntegerTag R: destReg.
  	^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 - objectMemory numTagBits R: scratchReg;
- 		ArithmeticShiftRightCq: 64 - self numTagBits R: scratchReg;
  		AddCq: 1 R: scratchReg;
+ 		AndCq: 1 << (objectMemory numTagBits + 1) - 1 R: scratchReg; "sign and top numTags bits must be the same"
- 		AndCq: 1 << (self numTagBits + 1) - 1 R: scratchReg; "sign and top numTags bits must be the same"
  		CmpCq: 1 R: scratchReg;
  		JumpLessOrEqual: 0!

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 - objectMemory numTagBits R: scratchReg;
- 		ArithmeticShiftRightCq: 64 - self numTagBits R: scratchReg;
  		AddCq: 1 R: scratchReg;
+ 		AndCq: 1 << (objectMemory numTagBits + 1) - 1 R: scratchReg; "sign and top numTags bits must be the same"
- 		AndCq: 1 << (self numTagBits + 1) - 1 R: scratchReg; "sign and top numTags bits must be the same"
  		CmpCq: 1 R: scratchReg;
  		JumpGreater: 0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genJumpNotSmallIntegersIn:andScratchReg: (in category 'compile abstract instructions') -----
  genJumpNotSmallIntegersIn: aRegister andScratchReg: scratchReg
  	"Generate a compare and branch to test if aRegister and scratchReg contains other than SmallIntegers,
  	 i.e. don't branch if both aRegister and scratchReg contain SmallIntegers.
  	 Answer the jump.  Destroy scratchReg if required."
  	<returnTypeC: #'AbstractInstruction *'>
  	^cogit
  		XorR: aRegister R: scratchReg;
+ 		AndCq: objectMemory tagMask R: scratchReg;
- 		AndCq: self tagMask R: scratchReg;
  		JumpNonZero: 0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genShiftAwaySmallIntegerTagsInScratchReg: (in category 'compile abstract instructions') -----
  genShiftAwaySmallIntegerTagsInScratchReg: scratchReg
+ 	cogit ArithmeticShiftRightCq: objectMemory numTagBits R: scratchReg.
- 	cogit ArithmeticShiftRightCq: self numTagBits R: scratchReg.
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>maybeGenConvertIfSmallFloatIn:scratchReg:into:andJumpTo: (in category 'primitive generators') -----
  maybeGenConvertIfSmallFloatIn: oopReg scratchReg: scratch into: dpReg andJumpTo: targetInst
  	"Generate a test for a smallFloat in  oopReg, converting it to the float value in dpReg and jumping to targetInst.
  	 c.f. Spur64BitMemoryManager>>smallFloatBitsOf:"
  	<var: 'targetInst' type: #'AbstractInstruction *'>
  	| jumpNotSF jumpSFZero |
  	<var: 'jumpNotSF' type: #'AbstractInstruction *'>
  	<var: 'jumpSFZero' type: #'AbstractInstruction *'>
  	jumpNotSF := self genJumpNotSmallFloat: oopReg scratchReg: scratch.
  	cogit
  		MoveR: oopReg R: scratch;
+ 		LogicalShiftRightCq: objectMemory numTagBits R: scratch;
- 		LogicalShiftRightCq: self numTagBits R: scratch;
  		CmpCq: 1 R: scratch.
  	jumpSFZero := cogit JumpAbove: 0.
  	cogit AddCq: objectMemory smallFloatExponentOffset << (objectMemory smallFloatMantissaBits + 1) R: scratch.
  	jumpSFZero jmpTarget: (cogit RotateRightCq: 1 R: scratch).
  	cogit
  		MoveR: scratch Rd: dpReg;
  		Jump: targetInst.
  	jumpNotSF jmpTarget: cogit Label.
  	^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor64BitSpur>>numTagBits (in category 'compile abstract instructions') -----
- numTagBits
- 	<inline: true>
- 	^3!

Item was removed:
- ----- Method: CogObjectRepresentationFor64BitSpur>>tagMask (in category 'accessing') -----
- tagMask
- 	<inline: true>
- 	^7!

Item was added:
+ ----- Method: CogX64Compiler class>>isAbstract (in category 'testing') -----
+ isAbstract
+ 	^self == CogX64Compiler!

Item was added:
+ ----- Method: CogX64Compiler>>flushICacheFrom:to: (in category 'inline cacheing') -----
+ flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
+ 	<cmacro: '(me,startAddress,endAddress) 0'>
+ 	"On Intel processors where code and data have the same linear address, no
+ 	 special action is required to flush the instruciton cache.  One only needs to
+ 	 execute a serializing instruction (e.g. CPUID) if code and data are at different
+ 	 virtual addresses (e.g. a debugger using memory-mapping to access a debugee).
+ 	 Using the macro avoids an unnecessary call."
+ 	self halt: #ceFlushICache!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>numTagBits (in category 'object access') -----
  numTagBits
  	<api>
+ 	<cmacro: '() 2'>
  	^2!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>tagMask (in category 'word size') -----
  tagMask
  	<api>
+ 	<cmacro: '() 3'>
  	^3!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>numTagBits (in category 'object access') -----
  numTagBits
  	<api>
+ 	<cmacro: '() 3'>
  	"4th bit reserved for object alignment, which could imply e.g. what space the object is in."
  	^3!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>tagMask (in category 'word size') -----
  tagMask
  	<api>
+ 	<cmacro: '() 7'>
  	^7!

Item was changed:
  ----- Method: SpurMemoryManager>>numTagBits (in category 'object access') -----
  numTagBits
- 	<api>
  	^self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>tagMask (in category 'word size') -----
  tagMask
- 	<api>
  	^self subclassResponsibility!



More information about the Vm-dev mailing list