SeqColl.st
author claus
Mon, 10 Oct 1994 01:29:28 +0100
changeset 159 514c749165c3
parent 118 a0460951adf7
child 186 a4c3032fc825
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.
"

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

SequenceableCollection comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Attic/SeqColl.st,v 1.15 1994-10-10 00:28:06 claus Exp $
'!

!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.
"
!

version
"
$Header: /cvs/stx/stx/libbasic/Attic/SeqColl.st,v 1.15 1994-10-10 00:28:06 claus Exp $
"
!

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. See concrete subclasses (such as OrderedCollection).
"
! !

!SequenceableCollection class methodsFor:'instance creation'!

new:size withAll:element
    "return a new Collection of size, where all elements are
     initialized to element"

    |newCollection|

    newCollection := self new:size.
    newCollection atAllPut:element.
    ^ newCollection
! !

!SequenceableCollection methodsFor:'accessing'!

first
    "return the first element"

    ^ self at:1
!

last
    "return the last element"

    ^ self at:(self size)
!

at:index ifAbsent:exceptionBlock
    "return the element at index if valid. 
     If the index is invalid, return the result of evaluating 
     the exceptionblock."

    ((index < 1) or:[index > self size]) ifTrue:[
	^ exceptionBlock value
    ].
    ^ self at:index

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

!SequenceableCollection methodsFor:'queries'!

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

    ^ true
!

firstIndex
    "return the first elements index"

    ^ 1
!

lastIndex
    "return the last elements index"

    ^ self size
!

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

    ^ self subclassResponsibility
!

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

    |sz|

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

!SequenceableCollection methodsFor:'comparing'!

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

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

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

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

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

    "
     #(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   
    "
!

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 ..."

    ^ (self at:1 ifAbsent:[0]) hash * self size

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

startsWith:aCollection
    "return true, if the receivers first elements match those
     of aCollection"

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

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

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

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

    "
     'abcde' startsWith:#($a $b $c)
     #[1 2 3 4] startsWith:#(1 2 3)
     #(1 2 3 4) asOrderedCollection startsWith:#(1 2 3)
    "
!

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

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

    (aCollection == self) ifTrue:[^ true].
    (aCollection isSequenceableCollection) 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)
    "
! !

!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 species new:newSize) postCopyFrom:self.

    newCollection replaceFrom:1 to:mySize with:self startingAt:1.
    dstIndex := mySize + 1.
    (aCollection isSequenceableCollection) 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)
    "
!

copyWith:newElement
    "return a new collection consisting of a copy of the receivers elements
     plus the argument."

    |newCollection mySize newSize|

    mySize := self size.
    newSize := mySize + 1.
    newCollection := (self species new:newSize) postCopyFrom:self.
    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
    "
!

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."

    |copy skipIndex sz|

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

    sz := self size.
    copy := (self species new:(sz - 1)) postCopyFrom:self.
    copy replaceFrom:1 to:(skipIndex - 1) with:self startingAt:1.
    copy replaceFrom:skipIndex to:(sz - 1) 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
    "
!

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 copy srcIndex dstIndex skipIndex sz 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 species new:(sz - n)) postCopyFrom:self.

    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
     #($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
    "
!

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

    |copy sz|

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

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

copyFrom:start to:stop
    "return a new collection consisting of receivers elements
     between start and stop"

    |newCollection newSize|

    newSize := stop - start + 1.
    newCollection := (self species new:newSize) postCopyFrom:self.
    newCollection replaceFrom:1 to:newSize with:self startingAt:start.
    ^ newCollection

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

copyFrom:start
    "return a new collection consisting of receivers elements
     from start to the end of the collection"

    ^ self copyFrom:start to:(self size)

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

copyTo:stop
    "return a new collection consisting of receivers elements
     from 1 up to (including) index stop"

    ^ self copyFrom:1 to:stop

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

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
    "
!

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
    "
!

