SequenceableCollection.st
author Claus Gittinger <cg@exept.de>
Wed, 22 Sep 2004 11:55:56 +0200
changeset 8579 da7c9101e7a4
parent 8573 240f0fa27d20
child 8611 be457b330755
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1989 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.
"

"{ Package: 'stx:libbasic' }"

Collection subclass:#SequenceableCollection
	instanceVariableNames:''
	classVariableNames:'MissingClassInLiteralArrayErrorSignal'
	poolDictionaries:''
	category:'Collections-Abstract'
!

!SequenceableCollection class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 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.
"
!

documentation
"
    SequenceableCollections have ordered elements which can be accessed via
    a numeric index. 
    SequenceableCollection is an abstract class - there are no instances of 
    it in the system. 

    The methods found here assume that implementations of (at least)
    #at:/#at:put: are implemented (which are always found in Object for
    indexable objects).

    For performance, some subclasses redefine more methods, knowing the details
    of how elements are stored. 
    Especially, bulk data manipulation (i.e. #replaceFrom:to:with:startingAt:) 
    and search methods (i.e. #indexOf:startingAt:) are good candidates for this
    kind of tuneup.

    See concrete subclasses (such as OrderedCollection, Array or String).

    [author:]
        Claus Gittinger

    [see also:]
        OrderedCollection Array
        CharacterArray String
"
! !

!SequenceableCollection class methodsFor:'initialization'!

initialize
    MissingClassInLiteralArrayErrorSignal isNil ifTrue:[
        MissingClassInLiteralArrayErrorSignal := Error newSignalMayProceed:true.
        MissingClassInLiteralArrayErrorSignal nameClass:self message:#missingClassInLiteralArrayErrorSignal.
        MissingClassInLiteralArrayErrorSignal notifierString:'Missing class in literal encoding'.
    ]

    "Created: / 18.5.1999 / 14:49:51 / cg"
! !

!SequenceableCollection class methodsFor:'instance creation'!

decodeFromLiteralArray:anArray
    "create & return a new instance from information encoded in anArray.
     Redefined for faster creation.
    "
    |col i|
    col := self withSize:anArray size - 1.
    i := 1.
    anArray from:2 do:[:el| col at:i put:el decodeAsLiteralArray. i := i + 1].
    ^ col

!

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
!

newWithConcatenationOfAll:aCollectionOfCollections
    "this creates and returns a new collection consisting
     of the concatenation of all elements of the argument.
     I.e. it has the same effect as concatenating all elements
     of the argument using #, ,but is implemented more efficiently,
     by avoiding repeated garbage allocations.
     This is an O runtime algorithm, in contrast to the #, loop, which is O*O"

    |totalSize newColl idx|

    totalSize := aCollectionOfCollections 
                        inject:0
                        into:[:sumSoFar :el | sumSoFar + el size].
    newColl := self new:totalSize.
    idx := 1.
    aCollectionOfCollections do:[:el |
        |sz|

        sz := el size.
        newColl replaceFrom:idx to:(idx+sz-1) with:el startingAt:1.
        idx := idx + sz
    ].
    ^ newColl

    "
     this method optimizes the following (common) operation:

         |s|

         s := ''.
         #('hello' ' ' 'world' ' ' 'this is ' 'ST/X') do:[:e|
            s := s , e.
         ]. 
         s  

     String 
        newWithConcatenationOfAll:#('hello' ' ' 'world' ' ' 'this is ' 'ST/X')

     String 
        newWithConcatenationOfAll:#()   

     Array
        newWithConcatenationOfAll:#( (1 2 3 4) (5 6 7 8) (9 10 11 12) )   

     timing:
     -------
     speed-break-even is at around 5 elements for strings;
     for more elements, #newWithConcatenationOfAll: is much faster.

     |arr1 arr2 arr3 t|

     arr1 := #('hello' ' ' 'world' ' ' 'this is ' 'ST/X').
     arr2 := Array new:1000 withAll:'hello'.
     arr3 := Array new:10000 withAll:'hello'.

     (Array with:arr1 with:arr2 with:arr3) with:#(10000 100 10) do:[:arr :cnt |
         t := Time millisecondsToRun:[
            cnt timesRepeat:[
                String 
                    newWithConcatenationOfAll:arr
            ]
         ].
         Transcript showCR:(arr size printString , ' elements - time for #newWithConcatenationOfAll :' , (t/cnt) asFloat printString , 'mS').
         Transcript endEntry.

         t := Time millisecondsToRun:[
            cnt timesRepeat:[
                 |s|

                 s := ''.
                 arr do:[:e|
                    s := s , e.
                 ]. 
                 s  
            ]
         ].  
         Transcript showCR:(arr size printString , ' elements - time for loop over #, :' , (t/cnt) asFloat printString , 'mS').
         Transcript endEntry.
     ]
    "
!

withSize:size
    "return a new collection of size.
     For variable size collections, this is different from #new:,
     in that #new: creates an empty collection with preallocated size,
     while #withSize: creates a non empty one."

    |newCollection|

    newCollection := self new:size.
    newCollection grow:size.
    ^ newCollection

    "
     (OrderedCollection new:10) inspect.
     (OrderedCollection withSize:10) inspect.
     (Array new:10) inspect.
     (Array withSize:10) inspect.
    "
! !

!SequenceableCollection class methodsFor:'Compatibility-Squeak'!

streamContents:blockWithArg
    "create a write-stream on an instance of the receiver-class,
     evaluate blockWithArg, passing that stream,
     extract and return the streams contents."

    |stream|

    stream := WriteStream on:(self new:100).
    blockWithArg value:stream.
    ^ stream contents

    "
     |rslt|

     rslt := String streamContents:[:s | s nextPutAll:'hello'; space; nextPutAll:'world']
    "

    "Modified: / 31.10.2001 / 09:25:45 / cg"
!

writeStream
    "create a write-stream on an instance of the receiver-class"

    ^ WriteStream on:(self new:100).

    "
     String writeStream
    "
! !

!SequenceableCollection class methodsFor:'Signal constants'!

missingClassInLiteralArrayErrorSignal
    ^ MissingClassInLiteralArrayErrorSignal

    "Created: / 18.5.1999 / 14:50:04 / cg"
! !

!SequenceableCollection class methodsFor:'instance creation-multiDimensional'!

_at:nIndices
    "this is a synthetic selector, generated by the compiler,
     if a construct of the form expr[idx...] is parsed.
     I.e. 
        Array[n]
     generates
        Array _at: n
    "

    ^ self new:nIndices
!

_at:dim1 at:dim2
    "this is a synthetic selector, generated by the compiler,
     if a construct of the form expr[idx...] is parsed.
     I.e. 
        Array[n,m]
     generates
        Array _at:n at:m
    "

    |data|

    data := self withSize:(dim1 * dim2).
    ^ MultiDimensionalArrayAccessor
        collection:data
        dimensions:(Array with:dim1 with:dim2)
!

_at:dim1 at:dim2 at:dim3
    "this is a synthetic selector, generated by the compiler,
     if a construct of the form expr[idx...] is parsed.
     I.e. 
        Array[n,m,o]
     generates
        Array _at:n at:m at:o
    "

    |data|

    data := self withSize:(dim1 * dim2 * dim3).
    ^ MultiDimensionalArrayAccessor 
        collection:data
        dimensions:(Array with:dim1 with:dim2 with:dim3)
! !

!SequenceableCollection methodsFor:'Compatibility-Squeak'!

allButFirst
    "Return a copy of the receiver containing all but the first element. 
     Raise an error if there are not enough elements."

    ^ self copyFrom:2

    "
     '1234567890' allButFirst
    "
!

allButFirst:n
    "Return a copy of the receiver containing all but the first n elements. 
     Raise an error if there are not enough elements."

    ^ self copyFrom:n+1

    "
     '1234567890' allButFirst:5
    "
!

allButLast
    "Return a copy of the receiver containing all but the last element. 
     Raise an error if there are not enough elements."

    ^ self allButLast:1

    "
     '1234567890' allButLast
    "

    "Modified: / 13.11.2001 / 13:36:36 / cg"
!

allButLast:n
    "Return a copy of the receiver containing all but the last n elements. 
     Raise an error if there are not enough elements."

    ^ self copyFrom: 1 to: self size - n

    "
     '1234567890' allButLast:5
    "

    "Modified: / 13.11.2001 / 13:36:28 / cg"
!

atPin: index 
    "Return the index'th element of me if possible.
     Return the first or last element if index is out of bounds."

    index < 1 ifTrue:[^ self first].
    index > self size ifTrue:[^ self last].
    ^ self at:index

    "
     #(1 2 3) atPin:4    
     #(1 2 3) atPin:0    
     #(1 2 3) atPin:1    
     #(1 2 3) atPin:3    
    "
!

atRandom 
    "Return any random element from the receiver"

    ^ self atRandom:Random

    "
     #(1 2 3) atRandom  
    "
!

atRandom:aRandomGenerator 
    "Return any random element from the receiver"

    |max idx|

    (max := self size) == 0 ifTrue:[
        self emptyCollectionError
    ].
    idx := aRandomGenerator nextIntegerBetween:1 and:max.
    ^ self at:idx

    "
     #(1 2 3) atRandom:(Random new)  
    "
!

atWrap:index 
    "Return the index'th element of me if possible.
     Wrap the index modulu the receivers size if it is out of bounds."

    ^ self at:((index - 1) \\ (self size)) + 1

    "
     #(1 2 3) atWrap:1    
     #(1 2 3) atWrap:2    
     #(1 2 3) atWrap:3    
     #(1 2 3) atWrap:4    
     #(1 2 3) atWrap:5    
     #(1 2 3) atWrap:6    
     #(1 2 3) atWrap:7    
     #(1 2 3) atWrap:0    
     #(1 2 3) atWrap:-1    
    "
!

beginsWith:aCollection
    "Squeak & VW compatibility: same as #startsWith: - sigh"

    ^ self startsWith:aCollection

    "Modified: / 13.11.2001 / 13:49:18 / cg"
!

copyAfter: anElement
        "Answer a copy of the receiver from after the first occurence
        of anElement up to the end. If no such element exists, answer 
        an empty copy."
    |idx|

    idx := self indexOf:anElement.
    idx == 0 ifTrue:[idx := self size].
    ^ self copyFrom:idx + 1

    "
     'hello world' copyAfter:$l           
     '123456123456' copyAfter:$2           
     #(1 2 3 4 1 2 3 3 4 5 6) copyAfter:3   
     #(1 2 3 4 2 3 3 4 5 6) copyAfter:1  
     #(1 2 3 4 1 2 3 3 4 5 6) copyAfter:7 
    "
!

copyAfterLast:element
    "return a copy of the receiver from (but excluding) the last occurrence    
     of element to the end; uses = for comparison"

    |idx|

    idx := self lastIndexOf:element.
    idx == 0 ifTrue:[idx := self size].
    ^ self copyFrom:idx + 1

    "
     'hello world' copyAfterLast:$l           
     '123456123456' copyAfterLast:$2           
     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterLast:3   
     #(1 2 3 4 2 3 3 4 5 6) copyAfterLast:1  
     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterLast:7 
    "
!

copyUpToLast:element
    "return a copy of the receiver up to (but excluding) the last occurrence    
     of element; uses = for comparison"

    |idx|

    idx := self lastIndexOf:element.
    idx == 0 ifTrue:[idx := self size + 1].
    ^ self copyTo:idx - 1

    "
     'hello world' copyUpToLast:$l           
     '123456123456' copyUpToLast:$2           
     #(1 2 3 4 1 2 3 3 4 5 6) copyUpToLast:3   
     #(1 2 3 4 2 3 3 4 5 6) copyUpToLast:1  
     #(1 2 3 4 1 2 3 3 4 5 6) copyUpToLast:7 
    "
!

copyWithoutAll:elementsToSkip
    "return a new collection consisting of a copy of the receiver, with
     ALL elements equal to any in elementsToSkip are left out.
     No error is reported, if any in elementsToSkip is not in the collection."

    |n         "{ Class: SmallInteger }"
     sz        "{ Class: SmallInteger }"
     srcIndex  "{ Class: SmallInteger }"
     dstIndex  "{ Class: SmallInteger }"
     skipIndex "{ Class: SmallInteger }"
     copy l|

    "the code below may look like overkill, 
     however, for big collections its better to move data
     around in big chunks"

    n := self occurrencesOfAny:elementsToSkip.
    n == 0 ifTrue:[^ self copy].

    sz := self size.
    copy := self copyEmptyAndGrow:(sz - n).

    srcIndex := 1.
    dstIndex := 1.

    n timesRepeat:[
        skipIndex := self indexOfAny:elementsToSkip startingAt:srcIndex.
        l := skipIndex - srcIndex.
        l ~~ 0 ifTrue:[
            copy replaceFrom:dstIndex to:(dstIndex + l - 1) 
                        with:self startingAt:srcIndex.
            dstIndex := dstIndex + l
        ].
        srcIndex := skipIndex + 1
    ].
    l := sz - srcIndex.
    copy replaceFrom:dstIndex to:(dstIndex + l)
                with:self startingAt:srcIndex.
    ^ copy

    "
     #($a $b $c $d $e $f $g) copyWithoutAll:#($d $b $f)
     'abcdefghi' copyWithoutAll:'hai'    
     #(90 80 70 80 60 45 80 50) copyWithoutAll:#(80 70 45)
    "
!

copyWithoutFirst
    ^ self copyFrom:2
!

permutationsDo: aBlock
    "Repeatly value aBlock with a single copy of the receiver. Reorder the copy
     so that aBlock is presented all (self size factorial) possible permutations."

    self shallowCopy permutationsStartingAt:1 do:aBlock

    "
     (1 to: 4) permutationsDo:[:each | Transcript cr; show: each printString]
    "

    "Modified: / 13.11.2001 / 13:37:35 / cg"
!

permutationsStartingAt: anInteger do: aBlock
    "#(1 2 3 4) permutationsDo: [:each | Transcript cr; show: each printString]"

    |mySize|

    mySize := self size.
    anInteger > mySize ifTrue: [^self].
    anInteger = mySize ifTrue: [^aBlock value: self].
    anInteger to:mySize do:[:i | 
        self swap: anInteger with: i.
        self permutationsStartingAt: anInteger + 1 do: aBlock.
        self swap: anInteger with: i
    ]

    "Modified: / 13.11.2001 / 13:48:49 / cg"
! !

!SequenceableCollection methodsFor:'Compatibility-VW'!

replaceElementsFrom:start to:stop withArray:anArray startingAt:repStart
    ^ self replaceFrom:start to:stop with:anArray startingAt:repStart
! !

!SequenceableCollection methodsFor:'accessing'!

after:anObject
    "return the element, after anObject.
     If anObject is not in the receiver, report an error;
     if anObject is the last in the receiver, return nil.
     This depends on #after:ifAbsent: being implemented in a concrete class."

    ^ self after:anObject ifAbsent:[self errorValueNotFound:anObject]

    "
     #(4 3 2 1) asOrderedCollection after:3. 
     #(4 3 2 1) asOrderedCollection after:5 
     #(4 3 2 1) asOrderedCollection after:1 
    "

    "Created: 10.5.1996 / 13:59:29 / cg"
    "Modified: 10.5.1996 / 14:03:33 / cg"
!

after:anObject ifAbsent:exceptionBlock
    "return the element, after anObject. 
     If anObject is the last in the receiver, return nil.
     If there is no such element (anObject is not found),
     return the value from exceptionBlock."

    |idx|

    idx := self indexOf:anObject.
    idx ~~ 0 ifTrue:[
        idx == self size ifTrue:[^ nil].
        ^ self at:(idx + 1).
    ].
    ^ exceptionBlock value

    "
     #(4 3 2 1) after:3 ifAbsent:nil. 
     (2 to:10 by:2) after:4 ifAbsent:nil.     
     #(4 3 2 1) asOrderedCollection after:5 ifAbsent:nil. 
     (2 to:10 by:2) after:5 ifAbsent:nil. 
    "
!

anElement
    "return any element from the collection, 
     report an error if there is none"

    ^ self first
!

