Jump to the next item.

Require is_ok.

Property definitions

core $ Iterator :: next
	# Jump to the next item.
	# Require `is_ok`.
	fun next is abstract
lib/core/collection/abstract_collection.nit:211,2--213,21

core $ ArraySetIterator :: next
	redef fun next do _iter.next
lib/core/collection/array.nit:681,2--29

core $ IteratorDecorator :: next
	redef fun next do real.next
lib/core/collection/abstract_collection.nit:297,2--28

core $ CachedIterator :: next
	redef fun next do
		# If needed, fill the cache (an consume the current element)
		current_item
		# Empty the cache (so the next element will be read)
		cache = null
	end
lib/core/collection/abstract_collection.nit:341,2--346,4

core $ RefIterator :: next
	redef fun next do is_ok = false
lib/core/collection/abstract_collection.nit:388,2--32

core $ MapKeysIterator :: next
	redef fun next do self.original_iterator.next
lib/core/collection/abstract_collection.nit:816,2--46

core $ MapValuesIterator :: next
	redef fun next do self.original_iterator.next
lib/core/collection/abstract_collection.nit:827,2--46

core $ IteratorRange :: next
	redef fun next do _item = _item.successor(1)
lib/core/collection/range.nit:199,2--45

core $ ReverseIteratorRange :: next
	redef fun next do _item = _item.predecessor(1)
lib/core/collection/range.nit:215,2--47

core $ HashSetIterator :: next
	redef fun next
	do
		assert is_ok
		_node = _node._next_item
	end
lib/core/collection/hash_collection.nit:495,2--499,4

core $ FlatSubstringsIter :: next
	redef fun next do tgt = null
lib/core/text/flat.nit:34,2--29

cartesian $ CartesianIterator :: next
	redef fun next do
		# Next item in the second iterator
		icf.next
		if not icf.is_ok then
			# If it is over, then reset it and advance the first iterator
			icf = collection.cf.iterator
			ice.next
		end
		# Reset the cache
		item_cache = null
	end
lib/cartesian/cartesian.nit:161,2--171,4

combinations $ CartesianIterator :: next
	redef fun next
	do
		var rank = iterators.length - 1

		# Odometer-like increment starting from the last iterator
		loop
			var it = iterators[rank]
			it.next
			if it.is_ok then return

			# The iterator if over
			if rank == 0 then
				# It it is the first, then the whole thing is over
				is_ok = false
				return
			end

			# If not, restart the iterator and increment the previous one
			# (like a carry)
			iterators[rank] = collection.collections[rank].iterator
			rank -= 1
		end
	end
lib/combinations/combinations.nit:147,2--169,4

