grammar-combinators-0.2.7: A parsing library of context-free grammar combinators.

Safe HaskellNone

Text.GrammarCombinators.Base.ProductionRule

Synopsis

Documentation

class ProductionRule p whereSource

Base type class for production rule interpretations. A production rule interpretation that is an instance of the ProductionRule type class supports sequencing and disjunction of rules, empty rules, dead rules and end-of-input rules.

Methods

(>>>) :: p (a -> b) -> p a -> p bSource

Sequence two rules. Result of the sequenced rule is the application of the result of the first rule to the result of the second.

(|||) :: p va -> p va -> p vaSource

Disjunction of two rules.

endOfInput :: p ()Source

End of input rule. Matches only at end of input, consumes nothing, produces '()' as result.

die :: p aSource

Dead rule. Never matches.

Instances

ProductionRule (RecDecRule t) 
Token t => ProductionRule (WrapGenParser t) 
ProductionRule (PackratRule phi r t) 
(Domain phi, Token t) => ProductionRule (BranchSelectorComputer phi r t) 
Token t => ProductionRule (WrapP t loc ct) 
ProductionRule (AssessSizeProductionRule phi r t) 
ProductionRule (EnumTokensRule phi r t) 
ProductionRule (IsEpsilonRule phi r t) 
ProductionRule (LiftedRule phi r t) 
ProductionRule (PrintProductionRule phi r t) 
ProductionRule (GraphConstructor phi r t) 
ProductionRule (LLRule phi ixT r t) 
(Domain phi, Token t) => ProductionRule (FSCalculator phi ixT r t) 
ProductionRule (RealLL1Rule phi ixT r t) 
(ProductionRule p, EpsProductionRule p) => ProductionRule (CombineEpsilonsRule p phi r t) 
ProductionRule p => ProductionRule (FilterDiesRule p phi r t) 
Token t => ProductionRule (FSCalculator phi r t rr) 
ProductionRule (IsChainNT phi r t rr) 
(ProductionRule p, EpsProductionRule p) => ProductionRule (RuleToManyWrapper p phi r t) 
ProductionRule (EnumerateProductionRule phi ixT r t) 
ProductionRule (IsDeadRule phi r t rr) 
ProductionRule p => ProductionRule (UnfoldDeadRule p phi r t) 
ProductionRule p => ProductionRule (UnfoldLoopsWrapper p phi ixT r t) 
ProductionRule p => ProductionRule (RPWRule p phi ixT r t) 
(Token t, ProductionRule p, BiasedProductionRule p) => ProductionRule (IBW p phi r t rr) 
ProductionRule p => ProductionRule (PBEHProductionRule p phi (MaybeSemanticT r) r t) 
ProductionRule p => ProductionRule (UnfoldDepthFirstRule p phi r t rr) 
ProductionRule (FoldReachableIntRule phi r t rr n) 
ProductionRule p => ProductionRule (FLWrap p (FoldLoopsDomain phi) (FoldLoopsValue r) phi r t) 
ProductionRule p => ProductionRule (IGW p phiL phiR rL rR t) 
ProductionRule p => ProductionRule (CGW p phiL phiR rL rR t) 
(ProductionRule p, EpsProductionRule p, RecProductionRule p (LCDomain phi t) (LCValue r t)) => ProductionRule (TransformLCRule p (LCDomain phi t) (LCValue r t) phi r t) 
(ProductionRule p, LiftableProductionRule p) => ProductionRule (TransformUPWrapper p surrIx (UPDomain phi) (UPValue r) phi ixT r t) 

class ProductionRule p => LiftableProductionRule p whereSource

Methods

epsilonL :: a -> Q Exp -> p aSource

Epsilon rule with lifted value. Always matches, consumes nothing, produces the given value (with its lifted version) as result.

optionally :: p v -> p (Maybe v)Source

Optionally match a given rule.

Instances

