-----------------------------------------------------------------------------
-- |
-- Module     : Algebra.Graph.HigherKinded.Class
-- Copyright  : (c) Andrey Mokhov 2016-2022
-- 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 <https://github.com/snowleopard/alga-paper this paper> for the
-- motivation behind the library, the underlying theory, and implementation details.
--
-- This module defines the core type class 'Graph', a few graph subclasses, and
-- basic polymorphic graph construction primitives. Functions that cannot be
-- implemented fully polymorphically and require the use of an intermediate data
-- type are not included. For example, to compute the size of a 'Graph'
-- expression you will need to use a concrete data type, such as "Algebra.Graph".
--
-- See "Algebra.Graph.Class" for alternative definitions where the core type
-- class is not higher-kinded and permits more instances.
-----------------------------------------------------------------------------
module Algebra.Graph.HigherKinded.Class (
    -- * The core type class
    Graph (..), empty, vertex, overlay,

    -- * Undirected graphs
    Undirected,

    -- * Reflexive graphs
    Reflexive,

    -- * Transitive graphs
    Transitive,

    -- * Preorders
    Preorder,

    -- * Basic graph construction primitives
    edge, vertices, edges, overlays, connects,

    -- * Relations on graphs
    isSubgraphOf,

    -- * Graph properties
    hasEdge,

    -- * Standard families of graphs
    path, circuit, clique, biclique, star, stars, tree, forest, mesh, torus,
    deBruijn,

    -- * Graph transformation
    removeVertex, replaceVertex, mergeVertices, splitVertex, induce
    ) where

import Control.Applicative (Alternative(empty, (<|>)))
import Control.Monad (MonadPlus, mfilter)
import Data.Tree

import qualified Algebra.Graph as G

{-|
The core type class for constructing algebraic graphs is defined by introducing
the 'connect' method to the standard 'MonadPlus' class and reusing the following
existing methods:

* The 'empty' method comes from the 'Control.Applicative.Alternative' class and
corresponds to the /empty graph/. This module simply re-exports it.

* The 'vertex' graph construction primitive is an alias for 'pure' of the
'Applicative' type class.

* Graph 'overlay' is an alias for 'mplus' of the 'MonadPlus' type class.

The 'Graph' type class is characterised by the following minimal set of axioms.
In equations we use @+@ and @*@ as convenient shortcuts for 'overlay' and
'connect', respectively.

    * 'overlay' is commutative and associative:

        >       x + y == y + x
        > x + (y + z) == (x + y) + z

    * 'connect' is associative and has 'empty' as the identity:

        >   x * empty == x
        >   empty * x == x
        > x * (y * z) == (x * y) * z

    * 'connect' distributes over 'overlay':

        > x * (y + z) == x * y + x * z
        > (x + y) * z == x * z + y * z

    * 'connect' can be decomposed:

        > x * y * z == x * y + x * z + y * z

The following useful theorems can be proved from the above set of axioms.

    * 'overlay' has 'empty' as the identity and is idempotent:

        >   x + empty == x
        >   empty + x == x
        >       x + x == x

    * Absorption and saturation of 'connect':

        > x * y + x + y == x * y
        >     x * x * x == x * x

The core type class 'Graph' corresponds to unlabelled directed graphs.
'Undirected', 'Reflexive', 'Transitive' and 'Preorder' graphs can be obtained
by extending the minimal set of axioms.

When specifying the time and memory complexity of graph algorithms, /n/ will
denote the number of vertices in the graph, /m/ will denote the number of
edges in the graph, and /s/ will denote the /size/ of the corresponding
'Graph' expression.
-}
class MonadPlus g => Graph g where
    -- | Connect two graphs.
    connect :: g a -> g a -> g a

instance Graph G.Graph where
    connect :: Graph a -> Graph a -> Graph a
connect = Graph a -> Graph a -> Graph a
forall a. Graph a -> Graph a -> Graph a
G.connect

