ArrayedCollection.st
author Claus Gittinger <cg@exept.de>
Wed, 21 Feb 1996 15:10:57 +0100
changeset 990 284134c88e19
parent 916 a050d17c7e1f
child 1111 d8e423b7d5a1
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:#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)

    Notice: currently, ST/X supports growing fix-size collections
	    (such as Arrays, ByteArrays and Strings). However, this
	    can only be done in a very slow way (using #become).
	    Therefore, you SHOULD rewrite any application that does this
	    to make use of OrderedCollection 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.

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

!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. newCollection at:2 put:second.
    ^newCollection

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

with:first with:second with:third
    "return a new SequenceableCollection with three elements"

    |newCollection|

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

    "
     OrderedCollection with:1 with:2 with:3
     SortedCollection with:99 with:3 with:301
    "
!

with:first with:second with:third with:forth
    "return a new SequenceableCollection with four elements"

    |newCollection|

    newCollection := self new:4.
    newCollection at:1 put:first. newCollection at:2 put:second.
    newCollection at:3 put:third. newCollection at:4 put:forth.
    ^newCollection
!

with:one with:two with:three with:four with:five
    "return a new SequenceableCollection with five elements"

    |newCollection|

    newCollection := self new:5.
    newCollection at:1 put:one. newCollection at:2 put:two.
    newCollection at:3 put:three. newCollection at:4 put:four. newCollection at:5 put:five.
    ^newCollection
!

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"
	newCollection replaceFrom:1 to:newSize with:aCollection startingAt:1
    ] ifFalse:[
	"must enumerate the elements"
	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) 
    "
! !

!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
    "report an error that size of the collection cannot be changed.
     This is obsolete now."

    ^ self error:'cannot change size'
! !

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

!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 ..)
	    "/
	    'ARRCOLL: Warning: slow grow operation (' infoPrint.
	    self class name infoPrint. ') via ' infoPrint.
            sender := thisContext sender.
	    sender methodPrintString infoPrint. 
	    ' from ' infoPrint. sender sender methodPrintString infoPrintNL.
	].

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

removeAll
    'ARRCOLL: Warning: slow remove operation (' infoPrint.
    self class name infoPrint. ')' infoPrintNL.

    self become:(self copyEmpty)

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

!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.30 1996-02-21 14:10:57 cg Exp $'
! !