ProductionRule (RecDecRule t) => LiftableProductionRule (RecDecRule t) 
(ProductionRule (WrapGenParser t), Token t) => LiftableProductionRule (WrapGenParser t) 
ProductionRule (PackratRule phi r t) => LiftableProductionRule (PackratRule phi r t) 
(ProductionRule (BranchSelectorComputer phi r t), Domain phi, Token t) => LiftableProductionRule (BranchSelectorComputer phi r t) 
(ProductionRule (WrapP t loc ct), Token t) => LiftableProductionRule (WrapP t loc ct) 
ProductionRule (AssessSizeProductionRule phi r t) => LiftableProductionRule (AssessSizeProductionRule phi r t) 
ProductionRule (EnumTokensRule phi r t) => LiftableProductionRule (EnumTokensRule phi r t) 
ProductionRule (IsEpsilonRule phi r t) => LiftableProductionRule (IsEpsilonRule phi r t) 
ProductionRule (LiftedRule phi r t) => LiftableProductionRule (LiftedRule phi r t) 
ProductionRule (PrintProductionRule phi r t) => LiftableProductionRule (PrintProductionRule phi r t) 
ProductionRule (GraphConstructor phi r t) => LiftableProductionRule (GraphConstructor phi r t) 
ProductionRule (LLRule phi ixT r t) => LiftableProductionRule (LLRule phi ixT r t) 
(ProductionRule (FSCalculator phi ixT r t), Domain phi, Token t) => LiftableProductionRule (FSCalculator phi ixT r t) 
ProductionRule (RealLL1Rule phi ixT r t) => LiftableProductionRule (RealLL1Rule phi ixT r t) 
(ProductionRule (CombineEpsilonsRule p phi r t), EpsProductionRule p) => LiftableProductionRule (CombineEpsilonsRule p phi r t) 
(ProductionRule (FilterDiesRule p phi r t), LiftableProductionRule p) => LiftableProductionRule (FilterDiesRule p phi r t) 
(ProductionRule (FSCalculator phi r t rr), Token t) => LiftableProductionRule (FSCalculator phi r t rr) 
ProductionRule (IsChainNT phi r t rr) => LiftableProductionRule (IsChainNT phi r t rr) 
(ProductionRule (RuleToManyWrapper p phi r t), ProductionRule p, EpsProductionRule p) => LiftableProductionRule (RuleToManyWrapper p phi r t) 
ProductionRule (EnumerateProductionRule phi ixT r t) => LiftableProductionRule (EnumerateProductionRule phi ixT r t) 
ProductionRule (IsDeadRule phi r t rr) => LiftableProductionRule (IsDeadRule phi r t rr) 
(ProductionRule (UnfoldDeadRule p phi r t), LiftableProductionRule p) => LiftableProductionRule (UnfoldDeadRule p phi r t) 
(ProductionRule (UnfoldLoopsWrapper p phi ixT r t), LiftableProductionRule p) => LiftableProductionRule (UnfoldLoopsWrapper p phi ixT r t) 
(ProductionRule (RPWRule p phi ixT r t), LiftableProductionRule p) => LiftableProductionRule (RPWRule p phi ixT r t) 
(ProductionRule (IBW p phi r t rr), Token t, LiftableProductionRule p, BiasedProductionRule p) => LiftableProductionRule (IBW p phi r t rr) 
(ProductionRule (PBEHProductionRule p phi (MaybeSemanticT r) r t), LiftableProductionRule p) => LiftableProductionRule (PBEHProductionRule p phi (MaybeSemanticT r) r t) 
(ProductionRule (UnfoldDepthFirstRule p phi r t rr), LiftableProductionRule p) => LiftableProductionRule (UnfoldDepthFirstRule p phi r t rr) 
ProductionRule (FoldReachableIntRule phi r t rr n) => LiftableProductionRule (FoldReachableIntRule phi r t rr n) 
(ProductionRule (FLWrap p (FoldLoopsDomain phi) (FoldLoopsValue r) phi r t), LiftableProductionRule p) => LiftableProductionRule (FLWrap p (FoldLoopsDomain phi) (FoldLoopsValue r) phi r t) 
(ProductionRule (IGW p phiL phiR rL rR t), LiftableProductionRule p) => LiftableProductionRule (IGW p phiL phiR rL rR t) 
(ProductionRule (CGW p phiL phiR rL rR t), LiftableProductionRule p) => LiftableProductionRule (CGW p phiL phiR rL rR t) 
(ProductionRule (TransformLCRule p (LCDomain phi t) (LCValue r t) phi r t), ProductionRule p, EpsProductionRule p, RecProductionRule p (LCDomain phi t) (LCValue r t)) => LiftableProductionRule (TransformLCRule p (LCDomain phi t) (LCValue r t) phi r t) 
(ProductionRule (TransformUPWrapper p surrIx (UPDomain phi) (UPValue r) phi ixT r t), LiftableProductionRule p) => LiftableProductionRule (TransformUPWrapper p surrIx (UPDomain phi) (UPValue r) phi ixT r t) 

