Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Monadic Graph Algorithms
Synopsis
- mapFst :: (a -> b) -> (a, c) -> (b, c)
- mapSnd :: (a -> b) -> (c, a) -> (c, b)
- (><) :: (a -> b) -> (c -> d) -> (a, c) -> (b, d)
- orP :: (a -> Bool) -> (b -> Bool) -> (a, b) -> Bool
- newtype GT m g a = MGT (m g -> m (a, g))
- apply :: GT m g a -> m g -> m (a, g)
- apply' :: Monad m => GT m g a -> g -> m (a, g)
- applyWith :: Monad m => (a -> b) -> GT m g a -> m g -> m (b, g)
- applyWith' :: Monad m => (a -> b) -> GT m g a -> g -> m (b, g)
- runGT :: Monad m => GT m g a -> m g -> m a
- condMGT' :: Monad m => (s -> Bool) -> GT m s a -> GT m s a -> GT m s a
- recMGT' :: Monad m => (s -> Bool) -> GT m s a -> (a -> b -> b) -> b -> GT m s b
- condMGT :: Monad m => (m s -> m Bool) -> GT m s a -> GT m s a -> GT m s a
- recMGT :: Monad m => (m s -> m Bool) -> GT m s a -> (a -> b -> b) -> b -> GT m s b
- getNode :: GraphM m gr => GT m (gr a b) Node
- getContext :: GraphM m gr => GT m (gr a b) (Context a b)
- getNodes' :: (Graph gr, GraphM m gr) => GT m (gr a b) [Node]
- getNodes :: GraphM m gr => GT m (gr a b) [Node]
- sucGT :: GraphM m gr => Node -> GT m (gr a b) (Maybe [Node])
- sucM :: GraphM m gr => Node -> m (gr a b) -> m (Maybe [Node])
- graphRec :: GraphM m gr => GT m (gr a b) c -> (c -> d -> d) -> d -> GT m (gr a b) d
- graphRec' :: (Graph gr, GraphM m gr) => GT m (gr a b) c -> (c -> d -> d) -> d -> GT m (gr a b) d
- graphUFold :: GraphM m gr => (Context a b -> c -> c) -> c -> GT m (gr a b) c
- graphNodesM0 :: GraphM m gr => GT m (gr a b) [Node]
- graphNodesM :: GraphM m gr => GT m (gr a b) [Node]
- graphNodes :: GraphM m gr => m (gr a b) -> m [Node]
- graphFilterM :: GraphM m gr => (Context a b -> Bool) -> GT m (gr a b) [Context a b]
- graphFilter :: GraphM m gr => (Context a b -> Bool) -> m (gr a b) -> m [Context a b]
- dfsGT :: GraphM m gr => [Node] -> GT m (gr a b) [Node]
- dfsM :: GraphM m gr => [Node] -> m (gr a b) -> m [Node]
- dfsM' :: GraphM m gr => m (gr a b) -> m [Node]
- dffM :: GraphM m gr => [Node] -> GT m (gr a b) [Tree Node]
- graphDff :: GraphM m gr => [Node] -> m (gr a b) -> m [Tree Node]
- graphDff' :: GraphM m gr => m (gr a b) -> m [Tree Node]
Additional Graph Utilities
Graph Transformer Monad
MGT (m g -> m (a, g)) |
applyWith' :: Monad m => (a -> b) -> GT m g a -> g -> m (b, g) Source #
Graph Computations Based on Graph Monads
Monadic Graph Accessing Functions
Derived Graph Recursion Operators
graphRec :: GraphM m gr => GT m (gr a b) c -> (c -> d -> d) -> d -> GT m (gr a b) d Source #
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) d Source #
Examples: Graph Algorithms as Instances of Recursion Operators
Instances of graphRec
graphNodes :: GraphM m gr => m (gr a b) -> m [Node] 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:
- define the (possibly parameterized) graph transformer (e.g., dfsGT)
- 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