The Inbox: Collections-nice.891.mcz

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

The Inbox: Collections-nice.891.mcz

commits-2
Nicolas Cellier uploaded a new version of Collections to project The Inbox:
http://source.squeak.org/inbox/Collections-nice.891.mcz

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

Name: Collections-nice.891
Author: nice
Time: 2 May 2020, 7:40:45.298967 pm
UUID: 08510be0-8293-6744-959d-c1d41bc13ae1
Ancestors: Collections-nice.890

Experimental - For discussion

Group some (most) non-pointers collections under an abstract FixedBitWifthArray.
I know, the name is hard to pronounce and thus ugly: it's opened to discussion.

This enables factorization of some methods, for example the trick for atAllPut:
Also notice that most methods are shared between FloatArray and Float64Array.

Introduce SignedByteArray and Long64Array.
These are the only two missing in the panoply.
The heterogeneity of names generally sucks, but we won't change the ByteArray nor WordArray, so probably neither the DoubleByte and DoubleWord Arrays, it follows a legacy-compatible logic.
But for the 32 and 16 bits signed versions, we already have IntegerArray and ShortIntegerArray... What a mess.

We could use better names in the abstract levels too:
For example SignedIntegerArray instead of FixedBitWidthSignedIntegerArray.
Also we could let FloatArray be the abstract class rather than FixedBitWidthFloatArray.
It would be a factory for Float32Array so as to preserve backward compatiblity.

Note that Balloon ShortIntegerArray is currently word rather than doubleByte and should be mutated and moved into this collection. However, it's not easy to mutate because it has both a subclass and instances. We can handle that surgery later.

We can neither easily move ByteArray thru the hierarchy: it is protected because of the fear to break CompiledMethod. Another surgical operation, outside of this proof of concept.

One thing I don't know is the cost of extending intermediate hierachical levels with respect to lookup of message selector. Is it a problem?

While at it, document the internal format of ColorArray.
I hope it's consistent across VMs/platforms/endianness... If it's not, the comment SHALL tell so, that's the least I expect of serious software. I don't know why squeakers are so spare of comments...
Since those classes are good candidates for exchanging data with foreign functions, it's vital to have a minimum of documentation.

=============== Diff against Collections-nice.890 ===============

Item was changed:
+ FixedBitWidthArray variableWordSubclass: #ColorArray
- ArrayedCollection variableWordSubclass: #ColorArray
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Collections-Arrayed'!
+
+ !ColorArray commentStamp: 'nice 5/2/2020 17:11' prior: 0!
+ A ColorArray is an array of colors encoded on 32-bits.
+
+ The encoding of colors follows the ARGB scheme.
+ See https://en.wikipedia.org/wiki/RGBA_color_model
+
+ The color is decomposed into 4 channels of 8 bits (4 bytes)
+ - the most significant byte A is alpha channel which governs transparency
+   0 means a completely transparent (invisible) color
+   255 means an opaque color.
+ - the second most significant byte R encodes the level of red
+   the lower, the darker and/or least saturated
+ - the third most significant byte G encodes the level of green
+ - the least significant byte B encodes the level of blue
+
+ Color white is encoded as 16rFFFFFFFF.
+ ((ColorArray with: Color white) basicAt: 1) hex.
+ For historical reasons, notice that Color black is encoded as a very dark blue 16rFF000001 rather than 16rFF000000.
+ ((ColorArray with: Color black) basicAt: 1) hex.
+ Other example of pure red, pure green and pure blue showing the bit position of those channels:
+ ((ColorArray with: Color red) basicAt: 1) hex.
+ ((ColorArray with: Color green) basicAt: 1) hex.
+ ((ColorArray with: Color blue) basicAt: 1) hex.
+ Color transparent is encoded as zero on all channels:
+ ((ColorArray with: Color transparent) basicAt: 1) hex.!

Item was changed:
+ FixedBitWidthUnsignedIntegerArray variableDoubleByteSubclass: #DoubleByteArray
- ArrayedCollection variableDoubleByteSubclass: #DoubleByteArray
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Collections-Arrayed'!
 
  !DoubleByteArray commentStamp: 'nice 10/20/2016 23:23' prior: 0!
  DoubleByteArrays store 16-bit unsigned Integer values.!

Item was removed:
- ----- Method: DoubleByteArray>>defaultElement (in category 'accessing') -----
- defaultElement
- "Return the default element of the receiver"
- ^0!

Item was removed:
- ----- Method: DoubleByteArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
- replaceFrom: start to: stop with: replacement startingAt: repStart
- "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
- <primitive: 105>
- super replaceFrom: start to: stop with: replacement startingAt: repStart!

Item was changed:
+ FixedBitWidthUnsignedIntegerArray variableDoubleWordSubclass: #DoubleWordArray
- ArrayedCollection variableDoubleWordSubclass: #DoubleWordArray
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Collections-Arrayed'!
 
  !DoubleWordArray commentStamp: 'nice 9/20/2016 23:37' prior: 0!
  DoubleWordArrays store 64-bit unsigned Integer values.!

Item was removed:
- ----- Method: DoubleWordArray>>defaultElement (in category 'accessing') -----
- defaultElement
- "Return the default element of the receiver"
- ^0!

Item was removed:
- ----- Method: DoubleWordArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
- replaceFrom: start to: stop with: replacement startingAt: repStart
- "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
- <primitive: 105>
- super replaceFrom: start to: stop with: replacement startingAt: repStart!

Item was added:
+ ArrayedCollection subclass: #FixedBitWidthArray
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Collections-Arrayed'!
+
+ !FixedBitWidthArray commentStamp: 'nice 5/2/2020 18:58' prior: 0!
+ A FixedBitWidthArray is an abstract superclass for all arrays whose elements are not stored as pointer but as raw bits of fixed-width.
+ Currently, SpurVM supports arrays of elements with a bit-width of 8, 16, 32, or 64 bits.
+ When accessing a specific element with #basicAt: or #basicAt:put:, the bits are exchanged under the form of an unsigned Integer.
+ The range of such integer must be between 0 and 2**bitWidth-1 (which translates as 1<<bitWidth-1).
+
+ The subclasses are free to re-interpret those bits as more specialized Objects and shall provide convenient #at: and #at:put: protocol for exchanging those objects rather than raw bit-encoding.
+ For example, there is support for Signed Integers of different width, IEEE 754 32bits and 64bits Float, 32 bits Colors, etc...
+
+ It is the subclass responsibility to encode those objects as raw bits (an Integer), and decode the raw bits (an Integer) as an object.
+ Note however that SpurVM supports conversion to/from signed integer.
+
+ The name of subclasses is historical and constrained by backward compatibility.!

Item was added:
+ ----- Method: FixedBitWidthArray>>atAllPut: (in category 'accessing') -----
+ atAllPut: anObject
+ self isEmpty ifTrue: [^self].
+ "Note: primitiveConstantFill does only handle unsigned integer.
+ Let at:put: take care of properly encoding anObject as bits"
+ self at: 1 put: anObject.
+ self primFill: (self basicAt: 1)!

Item was added:
+ ----- Method: FixedBitWidthArray>>primFill: (in category 'private') -----
+ primFill: aPositiveInteger
+ "Fill the receiver, an indexable bytes or words object, with the given positive integer.
+ The range of possible fill values is :
+ - [0..255] for byte arrays;
+ - [0..65535] for double byte arrays;
+ - [0..(2^32 - 1)] for word arrays;
+ - [0..(2^64 - 1)] for double word arrays."
+
+ <primitive: 145>
+ self errorImproperStore.!

Item was added:
+ FixedBitWidthArray subclass: #FixedBitWidthFloatArray
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Collections-Arrayed'!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>* (in category 'arithmetic') -----
+ * anObject
+
+ ^self shallowCopy *= anObject!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>*= (in category 'arithmetic') -----
+ *= anObject
+ ^anObject isNumber
+ ifTrue:[self primMulScalar: anObject asFloat]
+ ifFalse:[self primMulArray: anObject]!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>+ (in category 'arithmetic') -----
+ + anObject
+
+ ^self shallowCopy += anObject!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>+= (in category 'arithmetic') -----
+ += anObject
+ ^anObject isNumber
+ ifTrue:[self primAddScalar: anObject asFloat]
+ ifFalse:[self primAddArray: anObject]!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>- (in category 'arithmetic') -----
+ - anObject
+
+ ^self shallowCopy -= anObject!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>-= (in category 'arithmetic') -----
+ -= anObject
+ ^anObject isNumber
+ ifTrue:[self primSubScalar: anObject asFloat]
+ ifFalse:[self primSubArray: anObject]!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>/ (in category 'arithmetic') -----
+ / anObject
+
+ ^self shallowCopy /= anObject!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>/= (in category 'arithmetic') -----
+ /= anObject
+ ^anObject isNumber
+ ifTrue:[self primDivScalar: anObject asFloat]
+ ifFalse:[self primDivArray: anObject]!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>\\= (in category 'arithmetic') -----
+ \\= other
+
+ other isNumber ifTrue: [
+ 1 to: self size do: [:i |
+ self at: i put: (self at: i) \\ other
+ ].
+ ^ self.
+ ].
+ 1 to: (self size min: other size) do: [:i |
+ self at: i put: (self at: i) \\ (other at: i).
+ ].
+
+ !

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>adaptToNumber:andSend: (in category 'arithmetic') -----
+ adaptToNumber: rcvr andSend: selector
+ "If I am involved in arithmetic with a Number. If possible,
+ convert it to a float and perform the (more efficient) primitive operation."
+ selector == #+ ifTrue:[^self + rcvr].
+ selector == #* ifTrue:[^self * rcvr].
+ selector == #- ifTrue:[^self negated += rcvr].
+ selector == #/ ifTrue:[
+ "DO NOT USE TRIVIAL CODE
+ ^self reciprocal * rcvr
+ BECAUSE OF GRADUAL UNDERFLOW
+ self should: (1.0e-39 / (FloatArray with: 1.0e-39)) first < 2."
+ ^(self class new: self size withAll: rcvr) / self
+ ].
+ ^super adaptToNumber: rcvr andSend: selector!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>defaultElement (in category 'accessing') -----
+ defaultElement
+ "Return the default element of the receiver"
+ ^0.0!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>length (in category 'accessing') -----
+ length
+ "Return the length of the receiver"
+ ^self squaredLength sqrt!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>negated (in category 'arithmetic') -----
+ negated
+
+ ^self shallowCopy *= -1!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
+ replaceFrom: start to: stop with: replacement startingAt: repStart
+ "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
+ <primitive: 105>
+ super replaceFrom: start to: stop with: replacement startingAt: repStart!

Item was added:
+ ----- Method: FixedBitWidthFloatArray>>squaredLength (in category 'accessing') -----
+ squaredLength
+ "Return the squared length of the receiver"
+ ^self dot: self!

Item was added:
+ FixedBitWidthArray subclass: #FixedBitWidthSignedIntegerArray
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Collections-Arrayed'!
+
+ !FixedBitWidthSignedIntegerArray commentStamp: 'nice 5/2/2020 16:30' prior: 0!
+ A FixedBitWidthSignedIntegerArray is an abstract class for all arrays of signed integer of fixed bit-width.
+
+ !

Item was added:
+ ----- Method: FixedBitWidthSignedIntegerArray>>defaultElement (in category 'accessing') -----
+ defaultElement
+ "Return the default element of the receiver"
+ ^0!

Item was added:
+ FixedBitWidthArray subclass: #FixedBitWidthUnsignedIntegerArray
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Collections-Arrayed'!
+
+ !FixedBitWidthUnsignedIntegerArray commentStamp: 'nice 5/2/2020 16:47' prior: 0!
+ A FixedBitWidthUnsignedIntegerArray is an abstract class for all arrays of unsigned integer of fixed bit-width.
+
+ !

Item was added:
+ ----- Method: FixedBitWidthUnsignedIntegerArray>>atAllPut: (in category 'accessing') -----
+ atAllPut: value
+ "Fill the receiver with the given value"
+
+ <primitive: 145>
+ super atAllPut: value!

Item was added:
+ ----- Method: FixedBitWidthUnsignedIntegerArray>>defaultElement (in category 'accessing') -----
+ defaultElement
+ "Return the default element of the receiver"
+ ^0!

Item was added:
+ ----- Method: FixedBitWidthUnsignedIntegerArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
+ replaceFrom: start to: stop with: replacement startingAt: repStart
+ <primitive: 105>
+ ^super replaceFrom: start to: stop with: replacement startingAt: repStart !

Item was changed:
+ FixedBitWidthFloatArray variableDoubleWordSubclass: #Float64Array
- ArrayedCollection variableDoubleWordSubclass: #Float64Array
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Collections-Arrayed'!
 
  !Float64Array commentStamp: '<historical>' prior: 0!
  Float64Arrays store 64bit IEEE floating point numbers.!

Item was removed:
- ----- Method: Float64Array>>* (in category 'arithmetic') -----
- * anObject
-
- ^self shallowCopy *= anObject!

Item was removed:
- ----- Method: Float64Array>>*= (in category 'arithmetic') -----
- *= anObject
- ^anObject isNumber
- ifTrue:[self primMulScalar: anObject asFloat]
- ifFalse:[self primMulArray: anObject]!

Item was removed:
- ----- Method: Float64Array>>+ (in category 'arithmetic') -----
- + anObject
-
- ^self shallowCopy += anObject!

Item was removed:
- ----- Method: Float64Array>>+= (in category 'arithmetic') -----
- += anObject
- ^anObject isNumber
- ifTrue:[self primAddScalar: anObject asFloat]
- ifFalse:[self primAddArray: anObject]!

Item was removed:
- ----- Method: Float64Array>>- (in category 'arithmetic') -----
- - anObject
-
- ^self shallowCopy -= anObject!

Item was removed:
- ----- Method: Float64Array>>-= (in category 'arithmetic') -----
- -= anObject
- ^anObject isNumber
- ifTrue:[self primSubScalar: anObject asFloat]
- ifFalse:[self primSubArray: anObject]!

Item was removed:
- ----- Method: Float64Array>>/ (in category 'arithmetic') -----
- / anObject
-
- ^self shallowCopy /= anObject!

Item was removed:
- ----- Method: Float64Array>>/= (in category 'arithmetic') -----
- /= anObject
- ^anObject isNumber
- ifTrue:[self primDivScalar: anObject asFloat]
- ifFalse:[self primDivArray: anObject]!

Item was removed:
- ----- Method: Float64Array>>\\= (in category 'arithmetic') -----
- \\= other
-
- other isNumber ifTrue: [
- 1 to: self size do: [:i |
- self at: i put: (self at: i) \\ other
- ].
- ^ self.
- ].
- 1 to: (self size min: other size) do: [:i |
- self at: i put: (self at: i) \\ (other at: i).
- ].
-
- !

Item was removed:
- ----- Method: Float64Array>>adaptToNumber:andSend: (in category 'arithmetic') -----
- adaptToNumber: rcvr andSend: selector
- "If I am involved in arithmetic with a Number. If possible,
- convert it to a float and perform the (more efficient) primitive operation."
- selector == #+ ifTrue:[^self + rcvr].
- selector == #* ifTrue:[^self * rcvr].
- selector == #- ifTrue:[^self negated += rcvr].
- selector == #/ ifTrue:[
- "DO NOT USE TRIVIAL CODE
- ^self reciprocal * rcvr
- BECAUSE OF GRADUAL UNDERFLOW
- self should: (1.0e-39 / (Float64Array with: 1.0e-39)) first < 2."
- ^(self class new: self size withAll: rcvr) / self
- ].
- ^super adaptToNumber: rcvr andSend: selector!

Item was added:
+ ----- Method: Float64Array>>byteSize (in category 'accessing') -----
+ byteSize
+ ^self size * 8!

Item was added:
+ ----- Method: Float64Array>>bytesPerElement (in category 'accessing') -----
+ bytesPerElement
+ "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
+ ^ 8!

Item was removed:
- ----- Method: Float64Array>>defaultElement (in category 'accessing') -----
- defaultElement
- "Return the default element of the receiver"
- ^0.0!

Item was removed:
- ----- Method: Float64Array>>length (in category 'accessing') -----
- length
- "Return the length of the receiver"
- ^self squaredLength sqrt!

Item was removed:
- ----- Method: Float64Array>>negated (in category 'arithmetic') -----
- negated
-
- ^self shallowCopy *= -1!

Item was removed:
- ----- Method: Float64Array>>replaceFrom:to:with:startingAt: (in category 'private') -----
- replaceFrom: start to: stop with: replacement startingAt: repStart
- "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
- <primitive: 105>
- super replaceFrom: start to: stop with: replacement startingAt: repStart!

Item was removed:
- ----- Method: Float64Array>>squaredLength (in category 'accessing') -----
- squaredLength
- "Return the squared length of the receiver"
- ^self dot: self!

Item was changed:
+ FixedBitWidthFloatArray variableWordSubclass: #FloatArray
- ArrayedCollection variableWordSubclass: #FloatArray
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Collections-Arrayed'!
 
  !FloatArray commentStamp: '<historical>' prior: 0!
  FloatArrays store 32bit IEEE floating point numbers.!

Item was removed:
- ----- Method: FloatArray>>* (in category 'arithmetic') -----
- * anObject
-
- ^self shallowCopy *= anObject!

Item was removed:
- ----- Method: FloatArray>>*= (in category 'arithmetic') -----
- *= anObject
- ^anObject isNumber
- ifTrue:[self primMulScalar: anObject asFloat]
- ifFalse:[self primMulArray: anObject]!

Item was removed:
- ----- Method: FloatArray>>+ (in category 'arithmetic') -----
- + anObject
-
- ^self shallowCopy += anObject!

Item was removed:
- ----- Method: FloatArray>>+= (in category 'arithmetic') -----
- += anObject
- ^anObject isNumber
- ifTrue:[self primAddScalar: anObject asFloat]
- ifFalse:[self primAddArray: anObject]!

Item was removed:
- ----- Method: FloatArray>>- (in category 'arithmetic') -----
- - anObject
-
- ^self shallowCopy -= anObject!

Item was removed:
- ----- Method: FloatArray>>-= (in category 'arithmetic') -----
- -= anObject
- ^anObject isNumber
- ifTrue:[self primSubScalar: anObject asFloat]
- ifFalse:[self primSubArray: anObject]!

Item was removed:
- ----- Method: FloatArray>>/ (in category 'arithmetic') -----
- / anObject
-
- ^self shallowCopy /= anObject!

Item was removed:
- ----- Method: FloatArray>>/= (in category 'arithmetic') -----
- /= anObject
- ^anObject isNumber
- ifTrue:[self primDivScalar: anObject asFloat]
- ifFalse:[self primDivArray: anObject]!

Item was removed:
- ----- Method: FloatArray>>\\= (in category 'arithmetic') -----
- \\= other
-
- other isNumber ifTrue: [
- 1 to: self size do: [:i |
- self at: i put: (self at: i) \\ other
- ].
- ^ self.
- ].
- 1 to: (self size min: other size) do: [:i |
- self at: i put: (self at: i) \\ (other at: i).
- ].
-
- !

