Back: Semaphore-mutual exclusion
Up: Class reference
Forward: SequenceableCollection class-instance creation
 
Top: GNU Smalltalk User's Guide
Contents: Table of Contents
Index: Class index
About: About this document

6.125 SequenceableCollection

Defined in namespace Smalltalk
Category: Collections-Sequenceable
My instances represent collections of objects that are ordered. I provide some access and manipulation methods.

6.125.1 SequenceableCollection class: instance creation  (class)
6.125.2 SequenceableCollection: basic  (instance)
6.125.3 SequenceableCollection: copying SequenceableCollections  (instance)
6.125.4 SequenceableCollection: enumerating  (instance)
6.125.5 SequenceableCollection: replacing items  (instance)
6.125.6 SequenceableCollection: testing  (instance)


6.125.1 SequenceableCollection class: instance creation

streamContents: aBlock
Create a ReadWriteStream on an empty instance of the receiver; pass the stream to aBlock, then retrieve its contents and answer them.


6.125.2 SequenceableCollection: basic

after: oldObject
Return the element after oldObject. Error if oldObject not found or if no following object is available

atAll: aCollection put: anObject
Put anObject at every index contained in aCollection

atAllPut: anObject
Put anObject at every index in the receiver

before: oldObject
Return the element before oldObject. Error if oldObject not found or if no preceding object is available

first
Answer the first item in the receiver

identityIndexOf: anElement
Answer the index of the first occurrence of an object identical to anElement in the receiver. Answer 0 if no item is found

identityIndexOf: anElement ifAbsent: exceptionBlock
Answer the index of the first occurrence of an object identical to anElement in the receiver. Invoke exceptionBlock and answer its result if no item is found

identityIndexOf: anElement startingAt: anIndex
Answer the first index > anIndex which contains an object identical to anElement. Answer 0 if no item is found

identityIndexOf: anObject startingAt: anIndex ifAbsent: exceptionBlock
Answer the first index > anIndex which contains an object exactly identical to anObject. Invoke exceptionBlock and answer its result if no item is found

indexOf: anElement
Answer the index of the first occurrence of anElement in the receiver. Answer 0 if no item is found

indexOf: anElement ifAbsent: exceptionBlock
Answer the index of the first occurrence of anElement in the receiver. Invoke exceptionBlock and answer its result if no item is found

indexOf: anElement startingAt: anIndex
Answer the first index > anIndex which contains anElement. Answer 0 if no item is found

indexOf: anElement startingAt: anIndex ifAbsent: exceptionBlock
Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found

indexOfSubCollection: aSubCollection
Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Answer 0 if no such sequence is found.

indexOfSubCollection: aSubCollection ifAbsent: exceptionBlock
Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Answer 0 if no such sequence is found.

indexOfSubCollection: aSubCollection startingAt: anIndex
Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Answer 0 if no such sequence is found.

indexOfSubCollection: aSubCollection startingAt: anIndex ifAbsent: exceptionBlock
Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Invoke exceptionBlock and answer its result if no such sequence is found

last
Answer the last item in the receiver


6.125.3 SequenceableCollection: copying SequenceableCollections

, aSequenceableCollection
Append aSequenceableCollection at the end of the receiver (using #add:), and answer a new collection

copyFrom: start
Answer a new collection containing all the items in the receiver from the start-th.

copyFrom: start to: stop
Answer a new collection containing all the items in the receiver from the start-th and to the stop-th

copyReplaceAll: oldSubCollection with: newSubCollection
Answer a new collection in which all the sequences matching oldSubCollection are replaced with newSubCollection

copyReplaceFrom: start to: stop with: replacementCollection
Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by the contents of the replacementCollection. Instead, If start = (stop + 1), like in `copyReplaceFrom: 4 to: 3 with: anArray', then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'.

copyReplaceFrom: start to: stop withObject: anObject
Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by the single element anObject. Instead, If start = (stop + 1), then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'.


6.125.4 SequenceableCollection: enumerating

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

do: aBlock
Evaluate aBlock for all the elements in the sequenceable collection

do: aBlock separatedBy: sepBlock
Evaluate aBlock for all the elements in the sequenceable collection. Between each element, evaluate sepBlock without parameters.

doWithIndex: aBlock
Evaluate aBlock for all the elements in the sequenceable collection, passing the index of each element as the second parameter. This method is mantained for backwards compatibility and is not mandated by the ANSI standard; use #keysAndValuesDo:

findFirst: aBlock
Returns the index of the first element of the sequenceable collection for which aBlock returns true, or 0 if none

findLast: aBlock
Returns the index of the last element of the sequenceable collection for which aBlock returns true, or 0 if none does

from: startIndex to: stopIndex do: aBlock
Evaluate aBlock for all the elements in the sequenceable collection whose indices are in the range index to stopIndex

from: startIndex to: stopIndex doWithIndex: aBlock
Evaluate aBlock for all the elements in the sequenceable collection whose indices are in the range index to stopIndex, passing the index of each element as the second parameter. This method is mantained for backwards compatibility and is not mandated by the ANSI standard; use #from:to:keysAndValuesDo:

from: startIndex to: stopIndex keysAndValuesDo: aBlock
Evaluate aBlock for all the elements in the sequenceable collection whose indices are in the range index to stopIndex, passing the index of each element as the first parameter and the element as the second.

keysAndValuesDo: aBlock
Evaluate aBlock for all the elements in the sequenceable collection, passing the index of each element as the first parameter and the element as the second.

readStream
Answer a ReadStream streaming on the receiver

readWriteStream
Answer a ReadWriteStream which streams on the receiver

reverse
Answer the receivers' contents in reverse order

reverseDo: aBlock
Evaluate aBlock for all elements in the sequenceable collection, from the last to the first.

with: aSequenceableCollection collect: aBlock
Evaluate aBlock for each pair of elements took respectively from the re- ceiver and from aSequenceableCollection; answer a collection of the same kind of the receiver, made with the block's return values. Fail if the receiver has not the same size as aSequenceableCollection.

with: aSequenceableCollection do: aBlock
Evaluate aBlock for each pair of elements took respectively from the re- ceiver and from aSequenceableCollection. Fail if the receiver has not the same size as aSequenceableCollection.

writeStream
Answer a WriteStream streaming on the receiver


6.125.5 SequenceableCollection: replacing items

replaceAll: anObject with: anotherObject
In the receiver, replace every occurrence of anObject with anotherObject.

replaceFrom: start to: stop with: replacementCollection
Replace the items from start to stop with replacementCollection's items from 1 to stop-start+1 (in unexpected order if the collection is not sequenceable).

replaceFrom: start to: stop with: replacementCollection startingAt: repStart
Replace the items from start to stop with replacementCollection's items from repStart to repStart+stop-start

replaceFrom: anIndex to: stopIndex withObject: replacementObject
Replace every item from start to stop with replacementObject.


6.125.6 SequenceableCollection: testing

= aCollection
Answer whether the receiver's items match those in aCollection

hash
Answer an hash value for the receiver

inspect
Print all the instance variables and context of the receiver on the Transcript




This document was generated on May, 12 2002 using texi2html