OrdColl.st
author claus
Tue, 08 Aug 1995 02:49:43 +0200
changeset 375 e5019c22f40e
parent 370 20f04d9b371b
child 379 5b5a130ccd09
permissions -rw-r--r--
.

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

SequenceableCollection subclass:#OrderedCollection
	 instanceVariableNames:'contentsArray firstIndex lastIndex'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Collections-Sequenceable'
!

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

$Header: /cvs/stx/stx/libbasic/Attic/OrdColl.st,v 1.29 1995-08-08 00:48:10 claus Exp $
'!

!OrderedCollection 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/OrdColl.st,v 1.29 1995-08-08 00:48:10 claus Exp $
"
!

documentation
"
    OrderedCollection have ordered elements. Insertion and removal at both ends
    is possible - therefore they can be used for queues and stacks.

    Instance variables:

    contentsArray   <Array>         the actual contents
    firstIndex      <SmallInteger>  index of first valid element
    lastIndex       <SmallInteger>  index of last valid element
"
! !

!OrderedCollection class methodsFor:'instance creation'!

new:size
    "create a new OrderedCollection"

    ^ (self basicNew) initContents:size
!

new
    "create a new OrderedCollection"

    ^ (self basicNew) initContents:10
! !

!OrderedCollection methodsFor:'private accessing'!

contentsArray
    ^ contentsArray
!

firstIndex
    ^ firstIndex
! !

!OrderedCollection methodsFor:'queries'!

size
    "return the number of elements in the collection"

    ^ lastIndex - firstIndex + 1
!

capacity
    "return the number of elements, that the receiver is
     prepared to take.
     Not used by the system; added for ST-80 compatibility."

    ^ contentsArray size
!

isFixedSize
    "return true if the receiver cannot grow - this will vanish once
     Arrays and Strings learn how to grow ..."

    ^ false
! !

!OrderedCollection methodsFor:'copying'!

copyEmpty
    "return a copy of the receiver without any elements."

    ^ self copyEmpty:10
!

postCopy
    "have to copy the contentsArray too"

    contentsArray := contentsArray shallowCopy
!

, aCollection
    "return a new collection formed from concatenating the receiver with
     the argument"

    |newCollection|

    newCollection := self copyEmpty:(self size + aCollection size).
    self do:[:element |
	newCollection add:element
    ].
    aCollection do:[:element |
	newCollection add:element
    ].
    ^ newCollection

    "
     #(1 2 3) asOrderedCollection , #(4 5 6) asOrderedCollection
     #(1 2 3) asSortedCollection , #(99 101 100) asSortedCollection
    "
!

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. "must grow, otherwise replace fails"
    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
    "
!

copy
    "return a new OrderedCollection containing the elements of the receiver."

    "redefinition is a consequence of the implementation with a
     separate array - otherwise we get a shallow copy of the
     contents array, which is not what we want here"

    ^ self copyFrom:1 to:self size
!

copyFrom:start to:stop
    "return a new OrderedCollection containing the elements
     from start to stop."

    |newCollection sz|

    sz := stop - start + 1.
    newCollection := self copyEmptyAndGrow:sz.   "must grow, otherwise replace fails"
    newCollection replaceFrom:1 to:sz with:self startingAt:start.
    ^ newCollection
! !

!OrderedCollection methodsFor:'adding & removing'!

