Copyright | (c) Karl Cronburg 2018 |
---|---|
License | BSD3 |
Maintainer | karl@cs.tufts.edu |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- type CanParse nts t = (Tabular nts, Tabular (Sym t), Tabular (StripEOF (Sym t)), HasEOF (Sym t), Ref t, Tabular t)
- type CanParse' nts sts = (Tabular nts, Tabular sts)
- type IsAST ast = (Ord ast, Eq ast, Hashable ast)
- type IsState st = (Ord st, Hashable st, Prettify st)
- type Tabular sym = (Ord sym, Hashable sym, Prettify sym, Eq sym)
- data ParseEvent ast nts t
- type Action ast nts t = ParseEvent ast nts t -> ast
- data Icon ts
- token2symbol :: Token n v -> TokenSymbol n
- data TokenSymbol n
- = TokenSymbol n
- | EOFSymbol
- class HasEOF t where
- isIcon :: Icon ts -> Bool
- isIconEps :: Icon ts -> Bool
- isIconEOF :: Icon ts -> Bool
- data AST nts t
- event2ast :: ParseEvent (AST nts t) nts t -> AST nts t
Documentation
type CanParse nts t = (Tabular nts, Tabular (Sym t), Tabular (StripEOF (Sym t)), HasEOF (Sym t), Ref t, Tabular t) Source #
Nonterminals in a grammar are tabular, terminal symbols are tabular (as are the EOF-stripped version), terminals are referenceable (can be symbolized), and terminals are also tabular.
type CanParse' nts sts = (Tabular nts, Tabular sts) Source #
Same as CanParse
but with second formal parameter representing (StripEOF (Sym t))
aka "sts" (stripped terminal symbol).
data ParseEvent ast nts t Source #
Action functions triggered during parsing are given the nonterminal we just matched on, the corresponding list of production elements (grammar symbols) in the RHS of the matched production alternative, and the result of recursively.
A ParseEvent
may also be just a terminal matched on, or an epsilon event
based heavily on which parsing algorithm is being run.
This data type is one of the data types that tie together terminal (token) types and terminal symbol types. When the parser produces a terminal event, you're seeing a token, but when the parser produces a nonterminal event, you're seeing a production in the grammar firing which contains terminal symbols, not tokens.
TermE t | A terminal was seen in the input |
NonTE (nts, ProdElems nts (StripEOF (Sym t)), [ast]) | A non-terminal was seen in the input |
EpsE | Epsilon event |
Instances
(Show ast, Show nts, Show (StripEOF (Sym t)), Show t) => Show (ParseEvent ast nts t) Source # | |
Defined in Text.ANTLR.Parser showsPrec :: Int -> ParseEvent ast nts t -> ShowS # show :: ParseEvent ast nts t -> String # showList :: [ParseEvent ast nts t] -> ShowS # | |
(Prettify ast, Prettify nts, Prettify (StripEOF (Sym t)), Prettify t) => Prettify (ParseEvent ast nts t) Source # | |
Defined in Text.ANTLR.Parser prettify :: ParseEvent ast nts t -> Pretty Source # prettifyList :: [ParseEvent ast nts t] -> Pretty Source # |
type Action ast nts t = ParseEvent ast nts t -> ast Source #
An Action as seen by the host language (Haskell) is a function from parse events to an abstract-syntax tree that the function constructs based on which non-terminal or terminal symbol was seen.
An Icon (as used in first and follow sets of the LL1 parser and the shift-reduce table of the LR1 parser) is just a terminal symbol taken from the grammar, or it's an epsilon or EOF.
Instances
Eq ts => Eq (Icon ts) Source # | |
Data ts => Data (Icon ts) Source # | |
Defined in Text.ANTLR.Parser gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Icon ts -> c (Icon ts) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Icon ts) # toConstr :: Icon ts -> Constr # dataTypeOf :: Icon ts -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Icon ts)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Icon ts)) # gmapT :: (forall b. Data b => b -> b) -> Icon ts -> Icon ts # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Icon ts -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Icon ts -> r # gmapQ :: (forall d. Data d => d -> u) -> Icon ts -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Icon ts -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Icon ts -> m (Icon ts) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Icon ts -> m (Icon ts) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Icon ts -> m (Icon ts) # | |
Ord ts => Ord (Icon ts) Source # | |
Show ts => Show (Icon ts) Source # | |
Generic (Icon ts) Source # | |
Lift ts => Lift (Icon ts) Source # | |
Hashable ts => Hashable (Icon ts) Source # | |
Defined in Text.ANTLR.Parser | |
Prettify ts => Prettify (Icon ts) Source # | |
type Rep (Icon ts) Source # | |
Defined in Text.ANTLR.Parser type Rep (Icon ts) = D1 (MetaData "Icon" "Text.ANTLR.Parser" "antlr-haskell-0.1.0.1-47wJxWjYxn91lXcjBVmKNu" False) (C1 (MetaCons "Icon" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ts)) :+: (C1 (MetaCons "IconEps" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IconEOF" PrefixI False) (U1 :: Type -> Type))) |
token2symbol :: Token n v -> TokenSymbol n Source #
This is the function defining the (n == Sym t == ts) relationship between the name type of a token, the symbol type of a terminal token (as constructed by the tokenizer), and the terminal symbol type as used by the parser. When a parser wants to compare the symbol of an input token to a terminal symbol found in the grammar, it should convert the token to an icon using this function and then compare icons using Eq because icons throw away the value of a token, leaving only the Eq-able piece that we care about.
data TokenSymbol n Source #
The symbol for some tokenize is either just it's name n
or the special EOF symbol.
TokenSymbol n | Named symbol |
EOFSymbol | End-of-file symbol |
Instances
A data type with an EOF constructor. There are two things you can do with a data type that has an EOF:
Ask for the type *without* the EOF at compile time Ask whether or not an instance is the EOF symbol at runtime
Whether or not the given value of type t is the EOF value
stripEOF :: t -> Maybe (StripEOF t) Source #
Take a token and try to unwrap its name (an EOF should result in Nothing)
Instances
HasEOF String Source # | |
HasEOF (TokenSymbol n) Source # | |
Defined in Text.ANTLR.Parser type StripEOF (TokenSymbol n) :: Type Source # isEOF :: TokenSymbol n -> Bool Source # stripEOF :: TokenSymbol n -> Maybe (StripEOF (TokenSymbol n)) Source # |
Universal Abstract Syntax Tree data type. All internal AST "nodes" have a
nonterminal, the grammar production symbols it reduced from, and the
resulting recursively defined AST nodes acquired from the parser. Leaf AST
nodes can be either an epsilon (when explicit epsilons are used in the
grammar) or more importantly a terminal symbol.
This is another type that defines the relationship between the terminal
token type t
and the terminal symbol type (ts == Sym t)
where the AST tells
you the production rule that fired containing ts
as well as the tokens t
contained in leaves of the AST.
LeafEps | Epsilon leaf AST node |
Leaf t | Terminal token leaf in the AST |
AST nts (ProdElems nts (StripEOF (Sym t))) [AST nts t] | Internal AST node |
Instances
event2ast :: ParseEvent (AST nts t) nts t -> AST nts t Source #
Default AST-constructor function which just copies over the contents of
some parse event into an AST
.