-- | Construct the graph comprising a single isolated vertex. An alias for 'pure'.
vertex :: Graph g => a -> g a
vertex :: a -> g a
vertex = a -> g a
forall (f :: * -> *) a. Applicative f => a -> f a
pure

-- | Overlay two graphs. An alias for '<|>'.
overlay :: Graph g => g a -> g a -> g a
overlay :: g a -> g a -> g a
overlay = g a -> g a -> g a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)

{-|
The class of /undirected graphs/ that satisfy the following additional axiom.

    * 'connect' is commutative:

        > x * y == y * x
-}
class Graph g => Undirected g

{-|
The class of /reflexive graphs/ that satisfy the following additional axiom.

    * Each vertex has a /self-loop/:

        > vertex x == vertex x * vertex x

    Or, alternatively, if we remember that 'vertex' is an alias for 'pure':

        > pure x == pure x * pure x

Note that by applying the axiom in the reverse direction, one can always remove
all self-loops resulting in an /irreflexive graph/. This type class can
therefore be also used in the context of irreflexive graphs.
-}
class Graph g => Reflexive g

{-|
The class of /transitive graphs/ that satisfy the following additional axiom.

    * The /closure/ axiom: graphs with equal transitive closures are equal.

        > y /= empty ==> x * y + x * z + y * z == x * y + y * z

By repeated application of the axiom one can turn any graph into its transitive
closure or transitive reduction.
-}
class Graph g => Transitive g

{-|
The class of /preorder graphs/ that are both reflexive and transitive.
-}
class (Reflexive g, Transitive g) => Preorder g

-- | Construct the graph comprising a single edge.
--
-- @
-- edge x y               == 'connect' ('vertex' x) ('vertex' y)
-- 'vertexCount' (edge 1 1) == 1
-- 'vertexCount' (edge 1 2) == 2
-- @
edge :: Graph g => a -> a -> g a
edge :: a -> a -> g a
edge a
x a
y = g a -> g a -> g a
forall (g :: * -> *) a. Graph g => g a -> g a -> g a
connect (a -> g a
forall (g :: * -> *) a. Graph g => a -> g a
vertex a
x) (a -> g a
forall (g :: * -> *) a. Graph g => a -> g a
vertex a
y)

-- | Construct the graph comprising a given list of isolated vertices.
-- Complexity: /O(L)/ time, memory and size, where /L/ is the length of the
-- given list.
--
-- @
-- vertices []            == 'empty'
-- vertices [x]           == 'vertex' x
-- vertices               == 'overlays' . map 'vertex'
-- 'hasVertex' x . vertices == 'elem' x
-- 'vertexCount' . vertices == 'length' . 'Data.List.nub'
-- 'vertexSet'   . vertices == Set.'Set.fromList'
-- @
vertices :: Graph g => [a] -> g a
vertices :: [a] -> g a
vertices []     = g a
forall (f :: * -> *) a. Alternative f => f a
empty
vertices [a
x]    = a -> g a
forall (g :: * -> *) a. Graph g => a -> g a
vertex a
x
vertices (a
x:[a]
xs) = a -> g a
forall (g :: * -> *) a. Graph g => a -> g a
vertex a
x g a -> g a -> g a
forall (g :: * -> *) a. Graph g => g a -> g a -> g a
`overlay` [a] -> g a
forall (g :: * -> *) a. Graph g => [a] -> g a
vertices [a]
xs

-- | Construct the graph from a list of edges.
-- Complexity: /O(L)/ time, memory and size, where /L/ is the length of the
-- given list.
--
-- @
-- edges []      == 'empty'
-- edges [(x,y)] == 'edge' x y
-- @
edges :: Graph g => [(a, a)] -> g a
edges :: [(a, a)] -> g a
edges = [g a] -> g a
forall (g :: * -> *) a. Graph g => [g a] -> g a
overlays ([g a] -> g a) -> ([(a, a)] -> [g a]) -> [(a, a)] -> g a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, a) -> g a) -> [(a, a)] -> [g a]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> a -> g a) -> (a, a) -> g a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry a -> a -> g a
forall (g :: * -> *) a. Graph g => a -> a -> g a
edge)

