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.
graph $ ReflexiveHashDigraph :: SELF
Type of this instance, automatically specialized in every classgraph $ ReflexiveHashDigraph :: a_shortest_path
Returns a shortest path from vertexu to v.
			graph $ ReflexiveHashDigraph :: predecessors
Returns the predecessors ofu.
			graph $ ReflexiveHashDigraph :: successors
Returns the successors ofu.
			graph :: Digraph :: a_shortest_path
Returns a shortest path from vertexu to v.
			graph :: MutableDigraph :: add_arcs
Adds all arcs ofarcs to this digraph.
			graph :: MutableDigraph :: add_vertex
Adds the vertexu to this graph.
			graph :: MutableDigraph :: add_vertices
Adds all vertices ofvertices to this digraph.
			graph :: Digraph :: arcs_iterator
Returns an iterator over the arcs of this graphcore :: Object :: class_factory
Implementation used byget_class to create the specific class.
			graph :: HashDigraph :: defaultinit
graph :: MutableDigraph :: defaultinit
core :: Object :: defaultinit
graph :: Digraph :: defaultinit
graph :: Digraph :: eulerian_path
Build a path (or circuit) from the vertexstart that visits every edge exactly once.
			graph :: MutableDigraph :: get_all_predecessors
Returns the all predecessors ofu.
			graph :: MutableDigraph :: get_all_successors
Returns the all successors ofu.
			graph :: Digraph :: has_circuit
Returns true if and only ifvertices is a circuit of this digraph.
			graph :: Digraph :: has_vertex
Returns true if and only ifu exists in this graph.
			graph :: Digraph :: incoming_arcs
Returns the incoming arcs of vertexu.
			graph :: Digraph :: is_predecessor
Returns true if and only ifu is a predecessor of v.
			core :: Object :: is_same_instance
Return true ifself and other are the same instance (i.e. same identity).
			core :: Object :: is_same_serialized
Isself the same as other in a serialization context?
			core :: Object :: is_same_type
Return true ifself and other have the same dynamic type.
			graph :: Digraph :: is_successor
Returns true if and only ifu is a successor of v.
			graph :: Digraph :: num_vertices
The number of vertices in this graph.graph :: Digraph :: out_degree
Returns the number of arcs whose source isu.
			graph :: Digraph :: outgoing_arcs
Returns the outgoing arcs of vertexu.
			core :: Object :: output_class_name
Display class name on stdout (debug only).graph :: Digraph :: predecessors
Returns the predecessors ofu.
			graph :: MutableDigraph :: remove_arc
Removes the arc(u,v) from this graph.
			graph :: MutableDigraph :: remove_eulerian_path
Build a path (or circuit) that removes every edge exactly once.graph :: MutableDigraph :: remove_vertex
Removes the vertexu from this graph and all its incident arcs.
			graph :: Digraph :: strongly_connected_components
Returns the strongly connected components of this digraph.graph :: Digraph :: successors
Returns the successors ofu.
			graph :: Digraph :: vertices_iterator
Returns an iterator over the vertices of this graph.graph :: Digraph :: weakly_connected_components
Returns the weak connected components of this digraph.
# 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