Sequences are indexed collections.

The first item is 0. The last is length-1.

The order is the main caracteristic of sequence and all concrete implementation of sequences are basically interchangeable.

Introduced properties

abstract fun [](index: Int): E

core :: SequenceRead :: []

Return the index-th element of the sequence.
fun get_or_default(index: Int, default: E): E

core :: SequenceRead :: get_or_default

Try to get an element, return default if the index is invalid.
fun get_or_null(index: Int): nullable E

core :: SequenceRead :: get_or_null

Try to get an element, return null if the index is invalid.
fun index_of(item: nullable Object): Int

core :: SequenceRead :: index_of

The index of the first occurrence of item.
fun index_of_from(item: nullable Object, pos: Int): Int

core :: SequenceRead :: index_of_from

The index of the first occurrence of item, starting from pos.
fun iterator_from(pos: Int): IndexedIterator[E]

core :: SequenceRead :: iterator_from

Gets a new Iterator starting at position pos
fun last: E

core :: SequenceRead :: last

Get the last item.
fun last_index_of(item: nullable Object): Int

core :: SequenceRead :: last_index_of

The index of the last occurrence of item.
fun last_index_of_from(item: nullable Object, pos: Int): Int

core :: SequenceRead :: last_index_of_from

The index of the last occurrence of item starting from pos and decrementing.
fun modulo(index: Int): E

core :: SequenceRead :: modulo

Return the index-th element but wrap
fun modulo_index(index: Int): Int

core :: SequenceRead :: modulo_index

Returns the real index for a modulo index.
abstract fun reverse_iterator: IndexedIterator[E]

core :: SequenceRead :: reverse_iterator

Gets an iterator starting at the end and going backwards
fun reverse_iterator_from(pos: Int): IndexedIterator[E]

core :: SequenceRead :: reverse_iterator_from

Gets an iterator on the chars of self starting from pos

Redefined properties

redef fun ==(o: nullable Object): Bool

core $ SequenceRead :: ==

Two sequences are equals if they have the same items in the same order.
redef type CONCURRENT: ConcurrentSequenceRead[E]

pthreads :: concurrent_collections $ SequenceRead :: CONCURRENT

Type of the concurrent variant of this collection
redef type SELF: SequenceRead[E]

core $ SequenceRead :: SELF

Type of this instance, automatically specialized in every class
redef fun first: E

core $ SequenceRead :: first

Get the first item.
redef fun hash: Int

core $ SequenceRead :: hash

Because of the law between == and hash, hash is redefined to be the sum of the hash of the elements
redef abstract fun iterator: IndexedIterator[E]

core $ SequenceRead :: iterator

Get a new iterator on the collection.
redef fun rand: E

core :: math $ SequenceRead :: rand

Optimized for large collections using []

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
abstract fun [](index: Int): E

core :: SequenceRead :: []

Return the index-th element of the sequence.
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 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 get_or_default(index: Int, default: E): E

core :: SequenceRead :: get_or_default

Try to get an element, return default if the index is invalid.
fun get_or_null(index: Int): nullable E

core :: SequenceRead :: get_or_null

Try to get an element, return null if the index is invalid.
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.
fun index_of(item: nullable Object): Int

core :: SequenceRead :: index_of

The index of the first occurrence of item.
fun index_of_from(item: nullable Object, pos: Int): Int

core :: SequenceRead :: index_of_from

The index of the first occurrence of item, starting from pos.
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 iterator_from(pos: Int): IndexedIterator[E]

core :: SequenceRead :: iterator_from

Gets a new Iterator starting at position pos
fun join(separator: nullable Text, last_separator: nullable Text): String

core :: Collection :: join

Concatenate and separate each elements with separator.
fun last: E

core :: SequenceRead :: last

Get the last item.
fun last_index_of(item: nullable Object): Int

core :: SequenceRead :: last_index_of

The index of the last occurrence of item.
fun last_index_of_from(item: nullable Object, pos: Int): Int

