core :: AbstractArrayRead :: copy_to
Copy a portion ofself to an other array.
			core :: AbstractArrayRead :: defaultinit
core :: AbstractArrayRead :: length=
core $ AbstractArrayRead :: SELF
Type of this instance, automatically specialized in every classcore $ AbstractArrayRead :: index_of_from
The index of the first occurrence ofitem, starting from pos.
			core $ AbstractArrayRead :: iterator
Get a new iterator on the collection.core $ AbstractArrayRead :: last_index_of
The index of the last occurrence ofitem.
			core $ AbstractArrayRead :: last_index_of_from
The index of the last occurrence ofitem starting from pos and decrementing.
			core $ AbstractArrayRead :: reverse_iterator
Gets an iterator starting at the end and going backwardscore :: Collection :: CONCURRENT
Type of the concurrent variant of this collectioncore :: Object :: class_factory
Implementation used byget_class to create the specific class.
			core :: Collection :: combinations
Allr-length combinations on self (in same order) without repeated elements.
			core :: Collection :: combinations_with_replacement
Allr-length combination on self (in same order) with repeated elements.
			core :: AbstractArrayRead :: copy_to
Copy a portion ofself to an other array.
			core :: Collection :: defaultinit
core :: SequenceRead :: defaultinit
core :: Object :: defaultinit
core :: AbstractArrayRead :: defaultinit
core :: SequenceRead :: get_or_default
Try to get an element, returndefault if the index is invalid.
			core :: SequenceRead :: get_or_null
Try to get an element, returnnull if the index is invalid.
			core :: Collection :: has_all
Does the collection contain at least each element ofother?
			core :: Collection :: has_any
Does the collection contain at least one element ofother?
			core :: Collection :: has_exactly
Does the collection contain exactly all the elements ofother?
			core :: SequenceRead :: index_of_from
The index of the first occurrence ofitem, starting from pos.
			core :: Object :: is_same_instance
Return true ifself and other are the same instance (i.e. same identity).
			core :: Object :: is_same_serialized
Isself the same as other in a serialization context?
			core :: Object :: is_same_type
Return true ifself and other have the same dynamic type.
			core :: SequenceRead :: iterator_from
Gets a new Iterator starting at positionpos
			core :: SequenceRead :: last_index_of
The index of the last occurrence ofitem.
			core :: SequenceRead :: last_index_of_from
The index of the last occurrence ofitem starting from pos and decrementing.
			core :: AbstractArrayRead :: length=
core :: SequenceRead :: modulo_index
Returns the real index for a modulo index.core :: Object :: output_class_name
Display class name on stdout (debug only).core :: Collection :: permutations
Allr-length permutations on self (all possible ordering) without repeated elements.
			core :: Collection :: product
Cartesian product, overr times self.
			core :: SequenceRead :: reverse_iterator
Gets an iterator starting at the end and going backwardscore :: SequenceRead :: reverse_iterator_from
Gets an iterator on the chars of self starting frompos
			core :: Collection :: to_concurrent
Wrapsself in a thread-safe collection
			core :: Collection :: to_counter
Create and fill up a counter with the elements of `self.core :: Collection :: to_curlslist
Convert Collection[String] to CURLSListcore :: Collection :: to_shuffle
Return a new array made of elements in a random order.c :: CByteArray
Wrapper around an array ofunsigned char in C (unsigned char*) with length and destroy state
			c :: CCStringArray
Wrapper around an array ofCString in C (char**) with length and destroy state.
			c :: CUInt16Array
Wrapper of a C array of typeuint16_t* with length and destroy state
			Array
			
# 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