A view of a Cartesian-product collection over homogeneous collections.

Therefore, this view generates all the sequences of elements constructed by associating en element for each one of the original collections.

It is equivalent to doing nesting for for each collection.

var xs = [1, 2, 3]
var ys = [8, 9]
var xys = new CartesianCollection[Int]([xs, ys])
assert xys.length == 6
assert xys.to_a == [[1,8], [1,9], [2,8], [2,9], [3,8], [3,9]]

The pattern of the generate sequences produces a lexicographical order.

Because it is a generator, it is memory-efficient and the sequences are created only when needed.

Note: because it is a view, changes on the base collections are reflected on the view.

assert xs.pop == 3
assert ys.pop == 9
assert xys.to_a == [[1,8], [2,8]]

Introduced properties

fun collections: SequenceRead[Collection[E]]

combinations :: CartesianCollection :: collections

The base collections used to generate the sequences.
protected fun collections=(collections: SequenceRead[Collection[E]])

combinations :: CartesianCollection :: collections=

The base collections used to generate the sequences.

Redefined properties

redef type SELF: CartesianCollection[E]

combinations $ CartesianCollection :: SELF

Type of this instance, automatically specialized in every class
redef fun iterator: Iterator[SequenceRead[E]]

combinations $ CartesianCollection :: iterator

Get a new iterator on the collection.
redef fun length: Int

combinations $ CartesianCollection :: length

Number of items in the collection.

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
fun ==(other: nullable Object): Bool

core :: Object :: ==

Have self and other the same value?
type CLASS: Class[SELF]

core :: Object :: CLASS

The type of the class of self.
type CONCURRENT: ConcurrentCollection[E]

core :: Collection :: CONCURRENT

Type of the concurrent variant of this collection
type SELF: Object

core :: Object :: SELF

Type of this instance, automatically specialized in every class
protected fun class_factory(name: String): CLASS

core :: Object :: class_factory

Implementation used by get_class to create the specific class.
fun class_name: String

core :: Object :: class_name

The class name of the object.
fun collections: SequenceRead[Collection[E]]

combinations :: CartesianCollection :: collections

The base collections used to generate the sequences.
protected fun collections=(collections: SequenceRead[Collection[E]])

combinations :: CartesianCollection :: collections=

The base collections used to generate the sequences.
fun combinations(r: Int): Collection[SequenceRead[E]]

core :: Collection :: combinations

All r-length combinations on self (in same order) without repeated elements.
fun combinations_with_replacement(r: Int): Collection[SequenceRead[E]]

core :: Collection :: combinations_with_replacement

All r-length combination on self (in same order) with repeated elements.
fun count(item: nullable Object): Int

core :: Collection :: count

How many occurrences of item are in the collection?
fun first: E

core :: Collection :: first

Return the first item of the collection
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun has(item: nullable Object): Bool

core :: Collection :: has

Is item in the collection ?
fun has_all(other: Collection[nullable Object]): Bool

core :: Collection :: has_all

Does the collection contain at least each element of other?
fun has_any(other: Collection[nullable Object]): Bool

core :: Collection :: has_any

Does the collection contain at least one element of other?
fun has_exactly(other: Collection[nullable Object]): Bool

core :: Collection :: has_exactly

Does the collection contain exactly all the elements of other?
fun has_only(item: nullable Object): Bool

core :: Collection :: has_only

Is the collection contain only item?
fun hash: Int

core :: Object :: hash

The hash code of the object.
init init

core :: Object :: init

fun inspect: String

core :: Object :: inspect

Developer readable representation of self.
protected fun inspect_head: String

core :: Object :: inspect_head

Return "CLASSNAME:#OBJECTID".
fun is_empty: Bool

core :: Collection :: is_empty

Is there no item in the collection?
intern fun is_same_instance(other: nullable Object): Bool

core :: Object :: is_same_instance

Return true if self and other are the same instance (i.e. same identity).
fun is_same_serialized(other: nullable Object): Bool

core :: Object :: is_same_serialized

Is self the same as other in a serialization context?
intern fun is_same_type(other: Object): Bool

core :: Object :: is_same_type

Return true if self and other have the same dynamic type.
abstract fun iterator: Iterator[E]

core :: Collection :: iterator

Get a new iterator on the collection.
fun join(separator: nullable Text, last_separator: nullable Text): String

core :: Collection :: join

Concatenate and separate each elements with separator.
fun length: Int

core :: Collection :: length

Number of items in the collection.
fun not_empty: Bool

core :: Collection :: not_empty

Alias for not is_empty.
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
fun output

core :: Object :: output

Display self on stdout (debug only).
intern fun output_class_name

core :: Object :: output_class_name

Display class name on stdout (debug only).
fun permutations(r: Int): Collection[SequenceRead[E]]

core :: Collection :: permutations

All r-length permutations on self (all possible ordering) without repeated elements.
fun plain_to_s: String

core :: Collection :: plain_to_s

Concatenate elements without separators
fun product(r: Int): Collection[SequenceRead[E]]

core :: Collection :: product

Cartesian product, over r times self.
fun rand: E

core :: Collection :: rand

Return a random element form the collection
fun sample(length: Int): Array[E]

core :: Collection :: sample

Return a new array made of (at most) length elements randomly chosen.
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
fun to_a: Array[E]

core :: Collection :: to_a

Build a new array from a collection
abstract fun to_concurrent: CONCURRENT

core :: Collection :: to_concurrent

Wraps self in a thread-safe collection
fun to_counter: Counter[E]

core :: Collection :: to_counter

Create and fill up a counter with the elements of `self.
fun to_curlslist: CURLSList

core :: Collection :: to_curlslist

Convert Collection[String] to CURLSList
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

fun to_s: String

core :: Object :: to_s

User readable representation of self.
fun to_shuffle: Array[E]

core :: Collection :: to_shuffle

Return a new array made of elements in a random order.
package_diagram combinations::CartesianCollection CartesianCollection core::Collection Collection combinations::CartesianCollection->core::Collection core::Object Object core::Collection->core::Object ...core::Object ... ...core::Object->core::Object

Ancestors

interface Object

core :: Object

The root of the class hierarchy.

Parents

interface Collection[E: nullable Object]

core :: Collection

The root of the collection hierarchy.

Class definitions

combinations $ CartesianCollection
# A view of a Cartesian-product collection over homogeneous collections.
#
# Therefore, this view *generates* all the sequences of elements constructed by associating
# en element for each one of the original collections.
#
# It is equivalent to doing nesting `for` for each collection.
#
# ~~~~
# var xs = [1, 2, 3]
# var ys = [8, 9]
# var xys = new CartesianCollection[Int]([xs, ys])
# assert xys.length == 6
# assert xys.to_a == [[1,8], [1,9], [2,8], [2,9], [3,8], [3,9]]
# ~~~~
#
# The pattern of the generate sequences produces a lexicographical order.
#
# Because it is a generator, it is memory-efficient and the sequences are created only when needed.
#
# Note: because it is a view, changes on the base collections are reflected on the view.
#
# ~~~~
# assert xs.pop == 3
# assert ys.pop == 9
# assert xys.to_a == [[1,8], [2,8]]
# ~~~~
class CartesianCollection[E]
	super Collection[SequenceRead[E]]

	# The base collections used to generate the sequences.
	var collections: SequenceRead[Collection[E]]

	redef fun length
	do
		var res = 1
		for c in collections do res = res * c.length
		return res
	end

	redef fun iterator do return new CartesianIterator[E](self)
end
lib/combinations/combinations.nit:76,1--116,3