eXept Software AG Logo

Smalltalk/X Webserver

Documentation of class 'Collection':

Home

Documentation
www.exept.de
Everywhere
for:
[back]

Class: Collection


Inheritance:

   Object
   |
   +--Collection
      |
      +--Bag
      |
      +--BinaryTree
      |
      +--BloomFilter
      |
      +--BoundedCollection
      |
      +--CharacterDictionary
      |
      +--CharacterSet
      |
      +--Dolphin::SharedSet
      |
      +--FileDirectory
      |
      +--Iterator
      |
      +--KeyedCollection
      |
      +--MappedCollection
      |
      +--PowerSet
      |
      +--PriorityQueue
      |
      +--Queue
      |
      +--SequenceableCollection
      |
      +--Set
      |
      +--SharedCollection
      |
      +--SkipList
      |
      +--TreeSet
      |
      +--VirtualDictionary

Package:
stx:libbasic
Category:
Collections-Abstract
Version:
rev: 1.615 date: 2024/04/24 09:00:45
user: cg
file: Collection.st directory: libbasic
module: stx stc-classLibrary: libbasic

Description:


Abstract superclass for all collections.
This abstract class provides functionality common to all collections,
without knowing how the concrete class implements things.
Thus, all methods found here depend on some basic mechanisms
to be defined in the concrete class.
These basic methods are usually defined as #subclassResponsibility here.
Some methods are also redefined for better performance.

Subclasses MUST at least implement:
    do:     - enumerate elements

They should implement one of the following set of access messages:
For keyed collections:
    at:ifAbsent:            - fetching an element
    at:                     - fetching an element
    at:put:                 - storing an element

For unkeyed collections:
    add:                    - add an element
    remove:ifAbsent:        - remove an element

Given that the above is implemented in a concrete subclass,
Collection provides protocol for enumeration, searching and others.

However, for performance reasons, many of them are also redefined in
concrete subclasses, as some can be implemented much faster if implementation
details are known (for example, searching can be done faster if it is known that
elements are sorted or accessible by an integer key).

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.

Class protocol:

Compatibility-Squeak
o  ofSize: n
( an extension from the stx:libcompat package )
return a new collection which really provides space for n elements.
Kludges around the stupid definition of OrderedCollection>>new:

JS syntactic sugar
o  with: el1 _: el2
( an extension from the stx:libjavascript package )
for JS easy syntax - allows: Array.with(el1, el2,...)

o  with: el1 _: el2 _: el3
( an extension from the stx:libjavascript package )
for JS easy syntax - allows: Array.with(el1, el2,...)

o  with: el1 _: el2 _: el3 _: el4
( an extension from the stx:libjavascript package )
for JS easy syntax - allows: Array.with(el1, el2,...)

o  with: el1 _: el2 _: el3 _: el4 _: el5
( an extension from the stx:libjavascript package )
for JS easy syntax - allows: Array.with(el1, el2,...)

o  with: el1 _: el2 _: el3 _: el4 _: el5 _: el6
( an extension from the stx:libjavascript package )
for JS easy syntax - allows: Array.with(el1, el2,...)

o  with: el1 _: el2 _: el3 _: el4 _: el5 _: el6 _: el7
( an extension from the stx:libjavascript package )
for JS easy syntax - allows: Array.with(el1, el2,...)

o  with: el1 _: el2 _: el3 _: el4 _: el5 _: el6 _: el7 _: el8
( an extension from the stx:libjavascript package )
for JS easy syntax - allows: Array.with(el1, el2,...)

Signal constants
o  emptyCollectionSignal
return the signal used to report non-allowed operation on empty collections

o  invalidKeySignal
return the signal used to report bad key usage

o  notEnoughElementsSignal
return the signal used to report attempts for an operation, for which
there are not enough elements in the collection

o  valueNotFoundSignal
return the signal used to report a nonexisting element.

initialization
o  initialize
setup the signal

instance creation
o  collect: aCollection usingEnumerator: aBlockOrEnumeratorSelector
apply aBlock or enumeratorSelector to the receiver
and collect the enumerated elements.
If the enumerator is a symbol, it should be the name of an enumerator method (i.e. do:, reverseDo:, etc.).
If it is a block, it should be a two-arg block, expecting the collection first, and
a block to be applied to each element.
Can be used if the collection needs to be enumerated with a different enumerator
(eg. a tree, which implements aka. childrenDo:)

Usage example(s):

     OrderedCollection collect:#(1 2 3 4 5) usingEnumerator:#do:
     OrderedCollection collect:#(1 2 3 4 5) usingEnumerator:#reverseDo:
     OrderedCollection collect:#(1 2 3 4 5) usingEnumerator:[:coll :block | coll do:block]
     OrderedCollection collect:#(1 2 3 4 5) usingEnumerator:[:coll :block | coll reverseDo:block]

o  combiningEach: collection1 withEach: collection2 using: aTwoArgBlock
evaluate aTwoArgBlock for each combination of elements from collection1
and collection2 and return an instance of the receiver containing all those elements

Usage example(s):

     Set combiningEach:#(1 2 3 4 5) withEach:(10 to:100 by:10) using:[:a :b | a * b] 
     Set combiningEach:#(1 2 3 4 5) withEach:#(1 2 3 4 5) using:[:a :b | a * b] 
     Array combiningEach:#(1 2 3 4 5) withEach:#(1 2 3 4 5) using:[:a :b | a * b] 

o  new: size withAll: element
return a new Collection of size, where all elements are
initialized to element

o  newFrom: aCollection
Return an instance of me containing the same elements as aCollection.

Usage example(s):

     Bag newFrom:#(1 2 3 4 4 5 6 7 7 7 )  
     Set newFrom:#(1 2 3 4 4 5 6 7 7 7 ) 

o  newWithCapacity: n
return a new empty Collection preferrably with capacity for n elements.
Redefined in StringCollection, where #new: returns a non-empty collection.
This does not work for ArrayedCollections, which will be not empty.

We return an empty collection here, because there are subclasses
which do not implement #new:.

o  newWithSize: n
return a new non-empty collection with n elements.
Kludges around the inconsistent definition of #new: in
returning an empty collection in OrderedCollection and Set
and
returning an non-empty collection in ArrayedCollectins and StringCollection.

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

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

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

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

o  with: a1 with: a2 with: a3 with: a4 with: a5
return a new Collection with five elements

o  with: a1 with: a2 with: a3 with: a4 with: a5 with: a6
return a new Collection with size elements

o  with: a1 with: a2 with: a3 with: a4 with: a5 with: a6 with: a7
return a new Collection with seven elements

o  with: a1 with: a2 with: a3 with: a4 with: a5 with: a6 with: a7 with: a8
return a new Collection with eight elements

o  with: a1 with: a2 with: a3 with: a4 with: a5 with: a6 with: a7 with: a8 with: a9
return a new Collection with nine elements

o  with: a1 with: a2 with: a3 with: a4 with: a5 with: a6 with: a7 with: a8 with: a9 with: a10
return a new Collection with ten elements

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

Usage example(s):

        OrderedCollection withAll:#(1 2 3 4 5 6)
        List withAll:#(1 2 3 4 5 6)
        Array withAll:#(1 2 3 4 5 6)
        Set withAll:#(1 2 3 4 5 6)
        StringCollection withAll:#('line1' 'line2' 'line3')
        String withAll:#($a $b $c)
        Set withAll:(Iterator on:[:whatToDo | 1 to:10 do:[:i | whatToDo value:i]]).

o  withSize: n
obsolete: please use newWithSize:, for its better name

** This is an obsolete interface - do not use it (it may vanish in future versions) **

instance creation - streaming
o  writeStreamClass
the type of stream used in writeStream

Usage example(s):

     OrderedCollection writeStreamClass

misc ui support
o  iconInBrowserSymbol
( an extension from the stx:libtool package )
the browser will use this as index into the toolbariconlibrary

queries
o  growIsCheap
return true, if this collection can easily grow
(i.e. without a need for become:).
Returns true here; this method is redefined in fix-size
collections

o  isAbstract
Return if this class is an abstract class.
True is returned for Collection here; false for subclasses.
Abstract subclasses must redefine this again.

o  isValidElement: anObject
return true, if Iinstances of me can hold this kind of object


Instance protocol:

Compatibility-ANSI
o  identityIncludes: anObject
( an extension from the stx:libcompat package )
return true, if the argument, anObject is in the collection.
Same as #includesIdentical for Dolphin/ANSI compatibility.

Compatibility-Dolphin
o  includesAllOf: aCollection
( an extension from the stx:libcompat package )
same as #includesAll for Squeak/Dolphin compatibility.

Usage example(s):

     #(1 2 3 4 5 6 7) includesAllOf:#(1 2 3)
     #('hello' 'there' 'world') includesAllOf:#('hello' 'world')
     #(1 2 3 4 5 6 7) includesAllOf:#(7 8 9)
     #(1 2 3 4 5 6 7) includesAllOf:#(8 9 10)

o  includesAnyOf: aCollection
( an extension from the stx:libcompat package )
same as #includesAny for Squeak/Dolphin compatibility.

o  symmetricDifference: aCollection
( an extension from the stx:libcompat package )
return a new set containing all elements,
which are contained in either the receiver or aCollection, but not in both.
Same as xor: - for compatibility

Usage example(s):

     |c1 c2|

     c1 := #( foo bar baz baloo ).
     c2 := #( foe bar banana baloo ).
     c1 symmetricDifference:c2.         
     self assert:(c1 symmetricDifference:c2) asSet = (c2 symmetricDifference:c1) asSet

Compatibility-Squeak
o  , aCollection
return a new collection formed from concatenating the receiver with the argument

o  addIfNotPresent: anObject
( an extension from the stx:libcompat package )
Include anObject as one of the receiver's elements, but only if there
is no such element already. Answer anObject.
Better use #testAndAdd:, which answers whether anObject already existed in the collection.

o  anyOne
return any element from the collection.
Report an error if there is none.
Same as #anElement - for Squeak compatibility

o  associationsDo: aBlock
cg: I think this is bad, but - well...

o  collectAsSet: aBlock
( an extension from the stx:libcompat package )
Evaluates aBlock for each element of the receiver and collects
the resulting values into a Set.

o  contents
I am the contents of the collection

o  deepFlatten
( an extension from the stx:libcompat package )

o  deepFlattenInto: stream
( an extension from the stx:libcompat package )

o  detect: aOneArgBlockOrSymbol ifFound: foundBlock ifNone: exceptionValue
( an extension from the stx:libcompat package )
evaluate the argument aOneArgBlock for each element in the receiver until
the block returns true;
in this case evaluate foundBlock with the element that caused the true evaluation.
If none of the evaluations returns true, return the value from exceptionValue

Usage example(s):

     #(1 2 3 4) detect:[:n | n even] ifFound:[:n | n squared] ifNone:['sorry']

o  detect: aBlock ifOne: presentBlock
( an extension from the stx:libcompat package )

o  detect: aBlock ifOne: presentBlock ifNone: noneBlock
( an extension from the stx:libcompat package )

o  difference: aCollection
Answer the set-theoretic difference of two collections.

Usage example(s):

     #(0 2 4 6 8) difference:#(2 4)   

o  do: block displayingProgress: progressMessage
( an extension from the stx:libcompat package )
ProgressNotification handle:[:ex |
Transcript showCR:ex progressValue rounded.
ex proceed.
] do:[
#(0 1 2 3 4 5 6 6 7 8 9)
do:[:i| Delay waitForMilliseconds: 50]
displayingProgress: 'Progress'
].

o  equalsTo: aCollection
( an extension from the stx:libcompat package )
Answer true if the receiver contains the same elements as aCollection, and vice versa.

o  flatCollect: aBlock
( an extension from the stx:libcompat package )
Evaluate aBlock for each of the receiver's elements and answer the
list of all resulting values flatten one level.
Assumes that aBlock returns some kind of collection for each element.
Equivalent to the lisp's mapcan.
Notice that this is different from gather, which recurses deeper into elements.

Usage example(s):

     #((1 2) (3 4) (5 6) (7 8 (9))) flatCollect:[:el | el]  

     #((1 2) (3 4) (5 6) (7 8) (9)) gather:[:el | el]    

o  flatCollect: aBlock as: aCollectionClass
( an extension from the stx:libcompat package )
Evaluate aBlock for each of the receiver's elements and answer the
list of all resulting values flatten one level. Assumes that aBlock returns some kind
of collection for each element. Equivalent to lisp's mapcan

o  flatCollectAsSet: aBlock
( an extension from the stx:libcompat package )
Evaluate aBlock for each of the receiver's elements and answer the
list of all resulting values flatten one level. Assumes that aBlock returns some kind
of collection for each element. Equivalent to lisp's mapcan

Usage example(s):

     #((1) (2) (3 -4) (5 (-6 7) 8) (9 10)) flatCollect:[:i | i abs] as:Set
     #((1) (2) (3 -4) (5 (-6 7) 8) (9 10)) flatCollectAsSet:[:i | i abs]

o  flatten
( an extension from the stx:libcompat package )
Recursively collect each non-collection element of the receiver and its descendant
collections. Please note, this implementation assumes that strings are to be treated
as objects rather than as collection.

o  gather: aBlock
return an Array,
containing all elements as returned from applying aBlock to each element of the receiver,
where the block returns a collection of to-be-added elements.
This could also be called: collectAllAsArray:

