Cabal-3.2.1.0: A framework for packaging Haskell software
Copyright(c) Edward Z. Yang 2016
LicenseBSD3
Maintainercabal-dev@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Distribution.Compat.Graph

Description

A data type representing directed graphs, backed by Data.Graph. It is strict in the node type.

This is an alternative interface to Data.Graph. In this interface, nodes (identified by the IsNode type class) are associated with a key and record the keys of their neighbors. This interface is more convenient than Graph, which requires vertices to be explicitly handled by integer indexes.

The current implementation has somewhat peculiar performance characteristics. The asymptotics of all map-like operations mirror their counterparts in Data.Map. However, to perform a graph operation, we first must build the Data.Graph representation, an operation that takes O(V + E log V). However, this operation can be amortized across all queries on that particular graph.

Some nodes may be broken, i.e., refer to neighbors which are not stored in the graph. In our graph algorithms, we transparently ignore such edges; however, you can easily query for the broken vertices of a graph using broken (and should, e.g., to ensure that a closure of a graph is well-formed.) It's possible to take a closed subset of a broken graph and get a well-formed graph.

Synopsis

Graph type

data Graph a Source #

A graph of nodes a. The nodes are expected to have instance of class IsNode.

Instances

Instances details
Foldable Graph # 
Instance details

Defined in Distribution.Compat.Graph

Methods

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

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

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

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

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

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

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

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

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

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

null :: Graph a -> Bool Source #

length :: Graph a -> Int Source #

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

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

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

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

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

(Eq (Key a), Eq a) => Eq (Graph a) # 
Instance details

Defined in Distribution.Compat.Graph

Methods

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

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

(IsNode a, Read a, Show (Key a)) => Read (Graph a) # 
Instance details

Defined in Distribution.Compat.Graph

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

Defined in Distribution.Compat.Graph

(IsNode a, Binary a, Show (Key a)) => Binary (Graph a) # 
Instance details

Defined in Distribution.Compat.Graph

Methods

put :: Graph a -> Put Source #

get :: Get (Graph a) Source #

putList :: [Graph a] -> Put Source #

(NFData a, NFData (Key a)) => NFData (Graph a) # 
Instance details

Defined in Distribution.Compat.Graph

Methods

rnf :: Graph a -> () Source #

Structured a => Structured (Graph a) # 
Instance details

Defined in Distribution.Compat.Graph

Methods

structure :: Proxy (Graph a) -> Structure Source #

structureHash' :: Tagged (Graph a) MD5

class Ord (Key a) => IsNode a where Source #

The IsNode class is used for datatypes which represent directed graph nodes. A node of type a is associated with some unique key of type Key a; given a node we can determine its key (nodeKey) and the keys of its neighbors (nodeNeighbors).

Associated Types

type Key a Source #

Methods

nodeKey :: a -> Key a Source #

nodeNeighbors :: a -> [Key a] Source #

Query

null :: Graph a -> Bool Source #

O(1). Is the graph empty?

size :: Graph a -> Int Source #

O(1). The number of nodes in the graph.

member :: IsNode a => Key a -> Graph a -> Bool Source #

O(log V). Check if the key is in the graph.

lookup :: IsNode a => Key a -> Graph a -> Maybe a Source #

O(log V). Lookup the node at a key in the graph.

Construction

empty :: IsNode a => Graph a Source #

O(1). The empty graph.

insert :: IsNode a => a -> Graph a -> Graph a Source #

O(log V). Insert a node into a graph.

deleteKey :: IsNode a => Key a -> Graph a -> Graph a Source #

O(log V). Delete the node at a key from the graph.

deleteLookup :: IsNode a => Key a -> Graph a -> (Maybe a, Graph a) Source #

O(log V). Lookup and delete. This function returns the deleted value if it existed.

Combine

unionLeft :: IsNode a => Graph a -> Graph a -> Graph a Source #

O(V + V'). Left-biased union, preferring entries from the first map when conflicts occur.

unionRight :: IsNode a => Graph a -> Graph a -> Graph a Source #

O(V + V'). Right-biased union, preferring entries from the second map when conflicts occur. nodeKey x = nodeKey (f x).

Graph algorithms

stronglyConnComp :: Graph a -> [SCC a] Source #

Ω(V + E). Compute the strongly connected components of a graph. Requires amortized construction of graph.

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

Instances details
Functor SCC

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

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 #

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

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

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

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

Read1 SCC

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

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)

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

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

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

Data vertex => Data (SCC vertex)

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 :: forall r r'. (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)

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)

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)

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Associated Types

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

