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

commits at source.squeak.org commits at source.squeak.org
Thu Nov 20 06:55:28 UTC 2014


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

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

Name: VMMaker.oscog-eem.946
Author: eem
Time: 19 November 2014, 10:51:08.302 pm
UUID: cdb491d7-dbc3-4758-82fb-f77bab8ce8d5
Ancestors: VMMaker.oscog-eem.945

Fix CArray>>at:put: for 64-bits.
Implement sizeof: in InterpreterPlugin to handle SQFile
and squeakFileOffsetType.  Nuke FilePluginSImulator
implementation.
Use numBytesOf: in signed32BitValueOf:.
Fix 64-bit storeFloatAt:from:.
Fix slip in 64-bit setFormatOf:to:
Fix convertFloatsToPlatformOrder.
Fix SmallInteger class>>ccgCanConvertFrom: for 64 bits.

Simulator now starts up Spur 64-bit image, drawing
entire display correctly.

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

Item was changed:
  ----- Method: CArray>>at: (in category 'accessing') -----
  at: offset
  	| ptrAddress |
  	ptrAddress := self ptrAddress.
  	unitSize = 1 ifTrue: [^ interpreter byteAt: ptrAddress + offset].
  	unitSize = 2 ifTrue: [^ interpreter shortAt: ptrAddress + (offset * 2)].
  	unitSize = 4 ifTrue: [^ interpreter long32At: ptrAddress + (offset * 4)].
+ 	unitSize = 8 ifTrue: [^ interpreter long64At: ptrAddress + (offset * 8)].
  	self halt: 'Can''t handle unitSize ', unitSize printString!

Item was changed:
  ----- Method: CArray>>at:put: (in category 'accessing') -----
  at: offset put: val
  	| ptrAddress |
  	ptrAddress := self ptrAddress.
  	unitSize = 1 ifTrue: [^ interpreter byteAt: ptrAddress + offset put: val].
  	unitSize = 2 ifTrue: [^ interpreter byteAt: ptrAddress + (offset * 2) put: val].
  	unitSize = 4 ifTrue: [^ interpreter long32At: ptrAddress + (offset * 4) put: val].
+ 	unitSize = 8 ifTrue: [^ interpreter long64At: ptrAddress + (offset * 8) put: val].
  	self halt: 'Can''t handle unitSize ', unitSize printString!

Item was removed:
- ----- Method: FilePluginSimulator>>sizeof: (in category 'simulation') -----
- sizeof: objectSymbolOrClass
- 	"In the simulator file handles are just integer indices into openFiles and so need only be BytesPerWord big.  We assume the file offset type is always 64-bit"
- 	| index |
- 	index := #(	#SQFile #squeakFileOffsetType)
- 						indexOf: objectSymbolOrClass
- 						ifAbsent: [^super sizeof: objectSymbolOrClass].
- 	^{interpreterProxy wordSize.
- 	    8 } at: index!

Item was added:
+ ----- Method: InterpreterPlugin>>sizeof: (in category 'simulation support') -----
+ sizeof: objectSymbolOrClass
+ 	<doNotGenerate>
+ 	"In the simulator file handles are just integer indices into openFiles and so need only be BytesPerWord big.
+ 	 But in the actual VM they are 5 words long.  We assume the file offset type is always 64-bit"
+ 	objectSymbolOrClass == #SQFile ifTrue:
+ 		[^interpreterProxy wordSize * 5].
+ 	objectSymbolOrClass == #squeakFileOffsetType ifTrue:
+ 		[^8].
+ 	^super sizeof: objectSymbolOrClass!

Item was changed:
  ----- Method: InterpreterPrimitives>>signed32BitValueOf: (in category 'primitive support') -----
  signed32BitValueOf: oop
  	"Convert the given object into an integer value.
  	The object may be either a positive SmallInteger or a four-byte LargeInteger."
  	| value negative ok |
  	<inline: false>
  	<returnTypeC: #int>
  	<var: #value type: #int>
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[^objectMemory integerValueOf: oop].
  
  	(objectMemory isNonIntegerImmediate: oop) ifTrue:
  		[^self primitiveFail].
  
  	ok := objectMemory isClassOfNonImm: oop
  					equalTo: (objectMemory splObj: ClassLargePositiveInteger)
  					compactClassIndex: ClassLargePositiveIntegerCompactIndex.
  	ok
  		ifTrue: [negative := false]
  		ifFalse:
  			[negative := true.
  			 ok := objectMemory isClassOfNonImm: oop
  							equalTo: (objectMemory splObj: ClassLargeNegativeInteger)
  							compactClassIndex: ClassLargeNegativeIntegerCompactIndex.
  			ok ifFalse: [^self primitiveFail]].
