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

Safe HaskellNone
LanguageHaskell2010

Data.Regex.MultiRules

Contents

Description

Attribute grammars with regular expression matching.

Synopsis

Children maps

data Child c attrib where Source

A child records both an actual values and the index it corresponds to.

Constructors

Child :: c ix -> [attrib ix] -> Child c attrib 

type Children c attrib = [Child c attrib] Source

Children are just a list of Childs.

lookupChild :: EqM c => c ix -> Children c attrib -> [attrib ix] Source

Basic blocks

type Action c f inh syn ix = Fix f ix -> inh ix -> Children c syn -> (Bool, Children c inh, syn ix) Source

Actions create new inherited attributes for their children, and synthesized attribute for its own node, from the synthesized attributes of children and the inheritance from its parent. Additionally, actions may include an explicit backtrack.

data Rule c f inh syn where Source

A rule comprises the regular expression to match and the action to execute if successful.

Constructors

Rule :: Regex c f ix -> Action c f inh syn ix -> Rule c f inh syn 

type Grammar c f inh syn = [Rule c f inh syn] Source

A grammar is simply a list of rules.

eval :: forall c f inh syn ix. Capturable c f => Grammar c f inh syn -> inh ix -> Fix f ix -> syn ix Source

Evaluate an attribute grammar over a certain term.

Nice syntax for defining rules

rule :: RuleBuilder f inh syn ixs fn => (fn -> IxList (Wrap Integer) ixs -> Rule (Wrap Integer) f inh syn) -> Rule (Wrap Integer) f inh syn Source

Converts a rule description into an actual Rule. Its use must follow this pattern:

  • A block of lambda-bound variables will introduce the capture names,
  • A tree regular expression to match should capture using the previous names,
  • After ->>> or ->>, the state calculation should proceed.
rule $ \c1 c2 ->
  regex ... c1 <<- ... c2 <<- ... ->> do
    at c2 . inh .= ...          -- Set inherited for children
    c1Syn <- use (at c1 . syn)  -- Get synthesized from children
    this . syn  .= ...          -- Set upwards synthesized attributes

rule0 :: (IxList (Wrap Integer) [] -> Rule (Wrap Integer) f inh syn) -> Rule (Wrap Integer) f inh syn Source

Special case for rules without capture.

Combinators

check :: Bool -> State (ActionState (Wrap Integer) inh syn ix) () Source

Makes the attribute calculation fail if the condition is false. This function can be used to add extra conditions over whether a certain rule should be applied (a bit like guards).

(->>>) :: forall f ix inh syn ixs. (IxListMonoid inh ixs, Monoid (syn ix), IxListMonoid syn ixs) => (forall c. Regex' c (Wrap Integer) f ix) -> (Fix f ix -> State (ActionState (Wrap Integer) inh syn ix) ()) -> IxList (Wrap Integer) ixs -> Rule (Wrap Integer) f inh syn Source

Separates matching and attribute calculation on a rule. The action should take as extra parameter the node which was matched.

(->>) :: forall f ix inh syn ixs. (IxListMonoid inh ixs, Monoid (syn ix), IxListMonoid syn ixs) => (forall c. Regex' c (Wrap Integer) f ix) -> State (ActionState (Wrap Integer) inh syn ix) () -> IxList (Wrap Integer) ixs -> Rule (Wrap Integer) f inh syn Source

Separates matching and attribute calculation on a rule.

Special lenses

this :: Functor f => (InhAndSyn inh syn ix -> f (InhAndSyn inh syn ix)) -> ActionState c inh syn ix -> f (ActionState c inh syn ix) Source

Lens for the attributes of the current node. To be used in composition with inh or syn.

at :: (EqM c, Functor f) => c xi -> (InhAndSyn inh syn xi -> f (InhAndSyn inh syn xi)) -> ActionState c inh syn ix -> f (ActionState c inh syn ix) Source

Lens the attributes of a child node. To be used in composition with inh or syn.

inh :: Functor f => (inh ix -> f (inh ix)) -> InhAndSyn inh syn ix -> f (InhAndSyn inh syn ix) Source

Lens for the inherited attributes of a node. Use only as getter with this and as setter with at.

syn :: Functor f => (syn ix -> f (syn ix)) -> InhAndSyn inh syn ix -> f (InhAndSyn inh syn ix) Source

Lens the inherited synthesized attributes of a node. Use only as setter with this and as getter with at.

Index-independent attributes

newtype IndexIndependent t ix Source

Utility type which does not distinguish between indices.

Constructors

IndexIndependent t 

Instances

Eq t => Eq (IndexIndependent k t ix) 
Ord t => Ord (IndexIndependent k t ix) 
Show t => Show (IndexIndependent k t ix) 
Monoid t => Monoid (IndexIndependent k t ix) 

type IndexIndependentGrammar c f inh syn = Grammar c f (IndexIndependent inh) (IndexIndependent syn) Source

A grammar whose attributes are equal throughout all indices.

iieval :: forall c f inh syn ix. Capturable c f => IndexIndependentGrammar c f inh syn -> inh -> Fix f ix -> syn Source

Evaluate an index-indendepent grammar.

inh_ :: Functor f => (inh -> f inh) -> InhAndSyn (IndexIndependent inh) syn ix -> f (InhAndSyn (IndexIndependent inh) syn ix) Source

Lens for Indexed inherited attributes of a node. Use only as getter with this and as setter with at.

syn_ :: Functor f => (syn -> f syn) -> InhAndSyn inh (IndexIndependent syn) ix -> f (InhAndSyn inh (IndexIndependent syn) ix) Source

Lens the Indexed synthesized attributes of a node. Use only as setter with this and as getter with at.

copy :: EqM c => [c xi] -> State (ActionState c (IndexIndependent inh) syn ix) () Source

Apply copy rule for inherited attributes.