t-regex-0.1.0.0: Matchers and grammars using tree regular expressions

Safe HaskellNone
LanguageHaskell2010

Data.Regex.MultiGenerics

Contents

Description

Tree regular expressions over mutually recursive regular data types.

Synopsis

Base types

newtype Regex c f ix Source

Tree regular expressions over mutually recursive data types given by the pattern functor f, where the top node is at index ix, and with capture identifiers of type c.

Constructors

Regex (forall s. Regex' s c f ix) 

data Regex' s c f ix Source

The basic data type for tree regular expressions.

  • k is used as phantom type to point to concatenation and iteration positions.
  • c is the type of capture identifiers.
  • f is the family of pattern functors over which regular expressions match. In tree regular expression jargon, expresses the set of constructors for nodes.
  • ix is the index of the data type over which the regular expression matches.

newtype Fix f ix Source

Multirec-style fix-point, indexed by data kind.

Constructors

Fix 

Fields

unFix :: f (Fix f) ix
 

Constructors

For a description and study of tree regular expressions, you are invited to read Chapter 2 of Tree Automata Techniques and Applications.

Emptiness

empty_ :: Regex' k c f ix Source

Matches no value.

none :: Regex' k c f ix Source

Matches no value.

Whole language

any_ :: Regex' k c f ix Source

Matches any value of the data type.

Injection

inj :: f (Regex' k c f) ix -> Regex' k c f ix Source

Injects a constructor as a regular expression. That is, specifies a tree regular expression whose root is given by a constructor of the corresponding pattern functor, and whose nodes are other tree regular expressions. When matching, fields of types other than f are checked for equality, except when using __ as the value.

__ :: a Source

Serves as a placeholder for any value in a non-f-typed position.

Holes/squares

square :: k ix -> Regex' k c f ix Source

Indicates the position of a hole in a regular expression.

var :: k ix -> Regex' k c f ix Source

Indicates the position of a hole in a regular expression.

(!) :: k ix -> Regex' k c f ix Source

Indicates the position of a hole in a regular expression. This function is meant to be used with the PostfixOperators pragma.

Alternation

choice :: Regex' k c f ix -> Regex' k c f ix -> Regex' k c f ix Source

Expresses alternation between two tree regular expressions: Data types may match one or the other. When capturing, the first one is given priority.

(<||>) :: Regex' k c f ix -> Regex' k c f ix -> Regex' k c f ix infixl 3 Source

Expresses alternation between two tree regular expressions: Data types may match one or the other. When capturing, the first one is given priority.

Concatenation

concat_ :: (k xi -> Regex' k c f ix) -> Regex' k c f xi -> Regex' k c f ix Source

Concatenation: a whole in the first tree regular expression is replaced by the second one.

(<.>) :: (k xi -> Regex' k c f ix) -> Regex' k c f xi -> Regex' k c f ix Source

Concatenation: a whole in the first tree regular expression is replaced by the second one.

Iteration

iter :: (k ix -> Regex' k c f ix) -> Regex' k c f ix Source

Repeated replacement of a hole in a tree regular expression. Iteration fulfills the law: iter r = r <.> iter r.

(^*) :: (k ix -> Regex' k c f ix) -> Regex' k c f ix Source

Repeated replacement of a hole in a tree regular expression. This function is meant to be used with the PostfixOperators pragma.

Capture

capture :: c ix -> Regex' k c f ix -> Regex' k c f ix Source

Indicates a part of a value that, when matched, should be given a name of type c and saved for querying.

(<<-) :: c ix -> Regex' k c f ix -> Regex' k c f ix infixl 4 Source

Indicates a part of a value that, when matched, should be given a name of type c and saved for querying.

Matching

type Matchable f = (Generic1m f, MatchG (Rep1m f)) Source

Types which can be matched.

matches :: Matchable f => Regex c f ix -> Fix f ix -> Bool Source

Checks whether a term t matches the tree regular expression r.

type Capturable c f = (Generic1m f, MatchG (Rep1m f), EqM c) Source

Types which can be matched and captured.

match :: (Capturable c f, Alternative m) => Regex c f ix -> Fix f ix -> Maybe [CaptureGroup c f m] Source

Checks whether a term t matches the tree regular expression r. When successful, it returns in addition a map of captured subterms.

The behaviour of several matches over the same capture identifier is governed by the Alternative functor m. For example, if m = [], all matches are returned in prefix-order. If m = Maybe, only the first result is returned.

Querying capture groups

data CaptureGroup c f m where Source

Constructors

CaptureGroup :: c ix -> m (Fix f ix) -> CaptureGroup c f m 

Instances

(ShowM k c, Foldable m, ShowM k (Fix k f)) => Show (CaptureGroup k c f m) 

lookupGroup :: EqM c => c ix -> [CaptureGroup c f m] -> Maybe (m (Fix f ix)) Source

Views

with :: With f ix fn r => fn -> Fix f ix -> Maybe r Source

Useful function to be used as view pattern. The first argument should be a function, which indicates those places where captured are found Those captured are automatically put in a tuple, giving a simpler and type-safer access to captured subterms that looking inside a map.

As an example, here is how one would use it for capturing two subterms:

f (with (\x y -> iter $ \k -> x <<- inj One <||> y <<- inj (Two (var k))) -> Just (x, y)) = ... x and y available here ...

For more concise syntax which uses quasi-quotation, check Data.Regex.TH.

newtype Wrap c ix Source

Data type used to tag capture identifiers with their expected type.

Constructors

Wrap c 

Instances

Eq c => EqM k (Wrap k c) 
Show c => ShowM k (Wrap k c) 
Eq c => Eq (Wrap k c ix) 
Ord c => Ord (Wrap k c ix) 

(?) :: c -> Wrap c ix Source

Wraps an already existing type to recall extra index information.

Random generation

arbitraryFromRegex :: (Generic1m f, ArbitraryRegexG (Rep1m f), ArbitraryM (Fix f), SingI ix) => Regex c f ix -> Gen (Fix f ix) Source

Return a random value which matches the given regular expression.

arbitraryFromRegexAndGen :: (Generic1m f, ArbitraryRegexG (Rep1m f), SingI ix) => GenM (Fix f) -> Regex c f ix -> Gen (Fix f ix) Source

Return a random value which matches the given regular expression, and which uses a supplied generator for any_.