Item was removed:
- ----- Method: FloatArray>>adaptToNumber:andSend: (in category 'arithmetic') -----
- adaptToNumber: rcvr andSend: selector
- "If I am involved in arithmetic with a Number. If possible,
- convert it to a float and perform the (more efficient) primitive operation."
- selector == #+ ifTrue:[^self + rcvr].
- selector == #* ifTrue:[^self * rcvr].
- selector == #- ifTrue:[^self negated += rcvr].
- selector == #/ ifTrue:[
- "DO NOT USE TRIVIAL CODE
- ^self reciprocal * rcvr
- BECAUSE OF GRADUAL UNDERFLOW
- self should: (1.0e-39 / (FloatArray with: 1.0e-39)) first < 2."
- ^(self class new: self size withAll: rcvr) / self
- ].
- ^super adaptToNumber: rcvr andSend: selector!

Item was added:
+ ----- Method: FloatArray>>byteSize (in category 'accessing') -----
+ byteSize
+ ^self size * 4!

Item was added:
+ ----- Method: FloatArray>>bytesPerElement (in category 'accessing') -----
+ bytesPerElement
+ "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
+ ^ 4!

Item was removed:
- ----- Method: FloatArray>>defaultElement (in category 'accessing') -----
- defaultElement
- "Return the default element of the receiver"
- ^0.0!

Item was removed:
- ----- Method: FloatArray>>length (in category 'accessing') -----
- length
- "Return the length of the receiver"
- ^self squaredLength sqrt!

Item was removed:
- ----- Method: FloatArray>>negated (in category 'arithmetic') -----
- negated
-
- ^self shallowCopy *= -1!

Item was removed:
- ----- Method: FloatArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
- replaceFrom: start to: stop with: replacement startingAt: repStart
- "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
- <primitive: 105>
- super replaceFrom: start to: stop with: replacement startingAt: repStart!

Item was removed:
- ----- Method: FloatArray>>squaredLength (in category 'accessing') -----
- squaredLength
- "Return the squared length of the receiver"
- ^self dot: self!

Item was changed:
+ FixedBitWidthSignedIntegerArray variableWordSubclass: #IntegerArray
- ArrayedCollection variableWordSubclass: #IntegerArray
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Collections-Arrayed'!
 
  !IntegerArray commentStamp: '<historical>' prior: 0!
  IntegerArrays store 32bit signed Integer values.
  Negative values are stored as 2's complement.!

Item was removed:
- ----- Method: IntegerArray>>atAllPut: (in category 'accessing') -----
- atAllPut: anInteger
- | word |
- anInteger < 0
- ifTrue:[anInteger < -16r80000000 ifTrue: [self error: anInteger asString , ' out of range'].
- "word := 16r100000000 + anInteger"
- word := (anInteger + 1) negated bitInvert32]
- ifFalse:[anInteger > 16r7FFFFFFF ifTrue: [self error: anInteger asString , ' out of range'].
- word := anInteger].
- self primFill: word.!

Item was added:
+ ----- Method: IntegerArray>>byteSize (in category 'accessing') -----
+ byteSize
+ ^self size * 4!

Item was added:
+ ----- Method: IntegerArray>>bytesPerElement (in category 'accessing') -----
+ bytesPerElement
+ "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
+ ^ 4!

Item was removed:
- ----- Method: IntegerArray>>defaultElement (in category 'accessing') -----
- defaultElement
- "Return the default element of the receiver"
- ^0!

Item was removed:
- ----- Method: IntegerArray>>primFill: (in category 'private') -----
- primFill: aPositiveInteger
- "Fill the receiver, an indexable bytes or words object, with the given positive integer. The range of possible fill values is [0..255] for byte arrays and [0..(2^32 - 1)] for word arrays."
-
- <primitive: 145>
- self errorImproperStore.!

Item was added:
+ FixedBitWidthSignedIntegerArray variableDoubleWordSubclass: #Long64Array
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Collections-Arrayed'!
+
+ !Long64Array commentStamp: 'nice 5/2/2020 15:44' prior: 0!
+ Long64Arrays store 64bit signed Integer values.
+ Negative values are stored as 2's complement.!

Item was added:
+ ----- Method: Long64Array>>at: (in category 'accessing') -----
+ at: index
+ | word64 |
+ <primitive: 165>
+ word64 := self basicAt: index.
+ word64 < SmallInteger maxVal ifTrue:[^word64]. "Avoid LargeInteger computations"
+ ^word64 >= 16r8000000000000000 "Negative?!!"
+ ifTrue: ["word64 - 16r10000000000000000"
+  (word64 bitInvert64 + 1) negated]
+ ifFalse: [word64]!

Item was added:
+ ----- Method: Long64Array>>at:put: (in category 'accessing') -----
+ at: index put: anInteger
+ | word64 |
+ <primitive: 166>
+ anInteger < 0
+ ifTrue:
+ [anInteger < -16r8000000000000000 ifTrue: [self error: anInteger asString , ' out of range'].
+ "word64 := 16r10000000000000000 + anInteger"
+ word64 := (anInteger + 1) negated bitInvert64]
+ ifFalse:
+ [anInteger > 16r7FFFFFFFFFFFFFFF ifTrue: [self error: anInteger asString , ' out of range'].
+ word64 := anInteger].
+ self  basicAt: index put: word64.
+ ^anInteger!

Item was added:
+ ----- Method: Long64Array>>byteSize (in category 'accessing') -----
+ byteSize
+ ^self size * 8!

Item was added:
+ ----- Method: Long64Array>>bytesPerElement (in category 'accessing') -----
+ bytesPerElement
+ "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
+ ^ 8!

Item was added:
+ FixedBitWidthSignedIntegerArray variableByteSubclass: #SignedByteArray
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Collections-Arrayed'!
+
+ !SignedByteArray commentStamp: 'nice 5/2/2020 15:20' prior: 0!
+ IntegerArrays store 8bit signed Integer values.
+ Negative values are stored as 2's complement.!

Item was added:
+ ----- Method: SignedByteArray>>at: (in category 'accessing') -----
+ at: index
+ | word |
+ <primitive: 165>
+ word := self basicAt: index.
+ ^word >= 16r80 "Negative?!!"
+ ifTrue:[16r100 - word]
+ ifFalse:[word]!

Item was added:
+ ----- Method: SignedByteArray>>at:put: (in category 'accessing') -----
+ at: index put: anInteger
+ | byte |
+ <primitive: 166>
+ anInteger < 0
+ ifTrue:
+ [anInteger < -16r80 ifTrue: [self error: anInteger asString , ' out of range'].
+ byte := 16r100 + anInteger]
+ ifFalse:
+ [anInteger > 16r7F ifTrue: [self error: anInteger asString , ' out of range'].
+ byte := anInteger].
+ self  basicAt: index put: byte.
+ ^anInteger!

Item was added:
+ ----- Method: SignedByteArray>>byteSize (in category 'accessing') -----
+ byteSize
+ ^self size!

Item was added:
+ ----- Method: SignedByteArray>>bytesPerElement (in category 'accessing') -----
+ bytesPerElement
+ "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
+ ^ 1!

Item was changed:
+ FixedBitWidthUnsignedIntegerArray variableWordSubclass: #WordArray
- ArrayedCollection variableWordSubclass: #WordArray
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Collections-Arrayed'!
 
  !WordArray commentStamp: '<historical>' prior: 0!
  WordArrays store 32-bit unsigned Integer values.
  !

Item was removed:
- ----- Method: WordArray>>atAllPut: (in category 'accessing') -----
- atAllPut: value
- "Fill the receiver with the given value"
-
- <primitive: 145>
- super atAllPut: value!

Item was removed:
- ----- Method: WordArray>>defaultElement (in category 'accessing') -----
- defaultElement
- "Return the default element of the receiver"
- ^0!

Item was removed:
- ----- Method: WordArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
- replaceFrom: start to: stop with: replacement startingAt: repStart
- <primitive: 105>
- ^super replaceFrom: start to: stop with: replacement startingAt: repStart !


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

Eliot Miranda-2
Hi Nicolas,

> On May 2, 2020, at 10:41 AM, [hidden email] wrote:
>
> Nicolas Cellier uploaded a new version of Collections to project The Inbox:
> http://source.squeak.org/inbox/Collections-nice.891.mcz
>
> ==================== Summary ====================
>
> Name: Collections-nice.891
> Author: nice
> Time: 2 May 2020, 7:40:45.298967 pm
> UUID: 08510be0-8293-6744-959d-c1d41bc13ae1
> Ancestors: Collections-nice.890
>
> Experimental - For discussion
>
> Group some (most) non-pointers collections under an abstract FixedBitWidthArray.
> I know, the name is hard to pronounce and thus ugly: it's opened to discussion.

Why not just BitFieldArray or BitsArray?  Or AbstractBitFieldArray or AbstractBitsArray?

> This enables factorization of some methods, for example the trick for atAllPut:
> Also notice that most methods are shared between FloatArray and Float64Array.
>
> Introduce SignedByteArray and Long64Array.
> These are the only two missing in the panoply.
> The heterogeneity of names generally sucks, but we won't change the ByteArray nor WordArray, so probably neither the DoubleByte and DoubleWord Arrays, it follows a legacy-compatible logic.

I like this idea a lot.  It moves us towards better support for vector arithmetic and hence for areas such as machine learning.

> But for the 32 and 16 bits signed versions, we already have IntegerArray and ShortIntegerArray... What a mess.

Sure, but one that we can clean up.  For example, moving IntegerArray underneath some rationally named class in the bit array hierarchy for backwards compatibility, and then deprecating it in a subsequent release.

> We could use better names in the abstract levels too:
> For example SignedIntegerArray instead of FixedBitWidthSignedIntegerArray.
> Also we could let FloatArray be the abstract class rather than FixedBitWidthFloatArray.
> It would be a factory for Float32Array so as to preserve backward compatiblity.

+1.

> Note that Balloon ShortIntegerArray is currently word rather than doubleByte and should be mutated and moved into this collection. However, it's not easy to mutate because it has both a subclass and instances. We can handle that surgery later.

Right.  Once the bit array hierarchy is in place, moving the old less coherent classes into a better place is possible.

> We can neither easily move ByteArray thru the hierarchy: it is protected because of the fear to break CompiledMethod. Another surgical operation, outside of this proof of concept.

It’ll be apparent really quickly whether CompiledMethod gets broken.  Bit IMO CompiledCode shouldn’t inherit from ByteArray.  It’s a bit of a hack.  Most ByteArray methods aren’t useful because CompiledCode isn’t a ByteArray, but a hybrid of a header, an array of I ops and an array of bytes (& Tim, save your breath, my experience with VisualWorks & an old conversation with Peter Deutsch at York convinced me that actually this hybrid is better than the alternative if one has an interpreter in the execution engine, which we do in all Cog VMs).  For example, replaceFrom:to:with:startingAt: is entirely inappropriate for CompiledCode.  So it would be better to implement the byte access methods in CompiledCode and inherit from Object.  For example, since CompiledCode can’t respond to do: or size without ambiguity I don’t think it makes sense to think of it as a collection at all.  It is an object containing an array of literals, an array of bytecodes and a trailer encoded in extra bytes, represented oddly for good reasons (compactness and faster interpretation).  If it is a collection then it is a collection of collections :-)

> One thing I don't know is the cost of extending intermediate hierachical levels with respect to lookup of message selector. Is it a problem?

Arguably only for doesNotUnderstand: in the interpreter.  In the interpreter the first-level method look up cache is very effective in reducing lookup costs, except for doesNotUnderstand:.  In the JIT in-line cacheing eliminates lookup costs entirely, including those for doesNotUnderstand:.  So in frequently executed code lookup costs are essentially zero.  (One can construct some polymorphic doesNotUnderstand: examples which would incur very high lookup costs but these would not occur in practice).

