| Copyright | (c) Andrey Mokhov 2016-2018 |
|---|---|
| License | MIT (see the file LICENSE) |
| Maintainer | andrey.mokhov@gmail.com |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Algebra.Graph.ToGraph
Description
Alga is a library for algebraic construction and manipulation of graphs in Haskell. See this paper for the motivation behind the library, the underlying theory, and implementation details.
This module defines the type class ToGraph for capturing data types that
can be converted to algebraic graphs. To make an instance of this class you
need to define just a single method (toGraph or foldg), which gives you
access to many other useful methods for free. This type class is similar to
the standard Data.Foldable defined for lists.
Documentation
class ToGraph t where Source #
The ToGraph type class captures data types that can be converted to
algebraic graphs.
Methods
toGraph :: t -> Graph (ToVertex t) Source #
Convert a value to the corresponding algebraic graph, see Algebra.Graph.
toGraph ==foldgEmptyVertexOverlayConnect
foldg :: r -> (ToVertex t -> r) -> (r -> r -> r) -> (r -> r -> r) -> t -> r Source #
The method foldg is used for generalised graph folding. It collapses
a given value by applying the provided graph construction primitives. The
order of arguments is: empty, vertex, overlay and connect, and it is
assumed that the arguments satisfy the axioms of the graph algebra.
foldg == Algebra.Graph.foldg.toGraph
Check if a graph is empty.
isEmpty == foldg True (const False) (&&) (&&)
The size of a graph, i.e. the number of leaves of the expression
including empty leaves.
size == foldg 1 (const 1) (+) (+)
hasVertex :: Eq (ToVertex t) => ToVertex t -> t -> Bool Source #
Check if a graph contains a given vertex.
hasVertex x == foldg False (==x) (||) (||)
hasEdge :: Eq (ToVertex t) => ToVertex t -> ToVertex t -> t -> Bool Source #
vertexCount :: Ord (ToVertex t) => t -> Int Source #
edgeCount :: Ord (ToVertex t) => t -> Int Source #
vertexList :: Ord (ToVertex t) => t -> [ToVertex t] Source #
edgeList :: Ord (ToVertex t) => t -> [(ToVertex t, ToVertex t)] Source #
vertexSet :: Ord (ToVertex t) => t -> Set (ToVertex t) Source #
vertexIntSet :: ToVertex t ~ Int => t -> IntSet Source #
The set of vertices of a graph. Like vertexSet but specialised for
graphs with vertices of type Int.
vertexIntSet ==foldgIntSet.emptyIntSet.singletonIntSet.unionIntSet.union
edgeSet :: Ord (ToVertex t) => t -> Set (ToVertex t, ToVertex t) Source #
The set of edges of a graph.
edgeSet == Algebra.Graph.AdjacencyMap.edgeSet.toAdjacencyMap
preSet :: Ord (ToVertex t) => ToVertex t -> t -> Set (ToVertex t) Source #
The preset of a vertex is the set of its direct predecessors.
preSet x == Algebra.Graph.AdjacencyMap.preSetx .toAdjacencyMap
preIntSet :: ToVertex t ~ Int => Int -> t -> IntSet Source #
The preset (here preIntSet) of a vertex is the set of its
direct predecessors. Like preSet but specialised for graphs with
vertices of type Int.
preIntSet x == Algebra.Graph.AdjacencyIntMap.preIntSetx .toAdjacencyIntMap
postSet :: Ord (ToVertex t) => ToVertex t -> t -> Set (ToVertex t) Source #
The postset of a vertex is the set of its direct successors.
postSet x == Algebra.Graph.AdjacencyMap.postSetx .toAdjacencyMap
postIntSet :: ToVertex t ~ Int => Int -> t -> IntSet Source #
The postset (here postIntSet) of a vertex is the set of its
direct successors. Like postSet but specialised for graphs with
vertices of type Int.
postIntSet x == Algebra.Graph.AdjacencyIntMap.postIntSetx .toAdjacencyIntMap
adjacencyList :: Ord (ToVertex t) => t -> [(ToVertex t, [ToVertex t])] Source #
The sorted adjacency list of a graph.
adjacencyList == Algebra.Graph.AdjacencyMap.adjacencyList.toAdjacencyMap
adjacencyMap :: Ord (ToVertex t) => t -> Map (ToVertex t) (Set (ToVertex t)) Source #
The adjacency map of a graph: each vertex is associated with a set of its direct successors.
adjacencyMap == Algebra.Graph.AdjacencyMap.adjacencyMap.toAdjacencyMap
adjacencyIntMap :: ToVertex t ~ Int => t -> IntMap IntSet Source #
The adjacency map of a graph: each vertex is associated with a set
of its direct successors. Like adjacencyMap but specialised for
graphs with vertices of type Int.
adjacencyIntMap == Algebra.Graph.AdjacencyIntMap.adjacencyIntMap.toAdjacencyIntMap
adjacencyMapTranspose :: Ord (ToVertex t) => t -> Map (ToVertex t) (Set (ToVertex t)) Source #
The transposed adjacency map of a graph: each vertex is associated with a set of its direct predecessors.
adjacencyMapTranspose == Algebra.Graph.AdjacencyMap.adjacencyMap.toAdjacencyMapTranspose
adjacencyIntMapTranspose :: ToVertex t ~ Int => t -> IntMap IntSet Source #
The transposed adjacency map of a graph: each vertex is associated
with a set of its direct predecessors. Like adjacencyMapTranspose but
specialised for graphs with vertices of type Int.
adjacencyIntMapTranspose == Algebra.Graph.AdjacencyIntMap.adjacencyIntMap.toAdjacencyIntMapTranspose
dfsForest :: Ord (ToVertex t) => t -> Forest (ToVertex t) Source #
Compute the depth-first search forest of a graph that corresponds to
searching from each of the graph vertices in the Ord a order.
dfsForest == Algebra.Graph.AdjacencyMap.dfsForest . toAdjacencyMap
dfsForestFrom :: Ord (ToVertex t) => [ToVertex t] -> t -> Forest (ToVertex t) Source #
Compute the depth-first search forest of a graph, searching from each of the given vertices in order. Note that the resulting forest does not necessarily span the whole graph, as some vertices may be unreachable.
dfsForestFrom vs == Algebra.Graph.AdjacencyMap.dfsForestFrom vs . toAdjacencyMap
dfs :: Ord (ToVertex t) => [ToVertex t] -> t -> [ToVertex t] Source #
Compute the list of vertices visited by the depth-first search in a graph, when searching from each of the given vertices in order.
dfs vs == Algebra.Graph.AdjacencyMap.dfs vs . toAdjacencyMap
reachable :: Ord (ToVertex t) => ToVertex t -> t -> [ToVertex t] Source #
Compute the list of vertices that are reachable from a given source vertex in a graph. The vertices in the resulting list appear in the depth-first order.
reachable x == Algebra.Graph.AdjacencyMap.reachable x . toAdjacencyMap
topSort :: Ord (ToVertex t) => t -> Maybe [ToVertex t] Source #
Compute the topological sort of a graph or return Nothing if the
graph is cyclic.
topSort == Algebra.Graph.AdjacencyMap.topSort . toAdjacencyMap
isAcyclic :: Ord (ToVertex t) => t -> Bool Source #
Check if a given graph is acyclic.
isAcyclic == Algebra.Graph.AdjacencyMap.isAcyclic . toAdjacencyMap
toAdjacencyMap :: Ord (ToVertex t) => t -> AdjacencyMap (ToVertex t) Source #
Convert a value to the corresponding AdjacencyMap.
toAdjacencyMap ==foldgemptyvertexoverlayconnect
toAdjacencyMapTranspose :: Ord (ToVertex t) => t -> AdjacencyMap (ToVertex t) Source #
Convert a value to the corresponding AdjacencyMap and transpose the
result.
toAdjacencyMapTranspose ==foldgemptyvertexoverlay(flipconnect)
toAdjacencyIntMap :: ToVertex t ~ Int => t -> AdjacencyIntMap Source #
Convert a value to the corresponding AdjacencyIntMap.
toAdjacencyIntMap ==foldgemptyvertexoverlayconnect
toAdjacencyIntMapTranspose :: ToVertex t ~ Int => t -> AdjacencyIntMap Source #
Convert a value to the corresponding AdjacencyIntMap and transpose
the result.
toAdjacencyIntMapTranspose ==foldgemptyvertexoverlay(flipconnect)
isDfsForestOf :: Ord (ToVertex t) => Forest (ToVertex t) -> t -> Bool Source #
Check if a given forest is a valid depth-first search forest of a graph.
isDfsForestOf f == Algebra.Graph.AdjacencyMap.isDfsForestOf f . toAdjacencyMap
isTopSortOf :: Ord (ToVertex t) => [ToVertex t] -> t -> Bool Source #
Check if a given list of vertices is a valid topological sort of a graph.
isTopSortOf vs == Algebra.Graph.AdjacencyMap.isTopSortOf vs . toAdjacencyMap