-- | Overlay a given list of graphs.
-- Complexity: /O(L)/ time and memory, and /O(S)/ size, where /L/ is the length
-- of the given list, and /S/ is the sum of sizes of the graphs in the list.
--
-- @
-- overlays []        == 'empty'
-- overlays [x]       == x
-- overlays [x,y]     == 'overlay' x y
-- overlays           == 'foldr' 'overlay' 'empty'
-- 'isEmpty' . overlays == 'all' 'isEmpty'
-- @
overlays :: Graph g => [g a] -> g a
overlays :: [g a] -> g a
overlays []     = g a
forall (f :: * -> *) a. Alternative f => f a
empty
overlays [g a
x]    = g a
x
overlays (g a
x:[g a]
xs) = g a
x g a -> g a -> g a
forall (g :: * -> *) a. Graph g => g a -> g a -> g a
`overlay` [g a] -> g a
forall (g :: * -> *) a. Graph g => [g a] -> g a
overlays [g a]
xs

-- | Connect a given list of graphs.
-- Complexity: /O(L)/ time and memory, and /O(S)/ size, where /L/ is the length
-- of the given list, and /S/ is the sum of sizes of the graphs in the list.
--
-- @
-- connects []        == 'empty'
-- connects [x]       == x
-- connects [x,y]     == 'connect' x y
-- connects           == 'foldr' 'connect' 'empty'
-- 'isEmpty' . connects == 'all' 'isEmpty'
-- @
connects :: Graph g => [g a] -> g a
connects :: [g a] -> g a
connects []     = g a
forall (f :: * -> *) a. Alternative f => f a
empty
connects [g a
x]    = g a
x
connects (g a
x:[g a]
xs) = g a
x g a -> g a -> g a
forall (g :: * -> *) a. Graph g => g a -> g a -> g a
`connect` [g a] -> g a
forall (g :: * -> *) a. Graph g => [g a] -> g a
connects [g a]
xs

-- | The 'isSubgraphOf' function takes two graphs and returns 'True' if the
-- first graph is a /subgraph/ of the second. Here is the current implementation:
--
-- @
-- isSubgraphOf x y = 'overlay' x y == y
-- @
-- The complexity therefore depends on the complexity of equality testing of
-- the specific graph instance.
--
-- @
-- 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 :: (Graph g, Eq (g a)) => g a -> g a -> Bool
isSubgraphOf :: g a -> g a -> Bool
isSubgraphOf g a
x g a
y = g a -> g a -> g a
forall (g :: * -> *) a. Graph g => g a -> g a -> g a
overlay g a
x g a
y g a -> g a -> Bool
forall a. Eq a => a -> a -> Bool
== g a
y

-- | Check if a graph contains a given edge.
-- Complexity: /O(s)/ time.
--
-- @
-- hasEdge x y 'empty'            == False
-- hasEdge x y ('vertex' z)       == False
-- hasEdge x y ('edge' x y)       == True
-- hasEdge x y                  == 'elem' (x,y) . 'edgeList'
-- @
hasEdge :: (Eq (g a), Graph g, Ord a) => a -> a -> g a -> Bool
hasEdge :: a -> a -> g a -> Bool
hasEdge a
u a
v = (a -> a -> g a
forall (g :: * -> *) a. Graph g => a -> a -> g a
edge a
u a
v g a -> g a -> Bool
forall (g :: * -> *) a. (Graph g, Eq (g a)) => g a -> g a -> Bool
`isSubgraphOf`) (g a -> Bool) -> (g a -> g a) -> g a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> g a -> g a
forall (g :: * -> *) a. Graph g => (a -> Bool) -> g a -> g a
induce (\a
x -> a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
u Bool -> Bool -> Bool
|| a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
v)

