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

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

Text.ANTLR.Allstar.ParserGenerator

Description

 
Synopsis

Documentation

data GrammarSymbol nt t Source #

Grammar symbol types

Constructors

NT nt 
T t 
EPS 
Instances
(Eq nt, Eq t) => Eq (GrammarSymbol nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

Methods

(==) :: GrammarSymbol nt t -> GrammarSymbol nt t -> Bool #

(/=) :: GrammarSymbol nt t -> GrammarSymbol nt t -> Bool #

(Ord nt, Ord t) => Ord (GrammarSymbol nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

Methods

compare :: GrammarSymbol nt t -> GrammarSymbol nt t -> Ordering #

(<) :: GrammarSymbol nt t -> GrammarSymbol nt t -> Bool #

(<=) :: GrammarSymbol nt t -> GrammarSymbol nt t -> Bool #

(>) :: GrammarSymbol nt t -> GrammarSymbol nt t -> Bool #

(>=) :: GrammarSymbol nt t -> GrammarSymbol nt t -> Bool #

max :: GrammarSymbol nt t -> GrammarSymbol nt t -> GrammarSymbol nt t #

min :: GrammarSymbol nt t -> GrammarSymbol nt t -> GrammarSymbol nt t #

(Show nt, Show t) => Show (GrammarSymbol nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

Methods

showsPrec :: Int -> GrammarSymbol nt t -> ShowS #

show :: GrammarSymbol nt t -> String #

showList :: [GrammarSymbol nt t] -> ShowS #

(Prettify nt, Prettify t) => Prettify (GrammarSymbol nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

type ATNEnv nt t = Set (ATNEdge nt t) Source #

A set of ATN edges, defining the grammar over which the ALL(*) parsing algorithm operates.

data AST nt tok Source #

Input sequence type

Return type of parse function

Constructors

Node nt [GrammarSymbol nt (Label tok)] [AST nt tok] 
Leaf tok 
Instances
(Eq nt, Eq tok, Eq (Label tok)) => Eq (AST nt tok) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

Methods

(==) :: AST nt tok -> AST nt tok -> Bool #

(/=) :: AST nt tok -> AST nt tok -> Bool #

(Show nt, Show tok, Show (Label tok)) => Show (AST nt tok) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

Methods

showsPrec :: Int -> AST nt tok -> ShowS #

show :: AST nt tok -> String #

showList :: [AST nt tok] -> ShowS #

(Prettify nt, Prettify tok, Prettify (Label tok)) => Prettify (AST nt tok) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

Methods

prettify :: AST nt tok -> Pretty Source #

prettifyList :: [AST nt tok] -> Pretty Source #

data ATNState nt Source #

Specifies the nonterminal we're currently parsing as well as what state we are in for parsing some NT symbol.

Constructors

Init nt

Starting state

Middle nt Int Int

Intermediate state

Final nt

Accepting state

Instances
Eq nt => Eq (ATNState nt) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

Methods

(==) :: ATNState nt -> ATNState nt -> Bool #

(/=) :: ATNState nt -> ATNState nt -> Bool #

Ord nt => Ord (ATNState nt) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

Methods

compare :: ATNState nt -> ATNState nt -> Ordering #

(<) :: ATNState nt -> ATNState nt -> Bool #

(<=) :: ATNState nt -> ATNState nt -> Bool #

(>) :: ATNState nt -> ATNState nt -> Bool #

(>=) :: ATNState nt -> ATNState nt -> Bool #

max :: ATNState nt -> ATNState nt -> ATNState nt #

min :: ATNState nt -> ATNState nt -> ATNState nt #

Show nt => Show (ATNState nt) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

Methods

showsPrec :: Int -> ATNState nt -> ShowS #

show :: ATNState nt -> String #

showList :: [ATNState nt] -> ShowS #

Prettify nt => Prettify (ATNState nt) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

type ATNEdge nt t = (ATNState nt, ATNEdgeLabel nt t, ATNState nt) Source #

Starting state, NT/T symbol to parse, and ending state.

data ATNEdgeLabel nt t Source #

The domain of labels on edges in an augmented recursive transition network, namely the symbol we parse upon traversing an edge.

Constructors

GS (GrammarSymbol nt t)

The symbol to parse upon traversing an edge

PRED Bool

Unimplemented predicates in ALL(*)

Instances
(Eq nt, Eq t) => Eq (ATNEdgeLabel nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

Methods

(==) :: ATNEdgeLabel nt t -> ATNEdgeLabel nt t -> Bool #

(/=) :: ATNEdgeLabel nt t -> ATNEdgeLabel nt t -> Bool #

(Ord nt, Ord t) => Ord (ATNEdgeLabel nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

Methods

compare :: ATNEdgeLabel nt t -> ATNEdgeLabel nt t -> Ordering #

(<) :: ATNEdgeLabel nt t -> ATNEdgeLabel nt t -> Bool #

(<=) :: ATNEdgeLabel nt t -> ATNEdgeLabel nt t -> Bool #

(>) :: ATNEdgeLabel nt t -> ATNEdgeLabel nt t -> Bool #

(>=) :: ATNEdgeLabel nt t -> ATNEdgeLabel nt t -> Bool #

max :: ATNEdgeLabel nt t -> ATNEdgeLabel nt t -> ATNEdgeLabel nt t #

min :: ATNEdgeLabel nt t -> ATNEdgeLabel nt t -> ATNEdgeLabel nt t #

(Show nt, Show t) => Show (ATNEdgeLabel nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

Methods

showsPrec :: Int -> ATNEdgeLabel nt t -> ShowS #

show :: ATNEdgeLabel nt t -> String #

showList :: [ATNEdgeLabel nt t] -> ShowS #

(Prettify nt, Prettify t) => Prettify (ATNEdgeLabel nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ParserGenerator

type Label tok = StripEOF (Sym tok) Source #

parse :: forall chr tok nt. (CanParse nt tok, Prettify chr) => Tokenizer chr tok -> [chr] -> GrammarSymbol nt (Label tok) -> ATNEnv nt (Label tok) -> Bool -> Either String (AST nt tok) Source #

ALL(*) parsing algorithm. This is not the entrypoint as used by user-facing code. See parse instead.

type Tokenizer chr tok = [chr] -> [(tok, [chr])] Source #