Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Oberon grammar adapted from http://www.ethoberon.ethz.ch/EBNF.html
Extracted from the book Programmieren in Oberon - Das neue Pascal by N. Wirth and M. Reiser and translated by J. Templ.
The grammars in this module attempt to follow the language grammars from the reports, while generating a semantically meaningful abstract syntax tree; the latter is defined in Language.Oberon.AST. As the grammars are ambiguous, it is necessary to resolve the ambiguities after parsing all Oberon modules in use. Language.Oberon.Resolver provides this functionality. Only after the ambiguity resolution can the abstract syntax tree be pretty-printed using the instances from Language.Oberon.Pretty. Alternatively, since the parsing preserves the original parsed lexemes including comments in the AST, you can use Language.Oberon.Reserializer to reproduce the original source code from the AST.
Synopsis
- data OberonGrammar l f p = OberonGrammar {
- module_prod :: p (f (Module l l f f))
- ident :: p Ident
- letter :: p Text
- digit :: p Text
- importList :: p [Import l]
- import_prod :: p (Import l)
- declarationSequence :: p [f (Declaration l l f f)]
- constantDeclaration :: p (Declaration l l f f)
- identdef :: p (IdentDef l)
- constExpression :: p (f (Expression l l f f))
- expression :: p (f (Expression l l f f))
- simpleExpression :: p (f (Expression l l f f))
- term :: p (f (Expression l l f f))
- factor :: p (f (Expression l l f f))
- number :: p (Value l l f f)
- integer :: p (Value l l f f)
- hexDigit :: p Text
- real :: p (Value l l f f)
- scaleFactor :: p Text
- charConstant :: p (Value l l f f)
- string_prod :: p Text
- set :: p (Expression l l f f)
- element :: p (Element l l f f)
- designator :: p (f (Designator l l f f))
- unguardedDesignator :: p (Designator l l f f)
- expList :: p (NonEmpty (f (Expression l l f f)))
- actualParameters :: p [f (Expression l l f f)]
- mulOperator :: p (BinOp l f)
- addOperator :: p (BinOp l f)
- relation :: p RelOp
- typeDeclaration :: p (Declaration l l f f)
- type_prod :: p (Type l l f f)
- qualident :: p (QualIdent l)
- arrayType :: p (Type l l f f)
- length :: p (f (Expression l l f f))
- recordType :: p (Type l l f f)
- baseType :: p (BaseType l)
- fieldListSequence :: p [f (FieldList l l f f)]
- fieldList :: p (FieldList l l f f)
- identList :: p (IdentList l)
- pointerType :: p (Type l l f f)
- procedureType :: p (Type l l f f)
- variableDeclaration :: p (Declaration l l f f)
- procedureDeclaration :: p (Declaration l l f f)
- procedureHeading :: p (Ident, ProcedureHeading l l f f)
- formalParameters :: p (FormalParameters l l f f)
- fPSection :: p (FPSection l l f f)
- formalType :: p (Type l l f f)
- procedureBody :: p (Block l l f f)
- forwardDeclaration :: p (Declaration l l f f)
- statementSequence :: p (StatementSequence l l f f)
- statement :: p (f (Statement l l f f))
- assignment :: p (Statement l l f f)
- procedureCall :: p (Statement l l f f)
- ifStatement :: p (Statement l l f f)
- caseStatement :: p (Statement l l f f)
- case_prod :: p (Case l l f f)
- caseLabelList :: p (NonEmpty (f (CaseLabels l l f f)))
- caseLabels :: p (CaseLabels l l f f)
- whileStatement :: p (Statement l l f f)
- repeatStatement :: p (Statement l l f f)
- forStatement :: p (Statement l l f f)
- loopStatement :: p (Statement l l f f)
- withStatement :: p (Statement l l f f)
- type Parser = ParserT ((,) [[Lexeme]])
- type NodeWrap = Compose ((,) (Down Int, Down Int)) (Compose Ambiguous ((,) ParsedLexemes))
- newtype ParsedLexemes = Trailing [Lexeme]
- data Lexeme
- = WhiteSpace {
- lexemeText :: Text
- | Comment {
- lexemeText :: Text
- | Token { }
- = WhiteSpace {
- data TokenType
- oberonGrammar :: Grammar (OberonGrammar Language NodeWrap) Parser Text
- oberon2Grammar :: Grammar (OberonGrammar Language NodeWrap) Parser Text
- oberonDefinitionGrammar :: Grammar (OberonGrammar Language NodeWrap) Parser Text
- oberon2DefinitionGrammar :: Grammar (OberonGrammar Language NodeWrap) Parser Text
Documentation
data OberonGrammar l f p Source #
All the productions of the Oberon grammar
Instances
type NodeWrap = Compose ((,) (Down Int, Down Int)) (Compose Ambiguous ((,) ParsedLexemes)) Source #
Every node in the parsed AST will be wrapped in this data type.
newtype ParsedLexemes Source #
Instances
WhiteSpace | |
| |
Comment | |
| |
Token | |
|
Instances
Instances
Data TokenType Source # | |
Defined in Language.Oberon.Grammar gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TokenType -> c TokenType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenType # toConstr :: TokenType -> Constr # dataTypeOf :: TokenType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TokenType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenType) # gmapT :: (forall b. Data b => b -> b) -> TokenType -> TokenType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenType -> r # gmapQ :: (forall d. Data d => d -> u) -> TokenType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType # | |
Show TokenType Source # | |
Eq TokenType Source # | |
oberonGrammar :: Grammar (OberonGrammar Language NodeWrap) Parser Text Source #
Grammar of an Oberon module
oberon2Grammar :: Grammar (OberonGrammar Language NodeWrap) Parser Text Source #
Grammar of an Oberon-2 module
oberonDefinitionGrammar :: Grammar (OberonGrammar Language NodeWrap) Parser Text Source #
Grammar of an Oberon definition module
oberon2DefinitionGrammar :: Grammar (OberonGrammar Language NodeWrap) Parser Text Source #
Grammar of an Oberon-2 definition module