Usage example(s):

     (Set withAll:#(10 20 30 10 20 40)) gather:[:el | Array with:el with:el * 2]
     #((10 20) (30 10) (20 40)) flatten
     #(((10) (20)) ((30) (10)) ((20) (40))) flatten 
     #(((10) (20)) ((30) (10)) ((20) (40))) deepFlatten 

o  gather: aBlock as: aClass
return an instance of the collection-class aClass,
containing all elements as returned from applying aBlock to each element of the receiver.
where the block returns a collection of to-be-added elements.
This could also be called: collectAll:as:

Usage example(s):

     (Set withAll:#(10 20 30 10 20 40)) gather:[:el | Array with:el with:el * 2] as:OrderedCollection
     (Set withAll:#(10 20 30 10 20 40)) collectAll:[:el | Array with:el with:el * 2]

o  groupBy: keyBlock having: selectBlock
Like in SQL operation - Split the receiver's contents into collections of
elements for which keyBlock returns the same results, and return those
collections allowed by selectBlock.

Usage example(s):

     #(1 2 3 4 5 6 7 8 9) groupBy:[:e | e odd] having:[:a | true]  

o  groupedBy: aBlock
( an extension from the stx:libcompat package )
Return a dictionary whose keys are the result of evaluating aBlock for all elements in
the collection, and the value for each key is the collection of elements that evaluated
to that key. e.g.
#(1 2 3 4 5) groupedBy: [:each | each odd]
a Dictionary
true ---> #( 1 3 5)
false --> #(2 4)
originally developed by a. kuhn and released under MIT.

o  groupedBy: aBlock affect: anotherBlock
( an extension from the stx:libcompat package )
First, evaluate aBlock for each of the receiver's elements and group the
elements by the resulting values, and second, evaluate anotherBlock for
each of the resulting groups
and return a dictionary with the first pass'
results as keys and the second pass' results as values.
cg: the comment is wrong: it returns the resuts as keys.

Usage example(s):

This is a shorthand for [ (self groupedBy: aBlock) collect: anotherBlock ].

o  ifEmpty: alternativeValue
return the receiver if not empty, alternativeValue otherwise

Usage example(s):

     'foo' ifEmpty: 'bar'
     '' ifEmpty: 'bar'
     '' ifEmpty: [ Time now printString ]

o  ifEmpty: ifEmptyValue ifNotEmpty: ifNotEmptyValue
return ifNotEmptyValue if not empty, ifEmptyValue otherwise

o  ifEmpty: ifEmptyValue ifNotEmptyDo: ifNotEmptyValue
return ifNotEmptyValue if not empty, ifEmptyValue otherwise

o  ifEmptyDo: ifEmptyValue ifNotEmpty: ifNotEmptyValue
return ifNotEmptyValue if not empty, ifEmptyValue otherwise.
ATTENTION:
Be aware that the compilers are not (currently) inlining this code;
therefore, full blocks will be generated and the code runs much slower than
a regular isEmpty ifTrue/ifFalse.
This has been added for compatibility only - to allow easy fileIn of squeak code

o  ifNotEmpty: ifNotEmptyValue
return ifNotEmptyValue if not empty, nil otherwise.
ATTENTION:
Be aware that the compilers are not (currently) inlining this code;
therefore, full blocks will be generated and the code runs much slower than
a regular isEmpty ifTrue/ifFalse.
This has been added for compatibility only - to allow easy fileIn of squeak code

o  ifNotEmptyDo: ifNotEmptyValue
return ifNotEmptyValue if not empty, nil otherwise.
ATTENTION:
Be aware that the compilers are not (currently) inlining this code;
therefore, full blocks will be generated and the code runs much slower than
a regular isEmpty ifTrue/ifFalse.
This has been added for compatibility only - to allow easy fileIn of squeak code

o  ifNotEmptyDo: ifNotEmptyValue ifEmpty: ifEmptyValue
return ifNotEmptyValue if not empty, ifEmptyValue otherwise.
ATTENTION:
Be aware that the compilers are not (currently) inlining this code;
therefore, full blocks will be generated and the code runs much slower than
a regular isEmpty ifTrue/ifFalse.
This has been added for compatibility only - to allow easy fileIn of squeak code

o  intersection: aCollection
( an extension from the stx:libcompat package )
same as intersect: for Squeak compatibility

o  nilSafeGroupedBy: aBlock
( an extension from the stx:libcompat package )

o  selectAsSet: aBlock
( an extension from the stx:libcompat package )
Evaluate aBlock with each of the receiver's elements as the argument.
Collect into a new set, only those elements for which
aBlock evaluates to true. Answer the new collection.

o  sorted: aBlock
( an extension from the stx:libcompat package )
Create a copy that is sorted.
Sort criteria is the block that accepts two arguments.
When the block returns true, the first arg goes first
i.e. [:a :b | a > b] sorts in descending order.

JavaScript support
o  forEach: aBlock
( an extension from the stx:libjavascript package )
same as do: for javaScript

o  length
( an extension from the stx:libjavascript package )
returns the length of the collection

Usage example(s):

     JavaScriptParser
        evaluate:'''hello''.length'

accessing
o  anElement
return any element from the collection,
report an error if there is none.
Use this to fetch the some element from a collection which is non-indexed or which
has a non-numeric index. I.e. if someone gets an arbitrary collection which might be either indexable
or not, anElement is a save way to access some element without a need to check for a proper key.

Usage example(s):

     #() anElement             -> Error
     #(1 2 3) anElement        -> 1
     #(1 2 3) asSet anElement  -> one of them (undefined, which one)

o  at: index add: anObject
assuming that the receiver is an indexed collection of collections,
retrieve the collection at index, and add anObject to it.
Raise an error, of there is no collection at that index (or the index is invalid).
Typically used with dictionaries of sets.

Usage example(s):

     (Dictionary new 
        at:'one' put:Set new;
        at:'two' put:Set new;
        yourself)
            at:'one' add:1;
            at:'two' add:2;
            at:'one' add:11;
            at:'two' add:22;
            yourself.

o  at: aKey ifAbsent: absentBlock
return the element at aKey if valid.
If the key is not present, return the result from evaluating the absentBlock.
NOTICE:
in ST-80, this message is only defined for Dictionaries,
however, having a common protocol with indexed collections
often simplifies things.

Usage example(s):

     #(1 2 3 4) at:5 ifAbsent:['bla']

o  at: index ifAbsentPut: initializerValue
return the element indexed by aKey if present,
if not present, store the result of evaluating valueBlock
under aKey and return it.

** This method must be redefined in concrete classes (subclassResponsibility) **

o  at: index ifAbsentPut: initializerValue add: anObject
assuming that the receiver is an indexed collection of collections,
retrieve the collection at index, and add anObject to it.
If there is no collection at that index put the value of initializerValue there
and add to that.
Typically used with dictionaries of sets.

Usage example(s):

     (Dictionary new 
        at:'one' ifAbsentPut:[Set new] add:'eins';
        at:'one' ifAbsentPut:[Set new] add:'une';
        at:'one' ifAbsentPut:[Set new] add:'uno';
        at:'two' ifAbsentPut:[Set new] add:'zwei';
        at:'two' ifAbsentPut:[Set new] add:'due';
        at:'two' ifAbsentPut:[Set new] add:'dos';
        yourself)

o  at: aKey ifNilOrAbsentPut: valueBlock
try to fetch the element at aKey. If either the key is invalid (as in a Dictionary)
or there is no element stored under that key (as in an Array), set the element
from the valueBlock and return it.
Useful for lazy initialization of collections.

Usage example(s):

     |d|

     d := Dictionary new.
     d at:#foo ifNilOrAbsentPut:[ 'hello' ]. 
     d     

Usage example(s):

     |a|

     a := Array new:10.
     a at:1 ifNilOrAbsentPut:[ 'hello' ].  
     a    

o  at: aKey ifPresent: presentBlock
try to retrieve the value stored at aKey.
If there is nothing stored under this key, do nothing.
Otherwise, evaluate aBlock, passing the retrieved value as argument.

Usage example(s):

     |d|
     d := Dictionary new.
     d at:'foo' put:'bar'.   
     d at:'foo' ifPresent:[:val | Transcript showCR:'foo is: %1' with:val]. 
     d at:'bla' ifPresent:[:val | Transcript showCR:'bla is: %1' with:val].

Usage example(s):

     |a|
     a := #(10 20 30).
     a at:2 ifPresent:[:val | Transcript showCR:'[2] is: %1' with:val]. 
     a at:4 ifPresent:[:val | Transcript showCR:'[4] is: %1' with:val]. 

o  at: aKey putIfNotNil: value
if value is not nil, it is stored using at:put:.
Otherwise, it is ignored.
This is mainly of use, if values are added to a dictionary in a cascade expression

Usage example(s):

     |a d|
     a := #(1 2 nil 3 4 5 6 nil 7 8 9).
     d := Dictionary new.
     a doWithIndex:[:each :idx | d at:idx putIfNotNil:each].
     d 

o  atAll: indexCollection put: anObject
put anObject into all indexes from indexCollection in the receiver.
This abstract implementation requires that the receiver supports
access via a key (and indexCollection contains valid keys).

Notice: This operation modifies the receiver, NOT a copy;
therefore the change may affect all others referencing the receiver.

Usage example(s):

     (Array new:10) atAll:(1 to:5) put:0
     (Array new:10) atAll:#(1 5 6 9) put:0
     (Dictionary new) atAll:#(foo bar baz) put:'hello' 

    raises an error:
     (Set new) atAll:#(foo bar baz) put:'hello' 

o  atAny: aCollectionOfKeysTriedInSequence ifAbsent: absentBlock
try aCollectionOfKeysTriedInSequence and return the element at
the first found valid key.
If none of the keys is not present, return the result of evaluating
the exceptionblock.

Usage example(s):

     |d|
     d := Dictionary new.
     d at:'$foo' put:'yes'.
     d at:'#foo' put:'yes2'.
     d atAny:#('$foo' '#foo') ifAbsent:['no'].
     d atAny:#('#foo' '$foo') ifAbsent:['no'].
     d atAny:#('#bar' '$bar') ifAbsent:['no'].

o  decrementAt: aKey
remove 1 from the count stored under aKey.
If not yet present, assume 0 as initial counter value.

o  fifth
return the fifth element of the collection.
For unordered collections, this simply returns the fifth
element when enumerating them.
This should be redefined in subclasses.

Usage example(s):

     #(1 2 3 4 5) fifth

o  first
return the first element of the collection.
For unordered collections, this simply returns the first
element when enumerating them.
This should be redefined in subclasses.

o  first: n
return the n first elements of the collection.
No longer raises an error if there are not enough elements;
instead, returns what is there.

For unordered collections, this simply returns the first
n elements when enumerating them.
(Warning: the contents of the returned collection is not deterministic in this case).
This should be redefined in subclasses.

Usage example(s):

     #(1 2 3 4 5) first:3
     #(1 2 3 4 5) asSet first:3
     #(1 2 3) first:5
     #(1 2 3) asSet first:5

o  firstIfEmpty: exceptionValue
return the first element of the collection.
If it's empty, return the exceptionValue.
(i.e. don't trigger an error as done in #first)

o  firstOrNil
return the first element of the collection.
If it's empty, return nil.
(i.e. don't trigger an error as done in #first)

o  fourth
return the fourth element of the collection.
For unordered collections, this simply returns the fourth
element when enumerating them.
This should be redefined in subclasses.

Usage example(s):

     #(1 2 3 4) fourth

o  incrementAt: aKey
add 1 to the count stored under aKey.
If not yet present, assume 0 as initial counter value.

o  incrementAt: aKey by: more
add count to the count stored under aKey.
If not yet present, assume 0 as initial (counter) value.

Usage example(s):

     |coll|

     coll := Dictionary new.
     coll incrementAt:'foo' by:1.
     coll incrementAt:'bar' by:2.
     Transcript showCR:coll.
     coll incrementAt:'foo' by:11.
     coll incrementAt:'baz' by:2.
     coll incrementAt:'bar' by:20.
     Transcript showCR:coll.

o  keys
return the keys of the collection.

** This method must be redefined in concrete classes (subclassResponsibility) **

o  keysSorted
return the keys as a sorted sequenceable collection.
Some collections (which keep their keys already sorted) may
redefine this method to return the keys as they are kept internally.
The fallback here sorts them into an OrderedCollection

o  keysSorted: aBlock
return the keys as a sorted sequenceable collection.
Some collections (which keep their keys already sorted) may
redefine this method to return the keys as they are kept internally.
The fallback here sorts them into an OrderedCollection

o  last
return the last element of the collection.
This is a slow fallback implementation,
and should be redefined in subclasses which can do indexed accesses.

o  last: n
return the n last elements of the collection.
No longer raises an error if there are not enough elements;
instead, returns what is there.
For unordered collections, this simply returns the last
n elements when enumerating them
(Warning: the contents of the returned collection is not deterministic in this case).
This should be redefined in subclasses since the implementation here is VERY inefficient.

Usage example(s):

     #(1 2 3 4 5) last:3
     #(1 2 3 4 5 6 7 8 9 0) asSet last:3
     'hello world' last:5
     'hello' last:10
     'hello' asSet last:10

o  lastIfEmpty: exceptionValue
return the last element of the collection.
If it is empty, return the exceptionValue.
(i.e. don't trigger an error as done in #last)

o  lastOrNil
return the first element of the collection.
If it's empty, return nil.
(i.e. don't trigger an error as done in #first)

o  nth: n
return the nth element of the collection.
For unordered collections, this simply returns the nth
element when enumerating them.
This should be redefined in subclasses which can accecss fast by numeric index (aka Array-like things).

Usage example(s):

     #(1 2 3 4) nth:3
     #(1 2 3 4) nth:5

     #(1 2 3 4) asSet nth:3  
     #(1 2 3 4) asSet nth:5

o  order
report an error that only OrderedXXX's have an order

o  second
return the second element of the collection.
For unordered collections, this simply returns the second
element when enumerating them.
This should be redefined in subclasses.

Usage example(s):

     #(1 2 3) second

o  secondLast
return the second last element of the collection.
This is a slow fallback implementation,
and should be redefined in subclasses which can do indexed accesses.

o  seventh
return the seventh element of the collection.
For unordered collections, this simply returns the sixth
element when enumerating them.
This should be redefined in subclasses.

Usage example(s):

     #(1 2 3 4 5 6 7) seventh

o  sixth
return the sixth element of the collection.
For unordered collections, this simply returns the sixth
element when enumerating them.
This should be redefined in subclasses.

Usage example(s):

     #(1 2 3 4 5 6 7) sixth

o  third
return the third element of the collection.
For unordered collections, this simply returns the third
element when enumerating them.
This should be redefined in subclasses.

Usage example(s):

     #(1 2 3) third

o  values
return a collection containing all values of the receiver.
This is to make value access to an OrderedDictionary compatible with any-Collection

Usage example(s):

        #(1 2 3 4 5) values     
        #(1 2 3 4 5) asSet values
        #(1 2 3 4 5) asOrderedSet values

adding & removing
o  add: anObject
add the argument, anObject to the receiver.
If the receiver is ordered, the position of the new element is undefined
(i.e. don't depend on where it will be put).
An error is raised here - it is to be implemented by a concrete subclass.

** This method must be redefined in concrete classes (subclassResponsibility) **

o  add: newObject withOccurrences: anInteger
add the argument, anObject anInteger times to the receiver.
Returns the object.

o  addAll: aCollection
add all elements of the argument, aCollection to the receiver.
Returns the argument, aCollection.

Usage example(s):

     #(1 2 3 4) copy addAll:#(5 6 7 8); yourself
     #(1 2 3 4) asOrderedCollection addAll:#(5 6 7 8); yourself

o  addAll: aCollectionOfObjects withOccurrences: anInteger
add each element from aCollection, anInteger times to the receiver.
Returns the argument, aCollection (sigh).

o  addAllFirst: aCollection
insert all elements of the argument, aCollection at the beginning
of the receiver. Returns the argument, aCollection.

Usage example(s):

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

o  addAllLast: aCollection
add all elements of the argument, aCollection to the receiver.
Returns the argument, aCollection.

Usage example(s):

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

o  addAllNonNilElements: aCollection
add all non-nil elements of the argument, aCollection to the receiver.
Use this, when operating on a Set, that should not hold nil.
Answer the argument, aCollection.

Usage example(s):

     #(1 2 3 4) asSet addAllNonNilElements:#(5 nil 6 7 8); yourself

o  addAllReversed: aCollection
add all elements of the argument, aCollection in reverse order to the receiver.
Returns the argument, aCollection (sigh).

Usage example(s):

     #(1 2 3 4) copy addAllReversed:#(5 6 7 8); yourself
     #(1 2 3 4) asOrderedCollection addAllReversed:#(5 6 7 8); yourself

o  addFirst: anObject
add the argument, anObject to the receiver.
If the receiver is ordered, the new element will be added at the beginning.
An error is raised here - it is to be implemented by a concrete subclass.

** This method must be redefined in concrete classes (subclassResponsibility) **

o  addLast: anObject
add the argument, anObject to the receiver.
If the receiver is ordered, the new element will be added at the end.
Return the argument, anObject.

This usually has the same semantics as #add:.
OrderedSet and OrderedDictionary redefine this, to move anObject to
the end, even if it is already present in the collection.

o  clearContents
remove all elements from the receiver. Returns the receiver.
Subclasses may redefine this to keep the container.

o  contents: aCollection
set my contents from aCollection
- this may be redefined in a concrete subclass for more performance

o  dropAllSuchThat: aBlock
Apply the condition to each element and remove it if the condition is true.
First elements-to-remove are collected, then removed in one operation.
Differs from #removeAllSuchThat:
returns self instead of a collection containing the removed elements.
Delegated to #removeAllSuchThat: to ensure the functionality in subclasses
that do not implement this method (yet).

Usage example(s):

     |coll|

     coll := #(1 2 2 3 4 5 6 7 8 9 10) asSet.
     coll dropAllSuchThat:[:el | el even].
     coll     

o  dropFirst: n
remove the first n elements from the receiver.
Return the receiver.
Notice: for some collections (those not tuned for
resizing themself) this may be very slow.

Usage example(s):

     |coll|
     coll := OrderedCollection withAll:#(1 2 3 4 5 6).
     coll dropFirst:3.   
     coll  

o  dropLast: n
remove the last n elements from the receiver collection.
Return the receiver.
Notice: for some collections this may be very slow
(those not tuned for resizing themself).

o  remove: anObject
search for the first element, which is equal to anObject;
if found, remove and return it.
If not found, report a 'value not found'-error.
Uses equality compare (=) to search for the occurrence.

o  remove: anObject ifAbsent: exceptionBlock
search for the first element, which is equal to anObject;
if found, remove and return it.
If not found, return the value of the exceptionBlock.
Uses equality compare (=) to search for the occurrence.
An error is raised here - it is to be implemented by a concrete subclass.

** This method must be redefined in concrete classes (subclassResponsibility) **

o  removeAll
remove all elements from the receiver. Returns the receiver.
This should be reimplemented in subclasses for better
performance.

o  removeAll: aCollection
remove all elements from the receiver which are equal to any in aCollection.
Return the argument, aCollection.
Raises an error, if some element-to-remove is not in the receiver.
(see also: #removeAllFoundIn:, which does not raise an error).

Notice: for some collections (those not tuned for
resizing themself) this may be very slow.
If the number of removed elements is big compared to
the receiver's size, it may be better to copy the
ones which are not to be removed into a new collection.

Usage example(s):

     |coll|

     coll := #(1 2 3 4 5 6) asSet.
     coll removeAll:#(4 5 6).
     coll

o  removeAllFoundIn: aCollection
remove all elements from the receiver which are equal to any in aCollection.
No error is raised, if some element-to-remove is not in the receiver.
(see also: #removeAll:, which does raise an error).

Usage example(s):

     |coll|

     coll := #(1 2 3 4 5 6) asSet.
     coll removeAllFoundIn:#(4 5 6 7 8).
     coll

o  removeAllIdentical: aCollection
remove all elements from the receiver which are in aCollection.
Return the argument, aCollection.
Raises an error, if some element-to-remove is not in the receiver.
(see also: #removeAllFoundIn:, which does not raise an error).

Notice: for some collections (those not tuned for
resizing themself) this may be very slow.
If the number of removed elements is big compared to
the receiver's size, it may be better to copy the
ones which are not to be removed into a new collection.

o  removeAllIdenticalFoundIn: aCollection
remove all elements from the receiver which are in aCollection.
No error is raised, if some element-to-remove is not in the receiver.
(see also: #removeAll:, which does raise an error).

o  removeAllSuchThat: aBlock
Apply the condition block to each element and remove it if the condition is true.
Return a collection of removed elements.
First elements-to-remove are collected, then removed in one operation.

Usage example(s):

     |coll|

     coll := #(1 2 2 3 4 5 6 7 8 9 10) asOrderedCollection.
     coll removeAllSuchThat:[:el | el even].
     coll     

Usage example(s):

     |coll bla|

     bla := 'bla' copy.
     coll := #(1 'bla' 3 4 5 6 7 8 9 10) asOrderedCollection.
     coll add:bla.
     coll removeAllSuchThat:[:el | el == bla].
     coll     

Usage example(s):

     |coll|

     coll := #(1 2 3 4 5 6 7 8 9 10) asSet.
     coll removeAllSuchThat:[:el | el even].
     coll     

o  removeFirst
remove the first element from the receiver.
Return the removed element.

Usage example(s):

     (Set with:3 with:2 with:1) removeFirst 

o  removeFirst: nIn
remove the first n elements from the receiver.
Return a collection of removed elements.
Notice: for some collections (those not tuned for
resizing themself) this may be very slow.

Usage example(s):

     |coll|
     coll := OrderedCollection withAll:#(1 2 3 4 5 6).
     coll removeFirst:3.   
     coll  

o  removeFirstIfAbsent: exceptionBlock
remove the first element from the collection; return the removed element.
If there is no element in the receiver collection, return the value from
exceptionBlock.
Destructive: modifies the receiver

Usage example(s):

     (Set with:3 with:2 with:1) removeFirst 
     Set new removeFirstIfAbsent:'nothing' 

o  removeIdentical: anObject
search for the first element, which is identical to anObject;
if found, remove and return it.
If not found, report a 'value not found'-error.
Uses identity compare (==) to search for the occurrence.

o  removeIdentical: anObject ifAbsent: exceptionBlock
search for the first element, which is identical to anObject;
if found, remove and return it.
If not found, return the value of the exceptionBlock.
Uses identity compare (==) to search for the occurrence.
An error is raised here - it is to be implemented by a concrete subclass.

** This method must be redefined in concrete classes (subclassResponsibility) **

o  removeLast
remove the last element from the receiver.
Return the removed element.
An error is raised here - it is to be implemented by a concrete subclass.

** This method must be redefined in concrete classes (subclassResponsibility) **

o  removeLast: n
remove the last n elements from the receiver collection.
Destructive: modifies the receiver.
Return a collection of removed elements.
Notice: for some collections this may be very slow
(those not tuned for resizing themself).

o  testAndAdd: anElement
Test, if the element is present in the receiver.
If the element does not exist, add it to the collection.
Answer true, if the element was already in the collection.
Provided mostly for Sets, which can do the test and add faster
(avoid hashing twice)

WARNING: do not add elements while iterating over the receiver.
Iterate over a copy to do this.

o  unless: aCheckBlockOrBoolean add: anObject
if aCheckBlockOrBoolean evaluates to false,
add the argument, anObject to the receiver.
Otherwise do nothing.

o  when: aCheckBlockOrBoolean add: anObject
if aCheckBlockOrBoolean evaluates to true,
add the argument, anObject to the receiver.
Otherwise do nothing.
Useful when constructing collections in a cascade

Usage example(s):

     |coll a|

     a := 10.
     coll := OrderedCollection new
        when:[a > 5] add:a;
        when:[a > 15] add:a;
        yourself.
     coll inspect.

bulk operations
o  abs
absolute value of all elements in the collection.
Elements are supposed to be numeric

Usage example(s):

     TestCase assert:( #(1 -2 -3 4) abs = #(1 2 3 4)).

o  negated
negated value of all elements in the collection.
Elements are supposed to be numeric

Usage example(s):

     TestCase assert:( #(1 -2 -3 4) negated = #(-1 2 3 -4)).

o  product
return the product of all elements which are supposed to be numeric.
Returns 1 for an empty receiver.

Usage example(s):

     TestCase should:[ Array new product ] raise:Error.

     TestCase assert:( #(1) product == 1).
     TestCase assert:( #(6) product == 6).
     TestCase assert:( #(1 2 3 4 5) product = 5 factorial )

o  product: aBlock
for each element in the receiver, evaluate the argument, aBlock and multiply up the results.
Return the total product or 1 for an empty collection.
Similar to (self collect...) product, but avoids creation of an intermediate collection.

Usage example(s):

     TestCase assert:(
        ((1 to:10) collect:[:n | n squared]) product = ((1 to:10) product:[:n | n squared])
     )
     TestCase assert:(
        ((1 to:10) collect:[:n | n squared]) product = ((1 to:10) product:#squared)
     )

o  sum
return the sum of all elements which are supposed to be numeric.
Returns 0 for an empty receiver.

Usage example(s):

     TestCase assert: ( #() sum = 0 ).
     TestCase assert: ( #(1) sum = 1 ).
     TestCase assert: ( #(1 2 3 4) sum = 10 ).
     TestCase assert: ( (1 to:10) sum = 55 ).
     TestCase assert: ( 'abc' asByteArray sum = 294 ).
     TestCase assert: ( { 10 +/- 2.
                          20 +/- 4.
                         100 +/- 10 } sum = (130 +/- 16) ).

     TestCase assert: ( { (1 / 9).
                          (1 / 7).
                        } sum = (16 / 63) ).

o  sum: aBlock
for each element in the receiver, evaluate the argument, aBlock and sum up the results.
Return the total sum or 0 for an empty collection.
Similar to (self collect...) sum, but avoids creation of an intermediate collection.

Usage example(s):

     TestCase assert:(
        ((1 to:10) collect:[:n | n squared]) sum = ((1 to:10) sum:[:n | n squared])
     )

comparing
o  identicalContentsAs: aCollection
return true if the receiver and aCollection represent collections
with identical contents. This is much like #sameContentsAs:, but compares
elements using #== instead of #=.

Usage example(s):

     #(1 2 3 4 5) = #(1 2 3 4 5)
     #(1 2 3 4 5) = #(1.0 2 3 4.0 5)
     #($1 $2 $3 $4 $5) = '12345'

     #(1 2 3 4 5) identicalContentsAs:#(1 2 3 4 5)
     #(1 2 3 4 5) identicalContentsAs: #(1.0 2 3 4.0 5)
     #($1 $2 $3 $4 $5) identicalContentsAs: '12345'

Usage example(s):

     |col|

     col := #('aaa' 'bbb' 'ccc' 'ddd').
     col identicalContentsAs:(col asIdentitySet).  
     col identicalContentsAs:(col copy asIdentitySet).  
     col identicalContentsAs:(col deepCopy asIdentitySet).  

o  sameContentsAs: aCollection
answer true, if all the elements in self and aCollection
are common. This is not defined as #=, since we cannot redefine #hash
for aCollection.

Usage example(s):

      #(1 2 3) asSet sameContentsAs: #(1 2 3)
      #(1 2 3 4) asSet sameContentsAs: #(1 2 3)
      #(1 2 3) asSet sameContentsAs: #(1 2 3 3)
      #(1 2 3 'aa') asSet sameContentsAs: #(1 2 3 'aa')
      #(1 2 3 'aa') asIdentitySet sameContentsAs: #(1 2 3 'aa')
      #(1 2 3 #aa) asIdentitySet sameContentsAs: #(1 2 3 #aa)

o  sameContentsAs: aCollection whenComparedWith: compareBlock
answer true, if all the elements in self and aCollection
are common. This is not defined as #=, since we cannot redefine #hash
for aCollection.

Usage example(s):

     #(1 2 3 4 5) asSet sameContentsAs: #(1 2 3 4 5) whenComparedWith:[:a :b | a = b]
     #(1 2 3 4 5) sameContentsAs: #(1 2 3 4 5) asSet whenComparedWith:[:a :b | a = b]
     #(1 2 3 4 5) asSet sameContentsAs: #(1 2 3 4 5)     whenComparedWith:[:a :b | a == b]
     #(1 2 3 4 5) asSet sameContentsAs: #(1.0 2 3 4.0 5) whenComparedWith:[:a :b | a = b]
     #(1 2 3 4 5) asSet sameContentsAs: #(1.0 2 3 4.0 5) whenComparedWith:[:a :b | a == b]

     #('Hello' 'ABC' 'worlD') asSet sameContentsAs: #('Hello' 'ABC' 'worlD') whenComparedWith:[:a :b | a sameAs:b]

converting
o  asArray
return an Array with the collection's elements.
Notice: this is redefined in Array, where it returns the receiver.
Use asNewArray, if you intent to modify the returned collection.

o  asArrayOfType: arrayClass
return a new instance of arrayClass with the collection's elements

o  asBag
return a new Bag with the receiver collection's elements

o  asByteArray
return a new ByteArray with the collection's elements
(which must convert to 8bit integers in the range 0..255).

o  asCollection
return myself as a Collection.
I am already a Collection.

o  asCollectionDo: aBlock
enumerate myself

o  asCollectionOrEmptyIfNil
return myself as a Collection.
I am already a Collection.

o  asDictionary
return a Dictionary with the receiver collection's elements,
using the original keys of the receiver as dictionary key.
Notice: this is redefined in Dictionary, where it returns the receiver.
Use asNewDictionary, if you intend to modify the returned collection.
See associationsAsDictionary if you already have a collection of associations

Usage example(s):

     #(10 20 30 40 50 60 70 80 90) asDictionary 

o  asDoubleArray
return a new DoubleArray with the collection's elements
(which must convert to 64bit floats).

o  asFlatOrderedCollection
return a new ordered collection containing all elements of the receiver
and recursively of all collectionelements from the receiver

Usage example(s):

     #(
        (1 2 3)
        4 5
        (6)
        7
        (8 (9 10) 11 12 (13 (14 (15) 16)))
     ) asFlatOrderedCollection

o  asFloatArray
return a new FloatArray with the collection's elements
(which must convert to 32bit floats).

o  asHalfFloatArray
( an extension from the stx:libbasic2 package )
return a new HalfFloatArray with the collection's elements
(which must convert to 16bit half-floats).

o  asIdentitySet
return a new IdentitySet with the receiver collection's elements

o  asIdentitySkipList
( an extension from the stx:libbasic2 package )
Answer a IdentitySkipList whose elements are the elements of the
receiver. The sort order is the default less than or equal.

o  asIntegerArray
return a new IntegerArray with the collection's elements
(which must convert to 32bit unsigned integers in the range 0..16rFFFFFFFF).
Please use asUnsignedIntXXArray to make the signedness and bitsize clear

o  asIntegerArray: arrayClass
return a new instance of arrayClass with the collection's elements;
arrayClass is supposed to hold integers (i.e. WordArray, LongArray, etc.)

o  asKeysAndValues
return a Dictionary with the receiver's associations as key->value pairs
using each element's key as dictionary key and value as dictionary value.

Usage example(s):

     { 'ten' -> 10 . 'twenty' -> 20 . 'thirty' -> 30 } asSet asKeysAndValues 
     { 'ten' -> 10 . 'twenty' -> 20 . 'thirty' -> 30 } asKeysAndValues 

o  asList
( an extension from the stx:libbasic2 package )
return a new List with the receiver collection's elements

o  asLongIntegerArray
return a new LongIntegerArray with the collection's elements
(which must convert to 64bit ned unsigned integers in the range
0..16rFFFFFFFFFFFFFFFF).
Please use asUnsignedIntXXArray to make the signedness and bitsize clear

o  asMutableCollection
return myself

o  asNewArray
return a new Array with the receiver collection's elements.
This method ensures that the returned collection is a new one, not
the same or shared with the original receiver

o  asNewDictionary
return a new Dictionary with the receiver collection's elements.
This method ensures that the returned collection is a new one, not
the same or shared with the original receiver

o  asNewIdentitySet
return a new IdentitySet with the receiver collection's elements.
This method ensures that the returned collection is a new one, not
the same or shared with the original receiver

o  asNewOrderedCollection
return a new OrderedCollection with the receiver collection's elements.
This method ensures that the returned collection is a new one, not
the same or shared with the original receiver

o  asNewOrderedSet
return a new OrderedSet with the receiver collection's elements.
This method ensures that the returned collection is a new one, not
the same or shared with the original receiver

o  asNewSet
return a new Set with the receiver collection's elements.
This method ensures that the returned collection is a new one,
not the same or shared with the original receiver

o  asNilIfEmpty
return mySelf, or nil if I am empty

o  asOrderedCollection
return an OrderedCollection with the receiver collection's elements.
Notice: this is redefined in OrderedCollection, where it returns the receiver.
Use asNewOrderedCollection, if you intent to modify the returned collection.

o  asOrderedSet
return a new OrderedSet with the receiver collection's elements.
Notice: this is redefined in OrderedSet, where it returns the receiver.
Use asNewOrderedSet, if you intent to modify the returned collection.

o  asRunArray
( an extension from the stx:libbasic2 package )
return a new RunArray with the collection's elements

Usage example(s):

     #(1 2 3 3 3 4 4 4 4 5 6 7) asRunArray 

o  asSequenceableCollection
return myself as a SequenceableCollection.
I am already a Collection, but not sequenceable.

o  asSet
return a Set with the receiver collection's elements.
Notice: this is redefined in Set, where it returns the receiver.
Use asNewSet, if you intent to modify the returned collection.

o  asSharedCollection
( an extension from the stx:libbasic2 package )
return a shared collection on the receiver.
This implements synchronized (i.e. mutually excluded) access to me.
Use this for safe access when multiple processes access me concurrently.
Notice that this is a general (possibly suboptimal) mechanism, which should
work with all collections. Look for specialized collections (SharedQueue), which are
tuned for this kind of operation.

o  asSharedCollectionWithLock: aRecursionLock
( an extension from the stx:libbasic2 package )
return a shared collection on the receiver.
Reuse aRecursionLock for locking.
This implements synchronized (i.e. mutually excluded) access to me.
Use this for safe access when multiple processes access me concurrently.
Notice that this is a general (possibly suboptimal) mechanism, which should
work with all collections. Look for specialized collections (SharedQueue), which are
tuned for this kind of operation.

o  asSignedByteArray
return a new ByteArray with the collection's elements
(which must convert to 8bit integers in the range -128..127).

Usage example(s):

        #( 1 2 3 4 -128 -5 -6) asSignedByteArray

o  asSignedInt16Array
return a new WordArray with the collection's elements
(which must convert to 16bit integers in the range -0x8000..16r7FFF).

o  asSignedInt32Array
return a new IntegerArray with the collection's elements
(which must convert to 16bit unsigned integers in the range -0x80000000..16r7FFFFFFF).

Usage example(s):

     #[1 2 3 4] asSignedInt32Array 

o  asSignedInt64Array
return a new IntegerArray with the collection's elements
(which must convert to 64bit signed integers.

Usage example(s):

     #[1 2 3 4] asSignedInt64Array 

o  asSignedIntegerArray
return a new SignedIntegerArray with the collection's elements
(which must convert to 32bit signed integers in the range 16r-80000000..16r7FFFFFFF).
Please use asSignedIntXXArray to make the bitsize clear

o  asSignedLongIntegerArray
return a new LongIntegerArray with the collection's elements
(which must convert to 64bit integers in the range 16r-8000000000000000..16r7FFFFFFFFFFFFFFF).
Please use asSignedIntXXArray to make the bitsize clear

o  asSignedWordArray
return a new WordArray with the collection's elements
(which must convert to 16bit integers in the range -0x8000..16r7FFF).
Please use asSignedIntXXArray to make the bitsize clear

o  asSkipList
( an extension from the stx:libbasic2 package )
Answer a SkipList whose elements are the elements of the
receiver. The sort order is the default less than or equal.

o  asSkipList: aSortBlock
( an extension from the stx:libbasic2 package )
Answer a SkipList whose elements are the elements of the
receiver. The sort order is defined by the argument, aSortBlock.

o  asSortedCollection
return a new SortedCollection with the receiver collection's elements

o  asSortedCollection: sortBlock
return a new SortedCollection with the receiver collection's elements,
using sortBlock for comparing

o  asSortedStrings
Create & return a SortedCollection that sorts the receiver's
elements according to the locales collating policy.
This is currently not really supported - strings are sorted
without caring for the locale.

o  asSortedStrings: sortBlock
Create & return a SortedCollection that sorts the receiver's
elements using sortBlock and according to the locales collating policy,
which is passed as first arg to sortBlock.
This is currently not really supported - strings are sorted
without caring for the locale.

o  asSortedStrings: sortBlock with: aCollationPolicy
Create & return a SortedCollection that sorts the receiver's
elements using sortBlock and according to the specified locales collating policy.
This is currently not really supported - strings are sorted
without caring for the locale.

o  asSortedStringsWith: aCollationPolicy
Create & return a SortedCollection that sorts the receiver's
elements according to the specified locales collating policy.
This is currently not really supported - strings are sorted
without caring for the locale.

o  asString
return a String with the collection's elements.
If all elements are characters, answer a String consisting of the characters,
otherwise answer the printString of the Collection.

Usage example(s):

     #(83 80 81 82) asString
     #($a $b $c) asString
     #(16r8000 16r8001 16r8002) asString
     #(16r80000 16r80001 16r80002) asString
     #(16r80 16r800 16r8000) asString
     #(16r80 asCharacter) asString

o  asStringCollection
return a new string collection containing the elements;
these ought to be strings. (i.e. String or Text instances)

o  asUnicodeString
return a String with the collection's elements
(which must convert to characters)

Usage example(s):

      #(16r440 16r443 16r441 16r441 16r43A 16r438 16r439 16r20 16r44F 16r437 16r44B 16r43A) asUnicodeString
      #(16r440 16r443 16r441 16r1f600 16r443 16r441 16r441) asUnicodeString

o  asUnsignedByteArray
return a new ByteArray with the collection's elements
(which must convert to 8bit integers in the range 0..255).

o  asUnsignedInt16Array
return a new WordArray with the collection's elements
(which must convert to 16bit unsigned integers in the range 0..16rFFFF).

Usage example(s):

     #[1 2 3 4] asUnsignedInt16Array

o  asUnsignedInt32Array
return a new IntegerArray with the collection's elements
(which must convert to 32bit unsigned integers in the range 0..16rFFFFFFFF).

Usage example(s):

     #[1 2 3 4] asUnsignedInt32Array 

o  asUnsignedInt64Array
return a new IntegerArray with the collection's elements
(which must convert to 64bit unsigned integers.

o  asWordArray
return a new WordArray with the collection's elements
(which must convert to unsigned integers in the range 0..16rFFFF).
Please use asUnsignedIntXXArray to make the signedness and bitsize clear

o  associationsAsDictionary
Modified (comment): / 14-09-2018 / 18:13:21 / Stefan Vogel

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  copyAs: collectionClass
return a new instance of collectionClass with the receiver collection's elements.
This is similar to copy as:collectionClass, to ensure that we get a new
(unshared) collection, but avoids the copy if the receiver is not already an
instance of collectionClass.

Usage example(s):

     |coll1 coll2|

     coll1 := #(1 2 3 4 5). 
     coll2 := coll1 copyAs:Array.                   '-- will generate a copy'.
     self assert:(coll1 ~~ coll2).
     self assert:(coll1 = coll2).

     coll1 := #(1 2 3 4 5). 
     coll2 := coll1 copyAs:OrderedCollection.       '-- will generate an OC'.
     self assert:(coll1 ~~ coll2).
     self assert:(coll1 isSameSequenceAs: coll2).

     coll1 := #(1 2 3 4 5) asOrderedCollection.
     coll2 := coll1 copyAs:OrderedCollection.       '-- will generate a copy'.
     self assert:(coll1 ~~ coll2).
     self assert:(coll1 = coll2).

o  copyAsOrderedCollection
return a new OrderedCollection with the receiver collection's elements.
This is similar to copy asOrderedCollection, to ensure that we get a new
(unshared) collection, but avoids the copy if the receiver is not already an
OrderedCollection.

o  keysAndValues
return an OrderedCollection with the receiver's associations as key->value pairs
using each element's key as dictionary key and value as dictionary value.

Usage example(s):

     #(10 20 30 40 50 60) keysAndValues

o  literalArrayEncoding
encode myself as an array literal, from which a copy of the receiver
can be reconstructed with #decodeAsLiteralArray.

Usage example(s):

     (Array with:(Color red:50 green:50 blue:50)
            with:(1 @ 2)
     ) literalArrayEncoding decodeAsLiteralArray

o  pairsAsDictionary
return a new Dictionary with the receiver collection's elements,
each of which must be a SequenceableCollection with two elements

Usage example(s):

     #( ('ten' 10) ('twenty' 20) ('thirty' 30)) asSet pairsAsDictionary 
     #( ('ten' 10) ('twenty' 20) ('thirty' 30)) pairsAsDictionary 

o  readStream
return a stream for reading from the receiver

Usage example(s):

     |s|

     s := 'hello world' readStream.
     s next:5.
     s next.
     (s next:5) inspect

o  readStreamOrNil
return a stream for reading from the receiver.
This has been defined for protocol compatibility with FileName,
but nil is never returned here

o  readWriteStream
return a stream for reading and writing from/to the receiver

Usage example(s):

     'hello world' readWriteStream
        nextPutAll:'+Foo';
        contents

     'hello world' readWriteStream
        setToEnd;
        nextPutAll:'+Foo';
        contents

o  readingStreamDo: aBlock
simular to FileStream readingFileDo:,
this evaluates aBlock passing a readStream on the receiver

Usage example(s):

     'hello world' readingStreamDo:[:s |
        Transcript showCR:(s next:5).
     ]                

o  writeStream
return a stream for writing onto the receiver

Usage example(s):

     |s|

     s := #() writeStream.
     s nextPut:1.
     s nextPut:2.
     s nextPut:3.
     s contents inspect

Usage example(s):

     |s|

     s := OrderedCollection new writeStream.
     s nextPut:1.
     s nextPut:2.
     s nextPut:3.
     s contents inspect

o  writeStreamOrNil
return a stream for writing onto the receiver.
This has been defined for protocol compatibility with FileName,
but nil is never returned here

copying
o  copy
return a copy of the receiver.
Redefined to pass the original as argument to the postCopyFrom method.

o  copyEmpty
return a copy of the receiver with no elements.
This is used by copying and enumeration methods
to get a new instance which is similar to the receiver.

o  copyEmpty: size
return a copy of the receiver with no elements, but space for
size elements. This is used by copying and enumeration methods
to get a new instance which is similar to the receiver.
This method should be redefined in subclasses with instance
variables, which should be put into the copy too.
For example, SortedCollection has to copy its sortBlock into the
new collection.

o  copyEmptyAndGrow: size
return a copy of the receiver with size nil elements.
This is used by copying and enumeration methods
to get a new instance which is similar to the receiver.

o  copyWith: additionalElement
Return a copy of the dictionary that is 1 bigger than the receiver and
includes the argument, additionalElement, at the end.

o  copyWithout: elementToSkip
return a new collection consisting of a copy of the receiver,
with ALL elements equal to elementToSkip left out.
No error is reported, if elementToSkip is not in the collection.
This is a slow generic fallback. Many collections redefine this for performance.

Usage example(s):

     #($a $b $c $d $e $f $g $a $b $a $d $a $f $a) asBag copyWithout:$a
     #($a $b $c $d $e $f $g $a $b $a $d $a $f $a) asSet copyWithout:$a

o  copyWithoutAll: elementsToSkip
return a new collection consisting of a copy of the receiver, with
ALL elements equal to any in elementsToSkip are left out.
No error is reported, if any in elementsToSkip is not in the collection.

Usage example(s):

     #($a $b $c $d $e $f $g $a $b $a $d $a $f $a) asBag copyWithoutAll:'abc'

o  postCopyFrom: original
sent to a freshly copied object to give it a chance to adjust things.
Notice, that for Sets/Dicts etc. a rehash is not needed, since the copy
will have the same hash key as the receiver (as long as ST/X provides the
setHash: functionality).

encoding & decoding
o  readJSONContentsFrom: aJSONArrayObject
(comment from inherited method)
redefinable to use direct instvar access

enumerating
o  addAllNonNilElementsTo: aCollection
add all nonNil elements of the receiver to aCollection.
Return aCollection.

Usage example(s):

     #(1 2 3 4 5 1 2 3 4 5 nil) asOrderedCollection addAllNonNilElementsTo:Set new

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

Usage example(s):

     #(1 2 3 4 5 1 2 3 4 5) addAllTo:Set new

o  and: aSecondCollection and: aThirdCollection do: aBlock
evaluate the argument, aBlock for each element in the receiver,
then for each element in aSecondCollection, then for each in aThirdCollection.
Useful if multiple collections need to be enumerated by the same codeBlock,
and you want to avoid constructing a new temp collection for that
(i.e. similar to (coll1,coll2,coll3) do:[...] but without the overhead of
concatenating)

Usage example(s):

     #(1 2 3) 
        and: #(a b c) 
        and: #(x y z) 
        do:[:each | Transcript showCR:each]       

o  and: aSecondCollection do: aBlock
evaluate the argument, aBlock for each element in the receiver,
then for each element in aSecondCollection.
Useful if multiple collections need to be enumerated by the same codeBlock,
and you want to avoid constructing a new temp collection for that
(i.e. similar to (coll1,coll2,coll3) do:[...] but without the overhead of
concatenating)

Usage example(s):

     #(1 2 3) and: #(a b c) do:[:each | Transcript showCR:each]

o  and: finalValue inject: thisValue into: binaryBlock
starting with thisValue for value, pass this value and each element
to binaryBlock, replacing value with the result returned from the block
in the next iteration.
As a last step, inject finalValue.
This last injection is useful to signal end-of-input to the block;
typically, a nil or other marker is injected as finalValue.

See also: #fold: #reduce:

Usage example(s):

     #(1 2 3 4) and:5 inject:0 into:[:accu :element | accu + element]   
     (1 to:10) and:1000 inject:0 into:[:accu :element | accu + element]     
     (1 to:10) and:1000 inject:0 into:#+     

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

Usage example(s):

     #(1 2 3 4) asSet collect:[:n | n * 2]
     #(1 2 3 4) asSet collect:#mul2
     (Cons car:1 cdr:(Cons car:2 cdr:(Cons car:3 cdr:nil))) collect:#mul2  

o  collect: aBlockOrSymbol as: aClass
like collect, but use an instance of aClass to collect the results.
Also avoids the need for an extra intermediate collection which is created with
the standard coding: '(self collect:[...]) asXXXX' or 'self asXXXX collect:[...]

Usage example(s):

     #(one two three four five six) collect:[:element | element asUppercase] as:OrderedCollection
     'abcdef' collect:[:char | char digitValue] as:ByteArray

     'abcdef' collect:#digitValue as:ByteArray
     (0 to:9) collect:[:i | $a+i] as:String
     (0 to:9) collect:[:i | $a+i] as:OrderedCollection
     #(1 2 2 3 4) collect:#mul2 as:Set

o  collect: collectBlock thenDetect: detectBlock ifNone: exceptionalValue
first apply collectBlock to each element, then pass the result to
detectBlock.
Return the first element from collectBlock for which detectBlock evaluates to true.
If none does, return the value of exceptionalValue, which is usually a block.
Returns the same as if two separate collect:+detect:ifNone: messages were sent,
but avoids the creation of intermediate collections, so this is nicer for
big collections.

Usage example(s):

     ( #(1 2 3 4) collect:[:e | e squared] ) detect:[:e| e odd] ifNone:0
     #(1 2 3 4) collect:[:e | e squared] thenDetect:[:e| e odd] ifNone:0
     #(1 2 3 4) collect:#squared thenDetect:#odd ifNone:0

o  collect: collectBlock thenDo: aBlock
combination of collect followed by do.
Avoids the creation of intermediate garbage,
so this is nicer for big collections.

Usage example(s):

     #(1 2 3 4 5 6 7) collect:[:i | i * 2] thenDo:[:i | Transcript showCR:i ]

o  collect: collectBlock thenReject: rejectBlock
combination of collect followed by reject.
May be redefined by some subclasses for optimal performance
(avoiding the creation of intermediate garbage)

Usage example(s):

     #(1 2 3 4 5 6 7) collect:[:i | i * 2] thenReject:[:i | i > 10]

o  collect: collectBlockOrSymbol thenSelect: selectBlockOrSymbol
combination of collect followed by select.
Redefined by some subclasses for optimal performance
(avoiding the creation of intermediate garbage)

Usage example(s):

     #(1 2 3 4 5 6 7) collect:[:i | i * 2] thenSelect:[:i | i < 10]
     #(1 2 3 4 5 6 7) collect:#mul2 thenSelect:#isPerfectSquare

o  collect: collectBlock thenSelect: selectBlock as: aCollectionClass
first apply collectBlock to each element, then pass the result to
selectBlock.
Return a new collection with all elements from the receiver,
for which the selectBlock evaluates to true.
Returns the same as if three separate collect+select+as messages were sent,
but avoids the creation of intermediate collections,
so this is nicer for big collections.

o  collectAll: aBlock
for each element in the receiver, evaluate the argument, aBlock.
The block is supposed to return a collection, whose elements are collected.
The species of the returned collection is that of the first returned
partial result.

Usage example(s):

     #(1 2 3 4) collectAll:[:n | Array new:n withAll:n ]  
     #(1 2 3 4) collectAll:[:n | Array with:n with:n squared ]   
     #(1 2 3 4) collectAll:[:n | 1 to:n ]      
     (Array with:Point with:Rectangle) collectAll:[:c | c instVarNames ]      
     #( (1 1) (2 2) (3 3)) collectAll:#yourself

o  collectAll: aBlock as: collectionClass
for each element in the receiver, evaluate the argument, aBlock.
The block is supposed to return a collection, whose elements are collected.
The returned collection will be an instance of collectionClass

Usage example(s):

     #(1 2 3 4) collectAll:[:n | Array new:n withAll:n ] as:OrderedCollection  
     #(1 2 3 4) collectAll:[:n | Array new:n withAll:n ] as:Bag  
     #(1 2 3 4) collectAll:[:n | Array with:n with:n squared ] as: OrderedCollection  
     #(1 2 3 4) collectAll:[:n | 1 to:n ] as: Set     
     (Array with:Point with:Rectangle) collectAll:[:c | c instVarNames ] as:StringCollection     
     #( (1 1) (2 2) (3 3)) collectAll:#yourself as:Set

o  collectColumn: columnNumberOrKey
for each row-element in the receiver (which ought to be indexable by columnNumberOrKey),
retrieve the indexed element at columnNumberOrKey,
and return a new collection with those column values

Usage example(s):

     #((1 one) (2 two) (3 three) (4 four)) collectColumn:1
     #((1 one) (2 two) (3 three) (4 four)) collectColumn:2
    similar (but more general) to:
     #((1 one) (2 two) (3 three) (4 four)) collect:#first
     #((1 one) (2 two) (3 three) (4 four)) collect:#second

o  collectColumn: columnNumberOrKey ifAbsent: replacementValue
for each row-element in the receiver (which ought to be indexable by columnNumberOrKey),
retrieve the indexed element at columnNumberOrKey,
and return a new collection with those column values

Usage example(s):

     #((1 one) (2 two) (3) (4 four)) collectColumn:2 ifAbsent:'foo'
     #((1 one) (2 two) (3) (4 four)) collectColumn:2 ifAbsent:[:e | e at:1]

o  collectWithIndex: aTwoArgBlock
for each element in the receiver and a running index,
evaluate the argument, aTwoArgBlock.
Return a new collection with the results

Usage example(s):

     #(1 2 3 4) collectWithIndex:[:n :i | n * 2 + i]  
     #(1 2 3 4) collectWithIndex:[:n :i | i -> (n * 2)]  

o  count: aBlockOrSymbol
count elements, for which aBlock returns true.
Return the sum.

Usage example(s):

     #(1 2 3 4 6 8 10) count:[:a | a even]     
     #(1 nil nil nil 2 3 nil 4 5) count:[:a | a isNil]   
     #(1 nil nil nil 2 3 nil 4 5) count:#isNil   

o  detect: aBlockOrSmbol
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, report an error

Usage example(s):

     #(1 2 3 4) detect:[:n | n odd]   
     #(2 4 6 8) detect:[:n | n odd]  

     #(1 2 3 4) detect: #odd     
     #(2 4 6 8) detect: #odd  

o  detect: generatorBlock forWhich: testBlock ifNone: exceptionValue
evaluate generatorBlock for each element in the receiver until
testBlock returns true for it;
in this case return the value from generatorBlock, which caused the true evaluation.
If none of the test evaluations returns true, return the value from exceptionValue

Usage example(s):

     #(2 3 4) detect:[:n | n squared] forWhich:[:nsq | nsq odd] ifNone:['sorry']    
     #( 2 4 ) detect:[:n | n squared] forWhich:[:nsq | nsq odd] ifNone:['sorry']    

     #( 'st' 'c' 'java' ) 
        detect:[:ext | 'Foo' asFilename withSuffix:ext]
        forWhich:[:fn | fn exists]
        ifNone:nil    

o  detect: aOneArgBlockOrSymbol ifNone: exceptionValue
evaluate the argument aOneArgBlock for each element in the receiver until
the block returns true; in this case return the element that caused the
true evaluation.
If none of the evaluations returns true, return the value from exceptionValue

Usage example(s):

     #(1 2 3 4) detect:[:n | n odd] ifNone:['sorry']
     #(2 4 6 8) detect:[:n | n odd] ifNone:['sorry']
     #(1 2 3 4) detect:#odd ifNone:['sorry']
     #(2 4 6 8) detect:#odd ifNone:['sorry']

o  detect: checkBlock thenCompute: evalBlock
evaluate the argument, aBlock for each element in the receiver until
checkBck returns true; in this case return the value from evalBlock
applied to the element which caused the true evaluation.
If none of the evaluations returns true, report an error.
This is useful if the receiver contains objects with multiple aspects,
and you want to find an element by one aspect (typically the name),
but then want to retrieve another aspect of that element.

Usage example(s):

     #((1 'one') (2 'two') (3 'three') (4 'four')) 
        detect:[:pair | pair first odd] thenCompute:[:pair | pair second]

     #((1 'one') (2 'two') (3 'three') (4 'four')) 
        detect:[:pair | pair first odd] thenCompute:#second 

     #( (2 'two') (4 'four')) 
        detect:[:pair | pair first odd] thenCompute:[:pair | pair second] 

     #( 1 2 3 4 5 6 7 8 ) detect:[:el | el > 5] thenCompute:#squared 

o  detect: checkBlock thenCompute: evalBlock ifNone: exceptionValue
evaluate the argument checkBlock for each element in the receiver until
it returns true; in this case return the value from evalBlock applied to
the element that caused the true evaluation.
If none of the evaluations returns true, return the value from exceptionValue.

Usage example(s):

     #((1 'one') (2 'two') (3 'three') (4 'four'))
        detect:[:pair | pair first odd] thenCompute:[:pair | pair second]
        ifNone:[ nil ].

Usage example(s):

     #( (2 'two')  (4 'four'))
        detect:[:pair | pair first odd] thenCompute:[:pair | pair second]
        ifNone:[ nil ].

o  detectLast: 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. The elements are processed in reverse order.
If none of the evaluations returns true, report an error

Usage example(s):

     #(1 2 3 4) detectLast:[:n | n odd]   
     #(1 2 3 4) detectLast:#odd   
     #(2 4 6 8) detectLast:[:n | n odd]  

o  detectLast: aBlock ifNone: exceptionValue
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. The elements are processed in reverse order.
If none of the evaluations returns true, return the value from exceptionValue

Usage example(s):

     #(1 2 3 4) detectLast:[:n | n odd] ifNone:['sorry']    
     #(2 4 6 8) detectLast:[:n | n odd] ifNone:['sorry']     

o  detectMax: aBlockOrSymbol
Evaluate aBlock with each of the receiver's elements as argument.
Answer the element for which aBlock evaluates to the highest magnitude.
If the receiver collection is empty, return nil.
This method might also be called elect:.

Usage example(s):

     #(1 -1 5 -17 10 -8 5) detectMax: #abs

o  detectMin: aBlockOrSymbol
Evaluate aBlock with each of the receiver's elements as argument.
Answer the element for which aBlock evaluates to the lowest number.
If the receiver collection is empty, return nil.

Usage example(s):

     #(1 -1 5 -17 10 -8 5) detectMin: #abs   

o  do: aBlock
evaluate the argument, aBlock for each element.
Return the receiver
(subclasses should care to also return the receiver,
in case do: is used in a chain of messages.)

** This method must be redefined in concrete classes (subclassResponsibility) **

o  do: aBlock inBetweenDo: betweenBlock
evaluate the argument, aBlock for each element.
Between elements (i.e. after each except for the last),
evaluate betweenBlock.
This is a utility helper for collection printers
(for example, to print a space between elements).

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  do: aBlock separatedBy: betweenBlock
evaluate the argument, aBlock for each element.
Between elements (i.e. after each except for the last),
evaluate betweenBlock.
This is a utility helper for collection printers
(for example, to print a space between elements).

Usage example(s):

     #(1 2 3 4) do:[:el | Transcript show:el]
                separatedBy:[ Transcript show:'-']

     (Dictionary with:(1->'one') with:(2->'two'))
         do:[:el | Transcript showCR:el printString]
         separatedBy:[ Transcript showCR:'----']

     (Dictionary with:(1->'one') with:(2->'two'))
        associations
         do:[:el | Transcript showCR:el printString]
         separatedBy:[ Transcript showCR:'----']

o  do: aBlock separatedBy: betweenBlock afterEachCount: afterEachCount do: afterEachBlock
evaluate the argument, aBlock for each element.
Evaluate betweenBlock except after each count iteration and after the last,
Instead, after each count, but not at the end, the afterEachBlock is evaluated.
This is a utility helper for collection printers
(for example, to print a space between elements and a newline after each group).

Usage example(s):

     #(1 2 3 4 5 6 7 8) 
        do:[:el | Transcript show:el]
        separatedBy:[ Transcript show:'-']
        afterEachCount:3
        do:[Transcript cr]

     #(1 2 3 4 5 6 7 8) 
        do:[:el | Transcript show:el]
        separatedBy:[ Transcript show:'-']
        afterEachCount:2
        do:[Transcript cr]

     #(1 2 3 4 5 6 7 8) 
        do:[:el | Transcript show:el]
        separatedBy:[ Transcript show:' ']
        afterEachCount:4
        do:[ Transcript show:' \'. Transcript cr]

     #(1 2 3 4) 
        do:[:el | Transcript show:el]
        separatedBy:[ Transcript show:'-']
        afterEachCount:5
        do:[Transcript cr]

     #() 
        do:[:el | Transcript show:el]
        separatedBy:[ Transcript show:'-']
        afterEachCount:5
        do:[Transcript cr]

     #(1) 
        do:[:el | Transcript show:el]
        separatedBy:[ Transcript show:'-']
        afterEachCount:5
        do:[Transcript cr]

o  do: aBlock untilFalse: untilBlock
evaluate the argument, aBlock for each element
until untilBlock evaluates to false.
Answer the last result from evaluating aBlock,
or nil if none returned true.

o  do: aBlock untilTrue: untilBlock
evaluate the argument, aBlock for each element
until untilBlock evaluates to true.
Answer the last result from evaluating aBlock,
or nil if none returned true.

o  do: aBlock withArgument: arg2ForBlock
call aBlock for each element, passing arg2ForBlock as second argument

Usage example(s):

     #(1 2 3 4 999 5 6 7 8 9) 
        do:[:el :x | Transcript showCR:(el + x) ]
        withArgument:10

o  do: aBlock withArgument: arg2ForBlock andArgument: arg3ForBlock
call aBlock for each element, passing arg2ForBlock and arg3ForBlock as additional arguments

Usage example(s):

     #(1 2 3 4 999 5 6 7 8 9) 
        do:[:el :x :y| Transcript showCR:(el + x + y) ]
        withArgument:10
        andArgument:20

o  do: aBlock without: anItem
enumerate all elements except those equal to anItem into aBlock.
Return the receiver

Usage example(s):

     #(1 2 3 4 999 5 6 7 8 9) 
        do:[:el | Transcript showCR:el ]
        without:5

o  doIfNotNil: aBlock
if I am a collection, then enumerate myself into aBlock.
if I am nil, then do nothing.
Otherwise, evaluate aBlock with myself as argument.
Return the receiver.

o  doWhileFalse: aBlock
evaluate the argument, aBlock for each element,
until it evaluates to true.
Answer false, if all the elements have been processed,
true otherwise.
Notice: to get the element, use #detect:ifNone:
to get its index, use #findFirst:ifNone:

Notice: although the implementation is the same here as anySatisfy:,
do not rewrite this to call the other.
This is to enumerate in the do: order, whereas anySatisfy is allowed
to be redefine by a faster algorithm
(eg. a min-max bounds check without any enumerations).
If at all, redefine anySatisfy, to call me, but not vice versa.

o  doWhileTrue: aBlock
evaluate the argument, aBlock for each element,
until it evaluates to false.
Answer true, if all the elements have been processed,
false otherwise.
Notice: to get the element, use #detect:ifNone:
to get its index, use #findFirst:ifNone:

Notice: although the implementation is the same here as conform:,
do not rewrite this to call the other.
This is to enumerate in the do: order, whereas conform is allowed
to be redefine by a faster algorithm
(eg. a min-max bounds check without any enumerations).
If at all, redefine conform, to call me, but not vice versa.

o  doWithBreak: aTwoArgBlock
evaluate the argument, aBlock for each element.
Passes an additional exit object, which can be used to leave
the loop early, by sending it a #value message.
Returns nil if exited early, the receiver otherwise.

Notice, that this is different to a return statement in the block,
which returns from the enclosed method, NOT only from the block.

o  doWithExit: aTwoArgBlock
evaluate the argument, aBlock for each element.
Passes an additional exit object, which can be used to leave
the loop early, by sending it a #value or #value: message.
Returns nil or the value passed to the exit>>value: message.

Notice, that this is different to a return statement in the block,
which returns from the enclosed method, NOT only from the block.

o  doWithExitAndContinue: aThreeArgBlock
evaluate the argument, aBlock for each element.
Passes an additional exit object, which can be used to leave
the loop early, and an addition continue object, which can be used to
proceed to the next loop iteration.
Both can be sent a #value message, the exit block can also be sent #value:,
to return that value from the loop.
Returns nil or the value passed to the exit>>value: message.
This implements the traditional break+continue functionality of eg. C or Java loops.

Notice, that this is different to a return statement in the block,
which returns from the enclosed method, NOT only from the block.

o  doWithIndex: aTwoArgBlock
Squeak/V'Age compatibility;
like keysAndValuesDo:, but passes the index as second argument.
Same as withIndexDo:, due to parallel evolution of different Smalltalk dialects

o  eachDo: aBlock
evaluate the argument, aBlock for each element in each collection of the receiver.
That is, the receiver must be a collection of collections of which each is to be
enumerated.
Useful if multiple collections need to be enumerated by the same codeBlock

Usage example(s):

     |collections|
     collections := #( 'abc' 'def' '123' '456' ).
     collections eachDo:[:eachChar | Transcript showCR:eachChar]

o  flatDetect: aBlock
for each element of the collection, if it's a scalar, evaluate aBlock for it;
otherwise, recursively invoke flatDetect: on the collection.
Return the first element for which aBlock evaluates to true.
Thus implementing a depth-first search.
Raises an error, if no element is found

Usage example(s):

     #(
        (1 2 3)
        4 5
        (6)
        7
        (8 (9 10) 11 12 (13 (14 (15) 16)))) flatDetect:[:el | el>5]

o  flatDetect: aBlock ifNone: exceptionValue
for each element of the collection, if it's a scalar, evaluate aBlock for it;
otherwise, recursively invoke flatDetect: on the collection.
Return the first element for which aBlock evaluates to true.
Thus implementing a depth-first search.
Return the value from exceptionValue if none found

Usage example(s):

     #(
        (1 2 3)
        4 5
        (6)
        7
        (  8 
          (9 10) 
          11 
          12 
          ( 13
           ( 14 
            (15) 
            16)
           )
          )
      ) flatDetect:[:el | el<0] ifNone:#none       

Usage example(s):

     #(
        (1 2 3)
        4 5
        (6)
        7
        (  8 
          (9 10) 
          11 
          12 
          ( 13
           ( 14 
            (15) 
            16)
           )
          )
      ) flatDetect:[:el | el>15] ifNone:#none       

o  flatDo: aBlock
for each element of the collection, if it's a scalar, evaluate aBlock for it;
otherwise, recursively invoke flatDo: on the collection.
Thus implementing a depth-first enumeration

Usage example(s):

     #(
        (1 2 3)
        4 5
        (6)
        7
        (8 (9 10) 11 12 (13 (14 (15) 16)))
     ) flatDo:[:el | Transcript showCR:el]

o  flatDoWithParent: aTwoArgBlock
for each element of the collection, if it's a scalar, evaluate aBlock for it;
otherwise, recursively invoke flatWithParentDo: on the collection.
The block is called with two arguments, the element itself and its parent (owner),
thus implementing a depth-first enumeration

Usage example(s):

     #(
        (1 2 3)
        4 5
        (6)
        7
        (8 (9 10) 11 12 (13 (14 (15) 16)))
     ) flatDoWithParent:[:el :parent | Transcript showCR:(parent -> el)]

o  fold: binaryBlock
Evaluate the block with the first two elements of the receiver,
then with the result of the first evaluation and the next element,
and so on. Answer the result of the final evaluation. If the receiver
is empty, raise an error. If the receiver has a single element, answer
that element.

Here the reduction is done from left to right.

See also: #inject:into: #reduce:

Usage example(s):

     (1 to:10) fold:[:sum :el| sum + el]
     #(10 -4 3 20 9 -15 -33) fold:[:max :el| max max:el] 
     #(10 -4 3 20 9 -15 -33) maxApplying:[:el| el abs] 
     #(10 -4 3 20 9 -15 -33) maxApplying:#abs 
     (1 to:10) fold:#+
     (1 to:15) fold:[:x :y| '(', x printString, '+', y printString, ')']
     (1 to:15) reduce:[:x :y| '(', x printString, '+', y printString, ')']
     #('if' 'it' 'is' 'to' 'be' 'it' 'is' 'up' 'to' 'me') fold: [:a :b | a, ' ', b]
     #('if' 'it' 'is' 'to' 'be' 'it' 'is' 'up' 'to' 'me') reduce: [:a :b | a, ' ', b]
     #() fold: [:a :b | a, ' ', b] -- raises an error

o  inject: thisValue into: binaryBlock
starting with thisValue for value, pass this value and each element
to binaryBlock, replacing value with the result returned from the block
in the next iteration.

See also: #fold: #reduce:

Usage example(s):

sum up the elements of a collection:

     #(1 2 3 4) inject:0 into:[:accu :element | accu + element]   
     (1 to:10) inject:0 into:[:accu :element | accu + element]     
     (1 to:10) inject:0 into:#+     

     find the minimum:

     |coll|
     coll := #(1 99 -15 20 100).
     coll inject:(coll first) into:[:minSoFar :element | minSoFar min:element]

     |coll|
     coll := #(1 99 -15 20 100).
     coll inject:(coll first) into:#min:

o  injectAndCollect: thisValue into: binaryBlock
starting with thisValue for value, pass this value and each element
to binaryBlock, replacing value with the result returned from the block
in the next iteration.
Collect all results and return them all.

See also: #fold: #reduce:

Usage example(s):

sum up the elements of a collection:

     #(1 2 3 4) inject:0 into:[:accu :element | accu + element]     
     (1 to:10) inject:0 into:[:accu :element | accu + element]      

     same, getting all partial sums:
     (1 to:10)  injectAndCollect:0 into:[:accu :element | accu + element] 

o  keysAndValuesCollect: aTwoArgBlock
for each key-value pair in the receiver, evaluate the argument, aBlock
and return a collection with the results.

See also:
#associationsCollect: (which passes keys->value pairs)
#collect: (which only passes values)

This is much like #associationsCollect:, but aBlock gets the
key and value as two separate arguments.
#associationsCollect: is a bit slower.

WARNING: do not add/remove elements while iterating over the receiver.
Iterate over a copy to do this.

Usage example(s):

     |ages|

     ages := Dictionary new.
     ages at:'cg' put:37.
     ages at:'ca' put:33.
     ages at:'sv' put:36.
     ages at:'tk' put:28.
     ages keysAndValuesCollect:[:name :age | 
                name , '''s age is ' , age printString]

o  keysAndValuesConform: aTwoArgBlock
evaluate the argument, aBlock for every element in the collection,
passing both index and element as arguments.
Return false if any such evaluation returns false, true otherwise.

Usage example(s):

     #(10 20 30 40) keysAndValuesConform:[:key :element | element = (key * 10) ]. 
     #(10 20 30 33 40) keysAndValuesConform:[:key :element | element = (key * 10) ]. 

o  keysAndValuesDetect: aTwoArgBlock ifNone: exceptionalValue
for each key-value pair in the receiver, evaluate the argument, aBlock
and return the value for which aBlock returns true the very first time.
If none of the evaluations returns true, return the result of the
evaluation of the exceptionBlock

Usage example(s):

     |ages|

     ages := Dictionary new.
     ages at:'cg' put:37.
     ages at:'ca' put:33.
     ages at:'sv' put:36.
     ages at:'tk' put:28.
     ages keysAndValuesDetect:[:name :age | age = 33].

o  keysAndValuesDetectKey: aTwoArgBlock ifNone: exceptionalValue
for each key-value pair in the receiver, evaluate the argument, aBlock
and return the key/index for which aBlock returns true the very first time.
If none of the evaluations returns true, return the result of the
evaluation of the exceptionBlock

Usage example(s):

     |ages|

     ages := Dictionary new.
     ages at:'cg' put:37.
     ages at:'ca' put:33.
     ages at:'sv' put:36.
     ages at:'tk' put:28.
     ages keysAndValuesDetectKey:[:name :age | age = 33] ifNone:nil.

o  keysAndValuesDo: aTwoArgBlock
evaluate the argument, aBlock for every element in the collection,
passing both index and element as arguments.
Blocked here - must be redefined in subclasses which have keyed elements

o  keysAndValuesDo: aTwoArgBlock separatedBy: sepBlock
evaluate the argument, aBlock for every element in the collection,
passing both index/key and element as arguments.
Between elements, evaluate aBlock (but not before the first).

Usage example(s):

     |d|
     d := OrderedDictionary withKeysAndValues:#('one' 1 'two' 2 'three' 3 'four' 4).
     
     d keysAndValuesDo:[:k :v | Transcript showCR:'%1 -> %2' with:k with:v]
       separatedBy:[Transcript showCR:'===='].
     
     Transcript cr;cr.
     d keysAndValuesDo:[:k :v | Transcript showCR:'%1 -> %2' with:k with:v].

o  keysAndValuesDoWithExit: aThreeArgBlock
evaluate the argument, aBlock for each key and element.
Passes an additional exit object, which can be used to leave
the loop early, by sending it a #value or #value: message.
Returns nil or the value passed to the exit>>value: message.

Notice, that this is different to a return statement in the block,
which returns from the enclosed method, NOT only from the block.

o  keysAndValuesReverseDo: aTwoArgBlock
evaluate the argument, aBlock in reverse order for every element in the collection,
passing both index and element as arguments.
Blocked here - must be redefined in subclasses which have keyed elements

o  keysAndValuesSelect: selectBlockWith2Args
first call the selectBlockWith2Args, passsing it each key and element,
collect the elements for which the block returns true in an OrderedCollection.

Usage example(s):

     #(10 20 30 40) 
        keysAndValuesSelect:[:idx :val | idx odd] 

o  keysAndValuesSelect: selectBlockWith2Args thenCollect: collectBlockWith2Args
first call the selectBlockWith2Args, passsing it each key and element,
if that returns true, call the collectBlockWith2Args, also with key and element,
and collect the resulting values in an OrderedCollection.

Usage example(s):

     #(10 20 30 40) 
        keysAndValuesSelect:[:idx :val | idx > 2] 
        thenCollect:[:idx :val | idx->val]

o  keysDo: aBlock
evaluate the argument, aBlock for every key in the collection.

o  map: selectorOrBlock
for lisp fans (and also for Javascript) - alias for collect:

Usage example(s):

     #(1 2 3 4) map:[:el | el negated] 
     #(1 2 3 4) map:#negated          

     Time millisecondsToRun:[
       (1 to:10000000) map:#negated 
     ]   

     Time millisecondsToRun:[
       (1 to:10000000) collect:#negated 
     ]  

o  map: selectorOrTwoArgBlock with: arg
for lisp fans - similar to collect:, passing arg to each evaluation as second argument

Usage example(s):

     #(1 2 3 4) map:[:a :b | a + b] with:1   
     #(1 2 3 4) map:#+ with:1  
     #(1 2 3 4) map:#+ with:10  

o  nonNilElementsDo: aBlock
evaluate the argument, aBlock for every non-nil element in the collection.

Usage example(s):

     #(1 nil 3 nil nil 6 7 nil)
        nonNilElementsDo:[:el | Transcript showCR:el]

o  pairsDo: aTwoArgBlock
evaluate the argument, aTwoArgBlock for every element in the collection,
which is supposed to consist of 2-element collections.
The block is called with 2 arguments for each collection in the receiver.
CONFUSION ATTACK:
this is different from pairWiseDo:.
but the Squeak-pairsDo: does the same as our pairWiseDo:
(sigh: but we were first, so they should have adapted...)

Usage example(s):

     #( 
        (1 one) 
        (2 two) 
        (3 three) 
        (4 four) 
        (5 five) 
        (6 six)
      ) pairsDo:
        [:num :sym | 
            Transcript show:num; show:' is: '; showCR:sym]

     #( (1 1)  (1 2)  (1 3)  (1 4)  (1 5)) 
     pairsDo:[:x :y | Transcript showCR:x@y]

o  partition: check as: species into: aTwoArgBlock
enumerate the receiver's elements and partition them into two collections,
depending on the outcome of a check block.
The type of result collection is passed in via the species argument.
Evaluate aTwoArgBlock on the two selected and rejected value collections.
Return the block's value as return value.
The effect is the same as performing a select: and a reject: on the receiver
and evaluating the block on both outcomes.
However, partition only enumerates and performs the check once per element.

Usage example(s):

     #(1 2 3 4 5 6 7 8)
        partition:[:el | el even]
        as:Set    
        into:[:evenElements :oddElements |
            Transcript show:'even: '; showCR:evenElements.
            Transcript show:' odd: '; showCR:oddElements.
            (Set withAll:evenElements) addAll:oddElements; yourself
        ].      
        
     #(1 2 3 4 5 6 7 8)
        partition:#even
        into:[:evenElements :oddElements |
            Transcript show:'even: '; showCR:evenElements.
            Transcript show:' odd: '; showCR:oddElements.
            evenElements , oddElements
        ].    

o  partition: check into: aTwoArgBlock
enumerate the receiver's elements and partition them into two collections,
depending on the outcome of a check block.
Evaluate aTwoArgBlock on the two selected and rejected value collections.
Return the block's value as return value.
The effect is the same as performing a select: and a reject: on the receiver
and evaluating the block on both outcomes.
However, partition only enumerates and performs the check once per element.

Usage example(s):

     #(1 2 3 4 5 6 7 8)
        partition:[:el | el even]
        into:[:evenElements :oddElements |
            Transcript show:'even: '; showCR:evenElements.
            Transcript show:' odd: '; showCR:oddElements.
        ].

o  reduce: binaryBlock
Evaluate the block with the first two elements of the receiver,
then with the result of the first evaluation and the next element,
and so on. Answer the result of the final evaluation. If the receiver
is empty, raise an error. If the receiver has a single element, answer
that element.

Here the reduction is done from right to left.

See also: #inject:into: #fold:

Usage example(s):

     (1 to:15) reduce:[:x :y| '(', x printString, '+', y printString, ')']
     (1 to:15) fold:[:x :y| '(', x printString, '+', y printString, ')']
     #('if' 'it' 'is' 'to' 'be' 'it' 'is' 'up' 'to' 'me') reduce: [:a :b | a, ' ', b]
     #('if' 'it' 'is' 'to' 'be' 'it' 'is' 'up' 'to' 'me') fold: [:a :b | a, ' ', b]
     #(10 1 2 3) reduce:[:el :diff | diff - el] 
     #(10 1 2 3) reduce:[:el :diff | diff + el] 
     #(10 1 2 3) reduce:#+ 
     #(10 1 2 3) reduce:#max: 

o  reduceLeft: aTwoArgBlock
#(1 2 3 4 5) reduceLeft:[:sum :el | sum + el]
#(1 2 3 4 5) reduceLeft:#+

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

Usage example(s):

     #(1 2 3 4) reject:[:e | e odd]   
     (1 to:10) reject:[:e | e even]     

o  reject: aBlock as: aCollectionClass
return a new collection with all elements from the receiver, for which
the argument aBlock evaluates to false.
See also: #removeAllFoundIn: and #removeAllSuchThat:

Usage example(s):

     #(1 2 3 4) select:[:e | e odd] as:OrderedCollection.
     #(1 2 3 4) reject:[:e | e odd] as:OrderedCollection.

o  reject: rejectBlock thenCollect: collectBlock
combination of reject followed by collect.
Redefined by some subclasses for optimal performance
(avoiding the creation of intermediate garbage)

Usage example(s):

     #(1 2 3 4 5 6 7) reject:[:i | i even] thenCollect:[:i | i * 2]

o  reject: selectBlock thenDo: doBlock
combination of reject followed by do
Avoids the creation of intermediate garbage,
so this is nicer for big collections.

Usage example(s):

     #(1 2 3 4 5 6 7) reject:[:i | i even] thenDo:[:i | Transcript showCR:i]

o  reverseDo: aBlock
evaluate the argument, aBlock for each element in reverse order.

** This method must be redefined in concrete classes (subclassResponsibility) **

o  select: aBlock
return a new collection with all elements from the receiver, for which
the argument aBlock evaluates to true.
See also: #removeAllFoundIn: and #removeAllSuchThat:

Usage example(s):

     #(1 2 3 4) select:[:e | e odd]
     (1 to:10) select:[:e | e even]
     (1 to:10) select:#even

o  select: aBlock as: aCollectionClass
return a new collection with all elements from the receiver, for which
the argument aBlock evaluates to true.
See also: #removeAllFoundIn: and #removeAllSuchThat:

Usage example(s):

     #(1 2 3 4) select:[:e | e odd] as:OrderedCollection.
     (1 to:10) select:[:e | e even] as:OrderedCollection.

     #(1 2 3 4) select:[:e | e odd] as:Set.
     (1 to:10) select:[:e | e even] as:Set.

     #(1 2 3 4) select:[:e | e odd] as:ByteArray.
     (1 to:10) select:[:e | e even] as:ByteArray.

o  select: aBlock ifNone: exceptionValue
try a new collection with all elements from the receiver, for which
the argument aBlock evaluates to true. If none of the elements passes
the check of aBlock, return the value from exceptionValue.
See also: #removeAllFoundIn: and #removeAllSuchThat:

Usage example(s):

     #(1 2 3 4) select:[:e | e > 10] ifNone:['sorry']  
     #(1 2 3 4) select:[:e | e > 10] 

o  select: selectBlock thenCollect: collectBlock
combination of select followed by collect.
Redefined by some subclasses for optimal performance
(avoiding the creation of intermediate garbage)

Usage example(s):

^ self select:selectBlock thenCollect:collectBlock as:self species

Usage example(s):

     #(1 2 3 4 5 6 7) select:[:i | i even] thenCollect:[:i | i * 2]

o  select: selectBlock thenCollect: collectBlock as: aCollectionClass
return a new collection with all elements from the receiver,
for which the argument selectBlock evaluates to true.
Process the elements through collectBlock before adding.
Returns the same as if three separate collect+select+as: messages were sent,
but avoids the creation of intermediate collections,
so this is nicer for big collections.

Usage example(s):

     #(1 2 3 4) select:[:e | e odd] thenCollect:[:e| e*e] as:OrderedCollection  
     (1 to:10) select:[:e | e even] thenCollect:[:e| e*e] as:IdentitySet       

o  select: selectBlock thenDo: doBlock
combination of select followed by do.
The same as if two separate select:+do: messages were sent,
but avoids the creation of intermediate collections,
so this is nicer for big collections.

Usage example(s):

     #(1 2 3 4 5 6 7) select:[:i | i even] thenDo:[:i | Transcript showCR:i]

o  select: aTwoArgBlock withArgument: arg
return a new collection with all elements from the receiver,
for which the argument aTwoArgBlock evaluates to true.
aTwoArgBlock is called with value and arg as arguments.
Hacky way to allow for a cheapBlock to be used in select.

Usage example(s):

     #(10 20 30 40) select:[:e :v | e = v] withArgument:30.0      => #(30)
     #(10 30.0 20 30 40) select:[:e :v | e = v] withArgument:30.0 => #(30.0 30)

o  selectWithIndex: aTwoArgBlock
return a new collection with all elements from the receiver,
for which the argument aTwoArgBlock evaluates to true.
aTwoArgBlock is called with value and index as arguments.

Usage example(s):

     #(10 20 30 40) selectWithIndex:[:e :i | i odd]
     #(10 20 30 40) selectWithIndex:[:e :i | i even]

o  triplesDo: aThreeArgBlock
evaluate the argument, aThreeArgBlock for every element in the collection,
which is supposed to consist of 3-element collections.
The block is called with 3 arguments for each collection in the receiver.

Usage example(s):

     #(
        (1 one eins)
        (2 two zwei)
        (3 three drei)
        (4 four vier)
        (5 five #'fuenf')
        (6 six sechs)
     )
     triplesDo:[:num :sym1 :sym2 |
                    Transcript show:num; space; show:sym1; space; showCR:sym2
               ]

o  tuplesCollect: anNArgBlock
evaluate the argument, anNArgBlock for every element in the collection,
which is supposed to consist of N-element collections.
The block is called with N arguments for each collection in the receiver.
The results are collected and returned as a new collection

Usage example(s):

     #(
        (1 one eins uno)
        (2 two zwei due)
        (3 three drei tre)
        (4 four vier quattro)
        (5 five #'fuenf' cinque)
     )
     tuplesCollect:[:num :sym1 :sym2 :sym3 |
        e'The number {num} in 3 languages: {sym1}, {sym2}, {sym3}'
     ]

o  tuplesDo: anNArgBlock
evaluate the argument, anNArgBlock for every element in the collection,
which is supposed to consist of N-element collections.
The block is called with N arguments for each collection in the receiver.

Usage example(s):

     #(
        (1 one eins uno)
        (2 two zwei due)
        (3 three drei tre)
        (4 four vier quattro)
        (5 five #'fuenf' cinque)
     )
     tuplesDo:[:num :sym1 :sym2 :sym3 |
        Transcript show:num; space; show:sym1; space; show:sym2; space; showCR:sym3
     ]

o  validElementsDo: aBlock
for compatibility with weakArray

o  with: aCollection andDefault: defaultElement collect: aTwoArgBlock
like with:collect:, but use defaultElement for missing elements in aCollection
(i.e. if the receiver is longer)
The third argument, aBlock must be a two-argument block, which is
evaluated for each element-pair.
Collect the results and return a collection containing them.
This method fails if neither the receiver nor aCollection is
a sequenceable collection (i.e. implements numeric key access).
Can be used like zip/zipAll in other languages.

Usage example(s):

     (1 to:3) with:#(one two) andDefault:'xxx' collect:[:num :sym | (num->sym)]
     #(1 2 3) with:#(10 20) andDefault:99 collect:[:x :y | (x@y)]

o  with: aSequenceableCollection andDefault: defaultElement do: aTwoArgBlock
evaluate the argument, aBlock for successive elements from
each the receiver and the argument, aSequenceableCollection.
If the receiver has more elements than the argument, use defaultElement
for remaining evaluations.
The third argument, aBlock must be a two-argument block.
This method fails if neither the receiver nor aCollection is
a sequenceable collection (i.e. implements numeric key access)

Usage example(s):

     (1 to:3) with:#(one two) andDefault:99 do:[:num :sym |
        Transcript showCR:(num->sym)
     ]

o  with: aCollection anySatisfy: aTwoArgBlock
evaluate the argument, aBlock for successive elements from
each the receiver and the argument, aCollection.
Return true, if the block returns true for any of these pairs.
This method fails if neither the receiver nor aCollection is
a sequenceable collection (i.e. implements numeric key access).

Usage example(s):

     (1 to:3) with:#(1 2 3 4) anySatisfy:[:a :b | a ~= b]   --- raises an error
     (1 to:3) with:#(1 22 3) anySatisfy:[:a :b | a ~= b]  
     (1 to:3) with:#(1 2 3) anySatisfy:[:a :b | a ~= b]  
     (1 to:3) with:#(1 2 4) anySatisfy:#~=  

o  with: aCollection collect: aTwoArgBlockOrSymbol
evaluate the argument, aBlock for successive elements from
each the receiver and the argument, aSequenceableCollection;
The second argument, aBlock must be a two-argument block, which is
evaluated for each element-pair.
Collect the results and return a collection containing them.
This method fails if neither the receiver nor aCollection is
a sequenceable collection (i.e. implements numeric key access).
Can be used like zip/zipAll in other languages.

Usage example(s):

     (1 to:3) with:#(one two three) collect:[:num :sym | (num->sym)]
     #(1 2 3) with:#(10 20 30) collect:[:x :y | (x@y)]
     #(1 2 3) with:#(10 20 30) collect:#@

o  with: aCollection conform: aTwoArgBlock
evaluate the argument, aBlock for successive elements from
each the receiver and the argument, aCollection.
Return true, if the block returns true for all of these pairs.
This method fails if neither the receiver nor aCollection is
a sequenceable collection (i.e. implements numeric key access).

Usage example(s):

     (1 to:3) with:#(1 2 3 4) conform:[:a :b | a = b]   --- raises an error
     (1 to:3) with:#(1 22 3) conform:[:a :b | a = b]
     (1 to:3) with:#(1 2 3) conform:[:a :b | a = b]
     (1 to:3) with:#(1 2 3) conform:#=
     (1 to:3) with:#(1.0 2.0 3.0) conform:#=
     (1 to:3) with:#(1.0 2.0 3.0) conform:#==
     (1 to:3) with:#('1' '2' '3') conform:[:a :b | a asString = b asString]

o  with: aCollection contains: aTwoArgBlock
marked as obsolete by Stefan Vogel at 7-Nov-2022

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  with: aCollection count: aTwoArgBlock
evaluate the argument, aBlock for successive elements from
each the receiver and the argument, aSequenceableCollection.
Count, how often the second argument, aTwoArgBlock returns true.
This method fails if neither the receiver nor aCollection is
a sequenceable collection (i.e. implements numeric key access).

Usage example(s):

     (1 to:3) with:#(1 3 3) count:[:n1 :n2 | n1 = n2]
     (1 to:3) with:#(1 3 3) count:#=

o  with: aCollection do: aTwoArgBlock
evaluate the argument, aBlock for successive elements from
each the receiver and the argument, aSequenceableCollection.
The second argument, aBlock must be a two-argument block.
This method fails if neither the receiver nor aCollection is
a sequenceable collection (i.e. implements numeric key access)
or (new!) if the sizes are different.

Usage example(s):

     (1 to:3) with:#(one two three) do:[:num :sym |
        Transcript showCR:(num->sym)
     ]

     the following fail because sets do not have ordered elements

     (1 to:3) with:#(one two three) asSet do:[:num :sym |
        Transcript showCR:(num->sym)
     ].
     (1 to:3) asSet with:#(one two three) do:[:num :sym |
        Transcript showCR:(num->sym)
     ]

