Safe Haskell | None |
---|---|
Language | Haskell98 |
Happy.Grammar
Description
This module exports the Grammar
data type, which
Synopsis
- newtype Name = MkName {}
- data Production eliminator = Production Name [Name] (eliminator, [Int]) Priority
- data TokenSpec
- data Grammar eliminator = Grammar {
- productions :: [Production eliminator]
- lookupProdNo :: Int -> Production eliminator
- lookupProdsOfName :: Name -> [Int]
- token_specs :: [(Name, TokenSpec)]
- terminals :: [Name]
- non_terminals :: [Name]
- starts :: [(String, Name, Name, Bool)]
- types :: Array Name (Maybe String)
- token_names :: Array Name String
- first_nonterm :: Name
- first_term :: Name
- eof_term :: Name
- priorities :: [(Name, Priority)]
- data AttributeGrammarExtras = AttributeGrammarExtras {
- attributes :: [(String, String)]
- attributetype :: String
- data Priority
- = No
- | Prio Assoc Int
- | PrioLowest
- data Assoc
- = LeftAssoc
- | RightAssoc
- | None
- data ErrorHandlerInfo
- data ErrorExpectedMode
- data Directives = Directives {
- token_type :: String
- imported_identity :: Bool
- monad :: (Bool, String, String, String, String)
- expect :: Maybe Int
- lexer :: Maybe (String, String)
- error_handler :: ErrorHandlerInfo
- error_expected :: ErrorExpectedMode
- errorName :: String
- errorTok :: Name
- catchName :: String
- catchTok :: Name
- startName :: String
- dummyName :: String
- firstStartTok :: Name
- dummyTok :: Name
- eofName :: String
- epsilonTok :: Name
Documentation
data Production eliminator Source #
Constructors
Production Name [Name] (eliminator, [Int]) Priority |
Instances
Show eliminator => Show (Production eliminator) Source # | |
Defined in Happy.Grammar Methods showsPrec :: Int -> Production eliminator -> ShowS # show :: Production eliminator -> String # showList :: [Production eliminator] -> ShowS # |
Constructors
TokenFixed String | The token is just a fixed value |
TokenWithValue ExpressionWithHole | The token is an expression involving the value of the lexed token. |
Instances
data Grammar eliminator Source #
Constructors
Grammar | |
Fields
|
data AttributeGrammarExtras Source #
Constructors
AttributeGrammarExtras | |
Fields
|
Constructors
No | |
Prio Assoc Int | |
PrioLowest |
Constructors
LeftAssoc | |
RightAssoc | |
None |
data ErrorHandlerInfo Source #
Constructors
DefaultErrorHandler | Default handler |
CustomErrorHandler String | Call this handler on error. |
ResumptiveErrorHandler String String | `ResumptiveErrorHandler abort report`:
Upon encountering a parse error, call non-fatal function |
data ErrorExpectedMode Source #
Constructors
NoExpected | Neither `%errorhandertype explist` nor `%error.expected` |
OldExpected | `%errorhandertype explist`. The error handler takes a pair `(Token, [String])` |
NewExpected | `%error.expected`. The error handler takes two (or more) args `Token -> [String] -> ...`. |
Instances
Eq ErrorExpectedMode Source # | |
Defined in Happy.Grammar Methods (==) :: ErrorExpectedMode -> ErrorExpectedMode -> Bool # (/=) :: ErrorExpectedMode -> ErrorExpectedMode -> Bool # |
data Directives Source #
Stuff like `%monad`, `%expect`
Constructors
Directives | |
Fields
|
firstStartTok :: Name Source #
epsilonTok :: Name Source #