algebraic-graphs-0.7: A library for algebraic graph construction and transformation
Copyright(c) Anton Lorenzen Andrey Mokhov 2016-2022
LicenseMIT (see the file LICENSE)
Maintaineranfelor@posteo.de, andrey.mokhov@gmail.com
Stabilityunstable
Safe HaskellNone
LanguageHaskell2010

Data.Graph.Typed

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 provides primitives for interoperability between this library and the Data.Graph module of the containers library. It is for internal use only and may be removed without notice at any point.

Synopsis

Data type and construction

data GraphKL a Source #

GraphKL encapsulates King-Launchbury graphs, which are implemented in the Data.Graph module of the containers library.

Constructors

GraphKL 

Fields

fromAdjacencyMap :: Ord a => AdjacencyMap a -> GraphKL a Source #

Build GraphKL from an AdjacencyMap. If fromAdjacencyMap g == h then the following holds:

map (fromVertexKL h) (vertices $ toGraphKL h)                               == vertexList g
map (\(x, y) -> (fromVertexKL h x, fromVertexKL h y)) (edges $ toGraphKL h) == edgeList g
toGraphKL (fromAdjacencyMap (1 * 2 + 3 * 1))                                == array (0,2) [(0,[1]), (1,[]), (2,[0])]
toGraphKL (fromAdjacencyMap (1 * 2 + 2 * 1))                                == array (0,1) [(0,[1]), (1,[0])]

fromAdjacencyIntMap :: AdjacencyIntMap -> GraphKL Int Source #

Build GraphKL from an AdjacencyIntMap. If fromAdjacencyIntMap g == h then the following holds:

map (fromVertexKL h) (vertices $ toGraphKL h)                               == toAscList (vertexIntSet g)
map (\(x, y) -> (fromVertexKL h x, fromVertexKL h y)) (edges $ toGraphKL h) == edgeList g
toGraphKL (fromAdjacencyIntMap (1 * 2 + 3 * 1))                             == array (0,2) [(0,[1]), (1,[]), (2,[0])]
toGraphKL (fromAdjacencyIntMap (1 * 2 + 2 * 1))                             == array (0,1) [(0,[1]), (1,[0])]

Basic algorithms

dfsForest :: GraphKL a -> Forest a Source #

Compute the depth-first search forest of a graph.

In the following examples we will use the helper function:

(%) :: Ord a => (GraphKL a -> b) -> AdjacencyMap a -> b
f % x = f (fromAdjacencyMap x)

for greater clarity.

forest (dfsForest % edge 1 1)           == vertex 1
forest (dfsForest % edge 1 2)           == edge 1 2
forest (dfsForest % edge 2 1)           == vertices [1,2]
isSubgraphOf (forest $ dfsForest % x) x == True
dfsForest % forest (dfsForest % x)      == dfsForest % x
dfsForest % vertices vs                 == map (\v -> Node v []) (nub $ sort vs)
dfsForest % (3 * (1 + 4) * (1 + 5))     == [ Node { rootLabel = 1
                                                  , subForest = [ Node { rootLabel = 5
                                                                       , subForest = [] }]}
                                           , Node { rootLabel = 3
                                                  , subForest = [ Node { rootLabel = 4
                                                                       , subForest = [] }]}]

dfsForestFrom :: GraphKL a -> [a] -> Forest a 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.

In the following examples we will use the helper function:

(%) :: Ord a => (GraphKL a -> b) -> AdjacencyMap a -> b
f % x = f (fromAdjacencyMap x)

for greater clarity.

forest $ (dfsForestFrom % edge 1 1) [1]          == vertex 1
forest $ (dfsForestFrom % edge 1 2) [0]          == empty
forest $ (dfsForestFrom % edge 1 2) [1]          == edge 1 2
forest $ (dfsForestFrom % edge 1 2) [2]          == vertex 2
forest $ (dfsForestFrom % edge 1 2) [2,1]        == vertices [1,2]
isSubgraphOf (forest $ dfsForestFrom % x $ vs) x == True
dfsForestFrom % x $ vertexList x                 == dfsForest % x
dfsForestFrom % vertices vs $ vs                 == map (\v -> Node v []) (nub vs)
dfsForestFrom % x $ []                           == []
dfsForestFrom % (3 * (1 + 4) * (1 + 5)) $ [1,4]  == [ Node { rootLabel = 1
                                                           , subForest = [ Node { rootLabel = 5
                                                                                , subForest = [] }
                                                    , Node { rootLabel = 4
                                                           , subForest = [] }]

dfs :: GraphKL a -> [a] -> [a] 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.

In the following examples we will use the helper function:

(%) :: Ord a => (GraphKL a -> b) -> AdjacencyMap a -> b
f % x = f (fromAdjacencyMap x)

for greater clarity.

dfs % edge 1 1 $ [1]   == [1]
dfs % edge 1 2 $ [0]   == []
dfs % edge 1 2 $ [1]   == [1,2]
dfs % edge 1 2 $ [2]   == [2]
dfs % edge 1 2 $ [1,2] == [1,2]
dfs % edge 1 2 $ [2,1] == [2,1]
dfs % x        $ []    == []

dfs % (3 * (1 + 4) * (1 + 5)) $ [1,4]     == [1,5,4]
and [ hasVertex v x | v <- dfs % x $ vs ] == True

topSort :: GraphKL a -> [a] Source #

Compute the topological sort of a graph. Note that this function returns a result even if the graph is cyclic.

In the following examples we will use the helper function:

(%) :: Ord a => (GraphKL a -> b) -> AdjacencyMap a -> b
f % x = f (fromAdjacencyMap x)

for greater clarity.

topSort % (1 * 2 + 3 * 1) == [3,1,2]
topSort % (1 * 2 + 2 * 1) == [1,2]