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

Language.ANTLR4.Boot.Syntax

Contents

Description

 
Synopsis

Documentation

data G4 Source #

.g4 style syntax representation

Constructors

Grammar

Grammar name declaration in g4

Fields

Prod

One or more g4 productions

Fields

Lex

A single, possibly annotated, g4 lexical rule

Fields

Instances
Eq G4 Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

(==) :: G4 -> G4 -> Bool #

(/=) :: G4 -> G4 -> Bool #

Show G4 Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

showsPrec :: Int -> G4 -> ShowS #

show :: G4 -> String #

showList :: [G4] -> ShowS #

Generic G4 Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Associated Types

type Rep G4 :: Type -> Type #

Methods

from :: G4 -> Rep G4 x #

to :: Rep G4 x -> G4 #

Lift G4 Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

lift :: G4 -> Q Exp #

Hashable G4 Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

hashWithSalt :: Int -> G4 -> Int #

hash :: G4 -> Int #

type Rep G4 Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

data PRHS Source #

The right-hand side of a G4 production rule.

Constructors

PRHS 

Fields

Instances
Eq PRHS Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

(==) :: PRHS -> PRHS -> Bool #

(/=) :: PRHS -> PRHS -> Bool #

Show PRHS Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

showsPrec :: Int -> PRHS -> ShowS #

show :: PRHS -> String #

showList :: [PRHS] -> ShowS #

Generic PRHS Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Associated Types

type Rep PRHS :: Type -> Type #

Methods

from :: PRHS -> Rep PRHS x #

to :: Rep PRHS x -> PRHS #

Lift PRHS Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

lift :: PRHS -> Q Exp #

Hashable PRHS Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

hashWithSalt :: Int -> PRHS -> Int #

hash :: PRHS -> Int #

type Rep PRHS Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

data ProdElem Source #

A single production element with any accompanying regex annotation

Constructors

GTerm TermAnnot String

G4 terminal

GNonTerm TermAnnot String

G4 nonterminal

Instances
Eq ProdElem Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Ord ProdElem Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Show ProdElem Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Generic ProdElem Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Associated Types

type Rep ProdElem :: Type -> Type #

Methods

from :: ProdElem -> Rep ProdElem x #

to :: Rep ProdElem x -> ProdElem #

Lift ProdElem Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

lift :: ProdElem -> Q Exp #

Hashable ProdElem Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

hashWithSalt :: Int -> ProdElem -> Int #

hash :: ProdElem -> Int #

type Rep ProdElem Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

data GAnnot Source #

Allowable annotations on a lexical production rule

Constructors

Fragment

For now the only annotation is fragment.

Instances
Eq GAnnot Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

(==) :: GAnnot -> GAnnot -> Bool #

(/=) :: GAnnot -> GAnnot -> Bool #

Show GAnnot Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Generic GAnnot Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Associated Types

type Rep GAnnot :: Type -> Type #

Methods

from :: GAnnot -> Rep GAnnot x #

to :: Rep GAnnot x -> GAnnot #

Lift GAnnot Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

lift :: GAnnot -> Q Exp #

Hashable GAnnot Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

hashWithSalt :: Int -> GAnnot -> Int #

hash :: GAnnot -> Int #

type Rep GAnnot Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

