SequenceableCollection.st
changeset 1 a27a279701f8
child 2 6526dde5f3ac
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/SequenceableCollection.st	Fri Jul 16 11:39:45 1993 +0200
@@ -0,0 +1,955 @@
+"
+ COPYRIGHT (c) 1989-93 by Claus Gittinger
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+Collection subclass:#SequenceableCollection
+       instanceVariableNames:''
+       classVariableNames:''
+       poolDictionaries:''
+       category:'Collections-Abstract'
+!
+
+SequenceableCollection comment:'
+
+COPYRIGHT (c) 1989-93 by Claus Gittinger
+              All Rights Reserved
+
+SequenceableCollections have ordered elements which can be accessed via
+an index. SequenceableCollection is an abstract class - there are no
+instances of it in the system.
+
+%W% %E%
+
+written spring 89 by claus
+'!
+
+!SequenceableCollection class methodsFor:'instance creation'!
+
+new:size withAll:element
+    "return a new Collection of size, where all elements are
+     initialized to element"
+
+    |newCollection|
+
+    newCollection := self new:size.
+    newCollection atAllPut:element.
+    ^ newCollection
+! !
+
+!SequenceableCollection methodsFor:'accessing'!
+
+first
+    "return the first element"
+
+    ^ self at:1
+!
+
+last
+    "return the last element"
+
+    ^ self at:(self size)
+! !
+
+!SequenceableCollection methodsFor:'comparing'!
+
+= aCollection
+    "return true if the receiver and aCollection represent collections
+     with equal contents."
+
+    |index "{ Class: SmallInteger }"
+     stop  "{ Class: SmallInteger }" |
+
+    (aCollection == self) ifTrue:[^true].
+    (aCollection isKindOf:SequenceableCollection) ifFalse:[^false].
+
+    stop := self size.
+    stop == (aCollection size) ifFalse:[^false].
+    index := 1.
+    [index <= stop] whileTrue:[
+        (self at:index) = (aCollection at:index) ifFalse:[^false].
+        index := index + 1
+    ].
+    ^ true
+!
+
+startsWith:aCollection
+    "return true, if the receivers first elements match those
+     of aCollection"
+
+    |index "{ Class: SmallInteger }"
+     stop  "{ Class: SmallInteger }" |
+
+    (aCollection == self) ifTrue:[^true].
+    (aCollection isKindOf:SequenceableCollection) ifFalse:[^false].
+
+    stop := aCollection size.
+    stop > self size ifTrue:[^false].
+
+    index := 1.
+    [index <= stop] whileTrue:[
+        (self at:index) = (aCollection at:index) ifFalse:[^false].
+        index := index + 1
+    ].
+    ^ true
+
+    "'abcde' startsWith:#($a $b $c)"
+    "#[1 2 3 4] startsWith:#(1 2 3)"
+    "#(1 2 3 4) asOrderedCollection startsWith:#(1 2 3)"
+!
+
+endsWith:aCollection
+    "return true, if the receivers last elements match those
+     of aCollection"
+
+    |index1 "{ Class: SmallInteger }"
+     index2 "{ Class: SmallInteger }" 
+     stop   "{ Class: SmallInteger }" |
+
+    (aCollection == self) ifTrue:[^true].
+    (aCollection isKindOf:SequenceableCollection) ifFalse:[^false].
+
+    stop := aCollection size.
+    stop > self size ifTrue:[^false].
+
+    index1 := self size.
+    index2 := aCollection size.
+    [index2 > 0] whileTrue:[
+        (self at:index1) = (aCollection at:index2) ifFalse:[^false].
+        index1 := index1 - 1.
+        index2 := index2 - 1
+    ].
+    ^ true
+
+    "'abcde' endsWith:#($d $e)"
+    "#[1 2 3 4] endsWith:#(3 4)"
+    "#(1 2 3 4) asOrderedCollection endsWith:#(3 4)"
+! !
+
+!SequenceableCollection methodsFor:'testing'!
+
+size
+    "return the number of elements in the collection.
+     concrete implementations must define this"
+
+    ^ self subclassResponsibility
+! !
+
+!SequenceableCollection methodsFor:'copying'!
+
+, aCollection
+    "return a new collection formed from concatenating the receiver with
+     the argument"
+
+    |newCollection 
+     mySize    "{ Class: SmallInteger }"
+     newSize   "{ Class: SmallInteger }"
+     otherSize "{ Class: SmallInteger }"
+     dstIndex  "{ Class: SmallInteger }"|
+
+    mySize := self size.
+    otherSize := aCollection size.
+    newSize := mySize + otherSize.
+    newCollection := self species new:newSize.
+
+    newCollection replaceFrom:1 to:mySize with:self startingAt:1.
+    dstIndex := mySize + 1.
+    (aCollection isKindOf:SequenceableCollection) ifTrue:[
+        "yes, aCollection has indexed elements"
+        newCollection replaceFrom:dstIndex to:newSize
+                             with:aCollection startingAt:1.
+        ^ newCollection
+    ] ifFalse:[
+        "no, enumerate aCollection"
+        aCollection do:[:element |
+            newCollection at:dstIndex put:element.
+            dstIndex := dstIndex + 1
+        ]
+    ].
+    ^ newCollection
+!
+
+copyWith:newElement
+    "return a new collection consisting of receivers elements
+     plus the argument"
+
+    |newCollection mySize newSize|
+
+    mySize := self size.
+    newSize := mySize + 1.
+    newCollection := self species new:newSize.
+    newCollection replaceFrom:1 to:mySize with:self startingAt:1.
+    newCollection at:newSize put:newElement.
+    ^newCollection
+!
+
+copyWithout:anElement
+    "return a new collection consisting of receivers elements
+     without anElement (if it was present)"
+
+    |newCollection skipIndex 
+     dstIndex "{ Class: SmallInteger }"
+     index    "{ Class: SmallInteger }"
+     stop     "{ Class: SmallInteger }" |
+
+    skipIndex := self indexOf:anElement startingAt:1.
+    (skipIndex == 0) ifTrue:[^ self copy].
+    stop := self size.
+    newCollection := self class new:(stop - 1).
+    dstIndex := 1.
+    index := 1.
+    [index <= stop] whileTrue:[
+        (index ~~ skipIndex) ifTrue:[
+            newCollection at:dstIndex put:(self at:index).
+            dstIndex := dstIndex + 1
+        ].
+        index := index + 1
+    ].
+    ^ newCollection
+!
+
+copyFrom:start to:stop
+    "return a new collection consisting of receivers elements
+     between start and stop"
+
+    |newCollection newSize|
+
+    newSize := stop - start + 1.
+    newCollection := self class new:newSize.
+    newCollection replaceFrom:1 to:newSize with:self startingAt:start.
+    ^ newCollection
+!
+
+copyFrom:start
+    "return a new collection consisting of receivers elements
+     from start to the end of the collection"
+
+    ^ self copyFrom:start to:(self size)
+!
+
+copyTo:stop
+    "return a new collection consisting of receivers elements
+     from 1 up to index stop"
+
+    ^ self copyFrom:1 to:stop
+!
+
+copyWithoutIndex:omitIndex
+    "return a new collection consisting of receivers elements
+     without the argument stored at omitIndex"
+
+    |copy|
+
+    copy := self class new:(self size - 1).
+    copy replaceFrom:1 to:(omitIndex - 1) with:self startingAt:1.
+    copy replaceFrom:omitIndex to:(copy size) 
+                with:self startingAt:(omitIndex + 1).
+    ^ copy
+! !
+
+!SequenceableCollection methodsFor:'filling and replacing'!
+
+from:index1 to:index2 put:anObject
+    "replace the elements from index1 to index2 of the collection
+     by the argument, anObject"
+
+    |index "{ Class: SmallInteger }"
+     end   "{ Class: SmallInteger }"|
+
+    index := index1.
+    end := index2.
+    [index <= end] whileTrue:[
+        self at:index put:anObject.
+        index := index + 1
+    ]
+!
+
+atAllPut:anObject
+    "replace all elements of the collection by the argument, anObject"
+
+    self from:1 to:(self size) put:anObject
+!
+
+atAll:indexCollection put:anObject
+    "put anObject into all indexes from indexCollection in the receiver"
+
+    indexCollection do:[:index | self at:index put:anObject]
+
+    "(Array new:10) atAll:(1 to:5) put:0"
+    "(Array new:10) atAll:#(1 5 6 9) put:0"
+!
+
+replaceAll:oldObject by:newObject
+    "replace all oldObjects by newObject in the receiver"
+
+    1 to:self size do:[:index |
+        (self at:index) = oldObject ifTrue:[
+            self at:index put:newObject
+        ]
+    ]
+!
+
+replaceFrom:start with:replacementCollection
+    "replace elements starting at start with elements
+     taken from replacementCollection (starting at 1)"
+
+    ^ self replaceFrom:start 
+                    to:(start + replacementCollection size - 1)
+                  with:replacementCollection
+            startingAt:1
+!
+
+replaceFrom:start to:stop with:replacementCollection
+    "replace elements between index start and stop with elements
+     taken from replacementCollection (starting at 1)"
+
+    ^ self replaceFrom:start
+                    to:stop
+                  with:replacementCollection
+            startingAt:1
+!
+
+replaceFrom:start to:stop with:replacementCollection startingAt:repStart
+    "replace elements between index start and stop with elements
+     taken from replacementCollection (starting at repStart)"
+
+    |srcIndex "{ Class: SmallInteger }"
+     dstIndex "{ Class: SmallInteger }"
+     end      "{ Class: SmallInteger }" |
+
+    (replacementCollection == self) ifTrue:[
+        (repStart < start) ifTrue:[
+            " must do reverse copy "
+            srcIndex := repStart + (stop - start).
+            dstIndex := stop.
+            end := start.
+            [dstIndex >= end] whileTrue:[
+                self at:dstIndex put:(replacementCollection at:srcIndex).
+                srcIndex := srcIndex - 1.
+                dstIndex := dstIndex - 1
+            ].
+            ^ self
+        ]
+    ].
+
+    srcIndex := repStart.
+    dstIndex := start.
+    end := stop.
+    [dstIndex <= end] whileTrue:[
+        self at:dstIndex put:(replacementCollection at:srcIndex).
+        srcIndex := srcIndex + 1.
+        dstIndex := dstIndex + 1
+    ]
+!
+
+withCRs
+    "return a new collection consisting of receivers elements
+     with all \-characters replaced by cr-characters"
+
+    |newCollection
+     size "{ Class: SmallInteger }" |
+
+    newCollection := self copy.
+    size := self size.
+    1 to:size do:[:index |
+        ((self at:index) == $\) ifTrue:[
+            newCollection at:index put:(Character cr)
+        ]
+    ].
+    ^ newCollection
+!
+
+withoutCRs
+    "return a new collection consisting of receivers elements
+     with all cr-characters replaced by \-characters"
+
+    |newCollection 
+     size "{ Class: SmallInteger }" |
+
+    newCollection := self copy.
+    size := self size.
+    1 to:size do:[:index|
+        ((self at:index) == Character cr) ifTrue:[
+            newCollection at:index put:$\
+        ]
+    ].
+    ^ newCollection
+! !
+
+!SequenceableCollection methodsFor:'adding & removing'!
+
+addFirst:anElement
+    "prepend the argument, anElement to the collection"
+
+    |newSize|
+
+    newSize := self size + 1.
+    self grow:newSize.
+    self replaceFrom:2 to:newSize with:self startingAt:1.
+    self at:1 put:anElement
+!
+
+add:anElement
+    "append the argument, anElement to the collection"
+
+    |newSize|
+
+    newSize := self size + 1.
+    self grow:newSize.
+    self at:newSize put:anElement
+!
+
+add:anElement beforeIndex:index
+    "insert the first argument, anObject into the collection before slot index"
+
+    |newSize|
+
+    newSize := self size + 1.
+    self grow:newSize.
+    self replaceFrom:index + 1 to:newSize with:self startingAt:index.
+    self at:index put:anElement
+!
+
+remove:anElement ifAbsent:aBlock
+    "search for anElement and, if present remove it; if not present
+     return the value of evaluating aBlock"
+
+    |any 
+     dstIndex "{ Class: SmallInteger }"
+     sz       "{ Class: SmallInteger }"|
+
+    dstIndex := 1.
+    any := false.
+    sz := self size.
+    1 to:sz do:[:srcIndex |
+        (anElement = (self at:srcIndex)) ifTrue:[
+            any := true
+        ] ifFalse:[
+            (dstIndex ~~ srcIndex) ifTrue:[
+                self at:dstIndex put:(self at:srcIndex)
+            ].
+            dstIndex := dstIndex + 1
+        ]
+    ].
+    any ifTrue:[
+        self grow:dstIndex - 1
+    ] ifFalse:[
+        aBlock value
+    ]
+!
+
+removeFromIndex:startIndex toIndex:endIndex
+    "remove the elements stored at indexes between startIndex and endIndex"
+
+    |newSize|
+
+    newSize := self size - endIndex + startIndex - 1.
+    self replaceFrom:startIndex to:newSize with:self startingAt:(endIndex + 1).
+    self grow:newSize
+!
+
+removeIndex:index
+    "remove the argument stored at index"
+
+    self removeFromIndex:index toIndex:index
+! !
+
+!SequenceableCollection methodsFor:'searching'!
+
+detect:aBlock ifNone:exceptionBlock
+    "find the first element, for which evaluation of the argument, aBlock
+     return true; if none does so, return the evaluation of exceptionBlock
+
+    reimplemented here for speed"
+
+    |index "{ Class: SmallInteger }"
+     stop  "{ Class: SmallInteger }"
+     element|
+
+    stop := self size.
+    index := 1.
+    [index <= stop] whileTrue:[
+        element := self at:index.
+        (aBlock value:element) ifTrue:[
+            ^ element
+        ].
+        index := index + 1
+    ].
+    ^ exceptionBlock value
+!
+
+indexOf:anElement
+    "search the collection for anElement;
+     if found, return the index otherwise return 0.
+     The comparison is done using = (i.e. equality test)."
+
+    ^ self indexOf:anElement startingAt:1
+!
+
+indexOf:anElement ifAbsent:exceptionBlock
+    "search the collection for anElement;
+     if found, return the index otherwise return the value of the
+     exceptionBlock.
+     The comparison is done using = (i.e. equality test)."
+
+    |index|
+
+    index := self indexOf:anElement startingAt:1.
+    (index == 0) ifTrue:[^ exceptionBlock value].
+    ^ index
+!
+
+indexOf:anElement startingAt:start
+    "search the collection for anElement staring search at index start;
+     if found, return the index otherwise return 0.
+     The comparison is done using = (i.e. equality test)."
+
+    |index "{ Class: SmallInteger }"
+     stop  "{ Class: SmallInteger }" |
+
+    index := start.
+    stop := self size.
+    [index <= stop] whileTrue:[
+        anElement = (self at:index) ifTrue:[^ index].
+        index := index + 1
+    ].
+    ^ 0
+!
+
+indexOf:anElement startingAt:start ifAbsent:exceptionBlock
+    "search the collection for anElement starting search at start;
+     if found, return the index otherwise return the value of the
+     exceptionBlock.
+     The comparison is done using = (i.e. equality test)."
+
+    |index|
+
+    index := self indexOf:anElement startingAt:start.
+    (index == 0) ifTrue:[^ exceptionBlock value].
+    ^ index
+!
+
+identityIndexOf:anElement
+    "search the collection for anElement using identity compare (i.e. ==);
+     if found, return the index otherwise return 0."
+
+    ^ self identityIndexOf:anElement startingAt:1
+!
+
+identityIndexOf:anElement ifAbsent:exceptionBlock
+    "search the collection for anElement using identity compare (i.e. ==);
+     if found, return the index otherwise return the value of the
+     exceptionBlock."
+
+    |index|
+
+    index := self identityIndexOf:anElement startingAt:1.
+    (index == 0) ifTrue:[^ exceptionBlock value].
+    ^ index
+!
+
+identityIndexOf:anElement startingAt:start
+    "search the collection for anElement staring search at index start
+     using identity compare  (i.e. ==);
+     if found, return the index otherwise return 0."
+
+    |index "{ Class: SmallInteger }"
+     stop  "{ Class: SmallInteger }" |
+
+    index := start.
+    stop := self size.
+    [index <= stop] whileTrue:[
+        anElement == (self at:index) ifTrue:[^ index].
+        index := index + 1
+    ].
+    ^ 0
+!
+
+identityIndexOf:anElement startingAt:start ifAbsent:exceptionBlock
+    "search the collection for anElement starting search at start;
+     if found, return the index otherwise return the value of the
+     exceptionBlock.
+     This one searches for identical objects (i.e. ==)."
+
+    |index|
+
+    index := self identityIndexOf:anElement startingAt:start.
+    (index == 0) ifTrue:[^ exceptionBlock value].
+    ^ index
+!
+
+findFirst:aBlock
+    "find the first element, for which evaluation of the argument, aBlock
+     return true; return its index or 0 if none detected."
+
+    |index "{ Class: SmallInteger }"
+     stop  "{ Class: SmallInteger }" |
+
+    stop := self size.
+    index := 1.
+    [index <= stop] whileTrue:[
+        (aBlock value:(self at:index)) ifTrue:[^ index].
+        index := index + 1
+    ].
+    ^ 0
+
+    "#(1 2 3 4 5 6) findFirst:[:x | (x > 3) and:[x even]]"
+!
+
+includes:anElement
+    "return true if the collection contains anElement; false otherwise.
+     Comparison is done using equality compare (i.e. =)."
+
+    ((self indexOf:anElement startingAt:1) == 0) ifTrue:[^ false].
+    ^ true
+! !
+
+!SequenceableCollection methodsFor:'sorting & reordering'!
+
+reverse
+    "reverse the order of the arguments inplace"
+
+    |lowIndex "{ Class: SmallInteger }"
+     hiIndex  "{ Class: SmallInteger }"
+     t|
+
+    hiIndex := self size.
+    lowIndex := 1.
+    [lowIndex < hiIndex] whileTrue:[
+        t := self at:lowIndex.
+        self at:lowIndex put:(self at:hiIndex). 
+        self at:hiIndex put:t.
+        lowIndex := lowIndex + 1.
+        hiIndex := hiIndex - 1
+    ]
+    "#(4 5 6 7 7) reverse"
+!
+
+quickSortFrom:begin to:end
+    "actual quicksort worker for sort-message"
+
+    |b "{ Class: SmallInteger }"
+     e "{ Class: SmallInteger }"
+     middleElement temp |
+
+    b := begin.
+    e := end.
+    middleElement := self at:((b + e) // 2).
+
+    [b < e] whileTrue:[
+        [b < end and:[(self at:b) < middleElement]] whileTrue:[b := b + 1].
+        [e > begin and:[middleElement < (self at:e)]] whileTrue:[e := e - 1].
+
+        (b <= e) ifTrue:[
+            (b == e) ifFalse:[
+                temp := self at:b.
+                self at:b put:(self at:e).
+                self at:e put:temp
+            ].
+            b := b + 1.
+            e := e - 1
+        ]
+    ].
+    (begin < e) ifTrue:[self quickSortFrom:begin to:e].
+    (b < end) ifTrue:[self quickSortFrom:b to:end]
+!
+
+quickSortFrom:begin to:end with:aCollection
+    "actual quicksort worker for sortWith-message"
+
+    |b "{ Class: SmallInteger }"
+     e "{ Class: SmallInteger }"
+     middleElement temp |
+
+    b := begin.
+    e := end.
+    middleElement := self at:((b + e) // 2).
+
+    [b < e] whileTrue:[
+        [b < end and:[(self at:b) < middleElement]] whileTrue:[b := b + 1].
+        [e > begin and:[middleElement < (self at:e)]] whileTrue:[e := e - 1].
+
+        (b <= e) ifTrue:[
+            (b == e) ifFalse:[
+                temp := self at:b.
+                self at:b put:(self at:e).
+                self at:e put:temp.
+                temp := aCollection at:b.
+                aCollection at:b put:(aCollection at:e).
+                aCollection at:e put:temp
+            ].
+            b := b + 1.
+            e := e - 1
+        ]
+    ].
+    (begin < e) ifTrue:[self quickSortFrom:begin to:e with:aCollection].
+    (b < end) ifTrue:[self quickSortFrom:b to:end with:aCollection]
+!
+
+quickSortFrom:begin to:end sortBlock:sortBlock
+    "actual quicksort worker for sort:-message"
+
+    |b "{ Class: SmallInteger }"
+     e "{ Class: SmallInteger }"
+     middleElement temp |
+
+    b := begin.
+    e := end.
+    middleElement := self at:((b + e) // 2).
+
+    [b < e] whileTrue:[
+        [b < end and:[sortBlock value:(self at:b) value:middleElement]] whileTrue:[b := b + 1].
+        [e > begin and:[sortBlock value:middleElement value:(self at:e)]] whileTrue:[e := e - 1].
+
+        (b <= e) ifTrue:[
+            (b == e) ifFalse:[
+                temp := self at:b.
+                self at:b put:(self at:e).
+                self at:e put:temp
+            ].
+            b := b + 1.
+            e := e - 1
+        ]
+    ].
+    (begin < e) ifTrue:[self quickSortFrom:begin to:e sortBlock:sortBlock].
+    (b < end) ifTrue:[self quickSortFrom:b to:end sortBlock:sortBlock]
+!
+
+quickSortFrom:begin to:end sortBlock:sortBlock with:aCollection
+    "actual quicksort worker for sort:with:-message"
+
+    |b "{ Class: SmallInteger }"
+     e "{ Class: SmallInteger }"
+     middleElement temp |
+
+    b := begin.
+    e := end.
+    middleElement := self at:((b + e) // 2).
+
+    [b < e] whileTrue:[
+        [b < end and:[sortBlock value:(self at:b) value:middleElement]] whileTrue:[b := b + 1].
+        [e > begin and:[sortBlock value:middleElement value:(self at:e)]] whileTrue:[e := e - 1].
+
+        (b <= e) ifTrue:[
+            (b == e) ifFalse:[
+                temp := self at:b.
+                self at:b put:(self at:e).
+                self at:e put:temp.
+                temp := aCollection at:b.
+                aCollection at:b put:(aCollection at:e).
+                aCollection at:e put:temp
+            ].
+            b := b + 1.
+            e := e - 1
+        ]
+    ].
+    (begin < e) ifTrue:[self quickSortFrom:begin to:e sortBlock:sortBlock with:aCollection].
+    (b < end) ifTrue:[self quickSortFrom:b to:end sortBlock:sortBlock with:aCollection]
+!
+
+bubbleSort
+    "sort the collection inplace using bubbleSort (sloooow)
+     - this one makes only sense to sort after inserting an element into
+       an already sorted collection (if at all)"
+
+    |index  "{ Class: SmallInteger }"
+     index2 "{ Class: SmallInteger }"
+     end    "{ Class: SmallInteger }"
+     smallest smallestIndex thisOne|
+
+    end := self size.
+    index := 1.
+    [index <= end] whileTrue:[
+        smallest := self at:index.
+        smallestIndex := index.
+        index2 := index + 1.
+        [index2 <= end] whileTrue:[
+            (self at:index2) < smallest ifTrue:[
+                smallestIndex := index2.
+                smallest := self at:index2
+            ].
+            index2 := index2 + 1
+        ].
+        (smallestIndex ~~ index) ifTrue:[
+            thisOne := self at:index.
+            self at:index put:smallest.
+            self at:smallestIndex put:thisOne
+        ].
+        index := index + 1
+    ]
+
+    "#(1 16 7 98 3 19 4 0) bubbleSort"
+!
+
+sort
+    "sort the collection inplace. The elements are compared using
+     > and < i.e. they should offer a magnitude-like protocol."
+    |sz|
+
+    sz := self size.
+    (sz > 1) ifTrue:[
+        self quickSortFrom:1 to:sz
+    ]
+
+    "#(1 16 7 98 3 19 4 0) sort"
+!
+
+sortWith:aCollection
+    "sort the receiver collection inplace, also sort aCollection with it.
+     Use, when you have a key collection to sort another collection with."
+
+    |sz|
+
+    sz := self size.
+    (sz > 1) ifTrue:[
+        self quickSortFrom:1 to:sz with:aCollection
+    ]
+
+    "|c1 c2|
+     c1 := #(1 16 7 9).
+     c2 := #('one' 'sixteen' 'seven' 'nine').
+     c1 sortWith:c2.
+     c1 printNewline.
+     c2 printNewline"
+!
+
+sort:sortBlock
+    "sort the collection inplace using the 2-arg block sortBlock
+     for comparison. This allows any sort criteria to be implemented."
+
+    |sz|
+
+    sz := self size.
+    (sz > 1) ifTrue:[
+        self quickSortFrom:1 to:sz sortBlock:sortBlock
+    ]
+
+    "#(1 16 7 98 3 19 4 0) sort:[:a :b | a < b]"
+    "#(1 16 7 98 3 19 4 0) sort:[:a :b | a > b]"
+!
+
+sort:sortBlock with:aCollection
+    "sort the collection inplace using the 2-arg block sortBlock
+     for comparison. Also reorder the elements in aCollection"
+
+    |sz|
+
+    sz := self size.
+    (sz > 1) ifTrue:[
+        self quickSortFrom:1 to:sz sortBlock:sortBlock with:aCollection
+    ]
+
+    "|c1 c2|
+     c1 := #(1 16 7 9).
+     c2 := #('one' 'sixteen' 'seven' 'nine').
+     c1 sort:[:a :b | a > b] with:c2.
+     c1 printNewline.
+     c2 printNewline"
+! !
+
+!SequenceableCollection methodsFor:'enumerating'!
+
+do:aBlock
+    "evaluate the argument, aBlock for every element in the collection."
+
+    |index  "{ Class:SmallInteger }"
+     length "{ Class:SmallInteger }"|
+
+    index := 1.
+    length := self size.
+    [index <= length] whileTrue:[
+        aBlock value:(self at:index).
+        index := index + 1
+    ]
+!
+
+from:index1 to:index2 do:aBlock
+    "evaluate the argument, aBlock for the elements with index index1 to
+     index2 in the collection"
+
+    |index "{ Class:SmallInteger }"
+     stop  "{ Class:SmallInteger }" |
+
+    index := index1.
+    stop := index2.
+    [index <= stop] whileTrue:[
+        aBlock value:(self at:index).
+        index := index + 1
+    ]
+!
+
+with:aCollection do:aBlock
+    "evaluate the argument, aBlock for successive elements from
+     each of the two collections self and aCollection.
+     aBlock must be a two-argument block"
+
+    |index "{ Class: SmallInteger }"
+     stop  "{ Class: SmallInteger }" |
+
+    index := 1.
+    stop := self size.
+    [index <= stop] whileTrue:[
+        aBlock value:(self at:index) value:(aCollection at:index).
+        index := index + 1
+    ]
+!
+
+reverseDo:aBlock
+    "evaluate the argument, aBlock for every element in the collection
+     in reverse order"
+
+    |index "{ Class:SmallInteger }" |
+
+    index := self size.
+    [index > 0] whileTrue:[
+        aBlock value:(self at:index).
+        index := index - 1
+    ]
+!
+
+collect:aBlock
+    "evaluate the argument, aBlock for every element in the collection
+     and return a collection of the results"
+
+    |newCollection
+     index  "{ Class:SmallInteger }"
+     length "{ Class:SmallInteger }" |
+
+    length := self size.
+    newCollection := self species new:length.
+    index := 1.
+    [index <= length] whileTrue:[
+        newCollection at:index put:(aBlock value:(self at:index)).
+        index := index + 1
+    ].
+    ^ newCollection
+!
+
+select:aBlock
+    "evaluate the argument, aBlock for every element in the collection
+     and return a collection of all elements for which the block return
+     true"
+
+    |element newColl
+     index  "{ Class:SmallInteger }"
+     length "{ Class:SmallInteger }" |
+
+    length := self size.
+    newColl := OrderedCollection new:length.
+    index := 1.
+    [index <= length] whileTrue:[
+        element := self at:index.
+        (aBlock value:element) ifTrue:[
+            newColl add:element
+        ].
+        index := index + 1
+    ].
+    ^ newColl
+! !