[squeak-dev] The Trunk: Collections-nice.890.mcz

commits at source.squeak.org commits at source.squeak.org
Sat May 2 01:05:21 UTC 2020


David T. Lewis uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-nice.890.mcz

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

Name: Collections-nice.890
Author: nice
Time: 2 May 2020, 12:46:11.423176 am
UUID: e7907bbc-eb45-4b41-b70a-f1290a10a4e4
Ancestors: Collections-mt.889

Introduce Float64Array.
This will be fast once the Float64ArrayPlugin is delivered.

=============== Diff against Collections-mt.889 ===============

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

Item was added:
+ ----- Method: Float64Array class>>fromFloatArray: (in category 'instance creation') -----
+ fromFloatArray: aFloatArray
+ 	^(self new: aFloatArray) copyFromFloatArray: aFloatArray!

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

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

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

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

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

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

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

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

Item was added:
+ ----- Method: Float64Array>>= (in category 'comparing') -----
+ = aFloat64Array 
+ 	<primitive: 'primitiveEqual' module: 'Float64ArrayPlugin'>
+ 	^super = aFloat64Array!

Item was added:
+ ----- 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 added:
+ ----- 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>>asFloat64Array (in category 'converting') -----
+ asFloat64Array
+ 	^self!

Item was added:
+ ----- Method: Float64Array>>asFloatArray (in category 'converting') -----
+ asFloatArray
+ 	^FloatArray fromFloat64Array: self!

Item was added:
+ ----- Method: Float64Array>>at: (in category 'accessing') -----
+ at: index
+ 	<primitive: 'primitiveAt' module: 'Float64ArrayPlugin'>
+ 	| f64 u64 |
+ 	u64 := self basicAt: index.
+ 	(f64 := Float basicNew)
+ 		basicAt: 1 put: (u64 >> 32);
+ 		basicAt: 2 put: (u64 bitAnd: 16rFFFFFFFF).
+ 	^f64 * 1.0!

Item was added:
+ ----- Method: Float64Array>>at:put: (in category 'accessing') -----
+ at: index put: value
+ 	<primitive: 'primitiveAtPut' module: 'Float64ArrayPlugin'>
+ 	value isFloat 
+ 		ifTrue:[self basicAt: index put: (value basicAt: 1) << 32 + (value basicAt: 2)]
+ 		ifFalse:[self at: index put: value asFloat].
+ 	^value!

Item was added:
+ ----- Method: Float64Array>>copyFromFloatArray: (in category 'initialize-release') -----
+ copyFromFloatArray: aFloatArray
+ 	"Destructively replace the elements of self with those of aFloatArray"
+ 	<primitive: 'primitiveFromFloatArray' module: 'Float64ArrayPlugin'>
+ 	self isOfSameSizeCheck: aFloatArray.
+ 	1 to: self size do:[:i| self at: i put: (aFloatArray at: i)].!

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

Item was added:
+ ----- Method: Float64Array>>dot: (in category 'arithmetic') -----
+ dot: aFloatVector
+ 	"Primitive. Return the dot product of the receiver and the argument.
+ 	Fail if the argument is not of the same size as the receiver."
+ 
+ 	| result |
+ 	<primitive: 'primitiveDotProduct' module: 'Float64ArrayPlugin'>
+ 	self size = aFloatVector size ifFalse:[^self error:'Must be equal size'].
+ 	result := 0.0.
+ 	1 to: self size do:[:i|
+ 		result := result + ((self at: i) * (aFloatVector at: i)).
+ 	].
+ 	^result!

Item was added:
+ ----- Method: Float64Array>>hash (in category 'comparing') -----
+ hash
+ 	| result |
+ 	<primitive:'primitiveHashArray' module: 'Float64ArrayPlugin'>
+ 	result := 0.
+ 	1 to: self size do:[:i| result := result + (self basicAt: i) ].
+ 	^result bitAnd: 16r1FFFFFFF!

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

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

Item was added:
+ ----- Method: Float64Array>>normalize (in category 'arithmetic') -----
+ normalize
+ 	"Unsafely normalize the receiver in-place (become a unit vector).
+  	 Div-by-Zero raised if len 0."
+ 	<primitive: 'primitiveNormalize' module: 'Float64ArrayPlugin'>
+ 	self /= self length.!

Item was added:
+ ----- Method: Float64Array>>primAddArray: (in category 'primitives-plugin') -----
+ primAddArray: floatArray
+ 
+ 	<primitive: 'primitiveAddFloat64Array' module: 'Float64ArrayPlugin'>
+ 	self isOfSameSizeCheck: floatArray.
+ 	1 to: self size do:[:i| self at: i put: (self at: i) + (floatArray at: i)].!

