VM Maker: VMMaker.oscog-eem.2665.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker.oscog-eem.2665.mcz

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

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

Name: VMMaker.oscog-eem.2665
Author: eem
Time: 18 January 2020, 6:27:06.366466 pm
UUID: 8e071f1a-2517-4296-a4f9-5d4f3898f6f9
Ancestors: VMMaker.oscog-eem.2664

Spur:
Succumb to temptation and avoid moving the value through the FPU in 64-bit floatAt:[put:].  Rename the primitives to fit the house style (primitiveSpurFoo, not primitiveFooSpur).
Refactor smallFloatObjectOf: to avoid duplication.

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

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveFloatArrayAt (in category 'indexing primitives') -----
  primitiveFloatArrayAt
  "Index the receiver, which must be an indexable non-pointer
  object, and yield a float."
  objectMemory hasSpurMemoryManagerAPI
+ ifTrue: [self primitiveSpurFloatArrayAt]
- ifTrue: [self primitiveFloatArrayAtSpur]
  ifFalse: [self primitiveFailFor: PrimErrUnsupported]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveFloatArrayAtPut (in category 'indexing primitives') -----
  primitiveFloatArrayAtPut
  "Index the receiver, which must be an indexable non-pointer
  object, and store a float."
  objectMemory hasSpurMemoryManagerAPI
+ ifTrue: [self primitiveSpurFloatArrayAtPut]
- ifTrue: [self primitiveFloatArrayAtPutSpur]
  ifFalse: [self primitiveFailFor: PrimErrUnsupported]!

Item was removed:
- ----- Method: InterpreterPrimitives>>primitiveFloatArrayAtPutSpur (in category 'indexing primitives') -----
- primitiveFloatArrayAtPutSpur
- "Index the receiver, which must be an indexable non-pointer
- object, and store a float. In Spur, if the receiver is a WordArray the float is
- stored in IEEE single precision (if possible), and if a DoubleWordArray in
- IEEE double precision."
-
- <inline: true>
- | index rcvr valueOop fmt numSlots |
- valueOop := self stackValue: 0.
- index := self stackValue: 1.
- rcvr := self stackValue: 2.
- ((objectMemory isFloatInstance: valueOop)
- and: [objectMemory isIntegerObject: index]) ifFalse:
- [^self primitiveFailFor: PrimErrBadArgument].
- (objectMemory isImmediate: rcvr) ifTrue:
- [^self primitiveFailFor: PrimErrBadReceiver].
- (objectMemory isObjImmutable: rcvr) ifTrue:
- [^self primitiveFailFor: PrimErrNoModification].
- fmt := objectMemory formatOf: rcvr.
- index := (objectMemory integerValueOf: index) - 1.
-
- fmt = objectMemory sixtyFourBitIndexableFormat ifTrue:
- ["Note that a high-quality implementation would not move bits to/from the double data type,
-  but simply move bits. We leave this sophistication to the JIT implementation."
- numSlots := objectMemory num64BitUnitsOf: rcvr.
- (self asUnsigned: index) < numSlots ifTrue:
- [objectMemory storeFloat64: index ofObject: rcvr withValue: (objectMemory floatValueOf: valueOop).
- self methodReturnValue: valueOop.
- ^0].
- ^self primitiveFailFor: PrimErrBadIndex].
-
- "N.B. Currently we simply truncate to 32-bits, which matches the behavior of the FloatArrayPlugin.
- Maybe we should validate and range check."
- (fmt >= objectMemory firstLongFormat
- and: [fmt <= (objectMemory firstLongFormat + 1)]) ifTrue:
- [numSlots := objectMemory num32BitUnitsOf: rcvr.
- (self asUnsigned: index) < numSlots ifTrue:
- [objectMemory storeFloat32: index ofObject: rcvr withValue: (objectMemory floatValueOf: valueOop).
- self methodReturnValue: valueOop.
- ^0].
- ^self primitiveFailFor: PrimErrBadIndex].
-
- ^self primitiveFailFor: PrimErrBadReceiver!