combinations $ CombinationIterator :: next
	redef fun next
	do
		var rank = product.repeat - 1

		loop
			var it = iterators[rank]

			if are_unique and not are_sorted then
				var idx = indices[rank] + 1
				it.next
				var adv = next_free(rank, idx)
				for i in [idx..adv[ do it.next
				indices[rank] = adv
			else
				it.next
				indices[rank] += 1
			end

			if it.is_ok then break
			if rank == 0 then
				is_ok = false
				return
			end
			rank -= 1
		end

		for r in [rank+1..product.repeat[ do
			reset_iterator(r)
		end
	end
lib/combinations/combinations.nit:346,2--375,4

dummy_array $ DummyIterator :: next
	redef fun next do _pos = _pos + 1 end
lib/dummy_array/dummy_array.nit:107,2--38

for_abuse $ ReadFileForAbuserIterator :: next
	redef fun next
	do
		# end of service is to close the file
		# there is only one iteration
		is_ok = false
		item.close
	end
lib/for_abuse/for_abuse.nit:57,2--63,4

for_abuse $ SortAbuserIterator :: next
	redef fun next
	do
		# Process the last query
		if item.res > 0 then
			var tmp = array[i]
			array[i] = array[j]
			array[j] = tmp
		end
		# Get the next iteration
		j += 1
		if j >= array.length then
			# End of small loop
			i += 1
			j = i + 1
		end
		if not is_ok then return
		# Prepare the next query
		item.a = array[i]
		item.b = array[j]
		item.res = 0
	end
lib/for_abuse/for_abuse.nit:114,2--134,4

functional $ FunIter :: next
        redef fun next
        do
                my_iter.next
        end
lib/functional/iter_extras.nit:235,9--238,11

pipeline $ Iterator2 :: next
	redef fun next
	do
		var i = current_iterator
		assert i != null
		i.next
	end
lib/pipeline/pipeline.nit:215,2--220,4

pipeline $ NullSkipper :: next
	redef fun next do
		inner.next
		skip_nulls
	end
lib/pipeline/pipeline.nit:282,2--285,4

pipeline $ PipeUniq :: next
	redef fun next
	do
		self.seen.add(self.item.as(Object))
		source.next
		while source.is_ok and self.seen.has(source.item.as(Object)) do
			source.next
		end
	end
lib/pipeline/pipeline.nit:345,2--352,4

pipeline $ PipeSeqUniq :: next
	redef fun next
	do
		var seen = self.item
		source.next
		while source.is_ok and seen == source.item do
			source.next
		end
	end
lib/pipeline/pipeline.nit:364,2--371,4

pipeline $ PipeJoin :: next
	redef fun next
	do
		if source1.is_ok then source1.next else source2.next
	end
lib/pipeline/pipeline.nit:389,2--392,4

pipeline $ PipeAlternate :: next
	redef fun next
	do
		if odd then
			source.next
		end
		odd = not odd
	end
lib/pipeline/pipeline.nit:413,2--419,4

pipeline $ PipeSkip :: next
	redef fun next
	do
		source.next
		do_skip
	end
lib/pipeline/pipeline.nit:439,2--443,4

pipeline $ PipeHead :: next
	redef fun next
	do
		length -= 1
		source.next
	end
lib/pipeline/pipeline.nit:457,2--461,4

pipeline $ PipeSkipTail :: next
	redef fun next
	do
		lasts.shift
		lasts.push(source.item)
		source.next
	end
lib/pipeline/pipeline.nit:486,2--491,4

pipeline $ PipeSelect :: next
	redef fun next
	do
		source.next
		do_skip
	end
lib/pipeline/pipeline.nit:512,2--516,4

pipeline $ PipeMap :: next
	redef fun next do
		source.next
		item_cached = false
	end
lib/pipeline/pipeline.nit:537,2--540,4

graph $ ArcsIterator :: next
	redef fun next
	do
		targets_iterator.next
		update_iterators
	end
lib/graph/digraph.nit:694,2--698,4

sqlite3 $ StatementIterator :: next
	# require: `self.statement.is_open`
	redef fun next
	do
		assert statement_closed: statement.is_open

		var err = statement.native_statement.step
		if err.is_row then
			is_ok = true
		else if err.is_done then
			# Clean complete
			is_ok = false
		else
			# error
			# FIXME do something with the error?
			is_ok = false
		end
	end
lib/sqlite3/sqlite3.nit:293,2--309,4

nitcc_runtime $ DephIterator :: next
	redef fun next
	do
		var i = stack.last
		stack.push i.item.children.iterator
		i.next
		while is_ok do
			if not stack.last.is_ok then
				stack.pop
				continue
			end
			if stack.last.item == null then
				stack.last.next
				continue
			end
			return
		end
	end
lib/nitcc_runtime/nitcc_runtime.nit:444,2--460,4

ordered_tree $ OrderedTreeIterator :: next
	redef fun next do
		assert is_ok
		if tree.sub.has_key(item) then
			iterators.add tree.sub[item].iterator
		else
			iterators.last.next
			while is_ok and not iterators.last.is_ok do
				iterators.pop
				if is_ok and iterators.last.is_ok then
					iterators.last.next
				end
			end
		end
	end
lib/ordered_tree/ordered_tree.nit:313,2--326,4

core $ ArrayIterator :: next
	redef fun next do _index += 1
lib/core/collection/array.nit:566,2--30

core $ StepIterator :: next
	redef fun next do real.next_by(step)
lib/core/collection/abstract_collection.nit:306,2--37

core $ DowntoIteratorRange :: next
	redef fun next do _item = _item.predecessor(1)
lib/core/collection/range.nit:232,2--47

core $ ListIterator :: next
	redef fun next
	do
		_node = _node.as(not null).next
		_index += 1
	end
lib/core/collection/list.nit:279,2--283,4

core $ CircularArrayIterator :: next
	redef fun next do index += 1
lib/core/collection/circular_array.nit:257,2--29

core $ RopeByteReverseIterator :: next
	redef fun next do
		pns -= 1
		pos -= 1
		if pns >= 0 then return
		if not subs.is_ok then return
		subs.next
		if not subs.is_ok then return
		var s = subs.item
		ns = s._items
		pns = s.last_byte
	end
lib/core/text/ropes.nit:360,2--370,4

core $ RopeByteIterator :: next
	redef fun next do
		pns += 1
		pos += 1
		if pns < subs.item._byte_length then return
		if not subs.is_ok then return
		subs.next
		if not subs.is_ok then return
		ns = subs.item._items
		pns = 0
	end
lib/core/text/ropes.nit:402,2--411,4

core $ RopeCharReverseIterator :: next
	redef fun next do
		pns -= 1
		pos -= 1
		if pns >= 0 then return
		if not subs.is_ok then return
		subs.next
		if not subs.is_ok then return
		ns = subs.item
		pns = ns.length - 1
	end
lib/core/text/ropes.nit:442,2--451,4

core $ RopeCharIterator :: next
	redef fun next do
		pns += 1
		pos += 1
		if pns < subs.item.length then return
		if not subs.is_ok then return
		subs.next
		if not subs.is_ok then return
		str = subs.item
		pns = 0
	end
lib/core/text/ropes.nit:483,2--492,4

core $ ReverseRopeSubstrings :: next
	redef fun next do
		if pos < 0 then return
		var curr = iter.prev
		var currit = curr.as(not null).node
		while curr != null do
			currit = curr.node
			if not currit isa Concat then
				str = currit.as(FlatString)
				pos -= str.length
				iter = curr
				return
			end
			if not curr.rdone then
				curr.rdone = true
				curr = new RopeCharIteratorPiece(currit._right, false, false, curr)
				continue
			end
			if not curr.ldone then
				curr.ldone = true
				curr = new RopeCharIteratorPiece(currit._left, false, false, curr)
				continue
			end
			curr = curr.prev
		end
		pos = -1
	end
lib/core/text/ropes.nit:538,2--563,4

core $ RopeSubstrings :: next
	redef fun next do
		pos += str.length
		if pos > max then return
		var it = iter.prev.as(not null)
		var rnod = it.node
		loop
			if not rnod isa Concat then
				it.ldone = true
				it.rdone = true
				str = rnod.as(FlatString)
				iter = it
				break
			end
			if not it.ldone then
				rnod = rnod._left
				it.ldone = true
				it = new RopeCharIteratorPiece(rnod, false, false, it)
			else if not it.rdone then
				it.rdone = true
				rnod = rnod._right
				it = new RopeCharIteratorPiece(rnod, false, false, it)
			else
				it = it.prev.as(not null)
				rnod = it.node
				continue
			end
		end
	end
lib/core/text/ropes.nit:612,2--639,4

core $ FlatStringCharReverseIterator :: next
	redef fun next do curr_pos -= 1
lib/core/text/flat.nit:746,2--32

core $ FlatStringCharIterator :: next
	redef fun next do curr_pos += 1
lib/core/text/flat.nit:767,2--32

core $ FlatStringByteReverseIterator :: next
	redef fun next do curr_pos -= 1
lib/core/text/flat.nit:806,2--32

core $ FlatStringByteIterator :: next
	redef fun next do curr_pos += 1
lib/core/text/flat.nit:832,2--32

core $ FlatBufferByteReverseIterator :: next
	redef fun next do curr_pos -= 1
lib/core/text/flat.nit:1182,2--32

core $ FlatBufferByteIterator :: next
	redef fun next do curr_pos += 1
lib/core/text/flat.nit:1216,2--32

core $ FlatBufferCharReverseIterator :: next
	redef fun next do curr_pos -= 1
lib/core/text/flat.nit:1233,2--32

core $ FlatBufferCharIterator :: next
	redef fun next do curr_pos += 1
lib/core/text/flat.nit:1299,2--32

core $ BytesIterator :: next
	redef fun next do index += 1
lib/core/bytes.nit:787,2--29

java $ JavaArrayIterator :: next
	redef fun next do index += 1
lib/java/collections.nit:188,2--29

java $ JavaArrayReverseIterator :: next
	redef fun next do index -= 1
lib/java/collections.nit:203,2--29

core $ U16StringCharIterator :: next
	redef fun next do curr_pos += 1
lib/core/text/u16_string.nit:200,2--32

core $ U16StringCharReverseIterator :: next
	redef fun next do curr_pos -= 1
lib/core/text/u16_string.nit:216,2--32

functional $ FilterIter :: next
        redef fun next
        do
                loop
                        my_iter.next
                        if not is_ok then
                                break
                        end
                        var x = my_iter.item
                        if pred.call(x) then
                                break
                        end
                end
        end
lib/functional/iter_extras.nit:295,9--307,11

functional $ FlatMapIter :: next
        redef fun next
        do
                inner.next
                if not inner.is_ok then
                        super
                        try_compute_inner
                end
        end
lib/functional/iter_extras.nit:332,9--339,11

functional $ OrderedIter :: next
        redef fun next
        do
                sorted_iter.next
        end
lib/functional/iter_extras.nit:367,9--370,11

nitcc_runtime $ NProdIterator :: next
	redef fun next do index += 1
lib/nitcc_runtime/nitcc_runtime.nit:583,2--29

core $ ArrayReverseIterator :: next
	redef fun next do _index -= 1
lib/core/collection/array.nit:580,2--30

core $ ListReverseIterator :: next
	redef fun next
	do
		_node = _node.as(not null).prev
		_index -= 1
	end
lib/core/collection/list.nit:316,2--320,4

more_collections $ UnrolledIterator :: next
	redef fun next
	do
		index += 1
		index_in_node += 1

		if index_in_node >= node.tail_index then
			node = node.next
			if node != null then index_in_node = node.head_index
		end
	end
lib/more_collections/more_collections.nit:668,2--677,4

mongodb $ MongoCursor :: next
	redef fun next do is_ok = native.next
lib/mongodb/mongodb.nit:722,2--38