mini-1.5.5.0: Minimal essentials
Safe HaskellSafe-Inferred
LanguageHaskell2010

Mini.Data.Graph

Description

A structure representing unique vertices and their interrelations

Synopsis

A Note on Performance

In order to provide a friendly user interface, some performance has been sacrificed. The internal adjacency lists are implemented via maps rather than arrays, meaning accesses are done in logarithmic time rather than constant time.

Type

data Graph a Source #

A graph with directed edges between vertices of type a

Instances

Instances details
Foldable Graph Source # 
Instance details

Defined in Mini.Data.Graph

Methods

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

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

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

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

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

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

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

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

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

toList :: Graph a -> [a] #

null :: Graph a -> Bool #

length :: Graph a -> Int #

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

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

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

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

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

Ord a => Monoid (Graph a) Source # 
Instance details

Defined in Mini.Data.Graph

Methods

mempty :: Graph a #

mappend :: Graph a -> Graph a -> Graph a #

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

Ord a => Semigroup (Graph a) Source # 
Instance details

Defined in Mini.Data.Graph

Methods

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

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

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

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

Defined in Mini.Data.Graph

Methods

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

show :: Graph a -> String #

showList :: [Graph a] -> ShowS #

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

Defined in Mini.Data.Graph

Methods

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

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

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

Defined in Mini.Data.Graph

Methods

compare :: Graph a -> Graph a -> Ordering #

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

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

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

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

max :: Graph a -> Graph a -> Graph a #

min :: Graph a -> Graph a -> Graph a #

Primitive Recursion

graph Source #

Arguments

:: (Map a (Set a) -> Map a (Set a) -> b)

Function applied to the adjacency lists of the graph: incoming edges, outgoing edges

-> Graph a

The graph

-> b 

Primitive recursion on graphs (internally represented by adjacency lists)

Algorithms

distance :: Ord a => Graph a -> a -> a -> Maybe Int Source #

Get the shortest distance in a graph between a vertex and another

layers :: Ord a => Graph a -> a -> [[a]] Source #

Breadth-first search for the hierarchy in a graph from a starting vertex

path :: Ord a => Graph a -> a -> a -> Bool Source #

Check whether there is a path in a graph from a vertex to another

reachable :: Ord a => Graph a -> a -> [a] Source #

Get the reachable vertices in a graph from a starting vertex

sort :: Ord a => Graph a -> [a] Source #

Topologically sort a graph (assumes acyclicity)

Construction

empty :: Graph a Source #

The empty graph

fromList :: Ord a => [(a, [a])] -> Graph a Source #

Make a graph from a list of vertex associations

singleton :: a -> Graph a Source #

Make a graph with an isolated vertex

Modification

add :: Ord a => a -> Graph a -> Graph a Source #

Add an isolated vertex to a graph unless already present

remove :: Ord a => a -> Graph a -> Graph a Source #

Remove a vertex and its associations from a graph

connect :: Ord a => a -> [a] -> Graph a -> Graph a Source #

Add edges from a vertex to a list of vertices in a graph

disconnect :: Ord a => a -> [a] -> Graph a -> Graph a Source #

Remove edges from a vertex to a list of vertices in a graph

transpose :: Graph a -> Graph a Source #

Reverse the edges of a graph

Query

assocs :: Graph a -> [(a, [a])] Source #

Get the vertex associations of a graph

edges :: Graph a -> [(a, a)] Source #

Get the edges of a graph

vertices :: Graph a -> [a] Source #

Get the vertices of a graph

indegree :: Ord a => a -> Graph a -> Maybe Int Source #

Get the number of incoming edges to a vertex in a graph

indegrees :: Graph a -> [(a, Int)] Source #

Get the number of incoming edges of each vertex in a graph

outdegree :: Ord a => a -> Graph a -> Maybe Int Source #

Get the number of outgoing edges from a vertex in a graph

outdegrees :: Graph a -> [(a, Int)] Source #

Get the number of outgoing edges of each vertex in a graph

lookup :: Ord a => a -> Graph a -> Maybe [a] Source #

Get the associations of a vertex from a graph

lookupGE :: Ord a => a -> Graph a -> Maybe (a, [a]) Source #

Get the associations of the least vertex greater than or equal to a vertex

lookupGT :: Ord a => a -> Graph a -> Maybe (a, [a]) Source #

Get the associations of the least vertex strictly greater than a vertex

lookupLE :: Ord a => a -> Graph a -> Maybe (a, [a]) Source #

Get the associations of the greatest vertex less than or equal to a vertex

lookupLT :: Ord a => a -> Graph a -> Maybe (a, [a]) Source #

Get the associations of the greatest vertex strictly less than a vertex

lookupMax :: Graph a -> Maybe (a, [a]) Source #

Get the associations of the maximum vertex from a graph

lookupMin :: Graph a -> Maybe (a, [a]) Source #

Get the associations of the minimum vertex from a graph

member :: Ord a => a -> Graph a -> Bool Source #

Check whether a vertex is in a graph

sourceMax :: Graph a -> Maybe a Source #

Get the maximum vertex with no incoming edges from a graph

sourceMin :: Graph a -> Maybe a Source #

Get the minimum vertex with no incoming edges from a graph

sources :: Graph a -> [a] Source #

Get the vertices with no incoming edges from a graph

sinkMax :: Graph a -> Maybe a Source #

Get the maximum vertex with no outgoing edges from a graph

sinkMin :: Graph a -> Maybe a Source #

Get the minimum vertex with no outgoing edges from a graph

sinks :: Graph a -> [a] Source #

Get the vertices with no outgoing edges from a graph