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.Internal

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 various internal utilities and data structures used throughout the library, such as lists with fast concatenation. The API is unstable and unsafe, and is exposed only for documentation.

Synopsis

General data structures

newtype List a Source #

An abstract list data type with O(1) time concatenation (the current implementation uses difference lists). Here a is the type of list elements. List a is a Monoid: mempty corresponds to the empty list and two lists can be concatenated with mappend (or operator <>). Singleton lists can be constructed using the function pure from the Applicative instance. List a is also an instance of IsList, therefore you can use list literals, e.g. [1,4] :: List Int is the same as pure 1 <> pure 4; note that this requires the OverloadedLists GHC extension. To extract plain Haskell lists you can use the toList function from the Foldable instance.

Constructors

List (Endo [a]) 
Instances
Monad List Source # 
Instance details

Defined in Algebra.Graph.Internal

Methods

(>>=) :: List a -> (a -> List b) -> List b #

(>>) :: List a -> List b -> List b #

return :: a -> List a #

fail :: String -> List a #

Functor List Source # 
Instance details

Defined in Algebra.Graph.Internal

Methods

fmap :: (a -> b) -> List a -> List b #

(<$) :: a -> List b -> List a #

Applicative List Source # 
Instance details

Defined in Algebra.Graph.Internal

Methods

pure :: a -> List a #

(<*>) :: List (a -> b) -> List a -> List b #

liftA2 :: (a -> b -> c) -> List a -> List b -> List c #

(*>) :: List a -> List b -> List b #

(<*) :: List a -> List b -> List a #

Foldable List Source # 
Instance details

Defined in Algebra.Graph.Internal

Methods

fold :: Monoid m => List m -> m #

foldMap :: Monoid m => (a -> m) -> List a -> m #

foldr :: (a -> b -> b) -> b -> List a -> b #

foldr' :: (a -> b -> b) -> b -> List a -> b #

foldl :: (b -> a -> b) -> b -> List a -> b #

foldl' :: (b -> a -> b) -> b -> List a -> b #

foldr1 :: (a -> a -> a) -> List a -> a #

foldl1 :: (a -> a -> a) -> List a -> a #

toList :: List a -> [a] #

null :: List a -> Bool #

length :: List a -> Int #

elem :: Eq a => a -> List a -> Bool #

maximum :: Ord a => List a -> a #

minimum :: Ord a => List a -> a #

sum :: Num a => List a -> a #

product :: Num a => List a -> a #

IsList (List a) Source # 
Instance details

Defined in Algebra.Graph.Internal

Associated Types

type Item (List a) :: * #

Methods

fromList :: [Item (List a)] -> List a #

fromListN :: Int -> [Item (List a)] -> List a #

toList :: List a -> [Item (List a)] #

Eq a => Eq (List a) Source # 
Instance details

Defined in Algebra.Graph.Internal

Methods

(==) :: List a -> List a -> Bool #

(/=) :: List a -> List a -> Bool #

Ord a => Ord (List a) Source # 
Instance details

Defined in Algebra.Graph.Internal

Methods

compare :: List a -> List a -> Ordering #

(<) :: List a -> List a -> Bool #

(<=) :: List a -> List a -> Bool #

(>) :: List a -> List a -> Bool #

(>=) :: List a -> List a -> Bool #

max :: List a -> List a -> List a #

min :: List a -> List a -> List a #

Show a => Show (List a) Source # 
Instance details

Defined in Algebra.Graph.Internal

Methods

showsPrec :: Int -> List a -> ShowS #

show :: List a -> String #

showList :: [List a] -> ShowS #

Semigroup (List a) Source # 
Instance details

Defined in Algebra.Graph.Internal

Methods

(<>) :: List a -> List a -> List a #

sconcat :: NonEmpty (List a) -> List a #

stimes :: Integral b => b -> List a -> List a #

Monoid (List a) Source # 
Instance details

Defined in Algebra.Graph.Internal

Methods

mempty :: List a #

mappend :: List a -> List a -> List a #

mconcat :: [List a] -> List a #

type Item (List a) Source # 
Instance details

Defined in Algebra.Graph.Internal

type Item (List a) = a

Data structures for graph traversal

data Focus a Source #

The focus of a graph expression is a flattened represenentation of the subgraph under focus, its context, as well as the list of all encountered vertices. See removeEdge for a use-case example.

Constructors

Focus

All vertices (leaves) of the graph expression.

Fields

  • ok :: Bool

    True if focus on the specified subgraph is obtained.

  • is :: List a

    Inputs into the focused subgraph.

  • os :: List a

    Outputs out of the focused subgraph.

  • vs :: List a
     

emptyFocus :: Focus a Source #

Focus on the empty graph.

vertexFocus :: (a -> Bool) -> a -> Focus a Source #

Focus on the graph with a single vertex, given a predicate indicating whether the vertex is of interest.

overlayFoci :: Focus a -> Focus a -> Focus a Source #

Overlay two foci.

connectFoci :: Focus a -> Focus a -> Focus a Source #

Connect two foci.

data Hit Source #

An auxiliary data type for hasEdge: when searching for an edge, we can hit its Tail, i.e. the source vertex, the whole Edge, or Miss it entirely.

Constructors

Miss 
Tail 
Edge 
Instances
Eq Hit Source # 
Instance details

Defined in Algebra.Graph.Internal

Methods

(==) :: Hit -> Hit -> Bool #

(/=) :: Hit -> Hit -> Bool #

Ord Hit Source # 
Instance details

Defined in Algebra.Graph.Internal

Methods

compare :: Hit -> Hit -> Ordering #

(<) :: Hit -> Hit -> Bool #

(<=) :: Hit -> Hit -> Bool #

(>) :: Hit -> Hit -> Bool #

(>=) :: Hit -> Hit -> Bool #

max :: Hit -> Hit -> Hit #

min :: Hit -> Hit -> Hit #

foldr1Safe :: (a -> a -> a) -> [a] -> Maybe a Source #

A safe version of foldr1