OrderedSet.st
author Claus Gittinger <cg@exept.de>
Fri, 26 Oct 2007 16:07:25 +0200
changeset 1905 ec30ff95406a
parent 1603 a2a4ce010ef3
child 1915 c7fbd33fc982
permissions -rw-r--r--
default printFormat

"
 COPYRIGHT (c) 2001 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

"{ Package: 'stx:libbasic2' }"

Set subclass:#OrderedSet
	instanceVariableNames:'order'
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Sequenceable'
!

!OrderedSet class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2001 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    I am a subclass of Set whose elements are ordered in a
    similar fashion to OrderedCollection.
    That is, I have both Set behavior (only keeping a single instance of
    an element) but I also remember the original order, in which elements
    were added.

    I have one additional instance variable:

    order <OrderedCollection>       Ordered collection of values reflecting the order 
                                    in the set. 

    [author:]
        Claus Gittinger

    [see also:]
        OrderedCollection 
        Dictionary OrderedDictionary
        Set Bag
"
!

examples
"
                                                                    [exBegin]
        |s|

        s := OrderedSet new.
        s add:'one'.
        s add:'two'.
        s add:'one'.
        s add:'two'.
        s add:'three'.
        s size.         
        s do:[:each | Transcript showCR:each].         
                                                                    [exEnd]


                                                                    [exBegin]
        |s|

        s := OrderedSet new.
        s add:'one'.
        s add:'two'.
        s add:'one'.
        s add:'two'.
        s add:'three'.
        s remove:'one'.
        s size.         
        s do:[:each | Transcript showCR:each].         
                                                                    [exEnd]

                                                                    [exBegin]
        |s|

        s := OrderedSet new.
        s add:'one'.
        s addFirst:'two'.
        s addFirst:'three'.
        s add:'one'.
        s add:'two'.
        s add:'three'.
        s size.         
        s do:[:each | Transcript showCR:each].         
                                                                    [exEnd]
"
! !

!OrderedSet class methodsFor:'instance creation'!

new
        ^super new initializeOrder

    "Created: / 16.11.2001 / 10:10:37 / cg"
!

new: anInteger
        ^(super new: anInteger) initializeOrder

    "Created: / 16.11.2001 / 10:10:07 / cg"
! !

!OrderedSet methodsFor:'accessing'!

at:index
    "return the indexed instance variable with index, anInteger.
     Report an error, if the index is wrong."

    ^ order at:index

    "Modified: / 16.11.2001 / 10:27:40 / cg"
!

at:index ifAbsent:exceptionalValue
    "return the indexed instance variable with index, anInteger.
     If not present, return the value from exceptionalValue."

    ^ order at:index ifAbsent:exceptionalValue

    "Modified: / 16.11.2001 / 10:27:40 / cg"
! !

!OrderedSet methodsFor:'adding & removing'!

add:anObject 
    "Add anObject to the receiver (if not already included). 
     Also, remember in the order (i.e. add to the end)"

    self addLast:anObject.
    ^ anObject
!

addFirst:anObject 
    "Add anObject to the receiver (if not already included). 
     Also, remember in the order (i.e. add to the beginning)"

    anObject isNil ifTrue:[
        ^ self invalidElementError.
    ].
    (self includes:anObject) ifFalse:[
        super add:anObject.
        order addFirst:anObject.
    ].
    ^ anObject
!

addLast:anObject 
    "Add anObject to the receiver (if not already included). 
     Also, remember in the order (i.e. add to the end)"

    anObject isNil ifTrue:[
        ^ self invalidElementError.
    ].
    (self includes:anObject) ifFalse:[
        super add:anObject.
        order addLast:anObject.
    ].
    ^ anObject
!

remove:oldObject ifAbsent:exceptionValueProvider
    "remove oldObject from the collection and return it.
     If it was not in the collection return the value of exceptionValueProvider.

     WARNING: do not remove elements while iterating over the receiver."

    |removedObject|

    oldObject isNil ifTrue:[^ exceptionValueProvider value].
    (self includes:oldObject) ifFalse:[^ exceptionValueProvider value].        

    removedObject := super remove:oldObject 
                           ifAbsent:[ ^ exceptionValueProvider value].      
    order removeIdentical:removedObject.

    ^ removedObject

    "Modified: / 16.11.2001 / 10:21:07 / cg"
!

removeAll
    "remove all elements from the receiver. Returns the receiver."

    super removeAll.
    order := OrderedCollection new.

    "Created: / 16.11.2001 / 10:21:40 / cg"
!

removeFirst
    "remove the first object from the collection and return it.
     If it was not in the collection, raise an error.

     WARNING: do not remove elements while iterating over the receiver."

    ^ self removeFirstIfAbsent:[self emptyCollectionError].
!

removeFirstIfAbsent:exceptionalValue
    "remove the first object from the collection and return it.
     If it was not in the collection, return the value from exceptionalValue.

     WARNING: do not remove elements while iterating over the receiver."

    |element|

    order isEmpty ifTrue:[^ exceptionalValue value].
    element := order first.
    ^ self remove:element.
!

removeLast
    "remove the last object from the collection and return it.
     If it was not in the collection, raise an error.

     WARNING: do not remove elements while iterating over the receiver."

    ^ self removeLastIfAbsent:[self emptyCollectionError].
!

removeLastIfAbsent:exceptionalValue
    "remove the last object from the collection and return it.
     If it was not in the collection, return the value from exceptionalValue.

     WARNING: do not remove elements while iterating over the receiver."

    |lastElement|

    order isEmpty ifTrue:[^ exceptionalValue value].
    lastElement := order last.
    ^ self remove:lastElement.
!

saveRemove:oldObject 
    "remove the element, oldObject from the collection.
     Return the element 
     (could be non-identical to oldObject, since I hash on equality, not on identity).
     If it was not in the collection return nil.

     In contrast to #remove:, this does not resize the underlying collection
     and therefore does NOT rehash & change the elements order.
     Therefor this can be used while enumerating the receiver,
     which is not possible if #remove: is used.

     WARNING: since no resizing is done, the physical amount of memory used
              by the container remains the same, although the logical size shrinks.
              You may want to manually resize the receiver using #emptyCheck.
              (after the loop)"

    |removedObject|

    removedObject := super saveRemove:oldObject.
    removedObject notNil ifTrue:[
        order removeIdentical:removedObject.
    ].
    ^ removedObject

    "Created: / 16.11.2001 / 10:23:48 / cg"
    "Modified: / 16.11.2001 / 10:24:03 / cg"
! !

!OrderedSet methodsFor:'copying'!

postCopy
    "have to copy the keyArray too"

    super postCopy.
    order := order copy.

    "Created: / 16.11.2001 / 10:28:50 / cg"
! !

!OrderedSet methodsFor:'enumerating'!

do:aBlock 
    "Evaluate aBlock for each of the sets's values."

    order do:[:val | aBlock value:val ]

    "Modified: / 16.11.2001 / 10:04:00 / cg"
! !

!OrderedSet methodsFor:'enumerting & searching'!

indexOf:anObject

    ^ order indexOf:anObject.
! !

!OrderedSet methodsFor:'initialization'!

initializeOrder
    order := OrderedCollection new

    "Created: / 16.11.2001 / 10:06:05 / cg"
! !

!OrderedSet class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/Attic/OrderedSet.st,v 1.12 2006-03-06 08:54:58 cg Exp $'
! !