graph (stdlib v7.2-rc0)
View SourceA functional implementation of labeled directed graphs.
This module is closely modelled on the digraph and digraph_utils
modules, which represent graphs using mutable ETS tables. This functional
implementation is more lightweight and does not involve mutable state and
table ownership, and makes it easy to keep multiple versions of a graph, but
for large tables with a long lifetime, the ETS based implementation can be
more suitable. In the context of this module, we only use the term "digraph"
when referring to the digraph implementation, and not to directed graphs
in general.
When rewriting code from using digraph to using graph, keep in mind that:
- Graphs are immutable: each modifying operation returns the new graph,
which needs to be saved in a variable and passed to the next operation,
for example
G0 = graph:new(), G1 = graph:add_vertex(G0, v1), G2 = graph:add_vertex(G1, v2). - Graphs are garbage collected and do not need to be explicitly deleted.
- There are no
protectedorprivateoptions and nomemoryinfo key. - Edges are not objects with identity and state. An edge is uniquely
identified by the triple
{From, To, Label}where the default label is[]. There can be multiple edges with the sameFromandTobut only if they have different values forLabel. - Vertices, however, have a unique identifier just as in
digraph. The label of an existing vertex can be replaced by a new call toadd_vertex(Id, Label). The label defaults to[]. - The functions in
digraph_utilshave been included directly in thegraphmodule for simplicity.
Some graph theoretical definitions:
A directed graph (here simply called "graph") is a pair (V, E) of a finite set V of vertices and a finite set E of directed edges (here simply called "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 graph is called the empty graph. Each vertex has a unique Erlang term as identifier.
Graphs can be annotated with more information. Such information can be attached to the vertices and to the edges of the graph. An annotated graph is called a labeled graph, 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 subgraph G' of G is a graph whose vertices and edges form subsets of the vertices and edges of G.
G' is maximal with respect to a property P if all other subgraphs that include the vertices of G' do not have property P.
A path P from v[1] to v[k] in a graph (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 graph is a graph without cycles.
A tree is an acyclic non-empty graph such that there is a unique path between every pair of vertices, considering all edges undirected. In an undirected tree, any vertex can be used as root. Informally however, "tree" is often used to refer to mean an out-tree (arborescence), in particular in computer science.
An arborescence or directed rooted tree or out-tree is an acyclic directed graph with a vertex V, the root, such that there is a unique path from V to every other vertex of G.
A forest is a disjoint union of trees.
A strongly connected component is a maximal subgraph such that there is a path between each pair of vertices.
A connected component is a maximal subgraph such that there is a path between each pair of vertices, considering all edges undirected.
This module also provides algorithms based on depth-first traversal of directed graphs.
- A depth-first traversal of a directed graph can be viewed as a process that visits all vertices of the graph. Initially, all vertices are marked as unvisited. The traversal starts with an arbitrarily chosen vertex, which is marked as visited, and follows an edge to an unmarked vertex, marking that vertex. The search then proceeds from that vertex in the same fashion, until there is no edge leading to an unvisited vertex. At that point the process backtracks, and the traversal continues as long as there are unexamined edges. If unvisited vertices remain when all edges from the first vertex have been examined, some so far unvisited vertex is chosen, and the process is repeated.
- A partial ordering of a set S is a transitive, antisymmetric, and reflexive relation between the objects of S.
- The problem of topological sorting
is to find a total ordering of S that is a superset of the partial ordering.
A graph G = (V, E) is equivalent to a relation E on V (we neglect that
the version of directed graphs provided by the
digraphmodule allows multiple edges between vertices). If the graph has no cycles of length two or more, the reflexive and transitive closure of E is a partial ordering.
Summary
Functions
Equivalent to add_edge(G, V1, V2, []).
Creates an edge {V1, V2, L} in graph G.
Adds a new vertex to graph G, returning the created vertex id.
Equivalent to add_vertex(G, V, []).
Creates or modifies vertex V of graph G, using L as the (new)
label of the vertex.
Returns {yes, V} if G is an arborescence (a
directed tree) with vertex V as the root, otherwise no.
Returns a list of connected components.
Creates a graph where the vertices are the strongly connected
components of G as returned by
strong_components/1.
Returns a list of cyclic strongly connected components.
Deletes edge E from graph G.
Deletes the edges in list Es from graph G.
Deletes all edges from vertex V1 to vertex V2 in graph G.
Deletes edges from graph G until there are no paths from
vertex V1 to vertex V2.
Deletes vertex V from graph G.
Deletes the vertices in list Vs from graph G.
Returns a list of all edges of graph G, in some unspecified order.
Returns the ordered set of edges from V1 to V2.
Fold Fun over the vertices of graph G, in some unspecified order.
Tries to find a cycle in G which includes vertex V.
Tries to find a simple path from vertex V1 to
vertex V2 of graph G.
Like get_cycle/2, but a cycle of length one is preferred.
Like get_path/3, but using a breadth-first search to find a short path.
Returns true if and only if G contains edge E.
Returns true if and only if G contains some edge from V1 to V2.
Returns true if and only if there is a path in G from
vertex V1 to vertex V2.
Returns true if and only if G contains vertex V.
Returns the in-degree of vertex V of graph G.
Returns a list of all edges incident on V of graph
G, in some unspecified order.
Returns a list of all in-neighbors of V of graph
G, in some unspecified order.
Returns a list of {Tag, Value} pairs describing graph G.
Returns true if and only if graph G is
acyclic.
Returns true if and only if graph G is an
arborescence (a directed tree with a unique root).
Returns true if and only if graph G is a
tree, considering all edges undirected.
Returns a list of all vertices of G that are included in some
loop.
Creates a new graph.
Returns the number of edges of graph G.
Returns the number of vertices of graph G.
Returns the out-degree of vertex V of graph G.
Returns a list of all edges emanating from V of graph
G, in some unspecified order.
Returns a list of all out-neighbors of V of
graph G, in some unspecified order.
Equivalent to postorder(G, roots(G)).
Returns the vertices of graph G reachable from Vs, listed in post-order.
Equivalent to preorder(G, roots(G)).
Returns all vertices of graph G reachable from Vs, listed in pre-order.
Returns an unsorted list of graph vertices such that for each vertex in the
list, there is a path in G from some vertex of Vs to
the vertex.
Returns an unsorted list of graph vertices such that for each vertex in the
list, there is a path in G of length one or more from
some vertex of Vs to the vertex.
Returns an unsorted list of graph vertices such that for each vertex in the
list, there is a path from the vertex to some vertex of
Vs.
Returns an unsorted list of graph vertices such that for each vertex in the
list, there is a path of length one or more from the
vertex to some vertex of Vs.
Equivalent to reverse_postorder(G, roots(G)).
Returns the vertices of graph G reachable from Vs, listed in reverse
post-order.
Returns a minimal list of vertices of G from which all vertices of G can
be reached.
Returns a list of all vertices of graph G with
out-degree zero.
Returns a list of all vertices of graph G with
in-degree zero.
Returns a list of strongly connected components.
Equivalent to subgraph(G, Vs, []).
Creates a maximal subgraph of G restricted to the
vertices listed in Vs.
Returns a topological ordering of the vertices of graph
G if such an ordering exists, otherwise false.
Returns the label of the vertex V of graph G.
Returns the label of the vertex V of graph G,
or returns Default if V does not exist in G.
Returns a list of all vertices of graph G, in some unspecified order.
Returns a list of all pairs {V, L} of vertices of graph G and their
respective labels, in some unspecified order.
Types
-type edge_map() :: #{vertex() => ordsets:ordset(vertex())}.
-type graph() :: #graph{vs :: vertice_map(), in_es :: edge_map(), out_es :: edge_map(), cyclic :: boolean(), next_vid :: non_neg_integer()}.
-type graph_cyclicity() :: acyclic | cyclic.
-type graph_type() :: graph_cyclicity().
-type label() :: term().
-type vertex() :: term().
Functions
Equivalent to add_edge(G, V1, V2, []).
-spec add_edge(G, V1, V2, L) -> graph() when G :: graph(), V1 :: vertex(), V2 :: vertex(), L :: label().
Creates an edge {V1, V2, L} in graph G.
The edge is emanating from V1 and
incident on V2, and has label
L. The edge is uniquely identified by this triple. A graph can have
multiple edges between the same vertices V1 and V2 but only if the
edges have different labels.
If G was created with option acyclic, then attempting to add an edge that
would introduce a cycle will raise an error {bad_edge, {From, To}}. Note
that checking for cyclicity slows down the adding of edges.
Adds a new vertex to graph G, returning the created vertex id.
The new vertex will have the empty list [] as label.
Note: Vertex ID:s are assigned as integers in increasing order starting from
zero. If you use add_vertex/2 or add_vertex/3 to insert vertices with
your own identifiers, this function could generate an ID that already exists
in the graph.
Equivalent to add_vertex(G, V, []).
Creates or modifies vertex V of graph G, using L as the (new)
label of the vertex.
Returns {yes, V} if G is an arborescence (a
directed tree) with vertex V as the root, otherwise no.
Returns a list of connected components.
Each component is represented by its vertices. The order of the vertices
and the order of the components are arbitrary. Each vertex of graph G
occurs in exactly one component.
Creates a graph where the vertices are the strongly connected
components of G as returned by
strong_components/1.
If X and Y are two different strongly connected components, and vertices x and y exist in X and Y, respectively, such that there is an edge emanating from x and incident on y, then an edge emanating from X and incident on Y is created.
The created graph has the same type as G. All vertices and edges have
the default label [].
Each cycle is included in some strongly connected component, which implies that a topological ordering of the created graph always exists.
Returns a list of cyclic strongly connected components.
Each strongly component is represented by its vertices. The order of the
vertices and the order of the components are arbitrary. Only vertices
that are included in some cycle in G are returned,
otherwise the returned list is equal to that returned by
strong_components/1.
Deletes edge E from graph G.
Deletes the edges in list Es from graph G.
Deletes all edges from vertex V1 to vertex V2 in graph G.
Deletes edges from graph 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
V1toV2inG. - Remove all edges of
Gemanating from v[i] and incident to v[i+1] for 1 <= i < k (including multiple edges). - Repeat until there is no path between
V1andV2.
Deletes vertex V from graph G.
Any edges emanating from V or
incident on V are also deleted.
Deletes the vertices in list Vs from graph G.
Returns a list of all edges of graph G, in some unspecified order.
Returns a list of all edges emanating from or
incident on V of graph G, in some unspecified
order.
Edges may occur twice in the list. Use ordsets:from_list/1 on the
result if you need to remove duplicates.
-spec edges(G :: graph(), V1 :: vertex(), V2 :: vertex()) -> ordsets:ordset(edge()).
Returns the ordered set of edges from V1 to V2.
-spec fold_vertices(G, Fun, Acc) -> any() when G :: graph(), Fun :: fun((vertex(), label(), any()) -> any()), Acc :: any().
Fold Fun over the vertices of graph G, in some unspecified order.
Tries to find a cycle in G which includes vertex V.
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 graph 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.
The graph is traversed in a depth-first manner, and the first found path is returned.
Like get_cycle/2, but a cycle of length one is preferred.
Tries to find an as short as possible simple
cycle through vertex V of graph 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].
Like get_path/3, but using a breadth-first search to find a short path.
Tries to find an as short as possible simple path
from vertex V1 to vertex V2 of graph 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.
Graph G is traversed in a breadth-first manner, and the first found path is
returned.
Returns true if and only if G contains edge E.
Note that the identity of an edge includes its label. To check for an
arbitrary edge between two vertices, use has_edge/3.
Returns true if and only if G contains some edge from V1 to V2.
Returns true if and only if there is a path in G from
vertex V1 to vertex V2.
Returns true if and only if G contains vertex V.
-spec in_degree(G :: graph(), V :: vertex()) -> non_neg_integer().
Returns the in-degree of vertex V of graph G.
Returns a list of all edges incident on V of graph
G, in some unspecified order.
Returns a list of all in-neighbors of V of graph
G, in some unspecified order.
-spec info(graph()) -> [{cyclicity, graph_cyclicity()}].
Returns a list of {Tag, Value} pairs describing graph G.
The following pairs are returned:
{cyclicity, Cyclicity}, whereCyclicityiscyclicoracyclic, according to the options given tonew.
Returns true if and only if graph G is
acyclic.
Returns true if and only if graph G is an
arborescence (a directed tree with a unique root).
Returns true if and only if graph G is a
tree, considering all edges undirected.
Returns a list of all vertices of G that are included in some
loop.
-spec new() -> graph().
Equivalent to new([]).
-spec new([graph_type()]) -> graph().
Creates a new graph.
Returns an empty graph with properties according to
the options in Options:
cyclic- Allows cycles in the graph (default).acyclic- The graph is to be kept acyclic. Attempting to add an edge that would introduce a cycle will raise an error{bad_edge, {From, To}}. Note that this slows down the adding of edges.
If an unrecognized option is specified or Options is not a proper list, a
badarg exception is raised.
-spec no_edges(G :: graph()) -> non_neg_integer().
Returns the number of edges of graph G.
-spec no_vertices(G :: graph()) -> non_neg_integer().
Returns the number of vertices of graph G.
-spec out_degree(G :: graph(), V :: vertex()) -> non_neg_integer().
Returns the out-degree of vertex V of graph G.
Returns a list of all edges emanating from V of graph
G, in some unspecified order.
Returns a list of all out-neighbors of V of
graph G, in some unspecified order.
Equivalent to postorder(G, roots(G)).
Returns the vertices of graph G reachable from Vs, listed in post-order.
The order is given by a depth-first traversal of the graph, collecting visited vertices in postorder. More precisely, the vertices visited while searching from an arbitrarily chosen vertex are collected in postorder, and all those collected vertices are placed before the subsequently visited vertices.
Equivalent to preorder(G, roots(G)).
Returns all vertices of graph G reachable from Vs, listed in pre-order.
The order is given by a depth-first traversal of the graph, collecting visited vertices in preorder.
Returns an unsorted list of graph vertices such that for each vertex in the
list, there is a path in G from some vertex of Vs to
the vertex.
In particular, as paths can have length zero, the vertices of Vs are all
included in the returned list.
Returns an unsorted list of graph vertices such that for each vertex in the
list, there is a path in G of length one or more from
some vertex of Vs to the vertex.
Hence, vertices in Vs will only be included in the result if they are part
of some cycle.
Returns an unsorted list of graph vertices such that for each vertex in the
list, there is a path from the vertex to some vertex of
Vs.
In particular, as paths can have length zero, the vertices of Vs are all
included in the returned list.
Returns an unsorted list of graph vertices such that for each vertex in the
list, there is a path of length one or more from the
vertex to some vertex of Vs.
Hence, vertices in Vs will only be included in the result if they are part
of some cycle.
Equivalent to reverse_postorder(G, roots(G)).
Returns the vertices of graph G reachable from Vs, listed in reverse
post-order.
This effectively performs a topological sort of the reachable nodes.
The graph is traversed as for postorder/2, but producing the result in
reverse order.
Returns a minimal list of vertices of G from which all vertices of G can
be reached.
Returns a list of all vertices of graph G with
out-degree zero.
Returns a list of all vertices of graph G with
in-degree zero.
Returns a list of strongly connected components.
Each strongly component is represented by its vertices. The order of the
vertices and the order of the components are arbitrary. Each vertex of
graph G occurs in exactly one strong component.
Equivalent to subgraph(G, Vs, []).
-spec subgraph(graph(), [vertex()], Options) -> graph() when Options :: [{type, SubgraphType} | {keep_labels, boolean()}], SubgraphType :: inherit | [graph_type()].
Creates a maximal subgraph of G restricted to the
vertices listed in Vs.
If the value of option type is inherit, which is the default, the type
of G is used for the subgraph as well (for example, whether the graph
allows cycles). Otherwise the value of the type option is used as argument
to new/1.
If the value of option keep_labels is true, which is the default, the
labels of vertices and edges of G are used for the
subgraph as well. If the value is false, the vertices and edges of the
subgraph will have the default labels.
If any of the arguments are invalid, a badarg exception is raised.
Returns a topological ordering of the vertices of graph
G if such an ordering exists, otherwise false.
For each vertex in the returned list, no out-neighbors occur earlier in the list.
This is currently implemented simply as reverse_postorder(G), but this
detail is subject to change and should not be relied on.
Returns the label of the vertex V of graph G.
An exception is raised if V does not exist in G.
Returns the label of the vertex V of graph G,
or returns Default if V does not exist in G.
Returns a list of all vertices of graph G, in some unspecified order.
Returns a list of all pairs {V, L} of vertices of graph G and their
respective labels, in some unspecified order.