View Source digraph (stdlib v6.1.2)
This module provides a version of labeled directed graphs ("digraphs").
The digraphs managed by this module are stored in ETS tables. That implies the following:
- Only the process that created the digraph is allowed to update it.
- Digraphs will not be garbage collected. The ETS tables used for a digraph will
only be deleted when
delete/1
is called or the process that created the digraph terminates. - A digraph is a mutable data structure.
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.
See Also
Summary
Types
The error reason for when an edge could not be added to a graph.
Serves as the identifier or "name" of an edge. This is distinct from an edge "label" which attaches ancillary information to the edge rather than identifying the edge itself.
Functions
Equivalent to add_edge(G, V1, V2, [])
.
Equivalent to add_edge(G, E, V1, V2, Label)
, where E
is a created edge.
Creates a vertex using the empty list as label, and returns the created vertex.
Equivalent to add_vertex(G, V, [])
.
Creates (or modifies) vertex V
of digraph G
, using Label
as the (new)
label of the vertex. Returns the new vertex V
.
Deletes edge E
from digraph G
.
Deletes the edges in list Edges
from digraph G
.
Deletes edges from digraph G
until there are no paths from
vertex V1
to vertex V2
.
Deletes the vertices in list Vertices
from digraph G
.
Deletes digraph G
. 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.
Returns a list of all edges of digraph G
, in some unspecified order.
If a simple cycle of length two or more exists
through vertex V
, the cycle is returned as a list [V, ..., V]
of vertices.
If a loop through V
exists, the loop is returned as a list
[V]
. If no cycles through V
exist, false
is returned.
Tries to find a simple path from vertex V1
to
vertex V2
of digraph G
. Returns the path as a list [V1, ..., V2]
of
vertices, or false
if no simple path from V1
to V2
of length one or more
exists.
Tries to find an as short as possible simple cycle
through vertex V
of digraph G
. Returns the cycle as a list [V, ..., V]
of
vertices, or false
if no simple cycle through V
exists. Notice that a
loop through V
is returned as list [V, V]
.
Tries to find an as short as possible simple path
from vertex V1
to vertex V2
of digraph G
. Returns the path as a list
[V1, ..., V2]
of vertices, or false
if no simple path from V1
to V2
of
length one or more exists.
Returns the in-degree of vertex V
of digraph G
.
Returns a list of all edges incident on V
of digraph
G
, in some unspecified order.
Returns a list of all in-neighbors of V
of digraph
G
, in some unspecified order.
Returns a list of {Tag, Value}
pairs describing digraph G
. The following
pairs are returned
Returns an empty digraph with properties according
to the options in Type
Returns the number of edges of digraph G
.
Returns the number of vertices of digraph G
.
Returns the out-degree of vertex V
of digraph G
.
Returns a list of all edges emanating from V
of digraph
G
, in some unspecified order.
Returns a list of all out-neighbors of V
of
digraph G
, in some unspecified order.
Returns {V, Label}
, where Label
is the label of the
vertex V
of digraph G
, or false
if no vertex V
of digraph G
exists.
Returns a list of all vertices of digraph G
, in some unspecified order.
Types
The error reason for when an edge could not be added to a graph.
If the edge would create a cycle in an
acyclic digraph, {error, {bad_edge, Path}}
is
returned. If G
already has an edge with value E
connecting a different pair
of vertices, {error, {bad_edge, [V1, V2]}}
is returned. If either of V1
or
V2
is not a vertex of digraph G
, {error, {bad_vertex,
V}}
is returned,
V = V1
or V = V2
.
-type d_cyclicity() :: acyclic | cyclic.
-type d_protection() :: private | protected.
-type d_type() :: d_cyclicity() | d_protection().
-type edge() :: term().
Serves as the identifier or "name" of an edge. This is distinct from an edge "label" which attaches ancillary information to the edge rather than identifying the edge itself.
-opaque graph()
A digraph as returned by new/0,1
.
-type label() :: term().
-type vertex() :: term().
Functions
-spec add_edge(G, V1, V2) -> edge() | {error, add_edge_err_rsn()} when G :: graph(), V1 :: vertex(), V2 :: vertex().
Equivalent to add_edge(G, V1, V2, [])
.
-spec add_edge(G, V1, V2, Label) -> edge() | {error, add_edge_err_rsn()} when G :: graph(), V1 :: vertex(), V2 :: vertex(), Label :: label().
Equivalent to add_edge(G, E, V1, V2, Label)
, where E
is a created edge.
The created edge is represented by term ['$e' | N]
, where N
is an integer >= 0.
See add_edge_err_rsn/0
for details on possible errors.
-spec add_edge(G, E, V1, V2, Label) -> edge() | {error, add_edge_err_rsn()} when G :: graph(), E :: edge(), V1 :: vertex(), V2 :: vertex(), Label :: label().
Creates (or modifies) an edge with the identifier
E
of digraph G
, using Label
as the (new) label of the
edge. The edge is emanating from V1
and
incident on V2
. Returns E
.
See add_edge_err_rsn/0
for details on possible errors.
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.
Equivalent to add_vertex(G, V, [])
.
Creates (or modifies) vertex V
of digraph G
, using Label
as the (new)
label of the vertex. Returns the new vertex V
.
Deletes edge E
from digraph G
.
Deletes the edges in list Edges
from digraph G
.
Deletes edges from digraph G
until there are no paths from
vertex V1
to vertex V2
.
A sketch of the procedure employed:
- Find an arbitrary simple path
v[1], v[2], ..., v[k] from
V1
toV2
inG
. - Remove all edges of
G
emanating from v[i] and incident to v[i+1] for 1 <= i < k (including multiple edges). - Repeat until there is no path between
V1
andV2
.
Deletes vertex V
from digraph G
. Any edges emanating
from V
or incident on V
are also deleted.
Deletes the vertices in list Vertices
from digraph G
.
-spec delete(G) -> true when G :: graph().
Deletes digraph G
. 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.
-spec edge(G, E) -> {E, V1, V2, Label} | false when G :: graph(), E :: edge(), V1 :: vertex(), V2 :: vertex(), Label :: label().
Returns {E, V1, V2, Label}
, where Label
is the label of
edge E
emanating from V1
and
incident on V2
of digraph G
. If no edge E
of
digraph G
exists, false
is returned.
Returns a list of all edges of digraph G
, in some unspecified order.
Returns a list of all edges emanating from or
incident on V
of digraph G
, in some unspecified
order.
-spec get_cycle(G, V) -> Vertices | false when G :: graph(), V :: vertex(), Vertices :: [vertex(), ...].
If a simple cycle of length two or more exists
through vertex V
, the cycle is returned as a list [V, ..., V]
of vertices.
If a loop through V
exists, the loop is returned as a list
[V]
. If no cycles through V
exist, false
is returned.
get_path/3
is used for finding a simple cycle through V
.
-spec get_path(G, V1, V2) -> Vertices | false when G :: graph(), V1 :: vertex(), V2 :: vertex(), Vertices :: [vertex(), ...].
Tries to find a simple path from vertex V1
to
vertex V2
of digraph G
. Returns the path as a list [V1, ..., V2]
of
vertices, or false
if no simple path from V1
to V2
of length one or more
exists.
Digraph G
is traversed in a depth-first manner, and the first found path is
returned.
-spec get_short_cycle(G, V) -> Vertices | false when G :: graph(), V :: vertex(), Vertices :: [vertex(), ...].
Tries to find an as short as possible simple cycle
through vertex V
of digraph G
. Returns the cycle as a list [V, ..., V]
of
vertices, or false
if no simple cycle through V
exists. Notice that a
loop through V
is returned as list [V, V]
.
get_short_path/3
is used for finding a simple cycle through V
.
-spec get_short_path(G, V1, V2) -> Vertices | false when G :: graph(), V1 :: vertex(), V2 :: vertex(), Vertices :: [vertex(), ...].
Tries to find an as short as possible simple path
from vertex V1
to vertex V2
of digraph G
. Returns the path as a list
[V1, ..., V2]
of vertices, or false
if no simple path from V1
to V2
of
length one or more exists.
Digraph G
is traversed in a breadth-first manner, and the first found path is
returned.
-spec in_degree(G, V) -> non_neg_integer() when G :: graph(), V :: vertex().
Returns the in-degree of vertex V
of digraph G
.
Returns a list of all edges incident on V
of digraph
G
, in some unspecified order.
Returns a list of all in-neighbors of V
of digraph
G
, in some unspecified order.
-spec info(G) -> InfoList when G :: graph(), InfoList :: [{cyclicity, Cyclicity :: d_cyclicity()} | {memory, NoWords :: non_neg_integer()} | {protection, Protection :: d_protection()}].
Returns a list of {Tag, Value}
pairs describing digraph G
. The following
pairs are returned:
{cyclicity, Cyclicity}
, whereCyclicity
iscyclic
oracyclic
, according to the options given tonew
.{memory, NoWords}
, whereNoWords
is the number of words allocated to the ETS tables.{protection, Protection}
, whereProtection
isprotected
orprivate
, according to the options given tonew
.
-spec new() -> graph().
Equivalent to new([])
.
Returns an empty digraph with properties according
to the options in Type
:
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 Type
is not a proper list,
a badarg
exception is raised.
-spec no_edges(G) -> non_neg_integer() when G :: graph().
Returns the number of edges of digraph G
.
-spec no_vertices(G) -> non_neg_integer() when G :: graph().
Returns the number of vertices of digraph G
.
-spec out_degree(G, V) -> non_neg_integer() when G :: graph(), V :: vertex().
Returns the out-degree of vertex V
of digraph G
.
Returns a list of all edges emanating from V
of digraph
G
, in some unspecified order.
Returns a list of all out-neighbors of V
of
digraph G
, in some unspecified order.
Returns {V, Label}
, where Label
is the label of the
vertex V
of digraph G
, or false
if no vertex V
of digraph G
exists.
Returns a list of all vertices of digraph G
, in some unspecified order.