> While at it, document the internal format of ColorArray.
> I hope it's consistent across VMs/platforms/endianness... If it's not, the comment SHALL tell so, that's the least I expect of serious software. I don't know why squeakers are so spare of comments...
> Since those classes are good candidates for exchanging data with foreign functions, it's vital to have a minimum of documentation.
>
> =============== Diff against Collections-nice.890 ===============
>
> Item was changed:
> + FixedBitWidthArray variableWordSubclass: #ColorArray
> - ArrayedCollection variableWordSubclass: #ColorArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
> +
> + !ColorArray commentStamp: 'nice 5/2/2020 17:11' prior: 0!
> + A ColorArray is an array of colors encoded on 32-bits.
> +
> + The encoding of colors follows the ARGB scheme.
> + See https://en.wikipedia.org/wiki/RGBA_color_model
> +
> + The color is decomposed into 4 channels of 8 bits (4 bytes)
> + - the most significant byte A is alpha channel which governs transparency
> +   0 means a completely transparent (invisible) color
> +   255 means an opaque color.
> + - the second most significant byte R encodes the level of red
> +   the lower, the darker and/or least saturated
> + - the third most significant byte G encodes the level of green
> + - the least significant byte B encodes the level of blue
> +
> + Color white is encoded as 16rFFFFFFFF.
> +    ((ColorArray with: Color white) basicAt: 1) hex.
> + For historical reasons, notice that Color black is encoded as a very dark blue 16rFF000001 rather than 16rFF000000.
> +    ((ColorArray with: Color black) basicAt: 1) hex.
> + Other example of pure red, pure green and pure blue showing the bit position of those channels:
> +    ((ColorArray with: Color red) basicAt: 1) hex.
> +    ((ColorArray with: Color green) basicAt: 1) hex.
> +    ((ColorArray with: Color blue) basicAt: 1) hex.
> + Color transparent is encoded as zero on all channels:
> +    ((ColorArray with: Color transparent) basicAt: 1) hex.!
>
> Item was changed:
> + FixedBitWidthUnsignedIntegerArray variableDoubleByteSubclass: #DoubleByteArray
> - ArrayedCollection variableDoubleByteSubclass: #DoubleByteArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !DoubleByteArray commentStamp: 'nice 10/20/2016 23:23' prior: 0!
>  DoubleByteArrays store 16-bit unsigned Integer values.!
>
> Item was removed:
> - ----- Method: DoubleByteArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0!
>
> Item was removed:
> - ----- Method: DoubleByteArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> -    <primitive: 105>
> -    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was changed:
> + FixedBitWidthUnsignedIntegerArray variableDoubleWordSubclass: #DoubleWordArray
> - ArrayedCollection variableDoubleWordSubclass: #DoubleWordArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !DoubleWordArray commentStamp: 'nice 9/20/2016 23:37' prior: 0!
>  DoubleWordArrays store 64-bit unsigned Integer values.!
>
> Item was removed:
> - ----- Method: DoubleWordArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0!
>
> Item was removed:
> - ----- Method: DoubleWordArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> -    <primitive: 105>
> -    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was added:
> + ArrayedCollection subclass: #FixedBitWidthArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !FixedBitWidthArray commentStamp: 'nice 5/2/2020 18:58' prior: 0!
> + A FixedBitWidthArray is an abstract superclass for all arrays whose elements are not stored as pointer but as raw bits of fixed-width.
> + Currently, SpurVM supports arrays of elements with a bit-width of 8, 16, 32, or 64 bits.
> + When accessing a specific element with #basicAt: or #basicAt:put:, the bits are exchanged under the form of an unsigned Integer.
> + The range of such integer must be between 0 and 2**bitWidth-1 (which translates as 1<<bitWidth-1).
> +
> + The subclasses are free to re-interpret those bits as more specialized Objects and shall provide convenient #at: and #at:put: protocol for exchanging those objects rather than raw bit-encoding.
> + For example, there is support for Signed Integers of different width, IEEE 754 32bits and 64bits Float, 32 bits Colors, etc...
> +
> + It is the subclass responsibility to encode those objects as raw bits (an Integer), and decode the raw bits (an Integer) as an object.
> + Note however that SpurVM supports conversion to/from signed integer.
> +
> + The name of subclasses is historical and constrained by backward compatibility.!
>
> Item was added:
> + ----- Method: FixedBitWidthArray>>atAllPut: (in category 'accessing') -----
> + atAllPut: anObject
> +    self isEmpty ifTrue: [^self].
> +    "Note: primitiveConstantFill does only handle unsigned integer.
> +    Let at:put: take care of properly encoding anObject as bits"
> +    self at: 1 put: anObject.
> +    self primFill: (self basicAt: 1)!
>
> Item was added:
> + ----- Method: FixedBitWidthArray>>primFill: (in category 'private') -----
> + primFill: aPositiveInteger
> +    "Fill the receiver, an indexable bytes or words object, with the given positive integer.
> +    The range of possible fill values is :
> +    - [0..255] for byte arrays;
> +    - [0..65535] for double byte arrays;
> +    - [0..(2^32 - 1)] for word arrays;
> +    - [0..(2^64 - 1)] for double word arrays."
> +
> +    <primitive: 145>
> +    self errorImproperStore.!
>
> Item was added:
> + FixedBitWidthArray subclass: #FixedBitWidthFloatArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>* (in category 'arithmetic') -----
> + * anObject
> +
> +    ^self shallowCopy *= anObject!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>*= (in category 'arithmetic') -----
> + *= anObject
> +    ^anObject isNumber
> +        ifTrue:[self primMulScalar: anObject asFloat]
> +        ifFalse:[self primMulArray: anObject]!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>+ (in category 'arithmetic') -----
> + + anObject
> +
> +    ^self shallowCopy += anObject!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>+= (in category 'arithmetic') -----
> + += anObject
> +    ^anObject isNumber
> +        ifTrue:[self primAddScalar: anObject asFloat]
> +        ifFalse:[self primAddArray: anObject]!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>- (in category 'arithmetic') -----
> + - anObject
> +
> +    ^self shallowCopy -= anObject!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>-= (in category 'arithmetic') -----
> + -= anObject
> +    ^anObject isNumber
> +        ifTrue:[self primSubScalar: anObject asFloat]
> +        ifFalse:[self primSubArray: anObject]!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>/ (in category 'arithmetic') -----
> + / anObject
> +
> +    ^self shallowCopy /= anObject!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>/= (in category 'arithmetic') -----
> + /= anObject
> +    ^anObject isNumber
> +        ifTrue:[self primDivScalar: anObject asFloat]
> +        ifFalse:[self primDivArray: anObject]!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>\\= (in category 'arithmetic') -----
> + \\= other
> +
> +    other isNumber ifTrue: [
> +        1 to: self size do: [:i |
> +            self at: i put: (self at: i) \\ other
> +        ].
> +        ^ self.
> +    ].
> +    1 to: (self size min: other size) do: [:i |
> +        self at: i put: (self at: i) \\ (other at: i).
> +    ].
> +
> + !
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>adaptToNumber:andSend: (in category 'arithmetic') -----
> + adaptToNumber: rcvr andSend: selector
> +    "If I am involved in arithmetic with a Number. If possible,
> +    convert it to a float and perform the (more efficient) primitive operation."
> +    selector == #+ ifTrue:[^self + rcvr].
> +    selector == #* ifTrue:[^self * rcvr].
> +    selector == #- ifTrue:[^self negated += rcvr].
> +    selector == #/ ifTrue:[
> +        "DO NOT USE TRIVIAL CODE
> +            ^self reciprocal * rcvr
> +        BECAUSE OF GRADUAL UNDERFLOW
> +        self should: (1.0e-39 / (FloatArray with: 1.0e-39)) first < 2."
> +            ^(self class new: self size withAll: rcvr) / self
> +        ].
> +    ^super adaptToNumber: rcvr andSend: selector!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>defaultElement (in category 'accessing') -----
> + defaultElement
> +    "Return the default element of the receiver"
> +    ^0.0!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>length (in category 'accessing') -----
> + length
> +    "Return the length of the receiver"
> +    ^self squaredLength sqrt!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>negated (in category 'arithmetic') -----
> + negated
> +
> +    ^self shallowCopy *= -1!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> + replaceFrom: start to: stop with: replacement startingAt: repStart
> +    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> +    <primitive: 105>
> +    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>squaredLength (in category 'accessing') -----
> + squaredLength
> +    "Return the squared length of the receiver"
> +    ^self dot: self!
>
> Item was added:
> + FixedBitWidthArray subclass: #FixedBitWidthSignedIntegerArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !FixedBitWidthSignedIntegerArray commentStamp: 'nice 5/2/2020 16:30' prior: 0!
> + A FixedBitWidthSignedIntegerArray is an abstract class for all arrays of signed integer of fixed bit-width.
> +
> + !
>
> Item was added:
> + ----- Method: FixedBitWidthSignedIntegerArray>>defaultElement (in category 'accessing') -----
> + defaultElement
> +    "Return the default element of the receiver"
> +    ^0!
>
> Item was added:
> + FixedBitWidthArray subclass: #FixedBitWidthUnsignedIntegerArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !FixedBitWidthUnsignedIntegerArray commentStamp: 'nice 5/2/2020 16:47' prior: 0!
> + A FixedBitWidthUnsignedIntegerArray is an abstract class for all arrays of unsigned integer of fixed bit-width.
> +
> + !
>
> Item was added:
> + ----- Method: FixedBitWidthUnsignedIntegerArray>>atAllPut: (in category 'accessing') -----
> + atAllPut: value
> +    "Fill the receiver with the given value"
> +
> +    <primitive: 145>
> +    super atAllPut: value!
>
> Item was added:
> + ----- Method: FixedBitWidthUnsignedIntegerArray>>defaultElement (in category 'accessing') -----
> + defaultElement
> +    "Return the default element of the receiver"
> +    ^0!
>
> Item was added:
> + ----- Method: FixedBitWidthUnsignedIntegerArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> + replaceFrom: start to: stop with: replacement startingAt: repStart
> +    <primitive: 105>
> +    ^super replaceFrom: start to: stop with: replacement startingAt: repStart !
>
> Item was changed:
> + FixedBitWidthFloatArray variableDoubleWordSubclass: #Float64Array
> - ArrayedCollection variableDoubleWordSubclass: #Float64Array
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !Float64Array commentStamp: '<historical>' prior: 0!
>  Float64Arrays store 64bit IEEE floating point numbers.!
>
> Item was removed:
> - ----- Method: Float64Array>>* (in category 'arithmetic') -----
> - * anObject
> -
> -    ^self shallowCopy *= anObject!
>
> Item was removed:
> - ----- Method: Float64Array>>*= (in category 'arithmetic') -----
> - *= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primMulScalar: anObject asFloat]
> -        ifFalse:[self primMulArray: anObject]!
>
> Item was removed:
> - ----- Method: Float64Array>>+ (in category 'arithmetic') -----
> - + anObject
> -
> -    ^self shallowCopy += anObject!
>
> Item was removed:
> - ----- Method: Float64Array>>+= (in category 'arithmetic') -----
> - += anObject
> -    ^anObject isNumber
> -        ifTrue:[self primAddScalar: anObject asFloat]
> -        ifFalse:[self primAddArray: anObject]!
>
> Item was removed:
> - ----- Method: Float64Array>>- (in category 'arithmetic') -----
> - - anObject
> -
> -    ^self shallowCopy -= anObject!
>
> Item was removed:
> - ----- Method: Float64Array>>-= (in category 'arithmetic') -----
> - -= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primSubScalar: anObject asFloat]
> -        ifFalse:[self primSubArray: anObject]!
>
> Item was removed:
> - ----- Method: Float64Array>>/ (in category 'arithmetic') -----
> - / anObject
> -
> -    ^self shallowCopy /= anObject!
>
> Item was removed:
> - ----- Method: Float64Array>>/= (in category 'arithmetic') -----
> - /= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primDivScalar: anObject asFloat]
> -        ifFalse:[self primDivArray: anObject]!
>
> Item was removed:
> - ----- Method: Float64Array>>\\= (in category 'arithmetic') -----
> - \\= other
> -
> -    other isNumber ifTrue: [
> -        1 to: self size do: [:i |
> -            self at: i put: (self at: i) \\ other
> -        ].
> -        ^ self.
> -    ].
> -    1 to: (self size min: other size) do: [:i |
> -        self at: i put: (self at: i) \\ (other at: i).
> -    ].
> -
> - !
>
> Item was removed:
> - ----- Method: Float64Array>>adaptToNumber:andSend: (in category 'arithmetic') -----
> - adaptToNumber: rcvr andSend: selector
> -    "If I am involved in arithmetic with a Number. If possible,
> -    convert it to a float and perform the (more efficient) primitive operation."
> -    selector == #+ ifTrue:[^self + rcvr].
> -    selector == #* ifTrue:[^self * rcvr].
> -    selector == #- ifTrue:[^self negated += rcvr].
> -    selector == #/ ifTrue:[
> -        "DO NOT USE TRIVIAL CODE
> -            ^self reciprocal * rcvr
> -        BECAUSE OF GRADUAL UNDERFLOW
> -        self should: (1.0e-39 / (Float64Array with: 1.0e-39)) first < 2."
> -            ^(self class new: self size withAll: rcvr) / self
> -        ].
> -    ^super adaptToNumber: rcvr andSend: selector!
>
> Item was added:
> + ----- Method: Float64Array>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size * 8!
>
> Item was added:
> + ----- Method: Float64Array>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 8!
>
> Item was removed:
> - ----- Method: Float64Array>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0.0!
>
> Item was removed:
> - ----- Method: Float64Array>>length (in category 'accessing') -----
> - length
> -    "Return the length of the receiver"
> -    ^self squaredLength sqrt!
>
> Item was removed:
> - ----- Method: Float64Array>>negated (in category 'arithmetic') -----
> - negated
> -
> -    ^self shallowCopy *= -1!
>
> Item was removed:
> - ----- Method: Float64Array>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> -    <primitive: 105>
> -    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was removed:
> - ----- Method: Float64Array>>squaredLength (in category 'accessing') -----
> - squaredLength
> -    "Return the squared length of the receiver"
> -    ^self dot: self!
>
> Item was changed:
> + FixedBitWidthFloatArray variableWordSubclass: #FloatArray
> - ArrayedCollection variableWordSubclass: #FloatArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !FloatArray commentStamp: '<historical>' prior: 0!
>  FloatArrays store 32bit IEEE floating point numbers.!
>
> Item was removed:
> - ----- Method: FloatArray>>* (in category 'arithmetic') -----
> - * anObject
> -
> -    ^self shallowCopy *= anObject!
>
> Item was removed:
> - ----- Method: FloatArray>>*= (in category 'arithmetic') -----
> - *= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primMulScalar: anObject asFloat]
> -        ifFalse:[self primMulArray: anObject]!
>
> Item was removed:
> - ----- Method: FloatArray>>+ (in category 'arithmetic') -----
> - + anObject
> -
> -    ^self shallowCopy += anObject!
>
> Item was removed:
> - ----- Method: FloatArray>>+= (in category 'arithmetic') -----
> - += anObject
> -    ^anObject isNumber
> -        ifTrue:[self primAddScalar: anObject asFloat]
> -        ifFalse:[self primAddArray: anObject]!
>
> Item was removed:
> - ----- Method: FloatArray>>- (in category 'arithmetic') -----
> - - anObject
> -
> -    ^self shallowCopy -= anObject!
>
> Item was removed:
> - ----- Method: FloatArray>>-= (in category 'arithmetic') -----
> - -= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primSubScalar: anObject asFloat]
> -        ifFalse:[self primSubArray: anObject]!
>
> Item was removed:
> - ----- Method: FloatArray>>/ (in category 'arithmetic') -----
> - / anObject
> -
> -    ^self shallowCopy /= anObject!
>
> Item was removed:
> - ----- Method: FloatArray>>/= (in category 'arithmetic') -----
> - /= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primDivScalar: anObject asFloat]
> -        ifFalse:[self primDivArray: anObject]!
>
> Item was removed:
> - ----- Method: FloatArray>>\\= (in category 'arithmetic') -----
> - \\= other
> -
> -    other isNumber ifTrue: [
> -        1 to: self size do: [:i |
> -            self at: i put: (self at: i) \\ other
> -        ].
> -        ^ self.
> -    ].
> -    1 to: (self size min: other size) do: [:i |
> -        self at: i put: (self at: i) \\ (other at: i).
> -    ].
> -
> - !
>
> Item was removed:
> - ----- Method: FloatArray>>adaptToNumber:andSend: (in category 'arithmetic') -----
> - adaptToNumber: rcvr andSend: selector
> -    "If I am involved in arithmetic with a Number. If possible,
> -    convert it to a float and perform the (more efficient) primitive operation."
> -    selector == #+ ifTrue:[^self + rcvr].
> -    selector == #* ifTrue:[^self * rcvr].
> -    selector == #- ifTrue:[^self negated += rcvr].
> -    selector == #/ ifTrue:[
> -        "DO NOT USE TRIVIAL CODE
> -            ^self reciprocal * rcvr
> -        BECAUSE OF GRADUAL UNDERFLOW
> -        self should: (1.0e-39 / (FloatArray with: 1.0e-39)) first < 2."
> -            ^(self class new: self size withAll: rcvr) / self
> -        ].
> -    ^super adaptToNumber: rcvr andSend: selector!
>
> Item was added:
> + ----- Method: FloatArray>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size * 4!
>
> Item was added:
> + ----- Method: FloatArray>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 4!
>
> Item was removed:
> - ----- Method: FloatArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0.0!
>
> Item was removed:
> - ----- Method: FloatArray>>length (in category 'accessing') -----
> - length
> -    "Return the length of the receiver"
> -    ^self squaredLength sqrt!
>
> Item was removed:
> - ----- Method: FloatArray>>negated (in category 'arithmetic') -----
> - negated
> -
> -    ^self shallowCopy *= -1!
>
> Item was removed:
> - ----- Method: FloatArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> -    <primitive: 105>
> -    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was removed:
> - ----- Method: FloatArray>>squaredLength (in category 'accessing') -----
> - squaredLength
> -    "Return the squared length of the receiver"
> -    ^self dot: self!
>
> Item was changed:
> + FixedBitWidthSignedIntegerArray variableWordSubclass: #IntegerArray
> - ArrayedCollection variableWordSubclass: #IntegerArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !IntegerArray commentStamp: '<historical>' prior: 0!
>  IntegerArrays store 32bit signed Integer values.
>  Negative values are stored as 2's complement.!
>
> Item was removed:
> - ----- Method: IntegerArray>>atAllPut: (in category 'accessing') -----
> - atAllPut: anInteger
> -    | word |
> -    anInteger < 0
> -        ifTrue:[anInteger < -16r80000000 ifTrue: [self error: anInteger asString , ' out of range'].
> -                "word := 16r100000000 + anInteger"
> -                word := (anInteger + 1) negated bitInvert32]
> -        ifFalse:[anInteger > 16r7FFFFFFF ifTrue: [self error: anInteger asString , ' out of range'].
> -                word := anInteger].
> -    self primFill: word.!
>
> Item was added:
> + ----- Method: IntegerArray>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size * 4!
>
> Item was added:
> + ----- Method: IntegerArray>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 4!
>
> Item was removed:
> - ----- Method: IntegerArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0!
>
> Item was removed:
> - ----- Method: IntegerArray>>primFill: (in category 'private') -----
> - primFill: aPositiveInteger
> -    "Fill the receiver, an indexable bytes or words object, with the given positive integer. The range of possible fill values is [0..255] for byte arrays and [0..(2^32 - 1)] for word arrays."
> -
> -    <primitive: 145>
> -    self errorImproperStore.!
>
> Item was added:
> + FixedBitWidthSignedIntegerArray variableDoubleWordSubclass: #Long64Array
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !Long64Array commentStamp: 'nice 5/2/2020 15:44' prior: 0!
> + Long64Arrays store 64bit signed Integer values.
> + Negative values are stored as 2's complement.!
>
> Item was added:
> + ----- Method: Long64Array>>at: (in category 'accessing') -----
> + at: index
> +    | word64 |
> +    <primitive: 165>
> +    word64 := self basicAt: index.
> +    word64 < SmallInteger maxVal ifTrue:[^word64]. "Avoid LargeInteger computations"
> +    ^word64 >= 16r8000000000000000    "Negative?!!"
> +        ifTrue: ["word64 - 16r10000000000000000"
> +              (word64 bitInvert64 + 1) negated]
> +        ifFalse: [word64]!
>
> Item was added:
> + ----- Method: Long64Array>>at:put: (in category 'accessing') -----
> + at: index put: anInteger
> +    | word64 |
> +    <primitive: 166>
> +    anInteger < 0
> +        ifTrue:
> +            [anInteger < -16r8000000000000000 ifTrue: [self error: anInteger asString , ' out of range'].
> +            "word64 := 16r10000000000000000 + anInteger"
> +            word64 := (anInteger + 1) negated bitInvert64]
> +        ifFalse:
> +            [anInteger > 16r7FFFFFFFFFFFFFFF ifTrue: [self error: anInteger asString , ' out of range'].
> +            word64 := anInteger].
> +    self  basicAt: index put: word64.
> +    ^anInteger!
>
> Item was added:
> + ----- Method: Long64Array>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size * 8!
>
> Item was added:
> + ----- Method: Long64Array>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 8!
>
> Item was added:
> + FixedBitWidthSignedIntegerArray variableByteSubclass: #SignedByteArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !SignedByteArray commentStamp: 'nice 5/2/2020 15:20' prior: 0!
> + IntegerArrays store 8bit signed Integer values.
> + Negative values are stored as 2's complement.!
>
> Item was added:
> + ----- Method: SignedByteArray>>at: (in category 'accessing') -----
> + at: index
> +    | word |
> +    <primitive: 165>
> +    word := self basicAt: index.
> +    ^word >= 16r80    "Negative?!!"
> +        ifTrue:[16r100 - word]
> +        ifFalse:[word]!
>
> Item was added:
> + ----- Method: SignedByteArray>>at:put: (in category 'accessing') -----
> + at: index put: anInteger
> +    | byte |
> +    <primitive: 166>
> +    anInteger < 0
> +        ifTrue:
> +            [anInteger < -16r80 ifTrue: [self error: anInteger asString , ' out of range'].
> +             byte := 16r100 + anInteger]
> +        ifFalse:
> +            [anInteger > 16r7F ifTrue: [self error: anInteger asString , ' out of range'].
> +             byte := anInteger].
> +    self  basicAt: index put: byte.
> +    ^anInteger!
>
> Item was added:
> + ----- Method: SignedByteArray>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size!
>
> Item was added:
> + ----- Method: SignedByteArray>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 1!
>
> Item was changed:
> + FixedBitWidthUnsignedIntegerArray variableWordSubclass: #WordArray
> - ArrayedCollection variableWordSubclass: #WordArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !WordArray commentStamp: '<historical>' prior: 0!
>  WordArrays store 32-bit unsigned Integer values.
>  !
>
> Item was removed:
> - ----- Method: WordArray>>atAllPut: (in category 'accessing') -----
> - atAllPut: value
> -    "Fill the receiver with the given value"
> -
> -    <primitive: 145>
> -    super atAllPut: value!
>
> Item was removed:
> - ----- Method: WordArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0!
>
> Item was removed:
> - ----- Method: WordArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    <primitive: 105>
> -    ^super replaceFrom: start to: stop with: replacement startingAt: repStart !
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

timrowledge
Help Help! I'm being oppressed!

> On 2020-05-02, at 11:50 AM, Eliot Miranda <[hidden email]> wrote:
>
> (& Tim, save your breath, my experience with VisualWorks & an old conversation with Peter Deutsch at York convinced me that actually this hybrid is better than the alternative if one has an interpreter in the execution engine, which we do in all Cog VMs

I like the separated out idea because it's a cleaner conceptual design. If the less-clean actual design works better in actual use, then it's actually preferable. I'm an engineer, not a Computer Scientist; we like things that work. And Dilithium crystals.

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
"...sin, young man, is when you treat people as things". Granny said it, Pterry wrote it, That settles it.


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

Nicolas Cellier
In reply to this post by Eliot Miranda-2
Hi Eliot

Le sam. 2 mai 2020 à 20:50, Eliot Miranda <[hidden email]> a écrit :
Hi Nicolas,

> On May 2, 2020, at 10:41 AM, [hidden email] wrote:
>
> Nicolas Cellier uploaded a new version of Collections to project The Inbox:
> http://source.squeak.org/inbox/Collections-nice.891.mcz
>
> ==================== Summary ====================
>
> Name: Collections-nice.891
> Author: nice
> Time: 2 May 2020, 7:40:45.298967 pm
> UUID: 08510be0-8293-6744-959d-c1d41bc13ae1
> Ancestors: Collections-nice.890
>
> Experimental - For discussion
>
> Group some (most) non-pointers collections under an abstract FixedBitWidthArray.
> I know, the name is hard to pronounce and thus ugly: it's opened to discussion.

Why not just BitFieldArray or BitsArray?  Or AbstractBitFieldArray or AbstractBitsArray?

BitField carries a different meaning in other languages...
I like BitsArray, but isn't it too close to BitSet? an Array of Bits?
AbstractBitsArray sounds unambiguous.

> This enables factorization of some methods, for example the trick for atAllPut:
> Also notice that most methods are shared between FloatArray and Float64Array.
>
> Introduce SignedByteArray and Long64Array.
> These are the only two missing in the panoply.
> The heterogeneity of names generally sucks, but we won't change the ByteArray nor WordArray, so probably neither the DoubleByte and DoubleWord Arrays, it follows a legacy-compatible logic.

I like this idea a lot.  It moves us towards better support for vector arithmetic and hence for areas such as machine learning.

> But for the 32 and 16 bits signed versions, we already have IntegerArray and ShortIntegerArray... What a mess.

Sure, but one that we can clean up.  For example, moving IntegerArray underneath some rationally named class in the bit array hierarchy for backwards compatibility, and then deprecating it in a subsequent release.

Yes, that's what I thought.
What would be the clean names of SignedIntegerArrays?

> We could use better names in the abstract levels too:
> For example SignedIntegerArray instead of FixedBitWidthSignedIntegerArray.
> Also we could let FloatArray be the abstract class rather than FixedBitWidthFloatArray.
> It would be a factory for Float32Array so as to preserve backward compatiblity.

+1.

> Note that Balloon ShortIntegerArray is currently word rather than doubleByte and should be mutated and moved into this collection. However, it's not easy to mutate because it has both a subclass and instances. We can handle that surgery later.

Right.  Once the bit array hierarchy is in place, moving the old less coherent classes into a better place is possible.

> We can neither easily move ByteArray thru the hierarchy: it is protected because of the fear to break CompiledMethod. Another surgical operation, outside of this proof of concept.

It’ll be apparent really quickly whether CompiledMethod gets broken.  Bit IMO CompiledCode shouldn’t inherit from ByteArray.  It’s a bit of a hack.  Most ByteArray methods aren’t useful because CompiledCode isn’t a ByteArray, but a hybrid of a header, an array of I ops and an array of bytes (& Tim, save your breath, my experience with VisualWorks & an old conversation with Peter Deutsch at York convinced me that actually this hybrid is better than the alternative if one has an interpreter in the execution engine, which we do in all Cog VMs).  For example, replaceFrom:to:with:startingAt: is entirely inappropriate for CompiledCode.  So it would be better to implement the byte access methods in CompiledCode and inherit from Object.  For example, since CompiledCode can’t respond to do: or size without ambiguity I don’t think it makes sense to think of it as a collection at all.  It is an object containing an array of literals, an array of bytecodes and a trailer encoded in extra bytes, represented oddly for good reasons (compactness and faster interpretation).  If it is a collection then it is a collection of collections :-)

