----------------------------------------------------------------------------- -- | -- Module : Algebra.Graph.Relation -- Copyright : (c) Andrey Mokhov 2016-2017 -- License : MIT (see the file LICENSE) -- Maintainer : andrey.mokhov@gmail.com -- Stability : experimental -- -- __Alga__ is a library for algebraic construction and manipulation of graphs -- in Haskell. See for the -- motivation behind the library, the underlying theory, and implementation details. -- -- This module defines the 'Relation' data type, as well as associated -- operations and algorithms. 'Relation' is an instance of the 'C.Graph' type -- class, which can be used for polymorphic graph construction and manipulation. ----------------------------------------------------------------------------- module Algebra.Graph.Relation ( -- * Data structure Relation, domain, relation, -- * Basic graph construction primitives empty, vertex, edge, overlay, connect, vertices, edges, overlays, connects, graph, fromAdjacencyList, -- * Relations on graphs isSubgraphOf, -- * Graph properties isEmpty, hasVertex, hasEdge, vertexCount, edgeCount, vertexList, edgeList, vertexSet, vertexIntSet, edgeSet, preset, postset, -- * Standard families of graphs path, circuit, clique, biclique, star, tree, forest, -- * Graph transformation removeVertex, removeEdge, replaceVertex, mergeVertices, gmap, induce, -- * Operations on binary relations reflexiveClosure, symmetricClosure, transitiveClosure, preorderClosure ) where import Algebra.Graph.Relation.Internal import qualified Algebra.Graph.Class as C import qualified Data.IntSet as IntSet import qualified Data.Set as Set import qualified Data.Tree as Tree -- | Construct the graph comprising /a single edge/. -- Complexity: /O(1)/ time, memory and size. -- -- @ -- edge x y == 'connect' ('vertex' x) ('vertex' y) -- 'hasEdge' x y (edge x y) == True -- 'edgeCount' (edge x y) == 1 -- 'vertexCount' (edge 1 1) == 1 -- 'vertexCount' (edge 1 2) == 2 -- @ edge :: Ord a => a -> a -> Relation a edge = C.edge -- | Overlay a given list of graphs. -- Complexity: /O((n + m) * log(n))/ time and /O(n + m)/ memory. -- -- @ -- overlays [] == 'empty' -- overlays [x] == x -- overlays [x,y] == 'overlay' x y -- 'isEmpty' . overlays == 'all' 'isEmpty' -- @ overlays :: Ord a => [Relation a] -> Relation a overlays = C.overlays -- | Connect a given list of graphs. -- Complexity: /O((n + m) * log(n))/ time and /O(n + m)/ memory. -- -- @ -- connects [] == 'empty' -- connects [x] == x -- connects [x,y] == 'connect' x y -- 'isEmpty' . connects == 'all' 'isEmpty' -- @ connects :: Ord a => [Relation a] -> Relation a connects = C.connects -- | Construct the graph from given lists of vertices /V/ and edges /E/. -- The resulting graph contains the vertices /V/ as well as all the vertices -- referred to by the edges /E/. -- Complexity: /O((n + m) * log(n))/ time and /O(n + m)/ memory. -- -- @ -- graph [] [] == 'empty' -- graph [x] [] == 'vertex' x -- graph [] [(x,y)] == 'edge' x y -- graph vs es == 'overlay' ('vertices' vs) ('edges' es) -- @ graph :: Ord a => [a] -> [(a, a)] -> Relation a graph = C.graph -- | The 'isSubgraphOf' function takes two graphs and returns 'True' if the -- first graph is a /subgraph/ of the second. -- Complexity: /O((n + m) * log(n))/ time. -- -- @ -- isSubgraphOf 'empty' x == True -- isSubgraphOf ('vertex' x) 'empty' == False -- isSubgraphOf x ('overlay' x y) == True -- isSubgraphOf ('overlay' x y) ('connect' x y) == True -- isSubgraphOf ('path' xs) ('circuit' xs) == True -- @ isSubgraphOf :: Ord a => Relation a -> Relation a -> Bool isSubgraphOf x y = domain x `Set.isSubsetOf` domain y && relation x `Set.isSubsetOf` relation y -- | Check if a relation is empty. -- Complexity: /O(1)/ time. -- -- @ -- isEmpty 'empty' == True -- isEmpty ('overlay' 'empty' 'empty') == True -- isEmpty ('vertex' x) == False -- isEmpty ('removeVertex' x $ 'vertex' x) == True -- isEmpty ('removeEdge' x y $ 'edge' x y) == False -- @ isEmpty :: Relation a -> Bool isEmpty = null . domain -- | Check if a graph contains a given vertex. -- Complexity: /O(log(n))/ time. -- -- @ -- hasVertex x 'empty' == False -- hasVertex x ('vertex' x) == True -- hasVertex x . 'removeVertex' x == const False -- @ hasVertex :: Ord a => a -> Relation a -> Bool hasVertex x = Set.member x . domain -- | Check if a graph contains a given edge. -- Complexity: /O(log(n))/ time. -- -- @ -- hasEdge x y 'empty' == False -- hasEdge x y ('vertex' z) == False -- hasEdge x y ('edge' x y) == True -- hasEdge x y . 'removeEdge' x y == const False -- @ hasEdge :: Ord a => a -> a -> Relation a -> Bool hasEdge x y = Set.member (x, y) . relation -- | The number of vertices in a graph. -- Complexity: /O(1)/ time. -- -- @ -- vertexCount 'empty' == 0 -- vertexCount ('vertex' x) == 1 -- vertexCount == 'length' . 'vertexList' -- @ vertexCount :: Ord a => Relation a -> Int vertexCount = Set.size . domain -- | The number of edges in a graph. -- Complexity: /O(1)/ time. -- -- @ -- edgeCount 'empty' == 0 -- edgeCount ('vertex' x) == 0 -- edgeCount ('edge' x y) == 1 -- edgeCount == 'length' . 'edgeList' -- @ edgeCount :: Ord a => Relation a -> Int edgeCount = Set.size . relation -- | The sorted list of vertices of a given graph. -- Complexity: /O(n)/ time and memory. -- -- @ -- vertexList 'empty' == [] -- vertexList ('vertex' x) == [x] -- vertexList . 'vertices' == 'Data.List.nub' . 'Data.List.sort' -- @ vertexList :: Ord a => Relation a -> [a] vertexList = Set.toAscList . domain -- | The set of vertices of a given graph. -- Complexity: /O(1)/ time. -- -- @ -- vertexSet 'empty' == Set.'Set.empty' -- vertexSet . 'vertex' == Set.'Set.singleton' -- vertexSet . 'vertices' == Set.'Set.fromList' -- vertexSet . 'clique' == Set.'Set.fromList' -- @ vertexSet :: Ord a => Relation a -> Set.Set a vertexSet = domain -- | The set of vertices of a given graph. Like 'vertexSet' but specialised for -- graphs with vertices of type 'Int'. -- Complexity: /O(n)/ time. -- -- @ -- vertexIntSet 'empty' == IntSet.'IntSet.empty' -- vertexIntSet . 'vertex' == IntSet.'IntSet.singleton' -- vertexIntSet . 'vertices' == IntSet.'IntSet.fromList' -- vertexIntSet . 'clique' == IntSet.'IntSet.fromList' -- @ vertexIntSet :: Relation Int -> IntSet.IntSet vertexIntSet = IntSet.fromAscList . vertexList -- | The set of edges of a given graph. -- Complexity: /O(1)/ time. -- -- @ -- edgeSet 'empty' == Set.'Set.empty' -- edgeSet ('vertex' x) == Set.'Set.empty' -- edgeSet ('edge' x y) == Set.'Set.singleton' (x,y) -- edgeSet . 'edges' == Set.'Set.fromList' -- @ edgeSet :: Ord a => Relation a -> Set.Set (a, a) edgeSet = relation -- | The /path/ on a list of vertices. -- Complexity: /O((n + m) * log(n))/ time and /O(n + m)/ memory. -- -- @ -- path [] == 'empty' -- path [x] == 'vertex' x -- path [x,y] == 'edge' x y -- @ path :: Ord a => [a] -> Relation a path = C.path -- | The /circuit/ on a list of vertices. -- Complexity: /O((n + m) * log(n))/ time and /O(n + m)/ memory. -- -- @ -- circuit [] == 'empty' -- circuit [x] == 'edge' x x -- circuit [x,y] == 'edges' [(x,y), (y,x)] -- @ circuit :: Ord a => [a] -> Relation a circuit = C.circuit -- | The /clique/ on a list of vertices. -- Complexity: /O((n + m) * log(n))/ time and /O(n + m)/ memory. -- -- @ -- clique [] == 'empty' -- clique [x] == 'vertex' x -- clique [x,y] == 'edge' x y -- clique [x,y,z] == 'edges' [(x,y), (x,z), (y,z)] -- @ clique :: Ord a => [a] -> Relation a clique = C.clique -- | The /biclique/ on a list of vertices. -- Complexity: /O((n + m) * log(n))/ time and /O(n + m)/ memory. -- -- @ -- biclique [] [] == 'empty' -- biclique [x] [] == 'vertex' x -- biclique [] [y] == 'vertex' y -- biclique [x1,x2] [y1,y2] == 'edges' [(x1,y1), (x1,y2), (x2,y1), (x2,y2)] -- @ biclique :: Ord a => [a] -> [a] -> Relation a biclique = C.biclique -- | The /star/ formed by a centre vertex and a list of leaves. -- Complexity: /O((n + m) * log(n))/ time and /O(n + m)/ memory. -- -- @ -- star x [] == 'vertex' x -- star x [y] == 'edge' x y -- star x [y,z] == 'edges' [(x,y), (x,z)] -- @ star :: Ord a => a -> [a] -> Relation a star = C.star -- | The /tree graph/ constructed from a given 'Tree' data structure. -- Complexity: /O((n + m) * log(n))/ time and /O(n + m)/ memory. tree :: Ord a => Tree.Tree a -> Relation a tree = C.tree -- | The /forest graph/ constructed from a given 'Forest' data structure. -- Complexity: /O((n + m) * log(n))/ time and /O(n + m)/ memory. forest :: Ord a => Tree.Forest a -> Relation a forest = C.forest -- | The function @'replaceVertex' x y@ replaces vertex @x@ with vertex @y@ in a -- given 'AdjacencyMap'. If @y@ already exists, @x@ and @y@ will be merged. -- Complexity: /O((n + m) * log(n))/ time. -- -- @ -- replaceVertex x x == id -- replaceVertex x y ('vertex' x) == 'vertex' y -- replaceVertex x y == 'mergeVertices' (== x) y -- @ replaceVertex :: Ord a => a -> a -> Relation a -> Relation a replaceVertex u v = gmap $ \w -> if w == u then v else w -- | Merge vertices satisfying a given predicate with a given vertex. -- Complexity: /O((n + m) * log(n))/ time, assuming that the predicate takes -- /O(1)/ to be evaluated. -- -- @ -- mergeVertices (const False) x == id -- mergeVertices (== x) y == 'replaceVertex' x y -- mergeVertices even 1 (0 * 2) == 1 * 1 -- mergeVertices odd 1 (3 + 4 * 5) == 4 * 1 -- @ mergeVertices :: Ord a => (a -> Bool) -> a -> Relation a -> Relation a mergeVertices p v = gmap $ \u -> if p u then v else u