Copyright | (c) Karl Cronburg 2018 |
---|---|
License | BSD3 |
Maintainer | karl@cs.tufts.edu |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Item a nts sts = Item (ItemLHS nts) (ProdElems nts sts) (ProdElems nts sts) a
- data ItemLHS nts
- kernel :: (Ord a, Ord sts, Ord nts, Hashable a, Hashable sts, Hashable nts) => Set (Item a nts sts) -> Set (Item a nts sts)
- items :: forall a nts sts. (Ord a, Ord nts, Ord sts, Eq nts, Eq sts, Hashable a, Hashable sts, Hashable nts) => Grammar () nts sts -> Goto' nts sts (CoreLRState a nts sts) -> CoreLRState a nts sts -> Set (CoreLRState a nts sts)
- slrClosure :: forall nts sts. (Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> SLRClosure (CoreSLRState nts sts)
- slrGoto :: forall nts sts. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> Goto' nts sts (CoreSLRState nts sts)
- slrItems :: forall nts sts. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> Set (Set (SLRItem nts sts))
- allSLRItems :: forall nts sts. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> Set (SLRItem nts sts)
- slrTable :: forall nts sts. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable nts, Hashable sts) => Grammar () nts sts -> SLRTable nts sts (CoreSLRState nts sts)
- slrParse :: (Eq (Sym nts), Eq (Sym t), Eq (StripEOF (Sym t)), Ref t, HasEOF (Sym t), Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Hashable nts, Hashable (Sym t), Hashable t, Hashable (StripEOF (Sym t)), Prettify t, Prettify nts, Prettify (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) -> Action ast nts t -> [t] -> LRResult (CoreSLRState nts (StripEOF (Sym t))) t ast
- slrRecognize :: (Eq (Sym nts), Eq (Sym t), Eq (StripEOF (Sym t)), Ref t, HasEOF (Sym t), Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Hashable nts, Hashable (Sym t), Hashable t, Hashable (StripEOF (Sym t)), Prettify t, Prettify nts, Prettify (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) -> [t] -> Bool
- lr1Closure :: forall nts sts. (Eq nts, Eq sts, Ord nts, Ord sts, Ord sts, Hashable sts, Hashable sts, Hashable nts) => Grammar () nts sts -> Closure (CoreLR1State nts sts)
- lr1Goto :: (Eq nts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> Goto' nts sts (CoreLR1State nts sts)
- lr1Items :: (Eq sts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> Set (CoreLRState (LR1LookAhead sts) nts sts)
- lr1Table :: forall nts sts. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> LRTable nts sts (CoreLR1State nts sts)
- lr1Parse :: (Eq (Sym nts), Eq (Sym t), Eq (StripEOF (Sym t)), Ref t, HasEOF (Sym t), Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Hashable nts, Hashable (Sym t), Hashable t, Hashable (StripEOF (Sym t)), Prettify t, Prettify nts, Prettify (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) -> Action ast nts t -> [t] -> LRResult (CoreLR1State nts (StripEOF (Sym t))) t ast
- lr1Recognize :: (Eq (Sym nts), Eq (Sym t), Eq (StripEOF (Sym t)), Ref t, HasEOF (Sym t), Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Hashable nts, Hashable (Sym t), Hashable t, Hashable (StripEOF (Sym t)), Prettify t, Prettify nts, Prettify (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) -> [t] -> Bool
- type LR1LookAhead sts = Icon sts
- type CoreLRState a nts sts = Set (Item a nts sts)
- type CoreLR1State nts sts = Set (LR1Item nts sts)
- type CoreSLRState nts sts = Set (Item () nts sts)
- type LRTable nts sts lrstate = Map (lrstate, Icon sts) (LRAction nts sts lrstate)
- type LRTable' nts sts lrstate = Map (lrstate, Icon sts) (LRAction nts sts lrstate)
- data LRAction nts sts lrstate
- = Shift lrstate
- | Reduce (Production () nts sts)
- | Accept
- | Error
- lrParse :: forall ast a nts t lrstate. (Ord lrstate, Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Eq nts, Eq (Sym t), Eq (StripEOF (Sym t)), Ref t, HasEOF (Sym t), Hashable (Sym t), Hashable t, Hashable lrstate, Hashable nts, Hashable (StripEOF (Sym t)), Prettify lrstate, Prettify t, Prettify nts, Prettify (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) -> LRTable nts (StripEOF (Sym t)) lrstate -> Goto nts (StripEOF (Sym t)) lrstate -> lrstate -> Action ast nts t -> [t] -> LRResult lrstate t ast
- data LRResult lrstate t ast
- = ErrorNoAction (Config lrstate t) [ast]
- | ErrorAccept (Config lrstate t) [ast]
- | ResultSet (Set (LRResult lrstate t ast))
- | ResultAccept ast
- | ErrorTable (Config lrstate t) [ast]
- type LR1Result lrstate t ast = LRResult lrstate t ast
- glrParse :: (Ord nts, Ord (StripEOF (Sym t)), Ord (Sym t), Ord t, Ord ast, Ref t, HasEOF (Sym t), Hashable (Sym t), Hashable t, Hashable nts, Hashable (StripEOF (Sym t)), Hashable ast, Prettify (StripEOF (Sym t)), Prettify nts, Prettify t) => Grammar () nts (StripEOF (Sym t)) -> Action ast nts t -> [t] -> LRResult (CoreLR1State nts (StripEOF (Sym t))) t ast
- glrParseInc :: (Ref t, HasEOF (Sym t), Prettify t, Prettify nts, Prettify (StripEOF (Sym t)), Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Ord ast, Ord c, Hashable (Sym t), Hashable t, Hashable nts, Hashable (StripEOF (Sym t)), Hashable ast, Hashable c) => Grammar () nts (StripEOF (Sym t)) -> Action ast nts t -> (Set (StripEOF (Sym t)) -> [c] -> (t, [c])) -> [c] -> LR1Result (CoreLR1State nts (StripEOF (Sym t))) c ast
- isAccept :: LRResult lrstate t ast -> Bool
- isError :: LRResult lrstate t ast -> Bool
- lr1S0 :: (Eq sts, Ord sts, Ord nts, Hashable sts, Hashable nts) => Grammar () nts sts -> CoreLRState (LR1LookAhead sts) nts sts
- glrParseInc' :: forall ast nts t c lrstate. (Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Ord ast, Ord lrstate, Eq nts, Eq (Sym t), Eq (StripEOF (Sym t)), Eq ast, Ref t, HasEOF (Sym t), Hashable (Sym t), Hashable t, Hashable nts, Hashable (StripEOF (Sym t)), Hashable ast, Hashable lrstate, Prettify t, Prettify nts, Prettify (StripEOF (Sym t)), Prettify lrstate, Eq c, Ord c, Hashable c) => Grammar () nts (StripEOF (Sym t)) -> 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] -> LR1Result lrstate c ast
- glrParseInc2 :: (Ref t, HasEOF (Sym t), Prettify t, Prettify nts, Prettify (StripEOF (Sym t)), Ord (Sym t), Ord t, Ord ast, Ord c, Hashable (Sym t), Hashable t, Hashable ast, Hashable c, Hashable (StripEOF (Sym t)), Hashable nts, Ord nts, Ord (StripEOF (Sym t)), Show nts, Show (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) -> Action ast nts t -> (Set (StripEOF (Sym t)) -> [c] -> (t, [c])) -> [c] -> LR1Result Int c ast
- convGoto :: (Hashable lrstate, Ord lrstate, Ord sts, Ord nts) => Grammar () nts sts -> Goto' nts sts lrstate -> [lrstate] -> Goto nts sts lrstate
- convStateInt :: forall lrstate. (Ord lrstate, Show lrstate) => [lrstate] -> lrstate -> Int
- convGotoStatesInt :: forall lrstate nts sts. (Ord lrstate, Ord sts, Ord nts, Hashable nts, Hashable sts, Hashable lrstate, Eq nts, Show lrstate) => Goto nts sts lrstate -> [lrstate] -> Goto nts sts Int
- convTableInt :: forall lrstate nts sts. (Ord lrstate, Ord sts, Hashable nts, Hashable sts, Hashable lrstate, Eq nts, Show lrstate) => LRTable nts sts lrstate -> [lrstate] -> LRTable nts sts Int
- tokenizerFirstSets :: (Ord k, Ord nts, Ord a, Hashable a, Hashable nts) => (CoreLR1State nts a -> k) -> Grammar () nts a -> Map k (HashSet a)
- disambiguate :: (Prettify lrstate, Prettify nts, Prettify sts, Ord lrstate, Ord nts, Ord sts, Hashable lrstate, Hashable nts, Hashable sts, Data lrstate, Data nts, Data sts, Show lrstate, Show nts, Show sts) => LRTable nts sts lrstate -> (LRTable' nts sts lrstate, Int)
- type SLRClosure lrstate = Closure lrstate
- type SLRItem nts sts = Item () nts sts
- type SLRTable nts sts lrstate = LRTable nts sts lrstate
- type Closure lrstate = lrstate -> lrstate
- type LR1Item nts sts = Item (LR1LookAhead sts) nts sts
- type Goto nts sts lrstate = Map (lrstate, ProdElem nts sts) lrstate
- type Goto' nts sts lrstate = lrstate -> ProdElem nts sts -> lrstate
- type Config lrstate t = ([lrstate], [t])
- type Tokenizer t c = Set (StripEOF (Sym t)) -> [c] -> (t, [c])
Documentation
An Item is a production with a dot in it indicating how far into the production we have parsed:
A -> α . β
Instances
(Eq nts, Eq sts, Eq a) => Eq (Item a nts sts) Source # | |
(Data a, Data nts, Data sts) => Data (Item a nts sts) Source # | |
Defined in Text.ANTLR.LR 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 # | |
Defined in Text.ANTLR.LR 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 # | |
(Show nts, Show sts, Show a) => Show (Item a nts sts) Source # | |
Generic (Item a nts sts) Source # | |
(Lift nts, Lift sts, Lift a) => Lift (Item a nts sts) Source # | |
(Hashable nts, Hashable sts, Hashable a) => Hashable (Item a nts sts) Source # | |
Defined in Text.ANTLR.LR | |
(Prettify a, Prettify nts, Prettify sts) => Prettify (Item a nts sts) Source # | |
type Rep (Item a nts sts) Source # | |
Defined in Text.ANTLR.LR type Rep (Item a nts sts) = D1 (MetaData "Item" "Text.ANTLR.LR" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" False) (C1 (MetaCons "Item" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ItemLHS nts)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ProdElems nts sts))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ProdElems nts sts)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))) |
The nonterminal symbol for which an item refers to.
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 # | |
Data nts => Data (ItemLHS nts) Source # | |
Defined in Text.ANTLR.LR 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 # | |
Defined in Text.ANTLR.LR | |
Show nts => Show (ItemLHS nts) Source # | |
Generic (ItemLHS nts) Source # | |
Lift nts => Lift (ItemLHS nts) Source # | |
Hashable nts => Hashable (ItemLHS nts) Source # | |
Defined in Text.ANTLR.LR | |
Prettify nts => Prettify (ItemLHS nts) Source # | |
type Rep (ItemLHS nts) Source # | |
Defined in Text.ANTLR.LR type Rep (ItemLHS nts) = D1 (MetaData "ItemLHS" "Text.ANTLR.LR" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" 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 :: (Ord a, Ord sts, Ord nts, Hashable a, Hashable sts, Hashable nts) => 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 a nts sts. (Ord a, Ord nts, Ord sts, Eq nts, Eq sts, Hashable a, Hashable sts, Hashable nts) => Grammar () nts sts -> 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. (Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> SLRClosure (CoreSLRState nts sts) Source #
Algorithm for computing an SLR closure.
slrGoto :: forall nts sts. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> Goto' nts sts (CoreSLRState nts sts) Source #
Goto with an SLR closure, slrClosure
.
slrItems :: forall nts sts. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> Set (Set (SLRItem nts sts)) Source #
Compute SLR table with appropriate slrGoto
and slrClosure
.
allSLRItems :: forall nts sts. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> Set (SLRItem nts sts) Source #
Generate the set of all possible Items for a given grammar:
slrTable :: forall nts sts. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable nts, Hashable sts) => Grammar () nts sts -> SLRTable nts sts (CoreSLRState nts sts) Source #
Algorithm for computing the SLR table.
slrParse :: (Eq (Sym nts), Eq (Sym t), Eq (StripEOF (Sym t)), Ref t, HasEOF (Sym t), Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Hashable nts, Hashable (Sym t), Hashable t, Hashable (StripEOF (Sym t)), Prettify t, Prettify nts, Prettify (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) -> Action ast nts t -> [t] -> LRResult (CoreSLRState nts (StripEOF (Sym t))) t ast Source #
Entrypoint for SLR parsing.
slrRecognize :: (Eq (Sym nts), Eq (Sym t), Eq (StripEOF (Sym t)), Ref t, HasEOF (Sym t), Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Hashable nts, Hashable (Sym t), Hashable t, Hashable (StripEOF (Sym t)), Prettify t, Prettify nts, Prettify (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) -> [t] -> Bool Source #
SLR language recognizer.
lr1Closure :: forall nts sts. (Eq nts, Eq sts, Ord nts, Ord sts, Ord sts, Hashable sts, Hashable sts, Hashable nts) => Grammar () nts sts -> Closure (CoreLR1State nts sts) Source #
Algorithm for computing an LR(1) closure.
lr1Goto :: (Eq nts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> Goto' nts sts (CoreLR1State nts sts) Source #
LR(1) goto table (function) of a grammar.
lr1Items :: (Eq sts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> Set (CoreLRState (LR1LookAhead sts) nts sts) Source #
Items computed for LR(1) with an lr1Goto
and an lr1Closure
.
lr1Table :: forall nts sts. (Eq nts, Eq sts, Ord nts, Ord sts, Hashable sts, Hashable nts) => Grammar () nts sts -> LRTable nts sts (CoreLR1State nts sts) Source #
Algorithm for computing the LR(1) table.
lr1Parse :: (Eq (Sym nts), Eq (Sym t), Eq (StripEOF (Sym t)), Ref t, HasEOF (Sym t), Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Hashable nts, Hashable (Sym t), Hashable t, Hashable (StripEOF (Sym t)), Prettify t, Prettify nts, Prettify (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) -> Action ast nts t -> [t] -> LRResult (CoreLR1State nts (StripEOF (Sym t))) t ast Source #
Entrypoint for LR(1) parser.
lr1Recognize :: (Eq (Sym nts), Eq (Sym t), Eq (StripEOF (Sym t)), Ref t, HasEOF (Sym t), Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Hashable nts, Hashable (Sym t), Hashable t, Hashable (StripEOF (Sym t)), Prettify t, Prettify nts, Prettify (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) -> [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.
Shift lrstate | Shift |
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 # | |
(Data nts, Data sts, Data lrstate) => Data (LRAction nts sts lrstate) Source # | |
Defined in Text.ANTLR.LR 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 # | |
Defined in Text.ANTLR.LR 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 # | |
Generic (LRAction nts sts lrstate) Source # | |
(Lift lrstate, Lift nts, Lift sts) => Lift (LRAction nts sts lrstate) Source # | |
(Hashable lrstate, Hashable nts, Hashable sts) => Hashable (LRAction nts sts lrstate) Source # | |
Defined in Text.ANTLR.LR | |
(Prettify lrstate, Prettify nts, Prettify sts, Hashable lrstate, Hashable sts, Hashable nts, Eq lrstate, Eq sts, Eq nts) => Prettify (LRAction nts sts lrstate) Source # | |
type Rep (LRAction nts sts lrstate) Source # | |
Defined in Text.ANTLR.LR type Rep (LRAction nts sts lrstate) = D1 (MetaData "LRAction" "Text.ANTLR.LR" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" 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 ast a nts t lrstate. (Ord lrstate, Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Eq nts, Eq (Sym t), Eq (StripEOF (Sym t)), Ref t, HasEOF (Sym t), Hashable (Sym t), Hashable t, Hashable lrstate, Hashable nts, Hashable (StripEOF (Sym t)), Prettify lrstate, Prettify t, Prettify nts, Prettify (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) -> LRTable nts (StripEOF (Sym t)) lrstate -> Goto nts (StripEOF (Sym t)) lrstate -> lrstate -> Action ast nts t -> [t] -> LRResult lrstate t ast Source #
The core LR parsing algorithm, parametrized for different variants (SLR, LR(1), ...).
data LRResult lrstate t ast Source #
The different kinds of results an LR parser can return.
ErrorNoAction (Config lrstate t) [ast] | Parser got stuck (no action performable). |
ErrorAccept (Config lrstate t) [ast] | Parser accepted but still has |
ResultSet (Set (LRResult lrstate t ast)) | The grammar / parse was ambiguously accepted. |
ResultAccept ast | Parse accepted and produced a single |
ErrorTable (Config lrstate t) [ast] | The goto table was missing an entry. |
Instances
glrParse :: (Ord nts, Ord (StripEOF (Sym t)), Ord (Sym t), Ord t, Ord ast, Ref t, HasEOF (Sym t), Hashable (Sym t), Hashable t, Hashable nts, Hashable (StripEOF (Sym t)), Hashable ast, Prettify (StripEOF (Sym t)), Prettify nts, Prettify t) => Grammar () nts (StripEOF (Sym t)) -> Action ast nts t -> [t] -> LRResult (CoreLR1State nts (StripEOF (Sym t))) t ast Source #
Entrypoint for GLR parsing algorithm.
glrParseInc :: (Ref t, HasEOF (Sym t), Prettify t, Prettify nts, Prettify (StripEOF (Sym t)), Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Ord ast, Ord c, Hashable (Sym t), Hashable t, Hashable nts, Hashable (StripEOF (Sym t)), Hashable ast, Hashable c) => Grammar () nts (StripEOF (Sym t)) -> Action ast nts t -> (Set (StripEOF (Sym t)) -> [c] -> (t, [c])) -> [c] -> LR1Result (CoreLR1State nts (StripEOF (Sym t))) c ast Source #
Entrypoint for an incremental GLR parser.
lr1S0 :: (Eq sts, Ord sts, Ord nts, Hashable sts, Hashable nts) => Grammar () nts sts -> CoreLRState (LR1LookAhead sts) nts sts Source #
LR(1) start state of a grammar.
glrParseInc' :: forall ast nts t c lrstate. (Ord nts, Ord (Sym t), Ord t, Ord (StripEOF (Sym t)), Ord ast, Ord lrstate, Eq nts, Eq (Sym t), Eq (StripEOF (Sym t)), Eq ast, Ref t, HasEOF (Sym t), Hashable (Sym t), Hashable t, Hashable nts, Hashable (StripEOF (Sym t)), Hashable ast, Hashable lrstate, Prettify t, Prettify nts, Prettify (StripEOF (Sym t)), Prettify lrstate, Eq c, Ord c, Hashable c) => Grammar () nts (StripEOF (Sym t)) -> 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] -> LR1Result lrstate c ast Source #
Internal algorithm for incremental GLR parser.
glrParseInc2 :: (Ref t, HasEOF (Sym t), Prettify t, Prettify nts, Prettify (StripEOF (Sym t)), Ord (Sym t), Ord t, Ord ast, Ord c, Hashable (Sym t), Hashable t, Hashable ast, Hashable c, Hashable (StripEOF (Sym t)), Hashable nts, Ord nts, Ord (StripEOF (Sym t)), Show nts, Show (StripEOF (Sym t))) => Grammar () nts (StripEOF (Sym t)) -> Action ast nts t -> (Set (StripEOF (Sym t)) -> [c] -> (t, [c])) -> [c] -> LR1Result Int c ast Source #
Incremental GLR parser with parse states compressed into integers.
convGoto :: (Hashable lrstate, Ord lrstate, Ord sts, Ord nts) => Grammar () nts sts -> 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. (Ord lrstate, Show 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. (Ord lrstate, Ord sts, Ord nts, Hashable nts, Hashable sts, Hashable lrstate, Eq nts, Show lrstate) => Goto nts sts lrstate -> [lrstate] -> Goto nts sts Int Source #
Convert the states in a goto to integers.
convTableInt :: forall lrstate nts sts. (Ord lrstate, Ord sts, Hashable nts, Hashable sts, Hashable lrstate, Eq nts, Show lrstate) => 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 a, Hashable nts) => (CoreLR1State nts a -> k) -> Grammar () nts a -> 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 :: (Prettify lrstate, Prettify nts, Prettify sts, Ord lrstate, Ord nts, Ord sts, Hashable lrstate, Hashable nts, Hashable sts, Data lrstate, Data nts, Data sts, Show lrstate, Show nts, Show 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 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.