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

commits at source.squeak.org commits at source.squeak.org
Thu Dec 10 02:49:33 UTC 2015


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

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

Name: VMMaker.oscog-eem.1570
Author: eem
Time: 9 December 2015, 6:47:48.811 pm
UUID: f0f897bb-a851-48e8-9d3a-44461a674794
Ancestors: VMMaker.oscog-eem.1569

x64 Cogit:
Fix creating small floats on x64; it helps if the result is written to the register expected to receive it ;-).

Fix TstCqR for > 32-bits; it is backwards w.r.t. other clients of concretizeArithCwR:

Add the primitive failure handling to primitiveDirectoryEntry in the StackInterpreter (because I'm comoaring the StackInterpreter with the Cogit to find out if the bitblt issue is a bug in the Cogit - it isn't).

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

Item was changed:
  ----- Method: CogInLineLiteralsX64Compiler>>concretizeArithCwR: (in category 'generate machine code') -----
  concretizeArithCwR: opcode
  	| value reg |
  	value := operands at: 0.
  	reg := self concreteRegister: (operands at: 1).
  	machineCode
  		at:  0 put: (self rexR: ConcreteRISCTempReg x: 0 b: ConcreteRISCTempReg);
  		at:  1 put: 16rB8 + (ConcreteRISCTempReg bitAnd: 7);
  		at:  2 put: (value bitAnd: 16rFF);
  		at:  3 put: (value >> 8 bitAnd: 16rFF);
  		at:  4 put: (value >> 16 bitAnd: 16rFF);
  		at:  5 put: (value >> 24 bitAnd: 16rFF);
  		at:  6 put: (value >> 32 bitAnd: 16rFF);
  		at:  7 put: (value >> 40 bitAnd: 16rFF);
  		at:  8 put: (value >> 48 bitAnd: 16rFF);
  		at:  9 put: (value >> 56 bitAnd: 16rFF);
+ 		at: 10 put: (opcode = 16r85 "Tst; backwards"
+ 					ifTrue: [self rexR: ConcreteRISCTempReg x: 0 b: reg]
+ 					ifFalse: [self rexR: reg x: 0 b: ConcreteRISCTempReg]);
- 		at: 10 put: (self rexR: reg x: 0 b: ConcreteRISCTempReg);
  		at: 11 put: opcode;
+ 		at: 12 put: (opcode = 16r85 "Tst; backwards"
+ 					ifTrue: [self mod: ModReg RM: reg RO: ConcreteRISCTempReg]
+ 					ifFalse: [self mod: ModReg RM: ConcreteRISCTempReg RO: reg]).
- 		at: 12 put: (self mod: ModReg RM: ConcreteRISCTempReg RO: reg).
  	^machineCodeSize := 13!

Item was changed:
  ----- 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: resultReg.
+ 	jumpNotSF := self genJumpNotSmallFloatValueBits: resultReg scratch: scratch1.
+ 	self genConvertBitsToSmallFloatIn: resultReg scratch: scratch1.
- 	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 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:"
- 	"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: StackInterpreterSimulator>>primitiveDirectoryEntry (in category 'file primitives') -----
  primitiveDirectoryEntry
+ 	| name pathName arrayNilOrSymbol result |
- 	| name pathName array result |
  	name := self stringOf: self stackTop.
  	pathName := self stringOf: (self stackValue: 1).
  	
  	self successful ifFalse:
  		[^self primitiveFail].
  
+ 	arrayNilOrSymbol := FileDirectory default primLookupEntryIn: pathName name: name.
+ 	arrayNilOrSymbol ifNil:
- 	array := FileDirectory default primLookupEntryIn: pathName name: name.
- 	array == nil ifTrue:
  		[self pop: 3 thenPush: objectMemory nilObject.
+ 		 ^self].
+ 	arrayNilOrSymbol isArray ifFalse:
+ 		[arrayNilOrSymbol ~~ #primFailed ifTrue:
+ 			[self halt].
+ 		 ^self primitiveFail].
- 		^array].
- 	array == #badDirectoryPath ifTrue:
- 		[self halt.
- 		^self primitiveFail].
  
+ 	result := PharoVM 
+ 		ifTrue:
+ 			[self makeDirEntryName: (arrayNilOrSymbol at: 1) size: (arrayNilOrSymbol at: 1) size
+ 				createDate: (arrayNilOrSymbol at: 2) modDate: (arrayNilOrSymbol at: 3)
+ 				isDir: (arrayNilOrSymbol at: 4) fileSize: (arrayNilOrSymbol at: 5)
+ 				posixPermissions: (arrayNilOrSymbol at: 6) isSymlink: (arrayNilOrSymbol at: 7) ]
+ 		ifFalse:
+ 			[self makeDirEntryName: (arrayNilOrSymbol at: 1) size: (arrayNilOrSymbol at: 1) size
+ 				createDate: (arrayNilOrSymbol at: 2) modDate: (arrayNilOrSymbol at: 3)
+ 				isDir: (arrayNilOrSymbol at: 4) fileSize: (arrayNilOrSymbol at: 5) ].
- 	PharoVM 
- 		ifTrue: [ 
- 			result := self makeDirEntryName: (array at: 1) size: (array at: 1) size
- 				createDate: (array at: 2) modDate: (array at: 3)
- 				isDir: (array at: 4) fileSize: (array at: 5)
- 				posixPermissions: (array at: 6) isSymlink: (array at: 7) ]
- 		ifFalse: [ 
- 			result := self makeDirEntryName: (array at: 1) size: (array at: 1) size
- 				createDate: (array at: 2) modDate: (array at: 3)
- 				isDir: (array at: 4)  fileSize: (array at: 5) ].
  	self pop: 3 thenPush: result!



More information about the Vm-dev mailing list