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.LR

Description

 
Synopsis

Documentation

data Item a nts sts Source #

An Item is a production with a dot in it indicating how far into the production we have parsed:

A ->  α . β

Constructors

Item (ItemLHS nts) (ProdElems nts sts) (ProdElems nts sts) a 
Instances
(Eq nts, Eq sts, Eq a) => Eq (Item a nts sts) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

(==) :: Item a nts sts -> Item a nts sts -> Bool #

(/=) :: Item a nts sts -> Item a nts sts -> Bool #

(Data a, Data nts, Data sts) => Data (Item a nts sts) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Item a nts sts -> c (Item a nts sts) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Item a nts sts) #

toConstr :: Item a nts sts -> Constr #

dataTypeOf :: Item a nts sts -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Item a nts sts)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Item a nts sts)) #

gmapT :: (forall b. Data b => b -> b) -> Item a nts sts -> Item a nts sts #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Item a nts sts -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Item a nts sts -> r #

gmapQ :: (forall d. Data d => d -> u) -> Item a nts sts -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Item a nts sts -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Item a nts sts -> m (Item a nts sts) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Item a nts sts -> m (Item a nts sts) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Item a nts sts -> m (Item a nts sts) #

(Ord nts, Ord sts, Ord a) => Ord (Item a nts sts) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

compare :: Item a nts sts -> Item a nts sts -> Ordering #

(<) :: Item a nts sts -> Item a nts sts -> Bool #

(<=) :: Item a nts sts -> Item a nts sts -> Bool #

(>) :: Item a nts sts -> Item a nts sts -> Bool #

(>=) :: Item a nts sts -> Item a nts sts -> Bool #

max :: Item a nts sts -> Item a nts sts -> Item a nts sts #

min :: Item a nts sts -> Item a nts sts -> Item a nts sts #

(Show nts, Show sts, Show a) => Show (Item a nts sts) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

showsPrec :: Int -> Item a nts sts -> ShowS #

show :: Item a nts sts -> String #

showList :: [Item a nts sts] -> ShowS #

Generic (Item a nts sts) Source # 
Instance details

Defined in Text.ANTLR.LR

Associated Types

type Rep (Item a nts sts) :: Type -> Type #

Methods

from :: Item a nts sts -> Rep (Item a nts sts) x #

to :: Rep (Item a nts sts) x -> Item a nts sts #

(Lift nts, Lift sts, Lift a) => Lift (Item a nts sts) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

lift :: Item a nts sts -> Q Exp #

(Hashable nts, Hashable sts, Hashable a) => Hashable (Item a nts sts) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

hashWithSalt :: Int -> Item a nts sts -> Int #

hash :: Item a nts sts -> Int #

(Prettify a, Prettify nts, Prettify sts) => Prettify (Item a nts sts) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

prettify :: Item a nts sts -> Pretty Source #

prettifyList :: [Item a nts sts] -> Pretty Source #

type Rep (Item a nts sts) Source # 
Instance details

Defined in Text.ANTLR.LR

data ItemLHS nts Source #

The nonterminal symbol for which an item refers to.

Constructors

Init nts

This is S' if S is the grammar start symbol

ItemNT nts

Just an item wrapper around a nonterminal symbol

Instances
Eq nts => Eq (ItemLHS nts) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

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

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

Data nts => Data (ItemLHS nts) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ItemLHS nts -> c (ItemLHS nts) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ItemLHS nts) #

toConstr :: ItemLHS nts -> Constr #

dataTypeOf :: ItemLHS nts -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ItemLHS nts)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ItemLHS nts)) #

gmapT :: (forall b. Data b => b -> b) -> ItemLHS nts -> ItemLHS nts #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ItemLHS nts -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ItemLHS nts -> r #

gmapQ :: (forall d. Data d => d -> u) -> ItemLHS nts -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ItemLHS nts -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ItemLHS nts -> m (ItemLHS nts) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ItemLHS nts -> m (ItemLHS nts) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ItemLHS nts -> m (ItemLHS nts) #

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