+1 for detaching CompiledCode

> One thing I don't know is the cost of extending intermediate hierachical levels with respect to lookup of message selector. Is it a problem?

Arguably only for doesNotUnderstand: in the interpreter.  In the interpreter the first-level method look up cache is very effective in reducing lookup costs, except for doesNotUnderstand:.  In the JIT in-line cacheing eliminates lookup costs entirely, including those for doesNotUnderstand:.  So in frequently executed code lookup costs are essentially zero.  (One can construct some polymorphic doesNotUnderstand: examples which would incur very high lookup costs but these would not occur in practice).


OK, doesNotUnderstand: should not be abused anyway.

> While at it, document the internal format of ColorArray.
> I hope it's consistent across VMs/platforms/endianness... If it's not, the comment SHALL tell so, that's the least I expect of serious software. I don't know why squeakers are so spare of comments...
> Since those classes are good candidates for exchanging data with foreign functions, it's vital to have a minimum of documentation.
>
> =============== Diff against Collections-nice.890 ===============
>
> Item was changed:
> + FixedBitWidthArray variableWordSubclass: #ColorArray
> - ArrayedCollection variableWordSubclass: #ColorArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
> +
> + !ColorArray commentStamp: 'nice 5/2/2020 17:11' prior: 0!
> + A ColorArray is an array of colors encoded on 32-bits.
> +
> + The encoding of colors follows the ARGB scheme.
> + See https://en.wikipedia.org/wiki/RGBA_color_model
> +
> + The color is decomposed into 4 channels of 8 bits (4 bytes)
> + - the most significant byte A is alpha channel which governs transparency
> +   0 means a completely transparent (invisible) color
> +   255 means an opaque color.
> + - the second most significant byte R encodes the level of red
> +   the lower, the darker and/or least saturated
> + - the third most significant byte G encodes the level of green
> + - the least significant byte B encodes the level of blue
> +
> + Color white is encoded as 16rFFFFFFFF.
> +    ((ColorArray with: Color white) basicAt: 1) hex.
> + For historical reasons, notice that Color black is encoded as a very dark blue 16rFF000001 rather than 16rFF000000.
> +    ((ColorArray with: Color black) basicAt: 1) hex.
> + Other example of pure red, pure green and pure blue showing the bit position of those channels:
> +    ((ColorArray with: Color red) basicAt: 1) hex.
> +    ((ColorArray with: Color green) basicAt: 1) hex.
> +    ((ColorArray with: Color blue) basicAt: 1) hex.
> + Color transparent is encoded as zero on all channels:
> +    ((ColorArray with: Color transparent) basicAt: 1) hex.!
>
> Item was changed:
> + FixedBitWidthUnsignedIntegerArray variableDoubleByteSubclass: #DoubleByteArray
> - ArrayedCollection variableDoubleByteSubclass: #DoubleByteArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !DoubleByteArray commentStamp: 'nice 10/20/2016 23:23' prior: 0!
>  DoubleByteArrays store 16-bit unsigned Integer values.!
>
> Item was removed:
> - ----- Method: DoubleByteArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0!
>
> Item was removed:
> - ----- Method: DoubleByteArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> -    <primitive: 105>
> -    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was changed:
> + FixedBitWidthUnsignedIntegerArray variableDoubleWordSubclass: #DoubleWordArray
> - ArrayedCollection variableDoubleWordSubclass: #DoubleWordArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !DoubleWordArray commentStamp: 'nice 9/20/2016 23:37' prior: 0!
>  DoubleWordArrays store 64-bit unsigned Integer values.!
>
> Item was removed:
> - ----- Method: DoubleWordArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0!
>
> Item was removed:
> - ----- Method: DoubleWordArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> -    <primitive: 105>
> -    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was added:
> + ArrayedCollection subclass: #FixedBitWidthArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !FixedBitWidthArray commentStamp: 'nice 5/2/2020 18:58' prior: 0!
> + A FixedBitWidthArray is an abstract superclass for all arrays whose elements are not stored as pointer but as raw bits of fixed-width.
> + Currently, SpurVM supports arrays of elements with a bit-width of 8, 16, 32, or 64 bits.
> + When accessing a specific element with #basicAt: or #basicAt:put:, the bits are exchanged under the form of an unsigned Integer.
> + The range of such integer must be between 0 and 2**bitWidth-1 (which translates as 1<<bitWidth-1).
> +
> + The subclasses are free to re-interpret those bits as more specialized Objects and shall provide convenient #at: and #at:put: protocol for exchanging those objects rather than raw bit-encoding.
> + For example, there is support for Signed Integers of different width, IEEE 754 32bits and 64bits Float, 32 bits Colors, etc...
> +
> + It is the subclass responsibility to encode those objects as raw bits (an Integer), and decode the raw bits (an Integer) as an object.
> + Note however that SpurVM supports conversion to/from signed integer.
> +
> + The name of subclasses is historical and constrained by backward compatibility.!
>
> Item was added:
> + ----- Method: FixedBitWidthArray>>atAllPut: (in category 'accessing') -----
> + atAllPut: anObject
> +    self isEmpty ifTrue: [^self].
> +    "Note: primitiveConstantFill does only handle unsigned integer.
> +    Let at:put: take care of properly encoding anObject as bits"
> +    self at: 1 put: anObject.
> +    self primFill: (self basicAt: 1)!
>
> Item was added:
> + ----- Method: FixedBitWidthArray>>primFill: (in category 'private') -----
> + primFill: aPositiveInteger
> +    "Fill the receiver, an indexable bytes or words object, with the given positive integer.
> +    The range of possible fill values is :
> +    - [0..255] for byte arrays;
> +    - [0..65535] for double byte arrays;
> +    - [0..(2^32 - 1)] for word arrays;
> +    - [0..(2^64 - 1)] for double word arrays."
> +
> +    <primitive: 145>
> +    self errorImproperStore.!
>
> Item was added:
> + FixedBitWidthArray subclass: #FixedBitWidthFloatArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>* (in category 'arithmetic') -----
> + * anObject
> +
> +    ^self shallowCopy *= anObject!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>*= (in category 'arithmetic') -----
> + *= anObject
> +    ^anObject isNumber
> +        ifTrue:[self primMulScalar: anObject asFloat]
> +        ifFalse:[self primMulArray: anObject]!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>+ (in category 'arithmetic') -----
> + + anObject
> +
> +    ^self shallowCopy += anObject!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>+= (in category 'arithmetic') -----
> + += anObject
> +    ^anObject isNumber
> +        ifTrue:[self primAddScalar: anObject asFloat]
> +        ifFalse:[self primAddArray: anObject]!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>- (in category 'arithmetic') -----
> + - anObject
> +
> +    ^self shallowCopy -= anObject!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>-= (in category 'arithmetic') -----
> + -= anObject
> +    ^anObject isNumber
> +        ifTrue:[self primSubScalar: anObject asFloat]
> +        ifFalse:[self primSubArray: anObject]!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>/ (in category 'arithmetic') -----
> + / anObject
> +
> +    ^self shallowCopy /= anObject!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>/= (in category 'arithmetic') -----
> + /= anObject
> +    ^anObject isNumber
> +        ifTrue:[self primDivScalar: anObject asFloat]
> +        ifFalse:[self primDivArray: anObject]!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>\\= (in category 'arithmetic') -----
> + \\= other
> +
> +    other isNumber ifTrue: [
> +        1 to: self size do: [:i |
> +            self at: i put: (self at: i) \\ other
> +        ].
> +        ^ self.
> +    ].
> +    1 to: (self size min: other size) do: [:i |
> +        self at: i put: (self at: i) \\ (other at: i).
> +    ].
> +
> + !
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>adaptToNumber:andSend: (in category 'arithmetic') -----
> + adaptToNumber: rcvr andSend: selector
> +    "If I am involved in arithmetic with a Number. If possible,
> +    convert it to a float and perform the (more efficient) primitive operation."
> +    selector == #+ ifTrue:[^self + rcvr].
> +    selector == #* ifTrue:[^self * rcvr].
> +    selector == #- ifTrue:[^self negated += rcvr].
> +    selector == #/ ifTrue:[
> +        "DO NOT USE TRIVIAL CODE
> +            ^self reciprocal * rcvr
> +        BECAUSE OF GRADUAL UNDERFLOW
> +        self should: (1.0e-39 / (FloatArray with: 1.0e-39)) first < 2."
> +            ^(self class new: self size withAll: rcvr) / self
> +        ].
> +    ^super adaptToNumber: rcvr andSend: selector!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>defaultElement (in category 'accessing') -----
> + defaultElement
> +    "Return the default element of the receiver"
> +    ^0.0!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>length (in category 'accessing') -----
> + length
> +    "Return the length of the receiver"
> +    ^self squaredLength sqrt!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>negated (in category 'arithmetic') -----
> + negated
> +
> +    ^self shallowCopy *= -1!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> + replaceFrom: start to: stop with: replacement startingAt: repStart
> +    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> +    <primitive: 105>
> +    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>squaredLength (in category 'accessing') -----
> + squaredLength
> +    "Return the squared length of the receiver"
> +    ^self dot: self!
>
> Item was added:
> + FixedBitWidthArray subclass: #FixedBitWidthSignedIntegerArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !FixedBitWidthSignedIntegerArray commentStamp: 'nice 5/2/2020 16:30' prior: 0!
> + A FixedBitWidthSignedIntegerArray is an abstract class for all arrays of signed integer of fixed bit-width.
> +
> + !
>
> Item was added:
> + ----- Method: FixedBitWidthSignedIntegerArray>>defaultElement (in category 'accessing') -----
> + defaultElement
> +    "Return the default element of the receiver"
> +    ^0!
>
> Item was added:
> + FixedBitWidthArray subclass: #FixedBitWidthUnsignedIntegerArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !FixedBitWidthUnsignedIntegerArray commentStamp: 'nice 5/2/2020 16:47' prior: 0!
> + A FixedBitWidthUnsignedIntegerArray is an abstract class for all arrays of unsigned integer of fixed bit-width.
> +
> + !
>
> Item was added:
> + ----- Method: FixedBitWidthUnsignedIntegerArray>>atAllPut: (in category 'accessing') -----
> + atAllPut: value
> +    "Fill the receiver with the given value"
> +
> +    <primitive: 145>
> +    super atAllPut: value!
>
> Item was added:
> + ----- Method: FixedBitWidthUnsignedIntegerArray>>defaultElement (in category 'accessing') -----
> + defaultElement
> +    "Return the default element of the receiver"
> +    ^0!
>
> Item was added:
> + ----- Method: FixedBitWidthUnsignedIntegerArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> + replaceFrom: start to: stop with: replacement startingAt: repStart
> +    <primitive: 105>
> +    ^super replaceFrom: start to: stop with: replacement startingAt: repStart !
>
> Item was changed:
> + FixedBitWidthFloatArray variableDoubleWordSubclass: #Float64Array
> - ArrayedCollection variableDoubleWordSubclass: #Float64Array
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !Float64Array commentStamp: '<historical>' prior: 0!
>  Float64Arrays store 64bit IEEE floating point numbers.!
>
> Item was removed:
> - ----- Method: Float64Array>>* (in category 'arithmetic') -----
> - * anObject
> -
> -    ^self shallowCopy *= anObject!
>
> Item was removed:
> - ----- Method: Float64Array>>*= (in category 'arithmetic') -----
> - *= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primMulScalar: anObject asFloat]
> -        ifFalse:[self primMulArray: anObject]!
>
> Item was removed:
> - ----- Method: Float64Array>>+ (in category 'arithmetic') -----
> - + anObject
> -
> -    ^self shallowCopy += anObject!
>
> Item was removed:
> - ----- Method: Float64Array>>+= (in category 'arithmetic') -----
> - += anObject
> -    ^anObject isNumber
> -        ifTrue:[self primAddScalar: anObject asFloat]
> -        ifFalse:[self primAddArray: anObject]!
>
> Item was removed:
> - ----- Method: Float64Array>>- (in category 'arithmetic') -----
> - - anObject
> -
> -    ^self shallowCopy -= anObject!
>
> Item was removed:
> - ----- Method: Float64Array>>-= (in category 'arithmetic') -----
> - -= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primSubScalar: anObject asFloat]
> -        ifFalse:[self primSubArray: anObject]!
>
> Item was removed:
> - ----- Method: Float64Array>>/ (in category 'arithmetic') -----
> - / anObject
> -
> -    ^self shallowCopy /= anObject!
>
> Item was removed:
> - ----- Method: Float64Array>>/= (in category 'arithmetic') -----
> - /= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primDivScalar: anObject asFloat]
> -        ifFalse:[self primDivArray: anObject]!
>
> Item was removed:
> - ----- Method: Float64Array>>\\= (in category 'arithmetic') -----
> - \\= other
> -
> -    other isNumber ifTrue: [
> -        1 to: self size do: [:i |
> -            self at: i put: (self at: i) \\ other
> -        ].
> -        ^ self.
> -    ].
> -    1 to: (self size min: other size) do: [:i |
> -        self at: i put: (self at: i) \\ (other at: i).
> -    ].
> -
> - !
>
> Item was removed:
> - ----- Method: Float64Array>>adaptToNumber:andSend: (in category 'arithmetic') -----
> - adaptToNumber: rcvr andSend: selector
> -    "If I am involved in arithmetic with a Number. If possible,
> -    convert it to a float and perform the (more efficient) primitive operation."
> -    selector == #+ ifTrue:[^self + rcvr].
> -    selector == #* ifTrue:[^self * rcvr].
> -    selector == #- ifTrue:[^self negated += rcvr].
> -    selector == #/ ifTrue:[
> -        "DO NOT USE TRIVIAL CODE
> -            ^self reciprocal * rcvr
> -        BECAUSE OF GRADUAL UNDERFLOW
> -        self should: (1.0e-39 / (Float64Array with: 1.0e-39)) first < 2."
> -            ^(self class new: self size withAll: rcvr) / self
> -        ].
> -    ^super adaptToNumber: rcvr andSend: selector!
>
> Item was added:
> + ----- Method: Float64Array>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size * 8!
>
> Item was added:
> + ----- Method: Float64Array>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 8!
>
> Item was removed:
> - ----- Method: Float64Array>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0.0!
>
> Item was removed:
> - ----- Method: Float64Array>>length (in category 'accessing') -----
> - length
> -    "Return the length of the receiver"
> -    ^self squaredLength sqrt!
>
> Item was removed:
> - ----- Method: Float64Array>>negated (in category 'arithmetic') -----
> - negated
> -
> -    ^self shallowCopy *= -1!
>
> Item was removed:
> - ----- Method: Float64Array>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> -    <primitive: 105>
> -    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was removed:
> - ----- Method: Float64Array>>squaredLength (in category 'accessing') -----
> - squaredLength
> -    "Return the squared length of the receiver"
> -    ^self dot: self!
>
> Item was changed:
> + FixedBitWidthFloatArray variableWordSubclass: #FloatArray
> - ArrayedCollection variableWordSubclass: #FloatArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !FloatArray commentStamp: '<historical>' prior: 0!
>  FloatArrays store 32bit IEEE floating point numbers.!
>
> Item was removed:
> - ----- Method: FloatArray>>* (in category 'arithmetic') -----
> - * anObject
> -
> -    ^self shallowCopy *= anObject!
>
> Item was removed:
> - ----- Method: FloatArray>>*= (in category 'arithmetic') -----
> - *= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primMulScalar: anObject asFloat]
> -        ifFalse:[self primMulArray: anObject]!
>
> Item was removed:
> - ----- Method: FloatArray>>+ (in category 'arithmetic') -----
> - + anObject
> -
> -    ^self shallowCopy += anObject!
>
> Item was removed:
> - ----- Method: FloatArray>>+= (in category 'arithmetic') -----
> - += anObject
> -    ^anObject isNumber
> -        ifTrue:[self primAddScalar: anObject asFloat]
> -        ifFalse:[self primAddArray: anObject]!
>
> Item was removed:
> - ----- Method: FloatArray>>- (in category 'arithmetic') -----
> - - anObject
> -
> -    ^self shallowCopy -= anObject!
>
> Item was removed:
> - ----- Method: FloatArray>>-= (in category 'arithmetic') -----
> - -= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primSubScalar: anObject asFloat]
> -        ifFalse:[self primSubArray: anObject]!
>
> Item was removed:
> - ----- Method: FloatArray>>/ (in category 'arithmetic') -----
> - / anObject
> -
> -    ^self shallowCopy /= anObject!
>
> Item was removed:
> - ----- Method: FloatArray>>/= (in category 'arithmetic') -----
> - /= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primDivScalar: anObject asFloat]
> -        ifFalse:[self primDivArray: anObject]!
>
> Item was removed:
> - ----- Method: FloatArray>>\\= (in category 'arithmetic') -----
> - \\= other
> -
> -    other isNumber ifTrue: [
> -        1 to: self size do: [:i |
> -            self at: i put: (self at: i) \\ other
> -        ].
> -        ^ self.
> -    ].
> -    1 to: (self size min: other size) do: [:i |
> -        self at: i put: (self at: i) \\ (other at: i).
> -    ].
> -
> - !
>
> Item was removed:
> - ----- Method: FloatArray>>adaptToNumber:andSend: (in category 'arithmetic') -----
> - adaptToNumber: rcvr andSend: selector
> -    "If I am involved in arithmetic with a Number. If possible,
> -    convert it to a float and perform the (more efficient) primitive operation."
> -    selector == #+ ifTrue:[^self + rcvr].
> -    selector == #* ifTrue:[^self * rcvr].
> -    selector == #- ifTrue:[^self negated += rcvr].
> -    selector == #/ ifTrue:[
> -        "DO NOT USE TRIVIAL CODE
> -            ^self reciprocal * rcvr
> -        BECAUSE OF GRADUAL UNDERFLOW
> -        self should: (1.0e-39 / (FloatArray with: 1.0e-39)) first < 2."
> -            ^(self class new: self size withAll: rcvr) / self
> -        ].
> -    ^super adaptToNumber: rcvr andSend: selector!
>
> Item was added:
> + ----- Method: FloatArray>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size * 4!
>
> Item was added:
> + ----- Method: FloatArray>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 4!
>
> Item was removed:
> - ----- Method: FloatArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0.0!
>
> Item was removed:
> - ----- Method: FloatArray>>length (in category 'accessing') -----
> - length
> -    "Return the length of the receiver"
> -    ^self squaredLength sqrt!
>
> Item was removed:
> - ----- Method: FloatArray>>negated (in category 'arithmetic') -----
> - negated
> -
> -    ^self shallowCopy *= -1!
>
> Item was removed:
> - ----- Method: FloatArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> -    <primitive: 105>
> -    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was removed:
> - ----- Method: FloatArray>>squaredLength (in category 'accessing') -----
> - squaredLength
> -    "Return the squared length of the receiver"
> -    ^self dot: self!
>
> Item was changed:
> + FixedBitWidthSignedIntegerArray variableWordSubclass: #IntegerArray
> - ArrayedCollection variableWordSubclass: #IntegerArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !IntegerArray commentStamp: '<historical>' prior: 0!
>  IntegerArrays store 32bit signed Integer values.
>  Negative values are stored as 2's complement.!
>
> Item was removed:
> - ----- Method: IntegerArray>>atAllPut: (in category 'accessing') -----
> - atAllPut: anInteger
> -    | word |
> -    anInteger < 0
> -        ifTrue:[anInteger < -16r80000000 ifTrue: [self error: anInteger asString , ' out of range'].
> -                "word := 16r100000000 + anInteger"
> -                word := (anInteger + 1) negated bitInvert32]
> -        ifFalse:[anInteger > 16r7FFFFFFF ifTrue: [self error: anInteger asString , ' out of range'].
> -                word := anInteger].
> -    self primFill: word.!
>
> Item was added:
> + ----- Method: IntegerArray>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size * 4!
>
> Item was added:
> + ----- Method: IntegerArray>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 4!
>
> Item was removed:
> - ----- Method: IntegerArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0!
>
> Item was removed:
> - ----- Method: IntegerArray>>primFill: (in category 'private') -----
> - primFill: aPositiveInteger
> -    "Fill the receiver, an indexable bytes or words object, with the given positive integer. The range of possible fill values is [0..255] for byte arrays and [0..(2^32 - 1)] for word arrays."
> -
> -    <primitive: 145>
> -    self errorImproperStore.!
>
> Item was added:
> + FixedBitWidthSignedIntegerArray variableDoubleWordSubclass: #Long64Array
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !Long64Array commentStamp: 'nice 5/2/2020 15:44' prior: 0!
> + Long64Arrays store 64bit signed Integer values.
> + Negative values are stored as 2's complement.!
>
> Item was added:
> + ----- Method: Long64Array>>at: (in category 'accessing') -----
> + at: index
> +    | word64 |
> +    <primitive: 165>
> +    word64 := self basicAt: index.
> +    word64 < SmallInteger maxVal ifTrue:[^word64]. "Avoid LargeInteger computations"
> +    ^word64 >= 16r8000000000000000    "Negative?!!"
> +        ifTrue: ["word64 - 16r10000000000000000"
> +              (word64 bitInvert64 + 1) negated]
> +        ifFalse: [word64]!
>
> Item was added:
> + ----- Method: Long64Array>>at:put: (in category 'accessing') -----
> + at: index put: anInteger
> +    | word64 |
> +    <primitive: 166>
> +    anInteger < 0
> +        ifTrue:
> +            [anInteger < -16r8000000000000000 ifTrue: [self error: anInteger asString , ' out of range'].
> +            "word64 := 16r10000000000000000 + anInteger"
> +            word64 := (anInteger + 1) negated bitInvert64]
> +        ifFalse:
> +            [anInteger > 16r7FFFFFFFFFFFFFFF ifTrue: [self error: anInteger asString , ' out of range'].
> +            word64 := anInteger].
> +    self  basicAt: index put: word64.
> +    ^anInteger!
>
> Item was added:
> + ----- Method: Long64Array>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size * 8!
>
> Item was added:
> + ----- Method: Long64Array>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 8!
>
> Item was added:
> + FixedBitWidthSignedIntegerArray variableByteSubclass: #SignedByteArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !SignedByteArray commentStamp: 'nice 5/2/2020 15:20' prior: 0!
> + IntegerArrays store 8bit signed Integer values.
> + Negative values are stored as 2's complement.!
>
> Item was added:
> + ----- Method: SignedByteArray>>at: (in category 'accessing') -----
> + at: index
> +    | word |
> +    <primitive: 165>
> +    word := self basicAt: index.
> +    ^word >= 16r80    "Negative?!!"
> +        ifTrue:[16r100 - word]
> +        ifFalse:[word]!
>
> Item was added:
> + ----- Method: SignedByteArray>>at:put: (in category 'accessing') -----
> + at: index put: anInteger
> +    | byte |
> +    <primitive: 166>
> +    anInteger < 0
> +        ifTrue:
> +            [anInteger < -16r80 ifTrue: [self error: anInteger asString , ' out of range'].
> +             byte := 16r100 + anInteger]
> +        ifFalse:
> +            [anInteger > 16r7F ifTrue: [self error: anInteger asString , ' out of range'].
> +             byte := anInteger].
> +    self  basicAt: index put: byte.
> +    ^anInteger!
>
> Item was added:
> + ----- Method: SignedByteArray>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size!
>
> Item was added:
> + ----- Method: SignedByteArray>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 1!
>
> Item was changed:
> + FixedBitWidthUnsignedIntegerArray variableWordSubclass: #WordArray
> - ArrayedCollection variableWordSubclass: #WordArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !WordArray commentStamp: '<historical>' prior: 0!
>  WordArrays store 32-bit unsigned Integer values.
>  !
>
> Item was removed:
> - ----- Method: WordArray>>atAllPut: (in category 'accessing') -----
> - atAllPut: value
> -    "Fill the receiver with the given value"
> -
> -    <primitive: 145>
> -    super atAllPut: value!
>
> Item was removed:
> - ----- Method: WordArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0!
>
> Item was removed:
> - ----- Method: WordArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    <primitive: 105>
> -    ^super replaceFrom: start to: stop with: replacement startingAt: repStart !
>
>



Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