copyUpTo:element
    "return a new collection consisting of the receiver elements
     up-to (but excluding) the first occurence of element."

    |idx|

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

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

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
    "
!

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 replSize|

    replSize := aCollection size.
    newColl := self species new:(self size - (endIndex - startIndex + 1) + replSize).
    newColl postCopyFrom:self.
    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, '  
    "
! !

!SequenceableCollection methodsFor:'filling and replacing'!

from:index1 to:index2 put:anObject
    "replace the elements from index1 to index2 of the collection
     by the argument, anObject.
     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
    ]

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

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

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

atAll:indexCollection put:anObject
    "put anObject into all indexes from indexCollection in the receiver.
     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    indexCollection do:[:index | self at:index put:anObject]

    "
     (Array new:10) atAll:(1 to:5) put:0
     (Array new:10) atAll:#(1 5 6 9) put:0
    "
!

replaceAll:oldObject by:newObject
    "replace all oldObjects by newObject in the receiver.
     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    1 to:self size do:[:index |
	(self at:index) = oldObject ifTrue:[
	    self at:index put:newObject
	]
    ]

    "
     '123123abc123' replaceAll:$1 by:$*
     #($a $b $a $c $a $d $a $e) replaceAll:$a by:$A
    "
!

replaceAny:aCollection by:newObject
    "replace all elements, which are in aCollection by newObject in the receiver.
     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    1 to:self size do:[:index |
	(aCollection includes:(self at:index)) ifTrue:[
	    self at:index put:newObject
	]
    ]

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

replaceFrom:start with:replacementCollection
    "replace elements in the receiver starting at start,
     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:start 
		    to:(start + replacementCollection size - 1)
		  with:replacementCollection
	    startingAt:1

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

replaceFrom:start with:replacementCollection startingAt:offset
    "replace elements in the receiver starting at start,
     with elements taken from replacementCollection starting at offset
     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:start 
		    to:(start + replacementCollection size - offset)
		  with:replacementCollection
	    startingAt:offset

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

replaceFrom:start to:stop with:replacementCollection
    "replace elements in the receiver between index start and stop,
     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:start
		    to:stop
		  with:replacementCollection
	    startingAt:1

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

replaceFrom:start to:stop with:replacementCollection startingAt:repStart
    "replace elements in the receiver between index start and stop,
     with elements  taken from replacementCollection starting at repStart.
     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 }" |

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

    srcIndex := repStart.
    dstIndex := start.
    end := stop.
    [dstIndex <= end] whileTrue:[
	self at:dstIndex put:(replacementCollection at:srcIndex).
	srcIndex := srcIndex + 1.
	dstIndex := dstIndex + 1
    ]

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

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'
    "
!

withCRs
    "return a new collection consisting of receivers elements
     with all \-characters replaced by cr-characters.
     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    ^ self copy replaceAll:$\ by:(Character cr)
!

withoutCRs
    "return a new collection consisting of receivers elements
     with all cr-characters replaced by \-characters.
     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    ^ self copy replaceAll:(Character cr) by:$\
! !

!SequenceableCollection methodsFor:'adding & removing'!

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
    "
!

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
    "
!

remove:anElement ifAbsent:aBlock
    "search for anElement and, if present remove and return it.
     If not present, return the value of evaluating aBlock.

     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]
    "
!

removeFromIndex:startIndex toIndex:endIndex
    "remove the elements stored at indexes between startIndex and endIndex.

     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)."

    |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 
    "
!

removeAtIndex:index
    "remove the argument stored at index 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)."

    |element|

    element := self at:index.
    self removeIndex:index.
    ^ element

    "
     #($a $b $c $d $e $f $g) removeAtIndex:3
    "
!

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

    "
     #($a $b $c $d $e $f $g) removeIndex: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
    "
!

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:'searching'!

detect:aBlock ifNone:exceptionBlock
    "find the first element, for which evaluation of the argument, aBlock
     return true; if none does so, return the evaluation of exceptionBlock

    reimplemented here for speed"

    |stop  "{ Class: SmallInteger }"
     element|

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

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

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

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

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

    "
     #(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'] 
    "