type Rep GAnnot = D1 (MetaData "GAnnot" "Language.ANTLR4.Boot.Syntax" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" False) (C1 (MetaCons "Fragment" PrefixI False) (U1 :: Type -> Type))

data Directive Source #

Antiquoted (or g4-embedded) string that goes to the right of an arrow in a g4 production rule. This specifies how to construct a Haskell type.

Constructors

UpperD String

Probably a Haskell data constructor

LowerD String

Probably just a Haskell function to call

HaskellD String

Arbitrary antiquoted Haskell code embedded in the G4 grammar

Instances
Eq Directive Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Show Directive Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Generic Directive Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Associated Types

type Rep Directive :: Type -> Type #

Lift Directive Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

lift :: Directive -> Q Exp #

Hashable Directive Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

type Rep Directive Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

data LRHS Source #

Right-hand side of a lexical G4 rule

Constructors

LRHS 

Fields

Instances
Eq LRHS Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

(==) :: LRHS -> LRHS -> Bool #

(/=) :: LRHS -> LRHS -> Bool #

Show LRHS Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

showsPrec :: Int -> LRHS -> ShowS #

show :: LRHS -> String #

showList :: [LRHS] -> ShowS #

Generic LRHS Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Associated Types

type Rep LRHS :: Type -> Type #

Methods

from :: LRHS -> Rep LRHS x #

to :: Rep LRHS x -> LRHS #

Lift LRHS Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

lift :: LRHS -> Q Exp #

Hashable LRHS Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

hashWithSalt :: Int -> LRHS -> Int #

hash :: LRHS -> Int #

type Rep LRHS Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

type Rep LRHS = D1 (MetaData "LRHS" "Language.ANTLR4.Boot.Syntax" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" False) (C1 (MetaCons "LRHS" PrefixI True) (S1 (MetaSel (Just "regex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Regex Char)) :*: S1 (MetaSel (Just "directive") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Directive))))

data Regex s Source #

G4 representation of a regex (G4 regex syntax, not regexs used by tokenizer)

Constructors

Epsilon

Consume no input

Literal [s]

Match on a literal string (sequence of characters)

Union [Regex s]

Match on any

Concat [Regex s]

Match in sequence

Kleene (Regex s)

Match zero or more times

PosClos (Regex s)

Match one or more times

Question (Regex s)

Match zero or one time.

CharSet [s]

Match once on any of the characters

Negation (Regex s)

Match anything that doesn't match this

Named String

A reference to some other regex (need to track an environment)

Instances
Eq s => Eq (Regex s) Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

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

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

Show s => Show (Regex s) Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

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

show :: Regex s -> String #

showList :: [Regex s] -> ShowS #

Generic (Regex s) Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Associated Types

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

Methods

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

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

Lift s => Lift (Regex s) Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

lift :: Regex s -> Q Exp #

Hashable s => Hashable (Regex s) Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

hashWithSalt :: Int -> Regex s -> Int #

hash :: Regex s -> Int #

type Rep (Regex s) Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

type Rep (Regex s) = D1 (MetaData "Regex" "Language.ANTLR4.Boot.Syntax" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" False) (((C1 (MetaCons "Epsilon" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Literal" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [s]))) :+: (C1 (MetaCons "Union" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Regex s])) :+: (C1 (MetaCons "Concat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Regex s])) :+: C1 (MetaCons "Kleene" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Regex s)))))) :+: ((C1 (MetaCons "PosClos" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Regex s))) :+: C1 (MetaCons "Question" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Regex s)))) :+: (C1 (MetaCons "CharSet" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [s])) :+: (C1 (MetaCons "Negation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Regex s))) :+: C1 (MetaCons "Named" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))))

isGTerm :: ProdElem -> Bool Source #

Is this a terminal G4 element?

isGNonTerm :: ProdElem -> Bool Source #

Is this a nonterminal G4 element?

data TermAnnot Source #

Annotations on a term (nonterminal or terminal) for extending our G4 BNF-like syntax with regular expression modifiers.

Constructors

Regular Char

Regular expression modifier (e.g. +, ?, *)

NoAnnot

Term is not annotated with anything

Instances
Eq TermAnnot Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Ord TermAnnot Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Show TermAnnot Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Generic TermAnnot Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Associated Types

type Rep TermAnnot :: Type -> Type #

Lift TermAnnot Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

Methods

lift :: TermAnnot -> Q Exp #

Hashable TermAnnot Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

type Rep TermAnnot Source # 
Instance details

Defined in Language.ANTLR4.Boot.Syntax

type Rep TermAnnot = D1 (MetaData "TermAnnot" "Language.ANTLR4.Boot.Syntax" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" False) (C1 (MetaCons "Regular" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)) :+: C1 (MetaCons "NoAnnot" PrefixI False) (U1 :: Type -> Type))

isNoAnnot :: TermAnnot -> Bool Source #

Does this TermAnnot have no annotation?

annot :: ProdElem -> TermAnnot Source #

Get the annotation from a ProdElem

Orphan instances

Lift Exp Source # 
Instance details

Methods

lift :: Exp -> Q Exp #