fgl-5.5.0.0: Martin Erwig's Functional Graph Library

Safe HaskellSafe-Inferred

Data.Graph.Inductive.Query.Monad

Contents

Description

Monadic Graph Algorithms

Synopsis

Additional Graph Utilities

mapFst :: (a -> b) -> (a, c) -> (b, c)Source

mapSnd :: (a -> b) -> (c, a) -> (c, b)Source

(><) :: (a -> b) -> (c -> d) -> (a, c) -> (b, d)Source

orP :: (a -> Bool) -> (b -> Bool) -> (a, b) -> BoolSource

Graph Transformer Monad

data GT m g a Source

Constructors

MGT (m g -> m (a, g)) 

Instances

Monad m => Monad (GT m g) 

apply :: GT m g a -> m g -> m (a, g)Source

apply' :: Monad m => GT m g a -> g -> m (a, g)Source

applyWith :: Monad m => (a -> b) -> GT m g a -> m g -> m (b, g)Source

applyWith' :: Monad m => (a -> b) -> GT m g a -> g -> m (b, g)Source

runGT :: Monad m => GT m g a -> m g -> m aSource

condMGT' :: Monad m => (s -> Bool) -> GT m s a -> GT m s a -> GT m s aSource

recMGT' :: Monad m => (s -> Bool) -> GT m s a -> (a -> b -> b) -> b -> GT m s bSource

condMGT :: Monad m => (m s -> m Bool) -> GT m s a -> GT m s a -> GT m s aSource

recMGT :: Monad m => (m s -> m Bool) -> GT m s a -> (a -> b -> b) -> b -> GT m s bSource

Graph Computations Based on Graph Monads

Monadic Graph Accessing Functions

getNode :: GraphM m gr => GT m (gr a b) NodeSource

getContext :: GraphM m gr => GT m (gr a b) (Context a b)Source

getNodes' :: (Graph gr, GraphM m gr) => GT m (gr a b) [Node]Source

getNodes :: GraphM m gr => GT m (gr a b) [Node]Source

sucGT :: GraphM m gr => Node -> GT m (gr a b) (Maybe [Node])Source

sucM :: GraphM m gr => Node -> m (gr a b) -> m (Maybe [Node])Source

Derived Graph Recursion Operators

graphRec :: GraphM m gr => GT m (gr a b) c -> (c -> d -> d) -> d -> GT m (gr a b) dSource

encapsulates a simple recursion schema on graphs

graphRec' :: (Graph gr, GraphM m gr) => GT m (gr a b) c -> (c -> d -> d) -> d -> GT m (gr a b) dSource

graphUFold :: GraphM m gr => (Context a b -> c -> c) -> c -> GT m (gr a b) cSource

Examples: Graph Algorithms as Instances of Recursion Operators

Instances of graphRec

graphNodesM0 :: GraphM m gr => GT m (gr a b) [Node]Source

graphNodesM :: GraphM m gr => GT m (gr a b) [Node]Source

graphNodes :: GraphM m gr => m (gr a b) -> m [Node]Source

graphFilterM :: GraphM m gr => (Context a b -> Bool) -> GT m (gr a b) [Context a b]Source

graphFilter :: GraphM m gr => (Context a b -> Bool) -> m (gr a b) -> m [Context a b]Source

Example: Monadic DFS Algorithm(s)

dfsGT :: GraphM m gr => [Node] -> GT m (gr a b) [Node]Source

Monadic graph algorithms are defined in two steps:

  1. define the (possibly parameterized) graph transformer (e.g., dfsGT) (2) run the graph transformer (applied to arguments) (e.g., dfsM)

dfsM :: GraphM m gr => [Node] -> m (gr a b) -> m [Node]Source

depth-first search yielding number of nodes

dfsM' :: GraphM m gr => m (gr a b) -> m [Node]Source

dffM :: GraphM m gr => [Node] -> GT m (gr a b) [Tree Node]Source

depth-first search yielding dfs forest

graphDff :: GraphM m gr => [Node] -> m (gr a b) -> m [Tree Node]Source

graphDff' :: GraphM m gr => m (gr a b) -> m [Tree Node]Source