Defined in Text.ANTLR.LR

Methods

compare :: ItemLHS nts -> ItemLHS nts -> Ordering #

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

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

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

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

max :: ItemLHS nts -> ItemLHS nts -> ItemLHS nts #

min :: ItemLHS nts -> ItemLHS nts -> ItemLHS nts #

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

Defined in Text.ANTLR.LR

Methods

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

show :: ItemLHS nts -> String #

showList :: [ItemLHS nts] -> ShowS #

Generic (ItemLHS nts) Source # 
Instance details

Defined in Text.ANTLR.LR

Associated Types

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

Methods

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

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

Lift nts => Lift (ItemLHS nts) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

lift :: ItemLHS nts -> Q Exp #

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

Defined in Text.ANTLR.LR

Methods

hashWithSalt :: Int -> ItemLHS nts -> Int #

hash :: ItemLHS nts -> Int #

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

Defined in Text.ANTLR.LR

type Rep (ItemLHS nts) Source # 
Instance details

Defined in Text.ANTLR.LR

type Rep (ItemLHS nts) = D1 (MetaData "ItemLHS" "Text.ANTLR.LR" "antlr-haskell-0.1.0.1-47wJxWjYxn91lXcjBVmKNu" False) (C1 (MetaCons "Init" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 nts)) :+: C1 (MetaCons "ItemNT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 nts)))

kernel :: (Tabular nts, Tabular sts, Ord a, Hashable a) => Set (Item a nts sts) -> Set (Item a nts sts) Source #

The kernel of a set items, namely the items where the dot is not at the left-most position of the RHS (also excluding the starting symbol).

items :: forall nts sts dt a. (CanParse' nts sts, Ord a, Hashable a) => Grammar () nts sts dt -> Goto' nts sts (CoreLRState a nts sts) -> CoreLRState a nts sts -> Set (CoreLRState a nts sts) Source #

Compute all possible LR items for a grammar by iteratively running goto until reaching a fixed point.

slrClosure :: forall nts sts dt. CanParse' nts sts => Grammar () nts sts dt -> SLRClosure (CoreSLRState nts sts) Source #

Algorithm for computing an SLR closure.

slrGoto :: forall nts sts dt. CanParse' nts sts => Grammar () nts sts dt -> Goto' nts sts (CoreSLRState nts sts) Source #

Goto with an SLR closure, slrClosure.

slrItems :: forall nts sts dt. (Tabular nts, Tabular sts) => Grammar () nts sts dt -> Set (Set (SLRItem nts sts)) Source #

Compute SLR table with appropriate slrGoto and slrClosure.

allSLRItems :: forall nts sts dt. CanParse' nts sts => Grammar () nts sts dt -> Set (SLRItem nts sts) Source #

Generate the set of all possible Items for a given grammar:

slrTable :: forall nts sts dt. (Tabular nts, Tabular sts) => Grammar () nts sts dt -> SLRTable nts sts (CoreSLRState nts sts) Source #

Algorithm for computing the SLR table.

slrParse :: forall nts t dt ast. (CanParse nts t, IsAST ast) => Grammar () nts (StripEOF (Sym t)) dt -> Action ast nts t -> [t] -> LRResult (CoreSLRState nts (StripEOF (Sym t))) t t ast Source #

Entrypoint for SLR parsing.

slrRecognize :: forall nts t dt. CanParse nts t => Grammar () nts (StripEOF (Sym t)) dt -> [t] -> Bool Source #

SLR language recognizer.

lr1Closure :: forall nts sts dt. (Tabular nts, Tabular sts) => Grammar () nts sts dt -> Closure (CoreLR1State nts sts) Source #

Algorithm for computing an LR(1) closure.

lr1Goto :: (Tabular nts, Tabular sts) => Grammar () nts sts dt -> Goto' nts sts (CoreLR1State nts sts) Source #

LR(1) goto table (function) of a grammar.

lr1Items :: CanParse' nts sts => Grammar () nts sts dt -> Set (CoreLRState (LR1LookAhead sts) nts sts) Source #

Items computed for LR(1) with an lr1Goto and an lr1Closure.

lr1Table :: forall nts sts dt. (Tabular nts, Tabular sts) => Grammar () nts sts dt -> LRTable nts sts (CoreLR1State nts sts) Source #

Algorithm for computing the LR(1) table.

lr1Parse :: forall nts t dt ast. (CanParse nts t, IsAST ast) => Grammar () nts (StripEOF (Sym t)) dt -> Action ast nts t -> [t] -> LRResult (CoreLR1State nts (StripEOF (Sym t))) t t ast Source #

Entrypoint for LR(1) parser.

lr1Recognize :: forall nts t dt. CanParse nts t => Grammar () nts (StripEOF (Sym t)) dt -> [t] -> Bool Source #

LR(1) language recognizer.

type LR1LookAhead sts = Icon sts Source #

LR1 lookahead is a single Icon

type CoreLRState a nts sts = Set (Item a nts sts) Source #

CoreLRState is the one computed from the grammar (no information loss)

type CoreLR1State nts sts = Set (LR1Item nts sts) Source #

An LR1 state is a set of items with one lookahead symbol.

type CoreSLRState nts sts = Set (Item () nts sts) Source #

An SLR state is a set of items without a lookahead.

type LRTable nts sts lrstate = Map (lrstate, Icon sts) (LRAction nts sts lrstate) Source #

Ambiguous LR tables (can perform more than one action per lrstate)

type LRTable' nts sts lrstate = Map (lrstate, Icon sts) (LRAction nts sts lrstate) Source #

Disambiguated LR table (only one action performable per lrstate)

data LRAction nts sts lrstate Source #

The actions that an LR parser can tell the user about.

Constructors

Shift lrstate

Shift lrstate onto the stack.

Reduce (Production () nts sts ())

Reduce a production rule (and fire off any data constructor)

Accept

The parser has accepted the input.

Error

A parse error occured.

Instances
(Eq lrstate, Eq nts, Eq sts) => Eq (LRAction nts sts lrstate) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

(==) :: LRAction nts sts lrstate -> LRAction nts sts lrstate -> Bool #

(/=) :: LRAction nts sts lrstate -> LRAction nts sts lrstate -> Bool #

(Data nts, Data sts, Data lrstate) => Data (LRAction nts sts lrstate) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LRAction nts sts lrstate -> c (LRAction nts sts lrstate) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LRAction nts sts lrstate) #

toConstr :: LRAction nts sts lrstate -> Constr #

dataTypeOf :: LRAction nts sts lrstate -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LRAction nts sts lrstate)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LRAction nts sts lrstate)) #