-- | The /path/ on a list of vertices.
-- Complexity: /O(L)/ time, memory and size, where /L/ is the length of the
-- given list.
--
-- @
-- path []    == 'empty'
-- path [x]   == 'vertex' x
-- path [x,y] == 'edge' x y
-- @
path :: Graph g => [a] -> g a
path :: [a] -> g a
path [a]
xs = case [a]
xs of []     -> g a
forall (f :: * -> *) a. Alternative f => f a
empty
                     [a
x]    -> a -> g a
forall (g :: * -> *) a. Graph g => a -> g a
vertex a
x
                     (a
_:[a]
ys) -> [(a, a)] -> g a
forall (g :: * -> *) a. Graph g => [(a, a)] -> g a
edges ([a] -> [a] -> [(a, a)]
forall a b. [a] -> [b] -> [(a, b)]
zip [a]
xs [a]
ys)

-- | The /circuit/ on a list of vertices.
-- Complexity: /O(L)/ time, memory and size, where /L/ is the length of the
-- given list.
--
-- @
-- circuit []    == 'empty'
-- circuit [x]   == 'edge' x x
-- circuit [x,y] == 'edges' [(x,y), (y,x)]
-- @
circuit :: Graph g => [a] -> g a
circuit :: [a] -> g a
circuit []     = g a
forall (f :: * -> *) a. Alternative f => f a
empty
circuit (a
x:[a]
xs) = [a] -> g a
forall (g :: * -> *) a. Graph g => [a] -> g a
path ([a] -> g a) -> [a] -> g a
forall a b. (a -> b) -> a -> b
$ [a
x] [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a]
xs [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a
x]

-- | The /clique/ on a list of vertices.
-- Complexity: /O(L)/ time, memory and size, where /L/ is the length of the
-- given list.
--
-- @
-- clique []         == 'empty'
-- clique [x]        == 'vertex' x
-- clique [x,y]      == 'edge' x y
-- clique [x,y,z]    == 'edges' [(x,y), (x,z), (y,z)]
-- clique (xs ++ ys) == 'connect' (clique xs) (clique ys)
-- @
clique :: Graph g => [a] -> g a
clique :: [a] -> g a
clique = [g a] -> g a
forall (g :: * -> *) a. Graph g => [g a] -> g a
connects ([g a] -> g a) -> ([a] -> [g a]) -> [a] -> g a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> g a) -> [a] -> [g a]
forall a b. (a -> b) -> [a] -> [b]
map a -> g a
forall (g :: * -> *) a. Graph g => a -> g a
vertex

-- | The /biclique/ on two lists of vertices.
-- Complexity: /O(L1 + L2)/ time, memory and size, where /L1/ and /L2/ are the
-- lengths of the given lists.
--
-- @
-- 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 xs      ys      == 'connect' ('vertices' xs) ('vertices' ys)
-- @
biclique :: Graph g => [a] -> [a] -> g a
biclique :: [a] -> [a] -> g a
biclique [a]
xs [] = [a] -> g a
forall (g :: * -> *) a. Graph g => [a] -> g a
vertices [a]
xs
biclique [] [a]
ys = [a] -> g a
forall (g :: * -> *) a. Graph g => [a] -> g a
vertices [a]
ys
biclique [a]
xs [a]
ys = g a -> g a -> g a
forall (g :: * -> *) a. Graph g => g a -> g a -> g a
connect ([a] -> g a
forall (g :: * -> *) a. Graph g => [a] -> g a
vertices [a]
xs) ([a] -> g a
forall (g :: * -> *) a. Graph g => [a] -> g a
vertices [a]
ys)

-- | The /star/ formed by a centre vertex connected to a list of leaves.
-- Complexity: /O(L)/ time, memory and size, where /L/ is the length of the
-- given list.
--
-- @
-- star x []    == 'vertex' x
-- star x [y]   == 'edge' x y
-- star x [y,z] == 'edges' [(x,y), (x,z)]
-- star x ys    == 'connect' ('vertex' x) ('vertices' ys)
-- @
star :: Graph g => a -> [a] -> g a
star :: a -> [a] -> g a
star a
x [] = a -> g a
forall (g :: * -> *) a. Graph g => a -> g a
vertex a
x
star a
x [a]
ys = g a -> g a -> g a
forall (g :: * -> *) a. Graph g => g a -> g a -> g a
connect (a -> g a
forall (g :: * -> *) a. Graph g => a -> g a
vertex a
x) ([a] -> g a
forall (g :: * -> *) a. Graph g => [a] -> g a
vertices [a]
ys)

