[squeak-dev] The Inbox: Collections-ul.743.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Mar 26 20:29:06 UTC 2017


Levente Uzonyi uploaded a new version of Collections to project The Inbox:
http://source.squeak.org/inbox/Collections-ul.743.mcz

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

Name: Collections-ul.743
Author: ul
Time: 26 March 2017, 10:10:37.350006 pm
UUID: 854bfcea-dba7-48c9-ba6c-9de1f457b743
Ancestors: Collections-ul.742

- OrderedCollection >> #collect: & friends return an OrderedCollection. This affects its subclasses. It fixes WeakOrderedCollection (collected objects won't vanish), FloatCollection (there'll be no errors if the collected value is not a Float) and SortedCollection (#collect: was implemented like this, but other methods were not)). Other subclasses may have to be fixed/removed.
- Introduced NonPointersOrderedCollection, a common superclass for classes like FloatCollection. This fixes removal from FloatCollection, and makes it easy to create similar specialized ordered collections.

=============== Diff against Collections-ul.742 ===============

Item was changed:
+ NonPointersOrderedCollection subclass: #FloatCollection
- OrderedCollection subclass: #FloatCollection
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Collections-Sequenceable'!
  
  !FloatCollection commentStamp: 'cmm 1/28/2013 19:49' prior: 0!
  FloatCollctions store 32bit IEEE floating point numbers.!

Item was changed:
+ ----- Method: FloatCollection class>>arrayType (in category 'private') -----
- ----- Method: FloatCollection class>>arrayType (in category 'overriding') -----
  arrayType
  	^ FloatArray!

Item was removed:
- ----- Method: FloatCollection>>addLast: (in category 'adding') -----
- addLast: aFloat
- 	aFloat isNumber ifFalse: [ self error: 'This collection can only store Floats.' ].
- 	^ super addLast: aFloat!

Item was changed:
+ ----- Method: FloatCollection>>asFloatArray (in category 'converting') -----
- ----- Method: FloatCollection>>asFloatArray (in category 'adding') -----
  asFloatArray
  	"Optimized version"
  
  	^array copyFrom: firstIndex to: lastIndex!

Item was added:
+ OrderedCollection subclass: #NonPointersOrderedCollection
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Collections-Sequenceable'!
+ 
+ !NonPointersOrderedCollection commentStamp: 'ul 3/26/2017 21:38' prior: 0!
+ I am an OrderedCollection with an internal array holding non-pointers objects. This has the advantage that the array is never subject of garbage collection. But I can only hold objects of a given type defined by my class-side #arrayType method, which is the only method they have to implement.!

Item was added:
+ ----- Method: NonPointersOrderedCollection class>>arrayType (in category 'private') -----
+ arrayType
+ 	"This method must return a non-pointers array class."
+ 
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: NonPointersOrderedCollection>>makeRoomAtFirst (in category 'private') -----
+ makeRoomAtFirst
+ 	"Same as super without trying to store nil in the emptied slots of array."
+ 	
+ 	| tally newFirstIndex newLastIndex capacity |
+ 	tally := self size.
+ 	capacity := array size.
+ 	tally * 2 >= capacity ifTrue: [ ^self growAtFirst ].
+ 	tally = 0 ifTrue: [ ^self resetTo: capacity + 1 ].
+ 	newFirstIndex := capacity // 2 + 1.
+ 	newLastIndex := newFirstIndex - firstIndex + lastIndex.
+ 	0 to: tally - 1 do: [ :offset |
+ 		array at: newLastIndex - offset put: (array at: lastIndex - offset) ].
+ 	firstIndex := newFirstIndex.
+ 	lastIndex := newLastIndex!