gmapT :: (forall b. Data b => b -> b) -> LRAction nts sts lrstate -> LRAction nts sts lrstate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LRAction nts sts lrstate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LRAction nts sts lrstate -> r #

gmapQ :: (forall d. Data d => d -> u) -> LRAction nts sts lrstate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LRAction nts sts lrstate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LRAction nts sts lrstate -> m (LRAction nts sts lrstate) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LRAction nts sts lrstate -> m (LRAction nts sts lrstate) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LRAction nts sts lrstate -> m (LRAction nts sts lrstate) #

(Ord lrstate, Ord nts, Ord sts) => Ord (LRAction nts sts lrstate) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

compare :: LRAction nts sts lrstate -> LRAction nts sts lrstate -> Ordering #

(<) :: LRAction nts sts lrstate -> LRAction nts sts lrstate -> Bool #

(<=) :: LRAction nts sts lrstate -> LRAction nts sts lrstate -> Bool #

(>) :: LRAction nts sts lrstate -> LRAction nts sts lrstate -> Bool #

(>=) :: LRAction nts sts lrstate -> LRAction nts sts lrstate -> Bool #

max :: LRAction nts sts lrstate -> LRAction nts sts lrstate -> LRAction nts sts lrstate #

min :: LRAction nts sts lrstate -> LRAction nts sts lrstate -> LRAction nts sts lrstate #