o  with: aCollection reverseDo: aTwoArgBlock
evaluate the argument, aBlock in reverse order for successive elements from
each the receiver and the argument, aSequenceableCollection.
The second argument, aBlock must be a two-argument block.
This method fails if neither the receiver nor aCollection is
a sequenceable collection (i.e. implements numeric key access)
or (new!) if the sizes are different.

Usage example(s):

     (1 to:3) with:#(one two three) reverseDo:[:num :sym |
        Transcript showCR:(num->sym)
     ]

     the following fail because sets do not have ordered elements

     (1 to:3) with:#(one two three) asSet reverseDo:[:num :sym |
        Transcript showCR:(num->sym)
     ].
     (1 to:3) asSet with:#(one two three) reverseDo:[:num :sym |
        Transcript showCR:(num->sym)
     ]

o  withAllCollections: aCollectionOfCollections do: aManyArgBlock
take successive elements from the receiver and collections in
aCollectionOfCollections and evaluate the argument, aBlock for those.
The block's number arguments must be 1 plus the number of collections given
and all collections there must have the same number of elements (as the receiver).
This method works with any kind of collection, preferrably sequenceable ones.
This method does what the multi-arg map does in Scheme.

o  withIndexCollect: aTwoArgBlock
same as keysAndValuesCollect:, but with argument order reversed

