module Algebra.Graph.Class (
Graph (..),
Undirected,
Reflexive,
Transitive,
Preorder,
edge, vertices, overlays, connects, edges,
isSubgraphOf,
path, circuit, clique, biclique, star, tree, forest
) where
import Data.Tree
import Algebra.Graph.Label (Dioid, one)
import qualified Algebra.Graph as G
import qualified Algebra.Graph.Undirected as UG
import qualified Algebra.Graph.AdjacencyMap as AM
import qualified Algebra.Graph.Labelled as LG
import qualified Algebra.Graph.Labelled.AdjacencyMap as LAM
import qualified Algebra.Graph.AdjacencyIntMap as AIM
import qualified Algebra.Graph.Relation as R
import qualified Algebra.Graph.Relation.Symmetric as RS
class Graph g where
type Vertex g
empty :: g
vertex :: Vertex g -> g
overlay :: g -> g -> g
connect :: g -> g -> g
instance Graph (G.Graph a) where
type Vertex (G.Graph a) = a
empty :: Graph a
empty = Graph a
forall a. Graph a
G.empty
vertex :: Vertex (Graph a) -> Graph a
vertex = Vertex (Graph a) -> Graph a
forall a. a -> Graph a
G.vertex
overlay :: Graph a -> Graph a -> Graph a
overlay = Graph a -> Graph a -> Graph a
forall a. Graph a -> Graph a -> Graph a
G.overlay
connect :: Graph a -> Graph a -> Graph a
connect = Graph a -> Graph a -> Graph a
forall a. Graph a -> Graph a -> Graph a
G.connect
instance Graph (UG.Graph a) where
type Vertex (UG.Graph a) = a
empty :: Graph a
empty = Graph a
forall a. Graph a
UG.empty
vertex :: Vertex (Graph a) -> Graph a
vertex = Vertex (Graph a) -> Graph a
forall a. a -> Graph a
UG.vertex
overlay :: Graph a -> Graph a -> Graph a
overlay = Graph a -> Graph a -> Graph a
forall a. Graph a -> Graph a -> Graph a
UG.overlay
connect :: Graph a -> Graph a -> Graph a
connect = Graph a -> Graph a -> Graph a
forall a. Graph a -> Graph a -> Graph a
UG.connect
instance Undirected (UG.Graph a)
instance Ord a => Graph (AM.AdjacencyMap a) where
type Vertex (AM.AdjacencyMap a) = a
empty :: AdjacencyMap a
empty = AdjacencyMap a
forall a. AdjacencyMap a
AM.empty
vertex :: Vertex (AdjacencyMap a) -> AdjacencyMap a
vertex = Vertex (AdjacencyMap a) -> AdjacencyMap a
forall a. a -> AdjacencyMap a
AM.vertex
overlay :: AdjacencyMap a -> AdjacencyMap a -> AdjacencyMap a
overlay = AdjacencyMap a -> AdjacencyMap a -> AdjacencyMap a
forall a.
Ord a =>
AdjacencyMap a -> AdjacencyMap a -> AdjacencyMap a
AM.overlay
connect :: AdjacencyMap a -> AdjacencyMap a -> AdjacencyMap a
connect = AdjacencyMap a -> AdjacencyMap a -> AdjacencyMap a
forall a.
Ord a =>
AdjacencyMap a -> AdjacencyMap a -> AdjacencyMap a
AM.connect
instance Graph AIM.AdjacencyIntMap where
type Vertex AIM.AdjacencyIntMap = Int
empty :: AdjacencyIntMap
empty = AdjacencyIntMap
AIM.empty
vertex :: Vertex AdjacencyIntMap -> AdjacencyIntMap
vertex = Int -> AdjacencyIntMap
Vertex AdjacencyIntMap -> AdjacencyIntMap
AIM.vertex
overlay :: AdjacencyIntMap -> AdjacencyIntMap -> AdjacencyIntMap
overlay = AdjacencyIntMap -> AdjacencyIntMap -> AdjacencyIntMap
AIM.overlay
connect :: AdjacencyIntMap -> AdjacencyIntMap -> AdjacencyIntMap
connect = AdjacencyIntMap -> AdjacencyIntMap -> AdjacencyIntMap
AIM.connect
instance Dioid e => Graph (LG.Graph e a) where
type Vertex (LG.Graph e a) = a
empty :: Graph e a
empty = Graph e a
forall e a. Graph e a
LG.empty
vertex :: Vertex (Graph e a) -> Graph e a
vertex = Vertex (Graph e a) -> Graph e a
forall a e. a -> Graph e a
LG.vertex
overlay :: Graph e a -> Graph e a -> Graph e a
overlay = Graph e a -> Graph e a -> Graph e a
forall e a. Monoid e => Graph e a -> Graph e a -> Graph e a
LG.overlay
connect :: Graph e a -> Graph e a -> Graph e a
connect = e -> Graph e a -> Graph e a -> Graph e a
forall e a. e -> Graph e a -> Graph e a -> Graph e a
LG.connect e
forall a. Semiring a => a
one
instance (Dioid e, Eq e, Ord a) => Graph (LAM.AdjacencyMap e a) where
type Vertex (LAM.AdjacencyMap e a) = a
empty :: AdjacencyMap e a
empty = AdjacencyMap e a
forall e a. AdjacencyMap e a
LAM.empty
vertex :: Vertex (AdjacencyMap e a) -> AdjacencyMap e a
vertex = Vertex (AdjacencyMap e a) -> AdjacencyMap e a
forall a e. a -> AdjacencyMap e a
LAM.vertex
overlay :: AdjacencyMap e a -> AdjacencyMap e a -> AdjacencyMap e a
overlay = AdjacencyMap e a -> AdjacencyMap e a -> AdjacencyMap e a
forall e a.
(Eq e, Monoid e, Ord a) =>
AdjacencyMap e a -> AdjacencyMap e a -> AdjacencyMap e a
LAM.overlay
connect :: AdjacencyMap e a -> AdjacencyMap e a -> AdjacencyMap e a
connect = e -> AdjacencyMap e a -> AdjacencyMap e a -> AdjacencyMap e a
forall e a.
(Eq e, Monoid e, Ord a) =>
e -> AdjacencyMap e a -> AdjacencyMap e a -> AdjacencyMap e a
LAM.connect e
forall a. Semiring a => a
one
instance Ord a => Graph (R.Relation a) where
type Vertex (R.Relation a) = a
empty :: Relation a
empty = Relation a
forall a. Relation a
R.empty
vertex :: Vertex (Relation a) -> Relation a
vertex = Vertex (Relation a) -> Relation a
forall a. a -> Relation a
R.vertex
overlay :: Relation a -> Relation a -> Relation a
overlay = Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
R.overlay
connect :: Relation a -> Relation a -> Relation a
connect = Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
R.connect
instance Ord a => Graph (RS.Relation a) where
type Vertex (RS.Relation a) = a
empty :: Relation a
empty = Relation a
forall a. Relation a
RS.empty
vertex :: Vertex (Relation a) -> Relation a
vertex = Vertex (Relation a) -> Relation a
forall a. a -> Relation a
RS.vertex
overlay :: Relation a -> Relation a -> Relation a
overlay = Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
RS.overlay
connect :: Relation a -> Relation a -> Relation a
connect = Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
RS.connect
instance Ord a => Undirected (RS.Relation a)
class Graph g => Undirected g
class Graph g => Reflexive g
class Graph g => Transitive g
class (Reflexive g, Transitive g) => Preorder g
instance Graph () where
type Vertex () = ()
empty :: ()
empty = ()
vertex :: Vertex () -> ()
vertex Vertex ()
_ = ()
overlay :: () -> () -> ()
overlay ()
_ ()
_ = ()
connect :: () -> () -> ()
connect ()
_ ()
_ = ()
instance Undirected ()
instance Reflexive ()
instance Transitive ()
instance Preorder ()
instance Graph g => Graph (Maybe g) where
type Vertex (Maybe g) = Vertex g
empty :: Maybe g
empty = g -> Maybe g
forall (f :: * -> *) a. Applicative f => a -> f a
pure g
forall g. Graph g => g
empty
vertex :: Vertex (Maybe g) -> Maybe g
vertex = g -> Maybe g
forall (f :: * -> *) a. Applicative f => a -> f a
pure (g -> Maybe g) -> (Vertex g -> g) -> Vertex g -> Maybe g
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vertex g -> g
forall g. Graph g => Vertex g -> g
vertex
overlay :: Maybe g -> Maybe g -> Maybe g
overlay Maybe g
x Maybe g
y = g -> g -> g
forall g. Graph g => g -> g -> g
overlay (g -> g -> g) -> Maybe g -> Maybe (g -> g)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe g
x Maybe (g -> g) -> Maybe g -> Maybe g
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe g
y
connect :: Maybe g -> Maybe g -> Maybe g
connect Maybe g
x Maybe g
y = g -> g -> g
forall g. Graph g => g -> g -> g
connect (g -> g -> g) -> Maybe g -> Maybe (g -> g)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe g
x Maybe (g -> g) -> Maybe g -> Maybe g
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe g
y
instance Undirected g => Undirected (Maybe g)
instance Reflexive g => Reflexive (Maybe g)
instance Transitive g => Transitive (Maybe g)
instance Preorder g => Preorder (Maybe g)
instance Graph g => Graph (a -> g) where
type Vertex (a -> g) = Vertex g
empty :: a -> g
empty = g -> a -> g
forall (f :: * -> *) a. Applicative f => a -> f a
pure g
forall g. Graph g => g
empty
vertex :: Vertex (a -> g) -> a -> g
vertex = g -> a -> g
forall (f :: * -> *) a. Applicative f => a -> f a
pure (g -> a -> g) -> (Vertex g -> g) -> Vertex g -> a -> g
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vertex g -> g
forall g. Graph g => Vertex g -> g
vertex
overlay :: (a -> g) -> (a -> g) -> a -> g
overlay a -> g
x a -> g
y = g -> g -> g
forall g. Graph g => g -> g -> g
overlay (g -> g -> g) -> (a -> g) -> a -> g -> g
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> g
x (a -> g -> g) -> (a -> g) -> a -> g
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> g
y
connect :: (a -> g) -> (a -> g) -> a -> g
connect a -> g
x a -> g
y = g -> g -> g
forall g. Graph g => g -> g -> g
connect (g -> g -> g) -> (a -> g) -> a -> g -> g
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> g
x (a -> g -> g) -> (a -> g) -> a -> g
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> g
y
instance Undirected g => Undirected (a -> g)
instance Reflexive g => Reflexive (a -> g)
instance Transitive g => Transitive (a -> g)
instance Preorder g => Preorder (a -> g)
instance (Graph g, Graph h) => Graph (g, h) where
type Vertex (g, h) = (Vertex g , Vertex h )
empty :: (g, h)
empty = (g
forall g. Graph g => g
empty , h
forall g. Graph g => g
empty )
vertex :: Vertex (g, h) -> (g, h)
vertex (x, y ) = (Vertex g -> g
forall g. Graph g => Vertex g -> g
vertex Vertex g
x , Vertex h -> h
forall g. Graph g => Vertex g -> g
vertex Vertex h
y )
overlay :: (g, h) -> (g, h) -> (g, h)
overlay (g
x1, h
y1) (g
x2, h
y2) = (g -> g -> g
forall g. Graph g => g -> g -> g
overlay g
x1 g
x2, h -> h -> h
forall g. Graph g => g -> g -> g
overlay h
y1 h
y2)
connect :: (g, h) -> (g, h) -> (g, h)
connect (g
x1, h
y1) (g
x2, h
y2) = (g -> g -> g
forall g. Graph g => g -> g -> g
connect g
x1 g
x2, h -> h -> h
forall g. Graph g => g -> g -> g
connect h
y1 h
y2)
instance (Undirected g, Undirected h) => Undirected (g, h)
instance (Reflexive g, Reflexive h) => Reflexive (g, h)
instance (Transitive g, Transitive h) => Transitive (g, h)
instance (Preorder g, Preorder h) => Preorder (g, h)
instance (Graph g, Graph h, Graph i) => Graph (g, h, i) where
type Vertex (g, h, i) = (Vertex g , Vertex h , Vertex i )
empty :: (g, h, i)
empty = (g
forall g. Graph g => g
empty , h
forall g. Graph g => g
empty , i
forall g. Graph g => g
empty )
vertex :: Vertex (g, h, i) -> (g, h, i)
vertex (x, y , z ) = (Vertex g -> g
forall g. Graph g => Vertex g -> g
vertex Vertex g
x , Vertex h -> h
forall g. Graph g => Vertex g -> g
vertex Vertex h
y , Vertex i -> i
forall g. Graph g => Vertex g -> g
vertex Vertex i
z )
overlay :: (g, h, i) -> (g, h, i) -> (g, h, i)
overlay (g
x1, h
y1, i
z1) (g
x2, h
y2, i
z2) = (g -> g -> g
forall g. Graph g => g -> g -> g
overlay g
x1 g
x2, h -> h -> h
forall g. Graph g => g -> g -> g
overlay h
y1 h
y2, i -> i -> i
forall g. Graph g => g -> g -> g
overlay i
z1 i
z2)
connect :: (g, h, i) -> (g, h, i) -> (g, h, i)
connect (g
x1, h
y1, i
z1) (g
x2, h
y2, i
z2) = (g -> g -> g
forall g. Graph g => g -> g -> g
connect g
x1 g
x2, h -> h -> h
forall g. Graph g => g -> g -> g
connect h
y1 h
y2, i -> i -> i
forall g. Graph g => g -> g -> g
connect i
z1 i
z2)
instance (Undirected g, Undirected h, Undirected i) => Undirected (g, h, i)
instance (Reflexive g, Reflexive h, Reflexive i) => Reflexive (g, h, i)
instance (Transitive g, Transitive h, Transitive i) => Transitive (g, h, i)
instance (Preorder g, Preorder h, Preorder i) => Preorder (g, h, i)
edge :: Graph g => Vertex g -> Vertex g -> g
edge :: Vertex g -> Vertex g -> g
edge Vertex g
x Vertex g
y = g -> g -> g
forall g. Graph g => g -> g -> g
connect (Vertex g -> g
forall g. Graph g => Vertex g -> g
vertex Vertex g
x) (Vertex g -> g
forall g. Graph g => Vertex g -> g
vertex Vertex g
y)
vertices :: Graph g => [Vertex g] -> g
vertices :: [Vertex g] -> g
vertices = [g] -> g
forall g. Graph g => [g] -> g
overlays ([g] -> g) -> ([Vertex g] -> [g]) -> [Vertex g] -> g
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vertex g -> g) -> [Vertex g] -> [g]
forall a b. (a -> b) -> [a] -> [b]
map Vertex g -> g
forall g. Graph g => Vertex g -> g
vertex
edges :: Graph g => [(Vertex g, Vertex g)] -> g
edges :: [(Vertex g, Vertex g)] -> g
edges = [g] -> g
forall g. Graph g => [g] -> g
overlays ([g] -> g)
-> ([(Vertex g, Vertex g)] -> [g]) -> [(Vertex g, Vertex g)] -> g
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Vertex g, Vertex g) -> g) -> [(Vertex g, Vertex g)] -> [g]
forall a b. (a -> b) -> [a] -> [b]
map ((Vertex g -> Vertex g -> g) -> (Vertex g, Vertex g) -> g
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Vertex g -> Vertex g -> g
forall g. Graph g => Vertex g -> Vertex g -> g
edge)
overlays :: Graph g => [g] -> g
overlays :: [g] -> g
overlays [] = g
forall g. Graph g => g
empty
overlays [g
x] = g
x
overlays (g
x:[g]
xs) = g
x g -> g -> g
forall g. Graph g => g -> g -> g
`overlay` [g] -> g
forall g. Graph g => [g] -> g
overlays [g]
xs
connects :: Graph g => [g] -> g
connects :: [g] -> g
connects [] = g
forall g. Graph g => g
empty
connects [g
x] = g
x
connects (g
x:[g]
xs) = g
x g -> g -> g
forall g. Graph g => g -> g -> g
`connect` [g] -> g
forall g. Graph g => [g] -> g
connects [g]
xs
isSubgraphOf :: (Graph g, Eq g) => g -> g -> Bool
isSubgraphOf :: g -> g -> Bool
isSubgraphOf g
x g
y = g -> g -> g
forall g. Graph g => g -> g -> g
overlay g
x g
y g -> g -> Bool
forall a. Eq a => a -> a -> Bool
== g
y
path :: Graph g => [Vertex g] -> g
path :: [Vertex g] -> g
path [Vertex g]
xs = case [Vertex g]
xs of [] -> g
forall g. Graph g => g
empty
[Vertex g
x] -> Vertex g -> g
forall g. Graph g => Vertex g -> g
vertex Vertex g
x
(Vertex g
_:[Vertex g]
ys) -> [(Vertex g, Vertex g)] -> g
forall g. Graph g => [(Vertex g, Vertex g)] -> g
edges ([Vertex g] -> [Vertex g] -> [(Vertex g, Vertex g)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Vertex g]
xs [Vertex g]
ys)
circuit :: Graph g => [Vertex g] -> g
circuit :: [Vertex g] -> g
circuit [] = g
forall g. Graph g => g
empty
circuit (Vertex g
x:[Vertex g]
xs) = [Vertex g] -> g
forall g. Graph g => [Vertex g] -> g
path ([Vertex g] -> g) -> [Vertex g] -> g
forall a b. (a -> b) -> a -> b
$ [Vertex g
x] [Vertex g] -> [Vertex g] -> [Vertex g]
forall a. [a] -> [a] -> [a]
++ [Vertex g]
xs [Vertex g] -> [Vertex g] -> [Vertex g]
forall a. [a] -> [a] -> [a]
++ [Vertex g
x]
clique :: Graph g => [Vertex g] -> g
clique :: [Vertex g] -> g
clique = [g] -> g
forall g. Graph g => [g] -> g
connects ([g] -> g) -> ([Vertex g] -> [g]) -> [Vertex g] -> g
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vertex g -> g) -> [Vertex g] -> [g]
forall a b. (a -> b) -> [a] -> [b]
map Vertex g -> g
forall g. Graph g => Vertex g -> g
vertex
biclique :: Graph g => [Vertex g] -> [Vertex g] -> g
biclique :: [Vertex g] -> [Vertex g] -> g
biclique [Vertex g]
xs [] = [Vertex g] -> g
forall g. Graph g => [Vertex g] -> g
vertices [Vertex g]
xs
biclique [] [Vertex g]
ys = [Vertex g] -> g
forall g. Graph g => [Vertex g] -> g
vertices [Vertex g]
ys
biclique [Vertex g]
xs [Vertex g]
ys = g -> g -> g
forall g. Graph g => g -> g -> g
connect ([Vertex g] -> g
forall g. Graph g => [Vertex g] -> g
vertices [Vertex g]
xs) ([Vertex g] -> g
forall g. Graph g => [Vertex g] -> g
vertices [Vertex g]
ys)
star :: Graph g => Vertex g -> [Vertex g] -> g
star :: Vertex g -> [Vertex g] -> g
star Vertex g
x [] = Vertex g -> g
forall g. Graph g => Vertex g -> g
vertex Vertex g
x
star Vertex g
x [Vertex g]
ys = g -> g -> g
forall g. Graph g => g -> g -> g
connect (Vertex g -> g
forall g. Graph g => Vertex g -> g
vertex Vertex g
x) ([Vertex g] -> g
forall g. Graph g => [Vertex g] -> g
vertices [Vertex g]
ys)
tree :: Graph g => Tree (Vertex g) -> g
tree :: Tree (Vertex g) -> g
tree (Node Vertex g
x []) = Vertex g -> g
forall g. Graph g => Vertex g -> g
vertex Vertex g
x
tree (Node Vertex g
x [Tree (Vertex g)]
f ) = Vertex g -> [Vertex g] -> g
forall g. Graph g => Vertex g -> [Vertex g] -> g
star Vertex g
x ((Tree (Vertex g) -> Vertex g) -> [Tree (Vertex g)] -> [Vertex g]
forall a b. (a -> b) -> [a] -> [b]
map Tree (Vertex g) -> Vertex g
forall a. Tree a -> a
rootLabel [Tree (Vertex g)]
f)
g -> g -> g
forall g. Graph g => g -> g -> g
`overlay` [Tree (Vertex g)] -> g
forall g. Graph g => Forest (Vertex g) -> g
forest ((Tree (Vertex g) -> Bool) -> [Tree (Vertex g)] -> [Tree (Vertex g)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> (Tree (Vertex g) -> Bool) -> Tree (Vertex g) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tree (Vertex g)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Tree (Vertex g)] -> Bool)
-> (Tree (Vertex g) -> [Tree (Vertex g)])
-> Tree (Vertex g)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tree (Vertex g) -> [Tree (Vertex g)]
forall a. Tree a -> [Tree a]
subForest) [Tree (Vertex g)]
f)
forest :: Graph g => Forest (Vertex g) -> g
forest :: Forest (Vertex g) -> g
forest = [g] -> g
forall g. Graph g => [g] -> g
overlays ([g] -> g) -> (Forest (Vertex g) -> [g]) -> Forest (Vertex g) -> g
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tree (Vertex g) -> g) -> Forest (Vertex g) -> [g]
forall a b. (a -> b) -> [a] -> [b]
map Tree (Vertex g) -> g
forall g. Graph g => Tree (Vertex g) -> g
tree