Copyright | (c) Karl Cronburg 2018 |
---|---|
License | BSD3 |
Maintainer | karl@cs.tufts.edu |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- recognize :: (Eq nts, Ref t, Eq (Sym t), HasEOF (Sym t), Ord nts, Ord t, Ord (Sym t), Ord (StripEOF (Sym t)), Prettify nts, Prettify t, Prettify (Sym t), Prettify (StripEOF (Sym t)), Hashable (Sym t), Hashable nts, Hashable (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) dt -> [t] -> Bool
- first :: forall sts nts dt. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable nts, Hashable sts) => Grammar () nts sts dt -> [ProdElem nts sts] -> Set (Icon sts)
- follow :: forall nts sts dt. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable nts, Hashable sts) => Grammar () nts sts dt -> nts -> Set (Icon sts)
- foldWhileEpsilon :: (Eq ts, Hashable ts) => (HashSet (Icon ts) -> HashSet a -> HashSet a) -> HashSet a -> [HashSet (Icon ts)] -> HashSet a
- isLL1 :: (Eq nts, Eq sts, Ord nts, Ord sts, Hashable nts, Hashable sts) => Grammar () nts sts dt -> Bool
- parseTable :: forall nts sts dt. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts dt -> ParseTable nts sts
- predictiveParse :: forall nts t ast dt. (Prettify nts, Prettify t, Prettify (Sym t), Prettify (StripEOF (Sym t)), Prettify ast, Eq nts, Eq (Sym t), HasEOF (Sym t), Ord (Sym t), Ord nts, Ord t, Ord (StripEOF (Sym t)), Hashable (Sym t), Hashable nts, Hashable (StripEOF (Sym t)), Ref t) => Grammar () nts (StripEOF (Sym t)) dt -> Action ast nts t -> [t] -> Maybe ast
- removeEpsilons :: forall s nts t dt. (Eq t, Eq nts, Eq dt, Prettify t, Prettify nts, Prettify s, Ord t, Ord nts, Ord dt, Hashable t, Hashable nts) => Grammar s nts t dt -> Grammar s nts t dt
- removeEpsilons' :: forall s nts t dt. (Eq t, Eq nts, Eq dt, Prettify t, Prettify nts, Prettify s, Ord t, Ord nts, Hashable t, Hashable nts) => [Production s nts t dt] -> [Production s nts t dt]
- leftFactor :: forall s nts t dt. (Eq t, Eq nts, Prettify t, Prettify nts, Ord t, Ord nts, Hashable nts) => Grammar s nts t dt -> Grammar s (Prime nts) t dt
- newtype Prime nts = Prime (nts, Int)
- type ParseTable nts sts = Map (PTKey nts sts) (PTValue nts sts)
- type PTKey nts sts = (nts, Icon sts)
- type PTValue nts sts = Set (ProdElems nts sts)
Documentation
recognize :: (Eq nts, Ref t, Eq (Sym t), HasEOF (Sym t), Ord nts, Ord t, Ord (Sym t), Ord (StripEOF (Sym t)), Prettify nts, Prettify t, Prettify (Sym t), Prettify (StripEOF (Sym t)), Hashable (Sym t), Hashable nts, Hashable (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) dt -> [t] -> Bool Source #
Language recognizer using predictiveParse
.
first :: forall sts nts dt. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable nts, Hashable sts) => Grammar () nts sts dt -> [ProdElem nts sts] -> Set (Icon sts) Source #
First set of a grammar.
follow :: forall nts sts dt. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable nts, Hashable sts) => Grammar () nts sts dt -> nts -> Set (Icon sts) Source #
Follow set of a grammar.
foldWhileEpsilon :: (Eq ts, Hashable ts) => (HashSet (Icon ts) -> HashSet a -> HashSet a) -> HashSet a -> [HashSet (Icon ts)] -> HashSet a Source #
Fold over a set of ProdElems (symbols) while all the previous sets of symbols contains an epsilon.
isLL1 :: (Eq nts, Eq sts, Ord nts, Ord sts, Hashable nts, Hashable sts) => Grammar () nts sts dt -> Bool Source #
Is the given grammar in LL(1)?
A -> α | β for all distinct ordered pairs of α and β, first(α)intersection
first(β) == empty and if epsilon is in α, then first(α)intersection
follow(A) == empty
parseTable :: forall nts sts dt. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts dt -> ParseTable nts sts Source #
The algorithm for computing an LL parse table from a grammar.
predictiveParse :: forall nts t ast dt. (Prettify nts, Prettify t, Prettify (Sym t), Prettify (StripEOF (Sym t)), Prettify ast, Eq nts, Eq (Sym t), HasEOF (Sym t), Ord (Sym t), Ord nts, Ord t, Ord (StripEOF (Sym t)), Hashable (Sym t), Hashable nts, Hashable (StripEOF (Sym t)), Ref t) => Grammar () nts (StripEOF (Sym t)) dt -> Action ast nts t -> [t] -> Maybe ast Source #
Top-down predictive parsing algorithm.
removeEpsilons :: forall s nts t dt. (Eq t, Eq nts, Eq dt, Prettify t, Prettify nts, Prettify s, Ord t, Ord nts, Ord dt, Hashable t, Hashable nts) => Grammar s nts t dt -> Grammar s nts t dt Source #
Remove all epsilon productions, i.e. productions of the form "A -> eps", without affecting the language accepted.
removeEpsilons' :: forall s nts t dt. (Eq t, Eq nts, Eq dt, Prettify t, Prettify nts, Prettify s, Ord t, Ord nts, Hashable t, Hashable nts) => [Production s nts t dt] -> [Production s nts t dt] Source #
Remove all epsilon productions, i.e. productions of the form "A -> eps", without affecting the language accepted.
leftFactor :: forall s nts t dt. (Eq t, Eq nts, Prettify t, Prettify nts, Ord t, Ord nts, Hashable nts) => Grammar s nts t dt -> Grammar s (Prime nts) t dt Source #
Left-factor a grammar to make it LL(1). This is experimental and mostly untested.
This adds Prime
s to the nonterminal symbols in cases where we need to break up
a production rule in order to left factor it.
Add primes to nonterminal symbols.
Instances
Eq nts => Eq (Prime nts) Source # | |
Ord nts => Ord (Prime nts) Source # | |
Defined in Text.ANTLR.LL1 | |
Show nts => Show (Prime nts) Source # | |
Generic (Prime nts) Source # | |
Hashable nts => Hashable (Prime nts) Source # | |
Defined in Text.ANTLR.LL1 | |
Prettify nts => Prettify (Prime nts) Source # | |
type Rep (Prime nts) Source # | |
Defined in Text.ANTLR.LL1 |