containers-0.5.11.0: Assorted concrete container types

Copyright(c) The University of Glasgow 2002
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell98

Data.Graph

Contents

Description

A version of the graph algorithms described in:

Structuring Depth-First Search Algorithms in Haskell, by David King and John Launchbury.

Synopsis

External interface

stronglyConnComp Source #

Arguments

:: Ord key 
=> [(node, key, [key])]

The graph: a list of nodes uniquely identified by keys, with a list of keys of nodes this node has edges to. The out-list may contain keys that don't correspond to nodes of the graph; such edges are ignored.

-> [SCC node] 

The strongly connected components of a directed graph, topologically sorted.

stronglyConnCompR Source #

Arguments

:: Ord key 
=> [(node, key, [key])]

The graph: a list of nodes uniquely identified by keys, with a list of keys of nodes this node has edges to. The out-list may contain keys that don't correspond to nodes of the graph; such edges are ignored.

-> [SCC (node, key, [key])]

Topologically sorted

The strongly connected components of a directed graph, topologically sorted. The function is the same as stronglyConnComp, except that all the information about each node retained. This interface is used when you expect to apply SCC to (some of) the result of SCC, so you don't want to lose the dependency information.

data SCC vertex Source #

Strongly connected component.

Constructors

AcyclicSCC vertex

A single vertex that is not in any cycle.

CyclicSCC [vertex]

A maximal set of mutually reachable vertices.

Instances
Functor SCC Source #

Since: containers-0.5.4

Instance details

Defined in Data.Graph

Methods

fmap :: (a -> b) -> SCC a -> SCC b Source #

(<$) :: a -> SCC b -> SCC a Source #

Foldable SCC Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

fold :: Monoid m => SCC m -> m Source #

foldMap :: Monoid m => (a -> m) -> SCC a -> m Source #

foldr :: (a -> b -> b) -> b -> SCC a -> b Source #

foldr' :: (a -> b -> b) -> b -> SCC a -> b Source #

foldl :: (b -> a -> b) -> b -> SCC a -> b Source #

foldl' :: (b -> a -> b) -> b -> SCC a -> b Source #

foldr1 :: (a -> a -> a) -> SCC a -> a Source #

foldl1 :: (a -> a -> a) -> SCC a -> a Source #

toList :: SCC a -> [a] Source #

null :: SCC a -> Bool Source #

length :: SCC a -> Int Source #

elem :: Eq a => a -> SCC a -> Bool Source #

maximum :: Ord a => SCC a -> a Source #

minimum :: Ord a => SCC a -> a Source #

sum :: Num a => SCC a -> a Source #

product :: Num a => SCC a -> a Source #

Traversable SCC Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

traverse :: Applicative f => (a -> f b) -> SCC a -> f (SCC b) Source #

sequenceA :: Applicative f => SCC (f a) -> f (SCC a) Source #

mapM :: Monad m => (a -> m b) -> SCC a -> m (SCC b) Source #

sequence :: Monad m => SCC (m a) -> m (SCC a) Source #

Eq1 SCC Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

liftEq :: (a -> b -> Bool) -> SCC a -> SCC b -> Bool Source #

Read1 SCC Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (SCC a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [SCC a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (SCC a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [SCC a] Source #

Show1 SCC Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> SCC a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [SCC a] -> ShowS Source #

Eq vertex => Eq (SCC vertex) Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

(==) :: SCC vertex -> SCC vertex -> Bool Source #

(/=) :: SCC vertex -> SCC vertex -> Bool Source #

Data vertex => Data (SCC vertex) Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SCC vertex -> c (SCC vertex) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SCC vertex) Source #

toConstr :: SCC vertex -> Constr Source #

dataTypeOf :: SCC vertex -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SCC vertex)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SCC vertex)) Source #

gmapT :: (forall b. Data b => b -> b) -> SCC vertex -> SCC vertex Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SCC vertex -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SCC vertex -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> SCC vertex -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SCC vertex -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) Source #

Read vertex => Read (SCC vertex) Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

readsPrec :: Int -> ReadS (SCC vertex) Source #

readList :: ReadS [SCC vertex] Source #

readPrec :: ReadPrec (SCC vertex) Source #

readListPrec :: ReadPrec [SCC vertex] Source #

Show vertex => Show (SCC vertex) Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

showsPrec :: Int -> SCC vertex -> ShowS Source #

show :: SCC vertex -> String Source #

showList :: [SCC vertex] -> ShowS Source #

Generic (SCC vertex) Source # 
Instance details

Defined in Data.Graph

Associated Types

type Rep (SCC vertex) :: * -> * Source #

Methods

from :: SCC vertex -> Rep (SCC vertex) x Source #