class LiftableProductionRule p => EpsProductionRule p whereSource

Methods

epsilon :: a -> p aSource

Epsilon rule. Always matches, consumes nothing, produces the given value as result.

Instances

LiftableProductionRule (RecDecRule t) => EpsProductionRule (RecDecRule t) 
(LiftableProductionRule (WrapGenParser t), Token t) => EpsProductionRule (WrapGenParser t) 
LiftableProductionRule (PackratRule phi r t) => EpsProductionRule (PackratRule phi r t) 
(LiftableProductionRule (BranchSelectorComputer phi r t), Domain phi, Token t) => EpsProductionRule (BranchSelectorComputer phi r t) 
(LiftableProductionRule (WrapP t loc ct), Token t) => EpsProductionRule (WrapP t loc ct) 
LiftableProductionRule (AssessSizeProductionRule phi r t) => EpsProductionRule (AssessSizeProductionRule phi r t) 
LiftableProductionRule (EnumTokensRule phi r t) => EpsProductionRule (EnumTokensRule phi r t) 
LiftableProductionRule (IsEpsilonRule phi r t) => EpsProductionRule (IsEpsilonRule phi r t) 
LiftableProductionRule (PrintProductionRule phi r t) => EpsProductionRule (PrintProductionRule phi r t) 
LiftableProductionRule (GraphConstructor phi r t) => EpsProductionRule (GraphConstructor phi r t) 
LiftableProductionRule (LLRule phi ixT r t) => EpsProductionRule (LLRule phi ixT r t) 
(LiftableProductionRule (FSCalculator phi ixT r t), Domain phi, Token t) => EpsProductionRule (FSCalculator phi ixT r t) 
LiftableProductionRule (RealLL1Rule phi ixT r t) => EpsProductionRule (RealLL1Rule phi ixT r t) 
(LiftableProductionRule (CombineEpsilonsRule p phi r t), EpsProductionRule p) => EpsProductionRule (CombineEpsilonsRule p phi r t) 
(LiftableProductionRule (FilterDiesRule p phi r t), EpsProductionRule p) => EpsProductionRule (FilterDiesRule p phi r t) 
(LiftableProductionRule (FSCalculator phi r t rr), Token t) => EpsProductionRule (FSCalculator phi r t rr) 
LiftableProductionRule (IsChainNT phi r t rr) => EpsProductionRule (IsChainNT phi r t rr) 
(LiftableProductionRule (RuleToManyWrapper p phi r t), ProductionRule p, EpsProductionRule p) => EpsProductionRule (RuleToManyWrapper p phi r t) 
LiftableProductionRule (EnumerateProductionRule phi ixT r t) => EpsProductionRule (EnumerateProductionRule phi ixT r t) 
LiftableProductionRule (IsDeadRule phi r t rr) => EpsProductionRule (IsDeadRule phi r t rr) 
(LiftableProductionRule (UnfoldDeadRule p phi r t), EpsProductionRule p) => EpsProductionRule (UnfoldDeadRule p phi r t) 
(LiftableProductionRule (UnfoldLoopsWrapper p phi ixT r t), EpsProductionRule p) => EpsProductionRule (UnfoldLoopsWrapper p phi ixT r t) 
(LiftableProductionRule (RPWRule p phi ixT r t), EpsProductionRule p) => EpsProductionRule (RPWRule p phi ixT r t) 
(LiftableProductionRule (IBW p phi r t rr), Token t, EpsProductionRule p, BiasedProductionRule p) => EpsProductionRule (IBW p phi r t rr) 
(LiftableProductionRule (PBEHProductionRule p phi (MaybeSemanticT r) r t), EpsProductionRule p) => EpsProductionRule (PBEHProductionRule p phi (MaybeSemanticT r) r t) 
(LiftableProductionRule (UnfoldDepthFirstRule p phi r t rr), EpsProductionRule p) => EpsProductionRule (UnfoldDepthFirstRule p phi r t rr) 
LiftableProductionRule (FoldReachableIntRule phi r t rr n) => EpsProductionRule (FoldReachableIntRule phi r t rr n) 
(LiftableProductionRule (FLWrap p (FoldLoopsDomain phi) (FoldLoopsValue r) phi r t), EpsProductionRule p) => EpsProductionRule (FLWrap p (FoldLoopsDomain phi) (FoldLoopsValue r) phi r t) 
(LiftableProductionRule (IGW p phiL phiR rL rR t), EpsProductionRule p) => EpsProductionRule (IGW p phiL phiR rL rR t) 
(LiftableProductionRule (CGW p phiL phiR rL rR t), EpsProductionRule p) => EpsProductionRule (CGW p phiL phiR rL rR t) 
(LiftableProductionRule (TransformLCRule p (LCDomain phi t) (LCValue r t) phi r t), ProductionRule p, EpsProductionRule p, RecProductionRule p (LCDomain phi t) (LCValue r t)) => EpsProductionRule (TransformLCRule p (LCDomain phi t) (LCValue r t) phi r t) 
(LiftableProductionRule (TransformUPWrapper p surrIx (UPDomain phi) (UPValue r) phi ixT r t), EpsProductionRule p) => EpsProductionRule (TransformUPWrapper p surrIx (UPDomain phi) (UPValue r) phi ixT r t) 