Usage example(s):

     #(one two three) withIndexCollect:[:sym :num | (num->sym)] 
     #(10 20 30) withIndexCollect:[:n :i | n*i ]  

o  withIndexDo: aTwoArgBlock
evaluate the argument, aBlock for every element in the collection,
passing both element and index as arguments.
Same as doWithIndex:, due to parallel evolution of different Smalltalk dialects

enumerating-tests
o  allSatisfy: aBlock
evaluate aBlock for each of the receiver's elements.
Return true, if aBlock returns true for all elements, false otherwise
(i.e. false if any element fails to satisfy the block-condition).
This is an ANSI renomer of #conform:

Usage example(s):

     #(1 2 3 4 5) allSatisfy:[:el | el odd]   
     #(2 4 6 8 10) allSatisfy:[:el | el odd]  
     #(2 4 6 8 10) allSatisfy:[:el | el even]  

o  anySatisfy: aOneArgBlock
evaluate aBlock for each of the receiver's elements.
Return true, if aBlock ever returns true, false otherwise
(i.e. if any element satisfies the block-condition).
This is an ANSI renomer of #contains:
(which is a better name, because #contains: is often misread as #includes by beginners)

Usage example(s):

     #(1 2 3 4 5) anySatisfy:[:el | el odd]   
     #(2 4 6 8 10) anySatisfy:[:el | el odd]  
     #(1 2 3 4 5) anySatisfy:#odd   
     #(2 4 6 8 10) anySatisfy:#odd
     (Cons car:1 cdr:(Cons car:2 cdr:(Cons car:3 cdr:nil))) anySatisfy:[:el | el odd]  

o  conform: aOneArgBlock
return true, if every element conforms to some condition.
I.e. return false, if aBlock returns false for any element;
true otherwise. Returns true for empty receivers.

Usage example(s):

     #(1 2 3 4 5) conform:[:el | el even]     
     #(2 4 6 8 10) conform:[:el | el even]    
     #() conform:[:el | el even]    
     (Cons car:1 cdr:(Cons car:2 cdr:(Cons car:3 cdr:nil))) conform:[:el | el isNumber]  

o  contains: aOneArgBlock
evaluate aOneArgBlock for each of the receiver's elements
Return true and skip remaining elements, if aBlock ever returns true,
otherwise return false.
Use #anySatisfy: it is a better name, because #contains: is often misread as #includes by beginners

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  noneSatisfy: aBlock
evaluate aBlock for each of the receiver's elements.
Return true, if aBlock returns false for all elements, false otherwise
(i.e. false if any element satisfies the block-condition).

Usage example(s):

     #(1 2 3 4 5) noneSatisfy:[:el | el odd]
     #(2 4 6 8 10) noneSatisfy:[:el | el odd]
     #(2 4 6 8 10) noneSatisfy:[:el | el even]

error handling
o  emptyCheck
check if the receiver is empty; report an error if so

o  emptyCollectionError
report an error that the operation is not allowed for empty collections

o  errorInvalidKey: aKey
report an error that the given key was invalid

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

o  errorValueNotFound: anObject
report an error that an object was not found in the collection

o  notEnoughElementsError
report an error that the operation is not allowed,
since not enough elements are in the collection

growing
o  changeCapacityTo: newSize

o  grow
make the receiver larger

o  grow: howBig
change the receiver's size

** This method must be redefined in concrete classes (subclassResponsibility) **

o  growSize
return a suitable size increment for growing.
The default returned here may be (and is) redefined in subclasses.

inspecting
o  inspectorValueListIconFor: anInspector
( an extension from the stx:libtool package )
returns the icon to be shown alongside the value list of an inspector

o  inspectorValueStringInListFor: anInspector
( an extension from the stx:libtool package )
returns a string to be shown in the inspector's list

printing & storing
o  displayElement: element on: aStream
print a representation of element on aStream.
Subclasses may redefine this.

o  displayOn: aGCOrStream
print a representation of the receiver on aGCOrStream for display in inspectors etc.

o  displayStringName
redefinable helper for displayString

o  maxPrint
the print-limit; printOn: will try to not produce more output
than the limit defined here.

o  printElementsDo: aBlock
perform aBlock (1 arg) for all elements.
Used in #printOn:.
Subclasses (e.g. Dictionary) may redefine this.

o  printElementsOn: aStream
append a user readable representation of the receiver to aStream.
The text appended is not meant to be read back for reconstruction of
the receiver. Also, this method limits the size of generated string.

o  printOn: aStream
append a user readable representation of the receiver to aStream.
The text appended is not meant to be read back for reconstruction of
the receiver. Also, this method limits the size of generated string.

Usage example(s):

     #(1 2 3 'hello' $a) printOn:Transcript
     (Array new:100000) printOn:Transcript
     (Array new:100000) printOn:Stdout
     (Array new:100000) printString size
     (Dictionary new at:#hello put:'world';
                     at:#foo put:'bar'; yourself) printOn:Transcript

Usage example(s):

     |a|
     a := Array new:3.
     a at:2 put:a.
     a printOn:Transcript

o  storeNamedInstvarsOn: aStream
each subclass MUST know, which instvars are relevant and storable
(especially think of SortedCollection's sortBlock).
HERE DO NOT STORE INSTVARS, otherwise List and many others generate wrong storeStrings.
If you need them, do it in a subclass.
NOTE: In this case, you have also to define #hasLiteralContents to return false!
(returns false, since no expression was generated; which implies that no #yourself is needed)

o  storeOn: aStream
output a printed representation onto the argument, aStream.
The text can be re-read to reconstruct (a copy of) the receiver.
Recursive (i.e. cyclic) collections cannot be stored correctly
(use storeBinaryOn: to handle those).

queries
o  allElementsHaveTheIdenticalValue
true if all elements of the receiver have the same identical value

Usage example(s):

     #(1 2 3 5 6 7 8 9) allElementsHaveTheIdenticalValue  => false
     #(1 1 1 1 1 1) allElementsHaveTheIdenticalValue      => true
     #(1 1 1.0 1.0 1) allElementsHaveTheIdenticalValue    => false
     #(1 1 1.0 1.0 1) allElementsHaveTheSameValue         => true  

o  allElementsHaveTheSameValue
true if all elements of the receiver have the same equal value.
Computes the same as:
(self asSet) size <= 1
However, stops when the first duplicate value is generated

Usage example(s):

     #(1 2 3 5 6 7 8 9) allElementsHaveTheSameValue   => false
     #(1 1 1 1 1 1) allElementsHaveTheSameValue       => true
     #(1 1 1.0 1.0 1) allElementsHaveTheSameValue     => true

     #(1 1 1 1 1 1) allElementsHaveTheIdenticalValue       => true
     #(1 1 1.0 1.0 1) allElementsHaveTheIdenticalValue     => false

o  defaultElement

o  hasLiteralContents
answer true, if all my elements are literals.
This is faster than using #conform:#isLiteral.

o  identicalValuesComputedBy: aBlock
true if aBlock answers identical values for all elements of the receiver

o  includes: searchedElement
return true, if an element equal to the argument, searchedElement is in the collection.
This compares using #= (i.e. it does not look for the object itself,
instead, one that compares equal).
See #includesIdentical: when identity is asked for.
This is a *very* slow fallback - many subclasses redefine this for performance.

o  includesAll: aCollection
return true if the receiver includes all elements of
the argument, aCollection; false if any is missing.
Notice: depending on the concrete collection,
this method may have O(n²) runtime behavior,
and may be slow for big receivers/args.
Think about using a Set, or Dictionary.

Usage example(s):

     #(1 2 3 4 5 6 7) includesAll:#(1 2 3)
     #('hello' 'there' 'world') includesAll:#('hello' 'world')
     #(1 2 3 4 5 6 7) includesAll:#(7 8 9)

o  includesAllKeys: aCollectionOfKeys
return true if the receiver includes all keys in aCollectionOfKeys,
false if any is missing.

Usage example(s):

     (Dictionary withKeys:#('one' 'two' 'three') andValues:#(1 2 3)) includesAllKeys:#('two' 'three') 
     (Dictionary withKeys:#('one' 'two' 'three') andValues:#(1 2 3)) includesAllKeys:#('two' 'four')  
     (Dictionary withKeys:#('one' 'two' 'three') andValues:#(1 2 3)) includesAllKeys:#(1 2)           
     (Dictionary withKeys:#('one' 'two' 'three') andValues:#(1 2 3)) includesAll:#(1 2)               

     #(1 2 3 4 5 6 7) includesAllKeys:#(1 2 3) 
     #('hello' 'there' 'world') includesAllKeys:#('hello' 'world')    
     #(1 2 3 4 5 6 7) includesAllKeys:#(7 8 9)  

o  includesAny: searchedElementsCollection
return true if the receiver includes any from the argument, aCollection.
Return false if it includes none.
Uses #= (value compare)
Notice:
depending on the concrete collection,
this method may have O(n²) runtime behavior,
and may be slow for big receivers/args.
Think about using a Set, or Dictionary.

Some speedup is also possible, by arranging highly
probable elements towards the beginning of aCollection,
to avoid useless searches.

Also: I am not sure, if (and if so, at which breakeven),
it is better to reverse the loops, and walk over the receiver's
elements once, walking over the searched elements in the inner loop.
If the receiver is large, caching effects will definitely favour this,
as the smaller collection might fit into the cache.

Usage example(s):

     #(1 2 3 4 5 6 7) includesAny:#(1 2 3)
     #('hello' 'there' 'world') includesAny:#('hello' 'world')
     #(1 2 3 4 5 6 7) includesAny:#(7 8 9)
     #(1 2 3 4 5 6 7) includesAny:#(8 9 10)

     |coll|
     coll := (1 to:10000) asOrderedCollection.
     Time millisecondsToRun:[
        1000000 timesRepeat:[ coll includesAny:#(500 600) ]
     ].

     |coll|
     coll := (1 to:10000).
     Time millisecondsToRun:[
        1000000 timesRepeat:[ coll includesAny:#(500 600) ]
     ].

     |coll|
     coll := (1 to:10000) asOrderedCollection.
     Time millisecondsToRun:[
        100000 timesRepeat:[ coll includesAny:#(-1 -10) ]
     ].

     Notice: it is redefined for string search in a subclass:

     |coll|
     coll := String new:10000 withAll:$a.
     coll at:500 put:$b.
     Time millisecondsToRun:[
        100000 timesRepeat:[ coll includesAny:'bc' ]
     ].

     |coll|
     coll := String new:10000 withAll:$a.
     Time millisecondsToRun:[
        100000 timesRepeat:[ coll includesAny:'bc' ]
     ].

o  includesAnyIdentical: searchedElementsCollection
return true, if the receiver includes any from the argument, aCollection.
Return false if it includes none.
Use identity compare for comparing.
Notice:
depending on the concrete collection,
this method may have O(n²) runtime behavior for some subclasses
and may be slow for big receivers/args.
Think about using a Set or Dictionary.
Some speedup is also possible, by arranging highly
probable elements towards the beginning of either collection, to avoid useless searches.

Usage example(s):

     #(1 2 3 4 5 6 7) includesAnyIdentical:#(1 2 3)
     #('hello' 'there' 'world') includesAnyIdentical:#('hello' 'world')
     #(1 2 3 4 5 6 7) includesAnyIdentical:#(7 8 9)
     #(1 2 3 4 5 6 7) includesAnyIdentical:#(8 9 10)

o  includesAnyKey: aCollectionOfKeys
return true if the receiver includes any key from aCollectionOfKeys,
false if none is present.
Notice:
depending on the concrete collection,
this method may have O(n²) runtime behavior for some subclasses
and may be slow for big receivers/args.
Think about using a Set or Dictionary.

o  includesIdentical: searchedElement
return true, if the argument, searchedElement is in the collection.
This compares using #== (i.e. object identity).
See #includes: when equality is asked for.
This is a *very* slow fallback - many subclasses redefine this for performance.

o  includesKey: aKey

** This method must be redefined in concrete classes (subclassResponsibility) **

o  isEmpty
return true, if the receiver is empty

o  isEmptyOrNil
return true if I am nil or an empty collection - true here, if the receiver's size is 0,
(from Squeak)

o  isReadOnly
true if this is a readOnly (immutable) collection.
Q1: should this be called isImmutable?
Q2: who uses this?

o  isValidElement: anObject
return true, if I can hold this kind of object

o  isWritable
true if this is not a readOnly (immutable) collection.
Q1: should this be called isMutable?
Q2: who uses this?

o  newSpeciesForAdding
used when doing #select: operations

o  newSpeciesForCollecting
used when doing collect operations.
Redefinable for collections which do not know their size in advance

o  notEmpty
return true, if the receiver is not empty

o  notEmptyOrNil
Squeak compatibility:
return true if I am neither nil nor an empty collection.

o  occurrencesOf: anElement
return the number of occurrences of the argument, anElement in
the receiver. Uses #= (i.e. equality) compare.

o  occurrencesOfAny: aCollectionOfElements
return the number of occurrences of any in aCollectionOfElements in the receiver.
Uses #= (i.e. equality) compare.
Should be redefined in subclass(es) if ever used heavily.

Usage example(s):

     #(1 4 6 8 4 1) occurrencesOfAny:#(1 4)
     #(1 4 6 8 4 1) occurrencesOfAny:#(2 5)
     'hello world' occurrencesOfAny:'hel'

o  sameValuesComputedBy: aBlock
true if aBlock answers equal values for all elements of the receiver.
Computes the same as:
(self collect:aBlock as:Set) size <= 1
However, stops when the first duplicate value is generated

Usage example(s):

     #(1 2 3 5 6 7 8 9) sameValuesComputedBy:[:el | el even] => false
     #(1 1 1 1 1 1) sameValuesComputedBy:[:el | el even]     => true
     #(1 1 1.0 1.0 1) sameValuesComputedBy:[:el | el even]   => true
     #(1 3 3 15 1) sameValuesComputedBy:[:el | el even]      => true
     #(1 3 3 15 1) sameValuesComputedBy:#even                => true
     #(2 4 4 16 2) sameValuesComputedBy:#even                => true
     #(2 4 3 16 2) sameValuesComputedBy:#even                => false

o  size
return the number of elements in the receiver.
This is usually redefined in subclasses for more performance.

o  speciesForAdding
like species, but redefined for collections which cannot grow easily.
Used by functions which create a growing collection (see collect:with:, for example)

o  speciesForCollecting
like species, but used when doing collect operations.
Redefined for collections which return a different classes object when doing collect.

searching
o  findFirst: aBlock
find the index of the first element,
for which evaluation of the argument, aBlock returns true;
return its index or 0 if none detected.
This is much like #detect, however, here an INDEX is returned,
while #detect returns the element.

Usage example(s):

     #(1 2 3 4 5 6) findFirst:[:x | (x >= 3)]
     #(1 2 3 4 5 6) findFirst:[:x | (x >= 3) and:[x even]]
     #(1 2 3 4 5 6) findFirst:[:x | (x >= 8)]
     'one.two.three' findFirst:[:c | (c == $.)]
     '__one.two.three' findFirst:[:c | (c ~= $_)]
     'one.two.three' findFirst:[:c | (c ~= $_)]

o  findFirst: aBlock ifNone: exceptionValue
find the index of the first element, for which evaluation of the argument, aBlock returns true;
return its index or the value from exceptionValue if none detected.
This is much like #detect:ifNone:, however, here an INDEX is returned,
while #detect:ifNone: returns the element.

** This method must be redefined in concrete classes (subclassResponsibility) **

o  findLast: aBlock
find the last element, for which evaluation of the argument, aBlock returns true.
Return its index or 0 if none detected.

Usage example(s):

     #(1 99 3 99 5 6) findLast:[:x | (x == 99)]
     'one.two.three' findLast:[:c | (c == $.)]

o  findLast: aBlock ifNone: exceptionValue
find the index of the last element, for which evaluation of the argument, aBlock returns true.
Return its index or the value from exceptionValue if none detected.

** This method must be redefined in concrete classes (subclassResponsibility) **

o  keysOfLargest: n
return the keys (aka indices) of the n largest elements, key of largest last.
Raises an exception, if the receiver does not contain at least n elements

Usage example(s):

     #(10 35 20 45 30 5) keysOfLargest:1    
     #(10 35 20 45 30 5) keysOfLargest:2    
     #(10 35 20 45 30 5) largest:2          
     #(10 35 20 45 30 5) keysOfLargest:3   
     #(10 35 20 45 30 5) keysOfLargest:5   
     #(10 35 20 45 30 5) keysOfLargest:6   
     #(10 35 20 45 30 5) keysOfLargest:8
      (1 to: 1000) asArray shuffled keysOfLargest:51

Usage example(s):

     |t1 t2 data|

     data := (1 to:10000) collect:[:i | Random nextInteger ].
     t1 := Time millisecondsToRun:[
        40 timesRepeat:[
            data asSortedCollection at:3 
        ]
     ].
     t2 := Time millisecondsToRun:[
        40 timesRepeat:[
            data keysOfLargest:3
        ].
     ].
     Transcript show:'asSorted-at -> '; show:t1; showCR:'ms'.
     Transcript show:'largest     -> '; show:t2; showCR:'ms'.

o  keysOfSmallest: n
return the keys (aka indices) of the n smallest elements, key of largest last.
Raises an exception, if the receiver does not contain at least n elements

Usage example(s):

     #(10 35 20 45 30 5) keysOfSmallest:1    
     #(10 35 20 45 30 5) keysOfSmallest:2    
     #(10 35 20 45 30 5) smallest:2          
     #(10 35 20 45 30 5) keysOfSmallest:3   
     #(10 35 20 45 30 5) keysOfSmallest:5   
     #(10 35 20 45 30 5) keysOfSmallest:6   
     #(10 35 20 45 30 5) keysOfSmallest:8
      (1 to: 1000) asArray shuffled keysOfSmallest:51 

Usage example(s):

     |t1 t2 data|

     data := (1 to:10000) collect:[:i | Random nextInteger ].
     t1 := Time millisecondsToRun:[
        40 timesRepeat:[
            data asSortedCollection at:3 
        ]
     ].
     t2 := Time millisecondsToRun:[
        40 timesRepeat:[
            data keysOfSmallest:3
        ].
     ].
     Transcript show:'asSorted-at -> '; show:t1; showCR:'ms'.
     Transcript show:'largest     -> '; show:t2; showCR:'ms'.

o  largest: n
return a collection containing the n largest elements, largest last.
Raises an exception, if the receiver does not contain at least n elements

Usage example(s):

     #(10 35 20 45 30 5) largest:1   
     #(10 35 20 45 30 5) largest:2   
     #(10 35 20 45 30 5) largest:3   
     #(10 35 20 45 30 5) largest:5    
     #(10 35 20 45 30 5) largest:6    
     #(10 35 20 45 30 5) largest:8

Usage example(s):

     |t1 t2 data|

     data := (1 to:100000) collect:[:i | Random nextInteger ].
     t1 := Time millisecondsToRun:[
        40 timesRepeat:[
            data asSortedCollection copyLast:2 
        ]
     ].
     t2 := Time millisecondsToRun:[
        40 timesRepeat:[
            data largest:2
        ].
     ].
     Transcript show:'asSorted -> '; show:t1; showCR:'ms'.
     Transcript show:'largest  -> '; show:t2; showCR:'ms'.

o  longestCommonPrefix
return the longest common prefix of my elements.
Typically used with string collections.

Usage example(s):

     #('Array' 'ArrayedCollection' 'ArrayOfFoo') longestCommonPrefix 
     #('Arra' 'ArrayedCollection' 'ArrayOfFoo') longestCommonPrefix 
     #('Arra' 'b' 'c') longestCommonPrefix 
     #( (1 2 3 4) (1 2 3) (1 2 3 7) (1 2 3 9 10 11)) longestCommonPrefix

o  longestCommonPrefixCaseSensitive: caseSensitive
return the longest common prefix of all of my elements (which must be sequenceable collections).
Typically used with string collections,
especially with completion of selectors or filenames.

Usage example(s):

     #('Array' 'arrayedCollection' 'ARRAYOfFoo') longestCommonPrefixCaseSensitive:false 
     #('Array' 'arrayedCollection' 'ARRAYOfFoo') longestCommonPrefixCaseSensitive:true 
     #('Array' 'ArayedCollection' 'ARRAYOfFoo') longestCommonPrefixCaseSensitive:true   
     #('AAA' 'A11' 'AA2') longestCommonPrefixCaseSensitive:true   
     #('AAA' 'BBB' 'CCC') longestCommonPrefixCaseSensitive:true   

o  longestCommonPrefixIgnoreCase: ignoreCase
return the longest common prefix of my elements (which must be sequenceableCollections).
Typically used with string collections,
especially with completion of selectors or filenames.

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  longestCommonSuffix
return the longest common suffix (tail) of my elements.
Typically used with string collections.

Usage example(s):

     #('abcdefg' '1234cdefg' 'aaaaaadefg') longestCommonSuffix    

o  longestCommonSuffixCaseSensitive: caseSensitive
return the longest common suffix (tail) of my elements
(which must be sequenceableCollections).

Usage example(s):

     #('Array' 'ByteArray' 'BigArray') longestCommonSuffixCaseSensitive:false
     #('AAA' 'BBBAA' 'CCCAAAA') longestCommonSuffixCaseSensitive:true
     #('AAA' 'BBB' 'CCC') longestCommonSuffixCaseSensitive:true

o  longestCommonSuffixIgnoreCase: ignoreCase
return the longest common suffix (tail) of my elements
(which must be sequenceableCollections).

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  max
return the maximum value in the receiver collection,
using #< to compare elements.
Raises an error, if the receiver is empty.

Usage example(s):

     #(15 1 -9 10 5) max  
     (1 to:15) max  
     (-1 to:-15 by:-1) max  
     (-1 to:-15 by:-4) max  
     (0 to:15 by:4) max     

o  max: comparator
return the maximum value in the receiver collection,
using comparator to compare elements.
The argument comparator is a 2-arg block returning true if the first arg is less than the second.
Raises an error if the receiver is empty.

Usage example(s):

     find the largest element (same as max without comparator):
         #(15 1 -20 -9 10 5) max:[:a :b | a < b]

     find the element which has the largest abs value:
         #(15 1 -20 -9 10 5) max:[:a :b | a abs < b abs]

     find the (first) longest element
         #('aaa' 'b' 'cc' 'ddd' 'e' 'ffff' 'eeee') max:[:a :b | a size < b size]  

     find the (first) shortest element
         #('aaa' 'b' 'cc' 'ddd' 'e' 'ffff' 'eeee') max:[:a :b | a size > b size]  

o  maxAbs
return the maximum absolute value in the receiver collection.
Raises an error, if the receiver is empty.

Usage example(s):

     #(15 1 -9 10 5) maxAbs  
     #(15 1 -9 -20 10 5) maxAbs  
     (1 to:15) maxAbs  
     (-20 to:15) maxAbs  
     (-1 to:-15 by:-1) maxAbs 15 
     (-1 to:-15 by:-4) maxAbs  
     (0 to:15 by:4) maxAbs     

o  maxApplying: aBlock
return the maximum value from applying aBlock to each element in the receiver collection,
using aBlock to compare elements.
Raises an error, if the receiver is empty.

Usage example(s):

     #() max                                        -> Error
     #(15 1 -9 -20 10 5) max                        -> 15
     #(15 1 -9 -20 10 5) maxApplying:[:el | el abs] -> 20
     #(15 1 -9 -20 10 5) maxApplying:#abs           -> 20

Usage example(s):

     find the length of the longest element
         #('aaa' 'b' 'cc' 'ddd' 'e' 'ffff' 'eeee') maxApplying:#size 4  

     find the length of the shortest element
         #('aaa' 'b' 'cc' 'ddd' 'e' 'ffff' 'eeee') minApplying:#size  

o  min
return the minimum value in the receiver collection,
using < to compare elements.
Raises an error if the receiver is empty.

Usage example(s):

     #(15 1 -9 10 5) min
     (1 to:15) min
     (-1 to:-15 by:-1) min
     (-1 to:-15 by:-4) min

o  min: comparator
return the minimum value in the receiver collection,
using comparator to compare elements.
The argument comparator is a 2-arg block returning true if the first arg is less than the second.
Raises an error if the receiver is empty.

Usage example(s):

     find the smallest element (same as min without comparator):
         #(15 1 -9 10 5) min:[:a :b | a < b]
     
     find the element which has the smallest abs value:
         #(15 1 -9 10 5) min:[:a :b | a abs < b abs]

o  minApplying: aBlock
return the minimum value from applying aBlock to each element in the receiver collection,
using aBlock to compare elements.
Raises an error, if the receiver is empty.

Usage example(s):

     #(15 -1 -9 10 5) min                        -> -9
     #(15 -1 -9 10 5) minApplying:[:el | el abs] -> 1

o  minMax
return the minimum and maximum values in the receiver collection
as a two element array, using #< to compare elements.
Raises an error, if the receiver is empty.

Usage example(s):

     #(15 1 -9 10 5) minMax  
     (1 to:15) minMax  
     (-1 to:-15 by:-1) minMax  
     (-1 to:-15 by:-4) minMax  
     (0 to:15 by:4) minMax     

o  nthLargest: n
return the n-largest element

Usage example(s):

     #(10 35 20 45 30 5) nthLargest:1
     #(10 35 20 45 30 5) nthLargest:2
     #(10 35 20 45 30 5) nthLargest:3
     #(10 35 20 45 30 5) nthLargest:5
     #(10 35 20 45 30 5) nthLargest:6 
     #(10 35 20 45 30 5) nthLargest:8

Usage example(s):

     |t1 t2 data|

     data := (1 to:10000) collect:[:i | Random nextInteger ].
     t1 := Time millisecondsToRun:[
        40 timesRepeat:[
            data asSortedCollection at:6 
        ]
     ].
     t2 := Time millisecondsToRun:[
        40 timesRepeat:[
            data nthLargest:6 
        ].
     ].
     Transcript show:'asSorted-at -> '; show:t1; showCR:'ms'.
     Transcript show:'nthMost     -> '; show:t2; showCR:'ms'.

o  smallest: n
return the n smallest elements

Usage example(s):

     #(10 35 20 45 30 5) smallest:1
     #(10 35 20 45 30 5) smallest:2
     #(10 35 20 45 30 5) smallest:3
     #(10 35 20 45 30 5) smallest:5
     #(10 35 20 45 30 5) smallest:6
      (1 to:10000) asArray shuffled smallest:10
      (1 to:10000) asArray shuffled largest:10
     #(10 35 20 45 30 5) smallest:8

Usage example(s):

     |t1 t2 data|

     data := (1 to:10000) collect:[:i | Random nextInteger ].
     t1 := Time millisecondsToRun:[
        40 timesRepeat:[
            data asSortedCollection at:3
        ]
     ].
     t2 := Time millisecondsToRun:[
        40 timesRepeat:[
            data smallest:3
        ].
     ].
     Transcript show:'asSorted-at -> '; show:t1; showCR:'ms'.
     Transcript show:'smallest     -> '; show:t2; showCR:'ms'.

set operations
o  \ aCollection
return a new set containing all elements of the receiver,
which are NOT also contained in the aCollection
For large collections you better use a Set for aCollection

Usage example(s):

     #(0 1 2 3 4 5 6 7 8 9) \ #(1 2 3) asSet
     #(0 1 2 3 4 5 6 7 8 9) \ #(1 2 3) 
     #(0 1 2 3 4 5 ) \ #(0 1 2 3 4 5 6 7 8 9)  
     #(0 1 2 3 4 5 ) \ #(0 1 3 4 5 6 7 8 9)  
     #(0 1 2 3 4 5 ) \ #( 1 2 3 4 5 6 7 8 9)   
     #(0 1 2 3 4 5 ) \ #( 0 1 2 3 4 6 7 8 9)   
     ('hello' \ 'l')

     (Dictionary withKeysAndValues:#(1 'uno' 2 'due' 3 'tre' 4 'quatro'))
        \ (Dictionary withKeysAndValues:#(1 'uno'  4 'quatro'))

o  intersect: aCollection
return a new set containing all elements of the receiver,
which are also contained in the argument collection.
For large collections you better use a Set for aCollection

Usage example(s):

     #(0 1 2 3 4 5 6 7 8 9) asSet intersect:#(1 2 3 11)
     #(0 1 2 3 4 5 6 7 8 9) intersect:#(1 2 3 11)

     (Dictionary withKeysAndValues:#(1 'uno' 2 'due' 3 'tre' 4 'quatro'))
        intersect:(Dictionary withKeysAndValues:#(1 'uno'  4 'quatro' 5 'cinque'))

o  union: aCollection
return a new set containing all elements of the receiver
plus those of the aCollection

Usage example(s):

     #(0 2 4 6 8) union:#(1 3 5 7)
     #(0 2 4 6 8) union:#(0 1 3 5 7)
     (SortedSet withAll:#(0 2 4 6 8)) union:#(0 1 3 5 7)

     (Dictionary withKeysAndValues:#(1 'uno' 2 'due' 3 'tre' 4 'quatro'))
        union:(Dictionary withKeysAndValues:#(1 'uno'  4 'quatro' 5 'cinque'))

o  xor: aCollection
return a new set containing all elements,
which are contained in either the receiver or aCollection, but not in both.

For large collections you better use Sets for both self and aCollection

Usage example(s):

     #(0 1 2 3 4 5 6 7 8 9) xor:#(1 2 3 11)
     (Dictionary withKeysAndValues:#(1 'uno' 2 'due' 3 'tre' 4 'quatro'))
        xor:(Dictionary withKeysAndValues:#(1 'uno'  4 'quatro' 5 'cinque'))

sorting & reordering
o  sortedBy: aTwoArgBlock
Create a copy that is sorted. Sort criteria is the block that accepts two arguments.
When the block returns true, the first arg goes first ([:a :b | a > b] sorts in descending order).

o  sortedByApplying: aBlockOrSelector
Sort my contents based on the value of what aBlock returns for each element.
Similar to, but even more flexible than sortedBySelector.

o  sortedBySelector: aSelector
return a new collection containing my elements sorted based on the value of what aSelector returns when sent to my
elements. Sorting by a selector is so common, that it's worth a separate utility

Usage example(s):

     |a b|

     a := #(123 25235 12 13423423 234234).
     b := a sortedBySelector:#abs

o  topologicalSort
Sort a partial ordered collection.
The receiver consists of tupels defining a partial order.
Use the algorithm by R. E. Tarjan from 1972.
Answer an OrderedCollection containing the sorted items

o  topologicalSortStable: sortStable
Sort a partial ordered collection.
The receiver consists of tupels defining a partial order.
Use the algorithm by R. E. Tarjan from 1972.
Answer an OrderedCollection containing the sorted items.

If sortStable is true, try to make order stable among
multiple invocations. If false, stability is not guaranteed.

statistical functions
o  arithmeticMean
arithmetic mean value of all elements in the collection

Usage example(s):

     TestCase assert:( { 1. 2. 3. 4 } arithmeticMean = 2.5).
     TestCase assert:( { 13. 23. 12. 44. 55 } arithmeticMean closeTo: 29.4).
     TestCase assert:( { 13. 23. 12. 44. 55 } standardDeviation closeTo: 19.2431).

o  average
average value of all elements in the collection

Usage example(s):

     TestCase assert:( { 1. 2. 3. 4 } average = 2.5).

o  geometricMean
geometric mean value of all elements in the collection

Usage example(s):

     TestCase assert:( { 1. 2. 3. 4. } geometricMean closeTo: 2.21336).
     TestCase assert:( { 1. 2. 3. 4. 5 } geometricMean closeTo: 2.60517).
     TestCase assert:( { 13. 23. 12. 44. 55 } geometricMean closeTo: 24.41932).

o  harmonicMean
harmonic mean value of all elements in the collection

Usage example(s):

     TestCase assert:( { 5. 20. } harmonicMean = 8)

o  median
Return the middle element, or as close as we can get.

Usage example(s):

     #(10 35 20 45 30 5) median

o  standardDeviation
standard deviation value of all elements in the collection,
which is the complete set and not a sample.

Usage example(s):

     TestCase assert:( #( 1 2 3 4) arithmeticMean = 2.5).
     TestCase assert:( #(13 23 12 44 55) arithmeticMean closeTo: 29.4).
     TestCase assert:( #(13 23 12 44 55) standardDeviation closeTo: 17.2116).
     TestCase assert:( (1 to: 100) arithmeticMean = ((100 + 1)/2)).
     TestCase assert:( (1 to: 100) standardDeviation = ((100 squared - 1)/12) sqrt).
     TestCase assert:( (1 to: 6) standardDeviation = ((6 squared - 1)/12) sqrt).

o  variance
compute the variance over a complete data set (and not of a sample)

Usage example(s):

        #(1 1 1 1 1 1 1 1 1 1) arithmeticMean      => 1
        #(1 1 1 1 1 1 1 1 1 1) variance            => 0
        #(1 1 1 1 1 1 1 1 1 1) standardDeviation   => 0.0
        
        #(1 1 1 1 1 2 2 2 2 2) arithmeticMean      => (3/2)
        #(1 1 1 1 1 2 2 2 2 2) variance            => (1/4)
        #(1 1 1 1 1 2 2 2 2 2) standardDeviation   => 0.5

        #(1 2 3 4 5 6 7 8 9 0) arithmeticMean      => (9/2)
        #(1 2 3 4 5 6 7 8 9 0) variance            => (33/4)
        #(1 2 3 4 5 6 7 8 9 0) standardDeviation   => 2.87228132326901

testing
o  capacity
return the number of elements, that the receiver is prepared to take.
For most collections, this is the actual size.
However, some have more space preallocated to allow
for faster adding of elements (i.e. there are logical vs. physical sizes).

o  isCollection
return true, if the receiver is some kind of collection;
true is returned here - the method is redefined from Object.

o  isNonByteCollection
return true, if the receiver is some kind of collection, but not a String, ByteArray etc.;
true is returned here - the method is redefined from Object.

o  isOrdered
return true, if the receiver's elements are ordered.
This defaults to true here, and is to be redefined by collections which use
hashing, and the order of keys and values is therefore not guaranteed to remain
the same, as objects are added.
Notice, that this query might be useless/false for some collections;
for example, a file directory may change its order even though smalltalk does not touch it;
or a collection which is based on computed block values may return completely differently
ordered elements (also random value collections, etc.).
Therefore, use this only as a hint
(e.g. when showing values, to avoid sorting and destroying
any previous order in the visual representation)

o  isSorted
return true, if the receiver is sorted.
Collections which hold their elements in sorted order
should return true. Some algorithms (quicksort) degenerate when
operating on sorted collections and can be avoided if this information
is given. The default returned here (false) should not hurt.
I.e. you should NEVER depend on that in your application.

o  isSortedBy: aBlock
return true, if my elements are sorted (already) by the given criterion (sortBlock).
Collections which hold their elements in sorted order
should return true. Some algorithms (quicksort) degenerate when
operating on sorted collections and can be avoided if this information
is given. The default returned here (false) should not hurt.
I.e. you should NEVER depend on that in your application.

o  isSortedCollection
return true, if the receiver is a sortedCollection.

tracing
o  traceInto: aRequestor level: level from: referrer
double dispatch into tracer, passing my type implicitely in the selector

visiting
o  acceptVisitor: aVisitor with: aParameter
dispatch for visitor pattern; send #visitCollection:with: to aVisitor

xml conversion
o  asXMLElementNamed: aName
( an extension from the stx:goodies/xml/stx package )



ST/X 7.7.0.0; WebServer 1.702 at 20f6060372b9.unknown:8081; Sat, 27 Jul 2024 07:24:34 GMT