One dimension array of objects.

Introduced properties

fun copy_to(start: Int, len: Int, dest: AbstractArray[E], new_start: Int)

core :: AbstractArrayRead :: copy_to

Copy a portion of self to an other array.
protected fun length=(length: Int)

core :: AbstractArrayRead :: length=

fun reversed: Array[E]

core :: AbstractArrayRead :: reversed

Return a new array that is the reverse of self
fun sub(from: Int, count: Int): Array[E]

core :: AbstractArrayRead :: sub

Returns a sub-array containing count elements starting from from.

Redefined properties

redef type SELF: AbstractArrayRead[E]

core $ AbstractArrayRead :: SELF

Type of this instance, automatically specialized in every class
redef fun count(item: nullable Object): Int

core $ AbstractArrayRead :: count

How many occurrences of item are in the collection?
redef fun has(item: nullable Object): Bool

core $ AbstractArrayRead :: has

Is item in the collection ?
redef fun has_only(item: nullable Object): Bool

core $ AbstractArrayRead :: has_only

Is the collection contain only item?
redef fun index_of(item: nullable Object): Int

core $ AbstractArrayRead :: index_of

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

core $ AbstractArrayRead :: index_of_from

The index of the first occurrence of item, starting from pos.
redef fun is_empty: Bool

core $ AbstractArrayRead :: is_empty

Is there no item in the collection?
redef fun iterator: IndexedIterator[E]

core $ AbstractArrayRead :: iterator

Get a new iterator on the collection.
redef fun last_index_of(item: nullable Object): Int

core $ AbstractArrayRead :: last_index_of

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

core $ AbstractArrayRead :: last_index_of_from

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

core $ AbstractArrayRead :: length

Number of items in the collection.
redef fun output

core $ AbstractArrayRead :: output

Display self on stdout (debug only).
redef fun reverse_iterator: IndexedIterator[E]

core $ AbstractArrayRead :: reverse_iterator

Gets an iterator starting at the end and going backwards

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 copy_to(start: Int, len: Int, dest: AbstractArray[E], new_start: Int)

core :: AbstractArrayRead :: copy_to

Copy a portion of self to an other array.
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.
protected fun length=(length: Int)

core :: AbstractArrayRead :: length=

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 reversed: Array[E]

core :: AbstractArrayRead :: reversed

Return a new array that is the reverse of self
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
fun sub(from: Int, count: Int): Array[E]

core :: AbstractArrayRead :: sub

Returns a sub-array containing count elements starting from from.
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::AbstractArrayRead AbstractArrayRead core::SequenceRead SequenceRead core::AbstractArrayRead->core::SequenceRead core::Collection Collection core::SequenceRead->core::Collection ...core::Collection ... ...core::Collection->core::Collection core::AbstractArray AbstractArray core::AbstractArray->core::AbstractArrayRead c::CArray CArray c::CArray->core::AbstractArrayRead core::Array Array core::Array->core::AbstractArray core::Bytes Bytes core::Bytes->core::AbstractArray core::Array... ... core::Array...->core::Array core::Bytes... ... core::Bytes...->core::Bytes c::CIntArray CIntArray c::CIntArray->c::CArray c::CUInt16Array CUInt16Array c::CUInt16Array->c::CArray c::CByteArray CByteArray c::CByteArray->c::CArray c::CCStringArray CCStringArray c::CCStringArray->c::CArray c::CIntArray... ... c::CIntArray...->c::CIntArray c::CUInt16Array... ... c::CUInt16Array...->c::CUInt16Array c::CByteArray... ... c::CByteArray...->c::CByteArray c::CCStringArray... ... c::CCStringArray...->c::CCStringArray

Ancestors

interface Collection[E: nullable Object]

core :: Collection

The root of the collection hierarchy.
interface Object

core :: Object

The root of the class hierarchy.

Parents

interface SequenceRead[E: nullable Object]

core :: SequenceRead

Sequences are indexed collections.

Children

abstract class AbstractArray[E: nullable Object]

core :: AbstractArray

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

c :: CArray

A thin wrapper around a NativeCArray adding length information

Descendants

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 BoxedArray[E: Boxed[Numeric]]

geometry :: BoxedArray

BoxedCollection implemented by an array
class Bytes

core :: Bytes

A buffer containing Byte-manipulation facilities
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 ConcurrentArray[E: nullable Object]

pthreads :: ConcurrentArray

A concurrent variant to the standard Array
class Interfaces

nitcorn :: Interfaces

A list of interfaces with dynamic port listeners
class JsonArray

json :: JsonArray

