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.Allstar.ATN

Description

 
Synopsis

Documentation

type Gamma nt = Stacks (ATNState nt) Source #

Graph-structured stack over ATN states.

data ATN s nt t Source #

An ATN defining some language we wish to parse

Constructors

ATN 

Fields

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

Defined in Text.ANTLR.Allstar.ATN

Methods

(==) :: ATN s nt t -> ATN s nt t -> Bool #

(/=) :: ATN s nt t -> ATN s nt t -> Bool #

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

Defined in Text.ANTLR.Allstar.ATN

Methods

compare :: ATN s nt t -> ATN s nt t -> Ordering #

(<) :: ATN s nt t -> ATN s nt t -> Bool #

(<=) :: ATN s nt t -> ATN s nt t -> Bool #

(>) :: ATN s nt t -> ATN s nt t -> Bool #

(>=) :: ATN s nt t -> ATN s nt t -> Bool #

max :: ATN s nt t -> ATN s nt t -> ATN s nt t #

min :: ATN s nt t -> ATN s nt t -> ATN s nt t #

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

Defined in Text.ANTLR.Allstar.ATN

Methods

showsPrec :: Int -> ATN s nt t -> ShowS #

show :: ATN s nt t -> String #

showList :: [ATN s nt t] -> ShowS #

(Prettify s, Prettify nt, Prettify t, Hashable nt, Hashable t, Eq nt, Eq t) => Prettify (ATN s nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ATN

Methods

prettify :: ATN s nt t -> Pretty Source #

prettifyList :: [ATN s nt t] -> Pretty Source #

type Transition s nt t = (ATNState nt, Edge s nt t, ATNState nt) Source #

Tuple corresponding to a distinct transition in the ATN:

data ATNState nt Source #

The possible subscripts from Figure 8 of the ALL(*) paper

Constructors

Start nt 
Middle nt Int Int 
Accept nt 
Instances
Eq nt => Eq (ATNState nt) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ATN

Methods

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

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

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

Defined in Text.ANTLR.Allstar.ATN

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

Methods

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

show :: ATNState nt -> String #

showList :: [ATNState nt] -> ShowS #

Generic (ATNState nt) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ATN

Associated Types

type Rep (ATNState nt) :: Type -> Type #

Methods

from :: ATNState nt -> Rep (ATNState nt) x #

to :: Rep (ATNState nt) x -> ATNState nt #

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

Defined in Text.ANTLR.Allstar.ATN

Methods

hashWithSalt :: Int -> ATNState nt -> Int #

hash :: ATNState nt -> Int #

Prettify nt => Prettify (ATNState nt) Source #

LaTeX style ATN states. TODO: check length of NT printed and put curly braces around it if more than one character.

Instance details

Defined in Text.ANTLR.Allstar.ATN

type Rep (ATNState nt) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ATN

data Edge s nt t Source #

An edge in an ATN.

Constructors

NTE nt

Nonterminal edge

TE t

Terminal edge

PE (Predicate ())

Predicated edge with no state

ME (Mutator ())

Mutator edge with no state

Epsilon

Nondeterministic edge parsing nothing

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

Defined in Text.ANTLR.Allstar.ATN

Methods

(==) :: Edge s nt t -> Edge s nt t -> Bool #

(/=) :: Edge s nt t -> Edge s nt t -> Bool #

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

Defined in Text.ANTLR.Allstar.ATN

Methods

compare :: Edge s nt t -> Edge s nt t -> Ordering #

(<) :: Edge s nt t -> Edge s nt t -> Bool #

(<=) :: Edge s nt t -> Edge s nt t -> Bool #

(>) :: Edge s nt t -> Edge s nt t -> Bool #

(>=) :: Edge s nt t -> Edge s nt t -> Bool #

max :: Edge s nt t -> Edge s nt t -> Edge s nt t #

min :: Edge s nt t -> Edge s nt t -> Edge s nt t #

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

Defined in Text.ANTLR.Allstar.ATN

Methods

showsPrec :: Int -> Edge s nt t -> ShowS #

show :: Edge s nt t -> String #

showList :: [Edge s nt t] -> ShowS #

Generic (Edge s nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ATN

Associated Types

type Rep (Edge s nt t) :: Type -> Type #

Methods

from :: Edge s nt t -> Rep (Edge s nt t) x #

to :: Rep (Edge s nt t) x -> Edge s nt t #

(Hashable nt, Hashable t) => Hashable (Edge s nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ATN

Methods

hashWithSalt :: Int -> Edge s nt t -> Int #

hash :: Edge s nt t -> Int #

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

Defined in Text.ANTLR.Allstar.ATN

Methods

prettify :: Edge s nt t -> Pretty Source #

prettifyList :: [Edge s nt t] -> Pretty Source #

type Rep (Edge s nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ATN

atnOf :: forall nt t s. (Eq nt, Eq t, Hashable nt, Hashable t) => Grammar s nt t -> ATN s nt t Source #

Convert a G4 grammar into an ATN for parsing with ALL(*)