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

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.

Synopsis

Documentation

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 :: [a] -> Pattern n aSource

Something like an implicit monadic map

branchNodes :: [Node] -> Pattern n NodeSource

branch on each node, visit it, and return it

probe :: Pattern n a -> Pattern n BoolSource

Probe whether a pattern matches somewhere on the graph. You might want to combine this with amnesia.

matches :: Pattern n a -> Pattern n [Match]Source

probe a pattern returning the matches it has on the graph. You might want to combine this with amnesia.

(<|>) :: Pattern n a -> Pattern n a -> Pattern n aSource

choice

anyOf :: [Pattern n a] -> Pattern n aSource

choice over a list of patterns

require :: Monad m => Bool -> m ()Source

conditional rewriting: fail when predicate is not met

requireFailure :: Pattern n a -> Pattern n ()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 :: Reader (Graph n) a -> Pattern n aSource

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

node :: View v n => Pattern n vSource

any node anywhere in the graph

previous :: Pattern n NodeSource

a reference to the lastly matched node

edge :: Pattern n EdgeSource

any edge anywhere in the graph

nodeAt :: View v n => Edge -> Pattern n vSource

node that is connected to given edge

edgeOf :: View [Port] n => Node -> Pattern n EdgeSource

edge that is attached to given node

neighbour :: (View [Port] n, View v n) => Node -> Pattern n vSource

node that is connected to the given node, but not that node itself

relative :: (View [Port] n, View v n) => Node -> Pattern n vSource

node that is connected to the given node, permitting the node itself

adverse :: (View [Port] n, View v n) => Port -> Node -> Pattern n vSource

nodes connected to given port of the specified node, not including the node itself

amnesia :: Pattern n a -> Pattern n aSource

Do not remember any of the nodes matched by the supplied pattern

history :: Pattern n MatchSource

list of nodes matched until now with the most recent node in head position

nextFresh :: Pattern n a -> Pattern n aSource

only match nodes in the next pattern that have not been matched before

nextIs :: Node -> Pattern n a -> Pattern n aSource

only accept the given node in the next match

restrictOverlap :: (Match -> Match -> Bool) -> Pattern n a -> Pattern n aSource

First match is the history with the most recently matched node in head position. Second match is the future with the next matched node in head position.

linear :: Pattern n a -> Pattern n aSource

Nodes in the future may not be matched more than once.

data Pattern n a Source

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

Instances

type Match = [Node]Source

Nodes matched in the evaluation of a pattern with the lastly matched node at the head