Collection.st
author claus
Sat, 11 Dec 1993 01:46:55 +0100
changeset 12 8e03bd717355
parent 10 4f1f9a91e406
child 25 e34a6267c79b
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.
"

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

Collection comment:'

COPYRIGHT (c) 1989 by Claus Gittinger
              All Rights Reserved

Abstract superclass for all collections

$Header: /cvs/stx/stx/libbasic/Collection.st,v 1.6 1993-12-11 00:45:11 claus Exp $
'!

!Collection class methodsFor:'initialization'!

initialize
    "setup the signal"

    InvalidKeySignal := (Signal new) mayProceed:true.
    InvalidKeySignal notifierString:'invalid key'.
! !

!Collection class methodsFor:'signal access'!

invalidKeySignal
    "return the signal used to report bad key usage"

    ^ InvalidKeySignal
! !

!Collection class methodsFor:'instance creation'!

with:anObject
    "return a new Collection with one element:anObject"

    |newCollection|

    newCollection := self new.
    newCollection add:anObject.
    ^ newCollection
!

with:firstObject with:secondObject
    "return a new Collection with two elements:firstObject and secondObject"

    |newCollection|

    newCollection := self new.
    newCollection add:firstObject.
    newCollection add:secondObject.
    ^ newCollection
!

with:firstObject with:secondObject with:thirdObject
    "return a new Collection with three elements"

    |newCollection|

    newCollection := self new.
    newCollection add:firstObject.
    newCollection add:secondObject.
    newCollection add:thirdObject.
    ^ newCollection
!

with:firstObject with:secondObject with:thirdObject with:fourthObject
    "return a new Collection with four elements"

    |newCollection|

    newCollection := self new.
    newCollection add:firstObject.
    newCollection add:secondObject.
    newCollection add:thirdObject.
    newCollection add:fourthObject.
    ^ newCollection
!

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

    |newCollection|

    newCollection := self new:size.
    size timesRepeat:[newCollection add:element]
!

withAll:aCollection
    "return a new Collection with all elements taken from the argument,
     aCollection"

    |newCollection|

    newCollection := self new.
    newCollection addAll:aCollection.
    ^newCollection
! !

!Collection methodsFor:'error handling'!

errorNotKeyed
    "report an error that keyed access methods are not allowed"

    self error:(self class name, 's do not respond to keyed accessing messages')
! 

errorInvalidKey
    "report an error that the given key was invalid"

    InvalidKeySignal raise
! !

!Collection methodsFor:'accessing'!

anElement
    "return any element from the collection"

    self do: [:each | ^ each].
    ^ nil
! !

!Collection methodsFor:'adding & removing'!

add:anObject
    "add the argument, anObject to the receiver"

    ^ self subclassResponsibility
!

addLast:anObject
    "add the argument, anObject to the receiver"

    ^ self add:anObject
!

addFirst:anObject
    "add the argument, anObject to the receiver"

    ^ self subclassResponsibility
!

addAll:aCollection
    "add all elements of the argument, aCollection to the receiver"

    aCollection do:[:element |
        self add:element
    ].
    ^ aCollection
!

addAllLast:aCollection
    "add all elements of the argument, aCollection to the receiver"

    ^ self addAll:aCollection
!

addAllFirst:aCollection
    "insert all elements of the argument, aCollection at the beginning
     of the receiver"

    aCollection reverseDo:[:element | 
        self addFirst: element 
    ].
    ^ aCollection

    "
     |c|
     c := #(4 3 2 1) asOrderedCollection.
     c addAllFirst:#(9 8 7 6 5)
    "
!

remove:anObject ifAbsent:exceptionBlock
    "remove the argument, anObject from the receiver - if it was not
     in the collection returns the the value of the exceptionBlock"

    ^ self subclassResponsibility
!

remove:anObject
    "remove the argument, anObject from the receiver"

    self remove:anObject ifAbsent:[self errorNotFound]
!

removeAll:aCollection
    "remove all elements of the argument, aCollection from the receiver"

    aCollection do:[:element | self remove:element].
    ^ aCollection
