Property definitions

graph $ MutableDigraph :: defaultinit
# Mutable digraph
abstract class MutableDigraph[V: Object]
	super Digraph[V]

	## ---------------- ##
	## Abstract methods ##
	## ---------------- ##

	# Adds the vertex `u` to this graph.
	#
	# If `u` already belongs to the graph, then nothing happens.
	#
	# ~~~
	# var g = new HashDigraph[Int]
	# g.add_vertex(0)
	# assert g.has_vertex(0)
	# assert not g.has_vertex(1)
	# g.add_vertex(1)
	# assert g.num_vertices == 2
	# ~~~
	fun add_vertex(u: V) is abstract

	# Removes the vertex `u` from this graph and all its incident arcs.
	#
	# If the vertex does not exist in the graph, then nothing happens.
	#
	# ~~~
	# var g = new HashDigraph[Int]
	# g.add_vertex(0)
	# g.add_vertex(1)
	# assert g.has_vertex(0)
	# g.remove_vertex(0)
	# assert not g.has_vertex(0)
	# ~~~
	fun remove_vertex(u: V) is abstract

	# Adds the arc `(u,v)` to this graph.
	#
	# If there is already an arc from `u` to `v` in this graph, then
	# nothing happens. If vertex `u` or vertex `v` do not exist in the
	# graph, they are added.
	#
	# ~~~
	# var g = new HashDigraph[Int]
	# g.add_arc(0, 1)
	# g.add_arc(1, 2)
	# assert g.has_arc(0, 1)
	# assert g.has_arc(1, 2)
	# assert not g.has_arc(1, 0)
	# g.add_arc(1, 2)
	# assert g.num_arcs == 2
	# ~~~
	fun add_arc(u, v: V) is abstract

	# Removes the arc `(u,v)` from this graph.
	#
	# If the arc does not exist in the graph, then nothing happens.
	#
	# ~~~
	# var g = new HashDigraph[Int]
	# g.add_arc(0, 1)
	# assert g.num_arcs == 1
	# g.remove_arc(0, 1)
	# assert g.num_arcs == 0
	# g.remove_arc(0, 1)
	# assert g.num_arcs == 0
	# ~~~
	fun remove_arc(u, v: V) is abstract

	## -------------------- ##
	## Non abstract methods ##
	## -------------------- ##

	# Adds all vertices of `vertices` to this digraph.
	#
	# If vertices appear more than once, they are only added once.
	#
	# ~~~
	# var g = new HashDigraph[Int]
	# g.add_vertices([0,1,2,3])
	# assert g.num_vertices == 4
	# g.add_vertices([2,3,4,5])
	# assert g.num_vertices == 6
	# ~~~
	fun add_vertices(vertices: Collection[V])
	do
		for u in vertices do add_vertex(u)
	end

	# Adds all arcs of `arcs` to this digraph.
	#
	# If arcs appear more than once, they are only added once.
	#
	# ~~~
	# var g = new HashDigraph[Int]
	# var arcs = [[0,1], [1,2], [1,2]]
	# g.add_arcs(arcs)
	# assert g.num_arcs == 2
	# ~~~
	fun add_arcs(arcs: Collection[Array[V]])
	do
		for a in arcs do add_arc(a[0], a[1])
	end

	# Add all vertices and arcs from the `other` graph.
	#
	# ~~~
	# var g1 = new HashDigraph[Int]
	# var arcs1 = [[0,1], [1,2]]
	# g1.add_arcs(arcs1)
	# g1.add_arcs(arcs1)
	# g1.add_vertex(3)
	# var g2 = new HashDigraph[Int]
	# var arcs2 = [[0,1], [1,4]]
	# g2.add_arcs(arcs2)
	# g2.add_vertex(5)
	# g2.add_graph(g1)
	# assert g2.vertices.has_exactly([0, 1, 2, 3, 4, 5])
	# var arcs3 = [[0,1], [1,2], [1,4]]
	# assert g2.arcs.has_exactly(arcs3)
	# ~~~
	fun add_graph(other: Digraph[V])
	do
		for v in other.vertices do
			add_vertex(v)
			for w in other.successors(v) do
				add_arc(v, w)
			end
		end
	end

	# Build a path (or circuit) that removes every edge exactly once.
	#
	# See `eulerian_path` for details
	fun remove_eulerian_path(start: V): Array[V]
	do
		var stack = new Array[V]
		var path = new Array[V]
		var current = start
		loop
			if out_degree(current) == 0 then
				path.unshift current
				if stack.is_empty then break
				current = stack.pop
			else
				stack.add current
				var n = successors(current).first
				remove_arc(current, n)
				current = n
			end
		end
		return path
	end

	# Cache of all predecessors for each vertex.
	# This attribute are lazy to compute the list use `get_all_predecessors` for each needed vertexe.
	# Warning the cache must be invalidated after `add_arc`
	private var cache_all_predecessors = new HashMap[V, Set[V]]

	# Cache of all successors for each vertex.
	# This attribute are lazy to compute the list use `get_all_successors` for each needed vertexe.
	# Warning the cache must be invalidated after `add_arc`
	private var cache_all_successors = new HashMap[V, Set[V]]

	# Invalid all cache `cache_all_predecessors` and `cache_all_successors`
	private fun invalidated_all_cache
	do
		if not cache_all_successors.is_empty then cache_all_successors = new HashMap[V, Set[V]]
		if not cache_all_predecessors.is_empty then cache_all_predecessors = new HashMap[V, Set[V]]
	end

	# Returns the all predecessors of `u`.
	#
	# `u` is include in the returned collection
	#
	# Returns an empty Array is the `u` does not exist
	# ~~~
	# var g = new HashDigraph[Int]
	# g.add_arc(1, 2)
	# g.add_arc(2, 3)
	# g.add_arc(3, 4)
	# assert g.get_all_predecessors(4).has(4)
	# assert g.get_all_predecessors(4).has(3)
	# assert g.get_all_predecessors(4).has(2)
	# assert g.get_all_predecessors(4).has(1)
	# ~~~
	fun get_all_predecessors(u: V): Array[V]
	do
		if not vertices.has(u) then return new Array[V]
		if not cache_all_predecessors.has_key(u) then compute_all_link(u)
		return cache_all_predecessors[u].clone.to_a
	end

	# Returns the all successors of `u`.
	#
	# `u` is include in the returned collection
	#
	# Returns an empty Array is the `u` does not exist
	# ~~~
	# var g = new HashDigraph[Int]
	# g.add_arc(1, 2)
	# g.add_arc(2, 3)
	# g.add_arc(3, 4)
	# assert g.get_all_successors(2).has(3)
	# assert g.get_all_successors(2).has(4)
	# assert g.get_all_successors(2).has(2)
	# ~~~
	fun get_all_successors(u: V): Array[V]
	do
		if not vertices.has(u) then return new Array[V]
		if not cache_all_successors.has_key(u) then compute_all_link(u)
		return cache_all_successors[u].clone.to_a
	end

	# Compute all succesors and all predecessors for the given `u`
	# The result is stocked in `cache_all_predecessors` and `cache_all_predecessors`
	private fun compute_all_link(u: V)
	do
		if not vertices.has(u) then return
		if not cache_all_predecessors.has_key(u) then cache_all_predecessors[u] = new Set[V]
		if not cache_all_successors.has_key(u) then cache_all_successors[u] = new Set[V]
		for v in vertices do
			if distance(v, u) != null then cache_all_predecessors[u].add(v)
			if distance(u, v) != null then cache_all_successors[u].add(v)
		end
	end
end
lib/graph/digraph.nit:712,1--938,3