(Show lrstate, Show nts, Show sts) => Show (LRAction nts sts lrstate) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

showsPrec :: Int -> LRAction nts sts lrstate -> ShowS #

show :: LRAction nts sts lrstate -> String #

showList :: [LRAction nts sts lrstate] -> ShowS #

Generic (LRAction nts sts lrstate) Source # 
Instance details

Defined in Text.ANTLR.LR

Associated Types

type Rep (LRAction nts sts lrstate) :: Type -> Type #

Methods

from :: LRAction nts sts lrstate -> Rep (LRAction nts sts lrstate) x #

to :: Rep (LRAction nts sts lrstate) x -> LRAction nts sts lrstate #

(Lift lrstate, Lift nts, Lift sts) => Lift (LRAction nts sts lrstate) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

lift :: LRAction nts sts lrstate -> Q Exp #

(Hashable lrstate, Hashable nts, Hashable sts) => Hashable (LRAction nts sts lrstate) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

hashWithSalt :: Int -> LRAction nts sts lrstate -> Int #

hash :: LRAction nts sts lrstate -> Int #

(Prettify lrstate, Prettify nts, Prettify sts, Hashable lrstate, Hashable sts, Hashable nts, Eq lrstate, Eq sts, Eq nts) => Prettify (LRAction nts sts lrstate) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

prettify :: LRAction nts sts lrstate -> Pretty Source #

prettifyList :: [LRAction nts sts lrstate] -> Pretty Source #

type Rep (LRAction nts sts lrstate) Source # 
Instance details

Defined in Text.ANTLR.LR