! !

!Collection methodsFor:'growing'!

growSize
    "return a suitable size increment for growing"

    ^ self size max:2
!

grow
    "make the receiver larger"

    self grow:(self size + self growSize)
!

grow:howBig
    "change the receivers size"

    ^ self subclassResponsibility
! !

!Collection methodsFor:'testing'!

isEmpty
    "return true, if the receiver is empty"

    ^ self size == 0
!

includes:anElement
    "return true, if the argument, anObject is in the list"

    self do:[:element |
        (anElement = element) ifTrue:[^ true].
    ].
    ^ false
!

includesAll:aCollection
    "return true, if the the receiver includes all elements of
     the argument, aCollection; false if any is missing"

    aCollection do:[:element |
        (self includes:element) ifFalse:[^ false].
    ].
    ^ true
!

includesAny:aCollection
    "return true, if the the receiver includes any elements of
     the argument, aCollection; false if it includes none"

    aCollection do:[:element |
        (self includes:element) ifTrue:[^ true].
    ].
    ^ false
!

occurrencesOf:anElement
    "return the number of occurrences of the argument, anElement in
     the receiver"

    |count "<SmallInteger>" |

    count := 0.
    self do:[:element |
        (anElement = element) ifTrue:[
            count := count + 1
        ].
    ].
    ^ count
!

size
    "return the number of elements in the receiver"

    |count "<SmallInteger>" |

    count := 0.
    self do:[:element |
        count := count + 1
    ].
    ^ count
! !

!Collection methodsFor:'enumerating'!

do:aBlock
    "evaluate the argument, aBlock for each element"

    ^ self subclassResponsibility
!

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

    ^ self errorNotKeyed
!

collect:aBlock
    "for each element in the receiver, evaluate the argument, aBlock
     and return a new collection with the results"

    |newCollection|

    newCollection := self species new.
    self do:[:each | newCollection add:(aBlock value:each)].
    ^ newCollection
!

detect:aBlock
    "evaluate the argument, aBlock for each element in the receiver until
     the block returns true; in this case return the element which caused
     the true evaluation.
     If none of the evaluations return true, report an error"

    ^ self detect:aBlock ifNone:[self errorNotFound]
!

detect:aBlock ifNone:exceptionBlock
    "evaluate the argument, aBlock for each element in the receiver until
     the block returns true; in this case return the element which caused
     the true evaluation.
     If none of the evaluations returns true, return the result of the
     evaluation of the exceptionBlock"

    self do:[:each | 
        (aBlock value:each) ifTrue:[^ each].
    ].
    ^ exceptionBlock value
!

inject:thisValue into:binaryBlock
    |nextValue|

    nextValue := thisValue.
    self do: [:each | nextValue := binaryBlock value:nextValue value:each].
    ^ nextValue
!

reject:aBlock
    "return a new collection with all elements from the receiver, for which
     the argument aBlock evaluates to false"

    ^ self select:[:element | (aBlock value:element) == false]
!

select:aBlock
    "return a new collection with all elements from the receiver, for which
     the argument aBlock evaluates to true"

    |newCollection|

    newCollection := self species new.
    self do:[:each |
        (aBlock value:each) ifTrue:[newCollection add:each].
    ].
    ^ newCollection
!

addAllTo:aCollection
    "add all elements of the receiver, to aCollection.
     Return aCollection."

    self do:[:each | aCollection add:each].
    ^ aCollection
! !

!Collection methodsFor:'converting'!

asArray
    "return a new Array with the collections elements"

    |anArray 
     index "<SmallInteger>" |

    anArray := Array new:(self size).
    index := 1.
    self do:[:each |
        anArray at:index put:each.
        index := index + 1
    ].
    ^ anArray
!

asByteArray
    "return a new ByteArray with the collections elements"

    |aByteArray 
     index "<SmallInteger>" |

    aByteArray := ByteArray new:(self size).
    index := 1.
    self do:[:each |
        aByteArray at:index put:each asInteger.
        index := index + 1
    ].
    ^ aByteArray
!

