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

Contents

Description

 
Synopsis

Data types

data Grammar s nts ts Source #

Core representation of a grammar, as used by the parsing algorithms.

Constructors

G 

Fields

Instances
(Eq s, Eq nts, Eq ts, Hashable nts, Hashable ts, Prettify s, Prettify nts, Prettify ts) => Eq (Grammar s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

(==) :: Grammar s nts ts -> Grammar s nts ts -> Bool #

(/=) :: Grammar s nts ts -> Grammar s nts ts -> Bool #

(Show nts, Show ts, Show s) => Show (Grammar s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

showsPrec :: Int -> Grammar s nts ts -> ShowS #

show :: Grammar s nts ts -> String #

showList :: [Grammar s nts ts] -> ShowS #

(Hashable nts, Hashable ts, Eq nts, Eq ts, Lift nts, Lift ts, Data s) => Lift (Grammar s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

lift :: Grammar s nts ts -> Q Exp #

(Prettify s, Prettify nts, Prettify ts, Hashable ts, Eq ts, Hashable nts, Eq nts, Ord ts, Ord nts) => Prettify (Grammar s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

prettify :: Grammar s nts ts -> Pretty Source #

prettifyList :: [Grammar s nts ts] -> Pretty Source #

data ProdElem nts ts Source #

Grammar ProdElems

nts == Non Terminal Symbol (type)
ts == Terminal Symbol (type)

Production elements are only used in the grammar data structure and parser, therefore these types (nt and ts) are not necessarily equivalent to the terminal types seen by the tokenizer (nonterminals are special because no one sees them until after parsing). Also pushing (ts = Sym t) up to the top of data constructors gets rid of a lot of unnecessary standalone deriving instances. Standalone deriving instances in this case are a programming anti-pattern for allowing you to improperly parametrize your types. In this case a ProdElem cares about the terminal symbol type, not the __terminal token type__. In fact it's redundant to say *terminal token* because all tokens are terminals in the grammar. A token is by definition a tokenized value with a named terminal symbol, which is in fact exactly what the Token type looks like in Tokenizer: Token n v (name and value). So wherever I see an n type variable in the tokenizer, this is equivalent to (Sym t) in the parser. And wherever I see a (Token n v) in the tokenizer, this gets passed into the parser as t:

    n           == Sym t
    (Token n v) == t
  

Constructors

NT nts

Nonterminal production element

T ts

Terminal production element

Eps

Empty string production element

Instances
(Eq nts, Eq ts) => Eq (ProdElem nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

(==) :: ProdElem nts ts -> ProdElem nts ts -> Bool #

(/=) :: ProdElem nts ts -> ProdElem nts ts -> Bool #

(Data nts, Data ts) => Data (ProdElem nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProdElem nts ts -> c (ProdElem nts ts) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ProdElem nts ts) #

toConstr :: ProdElem nts ts -> Constr #

dataTypeOf :: ProdElem nts ts -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ProdElem nts ts)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ProdElem nts ts)) #

gmapT :: (forall b. Data b => b -> b) -> ProdElem nts ts -> ProdElem nts ts #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProdElem nts ts -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProdElem nts ts -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProdElem nts ts -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProdElem nts ts -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProdElem nts ts -> m (ProdElem nts ts) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProdElem nts ts -> m (ProdElem nts ts) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProdElem nts ts -> m (ProdElem nts ts) #

(Ord nts, Ord ts) => Ord (ProdElem nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

compare :: ProdElem nts ts -> ProdElem nts ts -> Ordering #

(<) :: ProdElem nts ts -> ProdElem nts ts -> Bool #

(<=) :: ProdElem nts ts -> ProdElem nts ts -> Bool #

(>) :: ProdElem nts ts -> ProdElem nts ts -> Bool #

(>=) :: ProdElem nts ts -> ProdElem nts ts -> Bool #

max :: ProdElem nts ts -> ProdElem nts ts -> ProdElem nts ts #

min :: ProdElem nts ts -> ProdElem nts ts -> ProdElem nts ts #

(Show nts, Show ts) => Show (ProdElem nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

showsPrec :: Int -> ProdElem nts ts -> ShowS #

show :: ProdElem nts ts -> String #

showList :: [ProdElem nts ts] -> ShowS #

Generic (ProdElem nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Associated Types

type Rep (ProdElem nts ts) :: Type -> Type #

Methods

from :: ProdElem nts ts -> Rep (ProdElem nts ts) x #

to :: Rep (ProdElem nts ts) x -> ProdElem nts ts #

(Lift nts, Lift ts) => Lift (ProdElem nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

lift :: ProdElem nts ts -> Q Exp #

(Hashable nts, Hashable ts) => Hashable (ProdElem nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

hashWithSalt :: Int -> ProdElem nts ts -> Int #

hash :: ProdElem nts ts -> Int #

(Prettify nts, Prettify ts) => Prettify (ProdElem nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

prettify :: ProdElem nts ts -> Pretty Source #

prettifyList :: [ProdElem nts ts] -> Pretty Source #

type Rep (ProdElem nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

type Rep (ProdElem nts ts) = D1 (MetaData "ProdElem" "Text.ANTLR.Grammar" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" False) (C1 (MetaCons "NT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 nts)) :+: (C1 (MetaCons "T" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ts)) :+: C1 (MetaCons "Eps" PrefixI False) (U1 :: Type -> Type)))

type ProdElems nts ts = [ProdElem nts ts] Source #

Zero or more production elements

data Production s nts ts Source #

A single production rule

Constructors

Production nts (ProdRHS s nts ts) 
Instances
(Eq nts, Eq ts) => Eq (Production s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

(==) :: Production s nts ts -> Production s nts ts -> Bool #

(/=) :: Production s nts ts -> Production s nts ts -> Bool #

(Data s, Data nts, Data ts) => Data (Production s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Production s nts ts -> c (Production s nts ts) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Production s nts ts) #

toConstr :: Production s nts ts -> Constr #

dataTypeOf :: Production s nts ts -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Production s nts ts)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Production s nts ts)) #

gmapT :: (forall b. Data b => b -> b) -> Production s nts ts -> Production s nts ts #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Production s nts ts -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Production s nts ts -> r #

gmapQ :: (forall d. Data d => d -> u) -> Production s nts ts -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Production s nts ts -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Production s nts ts -> m (Production s nts ts) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Production s nts ts -> m (Production s nts ts) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Production s nts ts -> m (Production s nts ts) #

(Ord nts, Ord ts) => Ord (Production s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

compare :: Production s nts ts -> Production s nts ts -> Ordering #

(<) :: Production s nts ts -> Production s nts ts -> Bool #

(<=) :: Production s nts ts -> Production s nts ts -> Bool #

(>) :: Production s nts ts -> Production s nts ts -> Bool #

(>=) :: Production s nts ts -> Production s nts ts -> Bool #

max :: Production s nts ts -> Production s nts ts -> Production s nts ts #

min :: Production s nts ts -> Production s nts ts -> Production s nts ts #

(Show s, Show nts, Show ts) => Show (Production s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

showsPrec :: Int -> Production s nts ts -> ShowS #

show :: Production s nts ts -> String #

showList :: [Production s nts ts] -> ShowS #

Generic (Production s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Associated Types

type Rep (Production s nts ts) :: Type -> Type #

Methods

from :: Production s nts ts -> Rep (Production s nts ts) x #

to :: Rep (Production s nts ts) x -> Production s nts ts #

(Lift nts, Lift ts) => Lift (Production s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

lift :: Production s nts ts -> Q Exp #

(Hashable nts, Hashable ts) => Hashable (Production s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

hashWithSalt :: Int -> Production s nts ts -> Int #

hash :: Production s nts ts -> Int #

(Prettify s, Prettify nts, Prettify ts) => Prettify (Production s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

prettify :: Production s nts ts -> Pretty Source #

prettifyList :: [Production s nts ts] -> Pretty Source #

type Rep (Production s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

type Rep (Production s nts ts) = D1 (MetaData "Production" "Text.ANTLR.Grammar" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" False) (C1 (MetaCons "Production" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 nts) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ProdRHS s nts ts))))

data ProdRHS s nts ts Source #

Right-hand side of a single production rule

Constructors

Prod (StateFncn s) (ProdElems nts ts) 
Instances
(Eq nts, Eq ts) => Eq (ProdRHS s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

(==) :: ProdRHS s nts ts -> ProdRHS s nts ts -> Bool #

(/=) :: ProdRHS s nts ts -> ProdRHS s nts ts -> Bool #

(Data s, Data nts, Data ts) => Data (ProdRHS s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProdRHS s nts ts -> c (ProdRHS s nts ts) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ProdRHS s nts ts) #

toConstr :: ProdRHS s nts ts -> Constr #

dataTypeOf :: ProdRHS s nts ts -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ProdRHS s nts ts)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ProdRHS s nts ts)) #

gmapT :: (forall b. Data b => b -> b) -> ProdRHS s nts ts -> ProdRHS s nts ts #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProdRHS s nts ts -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProdRHS s nts ts -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProdRHS s nts ts -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProdRHS s nts ts -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProdRHS s nts ts -> m (ProdRHS s nts ts) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProdRHS s nts ts -> m (ProdRHS s nts ts) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProdRHS s nts ts -> m (ProdRHS s nts ts) #

(Ord nts, Ord ts) => Ord (ProdRHS s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

compare :: ProdRHS s nts ts -> ProdRHS s nts ts -> Ordering #

(<) :: ProdRHS s nts ts -> ProdRHS s nts ts -> Bool #

(<=) :: ProdRHS s nts ts -> ProdRHS s nts ts -> Bool #

(>) :: ProdRHS s nts ts -> ProdRHS s nts ts -> Bool #

(>=) :: ProdRHS s nts ts -> ProdRHS s nts ts -> Bool #

max :: ProdRHS s nts ts -> ProdRHS s nts ts -> ProdRHS s nts ts #

min :: ProdRHS s nts ts -> ProdRHS s nts ts -> ProdRHS s nts ts #

(Show nts, Show ts) => Show (ProdRHS s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

showsPrec :: Int -> ProdRHS s nts ts -> ShowS #

show :: ProdRHS s nts ts -> String #

showList :: [ProdRHS s nts ts] -> ShowS #

Generic (ProdRHS s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Associated Types

type Rep (ProdRHS s nts ts) :: Type -> Type #

Methods

from :: ProdRHS s nts ts -> Rep (ProdRHS s nts ts) x #

to :: Rep (ProdRHS s nts ts) x -> ProdRHS s nts ts #

(Lift nts, Lift ts) => Lift (ProdRHS s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

lift :: ProdRHS s nts ts -> Q Exp #

(Hashable nts, Hashable ts) => Hashable (ProdRHS s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

hashWithSalt :: Int -> ProdRHS s nts ts -> Int #

hash :: ProdRHS s nts ts -> Int #

(Prettify s, Prettify nts, Prettify ts) => Prettify (ProdRHS s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

prettify :: ProdRHS s nts ts -> Pretty Source #

prettifyList :: [ProdRHS s nts ts] -> Pretty Source #

type Rep (ProdRHS s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

type Rep (ProdRHS s nts ts) = D1 (MetaData "ProdRHS" "Text.ANTLR.Grammar" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" False) (C1 (MetaCons "Prod" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (StateFncn s)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ProdElems nts ts))))

data StateFncn s Source #

A function to run when a production rule fires, operating some state s.

Constructors

Pass

No predicate or mutator

Sem (Predicate ())

Semantic predicate

Action (Mutator ())

Mutator, ProdElems is always empty in this one

Instances
Eq (StateFncn s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

(==) :: StateFncn s -> StateFncn s -> Bool #

(/=) :: StateFncn s -> StateFncn s -> Bool #

Data s => Data (StateFncn s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StateFncn s -> c (StateFncn s) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StateFncn s) #

toConstr :: StateFncn s -> Constr #

dataTypeOf :: StateFncn s -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StateFncn s)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StateFncn s)) #

gmapT :: (forall b. Data b => b -> b) -> StateFncn s -> StateFncn s #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StateFncn s -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StateFncn s -> r #

gmapQ :: (forall d. Data d => d -> u) -> StateFncn s -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StateFncn s -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StateFncn s -> m (StateFncn s) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StateFncn s -> m (StateFncn s) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StateFncn s -> m (StateFncn s) #

Ord (StateFncn s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Show (StateFncn s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Generic (StateFncn s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Associated Types

type Rep (StateFncn s) :: Type -> Type #

Methods

from :: StateFncn s -> Rep (StateFncn s) x #

to :: Rep (StateFncn s) x -> StateFncn s #

Lift (StateFncn s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

lift :: StateFncn s -> Q Exp #

Hashable (StateFncn s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

hashWithSalt :: Int -> StateFncn s -> Int #

hash :: StateFncn s -> Int #

Prettify (StateFncn s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

type Rep (StateFncn s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

type Rep (StateFncn s) = D1 (MetaData "StateFncn" "Text.ANTLR.Grammar" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" False) (C1 (MetaCons "Pass" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Sem" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Predicate ()))) :+: C1 (MetaCons "Action" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Mutator ())))))

data Predicate p Source #

Predicates and Mutators act over some state. The String identifiers should eventually correspond to source-level e.g. location / allocation site information, i.e. two predicates or mutators are equivalent iff they were constructed from the same production rule.

Constructors

Predicate String p 
Instances
Eq (Predicate s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

(==) :: Predicate s -> Predicate s -> Bool #

(/=) :: Predicate s -> Predicate s -> Bool #

Data p => Data (Predicate p) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Predicate p -> c (Predicate p) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Predicate p) #

toConstr :: Predicate p -> Constr #

dataTypeOf :: Predicate p -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Predicate p)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Predicate p)) #

gmapT :: (forall b. Data b => b -> b) -> Predicate p -> Predicate p #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Predicate p -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Predicate p -> r #

gmapQ :: (forall d. Data d => d -> u) -> Predicate p -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Predicate p -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Predicate p -> m (Predicate p) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Predicate p -> m (Predicate p) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Predicate p -> m (Predicate p) #

Ord (Predicate s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Show (Predicate s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

(Data s, Typeable s) => Lift (Predicate s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

lift :: Predicate s -> Q Exp #

Hashable (Predicate s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

hashWithSalt :: Int -> Predicate s -> Int #

hash :: Predicate s -> Int #

Prettify (Predicate s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

data Mutator s Source #

Function for mutating the state of the parser when a certain production rule fires.

Constructors

Mutator String () 
Instances
Eq (Mutator s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

(==) :: Mutator s -> Mutator s -> Bool #

(/=) :: Mutator s -> Mutator s -> Bool #

Data s => Data (Mutator s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Mutator s -> c (Mutator s) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Mutator s) #

toConstr :: Mutator s -> Constr #

dataTypeOf :: Mutator s -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Mutator s)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Mutator s)) #

gmapT :: (forall b. Data b => b -> b) -> Mutator s -> Mutator s #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mutator s -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mutator s -> r #

gmapQ :: (forall d. Data d => d -> u) -> Mutator s -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Mutator s -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Mutator s -> m (Mutator s) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Mutator s -> m (Mutator s) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Mutator s -> m (Mutator s) #

Ord (Mutator s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

compare :: Mutator s -> Mutator s -> Ordering #

(<) :: Mutator s -> Mutator s -> Bool #

(<=) :: Mutator s -> Mutator s -> Bool #

(>) :: Mutator s -> Mutator s -> Bool #

(>=) :: Mutator s -> Mutator s -> Bool #

max :: Mutator s -> Mutator s -> Mutator s #

min :: Mutator s -> Mutator s -> Mutator s #

Show (Mutator s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

showsPrec :: Int -> Mutator s -> ShowS #

show :: Mutator s -> String #

showList :: [Mutator s] -> ShowS #

(Data s, Typeable s) => Lift (Mutator s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

lift :: Mutator s -> Q Exp #

Hashable (Mutator s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

hashWithSalt :: Int -> Mutator s -> Int #

hash :: Mutator s -> Int #

Prettify (Mutator s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

class Ref v where Source #

Something is Ref if it can be symbolized by some symbol in a set of symbols. Symbols are typically Strings, an enum data type, or some other Eq-able (best if finite) set of things.

Associated Types

type Sym v :: * Source #

One symbol type for every value type v.

Methods

getSymbol :: v -> Sym v Source #

Compute (or extract) the symbol for some concrete value.

Instances
Ref String Source # 
Instance details

Defined in Text.ANTLR.Grammar

Associated Types

type Sym String :: Type Source #

Ref (String, b) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Associated Types

type Sym (String, b) :: Type Source #

Methods

getSymbol :: (String, b) -> Sym (String, b) Source #

Ref (Token n v) Source #

Tokens are symbolized by an icon containing their name.

Instance details

Defined in Text.ANTLR.Parser

Associated Types

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

Methods

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

Basic setter / getter functions:

getRHS :: Production s nts ts -> ProdRHS s nts ts Source #

Inline get ProdRHS of a Production

getLHS :: Production s nts ts -> nts Source #

Inline get the nonterminal symbol naming a Production

isSem :: ProdRHS s nts ts -> Bool Source #

Is this ProdRHS a semantic predicate?

isAction :: ProdRHS s nts ts -> Bool Source #

Is this ProdRHS a mutator?

sameNTs :: forall nt. (Ref nt, Eq (Sym nt)) => nt -> nt -> Bool Source #

Nonterminals can be symbolized (for now the types are equivalent, i.e. nt == Sym nt)

sameTs :: forall t. (Ref t, Eq (Sym t)) => t -> t -> Bool Source #

Terminals can be symbolized (in the current implementation, the input terminal type to a parser is (t == Token n v) and the terminal symbol type is (ts == 'Sym t' == n) where n is defined as the name of a token (Token n v).

isNT :: ProdElem nts ts -> Bool Source #

Is the ProdElem a nonterminal?

isT :: ProdElem nts ts -> Bool Source #

Is the ProdElem a terminal?

isEps :: ProdElem nts ts -> Bool Source #

Is the ProdElem an epsilon?

getNTs :: [ProdElem b ts] -> [b] Source #

Get just the nonterminals from a list

getTs :: [ProdElem nts b] -> [b] Source #

Get just the terminals from a list

getEps :: [ProdElem nts1 ts1] -> [ProdElem nts2 ts2] Source #

Get just the epsilons from a list (umm...)

prodsFor :: forall s nts ts. Eq nts => Grammar s nts ts -> nts -> [Production s nts ts] Source #

Get only the productions for the given nonterminal symbol nts:

getProds :: [ProdRHS s nts ts] -> [ProdElems nts ts] Source #

Get just the production elements from a bunch of production rules

validGrammar :: forall s nts ts. (Eq nts, Ord nts, Eq ts, Ord ts, Hashable nts, Hashable ts) => Grammar s nts ts -> Bool Source #

Does the given grammar make any sense?

hasAllNonTerms :: (Eq nts, Ord nts, Hashable nts, Hashable ts) => Grammar s nts ts -> Bool Source #

All nonterminals in production rules can be found in the nonterminals list.

hasAllTerms :: (Eq ts, Ord ts, Hashable nts, Hashable ts) => Grammar s nts ts -> Bool Source #

All terminals in production rules can be found in the terminal list.

startIsNonTerm :: (Ord nts, Hashable nts) => Grammar s nts ts -> Bool Source #

The starting symbol is a valid nonterminal.

symbols :: (Ord nts, Ord ts, Hashable s, Hashable nts, Hashable ts) => Grammar s nts ts -> Set (ProdElem nts ts) Source #

All possible production elements of a given grammar.

defaultGrammar :: forall s nts ts. (Ord ts, Hashable ts, Hashable nts, Eq nts) => nts -> Grammar s nts ts Source #

The empty grammar - accepts nothing, with one starting nonterminal and nowhere to go.