class TokenProductionRule p t | p -> t whereSource

Type class for production rules matching tokens of a certain token type t. t should be an instance of the Token type class.

Methods

token :: t -> p (ConcreteToken t)Source

Match a given token of type t and produce its concrete value (of type ConcreteToken t).

anyToken :: p (ConcreteToken t)Source

Instances

Token t => TokenProductionRule (RecDecRule t) t 
Token t => TokenProductionRule (WrapGenParser t) t 
Token t => TokenProductionRule (PackratRule phi r t) t 
(Token t, Domain phi) => TokenProductionRule (BranchSelectorComputer phi r t) t 
(Token t, Show ct, ~ * (ConcreteToken t) ct, IsLocationUpdatedBy loc ct) => TokenProductionRule (WrapP t loc ct) t 
Token t => TokenProductionRule (AssessSizeProductionRule phi r t) t 
Token t => TokenProductionRule (EnumTokensRule phi r t) t 
TokenProductionRule (IsEpsilonRule phi r t) t 
Token t => TokenProductionRule (LiftedRule phi r t) t 
Token t => TokenProductionRule (PrintProductionRule phi r t) t 
Token t => TokenProductionRule (GraphConstructor phi r t) t 
Token t => TokenProductionRule (LLRule phi ixT r t) t 
(Token t, Domain phi) => TokenProductionRule (FSCalculator phi ixT r t) t 
Token t => TokenProductionRule (RealLL1Rule phi ixT r t) t 
TokenProductionRule p t => TokenProductionRule (CombineEpsilonsRule p phi r t) t 
TokenProductionRule p t => TokenProductionRule (FilterDiesRule p phi r t) t 
Token t => TokenProductionRule (FSCalculator phi r t rr) t 
TokenProductionRule (IsChainNT phi r t rr) t 
ProductionRule p => TokenProductionRule (RuleToManyWrapper p phi r t) t 
Token t => TokenProductionRule (EnumerateProductionRule phi ixT r t) t 
TokenProductionRule (IsDeadRule phi r t rr) t 
TokenProductionRule p t => TokenProductionRule (UnfoldDeadRule p phi r t) t 
TokenProductionRule p t => TokenProductionRule (UnfoldLoopsWrapper p phi ixT r t) t 
TokenProductionRule p t => TokenProductionRule (RPWRule p phi ixT r t) t 
(Token t, TokenProductionRule p t) => TokenProductionRule (IBW p phi r t rr) t 
(PenaltyProductionRule p, LiftableProductionRule p, TokenProductionRule p t, Token t) => TokenProductionRule (PBEHProductionRule p phi (MaybeSemanticT r) r t) t 
TokenProductionRule p t => TokenProductionRule (UnfoldDepthFirstRule p phi r t rr) t 
TokenProductionRule (FoldReachableIntRule phi r t rr n) t 
TokenProductionRule p t => TokenProductionRule (FLWrap p (FoldLoopsDomain phi) (FoldLoopsValue r) phi r t) t 
TokenProductionRule p t => TokenProductionRule (IGW p phiL phiR rL rR t) t 
TokenProductionRule p t => TokenProductionRule (CGW p phiL phiR rL rR t) t 
(Token t, TokenProductionRule p t, ProductionRule p, LiftableProductionRule p, RecProductionRule p (LCDomain phi t) (LCValue r t)) => TokenProductionRule (TransformLCRule p unused1 unused2 phi r t) t 
(TokenProductionRule p t, ProductionRule p) => TokenProductionRule (TransformUPWrapper p surrIx (UPDomain phi) (UPValue r) phi ixT r t) t 

