Iterators generate a series of elements, one at a time.

They are mainly used with collections and obtained from Collection::iterator.

Introduced properties

fun +(other: Iterator[E]): Iterator[E]

core :: Iterator :: +

Combine two iterators.
fun all(pred: Fun1[E, Bool]): Bool

core :: Iterator :: all

Checks if all elements respect a predicate
fun alternate(e: E): Iterator[E]

core :: Iterator :: alternate

Alternate each item with e.
fun any(pred: Fun1[E, Bool]): Bool

core :: Iterator :: any

Checks if at least one element respects a predicate
fun enumerate: EnumerateIter[E]

core :: Iterator :: enumerate

Iterator that gives the current count and element as a pair
fun filter(pred: Fun1[E, Bool]): FilterIter[E]

core :: Iterator :: filter

Iterator that filters elements by a predicate
fun finish

core :: Iterator :: finish

Post-iteration hook.
fun flat_map(f: Fun1[E, Iterator[Object]]): FlatMapIter[E, Object]

core :: Iterator :: flat_map

Maps every element to a nested structure then flattens it
fun fold(acc: Object, f: Fun2[Object, E, Object]): Object

core :: Iterator :: fold

Folds an iterator from the left
fun fold1(f: Fun2[E, E, E]): E

core :: Iterator :: fold1

Folds and apply two element at a time
fun for_each(f: Proc1[E])

core :: Iterator :: for_each

Apply a mutation function over all elements
fun head(length: Int): Iterator[E]

core :: Iterator :: head

Filter: keep only the first length items.
abstract fun is_ok: Bool

core :: Iterator :: is_ok

Is there a current item ?
abstract fun item: E

core :: Iterator :: item

The current item.
fun iterator: Iterator[E]

core :: Iterator :: iterator

Iterate over self
fun map(f: Fun1[E, Object]): MapIter[E, Object]

core :: Iterator :: map

Applies a function to every elements
abstract fun next

core :: Iterator :: next

Jump to the next item.
fun next_by(step: Int)

core :: Iterator :: next_by

Jump to the next item step times.
fun order_by(f: Fun1[E, Comparable]): OrderedIter[E]

core :: Iterator :: order_by

Generates an Iterator whose elements are sorted by the function
fun select(predicate: Function[E, Bool]): Iterator[E]

core :: Iterator :: select

Filter: reject items that does not meet some criteria.
fun seq_uniq: Iterator[E]

core :: Iterator :: seq_uniq

Filter: reject continuous sequences of duplicates
fun skip(item: E): Iterator[E]

core :: Iterator :: skip

Filter: reject a given item.
fun skip_head(length: Int): Iterator[E]

core :: Iterator :: skip_head

Filter: reject the first length items.
fun skip_tail(length: Int): Iterator[E]

core :: Iterator :: skip_tail

Filter: reject the last length items.
fun sort: Iterator[E]

core :: Iterator :: sort

Filter: sort with default_comparator.
fun sort_with(comparator: Comparator): Iterator[E]

core :: Iterator :: sort_with

Filter: sort with a given comparator.
fun start

core :: Iterator :: start

Pre-iteration hook.
fun tail(length: Int): Iterator[E]

core :: Iterator :: tail

Filter: keep only the last length items.
fun to_a: Array[E]

core :: Iterator :: to_a

Interate on self and build an array
fun to_step(step: Int): Iterator[E]

core :: Iterator :: to_step

A decorator around self that advance self a given number of steps instead of one.
fun uniq: Iterator[E]

core :: Iterator :: uniq

Filter: reject duplicates.

Redefined properties

redef type SELF: Iterator[E]

core $ Iterator :: SELF

Type of this instance, automatically specialized in every class

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
fun +(other: Iterator[E]): Iterator[E]

core :: Iterator :: +

Combine two iterators.
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 SELF: Object

core :: Object :: SELF

Type of this instance, automatically specialized in every class
fun all(pred: Fun1[E, Bool]): Bool

core :: Iterator :: all

Checks if all elements respect a predicate
fun alternate(e: E): Iterator[E]

core :: Iterator :: alternate

Alternate each item with e.
fun any(pred: Fun1[E, Bool]): Bool

core :: Iterator :: any

Checks if at least one element respects a predicate
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 enumerate: EnumerateIter[E]

core :: Iterator :: enumerate

