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

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

Algebra.Graph.Labelled

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 provides a minimal and experimental implementation of algebraic graphs with edge labels. The API will be expanded in the next release.

Synopsis

Algebraic data type for edge-labeleld graphs

data Graph e a Source #

Edge-labelled graphs, where the type variable e stands for edge labels. For example, Graph Bool a is isomorphic to unlabelled graphs defined in the top-level module Algebra.Graph.Graph, where False and True denote the lack of and the existence of an unlabelled edge, respectively.

Constructors

Empty 
Vertex a 
Connect e (Graph e a) (Graph e a) 
Instances
Functor (Graph e) Source # 
Instance details

Defined in Algebra.Graph.Labelled

Methods

fmap :: (a -> b) -> Graph e a -> Graph e b #

(<$) :: a -> Graph e b -> Graph e a #

Foldable (Graph e) Source # 
Instance details

Defined in Algebra.Graph.Labelled

Methods

fold :: Monoid m => Graph e m -> m #

foldMap :: Monoid m => (a -> m) -> Graph e a -> m #

foldr :: (a -> b -> b) -> b -> Graph e a -> b #

foldr' :: (a -> b -> b) -> b -> Graph e a -> b #

foldl :: (b -> a -> b) -> b -> Graph e a -> b #

foldl' :: (b -> a -> b) -> b -> Graph e a -> b #

foldr1 :: (a -> a -> a) -> Graph e a -> a #

foldl1 :: (a -> a -> a) -> Graph e a -> a #

toList :: Graph e a -> [a] #

null :: Graph e a -> Bool #

length :: Graph e a -> Int #

elem :: Eq a => a -> Graph e a -> Bool #

maximum :: Ord a => Graph e a -> a #

minimum :: Ord a => Graph e a -> a #

sum :: Num a => Graph e a -> a #

product :: Num a => Graph e a -> a #

Traversable (Graph e) Source # 
Instance details

Defined in Algebra.Graph.Labelled

Methods

traverse :: Applicative f => (a -> f b) -> Graph e a -> f (Graph e b) #

sequenceA :: Applicative f => Graph e (f a) -> f (Graph e a) #

mapM :: Monad m => (a -> m b) -> Graph e a -> m (Graph e b) #

sequence :: Monad m => Graph e (m a) -> m (Graph e a) #

(Show a, Show e) => Show (Graph e a) Source # 
Instance details

Defined in Algebra.Graph.Labelled

Methods

showsPrec :: Int -> Graph e a -> ShowS #

show :: Graph e a -> String #

showList :: [Graph e a] -> ShowS #

Dioid e => Graph (Graph e a) Source # 
Instance details

Defined in Algebra.Graph.Labelled

Associated Types

type Vertex (Graph e a) :: * Source #

Methods

empty :: Graph e a Source #

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

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

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

type Vertex (Graph e a) Source # 
Instance details

Defined in Algebra.Graph.Labelled

type Vertex (Graph e a) = a

type UnlabelledGraph a = Graph Bool a Source #

A type synonym for unlabelled graphs.

empty :: Graph e a Source #

Construct the empty graph. An alias for the constructor Empty. Complexity: O(1) time, memory and size.

vertex :: a -> Graph e a Source #

Construct the graph comprising a single isolated vertex. An alias for the constructor Vertex. Complexity: O(1) time, memory and size.

edge :: Dioid e => a -> a -> Graph e a Source #

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

overlay :: Semilattice e => Graph e a -> Graph e a -> Graph e a Source #

Overlay two graphs. An alias for Connect zero. This is a commutative, associative and idempotent operation with the identity empty. Complexity: O(1) time and memory, O(s1 + s2) size.

connect :: Dioid e => Graph e a -> Graph e a -> Graph e a Source #

Connect two graphs. An alias for Connect one. This is an associative operation with the identity empty, which distributes over overlay and obeys the decomposition axiom. See the full list of laws in Algebra.Graph. Complexity: O(1) time and memory, O(s1 + s2) size. Note that the number of edges in the resulting graph is quadratic with respect to the number of vertices of the arguments: m = O(m1 + m2 + n1 * n2).

connectBy :: e -> Graph e a -> Graph e a -> Graph e a Source #

Connect two graphs with edges labelled by a given label. An alias for Connect. Complexity: O(1) time and memory, O(s1 + s2) size. Note that the number of edges in the resulting graph is quadratic with respect to the number of vertices of the arguments: m = O(m1 + m2 + n1 * n2).

(-<) :: Graph e a -> e -> (Graph e a, e) infixl 5 Source #

The left-hand part of a convenient ternary-ish operator x -<e>- y for connecting graphs with labelled edges. For example:

x = vertex "x"
y = vertex "y"
z = x -<2>- y

(>-) :: (Graph e a, e) -> Graph e a -> Graph e a infixl 5 Source #

The right-hand part of a convenient ternary-ish operator x -<e>- y for connecting graphs with labelled edges. For example:

x = vertex "x"
y = vertex "y"
z = x -<2>- y

Operations

edgeLabel :: (Eq a, Semilattice e) => a -> a -> Graph e a -> e Source #

Extract the label of a specified edge from a graph.