+ 	(objectMemory numBytesOf: oop) > 4 ifTrue:
- 	(objectMemory lengthOf: oop) > 4 ifTrue:
  		[^self primitiveFail].
  
  	value :=  (objectMemory fetchByte: 0 ofObject: oop) +
  			  ((objectMemory fetchByte: 1 ofObject: oop) <<  8) +
  			  ((objectMemory fetchByte: 2 ofObject: oop) << 16) +
  			  ((objectMemory fetchByte: 3 ofObject: oop) << 24).
  	self cCode: []
  		inSmalltalk:
  			[(value anyMask: 16r80000000) ifTrue:
  				[value := value - 16r100000000]].
  	"Filter out values out of range for the signed interpretation such as
  	 16rFFFFFFFF (positive w/ bit 32 set) and -16rFFFFFFFF (negative w/ bit
  	 32 set). Since the sign is implicit in the class we require that the high
  	 bit of the magnitude is not set which is a simple test here.  Note that
  	 we have to handle the most negative 32-bit value -2147483648 specially."
  	value < 0 ifTrue:
  		[self assert: (self sizeof: value) == 4.
  		 "Don't fail for -16r80000000/-2147483648
  		  Alas the simple (negative and: [value - 1 > 0]) isn't adequate since in C the result of signed integer
  		  overflow is undefined and hence under optimization this may fail.  The shift, however, is well-defined."
  		 (negative and: [0 = (self cCode: [value << 1]
  									inSmalltalk: [value << 1 bitAnd: (1 << 32) - 1])]) ifTrue: 
  			[^value].
  		 ^self primitiveFail].
  	^negative
  		ifTrue: [0 - value]
  		ifFalse: [value]!

Item was changed:
  ----- Method: SmallInteger class>>ccgCanConvertFrom: (in category '*VMMaker-plugin generation') -----
  ccgCanConvertFrom: anObject
  
+ 	^anObject isInteger!
- 	^anObject class == self!

Item was changed:
  ----- Method: Spur64BitMMLESimulator>>storeFloatAt:from: (in category 'float primitives') -----
  storeFloatAt: floatBitsAddress from: aFloat
+ 	self long32At: floatBitsAddress put: (aFloat at: 2).
+ 	self long32At: floatBitsAddress+4 put: (aFloat at: 1)!
- 	self long32At: floatBitsAddress put: (aFloat at: 1).
- 	self long32At: floatBitsAddress+4 put: (aFloat at: 2)!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>setFormatOf:to: (in category 'header access') -----
  setFormatOf: objOop to: format
  	"0 = 0 sized objects (UndefinedObject True False et al)
  	 1 = non-indexable objects with inst vars (Point et al)
  	 2 = indexable objects with no inst vars (Array et al)
  	 3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
  	 4 = weak indexable objects with inst vars (WeakArray et al)
  	 5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
  	 6 unused, reserved for exotic pointer objects?
  	 7 Forwarded Object, 1st field is pointer, rest of fields are ignored
  	 8 unused, reserved for exotic non-pointer objects?
  	 9 (?) 64-bit indexable
  	 10 - 11 32-bit indexable
  	 12 - 15 16-bit indexable
  	 16 - 23 byte indexable
  	 24 - 31 compiled method"
  	self assert: (format between: 0 and: self formatMask).
+ 	self longAt: objOop
- 	objOop
  		put: ((self longAt: objOop) bitAnd: (self formatMask << self formatShift) bitInvert64)
  			+ (format << self formatShift)!

Item was changed:
  ----- Method: StackInterpreter>>convertFloatsToPlatformOrder (in category 'image save/restore') -----
  convertFloatsToPlatformOrder
  	"Byte-swap the words of all bytes objects in a range of the 
  	 image, including Strings, ByteArrays, and CompiledMethods.
  	 This returns these objects to their original byte ordering 
  	 after blindly byte-swapping the entire image. For compiled 
  	 methods, byte-swap only their bytecodes part.
  	 Ensure floats are in platform-order."
  	objectMemory vmEndianness = imageFloatsBigEndian ifTrue:
  		[^nil].
  	self assert: ClassFloatCompactIndex ~= 0.
  	objectMemory allObjectsDo:
  		[:obj| | temp |
  		(objectMemory compactClassIndexOf: obj) = ClassFloatCompactIndex ifTrue:
+ 			[temp := objectMemory long32At: obj + objectMemory baseHeaderSize.
+ 			 objectMemory long32At: obj + objectMemory baseHeaderSize put: (objectMemory long32At: obj + objectMemory baseHeaderSize + 4).
+ 			 objectMemory long32At: obj + objectMemory baseHeaderSize + 4 put: temp]]!
- 			[temp := self longAt: obj + objectMemory baseHeaderSize.
- 			 self longAt: obj + objectMemory baseHeaderSize put: (self longAt: obj + objectMemory baseHeaderSize + 4).
- 			 self longAt: obj + objectMemory baseHeaderSize + 4 put: temp]]!



More information about the Vm-dev mailing list