Iterator that gives the current count and element as a pair
fun filter(pred: Fun1[E, Bool]): FilterIter[E]

core :: Iterator :: filter

Iterator that filters elements by a predicate
fun finish

core :: Iterator :: finish

Post-iteration hook.
fun flat_map(f: Fun1[E, Iterator[Object]]): FlatMapIter[E, Object]

core :: Iterator :: flat_map

Maps every element to a nested structure then flattens it
fun fold(acc: Object, f: Fun2[Object, E, Object]): Object

core :: Iterator :: fold

Folds an iterator from the left
fun fold1(f: Fun2[E, E, E]): E

core :: Iterator :: fold1

Folds and apply two element at a time
fun for_each(f: Proc1[E])

core :: Iterator :: for_each

Apply a mutation function over all elements
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun hash: Int

core :: Object :: hash

The hash code of the object.
fun head(length: Int): Iterator[E]

core :: Iterator :: head

Filter: keep only the first length items.
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".
abstract fun is_ok: Bool

core :: Iterator :: is_ok

Is there a current item ?
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 item: E

core :: Iterator :: item

The current item.
fun iterator: Iterator[E]

core :: Iterator :: iterator

Iterate over self
fun map(f: Fun1[E, Object]): MapIter[E, Object]

core :: Iterator :: map

Applies a function to every elements
abstract fun next

core :: Iterator :: next

Jump to the next item.
fun next_by(step: Int)

core :: Iterator :: next_by

Jump to the next item step times.
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
fun order_by(f: Fun1[E, Comparable]): OrderedIter[E]

core :: Iterator :: order_by

Generates an Iterator whose elements are sorted by the function
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 select(predicate: Function[E, Bool]): Iterator[E]

core :: Iterator :: select

Filter: reject items that does not meet some criteria.
fun seq_uniq: Iterator[E]

core :: Iterator :: seq_uniq

Filter: reject continuous sequences of duplicates
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
fun skip(item: E): Iterator[E]

core :: Iterator :: skip

Filter: reject a given item.
fun skip_head(length: Int): Iterator[E]

core :: Iterator :: skip_head

Filter: reject the first length items.
fun skip_tail(length: Int): Iterator[E]

core :: Iterator :: skip_tail

Filter: reject the last length items.
fun sort: Iterator[E]

core :: Iterator :: sort

Filter: sort with default_comparator.
fun sort_with(comparator: Comparator): Iterator[E]

core :: Iterator :: sort_with

Filter: sort with a given comparator.
fun start

core :: Iterator :: start

Pre-iteration hook.
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
fun tail(length: Int): Iterator[E]

core :: Iterator :: tail

Filter: keep only the last length items.
fun to_a: Array[E]

core :: Iterator :: to_a

Interate on self and build an array
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_step(step: Int): Iterator[E]

core :: Iterator :: to_step

A decorator around self that advance self a given number of steps instead of one.
fun uniq: Iterator[E]

core :: Iterator :: uniq

Filter: reject duplicates.
package_diagram core::Iterator Iterator core::Object Object core::Iterator->core::Object core::Iterator... ... core::Iterator...->core::Iterator

Parents

interface Object

core :: Object

The root of the class hierarchy.

Children

class ArcsIterator[V: Object]

graph :: ArcsIterator

Arcs iterator
abstract class CachedIterator[E: Object]

core :: CachedIterator

An iterator that lazyly cache the current item.
class CartesianIterator[E: nullable Object, F: nullable Object]

cartesian :: CartesianIterator

An iterator over a Cartesian-product collection.
class DummyIterator

dummy_array :: DummyIterator

An iterator over a DummyArray.
interface IndexedIterator[E: nullable Object]

core :: IndexedIterator

Iterators on indexed collections.
class Iterator2[E: nullable Object]

pipeline :: Iterator2

Concatenates a sequence of iterators.
abstract class IteratorDecorator[E: nullable Object]

core :: IteratorDecorator

A basic helper class to specialize specific Iterator decorators
class MapKeysIterator[K: nullable Object, V: nullable Object]

core :: MapKeysIterator

Iterator on a 'keys' point of view of a map
class MapValuesIterator[K: nullable Object, V: nullable Object]

core :: MapValuesIterator

Iterator on a 'values' point of view of a map
class MongoCursor

mongodb :: MongoCursor

A MongoDB query cursor.
class NullSkipper[E: Object]

