Efficient data structure to access both end of the sequence.

A circular array offers efficient random access, efficient manipulation at both ends of the structure (push, pop, shift and unshift) and automatic amortized growth.

Therefore it can be used as is or as an efficient queue (FIFO/LIFO).

Introduced properties

fun enlarge(capacity: Int)

core :: CircularArray :: enlarge

Ensure at least a given capacity
protected fun length=(length: Int)

core :: CircularArray :: length=

Redefined properties

redef type SELF: CircularArray[E]

core $ CircularArray :: SELF

Type of this instance, automatically specialized in every class
redef fun [](index: Int): E

core $ CircularArray :: []

Return the index-th element of the sequence.
redef fun []=(index: Int, item: E)

core $ CircularArray :: []=

Set the item at index.
redef fun add_all(items: Collection[E])

core $ CircularArray :: add_all

Add each item of coll.
redef fun clear

core $ CircularArray :: clear

Remove all items
redef fun insert(item: E, index: Int)

core $ CircularArray :: insert

Insert an element at a given position, following elements are shifted.
redef fun iterator: Iterator[E]

core $ CircularArray :: iterator

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

core $ CircularArray :: length

Number of items in the collection.
redef fun pop: E

core $ CircularArray :: pop

Remove the last item.
redef fun push(item: E)

core $ CircularArray :: push

Add an item after the last one.
redef fun shift: E

core $ CircularArray :: shift

Remove the first item.
redef fun unshift(item: E)

core $ CircularArray :: unshift

Add an item before the first one.

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

core :: Sequence :: []=

Set the item at index.
protected fun accept_json_serializer(v: JsonSerializer)

serialization :: Serializable :: accept_json_serializer

Refinable service to customize the serialization of this class to JSON
protected fun accept_msgpack_attribute_counter(v: AttributeCounter)

serialization :: Serializable :: accept_msgpack_attribute_counter

Hook to customize the behavior of the AttributeCounter
protected fun accept_msgpack_serializer(v: MsgPackSerializer)

serialization :: Serializable :: accept_msgpack_serializer

Hook to customize the serialization of this class to MessagePack
abstract fun add(item: E)

core :: SimpleCollection :: add

Add item to this collection.
fun add_all(coll: Collection[E])

core :: SimpleCollection :: add_all

Add each item of coll.
protected fun add_to_bundle(bundle: NativeBundle, key: JavaString)

serialization :: Serializable :: add_to_bundle

Called by []= to dynamically choose the appropriate method according
fun append(coll: Collection[E])

core :: Sequence :: append

Add each item of coll after the last.
fun as_fifo: Queue[E]

core :: Sequence :: as_fifo

Return a FIFO proxy queue where result.take is shift.
fun as_lifo: Queue[E]

core :: Sequence :: as_lifo

Return a LIFO proxy queue (stack) where result.take is pop.
fun as_random: Queue[E]

core :: SimpleCollection :: as_random

Return a random proxy queue where result.take is random.
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.
abstract fun clear

core :: RemovableCollection :: clear

Remove all items
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 core_serialize_to(serializer: Serializer)

serialization :: Serializable :: core_serialize_to

Actual serialization of self to serializer
fun count(item: nullable Object): Int

core :: Collection :: count

How many occurrences of item are in the collection?
fun enlarge(capacity: Int)

core :: CircularArray :: enlarge

Ensure at least a given capacity
fun first: E

core :: Collection :: first

Return the first item of the collection
fun first=(item: E)

core :: Sequence :: first=

Set the first item.
init from_deserializer(deserializer: Deserializer)

serialization :: Serializable :: from_deserializer

Create an instance of this class from the deserializer
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

abstract fun insert(item: E, index: Int)

core :: Sequence :: insert

Insert an element at a given position, following elements are shifted.
fun insert_all(coll: Collection[E], index: Int)

core :: Sequence :: insert_all

Insert all elements at a given position, following elements are shifted.
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=(item: E)

core :: Sequence :: last=

Set 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 :: CircularArray :: length=

