Using reSort on SortedCollections?

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

Using reSort on SortedCollections?

Christopher J. Demers
What is a good way to have a SortedCollection update the position of a
single item if it is edited such that an aspect relevant to the sort order
changes?

For example say I have a SortedCollection of Recipe objects sorted by their
time stamp.  Now lets say that I edit one, and its time stamp changes.
Obviously the sorted collection does not know anything has changed.  What I
did in the past was to send the reSort message.  However that is a private
message (I wonder if it should be), and I wonder if there is a more elegant
approach (or if there is not, then if there should be one)?  Fundamentally
it is a remove followed by an add, or it could be a more low-level swap.

This seems like a common enough thing that there should be a good way to do
it.  Any thoughts?

Chris


Reply | Threaded
Open this post in threaded view
|

Re: Using reSort on SortedCollections?

Blair McGlashan
"Christopher J. Demers" <[hidden email]> wrote in
message news:atos3i$18ac5$[hidden email]...
> What is a good way to have a SortedCollection update the position of a
> single item if it is edited such that an aspect relevant to the sort order
> changes?
>
> For example say I have a SortedCollection of Recipe objects sorted by
their
> time stamp.  Now lets say that I edit one, and its time stamp changes.
> Obviously the sorted collection does not know anything has changed.  What
I
> did in the past was to send the reSort message.  However that is a private
> message (I wonder if it should be), and I wonder if there is a more
elegant
> approach (or if there is not, then if there should be one)?  Fundamentally
> it is a remove followed by an add, or it could be a more low-level swap.
>
> This seems like a common enough thing that there should be a good way to
do
> it.  Any thoughts?

#reSort has been made public by the patch for #1093:  "SortedCollection's
are resorted on load from STB, providing a window of opportunity to run
malicious code even when just loading data."
 Also enhancement #266: "Improve worst case quick sort performance
(collection already sorted with many equal elements", means that #reSort on
a collection that is already mostly sorted should now be very fast.

Regards

Blair

--------------------------
"#266"!
!SortedCollection methodsFor!

quicksortFrom: start to: stop
 "Private - Sort elements start through stop of self to be non-descending
according to sortBlock.
 Note that this is not a stable sort, so any current ordering will be lost."

 "Implementation Note: This is a part iterative, part recursive, Quicksort
implementation
 based on that from 'Numerical Recipes in C', Press, Teukolsky, et al.. It
is marginally faster
 (about 5-15%) on average than the traditional Smalltalk-80 sort, which also
seems to be
 some kind of modified quicksort, and about twice as fast in some cases. In
particular it
 exhibits better performance when used in conjunction with a #<= comparison,
e.g. the
 default sort block, especially when the collection is already sorted."

 | up lo |
 up := stop.
 lo := start.
 [up - lo > 5] whileTrue:
   ["Choose median and arrange so [lo+1] <= [lo] <= [up]"

   | i j k m temp a |
   k := lo + up bitShift: -1.
   m := lo + 1.
   temp := self basicAt: k.
   self basicAt: k put: (self basicAt: m).
   self basicAt: m put: temp.
   (sortBlock value: (self basicAt: up) value: temp)
    ifTrue:
     [self basicAt: m put: (self basicAt: up).
     self basicAt: up put: temp].
   (sortBlock value: (self basicAt: up) value: (self basicAt: lo))
    ifTrue:
     [temp := self basicAt: up.
     self basicAt: up put: (self basicAt: lo).
     self basicAt: lo put: temp].
   (sortBlock value: (self basicAt: lo) value: (self basicAt: m))
    ifTrue:
     [temp := self basicAt: lo.
     self basicAt: lo put: (self basicAt: m).
     self basicAt: m put: temp].

   "Partition...(note we must test that i and j remain in bounds because the
sort block may use <= or >=."
   i := m. "i.e. start from lo+2"
   j := up. "i.e. start from up-1"
   a := self basicAt: lo.

   [[i < j and: [sortBlock value: (self basicAt: (i := i + 1)) value: a]]
whileTrue.
   [j >= i and: [sortBlock value: a value: (self basicAt: (j := j - 1))]]
whileTrue.
   j < i]
     whileFalse:
      [temp := self basicAt: i.
      self basicAt: i put: (self basicAt: j).
      self basicAt: j put: temp].

   "Insert partitioning element"
   self basicAt: lo put: (self basicAt: j).
   self basicAt: j put: a.

   "Skip sort-equal elements to speed up worst cases - suggested by John
Brant"
   [(j := j - 1) > lo and: [sortBlock value: a value: (self basicAt: j)]]
whileTrue.

   "Recursively sort smaller sub-interval and process larger remainder on
the next loop iteration"
   up - i < (j - lo)
    ifTrue:
     [self quicksortFrom: i to: up.
     up := j]
    ifFalse:
     [self quicksortFrom: lo to: j.
     lo := i]].

 "When interval size drops below threshold perform an insertion sort
(quicker for small numbers of elements)"
 ^self insertsortFrom: lo to: up! !
!SortedCollection categoriesFor: #quicksortFrom:to:!algorithms!private! !

"#1093"!

!STBSortedCollectionProxy methodsFor!

value
 "Answer a new SortedCollection with elements, array, and sort block,
sortBlock."

 "Implementation Note: The collection is assumed to be sorted in the correct
order, so the sort block
 is not evaluated at all. This modification for 5.02 makes it safe to at
least load an STB file containing a
 SortedCollection. Previously if the sortBlock contained malicious code,
then that code would be run
 purely as a result of realizing the content of the STB. This does mean that
potentially a SortedCollection
 may not be correctly sorted if the sort criteria differ for some reason
between the source image and
 the destination image. Where this is possible the application must
explicitly #reSort the collection."

 ^(class new: array size)
  sortBlock: sortBlock;
  addAllWithoutSorting: array;
  yourself! !
!STBSortedCollectionProxy categoriesFor: #value!converting!public! !

!SortedCollection methodsFor!

addAllWithoutSorting: aCollection
 "Append the elements of the <collection> argument to the receiver
 without doing any sorting. Answer aCollection."

 self makeRoomAtEndFor: aCollection size.
 aCollection do:
   [:each |
   lastIndex := lastIndex + 1.
   self basicAt: lastIndex put: each].
 ^aCollection!

addAll: aCollection
 "Include all the elements of the <collection> argument as elements of the
receiver.
 Answer aCollection."

 aCollection size > (self size // 3)
  ifTrue:
   [self addAllWithoutSorting: aCollection.
   self reSort]
  ifFalse: [aCollection do: [:each | self add: each]].
 ^aCollection! !
!SortedCollection categoriesFor: #addAllWithoutSorting:!adding!public! !
!SortedCollection categoriesFor: #addAll:!adding!public! !
!SortedCollection categoriesFor: #reSort!operations!public! !