removeFirst
    "remove the first element from the collection; return the element"

    |anObject |

    firstIndex > lastIndex ifTrue:[
	"error if collection is empty"
	^ self emptyCollectionError.
    ].
    anObject := contentsArray at:firstIndex.
    contentsArray at:firstIndex put:nil.
    firstIndex := firstIndex + 1.

    firstIndex > lastIndex ifTrue:[
	"reset to avoid ever growing"
	firstIndex := 1.
	lastIndex := 0 
    ].
    ^ anObject

    "
     (OrderedCollection withAll:#(1 2 3 4 5)) removeFirst; yourself
     OrderedCollection new removeFirst
     (SortedCollection withAll:#(5 4 3 2 1)) removeFirst; yourself
    "
!

removeLast
    "remove the last element from the collection; return the element"

    |anObject |

    firstIndex > lastIndex ifTrue:[
	"error if collection is empty"
	^ self emptyCollectionError.
    ].
    anObject := contentsArray at:lastIndex.
    contentsArray at:lastIndex put:nil.
    lastIndex := lastIndex - 1.

    firstIndex > lastIndex ifTrue:[
	"reset to avoid ever growing"
	firstIndex := 1.
	lastIndex := 0 
    ].
    ^ anObject

    "
     (OrderedCollection withAll:#(1 2 3 4 5)) removeLast; yourself
     OrderedCollection new removeLast
     (SortedCollection withAll:#(5 4 3 2 1)) removeLast; yourself
    "
!

removeFirst:n
    "remove the first n elements from the collection; 
     return the elements in an Array"

    |mySize ret|

    mySize := self size.
    mySize < n ifTrue:[
	"error if collection has not enough elements"
	^ self notEnoughElementsError.
    ].

    ret := Array new:n.
    ret replaceFrom:1 to:n with:contentsArray startingAt:firstIndex.
    "/
    "/ nil-out contents array, to not keep elements from being GC'd
    "/
    contentsArray from:firstIndex to:firstIndex + n - 1 put:nil.
    firstIndex := firstIndex + n.

    firstIndex > lastIndex ifTrue:[
	"reset to avoid ever growing"
	firstIndex := 1.
	lastIndex := 0 
    ].
    ^ ret

    "
     (OrderedCollection withAll:#(1 2 3 4 5)) removeFirst:2; yourself 
     (OrderedCollection withAll:#(1 2 3 4 5)) removeFirst:0; yourself 
     OrderedCollection new removeFirst:2 
     (OrderedCollection withAll:#(1 2 3 4 5)) removeFirst:6 
     (SortedCollection withAll:#(5 4 3 2 1)) removeFirst:2; yourself  
    "
!

removeLast:n
    "remove the last n elements from the collection; 
     return the elements in an Array"

    |mySize ret|

    mySize := self size.
    mySize < n ifTrue:[
	"error if collection has not enough elements"
	^ self notEnoughElementsError.
    ].

    ret := Array new:n.
    ret replaceFrom:1 to:n with:contentsArray startingAt:lastIndex - n + 1.
    "/
    "/ nil-out contents array, to not keep elements from being GC'd
    "/
    contentsArray from:lastIndex - n + 1 to:lastIndex put:nil.
    lastIndex := lastIndex - n.

    firstIndex > lastIndex ifTrue:[
	"reset to avoid ever growing"
	firstIndex := 1.
	lastIndex := 0 
    ].
    ^ ret

    "
     (OrderedCollection withAll:#(1 2 3 4 5)) removeLast:2; yourself 
     (OrderedCollection withAll:#(1 2 3 4 5)) removeLast:0; yourself 
     (OrderedCollection withAll:#(1 2 3 4 5)) removeLast:6; yourself 
     (SortedCollection withAll:#(5 4 3 2 1)) removeLast:2; yourself  
    "
!

removeFromIndex:startIndex toIndex:stopIndex
    "remove the elements stored under startIndex up to and including
     the elements under stopIndex.
     Return the receiver.
     Returning the receiver here is a historic leftover - it may change.
     Please use yourself in a cascade, if you need the receivers value
     when using this method."

    |nDeleted|

    (startIndex < 1
    or:[stopIndex > self size]) ifTrue:[
	^ self notEnoughElementsError
    ].
    nDeleted := stopIndex - startIndex + 1.
    contentsArray 
	replaceFrom:(firstIndex + startIndex - 1)
	to:(lastIndex - nDeleted)
	with:contentsArray 
	startingAt:(firstIndex + stopIndex).

    contentsArray
	from:(lastIndex - nDeleted + 1)
	to:lastIndex
	put:nil.

    lastIndex := lastIndex - nDeleted.
    firstIndex > lastIndex ifTrue:[
	"reset to avoid ever growing"
	firstIndex := 1.
	lastIndex := 0 
    ]

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

remove:anObject ifAbsent:exceptionBlock
    "remove the first occurrence of anObject from the collection;
     return the value of exceptionBlock if anObject is not in
     the collection"

    |index "{ Class:SmallInteger }"|

    index := firstIndex.
    [index <= lastIndex] whileTrue:[
	anObject = (contentsArray at:index) ifTrue:[
	    contentsArray 
		replaceFrom:index
		to:(contentsArray size - 1)
		with:contentsArray 
		startingAt:(index + 1).
	    contentsArray at:lastIndex put:nil.
	    lastIndex := lastIndex - 1.
	    firstIndex > lastIndex ifTrue:[
		"reset to avoid ever growing"
		firstIndex := 1.
		lastIndex := 0 
	    ].
	    ^ anObject
	].
	index := index + 1
    ].
    ^ exceptionBlock value

    "
     #(1 2 3 4 5 6 7 8 9) asOrderedCollection remove:3 ifAbsent:'oops' 
     #(1 2 3 4 5) asOrderedCollection remove:9 ifAbsent:'oops' 
    "
!

removeAll
    "remove all elements from the collection."

    self initContents:10
!

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

    "/ this is a q&d implementation (slow).
    "/ it should be rewritten to 

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

add:anObject
    "add the argument, anObject to the end of the collection
     Return the argument, anObject."

    |idx "{ Class:SmallInteger }"|

    idx := lastIndex.

    (idx == contentsArray size) ifTrue:[
	self makeRoomAtLast.
	idx := lastIndex.
    ].
    idx := lastIndex := idx + 1.
    contentsArray at:idx put:anObject.
"/    lastIndex := idx.
    ^ anObject

    "
     |c|
     c := #(4 3 2 1) asOrderedCollection.
     c add:'here'
    "
!

addFirst:anObject
    "add the argument, anObject to the beginning of the collection.
     Return the argument, anObject."

    (firstIndex == 1) ifTrue:[
	self makeRoomAtFront
    ].
    firstIndex := firstIndex - 1.
    contentsArray at:firstIndex put:anObject.
    ^ anObject

    "
     |c|
     c := #(1 2 3 4) asOrderedCollection.
     c addFirst:'here'.
     c
    "

    "
     |c|
     c := #() asOrderedCollection.
     c addFirst:'here'.
     c
    "
!

add:anObject beforeIndex:index
    "insert the argument, anObject to become located at index.
     Return the argument, anObject."

    self makeRoomAtIndex:(index - firstIndex + 1).
    contentsArray at:(index - firstIndex + 1) put:anObject.

    "
     |c|
     c := #(4 3 2 1) asOrderedCollection.
     c add:'here' beforeIndex:3
    "
    "
     |c|
     c := #(4 3 2 1) asOrderedCollection.
     c add:'here' beforeIndex:1   
    "
    "
     |c|
     c := #(4 3 2 1) asOrderedCollection.
     c add:'here' beforeIndex:5   
    "
!

add:anObject afterIndex:index
    "insert the argument, anObject to become located at index.
     Return the argument, anObject."

    ^ self add:anObject beforeIndex:(index + 1)

    "
     |c|
     c := #(4 3 2 1) asOrderedCollection.
     c add:'here' afterIndex:4           
    "
!

add:newObject after:oldObject
    "insert the argument, newObject after oldObject.
     If oldObject is not in the receiver, report an error,
     otherwise return the argument, anObject."

    |idx|

    idx := self indexOf:oldObject.
    idx ~~ 0 ifTrue:[
	^ self add:newObject beforeIndex:(idx + 1).
    ].
    self errorValueNotFound:oldObject

    "
     |c|
     c := #(4 3 2 1) asOrderedCollection.
     c add:'here' after:3. 
    "
    "
     |c|
     c := #(4 3 2 1) asOrderedCollection.
     c add:'here' after:1.   
    "
    "
     |c|
     c := #(4 3 2 1) asOrderedCollection.
     c add:'here' after:5 
    "
! 


add:newObject before:oldObject
    "insert the argument, newObject before oldObject.
     If oldObject is not in the receiver, report an error,
     otherwise return the argument, anObject."

    |idx|

    idx := self indexOf:oldObject.
    idx ~~ 0 ifTrue:[
	^ self add:newObject beforeIndex:idx.
    ].
    self errorValueNotFound:oldObject

    "
     |c|
     c := #(4 3 2 1) asOrderedCollection.
     c add:'here' before:3.
     c add:'here' before:5 
    "
! !

!OrderedCollection methodsFor:'grow & shrink'!

grow:newSize
    "grow the receiver to newSize"

    |oldSize newContents oldLast newLast|

    oldSize := lastIndex - firstIndex + 1.
    newSize ~~ oldSize ifTrue:[
	newLast := firstIndex + newSize - 1.
	newSize < oldSize ifTrue:[
	    oldLast := lastIndex.
	    lastIndex := newLast.
	    "
	     nil out rest, to give GC a chance to reclaim things
	    "
	    contentsArray from:lastIndex + 1 to:oldLast put:nil. 
	] ifFalse:[
	    newLast <= contentsArray size ifTrue:[
		lastIndex := newLast.
		^ self
	    ].

	    newContents := Array basicNew:newSize.
	    newContents replaceFrom:1 to:oldSize with:contentsArray startingAt:firstIndex.
	    contentsArray := newContents.
	    firstIndex := 1.
	    lastIndex := newSize
	]
    ]
! !

!OrderedCollection methodsFor:'accessing'!

at:anInteger
    "return the element at index, anInteger"

    |idx|

    idx := anInteger + firstIndex - 1.
    ((anInteger < 1) or:[idx > lastIndex]) ifTrue:[
	^ self subscriptBoundsError:anInteger
    ] ifFalse:[
	^ contentsArray at:idx
    ]
!

at:anInteger put:anObject
    "set the element at index, to be anInteger"

    |idx|

    idx := anInteger + firstIndex - 1.
    ((anInteger < 1) or:[idx > lastIndex]) ifTrue:[
	^ self subscriptBoundsError:anInteger
    ] ifFalse:[
	^ contentsArray at:idx put:anObject
    ]
!

first
    "return the first element"

    firstIndex <= lastIndex ifTrue:[
	^ contentsArray at:firstIndex
    ].
    "error if collection is empty"
    ^ self emptyCollectionError

    "
     (OrderedCollection withAll:#(1 2 3 4 5)) first
     (SortedCollection withAll:#(5 4 3 2 1)) first
    "
!

last
    "return the last element"

    firstIndex <= lastIndex ifTrue:[
	^ contentsArray at:lastIndex
    ].
    "error if collection is empty"
    ^ self emptyCollectionError

    "
     (OrderedCollection withAll:#(1 2 3 4 5)) last
     (SortedCollection withAll:#(5 4 3 2 1)) last
    "
! !

!OrderedCollection methodsFor:'filling & replacing'!

replaceFrom:start to:stop with:aCollection startingAt:repStart
    "redefined - can be done faster"

    |end|

    end := stop + firstIndex - 1.
    ((start >= 1) and:[end <= lastIndex]) ifTrue:[
	aCollection class == self class ifTrue:[
	    contentsArray
		replaceFrom:(start + firstIndex - 1)
		to:end
		with:aCollection contentsArray
		startingAt:(repStart + aCollection firstIndex - 1).
	] ifFalse:[
	    contentsArray
		replaceFrom:(start + firstIndex - 1)
		to:end
		with:aCollection
		startingAt:repStart.
	].
	^ self
    ].
    ^ super replaceFrom:start to:stop with:aCollection startingAt:repStart

    "
     |c|

     c := #(1 2 3 4 5 6) asOrderedCollection.
     c replaceFrom:3 to:6 with:c startingAt:2.
     c  
    "
    "
     |c|

     c := #(1 2 3 4 5 6) asOrderedCollection.
     c replaceFrom:3 to:5 with:c startingAt:4.
     c     
    "
! !

!OrderedCollection methodsFor:'searching'!

after:anObject
    "return the element, after anObject.
     If anObject is not in the receiver, report an error."

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

after:anObject ifAbsent:exceptionBlock
    "return the element after the argument anObject, nil if there is none.
     If anObject is not in the receiver, return the result from evaluating exceptionBlock."

    |idx|

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

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

before:anObject
    "return the element before the argument, anObject.
     If anObject is not in the receiver, report an error."

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

before:anObject ifAbsent:exceptionBlock
    "return the element before the argument anObject, nil if there is none.
     If anObject is not in the receiver, return the result from evaluating exceptionBlock."

    |idx|

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

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

!OrderedCollection methodsFor:'private'!

setFirstIndex:newFirstIndex lastIndex:newLastIndex
    "set first and last index"

    firstIndex := newFirstIndex.
    lastIndex := newLastIndex.
!

makeRoomAtLast
    "grow/shift the contents for more room at the end.
     Does not change the logical size.
     i.e.
     #(1 2 3 4 5 6) -> #(1 2 3 4 5 6 nil)"

    |newContents 
     oldSize    "{ Class:SmallInteger }"
     newSize    "{ Class:SmallInteger }" 
     startIndex "{ Class:SmallInteger }"
     sz         "{ Class:SmallInteger }"|

    oldSize := contentsArray size.
    sz := lastIndex - firstIndex + 1.

    "
     if there is lots of room at the beginning (> 50%), 
     shift instead of growing. This helps collections which get
     elements removed at front and added at the end.
    "
    oldSize > (sz * 2) ifTrue:[
	startIndex := firstIndex // 4.
	startIndex == 0 ifTrue:[
	    startIndex := 1
	].
	contentsArray 
	    replaceFrom:startIndex
	    to:startIndex + sz - 1
	    with:contentsArray
	    startingAt:firstIndex.
	contentsArray from:startIndex + sz to:lastIndex put:nil.
	firstIndex := startIndex.
	lastIndex := startIndex + sz - 1.
	^ self
    ].
    newSize := oldSize * 2.
    newSize == 0 ifTrue:[newSize := 3].
    newContents := Array basicNew:newSize.
    newContents 
	replaceFrom:1 
	to:oldSize 
	with:contentsArray
	startingAt:1.
    contentsArray := newContents
!

makeRoomAtFront
    "grow/shift the contents for more room at the beginning.
     Does not change the logical size.
     i.e.
     #(1 2 3 4 5 6) -> #(nil 1 2 3 4 5 6)"

    |newContents
     oldSize    "{ Class:SmallInteger }"
     newSize    "{ Class:SmallInteger }" 
     startIndex "{ Class:SmallInteger }"
     sz         "{ Class:SmallInteger }"|

    oldSize := contentsArray size.
    oldSize == 0 ifTrue:[ 
	contentsArray := Array basicNew:3.
	firstIndex := 2. lastIndex := 1.
	^ self
    ].

    sz := lastIndex - firstIndex + 1.

    "
     if there is lots of room at the end (> 50%), 
     shift instead of growing. This helps collections
     which get elements removed at the end and added at front.
    "
    oldSize > (sz * 2) ifTrue:[
	startIndex := oldSize // 4.
	startIndex == 0 ifTrue:[
	    startIndex := 1
	].
	contentsArray
	    replaceFrom:startIndex
	    to:startIndex + sz - 1
	    with:contentsArray
	    startingAt:1.
	contentsArray from:1 to:(startIndex - 1) put:nil.
	firstIndex := startIndex.
	lastIndex := startIndex + sz - 1.
	^ self
    ].
    newSize := oldSize * 2.
    newSize == 0 ifTrue:[ newSize := 3].
    newContents := Array basicNew:newSize.
    newContents
	replaceFrom:(oldSize + 1)
	to:newSize
	with:contentsArray
	startingAt:1.
    contentsArray := newContents.
    firstIndex := firstIndex + oldSize.
    lastIndex := lastIndex + oldSize
!

makeRoomAtIndex:index
    "grow the contents for inserting at index
     Changes the logical size.
     i.e.
     #(1 2 3 4 5 6) asOrderedCollection makeRoomAtIndex:3 -> #(1 2 nil 3 4 5 6)
     #(1 2 3 4 5 6) asOrderedCollection makeRoomAtIndex:1 -> #(nil 1 2 3 4 5 6)
     #(1 2 3 4 5 6) asOrderedCollection makeRoomAtIndex:7 -> #(1 2 3 4 5 6 nil)"

    |newContents
     newSize "{ Class:SmallInteger }" 
     oldSize "{ Class:SmallInteger }" |

    oldSize := contentsArray size.
    ((firstIndex > 1) and:[firstIndex > (oldSize // 4)]) ifTrue:[
	"there is room (>25%) at the beginning"

	index == 1 ifFalse:[
	    contentsArray
		replaceFrom:(firstIndex - 1)
		to:(index - 1)
		with:contentsArray
		startingAt:firstIndex.
	    contentsArray at:index put:nil.
	].
	firstIndex := firstIndex - 1.
	^ self
    ].
    lastIndex < (oldSize * 3 // 4) ifTrue:[
	"there is room (>25%) at the end"

	index == (lastIndex + 1) ifFalse:[
	    contentsArray
		replaceFrom:(index + 1)
		to:(lastIndex + 1) 
		with:contentsArray
		startingAt:index.
	    contentsArray at:index put:nil
	].
	lastIndex := lastIndex + 1.
	^ self
    ].

    newSize := oldSize * 2.
    newContents := Array basicNew:newSize.
    index ~~ 1 ifTrue:[
	newContents 
	    replaceFrom:1 
	    to:index-1 
	    with:contentsArray
	    startingAt:1.
    ].
    index ~~ newSize ifTrue:[
	newContents
	    replaceFrom:index + 1
	    to:oldSize + 1 
	    with:contentsArray
	    startingAt:index.
    ].
    contentsArray := newContents.
    lastIndex := lastIndex + 1
!

initContents:size
    "setup the receiver-collection to hold size entries"

    contentsArray := Array basicNew:size.
    firstIndex := 1.
    lastIndex := 0 
! !

!OrderedCollection methodsFor:'testing'!

includes:anObject
    "return true if anObject is in the collection. Compare using ="

    |index "{ Class:SmallInteger }"|

    index := contentsArray indexOf:anObject startingAt:firstIndex.
    ((index < firstIndex) or:[index > lastIndex]) ifTrue:[^ false].
    ^ true
!

identityIndexOf:anObject
    "return the index of anObject or 0 if not found. Compare using =="

    |index "{ Class:SmallInteger }"|

    index := contentsArray identityIndexOf:anObject startingAt:firstIndex.
    ((index < firstIndex) or:[index > lastIndex]) ifTrue:[^ 0].
    ^ index - firstIndex + 1
!

identityIndexOf:anObject startingAt:startIndex
    "return the index of anObject, starting search at startIndex.
     Compare using ==; return 0 if not found in the collection"

    |index "{ Class:SmallInteger }"|

    index := contentsArray identityIndexOf:anObject startingAt:(startIndex + firstIndex - 1).
    ((index < firstIndex) or:[index > lastIndex]) ifTrue:[^ 0].
    ^ index - firstIndex + 1
!

indexOf:anObject
    "return the index of anObject or 0 if not found in the collection.
     Compare using ="

    |index "{ Class:SmallInteger }"|

    index := contentsArray indexOf:anObject startingAt:firstIndex.
    ((index < firstIndex) or:[index > lastIndex]) ifTrue:[^ 0].
    ^ index - firstIndex + 1
!

indexOf:anObject startingAt:startIndex
    "return the index of anObject, starting search at startIndex.
     Compare using =; return 0 if not found in the collection"

    |index "{ Class:SmallInteger }"|

    index := contentsArray indexOf:anObject startingAt:(startIndex + firstIndex - 1).
    ((index < firstIndex) or:[index > lastIndex]) ifTrue:[^ 0].
    ^ index - firstIndex + 1
! !

!OrderedCollection methodsFor:'converting'!

asOrderedCollection 
    "return the receiver as an ordered collection"

    "could be an instance of a subclass..."
    self class == OrderedCollection ifTrue:[
	^ self
    ].
    ^ super asOrderedCollection
! !

!OrderedCollection methodsFor:'enumerating'!

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

    contentsArray from:firstIndex to:lastIndex do:aBlock
!

reverseDo:aBlock
    "evaluate the argument, aBlock for every element in the collection
     procesing elements in reverse direction (i.e. starting with the last)"

    contentsArray from:firstIndex to:lastIndex reverseDo:aBlock
!

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

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

    stop := lastIndex.
    start := firstIndex.
    start to:stop do:[:index |
	aTwoArgBlock value:index value:(contentsArray at:index)
    ]

    "
     #(10 20 30 40) asOrderedCollection keysAndValuesDo:[:index :value |
	Transcript show:index; show:' '; showCr:value
     ]  
    "
!

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

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

    newCollection := self copyEmpty:(self size).
    stop := lastIndex.
    start := firstIndex.
    start to:stop do:[:index |
	newCollection add:(aBlock value:(contentsArray at:index)).
    ].
    ^ newCollection

    "
     #(1 2 3 4) asOrderedCollection collect:[:i | i * i] 
     #(1 2 3 4) asOrderedCollection collect:[:i | i even] 
    "
! !

!OrderedCollection methodsFor:'inspecting'!

inspectorClass
    "redefined to launch an OrderedCollectionInspector
     (instead of the default InspectorView)."

    ^ OrderedCollectionInspectorView

    "
     (OrderedCollection withAll:#(3 2 1)) inspect
     (OrderedCollection withAll:#(3 2 1)) removeFirst; yourself; inspect
     #(0 8 15 3 99 2) asSortedCollection inspect
    "
! !