Eliot Miranda-2
In reply to this post by timrowledge


> On May 2, 2020, at 12:20 PM, tim Rowledge <[hidden email]> wrote:
>
> Help Help! I'm being oppressed!
>
>> On 2020-05-02, at 11:50 AM, Eliot Miranda <[hidden email]> wrote:
>>
>> (& Tim, save your breath, my experience with VisualWorks & an old conversation with Peter Deutsch at York convinced me that actually this hybrid is better than the alternative if one has an interpreter in the execution engine, which we do in all Cog VMs
>
> I like the separated out idea because it's a cleaner conceptual design. If the less-clean actual design works better in actual use, then it's actually preferable. I'm an engineer, not a Computer Scientist; we like things that work. And Dilithium crystals.

:-). <3

>
> tim
> --
> tim Rowledge; [hidden email]; http://www.rowledge.org/tim
> "...sin, young man, is when you treat people as things". Granny said it, Pterry wrote it, That settles it.
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

Eliot Miranda-2
In reply to this post by Nicolas Cellier


On May 2, 2020, at 1:14 PM, Nicolas Cellier <[hidden email]> wrote:


Hi Eliot

Le sam. 2 mai 2020 à 20:50, Eliot Miranda <[hidden email]> a écrit :
Hi Nicolas,

> On May 2, 2020, at 10:41 AM, [hidden email] wrote:
>
> Nicolas Cellier uploaded a new version of Collections to project The Inbox:
> http://source.squeak.org/inbox/Collections-nice.891.mcz
>
> ==================== Summary ====================
>
> Name: Collections-nice.891
> Author: nice
> Time: 2 May 2020, 7:40:45.298967 pm
> UUID: 08510be0-8293-6744-959d-c1d41bc13ae1
> Ancestors: Collections-nice.890
>
> Experimental - For discussion
>
> Group some (most) non-pointers collections under an abstract FixedBitWidthArray.
> I know, the name is hard to pronounce and thus ugly: it's opened to discussion.

Why not just BitFieldArray or BitsArray?  Or AbstractBitFieldArray or AbstractBitsArray?

BitField carries a different meaning in other languages...
I like BitsArray, but isn't it too close to BitSet? an Array of Bits?
AbstractBitsArray sounds unambiguous.

+1

> This enables factorization of some methods, for example the trick for atAllPut:
> Also notice that most methods are shared between FloatArray and Float64Array.
>
> Introduce SignedByteArray and Long64Array.
> These are the only two missing in the panoply.
> The heterogeneity of names generally sucks, but we won't change the ByteArray nor WordArray, so probably neither the DoubleByte and DoubleWord Arrays, it follows a legacy-compatible logic.

I like this idea a lot.  It moves us towards better support for vector arithmetic and hence for areas such as machine learning.

> But for the 32 and 16 bits signed versions, we already have IntegerArray and ShortIntegerArray... What a mess.

Sure, but one that we can clean up.  For example, moving IntegerArray underneath some rationally named class in the bit array hierarchy for backwards compatibility, and then deprecating it in a subsequent release.

Yes, that's what I thought.
What would be the clean names of SignedIntegerArrays?

What about substituting “Word” and “Byte” in DoubleWordArray, DoubleByteArray et al?  Is there a substitute that implies signedness?  Nothing vibes to mind right now; I’m lying on the couch drinking a beer after a long bike ride and my linguistic creativity (to the extent I ever had any) has deserted me for the moment :-)


> We could use better names in the abstract levels too:
> For example SignedIntegerArray instead of FixedBitWidthSignedIntegerArray.
> Also we could let FloatArray be the abstract class rather than FixedBitWidthFloatArray.
> It would be a factory for Float32Array so as to preserve backward compatiblity.

+1.

> Note that Balloon ShortIntegerArray is currently word rather than doubleByte and should be mutated and moved into this collection. However, it's not easy to mutate because it has both a subclass and instances. We can handle that surgery later.

Right.  Once the bit array hierarchy is in place, moving the old less coherent classes into a better place is possible.

> We can neither easily move ByteArray thru the hierarchy: it is protected because of the fear to break CompiledMethod. Another surgical operation, outside of this proof of concept.

It’ll be apparent really quickly whether CompiledMethod gets broken.  Bit IMO CompiledCode shouldn’t inherit from ByteArray.  It’s a bit of a hack.  Most ByteArray methods aren’t useful because CompiledCode isn’t a ByteArray, but a hybrid of a header, an array of I ops and an array of bytes (& Tim, save your breath, my experience with VisualWorks & an old conversation with Peter Deutsch at York convinced me that actually this hybrid is better than the alternative if one has an interpreter in the execution engine, which we do in all Cog VMs).  For example, replaceFrom:to:with:startingAt: is entirely inappropriate for CompiledCode.  So it would be better to implement the byte access methods in CompiledCode and inherit from Object.  For example, since CompiledCode can’t respond to do: or size without ambiguity I don’t think it makes sense to think of it as a collection at all.  It is an object containing an array of literals, an array of bytecodes and a trailer encoded in extra bytes, represented oddly for good reasons (compactness and faster interpretation).  If it is a collection then it is a collection of collections :-)

+1 for detaching CompiledCode

> One thing I don't know is the cost of extending intermediate hierachical levels with respect to lookup of message selector. Is it a problem?

Arguably only for doesNotUnderstand: in the interpreter.  In the interpreter the first-level method look up cache is very effective in reducing lookup costs, except for doesNotUnderstand:.  In the JIT in-line cacheing eliminates lookup costs entirely, including those for doesNotUnderstand:.  So in frequently executed code lookup costs are essentially zero.  (One can construct some polymorphic doesNotUnderstand: examples which would incur very high lookup costs but these would not occur in practice).


OK, doesNotUnderstand: should not be abused anyway.