at:index ifAbsent:exceptionBlock
    "return the element at index if valid. 
     If the index is invalid, return the result of evaluating 
     the exceptionblock.
     NOTICE: 
        in ST-80, this message is only defined for Dictionaries,
        however, having a common protocol with indexed collections
        often simplifies things."

    (index between:1 and:self size) ifFalse:[
        ^ exceptionBlock value
    ].
    ^ self at:index

    "
     #(1 2 3) at:4 ifAbsent:['no such index']
     #(1 2 3) asOrderedCollection at:4 ifAbsent:['no such index'] 
     #(1 2 3) at:4 ifAbsent:['no such index']  

     (Dictionary with:(#foo -> #bar)
                 with:(#frob -> #baz)) 
         at:#foobar ifAbsent:['no such index']
    "
!

before:anObject
    "return the element before the argument, anObject.
     If anObject is not in the receiver, report an error;
     if anObject is the first in the receiver, return nil.
     This depends on #before:ifAbsent: being implemented in a concrete class."

    ^ self before:anObject ifAbsent:[self errorValueNotFound:anObject]

    "
     #(4 3 2 1) asOrderedCollection before:3. 
     #(4 3 2 1) asOrderedCollection before:4 
     #(4 3 2 1) asOrderedCollection before:0 
    "

    "Created: 10.5.1996 / 14:03:27 / cg"
    "Modified: 10.5.1996 / 14:03:44 / cg"
!

before:anObject ifAbsent:exceptionBlock
    "return the element, before anObject. 
     If anObject is the first in the receiver, return nil.
     If there is no such element (anObject is not found),
     return the value from exceptionBlock."

    |idx|

    idx := self indexOf:anObject.
    idx ~~ 0 ifTrue:[
        idx == 1 ifTrue:[^ nil].
        ^ self at:(idx - 1).
    ].
    ^ exceptionBlock value

    "
     #(4 3 2 1) asOrderedCollection before:3 ifAbsent:nil. 
     #(4 3 2 1) asOrderedCollection before:5 ifAbsent:nil. 
     #(4 3 2 1) asOrderedCollection before:5. 
     #(4 3 2 1) asOrderedCollection before:4 ifAbsent:nil. 
     #(4 3 2 1) asOrderedCollection before:4.            
     (2 to:10 by:2) before:4 ifAbsent:nil.            
     (2 to:10 by:2) before:5 ifAbsent:nil.            
    "

!

first
    "return the first element; 
     report an error, if the collection is empty."

    ^ self at:1

    "
     args:    
     returns: firstElement <object>
    "

    "Modified: / 20.5.1998 / 14:50:25 / cg"
!

first:n
    "return the n first elements of the collection.
     Raises an error if there are not enough elements in the receiver."

    n < 0 ifTrue:[self error:'bad (negative) argument'].
    n > self size ifTrue:[^ self notEnoughElementsError].

    ^ self copyFirst:n

    "
     #(1 2 3 4 5) first:3           
     #(1 2 3 4 5) first:6           
     #(1 2 3 4 5) asSet first:3           
     'hello world' first:5           
    "
!

keyAtEqualValue:value
    "return the index of a value.
     This is normally not used (use indexOf:), but makes the
     protocol more compatible with dictionaries."

    ^ self indexOf:value
!

keyAtEqualValue:value ifAbsent:exceptionBlock
    "return the index of a value.
     This is normally not used (use indexOf:), but makes the
     protocol more compatible with dictionaries."

    ^ self indexOf:value ifAbsent:exceptionBlock
!

keyAtValue:value
    "return the index of a value.
     This is normally not used (use indexOf:), but makes the
     protocol more compatible with dictionaries."

    ^ self identityIndexOf:value
!

keyAtValue:value ifAbsent:exceptionBlock
    "return the index of a value.
     This is normally not used (use indexOf:), but makes the
     protocol more compatible with dictionaries."

    ^ self identityIndexOf:value ifAbsent:exceptionBlock
!

last
    "return the last element;
     report an error, if the collection is empty."

    |sz|

    (sz := self size) == 0 ifFalse:[
        ^ self at:sz
    ].
    "error if collection is empty"
    ^ self emptyCollectionError

    "
     #(1 2 3 4 5) last
     #() last
    "
!

last:n
    "return the n last elements of the collection.
     Raises an error if there are not enough elements in the receiver."

    n < 0 ifTrue:[self error:'bad (negative) argument'].
    n > self size ifTrue:[^ self notEnoughElementsError].

    ^ self copyLast:n

    "
     #(1 2 3 4 5) last:3           
     #(1 2 3 4 5) last:6           
     #(1 2 3 4 5) asSet last:3           
     'hello world' last:5           
    "
!

nth:n
    "return the nth element;
     report an error, if the collections size is smaller than n."

    ^ self at:n

    "
     args:    
     returns: nth element <object>
    "

    "
     #(10 20 30 40 50) nth:4   
     #(10 20 30 40 50) nth:6
     #() nth:1
    "

!

second
    "return the second element;
     report an error, if the collections size is smaller than 2."

    ^ self at:2

    "
     args:    
     returns: secondElement <object>
    "

    "Modified: / 20.5.1998 / 14:50:25 / cg"
!

swap:index1 with:index2
    "exchange two elements"

    |t|

    t := self at:index1.
    self at:index1 put:(self at:index2).
    self at:index2 put:t

    "Modified: 15.10.1997 / 19:27:08 / cg"
! !

!SequenceableCollection methodsFor:'adding & removing'!

add:anObject
    "append the argument, anObject to the collection.
     Return the argument, anObject.

     Notice, that this is modifies the receiver NOT a copy.
     Also note, that it may be a slow operation for some collections,
     due to the grow:-message, which is inefficient for fixed size 
     collections (i.e. for Strings and Arrays it is not recommened)."

    |newSize|

    newSize := self size + 1.
    self grow:newSize.
    self at:newSize put:anObject.
    ^ anObject

    "
     |a|
     a := #(1 2 3 4 5 6 7 8).
     a add:'hello'.
     a
    "
    "
     |c|
     c := #(1 2 3 4 5 6 7 8) asOrderedCollection.
     c add:'hello'.
     c
    "
!

add:anElement beforeIndex:index
    "insert the first argument, anObject into the collection before slot index.
     Return the receiver (sigh - ST-80 compatibility).

     Notice, that this is modifies the receiver NOT a copy.
     Also note, that it may be a slow operation for some collections,
     due to the grow:-message, which is inefficient for fixed size 
     collections (i.e. for Strings and Arrays it is not recommened)."

    |newSize|

    newSize := self size + 1.
    self grow:newSize.
    self replaceFrom:index + 1 to:newSize with:self startingAt:index.
    self at:index put:anElement

    "
     #(1 2 3 4 5 6 7 8) add:'hello' beforeIndex:5
    "
!

addFirst:anObject
    "prepend the argument, anObject to the collection.
     Return the argument, anObject.

     Notice, that this is modifies the receiver NOT a copy.
     Also note, that it may be a slow operation for some collections,
     due to the grow:-message, which is inefficient for fixed size 
     collections (i.e. for Strings and Arrays it is not recommened)."

    |newSize|

    newSize := self size + 1.
    self grow:newSize.
    self replaceFrom:2 to:newSize with:self startingAt:1.
    self at:1 put:anObject.
    ^ anObject

    "
     |a| 
     a:= #(1 2 3 4 5 6 7 8). 
     a addFirst:'hello'. 
     a 
    "
    "
     |c|
     c := #(1 2 3 4 5 6 7 8) asOrderedCollection.
     c addFirst:'hello'.
     c
    "
!

remove:anElement ifAbsent:aBlock
    "search for an object which is equal to anElement;
     if found remove and return it; if not, return the value from evaluating aBlock.
     Use equality compare (=) to search for an occurrence.

     Notice, that this is modifies the receiver NOT a copy.
     Also note, that it may be a slow operation for some collections,
     due to the grow:-message, which is inefficient for fixed size 
     collections (i.e. for Strings and Arrays it is not recommened)."

    |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.
        ^ anElement
    ].
    ^ aBlock value

    "
     #(1 2 3 4 5 6 7 8 9 0) remove:3 ifAbsent:[Transcript showCR:'no']
     #(1 2 3 4 5 6 7 8 9 0) remove:99 ifAbsent:[#oops]
     #(1.0 2.0 3.0 4.0 5.0) remove:5 ifAbsent:[#oops]
     #(1.0 2.0 3.0 4.0 5.0) removeIdentical:5 ifAbsent:[#oops]
    "

    "Modified: 1.2.1997 / 11:49:01 / cg"
!

removeAllSuchThat:aBlock
    "remove all elements that meet a test criteria as specified in aBlock.
     The argument, aBlock is evaluated for successive elements and all those,
     for which it returns true, are removed.
     Return a collection containing the removed elements."

    "/ this is a q&d implementation (possibly slow).

    |runIndex removed element|

    removed := self species new.

    runIndex := 1.
    [runIndex <= self size] whileTrue:[
        element := self at:runIndex.
        (aBlock value:element) ifTrue:[
            removed add:element.
            self removeAtIndex:runIndex
        ] ifFalse:[
            runIndex := runIndex + 1
        ]
    ].
    ^ removed

    "
     |coll|

     coll := OrderedCollection withAll:(1 to:10).
     Transcript showCR:(coll removeAllSuchThat:[:el | el even]).
     Transcript showCR:coll
    "

    "Created: 11.5.1996 / 09:49:30 / cg"
!

removeAtIndex:anIndex
    "remove the element stored at anIndex. Return the removed object.

     Notice, that this is modifies the receiver NOT a copy.
     Also note, that it may be a slow operation for some collections,
     due to the grow:-message, which is inefficient for fixed size 
     collections (i.e. for Strings and Arrays it is not recommened)."

    |element|

    element := self at:anIndex.
    self removeFromIndex:anIndex toIndex:anIndex.
    ^ element

    "
     #(1 2 3 4 5 6 7 8 9) asOrderedCollection removeAtIndex:3
     #(1 2 3 4 5) asOrderedCollection removeAtIndex:6
     #($a $b $c $d $e $f $g) removeAtIndex:3
    "
!

removeFirst
    "remove the first element of the receiver and return it.

     Notice, that this is modifies the receiver NOT a copy.
     Also note, that it may be a slow operation for some collections,
     due to the grow:-message, which is inefficient for fixed size 
     collections (i.e. for Strings and Arrays it is not recommened)."

    ^ self removeAtIndex:1

    "
     |a|
     a := #(1 2 3 4 5 6).
     a removeFirst.
     a 
    "
!

removeFromIndex:startIndex
    "remove the elements stored at indexes from startIndex to the end.
     Return the receiver.
     Returning the receiver is a historic leftover - it may at one
     time return a collection of the removed elements.

     Notice, that this is modifies the receiver - NOT a copy; 
     therefore any other users of the receiver will also see this change.
     Also note, that it may be a slow operation for some collections,
     due to the grow:-message, which is inefficient for fixed size 
     collections (i.e. for Strings and Arrays it is not recommened)."

    ^ self removeFromIndex:startIndex toIndex:(self size)

    "
     #(1 2 3 4 5 6 7 8 9 0) asOrderedCollection removeFromIndex:3 
     #(1 2 3 4 5 6 7 8 9 0) removeFromIndex:3
    "

    "Modified: 28.1.1997 / 12:35:20 / cg"
!

removeFromIndex:startIndex toIndex:endIndex
    "remove the elements stored at indexes between startIndex and endIndex.
     Return the receiver.
     Returning the receiver is a historic leftover - it may at one
     time return a collection of the removed elements.

     Notice, that this is modifies the receiver - NOT a copy; 
     therefore any other users of the receiver will also see this change.
     Also note, that it may be a slow operation for some collections,
     due to the grow:-message, which is inefficient for fixed size 
     collections (i.e. for Strings and Arrays it is not recommened)."

    |size newSize|

    (endIndex >= (size := self size)) ifTrue:[
        self grow:(startIndex - 1)
    ] ifFalse:[
        newSize := size - endIndex + startIndex - 1.
        self replaceFrom:startIndex to:newSize with:self startingAt:(endIndex + 1).
        self grow:newSize
    ]

"/    |newSize|
"/
"/    newSize := self size - endIndex + startIndex - 1.
"/    newSize <= 0 ifTrue:[
"/        self grow:0
"/    ] ifFalse:[
"/        self replaceFrom:startIndex to:newSize with:self startingAt:(endIndex + 1).
"/        self grow:newSize
"/    ]

    "
     #(1 2 3 4 5 6 7 8 9 0) asOrderedCollection removeFromIndex:3 toIndex:5 
     #(1 2 3 4 5 6 7 8 9 0) removeFromIndex:3 toIndex:5 
     #(1 2 3 4 5 6 7 8 9 0) asOrderedCollection removeFromIndex:1 toIndex:10 
     #(1 2 3 4 5 6 7 8 9 0) removeFromIndex:1 toIndex:10 
    "
!

removeIdentical:anElement ifAbsent:aBlock
    "search for an object which is identical to anElement;
     if found remove and return it; if not, return the value from evaluating aBlock.
     Uses identity compare (==) to search for an occurrence.

     Notice, that this is modifies the receiver NOT a copy.
     Also note, that it may be a slow operation for some collections,
     due to the grow:-message, which is inefficient for fixed size 
     collections (i.e. for Strings and Arrays it is not recommened)."

    |any el
     dstIndex "{ Class: SmallInteger }"
     sz       "{ Class: SmallInteger }"|

    dstIndex := 1.
    any := false.
    sz := self size.
    1 to:sz do:[:srcIndex |
        el := self at:srcIndex.
        (anElement == el) ifTrue:[
            any := true
        ] ifFalse:[
            (dstIndex ~~ srcIndex) ifTrue:[
                self at:dstIndex put:el
            ].
            dstIndex := dstIndex + 1
        ]
    ].
    any ifTrue:[
        self grow:dstIndex - 1.
        ^ anElement
    ].
    ^ aBlock value

    "
     #(1.0 2.0 3.0 4.0 5.0) remove:5 ifAbsent:[#oops]         
     #(1.0 2.0 3.0 4.0 5.0) removeIdentical:5 ifAbsent:[#oops]
    "

    "Modified: 8.2.1997 / 16:26:49 / cg"
!

removeIndex:index
    "remove the argument stored at index. Return the receiver.

     Notice, that this is modifies the receiver NOT a copy.
     Also note, that it may be a slow operation for some collections,
     due to the grow:-message, which is inefficient for fixed size 
     collections (i.e. for Strings and Arrays it is not recommened)."

    self removeFromIndex:index toIndex:index

    "
     #(1 2 3 4 5 6 7 8 9) asOrderedCollection removeIndex:3
     #(1 2 3 4 5) asOrderedCollection removeIndex:6
     #($a $b $c $d $e $f $g) removeIndex:3
    "
!

removeLast
    "remove the last element of the receiver and return it.

     Notice, that this is modifies the receiver NOT a copy.
     Also note, that it may be a slow operation for some collections,
     due to the grow:-message, which is inefficient for fixed size
     collections (i.e. for Strings and Arrays it is not recommened)."

    ^ self removeAtIndex:(self size) 

    "
     |a|
     a := #(1 2 3 4 5 6).
     a removeLast.
     a   
    "
! !

!SequenceableCollection methodsFor:'comparing'!

< aCollection
    "compare two sequenceable collections"
    
    |size               "{ Class: SmallInteger }"
     aCollectionSize    "{ Class: SmallInteger }"
     min                "{ Class: SmallInteger }"
     v1 v2|

    size := self size.
    aCollectionSize := aCollection size.
    size < aCollectionSize ifTrue:[
        min := size
    ] ifFalse:[
        min := aCollectionSize
    ].

    1 to: min do: [:i|
        v1 := self at: i.
        v2 := aCollection at: i.
        (v1 == v2 or:[v1 = v2]) ifFalse:[^ v1 < v2]
    ].
    ^ size < aCollectionSize

    "
      #(1 2 3) < #(1)
      #(1 2 3) < #(2)
      #(1 2 3) < #()
      #(1 2 3) < #(1 2 3)

      |a b|

      a := 'hello world'.
      b := a copy.
      Time millisecondsToRun:[
        1000000 timesRepeat:[
            a < b
        ]
      ]

      |a b|

      a := CharacterArray fromString:'hello world'.
      b := a copy.
      Time millisecondsToRun:[
        1000000 timesRepeat:[
            a < b
        ]
      ]

      |a b|

      a := #[1 2 3 4 5 6 7 8 9 10 11].
      b := a copy.
      Time millisecondsToRun:[
        1000000 timesRepeat:[
           a < b
        ]
      ]
    "
!

<= aCollection
    "Compare the receiver with the argument and return true if the
     receiver is less than or equal to the argument. Otherwise return false"

    ^ (aCollection < self) not
!

= aCollection
    "return true if the receiver and aCollection represent collections
     with equal contents."

    | stop "{ Class: SmallInteger }" |

    (aCollection == self) ifTrue:[^true].
    (aCollection isSequenceable) ifFalse:[^false].

    stop := self size.
    stop == (aCollection size) ifFalse:[^false].

    1 to:stop do:[:index|
        (self at:index) = (aCollection at:index) ifFalse:[^false].
    ].
    ^ true

    "
     #(1 2 3 4 5) = #(1 2 3 4 5)                        
     #($1 $2 $3 $4 $5) = #(1 2 3 4 5)                   
     #($1 $2 $3 $4 $5) = '12345'                       
     #($1 $2 $3 $4 $5) = '54321' asSortedCollection   
    "
!

> aCollection
    "Compare the receiver with the argument and return true if the
     receiver is greater than the argument.
     Otherwise return false."

    ^ aCollection < self
!

>= aCollection
    "Compare the receiver with the argument and return true if the
     receiver is greater than or equal to the argument.
     Otherwise return false."

    ^ (self < aCollection) not
!

commonPrefixWith:aCollection 
    "return the common prefix of myself and the argument, aCollection.
     If there is none, an empty collection is returned."

    ^ self commonPrefixWith:aCollection ignoreCase:false

    "
     'hello' commonPrefixWith:'hello'       
     'hello' commonPrefixWith:'hElLo'       
     'hello' commonPrefixWith:'hello world'   
     'hello' commonPrefixWith:'hElLo WoRlD' 

     'hello world' commonPrefixWith:'hello'  
     'hello WoRlD' commonPrefixWith:'hElLo'   

     'abcd' commonPrefixWith:'bcde'      

     'abcd' commonPrefixWith:'abab'      
     'abcd' commonPrefixWith:'ab'        
     'abcd' commonPrefixWith:'ababab'       
     'abcd' commonPrefixWith:'abcdef'       

     'abab' commonPrefixWith:'abcd'      
     'ab'   commonPrefixWith:'abcd'       
     'ababab' commonPrefixWith:'abcd'       
     'abcdef' commonPrefixWith:'abcd'       
    "
!

commonPrefixWith:aCollection ignoreCase:ignoreCase
    "return the common prefix of myself and the argument, aCollection.
     If there is none, an empty collection is returned."

    |matchLen|

    matchLen := self size min:aCollection size.
    1 to:matchLen do:[:idx |
        |elHere elThere same|

        elHere := self at:idx.
        elThere := aCollection at:idx.

        ignoreCase ifTrue:[
            same := elHere sameAs:elThere
        ] ifFalse:[
            same := elHere = elThere
        ].
        same ifFalse:[
            ^ self copyTo:(idx - 1).
        ]
    ].

    ^ self copyTo:matchLen

    "
     'hello' commonPrefixWith:'hello' ignoreCase:true       
     'hello' commonPrefixWith:'hElLo' ignoreCase:true       
     'hello' commonPrefixWith:'hello world' ignoreCase:true    
     'hello' commonPrefixWith:'hElLo WoRlD' ignoreCase:true    

     'hello world' commonPrefixWith:'hello' ignoreCase:true    
     'hello WoRlD' commonPrefixWith:'hElLo' ignoreCase:true    

     'abcd' commonPrefixWith:'bcde' ignoreCase:true     

     'abcd' commonPrefixWith:'abab' ignoreCase:true     
     'abcd' commonPrefixWith:'ab'   ignoreCase:true     
     'abcd' commonPrefixWith:'ababab'   ignoreCase:true    
     'abcd' commonPrefixWith:'abcdef'   ignoreCase:true    

     'abab' commonPrefixWith:'abcd' ignoreCase:true     
     'ab'   commonPrefixWith:'abcd'   ignoreCase:true    
     'ababab' commonPrefixWith:'abcd'   ignoreCase:true    
     'abcdef' commonPrefixWith:'abcd'   ignoreCase:true    
    "
!

commonSuffixWith:aCollection 
    "return the common suffix (tail) of myself and the argument, aCollection.
     If there is none, an empty collection is returned."

    ^ self commonSuffixWith:aCollection ignoreCase:false

    "
     'hello' commonSuffixWith:'hello'        
     'hello' commonSuffixWith:'hElLo'        
     'hello' commonSuffixWith:'hello world'     
     'hello' commonSuffixWith:'hElLo WoRlD'     
     'hello2 world' commonSuffixWith:'hello world'     
     'hello2 world' commonSuffixWith:'hElLo WoRlD'     

     'hello world' commonSuffixWith:'world'          
     'hello WoRlD' commonSuffixWith:'world'     

     'dcba' commonSuffixWith:'edcb'        

     'dcba' commonSuffixWith:'baba'      
     'dcba' commonSuffixWith:'ba'        
     'dcba' commonSuffixWith:'bababa'       
     'dcba' commonSuffixWith:'fdcba'       

     'baba' commonSuffixWith:'dcba'      
     'ba'   commonSuffixWith:'dcba'       
     'bababa' commonSuffixWith:'dcba'       
     'fdcba' commonSuffixWith:'dcba'       
    "
!

commonSuffixWith:aCollection ignoreCase:ignoreCase
    "return the common suffix (tail) of myself and the argument, aCollection.
     If there is none, an empty collection is returned."

    |matchLen l1 l2|

    l1 := self size.
    l2 := aCollection size.
    matchLen := l1 min:l2.
    1 to:matchLen do:[:idx |
        |elHere elThere same|

        elHere := self at:(l1 - idx + 1).
        elThere := aCollection at:(l2 - idx + 1).

        ignoreCase ifTrue:[
            same := elHere sameAs:elThere
        ] ifFalse:[
            same := elHere = elThere
        ].
        same ifFalse:[
            ^ self copyFrom:(l1 - idx + 2).
        ]
    ].

    ^ self copyFrom:(l1 - matchLen + 1)

    "
     'hello' commonSuffixWith:'hello' ignoreCase:true       
     'hello' commonSuffixWith:'hElLo' ignoreCase:true       
     'hello' commonSuffixWith:'hello world' ignoreCase:true    
     'hello' commonSuffixWith:'hElLo WoRlD' ignoreCase:true    
     'hello2 world' commonSuffixWith:'hello world' ignoreCase:true    
     'hello2 world' commonSuffixWith:'hElLo WoRlD' ignoreCase:true    

     'hello world' commonSuffixWith:'world' ignoreCase:true         
     'hello WoRlD' commonSuffixWith:'world' ignoreCase:true    

     'dcba' commonSuffixWith:'edcb' ignoreCase:true       

     'dcba' commonSuffixWith:'baba' ignoreCase:true     
     'dcba' commonSuffixWith:'ba'   ignoreCase:true     
     'dcba' commonSuffixWith:'bababa'   ignoreCase:true    
     'dcba' commonSuffixWith:'fdcba'   ignoreCase:true    

     'baba' commonSuffixWith:'dcba' ignoreCase:true     
     'ba'   commonSuffixWith:'dcba'   ignoreCase:true    
     'bababa' commonSuffixWith:'dcba'   ignoreCase:true    
     'fdcba' commonSuffixWith:'dcba'   ignoreCase:true    
    "
!

deepSameContentsAs:aCollection
    "return true, if the receiver and the arg have the same contents
     in both the named instance vars and any indexed instVars.
     This method descends into referenced objects, where #sameContentsAs: does not descend.

     Redefinded, so that SequenceableCollections are equivalent, especially OrderedCollections with
     unused space"

    |index "{ Class: SmallInteger }"
     stop  "{ Class: SmallInteger }" |

    (aCollection == self) ifTrue:[^true].
    (aCollection isSequenceable) ifFalse:[^false].

    stop := self size.
    stop == (aCollection size) ifFalse:[^false].

    index := 1.
    [index <= stop] whileTrue:[
        ((self at:index) deepSameContentsAs:(aCollection at:index)) ifFalse:[^false].
        index := index + 1
    ].
    ^ true

    "
     #(1 2 3 4 5) deepSameContentsAs: #(1 2 3 4 5)                        
     #($1 $2 $3 $4 $5) deepSameContentsAs: #(1 2 3 4 5)                   
     #($1 $2 $3 $4 $5) deepSameContentsAs: '12345'                       
     #($1 $2 $3 $4 $5) deepSameContentsAs: '54321' asSortedCollection   
    "
!

endsWith:aCollection
    "return true, if the receivers last elements match those
     of aCollection"

    |index1 "{ Class: SmallInteger }"
     index2 "{ Class: SmallInteger }" 
     stop   "{ Class: SmallInteger }" 
     sz     "{ Class: SmallInteger }"|

    (aCollection == self) ifTrue:[^ true].
    (aCollection isSequenceable) ifFalse:[^ false].

    stop := aCollection size.
    sz := self size.
    stop > sz ifTrue:[^false].

    index1 := sz.
    index2 := stop.
    [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)
    "
!

endsWithAnyOf:aCollectionOfCollections
    "return true, if the receiver endswith any in aCollection"

    ^ aCollectionOfCollections contains:[:eachTriedEnd | self endsWith:eachTriedEnd]

    "
     'abcde' endsWithAnyOf:#('DE' 'de')
     'abcde' endsWithAnyOf:#('DF' 'df')
     #[1 2 3 4] endsWithAnyOf:#( #(3 5) #(2 4))   
     #[1 2 3 4] endsWithAnyOf:#( #(3 4) #(2 4))   
    "
!

hash
    "return a hash key for the receiver"

    "this hash is stupid - but for larger collections, the hashing
     time can become much bigger than the time lost in added probing.
     Time will show ..."

    |mySize h|

    mySize := self size.
    mySize == 0 ifTrue:[^ 0].

    h := (self at:1) hash.
    h := h bitAnd:16r01FFFFFF.
    h := (h bitShift:5) + (self at:mySize) hash.
    h := h bitAnd:16r01FFFFFF.
    h := (h bitShift:5) + self size.
    ^ h bitAnd:16r3FFFFFFF.

    "/ cg: the code below may lead to largeInteger arithmetic, which was slow...
    "/     ^ ((((self first hash bitShift:5) + self last hash) bitShift:5) + self size hash) bitAnd:16r3FFFFFFF.

    "
     #(1 2 3 4 5 6) hash     
     (1 to:6) hash           

     #(1 2 3 4 5.0) asOrderedCollection hash   
     #(1 2 3 4 5) hash                         
    "

    "Modified: / 27.3.1998 / 17:33:49 / cg"
!

identicalContentsAs:aCollection
    "return true if the receiver and aCollection represent collections
     with identical contents. This is much like #=, but compares
     elements using #== instead of #=."

    ^ self
        sameContentsAs:aCollection 
        whenComparedWith:[:a :b | a == b]

"/    |index "{ Class: SmallInteger }"
"/     stop  "{ Class: SmallInteger }" |
"/
"/    (aCollection == self) ifTrue:[^ true].
"/    (aCollection size == self size) ifFalse:[^ false].
"/    (aCollection isSequenceable) ifFalse:[^ aCollection identicalContentsAs:self].
"/
"/    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

    "
     #(1 2 3 4 5) = #(1 2 3 4 5)                        
     #(1 2 3 4 5) = #(1.0 2 3 4.0 5)                        
     #($1 $2 $3 $4 $5) = '12345'     

     #(1 2 3 4 5) identicalContentsAs:#(1 2 3 4 5) 
     #(1 2 3 4 5) identicalContentsAs: #(1.0 2 3 4.0 5)                        
     #($1 $2 $3 $4 $5) identicalContentsAs: '12345'     
    "

    "Modified: / 31.10.2001 / 11:30:18 / cg"
!

isSameSequenceAs: otherCollection
    "Answer whether the receiver's size is the same as otherCollection's size, 
     and each of the receiver's elements equal the corresponding element of otherCollection.
    "

    | size |

    (size := self size) = otherCollection size ifFalse: [^false].

    1 to: size do:[:index |
        (self at: index) = (otherCollection at: index) ifFalse: [^false]
    ].
    ^ true
!

sameContentsAs:aCollection whenComparedWith:compareBlock
    "return true if the receiver and aCollection represent collections
     with the same contents, using compareSelector to compare elements. 
     This is a generic version of #= or #identicalContentsAs:;
     i.e. #= is the same as #sameContentsAs:whenComparedUsing:#=
     and #identicalContentsAs: is the same as #sameContentsAs:whenComparedUsing:#==.
    "

    |index "{ Class: SmallInteger }"
     stop  "{ Class: SmallInteger }" |

    (aCollection == self) ifTrue:[^ true].
    (aCollection size == self size) ifFalse:[^ false].
    (aCollection isSequenceable) ifFalse:[
        ^ aCollection sameContentsAs:self whenComparedWith:compareBlock
    ].

    stop := self size.
    stop == (aCollection size) ifFalse:[^ false].

    index := 1.
    [index <= stop] whileTrue:[
        (compareBlock value:(self at:index) value:(aCollection at:index)) ifFalse:[^ false].
        index := index + 1
    ].
    ^ true

    "
     #(1 2 3 4 5) sameContentsAs: #(1 2 3 4 5)     whenComparedWith:[:a :b | a = b]                   
     #(1 2 3 4 5) sameContentsAs: #(1 2 3 4 5)     whenComparedWith:[:a :b | a == b]                  
     #(1 2 3 4 5) sameContentsAs: #(1.0 2 3 4.0 5) whenComparedWith:[:a :b | a = b]                     
     #(1 2 3 4 5) sameContentsAs: #(1.0 2 3 4.0 5) whenComparedWith:[:a :b | a == b]                     

     #('Hello' 'ABC' 'worlD') sameContentsAs: #('Hello' 'ABC' 'worlD') whenComparedWith:[:a :b | a sameAs:b]
    "

    "Created: / 31.10.2001 / 11:29:38 / cg"
    "Modified: / 31.10.2001 / 11:30:32 / cg"
!

startsWith:aCollection
    "return true, if the receivers first elements match those
     of aCollection
     If the argument is empty, true is returned."

    |index "{ Class: SmallInteger }"
     stop  "{ Class: SmallInteger }" |

    (aCollection == self) ifTrue:[^true].
    (aCollection isSequenceable) 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)
     #(1 2 3 4) asOrderedCollection startsWith:#()   
    "
!

startsWithAnyOf:aCollectionOfCollections
    "return true, if the receiver starts with any in aCollection"

    ^ aCollectionOfCollections contains:[:eachTriedEnd | self startsWith:eachTriedEnd]

    "
     'abcde' startsWithAnyOf:#('AB' 'ab')
     'abcde' startsWithAnyOf:#('AC' 'ac')
     #[1 2 3 4] startsWithAnyOf:#( #(1 3) #(1 4))   
     #[1 2 3 4] startsWithAnyOf:#( #(1 3) #(1 2))   
    "
! !

!SequenceableCollection methodsFor:'converting'!

asSequenceableCollection
    "return myself as a SequenceableCollection.
     I am already a SequenceableCollection."

    ^ self


!

asStringCollection
    "return a new string collection containing the elements;
     these ought to be strings. (i.e. String or Text instances)"

    |newColl sz|

    sz := self size.
    newColl := (StringCollection new:sz) grow:sz.
    newColl replaceFrom:1 to:sz with:self startingAt:1.
    ^ newColl

    "Created: 18.5.1996 / 13:53:55 / cg"
    "Modified: 18.5.1996 / 14:00:16 / cg"
!

asStringWith:sepChar
    "return a string generated by concatenating my elements 
     (which must be strings or nil) and embedding sepChar characters in between.
     Nil entries and empty strings are counted as empty lines."

    ^ self 
        from:1 to:(self size) 
        asStringWith:sepChar 
        compressTabs:false
        final:nil

    "
     #('hello' 'world' 'foo' 'bar' 'baz') asStringWith:$;
    "

    "Modified: 18.5.1996 / 15:28:14 / cg"
!

asStringWith:sepCharacter from:firstLine to:lastLine
    "return part of myself as a string with embedded sepCharacters.
     My elements must be strings or nil; nil entries and empty strings are
     taken as empty lines."

    ^ self 
        from:firstLine to:lastLine
        asStringWith:sepCharacter 
        compressTabs:false
        final:nil
    "
     creating entries for searchpath:

     #('foo' 'bar' 'baz' '/foo/bar') asStringWith:$;   

     #('foo' 'bar' 'baz' '/foo/bar') asStringWith:$: from:1 to:3   
    "

    "Modified: 23.2.1996 / 15:28:55 / cg"
!

asStringWith:sepCharacter from:firstLine to:lastLine compressTabs:compressTabs final:endCharacter
    "return part of myself as a string or text with embedded sepCharacters.
     My elements must be strings or nil; nil entries and empty strings are
     taken as empty lines.
     If the argument compressTabs is true, leading spaces are converted
     to tab-characters (8col tabs). The last line is followed by a final
     character (if non-nil)."

    ^ self
        from:firstLine to:lastLine 
        asStringWith:sepCharacter 
        compressTabs:compressTabs 
        final:endCharacter 
        withEmphasis:true

    "Modified: / 17.6.1998 / 12:31:19 / cg"
!

asStringWith:sepCharacter from:firstLine to:lastLine compressTabs:compressTabs final:endCharacter withEmphasis:withEmphasis
    "return part of myself as a string or text with embedded sepCharacters
     and followup endCharacter.
     My elements must be strings or nil; nil entries and empty strings are
     taken as empty lines.
     sepCharacter and endCharacter may be nil, a character or a string.
     If the argument compressTabs is true, leading spaces are converted
     to tab-characters (8col tabs). The last line is followed by a final
     character (if non-nil).
     The withEmphais argument controls if the returned string should preserve
     any emphasis. If false, a plain string is returned.
     This method is tuned for big collections, in not creating many
     intermediate strings (has linear runtime). For very small collections
     and small strings, it may be faster to use the comma , operation."

    ^ self
        from:firstLine to:lastLine 
        asStringWith:sepCharacter 
        compressTabs:compressTabs 
        final:endCharacter 
        withEmphasis:withEmphasis
!

asStringWithCRs
    "return a string generated by concatenating my elements 
     (which must be strings or nil) and embedding cr characters in between.
     Nil entries and empty strings are counted as empty lines."

    ^ self asStringWithCRsFrom:1 to:(self size)

    "
     #('hello' 'world' 'foo' 'bar' 'baz') asStringWithCRs 

     (OrderedCollection new
        add:'hello'; 
        add:'world';
        add:'foo';
        add:('bar' asText allBold);
        yourself) asStringWithCRs

     Transcript showCR:
         (OrderedCollection new
            add:'hello'; 
            add:'world';
            add:'foo';
            add:('bar' asText allBold);
            yourself) asStringWithCRs
    "

    "Modified: 18.5.1996 / 16:43:47 / cg"
!

asStringWithCRsFrom:firstLine to:lastLine
    "return a string generated by concatenating some of my elements 
     (which must be strings or nil) and embedding cr characters in between.
     Nil entries and empty strings are counted as empty lines."

    ^ self asStringWithCRsFrom:firstLine to:lastLine compressTabs:false withCR:true

    "
     #('hello' 'world' 'foo' 'bar' 'baz') asStringWithCRsFrom:2 to:4 

    "

    "Modified: 18.5.1996 / 16:50:55 / cg"
!

asStringWithCRsFrom:firstLine to:lastLine compressTabs:compressTabs
    "return part of myself as a string with embedded cr's.
     My elements must be strings or nil.
     If the argument compressTabs is true, leading spaces are converted
     to tab-characters (8col tabs).
     Nil entries and empty strings are taken as empty lines."

    ^ self asStringWithCRsFrom:firstLine to:lastLine compressTabs:compressTabs withCR:true
!

asStringWithCRsFrom:firstLine to:lastLine compressTabs:compressTabs withCR:withCR
    "return part of myself as a string with embedded cr's.
     My elements must be strings or nil; nil entries and empty strings are
     taken as empty lines.
     If the argument compressTabs is true, leading spaces are converted
     to tab-characters (8col tabs). WithCR controls whether the last line
     should be followed by a cr or not."

    ^ self asStringWith:(Character cr)
                   from:firstLine 
                     to:lastLine 
           compressTabs:compressTabs 
                  final:(withCR ifTrue:[Character cr] ifFalse:[nil])
!

decodeAsLiteralArray
    "given a literalEncoding in the receiver,
     create & return the corresponding object.
     The inverse operation to #literalArrayEncoding."

    |clsName cls loadOwnerOf|

    clsName := self first.
    clsName isSymbol ifFalse:[
        ^ MissingClassInLiteralArrayErrorSignal 
                raiseRequestWith:clsName 
                errorString:('not a className in literalArray-spec')
    ].
    cls := Smalltalk at:clsName ifAbsent:nil.
    cls isNil ifTrue:[
        "/ is it a private class of an autoloaded class ?
        loadOwnerOf := [:clsName |
                            |t ownerName owner|

                            t := clsName.
                            [(t indexOf:$:) ~~ 0] whileTrue:[
                                t := t copyTo:(t lastIndexOf:$:).
                                (t endsWith:$:) ifTrue:[t:= t copyWithoutLast:1].
                                (t endsWith:$:) ifTrue:[t:= t copyWithoutLast:1].
                                ownerName := t.
                                owner := Smalltalk at:ownerName asSymbol ifAbsent:nil.
                                owner isNil ifTrue:[
                                    loadOwnerOf value:ownerName.
                                    owner := Smalltalk at:ownerName asSymbol ifAbsent:nil.
                                ].
                                owner notNil ifTrue:[
                                    owner autoload
                                ].
                            ].
                        ].
        loadOwnerOf value:clsName.
        cls := Smalltalk at:clsName ifAbsent:nil.
        cls isNil ifTrue:[
            ^ MissingClassInLiteralArrayErrorSignal 
                    raiseRequestWith:clsName 
                    errorString:('unknown class in literalArray-spec: ' , clsName)
        ].
    ].
    ^ cls decodeFromLiteralArray:self.

    "
     #(Point 10 20) decodeAsLiteralArray  
     #(Rectangle 100 200 400 500) decodeAsLiteralArray 
     #(#MenuItem #rawLabel: 'right' #value: #right) decodeAsLiteralArray 
    "

    "Modified: / 18.5.1999 / 14:51:58 / cg"
!

from:firstLine to:lastLine asStringWith:sepCharacter 
    "return part of myself as a string with embedded sepCharacters.
     My elements must be strings or nil; nil entries and empty strings are
     taken as empty lines."

    ^ self 
        from:firstLine 
        to:lastLine
        asStringWith:sepCharacter 
        compressTabs:false
        final:nil
    "
     creating entries for searchpath:

     #('foo' 'bar' 'baz' '/foo/bar') asStringWith:$;   

     #('foo' 'bar' 'baz' '/foo/bar') from:1 to:3 asStringWith:$:    

     (#('foo' 'bar' 'baz' '/foo/bar') copyFrom:1 to:3) asStringWith:$:    
    "

    "Modified: 23.2.1996 / 15:28:55 / cg"
!

from:firstLine to:lastLine asStringWith:sepCharacter compressTabs:compressTabs final:endCharacter
    "return part of myself as a string or text with embedded sepCharacters.
     My elements must be strings or nil; nil entries and empty strings are
     taken as empty lines.
     If the argument compressTabs is true, leading spaces are converted
     to tab-characters (8col tabs). The last line is followed by a final
     character (if non-nil)."

    ^ self
        from:firstLine 
        to:lastLine 
        asStringWith:sepCharacter 
        compressTabs:compressTabs 
        final:endCharacter 
        withEmphasis:true

    "Modified: / 17.6.1998 / 12:31:19 / cg"
!

from:firstLine to:lastLine asStringWith:sepCharacter compressTabs:compressTabs final:endCharacter withEmphasis:withEmphasis
    "return part of myself as a string or text with embedded sepCharacters
     and followup endCharacter.
     My elements must be strings or nil; nil entries and empty strings are
     taken as empty lines.
     sepCharacter and endCharacter may be nil, a character or a string.
     If the argument compressTabs is true, leading spaces are converted
     to tab-characters (8col tabs). The last line is followed by a final
     character (if non-nil).
     The withEmphais argument controls if the returned string should preserve
     any emphasis. If false, a plain string is returned.
     This method is tuned for big collections, in not creating many
     intermediate strings (has linear runtime). For very small collections
     and small strings, it may be faster to use the comma , operation."

    |idx1        "{ Class:SmallInteger }"
     idx2        "{ Class:SmallInteger }"
     totalLength "{ Class:SmallInteger }"
     pos         "{ Class:SmallInteger }"
     sepCnt      "{ Class:SmallInteger }"
     newString lineString spaces idx nTabs 
     maxBitsPerCharacter stringClass needEmphasis newRuns c
     thisLen anyTab|

    "
     first accumulate the size of the string, to avoid
     countless reallocations. If tabs are compressed,
     the size computed is not exact, but gives an upper bound ...
     On the fly, look if a 16bit string or emphasized text is needed.
    "
    needEmphasis := false.
    maxBitsPerCharacter := 8.

    totalLength := 0.
    sepCharacter isNil ifTrue:[
        sepCnt := 0
    ] ifFalse:[
        sepCharacter isCharacter ifTrue:[
            sepCnt := 1
        ] ifFalse:[
            sepCnt := sepCharacter size
        ]
    ].

    idx1 := firstLine.
    idx2 := lastLine.
    idx1 to:idx2 do:[:lineIndex |
        lineString := self at:lineIndex.

        lineString notNil ifTrue:[
            withEmphasis ifTrue:[
                lineString hasChangeOfEmphasis ifTrue:[
                    needEmphasis := true
                ].
            ].
            maxBitsPerCharacter := maxBitsPerCharacter max:(lineString bitsPerCharacter).
            totalLength := totalLength + lineString size
        ].
        totalLength := totalLength + sepCnt
    ].
    totalLength := totalLength - sepCnt.

    maxBitsPerCharacter > 8 ifTrue:[
        maxBitsPerCharacter > 16 ifTrue:[
            stringClass := Unicode32String.
        ] ifFalse:[
            stringClass := Unicode16String.
        ]
    ] ifFalse:[
        stringClass := String.
    ].

    endCharacter notNil ifTrue:[
        endCharacter isCharacter ifTrue:[
            totalLength := totalLength + 1
        ] ifFalse:[
            totalLength := totalLength + endCharacter size
        ].
    ].
    totalLength <= 0 ifTrue:[^ ''].

    spaces := '        '.
    newString := stringClass new:totalLength.

    needEmphasis ifTrue:[
        newRuns := RunArray new.
    ].

    "
     now, replace ...
     Be careful with runArrays:
        replacing individual elements is VERY expensive.
        Therefore, create a new runArray from scratch.
    "
    pos := 1.
    idx1 to:idx2 do:[:lineIndex |
        lineString := self at:lineIndex.
        thisLen := lineString size.
        thisLen ~~ 0 ifTrue:[
            withEmphasis ifFalse:[
                lineString := lineString string.
            ].

            (anyTab := compressTabs) ifTrue:[
                "
                 mhmh: could use withTabs from String-class here,
                 but we should avoid creating too many temporary strings
                 (especially, since this method is typically used when converting
                 big texts such as when saving in the filebrowser ...).
                 Therefore, we convert tabs inline here doing a direct replace
                 in newString."

                idx := lineString findFirst:[:c | (c ~~ Character space)].
                nTabs := (idx-1) // 8.
                anyTab := (nTabs > 0)
            ].
            anyTab ifTrue:[
                "any tabs"

                idx := nTabs * 8 + 1.   "/ index of first copied character in string

                newString atAll:(pos to:pos+nTabs-1) put:(Character tab).
                newRuns notNil ifTrue:[
                    newRuns add:nil withOccurrences:nTabs
                ].
                pos := pos + nTabs.

                newString replaceFrom:pos with:lineString startingAt:idx.
                newRuns notNil ifTrue:[
                    lineString hasChangeOfEmphasis ifTrue:[
                        idx to:lineString size do:[:pos |
                            newRuns add:(lineString emphasisAt:pos)
                        ]    
                    ] ifFalse:[
                        newRuns add:nil withOccurrences:(lineString size - idx + 1)
                    ]
                ].
                pos := pos + thisLen - (nTabs * 8).
            ] ifFalse:[
                newString replaceFrom:pos with:lineString.

                newRuns notNil ifTrue:[
                    lineString hasChangeOfEmphasis ifTrue:[
                        newRuns addAll:(lineString emphasis)
                    ] ifFalse:[
                        newRuns add:nil withOccurrences:lineString size
                    ]
                ].
                pos := pos + thisLen.
            ].
        ].

        lineIndex ~~ lastLine ifTrue:[
            c := sepCharacter
        ] ifFalse:[
            c := endCharacter
        ].

        c notNil ifTrue:[
            c isCharacter ifTrue:[
                newString at:pos put:c.
                newRuns notNil ifTrue:[
                    newRuns add:nil.
                ].
                pos := pos + 1
            ] ifFalse:[
                newString replaceFrom:pos with:c.
                newRuns notNil ifTrue:[
                    newRuns add:nil withOccurrences:c size
                ].
                pos := pos + c size
            ]
        ].
    ].

    "
     in case of tab compression, the result has to be
     cut to size ... sorry
    "
    pos ~~ totalLength ifTrue:[
        newString := newString copyTo:(pos - 1)
    ].

    newRuns notNil ifTrue:[
        newString := Text string:newString runs:newRuns.
    ].

    ^ newString

    "
     creating entries for searchpath:

       #('foo' 'bar' 'baz' '/foo/bar') 
          asStringWith:$: 
          from:1 to:4 
          compressTabs:false 
          final:nil 

     with trailing colon:

       #('foo' 'bar' 'baz' '/foo/bar') 
          asStringWith:$: 
          from:1 to:4 
          compressTabs:false 
          final:$: 

     concatenating elements (nil sepChars and nil endChars):

       #('foo' 'bar' 'baz') 
          asStringWith:nil 
          from:1 to:3 
          compressTabs:false 
          final:nil  

     creating a string from a collection of lines:

       #('foo' 'bar' 'baz') 
          asStringWith:(Character cr) 
          from:1 to:3 
          compressTabs:false 
          final:(Character cr) 

     creating a text from a collection of mixed texts and strings:

       (Array
            with:'foo'
            with:('bar' asText allBold)
            with:'baz'
            with:('baz2' asText emphasizeAllWith:#italic)
       ) 
          asStringWith:(Character cr) 
          from:1 to:4 
          compressTabs:false 
          final:(Character cr) 

     can also use strings as separating characters:

       #('foo' 'bar' 'baz') 
          asStringWith:'__' 
          from:1 to:3 
          compressTabs:false 
          final:nil       

     and as final characters:

       #('foo' 'bar' 'baz') 
          asStringWith:'__' 
          from:1 to:3 
          compressTabs:false 
          final:'***'       

    "

    "Created: / 17.6.1998 / 12:30:32 / cg"
    "Modified: / 17.6.1998 / 12:31:59 / cg"
!

literalArrayEncoding
    "encode myself as an array literal, from which a copy of the receiver
     can be reconstructed with #decodeAsLiteralArray."

    |encoding idx|

    encoding := Array new:self size + 1.
    encoding at:1 put:self class name.
    idx := 2.
    self do:[:element| 
        encoding at:idx put:element literalArrayEncoding.
        idx := idx + 1.
    ].
    ^ encoding


    "
     (Array with:(Color red:50 green:50 blue:50)
            with:(1 @ 2)
     ) literalArrayEncoding decodeAsLiteralArray  
    "

    "Modified: 22.4.1996 / 13:00:56 / cg"
! !

!SequenceableCollection methodsFor:'converting-reindexed'!

from:startIndex 
    "Create a ReindexedCollection from the receiver.
     The new collection represents the elements starting at startIndex to the end.
     (i.e. logically it represents the receiver copyFrom:startIndex,
     however, physically, no copy is made).
     The slice shares the memory for the element-data with the original,
     thos means that any modifications in the original are visible in the slice
     and vice versa."

    ^ self
        from:startIndex
        to:self size
        by:1

    "
     #(1 2 3 4 5 6 7) from:3              
     ( #(1 2 3 4 5 6 7) from:3 ) first    
     ( #(1 2 3 4 5 6 7) from:3 ) last     
     ( #(1 2 3 4 5 6 7) from:3 ) size     
    "
!

from:startIndex by:step 
    "Create a ReindexedCollection from the receiver"

    ^ self
        from:startIndex
        to:(step > 1
            ifTrue: [self size]
            ifFalse: [1])
        by:step

    "
     #(1 2 3 4 5 6 7) from:3 by:2             
     ( #(1 2 3 4 5 6 7) from:3 by:2) first    
     ( #(1 2 3 4 5 6 7) from:3 by:2) last     
     ( #(1 2 3 4 5 6 7) from:3 by:2) size     
    "
!

from:startIndex count:numberOfElements
    "return a sub-collection consisting of numberOfElements elements
     in the receiver starting at index start (i.e. reference to a slice).
     The slice shares the memory for the element-data with the original,
     thos means that any modifications in the original are visible in the slice
     and vice versa."

    ^ self
        from:startIndex
        to:(startIndex + numberOfElements - 1)

    "
     #($a $b $c $d $e $f $g) from:2 count:3 
     '1234567890' from:2 count:5    
    "

    "
     |coll slice|

     coll := #(1 2 3 4 5 6 7 8 9 10) copy.
     slice := coll from:3 to:7.
     slice.    
     coll at:4 put:40.
     slice.      
    "

    "
     |coll slice|

     coll := #(1 2 3 4 5 6 7 8 9 10) copy.
     slice := coll from:3 to:7.
     slice.    
     slice at:1 put:40.
     slice.       
    "
!

from:startIndex to:endIndex 
    "Create a ReindexedCollection from the receiver.
     The new collection represents the elements starting at startIndex to endIndex.
     (i.e. logically it represents the receiver copyFrom:startIndex,
     however, physically, no copy is made).
     The slice shares the memory for the element-data with the original,
     thos means that any modifications in the original are visible in the slice
     and vice versa."

    ^ self
        from:startIndex
        to:endIndex
        by: (startIndex <= endIndex
            ifTrue: [1]
            ifFalse: [-1])

    "
     #(1 2 3 4 5 6 7) from:3 to:6             
     ( #(1 2 3 4 5 6 7) from:3 to:6) first    
     ( #(1 2 3 4 5 6 7) from:3 to:6) last     
     ( #(1 2 3 4 5 6 7) from:3 to:6) size     
    "
!

from:startIndex to:endIndex by:step 
    "Create a ReindexedCollection from the receiver"

    ^ ReindexedCollection
        on:self
        from:startIndex
        to:endIndex
        by:step

    "
     #(1 2 3 4 5 6 7) from:3 to:7 by:2             
     ( #(1 2 3 4 5 6 7) from:3 to:7 by:2) first    
     ( #(1 2 3 4 5 6 7) from:3 to:7 by:2) last     
     ( #(1 2 3 4 5 6 7) from:3 to:7 by:2) size     
    "
!

to:endIndex 
    "Create a ReindexedCollection from the receiver.
     The new collection represents the receivers elements up to endIndex.
     (i.e. logically it represents the receiver copyTo:endIndex,
     however, physically, no copy is made).
     The slice shares the memory for the element-data with the original,
     thos means that any modifications in the original are visible in the slice
     and vice versa."

    ^ self
        from:1
        to:endIndex
        by:1

    "
     #(1 2 3 4 5 6 7) to:4             
     ( #(1 2 3 4 5 6 7) to:4) first    
     ( #(1 2 3 4 5 6 7) to:4) last     
     ( #(1 2 3 4 5 6 7) to:4) size     
    "
!

to:endIndex by:step 
    "Create a ReindexedCollection from the receiver"

    ^ self
        from:(step > 0
            ifTrue: [1]
            ifFalse: [self size])
        to:endIndex
        by:step

    "
     #(1 2 3 4 5 6 7) to:4 by:2            
     ( #(1 2 3 4 5 6 7) to:4 by:2) first    
     ( #(1 2 3 4 5 6 7) to:4 by:2) last     
     ( #(1 2 3 4 5 6 7) to:4 by:2) size     
    "
! !

!SequenceableCollection methodsFor:'copying'!

, aCollection
    "return a new collection formed from concatenating the receiver with
     the argument. The class of the new collection is determined by the
     receivers class, so mixing classes is possible, if the second collections
     elements can be stored into instances of the receivers class."

    |newCollection 
     mySize    "{ Class: SmallInteger }"
     newSize   "{ Class: SmallInteger }"
     otherSize "{ Class: SmallInteger }"
     dstIndex  "{ Class: SmallInteger }"|

    mySize := self size.
    otherSize := aCollection size.
    newSize := mySize + otherSize.

    newCollection := self copyEmptyAndGrow:newSize.   "must grow, otherwise replace fails"

    newCollection replaceFrom:1 to:mySize with:self startingAt:1.
    dstIndex := mySize + 1.
    aCollection isSequenceable 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

    "
     #($a $b $c) , #(1 2 3)
     #($a $b $c) , '123'
     'abc' , '123'
     'abc' , #($q $w $e $r $t $y) asSortedCollection
     'abc' , #(1 2 3 4 5)"  "-- will fail, since strings cannot store integers
     'abc' asArray , #(1 2 3 4 5)
    "
!

copyButFirst:count
    "return a new collection consisting of the receivers elements
     except for the first count elements - for convenience."

    ^ self copyFrom:(count + 1)

    "
     #($a $b $c $d $e $f $g) copyButFirst:2 
     '1234567890' copyButFirst:2
    "
!

copyButLast:count
    "return a new collection consisting of the receivers elements
     except for the last count elements - for convenience."

    ^ self copyTo:(self size - count)

    "
     #($a $b $c $d $e $f $g) copyButLast:2 
     '1234567890' copyButLast:2 
    "
!

copyFirst:count
    "return a new collection consisting of the receivers first count
     elements - this is just a rename of copyTo: - for compatibility."

    ^ self copyFrom:1 to:count

    "
     #($a $b $c $d $e $f $g) copyFirst:5
     '1234567890' copyFirst:4
    "
!

copyFrom:startIndex
    "return a new collection consisting of receivers elements
     from start to the end of the collection.
     Return an empty collection, if startIndex is beyond the receivers size."

    ^ self copyFrom:startIndex to:(self size)

    "
     #($a $b $c $d $e $f $g) copyFrom:2
     '1234567890' copyFrom:2
     (10 to:19) copyFrom:5  
    "
!

copyFrom:startIndex count:numberOfElements
    "return a new collection consisting of numberOfElements elements
     extracted from the receiver starting at index start
     (i.e. extract a slice).
     Returns an empty collection if startIndex is beyond the receivers size.
     Raise an error, if stopIndex is out of range."

    ^ self
        copyFrom:startIndex
        to:(startIndex + numberOfElements - 1)

    "
     #($a $b $c $d $e $f $g) copyFrom:2 count:3 
     '1234567890' copyFrom:2 count:5    
    "

    "Modified: 20.2.1997 / 14:23:01 / cg"
!

copyFrom:startIndex to:stopIndex
    "return a new collection consisting of receivers elements
     between start and stop.
     Returns an empty collection if startIndex is beyond the receivers size.
     Raise an error, if stopIndex is out of range."

    |newCollection newSize|

    newSize := stopIndex - startIndex + 1.
    newSize < 0 ifTrue:[
        newSize := 0
    ].
    newCollection := self copyEmptyAndGrow:newSize.
    newCollection replaceFrom:1 to:newSize with:self startingAt:startIndex.
    ^ newCollection

    "
     #($a $b $c $d $e $f $g) copyFrom:2 to:5
     '1234567890' copyFrom:2 to:5
     (1 to:10) copyFrom:2 to:5  

     '1234567890' copyFrom:2 to:15     
     (1 to:10) copyFrom:12 to:15  
    "
!

copyLast:count
    "return a new collection consisting of the receivers last count
     elements."

    |sz|

    sz := self size.
    ^ self copyFrom:(sz - count + 1) to:sz

    "
     #($a $b $c $d $e $f $g) copyLast:5
     '1234567890' copyLast:4
    "
!

copyReplaceAll:oldElement with:newElement
    "return a copy of the receiver, where all elements equal to oldElement
     have been replaced by newElement."

"/    'Warning: #copyReplaceAll:with: will change semantics as defined in ANSI soon' errorPrintCR.
    ^ self copy replaceAll:oldElement with:newElement

    "
     #(1 2 1 2 1 2 1 2 1 2) copyReplaceAll:1 with:99 
     'hello world' copyReplaceAll:$l with:$*         
    "

    "Modified: / 18.7.1998 / 22:52:17 / cg"
!

copyReplaceAll:oldObject withAll:aCollection
    "return a copy, where all oldObjects are replaced by all
     elements from aCollection (i.e. sliced in).
     Non-destructive; returns a new collection.
     The implementation here is a general-purpose one;
     and should be redefined in String, if heavily used."

    |s|

"/    'Warning: #copyReplaceAll:withAll: will change semantics as defined in ANSI soon' errorPrintCR.

    s := WriteStream on:self species new.
    self do:[:el |
        el = oldObject ifTrue:[
            aCollection do:[:el2 |
                s nextPut:el2
            ]
        ] ifFalse:[
            s nextPut:el
        ]
    ].
    ^ s contents

    "
     args:    oldObject  : <object>
              newObject  : <collection>

     returns: newCollection
    "

    "
     '123123abc123' copyReplaceAll:$1 withAll:'one'    
     #(1 2 3 4 1 2 3 4) copyReplaceAll:1 withAll:'one' 
    "
!

copyReplaceFrom:startIndex to:endIndex with:aCollection
    "return a copy of the receiver, where the elements from startIndex to
     endIndex have been replaced by the elements of aCollection"

    |newColl sz replSize|

    replSize := aCollection size.
    sz := self size - (endIndex - startIndex + 1) + replSize.
    newColl := self copyEmptyAndGrow:sz.
    newColl replaceFrom:1 to:(startIndex - 1) with:self.
    newColl replaceFrom:startIndex with:aCollection.
    newColl replaceFrom:(startIndex + replSize) with:self startingAt:(endIndex + 1).
    ^ newColl

    "
     #(1 2 3 4 5 6 7 8 9 0) copyReplaceFrom:3 to:6 with:#(a b c d e f g h i j k)
     'hello world' copyReplaceFrom:6 to:6 with:' there, '  
    "
!

copyReplaceFrom:startIndex with:aCollection
    "return a copy of the receiver, where the elements from startIndex to
     the end have been replaced by the elements of aCollection"

    ^ self copyReplaceFrom:startIndex to:(self size) with:aCollection

    "
     #(1 2 3 4 5 6 7 8 9 0) copyReplaceFrom:3 with:#(a b c)  
     'hello world' copyReplaceFrom:7 with:'smalltalk fan'  
    "
!

copyReplacing:oldElement withObject:newElement
    "return a copy of the receiver, where all elements equal to oldElement
     have been replaced by newElement.
     ANSI version of what used to be #copyReplaceAll:with:"

    ^ self copy replaceAll:oldElement with:newElement

    "
     #(1 2 1 2 1 2 1 2 1 2) copyReplacing:1 withObject:99 
     'hello world' copyReplacing:$l withObject:$*         
    "
!

copyThrough:element
    "return a new collection consisting of the receiver elements
     up-to (AND including) the first occurence of element."

    |idx|

    idx := self indexOf:element.
    idx == 0 ifTrue:[^ nil].    "question: is this ok?"
    ^ self copyFrom:1 to:idx

    "
     #($a $b $c $d $e $f $g) copyThrough:$d
     '1234567890' copyThrough:$5
     '1234567890' copyThrough:$a
     '1234567890' copyThrough:$1
    "
!

copyTo:stopIndex
    "return a new collection consisting of receivers elements
     from 1 up to (including) stopIndex.
     Raise an error, if stopIndex is out of range."

    ^ self copyFrom:1 to:stopIndex

    "
     #($a $b $c $d $e $f $g) copyTo:5
     '1234567890' copyTo:4
    "
!

copyToMax:stop
    "return a new collection consisting of receivers elements
     from 1 up to (including) index stop, or up to the receivers end, 
     whichever is smaller (i.e. like copyTo:, but do not err if receiver is smaller"

    ^ self copyFrom:1 to:(self size min:stop)

    "
     #($a $b $c $d $e $f $g) copyTo:10  - raises an error
     #($a $b $c $d $e $f $g) copyToMax:10
    "
!

copyUpTo:element
    "return a new collection consisting of the receiver elements
     up-to (but excluding) the first occurence of element;
     or to the end, if element is not included"

    |idx|

    idx := self indexOf:element.
    idx == 0 ifTrue:[^ self copy].    "question: is this ok?"
    idx == 1 ifTrue:[^ self copyEmpty].
    ^ self copyFrom:1 to:(idx-1)

    "
     #($a $b $c $d $e $f $g) copyUpTo:$d
     '1234567890' copyUpTo:$5
     '1234567890' copyUpTo:$a
     '1234567890' copyUpTo:$1
     '123456789' copyUpTo:$0
    "
!

copyWith:newElement
    "return a new collection containing the receivers elements
     and the single new element, newElement. 
     This is different from concatentation, which expects another collection
     as argument, but equivalent to copy-and-addLast."

    |newCollection mySize newSize|

    mySize := self size.
    newSize := mySize + 1.
    newCollection := self copyEmptyAndGrow:newSize.
    newCollection replaceFrom:1 to:mySize with:self startingAt:1.
    newCollection at:newSize put:newElement.
    ^newCollection

    "
     #(1 2 3 4 5) copyWith:$a
     'abcdefg' copyWith:$h
     'abcdefg' copyWith:'123'   -- will fail: string cannot be stored into string
     'abcdefg' copyWith:1       -- will fail: integer cannot be stored into string
    "
!

copyWithout:elementToSkip
    "return a new collection consisting of a copy of the receiver, with
     ALL elements equal to elementToSkip are left out.
     No error is reported, if elementToSkip is not in the collection."

    |n         "{ Class: SmallInteger }"
     sz        "{ Class: SmallInteger }"
     srcIndex  "{ Class: SmallInteger }"
     dstIndex  "{ Class: SmallInteger }"
     skipIndex "{ Class: SmallInteger }"
     copy l|

    "the code below may look like overkill, 
     however, for big collections its better to move data
     around in big chunks"

    n := self occurrencesOf:elementToSkip.
    n == 0 ifTrue:[^ self copy].

    sz := self size.
    copy := self copyEmptyAndGrow:(sz - n).

    srcIndex := 1.
    dstIndex := 1.

    n timesRepeat:[
        skipIndex := self indexOf:elementToSkip startingAt:srcIndex.
        l := skipIndex - srcIndex.
        l ~~ 0 ifTrue:[
            copy replaceFrom:dstIndex to:(dstIndex + l - 1) 
                        with:self startingAt:srcIndex.
            dstIndex := dstIndex + l
        ].
        srcIndex := skipIndex + 1
    ].
    l := sz - srcIndex.
    copy replaceFrom:dstIndex to:(dstIndex + l)
                with:self startingAt:srcIndex.
    ^ copy

    "
     #($a $b $c $d $e $f $g) copyWithout:$d
     #($a $b $c $d $e $f $g) copyWithout:$a
     #($a $b $c $d $e $f $g) copyWithout:$g
     'abcdefghi' copyWithout:$h    
     'abcdefg' copyWithout:$h       
     #($a $b $c $a $a $d $e $a $f $g) copyWithout:$a
     #($a $b $c $d $e $f $g) copyWithout:$x
     #(90 80 70 60 50) copyWithout:70
     #(90 80 70 80 60 45 80 50) copyWithout:80
    "
!

copyWithoutFirst:elementToSkip
    "return a new collection consisting of a copy of the receivers elements
     without the first elementToSkip, if it was present. 
     No error is reported, if elementToSkip is not in the collection.
     Do not confuse this with copyButFirst:"

    |copy skipIndex sz|

    skipIndex := self indexOf:elementToSkip startingAt:1.
    (skipIndex == 0) ifTrue:[^ self copy].

    sz := self size - 1.
    copy := self copyEmptyAndGrow:sz.
    copy replaceFrom:1 to:(skipIndex - 1) with:self startingAt:1.
    copy replaceFrom:skipIndex to:sz with:self startingAt:(skipIndex + 1).
    ^ copy

    "
     #($a $b $c $d $e $f $g) copyWithoutFirst:$d
     #($a $b $c $d $e $f $g) copyWithoutFirst:$x
     #(90 80 70 60 50) copyWithoutFirst:70
     #(90 80 70 80 60 45 80 50) copyWithoutFirst:80
    "
!

copyWithoutIndex:omitIndex
    "return a new collection consisting of receivers elements
     without the argument stored at omitIndex"

    |copy sz|

    sz := self size - 1.
    copy := self copyEmptyAndGrow:sz.
    copy replaceFrom:1 to:(omitIndex - 1) with:self startingAt:1.
    copy replaceFrom:omitIndex to:sz with:self startingAt:(omitIndex + 1).
    ^ copy

    "
     #(1 2 3 4 5 6 7 8 9 0) copyWithoutIndex:3
     'abcdefghijkl' copyWithoutIndex:5
    "
!

copyWithoutLast:count
    "return a new collection consisting of the receivers elements
     except the last count elements.
     That is the same as copyButLast: and badly named (for compatibility),
     because the name may confuse users with the copyWithoutFirst: functionality.
     Please use copyButLast:."

    ^ self copyTo:(self size - count)

    "
     #($a $b $c $d $e $f $g) copyWithoutLast:5 
     '1234567890' copyWithoutLast:4 
    "
!

restAfter:anElement
    "return a new collection consisting of the receivers elements after
     (but excluding) anElement.
     If anElement is not in the receiver, the returned collection
     will be empty.
     See also #upTo:."

    |pos|

    pos := self indexOf:anElement.
    pos == 0 ifTrue:[^ self copyEmpty].

    ^ self copyFrom:(pos + 1)

    "
     #(1 2 3 4 5 6 7 8 9) upTo:5  
     #(1 2 3 4 5 6 7 8 9) restAfter:5  
     'hello world' upTo:Character space  
     'hello world' restAfter:Character space  
     '1234.5678' upTo:$.  
     '1234.5678' restAfter:$.  
    "
!

upTo:anElement
    "return a new collection consisting of the receivers elements upTo
     (but excluding) anElement.
     If anElement is not in the receiver, the returned collection
     will consist of all elements of the receiver.
     See also #restAFter:  , #copyFrom:index."

    |pos|

    pos := self indexOf:anElement.
    pos == 0 ifTrue:[^ self copy].

    ^ self copyFrom:1 to:(pos - 1)

    "
     #(1 2 3 4 5 6 7 8 9) upTo:5  
     'hello world' upTo:Character space  
     #(9 8 7 6 5 4 3 2 1) asSortedCollection upTo:5 
     '1234.5678' upTo:$.  
     '1234'      upTo:$.  

     raises an error:

     (Dictionary new 
        at:#foo put:'foo';
        at:#bar put:'bar';
        at:#baz put:'baz';
        yourself) upTo:#bar
                
    "

    "Modified: 11.5.1996 / 11:14:05 / cg"
!

upTo:anElement count:count
    "return a new collection consisting of the receivers elements upTo
     (but excluding) count found anElements, i.e. the first found count-1 
     elements are included in the returned collection; if count < 0 the 
     procedure is done from the end of the collection backwards.
     If anElement is not in the receiver, the returned collection
     will consist of all elements of the receiver"

    |startPos endPos pos found|

    (count == 0 or: [count == 1]) ifTrue:[
        ^ self upTo:anElement
    ].

    startPos := 1.
    endPos   := self size.
    found    := 0.

    count > 1 ifTrue:[
        pos := 0.
        [pos < self size and: [found < count]]
            whileTrue: [pos := pos + 1. (self at: pos) == anElement ifTrue: [found := found + 1]].
        found == count ifTrue:[
            endPos   := pos - 1
        ]
    ].     

    count < 0 ifTrue:[
        pos := self size + 1.
        [pos > 1 and: [found < count abs]]
            whileTrue: [pos := pos - 1. (self at: pos) == anElement ifTrue: [found := found + 1]].
        found == count abs ifTrue:[
            startPos := pos + 1
        ]
    ].    

    ^ self copyFrom: startPos to: endPos

    "
     'hello1_hello2_hello3' upTo:$_ count:  2     returns first two 'hellos' 
     'hello1_hello2_hello3' upTo:$_ count: -1     returns last 'hello'
     'hello1_hello2_hello3' upTo:$_ count: 0      returns first 'hello1'
     'hello1_hello2_hello3' upTo:$_ count: 1      returns first 'hello1'
     'hello1_hello2_hello3' upTo:$_               same; returns first 'hello1'
    "
!

upToAny:aCollectionOfObjects
    "return a new collection consisting of the receivers elements upTo
     (but excluding) any in aCollectionOfObjects.
     If none of aCollectionOfObjects is found in the receiver, the returned collection
     will consist of all elements of the receiver.
     See also #upTo:"

    |pos|

    pos := self indexOfAny:aCollectionOfObjects.
    pos == 0 ifTrue:[^ self copy].

    ^ self copyFrom:1 to:(pos - 1)

    "
     'hello world' upToAny:#($/ $:)  
     'hello:world' upToAny:#($/ $:)  
     'hello/world' upToAny:#($/ $:)  
    "
! !

!SequenceableCollection methodsFor:'enumerating'!

collect:aBlock
    "evaluate the argument, aBlock for every element in the collection
     and return a collection of the results"

    |newCollection
     sz  "{ Class:SmallInteger }"|

    sz := self size.
    newCollection := self copyEmptyAndGrow:sz.
    1 to:sz do:[:index |
        newCollection at:index put:(aBlock value:(self at:index)).
    ].
    ^ newCollection

    "
     #(one two three four five six) collect:[:element | element asUppercase]  
     #(1 2 3 4 5 6 7 8 9) collect:[:element | element factorial]   
     (1 to:9) collect:[:element | element * element]   
    "
!

do:aBlock
    "evaluate the argument, aBlock for every element in the collection."

    |stop "{ Class:SmallInteger }"|

    stop := self size.
    1 to:stop do:[:index |
        aBlock value:(self at:index).
    ]

    "
     #(one two three four five six) do:[:element | Transcript showCR:element]
    "
!

do:aBlock separatedBy:sepBlock
    "evaluate the argument, aBlock for every element in the collection.
     Between each element (i.e. not before the first element and not after the
     last element), evaluate sepBlock.
     This supports printing of collections with elements separated by some
     string."

    |stop "{ Class:SmallInteger }"|

    stop := self size.
    stop < 1 ifTrue:[^ self].
    aBlock value:(self at:1).
    2 to:stop do:[:index |
        sepBlock value.
        aBlock value:(self at:index)
    ].

    "
     #(one two three four five six)
        do:[:each | Transcript show:each]
        separatedBy:[Transcript show:' , ']
    "
!

doWithIndex:aBlock
    "Squeak compatibility; like keysAndValuesDo:, but passes
     the index as second argument."

    self keysAndValuesDo:[:index :value |
        aBlock value:value value:index
    ].

    "Created: 17.10.1997 / 12:33:10 / cg"
!

from:start collect:aBlock
    "evaluate the argument, aBlock for the elements starting at start
     to the end and return a collection of the results"

    ^ self from:start to:self size collect:aBlock

    "
     #(one two three four five six) 
        from:2 
        collect:[:element | element asUppercase]  
    "

    "Created: / 30.1.2000 / 01:02:28 / cg"
!

from:startIndex do:aBlock
    "evaluate the argument, aBlock for the elements starting with the
     element at startIndex to the end."

    ^ self from:startIndex to:self size do:aBlock

    "
     #(one two three four five six) 
        from:3 
        do:[:element | Transcript showCR:element]
    "
!

from:startIndex keysAndValuesDo:aBlock
    "evaluate the argument, aBlock for the elements and indices starting with the
     element at startIndex to the end."

    ^ self from:startIndex to:self size keysAndValuesDo:aBlock

    "
     #(one two three four five six) 
        from:3 
        keysAndValuesDo:[:element :idx | Transcript showCR:(idx -> element) ]
    "
!

from:index1 to:index2 by:stepArg do:aBlock
    "evaluate the argument, aBlock for the elements with index index1 to index2 stepping by step in the collection"

    |start "{ Class:SmallInteger }"
     stop  "{ Class:SmallInteger }"
     step  "{ Class:SmallInteger }" |

    start := index1. "/ these assignments force type checking...
    stop := index2.  "/ and guarantee inline loop code below.
    step := stepArg.

    start to:stop by:step do:[:index |
        aBlock value:(self at:index).
    ]

    "
     #(one two three four five six seven eight nine ten) 
        from:2 
        to:10 
        by:2
        do:[:element | Transcript showCR:element]
    "
!

from:start to:stop collect:aBlock
    "evaluate the argument, aBlock for the elements indexed by start
     to stop in the collection and return a collection of the results"

    |newCollection sz
     idx  "{ Class:SmallInteger }"|

    sz := stop - start + 1.
    newCollection := self copyEmptyAndGrow:sz.
    idx := 1.
    start to:stop do:[:index |
        newCollection at:idx put:(aBlock value:(self at:index)).
        idx := idx + 1
    ].
    ^ newCollection

    "
     #(one two three four five six) 
        from:2 
        to:4 
        collect:[:element | element asUppercase]  
    "
!

from:index1 to:index2 do:aBlock
    "evaluate the argument, aBlock for the elements with index index1 to
     index2 in the collection"

    |start "{ Class:SmallInteger }"
     stop  "{ Class:SmallInteger }" |

    start := index1. "/ these assignments force type checking...
    stop := index2.  "/ and guarantee inline loop code below.

    start to:stop do:[:index |
        aBlock value:(self at:index).
    ]

    "
     #(one two three four five six) 
        from:3 
        to:5 
        do:[:element | Transcript showCR:element]
    "
!

from:index1 to:index2 keysAndValuesDo:aBlock
    "evaluate the argument, aBlock for the elements with index index1 to
     index2 in the collection; pass both index and value."

    |start "{ Class:SmallInteger }"
     stop  "{ Class:SmallInteger }" |

    start := index1. "/ these assignments force type checking...
    stop := index2.  "/ and guarantee inline loop code below.

    start to:stop do:[:index |
        aBlock value:index value:(self at:index).
    ]

    "
     #(one two three four five six) 
        from:3 
        to:5 
        keysAndValuesDo:[:idx :element | Transcript show:idx; space; showCR:element]
    "
!

from:index1 to:index2 reverseDo:aBlock
    "evaluate the argument, aBlock for the elements with index index1 to
     index2 in the collection. Step in reverse order"

    |start "{ Class:SmallInteger }"
     stop  "{ Class:SmallInteger }" |

    start := index1. "/ these assignments force type checking...
    stop := index2.  "/ and guarantee inline loop code below.

    stop to:start by:-1 do:[:index |
        aBlock value:(self at:index).
    ]

    "
     #(one two three four five six) 
        from:3 
        to:5 
        reverseDo:[:element | Transcript showCR:element]
    "
!

from:startIndex to:stopIndex select:aBlock
    "evaluate the argument, aBlock for the elements at startIndex..stopIndex
     and return a collection of those elements for which the block return true."

    |element newColl species needCopy
     n  "{ Class:SmallInteger }"|

    n := stopIndex - startIndex + 1.
    species := self species.
    species growIsCheap ifFalse:[
        newColl := OrderedCollection new:n.
        needCopy := true
    ] ifTrue:[
        newColl := self copyEmpty:n.
        needCopy := false
    ].
    startIndex to:stopIndex do:[:index |
        element := self at:index.
        (aBlock value:element) ifTrue:[
            newColl add:element
        ].
    ].
    needCopy ifTrue:[
        newColl := (species withAll:newColl) postCopyFrom:self
    ].
    ^ newColl

    "
     #(faba one two three four five six) 
        from:2 to:5 select:[:element | element startsWith:'f']      
    "
!

inGroupsOf:n collect:aBlock
    "evaluate the argument, aBlock for every group of n elements in the collection,
     and collect the results.
     The block is called with n arguments for group of n consecutive elements in the receiver.
     An error will be reported, if the number of elements in the receiver
     is not a multiple of n."

    |stop "{ Class:SmallInteger }" newCollection dstIdx argVector rslt|

    stop := self size.
    newCollection := self copyEmptyAndGrow:stop // n.
    dstIdx := 1.

    n == 2 ifTrue:[
        1 to:stop by:n do:[:index |
            rslt := aBlock value:(self at:index) value:(self at:index+1).
            newCollection at:dstIdx put:rslt.
            dstIdx := dstIdx + 1.
        ].
        ^ newCollection.
    ].
    n == 3 ifTrue:[
        1 to:stop by:n do:[:index |
            rslt := aBlock value:(self at:index) value:(self at:index+1) value:(self at:index+2).
            newCollection at:dstIdx put:rslt.
            dstIdx := dstIdx + 1.
        ].
        ^ newCollection.
    ].

    argVector := Array new:n.
    1 to:stop by:n do:[:index |
        argVector replaceFrom:1 to:n with:self startingAt:index.
        rslt := aBlock valueWithArguments:argVector.
        newCollection at:dstIdx put:rslt.
        dstIdx := dstIdx + 1.
    ].
    ^ newCollection

    "for groups of 2, this is the same as:
     #(1 one 2 two 3 three 4 four 5 five 6 six) 
         pairWiseCollect:[:num :sym | num->sym]  

     #(1 one 2 two 3 three 4 four 5 five 6 six) 
         inGroupsOf:2 collect:[:num :sym | num->sym]

     #( 1 2 3 4 5    6 7 8 9 10   11 12 13 14 15   16 17 18 19 20 )
         inGroupsOf:5 collect:[:a :b :c :d :e | Array with:a with:b with:c with:d with:e]
    "
!

inGroupsOf:n do:aBlock
    "evaluate the argument, aBlock for every group of n elements in the collection.
     The block is called with n arguments for group of n consecutive elements in the receiver.
     An error will be reported, if the number of elements in the receiver
     is not a multiple of n."

    |stop "{ Class:SmallInteger }" argVector|

    stop := self size.

    n == 2 ifTrue:[
        1 to:stop by:n do:[:index |
            aBlock value:(self at:index) value:(self at:index+1).
        ].
        ^ self.
    ].
    n == 3 ifTrue:[
        1 to:stop by:n do:[:index |
            aBlock value:(self at:index) value:(self at:index+1) value:(self at:index+2).
        ].
        ^ self.
    ].
    n == 4 ifTrue:[
        1 to:stop by:n do:[:index |
            aBlock value:(self at:index) value:(self at:index+1) value:(self at:index+2) value:(self at:index+3).
        ].
        ^ self.
    ].

    argVector := Array new:n.

    1 to:stop by:n do:[:index |
        argVector replaceFrom:1 to:n with:self startingAt:index.
        aBlock valueWithArguments:argVector.
    ].

    "for groups of 2, this is the same as:
     #(1 one 2 two 3 three 4 four 5 five 6 six) 
         pairWiseDo:[:num :sym | Transcript show:num; show:' is: '; showCR:sym]

     #(1 one 2 two 3 three 4 four 5 five 6 six) 
         inGroupsOf:2 do:[:num :sym | Transcript show:num; show:' is: '; showCR:sym]

     #( 1 2 3 4 5    6 7 8 9 10   11 12 13 14 15   16 17 18 19 20 )
         inGroupsOf:5 do:[:a :b :c :d :e | Transcript show:a;space;show:b;space;show:c;space;show:d;space;showCR:e]
    "
!

keysAndValuesDo:aTwoArgBlock
    "evaluate the argument, aBlock for every element in the collection,
     passing both index and element as arguments."

    |stop  "{ Class:SmallInteger }"|

    stop := self size.
    1 to:stop do:[:index |
        aTwoArgBlock value:index value:(self at:index).
    ]
    "
     #(one two three four five six) 
        keysAndValuesDo:[:key :element | 
                            Transcript show:key; space; showCR:element
                        ]
    "
!

keysAndValuesReverseDo:aTwoArgBlock
    "evaluate the argument, aBlock in reverse order, for every element 
     in the collection, passing both index and element as arguments."

    |stop  "{ Class:SmallInteger }"|

    stop := self size.
    stop to:1 by:-1 do:[:index |
        aTwoArgBlock value:index value:(self at:index).
    ]

    "
     #(one two three four five six) 
        keysAndValuesReverseDo:[:key :element | 
                                    Transcript show:key; space; showCR:element
                               ]
    "

    "Modified: 9.5.1996 / 00:57:23 / cg"
!

nonNilElementsDo:aBlock
    "evaluate the argument, aBlock for every non-nil element in the collection."

    |stop "{ Class:SmallInteger }"
     element|

    stop := self size.
    1 to:stop do:[:index |
        (element := self at:index) notNil ifTrue:[
            aBlock value:element.
        ]
    ]
    "
     #(one nil three nil five nil seven) nonNilElementsDo:[:element | Transcript showCR:element]
    "
!

pairWiseCollect:aBlock
    "evaluate the argument, aBlock for every pair of elements in the collection.
     The block is called with 2 arguments for each 2 elements in the receiver.
     An error will be reported, if the number of elements in the receiver
     is not a multiple of 2.
     Collect the results and return a new collection containing those."

    ^ self inGroupsOf:2 collect:aBlock

    "
     #(1 one 2 two 3 three 4 four 5 five 6 six) 
         pairWiseCollect:[:num :sym | sym->num]  


     #(1 1  1 2  1 3  1 4  1 5) 
         pairWiseCollect:[:x :y | x@y]   
    "
!

pairWiseDo:aBlock
    "evaluate the argument, aBlock for every pair of elements in the collection.
     The block is called with 2 arguments for each 2 elements in the receiver.
     An error will be reported, if the number of elements in the receiver
     is not a multiple of 2."

    ^ self inGroupsOf:2 do:aBlock

    "
     #(1 one 2 two 3 three 4 four 5 five 6 six) 
         pairWiseDo:[:num :sym | Transcript show:num; show:' is: '; showCR:sym]


     #(1 1  1 2  1 3  1 4  1 5) 
         pairWiseDo:[:x :y | Transcript showCR:x@y]
    "
!

reverseDo:aBlock
    "evaluate the argument, aBlock for every element in the collection
     in reverse order"

    |sz  "{ Class:SmallInteger }"|

    sz := self size.
    sz to:1 by:-1 do:[:index |
        aBlock value:(self at:index).
    ]

    "
     #(one two three four five six) reverseDo:[:element | Transcript showCR:element]
    "
!

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 species needCopy
     sz  "{ Class:SmallInteger }"|

    sz := self size.
    species := self species.
    species growIsCheap ifFalse:[
        newColl := OrderedCollection new:sz.
        needCopy := true
    ] ifTrue:[
        newColl := self copyEmpty:sz.
        needCopy := false
    ].
    1 to:sz do:[:index |
        element := self at:index.
        (aBlock value:element) ifTrue:[
            newColl add:element
        ].
    ].
    needCopy ifTrue:[
        newColl := (species withAll:newColl) postCopyFrom:self
    ].
    ^ newColl

    "
     #(one two three four five six) select:[:element | element startsWith:'f']   
     #(1 2 3 4 5 6 7 8 9) select:[:element | element odd]   
     (#(17 12 1 98 51) asSortedCollection:[:a :b | b < a]) select:[:element | element odd]   
     (1 to:9) select:[:element | element odd]   
     (Smalltalk allClasses) select:[:class | class name startsWith:'S']   
    "
!

with:aSequenceableCollection do:aTwoArgBlock
    "evaluate the argument, aBlock for successive elements from
     each the receiver and the argument, aSequenceableCollection.
     The second argument, aBlock must be a two-argument block.
     The collection argument must implement access via a numeric key."

    |stop  "{ Class: SmallInteger }" |

    stop := self size.
    1 to:stop do:[:index |
        aTwoArgBlock value:(self at:index) value:(aSequenceableCollection at:index).
    ]
    "
     #(one two three four five six) 
        with:(1 to:10) 
        do:[:el1 :el2 | Transcript show:el1; space; showCR:el2]
    "
! !

!SequenceableCollection methodsFor:'filling & replacing'!

atAllPut:anObject
    "replace all elements of the collection by the argument, anObject.
     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    self from:1 to:(self size) put:anObject

    "
     args:    anObject : <object>

     returns: self
    "

    "
     (Array new:10) atAllPut:1
     (String new:10) atAllPut:$a
    "

    "Modified: / 20.5.1998 / 15:14:11 / cg"
!

from:index1 to:index2 put:anObject
    "replace the elements from index1 to index2 of the collection
     by the argument, anObject.
     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    |index "{ Class: SmallInteger }"
     end   "{ Class: SmallInteger }"|

    index := index1.
    end := index2.
    [index <= end] whileTrue:[
        self at:index put:anObject.
        index := index + 1
    ]

    "
     args:    index1    : <integer>
              index2    : <integer>
              anObject  : <object>

     returns: self
    "

    "
     #(1 2 3 4 5 6 7 8 9 0) from:3 to:6 put:$X
     'abcdefghijkl' from:3 to:6 put:$X
    "

    "Modified: / 20.5.1998 / 15:16:52 / cg"
!

replaceAll:oldObject by:newObject
    "backward ST/X compatibility: an alias for #replaceAll:with:.
     Pleace do no longer use this one;
     instead use #replaceAll:with: for ST-80 compatibility."

    <resource:#obsolete>

    self obsoleteMethodWarning:'use #replaceAll:with:'.
    ^ self replaceAll:oldObject with:newObject

    "
     args:    oldObject  : <object>
              newObject  : <object>

     returns: self
    "

    "Modified: / 20.5.1998 / 15:16:28 / cg"
!

replaceAll:oldObject by:newObject from:startIndex to:stopIndex
    "backward ST/X compatibility: an alias for #replaceAll:with:from:to:.
     Please do no longer use this one;
     instead use #replaceAll:with:from:to: for ST-80 compatibility."

    <resource:#obsolete>

    self obsoleteMethodWarning:'use #replaceAll:with:from:to:'.
    ^ self replaceAll:oldObject with:newObject from:startIndex to:stopIndex

    "
     args:    oldObject  : <object>
              newObject  : <object>
              startIndex : <integer>
              stopIndex  : <integer>
        
     returns: self
    "

    "Modified: / 20.5.1998 / 15:16:02 / cg"
!

replaceAll:oldObject with:newObject
    "replace all oldObjects by newObject in the receiver.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    ^ self 
        replaceAll:oldObject 
        with:newObject 
        from:1 
        to:self size

    "
     args:    oldObject  : <object>
              newObject  : <object>

     returns: self
    "

    "
     '123123abc123' replaceAll:$1 with:$*  
     #(1 2 3 4 1 2 3 4) copy replaceAll:1 with:'one' 
    "

    "Modified: / 20.5.1998 / 15:26:10 / cg"
!

replaceAll:oldObject with:newObject from:startIndex to:stopIndex
    "replace all oldObjects found between startIndex and endIndex,
     by newObject in the receiver.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    |start "{ Class: SmallInteger }"
     stop  "{ Class: SmallInteger }"|

    start := startIndex.
    stop := stopIndex.
    startIndex to:stopIndex do:[:index |
        (self at:index) = oldObject ifTrue:[
            self at:index put:newObject
        ]
    ]

    "
     args:    oldObject  : <object>
              newObject  : <object>
              startIndex : <integer>
              stopIndex  : <integer> 

     returns: self
    "

    "
     '123123abc123' replaceAll:$1 with:$*
     '123123abc123' replaceAll:$1 with:$* from:1 to:6
     #(1 2 3 4 1 2 3 4) replaceAll:1 with:'one' from:1 to:4
    "

    "Modified: / 20.5.1998 / 15:23:10 / cg"
!

replaceAllForWhich:aConditionBlock with:newObject
    "replace all elements for which aConditionBlock returns true
     between startIndex and endIndex, by newObject in the receiver.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    self 
        replaceAllForWhich:aConditionBlock with:newObject 
        from:1 to:(self size)

    "
     args:    aConditionBlock  : <block>
              newObject        : <object>

     returns: self
    "
!

replaceAllForWhich:aConditionBlock with:newObject from:startIndex to:stopIndex
    "replace all elements for which aConditionBlock returns true
     between startIndex and endIndex, by newObject in the receiver.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    |start "{ Class: SmallInteger }"
     stop  "{ Class: SmallInteger }"|

    start := startIndex.
    stop := stopIndex.
    startIndex to:stopIndex do:[:index |
        (aConditionBlock value:(self at:index)) ifTrue:[
            self at:index put:newObject
        ]
    ]

    "
     args:    aConditionBlock  : <block>
              newObject        : <object>
              startIndex       : <integer>
              stopIndex        : <integer> 

     returns: self
    "
!

replaceAllIdentical:oldObject with:newObject
    "replace all oldObjects by newObject in the receiver.
     This is like #replaceAll:with:from:to:, but uses an identity compare.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    ^ self 
        replaceAllIdentical:oldObject 
        with:newObject 
        from:1 
        to:self size

    "
     args:    oldObject  : <object>
              newObject  : <object>

     returns: self
    "

    "
     #(1 2 3 4 1.0 2.0 3.0 4.0) copy replaceAll:1 with:'one'     
     #(1 2 3 4 1.0 2.0 3.0 4.0) copy replaceAllIdentical:1 with:'one' 
    "

!

replaceAllIdentical:oldObject with:newObject from:startIndex to:stopIndex
    "replace all oldObjects found between startIndex and endIndex,
     by newObject in the receiver.
     This is like #replaceAll:with:from:to:, but uses an identity compare.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    |start "{ Class: SmallInteger }"
     stop  "{ Class: SmallInteger }"|

    start := startIndex.
    stop := stopIndex.
    startIndex to:stopIndex do:[:index |
        (self at:index) == oldObject ifTrue:[
            self at:index put:newObject
        ]
    ]

    "
     args:    oldObject  : <object>
              newObject  : <object>
              startIndex : <integer>
              stopIndex  : <integer> 

     returns: self
    "

    "
     #(1 2 3 4 1 2 3 4) replaceAll:1 with:'one' from:1 to:8 
     #(1 2 3 4 1.0 2.0 3.0 4.0) replaceAll:1 with:'one' from:1 to:8  
     #(1 2 3 4 1.0 2.0 3.0 4.0) replaceAllIdentical:1 with:'one' from:1 to:8 
    "
!

replaceAny:aCollection by:newObject
    "backward ST/X compatibility; alias for #replaceAny:with:.
     Pleace do no longer use this one;
     instead use #replaceAny:with: for naming consistence."

    <resource:#obsolete>

    self obsoleteMethodWarning:'use #replaceAny:with:'.
    ^ self replaceAny:aCollection with:newObject from:1 to:self size 

    "
     args:    aCollection    : <colleciton of <object> >
              newObject      : <object>

     returns: self
    "

    "
     '123123abc123' replaceAny:#($1 $2) with:$*
     #('foo' 'bar' 'foo' 'baz' foo 1 2 3) replaceAny:#(foo 1) with:'*'
    "

    "Modified: / 20.5.1998 / 15:17:51 / cg"
!

replaceAny:aCollection by:newObject from:startIndex to:stopIndex
    "backward ST/X compatibility; alias for #replaceAny:with:from:to:.
     Pleace do no longer use this one;
     instead use #replaceAny:with:from:to: for naming consistence."
    
    <resource:#obsolete>

    self obsoleteMethodWarning:'use #replaceAny:with:from:to:'.
    ^ self replaceAny:aCollection with:newObject from:startIndex to:stopIndex 

    "
     args:    aCollection    : <colleciton of <object> >
              newObject      : <object>
              startIndex     : <integer>
              stopIndex     : <integer>

     returns: self
    "

    "
     '123123abc123' replaceAny:#($1 $2) with:$* from:1 to:6      
     #('foo' 'bar' 'foo' 'baz' foo 1 2 3) replaceAny:#(foo 1) with:'*'  
    "

    "Modified: / 20.5.1998 / 15:18:16 / cg"
!

replaceAny:aCollection with:newObject
    "replace all elements, which are in aCollection, by newObject.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    ^ self 
        replaceAny:aCollection 
        with:newObject 
        from:1 
        to:self size

    "
     args:    aCollection    : <colleciton of <object> >
              newObject      : <object>

     returns: self
    "

    "Modified: / 20.5.1998 / 15:25:58 / cg"
!

replaceAny:aCollection with:newObject from:startIndex to:stopIndex
    "replace all elements within a range,
     which are in contained in aCollection by newObject.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    |start "{ Class: SmallInteger }"
     stop "{ Class: SmallInteger }"|

    start := startIndex.
    stop := stopIndex.
    startIndex to:stopIndex do:[:index |
        (aCollection includes:(self at:index)) ifTrue:[
            self at:index put:newObject
        ]
    ]

    "
     args:    aCollection    : <colleciton of <object> >
              newObject      : <object>
              startIndex     : <integer>
              stopIndex      : <integer>

     returns: self
    "

    "
     '123123abc123' replaceAny:#($1 $2) with:$* from:1 to:6      
     #('foo' 'bar' 'foo' 'baz' foo 1 2 3) replaceAny:#(foo 1) with:'*'  
    "

    "Modified: / 20.5.1998 / 15:22:43 / cg"
!

replaceFrom:startIndex count:numberOfElements with:replacementCollection
    "replace numberOfElements elements in the receiver from startIndex,
     with elements taken from replacementCollection starting at 1.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    ^ self 
        replaceFrom:startIndex
        to:(startIndex + numberOfElements - 1)
        with:replacementCollection
        startingAt:1

    "
     '1234567890' replaceFrom:5 count:3 with:'abcdef'  
     #($a $b $c $d $e) replaceFrom:2 count:2 with:'12345'
    "

    "Modified: / 20.5.1998 / 15:25:46 / cg"
!

replaceFrom:startIndex count:numberOfElementsToReplace with:replacementCollection startingAt:repStartIndex
    "replace numberOfElementsToReplace elements in the receiver from startIndex,
     with elements taken from replacementCollection starting at repStartIndex.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    ^ self
        replaceFrom:startIndex
        to:(startIndex + numberOfElementsToReplace - 1)
        with:replacementCollection
        startingAt:repStartIndex

    "
     '1234567890' replaceFrom:5 count:3 with:'abcdef' startingAt:3  
     #($a $b $c $d $e) replaceFrom:2 count:3 with:'12345' startingAt:4 
     #($a $b $c $d $e) asOrderedCollection replaceFrom:2 count:3 with:'12345' startingAt:4 
    "

    "Modified: / 20.5.1998 / 15:22:22 / cg"
!

replaceFrom:startIndex to:stopIndex with:replacementCollection
    "replace elements in the receiver between index startIndex and stopIndex,
     with elements taken from replacementCollection starting at 1.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    ^ self 
        replaceFrom:startIndex
        to:stopIndex
        with:replacementCollection
        startingAt:1

    "
     args:    startIndex            : <integer>
              stopIndex             : <integer>
              replacementCollection : <colleciton of <object> >

     returns: self
    "

    "
     '1234567890' replaceFrom:5 to:7 with:'abcdef'
     #($a $b $c $d $e) replaceFrom:2 to:3 with:'12345'
    "

    "Modified: / 20.5.1998 / 15:25:37 / cg"
!

replaceFrom:startIndex to:stopIndex with:replacementCollection startingAt:repStartIndex
    "replace elements in the receiver between index startIndex and stopIndex,
     with elements  taken from replacementCollection starting at repStartIndex.
     Return the receiver.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    |srcIndex "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"
     end      "{ Class: SmallInteger }" |

    (repStartIndex < startIndex) ifTrue:[
        " must do reverse copy "
        srcIndex := repStartIndex + (stopIndex - startIndex).
        dstIndex := stopIndex.
        end := startIndex.
        [dstIndex >= end] whileTrue:[
            self at:dstIndex put:(replacementCollection at:srcIndex).
            srcIndex := srcIndex - 1.
            dstIndex := dstIndex - 1
        ].
        ^ self
    ].

    srcIndex := repStartIndex.
    dstIndex := startIndex.
    end := stopIndex.
    [dstIndex <= end] whileTrue:[
        self at:dstIndex put:(replacementCollection at:srcIndex).
        srcIndex := srcIndex + 1.
        dstIndex := dstIndex + 1
    ]

    "
     args:    startIndex            : <integer>
              stopIndex             : <integer>
              replacementCollection : <colleciton of <object> >
              repStartIndex         : <integer>

     returns: self
    "

    "
     '1234567890' replaceFrom:5 to:7 with:'abcdef' startingAt:3  
     #($a $b $c $d $e) replaceFrom:2 to:3 with:'12345' startingAt:4 
     #($a $b $c $d $e) asOrderedCollection replaceFrom:2 to:3 with:'12345' startingAt:4 

     |c|
     c := #($a $b $c $d $e) asOrderedCollection.
     c replaceFrom:2 to:3 with:c startingAt:4  

     |c|
     c := #($a $b $c $d $e) asOrderedCollection.
     c replaceFrom:4 to:5 with:c startingAt:2  
    "

    "Modified: / 20.5.1998 / 15:23:21 / cg"
!

replaceFrom:startIndex with:replacementCollection
    "replace elements in the receiver starting at startIndex,
     with elements taken from replacementCollection starting at 1
     to the end of replacementCollection.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    ^ self 
        replaceFrom:startIndex 
        to:(startIndex + replacementCollection size - 1)
        with:replacementCollection
        startingAt:1

    "
     args:    startIndex            : <integer>
              replacementCollection : <colleciton of <object> >

     returns: self
    "

    "
     '1234567890' replaceFrom:5 with:'abc'
     #($a $b $c $d $e) replaceFrom:2 with:'123'
    "

    "Modified: / 20.5.1998 / 15:25:27 / cg"
!

replaceFrom:startIndex with:replacementCollection startingAt:repStartIndex
    "replace elements in the receiver starting at startIndex,
     with elements taken from replacementCollection starting at repStartIndex
     to the end of replacementCollection.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    ^ self 
        replaceFrom:startIndex 
        to:(startIndex + replacementCollection size - repStartIndex)
        with:replacementCollection
        startingAt:repStartIndex

    "
     args:    startIndex            : <integer>
              replacementCollection : <colleciton of <object> >
              offset                : <integer>

     returns: self
    "

    "
     '1234567890' replaceFrom:5 with:'abcdef' startingAt:3  
     #($a $b $c $d $e) replaceFrom:2 with:'12345' startingAt:4
    "

    "Modified: / 20.5.1998 / 15:25:18 / cg"
!

startingAt:sourceStart replaceElementsIn:destColl from:destStartIndex to:destEndIndex
    "replace elements in destColl with elements from the receiver.

     Notice: This operation modifies the destination collection, NOT a copy;
     therefore the change may affect all others referencing this object."

    destColl 
        replaceFrom:destStartIndex 
        to:destEndIndex 
        with:self 
        startingAt:sourceStart

    "
     |s|
     s := 'abcdefghijklmnop'.
     '1234567890' startingAt:1 replaceElementsIn:s from:1 to:3.
     s'123defghijklmnop'
    "

    "Modified: / 20.5.1998 / 15:25:08 / cg"
! !

!SequenceableCollection methodsFor:'padded copying'!

leftPaddedTo:size with:padElement
    "return a new collection of length size, which contains the receiver
     right-adjusted (i.e. padded on the left).
     Elements on the left are filled with padElement.
     If the receivers size is equal or greater than the length argument, 
     the original receiver is returned unchanged."

    |len s|

    len := self size.
    (len < size) ifTrue:[
        s := self species new:size withAll:padElement.
        s replaceFrom:(size - len + 1) with:self.
        ^ s
    ]

    "
     'foo' leftPaddedTo:10 with:$.      
     'fooBar' leftPaddedTo:5 with:$.      
     123 printString leftPaddedTo:10 with:$.        
     (' ' , 123 printString) leftPaddedTo:10 with:$.        
     (Float pi printString) leftPaddedTo:15 with:(Character space)  
     (Float pi printString) leftPaddedTo:15 with:$-           
     (' ' , Float pi class name) leftPaddedTo:15 with:$.     
     #[1 2 3 4] leftPaddedTo:6 with:0     
     #[1 2 3 4] leftPaddedTo:10 with:99     
     #(1 2 3 4) leftPaddedTo:8 with:nil     
    "
!

paddedTo:newSize with:padElement
    "return a new collection consisting of the receivers elements,
     plus pad elements up to length.
     If the receivers size is equal or greater than the length argument, 
     the original receiver is returned unchanged."

    |s len|

    len := self size.
    len < newSize ifTrue:[
        s := self species new:newSize withAll:padElement.
        s replaceFrom:1 to:len with:self.
        ^ s
    ]

    "
     'foo' paddedTo:10 with:$.             
     123 printString paddedTo:10 with:$*   
     (Float pi printString) paddedTo:15 with:(Character space)  
     (Float pi printString) paddedTo:15 with:$-  
     (Float pi class name , ' ') paddedTo:15 with:$.  
     #[1 2 3 4] paddedTo:6 with:0     
     #[1 2 3 4] paddedTo:10 with:99     
     #(1 2 3 4) paddedTo:8 with:nil     
    "
!

paddedToMultipleOf:sizeModulu with:padElement
    |mySize mod numPad|

    mySize := self size.
    mod := (mySize \\ sizeModulu).
    mod == 0 ifTrue:[^ self].

    numPad := sizeModulu - mod.
    ^ self , (self species new:numPad withAll:padElement).

    "
     #[] paddedToMultipleOf:3 with:0  
     #[1] paddedToMultipleOf:3 with:0 
     #[1 2] paddedToMultipleOf:3 with:0  
     #[1 2 3] paddedToMultipleOf:3 with:0 
     #[1 2 3 4] paddedToMultipleOf:3 with:0

     #() paddedToMultipleOf:3 with:nil
     #(1) paddedToMultipleOf:3 with:nil
     #(1 2) paddedToMultipleOf:3 with:nil
     #(1 2 3) paddedToMultipleOf:3 with:nil
     #(1 2 3 4) paddedToMultipleOf:3 with:nil

     '' paddedToMultipleOf:3 with:Character space
     'a' paddedToMultipleOf:3 with:Character space
     'ab' paddedToMultipleOf:3 with:Character space
     'abc' paddedToMultipleOf:3 with:Character space
     'abcd' paddedToMultipleOf:3 with:Character space
    "
! !

!SequenceableCollection methodsFor:'private-sorting helpers'!

mergeFirst: first middle: middle last: last into: dst by: aBlock
    "Private!! 
     Merge the sorted ranges [first..middle] and [middle+1..last] of the receiver into the range [first..last] of dst."

    | i1 i2 val1 val2 out |

    i1 := first.
    i2 := middle + 1.
    val1 := self at: i1.
    val2 := self at: i2.
    out := first - 1.  "will be pre-incremented"

    "select 'lower' half of the elements based on comparator"
    [(i1 <= middle) and: [i2 <= last]] whileTrue: [
            (aBlock value: val1 value: val2)
                    ifTrue: [
                            dst at: (out := out + 1) put: val1.
                            val1 := self at: (i1 := i1 + 1)]
                    ifFalse: [
                            dst at: (out := out + 1) put: val2.
                            i2 := i2 + 1.
                            i2 <= last ifTrue: [val2 := self at: i2]]].

    "copy the remaining elements"
    i1 <= middle
            ifTrue: [
                    dst replaceFrom: out + 1 to: last with: self startingAt: i1]
            ifFalse: [
                    dst replaceFrom: out + 1 to: last with: self startingAt: i2].

!

mergeSortFrom: first to: last src: src dst: dst by: aBlock
    "Private!! Split the range to be sorted in half, sort each half, and merge the two half-ranges into dst."

    | middle |

    first = last ifTrue: [^ self].
    middle := (first + last) // 2.
    self mergeSortFrom: first to: middle src: dst dst: src by: aBlock.
    self mergeSortFrom: middle + 1 to: last src: dst dst: src by: aBlock.
    src mergeFirst: first middle: middle last: last into: dst by: aBlock.


!

quickSortFrom:inBegin to:inEnd
    "actual quicksort worker for sort-message.
     Simulates recursion in a stack, to avoid recursion overflow
     with degenerated collections.

     Use #< for element comparisons, since this is the (fastest) base 
     method in Magnitude, and the others may be defined by sending #<."

    |begin   "{ Class: SmallInteger }"
     end     "{ Class: SmallInteger }"
     b       "{ Class: SmallInteger }"
     e       "{ Class: SmallInteger }"
     middleElement temp1 temp2 stack |

    stack := OrderedCollection new.
    stack add:inBegin.
    stack add:inEnd.

    [stack notEmpty] whileTrue:[
        end := stack removeLast.
        begin := stack removeLast.

        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:[
                    temp1 := self at:b. temp2 := self at:e. 
                    self at:b put:temp2. self at:e put:temp1
                ].
                b := b + 1.
                e := e - 1
            ]
        ].
        (begin < e) ifTrue:[
            stack add:begin.
            stack add:e.
        ].
        (b < end) ifTrue:[
            stack add:b.
            stack add:end.
        ]
    ]
!

quickSortFrom:inBegin to:inEnd sortBlock:sortBlock
    "actual quicksort worker for sort:-message.
     Simulates recursion in a stack, to avoid recursion overflow
     with degenerated collections."

    |begin   "{ Class: SmallInteger }"
     end     "{ Class: SmallInteger }"
     bRun    "{ Class: SmallInteger }"
     eRun    "{ Class: SmallInteger }"
     m       "{ Class: SmallInteger }"
     nToSort "{ Class: SmallInteger }"
     elB elM elE temp stack|

    stack := OrderedCollection new.
    stack add:inBegin.
    stack add:inEnd.

    [stack notEmpty] whileTrue:[
        end := stack removeLast.
        begin := stack removeLast.

        (nToSort := end + 1 - begin) > 1 ifTrue:[
            elB := self at:begin.
            elE := self at:end.
            (sortBlock value:elB value:elE) ifFalse:[
                temp := elB. elB := elE. elE := temp.
                self at:begin put:elB. 
                self at:end put:elE.
            ].

            nToSort > 2 ifTrue:[
                m := (begin + end) // 2.  
                elM := self at:m.  
                (sortBlock value:elB value:elM) ifTrue:[
                    (sortBlock value:elM value:elE) ifFalse:[
                        temp := self at:end. 
                        self at:end put:(self at:m).
                        self at:m put:temp.
                        elM := elE
                    ]
                ] ifFalse:[
                    temp := self at:begin. 
                    self at:begin put:(self at:m).
                    self at:m put:temp.
                    elM := elB
                ].
                nToSort > 3 ifTrue:[
                     bRun := begin.
                     eRun := end.
                     [
                        [eRun := eRun - 1.  bRun <= eRun and:[sortBlock value:elM value: (self at:eRun)]] whileTrue. 
                        [bRun := bRun + 1.  bRun <= eRun and:[sortBlock value:(self at:bRun) value:elM]] whileTrue. 
                        bRun <= eRun
                     ] whileTrue:[
                        temp := self at:bRun. 
                        self at:bRun put:(self at:eRun).
                        self at:eRun put:temp.
                     ]. 
                     stack add:begin.
                     stack add:eRun.

                     stack add:bRun.
                     stack add:end.
                ]
            ]
        ]
    ]
!

quickSortFrom:inBegin to:inEnd sortBlock:sortBlock policy:p
    "actual quicksort worker for sort:-message.
     Simulates recursion in a stack, to avoid recursion overflow
     with degenerated collections."

    |begin   "{ Class: SmallInteger }"
     end     "{ Class: SmallInteger }"
     bRun    "{ Class: SmallInteger }"
     eRun    "{ Class: SmallInteger }"
     m       "{ Class: SmallInteger }"
     nToSort "{ Class: SmallInteger }"
     elB elM elE temp stack|

    stack := OrderedCollection new.
    stack add:inBegin.
    stack add:inEnd.

    [stack notEmpty] whileTrue:[
        end := stack removeLast.
        begin := stack removeLast.

       (nToSort := end + 1 - begin) > 1 ifTrue:[
            elB := self at:begin.
            elE := self at:end.
            (sortBlock value:p value:elB value:elE) ifFalse:[
                temp := elB. elB := elE. elE := temp.
                self at:begin put:elB. 
                self at:end put:elE.
            ].

            nToSort > 2 ifTrue:[
                m := (begin + end) // 2.  
                elM := self at:m.  
                (sortBlock value:p value:elB value:elM) ifTrue:[
                    (sortBlock value:p value:elM value:elE) ifFalse:[
                        temp := self at:end. 
                        self at:end put:(self at:m).
                        self at:m put:temp.
                        elM := elE
                    ]
                ] ifFalse:[
                    temp := self at:begin. 
                    self at:begin put:(self at:m).
                    self at:m put:temp.
                    elM := elB
                ].
                nToSort > 3 ifTrue:[
                     bRun := begin.
                     eRun := end.
                     [
                        [eRun := eRun - 1.  bRun <= eRun and:[sortBlock value:p value:elM value: (self at:eRun)]] whileTrue. 
                        [bRun := bRun + 1.  bRun <= eRun and:[sortBlock value:p value:(self at:bRun) value:elM]] whileTrue. 
                        bRun <= eRun
                     ] whileTrue:[
                        temp := self at:bRun. 
                        self at:bRun put:(self at:eRun).
                        self at:eRun put:temp.
                     ]. 
                     stack add:begin.
                     stack add:eRun.

                     stack add:bRun.
                     stack add:end.
                ]
            ]
        ]
    ]
!

quickSortFrom:inBegin to:inEnd sortBlock:sortBlock with:aCollection
    "actual quicksort worker for sort:-message.
     Simulates recursion in a stack, to avoid recursion overflow
     with degenerated collections."

    |begin   "{ Class: SmallInteger }"
     end     "{ Class: SmallInteger }"
     bRun    "{ Class: SmallInteger }"
     eRun    "{ Class: SmallInteger }"
     m       "{ Class: SmallInteger }"
     nToSort "{ Class: SmallInteger }"
     elB elM elE temp stack|

    stack := OrderedCollection new.
    stack add:inBegin.
    stack add:inEnd.

    [stack notEmpty] whileTrue:[
        end := stack removeLast.
        begin := stack removeLast.

        (nToSort := end + 1 - begin) > 1 ifTrue:[

            elB := self at:begin.
            elE := self at:end.
            (sortBlock value:elB value:elE) ifFalse:[
                temp := elB. elB := elE. elE := temp.
                self at:begin put:elB. 
                self at:end put:elE.

                temp := aCollection at:end. 
                aCollection at:end put:(aCollection at:begin).
                aCollection at:begin put:temp.
            ].

            nToSort > 2 ifTrue:[
                m := (begin + end) // 2.  
                elM := self at:m.  
                (sortBlock value:elB value:elM) ifTrue:[
                    (sortBlock value:elM value:elE) ifFalse:[
                        temp := self at:end. 
                        self at:end put:(self at:m).
                        self at:m put:temp.

                        temp := aCollection at:end. 
                        aCollection at:end put:(aCollection at:m).
                        aCollection at:m put:temp.

                        elM := elE
                    ]
                ] ifFalse:[
                    temp := self at:begin. 
                    self at:begin put:(self at:m).
                    self at:m put:temp.

                    temp := aCollection at:begin. 
                    aCollection at:begin put:(aCollection at:m).
                    aCollection at:m put:temp.
                    elM := elB
                ].
                nToSort > 3 ifTrue:[
                     bRun := begin.
                     eRun := end.
                     [
                        [eRun := eRun - 1.  bRun <= eRun and:[sortBlock value:elM value: (self at:eRun)]] whileTrue. 
                        [bRun := bRun + 1.  bRun <= eRun and:[sortBlock value:(self at:bRun) value:elM]] whileTrue. 
                        bRun <= eRun
                     ] whileTrue:[
                        temp := self at:bRun. 
                        self at:bRun put:(self at:eRun).
                        self at:eRun put:temp.

                        temp := aCollection at:bRun. 
                        aCollection at:bRun put:(aCollection at:eRun).
                        aCollection at:eRun put:temp.
                     ]. 
                     stack add:begin.
                     stack add:eRun.

                     stack add:bRun.
                     stack add:end.
                ]
            ]
        ]
    ]
!

quickSortFrom:inBegin to:inEnd with:aCollection
    "actual quicksort worker for sortWith-message.
     Simulates recursion in a stack, to avoid recursion overflow
     with degenerated collections.

     Use #< for element comparisons, since this is the (fastest) base 
     method in Magnitude, and the others may be defined by sending #<."

    |begin   "{ Class: SmallInteger }"
     end     "{ Class: SmallInteger }"
     b       "{ Class: SmallInteger }"
     e       "{ Class: SmallInteger }"
     middleElement temp1 temp2 stack|

    stack := OrderedCollection new.
    stack add:inBegin.
    stack add:inEnd.

    [stack notEmpty] whileTrue:[
        end := stack removeLast.
        begin := stack removeLast.

        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:[
                    temp1 := self at:b. temp2 := self at:e. 
                    self at:b put:temp2. self at:e put:temp1.
                    temp1 := aCollection at:b. temp2 := aCollection at:e. 
                    aCollection at:b put:temp2. aCollection at:e put:temp1
                ].
                b := b + 1.
                e := e - 1
            ]
        ].
        (begin < e) ifTrue:[
            stack add:begin.
            stack add:e.
        ].
        (b < end) ifTrue:[
            stack add:b.
            stack add:end.
        ]
    ]
!

randomizedQuickSortFrom:inBegin to:inEnd sortBlock:sortBlock with:aCollection
    "actual randomizedQuicksort worker for sort:with:-message.
     This exchanges a random element within the partition, to avoid
     the worst case O-square situation of quickSort.

     Notice, that this method has a much worse best- and average case
     runTime, due to the random number generation.
     The worst case of quickSort is encountered, if the choosen pivot
     element lies at either end of the partition, so that a split
     creates partitions of size 1 and (n-1).
     Since the middle element is choosen, this worst case is very unlikely
     to be encountered."

    <resource:#obsolete>

    self obsoleteMethodWarning:'use quickSortFrom:to:sortBlock:with:'.

    "/ code was never used - use regular sort for backward compatibility
    ^ self quickSortFrom:inBegin to:inEnd sortBlock:sortBlock with:aCollection


"/    |begin   "{ Class: SmallInteger }"
"/     end     "{ Class: SmallInteger }"
"/     b       "{ Class: SmallInteger }"
"/     e       "{ Class: SmallInteger }"
"/     rnd     "{ Class: SmallInteger }"
"/     middleElement temp1 temp2 |
"/
"/    begin := inBegin.   "/ this also does a type-check
"/    end := inEnd.
"/
"/    b := begin.
"/    e := end.
"/
"/    "/ randomize that partition
"/    "/ by exchanging the first element with any random
"/    "/ element.
"/    rnd := Random nextIntegerBetween:b and:e.
"/    temp1 := self at:b. temp2 := self at:rnd.
"/    self at:b put:temp2. self at:rnd put:temp1.
"/    aCollection notNil ifTrue:[
"/        temp1 := aCollection at:b. temp2 := aCollection at:rnd. 
"/        aCollection at:b put:temp2. aCollection at:rnd put:temp1
"/    ].
"/
"/    "/
"/    "/ now proceed as usual
"/    "/
"/    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:[
"/                temp1 := self at:b. temp2 := self at:e. 
"/                self at:b put:temp2. self at:e put:temp1.
"/                aCollection notNil ifTrue:[
"/                    temp1 := aCollection at:b. temp2 := aCollection at:e. 
"/                    aCollection at:b put:temp2. aCollection at:e put:temp1
"/                ].
"/            ].
"/            b := b + 1.
"/            e := e - 1
"/        ]
"/    ].
"/    (begin < e) ifTrue:[self randomizedQuickSortFrom:begin to:e sortBlock:sortBlock with:aCollection].
"/    (b < end) ifTrue:[self randomizedQuickSortFrom:b to:end sortBlock:sortBlock with:aCollection]
!

randomizedQuickSortFrom:inBegin to:inEnd with:aCollection
    "actual randomizedQuicksort worker for randomizedSort:-message.
     This exchanges a random element within the partition, to avoid
     the worst case O-square situation of quickSort.

     Notice, that this method has a much worse best- and average case
     runTime, due to the random number generation.
     The worst case of quickSort is encountered, if the choosen pivot
     element lies at either end of the partition, so that a split
     creates partitions of size 1 and (n-1).
     Since the middle element is choosen, this worst case is very unlikely
     to be encountered."

    <resource:#obsolete>

    self obsoleteMethodWarning:'use quickSortFrom:to:with:'.
    "/ code was never used - use regular sort for backward compatibility
    ^ self quickSortFrom:inBegin to:inEnd with:aCollection


"/    |begin   "{ Class: SmallInteger }"
"/     end     "{ Class: SmallInteger }"
"/     b       "{ Class: SmallInteger }"
"/     e       "{ Class: SmallInteger }"
"/     rnd     "{ Class: SmallInteger }"
"/     middleElement temp1 temp2 |
"/
"/    begin := inBegin.   "/ this also does a type-check
"/    end := inEnd.
"/
"/    b := begin.
"/    e := end.
"/
"/    "/ randomize that partition
"/    "/ by exchanging the first element with any random
"/    "/ element.
"/    rnd := Random nextIntegerBetween:b and:e.
"/    temp1 := self at:b. temp2 := self at:rnd.
"/    self at:b put:temp2. self at:rnd put:temp1.
"/    aCollection notNil ifTrue:[
"/        temp1 := aCollection at:b. temp2 := aCollection at:rnd. 
"/        aCollection at:b put:temp2. aCollection at:rnd put:temp1
"/    ].
"/
"/    "/
"/    "/ now proceed as usual
"/    "/
"/    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:[
"/                temp1 := self at:b. temp2 := self at:e. 
"/                self at:b put:temp2. self at:e put:temp1.
"/                aCollection notNil ifTrue:[
"/                    temp1 := aCollection at:b. temp2 := aCollection at:e. 
"/                    aCollection at:b put:temp2. aCollection at:e put:temp1
"/                ].
"/            ].
"/            b := b + 1.
"/            e := e - 1
"/        ]
"/    ].
"/    (begin < e) ifTrue:[self randomizedQuickSortFrom:begin to:e with:aCollection].
"/    (b < end) ifTrue:[self randomizedQuickSortFrom:b to:end with:aCollection]
"/
"/    "Modified: 21.8.1997 / 18:30:19 / cg"
"/    "Created: 21.8.1997 / 18:34:23 / cg"
! !

!SequenceableCollection methodsFor:'queries'!

firstIndex
    "return the first elements index"

    ^ 1
!

isSequenceable
    "return true, if the receiver is some kind of sequenceableCollection"

    ^ true
!

isSequenceableCollection
    "OBSOLETE: use isSequenceable for ST-80 compatibility.
     This method is a historic leftover and will be removed."

    <resource:#obsolete>

    self obsoleteMethodWarning:'use #isSequenceable'.
    ^ true

    "Modified: / 8.5.1998 / 21:27:18 / cg"
!

isSorted
    "return true. if my elements are sorted (already)"

    |lastEl el|

    lastEl := self first.
    2 to:self size do:[:i |
        el := self at:i.
        el >= lastEl ifFalse: [^ false].
        lastEl := el
    ].
    ^ true

    "
     #(1 2 3 5 10 100) isSorted    
     #(1 2 3 5 100 10) isSorted    
    "
!

isSortedBy:aBlock
    "return true, if my elements are sorted (already) by the given criterion (sortBlock)"

    |lastEl el|

    lastEl := self first.
    2 to:self size do:[:i |
        el := self at:i.
        (aBlock value:lastEl value:el) ifFalse: [^ false].
        lastEl := el
    ].
    ^ true

    "
     #(1 2 3 5 10 100) isSortedBy:[:a :b | a <= b]    
     #(1 2 3 5 100 10) isSortedBy:[:a :b | a <= b]       
     #(100 10 5 3 2 1) isSortedBy:[:a :b | a <= b]       
     #(100 10 5 3 2 1) isSortedBy:[:a :b | a > b]       
    "

!

keys
    "return a collection with all keys in the Smalltalk dictionary"

    |sz|

    sz := self size.
    sz == 0 ifTrue:[
        ^ #()
    ].
    ^ 1 to:sz
!

lastIndex
    "return the last elements index"

    ^ self size
!

size
    "return the number of elements in the collection.
     concrete implementations must define this"

    ^ self subclassResponsibility
!

zeroIndex
    "return the index value which is returned when nothing
     is found in an indexOf* kind of search.
     ST-compatibility"

    ^ 0

    "Created: 14.2.1997 / 16:13:03 / cg"
! !

!SequenceableCollection methodsFor:'searching'!

detect:aBlock startingAt:startIndex
    "find the first element, for which evaluation of the argument, aBlock
     return true, starting the search with startIndex.
     If none does so, report an error"

    ^ self detect:aBlock startingAt:startIndex ifNone:[self errorNotFound]

    "
     #(11 12 13 14) detect:[:n | n odd] startingAt:3    
     #(12 14 16 18) detect:[:n | n odd] startingAt:3     
    "

    "Created: / 21.10.1998 / 18:47:28 / cg"
!

detect:aBlock startingAt:startIndex ifNone:exceptionBlock
    "find the first element, for which evaluation of the argument, aBlock
     return true, starting the search with startIndex.
     If none does so, return the evaluation of exceptionBlock"

    |stop|

    stop := self size.
    self from:startIndex to:stop do:[:el |
        (aBlock value:el) ifTrue:[
            ^ el
        ].
    ].
    ^ exceptionBlock value

    "
     #(11 12 13 14) detect:[:n | n odd] startingAt:3 ifNone:['sorry']   
     #(12 14 16 18) detect:[:n | n odd] startingAt:3 ifNone:['sorry']     
    "

    "Created: / 21.10.1998 / 18:46:01 / cg"
!

findFirst:aBlock
    "find the first element, for which evaluation of the argument, aBlock
     returns true; return its index or 0 if none detected.
     This is much like #detect, however, here an INDEX is returned,
     while #detect returns the element."

    |stop  "{ Class: SmallInteger }" |

    stop := self size.
    1 to:stop do:[:index |
        (aBlock value:(self at:index)) ifTrue:[^ index].
    ].
    ^ 0

    "
     #(1 2 3 4 5 6) findFirst:[:x | (x >= 3)]
     #(1 2 3 4 5 6) findFirst:[:x | (x >= 3) and:[x even]]
     #(1 2 3 4 5 6) findFirst:[:x | (x >= 8)]           
     'one.two.three' findFirst:[:c | (c == $.)]
     '__one.two.three' findFirst:[:c | (c ~= $_)] 
     'one.two.three' findFirst:[:c | (c ~= $_)] 
    "

    "Modified: / 21.10.1998 / 18:48:10 / cg"
!

findFirst:aBlock startingAt:startIndex
    "find the first element, for which evaluation of the argument, aBlock
     returns true; return its index or 0 if none detected.
     This is much like #detect:startingAt:, however, here an INDEX is returned,
     while #detect returns the element."

    |start "{ Class: SmallInteger }"
     stop  "{ Class: SmallInteger }" |

    start := startIndex. "/ as a compiler hint
    stop := self size.
    start to:stop do:[:index |
        (aBlock value:(self at:index)) ifTrue:[^ index].
    ].
    ^ 0

    "
     #(1 4 3 4 3 6) findFirst:[:x | (x > 3)] startingAt:4
     'one.two.three' findFirst:[:c | (c == $.)] startingAt:5
    "

    "Modified: / 21.10.1998 / 18:48:22 / cg"
!

findLast:aBlock
    "find the last element, for which evaluation of the argument, aBlock
     returns true.
     Return its index or 0 if none detected."

    |start "{ Class: SmallInteger }"|

    start := self size.
    start to:1 by:-1 do:[:index |
        (aBlock value:(self at:index)) ifTrue:[^ index].
    ].
    ^ 0

    "
     #(1 99 3 99 5 6) findLast:[:x | (x == 99)]
     'one.two.three' findLast:[:c | (c == $.)]
    "
!

findLast:aBlock startingAt:startIndex
    "find the last element, for which evaluation of the argument, aBlock
     returns true. Start the search at startIndex.
     Return its index or 0 if none detected."

    |start "{ Class: SmallInteger }"|

    start := startIndex.
    start to:1 by:-1 do:[:index |
        (aBlock value:(self at:index)) ifTrue:[^ index].
    ].
    ^ 0

    "
     #(1 99 3 99 5 6) findLast:[:x | (x == 99)] startingAt:3
     'one.two.three' findLast:[:c | (c == $.)] startingAt:7
    "
!

findLast:aBlock startingAt:startIndex endingAt:endIndex
    "find the last element, for which evaluation of the argument, aBlock
     returns true. Start the search at startIndex.
     End the search at endIndex or when an element is found.
     Return its index or 0 if none detected."

    |start "{ Class: SmallInteger }"|

    start := startIndex.
    start to:endIndex by:-1 do:[:index |
        (aBlock value:(self at:index)) ifTrue:[^ index].
    ].
    ^ 0

    "
     #(1 99 3 99 5 6) findLast:[:x | (x == 99)] startingAt:3
     #(1 99 3 99 3 5 6) findLast:[:x | (x == 3)] startingAt:7 endingAt:6
     #(1 99 3 99 3 5 6) findLast:[:x | (x == 3)] startingAt:7 endingAt:5
     'one.two.three' findLast:[:c | (c == $.)] startingAt:7
    "
!

indexOfAny:aCollection
    "search the collection for an element in aCollection.
     if found, return the index otherwise return 0.
     The comparison is done using = 
     (i.e. equality test - not identity test).

     Notice, that for big collections, the runtime of this search
     grows proportional to size(receiver) * size(aCollection).
     You may think about using other mechanisms (Sets, Dictionaries etc)."

    ^ self indexOfAny:aCollection startingAt:1

    "
     #(10 20 30 40 50 60 70) indexOfAny:#(40 30 50)
     #(10 20 30 40 50 60 70) indexOfAny:#(40.0 30.0 50)
    "
!

indexOfAny:aCollection startingAt:start
    "search the collection for an element in aCollection,
     starting the search at index start;
     if found, return the index otherwise return 0.
     The comparison is done using = 
     (i.e. equality test - not identity test).

     Notice, that for big collections, the runtime of this search
     grows proportional to size(receiver) * size(aCollection).
     You may think about using other mechanisms (Sets, Dictionaries etc)."


    |startIndex "{ Class: SmallInteger }"
     stop       "{ Class: SmallInteger }" |

    startIndex := start.
    stop := self size.
    startIndex to:stop do:[:index |
        (aCollection includes:(self at:index)) ifTrue:[^ index].
    ].
    ^ 0
    "
     #(10 20 30 40 10 20 30 40) indexOfAny:#(40 50 30) startingAt:5  
     #(10 20 30 40 10 20 30 40) indexOfAny:#(40.0 50 30.0) startingAt:5  
    "
!

indexOfAny:aCollection startingAt:start ifAbsent:exceptionBlock
    "search the collection for an element in aCollection,
     starting the search at index start;
     if found, return the index. If not, return the value returned by exceptionBlock.
     The comparison is done using = 
     (i.e. equality test - not identity test).

     Notice, that for big collections, the runtime of this search
     grows proportional to size(receiver) * size(aCollection).
     You may think about using other mechanisms (Sets, Dictionaries etc)."


    |val|

    val := self indexOfAny:aCollection startingAt:start .
    val == 0 ifTrue:[^ exceptionBlock value].
    ^ val.

    "
     #(10 20 30 40 10 20 30 40) indexOfAny:#(40 50 30) startingAt:5 ifAbsent:-1  
     #(10 20 30 40 10 20 30 40) indexOfAny:#(40.0 50 30.0) startingAt:5 ifAbsent:-1  
     #(10 20 30 40 10 20 30 40) indexOfAny:#(99 88 77) startingAt:5 ifAbsent:['oops']  
    "
!

indexOfAnyOf:aCollection
    "squeak compatibility: same as #indexOfAny:"

    ^ self indexOfAny:aCollection

    "
     #(10 20 30 40 50 60 70) indexOfAnyOf:#(40 30 50)
     #(10 20 30 40 50 60 70) indexOfAnyOf:#(40.0 30.0 50)
    "
!

indexOfAnyOf:aCollection startingAt:start 
    "squeak compatibility: same as #indexOfAny:startingAt:"

    ^ self indexOfAny:aCollection startingAt:start

    "
     #(10 20 30 40 50 60 70) indexOfAnyOf:#(40 30 50)     startingAt:2
     #(10 20 30 40 50 60 70) indexOfAnyOf:#(40.0 30.0 50) startingAt:2
    "
!

indexOfAnyOf:aCollection startingAt:start ifAbsent:exceptionBlock
    "squeak compatibility: same as #indexOfAny:startingAt:ifAbsent:"

    ^ self indexOfAny:aCollection startingAt:start ifAbsent:exceptionBlock

!

indexOfSubCollection:aCollection
    "find a subcollection. 
     If found, return the index; if not found, return 0."

    ^ self indexOfSubCollection:aCollection startingAt:1 ifAbsent:0

    "
     #(1 2 3 4 5 6 7) indexOfSubCollection:#()  
     #(1 2 3 4 5 6 7) indexOfSubCollection:#(1)      
     #(1 2 3 4 5 6 7) indexOfSubCollection:#(1 2 3 4) 
     #(1 2 3 4 5 6 7) indexOfSubCollection:#(2 3 5)   
     #(1 2 3 2 3 4 5) indexOfSubCollection:#(2 3 4)  
     #(1 2 3 4 5 6 7) indexOfSubCollection:#(5 6 7)  
     #(1 2 3 4 5 6 7) indexOfSubCollection:#(5 6 8)  
     #(1 2 3 4 5 6 7) indexOfSubCollection:#(5 6 7 8)  
    "
!

indexOfSubCollection:aCollection ifAbsent:exceptionBlock
    "find a subcollection. If found, return the index;
     if not found, return the result of evaluating exceptionBlock."

    ^ self indexOfSubCollection:aCollection startingAt:1 ifAbsent:exceptionBlock
!

indexOfSubCollection:aCollection startingAt:startIndex
    "find a subcollection starting at index. 
     If found, return the index; if not found, return 0."

    ^ self indexOfSubCollection:aCollection startingAt:startIndex ifAbsent:0
!

indexOfSubCollection:aCollection startingAt:startIndex ifAbsent:exceptionBlock
    "find a subcollection, starting at index. If found, return the index;
     if not found, return the result of evaluating exceptionBlock.
     This is a q&d hack - not very efficient"

    |same first 
     mySize     "{Class: SmallInteger }"
     checkIndex "{Class: SmallInteger }"
     cmpIndex   "{Class: SmallInteger }"
     sz         "{Class: SmallInteger }"|

    mySize := self size.
    sz := aCollection size.
    sz == 0 ifTrue:[^ exceptionBlock value].
    first := aCollection at:1.

    checkIndex := startIndex - 1.    
    [true] whileTrue:[
        checkIndex := self indexOf:first startingAt:checkIndex+1.
        checkIndex == 0 ifTrue:[^ exceptionBlock value].

        (checkIndex + sz - 1) > mySize ifTrue:[
            ^ 0
        ].
        same := true.
        cmpIndex := 1.
        [same and:[cmpIndex <= sz]] whileTrue:[
            (self at:checkIndex + cmpIndex - 1) = (aCollection at:cmpIndex) ifFalse:[
                same := false
            ] ifTrue:[
                cmpIndex := cmpIndex + 1
            ]
        ].
        same ifTrue:[^ checkIndex].
    ]    

    "
     #(1 2 3 4 5 6 7) indexOfSubCollection:#()  startingAt:2 
     #(1 2 3 4 5 6 7) indexOfSubCollection:#(1) startingAt:2     
     #(1 2 1 2 1 2 3) indexOfSubCollection:#(1 2 3) startingAt:2 
     #(1 2 1 2 1 2 3) indexOfSubCollection:#(1 2)   startingAt:2  
     #(1 2 1 2 1 2 3) indexOfSubCollection:#(1 2)   startingAt:3  
     #(1 2 1 2 1 2 3) indexOfSubCollection:#(1 2)   startingAt:4 
    "
!

lastIndexOfSubCollection:aCollection
    "find a subcollection from the end. 
     If found, return the index; if not found, return 0."

    ^ self lastIndexOfSubCollection:aCollection startingAt:self size ifAbsent:0

    "Created: / 16.5.1998 / 20:08:55 / cg"
    "Modified: / 16.5.1998 / 20:12:37 / cg"
!

lastIndexOfSubCollection:aCollection ifAbsent:exceptionBlock
    "find a subcollection from the end. If found, return the index;
     if not found, return the result of evaluating exceptionBlock."

    ^ self lastIndexOfSubCollection:aCollection startingAt:self size ifAbsent:exceptionBlock

    "Created: / 16.5.1998 / 20:09:08 / cg"
    "Modified: / 16.5.1998 / 20:12:39 / cg"
!

lastIndexOfSubCollection:aCollection startingAt:startIndex
    "find a subcollection from the end starting at index. 
     If found, return the index; if not found, return 0."

    ^ self lastIndexOfSubCollection:aCollection startingAt:startIndex ifAbsent:0

    "Created: / 16.5.1998 / 20:09:23 / cg"
!

lastIndexOfSubCollection:aCollection startingAt:startIndex ifAbsent:exceptionBlock
    "find a subcollection from the end, starting at index. If found, return the index;
     if not found, return the result of evaluating exceptionBlock.
     This is a q&d hack - not very efficient"

    |same last 
     mySize     "{Class: SmallInteger }"
     checkIndex "{Class: SmallInteger }"
     cmpIndex   "{Class: SmallInteger }"
     sz         "{Class: SmallInteger }"|

    mySize := self size.
    sz := aCollection size.
    sz == 0 ifTrue:[^ exceptionBlock value].
    last := aCollection at:sz.

    checkIndex := startIndex + sz.    
    checkIndex >  mySize ifTrue:[
        checkIndex := mySize + 1
    ].
    [true] whileTrue:[
        checkIndex := self lastIndexOf:last startingAt:checkIndex-1.
        checkIndex == 0 ifTrue:[^ exceptionBlock value].

        (checkIndex - sz + 1) < 1 ifTrue:[
            ^ 0
        ].
        same := true.
        cmpIndex := 1.
        [same and:[cmpIndex <= sz]] whileTrue:[
            (self at:checkIndex - sz + cmpIndex) = (aCollection at:cmpIndex) ifFalse:[
                same := false
            ] ifTrue:[
                cmpIndex := cmpIndex + 1
            ]
        ].
        same ifTrue:[^ checkIndex - sz + 1].
    ]    

    "
     #(1 2 3 4 5 6 7) lastIndexOfSubCollection:#()  startingAt:2  
     #(1 2 3 4 5 6 7) lastIndexOfSubCollection:#(1)  
     #(1 2 3 4 5 6 7) lastIndexOfSubCollection:#(1) startingAt:4     
     #(1 3 1 2 1 3 3) lastIndexOfSubCollection:#(1 2 3)  
     #(1 2 1 2 1 2 3) lastIndexOfSubCollection:#(1 2 3) startingAt:2 
     #(1 2 1 2 1 2 3) lastIndexOfSubCollection:#(1 2 3) 
     #(1 2 1 2 1 2 3) lastIndexOfSubCollection:#(1 2)  
     #(1 2 1 2 1 2 3) lastIndexOfSubCollection:#(1 2)   startingAt:5 
     #(1 2 1 2 1 2 3) lastIndexOfSubCollection:#(1 2)   startingAt:4 
    "

    "Modified: / 16.5.1998 / 20:21:46 / cg"
! !

!SequenceableCollection methodsFor:'searching-equality'!

includes:anElement
    "return true if the collection contains anElement; false otherwise.
     Comparison is done using equality compare (i.e. =).
     See #includesIdentical: if identity is asked for."

    ((self indexOf:anElement startingAt:1) == 0) ifTrue:[^ false].
    ^ true

    "
     args:    anElement : <object> 

     returns: true  - if found
              false - if not found
    "

    "
     #(10 20 30 40 50 60 70) includes:99      
     #(10 20 30 40 50 60 70) includes:40     
     #(10 20 30 40 50 60 70) includes:40.0    
    "

    "Modified: / 20.5.1998 / 15:00:23 / cg"
!

indexOf:anElement
    "search the collection for anElement;
     if found, return the index otherwise return 0.
     The comparison is done using = 
     (i.e. equality test - not identity test)."

    ^ self indexOf:anElement startingAt:1

    "
     args:    anElement : <object>

     returns: elementIndex - if found
              0            - if not found
    "

    "
     #(10 20 30 40 50 60 70) indexOf:40
     #(10 20 30 40 50 60 70) indexOf:40.0
    "

    "Modified: / 20.5.1998 / 14:59:55 / cg"
!

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 - not identity test)."

    |index|

    index := self indexOf:anElement startingAt:1.
    (index == 0) ifTrue:[^ exceptionBlock value].
    ^ index

    "
     args:    anElement      : <object>
              exceptionBlock : <valueImplementor>

     returns: elementIndex         - if found
              exceptionBlock value - if not found
    "

    "
     #(10 20 30 40 10 20 30 40) indexOf:40   ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) indexOf:40.0 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) indexOf:35   ifAbsent:['none'] 
    "

    "Modified: / 20.5.1998 / 14:57:35 / cg"
!

indexOf:elementToFind replaceWith:replacement startingAt:start stoppingAt:stop
    "search for the first occurence of elementToFind starting at start,
     stopping the search at stop. If found, replace the element by replacement
     and return the index.
     If not found, return 0."

    |idx|

    idx := self indexOf:elementToFind startingAt:start.
    ((idx > 0) and:[idx <= stop]) ifTrue:[
        self at:idx put:replacement.
        ^ idx
    ].
    ^ 0

    "
     args:    elementToFind : <object> 
              replacement   : <integer>
              start         : <integer>
              stop          : <integer>

     returns: elementIndex - if found (and replaced)
              0            - if not found
    "

    "
     |a|

     a := #(10 20 30 40 50 60 70).
     (a indexOf:30 replaceWith:nil startingAt:1 stoppingAt:7) printNL.
     a printNL.
    "

    "Modified: / 20.5.1998 / 14:59:30 / cg"
!

indexOf:anElement startingAt:start
    "search the collection for anElement, starting the search at index start;
     if found, return the index otherwise return 0.
     The comparison is done using = 
     (i.e. equality test - not identity test)."

    |startIndex "{ Class: SmallInteger }"
     stop       "{ Class: SmallInteger }" |

    startIndex := start.
    stop := self size.
    startIndex to:stop do:[:index |
        anElement = (self at:index) ifTrue:[^ index].
    ].
    ^ 0

    "
     args:    anElement : <object> 
              start     : <integer>

     returns: elementIndex - if found
              0            - if not found
    "

    "
     #(10 20 30 40 10 20 30 40) indexOf:40   startingAt:5  
     #(10 20 30 40 10 20 30 40) indexOf:40.0 startingAt:5  
    "

    "Modified: / 20.5.1998 / 14:58:49 / cg"
!

indexOf:anElement startingAt:start endingAt:stop
    "search the collection for anElement, starting the search at index start;
     ending at stop.
     If found (within the range), return the index, otherwise return 0.
     The comparison is done using = 
     (i.e. equality test - not identity test)."

    |startIndex "{ Class: SmallInteger }"
     stopIndex  "{ Class: SmallInteger }" |

    startIndex := start.
    stopIndex := self size min:stop.
    startIndex to:stopIndex do:[:index |
        anElement = (self at:index) ifTrue:[^ index].
    ].
    ^ 0

    "
     args:    anElement      : <object> 
              start          : <integer> 
              stop           : <integer> 

     returns: elementIndex         - if found
              exceptionBlock value - if not found
    "

    "
     #(10 20 30 40 10 20 30 40) indexOf:40   startingAt:3 endingAt:99  
     #(10 20 30 40 10 20 30 40) indexOf:40   startingAt:3 endingAt:5  
     #(10 20 30 40 10 20 30 40) indexOf:40   startingAt:1 endingAt:3   
     #(10 20 30 40 10 20 30 40) indexOf:40.0 startingAt:5  
    "

    "Created: / 12.4.1996 / 17:37:13 / cg"
    "Modified: / 20.5.1998 / 14:58:28 / cg"
!

indexOf:anElement startingAt:start ifAbsent:exceptionBlock
    "search the collection for anElement starting the search at index start;
     if found, return the index otherwise return the value of the
     exceptionBlock.
     The comparison is done using = 
     (i.e. equality test - not identity test)."

    |index|

    index := self indexOf:anElement startingAt:start.
    (index == 0) ifTrue:[^ exceptionBlock value].
    ^ index

    "
     args:    anElement      : <object> 
              start          : <integer> 
              exceptionBlock : <valueImplementor>

     returns: elementIndex         - if found
              exceptionBlock value - if not found
    "

    "
     #(10 20 30 40 10 20 30 40) indexOf:40   startingAt:5 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) indexOf:40.0 startingAt:5 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) indexOf:35   startingAt:5 ifAbsent:['none'] 
    "

    "Modified: / 20.5.1998 / 14:58:05 / cg"
!

lastIndexOf:anElement
    "search the collection backwards for anElement;
     if found, return the index otherwise return 0.
     The comparison is done using = 
     (i.e. equality test - not identity test)."

    ^ self lastIndexOf:anElement startingAt:self size 

    "
     args:    anElement      : <object>

     returns: elementIndex - if found
              0            - if not found
    "

    "
     #(10 20 30 40 50 60 70) lastIndexOf:40    
     #(10 20 30 40 50 60 70) lastIndexOf:40.0  
     #(10 20 30 40 50 60 70) lastIndexOf:35    
     #(10 20 30 40 50 60 70) lastIndexOf:10    
    "

    "Modified: / 20.5.1998 / 15:02:10 / cg"
!

lastIndexOf:anElement ifAbsent:exceptionBlock
    "search the collection backwards for anElement;
     if found, return the index otherwise return the value of the
     exceptionBlock.
     The comparison is done using = 
     (i.e. equality test - not identity test)."

    |index|

    index := self lastIndexOf:anElement startingAt:self size.
    (index == 0) ifTrue:[^ exceptionBlock value].
    ^ index

    "
     #(10 20 30 40 10 20 30 40) lastIndexOf:40   ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) lastIndexOf:40.0 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) lastIndexOf:35   ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) lastIndexOf:10   ifAbsent:['none'] 
    "
!

lastIndexOf:anElement startingAt:start
    "search the collection backwards for anElement, starting the search at index start;
     if found, return the index otherwise return 0.
     The comparison is done using = 
     (i.e. equality test - not identity test)."

    |startIndex "{ Class: SmallInteger }"|

    startIndex := start.
    startIndex to:1 by:-1 do:[:index |
        anElement = (self at:index) ifTrue:[^ index].
    ].
    ^ 0

    "
     #(10 20 30 40 10 20 30 40) lastIndexOf:40   startingAt:8  
     #(10 20 30 40 10 20 30 40) lastIndexOf:40.0 startingAt:8  
     #(10 20 30 40 10 20 30 40) lastIndexOf:35   startingAt:8  
     #(10 20 30 40 10 20 30 40) lastIndexOf:10   startingAt:8  
     #(10 20 30 40 10 20 30 40) lastIndexOf:10   startingAt:4  
    "
!

lastIndexOf:anElement startingAt:start ifAbsent:exceptionBlock
    "search the collection backwards for anElement starting the search at 
     index start; if found, return the index 
     otherwise return the value of the exceptionBlock.
     The comparison is done using = 
     (i.e. equality test - not identity test)."

    |index|

    index := self lastIndexOf:anElement startingAt:start.
    (index == 0) ifTrue:[^ exceptionBlock value].
    ^ index

    "
     #(10 20 30 40 10 20 30 40) lastIndexOf:40   startingAt:8 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) lastIndexOf:40.0 startingAt:8 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) lastIndexOf:35   startingAt:8 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) lastIndexOf:10   startingAt:8 ifAbsent:['none'] 
    "
!

lastIndexOfAny:aCollection
    "search the collection backwards for any in aCollection;
     if found, return the index, otherwise return 0.
     The comparison is done using = 
     (i.e. equality test - not identity test)."

    ^ self lastIndexOfAny:aCollection startingAt:self size 

    "
     args:    aCollection    : <collection>

     returns: elementIndex - if found
              0            - if not found
    "

    "
     #(10 20 30 40 50 60 70) lastIndexOfAny:#(40 60)   
     #(10 20 30 40 50 60 70) lastIndexOfAny:#(40.0 60)
     #(10 20 30 40 50 60 70) lastIndexOfAny:#(35 40)    
     #(10 20 30 40 50 60 70) lastIndexOfAny:#(15 35)    
    "

    "Modified: / 20.5.1998 / 15:02:10 / cg"
!

lastIndexOfAny:aCollection startingAt:start
    "search the collection backwards for any in aCollection, starting the search at index start;
     if found, return the index, otherwise return 0.
     The comparison is done using = 
     (i.e. equality test - not identity test)."

    |startIndex "{ Class: SmallInteger }"|

    startIndex := start.
    startIndex to:1 by:-1 do:[:index |
        (aCollection includes:(self at:index)) ifTrue:[^ index].
    ].
    ^ 0

    "
     #(10 20 30 40 10 20 30 40) lastIndexOfAny:#(40 60)   startingAt:8  
     #(10 20 30 40 10 20 30 40) lastIndexOfAny:#(40 60)   startingAt:7  
    "
!

nextIndexOf:anElement from:start to:stop
    "search the collection for anElement, starting the search at index start,
     stopping at:stop;
     if found, return the index otherwise return nil.
     The comparison is done using = 
     (i.e. equality test - not identity test).

     NOTICE: nil is returned here if the element is not found,
             although this is somewhat strange (the indexOf-search
             methods return 0), this is done for VW compatibility."

    |startIndex "{ Class: SmallInteger }"
     stopIndex  "{ Class: SmallInteger }" |

    startIndex := start.
    stopIndex :=  stop.
    startIndex to:stop do:[:index |
        anElement = (self at:index) ifTrue:[^ index].
    ].
    ^ nil

    "
     args:    anElement : <object>
              start     : <integer>
              stop      : <integer>

     returns: elementIndex - if found
              nil          - if not found
    "

    "
     #(10 20 30 40 10 20 30 40) nextIndexOf:40   from:2 to:6  
     #(10 20 30 40 10 20 30 40) nextIndexOf:40.0 from:2 to:6   
     #(10 20 30 40 10 20 30 40) nextIndexOf:35   from:2 to:6   
    "

    "Modified: / 20.5.1998 / 15:11:32 / cg"
!

nextIndexOf:anElement from:start to:stop ifAbsent:exceptionBlock
    "search the collection for anElement, starting the search at index start
     and stopping at stop;
     if found, return the index otherwise return the value of the
     exceptionBlock.
     The comparison is done using = 
     (i.e. equality test - not identity test)."

    |index|

    index := self nextIndexOf:anElement from:start to:stop.
    index isNil ifTrue:[^ exceptionBlock value].
    ^ index

    "
     args:    anElement      : <object>
              start          : <integer>
              stop           : <integer>
              exceptionBlock : <valueImplementor>

     returns: elementIndex           - if found
              valueImplementor value - if not found
    "

    "
     #(10 20 30 40 10 20 30 40) nextIndexOf:40   from:2 to:6 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) nextIndexOf:40.0 from:2 to:6 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) nextIndexOf:35   from:2 to:6 ifAbsent:['none'] 
    "

    "Modified: / 20.5.1998 / 15:12:36 / cg"
!

prevIndexOf:anElement from:startSearchIndex to:endSearchIndex
    "search the collection for anElement, starting the search at index start;
     ending at stop, going in reverse direction.
     If found (within the range), return the index, otherwise return nil.
     The comparison is done using = 
     (i.e. equality test - not identity test).

     NOTICE: nil is returned here if the element is not found,
             although this is somewhat strange (the indexOf-search
             methods return 0), this is done for VW compatibility."

    |startIndex "{ Class: SmallInteger }"
     stopIndex  "{ Class: SmallInteger }" |

    startIndex := startSearchIndex.
    stopIndex := endSearchIndex max:1.
    startIndex to:stopIndex by:-1 do:[:index |
        anElement = (self at:index) ifTrue:[^ index].
    ].
    ^ nil

    "
     args:    anElement : <object>
              start     : <integer>
              stop      : <integer>

     returns: elementIndex - if found
              nil          - if not found
    "

    "
     #(10 20 30 40 10 20 30 40) prevIndexOf:40   from:7 to:2  
     #(10 20 30 40 10 20 30 40) prevIndexOf:40.0 from:7 to:2  
     #(10 20 30 40 10 20 30 40) prevIndexOf:35   from:7 to:5  
    "

    "Modified: / 20.5.1998 / 15:13:27 / cg"
!

prevIndexOf:anElement from:start to:stop ifAbsent:exceptionBlock
    "search the collection for anElement, starting the search at index start
     and stopping at stop, doing a reverse search;
     if found, return the index otherwise return the value of the
     exceptionBlock.
     The comparison is done using = 
     (i.e. equality test - not identity test)."

    |index|

    index := self prevIndexOf:anElement from:start to:stop.
    (index == 0) ifTrue:[^ exceptionBlock value].
    ^ index

    "
     args:    anElement      : <object>
              start          : <integer>
              stop           : <integer>
              exceptionBlock : <valueImplementor>

     returns: elementIndex           - if found
              valueImplementor value - if not found
    "

    "
     #(10 20 30 40 10 20 30 40) prevIndexOf:40   from:7 to:2 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) prevIndexOf:40.0 from:7 to:2 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) prevIndexOf:35   from:7 to:5 ifAbsent:['none'] 
    "

    "Modified: / 20.5.1998 / 15:13:05 / cg"
! !

!SequenceableCollection methodsFor:'searching-identity'!

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

    "
     args:    anElement : <object>

     returns: elementIndex - if found
              0            - if not found
    "

    "
     #(10 20 30 40 50 60 70) identityIndexOf:40
     #(10 20 30 40 50 60 70) identityIndexOf:40.0
     #(10 20 30 40 50 60 70) indexOf:40.0

    be careful:

     #(10 20 30 40.0 50 60 70) indexOf:40.0
     #(10 20 30 40.0 50 60 70) identityIndexOf:40.0

    "

    "Modified: / 20.5.1998 / 14:57:14 / cg"
!

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

    "
     args:    anElement      : <object>
              exceptionBlock : <valueImplementor>

     returns: elementIndex         - if found
              exceptionBlock value - if not found
    "

    "
     #(10 20 30 40 50 60 70) identityIndexOf:40  ifAbsent:['none']  
     #(10 20 30 40 50 60 70) identityIndexOf:35  ifAbsent:['none']  
     #(10 20 30 40 50 60 70) identityIndexOf:40.0 ifAbsent:['none'] 
     #(10 20 30 40 50 60 70) indexOf:40.0         ifAbsent:['none'] 
    "

    "Modified: / 20.5.1998 / 14:57:31 / cg"
!

identityIndexOf:anElement or:anotherElement
    "search the collection for anElement and anotherElement using identity compare (i.e. ==);
     if any is found, return the index otherwise return 0."

    ^ self identityIndexOf:anElement or:anotherElement startingAt:1

    "
     args:    anElement : <object>
              anotherElement : <object>

     returns: elementIndex - if found
              0            - if not found
    "
!

identityIndexOf:anElement or:anotherElement startingAt:start
    "search the collection for anElement and anotherElement, starting search at index start
     using identity compare  (i.e. ==);
     if any is found, return the index otherwise return 0."

    |startIndex "{ Class: SmallInteger }"
     stop       "{ Class: SmallInteger }" 
     el |

    startIndex := start.
    stop := self size.
    startIndex to:stop do:[:index |
        el := self at:index.
        anElement == el ifTrue:[^ index].
        anotherElement == el ifTrue:[^ index].
    ].
    ^ 0

    "
     args:    anElement : <object>
              anotherElement : <object>
              start     : <integer>

     returns: elementIndex - if found
              0            - if not found
    "

    "
     #(10 20 30 40 10 20 30 40) identityIndexOf:40 or:30  startingAt:2
    "
!

identityIndexOf:anElement startingAt:start
    "search the collection for anElement, starting search at index start
     using identity compare  (i.e. ==);
     if found, return the index otherwise return 0."

    |startIndex "{ Class: SmallInteger }"
     stop       "{ Class: SmallInteger }" |

    startIndex := start.
    stop := self size.
    startIndex to:stop do:[:index |
        anElement == (self at:index) ifTrue:[^ index].
    ].
    ^ 0

    "
     args:    anElement : <object>
              start     : <integer>

     returns: elementIndex - if found
              0            - if not found
    "

    "
     #(10 20 30 40 10 20 30 40) identityIndexOf:40   startingAt:5
     #(10 20 30 40 10 20 30 40) identityIndexOf:40.0 startingAt:5
     #(10 20 30 40 10 20 30 40) indexOf:40.0         startingAt:5 
    "

    "Modified: / 20.5.1998 / 14:57:09 / cg"
!

identityIndexOf:anElement startingAt:start endingAt:stop
    "search the collection for anElement, starting the search at index start;
     ending at stop.
     If found (within the range), return the index, otherwise return 0.
     The comparison is done using = 
     (i.e. equality test - not identity test)."

    |startIndex "{ Class: SmallInteger }"
     stopIndex  "{ Class: SmallInteger }" |

    startIndex := start.
    stopIndex := self size min:stop.
    startIndex to:stopIndex do:[:index |
        anElement == (self at:index) ifTrue:[^ index].
    ].
    ^ 0

    "
     args:    anElement : <object>
              start     : <integer>
              stop      : <integer>

     returns: elementIndex - if found
              0            - if not found
    "

    "Created: / 12.4.1996 / 18:23:07 / cg"
    "Modified: / 20.5.1998 / 15:00:50 / cg"
!

identityIndexOf:anElement startingAt:start ifAbsent:exceptionBlock
    "search the collection for anElement, starting search at index 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

    "
     args:    anElement      : <object>
              start          : <integer>
              exceptionBlock : <valueImplementor>

     returns: elementIndex         - if found
              exceptionBlock value - if not found
    "

    "
     #(10 20 30 40 10) identityIndexOf:10 startingAt:3 ifAbsent:['none'] 
     #(10 20 30 40 10) identityIndexOf:35 startingAt:3 ifAbsent:['none'] 
    "

    "Modified: / 20.5.1998 / 15:01:23 / cg"
!

includesIdentical:anElement
    "return true if the collection contains anElement; false otherwise.
     Comparison is done using identity compare (i.e. ==).
     See #includes: if equality is asked for."

    ((self identityIndexOf:anElement startingAt:1) == 0) ifTrue:[^ false].
    ^ true

    "
     args:    anElement : <object> 

     returns: true  - if found
              false - if not found
    "

    "
     #(10 20 30 40 50 60 70) includesIdentical:40     
     #(10 20 30 40 50 60 70) includesIdentical:40.0    
     #(10 20 30 40 50 60 70) includes:40     
     #(10 20 30 40 50 60 70) includes:40.0    

     be careful:

     #(10 20 30 40.0 50 60 70) includes:40.0    
     #(10 20 30 40.0 50 60 70) includesIdentical:40.0    
    "

    "Modified: / 20.5.1998 / 15:00:16 / cg"
!

lastIdentityIndexOf:anElement
    "search the collection backwards for anElement;
     if found, return the index otherwise return 0.
     The comparison is done using == 
     (i.e. identity test - not equality test)."

    ^ self lastIdentityIndexOf:anElement startingAt:self size 

    "
     args:    anElement      : <object>

     returns: elementIndex - if found
              0            - if not found
    "

    "
     #(10 20 30 40 50 60 70) lastIdentityIndexOf:40    
     #(10 20 30 40 50 60 70) lastIdentityIndexOf:40.0  
     #(10 20 30 40 50 60 70) lastIdentityIndexOf:35    
     #(10 20 30 40 50 60 70) lastIdentityIndexOf:10    
    "

    "Created: / 20.5.1998 / 15:03:06 / cg"
!

lastIdentityIndexOf:anElement ifAbsent:exceptionBlock
    "search the collection backwards for anElement;
     if found, return the index otherwise return the value of the
     exceptionBlock.
     The comparison is done using == 
     (i.e. identity test - not equality test)."

    |index|

    index := self lastIdentityIndexOf:anElement startingAt:self size.
    (index == 0) ifTrue:[^ exceptionBlock value].
    ^ index

    "
     args:    anElement      : <object>
              exceptionBlock : <valueImplementor>

     returns: elementIndex         - if found
              exceptionBlock value - if not found
    "

    "
     #(10 20 30 40 10 20 30 40) lastIdentityIndexOf:40   ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) lastIdentityIndexOf:40.0 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) lastIdentityIndexOf:35   ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) lastIdentityIndexOf:10   ifAbsent:['none'] 
    "

    "Created: / 20.5.1998 / 15:04:46 / cg"
    "Modified: / 20.5.1998 / 15:05:53 / cg"
!

lastIdentityIndexOf:anElement startingAt:start
    "search the collection backwards for anElement, starting the search at index start;
     if found, return the index otherwise return 0.
     The comparison is done using == 
     (i.e. identity test - not equality test)."

    |startIndex "{ Class: SmallInteger }"|

    startIndex := start.
    startIndex to:1 by:-1 do:[:index |
        anElement == (self at:index) ifTrue:[^ index].
    ].
    ^ 0

    "
     args:    anElement      : <object>
              start          : <integer>

     returns: elementIndex - if found
              0            - if not found
    "

    "
     #(10 20 30 40 10 20 30 40) lastIdentityIndexOf:40   startingAt:8  
     #(10 20 30 40 10 20 30 40) lastIdentityIndexOf:40.0 startingAt:8  
     #(10 20 30 40 10 20 30 40) lastIdentityIndexOf:35   startingAt:8  
     #(10 20 30 40 10 20 30 40) lastIdentityIndexOf:10   startingAt:8  
     #(10 20 30 40 10 20 30 40) lastIdentityIndexOf:10   startingAt:4  
    "

    "Modified: / 20.5.1998 / 15:06:04 / cg"
!

lastIdentityIndexOf:anElement startingAt:start ifAbsent:exceptionBlock
    "search the collection backwards for anElement starting the search at 
     index start; if found, return the index 
     otherwise return the value of the exceptionBlock.
     The comparison is done using == 
     (i.e. identity test - not equality test)."

    |index|

    index := self lastIdentityIndexOf:anElement startingAt:start.
    (index == 0) ifTrue:[^ exceptionBlock value].
    ^ index

    "
     args:    anElement      : <object>
              start          : <integer>
              exceptionBlock : <valueImplementor>

     returns: elementIndex         - if found
              exceptionBlock value - if not found
    "

    "
     #(10 20 30 40 10 20 30 40) lastIdentityIndexOf:40   startingAt:8 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) lastIdentityIndexOf:40.0 startingAt:8 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) lastIdentityIndexOf:35   startingAt:8 ifAbsent:['none'] 
     #(10 20 30 40 10 20 30 40) lastIdentityIndexOf:10   startingAt:8 ifAbsent:['none'] 
    "

    "Modified: / 20.5.1998 / 15:06:21 / cg"
    "Created: / 20.5.1998 / 15:07:42 / cg"
! !

!SequenceableCollection methodsFor:'sorting & reordering'!

detectFirstInOrder:sortBlock
    "find the first element of the collection sorted with sortBlock"

    |selectedForNow start|

    start := true.
    self do:[:element|
        start ifTrue:[
            start := false.
            selectedForNow := element.
        ] ifFalse:[
            (sortBlock value:element value:selectedForNow) ifTrue:[
                selectedForNow := element.
            ].
        ].
    ].

    ^ selectedForNow

    "
     #(1 16 7 98 3 19 4 0) detectFirstInOrder:[:a :b | a < b] 
     #(1 16 7 98 3 19 4 0) detectFirstInOrder:[:a :b | a > b] 
     #(1 -1 16 -16 7 -7 98 -98) detectFirstInOrder:[:a :b | a < b] 
     #(1 -1 16 -16 7 -7 98 -98) detectFirstInOrder:[:a :b | a abs < b abs] 
    "
!

mergeSort
    "sort the collection using a mergeSort algorithm. 
     The elements are compared using'<' 
     i.e. they should offer a magnitude-like protocol.

     The implementation uses the mergesort algorithm, which may not be
     the best possible for all situations 
     See also #quickSort and #randomizedSort for other sort algorithms
     with different worst- and average case behavior)"

    |stop|

    stop := self size.
    (stop > 1) ifTrue:[
        self mergeSort:[:a :b | a < b] from:1 to:stop
    ]

    "
     #(1 16 7 98 3 19 4 0) mergeSort

     |data|
     data := Random new next:100000.
     'merge random  ' print. (Time millisecondsToRun:[data mergeSort]) printNL.
     'merge sorted  ' print. (Time millisecondsToRun:[data mergeSort]) printNL.
     data reverse. 
     'merge reverse ' print. (Time millisecondsToRun:[data mergeSort]) printNL.

     data := Random new next:100000.
     'quick random  ' print. (Time millisecondsToRun:[data sort]) printNL.
     'quick sorted  ' print. (Time millisecondsToRun:[data sort]) printNL.
     data reverse. 
     'quick reverse ' print. (Time millisecondsToRun:[data sort]) printNL.

     data := Random new next:100000.
     'quickr random  ' print. (Time millisecondsToRun:[data randomizedSort]) printNL.
     'quickr sorted  ' print. (Time millisecondsToRun:[data randomizedSort]) printNL.
     data reverse. 
     'quickr reverse ' print. (Time millisecondsToRun:[data randomizedSort]) printNL.
    "
!

mergeSort:sortBlock
    "sort the collection using a mergeSort algorithm. 
     The elements are compared using'<' 
     i.e. they should offer a magnitude-like protocol.

     The implementation uses the mergesort algorithm, which may not be
     the best possible for all situations 
     See also #quickSort and #randomizedSort for other sort algorithms
     with different worst- and average case behavior)"

    |stop|

    stop := self size.
    (stop > 1) ifTrue:[
        self mergeSort:sortBlock from:1 to:stop
    ]

    "
     #(1 16 7 98 3 19 4 0) mergeSort

     |data|
     data := Random new next:200000.
     Transcript show:'merge random  '; showCR:(Time millisecondsToRun:[data mergeSort]).
     Transcript show:'merge sorted  '; showCR:(Time millisecondsToRun:[data mergeSort]).
     data reverse. 
     Transcript show:'merge reverse '; showCR:(Time millisecondsToRun:[data mergeSort]).

     data := Random new next:200000.
     Transcript show:'quick random  '; showCR:(Time millisecondsToRun:[data sort]).
     Transcript show:'quick sorted  '; showCR:(Time millisecondsToRun:[data sort]).
     data reverse. 
     Transcript show:'quick reverse '; showCR:(Time millisecondsToRun:[data sort]).

     data := Random new next:200000.
     Transcript show:'quickr random  '; showCR:(Time millisecondsToRun:[data randomizedSort]).
     Transcript show:'quickr sorted  '; showCR:(Time millisecondsToRun:[data randomizedSort]).
     data reverse. 
     Transcript show:'quickr reverse '; showCR:(Time millisecondsToRun:[data randomizedSort]).
    "
!

mergeSort:aBlock from: startIndex to: stopIndex
    "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."

    | temp |

    self size <= 1 ifTrue: [^ self].  "nothing to do"
    startIndex = stopIndex ifTrue: [^ self].
    (startIndex >= 1 and: [startIndex < stopIndex])
            ifFalse: [self error: 'bad start index'].
    stopIndex <= self size
            ifFalse: [self error: 'bad stop index'].
    temp := self clone.
    self mergeSortFrom: startIndex to: stopIndex src: temp dst: self by: aBlock.

    "
     #(1 16 7 98 3 19 4 0) mergeSort  
    "

    "
     |data|
     data := Random new next:100000.
     Transcript show:'merge random  '; showCR:(Time millisecondsToRun:[data mergeSort]).
     Transcript show:'merge sorted  '; showCR:(Time millisecondsToRun:[data mergeSort]).
     data reverse. 
     Transcript show:'merge reverse '; showCR:(Time millisecondsToRun:[data mergeSort]).
    "
    "
     |data|
     data := Random new next:100000.
     Transcript show:'quick random  '; showCR:(Time millisecondsToRun:[data quickSort]).
     Transcript show:'quick sorted  '; showCR:(Time millisecondsToRun:[data quickSort]).
     data reverse. 
     Transcript show:'quick reverse '; showCR:(Time millisecondsToRun:[data quickSort]).
    "
!

quickSort
    "sort the collection inplace. The elements are compared using
     '<' i.e. they should offer a magnitude-like protocol.

     The implementation uses the quicksort algorithm, which may not be
     the best possible for all situations (quickSort has O-square worst
     case behavior). See also #randomizedSort for a version with better
     worstCase behavior (but worse average & bestCase behavior)"

    |stop|

    stop := self size.
    (stop > 1) ifTrue:[
        self quickSortFrom:1 to:stop
    ]

    "
     #(1 16 7 98 3 19 4 0) sort

     |data|
     data := Random new next:100000.
     'random  ' print. (Time millisecondsToRun:[data sort]) printNL.
     'sorted  ' print. (Time millisecondsToRun:[data sort]) printNL.
     data reverse. 
     'reverse ' print. (Time millisecondsToRun:[data sort]) printNL.
    "

    "Modified: 21.8.1997 / 18:31:52 / cg"
!

quickSort:sortBlock
    "sort the collection inplace using the 2-arg block sortBlock
     for comparison. This allows any sort criteria to be implemented.

     The implementation uses the quicksort algorithm, which may not be
     the best possible for all situations (quickSort has O-square worst
     case behavior). See also #randomizedSort: for a version with better
     worstCase behavior (but worse average & bestCase behavior)"

    |stop|

    stop := self size.
    (stop > 1) ifTrue:[
        sortBlock numArgs == 3 ifTrue:[
            "/ TODO: pass a collating policy to aBlock
            self quickSortFrom:1 to:stop sortBlock:sortBlock policy:(StringCollationPolicy new)
        ] ifFalse:[
            self quickSortFrom:1 to:stop 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] 
     #(1 -1 16 -16 7 -7 98 -98) sort:[:a :b | a < b] 
     #(1 -1 16 -16 7 -7 98 -98) sort:[:a :b | a abs < b abs] 
    "

    "Modified: / 27.10.1997 / 20:03:22 / cg"
!

quickSort:sortBlock with:aCollection
    "sort the collection inplace using the 2-arg block sortBlock
     for comparison. Also reorder the elements in aCollection.
     Use this, when you have a key collection to sort some other collection with.

     The implementation uses the quicksort algorithm, which may not be
     the best possible for all situations (quickSort has O-square worst
     case behavior). See also #randomizedSort: for a version with better
     worstCase behavior (but worse average & bestCase behavior)"

    |stop|

    stop := self size.
    (stop > 1) ifTrue:[
        self quickSortFrom:1 to:stop 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 printNL.
     c2 printNL
    "

    "Modified: 21.8.1997 / 18:32:11 / cg"
!

quickSortWith:aCollection
    "sort the receiver collection inplace, using '<' to compare elements.
     Also, the elements of aCollection are reordered with it.
     Use this, when you have a key collection to sort another collection with.

     The implementation uses the quicksort algorithm, which may not be
     the best possible for all situations (quickSort has O-square worst
     case behavior). See also #randomizedSort: for a version with better
     worstCase behavior (but worse average & bestCase behavior)"

    |stop|

    stop := self size.
    (stop > 1) ifTrue:[
        self quickSortFrom:1 to:stop with:aCollection
    ]

    "Modified: 21.8.1997 / 18:32:21 / cg"
!

randomizedSort
    "sort the collection inplace. The elements are compared using
     '<' i.e. they should offer a magnitude-like protocol.

     This uses the randomized quicksort algorithm, 
     which has a better worstCase behavior than quickSort
     (bit worse bestCase & averageCase behavior).
     See: Knuth or Cormen,Leiserson,Rivest pg. 163"

"/    |stop|
"/
"/    stop := self size.
"/    (stop > 1) ifTrue:[
"/        self randomizedQuickSortFrom:1 to:stop sortBlock:[:a :b | a < b] with:nil
"/    ]

    "/ code was never used - use regular sort for backward compatibility
    ^ self sort

!

randomizedSort:sortBlock
    "sort the collection inplace using the 2-arg block sortBlock
     for comparison. This allows any sort criteria to be implemented.

     This uses the randomized quicksort algorithm, 
     which has a better worstCase behavior than quickSort
     (bit worse bestCase & averageCase behavior).
     See: Knuth or Cormen,Leiserson,Rivest pg. 163"

"/    |stop|
"/
"/    stop := self size.
"/    (stop > 1) ifTrue:[
"/        self randomizedQuickSortFrom:1 to:stop sortBlock:sortBlock with:nil
"/    ]

    "/ code was never used - use regular sort for backward compatibility
    ^ self sort:sortBlock

!

randomizedSort:sortBlock with:aCollection
    "sort the collection inplace using the 2-arg block sortBlock
     for comparison. Also reorder the elements in aCollection.
     Use this, when you have a key collection to sort some other collection with.

     This uses the randomized quicksort algorithm, 
     which has a better worstCase behavior than quickSort
     (bit worse bestCase & averageCase behavior).
     See: Knuth or Cormen,Leiserson,Rivest pg. 163"

"/    |stop|
"/
"/    stop := self size.
"/    (stop > 1) ifTrue:[
"/        self randomizedQuickSortFrom:1 to:stop sortBlock:sortBlock with:aCollection
"/    ]

    "/ code was never used - use regular sort for backward compatibility
    ^ self sort:sortBlock with:aCollection

!

randomizedSortWith:aCollection
    "sort the receiver collection inplace, using '<' to compare elements.
     Also, the elements of aCollection are reordered with it.
     Use this, when you have a key collection to sort another collection with.

     This uses the randomized quicksort algorithm, 
     which has a better worstCase behavior than quickSort
     (bit worse bestCase & averageCase behavior).
     See: Knuth or Cormen,Leiserson,Rivest pg. 163"

"/    |stop|
"/
"/    stop := self size.
"/    (stop > 1) ifTrue:[
"/        self randomizedQuickSortFrom:1 to:stop sortBlock:[:a :b | a < b] with:aCollection
"/    ]

    "/ code was never used - use regular sort for backward compatibility
    ^ self sortWith:aCollection

!

reverse
    "destructively reverse the order of the elements inplace.
     WARNING: this is a destructive operation, which modifies the receiver."

    |lowIndex "{ Class: SmallInteger }"
     hiIndex  "{ Class: SmallInteger }"
     t1 t2|

    hiIndex := self size.
    lowIndex := 1.
    [lowIndex < hiIndex] whileTrue:[
        t1 := self at:lowIndex.  t2 := self at:hiIndex.
        self at:lowIndex put:t2.  self at:hiIndex put:t1.

        lowIndex := lowIndex + 1.
        hiIndex := hiIndex - 1
    ]

    "
     #(4 5 6 7 7) reverse
     #(1 4 7 10 2 5) asOrderedCollection reverse
    "
!

reversed
    "return a copy with elements in reverse order"

    ^ self copy reverse

    "
     #(4 5 6 7 7) reversed           
     #(1 4 7 10 2 5) asOrderedCollection reversed
    "
!

sort
    "sort the collection inplace. The elements are compared using
     '<' i.e. they should offer a magnitude-like protocol.

     The implementation uses the quicksort algorithm, which may not be
     the best possible for all situations (quickSort has O-square worst
     case behavior). See also #randomizedSort for a version with better
     worstCase behavior (but worse average & bestCase behavior)"

    self quickSort

    "
     #(1 16 7 98 3 19 4 0) sort

     |data|
     data := Random new next:100000.
     'random  ' print. (Time millisecondsToRun:[data sort]) printNL.
     'sorted  ' print. (Time millisecondsToRun:[data sort]) printNL.
     data reverse. 
     'reverse ' print. (Time millisecondsToRun:[data sort]) printNL.
    "

    "Modified: 21.8.1997 / 18:31:52 / cg"
!

sort:sortBlock
    "sort the collection inplace using the 2-arg block sortBlock
     for comparison. This allows any sort criteria to be implemented.

     The implementation uses the quicksort algorithm, which may not be
     the best possible for all situations (quickSort has O-square worst
     case behavior). See also #randomizedSort: for a version with better
     worstCase behavior (but worse average & bestCase behavior)"

    self quickSort: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] 
     #(1 -1 16 -16 7 -7 98 -98) sort:[:a :b | a < b] 
     #(1 -1 16 -16 7 -7 98 -98) sort:[:a :b | a abs < b abs] 
    "

    "Modified: / 27.10.1997 / 20:03:22 / cg"
!

sort:sortBlock with:aCollection
    "sort the collection inplace using the 2-arg block sortBlock
     for comparison. Also reorder the elements in aCollection.
     Use this, when you have a key collection to sort some other collection with.

     The implementation uses the quicksort algorithm, which may not be
     the best possible for all situations (quickSort has O-square worst
     case behavior). See also #randomizedSort: for a version with better
     worstCase behavior (but worse average & bestCase behavior)"

    self quickSort:sortBlock with:aCollection

    "
     |c1 c2|
     c1 := #(1 16 7 9).
     c2 := #('one' 'sixteen' 'seven' 'nine').
     c1 sort:[:a :b | a > b] with:c2.
     c1 printNL.
     c2 printNL
    "

    "Modified: 21.8.1997 / 18:32:11 / cg"
!

sortWith:aCollection
    "sort the receiver collection inplace, using '<' to compare elements.
     Also, the elements of aCollection are reordered with it.
     Use this, when you have a key collection to sort another collection with.

     The implementation uses the quicksort algorithm, which may not be
     the best possible for all situations (quickSort has O-square worst
     case behavior). See also #randomizedSort: for a version with better
     worstCase behavior (but worse average & bestCase behavior)"

    self quickSortWith:aCollection
!

topologicalSort:sortBlock
    "sort the collection inplace using a sloooow sort algorithm.
     This algorithm has O-square runtime behavior and should be used only
     in special situations.
     It compares all elements, thus can be used when a>b, b>c does NOT imply
     a>c (for example, to sort classes by inheritance)

     In all other situations, use #sort; which implements the quicksort algorithm.
    "

    |smallestIndex "{ Class: SmallInteger }"
     end           "{ Class: SmallInteger }"
     index2        "{ Class: SmallInteger }"
     smallest thisOne|

    "this is just a q&d hack - there must be better implementations for this ;-)"

    end := self size.
    1 to:end-1 do:[:index |
        smallest := self at:index.
        smallestIndex := index.

        index2 := index + 1.
        [
            thisOne := self at:index2.
            (index2 ~~ smallestIndex 
            and:[sortBlock value:thisOne value:smallest]) ifTrue:[
                smallestIndex := index2.
                smallest := thisOne.
                index2 := index + 1.
            ] ifFalse:[
                index2 := index2 + 1.
            ].
        ] doWhile:[index2 <= end].

"/        (index + 1) to:end do:[:index2 |
"/            thisOne := self at:index2.
"/            (sortBlock value:thisOne value:smallest) ifTrue:[
"/                smallestIndex := index2.
"/                smallest := thisOne
"/            ].
"/        ].

        (smallestIndex ~~ index) ifTrue:[
            thisOne := self at:index.
            self at:index put:smallest.
            self at:smallestIndex put:thisOne
        ].
    ]

    "
     #(1 16 7 98 3 19 4 0) topologicalSort:[:a :b | a < b]   
     #(1 16 7 98 3 19 4 0) sort:[:a :b | a < b]              
     Smalltalk allClasses asArray topologicalSort:[:a :b | b isSubclassOf:a] 
     Smalltalk allClasses asArray sort:[:a :b | b isSubclassOf:a] 
    "

    "Modified: 21.8.1997 / 18:30:49 / cg"
! !

!SequenceableCollection methodsFor:'testing'!

includesKey:anIndex
    "return true, if anIndex is a valid key.
     NOTICE: in ST-80, this message is only defined for Dictionaries,
             however, having a common protocol with indexed collections
             often simplifies things."

    anIndex isInteger ifFalse:[^ false].
    ^ (anIndex >= 1) and:[anIndex <= self size]

    "
     #(1 2 3) includesKey:4 
     #(1 2 3) includesKey:3  
    "
! !

!SequenceableCollection methodsFor:'visiting'!

acceptVisitor:aVisitor with:aParameter

    ^ aVisitor visitSequenceableCollection:self with:aParameter
! !

!SequenceableCollection class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/SequenceableCollection.st,v 1.214 2004-09-22 09:55:16 cg Exp $'
! !

SequenceableCollection initialize!