core :: SequenceRead :: last_index_of_from

The index of the last occurrence of item starting from pos and decrementing.
fun length: Int

core :: Collection :: length

Number of items in the collection.
fun modulo(index: Int): E

core :: SequenceRead :: modulo

Return the index-th element but wrap
fun modulo_index(index: Int): Int

core :: SequenceRead :: modulo_index

Returns the real index for a modulo index.
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
abstract fun reverse_iterator: IndexedIterator[E]

core :: SequenceRead :: reverse_iterator

Gets an iterator starting at the end and going backwards
fun reverse_iterator_from(pos: Int): IndexedIterator[E]

core :: SequenceRead :: reverse_iterator_from

Gets an iterator on the chars of self starting from pos
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 core::SequenceRead SequenceRead core::Collection Collection core::SequenceRead->core::Collection core::Object Object core::Collection->core::Object ...core::Object ... ...core::Object->core::Object core::AbstractArrayRead AbstractArrayRead core::AbstractArrayRead->core::SequenceRead core::Sequence Sequence core::Sequence->core::SequenceRead pthreads::ConcurrentSequenceRead ConcurrentSequenceRead pthreads::ConcurrentSequenceRead->core::SequenceRead java::AbstractJavaArray AbstractJavaArray java::AbstractJavaArray->core::SequenceRead json::JsonSequenceRead JsonSequenceRead json::JsonSequenceRead->core::SequenceRead core::AbstractArray AbstractArray core::AbstractArray->core::AbstractArrayRead core::AbstractArray->core::Sequence c::CArray CArray c::CArray->core::AbstractArrayRead core::AbstractArray... ... core::AbstractArray...->core::AbstractArray c::CArray... ... c::CArray...->c::CArray core::List List core::List->core::Sequence core::CircularArray CircularArray core::CircularArray->core::Sequence pthreads::ConcurrentSequence ConcurrentSequence pthreads::ConcurrentSequence->core::Sequence pthreads::ConcurrentSequence->pthreads::ConcurrentSequenceRead more_collections::UnrolledList UnrolledList more_collections::UnrolledList->core::Sequence core::List... ... core::List...->core::List core::CircularArray... ... core::CircularArray...->core::CircularArray pthreads::ConcurrentSequence... ... pthreads::ConcurrentSequence...->pthreads::ConcurrentSequence more_collections::UnrolledList... ... more_collections::UnrolledList...->more_collections::UnrolledList java::JavaIntArray JavaIntArray java::JavaIntArray->java::AbstractJavaArray java::JavaShortArray JavaShortArray java::JavaShortArray->java::AbstractJavaArray java::JavaLongArray JavaLongArray java::JavaLongArray->java::AbstractJavaArray java::JavaFloatArray JavaFloatArray java::JavaFloatArray->java::AbstractJavaArray java::JavaDoubleArray JavaDoubleArray java::JavaDoubleArray->java::AbstractJavaArray java::JavaArray JavaArray java::JavaArray->java::AbstractJavaArray java::JavaBoolArray JavaBoolArray java::JavaBoolArray->java::AbstractJavaArray java::JavaByteArray JavaByteArray java::JavaByteArray->java::AbstractJavaArray java::JavaCharArray JavaCharArray java::JavaCharArray->java::AbstractJavaArray java::JavaIntArray... ... java::JavaIntArray...->java::JavaIntArray java::JavaShortArray... ... java::JavaShortArray...->java::JavaShortArray java::JavaLongArray... ... java::JavaLongArray...->java::JavaLongArray java::JavaFloatArray... ... java::JavaFloatArray...->java::JavaFloatArray java::JavaDoubleArray... ... java::JavaDoubleArray...->java::JavaDoubleArray java::JavaArray... ... java::JavaArray...->java::JavaArray java::JavaBoolArray... ... java::JavaBoolArray...->java::JavaBoolArray java::JavaByteArray... ... java::JavaByteArray...->java::JavaByteArray java::JavaCharArray... ... java::JavaCharArray...->java::JavaCharArray json::JsonArray JsonArray json::JsonArray->json::JsonSequenceRead json::JsonArray... ... json::JsonArray...->json::JsonArray

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.