Item was added:
+ ----- Method: NonPointersOrderedCollection>>makeRoomAtLast (in category 'private') -----
+ makeRoomAtLast
+ 	"Same as super without trying to store nil in the emptied slots of array."
+ 	
+ 	| tally newFirstIndex newLastIndex |
+ 	tally := self size.
+ 	tally * 2 >= lastIndex ifTrue: [ ^self growAtLast ].
+ 	tally = 0 ifTrue: [ ^self resetTo: 1 ].
+ 	newLastIndex := lastIndex // 2.
+ 	newFirstIndex := newLastIndex - lastIndex + firstIndex.
+ 	array 
+ 		replaceFrom: newFirstIndex
+ 		to: newLastIndex
+ 		with: array
+ 		startingAt: firstIndex.
+ 	firstIndex := newFirstIndex.
+ 	lastIndex := newLastIndex!

Item was added:
+ ----- Method: NonPointersOrderedCollection>>removeAllSuchThat: (in category 'removing') -----
+ removeAllSuchThat: aBlock 
+ 	"Same as super without trying to store nil in the emptied slots of array."
+ 
+ 	| n |
+ 	n := firstIndex.
+ 	firstIndex to: lastIndex do: [ :index |
+ 		| element |
+ 		(aBlock value: (element := array at: index)) ifFalse: [
+ 			array at: n put: element.
+ 			n := n + 1 ] ].
+ 	lastIndex := n - 1!

Item was added:
+ ----- Method: NonPointersOrderedCollection>>removeFirst (in category 'removing') -----
+ removeFirst
+ 	"Same as super without trying to store nil in the emptied slot of array."
+ 
+ 	| firstObject |
+ 	firstIndex > lastIndex ifTrue: [ self errorEmptyCollection ].
+ 	firstObject := array at: firstIndex.
+ 	firstIndex := firstIndex + 1.
+ 	^firstObject!

Item was added:
+ ----- Method: NonPointersOrderedCollection>>removeFirst: (in category 'removing') -----
+ removeFirst: n 
+ 	"Same as super without trying to store nil in the emptied slots of array."
+ 
+ 	| lastIndexToRemove result |
+ 	n < 1 ifTrue: [ self errorNoSuchElement ].
+ 	lastIndex < (lastIndexToRemove := firstIndex + n - 1) ifTrue: [ self errorNotEnoughElements ].
+ 	result := array copyFrom: firstIndex to: lastIndexToRemove.
+ 	firstIndex := lastIndexToRemove + 1.
+ 	^result!

Item was added:
+ ----- Method: NonPointersOrderedCollection>>removeIndex: (in category 'private') -----
+ removeIndex: removedIndex
+  	"Same as super without trying to store nil in the emptied slot of array."
+ 
+ 	array 
+ 		replaceFrom: removedIndex 
+ 		to: lastIndex - 1 
+ 		with: array 
+ 		startingAt: removedIndex + 1.
+ 	lastIndex := lastIndex - 1.!

Item was added:
+ ----- Method: NonPointersOrderedCollection>>removeLast (in category 'removing') -----
+ removeLast
+ 	"Same as super without trying to store nil in the emptied slot of array."
+ 	
+ 	| lastObject |
+ 	firstIndex > lastIndex ifTrue: [ self errorEmptyCollection ].
+ 	lastObject := array at: lastIndex.
+ 	lastIndex := lastIndex - 1.
+ 	^ lastObject!

Item was added:
+ ----- Method: NonPointersOrderedCollection>>removeLast: (in category 'removing') -----
+ removeLast: n
+ 	"Same as super without trying to store nil in the emptied slots of array."
+ 
+ 	| firstIndexToRemove result |
+ 	n < 1 ifTrue: [ self errorNoSuchElement ].
+ 	(firstIndexToRemove := lastIndex - n + 1) < firstIndex ifTrue: [ self errorNotEnoughElements ].
+ 	result := array copyFrom: firstIndexToRemove to: lastIndex.
+ 	lastIndex := firstIndexToRemove - 1.
+ 	^result!

Item was changed:
  ----- Method: OrderedCollection>>collect: (in category 'enumerating') -----
  collect: aBlock 
