graph-rewriting-0.7.10: Monadic graph rewriting of hypergraphs with ports and multiedges

Safe HaskellNone
LanguageHaskell98

GraphRewriting.Pattern

Contents

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.

Synopsis

Documentation

type Pattern n = PatternT n Identity Source #

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 #

branch :: Monad m => [a] -> PatternT n m a Source #

Something like an implicit monadic map

branchNodes :: Monad 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 :: Monad m => Bool -> m () Source #

conditional rewriting: fail when predicate is not met

requireFailure :: Monad m => PatternT n m a -> PatternT n m () Source #

fail if given pattern succeeds, succeed if it fails.

requireM :: Monad m => m Bool -> m () Source #

fail when monadic predicate is not met

liftReader :: Monad m => Reader (Graph n) a -> PatternT n m a Source #

Lift a scrutinisation from Reader to Pattern leaving the history unchanged.

node :: (Monad m, View v n) => PatternT n m v Source #

any node anywhere in the graph

nodeAt :: (Monad m, View v n) => Node -> PatternT n m v Source #

A specific node

edge :: Monad m => PatternT n m Edge Source #

any edge anywhere in the graph

nodeWith :: (Monad 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 :: Monad 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 :: (Monad 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

adverse :: (Monad m, View [Port] n, View v n) => Port -> Node -> PatternT n m v Source #

nodes connected to given port of the specified node, not including the node itself. Consider as an alternative linear combined with nodeWith.

visit :: Monad m => Node -> PatternT n m () Source #

A specific node

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

previous :: Monad m => PatternT n m Node Source #

a reference to the lastly matched node

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.

data PatternT n m a Source #

A pattern represents a graph scrutinisation that memorises all the scrutinised nodes during matching.

type Pattern n = PatternT n Identity Source #

A pattern represents a graph scrutinisation that memorises all the scrutinised nodes during matching.

type Match = [Node] Source #

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 #

An associative binary operation

Orphan instances

MonadTrans (PatternT n) Source # 

Methods

lift :: Monad m => m a -> PatternT n m a #

Monad m => Monad (PatternT n m) Source # 

Methods

(>>=) :: PatternT n m a -> (a -> PatternT n m b) -> PatternT n m b #

(>>) :: PatternT n m a -> PatternT n m b -> PatternT n m b #

return :: a -> PatternT n m a #

fail :: String -> PatternT n m a #

Monad m => Functor (PatternT n m) Source # 

Methods

fmap :: (a -> b) -> PatternT n m a -> PatternT n m b #

(<$) :: a -> PatternT n m b -> PatternT n m a #

Monad m => Applicative (PatternT n m) Source # 

Methods

pure :: a -> PatternT n m a #

(<*>) :: PatternT n m (a -> b) -> PatternT n m a -> PatternT n m b #

(*>) :: PatternT n m a -> PatternT n m b -> PatternT n m b #

(<*) :: PatternT n m a -> PatternT n m b -> PatternT n m a #

Monad m => Alternative (PatternT n m) Source # 

Methods

empty :: PatternT n m a #

(<|>) :: PatternT n m a -> PatternT n m a -> PatternT n m a #

some :: PatternT n m a -> PatternT n m [a] #

many :: PatternT n m a -> PatternT n m [a] #

Monad m => MonadPlus (PatternT n m) Source # 

Methods

mzero :: PatternT n m a #

mplus :: PatternT n m a -> PatternT n m a -> PatternT n m a #

Monad m => Monoid (PatternT n m a) Source # 

Methods

mempty :: PatternT n m a #

mappend :: PatternT n m a -> PatternT n m a -> PatternT n m a #

mconcat :: [PatternT n m a] -> PatternT n m a #