Item was added:
+ ----- Method: Float64Array>>primAddScalar: (in category 'primitives-plugin') -----
+ primAddScalar: scalarValue
+ 
+ 	<primitive: 'primitiveAddScalar' module: 'Float64ArrayPlugin'>
+ 	1 to: self size do:[:i| self at: i put: (self at: i) + scalarValue].!

Item was added:
+ ----- Method: Float64Array>>primDivArray: (in category 'primitives-plugin') -----
+ primDivArray: floatArray
+ 
+ 	<primitive: 'primitiveDivFloat64Array' module: 'Float64ArrayPlugin'>
+ 	self isOfSameSizeCheck: floatArray.
+ 	1 to: self size do:[:i| self at: i put: (self at: i) / (floatArray at: i)].!

Item was added:
+ ----- Method: Float64Array>>primDivScalar: (in category 'primitives-plugin') -----
+ primDivScalar: scalarValue
+ 
+ 	<primitive: 'primitiveDivScalar' module: 'Float64ArrayPlugin'>
+ 	1 to: self size do:[:i| self at: i put: (self at: i) / scalarValue].!

Item was added:
+ ----- Method: Float64Array>>primMulArray: (in category 'primitives-plugin') -----
+ primMulArray: floatArray
+ 
+ 	<primitive: 'primitiveMulFloat64Array' module: 'Float64ArrayPlugin'>
+ 	self isOfSameSizeCheck: floatArray.
+ 	1 to: self size do:[:i| self at: i put: (self at: i) * (floatArray at: i)].!

Item was added:
+ ----- Method: Float64Array>>primMulScalar: (in category 'primitives-plugin') -----
+ primMulScalar: scalarValue
+ 
+ 	<primitive: 'primitiveMulScalar' module: 'Float64ArrayPlugin'>
+ 	1 to: self size do:[:i| self at: i put: (self at: i) * scalarValue].!

Item was added:
+ ----- Method: Float64Array>>primSubArray: (in category 'primitives-plugin') -----
+ primSubArray: floatArray
+ 
+ 	<primitive: 'primitiveSubFloat64Array' module: 'Float64ArrayPlugin'>
+ 	self isOfSameSizeCheck: floatArray.
+ 	1 to: self size do:[:i| self at: i put: (self at: i) - (floatArray at: i)].!

Item was added:
+ ----- Method: Float64Array>>primSubScalar: (in category 'primitives-plugin') -----
+ primSubScalar: scalarValue
+ 
+ 	<primitive: 'primitiveSubScalar' module: 'Float64ArrayPlugin'>
+ 	1 to: self size do:[:i| self at: i put: (self at: i) - scalarValue].!

Item was added:
+ ----- 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 added:
+ ----- Method: Float64Array>>squaredLength (in category 'accessing') -----
+ squaredLength
+ 	"Return the squared length of the receiver"
+ 	^self dot: self!

Item was added:
+ ----- Method: Float64Array>>sum (in category 'primitives-plugin') -----
+ sum
+ 
+ 	<primitive: 'primitiveSum' module: 'Float64ArrayPlugin'>
+ 	^ super sum!

Item was added:
+ ----- Method: FloatArray class>>fromFloat64Array: (in category 'instance creation') -----
+ fromFloat64Array: aFloat64Array
+ 	^(self new: aFloat64Array) copyFromFloat64Array: aFloat64Array!

Item was added:
+ ----- Method: FloatArray>>asFloat64Array (in category 'converting') -----
+ asFloat64Array
+ 	^Float64Array fromFloatArray: self!

Item was added:
+ ----- Method: FloatArray>>copyFromFloat64Array: (in category 'initialize-release') -----
+ copyFromFloat64Array: aFloat64Array
+ 	"Destructively replace the elements of self with those of aFloat64Array"
+ 	<primitive: 'primitiveFromFloat64Array' module: 'Float64ArrayPlugin'>
+ 	self isOfSameSizeCheck: aFloat64Array.
+ 	1 to: self size do:[:i| self at: i put: (aFloat64Array at: i)].!

Item was added:
+ ----- Method: Matrix>>asFloat64Array (in category 'converting') -----
+ asFloat64Array
+ 	^contents asFloat64Array!

Item was added:
+ ----- Method: SequenceableCollection>>asFloatA64rray (in category 'converting') -----
+ asFloatA64rray
+ 	"Answer a Float64Array whose elements are the elements of the receiver, in 
+ 	the same order."
+ 
+ 	| floatArray |
+ 	floatArray := Float64Array new: self size.
+ 	1 to: self size do:[:i| floatArray at: i put: (self at: i) asFloat ].
+ 	^floatArray!



More information about the Squeak-dev mailing list