to :: Rep (SCC vertex) x -> SCC vertex Source #

NFData a => NFData (SCC a) Source # 
Instance details

Defined in Data.Graph

Methods

rnf :: SCC a -> () Source #

Generic1 SCC Source # 
Instance details

Defined in Data.Graph

Associated Types

type Rep1 SCC :: k -> * Source #

Methods

from1 :: SCC a -> Rep1 SCC a Source #

to1 :: Rep1 SCC a -> SCC a Source #

type Rep (SCC vertex) Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

type Rep (SCC vertex) = D1 (MetaData "SCC" "Data.Graph" "containers-0.5.11.0" False) (C1 (MetaCons "AcyclicSCC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 vertex)) :+: C1 (MetaCons "CyclicSCC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [vertex])))
type Rep1 SCC Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

flattenSCC :: SCC vertex -> [vertex] Source #

The vertices of a strongly connected component.

flattenSCCs :: [SCC a] -> [a] Source #

The vertices of a list of strongly connected components.

Graphs

type Graph = Table [Vertex] Source #

Adjacency list representation of a graph, mapping each vertex to its list of successors.

type Table a = Array Vertex a Source #

Table indexed by a contiguous set of vertices.

type Bounds = (Vertex, Vertex) Source #

The bounds of a Table.

type Edge = (Vertex, Vertex) Source #

An edge from the first vertex to the second.

type Vertex = Int Source #

Abstract representation of vertices.

Building graphs

graphFromEdges :: Ord key => [(node, key, [key])] -> (Graph, Vertex -> (node, key, [key]), key -> Maybe Vertex) Source #

Build a graph from a list of nodes uniquely identified by keys, with a list of keys of nodes this node should have edges to. The out-list may contain keys that don't correspond to nodes of the graph; they are ignored.

graphFromEdges' :: Ord key => [(node, key, [key])] -> (Graph, Vertex -> (node, key, [key])) Source #

Identical to graphFromEdges, except that the return value does not include the function which maps keys to vertices. This version of graphFromEdges is for backwards compatibility.

buildG :: Bounds -> [Edge] -> Graph Source #

Build a graph from a list of edges.

transposeG :: Graph -> Graph Source #

The graph obtained by reversing all edges.

Graph properties

vertices :: Graph -> [Vertex] Source #

All vertices of a graph.

edges :: Graph -> [Edge] Source #

All edges of a graph.

outdegree :: Graph -> Table Int Source #

A table of the count of edges from each node.

indegree :: Graph -> Table Int Source #

A table of the count of edges into each node.

Algorithms

dfs :: Graph -> [Vertex] -> Forest Vertex Source #

A spanning forest of the part of the graph reachable from the listed vertices, obtained from a depth-first search of the graph starting at each of the listed vertices in order.

dff :: Graph -> Forest Vertex Source #

A spanning forest of the graph, obtained from a depth-first search of the graph starting from each vertex in an unspecified order.

topSort :: Graph -> [Vertex] Source #

A topological sort of the graph. The order is partially specified by the condition that a vertex i precedes j whenever j is reachable from i but not vice versa.

components :: Graph -> Forest Vertex Source #

The connected components of a graph. Two vertices are connected if there is a path between them, traversing edges in either direction.

scc :: Graph -> Forest Vertex Source #

The strongly connected components of a graph.

bcc :: Graph -> Forest [Vertex] Source #

The biconnected components of a graph. An undirected graph is biconnected if the deletion of any vertex leaves it connected.

reachable :: Graph -> Vertex -> [Vertex] Source #

A list of vertices reachable from a given vertex.

path :: Graph -> Vertex -> Vertex -> Bool Source #

Is the second vertex reachable from the first?

type Forest a = [Tree a] Source #

data Tree a Source #

Multi-way trees, also known as rose trees.

Constructors

Node a (Forest a) 
Instances
Monad Tree Source # 
Instance details

Defined in Data.Tree

Methods

(>>=) :: Tree a -> (a -> Tree b) -> Tree b Source #

(>>) :: Tree a -> Tree b -> Tree b Source #

return :: a -> Tree a Source #

fail :: String -> Tree a Source #

Functor Tree Source # 
Instance details

Defined in Data.Tree

Methods

fmap :: (a -> b) -> Tree a -> Tree b Source #

(<$) :: a -> Tree b -> Tree a Source #

MonadFix Tree Source #

Since: containers-0.5.11

Instance details

Defined in Data.Tree

Methods

mfix :: (a -> Tree a) -> Tree a Source #

Applicative Tree Source # 
Instance details

Defined in Data.Tree

Methods

pure :: a -> Tree a Source #