!

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

    "
     #(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  
    "
!

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

    "
     #(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'] 
    "
!

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

    "
     #(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
    "
!

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

    "
     #(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'] 
    "
!

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

    "
     #(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 
    "
!

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

    "
     #(10 20 30 40 10) identityIndexOf:10 startingAt:3 ifAbsent:['none'] 
     #(10 20 30 40 10) identityIndexOf:35 startingAt:3 ifAbsent:['none'] 
    "
!

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  
    "
!

findFirst:aBlock
    "find the first element, for which evaluation of the argument, aBlock
     returns true; return its index or 0 if none detected."

    |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]]
     'one.two.three' findFirst:[:c | (c == $.)]
    "
!

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 == $.)]
    "
!

includes:anElement
    "return true if the collection contains anElement; false otherwise.
     Comparison is done using equality compare (i.e. =).
     Q: Should there also be some identityIncludes ?"

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

    "
     #(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    
    "
! !

!SequenceableCollection methodsFor:'sorting & reordering'!

reverse
    "reverse the order of the elements inplace"

    |lowIndex "{ Class: SmallInteger }"
     hiIndex  "{ Class: SmallInteger }"
     t|

    hiIndex := self size.
    lowIndex := 1.
    [lowIndex < hiIndex] whileTrue:[
	t := self at:lowIndex.
	self at:lowIndex put:(self at:hiIndex). 
	self at:hiIndex put:t.
	lowIndex := lowIndex + 1.
	hiIndex := hiIndex - 1
    ]
    "
     #(4 5 6 7 7) reverse
     #(1 4 7 10 2 5) asOrderedCollection reverse
    "
!