fun modulo(index: Int): E

core :: SequenceRead :: modulo

Return the index-th element but wrap
fun modulo=(index: Int, value: E)

core :: Sequence :: modulo=

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

core :: SequenceRead :: modulo_index

Returns the real index for a modulo index.
protected fun msgpack_extra_array_items: Int

serialization :: Serializable :: msgpack_extra_array_items

Hook to request a larger than usual metadata array
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
abstract fun pop: E

core :: Sequence :: pop

Remove the last item.
fun prepend(coll: Collection[E])

core :: Sequence :: prepend

Add all items of coll before the first one.
fun product(r: Int): Collection[SequenceRead[E]]

core :: Collection :: product

Cartesian product, over r times self.
abstract fun push(e: E)

core :: Sequence :: push

Add an item after the last one.
fun rand: E

core :: Collection :: rand

Return a random element form the collection
abstract fun remove(item: nullable Object)

core :: RemovableCollection :: remove

Remove an occurrence of item
fun remove_all(item: nullable Object)

core :: RemovableCollection :: remove_all

Remove all occurrences of item
abstract fun remove_at(index: Int)

core :: Sequence :: remove_at

Remove the item at index and shift all following elements
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 rotate_left

core :: Sequence :: rotate_left

Rotates the elements of self once to the left
fun rotate_right

core :: Sequence :: rotate_right

Rotates the elements of self once to the right
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 serialize_msgpack(plain: nullable Bool): Bytes

serialization :: Serializable :: serialize_msgpack

Serialize self to MessagePack bytes
fun serialize_to(serializer: Serializer)

serialization :: Serializable :: serialize_to

Serialize self to serializer
fun serialize_to_json(plain: nullable Bool, pretty: nullable Bool): String

serialization :: Serializable :: serialize_to_json

Serialize self to JSON
abstract fun shift: E

core :: Sequence :: shift

Remove the first item.
fun subarray(start: Int, len: Int): Array[E]

core :: Sequence :: subarray

Copy the content of self between start and len to a new Array.
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
fun to_json: String

serialization :: Serializable :: to_json

Serialize self to plain JSON
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

fun to_pretty_json: String

serialization :: Serializable :: to_pretty_json

Serialize self to plain pretty JSON
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.
abstract fun unshift(e: E)

core :: Sequence :: unshift

Add an item before the first one.
package_diagram core::CircularArray CircularArray core::Sequence Sequence core::CircularArray->core::Sequence core::SequenceRead SequenceRead core::Sequence->core::SequenceRead core::SimpleCollection SimpleCollection core::Sequence->core::SimpleCollection ...core::SequenceRead ... ...core::SequenceRead->core::SequenceRead ...core::SimpleCollection ... ...core::SimpleCollection->core::SimpleCollection

Ancestors

interface Collection[E: nullable Object]

core :: Collection

The root of the collection hierarchy.
interface Object

core :: Object

The root of the class hierarchy.
interface RemovableCollection[E: nullable Object]

core :: RemovableCollection

Items can be removed from this collection
interface SequenceRead[E: nullable Object]

core :: SequenceRead

Sequences are indexed collections.
interface Serializable

serialization :: Serializable

Instances of this class can be passed to Serializer::serialize
interface SimpleCollection[E: nullable Object]

core :: SimpleCollection

Items can be added to these collections.

Parents

interface Sequence[E: nullable Object]

core :: Sequence

Sequence are indexed collection.

Class definitions

