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

Safe HaskellNone
LanguageHaskell2010

Data.Regex.Generics

Contents

Description

Tree regular expressions over regular data types.

Synopsis

Base types

newtype Regex c f Source

Tree regular expressions over pattern functor f with capture identifiers of type c.

Constructors

Regex (forall k. Regex' k c f) 

data Regex' k c f 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 pattern functor over which regular expressions match. In tree regular expression jargon, expresses the set of constructors for nodes.

Constructors

Inject (f (Regex' k c f))

Useful for defining pattern synonyms for injected constructors.

newtype Fix f :: (* -> *) -> *

Constructors

Fix (f (Fix f)) 

Instances

Show Rose 
Show Tree 
Arbitrary Tree 
Eq (f (Fix f)) => Eq (Fix f) 
Ord (f (Fix f)) => Ord (Fix f) 
Read (f (Fix f)) => Read (Fix f) 
Show (f (Fix f)) => Show (Fix f) 
Arbitrary a => Arbitrary (List a) 
Functor f => Foldable (Fix f) 
Functor f => Unfoldable (Fix f) 
Typeable ((* -> *) -> *) Fix 
type Base (Fix f) = f 

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 Source

Matches no value.

none :: Regex' k c f Source

Matches no value.

Whole language

any_ :: Regex' k c f Source

Matches any value of the data type.

Injection

inj :: f (Regex' k c f) -> Regex' k c f 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 -> Regex' k c f Source

Indicates the position of a hole in a regular expression.

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

Indicates the position of a hole in a regular expression.

(#) :: k -> Regex' k c f 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 -> Regex' k c f -> Regex' k c f 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 -> Regex' k c f -> Regex' k c f 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 -> Regex' k c f) -> Regex' k c f -> Regex' k c f Source

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

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

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

Iteration

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

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

(^*) :: (k -> Regex' k c f) -> Regex' k c f 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 -> Regex' k c f -> Regex' k c f Source

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

(<<-) :: c -> Regex' k c f -> Regex' k c f 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 = (Generic1 f, MatchG (Rep1 f)) Source

Types which can be matched.

matches :: forall c f. (Ord c, Matchable f) => Regex c f -> Fix f -> Bool Source

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

match :: (Ord c, Matchable f, Alternative m) => Regex c f -> Fix f -> Maybe (Map c (m (Fix f))) 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.

Views

with :: With f fn r => fn -> Fix f -> 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.

Random generation

arbitraryFromRegex :: (Generic1 f, ArbitraryRegexG (Rep1 f), Arbitrary (Fix f)) => Regex c f -> Gen (Fix f) Source

Return a random value which matches the given regular expression.

arbitraryFromRegexAndGen :: (Generic1 f, ArbitraryRegexG (Rep1 f)) => Gen (Fix f) -> Regex c f -> Gen (Fix f) Source

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