type Rep (LRAction nts sts lrstate) = D1 (MetaData "LRAction" "Text.ANTLR.LR" "antlr-haskell-0.1.0.1-47wJxWjYxn91lXcjBVmKNu" False) ((C1 (MetaCons "Shift" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lrstate)) :+: C1 (MetaCons "Reduce" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Production () nts sts ())))) :+: (C1 (MetaCons "Accept" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Error" PrefixI False) (U1 :: Type -> Type)))

lrParse :: forall nts t dt ast lrstate. (CanParse nts t, IsState lrstate, IsAST ast) => Grammar () nts (StripEOF (Sym t)) dt -> LRTable nts (StripEOF (Sym t)) lrstate -> Goto nts (StripEOF (Sym t)) lrstate -> lrstate -> Action ast nts t -> [t] -> LRResult lrstate t t ast Source #

The core LR parsing algorithm, parametrized for different variants (SLR, LR(1), ...).

type GLRResult lrstate c t ast = LRResult lrstate c t ast Source #

GLR results are just LRResults

data LRResult lrstate c t ast Source #

The different kinds of results an LR parser can return.

Constructors

ErrorNoAction t (Config lrstate c) [ast]

Parser got stuck (no action performable).

ErrorAccept (Config lrstate c) [ast]

Parser accepted but still has asts to consume.

ResultSet (Set (LRResult lrstate c t ast))

The grammar / parse was ambiguously accepted.

ResultAccept ast

Parse accepted and produced a single ast.

ErrorTable (Config lrstate c) [ast]

The goto table was missing an entry.

Instances
(Eq t, Eq lrstate, Eq c, Eq ast) => Eq (LRResult lrstate c t ast) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

(==) :: LRResult lrstate c t ast -> LRResult lrstate c t ast -> Bool #

(/=) :: LRResult lrstate c t ast -> LRResult lrstate c t ast -> Bool #

(Ord t, Ord lrstate, Ord c, Ord ast) => Ord (LRResult lrstate c t ast) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

compare :: LRResult lrstate c t ast -> LRResult lrstate c t ast -> Ordering #

(<) :: LRResult lrstate c t ast -> LRResult lrstate c t ast -> Bool #

(<=) :: LRResult lrstate c t ast -> LRResult lrstate c t ast -> Bool #

(>) :: LRResult lrstate c t ast -> LRResult lrstate c t ast -> Bool #

(>=) :: LRResult lrstate c t ast -> LRResult lrstate c t ast -> Bool #

max :: LRResult lrstate c t ast -> LRResult lrstate c t ast -> LRResult lrstate c t ast #

min :: LRResult lrstate c t ast -> LRResult lrstate c t ast -> LRResult lrstate c t ast #

(Show t, Show lrstate, Show c, Show ast) => Show (LRResult lrstate c t ast) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

showsPrec :: Int -> LRResult lrstate c t ast -> ShowS #

show :: LRResult lrstate c t ast -> String #

showList :: [LRResult lrstate c t ast] -> ShowS #

Generic (LRResult lrstate c t ast) Source # 
Instance details

Defined in Text.ANTLR.LR

Associated Types

type Rep (LRResult lrstate c t ast) :: Type -> Type #

Methods

from :: LRResult lrstate c t ast -> Rep (LRResult lrstate c t ast) x #

to :: Rep (LRResult lrstate c t ast) x -> LRResult lrstate c t ast #

(Hashable t, Hashable lrstate, Hashable c, Hashable ast) => Hashable (LRResult lrstate c t ast) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

hashWithSalt :: Int -> LRResult lrstate c t ast -> Int #

hash :: LRResult lrstate c t ast -> Int #

(Prettify c, Prettify t, Prettify ast, Prettify lrstate, Eq c, Eq t, Eq ast, Eq lrstate, Hashable c, Hashable ast, Hashable t, Hashable lrstate) => Prettify (LRResult lrstate c t ast) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

prettify :: LRResult lrstate c t ast -> Pretty Source #

prettifyList :: [LRResult lrstate c t ast] -> Pretty Source #

type Rep (LRResult lrstate c t ast) Source # 
Instance details

Defined in Text.ANTLR.LR

type LR1Result lrstate t ast = LRResult lrstate t t ast Source #

LR1 results are just LRResults with identical tokens and characters

glrParse :: (HasEOF (Sym t), Ref t, Prettify nts, Prettify (Sym t), Prettify (StripEOF (Sym t)), Prettify t, Ord nts, Ord (Sym t), Ord (StripEOF (Sym t)), Ord t, Ord ast, Hashable nts, Hashable (Sym t), Hashable (StripEOF (Sym t)), Hashable t, Hashable ast) => Grammar () nts (StripEOF (Sym t)) dt -> Action ast nts t -> [t] -> LRResult (CoreLR1State nts (StripEOF (Sym t))) t t ast Source #

Entrypoint for GLR parsing algorithm.

glrParseInc :: (HasEOF (Sym t), Ref t, Ord nts, Ord (Sym t), Ord (StripEOF (Sym t)), Ord t, Ord ast, Ord c, Hashable nts, Hashable (Sym t), Hashable (StripEOF (Sym t)), Hashable t, Hashable ast, Hashable c, Prettify nts, Prettify (Sym t), Prettify (StripEOF (Sym t)), Prettify t, Prettify c) => Grammar () nts (StripEOF (Sym t)) dt -> Action ast nts t -> (Set (StripEOF (Sym t)) -> [c] -> (t, [c])) -> [c] -> GLRResult (CoreLR1State nts (StripEOF (Sym t))) c t ast Source #

Entrypoint for an incremental GLR parser.

isAccept :: LRResult lrstate c t ast -> Bool Source #

Is the LRResult an accept?

isError :: LRResult lrstate c t ast -> Bool Source #

Is this LRResult an error?

lr1S0 :: (Tabular sts, Tabular nts) => Grammar () nts sts dt -> CoreLRState (LR1LookAhead sts) nts sts Source #

LR(1) start state of a grammar.

glrParseInc' :: forall nts t dt ast lrstate c. (CanParse nts t, IsState lrstate, IsAST ast, Tabular c) => Grammar () nts (StripEOF (Sym t)) dt -> LRTable nts (StripEOF (Sym t)) lrstate -> Goto nts (StripEOF (Sym t)) lrstate -> lrstate -> Map lrstate (Set (StripEOF (Sym t))) -> Action ast nts t -> Tokenizer t c -> [c] -> GLRResult lrstate c t ast Source #

glrParseInc2 :: (HasEOF (Sym t), Ref t, Ord (Sym t), Ord t, Ord ast, Ord c, Hashable (Sym t), Hashable t, Hashable ast, Hashable c, Prettify (Sym t), Prettify t, Prettify c, Ord nts, Ord (StripEOF (Sym t)), Hashable nts, Hashable (StripEOF (Sym t)), Prettify (StripEOF (Sym t)), Prettify nts) => Grammar () nts (StripEOF (Sym t)) dt -> Action ast nts t -> (Set (StripEOF (Sym t)) -> [c] -> (t, [c])) -> [c] -> GLRResult Int c t ast Source #

Incremental GLR parser with parse states compressed into integers.

convGoto :: (IsState lrstate, Ord sts, Ord nts) => Grammar () nts sts dt -> Goto' nts sts lrstate -> [lrstate] -> Goto nts sts lrstate Source #

Convert a function-based goto to a map-based one once we know the set of all lrstates (sets of items for LR1) and all the production elements

convStateInt :: forall lrstate. IsState lrstate => [lrstate] -> lrstate -> Int Source #

Create a function that, given the list of all possible lrstate elements, converts an lrstate into a unique integer.

convGotoStatesInt :: forall lrstate nts sts. (IsState lrstate, Tabular sts, Tabular nts) => Goto nts sts lrstate -> [lrstate] -> Goto nts sts Int Source #

Convert the states in a goto to integers.

convTableInt :: forall lrstate nts sts. (IsState lrstate, Tabular nts, Tabular sts) => LRTable nts sts lrstate -> [lrstate] -> LRTable nts sts Int Source #

Convert the states in a LRTable into integers.

tokenizerFirstSets :: (Ord k, Ord nts, Ord a, Hashable nts, Hashable a, Prettify nts, Prettify a) => (CoreLR1State nts a -> k) -> Grammar () nts a dt -> Map k (HashSet a) Source #

Mapping from parse states to which symbols can be seen next so that the incremental tokenizer can check which DFAs to try tokenizing.

disambiguate :: (IsState lrstate, Tabular nts, Tabular sts, Data lrstate, Data nts, Data sts) => LRTable nts sts lrstate -> (LRTable' nts sts lrstate, Int) Source #

Returns the disambiguated LRTable, as well as the number of conflicts (ShiftReduce, ReduceReduce, etc...) reported.

type SLRClosure lrstate = Closure lrstate Source #

An SLRClosure is just a LR Closure in disguise.

type SLRItem nts sts = Item () nts sts Source #

SLR items have no lookahead.

type SLRTable nts sts lrstate = LRTable nts sts lrstate Source #

An SLRTable is just an LRTable in disguise.

type Closure lrstate = lrstate -> lrstate Source #

Functions for computing the state (set of items) we can go to next without consuming any input.

type LR1Item nts sts = Item (LR1LookAhead sts) nts sts Source #

An LR1 item is an Item with one lookahead symbol.

type Goto nts sts lrstate = Map (lrstate, ProdElem nts sts) lrstate Source #

An LR goto implemented as one-to-one mapping.

type Goto' nts sts lrstate = lrstate -> ProdElem nts sts -> lrstate Source #

Function form of a Goto

type Config lrstate t = ([lrstate], [t]) Source #

An LR configurate telling you the current stack of states [lrstate], and the rest of the input tokens [t].

type Tokenizer t c = Set (StripEOF (Sym t)) -> [c] -> (t, [c]) Source #

A tokenizer is a function that, given a set of DFA names to try tokenizing, returns a parsed token t and the remaining untokenized input [c].