Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Enquiry of the graph structure. Note: In this module the term "node" is often used synonymously to "node reference" and "node value". The two can easily distinguished by their type: the former has type Node
the latter usually n
.
Synopsis
- module Data.View
- module GraphRewriting.Graph.Types
- type WithGraph n = Reader (Graph n)
- readOnly :: MonadReader (Graph n) m => Reader (Graph n) a -> m a
- existNode :: MonadReader (Graph n) m => Node -> m Bool
- readNode :: (MonadReader (Graph n) m, MonadFail m) => Node -> m n
- inspectNode :: (View v n, MonadReader (Graph n) m, MonadFail m) => Node -> m v
- examineNode :: (View v n, MonadReader (Graph n) m, MonadFail m) => (v -> a) -> Node -> m a
- readNodeList :: MonadReader (Graph n) m => m [Node]
- readEdgeList :: MonadReader (Graph n) m => m [Edge]
- attachedEdges :: (View [Port] n, MonadReader (Graph n) m, MonadFail m) => Node -> m [Edge]
- attachedNodes :: (MonadReader (Graph n) m, MonadFail m) => Edge -> m [Node]
- edgeCardinality :: (View [Port] n, MonadReader (Graph n) m, MonadFail m) => Edge -> m Int
- neighbours :: (View [Port] n, MonadReader (Graph n) m, MonadFail m) => Node -> m [Node]
- relatives :: (View [Port] n, MonadReader (Graph n) m, MonadFail m) => Node -> m [Node]
- adverseNodes :: (MonadReader (Graph n) m, MonadFail m) => Node -> Port -> m [Node]
- connected :: (View [Port] n, MonadReader (Graph n) m, MonadFail m) => Node -> Node -> m Bool
- dangling :: (View [Port] n, MonadReader (Graph n) m, MonadFail m) => Port -> m Bool
- withNodes :: MonadReader (Graph n) m => (Node -> m a) -> m [a]
Documentation
module Data.View
module GraphRewriting.Graph.Types
readOnly :: MonadReader (Graph n) m => Reader (Graph n) a -> m a Source #
This forces the use of the Reader
monad. Wrapping a sequence of monadic read-only operations (such as those defined below) into a read-only block can save much overhead e.g. in the state monad.
inspectNode :: (View v n, MonadReader (Graph n) m, MonadFail m) => Node -> m v Source #
a wrapper to inspect
the given node
examineNode :: (View v n, MonadReader (Graph n) m, MonadFail m) => (v -> a) -> Node -> m a Source #
a wrapper to examine
the given node
readNodeList :: MonadReader (Graph n) m => m [Node] Source #
all of the graph's nodes
readEdgeList :: MonadReader (Graph n) m => m [Edge] Source #
all of the graph's edges
attachedEdges :: (View [Port] n, MonadReader (Graph n) m, MonadFail m) => Node -> m [Edge] Source #
edges attached to the given node
attachedNodes :: (MonadReader (Graph n) m, MonadFail m) => Edge -> m [Node] Source #
non-empty set of nodes attached to the given edge
edgeCardinality :: (View [Port] n, MonadReader (Graph n) m, MonadFail m) => Edge -> m Int Source #
amount of ports the given hyperedge is connected to
neighbours :: (View [Port] n, MonadReader (Graph n) m, MonadFail m) => Node -> m [Node] Source #
list of nodes that are connected to the given node, not including the node itself
relatives :: (View [Port] n, MonadReader (Graph n) m, MonadFail m) => Node -> m [Node] Source #
list of nodes that are connected to the given node, including the node itself
adverseNodes :: (MonadReader (Graph n) m, MonadFail m) => Node -> Port -> m [Node] Source #
nodes connected to given port of the specified node, not including the node itself
connected :: (View [Port] n, MonadReader (Graph n) m, MonadFail m) => Node -> Node -> m Bool Source #
whether two nodes are connected