> While at it, document the internal format of ColorArray.
> I hope it's consistent across VMs/platforms/endianness... If it's not, the comment SHALL tell so, that's the least I expect of serious software. I don't know why squeakers are so spare of comments...
> Since those classes are good candidates for exchanging data with foreign functions, it's vital to have a minimum of documentation.
>
> =============== Diff against Collections-nice.890 ===============
>
> Item was changed:
> + FixedBitWidthArray variableWordSubclass: #ColorArray
> - ArrayedCollection variableWordSubclass: #ColorArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
> +
> + !ColorArray commentStamp: 'nice 5/2/2020 17:11' prior: 0!
> + A ColorArray is an array of colors encoded on 32-bits.
> +
> + The encoding of colors follows the ARGB scheme.
> + See https://en.wikipedia.org/wiki/RGBA_color_model
> +
> + The color is decomposed into 4 channels of 8 bits (4 bytes)
> + - the most significant byte A is alpha channel which governs transparency
> +   0 means a completely transparent (invisible) color
> +   255 means an opaque color.
> + - the second most significant byte R encodes the level of red
> +   the lower, the darker and/or least saturated
> + - the third most significant byte G encodes the level of green
> + - the least significant byte B encodes the level of blue
> +
> + Color white is encoded as 16rFFFFFFFF.
> +    ((ColorArray with: Color white) basicAt: 1) hex.
> + For historical reasons, notice that Color black is encoded as a very dark blue 16rFF000001 rather than 16rFF000000.
> +    ((ColorArray with: Color black) basicAt: 1) hex.
> + Other example of pure red, pure green and pure blue showing the bit position of those channels:
> +    ((ColorArray with: Color red) basicAt: 1) hex.
> +    ((ColorArray with: Color green) basicAt: 1) hex.
> +    ((ColorArray with: Color blue) basicAt: 1) hex.
> + Color transparent is encoded as zero on all channels:
> +    ((ColorArray with: Color transparent) basicAt: 1) hex.!
>
> Item was changed:
> + FixedBitWidthUnsignedIntegerArray variableDoubleByteSubclass: #DoubleByteArray
> - ArrayedCollection variableDoubleByteSubclass: #DoubleByteArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !DoubleByteArray commentStamp: 'nice 10/20/2016 23:23' prior: 0!
>  DoubleByteArrays store 16-bit unsigned Integer values.!
>
> Item was removed:
> - ----- Method: DoubleByteArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0!
>
> Item was removed:
> - ----- Method: DoubleByteArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> -    <primitive: 105>
> -    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was changed:
> + FixedBitWidthUnsignedIntegerArray variableDoubleWordSubclass: #DoubleWordArray
> - ArrayedCollection variableDoubleWordSubclass: #DoubleWordArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !DoubleWordArray commentStamp: 'nice 9/20/2016 23:37' prior: 0!
>  DoubleWordArrays store 64-bit unsigned Integer values.!
>
> Item was removed:
> - ----- Method: DoubleWordArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0!
>
> Item was removed:
> - ----- Method: DoubleWordArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> -    <primitive: 105>
> -    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was added:
> + ArrayedCollection subclass: #FixedBitWidthArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !FixedBitWidthArray commentStamp: 'nice 5/2/2020 18:58' prior: 0!
> + A FixedBitWidthArray is an abstract superclass for all arrays whose elements are not stored as pointer but as raw bits of fixed-width.
> + Currently, SpurVM supports arrays of elements with a bit-width of 8, 16, 32, or 64 bits.
> + When accessing a specific element with #basicAt: or #basicAt:put:, the bits are exchanged under the form of an unsigned Integer.
> + The range of such integer must be between 0 and 2**bitWidth-1 (which translates as 1<<bitWidth-1).
> +
> + The subclasses are free to re-interpret those bits as more specialized Objects and shall provide convenient #at: and #at:put: protocol for exchanging those objects rather than raw bit-encoding.
> + For example, there is support for Signed Integers of different width, IEEE 754 32bits and 64bits Float, 32 bits Colors, etc...
> +
> + It is the subclass responsibility to encode those objects as raw bits (an Integer), and decode the raw bits (an Integer) as an object.
> + Note however that SpurVM supports conversion to/from signed integer.
> +
> + The name of subclasses is historical and constrained by backward compatibility.!
>
> Item was added:
> + ----- Method: FixedBitWidthArray>>atAllPut: (in category 'accessing') -----
> + atAllPut: anObject
> +    self isEmpty ifTrue: [^self].
> +    "Note: primitiveConstantFill does only handle unsigned integer.
> +    Let at:put: take care of properly encoding anObject as bits"
> +    self at: 1 put: anObject.
> +    self primFill: (self basicAt: 1)!
>
> Item was added:
> + ----- Method: FixedBitWidthArray>>primFill: (in category 'private') -----
> + primFill: aPositiveInteger
> +    "Fill the receiver, an indexable bytes or words object, with the given positive integer.
> +    The range of possible fill values is :
> +    - [0..255] for byte arrays;
> +    - [0..65535] for double byte arrays;
> +    - [0..(2^32 - 1)] for word arrays;
> +    - [0..(2^64 - 1)] for double word arrays."
> +
> +    <primitive: 145>
> +    self errorImproperStore.!
>
> Item was added:
> + FixedBitWidthArray subclass: #FixedBitWidthFloatArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>* (in category 'arithmetic') -----
> + * anObject
> +
> +    ^self shallowCopy *= anObject!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>*= (in category 'arithmetic') -----
> + *= anObject
> +    ^anObject isNumber
> +        ifTrue:[self primMulScalar: anObject asFloat]
> +        ifFalse:[self primMulArray: anObject]!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>+ (in category 'arithmetic') -----
> + + anObject
> +
> +    ^self shallowCopy += anObject!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>+= (in category 'arithmetic') -----
> + += anObject
> +    ^anObject isNumber
> +        ifTrue:[self primAddScalar: anObject asFloat]
> +        ifFalse:[self primAddArray: anObject]!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>- (in category 'arithmetic') -----
> + - anObject
> +
> +    ^self shallowCopy -= anObject!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>-= (in category 'arithmetic') -----
> + -= anObject
> +    ^anObject isNumber
> +        ifTrue:[self primSubScalar: anObject asFloat]
> +        ifFalse:[self primSubArray: anObject]!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>/ (in category 'arithmetic') -----
> + / anObject
> +
> +    ^self shallowCopy /= anObject!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>/= (in category 'arithmetic') -----
> + /= anObject
> +    ^anObject isNumber
> +        ifTrue:[self primDivScalar: anObject asFloat]
> +        ifFalse:[self primDivArray: anObject]!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>\\= (in category 'arithmetic') -----
> + \\= other
> +
> +    other isNumber ifTrue: [
> +        1 to: self size do: [:i |
> +            self at: i put: (self at: i) \\ other
> +        ].
> +        ^ self.
> +    ].
> +    1 to: (self size min: other size) do: [:i |
> +        self at: i put: (self at: i) \\ (other at: i).
> +    ].
> +
> + !
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>adaptToNumber:andSend: (in category 'arithmetic') -----
> + adaptToNumber: rcvr andSend: selector
> +    "If I am involved in arithmetic with a Number. If possible,
> +    convert it to a float and perform the (more efficient) primitive operation."
> +    selector == #+ ifTrue:[^self + rcvr].
> +    selector == #* ifTrue:[^self * rcvr].
> +    selector == #- ifTrue:[^self negated += rcvr].
> +    selector == #/ ifTrue:[
> +        "DO NOT USE TRIVIAL CODE
> +            ^self reciprocal * rcvr
> +        BECAUSE OF GRADUAL UNDERFLOW
> +        self should: (1.0e-39 / (FloatArray with: 1.0e-39)) first < 2."
> +            ^(self class new: self size withAll: rcvr) / self
> +        ].
> +    ^super adaptToNumber: rcvr andSend: selector!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>defaultElement (in category 'accessing') -----
> + defaultElement
> +    "Return the default element of the receiver"
> +    ^0.0!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>length (in category 'accessing') -----
> + length
> +    "Return the length of the receiver"
> +    ^self squaredLength sqrt!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>negated (in category 'arithmetic') -----
> + negated
> +
> +    ^self shallowCopy *= -1!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> + replaceFrom: start to: stop with: replacement startingAt: repStart
> +    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> +    <primitive: 105>
> +    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was added:
> + ----- Method: FixedBitWidthFloatArray>>squaredLength (in category 'accessing') -----
> + squaredLength
> +    "Return the squared length of the receiver"
> +    ^self dot: self!
>
> Item was added:
> + FixedBitWidthArray subclass: #FixedBitWidthSignedIntegerArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !FixedBitWidthSignedIntegerArray commentStamp: 'nice 5/2/2020 16:30' prior: 0!
> + A FixedBitWidthSignedIntegerArray is an abstract class for all arrays of signed integer of fixed bit-width.
> +
> + !
>
> Item was added:
> + ----- Method: FixedBitWidthSignedIntegerArray>>defaultElement (in category 'accessing') -----
> + defaultElement
> +    "Return the default element of the receiver"
> +    ^0!
>
> Item was added:
> + FixedBitWidthArray subclass: #FixedBitWidthUnsignedIntegerArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !FixedBitWidthUnsignedIntegerArray commentStamp: 'nice 5/2/2020 16:47' prior: 0!
> + A FixedBitWidthUnsignedIntegerArray is an abstract class for all arrays of unsigned integer of fixed bit-width.
> +
> + !
>
> Item was added:
> + ----- Method: FixedBitWidthUnsignedIntegerArray>>atAllPut: (in category 'accessing') -----
> + atAllPut: value
> +    "Fill the receiver with the given value"
> +
> +    <primitive: 145>
> +    super atAllPut: value!
>
> Item was added:
> + ----- Method: FixedBitWidthUnsignedIntegerArray>>defaultElement (in category 'accessing') -----
> + defaultElement
> +    "Return the default element of the receiver"
> +    ^0!
>
> Item was added:
> + ----- Method: FixedBitWidthUnsignedIntegerArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> + replaceFrom: start to: stop with: replacement startingAt: repStart
> +    <primitive: 105>
> +    ^super replaceFrom: start to: stop with: replacement startingAt: repStart !
>
> Item was changed:
> + FixedBitWidthFloatArray variableDoubleWordSubclass: #Float64Array
> - ArrayedCollection variableDoubleWordSubclass: #Float64Array
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !Float64Array commentStamp: '<historical>' prior: 0!
>  Float64Arrays store 64bit IEEE floating point numbers.!
>
> Item was removed:
> - ----- Method: Float64Array>>* (in category 'arithmetic') -----
> - * anObject
> -
> -    ^self shallowCopy *= anObject!
>
> Item was removed:
> - ----- Method: Float64Array>>*= (in category 'arithmetic') -----
> - *= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primMulScalar: anObject asFloat]
> -        ifFalse:[self primMulArray: anObject]!
>
> Item was removed:
> - ----- Method: Float64Array>>+ (in category 'arithmetic') -----
> - + anObject
> -
> -    ^self shallowCopy += anObject!
>
> Item was removed:
> - ----- Method: Float64Array>>+= (in category 'arithmetic') -----
> - += anObject
> -    ^anObject isNumber
> -        ifTrue:[self primAddScalar: anObject asFloat]
> -        ifFalse:[self primAddArray: anObject]!
>
> Item was removed:
> - ----- Method: Float64Array>>- (in category 'arithmetic') -----
> - - anObject
> -
> -    ^self shallowCopy -= anObject!
>
> Item was removed:
> - ----- Method: Float64Array>>-= (in category 'arithmetic') -----
> - -= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primSubScalar: anObject asFloat]
> -        ifFalse:[self primSubArray: anObject]!
>
> Item was removed:
> - ----- Method: Float64Array>>/ (in category 'arithmetic') -----
> - / anObject
> -
> -    ^self shallowCopy /= anObject!
>
> Item was removed:
> - ----- Method: Float64Array>>/= (in category 'arithmetic') -----
> - /= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primDivScalar: anObject asFloat]
> -        ifFalse:[self primDivArray: anObject]!
>
> Item was removed:
> - ----- Method: Float64Array>>\\= (in category 'arithmetic') -----
> - \\= other
> -
> -    other isNumber ifTrue: [
> -        1 to: self size do: [:i |
> -            self at: i put: (self at: i) \\ other
> -        ].
> -        ^ self.
> -    ].
> -    1 to: (self size min: other size) do: [:i |
> -        self at: i put: (self at: i) \\ (other at: i).
> -    ].
> -
> - !
>
> Item was removed:
> - ----- Method: Float64Array>>adaptToNumber:andSend: (in category 'arithmetic') -----
> - adaptToNumber: rcvr andSend: selector
> -    "If I am involved in arithmetic with a Number. If possible,
> -    convert it to a float and perform the (more efficient) primitive operation."
> -    selector == #+ ifTrue:[^self + rcvr].
> -    selector == #* ifTrue:[^self * rcvr].
> -    selector == #- ifTrue:[^self negated += rcvr].
> -    selector == #/ ifTrue:[
> -        "DO NOT USE TRIVIAL CODE
> -            ^self reciprocal * rcvr
> -        BECAUSE OF GRADUAL UNDERFLOW
> -        self should: (1.0e-39 / (Float64Array with: 1.0e-39)) first < 2."
> -            ^(self class new: self size withAll: rcvr) / self
> -        ].
> -    ^super adaptToNumber: rcvr andSend: selector!
>
> Item was added:
> + ----- Method: Float64Array>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size * 8!
>
> Item was added:
> + ----- Method: Float64Array>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 8!
>
> Item was removed:
> - ----- Method: Float64Array>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0.0!
>
> Item was removed:
> - ----- Method: Float64Array>>length (in category 'accessing') -----
> - length
> -    "Return the length of the receiver"
> -    ^self squaredLength sqrt!
>
> Item was removed:
> - ----- Method: Float64Array>>negated (in category 'arithmetic') -----
> - negated
> -
> -    ^self shallowCopy *= -1!
>
> Item was removed:
> - ----- Method: Float64Array>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> -    <primitive: 105>
> -    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was removed:
> - ----- Method: Float64Array>>squaredLength (in category 'accessing') -----
> - squaredLength
> -    "Return the squared length of the receiver"
> -    ^self dot: self!
>
> Item was changed:
> + FixedBitWidthFloatArray variableWordSubclass: #FloatArray
> - ArrayedCollection variableWordSubclass: #FloatArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !FloatArray commentStamp: '<historical>' prior: 0!
>  FloatArrays store 32bit IEEE floating point numbers.!
>
> Item was removed:
> - ----- Method: FloatArray>>* (in category 'arithmetic') -----
> - * anObject
> -
> -    ^self shallowCopy *= anObject!
>
> Item was removed:
> - ----- Method: FloatArray>>*= (in category 'arithmetic') -----
> - *= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primMulScalar: anObject asFloat]
> -        ifFalse:[self primMulArray: anObject]!
>
> Item was removed:
> - ----- Method: FloatArray>>+ (in category 'arithmetic') -----
> - + anObject
> -
> -    ^self shallowCopy += anObject!
>
> Item was removed:
> - ----- Method: FloatArray>>+= (in category 'arithmetic') -----
> - += anObject
> -    ^anObject isNumber
> -        ifTrue:[self primAddScalar: anObject asFloat]
> -        ifFalse:[self primAddArray: anObject]!
>
> Item was removed:
> - ----- Method: FloatArray>>- (in category 'arithmetic') -----
> - - anObject
> -
> -    ^self shallowCopy -= anObject!
>
> Item was removed:
> - ----- Method: FloatArray>>-= (in category 'arithmetic') -----
> - -= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primSubScalar: anObject asFloat]
> -        ifFalse:[self primSubArray: anObject]!
>
> Item was removed:
> - ----- Method: FloatArray>>/ (in category 'arithmetic') -----
> - / anObject
> -
> -    ^self shallowCopy /= anObject!
>
> Item was removed:
> - ----- Method: FloatArray>>/= (in category 'arithmetic') -----
> - /= anObject
> -    ^anObject isNumber
> -        ifTrue:[self primDivScalar: anObject asFloat]
> -        ifFalse:[self primDivArray: anObject]!
>
> Item was removed:
> - ----- Method: FloatArray>>\\= (in category 'arithmetic') -----
> - \\= other
> -
> -    other isNumber ifTrue: [
> -        1 to: self size do: [:i |
> -            self at: i put: (self at: i) \\ other
> -        ].
> -        ^ self.
> -    ].
> -    1 to: (self size min: other size) do: [:i |
> -        self at: i put: (self at: i) \\ (other at: i).
> -    ].
> -
> - !
>
> Item was removed:
> - ----- Method: FloatArray>>adaptToNumber:andSend: (in category 'arithmetic') -----
> - adaptToNumber: rcvr andSend: selector
> -    "If I am involved in arithmetic with a Number. If possible,
> -    convert it to a float and perform the (more efficient) primitive operation."
> -    selector == #+ ifTrue:[^self + rcvr].
> -    selector == #* ifTrue:[^self * rcvr].
> -    selector == #- ifTrue:[^self negated += rcvr].
> -    selector == #/ ifTrue:[
> -        "DO NOT USE TRIVIAL CODE
> -            ^self reciprocal * rcvr
> -        BECAUSE OF GRADUAL UNDERFLOW
> -        self should: (1.0e-39 / (FloatArray with: 1.0e-39)) first < 2."
> -            ^(self class new: self size withAll: rcvr) / self
> -        ].
> -    ^super adaptToNumber: rcvr andSend: selector!
>
> Item was added:
> + ----- Method: FloatArray>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size * 4!
>
> Item was added:
> + ----- Method: FloatArray>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 4!
>
> Item was removed:
> - ----- Method: FloatArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0.0!
>
> Item was removed:
> - ----- Method: FloatArray>>length (in category 'accessing') -----
> - length
> -    "Return the length of the receiver"
> -    ^self squaredLength sqrt!
>
> Item was removed:
> - ----- Method: FloatArray>>negated (in category 'arithmetic') -----
> - negated
> -
> -    ^self shallowCopy *= -1!
>
> Item was removed:
> - ----- Method: FloatArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
> -    <primitive: 105>
> -    super replaceFrom: start to: stop with: replacement startingAt: repStart!
>
> Item was removed:
> - ----- Method: FloatArray>>squaredLength (in category 'accessing') -----
> - squaredLength
> -    "Return the squared length of the receiver"
> -    ^self dot: self!
>
> Item was changed:
> + FixedBitWidthSignedIntegerArray variableWordSubclass: #IntegerArray
> - ArrayedCollection variableWordSubclass: #IntegerArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !IntegerArray commentStamp: '<historical>' prior: 0!
>  IntegerArrays store 32bit signed Integer values.
>  Negative values are stored as 2's complement.!
>
> Item was removed:
> - ----- Method: IntegerArray>>atAllPut: (in category 'accessing') -----
> - atAllPut: anInteger
> -    | word |
> -    anInteger < 0
> -        ifTrue:[anInteger < -16r80000000 ifTrue: [self error: anInteger asString , ' out of range'].
> -                "word := 16r100000000 + anInteger"
> -                word := (anInteger + 1) negated bitInvert32]
> -        ifFalse:[anInteger > 16r7FFFFFFF ifTrue: [self error: anInteger asString , ' out of range'].
> -                word := anInteger].
> -    self primFill: word.!
>
> Item was added:
> + ----- Method: IntegerArray>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size * 4!
>
> Item was added:
> + ----- Method: IntegerArray>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 4!
>
> Item was removed:
> - ----- Method: IntegerArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0!
>
> Item was removed:
> - ----- Method: IntegerArray>>primFill: (in category 'private') -----
> - primFill: aPositiveInteger
> -    "Fill the receiver, an indexable bytes or words object, with the given positive integer. The range of possible fill values is [0..255] for byte arrays and [0..(2^32 - 1)] for word arrays."
> -
> -    <primitive: 145>
> -    self errorImproperStore.!
>
> Item was added:
> + FixedBitWidthSignedIntegerArray variableDoubleWordSubclass: #Long64Array
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !Long64Array commentStamp: 'nice 5/2/2020 15:44' prior: 0!
> + Long64Arrays store 64bit signed Integer values.
> + Negative values are stored as 2's complement.!
>
> Item was added:
> + ----- Method: Long64Array>>at: (in category 'accessing') -----
> + at: index
> +    | word64 |
> +    <primitive: 165>
> +    word64 := self basicAt: index.
> +    word64 < SmallInteger maxVal ifTrue:[^word64]. "Avoid LargeInteger computations"
> +    ^word64 >= 16r8000000000000000    "Negative?!!"
> +        ifTrue: ["word64 - 16r10000000000000000"
> +              (word64 bitInvert64 + 1) negated]
> +        ifFalse: [word64]!
>
> Item was added:
> + ----- Method: Long64Array>>at:put: (in category 'accessing') -----
> + at: index put: anInteger
> +    | word64 |
> +    <primitive: 166>
> +    anInteger < 0
> +        ifTrue:
> +            [anInteger < -16r8000000000000000 ifTrue: [self error: anInteger asString , ' out of range'].
> +            "word64 := 16r10000000000000000 + anInteger"
> +            word64 := (anInteger + 1) negated bitInvert64]
> +        ifFalse:
> +            [anInteger > 16r7FFFFFFFFFFFFFFF ifTrue: [self error: anInteger asString , ' out of range'].
> +            word64 := anInteger].
> +    self  basicAt: index put: word64.
> +    ^anInteger!
>
> Item was added:
> + ----- Method: Long64Array>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size * 8!
>
> Item was added:
> + ----- Method: Long64Array>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 8!
>
> Item was added:
> + FixedBitWidthSignedIntegerArray variableByteSubclass: #SignedByteArray
> +    instanceVariableNames: ''
> +    classVariableNames: ''
> +    poolDictionaries: ''
> +    category: 'Collections-Arrayed'!
> +
> + !SignedByteArray commentStamp: 'nice 5/2/2020 15:20' prior: 0!
> + IntegerArrays store 8bit signed Integer values.
> + Negative values are stored as 2's complement.!
>
> Item was added:
> + ----- Method: SignedByteArray>>at: (in category 'accessing') -----
> + at: index
> +    | word |
> +    <primitive: 165>
> +    word := self basicAt: index.
> +    ^word >= 16r80    "Negative?!!"
> +        ifTrue:[16r100 - word]
> +        ifFalse:[word]!
>
> Item was added:
> + ----- Method: SignedByteArray>>at:put: (in category 'accessing') -----
> + at: index put: anInteger
> +    | byte |
> +    <primitive: 166>
> +    anInteger < 0
> +        ifTrue:
> +            [anInteger < -16r80 ifTrue: [self error: anInteger asString , ' out of range'].
> +             byte := 16r100 + anInteger]
> +        ifFalse:
> +            [anInteger > 16r7F ifTrue: [self error: anInteger asString , ' out of range'].
> +             byte := anInteger].
> +    self  basicAt: index put: byte.
> +    ^anInteger!
>
> Item was added:
> + ----- Method: SignedByteArray>>byteSize (in category 'accessing') -----
> + byteSize
> +    ^self size!
>
> Item was added:
> + ----- Method: SignedByteArray>>bytesPerElement (in category 'accessing') -----
> + bytesPerElement
> +    "Number of bytes in each item.  This multiplied by (self size)*8 gives the number of bits stored."
> +    ^ 1!
>
> Item was changed:
> + FixedBitWidthUnsignedIntegerArray variableWordSubclass: #WordArray
> - ArrayedCollection variableWordSubclass: #WordArray
>      instanceVariableNames: ''
>      classVariableNames: ''
>      poolDictionaries: ''
>      category: 'Collections-Arrayed'!
>
>  !WordArray commentStamp: '<historical>' prior: 0!
>  WordArrays store 32-bit unsigned Integer values.
>  !
>
> Item was removed:
> - ----- Method: WordArray>>atAllPut: (in category 'accessing') -----
> - atAllPut: value
> -    "Fill the receiver with the given value"
> -
> -    <primitive: 145>
> -    super atAllPut: value!
>
> Item was removed:
> - ----- Method: WordArray>>defaultElement (in category 'accessing') -----
> - defaultElement
> -    "Return the default element of the receiver"
> -    ^0!
>
> Item was removed:
> - ----- Method: WordArray>>replaceFrom:to:with:startingAt: (in category 'private') -----
> - replaceFrom: start to: stop with: replacement startingAt: repStart
> -    <primitive: 105>
> -    ^super replaceFrom: start to: stop with: replacement startingAt: repStart !
>
>




Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

K K Subbu
In reply to this post by commits-2
On 02/05/20 5:41 pm, [hidden email] wrote:

> Nicolas Cellier uploaded a new version of Collections to project The Inbox:
> http://source.squeak.org/inbox/Collections-nice.891.mcz
>
> ==================== Summary ====================
>
> Name: Collections-nice.891
> Author: nice
> Time: 2 May 2020, 7:40:45.298967 pm
> UUID: 08510be0-8293-6744-959d-c1d41bc13ae1
> Ancestors: Collections-nice.890
>
> Experimental - For discussion
>
> Group some (most) non-pointers collections under an abstract FixedBitWifthArray.
> I know, the name is hard to pronounce and thus ugly: it's opened to discussion.
>
> This enables factorization of some methods, for example the trick for atAllPut:
> Also notice that most methods are shared between FloatArray and Float64Array.

How about ImmediateWord/ImmediateObject and an ImmediateArray (an array
consisting only of Immediate elements)? It would be consistent with
isImmediateClass method.

An object chunk could be checked at loading time to see if it needs to
be converted from immediate to pointers or vice versa. In the typical
case, this will be a nop. But if the image is moved to a different host
type (say from 64b to 32b or from x86 to ARM), then some immediate
numbers may be converted into pointers or vice versa. If this increases
loading time for large images, then the image may be saved locally.

This is just a strawman. I haven't really thought through all its
implications.

Regards .. Subbu

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

Nicolas Cellier
Hi Subbu,
Yes those raw bits are somehow like immediates, but not exactly...

Immediates are objects having their value encoded into the pointer slot (either in 4 or 8 bytes, according to 32bits or 64bits VM word size).
Currently, this covers only SmallInteger, Character and SmallFloat on 64bits.

Here we have values encoded into slots of 1, 2, 4 or 8 bytes, but not into an object oriented pointer slot.
Technically, #(1 2.0 $3) is an Array of immediates, while ((ColorArray with: Color black) first) is not an immediate...
So even if it is the same notion of encoded value, it's not an exact match...

Concerning the use cases, I effectively want to use such bit arrays for fast data transfer.
For example, it is useful for FFI I use exclusivily this kind of array for Smallapack...
But also when reading big files in Matlab, National Instrument TDMS or HDF5 format.
it really helps to have all the possible flavours for common elementary types of values.
Otherwise, I have to use an intermediate ByteArray, or pointers to external heap via FFI (like I did in Smallapack).

More than often, the data transfer can handle offset and stride via a BitBlt tricks (unless we have an odd layout).
This enables extracting a single "column" or bloc of data from a big file with a single copy.
I may need to extend BitBlt to cope with all the available bit-widths, not just 8 (byte) or 32 (word) though.

Also, those formats offer packed and contiguous memory layout which is an advantage too when dealing with large chunks of data.
Especially if we have vectorized primitives operating on the arrays.

Also, creating non-immediate objects on the fly thru #at: #at:put: is very efficient if VM has generation scavenger because those objects are generally short-lived.
While retaining all the pointers to a whole collection of non immediate objects is putting a lot of pressure on the garbage collector.

The advantage somehow diminish with the advent of 64bits VM: most values can be immediates, so we have quasi-contiguous data at a few exceptions, and not so much GC pressure.
But still, the primitives can operate on raw bits, without having to handle the immediate tag, nor exceptional (non immediate) values.

