OrderedCollection.st
author claus
Tue, 17 May 1994 12:09:46 +0200
changeset 77 6c38ca59927f
parent 68 59faa75185ba
child 88 81dacba7a63a
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.
"

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/OrderedCollection.st,v 1.12 1994-05-17 10:08:27 claus Exp $
written spring 89 by claus
'!

!OrderedCollection class methodsFor:'documentation'!

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

size
    "return the number of elements in the collection"

    ^ lastIndex - firstIndex + 1
!

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

    ^ false
! !

!OrderedCollection methodsFor:'copying'!

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

    |newCollection|

    newCollection := self species new:(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"
!

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.
    newCollection grow: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"
!

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 species new:sz.
    newCollection grow:sz.
    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 subscriptBoundsError.
        ^ nil
    ].
    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"
    "(SortedCollection withAll:#(5 4 3 2 1)) removeFirst; yourself"
    "(SortedCollection new) removeFirst"
!

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

    |anObject |

    firstIndex > lastIndex ifTrue:[
        "error if collection is empty"
        self subscriptBoundsError.
        ^ nil
    ].
    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"
    "(SortedCollection withAll:#(5 4 3 2 1)) removeLast; yourself"
!

removeFromIndex:startIndex to:stopIndex
    "remove the elements stored under startIndex up to and including
     the elements under stopIndex.
     return the receiver."

    |nDeleted|

    nDeleted := stopIndex - startIndex + 1.
    contentsArray replaceFrom:(firstIndex + startIndex)
                           to:(lastIndex - nDeleted)
                         with:contentsArray 
                   startingAt:(firstIndex + stopIndex + 1).
    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 to: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
!

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

    (lastIndex == contentsArray size) ifTrue:[
        self makeRoomAtLast
    ].
    lastIndex := lastIndex + 1.
    contentsArray at:lastIndex put:anObject.
    ^ 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 := #(4 3 2 1) asOrderedCollection.
     c addFirst:'here'
    "
!

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

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 errorNotFound

    "
     |c|
     c := #(4 3 2 1) asOrderedCollection.
     c add:'here' after:3.
     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 errorNotFound

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

    |newContents oldLast|

    newSize <= (lastIndex - firstIndex + 1) ifTrue:[
        oldLast := lastIndex.
        lastIndex := firstIndex + newSize - 1.
        contentsArray from:lastIndex + 1 to:oldLast put:nil. 
    ] ifFalse:[
        newContents := Array new:newSize.
        newContents replaceFrom:1 to:(lastIndex - firstIndex + 1) with:contentsArray.
        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
    ] 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
    ] ifFalse:[
        ^ contentsArray at:idx put:anObject
    ]
!

first
    "return the first element"

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

    "(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 subscriptBoundsError

    "(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:[
        contentsArray
            replaceFrom:(start + firstIndex - 1)
            to:end
            with:aCollection
            startingAt:repStart.
        ^ self
    ].
    ^ super replaceFrom:start to:stop with:aCollection startingAt:repStart
! !

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

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

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

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

    oldSize := contentsArray size.
    sz := self size.

    "if there is lots of room at the beginning (> 50%), shift instead of growing"
    oldSize > (sz * 2) ifTrue:[
        startIndex := firstIndex // 4.
        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 := 1].
    newContents := Array new:newSize.
    newContents replaceFrom:1 to:oldSize with:contentsArray.
    contentsArray := newContents
!

makeRoomAtFront
    "grow/shift the contents for more room at the beginning"

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

    oldSize := contentsArray size.
    sz := self size.

    "if there is lots of room at the end (> 50%), shift instead of growing"
    oldSize > (sz * 2) ifTrue:[
        startIndex := oldSize // 4.
        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 := 1].
    newContents := Array new: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
     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 new:newSize.
    index == 1 ifFalse:[
        newContents replaceFrom:1 to:index-1 
                           with:contentsArray startingAt:1.
    ].
    index == newSize ifFalse:[
        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 new: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:'enumeration'!

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

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 species new).
    stop := lastIndex.
    start := firstIndex.
    start to:stop do:[:index |
        newCollection add:(aBlock value:(contentsArray at:index)).
    ].
    ^ newCollection
! !

!OrderedCollection methodsFor:'misc'!

inspect
    "redefined to launch a SequenceableCollectionInspector on the receiver
     (instead of the default InspectorView)."

    OrderedCollectionInspectorView isNil ifTrue:[
        super inspect
    ] ifFalse:[
        OrderedCollectionInspectorView openOn:self
    ]

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