Copyright | (c) Karl Cronburg 2018 |
---|---|
License | BSD3 |
Maintainer | karl@cs.tufts.edu |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data G4
- data PRHS = PRHS {}
- data ProdElem
- data GAnnot = Fragment
- data Directive
- data LRHS = LRHS {}
- data Regex s
- isGTerm :: ProdElem -> Bool
- isGNonTerm :: ProdElem -> Bool
- data TermAnnot
- isMaybeAnnot :: TermAnnot -> Bool
- isNoAnnot :: TermAnnot -> Bool
- annot :: ProdElem -> TermAnnot
- prodElemSymbol :: ProdElem -> String
Documentation
.g4 style syntax representation
Grammar | Grammar name declaration in g4 |
Prod | One or more g4 productions |
Lex | A single, possibly annotated, g4 lexical rule |
Instances
The right-hand side of a G4 production rule.
PRHS | |
|
Instances
Eq PRHS Source # | |
Show PRHS Source # | |
Generic PRHS Source # | |
Lift PRHS Source # | |
Hashable PRHS Source # | |
Defined in Language.ANTLR4.Boot.Syntax | |
Prettify PRHS Source # | |
type Rep PRHS Source # | |
Defined in Language.ANTLR4.Boot.Syntax type Rep PRHS = D1 (MetaData "PRHS" "Language.ANTLR4.Boot.Syntax" "antlr-haskell-0.1.0.1-47wJxWjYxn91lXcjBVmKNu" False) (C1 (MetaCons "PRHS" PrefixI True) ((S1 (MetaSel (Just "alphas") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ProdElem]) :*: S1 (MetaSel (Just "pred") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Exp))) :*: (S1 (MetaSel (Just "mutator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Exp)) :*: S1 (MetaSel (Just "pDirective") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Directive))))) |
A single production element with any accompanying regex annotation
Instances
Eq ProdElem Source # | |
Ord ProdElem Source # | |
Defined in Language.ANTLR4.Boot.Syntax | |
Show ProdElem Source # | |
Generic ProdElem Source # | |
Lift ProdElem Source # | |
Hashable ProdElem Source # | |
Defined in Language.ANTLR4.Boot.Syntax | |
Prettify ProdElem Source # | |
type Rep ProdElem Source # | |
Defined in Language.ANTLR4.Boot.Syntax type Rep ProdElem = D1 (MetaData "ProdElem" "Language.ANTLR4.Boot.Syntax" "antlr-haskell-0.1.0.1-47wJxWjYxn91lXcjBVmKNu" False) (C1 (MetaCons "GTerm" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TermAnnot) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "GNonTerm" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TermAnnot) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) |
Allowable annotations on a lexical production rule
Fragment | For now the only annotation is |
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.
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 # | |
Ord Directive Source # | |
Defined in Language.ANTLR4.Boot.Syntax | |
Show Directive Source # | |
Generic Directive Source # | |
Lift Directive Source # | |
Hashable Directive Source # | |
Defined in Language.ANTLR4.Boot.Syntax | |
Prettify Directive Source # | |
type Rep Directive Source # | |
Defined in Language.ANTLR4.Boot.Syntax type Rep Directive = D1 (MetaData "Directive" "Language.ANTLR4.Boot.Syntax" "antlr-haskell-0.1.0.1-47wJxWjYxn91lXcjBVmKNu" False) (C1 (MetaCons "UpperD" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: (C1 (MetaCons "LowerD" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "HaskellD" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) |
Right-hand side of a lexical G4 rule
Instances
Eq LRHS Source # | |
Show LRHS Source # | |
Generic LRHS Source # | |
Lift LRHS Source # | |
Hashable LRHS Source # | |
Defined in Language.ANTLR4.Boot.Syntax | |
type Rep LRHS Source # | |
Defined in Language.ANTLR4.Boot.Syntax type Rep LRHS = D1 (MetaData "LRHS" "Language.ANTLR4.Boot.Syntax" "antlr-haskell-0.1.0.1-47wJxWjYxn91lXcjBVmKNu" 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)))) |
G4 representation of a regex (G4 regex syntax, not regexs used by tokenizer)
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
isGNonTerm :: ProdElem -> Bool Source #
Is this a nonterminal G4 element?
Annotations on a term (nonterminal or terminal) for extending our G4 BNF-like syntax with regular expression modifiers.
Instances
Eq TermAnnot Source # | |
Ord TermAnnot Source # | |
Defined in Language.ANTLR4.Boot.Syntax | |
Show TermAnnot Source # | |
Generic TermAnnot Source # | |
Lift TermAnnot Source # | |
Hashable TermAnnot Source # | |
Defined in Language.ANTLR4.Boot.Syntax | |
Prettify TermAnnot Source # | |
type Rep TermAnnot Source # | |
Defined in Language.ANTLR4.Boot.Syntax type Rep TermAnnot = D1 (MetaData "TermAnnot" "Language.ANTLR4.Boot.Syntax" "antlr-haskell-0.1.0.1-47wJxWjYxn91lXcjBVmKNu" False) (C1 (MetaCons "Regular" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)) :+: C1 (MetaCons "NoAnnot" PrefixI False) (U1 :: Type -> Type)) |
prodElemSymbol :: ProdElem -> String Source #