class PenaltyProductionRule p whereSource

Methods

penalty :: Int -> p a -> p aSource

Instances

PenaltyProductionRule (LiftedRule phi r t) 
PenaltyProductionRule (PrintProductionRule phi r t) 
PenaltyProductionRule p => PenaltyProductionRule (FilterDiesRule p phi r t) 
PenaltyProductionRule (IsDeadRule phi r t rr) 
PenaltyProductionRule p => PenaltyProductionRule (UnfoldLoopsWrapper p phi ixT r t) 
PenaltyProductionRule p => PenaltyProductionRule (RPWRule p phi ixT r t) 
PenaltyProductionRule p => PenaltyProductionRule (UnfoldDepthFirstRule p phi r t rr) 
PenaltyProductionRule (FoldReachableIntRule phi r t rr n) 
PenaltyProductionRule p => PenaltyProductionRule (TransformUPWrapper p surrIx (UPDomain phi) (UPValue r) phi ixT r t) 

(*>>>) :: (ProductionRule p, LiftableProductionRule p) => p a -> p b -> p bSource

Sequence two rules, but drop the result of the first.

(>>>*) :: (ProductionRule p, LiftableProductionRule p) => p a -> p b -> p aSource

Sequence two rules, but drop the result of the second.

($>>) :: EpsProductionRule p => (a -> b) -> p a -> p bSource

Apply a given function to the result of a given rule.

($>>*) :: EpsProductionRule p => a -> p b -> p aSource

Replace a rule's result value with a given value.

($|>>) :: LiftableProductionRule p => (a -> b, Q Exp) -> p a -> p bSource

Apply a given function to the result of a given rule.

($|>>*) :: LiftableProductionRule p => (a, Q Exp) -> p b -> p aSource

Replace a rule's result value with a given value.

class RecProductionRule p phi r | p -> phi, p -> r whereSource

Production rule interpretations supporting the RecProductionRule type class support references to non-terminals in a given domain phi. The type of the result values of the rules is determined by semantic value family r.

Methods

ref :: phi ix -> p (r ix)Source

Reference a given non-terminal in a production rule.

Instances

RecProductionRule (PackratRule phi r t) phi r 
(Token t, Domain phi) => RecProductionRule (BranchSelectorComputer phi r t) phi r 
RecProductionRule (AssessSizeProductionRule phi r t) phi r 
ShowFam phi => RecProductionRule (EnumTokensRule phi r t) phi r 
RecProductionRule (IsEpsilonRule phi r t) phi r 
LiftFam phi => RecProductionRule (LiftedRule phi r t) phi r 
ShowFam phi => RecProductionRule (PrintProductionRule phi r t) phi r 
Domain phi => RecProductionRule (GraphConstructor phi r t) phi r 
RecProductionRule (LLRule phi ixT r t) phi r 
(Domain phi, Token t) => RecProductionRule (FSCalculator phi ixT r t) phi r 
RecProductionRule (RealLL1Rule phi ixT r t) phi r 
RecProductionRule p phi r => RecProductionRule (CombineEpsilonsRule p phi r t) phi r 
RecProductionRule p phi r => RecProductionRule (FilterDiesRule p phi r t) phi r 
(Token t, EqFam phi) => RecProductionRule (FSCalculator phi r t rr) phi r 
EqFam phi => RecProductionRule (IsChainNT phi r t rr) phi r 
LoopProductionRule p phi r => RecProductionRule (RuleToManyWrapper p phi r t) phi r 
RecProductionRule (EnumerateProductionRule phi ixT r t) phi r 
(ProductionRule p, RecProductionRule p phi r) => RecProductionRule (UnfoldDeadRule p phi r t) phi r 
RecProductionRule p phi r => RecProductionRule (UnfoldLoopsWrapper p phi ixT r t) phi r 
ProductionRule p => RecProductionRule (RPWRule p phi ixT r t) phi r 
(Token t, EqFam phi, RecProductionRule p phi r) => RecProductionRule (IBW p phi r t rr) phi r 
SimpleRecProductionRule p phi r rr => RecProductionRule (UnfoldDepthFirstRule p phi r t rr) phi r 
(RecProductionRule p phi (MaybeSemanticT r), LiftableProductionRule p, PenaltyProductionRule p) => RecProductionRule (PBEHProductionRule p phi (MaybeSemanticT r) r t) phi (MaybeSemanticT r) 
(RecProductionRule p (FoldLoopsDomain phi) (FoldLoopsValue r), ProductionRule p, EpsProductionRule p) => RecProductionRule (FLWrap p (FoldLoopsDomain phi) (FoldLoopsValue r) phi r t) phi r 
(EpsProductionRule p, ProductionRule p, RecProductionRule p (MergeDomain phiL phiR) (EitherFunctor rL rR)) => RecProductionRule (CGW p phiL phiR rL rR t) phiL rL 
(ProductionRule p, EqFam phi, EpsProductionRule p, RecProductionRule p (LCDomain phi t) (LCValue r t)) => RecProductionRule (TransformLCRule p (LCDomain phi t) (LCValue r t) phi r t) phi r 
(EpsProductionRule p, ProductionRule p, RecProductionRule p (MergeDomain phiL phiR) (EitherFunctor rL rR)) => RecProductionRule (IGW p phiL phiR rL rR t) (MergeDomain phiR phiL) (EitherFunctor rR rL) 
(RecProductionRule p (UPDomain phi) (UPValue r), LiftableProductionRule p, EqFam phi, LoopProductionRule p (UPDomain phi) (UPValue r)) => RecProductionRule (TransformUPWrapper p surrIx (UPDomain phi) (UPValue r) phi ixT r t) phi r 