Item was removed:
- ----- Method: InterpreterPrimitives>>primitiveFloatArrayAtSpur (in category 'indexing primitives') -----
- primitiveFloatArrayAtSpur
- "Index the receiver, which must be an indexable non-pointer object,
- and yield a float. In Spur, if the receiver is a WordArray the float is
- interpreted as IEEE single precision, and if a DoubleWordArray as
- IEEE double precision."
-
- <inline: true>
- | index rcvr fmt numSlots aDouble aFloat |
- index := self stackTop.
- rcvr := self stackValue: 1.
- (objectMemory isIntegerObject: index) ifFalse:
- [^self primitiveFailFor: PrimErrBadArgument].
- (objectMemory isImmediate: rcvr) ifTrue:
- [^self primitiveFailFor: PrimErrBadReceiver].
- fmt := objectMemory formatOf: rcvr.
- index := (objectMemory integerValueOf: index) - 1.
-
- fmt = objectMemory sixtyFourBitIndexableFormat ifTrue:
- ["Note that a high-quality implementation would not move bits to/from the double data type,
-  but simply move bits. We leave this sophistication to the JIT implementation."
- numSlots := objectMemory num64BitUnitsOf: rcvr.
- (self asUnsigned: index) < numSlots ifTrue:
- [aDouble := objectMemory fetchFloat64: index ofObject: rcvr.
- self methodReturnValue: (objectMemory floatObjectOf: aDouble).
- ^0].
- ^self primitiveFailFor: PrimErrBadIndex].
-
- (fmt >= objectMemory firstLongFormat
- and: [fmt <= (objectMemory firstLongFormat + 1)]) ifTrue:
- [numSlots := objectMemory num32BitUnitsOf: rcvr.
- (self asUnsigned: index) < numSlots ifTrue:
- [aFloat := objectMemory fetchFloat32: index ofObject: rcvr.
- self methodReturnValue: (objectMemory floatObjectOf: aFloat).
- ^0].
- ^self primitiveFailFor: PrimErrBadIndex].
-
- ^self primitiveFailFor: PrimErrBadReceiver!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSpurFloatArrayAt (in category 'indexing primitives') -----
+ primitiveSpurFloatArrayAt
+ "Index the receiver, which must be an indexable non-pointer object,
+ and yield a float. In Spur, if the receiver is a WordArray the float is
+ interpreted as IEEE single precision, and if a DoubleWordArray as
+ IEEE double precision."
+
+ <inline: true>
+ | index rcvr fmt numSlots aFloat doubleBits |
+ index := self stackTop.
+ rcvr := self stackValue: 1.
+ (objectMemory isIntegerObject: index) ifFalse:
+ [^self primitiveFailFor: PrimErrBadArgument].
+ (objectMemory isImmediate: rcvr) ifTrue:
+ [^self primitiveFailFor: PrimErrBadReceiver].
+ fmt := objectMemory formatOf: rcvr.
+ index := (objectMemory integerValueOf: index) - 1.
+
+ fmt = objectMemory sixtyFourBitIndexableFormat ifTrue:
+ [numSlots := objectMemory num64BitUnitsOf: rcvr.
+ (self asUnsigned: index) < numSlots ifTrue:
+ [doubleBits := objectMemory fetchLong64: index ofObject: rcvr.
+ self methodReturnValue: (objectMemory floatObjectOfBits: doubleBits).
+ ^0].
+ ^self primitiveFailFor: PrimErrBadIndex].
+
+ (fmt >= objectMemory firstLongFormat
+ and: [fmt <= (objectMemory firstLongFormat + 1)]) ifTrue:
+ [numSlots := objectMemory num32BitUnitsOf: rcvr.
+ (self asUnsigned: index) < numSlots ifTrue:
+ [aFloat := objectMemory fetchFloat32: index ofObject: rcvr.
+ self methodReturnValue: (objectMemory floatObjectOf: aFloat).
+ ^0].
+ ^self primitiveFailFor: PrimErrBadIndex].
+
+ ^self primitiveFailFor: PrimErrBadReceiver!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveSpurFloatArrayAtPut (in category 'indexing primitives') -----
+ primitiveSpurFloatArrayAtPut
+ "Index the receiver, which must be an indexable non-pointer
+ object, and store a float. In Spur, if the receiver is a WordArray the float is
+ stored in IEEE single precision (if possible), and if a DoubleWordArray in
+ IEEE double precision."
+
+ <inline: true>
+ | index rcvr valueOop fmt numSlots |
+ valueOop := self stackValue: 0.
+ index := self stackValue: 1.
+ rcvr := self stackValue: 2.
+ ((objectMemory isFloatInstance: valueOop)
+ and: [objectMemory isIntegerObject: index]) ifFalse:
+ [^self primitiveFailFor: PrimErrBadArgument].
+ (objectMemory isImmediate: rcvr) ifTrue:
+ [^self primitiveFailFor: PrimErrBadReceiver].
+ (objectMemory isObjImmutable: rcvr) ifTrue:
+ [^self primitiveFailFor: PrimErrNoModification].
+ fmt := objectMemory formatOf: rcvr.
+ index := (objectMemory integerValueOf: index) - 1.
+
+ fmt = objectMemory sixtyFourBitIndexableFormat ifTrue:
+ [numSlots := objectMemory num64BitUnitsOf: rcvr.
+ (self asUnsigned: index) < numSlots ifTrue:
+ [objectMemory storeLong64: index ofObject: rcvr withValue: (objectMemory floatValueBitsOf: valueOop).
+ self methodReturnValue: valueOop.
+ ^0].
+ ^self primitiveFailFor: PrimErrBadIndex].
+
+ "N.B. Currently we simply truncate to 32-bits, which matches the behavior of the FloatArrayPlugin.
+ Maybe we should validate and range check."
+ (fmt >= objectMemory firstLongFormat
+ and: [fmt <= (objectMemory firstLongFormat + 1)]) ifTrue:
+ [numSlots := objectMemory num32BitUnitsOf: rcvr.
+ (self asUnsigned: index) < numSlots ifTrue:
+ [objectMemory storeFloat32: index ofObject: rcvr withValue: (objectMemory floatValueOf: valueOop).
+ self methodReturnValue: valueOop.
+ ^0].
+ ^self primitiveFailFor: PrimErrBadIndex].
+
+ ^self primitiveFailFor: PrimErrBadReceiver!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>floatObjectOfBits: (in category 'interpreter access') -----
+ floatObjectOfBits: doubleFloatBits
+ <var: 'doubleFloatBits' type: #sqLong>
+ | newFloatObj |
+ newFloatObj := self
+ eeInstantiateSmallClassIndex: ClassFloatCompactIndex
+ format: self firstLongFormat
+ numSlots: (self sizeof: #double) / self bytesPerOop.
+ self storeLong64: 0 ofObject: newFloatObj withValue: doubleFloatBits.
+ ^newFloatObj!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>floatValueBitsOf: (in category 'interpreter access') -----
+ floatValueBitsOf: floatOop
+ "Answer the 64-bit value of the argument."
+ self assert: (self isFloatInstance: floatOop).
+ ^self fetchLong64: 0 ofObject: floatOop!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>floatObjectOfBits: (in category 'interpreter access') -----
+ floatObjectOfBits: doubleFloatBits
+ <var: 'doubleFloatBits' type: #sqLong>
+ | newFloatObj |
+ (self isSmallFloatValueBits: doubleFloatBits) ifTrue:
+ [^self smallFloatObjectOfBits: doubleFloatBits].
+ newFloatObj := self
+ eeInstantiateSmallClassIndex: ClassFloatCompactIndex
+ format: self firstLongFormat
+ numSlots: (self sizeof: #double) / self bytesPerOop.
+ self storeLong64: 0 ofObject: newFloatObj withValue: doubleFloatBits.
+ ^newFloatObj!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>floatValueBitsOf: (in category 'interpreter access') -----
+ floatValueBitsOf: floatOop
+ "Answer the 64-bit value of the argument as raw bits."
+ <inline: false>
+ self assert: (self isFloatInstance: floatOop).
+ (floatOop bitAnd: self tagMask) ~= 0 ifTrue:
+ [^self smallFloatBitsOf: floatOop].
+ ^self fetchLong64: 0 ofObject: floatOop!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>isSmallFloatValueBits: (in category 'interpreter access') -----
+ isSmallFloatValueBits: rawFloatBits
+ <inline: true>
+ <var: #rawFloatBits type: #usqLong>
+ | exponent |
+ exponent := rawFloatBits >> self smallFloatMantissaBits bitAnd: 16r7FF.
+ ^exponent > self smallFloatExponentOffset
+ ifTrue: [exponent <= (255 + self smallFloatExponentOffset)]
+ ifFalse:
+ [(rawFloatBits bitAnd: (1 << self smallFloatMantissaBits - 1)) = 0
+ ifTrue: [exponent = 0]
+ ifFalse: [exponent = self smallFloatExponentOffset]]!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>smallFloatObjectOf: (in category 'interpreter access') -----
  smallFloatObjectOf: aFloat
  "Encode the argument, aFloat in the SmallFloat range, as a tagged small float.
  See section 61-bit Immediate Floats in the SpurMemoryManager class comment.
 
  Encode: [1s][     11 exponent     ][52mantissa]
  rot sign: [     11 exponent     ][52mantissa][1s]
  sub exponent offset: [ 000 ][8expsubset][52 mantissa][1s]
  shift: [8expsubset][52 mantissa][1s][ 000 ]
  or/add tags: [8expsubset][52mantissa][1s][3tags]"
  <inline: true>
  <returnTypeC: #sqInt>
  <var: #aFloat type: #double>
+ | rawFloat |
- | rawFloat rot |
  <var: #rawFloat type: #usqLong>
- <var: #rot type: #usqLong>
  self assert: (self isSmallFloatValue: aFloat).
  self
  cCode: [self memcpy: (self addressOf: rawFloat) _: (self addressOf: aFloat) _: (self sizeof: rawFloat)]
  inSmalltalk: [rawFloat := (aFloat at: 1) << 32 + (aFloat at: 2)].
+ ^self smallFloatObjectOfBits: rawFloat!
- rot := self rotateLeft: rawFloat.
- rot > 1 ifTrue: "a.k.a. ~= +/-0.0"
- [rot := rot - (self smallFloatExponentOffset << (self smallFloatMantissaBits + 1)).
- self assert: rot > 0].
- ^self cCode: [rot << self numTagBits + self smallFloatTag]
- inSmalltalk: [((rot << self numTagBits) bitAnd: 16rFFFFFFFFFFFFFFFF) + self smallFloatTag]!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>smallFloatObjectOfBits: (in category 'interpreter access') -----
+ smallFloatObjectOfBits: rawFloatBits
+ "Encode the argument, rawFloatBits in the SmallFloat range, as a tagged small float.
+ See section 61-bit Immediate Floats in the SpurMemoryManager class comment.
+
+ Encode: [1s][     11 exponent     ][52mantissa]
+ rot sign: [     11 exponent     ][52mantissa][1s]
+ sub exponent offset: [ 000 ][8expsubset][52 mantissa][1s]
+ shift: [8expsubset][52 mantissa][1s][ 000 ]
+ or/add tags: [8expsubset][52mantissa][1s][3tags]"
+ <inline: #always>
+ <returnTypeC: #sqInt>
+ | rot |
+ <var: #rawFloatBits type: #usqLong>
+ <var: #rot type: #usqLong>
+ self assert: (self isSmallFloatValueBits: rawFloatBits).
+ rot := self rotateLeft: rawFloatBits.
+ rot > 1 ifTrue: "a.k.a. ~= +/-0.0"
+ [rot := rot - (self smallFloatExponentOffset << (self smallFloatMantissaBits + 1)).
+ self assert: rot > 0].
+ ^self cCode: [rot << self numTagBits + self smallFloatTag]
+ inSmalltalk: [((rot << self numTagBits) bitAnd: 16rFFFFFFFFFFFFFFFF) + self smallFloatTag]!