For the anecdote, in the 90s, I started to experiment some crashes in objectworks/visualworks when handling large Arrays of Float.
The console would only report: *out of memory*.
With increasing processor speed, the memory where exhausted before the low space monitoring process had a chance to handle the situation.
I then decided to handle all my Arrays of Float (Double) thru some UninterpretedBytes and ad-hoc primitives for at: at:put:
Since then, I never came back to pointer oriented arrays: if we want Smalltalk to scale, we need those basic objects  :)


Le dim. 3 mai 2020 à 06:50, K K Subbu <[hidden email]> a écrit :
On 02/05/20 5:41 pm, [hidden email] wrote:
> Nicolas Cellier uploaded a new version of Collections to project The Inbox:
> http://source.squeak.org/inbox/Collections-nice.891.mcz
>
> ==================== Summary ====================
>
> Name: Collections-nice.891
> Author: nice
> Time: 2 May 2020, 7:40:45.298967 pm
> UUID: 08510be0-8293-6744-959d-c1d41bc13ae1
> Ancestors: Collections-nice.890
>
> Experimental - For discussion
>
> Group some (most) non-pointers collections under an abstract FixedBitWifthArray.
> I know, the name is hard to pronounce and thus ugly: it's opened to discussion.
>
> This enables factorization of some methods, for example the trick for atAllPut:
> Also notice that most methods are shared between FloatArray and Float64Array.

How about ImmediateWord/ImmediateObject and an ImmediateArray (an array
consisting only of Immediate elements)? It would be consistent with
isImmediateClass method.

An object chunk could be checked at loading time to see if it needs to
be converted from immediate to pointers or vice versa. In the typical
case, this will be a nop. But if the image is moved to a different host
type (say from 64b to 32b or from x86 to ARM), then some immediate
numbers may be converted into pointers or vice versa. If this increases
loading time for large images, then the image may be saved locally.

This is just a strawman. I haven't really thought through all its
implications.

Regards .. Subbu



Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

David T. Lewis
I like the Collections-nice.891 proposal a lot. It is big improvement
for readability and comprehension.

The name 'FixedBitWidthArray' seems good to me. It might sound awkward
at first, but it clearly indicates the nature of this kind of collection,
and helps the reader understand the difference between these collections
compared to collections of object pointers and immediates.

The new class comments are also helpful, because they explain the basic
at:put: protocol and the interpretation of the array elements, which is
quite difference compared to other kinds of collection.

There is a minor typo in the SignedByteArray class comment, which
should say 'SignedByteArrays store...'

Dave

On Sun, May 03, 2020 at 03:52:38PM +0200, Nicolas Cellier wrote:

> Hi Subbu,
> Yes those raw bits are somehow like immediates, but not exactly...
>
> Immediates are objects having their value encoded into the pointer slot
> (either in 4 or 8 bytes, according to 32bits or 64bits VM word size).
> Currently, this covers only SmallInteger, Character and SmallFloat on
> 64bits.
>
> Here we have values encoded into slots of 1, 2, 4 or 8 bytes, but not into
> an object oriented pointer slot.
> Technically, #(1 2.0 $3) is an Array of immediates, while ((ColorArray
> with: Color black) first) is not an immediate...
> So even if it is the same notion of encoded value, it's not an exact
> match...
>
> Concerning the use cases, I effectively want to use such bit arrays for
> fast data transfer.
> For example, it is useful for FFI I use exclusivily this kind of array for
> Smallapack...
> But also when reading big files in Matlab, National Instrument TDMS or HDF5
> format.
> it really helps to have all the possible flavours for common elementary
> types of values.
> Otherwise, I have to use an intermediate ByteArray, or pointers to external
> heap via FFI (like I did in Smallapack).
>
> More than often, the data transfer can handle offset and stride via a
> BitBlt tricks (unless we have an odd layout).
> This enables extracting a single "column" or bloc of data from a big file
> with a single copy.
> I may need to extend BitBlt to cope with all the available bit-widths, not
> just 8 (byte) or 32 (word) though.
>
> Also, those formats offer packed and contiguous memory layout which is an
> advantage too when dealing with large chunks of data.
> Especially if we have vectorized primitives operating on the arrays.
>
> Also, creating non-immediate objects on the fly thru #at: #at:put: is very
> efficient if VM has generation scavenger because those objects are
> generally short-lived.
> While retaining all the pointers to a whole collection of non immediate
> objects is putting a lot of pressure on the garbage collector.
>
> The advantage somehow diminish with the advent of 64bits VM: most values
> can be immediates, so we have quasi-contiguous data at a few exceptions,
> and not so much GC pressure.
> But still, the primitives can operate on raw bits, without having to handle
> the immediate tag, nor exceptional (non immediate) values.
>
> For the anecdote, in the 90s, I started to experiment some crashes in
> objectworks/visualworks when handling large Arrays of Float.
> The console would only report: *out of memory*.
> With increasing processor speed, the memory where exhausted before the low
> space monitoring process had a chance to handle the situation.
> I then decided to handle all my Arrays of Float (Double) thru some
> UninterpretedBytes and ad-hoc primitives for at: at:put:
> Since then, I never came back to pointer oriented arrays: if we want
> Smalltalk to scale, we need those basic objects  :)
>
>
> Le dim. 3 mai 2020 ?? 06:50, K K Subbu <[hidden email]> a ??crit :
>
> > On 02/05/20 5:41 pm, [hidden email] wrote:
> > > Nicolas Cellier uploaded a new version of Collections to project The
> > Inbox:
> > > http://source.squeak.org/inbox/Collections-nice.891.mcz
> > >
> > > ==================== Summary ====================
> > >
> > > Name: Collections-nice.891
> > > Author: nice
> > > Time: 2 May 2020, 7:40:45.298967 pm
> > > UUID: 08510be0-8293-6744-959d-c1d41bc13ae1
> > > Ancestors: Collections-nice.890
> > >
> > > Experimental - For discussion
> > >
> > > Group some (most) non-pointers collections under an abstract
> > FixedBitWifthArray.
> > > I know, the name is hard to pronounce and thus ugly: it's opened to
> > discussion.
> > >
> > > This enables factorization of some methods, for example the trick for
> > atAllPut:
> > > Also notice that most methods are shared between FloatArray and
> > Float64Array.
> >
> > How about ImmediateWord/ImmediateObject and an ImmediateArray (an array
> > consisting only of Immediate elements)? It would be consistent with
> > isImmediateClass method.
> >
> > An object chunk could be checked at loading time to see if it needs to
> > be converted from immediate to pointers or vice versa. In the typical
> > case, this will be a nop. But if the image is moved to a different host
> > type (say from 64b to 32b or from x86 to ARM), then some immediate
> > numbers may be converted into pointers or vice versa. If this increases
> > loading time for large images, then the image may be saved locally.
> >
> > This is just a strawman. I haven't really thought through all its
> > implications.
> >
> > Regards .. Subbu
> >
> >

>


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

Tobias Pape
In reply to this post by Nicolas Cellier

> On 03.05.2020, at 15:52, Nicolas Cellier <[hidden email]> wrote:
>
> Hi Subbu,
> Yes those raw bits are somehow like immediates, but not exactly...

So the name maybe should include "raw"?
:D
-t

>
> Immediates are objects having their value encoded into the pointer slot (either in 4 or 8 bytes, according to 32bits or 64bits VM word size).
> Currently, this covers only SmallInteger, Character and SmallFloat on 64bits.
>
> Here we have values encoded into slots of 1, 2, 4 or 8 bytes, but not into an object oriented pointer slot.
> Technically, #(1 2.0 $3) is an Array of immediates, while ((ColorArray with: Color black) first) is not an immediate...
> So even if it is the same notion of encoded value, it's not an exact match...
>
> Concerning the use cases, I effectively want to use such bit arrays for fast data transfer.
> For example, it is useful for FFI I use exclusivily this kind of array for Smallapack...
> But also when reading big files in Matlab, National Instrument TDMS or HDF5 format.
> it really helps to have all the possible flavours for common elementary types of values.
> Otherwise, I have to use an intermediate ByteArray, or pointers to external heap via FFI (like I did in Smallapack).
>
> More than often, the data transfer can handle offset and stride via a BitBlt tricks (unless we have an odd layout).
> This enables extracting a single "column" or bloc of data from a big file with a single copy.
> I may need to extend BitBlt to cope with all the available bit-widths, not just 8 (byte) or 32 (word) though.
>
> Also, those formats offer packed and contiguous memory layout which is an advantage too when dealing with large chunks of data.
> Especially if we have vectorized primitives operating on the arrays.
>
> Also, creating non-immediate objects on the fly thru #at: #at:put: is very efficient if VM has generation scavenger because those objects are generally short-lived.
> While retaining all the pointers to a whole collection of non immediate objects is putting a lot of pressure on the garbage collector.
>
> The advantage somehow diminish with the advent of 64bits VM: most values can be immediates, so we have quasi-contiguous data at a few exceptions, and not so much GC pressure.
> But still, the primitives can operate on raw bits, without having to handle the immediate tag, nor exceptional (non immediate) values.
>
> For the anecdote, in the 90s, I started to experiment some crashes in objectworks/visualworks when handling large Arrays of Float.
> The console would only report: *out of memory*.
> With increasing processor speed, the memory where exhausted before the low space monitoring process had a chance to handle the situation.
> I then decided to handle all my Arrays of Float (Double) thru some UninterpretedBytes and ad-hoc primitives for at: at:put:
> Since then, I never came back to pointer oriented arrays: if we want Smalltalk to scale, we need those basic objects  :)
>
>
> Le dim. 3 mai 2020 à 06:50, K K Subbu <[hidden email]> a écrit :
> On 02/05/20 5:41 pm, [hidden email] wrote:
> > Nicolas Cellier uploaded a new version of Collections to project The Inbox:
> > http://source.squeak.org/inbox/Collections-nice.891.mcz
> >
> > ==================== Summary ====================
> >
> > Name: Collections-nice.891
> > Author: nice
> > Time: 2 May 2020, 7:40:45.298967 pm
> > UUID: 08510be0-8293-6744-959d-c1d41bc13ae1
> > Ancestors: Collections-nice.890
> >
> > Experimental - For discussion
> >
> > Group some (most) non-pointers collections under an abstract FixedBitWifthArray.
> > I know, the name is hard to pronounce and thus ugly: it's opened to discussion.
> >
> > This enables factorization of some methods, for example the trick for atAllPut:
> > Also notice that most methods are shared between FloatArray and Float64Array.
>
> How about ImmediateWord/ImmediateObject and an ImmediateArray (an array
> consisting only of Immediate elements)? It would be consistent with
> isImmediateClass method.
>
> An object chunk could be checked at loading time to see if it needs to
> be converted from immediate to pointers or vice versa. In the typical
> case, this will be a nop. But if the image is moved to a different host
> type (say from 64b to 32b or from x86 to ARM), then some immediate
> numbers may be converted into pointers or vice versa. If this increases
> loading time for large images, then the image may be saved locally.
>
> This is just a strawman. I haven't really thought through all its
> implications.
>
> Regards .. Subbu
>
>



Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

Nicolas Cellier


Le dim. 3 mai 2020 à 17:13, Tobias Pape <[hidden email]> a écrit :

> On 03.05.2020, at 15:52, Nicolas Cellier <[hidden email]> wrote:
>
> Hi Subbu,
> Yes those raw bits are somehow like immediates, but not exactly...

So the name maybe should include "raw"?
:D
-t

Yes, that was the first name that came in my mind.
From the abstract superclass POV, those are raw bits.
Only subclass really now how to interpret those bits as value objects.
I don't know why I then changed my mind...
Maybe because RawBits does not convey the meaning of FixedWidth.
Note that the class query is #isBits. So the AbstractBitsArray is somehow in line with that.

>
> Immediates are objects having their value encoded into the pointer slot (either in 4 or 8 bytes, according to 32bits or 64bits VM word size).
> Currently, this covers only SmallInteger, Character and SmallFloat on 64bits.
>
> Here we have values encoded into slots of 1, 2, 4 or 8 bytes, but not into an object oriented pointer slot.
> Technically, #(1 2.0 $3) is an Array of immediates, while ((ColorArray with: Color black) first) is not an immediate...
> So even if it is the same notion of encoded value, it's not an exact match...
>
> Concerning the use cases, I effectively want to use such bit arrays for fast data transfer.
> For example, it is useful for FFI I use exclusivily this kind of array for Smallapack...
> But also when reading big files in Matlab, National Instrument TDMS or HDF5 format.
> it really helps to have all the possible flavours for common elementary types of values.
> Otherwise, I have to use an intermediate ByteArray, or pointers to external heap via FFI (like I did in Smallapack).
>
> More than often, the data transfer can handle offset and stride via a BitBlt tricks (unless we have an odd layout).
> This enables extracting a single "column" or bloc of data from a big file with a single copy.
> I may need to extend BitBlt to cope with all the available bit-widths, not just 8 (byte) or 32 (word) though.
>
> Also, those formats offer packed and contiguous memory layout which is an advantage too when dealing with large chunks of data.
> Especially if we have vectorized primitives operating on the arrays.
>
> Also, creating non-immediate objects on the fly thru #at: #at:put: is very efficient if VM has generation scavenger because those objects are generally short-lived.
> While retaining all the pointers to a whole collection of non immediate objects is putting a lot of pressure on the garbage collector.
>
> The advantage somehow diminish with the advent of 64bits VM: most values can be immediates, so we have quasi-contiguous data at a few exceptions, and not so much GC pressure.
> But still, the primitives can operate on raw bits, without having to handle the immediate tag, nor exceptional (non immediate) values.
>
> For the anecdote, in the 90s, I started to experiment some crashes in objectworks/visualworks when handling large Arrays of Float.
> The console would only report: *out of memory*.
> With increasing processor speed, the memory where exhausted before the low space monitoring process had a chance to handle the situation.
> I then decided to handle all my Arrays of Float (Double) thru some UninterpretedBytes and ad-hoc primitives for at: at:put:
> Since then, I never came back to pointer oriented arrays: if we want Smalltalk to scale, we need those basic objects  :)
>
>
> Le dim. 3 mai 2020 à 06:50, K K Subbu <[hidden email]> a écrit :
> On 02/05/20 5:41 pm, [hidden email] wrote:
> > Nicolas Cellier uploaded a new version of Collections to project The Inbox:
> > http://source.squeak.org/inbox/Collections-nice.891.mcz
> >
> > ==================== Summary ====================
> >
> > Name: Collections-nice.891
> > Author: nice
> > Time: 2 May 2020, 7:40:45.298967 pm
> > UUID: 08510be0-8293-6744-959d-c1d41bc13ae1
> > Ancestors: Collections-nice.890
> >
> > Experimental - For discussion
> >
> > Group some (most) non-pointers collections under an abstract FixedBitWifthArray.
> > I know, the name is hard to pronounce and thus ugly: it's opened to discussion.
> >
> > This enables factorization of some methods, for example the trick for atAllPut:
> > Also notice that most methods are shared between FloatArray and Float64Array.
>
> How about ImmediateWord/ImmediateObject and an ImmediateArray (an array
> consisting only of Immediate elements)? It would be consistent with
> isImmediateClass method.
>
> An object chunk could be checked at loading time to see if it needs to
> be converted from immediate to pointers or vice versa. In the typical
> case, this will be a nop. But if the image is moved to a different host
> type (say from 64b to 32b or from x86 to ARM), then some immediate
> numbers may be converted into pointers or vice versa. If this increases
> loading time for large images, then the image may be saved locally.
>
> This is just a strawman. I haven't really thought through all its
> implications.
>
> Regards .. Subbu
>
>





Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

Nicolas Cellier
bah excuse the grammar...
I constantly invert now vs know and where vs were, I wish your brain is equipped with auto-correction.

Le dim. 3 mai 2020 à 17:20, Nicolas Cellier <[hidden email]> a écrit :


Le dim. 3 mai 2020 à 17:13, Tobias Pape <[hidden email]> a écrit :

> On 03.05.2020, at 15:52, Nicolas Cellier <[hidden email]> wrote:
>
> Hi Subbu,
> Yes those raw bits are somehow like immediates, but not exactly...

So the name maybe should include "raw"?
:D
-t

Yes, that was the first name that came in my mind.
From the abstract superclass POV, those are raw bits.
Only subclass really now how to interpret those bits as value objects.
I don't know why I then changed my mind...
Maybe because RawBits does not convey the meaning of FixedWidth.
Note that the class query is #isBits. So the AbstractBitsArray is somehow in line with that.

>
> Immediates are objects having their value encoded into the pointer slot (either in 4 or 8 bytes, according to 32bits or 64bits VM word size).
> Currently, this covers only SmallInteger, Character and SmallFloat on 64bits.
>
> Here we have values encoded into slots of 1, 2, 4 or 8 bytes, but not into an object oriented pointer slot.
> Technically, #(1 2.0 $3) is an Array of immediates, while ((ColorArray with: Color black) first) is not an immediate...
> So even if it is the same notion of encoded value, it's not an exact match...
>
> Concerning the use cases, I effectively want to use such bit arrays for fast data transfer.
> For example, it is useful for FFI I use exclusivily this kind of array for Smallapack...
> But also when reading big files in Matlab, National Instrument TDMS or HDF5 format.
> it really helps to have all the possible flavours for common elementary types of values.
> Otherwise, I have to use an intermediate ByteArray, or pointers to external heap via FFI (like I did in Smallapack).
>
> More than often, the data transfer can handle offset and stride via a BitBlt tricks (unless we have an odd layout).
> This enables extracting a single "column" or bloc of data from a big file with a single copy.
> I may need to extend BitBlt to cope with all the available bit-widths, not just 8 (byte) or 32 (word) though.
>
> Also, those formats offer packed and contiguous memory layout which is an advantage too when dealing with large chunks of data.
> Especially if we have vectorized primitives operating on the arrays.
>
> Also, creating non-immediate objects on the fly thru #at: #at:put: is very efficient if VM has generation scavenger because those objects are generally short-lived.
> While retaining all the pointers to a whole collection of non immediate objects is putting a lot of pressure on the garbage collector.
>
> The advantage somehow diminish with the advent of 64bits VM: most values can be immediates, so we have quasi-contiguous data at a few exceptions, and not so much GC pressure.
> But still, the primitives can operate on raw bits, without having to handle the immediate tag, nor exceptional (non immediate) values.
>
> For the anecdote, in the 90s, I started to experiment some crashes in objectworks/visualworks when handling large Arrays of Float.
> The console would only report: *out of memory*.
> With increasing processor speed, the memory where exhausted before the low space monitoring process had a chance to handle the situation.
> I then decided to handle all my Arrays of Float (Double) thru some UninterpretedBytes and ad-hoc primitives for at: at:put:
> Since then, I never came back to pointer oriented arrays: if we want Smalltalk to scale, we need those basic objects  :)
>
>
> Le dim. 3 mai 2020 à 06:50, K K Subbu <[hidden email]> a écrit :
> On 02/05/20 5:41 pm, [hidden email] wrote:
> > Nicolas Cellier uploaded a new version of Collections to project The Inbox:
> > http://source.squeak.org/inbox/Collections-nice.891.mcz
> >
> > ==================== Summary ====================
> >
> > Name: Collections-nice.891
> > Author: nice
> > Time: 2 May 2020, 7:40:45.298967 pm
> > UUID: 08510be0-8293-6744-959d-c1d41bc13ae1
> > Ancestors: Collections-nice.890
> >
> > Experimental - For discussion
> >
> > Group some (most) non-pointers collections under an abstract FixedBitWifthArray.
> > I know, the name is hard to pronounce and thus ugly: it's opened to discussion.
> >
> > This enables factorization of some methods, for example the trick for atAllPut:
> > Also notice that most methods are shared between FloatArray and Float64Array.
>
> How about ImmediateWord/ImmediateObject and an ImmediateArray (an array
> consisting only of Immediate elements)? It would be consistent with
> isImmediateClass method.
>
> An object chunk could be checked at loading time to see if it needs to
> be converted from immediate to pointers or vice versa. In the typical
> case, this will be a nop. But if the image is moved to a different host
> type (say from 64b to 32b or from x86 to ARM), then some immediate
> numbers may be converted into pointers or vice versa. If this increases
> loading time for large images, then the image may be saved locally.
>
> This is just a strawman. I haven't really thought through all its
> implications.
>
> Regards .. Subbu
>
>





Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