quickSortFrom:begin to:end
    "actual quicksort worker for sort-message"

    |b "{ Class: SmallInteger }"
     e "{ Class: SmallInteger }"
     middleElement temp |

    b := begin.
    e := end.
    middleElement := self at:((b + e) // 2).

    [b < e] whileTrue:[
	[b < end and:[(self at:b) < middleElement]] whileTrue:[b := b + 1].
	[e > begin and:[middleElement < (self at:e)]] whileTrue:[e := e - 1].

	(b <= e) ifTrue:[
	    (b == e) ifFalse:[
		temp := self at:b.
		self at:b put:(self at:e).
		self at:e put:temp
	    ].
	    b := b + 1.
	    e := e - 1
	]
    ].
    (begin < e) ifTrue:[self quickSortFrom:begin to:e].
    (b < end) ifTrue:[self quickSortFrom:b to:end]
!

quickSortFrom:begin to:end with:aCollection
    "actual quicksort worker for sortWith-message"

    |b "{ Class: SmallInteger }"
     e "{ Class: SmallInteger }"
     middleElement temp |

    b := begin.
    e := end.
    middleElement := self at:((b + e) // 2).

    [b < e] whileTrue:[
	[b < end and:[(self at:b) < middleElement]] whileTrue:[b := b + 1].
	[e > begin and:[middleElement < (self at:e)]] whileTrue:[e := e - 1].

	(b <= e) ifTrue:[
	    (b == e) ifFalse:[
		temp := self at:b.
		self at:b put:(self at:e).
		self at:e put:temp.
		temp := aCollection at:b.
		aCollection at:b put:(aCollection at:e).
		aCollection at:e put:temp
	    ].
	    b := b + 1.
	    e := e - 1
	]
    ].
    (begin < e) ifTrue:[self quickSortFrom:begin to:e with:aCollection].
    (b < end) ifTrue:[self quickSortFrom:b to:end with:aCollection]
!

quickSortFrom:begin to:end sortBlock:sortBlock
    "actual quicksort worker for sort:-message"

    |b "{ Class: SmallInteger }"
     e "{ Class: SmallInteger }"
     middleElement temp |

    b := begin.
    e := end.
    middleElement := self at:((b + e) // 2).

    [b < e] whileTrue:[
	[b < end and:[sortBlock value:(self at:b) value:middleElement]] whileTrue:[b := b + 1].
	[e > begin and:[sortBlock value:middleElement value:(self at:e)]] whileTrue:[e := e - 1].

	(b <= e) ifTrue:[
	    (b == e) ifFalse:[
		temp := self at:b.
		self at:b put:(self at:e).
		self at:e put:temp
	    ].
	    b := b + 1.
	    e := e - 1
	]
    ].
    (begin < e) ifTrue:[self quickSortFrom:begin to:e sortBlock:sortBlock].
    (b < end) ifTrue:[self quickSortFrom:b to:end sortBlock:sortBlock]
!

quickSortFrom:begin to:end sortBlock:sortBlock with:aCollection
    "actual quicksort worker for sort:with:-message"

    |b "{ Class: SmallInteger }"
     e "{ Class: SmallInteger }"
     middleElement temp |

    b := begin.
    e := end.
    middleElement := self at:((b + e) // 2).

    [b < e] whileTrue:[
	[b < end and:[sortBlock value:(self at:b) value:middleElement]] whileTrue:[b := b + 1].
	[e > begin and:[sortBlock value:middleElement value:(self at:e)]] whileTrue:[e := e - 1].

	(b <= e) ifTrue:[
	    (b == e) ifFalse:[
		temp := self at:b.
		self at:b put:(self at:e).
		self at:e put:temp.
		temp := aCollection at:b.
		aCollection at:b put:(aCollection at:e).
		aCollection at:e put:temp
	    ].
	    b := b + 1.
	    e := e - 1
	]
    ].
    (begin < e) ifTrue:[self quickSortFrom:begin to:e sortBlock:sortBlock with:aCollection].
    (b < end) ifTrue:[self quickSortFrom:b to:end sortBlock:sortBlock with:aCollection]
!

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 other situations, use #sort; which implements the quicksort algorithm.
    "

    |smallestIndex "{ Class: SmallInteger }"
     end           "{ Class: SmallInteger }"
     smallest thisOne|

    "this is just a q&d hack - there must be better implementations for this ;-)"

    end := self size.
    1 to:end do:[:index |
	smallest := self at:index.
	smallestIndex := index.

	(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] 
    "
!

sort
    "sort the collection inplace. The elements are compared using
     > and < 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."

    |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.
    "
!

sort:sortBlock
    "sort the collection inplace using the 2-arg block sortBlock
     for comparison. This allows any sort criteria to be implemented."

    |stop|

    stop := self size.
    (stop > 1) ifTrue:[
	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]
    "
!

sortWith:aCollection
    "sort the receiver collection inplace, also sort aCollection with it.
     Use, when you have a key collection to sort another collection with."

    |stop|

    stop := self size.
    (stop > 1) ifTrue:[
	self quickSortFrom:1 to:stop with:aCollection
    ]

    "
     |c1 c2|
     c1 := #(1 16 7 9).
     c2 := #('one' 'sixteen' 'seven' 'nine').
     c1 sortWith:c2.
     c1 printNL.
     c2 printNL
    "
!

sort:sortBlock with:aCollection
    "sort the collection inplace using the 2-arg block sortBlock
     for comparison. Also reorder the elements in aCollection.
     Use, when you have a key collection to sort some other collection with."

    |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
    "
! !

!SequenceableCollection methodsFor:'enumerating'!

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]
    "
!

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]
    "
!

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]
    "
!

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.
    stop := index2.
    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 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.
    stop := index2.
    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]
    "
!

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]
    "
!

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 species new:sz) postCopyFrom:self.
    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]   
    "
!

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
     idx  "{ Class:SmallInteger }"|

    newCollection := (self species new:(stop - start + 1)) postCopyFrom:self.
    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]  
    "
!

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 := (species new:sz) postCopyFrom:self.
	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']   
    "
! !