pipeline :: NullSkipper

Wraps an iterator to skip nulls.
class StatementIterator

sqlite3 :: StatementIterator

Iterator over the rows of a statement result

Descendants

class EnumerateIter[E: nullable Object]

functional :: EnumerateIter

An iterator that maps each item to a pair containing the item with its
class FilterIter[E: nullable Object]

functional :: FilterIter

An tierator that filter its element by a predicate pred.
class FlatMapIter[A: nullable Object, B: nullable Object]

functional :: FlatMapIter

An iterator that maps each item to an iterator and yield
class LineIterator

core :: LineIterator

Iterator returned by Reader::each_line.
class ListIterator[E: nullable Object]

core :: ListIterator

This is the iterator class of List
class MapIter[A: nullable Object, B: nullable Object]

functional :: MapIter

An iterator that maps each item with f.
class OrderedIter[E: nullable Object]

functional :: OrderedIter

An iterator that yield each item in order

Class definitions

core $ Iterator
# Iterators generate a series of elements, one at a time.
#
# They are mainly used with collections and obtained from `Collection::iterator`.
interface Iterator[E]
	# The current item.
	# Require `is_ok`.
	fun item: E is abstract

	# Jump to the next item.
	# Require `is_ok`.
	fun next is abstract

	# Jump to the next item `step` times.
	#
	# ~~~
	# var i = [11, 22, 33, 44].iterator
	# assert i.item == 11
	# i.next_by 2
	# assert i.item == 33
	# ~~~
	#
	# `next_by` should be used instead of looping on `next` because is takes care
	# of stopping if the end of iteration is reached prematurely whereas a loop of
	# `next` will abort because of the precondition on `is_ok`.
	#
	# ~~~
	# i.next_by 100
	# assert not i.is_ok
	# ~~~
	#
	# If `step` is negative, this method aborts.
	# But specific subclasses can change this and do something more meaningful instead.
	#
	# Require `is_ok`
	fun next_by(step: Int)
	do
		assert step >= 0
		while is_ok and step > 0 do
			next
			step -= 1
		end
	end

	# Is there a current item ?
	fun is_ok: Bool is abstract

	# Iterate over `self`
	fun iterator: Iterator[E] do return self

	# Pre-iteration hook.
	#
	# Used to inform `self` that the iteration is starting.
	# Specific iterators can use this to prepare some resources.
	#
	# Is automatically invoked at the beginning of `for` structures.
	#
	# Do nothing by default.
	fun start do end

	# Post-iteration hook.
	#
	# Used to inform `self` that the iteration is over.
	# Specific iterators can use this to free some resources.
	#
	# Is automatically invoked at the end of `for` structures.
	#
	# Do nothing by default.
	fun finish do end

	# A decorator around `self` that advance self a given number of steps instead of one.
	#
	# ~~~
	# var i = [11, 22, 33, 44, 55].iterator
	# var i2 = i.to_step(2)
	#
	# assert i2.item == 11
	# i2.next
	# assert i2.item == 33
	#
	# assert i.item == 33
	# ~~~
	fun to_step(step: Int): Iterator[E] do return new StepIterator[E](self, step)
end
lib/core/collection/abstract_collection.nit:203,1--285,3

core :: array $ Iterator
redef class Iterator[E]
	# Interate on `self` and build an array
	fun to_a: Array[E]
	do
		var res = new Array[E]
		while is_ok do
			res.add(item)
			next
		end
		finish
		return res
	end
end
lib/core/collection/array.nit:951,1--963,3

