A reflexive directed graph

i.e an element is in relation with itself (ie is implies self.has_arc(u,u))) This class avoids manually adding the reflexive vertices and at the same time it's avoids adding useless data to the hashmap.

Introduced properties

Redefined properties

redef type SELF: ReflexiveHashDigraph[V]

graph $ ReflexiveHashDigraph :: SELF

Type of this instance, automatically specialized in every class
redef fun a_shortest_path(u: V, v: V): nullable Sequence[V]

graph $ ReflexiveHashDigraph :: a_shortest_path

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

graph $ ReflexiveHashDigraph :: add_arc

Adds the arc (u,v) to this graph.
redef fun distance(u: V, v: V): nullable Int

graph $ ReflexiveHashDigraph :: distance

Returns the distance between u and v
redef fun has_arc(u: V, v: V): Bool

graph $ ReflexiveHashDigraph :: has_arc

Is (u,v) an arc in this graph?
redef fun predecessors(u: V): Collection[V]

graph $ ReflexiveHashDigraph :: predecessors

Returns the predecessors of u.
redef fun show_dot

graph $ ReflexiveHashDigraph :: show_dot

Open Graphviz with self.to_dot.
redef fun successors(u: V): Collection[V]

graph $ ReflexiveHashDigraph :: successors

Returns the successors of u.

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::ReflexiveHashDigraph ReflexiveHashDigraph graph::HashDigraph HashDigraph graph::ReflexiveHashDigraph->graph::HashDigraph graph::MutableDigraph MutableDigraph graph::HashDigraph->graph::MutableDigraph ...graph::MutableDigraph ... ...graph::MutableDigraph->graph::MutableDigraph

Ancestors

interface Digraph[V: Object]

graph :: Digraph

Interface for digraphs
abstract class MutableDigraph[V: Object]

graph :: MutableDigraph

Mutable digraph
interface Object

core :: Object

The root of the class hierarchy.

Parents

class HashDigraph[V: Object]

graph :: HashDigraph

A directed graph represented by hash maps

Class definitions

graph $ ReflexiveHashDigraph
# A reflexive directed graph
# i.e an element is in relation with itself (ie is implies `self.has_arc(u,u)`))
# This class avoids manually adding the reflexive vertices and at the same time it's avoids adding useless data to the hashmap.
class ReflexiveHashDigraph[V: Object]
	super HashDigraph[V]

	# Adds the arc (u,v) to this graph.
	# if `u` is the same as `v` do nothing
	#
	# ~~~
	# var g = new ReflexiveHashDigraph[Int]
	# g.add_arc(1, 2)
	# g.add_arc(3, 1)
	# assert g.has_arc(2,2)
	# assert g.has_arc(1,2)
	# assert g.has_arc(3,1)
	# ~~~
	redef fun add_arc(u, v)
	do
		# Check `u` is the same as `v`
		if u != v then
			super
		end
	end

	# Is (u,v) an arc in this graph?
	# If `u` is the same as `v` return true
	#
	# ~~~
	# var g = new ReflexiveHashDigraph[Int]
	# g.add_arc(1, 2)
	# g.add_arc(3, 1)
	# g.add_vertex(4)
	# assert g.has_arc(1,1)
	# assert g.has_arc(2,2)
	# assert g.has_arc(2,2)
	# assert g.has_arc(3,2) == false
	# assert g.has_arc(4,4)
	# ~~~
	redef fun has_arc(u, v)
	do
		return u == v or super
	end

	redef fun show_dot
	do
		var f = new ProcessWriter("dot", "-Txlib")
		f.write to_dot
		f.close
		f.wait
	end

	# Returns a shortest path from vertex `u` to `v`.
	#
	# If `u` is the same as `v` return `[u]`
	#
	# ~~~
	# var g = new ReflexiveHashDigraph[Int]
	# g.add_arc(1, 2)
	# g.add_arc(2, 3)
	# g.add_arc(3, 4)
	# assert g.a_shortest_path(1, 4).length == 4
	# assert g.a_shortest_path(1, 1).length == 1
	# ~~~
	redef fun a_shortest_path(u, v)
	do
		if u == v then
			var path = new List[V]
			path.add(u)
			return path
		end
		return super
	end

	# Returns the distance between `u` and `v`
	#
	# If `u` is the same as `v` return `1`
	#
	# ~~~
	# var g = new ReflexiveHashDigraph[Int]
	# g.add_arc(1, 2)
	# g.add_arc(2, 3)
	# g.add_arc(3, 4)
	# assert g.distance(1, 1) == 1
	# assert g.distance(2, 2) == 1
	# ~~~
	redef fun distance(u, v)
	do
		if has_arc(u, v) and u == v then return 1
		return super
	end

	# Returns the predecessors of `u`.
	#
	# `u` is include in the returned collection
	#
	# ~~~
	# var g = new ReflexiveHashDigraph[Int]
	# g.add_arc(1, 2)
	# g.add_arc(2, 3)
	# g.add_arc(3, 1)
	# assert g.predecessors(2).has(1)
	# assert g.predecessors(2).has(2)
	# ~~~
	redef fun predecessors(u)
	do
		var super_predecessors = super
		if incoming_vertices_map.has_key(u) then super_predecessors.add(u)
		return super_predecessors
	end

	# Returns the successors of `u`.
	#
	# `u` is include in the returned collection
	#
	# ~~~
	# var g = new ReflexiveHashDigraph[Int]
	# g.add_arc(1, 2)
	# g.add_arc(2, 3)
	# g.add_arc(3, 1)
	# assert g.successors(2).has(3)
	# assert g.successors(2).has(2)
	# ~~~
	redef fun successors(u: V)
	do
		var super_successors = super
		if outgoing_vertices_map.has_key(u) then super_successors.add(u)
		return super_successors
	end
end
lib/graph/digraph.nit:1024,1--1153,3