asString
    "return a String with the collections elements 
     (which must convertable to characters)"

    |aString 
     index "<SmallInteger>" |

    aString := String new:(self size).
    index := 1.
    self do:[:each |
        aString at:index put:each asCharacter.
        index := index + 1
    ].
    ^ aString
!

asText
    "return a new Text-object with the elements printstings"

    |aText
     index "<SmallInteger>" |

    aText := Text new:(self size).
    index := 1.
    self do:[:each |
        aText at:index put:(each printString).
        index := index + 1
    ].
    ^ aText
!

asBag
    "return a new Bag with the receiver collections elements"

    ^ self addAllTo:(Bag new)
!

asOrderedCollection
    "return a new OrderedCollection with the receiver collections elements"

    ^ self addAllTo:(OrderedCollection new:self size)
!

asSet
    "return a new Set with the receiver collections elements"

    ^ self addAllTo:(Set new:self size)
!

asIdentitySet
    "return a new IdentitySet with the receiver collections elements"

    ^ self addAllTo:(IdentitySet new:self size)
!

asSortedCollection
    "return a new SortedCollection with the receiver collections elements"

    |aSortedCollection|

    aSortedCollection := SortedCollection new:self size.
    aSortedCollection addAll:self.
    ^ aSortedCollection
!

asSortedCollection:sortBlock
    "return a new SortedCollection with the receiver collections elements,
     using sortBlock for comparing"

    |aSortedCollection|

    aSortedCollection := SortedCollection sortBlock:sortBlock.
    aSortedCollection addAll:self.
    ^ aSortedCollection
!

writeStream
    "return a stream for writing onto the receiver"

    ^ WriteStream on:self
!

readStream
    "return a stream for reading from the receiver"

    ^ ReadStream on:self
! !

!Collection methodsFor:'printing & storing'!

maxPrint
    ^ 5000
!

printOrDisplayStringUsing:aSelector
    "common code for printString and displayString; they only differ in
     the print-message sent to the elements"

    |thisString buffer count string noneYet total|

    string := (self class name) , '('.
    noneYet := true.
    buffer := ''.
    count := 0.
    total := 0.
    self do: [:element |
        thisString := element perform:aSelector.
        noneYet ifTrue:[
            noneYet := false.
            buffer := buffer , thisString
        ] ifFalse:[
            buffer := buffer , (' ' , thisString)
        ].
        count := count + 1.
        (count == 20) ifTrue:[
            string := string , buffer.
            buffer := ''.
            count := 0
        ].
        total := total + 1.
        (total > 5000) ifTrue:[
            string := string , buffer , '... )'.
            ^string
        ]
    ].
    string := string , buffer , ')'.
    ^string
!

printString
    "return a printed representation of the receiver"

    ^ self printOrDisplayStringUsing:#printString 
!

displayString
    "return a printed representation of the receiver for display in inspectors etc."

    ^ self printOrDisplayStringUsing:#displayString 
!

printOn:aStream
    |tooMany firstOne noMore|

    tooMany := aStream position + self maxPrint.
    aStream nextPutAll:self class name.
    aStream nextPut:$(.
    firstOne := true.
    noMore := false.
    self do:[:element |
        noMore ifFalse:[
            firstOne ifFalse:[
                aStream nextPut:(Character space)
            ] ifTrue:[
                firstOne := false
            ].
            (aStream position > tooMany) ifTrue:[
                aStream nextPutAll:'...etc...)'.
                noMore := true
            ] ifFalse:[
                element printOn:aStream
            ]
        ].
    ].
    aStream nextPut:$)
!

storeOn:aStream
    "output a printed representation (which can be re-read)
     onto the argument aStream"

    |isEmpty|

    aStream nextPutAll:'(('.
    aStream nextPutAll:(self class name).
    aStream nextPutAll:' new)'.
    isEmpty := true.
    self do:[:element |
        aStream nextPutAll:' add:('.
        element storeOn:aStream.
        aStream nextPutAll:');'.
        isEmpty := false
    ].
    isEmpty ifFalse:[aStream nextPutAll:' yourself'].
    aStream nextPut:$)
! !