A JSON array.
class MongoPipeline

mongodb :: MongoPipeline

Mongo pipelines are arrays of aggregation stages
class VirtualHosts

nitcorn :: VirtualHosts

A list of virtual hosts with dynamic port listeners

Class definitions

core $ AbstractArrayRead
# One dimension array of objects.
abstract class AbstractArrayRead[E]
	super SequenceRead[E]

	redef var length = 0

	redef fun is_empty do return _length == 0

	redef fun has(item)
	do
		var i = 0
		var l = length
		while i < l do
			if self[i] == item then return true
			i += 1
		end
		return false
	end

	redef fun has_only(item)
	do
		var i = 0
		var l = length
		while i < l do
			if self[i] != item then return false
			i += 1
		end
		return true
	end

	redef fun count(item)
	do
		var res = 0
		var i = 0
		var l = length
		while i < l do
			if self[i] == item then res += 1
			i += 1
		end
		return res
	end

	redef fun index_of(item) do return index_of_from(item, 0)

	redef fun last_index_of(item) do return last_index_of_from(item, length-1)

	redef fun index_of_from(item, pos) do
		var i = pos
		var len = length
		while i < len do
			if self[i] == item then
				return i
			end
			i += 1
		end
		return -1
	end

	redef fun last_index_of_from(item, pos)	do
		var i = pos
		while i >= 0 do
			if self[i] == item then
				return i
			else
				i -= 1
			end
		end
		return -1
	end

	# Return a new array that is the reverse of `self`
	#
	#     assert [1,2,3].reversed      ==  [3, 2, 1]
	fun reversed: Array[E]
	do
		var cmp = _length
		var result = new Array[E].with_capacity(cmp)
		while cmp > 0 do
			cmp -= 1
			result.add(self[cmp])
		end
		return result
	end

	# Copy a portion of `self` to an other array.
	#
	#     var a = [1, 2, 3, 4]
	#     var b = [10, 20, 30, 40, 50]
	#     a.copy_to(1, 2, b, 2)
	#     assert b      ==  [10, 20, 2, 3, 50]
	fun copy_to(start: Int, len: Int, dest: AbstractArray[E], new_start: Int)
	do
		if start < new_start then
			var i = len
			while i > 0 do
				i -= 1
				dest[new_start+i] = self[start+i]
			end
		else
			var i = 0
			while i < len do
				dest[new_start+i] = self[start+i]
				i += 1
			end
		end
	end

	redef fun output
	do
		var i = 0
		var l = length
		while i < l do
			var e = self[i]
			if e != null then e.output
			i += 1
		end
	end

	redef fun iterator: IndexedIterator[E] do
		var res = _free_iterator
		if res == null then return new ArrayIterator[E](self)
		res._index = 0
		_free_iterator = null
		return res
	end

	# An old iterator, free to reuse.
	# Once an iterator is `finish`, it become reusable.
	# Since some arrays are iterated a lot, this avoid most of the
	# continuous allocation/garbage-collection of the needed iterators.
	private var free_iterator: nullable ArrayIterator[E] = null

	redef fun reverse_iterator do return new ArrayReverseIterator[E](self)

	# Returns a sub-array containing `count` elements starting from `from`.
	#
	# For most cases (see other case bellow),
	# the first element is `from` and
	# the last element is `from+count-1`.
	#
	# ~~~
	# var a = [10, 20, 30, 40, 50]
	# assert a.sub(0, 3) == [10, 20, 30]
	# assert a.sub(3, 2) == [40, 50]
	# assert a.sub(3, 1) == [40]
	# ~~~
	#
	# If `count` is 0 or negative then an empty array is returned
	#
	# ~~~
	# assert a.sub(3,0).is_empty
	# assert a.sub(3,-1).is_empty
	# ~~~
	#
	# If `from < 0` or `from+count>length` then inexistent elements are ignored.
	# In this case the length of the result is lower than count.
	#
	# ~~~
	# assert a.sub(-2, 4)  == [10, 20]
	# assert a.sub(4, 99)  == [50]
	# assert a.sub(-9, 99) == [10,20,30,40,50]
	# assert a.sub(-99, 9).is_empty
	# ~~~
	fun sub(from: Int, count: Int): Array[E] do
		if from < 0 then
			count += from
			from = 0
		end
		if count < 0 then
			count = 0
		end
		var to = from + count
		if to > length then
			to = length
		end
		var res = new Array[E].with_capacity(to - from)
		while from < to do
			res.add(self[from])
			from += 1
		end
		return res
	end
end
lib/core/collection/array.nit:22,1--204,3