Methods

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

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

NFData a => NFData (SCC a) 
Instance details

Defined in Data.Graph

Methods

rnf :: SCC a -> () Source #

Generic1 SCC

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Associated Types

type Rep1 SCC :: k -> Type Source #

Methods

from1 :: forall (a :: k). SCC a -> Rep1 SCC a Source #

to1 :: forall (a :: k). Rep1 SCC a -> SCC a Source #

type Rep (SCC vertex) 
Instance details

Defined in Data.Graph

type Rep (SCC vertex) = D1 ('MetaData "SCC" "Data.Graph" "containers-0.6.5.1" '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 
Instance details

Defined in Data.Graph

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

Ω(V + E). Compute the cycles of a graph. Requires amortized construction of graph.

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

O(1). Return a list of nodes paired with their broken neighbors (i.e., neighbor keys which are not in the graph). Requires amortized construction of graph.

neighbors :: Graph a -> Key a -> Maybe [a] Source #

Lookup the immediate neighbors from a key in the graph. Requires amortized construction of graph.

revNeighbors :: Graph a -> Key a -> Maybe [a] Source #

Lookup the immediate reverse neighbors from a key in the graph. Requires amortized construction of graph.

closure :: Graph a -> [Key a] -> Maybe [a] Source #

Compute the subgraph which is the closure of some set of keys. Returns Nothing if one (or more) keys are not present in the graph. Requires amortized construction of graph.

revClosure :: Graph a -> [Key a] -> Maybe [a] Source #

Compute the reverse closure of a graph from some set of keys. Returns Nothing if one (or more) keys are not present in the graph. Requires amortized construction of graph.

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

Topologically sort the nodes of a graph. Requires amortized construction of graph.

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

Reverse topologically sort the nodes of a graph. Requires amortized construction of graph.

Conversions

Maps

toMap :: Graph a -> Map (Key a) a Source #

O(1). Convert a graph into a map from keys to nodes. The resulting map m is guaranteed to have the property that all ((k,n) -> k == nodeKey n) (toList m).

Lists

fromDistinctList :: (IsNode a, Show (Key a)) => [a] -> Graph a Source #

O(V log V). Convert a list of nodes (with distinct keys) into a graph.

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

O(V). Convert a graph into a list of nodes.

keys :: Graph a -> [Key a] Source #

O(V). Convert a graph into a list of keys.

Sets

keysSet :: Graph a -> Set (Key a) Source #

O(V). Convert a graph into a set of keys.

Graphs

toGraph :: Graph a -> (Graph, Vertex -> a, Key a -> Maybe Vertex) Source #

O(1). Convert a graph into a Graph. Requires amortized construction of graph.

Node type

data Node k a Source #

A simple, trivial data type which admits an IsNode instance.

Constructors

N a k [k] 

Instances

Instances details
Functor (Node k) # 
Instance details

Defined in Distribution.Compat.Graph

Methods

fmap :: (a -> b) -> Node k a -> Node k b Source #

(<$) :: a -> Node k b -> Node k a Source #

(Eq a, Eq k) => Eq (Node k a) # 
Instance details

Defined in Distribution.Compat.Graph

Methods

(==) :: Node k a -> Node k a -> Bool #

(/=) :: Node k a -> Node k a -> Bool #

(Show a, Show k) => Show (Node k a) # 
Instance details

Defined in Distribution.Compat.Graph

Methods

showsPrec :: Int -> Node k a -> ShowS Source #

show :: Node k a -> String Source #

showList :: [Node k a] -> ShowS Source #

Ord k => IsNode (Node k a) # 
Instance details

Defined in Distribution.Compat.Graph

Associated Types

type Key (Node k a) Source #

Methods

nodeKey :: Node k a -> Key (Node k a) Source #

nodeNeighbors :: Node k a -> [Key (Node k a)] Source #

type Key (Node k a) # 
Instance details

Defined in Distribution.Compat.Graph

type Key (Node k a) = k

nodeValue :: Node k a -> a Source #

Get the value from a Node.