(<*>) :: Tree (a -> b) -> Tree a -> Tree b Source #

liftA2 :: (a -> b -> c) -> Tree a -> Tree b -> Tree c Source #

(*>) :: Tree a -> Tree b -> Tree b Source #

(<*) :: Tree a -> Tree b -> Tree a Source #

Foldable Tree Source # 
Instance details

Defined in Data.Tree

Methods

fold :: Monoid m => Tree m -> m Source #

foldMap :: Monoid m => (a -> m) -> Tree a -> m Source #

foldr :: (a -> b -> b) -> b -> Tree a -> b Source #

foldr' :: (a -> b -> b) -> b -> Tree a -> b Source #

foldl :: (b -> a -> b) -> b -> Tree a -> b Source #

foldl' :: (b -> a -> b) -> b -> Tree a -> b Source #

foldr1 :: (a -> a -> a) -> Tree a -> a Source #

foldl1 :: (a -> a -> a) -> Tree a -> a Source #

toList :: Tree a -> [a] Source #

null :: Tree a -> Bool Source #

length :: Tree a -> Int Source #

elem :: Eq a => a -> Tree a -> Bool Source #

maximum :: Ord a => Tree a -> a Source #

minimum :: Ord a => Tree a -> a Source #

sum :: Num a => Tree a -> a Source #

product :: Num a => Tree a -> a Source #

Traversable Tree Source # 
Instance details

Defined in Data.Tree

Methods

traverse :: Applicative f => (a -> f b) -> Tree a -> f (Tree b) Source #

sequenceA :: Applicative f => Tree (f a) -> f (Tree a) Source #

mapM :: Monad m => (a -> m b) -> Tree a -> m (Tree b) Source #

sequence :: Monad m => Tree (m a) -> m (Tree a) Source #

Eq1 Tree Source #

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

liftEq :: (a -> b -> Bool) -> Tree a -> Tree b -> Bool Source #

Ord1 Tree Source #

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

liftCompare :: (a -> b -> Ordering) -> Tree a -> Tree b -> Ordering Source #

Read1 Tree Source #

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Tree a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Tree a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Tree a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Tree a] Source #

Show1 Tree Source #

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Tree a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Tree a] -> ShowS Source #

MonadZip Tree Source # 
Instance details

Defined in Data.Tree

Methods

mzip :: Tree a -> Tree b -> Tree (a, b) Source #

mzipWith :: (a -> b -> c) -> Tree a -> Tree b -> Tree c Source #

munzip :: Tree (a, b) -> (Tree a, Tree b) Source #

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

Defined in Data.Tree

Methods

(==) :: Tree a -> Tree a -> Bool Source #

(/=) :: Tree a -> Tree a -> Bool Source #

Data a => Data (Tree a) Source # 
Instance details

Defined in Data.Tree

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tree a -> c (Tree a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tree a) Source #

toConstr :: Tree a -> Constr Source #

dataTypeOf :: Tree a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Tree a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tree a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Tree a -> Tree a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Tree a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tree a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) Source #

Read a => Read (Tree a) Source # 
Instance details

Defined in Data.Tree

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

Defined in Data.Tree

Methods

showsPrec :: Int -> Tree a -> ShowS Source #

show :: Tree a -> String Source #

showList :: [Tree a] -> ShowS Source #

Generic (Tree a) Source # 
Instance details

Defined in Data.Tree

Associated Types

type Rep (Tree a) :: * -> * Source #

Methods

from :: Tree a -> Rep (Tree a) x Source #

to :: Rep (Tree a) x -> Tree a Source #

NFData a => NFData (Tree a) Source # 
Instance details

Defined in Data.Tree

Methods

rnf :: Tree a -> () Source #

Generic1 Tree Source # 
Instance details

Defined in Data.Tree

Associated Types

type Rep1 Tree :: k -> * Source #

Methods

from1 :: Tree a -> Rep1 Tree a Source #

to1 :: Rep1 Tree a -> Tree a Source #

type Rep (Tree a) Source #

Since: containers-0.5.8

Instance details

Defined in Data.Tree

type Rep (Tree a) = D1 (MetaData "Tree" "Data.Tree" "containers-0.5.11.0" False) (C1 (MetaCons "Node" PrefixI True) (S1 (MetaSel (Just "rootLabel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "subForest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Forest a))))
type Rep1 Tree Source #

Since: containers-0.5.8

Instance details

Defined in Data.Tree

type Rep1 Tree = D1 (MetaData "Tree" "Data.Tree" "containers-0.5.11.0" False) (C1 (MetaCons "Node" PrefixI True) (S1 (MetaSel (Just "rootLabel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "subForest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 Tree)))