pipeline :: pipeline $ Iterator
redef interface Iterator[E]
	# Filter: sort with `default_comparator`.
	# SEE: `sort_with` for details
	# REQUIRE: self isa Iterator[Comparable]
	#
	#     assert [1,3,2].iterator.sort.to_a	     ==  [1,2,3]
	fun sort: Iterator[E]
	do
		assert self isa Iterator[Comparable]
		var a = self.to_a
		default_comparator.sort(a)
		return a.iterator
	end

	# Filter: sort with a given `comparator`.
	# Important: require O(n) memory.
	#
	#     assert ["a", "c", "b"].iterator.sort_with(alpha_comparator).to_a  == ["a", "b", "c"]
	fun sort_with(comparator: Comparator): Iterator[E]
	do
		var a = self.to_a
		comparator.sort(a)
		return a.iterator
	end

	# Filter: reject duplicates.
	# Elements already seen are rejected.
	#
	# Important: rely on `==` and `hash`
	# Important: require O(m) in memory, where m is the total number of uniq items.
	#
	#     assert [1,2,1,1,1,3,2].iterator.uniq.to_a	     ==  [1,2,3]
	#
	# REQUIRE: self isa Iterator[Object]
	fun uniq: Iterator[E]
	do
		assert self isa Iterator[Object]
		return new PipeUniq[E](self)
	end

	# Filter: reject continuous sequences of duplicates
	#
	# Important: rely on `==`.
	#
	#     assert [1,2,1,1,1,3,2].iterator.seq_uniq.to_a	     ==  [1,2,1,3,2]
	fun seq_uniq: Iterator[E]
	do
		return new PipeSeqUniq[E](self)
	end

	# Combine two iterators.
	#
	# When the first iterator is terminated, the second is started.
	#
	#     assert ([1..20[.iterator + [20..40[.iterator).to_a	     ==  ([1..40[).to_a
	#
	# SEE: `Iterator2`
	fun +(other: Iterator[E]): Iterator[E]
	do
		return new PipeJoin[E](self, other)
	end

	# Alternate each item with `e`.
	#
	#     assert [1,2,3].iterator.alternate(0).to_a		     ==  [1,0,2,0,3]
	fun alternate(e: E): Iterator[E]
	do
		return new PipeAlternate[E](self, e)
	end

	# Filter: reject a given `item`.
	#
	#     assert [1,1,2,1,3].iterator.skip(1).to_a		     ==  [2,3]
	fun skip(item: E): Iterator[E]
	do
		return new PipeSkip[E](self, item)
	end

	# Filter: keep only the first `length` items.
	#
	# This filter does not always consume `self'.
	#
	#     var i = [1,2,3,4,5].iterator
	#     assert i.head(2).to_a   == [1,2]
	#     assert i.to_a           == [3,4,5]
	fun head(length: Int): Iterator[E]
	do
		return new PipeHead[E](self, length)
	end

	# Filter: reject the first `length` items.
	#
	#     assert [1,2,3,4,5].iterator.skip_head(2).to_a	     ==  [3,4,5]
	#
	# ENSURE: self == return
	fun skip_head(length: Int): Iterator[E]
	do
		while length > 0 and self.is_ok do
			length -= 1
			self.next
		end
		return self
	end

	# Filter: keep only the last `length` items.
	#
	#     assert [1,2,3,4,5].iterator.tail(2).to_a	     ==  [4,5]
	#
	# Important: require O(length) in memory
	fun tail(length: Int): Iterator[E]
	do
		var lasts = new List[E]
		while self.is_ok do
			while lasts.length >= length do lasts.shift
			lasts.push(self.item)
			self.next
		end
		return lasts.iterator
	end

	# Filter: reject the last `length` items.
	#
	#     assert [1,2,3,4,5].iterator.skip_tail(2).to_a	     ==  [1,2,3]
	#
	# Important: require O(length) in memory
	fun skip_tail(length: Int): Iterator[E]
	do
		return new PipeSkipTail[E](self, length)
	end

	# Filter: reject items that does not meet some criteria.
	#
	#     class IsEvenFunction
	#       super Function[Int, Bool]
	#       redef fun apply(i) do return i % 2 == 0
	#     end
	#     assert [1,2,3,4,8].iterator.select(new IsEvenFunction).to_a  == [2,4,8]
	fun select(predicate: Function[E, Bool]): Iterator[E]
	do
		return new PipeSelect[E](self, predicate)
	end
end
lib/pipeline/pipeline.nit:21,1--162,3