class (ProductionRule p, LiftableProductionRule p, RecProductionRule p phi r) => LoopProductionRule p phi r | p -> phi, p -> r whereSource

Production rule interpretations supporting the LoopProductionRule type class allow for Kleene-star quantified references to non-terminals (zero or more, see the manyRef function) as well as +-quantified references to non-terminals (one or more, see the many1Ref function).

An instance can implement either manyRef or many1Ref, both or neither. Not implementing either produces old-style many and many1 combinator behaviour (discouraged for most situations)

Methods

manyRef :: phi ix -> p [r ix]Source

Match a given non-terminal zero or more times.

many1Ref :: phi ix -> p [r ix]Source

Match a given non-terminal one or more times.

Instances

(ProductionRule (PackratRule phi r t), LiftableProductionRule (PackratRule phi r t), RecProductionRule (PackratRule phi r t) phi r) => LoopProductionRule (PackratRule phi r t) phi r 
(ProductionRule (BranchSelectorComputer phi r t), LiftableProductionRule (BranchSelectorComputer phi r t), RecProductionRule (BranchSelectorComputer phi r t) phi r, Token t, Domain phi) => LoopProductionRule (BranchSelectorComputer phi r t) phi r 
(ProductionRule (AssessSizeProductionRule phi r t), LiftableProductionRule (AssessSizeProductionRule phi r t), RecProductionRule (AssessSizeProductionRule phi r t) phi r) => LoopProductionRule (AssessSizeProductionRule phi r t) phi r 
(ProductionRule (EnumTokensRule phi r t), LiftableProductionRule (EnumTokensRule phi r t), RecProductionRule (EnumTokensRule phi r t) phi r, ShowFam phi) => LoopProductionRule (EnumTokensRule phi r t) phi r 
(ProductionRule (IsEpsilonRule phi r t), LiftableProductionRule (IsEpsilonRule phi r t), RecProductionRule (IsEpsilonRule phi r t) phi r) => LoopProductionRule (IsEpsilonRule phi r t) phi r 
(ProductionRule (LiftedRule phi r t), LiftableProductionRule (LiftedRule phi r t), RecProductionRule (LiftedRule phi r t) phi r, LiftFam phi) => LoopProductionRule (LiftedRule phi r t) phi r 
(ProductionRule (PrintProductionRule phi r t), LiftableProductionRule (PrintProductionRule phi r t), RecProductionRule (PrintProductionRule phi r t) phi r, ShowFam phi) => LoopProductionRule (PrintProductionRule phi r t) phi r 
(ProductionRule (GraphConstructor phi r t), LiftableProductionRule (GraphConstructor phi r t), RecProductionRule (GraphConstructor phi r t) phi r, Domain phi) => LoopProductionRule (GraphConstructor phi r t) phi r 
(ProductionRule (CombineEpsilonsRule p phi r t), LiftableProductionRule (CombineEpsilonsRule p phi r t), RecProductionRule (CombineEpsilonsRule p phi r t) phi r, EpsProductionRule p, LoopProductionRule p phi r) => LoopProductionRule (CombineEpsilonsRule p phi r t) phi r 
(ProductionRule (FilterDiesRule p phi r t), LiftableProductionRule (FilterDiesRule p phi r t), RecProductionRule (FilterDiesRule p phi r t) phi r, LoopProductionRule p phi r) => LoopProductionRule (FilterDiesRule p phi r t) phi r 
(ProductionRule (FSCalculator phi r t rr), LiftableProductionRule (FSCalculator phi r t rr), RecProductionRule (FSCalculator phi r t rr) phi r, Token t, EqFam phi) => LoopProductionRule (FSCalculator phi r t rr) phi r 
(ProductionRule (IsChainNT phi r t rr), LiftableProductionRule (IsChainNT phi r t rr), RecProductionRule (IsChainNT phi r t rr) phi r, EqFam phi) => LoopProductionRule (IsChainNT phi r t rr) phi r 
(ProductionRule (RuleToManyWrapper p phi r t), LiftableProductionRule (RuleToManyWrapper p phi r t), RecProductionRule (RuleToManyWrapper p phi r t) phi r, ProductionRule p, EpsProductionRule p, LoopProductionRule p phi r) => LoopProductionRule (RuleToManyWrapper p phi r t) phi r 
(ProductionRule (UnfoldDeadRule p phi r t), LiftableProductionRule (UnfoldDeadRule p phi r t), RecProductionRule (UnfoldDeadRule p phi r t) phi r, ProductionRule p, LiftableProductionRule p, LoopProductionRule p phi r) => LoopProductionRule (UnfoldDeadRule p phi r t) phi r 
(ProductionRule (UnfoldLoopsWrapper p phi ixT r t), LiftableProductionRule (UnfoldLoopsWrapper p phi ixT r t), RecProductionRule (UnfoldLoopsWrapper p phi ixT r t) phi r, ProductionRule p, LiftableProductionRule p, RecProductionRule p phi r) => LoopProductionRule (UnfoldLoopsWrapper p phi ixT r t) phi r 
(ProductionRule (RPWRule p phi ixT r t), LiftableProductionRule (RPWRule p phi ixT r t), RecProductionRule (RPWRule p phi ixT r t) phi r, LoopProductionRule p phi r) => LoopProductionRule (RPWRule p phi ixT r t) phi r 
(ProductionRule (IBW p phi r t rr), LiftableProductionRule (IBW p phi r t rr), RecProductionRule (IBW p phi r t rr) phi r, Token t, EqFam phi, BiasedProductionRule p, LiftableProductionRule p, LoopProductionRule p phi r) => LoopProductionRule (IBW p phi r t rr) phi r 
(ProductionRule (UnfoldDepthFirstRule p phi r t rr), LiftableProductionRule (UnfoldDepthFirstRule p phi r t rr), RecProductionRule (UnfoldDepthFirstRule p phi r t rr) phi r, ProductionRule p, LiftableProductionRule p, SimpleRecProductionRule p phi r rr, SimpleLoopProductionRule p phi r rr) => LoopProductionRule (UnfoldDepthFirstRule p phi r t rr) phi r 
(ProductionRule (PBEHProductionRule p phi (MaybeSemanticT r) r t), LiftableProductionRule (PBEHProductionRule p phi (MaybeSemanticT r) r t), RecProductionRule (PBEHProductionRule p phi (MaybeSemanticT r) r t) phi (MaybeSemanticT r), LoopProductionRule p phi (MaybeSemanticT r), LiftableProductionRule p, PenaltyProductionRule p) => LoopProductionRule (PBEHProductionRule p phi (MaybeSemanticT r) r t) phi (MaybeSemanticT r) 
(ProductionRule (FLWrap p (FoldLoopsDomain phi) (FoldLoopsValue r) phi r t), LiftableProductionRule (FLWrap p (FoldLoopsDomain phi) (FoldLoopsValue r) phi r t), RecProductionRule (FLWrap p (FoldLoopsDomain phi) (FoldLoopsValue r) phi r t) phi r, ProductionRule p, EpsProductionRule p, LiftableProductionRule p, TokenProductionRule p t, RecProductionRule p (FoldLoopsDomain phi) (FoldLoopsValue r)) => LoopProductionRule (FLWrap p (FoldLoopsDomain phi) (FoldLoopsValue r) phi r t) phi r 
(ProductionRule (CGW p phiL phiR rL rR t), LiftableProductionRule (CGW p phiL phiR rL rR t), RecProductionRule (CGW p phiL phiR rL rR t) phiL rL, EpsProductionRule p, ProductionRule p, LoopProductionRule p (MergeDomain phiL phiR) (EitherFunctor rL rR)) => LoopProductionRule (CGW p phiL phiR rL rR t) phiL rL 
(ProductionRule (TransformLCRule p (LCDomain phi t) (LCValue r t) phi r t), LiftableProductionRule (TransformLCRule p (LCDomain phi t) (LCValue r t) phi r t), RecProductionRule (TransformLCRule p (LCDomain phi t) (LCValue r t) phi r t) phi r, EqFam phi, EpsProductionRule p, LoopProductionRule p (LCDomain phi t) (LCValue r t)) => LoopProductionRule (TransformLCRule p (LCDomain phi t) (LCValue r t) phi r t) phi r 
(ProductionRule (IGW p phiL phiR rL rR t), LiftableProductionRule (IGW p phiL phiR rL rR t), RecProductionRule (IGW p phiL phiR rL rR t) (MergeDomain phiR phiL) (EitherFunctor rR rL), EpsProductionRule p, ProductionRule p, LoopProductionRule p (MergeDomain phiL phiR) (EitherFunctor rL rR)) => LoopProductionRule (IGW p phiL phiR rL rR t) (MergeDomain phiR phiL) (EitherFunctor rR rL) 
(ProductionRule (TransformUPWrapper p surrIx (UPDomain phi) (UPValue r) phi ixT r t), LiftableProductionRule (TransformUPWrapper p surrIx (UPDomain phi) (UPValue r) phi ixT r t), RecProductionRule (TransformUPWrapper p surrIx (UPDomain phi) (UPValue r) phi ixT r t) phi r, EqFam phi, LiftableProductionRule p, LoopProductionRule p (UPDomain phi) (UPValue r)) => LoopProductionRule (TransformUPWrapper p surrIx (UPDomain phi) (UPValue r) phi ixT r t) phi r 

