ArrayedCollection.st
author Claus Gittinger <cg@exept.de>
Wed, 22 Jan 1997 19:37:56 +0100
changeset 2225 53313e47007a
parent 2146 27069b34fb5a
child 2290 80404098824a
permissions -rw-r--r--
added with:with: type of instance creation messages for upTo 8 elements.

"
 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:#ArrayedCollection
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Abstract'
!

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

documentation
"
    ArrayedCollection is an abstract superclass for all collections where 
    the elements can be accessed via an integer index,
    AND the collection is a fixed size collection. 
    Those fixed size collections cannot easily grow, since they store the 
    elements directly within the object and a grow operation can only be done 
    by #becoming another object.
    (other collections keep a reference to the physical container, which
     can be easily replaced)

    [Warning:] 
        currently, ST/X supports growing fix-size collections
        (such as Arrays, ByteArrays and Strings). However, this
        is done in a very slow way (using #become).
        Become is a very slow operation in a direct-pointer smalltalk
        system.
                                                                                \
        Therefore, you SHOULD rewrite any application that does this,
        to make use of OrderedCollections or any other collection which
        can grow faster.
        To remind you of that, a warning message is sent to the
        standard error whenever such an operation is performed (see #grow).
                                                                                \
        Also note, that some other smalltalk systems do NOT allow
        fix size collection to change their size, and that future
        ST/X versions may be changed to trigger an error (instead of a
        warning) in those situations.

    [author:]
        Claus Gittinger

    [see also:]
        OrderedCollection Array
"
! !

!ArrayedCollection class methodsFor:'instance creation'!

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

    |newCollection|

    newCollection := self new:1.
    newCollection at:1 put:element.
    ^newCollection

    "
     OrderedCollection with:1
     SortedCollection with:99 
    "
!

with:first with:second
    "return a new SequenceableCollection with two elements"

    |newCollection|

    newCollection := self new:2.
    newCollection at:1 put:first; at:2 put:second.
    ^newCollection

    "
     OrderedCollection with:1 with:2
     SortedCollection with:99 with:3
     Array with:1 with:2
    "

    "Modified: 22.1.1997 / 19:35:43 / cg"
!

with:a1 with:a2 with:a3
    "return a new SequenceableCollection with three elements"

    |newCollection|

    newCollection := self new:3.
    newCollection at:1 put:a1; at:2 put:a2; at:3 put:a3.
    ^ newCollection

    "
     OrderedCollection with:1 with:2 with:3
     Array with:1 with:2 with:3
    "

    "Modified: 22.1.1997 / 19:35:47 / cg"
!

with:a1 with:a2 with:a3 with:a4
    "return a new SequenceableCollection with four elements"

    |newCollection|

    newCollection := self new:4.
    newCollection at:1 put:a1; at:2 put:a2; at:3 put:a3; at:4 put:a4.
    ^ newCollection

    "
     OrderedCollection with:1 with:2 with:3 with:4
     Array with:1 with:2 with:3 with:4
    "

    "Modified: 22.1.1997 / 19:35:52 / cg"
!

with:a1 with:a2 with:a3 with:a4 with:a5
    "return a new SequenceableCollection with five elements"

    |newCollection|

    newCollection := self new:5.
    newCollection at:1 put:a1; at:2 put:a2; at:3 put:a3; at:4 put:a4;
                  at:5 put:a5.
    ^ newCollection

    "
     OrderedCollection with:1 with:2 with:3 with:4 with:5
     Array with:1 with:2 with:3 with:4 with:5
    "

    "Modified: 22.1.1997 / 19:35:57 / cg"
!

with:a1 with:a2 with:a3 with:a4 with:a5 with:a6
    "return a new SequenceableCollection with six elements"

    |newCollection|

    newCollection := self new:6.
    newCollection at:1 put:a1; at:2 put:a2; at:3 put:a3; at:4 put:a4;
                  at:5 put:a5; at:6 put:a6.
    ^ newCollection

    "
     OrderedCollection with:1 with:2 with:3 with:4 with:5 with:6
     Array with:1 with:2 with:3 with:4 with:5 with:6
    "

    "Modified: 22.1.1997 / 19:36:03 / cg"
!

with:a1 with:a2 with:a3 with:a4 with:a5 with:a6 with:a7
    "return a new SequenceableCollection with seven elements"

    |newCollection|

    newCollection := self new:7.
    newCollection at:1 put:a1; at:2 put:a2; at:3 put:a3; at:4 put:a4;
                  at:5 put:a5; at:6 put:a6; at:7 put:a7.
    ^ newCollection

    "
     OrderedCollection with:1 with:2 with:3 with:4 with:5 with:6 with:7
     Array with:1 with:2 with:3 with:4 with:5 with:6 with:7
    "

    "Modified: 22.1.1997 / 19:36:20 / cg"
!

with:a1 with:a2 with:a3 with:a4 with:a5 with:a6 with:a7 with:a8
    "return a new SequenceableCollection with eight elements"

    |newCollection|

    newCollection := self new:8.
    newCollection at:1 put:a1; at:2 put:a2; at:3 put:a3; at:4 put:a4;
                  at:5 put:a5; at:6 put:a6; at:7 put:a7; at:8 put:a8.
    ^ newCollection

    "
     OrderedCollection with:1 with:2 with:3 with:4 with:5 with:6 with:7 with:8
     Array with:1 with:2 with:3 with:4 with:5 with:6 with:7 with:8
    "

    "Modified: 22.1.1997 / 19:35:21 / cg"
!

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

    |newCollection newSize
     index "{ Class: SmallInteger }" |

    newSize := aCollection size.
    newCollection := self new:newSize.
    aCollection isSequenceable ifTrue:[
	"/
	"/ aCollection has indexed elements
	"/ a block-replace may be faster
	"/
	newCollection replaceFrom:1 to:newSize with:aCollection startingAt:1
    ] ifFalse:[
	"/
	"/ must enumerate the elements individually
	"/
	index := 1.
	aCollection do:[:element |
	    newCollection at:index put:element.
	    index := index + 1
	]
    ].
    ^ newCollection

    "
     OrderedCollection withAll:#(1 2 3 4 5)
     SortedCollection withAll:#(99 17 53 1 101) 
    "

    "Modified: 13.4.1996 / 12:14:38 / cg"
! !

!ArrayedCollection class methodsFor:'queries'!

growIsCheap
    "return true, if this collection can easily grow
     (i.e. without a need for become:).
     Since this is the superclass of all indexed fix-size collections,
     return false here."

    ^ false
! !

!ArrayedCollection methodsFor:'copying'!

copyEmptyAndGrow:size
    "return a new instance of the receivers species with size
     nilled elements and any named instance variables copied."

    "special case for Array, which has no named instance vars"

    |cls|

    (cls := self class) instSize == 0 ifTrue:[
	^ cls new:size
    ].
    ^ super copyEmptyAndGrow:size
! !

!ArrayedCollection methodsFor:'error handling'!

fixedSizeError
    "{ Pragma: +optSpace }"

    "report an error that size of the collection cannot be changed.
     This is not used right now (instead, a warning is sent to stderr
     in the #grow method); however, future versions of ST/X may no longer
     allow fixed size collection to grow.
     Read the documentation on why things are that way ..."

    ^ self error:'cannot change size'

    "Modified: 18.7.1996 / 21:39:09 / cg"
! !

!ArrayedCollection methodsFor:'printing & storing'!

storeOn:aStream
    "output a printed representation (which can be re-read with readFrom:)
     onto the argument aStream. Redefined to output index access."

    |index "{ Class: SmallInteger }"|

    thisContext isRecursive ifTrue:[
	Transcript showCR:'Error: storeOn: of self referencing collection.'.
	aStream nextPutAll:'#recursive'.
	^ self
    ].

    aStream nextPutAll:'(('; nextPutAll:self class name; nextPutAll:' new:'.
    self size printOn:aStream.
    aStream nextPutAll:')'.
    index := 1.
    self do:[:element |
	aStream nextPutAll:' at:'. index printOn:aStream. aStream nextPutAll:' put:('.
	element storeOn:aStream.
	aStream nextPutAll:');'.
	index := index + 1
    ].
    index > 1 ifTrue:[aStream nextPutAll:' yourself'].
    aStream nextPut:$)

    "
     (Array with:(1@2) with:(1->2)) storeString    
    "

    "Modified: 18.5.1996 / 15:37:30 / cg"
! !

!ArrayedCollection methodsFor:'resizing'!

grow:newSize
    "grow the receiver i.e. cut off everything after newSize.
     Warning: this may be a slow operation due to the use of become 
     - you should write your collection classes to avoid the use of become. 
     You have been warned."

    |newArray oldSize sender|

    oldSize := self size.
    (newSize ~~ oldSize) ifTrue:[
        InfoPrinting ifTrue:[
            "/
            "/ output a warning - you should rewrite your application
            "/ to use some collection which implements grow: more efficient
            "/ (i.e. use OrderedCollection instead of Array ..)
            "/
            'ArrayedCollection [info]: slow grow operation (' infoPrint.
            self class name infoPrint. ') via ' infoPrint.
            sender := thisContext sender.
            sender methodPrintString infoPrint. 
            ' from ' infoPrint. sender sender methodPrintString infoPrintCR.
        ].

        newArray := self species new:newSize.
        newArray replaceFrom:1 to:(newSize min:oldSize) with:self.
        self become:newArray.
    ]

    "
     #(1 2 3 4 5 6) add:7
     #(1 2 3 4 5 6) remove:5 
     #(1 2 3 4 5 6) copy grow:3  
     #(1 2 3 4 5 6) copy grow:10  
     'hello world' copy grow:5   
     'hello' copy grow:20   
    "

    "Modified: 10.1.1997 / 15:14:43 / cg"
!

removeAll
    "{ Pragma: +optSpace }"

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

     For ArrayedCollections (which are actually fixed-size collections),
     this is a slow operation, since a #become: is required to update
     all owners. Better use a collection which is prepared for growing
     (i.e. an OrderedCollection).
     We output a warning message here, to remind you about that."

    'ArrayedCollection [info]: slow removeAll operation (' infoPrint.
    self class name infoPrint. ')' infoPrintCR.

    self become:(self copyEmpty)

    "
     #(1 2 3 4 5) copy removeAll    
     #(1 2 3 4 5) removeAll    
    "

    "Modified: 10.1.1997 / 15:14:55 / cg"
! !

!ArrayedCollection methodsFor:'testing'!

includesKey:anIndex
    "return true, if anIndex is a valid key.
     NOTICE: in ST-80, this message is only defined for Dictionaries,
	     however, having a common protocol with indexed collections
	     often simplifies things."

    ^ (anIndex >= 1) and:[anIndex <= self size]

    "
     #(1 2 3) includesKey:4 
     #(1 2 3) includesKey:3  
    "
!

size
    "redefined to re-enable size->basicSize forwarding
     (it is cought in SequencableCollection)"

    ^ self basicSize
! !

!ArrayedCollection class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/ArrayedCollection.st,v 1.42 1997-01-22 18:36:56 cg Exp $'
! !