Safe Haskell | None |
---|
GraphRewriting.Pattern
Description
Patterns allow monadic scrutinisation of the graph (modifications are not possible) while keeping track of matched nodes (history). A Pattern
is interpreted by runPattern
that returns a result for each position in the graph where the pattern matches. It is allowed to fail
inside the Pattern
monad, indicating that the pattern does not match, which corresponds to conditional rewriting.
- type Pattern n = PatternT n Identity
- runPatternT :: PatternT n m a -> Graph n -> m [(Match, a)]
- runPattern :: Pattern n a -> Graph n -> [(Match, a)]
- evalPattern :: Pattern n a -> Graph n -> [a]
- execPattern :: Pattern n a -> Graph n -> [Match]
- branch :: Monad m => [a] -> PatternT n m a
- branchNodes :: Monad m => [Node] -> PatternT n m Node
- probe :: Monad m => PatternT n m a -> PatternT n m Bool
- matches :: Monad m => PatternT n m a -> PatternT n m [Match]
- match :: Monad m => PatternT n m a -> PatternT n m [(Match, a)]
- anyOf :: Alternative f => [f a] -> f a
- require :: Monad m => Bool -> m ()
- requireFailure :: Monad m => PatternT n m a -> PatternT n m ()
- requireM :: Monad m => m Bool -> m ()
- liftReader :: Monad m => Reader (Graph n) a -> PatternT n m a
- node :: (Monad m, View v n) => PatternT n m v
- nodeAt :: (Monad m, View v n) => Node -> PatternT n m v
- edge :: Monad m => PatternT n m Edge
- nodeWith :: (Monad m, View v n) => Edge -> PatternT n m v
- edgeOf :: (Monad m, View [Port] n) => Node -> PatternT n m Edge
- neighbour :: Monad m => (View [Port] n, View v n) => Node -> PatternT n m v
- relative :: (Monad m, View [Port] n, View v n) => Node -> PatternT n m v
- adverse :: (Monad m, View [Port] n, View v n) => Port -> Node -> PatternT n m v
- visit :: Monad m => Node -> PatternT n m ()
- amnesia :: Monad m => PatternT n m a -> PatternT n m a
- history :: Monad m => PatternT n m Match
- previous :: Monad m => PatternT n m Node
- nextFresh :: Monad m => PatternT n m a -> PatternT n m a
- nextIs :: Monad m => Node -> PatternT n m a -> PatternT n m a
- restrictOverlap :: Monad m => (Match -> Match -> Bool) -> PatternT n m a -> PatternT n m a
- linear :: Monad m => PatternT n m a -> PatternT n m a
- data PatternT n m a
- type Pattern n = PatternT n Identity
- type Match = [Node]
- (<|>) :: Alternative f => forall a. f a -> f a -> f a
Documentation
type Pattern n = PatternT n IdentitySource
A pattern represents a graph scrutinisation that memorises all the scrutinised nodes during matching.
runPatternT :: PatternT n m a -> Graph n -> m [(Match, a)]Source
runPattern :: Pattern n a -> Graph n -> [(Match, a)]Source
Apply a pattern on a graph returning a result for each matching position in the graph together with the matched nodes.
evalPattern :: Pattern n a -> Graph n -> [a]Source
execPattern :: Pattern n a -> Graph n -> [Match]Source
branchNodes :: Monad m => [Node] -> PatternT n m NodeSource
branch
on each node, add it to the history, and return it
probe :: Monad m => PatternT n m a -> PatternT n m BoolSource
Probe whether a pattern matches somewhere on the graph. You might want to combine this with amnesia
.
matches :: Monad m => PatternT n m a -> PatternT n m [Match]Source
probe a pattern returning the matches it has on the graph. You might want to combine this with amnesia
.
match :: Monad m => PatternT n m a -> PatternT n m [(Match, a)]Source
probe a pattern returning the matches it has on the graph. You might want to combine this with amnesia
.
requireFailure :: Monad m => PatternT n m a -> PatternT n m ()Source
fail
if given pattern succeeds, succeed if it fails.
liftReader :: Monad m => Reader (Graph n) a -> PatternT n m aSource
edgeOf :: (Monad m, View [Port] n) => Node -> PatternT n m EdgeSource
edge that is attached to given node
neighbour :: Monad m => (View [Port] n, View v n) => Node -> PatternT n m vSource
node that is connected to the given node, but not that node itself
relative :: (Monad m, View [Port] n, View v n) => Node -> PatternT n m vSource
node that is connected to the given node, permitting the node itself
amnesia :: Monad m => PatternT n m a -> PatternT n m aSource
Do not remember any of the nodes matched by the supplied pattern
history :: Monad m => PatternT n m MatchSource
list of nodes matched until now with the most recent node in head position
nextFresh :: Monad m => PatternT n m a -> PatternT n m aSource
only match nodes in the next pattern that have not been matched before
nextIs :: Monad m => Node -> PatternT n m a -> PatternT n m aSource
only accept the given node in the next match
restrictOverlap :: Monad m => (Match -> Match -> Bool) -> PatternT n m a -> PatternT n m aSource
Restrict a pattern based on the which of nodes have matched been previously and which nodes will be matched in the future. The first parameter of the supplied function is the history with the most recently matched node in head position. The second parameter is the future with the next matched node in head position.
linear :: Monad m => PatternT n m a -> PatternT n m aSource
Nodes in the future may not be matched more than once.
A pattern represents a graph scrutinisation that memorises all the scrutinised nodes during matching.
type Pattern n = PatternT n IdentitySource
A pattern represents a graph scrutinisation that memorises all the scrutinised nodes during matching.
Nodes matched in the evaluation of a pattern with the lastly matched node at the head
(<|>) :: Alternative f => forall a. f a -> f a -> f a