class SuperProductionRule p whereSource

The 'SuperProductionRule| type class is in an experimental state, and currently not intended for general use.

Methods

subref :: (DomainEmbedding phi phi' supIxT, HFunctor phi (PF phi), ProductionRule (p phi ixT r t), ProductionRule (p phi' (IxMapSeq ixT supIxT) (SubVal supIxT r) t)) => (forall ix'. phi' ix' -> p phi' (IxMapSeq ixT supIxT) (SubVal supIxT r) t (PF phi' (SubVal supIxT r) ix')) -> phi' ix -> phi (supIxT ix) -> p phi ixT r t (PF phi r (supIxT ix))Source

tokenRange :: forall p t. (ProductionRule p, TokenProductionRule p t) => [t] -> p (ConcreteToken t)Source

Match any token in a given range of tokens.

string :: forall p t. (ProductionRule p, LiftableProductionRule p, TokenProductionRule p t) => [t] -> p [ConcreteToken t]Source

Consecutively match a given list of tokens and return their concrete token values as a list.

manyInf :: (ProductionRule p, LiftableProductionRule p) => p a -> p [a]Source

An old style many combinator. Produces an infinite rule similar to Parsec's many rule. Prefer to use the manyRef function whenever possible.

many1Inf :: (ProductionRule p, LiftableProductionRule p) => p a -> p [a]Source

An old style many combinator. Produces an infinite rule similar to Parsec's many rule. Prefer to use the manyRef function whenever possible.

class ProductionRuleWithLibrary p phi r | p -> phi, p -> r whereSource

Methods

lib :: phi ix -> p (r ix)Source

Instances

(EpsProductionRule p, ProductionRule p, RecProductionRule p (MergeDomain phiL phiR) (EitherFunctor rL rR)) => ProductionRuleWithLibrary (CGW p phiL phiR rL rR t) phiR rR 

class BiasedProductionRule p whereSource

Methods

(>|||) :: p a -> p a -> p aSource

Left-biased choice

(<|||) :: p a -> p a -> p aSource

Right-biased choice

Instances

BiasedProductionRule (WrapGenParser t) 
BiasedProductionRule (LiftedRule phi r t) 
BiasedProductionRule (PrintProductionRule phi r t) 
BiasedProductionRule (IsDeadRule phi r t rr) 
BiasedProductionRule p => BiasedProductionRule (RPWRule p phi ixT r t) 
BiasedProductionRule p => BiasedProductionRule (UnfoldDepthFirstRule p phi r t rr) 
BiasedProductionRule (FoldReachableIntRule phi r t rr n)