Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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.
Synopsis
- 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 :: MonadFail 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 :: MonadFail m => Bool -> m ()
- requireFailure :: MonadFail m => PatternT n m a -> PatternT n m ()
- requireM :: MonadFail m => m Bool -> m ()
- liftReader :: Monad m => Reader (Graph n) a -> PatternT n m a
- node :: (MonadFail 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 :: (MonadFail m, View v n) => Edge -> PatternT n m v
- edgeOf :: (Monad m, View [Port] n) => Node -> PatternT n m Edge
- neighbour :: MonadFail m => (View [Port] n, View v n) => Node -> PatternT n m v
- relative :: (MonadFail m, View [Port] n, View v n) => Node -> PatternT n m v
- adverse :: (MonadFail m, View [Port] n, View v n) => Port -> Node -> PatternT n m v
- visit :: MonadFail 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 => f a -> f a -> f a
Documentation
type Pattern n = PatternT n Identity Source #
A pattern represents a graph scrutinisation that memorises all the scrutinised nodes during matching.
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 #
branchNodes :: MonadFail m => [Node] -> PatternT n m Node Source #
branch
on each node, add it to the history, and return it
probe :: Monad m => PatternT n m a -> PatternT n m Bool Source #
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
.
anyOf :: Alternative f => [f a] -> f a Source #
choice over a list of patterns
require :: MonadFail m => Bool -> m () Source #
conditional rewriting: fail
when predicate is not met
requireFailure :: MonadFail m => PatternT n m a -> PatternT n m () Source #
fail
if given pattern succeeds, succeed if it fails.
nodeWith :: (MonadFail m, View v n) => Edge -> PatternT n m v Source #
node that is connected to given edge
edgeOf :: (Monad m, View [Port] n) => Node -> PatternT n m Edge Source #
edge that is attached to given node
neighbour :: MonadFail m => (View [Port] n, View v n) => Node -> PatternT n m v Source #
node that is connected to the given node, but not that node itself
relative :: (MonadFail m, View [Port] n, View v n) => Node -> PatternT n m v Source #
node that is connected to the given node, permitting the node itself
amnesia :: Monad m => PatternT n m a -> PatternT n m a Source #
Do not remember any of the nodes matched by the supplied pattern
history :: Monad m => PatternT n m Match Source #
list of nodes matched until now with the most recent node in head position
nextFresh :: Monad m => PatternT n m a -> PatternT n m a Source #
only match nodes in the next pattern that have not been matched before
nextIs :: Monad m => Node -> PatternT n m a -> PatternT n m a Source #
only accept the given node in the next match
restrictOverlap :: Monad m => (Match -> Match -> Bool) -> PatternT n m a -> PatternT n m a Source #
Restrict a pattern based on the which of nodes have been matched 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 a Source #
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.
Instances
MonadTrans (PatternT n) Source # | |
Defined in GraphRewriting.Pattern | |
MonadFail m => MonadFail (PatternT n m) Source # | |
Defined in GraphRewriting.Pattern | |
MonadFail m => Alternative (PatternT n m) Source # | |
Monad m => Applicative (PatternT n m) Source # | |
Defined in GraphRewriting.Pattern | |
Monad m => Functor (PatternT n m) Source # | |
Monad m => Monad (PatternT n m) Source # | |
MonadFail m => MonadPlus (PatternT n m) Source # | |
MonadFail m => Monoid (PatternT n m a) Source # | |
MonadFail m => Semigroup (PatternT n m a) Source # | |
type Pattern n = PatternT n Identity Source #
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 => f a -> f a -> f a infixl 3 #
An associative binary operation
Orphan instances
MonadFail Identity Source # | |
MonadTrans (PatternT n) Source # | |
MonadFail m => MonadFail (PatternT n m) Source # | |
MonadFail m => Alternative (PatternT n m) Source # | |
Monad m => Applicative (PatternT n m) Source # | |
Monad m => Functor (PatternT n m) Source # | |
Monad m => Monad (PatternT n m) Source # | |
MonadFail m => MonadPlus (PatternT n m) Source # | |
MonadFail m => Monoid (PatternT n m a) Source # | |
MonadFail m => Semigroup (PatternT n m a) Source # | |