-- | The /stars/ formed by overlaying a list of 'star's. An inverse of
-- 'adjacencyList'.
-- Complexity: /O(L)/ time, memory and size, where /L/ is the total size of the
-- input.
--
-- @
-- stars []                      == 'empty'
-- stars [(x, [])]               == 'vertex' x
-- stars [(x, [y])]              == 'edge' x y
-- stars [(x, ys)]               == 'star' x ys
-- stars                         == 'overlays' . 'map' ('uncurry' 'star')
-- stars . 'adjacencyList'         == id
-- 'overlay' (stars xs) (stars ys) == stars (xs ++ ys)
-- @
stars :: Graph g => [(a, [a])] -> g a
stars :: [(a, [a])] -> g a
stars = [g a] -> g a
forall (g :: * -> *) a. Graph g => [g a] -> g a
overlays ([g a] -> g a) -> ([(a, [a])] -> [g a]) -> [(a, [a])] -> g a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, [a]) -> g a) -> [(a, [a])] -> [g a]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> [a] -> g a) -> (a, [a]) -> g a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry a -> [a] -> g a
forall (g :: * -> *) a. Graph g => a -> [a] -> g a
star)

-- | The /tree graph/ constructed from a given 'Tree' data structure.
-- Complexity: /O(T)/ time, memory and size, where /T/ is the size of the
-- given tree (i.e. the number of vertices in the tree).
--
-- @
-- tree (Node x [])                                         == 'vertex' x
-- tree (Node x [Node y [Node z []]])                       == 'path' [x,y,z]
-- tree (Node x [Node y [], Node z []])                     == 'star' x [y,z]
-- tree (Node 1 [Node 2 [], Node 3 [Node 4 [], Node 5 []]]) == 'edges' [(1,2), (1,3), (3,4), (3,5)]
-- @
tree :: Graph g => Tree a -> g a
tree :: Tree a -> g a
tree (Node a
x []) = a -> g a
forall (g :: * -> *) a. Graph g => a -> g a
vertex a
x
tree (Node a
x [Tree a]
f ) = a -> [a] -> g a
forall (g :: * -> *) a. Graph g => a -> [a] -> g a
star a
x ((Tree a -> a) -> [Tree a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map Tree a -> a
forall a. Tree a -> a
rootLabel [Tree a]
f)
         g a -> g a -> g a
forall (g :: * -> *) a. Graph g => g a -> g a -> g a
`overlay` [Tree a] -> g a
forall (g :: * -> *) a. Graph g => Forest a -> g a
forest ((Tree a -> Bool) -> [Tree a] -> [Tree a]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Tree a -> Bool) -> Tree a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tree a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Tree a] -> Bool) -> (Tree a -> [Tree a]) -> Tree a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tree a -> [Tree a]
forall a. Tree a -> Forest a
subForest) [Tree a]
f)

-- | The /forest graph/ constructed from a given 'Forest' data structure.
-- Complexity: /O(F)/ time, memory and size, where /F/ is the size of the
-- given forest (i.e. the number of vertices in the forest).
--
-- @
-- forest []                                                  == 'empty'
-- forest [x]                                                 == 'tree' x
-- forest [Node 1 [Node 2 [], Node 3 []], Node 4 [Node 5 []]] == 'edges' [(1,2), (1,3), (4,5)]
-- forest                                                     == 'overlays' . 'map' 'tree'
-- @
forest :: Graph g => Forest a -> g a
forest :: Forest a -> g a
forest = [g a] -> g a
forall (g :: * -> *) a. Graph g => [g a] -> g a
overlays ([g a] -> g a) -> (Forest a -> [g a]) -> Forest a -> g a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tree a -> g a) -> Forest a -> [g a]
forall a b. (a -> b) -> [a] -> [b]
map Tree a -> g a
forall (g :: * -> *) a. Graph g => Tree a -> g a
tree