Children

abstract class AbstractArrayRead[E: nullable Object]

core :: AbstractArrayRead

One dimension array of objects.
extern class AbstractJavaArray[E: Object]

java :: AbstractJavaArray

Java primitive array
abstract class ConcurrentSequenceRead[E: nullable Object]

pthreads :: ConcurrentSequenceRead

A concurrent variant to the standard SequenceRead
class JsonSequenceRead[E: nullable Serializable]

json :: JsonSequenceRead

A sequence that can be translated into a JSON array.
interface Sequence[E: nullable Object]

core :: Sequence

Sequence are indexed collection.

Descendants

abstract class AbstractArray[E: nullable Object]

core :: AbstractArray

Resizable one dimension array of objects.
class Array[E: nullable Object]

core :: Array

Resizable one dimension array of objects.
class ArrayCmp[E: nullable Comparable]

core :: ArrayCmp

Comparable array for comparable elements.
class BlockingQueue[E: nullable Object]

pthreads :: BlockingQueue

A Blocking queue implemented from a ConcurrentList
class BoxedArray[E: Boxed[Numeric]]

geometry :: BoxedArray

BoxedCollection implemented by an array
class Bytes

core :: Bytes

A buffer containing Byte-manipulation facilities
abstract class CArray[E: nullable Object]

c :: CArray

A thin wrapper around a NativeCArray adding length information
class CByteArray

c :: CByteArray

Wrapper around an array of unsigned char in C (unsigned char*) with length and destroy state
class CCStringArray

c :: CCStringArray

Wrapper around an array of CString in C (char**) with length and destroy state.
class CIntArray

c :: CIntArray

Wrapper around an array of int in C (int*) with length and destroy state
class CUInt16Array

c :: CUInt16Array

Wrapper of a C array of type uint16_t* with length and destroy state
class CircularArray[E: nullable Object]

core :: CircularArray

Efficient data structure to access both end of the sequence.
class ConcurrentArray[E: nullable Object]

pthreads :: ConcurrentArray

A concurrent variant to the standard Array
class ConcurrentList[E: nullable Object]

pthreads :: ConcurrentList

A concurrent variant to the standard List
abstract class ConcurrentSequence[E: nullable Object]

pthreads :: ConcurrentSequence

A concurrent variant to the standard Sequence
class Interfaces

nitcorn :: Interfaces

A list of interfaces with dynamic port listeners
extern class JavaArray

java :: JavaArray

Java primitive array Object[]
extern class JavaBoolArray

java :: JavaBoolArray

Java primitive array boolean[]
extern class JavaByteArray

java :: JavaByteArray

Java primitive array byte[]
extern class JavaCharArray

java :: JavaCharArray

Java primitive array char[]
extern class JavaDoubleArray

java :: JavaDoubleArray

Java primitive array double[]
extern class JavaFloatArray

java :: JavaFloatArray

Java primitive array float[]
extern class JavaIntArray

java :: JavaIntArray

Java primitive array int[]
extern class JavaLongArray

java :: JavaLongArray

Java primitive array long[]
extern class JavaShortArray

java :: JavaShortArray

Java primitive array short[]
class JsonArray

json :: JsonArray

A JSON array.
class List[E: nullable Object]

core :: List

Double linked lists.
class LiveGroup[E: LiveObject]

scene2d :: LiveGroup

Organizational class to manage groups of sprites and other live objects.
class Mailbox[E: nullable Object]

actors :: Mailbox

A Blocking queue implemented from a ConcurrentList
class MongoPipeline

mongodb :: MongoPipeline

Mongo pipelines are arrays of aggregation stages
class ReverseBlockingQueue[E: nullable Object]

pthreads :: ReverseBlockingQueue