core $ CircularArray
# Efficient data structure to access both end of the sequence.
#
# A circular array offers efficient random access, efficient manipulation
# at both ends of the structure (push, pop, shift and unshift) and
# automatic amortized growth.
#
# Therefore it can be used as is or as an efficient queue (FIFO/LIFO).
class CircularArray[E]
	super Sequence[E]

	# The low-level storage of the items.
	#
	# Internally, there is two main configurations
	#
	# One part: from `head` to `tail` (inclusive)
	#
	# ~~~raw
	# ...0123...
	#    h  t
	# ~~~
	#
	# Two parts: from `head` to `capacity-1`,
	# then from `0` to `tail` (both inclusive)
	# Test with `head > tail`
	#
	# ~~~raw
	# 345....012
	#   t    h
	# ~~~
	#
	# For consistency, *length* and *index* are used in the context of the sequence (self) and
	# *capacity* and *offset* are used in the context of the native array.
	#
	# Initially the native is not allocated, the first one is done with `enlarge`
	private var native: NativeArray[E] is noautoinit

	# The offset of the `first` item in `native`
	private var head = 0

	# The offset of the `last` item in `native`
	private var tail: Int = -1

	redef var length = 0

	# Transform an index into an offset.
	#
	# The method takes care of the initial gap and the possible wrapping.
	#
	# REQUIRE: `0 <= index and index < length`
	private fun offset(index: Int): Int
	do
		assert index >= 0
		var head = self._head
		var tail = self._tail
		var offset = head + index

		if head > tail then
			# Two parts
			var capacity = native.length
			if offset < capacity then
				return offset
			end
			offset -= capacity
		end

		assert offset <= tail
		return offset
	end

	redef fun [](index) do return native[offset(index)]

	redef fun []=(index, item) do
		var l = length
		if index == l then
			push(item)
			return
		end
		native[offset(index)] = item
	end

	redef fun push(item) do
		var l = length + 1
		enlarge(l)
		length = l

		var native = _native
		var cap = native.length
		var t = tail + 1
		if t >= cap then t -= cap

		native[t] = item
		tail = t
	end

	redef fun add_all(items) do
		enlarge length + items.length
		super
	end

	redef fun pop do
		var l = length - 1
		assert l >= 0
		length = l

		var native = _native
		var t = tail
		var res = native[t]

		t -= 1
		if t < 0 then t += native.length
		tail = t

		return res
	end

	redef fun unshift(item) do
		var l = length + 1
		enlarge(l)
		length = l

		var native = _native
		var h = head - 1
		if h < 0 then h += native.length

		native[h] = item
		head = h
	end

	redef fun shift do
		var l = length - 1
		assert l >= 0
		length = l

		var native = _native
		var h = head
		var res = native[h]

		h += 1
		var cap = native.length
		if h >= cap then h -= cap
		head = h

		return res
	end

	# Ensure at least a given capacity
	#
	# If the current capacity is enough, then no-op.
	fun enlarge(capacity: Int)
	do
		# First allocation
		if not isset _native then
			var new_c = 8
			while new_c < capacity do new_c *= 2
			native = new NativeArray[E](new_c)
			return
		end

		# Compute more capacity
		var c = native.length
		if capacity <= c then return
		var new_c = c
		while new_c < capacity do new_c *= 2

		var new_native = new NativeArray[E](new_c)

		# Reallocation: just realign the parts on 0
		if head > tail then
			# Two parts
			native.memmove(head, c-head, new_native, 0)
			native.memmove(0, tail+1, new_native, c-head)
		else
			# One part
			native.memmove(head, length, new_native, 0)
		end
		head = 0
		tail = length - 1
		native = new_native
	end

	redef fun insert(item, index)
	do
		# Special insertion at the end (is push)
		if index >= length then
			assert index == length
			push(item)
			return
		end
		assert index >= 0

		var new_len = length + 1

		# TODO be more efficient:
		# Here, we just allocate a new native and copy everything.

		# Allocate a new native array
		var c = native.length
		while c < new_len do c *= 2
		var new_native = new NativeArray[E](c)

		# Copy everything
		var i = 0
		while i < index do
			new_native[i] = self[i]
			i += 1
		end
		new_native[index] = item
		var l = length
		while i < l do
			new_native[i+1] = self[i]
			i += 1
		end

		# Use the new native array
		length = new_len
		head = 0
		tail = new_len - 1
		native = new_native
	end

	redef fun clear do
		length = 0
		head = 0
		tail = -1
	end

	redef fun iterator do return new CircularArrayIterator[E](self)
end
lib/core/collection/circular_array.nit:20,1--247,3