+ 	"Evaluate aBlock with each of my elements as the argument.
+ 	Collect the resulting values into an OrderedCollection."
- 	"Evaluate aBlock with each of my elements as the argument. Collect the 
- 	resulting values into a collection that is like me. Answer the new 
- 	collection. Override superclass in order to use addLast:, not at:put:."
  
  	| newCollection |
+ 	newCollection := OrderedCollection new: self size.
- 	newCollection := self species new: self size.
  	firstIndex to: lastIndex do:
  		[:index |
  		newCollection addLast: (aBlock value: (array at: index))].
  	^ newCollection!

Item was changed:
  ----- Method: OrderedCollection>>collect:from:to: (in category 'enumerating') -----
  collect: aBlock from: fromIndex to: toIndex
+ 	"Evaluate aBlock with each of my elements as the argument between fromIndex and toIndex.
+ 	Collect the resulting values into an OrderedCollection."
+ 
+ 	| result offset |
+ 	offset := firstIndex - 1.
+ 	(fromIndex < 1 or:[toIndex + offset > lastIndex])
- 	"Override superclass in order to use addLast:, not at:put:."
- 	| result |
- 	(fromIndex < 1 or:[toIndex + firstIndex - 1 > lastIndex])
  		ifTrue: [^self errorNoSuchElement].
+ 	result := OrderedCollection new: toIndex - fromIndex + 1.
+ 	fromIndex + offset to: toIndex + offset do:
- 	result := self species new: toIndex - fromIndex + 1.
- 	firstIndex + fromIndex - 1 to: firstIndex + toIndex - 1 do:
  		[:index | result addLast: (aBlock value: (array at: index))].
  	^ result
  !

Item was changed:
  ----- Method: OrderedCollection>>with:collect: (in category 'enumerating') -----
  with: otherCollection collect: twoArgBlock 
  	"Collect and return the result of evaluating twoArgBlock with 
  	corresponding elements from this collection and otherCollection."
  
  	| result offset size |
  	(size := self size) = otherCollection size ifFalse: [ self error: 'otherCollection must be the same size' ].
+ 	result := OrderedCollection new: size.
- 	result := self species new: size.
  	offset := 1 - firstIndex.
  	firstIndex to: lastIndex do: [ :index |
  		result addLast: (
  			twoArgBlock 
  				value: (array at: index)
  				value: (otherCollection at: index + offset)) ].
  	^result!

Item was changed:
  ----- Method: OrderedCollection>>withIndexCollect: (in category 'enumerating') -----
  withIndexCollect: elementAndIndexBlock 
  	"Just like with:collect: except that the iteration index supplies the second argument to the block. Override superclass in order to use addLast:, not at:put:."
  
  	| newCollection offset |
+ 	newCollection := OrderedCollection new: self size.
- 	newCollection := self species new: self size.
  	offset := 1 - firstIndex.
  	firstIndex to: lastIndex do:
  		[:index |
  		newCollection addLast: (elementAndIndexBlock
  			value: (array at: index)
  			value: index + offset) ].
  	^ newCollection!

Item was removed:
- ----- Method: SortedCollection>>collect: (in category 'enumerating') -----
- collect: aBlock 
- 	"Evaluate aBlock with each of my elements as the argument. Collect the 
- 	resulting values into an OrderedCollection. Answer the new collection. 
- 	Override the superclass in order to produce an OrderedCollection instead
- 	of a SortedCollection."
- 
- 	| newCollection | 
- 	newCollection := OrderedCollection new: self size.
- 	self do: [:each | newCollection addLast: (aBlock value: each)].
- 	^ newCollection!

Item was changed:
+ ----- Method: WeakOrderedCollection class>>arrayType (in category 'private') -----
- ----- Method: WeakOrderedCollection class>>arrayType (in category 'as yet unclassified') -----
  arrayType
  	^ WeakArray!



More information about the Squeak-dev mailing list