|
|
6.32 Collection
- Defined in namespace Smalltalk
- Category: Collections
- I am an abstract class. My instances are collections of objects. My
subclasses may place some restrictions or add some definitions to how
the objects are stored or organized; I say nothing about this. I merely
provide some object creation and access routines for general collections
of objects.
6.32.1 Collection class: instance creation
- with: anObject
- Answer a collection whose only element is anObject
- with: firstObject with: secondObject
- Answer a collection whose only elements are the parameters in the order they were passed
- with: firstObject with: secondObject with: thirdObject
- Answer a collection whose only elements are the parameters in the order they were passed
- with: firstObject with: secondObject with: thirdObject with: fourthObject
- Answer a collection whose only elements are the parameters in the order they were passed
- with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject
- Answer a collection whose only elements are the parameters in the order they were passed
- withAll: aCollection
- Answer a collection whose elements are all those in aCollection
6.32.2 Collection: Adding to a collection
- add: newObject
- Add newObject to the receiver, answer it
- addAll: aCollection
- Adds all the elements of 'aCollection' to the receiver, answer aCollection
6.32.3 Collection: converting
- asArray
- Answer an Array containing all the elements in the receiver
- asBag
- Answer a Bag containing all the elements in the receiver
- asByteArray
- Answer a ByteArray containing all the elements in the receiver
- asOrderedCollection
- Answer an OrderedCollection containing all the elements in the receiver
- asRunArray
- Answer the receiver converted to a RunArray. If the receiver is not ordered the order of the elements in the RunArray might not be the #do: order.
- asSet
- Answer a Set containing all the elements in the receiver with no duplicates
- asSortedCollection
- Answer a SortedCollection containing all the elements in the receiver with the default sort block - [ :a :b | a <= b ]
- asSortedCollection: aBlock
- Answer a SortedCollection whose elements are the elements of the receiver, sorted according to the sort block aBlock
6.32.4 Collection: copying Collections
- copyReplacing: targetObject withObject: newObject
- Copy replacing each object which is = to targetObject with newObject
- copyWith: newElement
- Answer a copy of the receiver to which newElement is added
- copyWithout: oldElement
- Answer a copy of the receiver to which all occurrences of oldElement are removed
6.32.5 Collection: enumerating the elements of a collection
- allSatisfy: aBlock
- Search the receiver for an element for which aBlock returns false. Answer true if none does, false otherwise.
- anyOne
- Answer an unspecified element of the collection. Example usage: ^coll inject: coll anyOne into: [ :max :each | max max: each ] to be used when you don't have a valid lowest-possible-value (which happens in common cases too, such as with arbitrary numbers
- anySatisfy: aBlock
- Search the receiver for an element for which aBlock returns true. Answer true if some does, false otherwise.
- beConsistent
- This method is private, but it is quite interesting so it is documented. It ensures that a collection is in a consistent state before attempting to iterate on it; its presence reduces the number of overrides needed by collections who try to amortize their execution times. The default implementation does nothing, so it is optimized out by the virtual machine and so it loses very little on the performance side. Note that descendants of Collection have to call it explicitly since #do: is abstract in Collection.
- collect: aBlock
- Answer a new instance of a Collection containing all the results of evaluating aBlock passing each of the receiver's elements
- conform: aBlock
- Search the receiver for an element for which aBlock returns false. Answer true if none does, false otherwise.
- contains: aBlock
- Search the receiver for an element for which aBlock returns true. Answer true if some does, false otherwise.
- detect: aBlock
- Search the receiver for an element for which aBlock returns true. If some does, answer it. If none does, fail
- detect: aBlock ifNone: exceptionBlock
- Search the receiver for an element for which aBlock returns true. If some does, answer it. If none does, answer the result of evaluating aBlock
- do: aBlock
- Enumerate each object of the receiver, passing them to aBlock
- do: aBlock separatedBy: separatorBlock
- Enumerate each object of the receiver, passing them to aBlock. Between every two invocations of aBlock, invoke separatorBlock
- inject: thisValue into: binaryBlock
- Pass to binaryBlock receiver thisValue and the first element of the receiver; for each subsequent element, pass the result of the previous evaluation and an element. Answer the result of the last invocation.
- reject: aBlock
- Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, don't answer true
- select: aBlock
- Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, answer true
6.32.6 Collection: printing
- inspect
- Print all the instance variables and objects in the receiver on the Transcript
- printOn: aStream
- Print a representation of the receiver on aStream
6.32.7 Collection: Removing from a collection
- remove: oldObject
- Remove oldObject from the receiver. If absent, fail, else answer oldObject.
- remove: oldObject ifAbsent: anExceptionBlock
- Remove oldObject from the receiver. If absent, evaluate anExceptionBlock and answer the result, else answer oldObject.
- removeAll: aCollection
- Remove each object in aCollection, answer aCollection, fail if some of them is absent. Warning: this could leave the collection in a semi-updated state.
- removeAll: aCollection ifAbsent: aBlock
- Remove each object in aCollection, answer aCollection; if some element is absent, pass it to aBlock.
6.32.8 Collection: storing
- storeOn: aStream
- Store Smalltalk code compiling to the receiver on aStream
6.32.9 Collection: testing collections
- capacity
- Answer how many elements the receiver can hold before having to grow.
- identityIncludes: anObject
- Answer whether we include the anObject object
- includes: anObject
- Answer whether we include anObject
- isEmpty
- Answer whether we are (still) empty
- notEmpty
- Answer whether we include at least one object
- occurrencesOf: anObject
- Answer how many occurrences of anObject we include
- size
- Answer how many objects we include
|