antlr-haskell-0.1.0.1: A Haskell implementation of the ANTLR top-down parser generator

Copyright(c) Karl Cronburg 2018
LicenseBSD3
Maintainerkarl@cs.tufts.edu
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Text.ANTLR.LL1

Description

 
Synopsis

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 Primes to the nonterminal symbols in cases where we need to break up a production rule in order to left factor it.

newtype Prime nts Source #

Add primes to nonterminal symbols.

Constructors

Prime (nts, Int) 
Instances
Eq nts => Eq (Prime nts) Source # 
Instance details

Defined in Text.ANTLR.LL1

Methods

(==) :: Prime nts -> Prime nts -> Bool #

(/=) :: Prime nts -> Prime nts -> Bool #

Ord nts => Ord (Prime nts) Source # 
Instance details

Defined in Text.ANTLR.LL1

Methods

compare :: Prime nts -> Prime nts -> Ordering #

(<) :: Prime nts -> Prime nts -> Bool #

(<=) :: Prime nts -> Prime nts -> Bool #

(>) :: Prime nts -> Prime nts -> Bool #

(>=) :: Prime nts -> Prime nts -> Bool #

max :: Prime nts -> Prime nts -> Prime nts #

min :: Prime nts -> Prime nts -> Prime nts #

Show nts => Show (Prime nts) Source # 
Instance details

Defined in Text.ANTLR.LL1

Methods

showsPrec :: Int -> Prime nts -> ShowS #

show :: Prime nts -> String #

showList :: [Prime nts] -> ShowS #

Generic (Prime nts) Source # 
Instance details

Defined in Text.ANTLR.LL1

Associated Types

type Rep (Prime nts) :: Type -> Type #

Methods

from :: Prime nts -> Rep (Prime nts) x #

to :: Rep (Prime nts) x -> Prime nts #

Hashable nts => Hashable (Prime nts) Source # 
Instance details

Defined in Text.ANTLR.LL1

Methods

hashWithSalt :: Int -> Prime nts -> Int #

hash :: Prime nts -> Int #

Prettify nts => Prettify (Prime nts) Source # 
Instance details

Defined in Text.ANTLR.LL1

type Rep (Prime nts) Source # 
Instance details

Defined in Text.ANTLR.LL1

type Rep (Prime nts) = D1 (MetaData "Prime" "Text.ANTLR.LL1" "antlr-haskell-0.1.0.1-47wJxWjYxn91lXcjBVmKNu" True) (C1 (MetaCons "Prime" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (nts, Int))))

type ParseTable nts sts = Map (PTKey nts sts) (PTValue nts sts) Source #

M[A,s] = α for each symbol s member FIRST(α)

type PTKey nts sts = (nts, Icon sts) Source #

Keys in the LL1 parse table.

type PTValue nts sts = Set (ProdElems nts sts) Source #

All possible productions we could reduce. Empty implies parse error, singleton implies unambiguous entry, multiple implies ambiguous: