algebraic-graphs-0.0.4: A library for algebraic graph construction and transformation

Copyright(c) Andrey Mokhov 2016-2017
LicenseMIT (see the file LICENSE)
Maintainerandrey.mokhov@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Algebra.Graph.Class

Contents

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 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 number of vertices in a Graph expression you will need to use a concrete data type, such as Algebra.Graph.Fold. Other useful Graph instances are defined in Algebra.Graph, Algebra.Graph.AdjacencyMap and Algebra.Graph.Relation.

See Algebra.Graph.HigherKinded.Class for the higher-kinded version of the core graph type class.

Synopsis

The core type class

class Graph g where Source #

The core type class for constructing algebraic graphs, 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.

Minimal complete definition

empty, vertex, overlay, connect

Associated Types

type Vertex g Source #

The type of graph vertices.

Methods

empty :: g Source #

Construct the empty graph.

vertex :: Vertex g -> g Source #

Construct the graph with a single vertex.

overlay :: g -> g -> g Source #

Overlay two graphs.

connect :: g -> g -> g Source #

Connect two graphs.

Instances

Graph () Source # 

Associated Types

type Vertex () :: * Source #

Methods

empty :: () Source #

vertex :: Vertex () -> () Source #

overlay :: () -> () -> () Source #

connect :: () -> () -> () Source #

Graph IntAdjacencyMap Source # 
Graph g => Graph (Maybe g) Source # 

Associated Types

type Vertex (Maybe g) :: * Source #

Methods

empty :: Maybe g Source #

vertex :: Vertex (Maybe g) -> Maybe g Source #

overlay :: Maybe g -> Maybe g -> Maybe g Source #

connect :: Maybe g -> Maybe g -> Maybe g Source #

Ord a => Graph (Relation a) Source # 

Associated Types

type Vertex (Relation a) :: * Source #

Ord a => Graph (PreorderRelation a) Source # 
Ord a => Graph (TransitiveRelation a) Source # 
Ord a => Graph (SymmetricRelation a) Source # 
Ord a => Graph (ReflexiveRelation a) Source # 
Ord a => Graph (AdjacencyMap a) Source # 
Graph (Fold a) Source # 

Associated Types

type Vertex (Fold a) :: * Source #

Methods

empty :: Fold a Source #

vertex :: Vertex (Fold a) -> Fold a Source #

overlay :: Fold a -> Fold a -> Fold a Source #

connect :: Fold a -> Fold a -> Fold a Source #

Graph (Graph a) Source # 

Associated Types

type Vertex (Graph a) :: * Source #

Methods

empty :: Graph a Source #

vertex :: Vertex (Graph a) -> Graph a Source #

overlay :: Graph a -> Graph a -> Graph a Source #

connect :: Graph a -> Graph a -> Graph a Source #

Graph g => Graph (a -> g) Source # 

Associated Types

type Vertex (a -> g) :: * Source #

Methods

empty :: a -> g Source #

vertex :: Vertex (a -> g) -> a -> g Source #

overlay :: (a -> g) -> (a -> g) -> a -> g Source #

connect :: (a -> g) -> (a -> g) -> a -> g Source #

(Graph g, Graph h) => Graph (g, h) Source # 

Associated Types

type Vertex (g, h) :: * Source #

Methods

empty :: (g, h) Source #

vertex :: Vertex (g, h) -> (g, h) Source #

overlay :: (g, h) -> (g, h) -> (g, h) Source #

connect :: (g, h) -> (g, h) -> (g, h) Source #

(Graph g, Graph h, Graph i) => Graph (g, h, i) Source # 

Associated Types

type Vertex (g, h, i) :: * Source #

Methods

empty :: (g, h, i) Source #

vertex :: Vertex (g, h, i) -> (g, h, i) Source #

overlay :: (g, h, i) -> (g, h, i) -> (g, h, i) Source #

connect :: (g, h, i) -> (g, h, i) -> (g, h, i) Source #

Undirected graphs

class Graph g => Undirected g Source #

The class of undirected graphs that satisfy the following additional axiom.

  • connect is commutative:

    x * y == y * x

Reflexive graphs

class Graph g => Reflexive g Source #

The class of reflexive graphs that satisfy the following additional axiom.

  • Each vertex has a self-loop:

    vertex x == vertex x * vertex 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.

Transitive graphs

class Graph g => Transitive g Source #

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.

Preorders

class (Reflexive g, Transitive g) => Preorder g Source #

The class of preorder graphs that are both reflexive and transitive.

Instances

Preorder () Source # 
Preorder g => Preorder (Maybe g) Source # 
Ord a => Preorder (PreorderRelation a) Source # 
Preorder g => Preorder (a -> g) Source # 
(Preorder g, Preorder h) => Preorder (g, h) Source # 
(Preorder g, Preorder h, Preorder i) => Preorder (g, h, i) Source # 

Basic graph construction primitives

edge :: Graph g => Vertex g -> Vertex g -> g Source #

Construct the graph comprising a single edge. Complexity: O(1) time, memory and size.

edge x y == connect (vertex x) (vertex y)

vertices :: Graph g => [Vertex g] -> g Source #

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

overlays :: Graph g => [g] -> g Source #

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

connects :: Graph g => [g] -> g Source #

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

edges :: Graph g => [(Vertex g, Vertex g)] -> g Source #

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

graph :: Graph g => [Vertex g] -> [(Vertex g, Vertex g)] -> g Source #

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(|V| + |E|) time, memory and size.

graph []  []      == empty
graph [x] []      == vertex x
graph []  [(x,y)] == edge x y
graph vs  es      == overlay (vertices vs) (edges es)

Relations on graphs

isSubgraphOf :: (Graph g, Eq g) => g -> g -> Bool Source #

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

Standard families of graphs

path :: Graph g => [Vertex g] -> g Source #

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

circuit :: Graph g => [Vertex g] -> g Source #

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)]

clique :: Graph g => [Vertex g] -> g Source #

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)]

biclique :: Graph g => [Vertex g] -> [Vertex g] -> g Source #

The biclique on a list 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)

star :: Graph g => Vertex g -> [Vertex g] -> g Source #

The star formed by a centre vertex and 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)]

tree :: Graph g => Tree (Vertex g) -> g Source #

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)]

forest :: Graph g => Forest (Vertex g) -> g Source #

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

Conversion between graph data types

class ToGraph t where Source #

The ToGraph type class captures data types that can be converted to polymorphic graph expressions. The conversion method toGraph semantically acts as the identity on graph data structures, but allows to convert graphs between different data representations.

      toGraph (g     :: Graph a  ) :: Graph a       == g
show (toGraph (1 * 2 :: Graph Int) :: Relation Int) == "edge 1 2"

Minimal complete definition

toGraph

Associated Types

type ToVertex t Source #

Methods

toGraph :: (Graph g, Vertex g ~ ToVertex t) => t -> g Source #

Instances

ToGraph (Fold a) Source # 

Associated Types

type ToVertex (Fold a) :: * Source #

Methods

toGraph :: (Graph g, (* ~ Vertex g) (ToVertex (Fold a))) => Fold a -> g Source #

ToGraph (Graph a) Source # 

Associated Types

type ToVertex (Graph a) :: * Source #

Methods

toGraph :: (Graph g, (* ~ Vertex g) (ToVertex (Graph a))) => Graph a -> g Source #