antlr-haskell-0.1.0.0: 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.Parser

Contents

Description

 
Synopsis

Documentation

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.

Constructors

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 # 
Instance details

Defined in Text.ANTLR.Parser

Methods

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 # 
Instance details

Defined in Text.ANTLR.Parser

Methods

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.

data Icon ts Source #

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.

Constructors

Icon ts

Terminal symbol icon

IconEps

Epsilon icon

IconEOF

EOF (end of file / input) icon

Instances
Eq ts => Eq (Icon ts) Source # 
Instance details

Defined in Text.ANTLR.Parser

Methods

(==) :: Icon ts -> Icon ts -> Bool #

(/=) :: Icon ts -> Icon ts -> Bool #

Data ts => Data (Icon ts) Source # 
Instance details

Defined in Text.ANTLR.Parser

Methods

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 # 
Instance details

Defined in Text.ANTLR.Parser

Methods

compare :: Icon ts -> Icon ts -> Ordering #

(<) :: Icon ts -> Icon ts -> Bool #

(<=) :: Icon ts -> Icon ts -> Bool #

(>) :: Icon ts -> Icon ts -> Bool #

(>=) :: Icon ts -> Icon ts -> Bool #

max :: Icon ts -> Icon ts -> Icon ts #

min :: Icon ts -> Icon ts -> Icon ts #

Show ts => Show (Icon ts) Source # 
Instance details

Defined in Text.ANTLR.Parser

Methods

showsPrec :: Int -> Icon ts -> ShowS #

show :: Icon ts -> String #

showList :: [Icon ts] -> ShowS #

Generic (Icon ts) Source # 
Instance details

Defined in Text.ANTLR.Parser

Associated Types

type Rep (Icon ts) :: Type -> Type #

Methods

from :: Icon ts -> Rep (Icon ts) x #

to :: Rep (Icon ts) x -> Icon ts #

Lift ts => Lift (Icon ts) Source # 
Instance details

Defined in Text.ANTLR.Parser

Methods

lift :: Icon ts -> Q Exp #

Hashable ts => Hashable (Icon ts) Source # 
Instance details

Defined in Text.ANTLR.Parser

Methods

hashWithSalt :: Int -> Icon ts -> Int #

hash :: Icon ts -> Int #

Prettify ts => Prettify (Icon ts) Source # 
Instance details

Defined in Text.ANTLR.Parser

type Rep (Icon ts) Source # 
Instance details

Defined in Text.ANTLR.Parser

type Rep (Icon ts) = D1 (MetaData "Icon" "Text.ANTLR.Parser" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" 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.

Constructors

TokenSymbol n

Named symbol

EOFSymbol

End-of-file symbol

Instances
Eq n => Eq (TokenSymbol n) Source # 
Instance details

Defined in Text.ANTLR.Parser

Ord n => Ord (TokenSymbol n) Source # 
Instance details

Defined in Text.ANTLR.Parser

Show n => Show (TokenSymbol n) Source # 
Instance details

Defined in Text.ANTLR.Parser

Generic (TokenSymbol n) Source # 
Instance details

Defined in Text.ANTLR.Parser

Associated Types

type Rep (TokenSymbol n) :: Type -> Type #

Methods

from :: TokenSymbol n -> Rep (TokenSymbol n) x #

to :: Rep (TokenSymbol n) x -> TokenSymbol n #

Hashable n => Hashable (TokenSymbol n) Source # 
Instance details

Defined in Text.ANTLR.Parser

Methods

hashWithSalt :: Int -> TokenSymbol n -> Int #

hash :: TokenSymbol n -> Int #

HasEOF (TokenSymbol n) Source # 
Instance details

Defined in Text.ANTLR.Parser

Associated Types

type StripEOF (TokenSymbol n) :: Type Source #

type Rep (TokenSymbol n) Source # 
Instance details

Defined in Text.ANTLR.Parser

type Rep (TokenSymbol n) = D1 (MetaData "TokenSymbol" "Text.ANTLR.Parser" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" False) (C1 (MetaCons "TokenSymbol" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 n)) :+: C1 (MetaCons "EOFSymbol" PrefixI False) (U1 :: Type -> Type))
type StripEOF (TokenSymbol n) Source # 
Instance details

Defined in Text.ANTLR.Parser

type StripEOF (TokenSymbol n) = n

class HasEOF t where Source #

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

Associated Types

type StripEOF t :: * Source #

The unwrapped type (without the EOF data constructor alternative)

Methods

isEOF :: t -> Bool Source #

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 # 
Instance details

Defined in Text.ANTLR.Parser

Associated Types

type StripEOF String :: Type Source #

HasEOF (TokenSymbol n) Source # 
Instance details

Defined in Text.ANTLR.Parser

Associated Types

type StripEOF (TokenSymbol n) :: Type Source #

isIcon :: Icon ts -> Bool Source #

Is this a terminal-symbol icon?

isIconEps :: Icon ts -> Bool Source #

Is this an epsilon icon?

isIconEOF :: Icon ts -> Bool Source #

Is this the EOF icon?

data AST nts t 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.

Constructors

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
(Eq (StripEOF (Sym t)), Eq nts, Eq t) => Eq (AST nts t) Source # 
Instance details

Defined in Text.ANTLR.Parser

Methods

(==) :: AST nts t -> AST nts t -> Bool #

(/=) :: AST nts t -> AST nts t -> Bool #

(Ord (StripEOF (Sym t)), Ord nts, Ord t) => Ord (AST nts t) Source # 
Instance details

Defined in Text.ANTLR.Parser

Methods

compare :: AST nts t -> AST nts t -> Ordering #

(<) :: AST nts t -> AST nts t -> Bool #

(<=) :: AST nts t -> AST nts t -> Bool #

(>) :: AST nts t -> AST nts t -> Bool #

(>=) :: AST nts t -> AST nts t -> Bool #

max :: AST nts t -> AST nts t -> AST nts t #

min :: AST nts t -> AST nts t -> AST nts t #

(Show (StripEOF (Sym t)), Show nts, Show t) => Show (AST nts t) Source # 
Instance details

Defined in Text.ANTLR.Parser

Methods

showsPrec :: Int -> AST nts t -> ShowS #

show :: AST nts t -> String #

showList :: [AST nts t] -> ShowS #

Generic (AST nts t) Source # 
Instance details

Defined in Text.ANTLR.Parser

Associated Types

type Rep (AST nts t) :: Type -> Type #

Methods

from :: AST nts t -> Rep (AST nts t) x #

to :: Rep (AST nts t) x -> AST nts t #

(Hashable (StripEOF (Sym t)), Hashable nts, Hashable t) => Hashable (AST nts t) Source # 
Instance details

Defined in Text.ANTLR.Parser

Methods

hashWithSalt :: Int -> AST nts t -> Int #

hash :: AST nts t -> Int #

(Prettify nts, Prettify t) => Prettify (AST nts t) Source # 
Instance details

Defined in Text.ANTLR.Parser

Methods

prettify :: AST nts t -> Pretty Source #

prettifyList :: [AST nts t] -> Pretty Source #

type Rep (AST nts t) Source # 
Instance details

Defined in Text.ANTLR.Parser

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.

Orphan instances

Ref (Token n v) Source #

Tokens are symbolized by an icon containing their name.

Instance details

Associated Types

type Sym (Token n v) :: Type Source #

Methods

getSymbol :: Token n v -> Sym (Token n v) Source #