-- | Construct a /mesh graph/ from two lists of vertices.
-- Complexity: /O(L1 * L2)/ time, memory and size, where /L1/ and /L2/ are the
-- lengths of the given lists.
--
-- @
-- mesh xs     []   == 'empty'
-- mesh []     ys   == 'empty'
-- mesh [x]    [y]  == 'vertex' (x, y)
-- mesh xs     ys   == 'box' ('path' xs) ('path' ys)
-- mesh [1..3] "ab" == 'edges' [ ((1,\'a\'),(1,\'b\')), ((1,\'a\'),(2,\'a\')), ((1,\'b\'),(2,\'b\')), ((2,\'a\'),(2,\'b\'))
--                           , ((2,\'a\'),(3,\'a\')), ((2,\'b\'),(3,\'b\')), ((3,\'a\'),(3,\'b\')) ]
-- @
mesh :: Graph g => [a] -> [b] -> g (a, b)
mesh :: [a] -> [b] -> g (a, b)
mesh []  [b]
_   = g (a, b)
forall (f :: * -> *) a. Alternative f => f a
empty
mesh [a]
_   []  = g (a, b)
forall (f :: * -> *) a. Alternative f => f a
empty
mesh [a
x] [b
y] = (a, b) -> g (a, b)
forall (g :: * -> *) a. Graph g => a -> g a
vertex (a
x, b
y)
mesh [a]
xs  [b]
ys  = [((a, b), [(a, b)])] -> g (a, b)
forall (g :: * -> *) a. Graph g => [(a, [a])] -> g a
stars ([((a, b), [(a, b)])] -> g (a, b))
-> [((a, b), [(a, b)])] -> g (a, b)
forall a b. (a -> b) -> a -> b
$  [ ((a
a1, b
b1), [(a
a1, b
b2), (a
a2, b
b1)]) | (a
a1, a
a2) <- [(a, a)]
ipxs, (b
b1, b
b2) <- [(b, b)]
ipys ]
                     [((a, b), [(a, b)])]
-> [((a, b), [(a, b)])] -> [((a, b), [(a, b)])]
forall a. [a] -> [a] -> [a]
++ [ ((a
lx,b
y1), [(a
lx,b
y2)]) | (b
y1,b
y2) <- [(b, b)]
ipys]
                     [((a, b), [(a, b)])]
-> [((a, b), [(a, b)])] -> [((a, b), [(a, b)])]
forall a. [a] -> [a] -> [a]
++ [ ((a
x1,b
ly), [(a
x2,b
ly)]) | (a
x1,a
x2) <- [(a, a)]
ipxs]
  where
    lx :: a
lx = [a] -> a
forall a. [a] -> a
last [a]
xs
    ly :: b
ly = [b] -> b
forall a. [a] -> a
last [b]
ys
    ipxs :: [(a, a)]
ipxs = [(a, a)] -> [(a, a)]
forall a. [a] -> [a]
init ([a] -> [(a, a)]
forall a. [a] -> [(a, a)]
pairs [a]
xs)
    ipys :: [(b, b)]
ipys = [(b, b)] -> [(b, b)]
forall a. [a] -> [a]
init ([b] -> [(b, b)]
forall a. [a] -> [(a, a)]
pairs [b]
ys)

-- | Construct a /torus graph/ from two lists of vertices.
-- Complexity: /O(L1 * L2)/ time, memory and size, where /L1/ and /L2/ are the
-- lengths of the given lists.
--
-- @
-- torus xs    []   == 'empty'
-- torus []    ys   == 'empty'
-- torus [x]   [y]  == 'edge' (x,y) (x,y)
-- torus xs    ys   == 'box' ('circuit' xs) ('circuit' ys)
-- torus [1,2] "ab" == 'edges' [ ((1,\'a\'),(1,\'b\')), ((1,\'a\'),(2,\'a\')), ((1,\'b\'),(1,\'a\')), ((1,\'b\'),(2,\'b\'))
--                           , ((2,\'a\'),(1,\'a\')), ((2,\'a\'),(2,\'b\')), ((2,\'b\'),(1,\'b\')), ((2,\'b\'),(2,\'a\')) ]
-- @
torus :: Graph g => [a] -> [b] -> g (a, b)
torus :: [a] -> [b] -> g (a, b)
torus [a]
xs [b]
ys = [((a, b), [(a, b)])] -> g (a, b)
forall (g :: * -> *) a. Graph g => [(a, [a])] -> g a
stars [ ((a
a1, b
b1), [(a
a1, b
b2), (a
a2, b
b1)]) | (a
a1, a
a2) <- [a] -> [(a, a)]
forall a. [a] -> [(a, a)]
pairs [a]
xs, (b
b1, b
b2) <- [b] -> [(b, b)]
forall a. [a] -> [(a, a)]
pairs [b]
ys ]

-- | Auxiliary function for 'mesh' and 'torus'
pairs :: [a] -> [(a, a)]
pairs :: [a] -> [(a, a)]
pairs [] = []
pairs as :: [a]
as@(a
x:[a]
xs) = [a] -> [a] -> [(a, a)]
forall a b. [a] -> [b] -> [(a, b)]
zip [a]
as ([a]
xs [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a
x])

-- | Construct a /De Bruijn graph/ of a given non-negative dimension using symbols
-- from a given alphabet.
-- Complexity: /O(A^(D + 1))/ time, memory and size, where /A/ is the size of the
-- alphabet and /D/ is the dimension of the graph.
--
-- @
--           deBruijn 0 xs               == 'edge' [] []
-- n > 0 ==> deBruijn n []               == 'empty'
--           deBruijn 1 [0,1]            == 'edges' [ ([0],[0]), ([0],[1]), ([1],[0]), ([1],[1]) ]
--           deBruijn 2 "0"              == 'edge' "00" "00"
--           deBruijn 2 "01"             == 'edges' [ ("00","00"), ("00","01"), ("01","10"), ("01","11")
--                                                , ("10","00"), ("10","01"), ("11","10"), ("11","11") ]
--           transpose   (deBruijn n xs) == 'fmap' 'reverse' $ deBruijn n xs
--           'vertexCount' (deBruijn n xs) == ('length' $ 'Data.List.nub' xs)^n
-- n > 0 ==> 'edgeCount'   (deBruijn n xs) == ('length' $ 'Data.List.nub' xs)^(n + 1)
-- @
deBruijn :: Graph g => Int -> [a] -> g [a]
deBruijn :: Int -> [a] -> g [a]
deBruijn Int
0   [a]
_        = [a] -> [a] -> g [a]
forall (g :: * -> *) a. Graph g => a -> a -> g a
edge [] []
deBruijn Int
len [a]
alphabet = g (Either [a] [a])
skeleton g (Either [a] [a]) -> (Either [a] [a] -> g [a]) -> g [a]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Either [a] [a] -> g [a]
expand
  where
    overlaps :: [[a]]
overlaps = (Int -> [a]) -> [Int] -> [[a]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ([a] -> Int -> [a]
forall a b. a -> b -> a
const [a]
alphabet) [Int
2..Int
len]
    skeleton :: g (Either [a] [a])
skeleton = [(Either [a] [a], Either [a] [a])] -> g (Either [a] [a])
forall (g :: * -> *) a. Graph g => [(a, a)] -> g a
edges    [        ([a] -> Either [a] [a]
forall a b. a -> Either a b
Left [a]
s, [a] -> Either [a] [a]
forall a b. b -> Either a b
Right [a]
s)   | [a]
s <- [[a]]
overlaps ]
    expand :: Either [a] [a] -> g [a]
expand Either [a] [a]
v = [[a]] -> g [a]
forall (g :: * -> *) a. Graph g => [a] -> g a
vertices [ ([a] -> [a]) -> ([a] -> [a]) -> Either [a] [a] -> [a]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([a
a] [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++) ([a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a
a]) Either [a] [a]
v | a
a <- [a]
alphabet ]

-- | Construct the /induced subgraph/ of a given graph by removing the
-- vertices that do not satisfy a given predicate.
-- Complexity: /O(s)/ time, memory and size, assuming that the predicate takes
-- constant time.
--
-- @
-- induce ('const' True ) x      == x
-- induce ('const' False) x      == 'empty'
-- induce (/= x)               == 'removeVertex' x
-- induce p . induce q         == induce (\\x -> p x && q x)
-- 'isSubgraphOf' (induce p x) x == True
-- @
induce :: Graph g => (a -> Bool) -> g a -> g a
induce :: (a -> Bool) -> g a -> g a
induce = (a -> Bool) -> g a -> g a
forall (m :: * -> *) a. MonadPlus m => (a -> Bool) -> m a -> m a
mfilter

-- | Remove a vertex from a given graph.
-- Complexity: /O(s)/ time, memory and size.
--
-- @
-- removeVertex x ('vertex' x)       == 'empty'
-- removeVertex 1 ('vertex' 2)       == 'vertex' 2
-- removeVertex x ('edge' x x)       == 'empty'
-- removeVertex 1 ('edge' 1 2)       == 'vertex' 2
-- removeVertex x . removeVertex x == removeVertex x
-- @
removeVertex :: (Eq a, Graph g) => a -> g a -> g a
removeVertex :: a -> g a -> g a
removeVertex a
v = (a -> Bool) -> g a -> g a
forall (g :: * -> *) a. Graph g => (a -> Bool) -> g a -> g a
induce (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
v)

-- | The function @'replaceVertex' x y@ replaces vertex @x@ with vertex @y@ in a
-- given 'Graph'. If @y@ already exists, @x@ and @y@ will be merged.
-- Complexity: /O(s)/ time, memory and size.
--
-- @
-- replaceVertex x x            == id
-- replaceVertex x y ('vertex' x) == 'vertex' y
-- replaceVertex x y            == 'mergeVertices' (== x) y
-- @
replaceVertex :: (Eq a, Graph g) => a -> a -> g a -> g a
replaceVertex :: a -> a -> g a -> g a
replaceVertex a
u a
v = (a -> a) -> g a -> g a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> a) -> g a -> g a) -> (a -> a) -> g a -> g a
forall a b. (a -> b) -> a -> b
$ \a
w -> if a
w a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
u then a
v else a
w

-- | Merge vertices satisfying a given predicate into a given vertex.
-- Complexity: /O(s)/ time, memory and size, assuming that the predicate takes
-- constant time.
--
-- @
-- 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 :: Graph g => (a -> Bool) -> a -> g a -> g a
mergeVertices :: (a -> Bool) -> a -> g a -> g a
mergeVertices a -> Bool
p a
v = (a -> a) -> g a -> g a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> a) -> g a -> g a) -> (a -> a) -> g a -> g a
forall a b. (a -> b) -> a -> b
$ \a
w -> if a -> Bool
p a
w then a
v else a
w

-- | Split a vertex into a list of vertices with the same connectivity.
-- Complexity: /O(s + k * L)/ time, memory and size, where /k/ is the number of
-- occurrences of the vertex in the expression and /L/ is the length of the
-- given list.
--
-- @
-- splitVertex x []                  == 'removeVertex' x
-- splitVertex x [x]                 == id
-- splitVertex x [y]                 == 'replaceVertex' x y
-- splitVertex 1 [0,1] $ 1 * (2 + 3) == (0 + 1) * (2 + 3)
-- @
splitVertex :: (Eq a, Graph g) => a -> [a] -> g a -> g a
splitVertex :: a -> [a] -> g a -> g a
splitVertex a
v [a]
us g a
g = g a
g g a -> (a -> g a) -> g a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
w -> if a
w a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
v then [a] -> g a
forall (g :: * -> *) a. Graph g => [a] -> g a
vertices [a]
us else a -> g a
forall (g :: * -> *) a. Graph g => a -> g a
vertex a
w