Mutable digraph

Introduced properties

abstract fun add_arc(u: V, v: V)

graph :: MutableDigraph :: add_arc

Adds the arc (u,v) to this graph.
fun add_arcs(arcs: Collection[Array[V]])

graph :: MutableDigraph :: add_arcs

Adds all arcs of arcs to this digraph.
fun add_graph(other: Digraph[V])

graph :: MutableDigraph :: add_graph

Add all vertices and arcs from the other graph.
abstract fun add_vertex(u: V)

graph :: MutableDigraph :: add_vertex

Adds the vertex u to this graph.
fun add_vertices(vertices: Collection[V])

graph :: MutableDigraph :: add_vertices

Adds all vertices of vertices to this digraph.
fun get_all_predecessors(u: V): Array[V]

graph :: MutableDigraph :: get_all_predecessors

Returns the all predecessors of u.
fun get_all_successors(u: V): Array[V]

graph :: MutableDigraph :: get_all_successors

Returns the all successors of u.
abstract fun remove_arc(u: V, v: V)

graph :: MutableDigraph :: remove_arc

Removes the arc (u,v) from this graph.
fun remove_eulerian_path(start: V): Array[V]

graph :: MutableDigraph :: remove_eulerian_path

Build a path (or circuit) that removes every edge exactly once.
abstract fun remove_vertex(u: V)

graph :: MutableDigraph :: remove_vertex

Removes the vertex u from this graph and all its incident arcs.

Redefined properties

redef type SELF: MutableDigraph[V]

graph $ MutableDigraph :: 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: 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 a_shortest_path(u: V, v: V): nullable Sequence[V]

graph :: Digraph :: a_shortest_path

Returns a shortest path from vertex u to v.
abstract fun add_arc(u: V, v: V)

graph :: MutableDigraph :: add_arc

Adds the arc (u,v) to this graph.
fun add_arcs(arcs: Collection[Array[V]])

graph :: MutableDigraph :: add_arcs

Adds all arcs of arcs to this digraph.
fun add_graph(other: Digraph[V])

graph :: MutableDigraph :: add_graph

Add all vertices and arcs from the other graph.
abstract fun add_vertex(u: V)

graph :: MutableDigraph :: add_vertex

Adds the vertex u to this graph.
fun add_vertices(vertices: Collection[V])

graph :: MutableDigraph :: add_vertices

Adds all vertices of vertices to this digraph.
fun arcs: Array[Array[V]]

graph :: Digraph :: arcs

Returns the arcs of this graph.
fun arcs_iterator: Iterator[Array[V]]

graph :: Digraph :: arcs_iterator

Returns an iterator over the arcs of this graph
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 distance(u: V, v: V): nullable Int

graph :: Digraph :: distance

Returns the distance between u and v
fun eulerian_path(start: V): Array[V]

graph :: Digraph :: eulerian_path

Build a path (or circuit) from the vertex start that visits every edge exactly once.
fun get_all_predecessors(u: V): Array[V]

graph :: MutableDigraph :: get_all_predecessors

Returns the all predecessors of u.
fun get_all_successors(u: V): Array[V]

graph :: MutableDigraph :: get_all_successors

Returns the all successors of u.
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
abstract fun has_arc(u: V, v: V): Bool

graph :: Digraph :: has_arc

Returns true if and only if (u,v) is an arc in this graph.
fun has_circuit(vertices: SequenceRead[V]): Bool

graph :: Digraph :: has_circuit

Returns true if and only if vertices is a circuit of this digraph.
fun has_path(vertices: SequenceRead[V]): Bool

graph :: Digraph :: has_path

Returns true if and only if vertices is a path of this digraph.
abstract fun has_vertex(u: V): Bool

graph :: Digraph :: has_vertex

Returns true if and only if u exists in this graph.
fun hash: Int

core :: Object :: hash

The hash code of the object.
fun in_degree(u: V): Int

graph :: Digraph :: in_degree

Returns the number of arcs whose target is u.
fun incoming_arcs(u: V): Collection[Array[V]]

graph :: Digraph :: incoming_arcs

Returns the incoming arcs of vertex u.
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".
fun is_empty: Bool

graph :: Digraph :: is_empty

Returns true if and only if this graph is empty.
fun is_predecessor(u: V, v: V): Bool

graph :: Digraph :: is_predecessor

Returns true if and only if u is a predecessor of v.
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.
fun is_successor(u: V, v: V): Bool

graph :: Digraph :: is_successor

Returns true if and only if u is a successor of v.
abstract fun num_arcs: Int

graph :: Digraph :: num_arcs

The number of arcs in this graph.
abstract fun num_vertices: Int

graph :: Digraph :: num_vertices

The number of vertices in this graph.
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
fun out_degree(u: V): Int

graph :: Digraph :: out_degree

Returns the number of arcs whose source is u.
fun outgoing_arcs(u: V): Collection[Array[V]]

graph :: Digraph :: outgoing_arcs

Returns the outgoing arcs of vertex u.
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 pagerank: PRMap[V]

graph :: Digraph :: pagerank

Compute PageRank for each vertex
abstract fun predecessors(u: V): Collection[V]

graph :: Digraph :: predecessors

Returns the predecessors of u.
abstract fun remove_arc(u: V, v: V)

graph :: MutableDigraph :: remove_arc

Removes the arc (u,v) from this graph.
fun remove_eulerian_path(start: V): Array[V]

graph :: MutableDigraph :: remove_eulerian_path

Build a path (or circuit) that removes every edge exactly once.
abstract fun remove_vertex(u: V)

graph :: MutableDigraph :: remove_vertex

Removes the vertex u from this graph and all its incident arcs.
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
fun show_dot

graph :: Digraph :: show_dot

Open Graphviz with self.to_dot.
fun strongly_connected_components: DisjointSet[V]

graph :: Digraph :: strongly_connected_components

Returns the strongly connected components of this digraph.
abstract fun successors(u: V): Collection[V]

graph :: Digraph :: successors

Returns the successors of u.
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
fun to_dot: String

graph :: Digraph :: to_dot

Returns a GraphViz string representing this digraph.
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 vertices: Array[V]

graph :: Digraph :: vertices

Returns an array containing the vertices of this graph.
abstract fun vertices_iterator: Iterator[V]

graph :: Digraph :: vertices_iterator

Returns an iterator over the vertices of this graph.
fun weakly_connected_components: DisjointSet[V]

graph :: Digraph :: weakly_connected_components

Returns the weak connected components of this digraph.
package_diagram graph::MutableDigraph MutableDigraph graph::Digraph Digraph graph::MutableDigraph->graph::Digraph core::Object Object graph::Digraph->core::Object ...core::Object ... ...core::Object->core::Object graph::HashDigraph HashDigraph graph::HashDigraph->graph::MutableDigraph graph::ReflexiveHashDigraph ReflexiveHashDigraph graph::ReflexiveHashDigraph->graph::HashDigraph graph::ReflexiveHashDigraph... ... graph::ReflexiveHashDigraph...->graph::ReflexiveHashDigraph

Ancestors

interface Object

core :: Object

The root of the class hierarchy.

Parents

interface Digraph[V: Object]

graph :: Digraph

Interface for digraphs

Children

class HashDigraph[V: Object]

graph :: HashDigraph

A directed graph represented by hash maps

Descendants

class ReflexiveHashDigraph[V: Object]

graph :: ReflexiveHashDigraph

A reflexive directed graph

Class definitions

graph $ MutableDigraph
# 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