Nicolas Cellier
were equipped of course, hem!

Le dim. 3 mai 2020 à 17:22, Nicolas Cellier <[hidden email]> a écrit :
bah excuse the grammar...
I constantly invert now vs know and where vs were, I wish your brain is equipped with auto-correction.

Le dim. 3 mai 2020 à 17:20, Nicolas Cellier <[hidden email]> a écrit :


Le dim. 3 mai 2020 à 17:13, Tobias Pape <[hidden email]> a écrit :

> On 03.05.2020, at 15:52, Nicolas Cellier <[hidden email]> wrote:
>
> Hi Subbu,
> Yes those raw bits are somehow like immediates, but not exactly...

So the name maybe should include "raw"?
:D
-t

Yes, that was the first name that came in my mind.
From the abstract superclass POV, those are raw bits.
Only subclass really now how to interpret those bits as value objects.
I don't know why I then changed my mind...
Maybe because RawBits does not convey the meaning of FixedWidth.
Note that the class query is #isBits. So the AbstractBitsArray is somehow in line with that.

>
> Immediates are objects having their value encoded into the pointer slot (either in 4 or 8 bytes, according to 32bits or 64bits VM word size).
> Currently, this covers only SmallInteger, Character and SmallFloat on 64bits.
>
> Here we have values encoded into slots of 1, 2, 4 or 8 bytes, but not into an object oriented pointer slot.
> Technically, #(1 2.0 $3) is an Array of immediates, while ((ColorArray with: Color black) first) is not an immediate...
> So even if it is the same notion of encoded value, it's not an exact match...
>
> Concerning the use cases, I effectively want to use such bit arrays for fast data transfer.
> For example, it is useful for FFI I use exclusivily this kind of array for Smallapack...
> But also when reading big files in Matlab, National Instrument TDMS or HDF5 format.
> it really helps to have all the possible flavours for common elementary types of values.
> Otherwise, I have to use an intermediate ByteArray, or pointers to external heap via FFI (like I did in Smallapack).
>
> More than often, the data transfer can handle offset and stride via a BitBlt tricks (unless we have an odd layout).
> This enables extracting a single "column" or bloc of data from a big file with a single copy.
> I may need to extend BitBlt to cope with all the available bit-widths, not just 8 (byte) or 32 (word) though.
>
> Also, those formats offer packed and contiguous memory layout which is an advantage too when dealing with large chunks of data.
> Especially if we have vectorized primitives operating on the arrays.
>
> Also, creating non-immediate objects on the fly thru #at: #at:put: is very efficient if VM has generation scavenger because those objects are generally short-lived.
> While retaining all the pointers to a whole collection of non immediate objects is putting a lot of pressure on the garbage collector.
>
> The advantage somehow diminish with the advent of 64bits VM: most values can be immediates, so we have quasi-contiguous data at a few exceptions, and not so much GC pressure.
> But still, the primitives can operate on raw bits, without having to handle the immediate tag, nor exceptional (non immediate) values.
>
> For the anecdote, in the 90s, I started to experiment some crashes in objectworks/visualworks when handling large Arrays of Float.
> The console would only report: *out of memory*.
> With increasing processor speed, the memory where exhausted before the low space monitoring process had a chance to handle the situation.
> I then decided to handle all my Arrays of Float (Double) thru some UninterpretedBytes and ad-hoc primitives for at: at:put:
> Since then, I never came back to pointer oriented arrays: if we want Smalltalk to scale, we need those basic objects  :)
>
>
> Le dim. 3 mai 2020 à 06:50, K K Subbu <[hidden email]> a écrit :
> On 02/05/20 5:41 pm, [hidden email] wrote:
> > Nicolas Cellier uploaded a new version of Collections to project The Inbox:
> > http://source.squeak.org/inbox/Collections-nice.891.mcz
> >
> > ==================== Summary ====================
> >
> > Name: Collections-nice.891
> > Author: nice
> > Time: 2 May 2020, 7:40:45.298967 pm
> > UUID: 08510be0-8293-6744-959d-c1d41bc13ae1
> > Ancestors: Collections-nice.890
> >
> > Experimental - For discussion
> >
> > Group some (most) non-pointers collections under an abstract FixedBitWifthArray.
> > I know, the name is hard to pronounce and thus ugly: it's opened to discussion.
> >
> > This enables factorization of some methods, for example the trick for atAllPut:
> > Also notice that most methods are shared between FloatArray and Float64Array.
>
> How about ImmediateWord/ImmediateObject and an ImmediateArray (an array
> consisting only of Immediate elements)? It would be consistent with
> isImmediateClass method.
>
> An object chunk could be checked at loading time to see if it needs to
> be converted from immediate to pointers or vice versa. In the typical
> case, this will be a nop. But if the image is moved to a different host
> type (say from 64b to 32b or from x86 to ARM), then some immediate
> numbers may be converted into pointers or vice versa. If this increases
> loading time for large images, then the image may be saved locally.
>
> This is just a strawman. I haven't really thought through all its
> implications.
>
> Regards .. Subbu
>
>





Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

Tobias Pape

> On 03.05.2020, at 17:23, Nicolas Cellier <[hidden email]> wrote:
>
> were equipped of course, hem!

Those keys :D no worries.
-t

>
> Le dim. 3 mai 2020 à 17:22, Nicolas Cellier <[hidden email]> a écrit :
> bah excuse the grammar...
> I constantly invert now vs know and where vs were, I wish your brain is equipped with auto-correction.
>
> Le dim. 3 mai 2020 à 17:20, Nicolas Cellier <[hidden email]> a écrit :
>
>
> Le dim. 3 mai 2020 à 17:13, Tobias Pape <[hidden email]> a écrit :
>
> > On 03.05.2020, at 15:52, Nicolas Cellier <[hidden email]> wrote:
> >
> > Hi Subbu,
> > Yes those raw bits are somehow like immediates, but not exactly...
>
> So the name maybe should include "raw"?
> :D
> -t
>
> Yes, that was the first name that came in my mind.
> From the abstract superclass POV, those are raw bits.
> Only subclass really now how to interpret those bits as value objects.
> I don't know why I then changed my mind...
> Maybe because RawBits does not convey the meaning of FixedWidth.
> Note that the class query is #isBits. So the AbstractBitsArray is somehow in line with that.
>
> >
> > Immediates are objects having their value encoded into the pointer slot (either in 4 or 8 bytes, according to 32bits or 64bits VM word size).
> > Currently, this covers only SmallInteger, Character and SmallFloat on 64bits.
> >
> > Here we have values encoded into slots of 1, 2, 4 or 8 bytes, but not into an object oriented pointer slot.
> > Technically, #(1 2.0 $3) is an Array of immediates, while ((ColorArray with: Color black) first) is not an immediate...
> > So even if it is the same notion of encoded value, it's not an exact match...
> >
> > Concerning the use cases, I effectively want to use such bit arrays for fast data transfer.
> > For example, it is useful for FFI I use exclusivily this kind of array for Smallapack...
> > But also when reading big files in Matlab, National Instrument TDMS or HDF5 format.
> > it really helps to have all the possible flavours for common elementary types of values.
> > Otherwise, I have to use an intermediate ByteArray, or pointers to external heap via FFI (like I did in Smallapack).
> >
> > More than often, the data transfer can handle offset and stride via a BitBlt tricks (unless we have an odd layout).
> > This enables extracting a single "column" or bloc of data from a big file with a single copy.
> > I may need to extend BitBlt to cope with all the available bit-widths, not just 8 (byte) or 32 (word) though.
> >
> > Also, those formats offer packed and contiguous memory layout which is an advantage too when dealing with large chunks of data.
> > Especially if we have vectorized primitives operating on the arrays.
> >
> > Also, creating non-immediate objects on the fly thru #at: #at:put: is very efficient if VM has generation scavenger because those objects are generally short-lived.
> > While retaining all the pointers to a whole collection of non immediate objects is putting a lot of pressure on the garbage collector.
> >
> > The advantage somehow diminish with the advent of 64bits VM: most values can be immediates, so we have quasi-contiguous data at a few exceptions, and not so much GC pressure.
> > But still, the primitives can operate on raw bits, without having to handle the immediate tag, nor exceptional (non immediate) values.
> >
> > For the anecdote, in the 90s, I started to experiment some crashes in objectworks/visualworks when handling large Arrays of Float.
> > The console would only report: *out of memory*.
> > With increasing processor speed, the memory where exhausted before the low space monitoring process had a chance to handle the situation.
> > I then decided to handle all my Arrays of Float (Double) thru some UninterpretedBytes and ad-hoc primitives for at: at:put:
> > Since then, I never came back to pointer oriented arrays: if we want Smalltalk to scale, we need those basic objects  :)
> >
> >
> > Le dim. 3 mai 2020 à 06:50, K K Subbu <[hidden email]> a écrit :
> > On 02/05/20 5:41 pm, [hidden email] wrote:
> > > Nicolas Cellier uploaded a new version of Collections to project The Inbox:
> > > http://source.squeak.org/inbox/Collections-nice.891.mcz
> > >
> > > ==================== Summary ====================
> > >
> > > Name: Collections-nice.891
> > > Author: nice
> > > Time: 2 May 2020, 7:40:45.298967 pm
> > > UUID: 08510be0-8293-6744-959d-c1d41bc13ae1
> > > Ancestors: Collections-nice.890
> > >
> > > Experimental - For discussion
> > >
> > > Group some (most) non-pointers collections under an abstract FixedBitWifthArray.
> > > I know, the name is hard to pronounce and thus ugly: it's opened to discussion.
> > >
> > > This enables factorization of some methods, for example the trick for atAllPut:
> > > Also notice that most methods are shared between FloatArray and Float64Array.
> >
> > How about ImmediateWord/ImmediateObject and an ImmediateArray (an array
> > consisting only of Immediate elements)? It would be consistent with
> > isImmediateClass method.
> >
> > An object chunk could be checked at loading time to see if it needs to
> > be converted from immediate to pointers or vice versa. In the typical
> > case, this will be a nop. But if the image is moved to a different host
> > type (say from 64b to 32b or from x86 to ARM), then some immediate
> > numbers may be converted into pointers or vice versa. If this increases
> > loading time for large images, then the image may be saved locally.
> >
> > This is just a strawman. I haven't really thought through all its
> > implications.
> >
> > Regards .. Subbu
> >
> >
>
>
>
>



Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

Tobias Pape
In reply to this post by Nicolas Cellier

> On 03.05.2020, at 17:20, Nicolas Cellier <[hidden email]> wrote:
>
>
>
> Le dim. 3 mai 2020 à 17:13, Tobias Pape <[hidden email]> a écrit :
>
> > On 03.05.2020, at 15:52, Nicolas Cellier <[hidden email]> wrote:
> >
> > Hi Subbu,
> > Yes those raw bits are somehow like immediates, but not exactly...
>
> So the name maybe should include "raw"?
> :D
> -t
>
> Yes, that was the first name that came in my mind.
> From the abstract superclass POV, those are raw bits.
> Only subclass really now how to interpret those bits as value objects.
> I don't know why I then changed my mind...
> Maybe because RawBits does not convey the meaning of FixedWidth.
> Note that the class query is #isBits. So the AbstractBitsArray is somehow in line with that.
>

I like the raw bit. I somehow don't like the bit bit although it is ...  truthful?
Talking about bits always makes me think I actually address bits. Octets? but that does not help too much…

sigh
Best regards
        -Tobias

> >
> > Immediates are objects having their value encoded into the pointer slot (either in 4 or 8 bytes, according to 32bits or 64bits VM word size).
> > Currently, this covers only SmallInteger, Character and SmallFloat on 64bits.
> >
> > Here we have values encoded into slots of 1, 2, 4 or 8 bytes, but not into an object oriented pointer slot.
> > Technically, #(1 2.0 $3) is an Array of immediates, while ((ColorArray with: Color black) first) is not an immediate...
> > So even if it is the same notion of encoded value, it's not an exact match...
> >
> > Concerning the use cases, I effectively want to use such bit arrays for fast data transfer.
> > For example, it is useful for FFI I use exclusivily this kind of array for Smallapack...
> > But also when reading big files in Matlab, National Instrument TDMS or HDF5 format.
> > it really helps to have all the possible flavours for common elementary types of values.
> > Otherwise, I have to use an intermediate ByteArray, or pointers to external heap via FFI (like I did in Smallapack).
> >
> > More than often, the data transfer can handle offset and stride via a BitBlt tricks (unless we have an odd layout).
> > This enables extracting a single "column" or bloc of data from a big file with a single copy.
> > I may need to extend BitBlt to cope with all the available bit-widths, not just 8 (byte) or 32 (word) though.
> >
> > Also, those formats offer packed and contiguous memory layout which is an advantage too when dealing with large chunks of data.
> > Especially if we have vectorized primitives operating on the arrays.
> >
> > Also, creating non-immediate objects on the fly thru #at: #at:put: is very efficient if VM has generation scavenger because those objects are generally short-lived.
> > While retaining all the pointers to a whole collection of non immediate objects is putting a lot of pressure on the garbage collector.
> >
> > The advantage somehow diminish with the advent of 64bits VM: most values can be immediates, so we have quasi-contiguous data at a few exceptions, and not so much GC pressure.
> > But still, the primitives can operate on raw bits, without having to handle the immediate tag, nor exceptional (non immediate) values.
> >
> > For the anecdote, in the 90s, I started to experiment some crashes in objectworks/visualworks when handling large Arrays of Float.
> > The console would only report: *out of memory*.
> > With increasing processor speed, the memory where exhausted before the low space monitoring process had a chance to handle the situation.
> > I then decided to handle all my Arrays of Float (Double) thru some UninterpretedBytes and ad-hoc primitives for at: at:put:
> > Since then, I never came back to pointer oriented arrays: if we want Smalltalk to scale, we need those basic objects  :)
> >
> >
> > Le dim. 3 mai 2020 à 06:50, K K Subbu <[hidden email]> a écrit :
> > On 02/05/20 5:41 pm, [hidden email] wrote:
> > > Nicolas Cellier uploaded a new version of Collections to project The Inbox:
> > > http://source.squeak.org/inbox/Collections-nice.891.mcz
> > >
> > > ==================== Summary ====================
> > >
> > > Name: Collections-nice.891
> > > Author: nice
> > > Time: 2 May 2020, 7:40:45.298967 pm
> > > UUID: 08510be0-8293-6744-959d-c1d41bc13ae1
> > > Ancestors: Collections-nice.890
> > >
> > > Experimental - For discussion
> > >
> > > Group some (most) non-pointers collections under an abstract FixedBitWifthArray.
> > > I know, the name is hard to pronounce and thus ugly: it's opened to discussion.
> > >
> > > This enables factorization of some methods, for example the trick for atAllPut:
> > > Also notice that most methods are shared between FloatArray and Float64Array.
> >
> > How about ImmediateWord/ImmediateObject and an ImmediateArray (an array
> > consisting only of Immediate elements)? It would be consistent with
> > isImmediateClass method.
> >
> > An object chunk could be checked at loading time to see if it needs to
> > be converted from immediate to pointers or vice versa. In the typical
> > case, this will be a nop. But if the image is moved to a different host
> > type (say from 64b to 32b or from x86 to ARM), then some immediate
> > numbers may be converted into pointers or vice versa. If this increases
> > loading time for large images, then the image may be saved locally.
> >
> > This is just a strawman. I haven't really thought through all its
> > implications.
> >
> > Regards .. Subbu
> >
> >
>
>
>
>



Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

K K Subbu
In reply to this post by Nicolas Cellier
On 03/05/20 7:22 pm, Nicolas Cellier wrote:

> More than often, the data transfer can handle offset and stride via a
> BitBlt tricks (unless we have an odd layout).
> This enables extracting a single "column" or bloc of data from a big
> file with a single copy.
> I may need to extend BitBlt to cope with all the available bit-widths,
> not just 8 (byte) or 32 (word) though.
>
> Also, those formats offer packed and contiguous memory layout which is
> an advantage too when dealing with large chunks of data.
> Especially if we have vectorized primitives operating on the arrays.
Ha! Now I get it. But FixedWidthBitArray is too primitive a type for
this purpose. It would expose host's word size to class methods instead
of encapsulating it in plugins.

I would apply recursive decomposition and use something like
PackedVector(stride, length) on the lines of a Form(width, height).
PackedVectors may decomposed into smaller packedvectors recursively
until they are small enough for ImmediateClass (i.e. stride = host's
word size). This would be well-suited to speed up through arch-specific
plugins.

When loading a packedvector from an image on a smaller word size host,
ImmediateClass elements could be converted into packedvectors. The
reverse could happen on larger word size hosts with a one-time
conversion cost.

Regards .. Subbu

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Collections-nice.891.mcz

Nicolas Cellier
Here is a snapshot of the hierarchy I used in VW several years ago.

Capture d’écran 2020-05-04 à 21.11.17.png
It is in cincom store SYSEXT-RawArray
Unlike squeak, I have used single-byte elements uniformly.
VW only provide 8(byte) and 16(word) bits elements, so there is not much to gain in complexifying the interface.
I did use Float and Double rather than Float32 and Float64 to fit what is in a VW image. For the rest, just int and uint...
I might re-create a similar hierarchy in STEM, but I would prefer to see a good one in the base image. That's useful for everyone.

Le lun. 4 mai 2020 à 09:29, K K Subbu <[hidden email]> a écrit :
On 03/05/20 7:22 pm, Nicolas Cellier wrote:
> More than often, the data transfer can handle offset and stride via a
> BitBlt tricks (unless we have an odd layout).
> This enables extracting a single "column" or bloc of data from a big
> file with a single copy.
> I may need to extend BitBlt to cope with all the available bit-widths,
> not just 8 (byte) or 32 (word) though.
>
> Also, those formats offer packed and contiguous memory layout which is
> an advantage too when dealing with large chunks of data.
> Especially if we have vectorized primitives operating on the arrays.
Ha! Now I get it. But FixedWidthBitArray is too primitive a type for
this purpose. It would expose host's word size to class methods instead
of encapsulating it in plugins.

I would apply recursive decomposition and use something like
PackedVector(stride, length) on the lines of a Form(width, height).
PackedVectors may decomposed into smaller packedvectors recursively
until they are small enough for ImmediateClass (i.e. stride = host's
word size). This would be well-suited to speed up through arch-specific
plugins.

When loading a packedvector from an image on a smaller word size host,
ImmediateClass elements could be converted into packedvectors. The
reverse could happen on larger word size hosts with a one-time
conversion cost.

Regards .. Subbu