A collection which is_empty method blocks until it's empty
class UnrolledList[E: nullable Object]

more_collections :: UnrolledList

An unrolled linked list
class VirtualHosts

nitcorn :: VirtualHosts

A list of virtual hosts with dynamic port listeners

Class definitions

core $ SequenceRead
# Sequences are indexed collections.
# The first item is 0. The last is `length-1`.
#
# The order is the main caracteristic of sequence
# and all concrete implementation of sequences are basically interchangeable.
interface SequenceRead[E]
	super Collection[E]

	# Get the first item.
	# Is equivalent with `self[0]`.
	#
	#     var a = [1,2,3]
	#     assert a.first   == 1
	#
	# REQUIRE `not is_empty`
	redef fun first
	do
		assert not_empty: not is_empty
		return self[0]
	end

	# Return the index-th element of the sequence.
	# The first element is 0 and the last is `length-1`
	# If index is invalid, the program aborts
	#
	#     var a = [10,20,30]
	#     assert a[0]   == 10
	#     assert a[1]   == 20
	#     assert a[2]   == 30
	#
	# REQUIRE `index >= 0 and index < length`
	fun [](index: Int): E is abstract

	# Return the index-th element but wrap
	#
	# Whereas `self[]` requires the index to exists, the `modulo` accessor automatically
	# wraps overbound and underbouds indexes.
	#
	# ~~~
	# var a = [10,20,30]
	# assert a.modulo(1) == 20
	# assert a.modulo(3) == 10
	# assert a.modulo(-1) == 30
	# assert a.modulo(-10) == 30
	# ~~~
	#
	# REQUIRE `not_empty`
	# ENSURE `result == self[modulo_index(index)]`
	fun modulo(index: Int): E do return self[modulo_index(index)]

	# Returns the real index for a modulo index.
	#
	# ~~~
	# var a = [10,20,30]
	# assert a.modulo_index(1) == 1
	# assert a.modulo_index(3) == 0
	# assert a.modulo_index(-1) == 2
	# assert a.modulo_index(-10) == 2
	# ~~~
	#
	# REQUIRE `not_empty`
	fun modulo_index(index: Int): Int
	do
		var length = self.length
		if index >= 0 then
			return index % length
		else
			return length - (-1 - index) % length - 1
		end
	end

	# Try to get an element, return `null` if the `index` is invalid.
	#
	# ~~~
	# var a = [10,20,30]
	# assert a.get_or_null(1) == 20
	# assert a.get_or_null(3) == null
	# assert a.get_or_null(-1) == null
	# assert a.get_or_null(-10) == null
	# ~~~
	fun get_or_null(index: Int): nullable E
	do
		if index >= 0 and index < length then return self[index]
		return null
	end

	# Try to get an element, return `default` if the `index` is invalid.
	#
	# ~~~
	# var a = [10,20,30]
	# assert a.get_or_default(1, -1) == 20
	# assert a.get_or_default(3, -1) == -1
	# assert a.get_or_default(-1, -1) == -1
	# assert a.get_or_default(-10, -1) == -1
	# ~~~
	fun get_or_default(index: Int, default: E): E
	do
		if index >= 0 and index < length then return self[index]
		return default
	end

	# Get the last item.
	# Is equivalent with `self[length-1]`.
	#
	#     var a = [1,2,3]
	#     assert a.last   == 3
	#
	# REQUIRE `not is_empty`
	fun last: E
	do
		assert not_empty: not is_empty
		return self[length-1]
	end

	# The index of the first occurrence of `item`.
	# Return -1 if `item` is not found.
	# Comparison is done with `==`.
	#
	#     var a = [10,20,30,10,20,30]
	#     assert a.index_of(20)   == 1
	#     assert a.index_of(40)   == -1
	fun index_of(item: nullable Object): Int do return index_of_from(item, 0)

	# The index of the last occurrence of `item`.
	# Return -1 if `item` is not found.
	# Comparison is done with `==`.
	#
	#     var a = [10,20,30,10,20,30]
	#     assert a.last_index_of(20)   == 4
	#     assert a.last_index_of(40)   == -1
	fun last_index_of(item: nullable Object): Int do return last_index_of_from(item, length-1)

	# The index of the first occurrence of `item`, starting from pos.
	# Return -1 if `item` is not found.
	# Comparison is done with `==`.
	#
	#     var a = [10,20,30,10,20,30]
	#     assert a.index_of_from(20, 3)   == 4
	#     assert a.index_of_from(20, 4)   == 4
	#     assert a.index_of_from(20, 5)   == -1
	fun index_of_from(item: nullable Object, pos: Int): Int
	do
		var p = 0
		var i = iterator
		while i.is_ok do
			if p>=pos and i.item == item then return i.index
			i.next
			p += 1
		end
		return -1
	end

	# The index of the last occurrence of `item` starting from `pos` and decrementing.
	# Return -1 if `item` is not found.
	# Comparison is done with `==`.
	#
	#     var a = [10,20,30,10,20,30]
	#     assert a.last_index_of_from(20, 2)   == 1
	#     assert a.last_index_of_from(20, 1)   == 1
	#     assert a.last_index_of_from(20, 0)   == -1
	fun last_index_of_from(item: nullable Object, pos: Int): Int do
		var i = pos
		while i >= 0 do
			if self[i] == item then return i
			i -= 1
		end
		return -1
	end

	# Two sequences are equals if they have the same items in the same order.
	#
	#     var a = new List[Int]
	#     a.add(1)
	#     a.add(2)
	#     a.add(3)
	#     assert a == [1,2,3]
	#     assert a != [1,3,2]
	redef fun ==(o)
	do
		if not o isa SequenceRead[nullable Object] then return false
		var l = length
		if o.length != l then return false
		var i = 0
		while i < l do
			if self[i] != o[i] then return false
			i += 1
		end
		return true
	end

	# Because of the law between `==` and `hash`, `hash` is redefined to be the sum of the hash of the elements
	redef fun hash
	do
		# The 17 and 2/3 magic numbers were determined empirically.
		# Note: the standard hash functions djb2, sbdm and fnv1 were also
		# tested but were comparable (or worse).
		var res = 17 + length
		for e in self do
			res = res * 3 / 2
			if e != null then res += e.hash
		end
		return res
	end

	redef fun iterator: IndexedIterator[E] is abstract

	# Gets a new Iterator starting at position `pos`
	#
	#     var iter = [10,20,30,40,50].iterator_from(2)
	#     assert iter.to_a == [30, 40, 50]
	fun iterator_from(pos: Int): IndexedIterator[E]
	do
		var res = iterator
		while pos > 0 and res.is_ok do
			res.next
			pos -= 1
		end
		return res
	end

	# Gets an iterator starting at the end and going backwards
	#
	#     var reviter = [1,2,3].reverse_iterator
	#     assert reviter.to_a == [3,2,1]
	fun reverse_iterator: IndexedIterator[E] is abstract

	# Gets an iterator on the chars of self starting from `pos`
	#
	#     var reviter = [10,20,30,40,50].reverse_iterator_from(2)
	#     assert reviter.to_a == [30,20,10]
	fun reverse_iterator_from(pos: Int): IndexedIterator[E]
	do
		var res = reverse_iterator
		while pos > 0 and res.is_ok do
			res.next
			pos -= 1
		end
		return res
	end
end
lib/core/collection/abstract_collection.nit:831,1--1070,3

core :: math $ SequenceRead
redef class SequenceRead[E]
	# Optimized for large collections using `[]`
	redef fun rand
	do
		assert not is_empty
		return self[length.rand]
	end
end
lib/core/math.nit:502,1--509,3

pthreads :: concurrent_collections $ SequenceRead
redef class SequenceRead[E]
	redef type CONCURRENT: ConcurrentSequenceRead[E]
end
lib/pthreads/concurrent_collections.nit:48,1--50,3