Directed graphs.
This module provides a version of labeled directed graphs. What makes the graphs provided here non-proper directed graphs is that multiple edges between vertices are allowed. However, the customary definition of directed graphs is used here.
-
A directed graph (or just "digraph") is a pair (V, E) of a finite set V of vertices and a finite set E of directed edges (or just "edges"). The set of edges E is a subset of V × V (the Cartesian product of V with itself).
In this module, V is allowed to be empty. The so obtained unique digraph is called the empty digraph. Both vertices and edges are represented by unique Erlang terms.
-
Digraphs can be annotated with more information. Such information can be attached to the vertices and to the edges of the digraph. An annotated digraph is called a labeled digraph, and the information attached to a vertex or an edge is called a label. Labels are Erlang terms.
-
An edge e = (v, w) is said to emanate from vertex v and to be incident on vertex w.
-
The out-degree of a vertex is the number of edges emanating from that vertex.
-
The in-degree of a vertex is the number of edges incident on that vertex.
-
If an edge is emanating from v and incident on w, then w is said to be an out-neighbor of v, and v is said to be an in-neighbor of w.
-
A path P from v[1] to v[k] in a digraph (V, E) is a non-empty sequence v[1], v[2], ..., v[k] of vertices in V such that there is an edge (v[i],v[i+1]) in E for 1 <= i < k.
-
The length of path P is k-1.
-
Path P is simple if all vertices are distinct, except that the first and the last vertices can be the same.
-
Path P is a cycle if the length of P is not zero and v[1] = v[k].
-
A loop is a cycle of length one.
-
A simple cycle is a path that is both a cycle and simple.
-
An acyclic digraph is a digraph without cycles.
Types
d_type() = d_cyclicity() | d_protection()
d_cyclicity() = acyclic | cyclic
d_protection() = private | protected
graph()
A digraph as returned by
new/0,1
.
edge()
label() = term()
vertex()
Functions
add_edge(G, V1, V2) -> edge() | {error, add_edge_err_rsn()}
add_edge(G, V1, V2, Label) -> edge() | {error, add_edge_err_rsn()}
add_edge(G, E, V1, V2, Label) ->
edge() | {error, add_edge_err_rsn()}
add_edge/5
creates (or modifies) edge
of digraph
, using
as
the (new) label of the edge. The
edge is emanating from
and
incident
on
. Returns
.
add_edge(
is equivalent to
add_edge(
,
where
is a created edge. The created edge is
represented by term ['$e' | N]
, where N
is an integer >= 0.
add_edge(
is equivalent to
add_edge(
.
If the edge would create a cycle in
an acyclic digraph,
{error, {bad_edge,
is returned.
If
already has an edge with value
connecting a different pair of vertices,
{error, {bad_edge, [
is returned.
If either of
or
is not
a vertex of digraph
,
{error, {bad_vertex,
}}
is
returned,
or
.
add_vertex(G) -> vertex()
G = graph()
add_vertex(G, V) -> vertex()
add_vertex(G, V, Label) -> vertex()
add_vertex/3
creates (or modifies) vertex
of digraph
, using
as the (new)
label of the
vertex. Returns
.
add_vertex(
is equivalent
to add_vertex(
.
add_vertex/1
creates a vertex using the empty list
as label, and returns the created vertex. The created vertex
is represented by term ['$v' | N]
,
where N
is an integer >= 0.
del_edges(G, Edges) -> true
Deletes the edges in list
from digraph
.
del_path(G, V1, V2) -> true
Deletes edges from digraph
until there are no
paths from vertex
to vertex
.
A sketch of the procedure employed:
-
Find an arbitrary simple path v[1], v[2], ..., v[k] from
toV1
inV2
.G -
Remove all edges of
emanating from v[i] and incident to v[i+1] for 1 <= i < k (including multiple edges).G -
Repeat until there is no path between
andV1
.V2
del_vertex(G, V) -> true
del_vertices(G, Vertices) -> true
Deletes the vertices in list
from
digraph
.
delete(G) -> true
G = graph()
Deletes digraph
. This call is important
as digraphs are implemented with ETS. There is
no garbage collection of ETS tables. However, the digraph
is deleted if the process that created the digraph terminates.
edge(G, E) -> {E, V1, V2, Label} | false
edges(G) -> Edges
Returns a list of all edges of digraph
, in
some unspecified order.
edges(G, V) -> Edges
get_cycle(G, V) -> Vertices | false
If a simple cycle of
length two or more exists through vertex
, the
cycle is returned as a list
[
of vertices.
If a loop through
exists, the loop is returned as a list
[
. If no cycles through
exist, false
is returned.
get_path/3
is used
for finding a simple cycle through
.
get_path(G, V1, V2) -> Vertices | false
Tries to find
a simple path from vertex
to vertex
of digraph
. Returns the path as a list
[
of vertices,
or false
if no simple path from
to
of length one or more exists.
Digraph
is traversed in a depth-first manner,
and the first found path is returned.
get_short_cycle(G, V) -> Vertices | false
Tries to find an as short as possible
simple cycle through
vertex
of digraph G
. Returns the cycle
as a list [
of vertices, or
false
if no simple cycle through
exists.
Notice that a loop through
is returned as list
[
.
get_short_path/3
is used for finding a simple cycle through
.
get_short_path(G, V1, V2) -> Vertices | false
Tries to find an as short as possible
simple path from vertex
to vertex
of digraph
. Returns the path as a list
[
of
vertices, or false
if no simple path from
to
of length one or more exists.
Digraph
is traversed in a breadth-first
manner, and the first found path is returned.
in_degree(G, V) -> integer() >= 0
Returns the in-degree of
vertex
of digraph
.
in_edges(G, V) -> Edges
Returns a list of all
edges incident on
of digraph
,
in some unspecified order.
in_neighbours(G, V) -> Vertex
Returns a list of
all in-neighbors of
of digraph
,
in some unspecified order.
info(G) -> InfoList
G = graph()
InfoList =
[{cyclicity, Cyclicity :: d_cyclicity()} |
{memory, NoWords :: integer() >= 0} |
{protection, Protection :: d_protection()}]
d_cyclicity() = acyclic | cyclic
d_protection() = private | protected
Returns a list of {Tag, Value}
pairs describing
digraph
. The following pairs are returned:
-
{cyclicity,
, whereCyclicity }
isCyclicity cyclic
oracyclic
, according to the options given tonew
. -
{memory,
, whereNoWords }
is the number of words allocated to the ETS tables.NoWords -
{protection,
, whereProtection }
isProtection protected
orprivate
, according to the options given tonew
.
new() -> graph()
Equivalent to new([])
.
new(Type) -> graph()
Type = [d_type()]
d_type() = d_cyclicity() | d_protection()
d_cyclicity() = acyclic | cyclic
d_protection() = private | protected
Returns
an empty digraph with
properties according to the options in
:
cyclic
Allows cycles in the digraph (default).
acyclic
The digraph is to be kept acyclic.
protected
Other processes can read the digraph (default).
private
The digraph can be read and modified by the creating process only.
If an unrecognized type option T
is specified or
is not a proper list, a badarg
exception is raised.
out_degree(G, V) -> integer() >= 0
Returns the out-degree of
vertex
of digraph
.
out_edges(G, V) -> Edges
Returns a list of all
edges emanating from
of digraph
,
in some unspecified order.
out_neighbours(G, V) -> Vertices
Returns a list of
all out-neighbors of
of digraph
,
in some unspecified order.
vertex(G, V) -> {V, Label} | false
Returns {
,
where
is the
label of the vertex
of digraph
,
or false
if no vertex
of digraph
exists.