The Trunk: Collections-ul.748.mcz

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

The Trunk: Collections-ul.748.mcz

commits-2
Levente Uzonyi uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-ul.748.mcz

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

Name: Collections-ul.748
Author: ul
Time: 23 April 2017, 6:01:07.769449 pm
UUID: 834a2107-7087-42e3-a165-edc40a9f65f7
Ancestors: Collections-pre.747, Collections-ul.743

- merged with Collections-ul.743
- ArrayedCollection >> #mergeSortFrom:to:by: signals errors instead of assertion failures and uses #shallowCopy instead of #clone
- optimized Heap >> #removeFirst and SequenceCollection >> #beginsWith:

=============== Diff against Collections-pre.747 ===============

Item was changed:
  ----- Method: ArrayedCollection>>mergeSortFrom:to:by: (in category 'sorting') -----
  mergeSortFrom: startIndex to: stopIndex by: aBlock
  "Sort the given range of indices using the mergesort algorithm.
  Mergesort is a worst-case O(N log N) sorting algorithm that usually
  does only half as many comparisons as heapsort or quicksort."
 
  "Details: recursively split the range to be sorted into two halves,
  mergesort each half, then merge the two halves together. An extra
  copy of the data is used as temporary storage and successive merge
  phases copy data back and forth between the receiver and this copy.
  The recursion is set up so that the final merge is performed into the
  receiver, resulting in the receiver being completely sorted."
 
+ | size |
+ (size := self size) <= 1 ifTrue: [^ self].  "nothing to do"
- self size <= 1 ifTrue: [^ self].  "nothing to do"
  startIndex = stopIndex ifTrue: [^ self].
+ 1 <= startIndex ifFalse: [ self errorSubscriptBounds: startIndex ].
+ stopIndex <= size ifFalse: [ self errorSubscriptBounds: stopIndex ].
+ startIndex < stopIndex ifFalse: [ self errorSubscriptBounds: startIndex ].
- self assert: [startIndex >= 1 and: [startIndex < stopIndex]]. "bad start index"
- self assert: [stopIndex <= self size]. "bad stop index"
  self
  mergeSortFrom: startIndex
  to: stopIndex
+ src: self shallowCopy
- src: self clone
  dst: self
  by: aBlock!

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 changed:
  ----- Method: Heap>>removeFirst (in category 'removing') -----
  removeFirst
+ "Remove the root element and make sure the sorting order is okay. Optimized version for the most common use case."
+
+ | removed |
+ tally = 0 ifTrue: [ self errorSubscriptBounds: 1 ].
+ removed := array at: 1.
+ array
+ at: 1 put: (array at: tally);
+ at: tally put: nil.
+ (tally := tally - 1) > 1 ifTrue: [
+ "Root node has at least one child."
+ self downHeapSingle: 1 ].
+ ^removed!
- "Remove the first element from the receiver"
- ^self removeAt: 1!

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 changed:
  ----- Method: SequenceableCollection>>beginsWith: (in category 'testing') -----
  beginsWith: sequence
  "Answer true if the receiver starts with the argument collection."
 
  | sequenceSize |
+ ((sequenceSize := sequence size) = 0 or: [ self size < sequenceSize ]) ifTrue: [ ^false ].
- ((sequenceSize := sequence size) = 0 or: [ self size < sequence size ]) ifTrue: [ ^false ].
  1 to: sequenceSize do: [ :index |
  (sequence at: index) = (self at: index) ifFalse: [ ^false ] ].
  ^true!

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!


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-ul.748.mcz

Tobias Pape

> On 23.04.2017, at 20:20, [hidden email] wrote:
>
> uses #shallowCopy instead of #clone

just curious, why?


Reply | Threaded
Open this post in threaded view
|

#clone and #shallowCopy (was: Re: The Trunk: Collections-ul.748.mcz)

Levente Uzonyi
On Sun, 23 Apr 2017, Tobias Pape wrote:

>
>> On 23.04.2017, at 20:20, [hidden email] wrote:
>>
>> uses #shallowCopy instead of #clone
>
> just curious, why?

Both methods are intended to do the same thing. IIRC #shallowCopy is the
cross-dialect method for this purpose, while #clone came with Morphic from
Self.

They both use primitive 148 to copy the object.

Object >> #clone used to raise an error when the primitive failed, but
that might have just been oversight. Now both methods try to fall back to
#basicNew(:) and manually copy the fields, which is what #shallowCopy has
always been doing.

However, #clone's fallback code now differs from #shallowCopy's, the
latter having the newer timestamp, but the former seems to be simpler,
because it relies on #copyFrom:.
I can't really tell which fallback code is better, so I'll leave that to
someone more knowledgeable.

So I suggest we
- update #shallowCopy if needed to have the best fallback code
- rewrite senders of #clone from the Trunk to use #shallowCopy
- deprecate Object >> #clone and make it be a send of #shallowCopy
- remove other implementors of #clone

Levente

P.S.: this was done long ago in Pharo

Reply | Threaded
Open this post in threaded view
|

Re: #clone and #shallowCopy (was: Re: The Trunk: Collections-ul.748.mcz)

Tobias Pape

> On 23.04.2017, at 20:57, Levente Uzonyi <[hidden email]> wrote:
>
> On Sun, 23 Apr 2017, Tobias Pape wrote:
>
>>
>>> On 23.04.2017, at 20:20, [hidden email] wrote:
>>> uses #shallowCopy instead of #clone
>>
>> just curious, why?
>
> Both methods are intended to do the same thing. IIRC #shallowCopy is the cross-dialect method for this purpose, while #clone came with Morphic from Self.
>
> They both use primitive 148 to copy the object.
>
> Object >> #clone used to raise an error when the primitive failed, but that might have just been oversight. Now both methods try to fall back to #basicNew(:) and manually copy the fields, which is what #shallowCopy has always been doing.
>
> However, #clone's fallback code now differs from #shallowCopy's, the latter having the newer timestamp, but the former seems to be simpler, because it relies on #copyFrom:.
> I can't really tell which fallback code is better, so I'll leave that to someone more knowledgeable.
>
> So I suggest we
> - update #shallowCopy if needed to have the best fallback code
> - rewrite senders of #clone from the Trunk to use #shallowCopy
> - deprecate Object >> #clone and make it be a send of #shallowCopy
> - remove other implementors of #clone

'k :)
Thanks
        -Tobias

>
> Levente
>
> P.S.: this was done long ago in Pharo
>