functional :: iter_extras $ Iterator
redef interface Iterator[E]

        # Applies a function to every elements
        #
        # ~~~~nitish
        # fun add(x: Int): Int do return x + 1
        #
        # var f = &add
        # var xs = [1,2,3,4,5]
        # var actual = xs.iterator.map(f).to_a
        # assert actual == [2,3,4,5,6]
        # ~~~~
        fun map(f: Fun1[E,Object]): MapIter[E,Object]
        do
                return new MapIter[E,Object](self, f)
        end

        # Iterator that gives the current count and element as a pair
        fun enumerate: EnumerateIter[E]
        do
                return new EnumerateIter[E](self)
        end

        # Iterator that filters elements by a predicate
        #
        # ~~~~nitish
        # fun lt10(x: Int): Bool do return x < 10
        #
        # var pred = &lt10
        # var xs = [1..20]
        # var actual = xs.iterator.filter(pred).to_a
        # assert actual == [1..9].to_a
        # ~~~~
        fun filter(pred: Fun1[E,Bool]): FilterIter[E]
        do
                return new FilterIter[E](self,pred)
        end

        # Checks if at least one element respects a predicate
        #
        # ~~~~nitish
        # fun eq10(x: Int): Bool do return x == 10
        #
        # var pred = &eq10
        # var xs = [1,2,5,7,9,10,44]
        # assert xs.iterator.any(pred)
        # var ys = []
        # assert not ys.iterator.any(pred)
        # assert not [1,2,44].iterator.any(pred)
        # ~~~~
        fun any(pred: Fun1[E,Bool]): Bool
        do
                for x in self do
                        if pred.call(x) then
                                return true
                        end
                end
                return false
        end

        # Checks if all elements respect a predicate
        #
        # ~~~~nitish
        # fun lt10(x: Int): Bool do return x < 10
        #
        # var pred = &lt10
        # var xs = [1..9]
        # assert xs.iterator.all(pred)
        # assert [].iterator.all(pred)
        # assert not [1..10].iterator.all(pred)
        # ~~~~
        fun all(pred: Fun1[E,Bool]): Bool
        do
                for x in self do
                        if not pred.call(x) then
                                return false
                        end
                end
                return true
        end

        # Folds an iterator from the left
        #
        # ~~~~nitish
        # fun adder(x: Int, y: Int): Int do return x + y
        #
        # var xs = [1..10]
        # assert xs.iterator.fold(0, &adder) == 55
        # ~~~~
        fun fold(acc: Object, f: Fun2[Object, E, Object]): Object
        do
                for x in self do
                        acc = f.call(acc, x)
                end
                return acc
        end

        # Folds and apply two element at a time
        #
        # ~~~~nitish
        # fun min_int(x: Int, y: Int): Int
        # do
        #       if x < y then return x
        #       return y
        # end
        #
        # var xs = [100,423,51,1,-19,55,999,-18]
        # assert xs.iterator.fold1(&min_int) == -19
        # ~~~~
        # REQUIRE : length > 1
        fun fold1(f: Fun2[E,E,E]): E
        do
                var a1 = item
                next
                var a2 = item
                next
                var res = f.call(a1,a2)
                for x in self do
                        res = f.call(res, x)
                end
                return res
        end

        # Apply a mutation function over all elements
        #
        # ~~~~nitish
        # class Person
        #       var age: Int
        #       def incr_age
        #       do
        #               age += 1
        #       end
        # end
        #
        # var ps = [new Persone(1), new Person(2), new Person(3)]
        # var ages = ps.iterator.for_each(&Person::incr_age).map(&Person::age).to_a
        # assert ages == [2,3,4]
        # ~~~~
        fun for_each(f: Proc1[E])
        do
                for x in self do
                        f.call(x)
                end
        end

        # Maps every element to a nested structure then flattens it
        #
        # ~~~~nitish
        # fun chars_fn(s: String): Iterator[Char]
        # do
        #       return s.chars.iterator
        # end
        # var cs = ["aaa","bbb","ccc"]
        # assert cs.iterator.flat_map(&chars_fn).to_a.join == "aaabbbccc"
        # ~~~~
        fun flat_map(f: Fun1[E, Iterator[Object]]): FlatMapIter[E, Object]
        do
                return new FlatMapIter[E, Object](self, f)
        end

        # Generates an `Iterator` whose elements are sorted by the function
        # passed in argument.
        #
        # ~~~~nitish
        # class Person
        #       var name: String
        # end
        #
        # def get_name(p: Person) do return p.name
        #
        # var ps = [new Person("Turing"), new Person("Curry"), new Person("Alfredo")]
        # var ordered_names = ps.iterator.order_by(&get_name).map(&get_name).to_a
        # assert ordered_names == ["Alfredo", "Curry", "Turing"]
        # ~~~~
        fun order_by(f: Fun1[E, Comparable]): OrderedIter[E]
        do
                return new OrderedIter[E](self, f)
        end

end
lib/functional/iter_extras.nit:49,1--228,3