diff --git a/Makefile b/Makefile index c54840f..09b9a5c 100644 --- a/Makefile +++ b/Makefile @@ -1,6 +1,7 @@ .PHONY: all antlr check demo develop install -all: antlr +all: + install: all pip install . @@ -9,11 +10,6 @@ develop: all pip install -Ur requirements.txt pip install -e . -antlr: jeff65/gold/grammar/Gold.py - -jeff65/gold/grammar/Gold.py: jeff65/gold/grammar/Gold.g4 - antlr4 -Dlanguage=Python3 $^ - check: all flake8 jeff65 tests python setup.py nosetests diff --git a/jeff65/gold/__init__.py b/jeff65/gold/__init__.py index cc00123..f88a1b1 100644 --- a/jeff65/gold/__init__.py +++ b/jeff65/gold/__init__.py @@ -14,11 +14,9 @@ # You should have received a copy of the GNU General Public License # along with this program. If not, see . -from .ast import ParseError from .compiler import parse, translate __all__ = [ - 'ParseError', 'parse', 'translate', ] diff --git a/jeff65/gold/ast.py b/jeff65/gold/ast.py index c4c673a..8eb54ea 100644 --- a/jeff65/gold/ast.py +++ b/jeff65/gold/ast.py @@ -14,13 +14,6 @@ # You should have received a copy of the GNU General Public License # along with this program. If not, see . -from .grammar import ParseListener - - -class ParseError(Exception): - def __init__(self, *args, **kwargs): - super().__init__(*args, **kwargs) - class AstNode: def __init__(self, t, position, attrs=None, children=None): @@ -48,7 +41,7 @@ def __eq__(self, other): and self.attrs == other.attrs and self.children == other.children) - def transform(self, transformer): + def transform(self, transformer, always_list=False): node = transformer.transform_enter(self.t, self) if transformer.transform_attrs and type(node) is AstNode: @@ -70,7 +63,7 @@ def transform(self, transformer): children = [] for child in node.children: if type(child) is AstNode: - children.extend(child.transform(transformer)) + children.extend(child.transform(transformer, always_list)) else: children.append(child) if children != node.children: @@ -85,7 +78,7 @@ def transform(self, transformer): elif type(nodes) is not list: nodes = [nodes] - if self.t == 'unit': + if not always_list and self.t == 'unit': assert len(nodes) == 1 return nodes[0] return nodes @@ -140,162 +133,3 @@ def __generic_enter(self, node): def __generic_exit(self, node): return [node] - - -class AstBuilder(ParseListener): - def __init__(self): - self.stack = [] - - @property - def ast(self): - return self.stack[0] - - def _push(self, node): - self.stack.append(node) - - def _pop(self): - c = self.stack.pop() - self.stack[-1].children.append(c) - return c - - def _pop_attr(self, attr): - a = self.stack.pop() - self.stack[-1].attrs[attr] = a - - def _pos(self, ctx): - return (ctx.start.line, ctx.start.column) - - def enterUnit(self, ctx): - self._push(AstNode("unit", self._pos(ctx))) - - def enterStmtUse(self, ctx): - self._push(AstNode("use", self._pos(ctx), { - "name": ctx.unitId.text - })) - - def exitStmtUse(self, ctx): - self._pop() - - def enterStmtConstant(self, ctx): - self._push(AstNode("constant", self._pos(ctx), { - "name": ctx.declaration().name.text - })) - - def exitStmtConstant(self, ctx): - self._pop() - - def enterStmtLet(self, ctx): - node = AstNode("let", self._pos(ctx)) - node.attrs['name'] = ctx.declaration().name.text - if ctx.storage(): - node.attrs['storage'] = ctx.storage().storage_class.text - self._push(node) - - def exitStmtLet(self, ctx): - self._pop() - - def enterStmtFun(self, ctx): - self._push(AstNode("fun", self._pos(ctx), { - "name": ctx.name.text, - 'return': None, - 'args': [], - })) - - def exitStmtFun(self, ctx): - self._pop() - - def enterStmtAssignVal(self, ctx): - self._push(AstNode("set", self._pos(ctx))) - - def exitStmtAssignVal(self, ctx): - self._pop() - - def enterTypePrimitive(self, ctx): - self.stack[-1].attrs["type"] = ctx.name.text - - def enterTypePointer(self, ctx): - self._push(AstNode("type_ref", self._pos(ctx))) - - def exitTypePointer(self, ctx): - self._pop_attr("type") - - def enterTypeArray(self, ctx): - self._push(AstNode('type_array', self._pos(ctx))) - - def exitTypeArray(self, ctx): - self._pop_attr('type') - - def enterExprMember(self, ctx): - self._push(AstNode("member_access", self._pos(ctx), { - "member": ctx.member.text - })) - - def exitExprMember(self, ctx): - self._pop() - - def enterExprId(self, ctx): - self.stack[-1].children.append(AstNode("identifier", self._pos(ctx), { - 'name': ctx.name.text, - })) - - def enterExprNumber(self, ctx): - text = ctx.value.text.lower() - if text.startswith('0x'): - value = int(text[2:], 16) - elif text.startswith('0o'): - value = int(text[2:], 8) - elif text.startswith('0b'): - value = int(text[2:], 2) - else: - value = int(text) - self.stack[-1].children.append(AstNode("numeric", self._pos(ctx), { - 'value': value, - })) - - def enterExprFunCall(self, ctx): - self._push(AstNode("call", self._pos(ctx))) - - def exitExprFunCall(self, ctx): - call = self.stack[-1] - call.attrs['target'] = call.children[0] - call.children = call.children[1:] - self._pop() - - def enterExprDeref(self, ctx): - self._push(AstNode("deref", self._pos(ctx))) - - def exitExprDeref(self, ctx): - self._pop() - - def enterExprSum(self, ctx): - if ctx.op.text == '+': - self._push(AstNode("add", self._pos(ctx))) - elif ctx.op.text == '-': - self._push(AstNode("sub", self._pos(ctx))) - else: - assert False - - def exitExprSum(self, ctx): - self._pop() - - def enterExprProduct(self, ctx): - if ctx.op.text == '*': - self._push(AstNode("mul", self._pos(ctx))) - elif ctx.op.text == '/': - self._push(AstNode("div", self._pos(ctx))) - else: - assert False - - def exitExprProduct(self, ctx): - self._pop() - - def enterExprNegation(self, ctx): - self._push(AstNode("negate", self._pos(ctx))) - - def exitExprNegation(self, ctx): - self._pop() - - def enterString(self, ctx): - self.stack[-1].children.append(AstNode('string', self._pos(ctx), { - 'value': "".join(s.text for s in ctx.s), - })) diff --git a/jeff65/gold/compiler.py b/jeff65/gold/compiler.py index 57cc8a1..85dc8e8 100644 --- a/jeff65/gold/compiler.py +++ b/jeff65/gold/compiler.py @@ -15,12 +15,9 @@ # along with this program. If not, see . import sys -import antlr4 -from . import ast -from .. import blum -from .grammar import Parser -from .lexer import Lexer -from .passes import asm, binding, lower, resolve, typepasses +from . import ast, grammar +from .. import blum, parsing +from .passes import asm, binding, lower, resolve, simplify, typepasses passes = [ @@ -48,15 +45,15 @@ def open_unit(unit): def parse(fileobj, name): - lexer = Lexer(fileobj, name=name) - tokens = antlr4.CommonTokenStream(lexer) - parser = Parser(tokens) - tree = parser.unit() - if parser._syntaxErrors > 0: - raise ast.ParseError("Unit {} had errors; terminating".format(name)) - builder = ast.AstBuilder() - antlr4.ParseTreeWalker.DEFAULT.walk(builder, tree) - return builder.ast + stream = parsing.ReStream(fileobj) + tree = grammar.parse( + stream, grammar.lex, + lambda t, s, c, m: ast.AstNode(t, s.start, children=c)) + # if parser._syntaxErrors > 0: + # raise ast.ParseError("Unit {} had errors; terminating".format(name)) + unit = tree.transform(simplify.Simplify(), always_list=True) + assert len(unit) == 1 + return unit[0] def translate(unit, verbose=False): diff --git a/jeff65/gold/grammar.py b/jeff65/gold/grammar.py new file mode 100644 index 0000000..ef3fef2 --- /dev/null +++ b/jeff65/gold/grammar.py @@ -0,0 +1,371 @@ +# jeff65 gold-syntax grammar +# Copyright (C) 2018 jeff65 maintainers +# +# This program is free software: you can redistribute it and/or modify +# it under the terms of the GNU General Public License as published by +# the Free Software Foundation, either version 3 of the License, or +# (at your option) any later version. +# +# This program is distributed in the hope that it will be useful, +# but WITHOUT ANY WARRANTY; without even the implied warranty of +# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +# GNU General Public License for more details. +# +# You should have received a copy of the GNU General Public License +# along with this program. If not, see . + +import enum +import re +from ..parsing import Grammar, Lexer, Parser, ReStream, Rule + + +@enum.unique +class Mode(enum.IntEnum): + NORMAL = Parser.NORMAL_MODE + COMMENT = 1 + STRING = 2 + + +T = enum.Enum('T', [ + # control tokens -- these tend to cause lexer mode switches + 'EOF', 'MYSTERY', 'STRING_DELIM', 'COMMENT_OPEN', 'COMMENT_CLOSE', + + # literals tokens + 'IDENTIFIER', 'NUMERIC', 'STRING', 'STRING_ESCAPE', 'WHITESPACE', + 'COMMENT_TEXT', + + # arithmetic operators + 'OPERATOR_PLUS', 'OPERATOR_MINUS', 'OPERATOR_TIMES', 'OPERATOR_DIVIDE', + + # logical operators + 'OPERATOR_NOT', 'OPERATOR_AND', 'OPERATOR_OR', + + # bitwise operators + 'OPERATOR_SHR', 'OPERATOR_SHL', 'OPERATOR_BITNOT', 'OPERATOR_BITAND', + 'OPERATOR_BITOR', 'OPERATOR_BITXOR', + + # comparison operators + 'OPERATOR_NE', 'OPERATOR_EQ', 'OPERATOR_LE', 'OPERATOR_GE', 'OPERATOR_LT', + 'OPERATOR_GT', + + # assignment operators + 'OPERATOR_ASSIGN', 'OPERATOR_ASSIGN_INC', 'OPERATOR_ASSIGN_DEC', + + # member access operators + 'OPERATOR_DOT', + + # pointer operators + 'OPERATOR_DEREF', 'OPERATOR_REF', + + # statement keywords + 'STMT_CONSTANT', 'STMT_FOR', 'STMT_FUN', 'STMT_IF', 'STMT_ISR', 'STMT_LET', + 'STMT_RETURN', 'STMT_USE', 'STMT_WHILE', + + # storage classes + 'STORAGE_MUT', 'STORAGE_STASH', + + # assorted punctuation + 'PUNCT_DO', 'PUNCT_ELSE', 'PUNCT_ELSEIF', 'PUNCT_END', 'PUNCT_ENDFUN', + 'PUNCT_ENDISR', 'PUNCT_IN', 'PUNCT_THEN', 'PUNCT_TO', 'PUNCT_COLON', + 'PUNCT_SEMICOLON', 'PUNCT_COMMA', 'PUNCT_ARROWR', + + # delimiters + 'PAREN_OPEN', 'PAREN_CLOSE', 'BRACKET_OPEN', 'BRACKET_CLOSE', 'BRACE_OPEN', + 'BRACE_CLOSE', +]) + + +# precedences. Note that these are in order of lowest precedence to highest +# precedence. Has to be an IntEnum for comparisons to work. +P = enum.IntEnum('P', [ + # Statements + 'STATEMENTS', + 'RETURN_VALUE', + 'ASSIGNMENTS', + + # Statement elements + 'TYPES', + 'STORAGE', + + # Expressions + 'LITERALS', + 'COMPARISONS', + 'SUMS', + 'PRODUCTS', + 'BITSHIFTS', + 'BITXOR', + 'BITOR', + 'BITAND', + 'PREFIX_UNARY', + 'CALLS', + 'SUBSCRIPTS', + 'MEMBERS', + 'PARENTHESES', +]) + + +# non-whitespace characters which can end tokens +specials = re.escape(r'()[]{}:;.,"\@&') + + +# creates a regex that matches the given word as long as it is followed by +# something that can end a token. Useful for defining keywords. +def _w(word): + return r'(?m){}(?=[\s{}]|$)'.format(re.escape(word), specials) + + +lex = Lexer(T.EOF, [ + # whitespace -> hidden channel + (Mode.NORMAL, r'(?m)\s+', T.WHITESPACE, ReStream.CHANNEL_HIDDEN), + + # keywords. Must come before the identifier match + (_w('and'), T.OPERATOR_AND), + (_w('bitand'), T.OPERATOR_BITAND), + (_w('bitor'), T.OPERATOR_BITOR), + (_w('bitxor'), T.OPERATOR_BITXOR), + (_w('constant'), T.STMT_CONSTANT), + (_w('do'), T.PUNCT_DO), + (_w('else'), T.PUNCT_ELSE), + (_w('elseif'), T.PUNCT_ELSEIF), + (_w('end'), T.PUNCT_END), + (_w('endfun'), T.PUNCT_ENDFUN), + (_w('endisr'), T.PUNCT_ENDISR), + (_w('for'), T.STMT_FOR), + (_w('fun'), T.STMT_FUN), + (_w('if'), T.STMT_IF), + (_w('in'), T.PUNCT_IN), + (_w('isr'), T.STMT_ISR), + (_w('let'), T.STMT_LET), + (_w('mut'), T.STORAGE_MUT), + (_w('not'), T.OPERATOR_NOT), + (_w('or'), T.OPERATOR_OR), + (_w('return'), T.STMT_RETURN), + (_w('stash'), T.STORAGE_STASH), + (_w('then'), T.PUNCT_THEN), + (_w('to'), T.PUNCT_TO), + (_w('use'), T.STMT_USE), + (_w('while'), T.STMT_WHILE), + + # Numeric tokens. Must come before the word match + (r'\d[^\s{}]*'.format(specials), T.NUMERIC), + + # Identifiers. Matches a letter, followed by zero or more non-token-ending + # characters. As written, this will actually match numbers as well, but + # because that one is run first we don't have to worry about that. + (r'\w[^\s{}]*'.format(specials), T.IDENTIFIER), + + # comment opener. When the lexer comes back, it will be in comment mode + (Mode.NORMAL, re.escape('/*'), T.COMMENT_OPEN, ReStream.CHANNEL_HIDDEN), + + # comment delimiers, but for comment mode. + (Mode.COMMENT, re.escape('/*'), T.COMMENT_OPEN, ReStream.CHANNEL_HIDDEN), + (Mode.COMMENT, re.escape('*/'), T.COMMENT_CLOSE, ReStream.CHANNEL_HIDDEN), + + # This is necessary because the next pattern matches up to, but not + # including, the newline; however, it will happily match zero characters, + # causing an infinite loop. This matches that last newline. + (Mode.COMMENT, r'\n', T.COMMENT_TEXT, ReStream.CHANNEL_HIDDEN), + + # Matches either to the next comment-control token, or the end of the line, + # whichever happens first. + (Mode.COMMENT, r'.*?(?=\/\*|\*\/|$)', T.COMMENT_TEXT, + ReStream.CHANNEL_HIDDEN), + + # String delimiter. When the lexer comes back, it will be in string mode + (re.escape('"'), T.STRING_DELIM), + + # String control tokens + (Mode.STRING, r'\\.', T.STRING_ESCAPE), + (Mode.STRING, re.escape('"'), T.STRING_DELIM), + + # Matches non-special text inside a string. The newline-matching pattern is + # for the same reason as for comments. + (Mode.STRING, r'\n', T.STRING), + (Mode.STRING, r'.*?(?=\\|"|$)', T.STRING), + + # operators & punctuation. These must be ordered such that if A is a prefix + # of B, then B comes before A. The easiest way to do this is to order them + # by length. + (re.escape('->'), T.PUNCT_ARROWR), + (re.escape('>>'), T.OPERATOR_SHR), + (re.escape('<<'), T.OPERATOR_SHL), + (re.escape('!='), T.OPERATOR_NE), + (re.escape('=='), T.OPERATOR_EQ), + (re.escape('<='), T.OPERATOR_LE), + (re.escape('>='), T.OPERATOR_GE), + (re.escape('+='), T.OPERATOR_ASSIGN_INC), + (re.escape('-='), T.OPERATOR_ASSIGN_DEC), + (re.escape('+'), T.OPERATOR_PLUS), + (re.escape('-'), T.OPERATOR_MINUS), + (re.escape('*'), T.OPERATOR_TIMES), + (re.escape('/'), T.OPERATOR_DIVIDE), + (re.escape('<'), T.OPERATOR_LT), + (re.escape('>'), T.OPERATOR_GT), + (re.escape('='), T.OPERATOR_ASSIGN), + (re.escape('.'), T.OPERATOR_DOT), + (re.escape('@'), T.OPERATOR_DEREF), + (re.escape('&'), T.OPERATOR_REF), + (re.escape(':'), T.PUNCT_COLON), + (re.escape(';'), T.PUNCT_SEMICOLON), + (re.escape(','), T.PUNCT_COMMA), + (re.escape('('), T.PAREN_OPEN), + (re.escape(')'), T.PAREN_CLOSE), + (re.escape('['), T.BRACKET_OPEN), + (re.escape(']'), T.BRACKET_CLOSE), + (re.escape('{'), T.BRACE_OPEN), + (re.escape('}'), T.BRACE_CLOSE), + + # If we fail to match anything, consume one character, and move on. + (r'.', T.MYSTERY), +]) + + +grammar = Grammar('start', [T.EOF], [ + Rule('alist_inner', ['expr']), + Rule('alist_inner', ['alist_inner', T.PUNCT_COMMA, 'expr']), + Rule('alist', []), + Rule('alist', ['alist_inner']), + + Rule('member', [T.IDENTIFIER]), + + Rule('expr', [T.PAREN_OPEN, 'expr', T.PAREN_CLOSE], prec=P.PARENTHESES), + Rule('expr', ['expr', T.OPERATOR_DOT, 'member'], prec=P.MEMBERS), + Rule('expr', ['expr', T.BRACKET_OPEN, 'expr', T.BRACKET_CLOSE], + prec=P.SUBSCRIPTS), + Rule('expr', ['expr', T.PAREN_OPEN, 'alist', T.PAREN_CLOSE], prec=P.CALLS), + Rule('expr', [(T.OPERATOR_DEREF, + T.OPERATOR_MINUS, + T.OPERATOR_BITNOT), 'expr'], + prec=P.PREFIX_UNARY, + rassoc=True), + Rule('expr', ['expr', T.OPERATOR_BITAND, 'expr'], prec=P.BITAND), + Rule('expr', ['expr', T.OPERATOR_BITOR, 'expr'], prec=P.BITOR), + Rule('expr', ['expr', T.OPERATOR_BITXOR, 'expr'], prec=P.BITXOR), + Rule('expr', ['expr', (T.OPERATOR_SHL, + T.OPERATOR_SHR), 'expr'], prec=P.BITSHIFTS), + Rule('expr', ['expr', (T.OPERATOR_TIMES, + T.OPERATOR_DIVIDE), 'expr'], prec=P.PRODUCTS), + Rule('expr', ['expr', (T.OPERATOR_PLUS, + T.OPERATOR_MINUS), 'expr'], prec=P.SUMS), + Rule('expr', ['expr', (T.OPERATOR_EQ, T.OPERATOR_NE, + T.OPERATOR_LE, T.OPERATOR_GE, + T.OPERATOR_LT, T.OPERATOR_GT), 'expr'], + prec=P.COMPARISONS), + Rule('expr', [(T.NUMERIC, T.IDENTIFIER, 'string')], prec=P.LITERALS), + + Rule('array', [T.BRACKET_OPEN, 'alist', T.BRACKET_CLOSE]), + + Rule('string', [T.STRING_DELIM, 'string_inner', T.STRING_DELIM], + prec=P.LITERALS), + Rule('string_inner', [], mode=Mode.STRING), + Rule('string_inner', ['string_inner', (T.STRING, T.STRING_ESCAPE)], + mode=Mode.STRING), + + Rule('storage', [], prec=P.STORAGE), + Rule('storage', [(T.STORAGE_MUT, T.STORAGE_STASH)]), + + Rule('range_to', ['expr', T.PUNCT_TO, 'expr']), + + Rule('type_id', [T.IDENTIFIER]), + Rule('type_id', [ + T.OPERATOR_REF, T.BRACKET_OPEN, + 'storage', 'type_id', T.BRACKET_CLOSE], prec=P.TYPES), + Rule('type_id', [T.OPERATOR_REF, 'storage', 'type_id']), + Rule('type_id', [T.BRACKET_OPEN, 'storage', 'type_id', T.PUNCT_SEMICOLON, + ('expr', 'range_to'), T.BRACKET_CLOSE]), + + Rule('declaration', [T.IDENTIFIER, T.PUNCT_COLON, 'type_id']), + + Rule('stmt_constant', [T.STMT_CONSTANT, 'declaration', + T.OPERATOR_ASSIGN, ('expr', 'array')], + prec=P.STATEMENTS), + + Rule('stmt_use', [T.STMT_USE, T.IDENTIFIER]), + + Rule('stmt_let', [T.STMT_LET, 'storage', 'declaration', + T.OPERATOR_ASSIGN, ('expr', 'array')], + prec=P.STATEMENTS), + + Rule('do_block', [T.PUNCT_DO, 'block', T.PUNCT_END]), + + Rule('stmt_while', [T.STMT_WHILE, 'expr', 'do_block']), + + Rule('stmt_for', [T.STMT_FOR, 'declaration', + T.PUNCT_IN, ('range_to', 'expr'), 'do_block']), + + Rule('branch_else_if', [T.PUNCT_ELSEIF, 'expr', T.PUNCT_THEN, 'block']), + Rule('branch_else', [T.PUNCT_ELSE, 'block']), + Rule('branch_else_ifs', ['branch_else_ifs', 'branch_else_if']), + Rule('branch_else_ifs', ['branch_else_if']), + Rule('stmt_if', [T.STMT_IF, 'expr', T.PUNCT_THEN, 'block', T.PUNCT_END]), + Rule('stmt_if', [T.STMT_IF, 'expr', T.PUNCT_THEN, 'block', + 'branch_else', T.PUNCT_END]), + Rule('stmt_if', [T.STMT_IF, 'expr', T.PUNCT_THEN, 'block', + 'branch_else_ifs', 'branch_else', T.PUNCT_END]), + + Rule('stmt_isr', [T.STMT_ISR, T.IDENTIFIER, 'block', T.PUNCT_ENDISR]), + + Rule('plist', []), + Rule('plist', ['plist_inner']), + Rule('plist_inner', ['declaration']), + Rule('plist_inner', ['plist_inner', T.PUNCT_COMMA, 'declaration']), + Rule('stmt_fun', [T.STMT_FUN, T.IDENTIFIER, + T.PAREN_OPEN, 'plist', T.PAREN_CLOSE, + 'block', T.PUNCT_ENDFUN]), + Rule('stmt_fun', [T.STMT_FUN, T.IDENTIFIER, + T.PAREN_OPEN, 'plist', T.PAREN_CLOSE, + T.PUNCT_ARROWR, 'type_id', + 'block', T.PUNCT_ENDFUN]), + + Rule('stmt_return', [T.STMT_RETURN], prec=P.STATEMENTS), + Rule('stmt_return', [T.STMT_RETURN, 'expr'], prec=P.RETURN_VALUE), + + Rule('stmt_assign', ['expr', (T.OPERATOR_ASSIGN, + T.OPERATOR_ASSIGN_INC, + T.OPERATOR_ASSIGN_DEC), 'expr'], + prec=P.ASSIGNMENTS), + + Rule('block', []), + Rule('block', ['block', ('stmt_constant', + 'stmt_for', + 'stmt_if', + 'stmt_let', + 'stmt_return', + 'stmt_while', + 'stmt_assign', + 'expr')], prec=P.STATEMENTS), + + Rule('unit', []), + Rule('unit', ['unit', ('stmt_constant', + 'stmt_isr', + 'stmt_let', + 'stmt_use', + 'stmt_fun')]), + + Rule('start', ['unit']), +]) + +comment_grammar = Grammar('start', [T.COMMENT_CLOSE, T.WHITESPACE, T.EOF], [ + # left-recursive definition of a comment + Rule('comment_inner', [], mode=Mode.COMMENT), + Rule('comment_inner', ['comment_inner', + (T.COMMENT_TEXT, 'comment_nested')], + mode=Mode.COMMENT), + + # we have to define a rule for nested comments separately to avoid + # mode/mode conflicts + Rule('comment_nested', [T.COMMENT_OPEN, 'comment_inner', T.COMMENT_CLOSE], + mode=Mode.COMMENT), + + # enter/exit mode split + Rule('comment', [T.COMMENT_OPEN, 'comment_inner', T.COMMENT_CLOSE]), + + # the empty rule handles whitespace + Rule('hidden', []), + Rule('hidden', ['comment']), + Rule('start', ['hidden']), +]) + +parse = grammar.build_parser({ + ReStream.CHANNEL_HIDDEN: comment_grammar, +}) diff --git a/jeff65/gold/grammar/Gold.g4 b/jeff65/gold/grammar/Gold.g4 deleted file mode 100644 index bcc4f96..0000000 --- a/jeff65/gold/grammar/Gold.g4 +++ /dev/null @@ -1,135 +0,0 @@ -parser grammar Gold; - -tokens { - // simple tokens - IDENTIFIER, NUMERIC, STRING, - - // arithmetic operators - OPERATOR_PLUS, OPERATOR_MINUS, OPERATOR_TIMES, OPERATOR_DIVIDE, - - // logical operators - OPERATOR_NOT, OPERATOR_AND, OPERATOR_OR, - - // bitwise operators - OPERATOR_SHR, OPERATOR_SHL, OPERATOR_BITNOT, OPERATOR_BITAND, - OPERATOR_BITOR, OPERATOR_BITXOR, - - // comparison operators - OPERATOR_NE, OPERATOR_EQ, OPERATOR_LE, OPERATOR_GE, OPERATOR_LT, - OPERATOR_GT, - - // assignment operators - OPERATOR_ASSIGN, OPERATOR_ASSIGN_INC, OPERATOR_ASSIGN_DEC, - - // member access operators - OPERATOR_DOT, - - // pointer operators - OPERATOR_DEREF, OPERATOR_REF, - - // statement keywords - STMT_CONSTANT, STMT_FOR, STMT_FUN, STMT_IF, STMT_ISR, STMT_LET, STMT_RETURN, - STMT_USE, STMT_WHILE, - - // storage classes - STORAGE_MUT, STORAGE_STASH, - - // assorted punctuation - PUNCT_DO, PUNCT_ELSE, PUNCT_ELSEIF, PUNCT_END, PUNCT_ENDFUN, PUNCT_ENDISR, - PUNCT_IN, PUNCT_THEN, PUNCT_TO, PUNCT_COLON, PUNCT_SEMICOLON, PUNCT_COMMA, - PUNCT_ARROWR, - - // delimiters - PAREN_OPEN, PAREN_CLOSE, BRACKET_OPEN, BRACKET_CLOSE, BRACE_OPEN, - BRACE_CLOSE, - - // dummy tokens for internal lexer use. - STRING_DELIM, COMMENT_OPEN, COMMENT_CLOSE, COMMENT_TEXT, WHITESPACE, MYSTERY -} - -expr : PAREN_OPEN expr PAREN_CLOSE # ExprParen - | expr OPERATOR_DOT member=IDENTIFIER # ExprMember - | expr BRACKET_OPEN expr BRACKET_CLOSE # ExprIndex - | fun=expr PAREN_OPEN (args+=expr (PUNCT_COMMA args+=expr)*)? PAREN_CLOSE # ExprFunCall - | OPERATOR_DEREF expr # ExprDeref - | OPERATOR_MINUS expr # ExprNegation - | expr OPERATOR_BITNOT expr # ExprBitNot - | expr OPERATOR_BITAND expr # ExprBitAnd - | expr OPERATOR_BITOR expr # ExprBitOr - | expr OPERATOR_BITXOR expr # ExprBitXor - | expr op=( OPERATOR_SHL | OPERATOR_SHR ) expr # ExprBitShift - | expr op=( OPERATOR_TIMES | OPERATOR_DIVIDE ) expr # ExprProduct - | expr op=( OPERATOR_PLUS | OPERATOR_MINUS ) expr # ExprSum - | expr op=( OPERATOR_EQ | OPERATOR_NE - | OPERATOR_LE | OPERATOR_GE - | OPERATOR_LT | OPERATOR_GT) expr # ExprCompare - | value=NUMERIC # ExprNumber - | name=IDENTIFIER # ExprId - ; - -array : BRACKET_OPEN (expr (PUNCT_COMMA expr)*)? BRACKET_CLOSE ; - -string : (s+=STRING)+ ; - -storage : storage_class=(STORAGE_MUT | STORAGE_STASH) ; - -typeId : name=IDENTIFIER # TypePrimitive - | OPERATOR_REF BRACKET_OPEN storage? typeId BRACKET_CLOSE # TypeSlice - | OPERATOR_REF storage? typeId # TypePointer - | BRACKET_OPEN storage? typeId PUNCT_SEMICOLON - (expr | rangeTo) BRACKET_CLOSE # TypeArray - ; - -rangeTo : expr PUNCT_TO expr ; - -declaration : name=IDENTIFIER PUNCT_COLON typeId ; - -stmtConstant : STMT_CONSTANT declaration OPERATOR_ASSIGN ( expr | array ) ; - -stmtUse : STMT_USE unitId=IDENTIFIER ; - -stmtLet : STMT_LET storage? declaration - OPERATOR_ASSIGN - ( expr | array | string ) ; - -stmtWhile : STMT_WHILE expr PUNCT_DO block PUNCT_END ; - -stmtFor : STMT_FOR declaration PUNCT_IN ( rangeTo | expr ) - PUNCT_DO block PUNCT_END ; - -stmtIf : STMT_IF expr PUNCT_THEN block - ( PUNCT_ELSEIF block )* - ( PUNCT_ELSE block )? - PUNCT_END ; - -stmtIsr : STMT_ISR IDENTIFIER block PUNCT_ENDISR ; - -stmtFun : STMT_FUN name=IDENTIFIER - PAREN_OPEN ( args+=declaration ( PUNCT_COMMA args+=declaration )* )? PAREN_CLOSE - ( PUNCT_ARROWR ret=typeId )? - block - PUNCT_ENDFUN ; - -stmtReturn : STMT_RETURN expr? ; - -stmtAssign : expr OPERATOR_ASSIGN expr # stmtAssignVal - | expr OPERATOR_ASSIGN_INC expr # stmtAssignInc - | expr OPERATOR_ASSIGN_DEC expr # stmtAssignDec - ; - -block : ( stmtConstant - | stmtFor - | stmtIf - | stmtLet - | stmtReturn - | stmtWhile - | stmtAssign // these need to be last - | expr - )* ; - -unit : ( stmtConstant - | stmtIsr - | stmtLet - | stmtUse - | stmtFun - )* EOF ; \ No newline at end of file diff --git a/jeff65/gold/grammar/Gold.py b/jeff65/gold/grammar/Gold.py deleted file mode 100644 index 73dced1..0000000 --- a/jeff65/gold/grammar/Gold.py +++ /dev/null @@ -1,2580 +0,0 @@ -# Generated from jeff65/gold/grammar/Gold.g4 by ANTLR 4.5.2 -# encoding: utf-8 -from antlr4 import * -from io import StringIO - -def serializedATN(): - with StringIO() as buf: - buf.write("\3\u0430\ud6d1\u8206\uad2d\u4417\uaef1\u8d80\uaadd\3B") - buf.write("\u011c\4\2\t\2\4\3\t\3\4\4\t\4\4\5\t\5\4\6\t\6\4\7\t\7") - buf.write("\4\b\t\b\4\t\t\t\4\n\t\n\4\13\t\13\4\f\t\f\4\r\t\r\4\16") - buf.write("\t\16\4\17\t\17\4\20\t\20\4\21\t\21\4\22\t\22\4\23\t\23") - buf.write("\4\24\t\24\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2") - buf.write("\5\2\64\n\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3") - buf.write("\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2") - buf.write("\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\3\2\7") - buf.write("\2[\n\2\f\2\16\2^\13\2\5\2`\n\2\3\2\7\2c\n\2\f\2\16\2") - buf.write("f\13\2\3\3\3\3\3\3\3\3\7\3l\n\3\f\3\16\3o\13\3\5\3q\n") - buf.write("\3\3\3\3\3\3\4\6\4v\n\4\r\4\16\4w\3\5\3\5\3\6\3\6\3\6") - buf.write("\3\6\5\6\u0080\n\6\3\6\3\6\3\6\3\6\3\6\5\6\u0087\n\6\3") - buf.write("\6\3\6\3\6\5\6\u008c\n\6\3\6\3\6\3\6\3\6\5\6\u0092\n\6") - buf.write("\3\6\3\6\5\6\u0096\n\6\3\7\3\7\3\7\3\7\3\b\3\b\3\b\3\b") - buf.write("\3\t\3\t\3\t\3\t\3\t\5\t\u00a5\n\t\3\n\3\n\3\n\3\13\3") - buf.write("\13\5\13\u00ac\n\13\3\13\3\13\3\13\3\13\3\13\5\13\u00b3") - buf.write("\n\13\3\f\3\f\3\f\3\f\3\f\3\f\3\r\3\r\3\r\3\r\3\r\5\r") - buf.write("\u00c0\n\r\3\r\3\r\3\r\3\r\3\16\3\16\3\16\3\16\3\16\3") - buf.write("\16\7\16\u00cc\n\16\f\16\16\16\u00cf\13\16\3\16\3\16\5") - buf.write("\16\u00d3\n\16\3\16\3\16\3\17\3\17\3\17\3\17\3\17\3\20") - buf.write("\3\20\3\20\3\20\3\20\3\20\7\20\u00e2\n\20\f\20\16\20\u00e5") - buf.write("\13\20\5\20\u00e7\n\20\3\20\3\20\3\20\5\20\u00ec\n\20") - buf.write("\3\20\3\20\3\20\3\21\3\21\5\21\u00f3\n\21\3\22\3\22\3") - buf.write("\22\3\22\3\22\3\22\3\22\3\22\3\22\3\22\3\22\3\22\5\22") - buf.write("\u0101\n\22\3\23\3\23\3\23\3\23\3\23\3\23\3\23\3\23\7") - buf.write("\23\u010b\n\23\f\23\16\23\u010e\13\23\3\24\3\24\3\24\3") - buf.write("\24\3\24\7\24\u0115\n\24\f\24\16\24\u0118\13\24\3\24\3") - buf.write("\24\3\24\2\3\2\25\2\4\6\b\n\f\16\20\22\24\26\30\32\34") - buf.write("\36 \"$&\2\7\3\2\r\16\3\2\b\t\3\2\6\7\3\2\23\30\3\2()") - buf.write("\u013d\2\63\3\2\2\2\4g\3\2\2\2\6u\3\2\2\2\by\3\2\2\2\n") - buf.write("\u0095\3\2\2\2\f\u0097\3\2\2\2\16\u009b\3\2\2\2\20\u009f") - buf.write("\3\2\2\2\22\u00a6\3\2\2\2\24\u00a9\3\2\2\2\26\u00b4\3") - buf.write("\2\2\2\30\u00ba\3\2\2\2\32\u00c5\3\2\2\2\34\u00d6\3\2") - buf.write("\2\2\36\u00db\3\2\2\2 \u00f0\3\2\2\2\"\u0100\3\2\2\2$") - buf.write("\u010c\3\2\2\2&\u0116\3\2\2\2()\b\2\1\2)*\7\35\2\2*\64") - buf.write("\5\2\2\16+,\7\7\2\2,\64\5\2\2\r-.\7\67\2\2./\5\2\2\2/") - buf.write("\60\78\2\2\60\64\3\2\2\2\61\64\7\4\2\2\62\64\7\3\2\2\63") - buf.write("(\3\2\2\2\63+\3\2\2\2\63-\3\2\2\2\63\61\3\2\2\2\63\62") - buf.write("\3\2\2\2\64d\3\2\2\2\65\66\f\f\2\2\66\67\7\17\2\2\67c") - buf.write("\5\2\2\r89\f\13\2\29:\7\20\2\2:c\5\2\2\f;<\f\n\2\2<=\7") - buf.write("\21\2\2=c\5\2\2\13>?\f\t\2\2?@\7\22\2\2@c\5\2\2\nAB\f") - buf.write("\b\2\2BC\t\2\2\2Cc\5\2\2\tDE\f\7\2\2EF\t\3\2\2Fc\5\2\2") - buf.write("\bGH\f\6\2\2HI\t\4\2\2Ic\5\2\2\7JK\f\5\2\2KL\t\5\2\2L") - buf.write("c\5\2\2\6MN\f\21\2\2NO\7\34\2\2Oc\7\3\2\2PQ\f\20\2\2Q") - buf.write("R\79\2\2RS\5\2\2\2ST\7:\2\2Tc\3\2\2\2UV\f\17\2\2V_\7\67") - buf.write("\2\2W\\\5\2\2\2XY\7\65\2\2Y[\5\2\2\2ZX\3\2\2\2[^\3\2\2") - buf.write("\2\\Z\3\2\2\2\\]\3\2\2\2]`\3\2\2\2^\\\3\2\2\2_W\3\2\2") - buf.write("\2_`\3\2\2\2`a\3\2\2\2ac\78\2\2b\65\3\2\2\2b8\3\2\2\2") - buf.write("b;\3\2\2\2b>\3\2\2\2bA\3\2\2\2bD\3\2\2\2bG\3\2\2\2bJ\3") - buf.write("\2\2\2bM\3\2\2\2bP\3\2\2\2bU\3\2\2\2cf\3\2\2\2db\3\2\2") - buf.write("\2de\3\2\2\2e\3\3\2\2\2fd\3\2\2\2gp\79\2\2hm\5\2\2\2i") - buf.write("j\7\65\2\2jl\5\2\2\2ki\3\2\2\2lo\3\2\2\2mk\3\2\2\2mn\3") - buf.write("\2\2\2nq\3\2\2\2om\3\2\2\2ph\3\2\2\2pq\3\2\2\2qr\3\2\2") - buf.write("\2rs\7:\2\2s\5\3\2\2\2tv\7\5\2\2ut\3\2\2\2vw\3\2\2\2w") - buf.write("u\3\2\2\2wx\3\2\2\2x\7\3\2\2\2yz\t\6\2\2z\t\3\2\2\2{\u0096") - buf.write("\7\3\2\2|}\7\36\2\2}\177\79\2\2~\u0080\5\b\5\2\177~\3") - buf.write("\2\2\2\177\u0080\3\2\2\2\u0080\u0081\3\2\2\2\u0081\u0082") - buf.write("\5\n\6\2\u0082\u0083\7:\2\2\u0083\u0096\3\2\2\2\u0084") - buf.write("\u0086\7\36\2\2\u0085\u0087\5\b\5\2\u0086\u0085\3\2\2") - buf.write("\2\u0086\u0087\3\2\2\2\u0087\u0088\3\2\2\2\u0088\u0096") - buf.write("\5\n\6\2\u0089\u008b\79\2\2\u008a\u008c\5\b\5\2\u008b") - buf.write("\u008a\3\2\2\2\u008b\u008c\3\2\2\2\u008c\u008d\3\2\2\2") - buf.write("\u008d\u008e\5\n\6\2\u008e\u0091\7\64\2\2\u008f\u0092") - buf.write("\5\2\2\2\u0090\u0092\5\f\7\2\u0091\u008f\3\2\2\2\u0091") - buf.write("\u0090\3\2\2\2\u0092\u0093\3\2\2\2\u0093\u0094\7:\2\2") - buf.write("\u0094\u0096\3\2\2\2\u0095{\3\2\2\2\u0095|\3\2\2\2\u0095") - buf.write("\u0084\3\2\2\2\u0095\u0089\3\2\2\2\u0096\13\3\2\2\2\u0097") - buf.write("\u0098\5\2\2\2\u0098\u0099\7\62\2\2\u0099\u009a\5\2\2") - buf.write("\2\u009a\r\3\2\2\2\u009b\u009c\7\3\2\2\u009c\u009d\7\63") - buf.write("\2\2\u009d\u009e\5\n\6\2\u009e\17\3\2\2\2\u009f\u00a0") - buf.write("\7\37\2\2\u00a0\u00a1\5\16\b\2\u00a1\u00a4\7\31\2\2\u00a2") - buf.write("\u00a5\5\2\2\2\u00a3\u00a5\5\4\3\2\u00a4\u00a2\3\2\2\2") - buf.write("\u00a4\u00a3\3\2\2\2\u00a5\21\3\2\2\2\u00a6\u00a7\7&\2") - buf.write("\2\u00a7\u00a8\7\3\2\2\u00a8\23\3\2\2\2\u00a9\u00ab\7") - buf.write("$\2\2\u00aa\u00ac\5\b\5\2\u00ab\u00aa\3\2\2\2\u00ab\u00ac") - buf.write("\3\2\2\2\u00ac\u00ad\3\2\2\2\u00ad\u00ae\5\16\b\2\u00ae") - buf.write("\u00b2\7\31\2\2\u00af\u00b3\5\2\2\2\u00b0\u00b3\5\4\3") - buf.write("\2\u00b1\u00b3\5\6\4\2\u00b2\u00af\3\2\2\2\u00b2\u00b0") - buf.write("\3\2\2\2\u00b2\u00b1\3\2\2\2\u00b3\25\3\2\2\2\u00b4\u00b5") - buf.write("\7\'\2\2\u00b5\u00b6\5\2\2\2\u00b6\u00b7\7*\2\2\u00b7") - buf.write("\u00b8\5$\23\2\u00b8\u00b9\7-\2\2\u00b9\27\3\2\2\2\u00ba") - buf.write("\u00bb\7 \2\2\u00bb\u00bc\5\16\b\2\u00bc\u00bf\7\60\2") - buf.write("\2\u00bd\u00c0\5\f\7\2\u00be\u00c0\5\2\2\2\u00bf\u00bd") - buf.write("\3\2\2\2\u00bf\u00be\3\2\2\2\u00c0\u00c1\3\2\2\2\u00c1") - buf.write("\u00c2\7*\2\2\u00c2\u00c3\5$\23\2\u00c3\u00c4\7-\2\2\u00c4") - buf.write("\31\3\2\2\2\u00c5\u00c6\7\"\2\2\u00c6\u00c7\5\2\2\2\u00c7") - buf.write("\u00c8\7\61\2\2\u00c8\u00cd\5$\23\2\u00c9\u00ca\7,\2\2") - buf.write("\u00ca\u00cc\5$\23\2\u00cb\u00c9\3\2\2\2\u00cc\u00cf\3") - buf.write("\2\2\2\u00cd\u00cb\3\2\2\2\u00cd\u00ce\3\2\2\2\u00ce\u00d2") - buf.write("\3\2\2\2\u00cf\u00cd\3\2\2\2\u00d0\u00d1\7+\2\2\u00d1") - buf.write("\u00d3\5$\23\2\u00d2\u00d0\3\2\2\2\u00d2\u00d3\3\2\2\2") - buf.write("\u00d3\u00d4\3\2\2\2\u00d4\u00d5\7-\2\2\u00d5\33\3\2\2") - buf.write("\2\u00d6\u00d7\7#\2\2\u00d7\u00d8\7\3\2\2\u00d8\u00d9") - buf.write("\5$\23\2\u00d9\u00da\7/\2\2\u00da\35\3\2\2\2\u00db\u00dc") - buf.write("\7!\2\2\u00dc\u00dd\7\3\2\2\u00dd\u00e6\7\67\2\2\u00de") - buf.write("\u00e3\5\16\b\2\u00df\u00e0\7\65\2\2\u00e0\u00e2\5\16") - buf.write("\b\2\u00e1\u00df\3\2\2\2\u00e2\u00e5\3\2\2\2\u00e3\u00e1") - buf.write("\3\2\2\2\u00e3\u00e4\3\2\2\2\u00e4\u00e7\3\2\2\2\u00e5") - buf.write("\u00e3\3\2\2\2\u00e6\u00de\3\2\2\2\u00e6\u00e7\3\2\2\2") - buf.write("\u00e7\u00e8\3\2\2\2\u00e8\u00eb\78\2\2\u00e9\u00ea\7") - buf.write("\66\2\2\u00ea\u00ec\5\n\6\2\u00eb\u00e9\3\2\2\2\u00eb") - buf.write("\u00ec\3\2\2\2\u00ec\u00ed\3\2\2\2\u00ed\u00ee\5$\23\2") - buf.write("\u00ee\u00ef\7.\2\2\u00ef\37\3\2\2\2\u00f0\u00f2\7%\2") - buf.write("\2\u00f1\u00f3\5\2\2\2\u00f2\u00f1\3\2\2\2\u00f2\u00f3") - buf.write("\3\2\2\2\u00f3!\3\2\2\2\u00f4\u00f5\5\2\2\2\u00f5\u00f6") - buf.write("\7\31\2\2\u00f6\u00f7\5\2\2\2\u00f7\u0101\3\2\2\2\u00f8") - buf.write("\u00f9\5\2\2\2\u00f9\u00fa\7\32\2\2\u00fa\u00fb\5\2\2") - buf.write("\2\u00fb\u0101\3\2\2\2\u00fc\u00fd\5\2\2\2\u00fd\u00fe") - buf.write("\7\33\2\2\u00fe\u00ff\5\2\2\2\u00ff\u0101\3\2\2\2\u0100") - buf.write("\u00f4\3\2\2\2\u0100\u00f8\3\2\2\2\u0100\u00fc\3\2\2\2") - buf.write("\u0101#\3\2\2\2\u0102\u010b\5\20\t\2\u0103\u010b\5\30") - buf.write("\r\2\u0104\u010b\5\32\16\2\u0105\u010b\5\24\13\2\u0106") - buf.write("\u010b\5 \21\2\u0107\u010b\5\26\f\2\u0108\u010b\5\"\22") - buf.write("\2\u0109\u010b\5\2\2\2\u010a\u0102\3\2\2\2\u010a\u0103") - buf.write("\3\2\2\2\u010a\u0104\3\2\2\2\u010a\u0105\3\2\2\2\u010a") - buf.write("\u0106\3\2\2\2\u010a\u0107\3\2\2\2\u010a\u0108\3\2\2\2") - buf.write("\u010a\u0109\3\2\2\2\u010b\u010e\3\2\2\2\u010c\u010a\3") - buf.write("\2\2\2\u010c\u010d\3\2\2\2\u010d%\3\2\2\2\u010e\u010c") - buf.write("\3\2\2\2\u010f\u0115\5\20\t\2\u0110\u0115\5\34\17\2\u0111") - buf.write("\u0115\5\24\13\2\u0112\u0115\5\22\n\2\u0113\u0115\5\36") - buf.write("\20\2\u0114\u010f\3\2\2\2\u0114\u0110\3\2\2\2\u0114\u0111") - buf.write("\3\2\2\2\u0114\u0112\3\2\2\2\u0114\u0113\3\2\2\2\u0115") - buf.write("\u0118\3\2\2\2\u0116\u0114\3\2\2\2\u0116\u0117\3\2\2\2") - buf.write("\u0117\u0119\3\2\2\2\u0118\u0116\3\2\2\2\u0119\u011a\7") - buf.write("\2\2\3\u011a\'\3\2\2\2\36\63\\_bdmpw\177\u0086\u008b\u0091") - buf.write("\u0095\u00a4\u00ab\u00b2\u00bf\u00cd\u00d2\u00e3\u00e6") - buf.write("\u00eb\u00f2\u0100\u010a\u010c\u0114\u0116") - return buf.getvalue() - - -class Gold ( Parser ): - - grammarFileName = "Gold.g4" - - atn = ATNDeserializer().deserialize(serializedATN()) - - decisionsToDFA = [ DFA(ds, i) for i, ds in enumerate(atn.decisionToState) ] - - sharedContextCache = PredictionContextCache() - - literalNames = [ ] - - symbolicNames = [ "", "IDENTIFIER", "NUMERIC", "STRING", "OPERATOR_PLUS", - "OPERATOR_MINUS", "OPERATOR_TIMES", "OPERATOR_DIVIDE", - "OPERATOR_NOT", "OPERATOR_AND", "OPERATOR_OR", "OPERATOR_SHR", - "OPERATOR_SHL", "OPERATOR_BITNOT", "OPERATOR_BITAND", - "OPERATOR_BITOR", "OPERATOR_BITXOR", "OPERATOR_NE", - "OPERATOR_EQ", "OPERATOR_LE", "OPERATOR_GE", "OPERATOR_LT", - "OPERATOR_GT", "OPERATOR_ASSIGN", "OPERATOR_ASSIGN_INC", - "OPERATOR_ASSIGN_DEC", "OPERATOR_DOT", "OPERATOR_DEREF", - "OPERATOR_REF", "STMT_CONSTANT", "STMT_FOR", "STMT_FUN", - "STMT_IF", "STMT_ISR", "STMT_LET", "STMT_RETURN", - "STMT_USE", "STMT_WHILE", "STORAGE_MUT", "STORAGE_STASH", - "PUNCT_DO", "PUNCT_ELSE", "PUNCT_ELSEIF", "PUNCT_END", - "PUNCT_ENDFUN", "PUNCT_ENDISR", "PUNCT_IN", "PUNCT_THEN", - "PUNCT_TO", "PUNCT_COLON", "PUNCT_SEMICOLON", "PUNCT_COMMA", - "PUNCT_ARROWR", "PAREN_OPEN", "PAREN_CLOSE", "BRACKET_OPEN", - "BRACKET_CLOSE", "BRACE_OPEN", "BRACE_CLOSE", "STRING_DELIM", - "COMMENT_OPEN", "COMMENT_CLOSE", "COMMENT_TEXT", "WHITESPACE", - "MYSTERY" ] - - RULE_expr = 0 - RULE_array = 1 - RULE_string = 2 - RULE_storage = 3 - RULE_typeId = 4 - RULE_rangeTo = 5 - RULE_declaration = 6 - RULE_stmtConstant = 7 - RULE_stmtUse = 8 - RULE_stmtLet = 9 - RULE_stmtWhile = 10 - RULE_stmtFor = 11 - RULE_stmtIf = 12 - RULE_stmtIsr = 13 - RULE_stmtFun = 14 - RULE_stmtReturn = 15 - RULE_stmtAssign = 16 - RULE_block = 17 - RULE_unit = 18 - - ruleNames = [ "expr", "array", "string", "storage", "typeId", "rangeTo", - "declaration", "stmtConstant", "stmtUse", "stmtLet", - "stmtWhile", "stmtFor", "stmtIf", "stmtIsr", "stmtFun", - "stmtReturn", "stmtAssign", "block", "unit" ] - - EOF = Token.EOF - IDENTIFIER=1 - NUMERIC=2 - STRING=3 - OPERATOR_PLUS=4 - OPERATOR_MINUS=5 - OPERATOR_TIMES=6 - OPERATOR_DIVIDE=7 - OPERATOR_NOT=8 - OPERATOR_AND=9 - OPERATOR_OR=10 - OPERATOR_SHR=11 - OPERATOR_SHL=12 - OPERATOR_BITNOT=13 - OPERATOR_BITAND=14 - OPERATOR_BITOR=15 - OPERATOR_BITXOR=16 - OPERATOR_NE=17 - OPERATOR_EQ=18 - OPERATOR_LE=19 - OPERATOR_GE=20 - OPERATOR_LT=21 - OPERATOR_GT=22 - OPERATOR_ASSIGN=23 - OPERATOR_ASSIGN_INC=24 - OPERATOR_ASSIGN_DEC=25 - OPERATOR_DOT=26 - OPERATOR_DEREF=27 - OPERATOR_REF=28 - STMT_CONSTANT=29 - STMT_FOR=30 - STMT_FUN=31 - STMT_IF=32 - STMT_ISR=33 - STMT_LET=34 - STMT_RETURN=35 - STMT_USE=36 - STMT_WHILE=37 - STORAGE_MUT=38 - STORAGE_STASH=39 - PUNCT_DO=40 - PUNCT_ELSE=41 - PUNCT_ELSEIF=42 - PUNCT_END=43 - PUNCT_ENDFUN=44 - PUNCT_ENDISR=45 - PUNCT_IN=46 - PUNCT_THEN=47 - PUNCT_TO=48 - PUNCT_COLON=49 - PUNCT_SEMICOLON=50 - PUNCT_COMMA=51 - PUNCT_ARROWR=52 - PAREN_OPEN=53 - PAREN_CLOSE=54 - BRACKET_OPEN=55 - BRACKET_CLOSE=56 - BRACE_OPEN=57 - BRACE_CLOSE=58 - STRING_DELIM=59 - COMMENT_OPEN=60 - COMMENT_CLOSE=61 - COMMENT_TEXT=62 - WHITESPACE=63 - MYSTERY=64 - - def __init__(self, input:TokenStream): - super().__init__(input) - self.checkVersion("4.5.2") - self._interp = ParserATNSimulator(self, self.atn, self.decisionsToDFA, self.sharedContextCache) - self._predicates = None - - - - class ExprContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - - def getRuleIndex(self): - return Gold.RULE_expr - - - def copyFrom(self, ctx:ParserRuleContext): - super().copyFrom(ctx) - - - class ExprParenContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.copyFrom(ctx) - - def PAREN_OPEN(self): - return self.getToken(Gold.PAREN_OPEN, 0) - def expr(self): - return self.getTypedRuleContext(Gold.ExprContext,0) - - def PAREN_CLOSE(self): - return self.getToken(Gold.PAREN_CLOSE, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprParen" ): - listener.enterExprParen(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprParen" ): - listener.exitExprParen(self) - - - class ExprBitXorContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.copyFrom(ctx) - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - def OPERATOR_BITXOR(self): - return self.getToken(Gold.OPERATOR_BITXOR, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprBitXor" ): - listener.enterExprBitXor(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprBitXor" ): - listener.exitExprBitXor(self) - - - class ExprSumContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.op = None # Token - self.copyFrom(ctx) - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - def OPERATOR_PLUS(self): - return self.getToken(Gold.OPERATOR_PLUS, 0) - def OPERATOR_MINUS(self): - return self.getToken(Gold.OPERATOR_MINUS, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprSum" ): - listener.enterExprSum(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprSum" ): - listener.exitExprSum(self) - - - class ExprIndexContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.copyFrom(ctx) - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - def BRACKET_OPEN(self): - return self.getToken(Gold.BRACKET_OPEN, 0) - def BRACKET_CLOSE(self): - return self.getToken(Gold.BRACKET_CLOSE, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprIndex" ): - listener.enterExprIndex(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprIndex" ): - listener.exitExprIndex(self) - - - class ExprBitShiftContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.op = None # Token - self.copyFrom(ctx) - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - def OPERATOR_SHL(self): - return self.getToken(Gold.OPERATOR_SHL, 0) - def OPERATOR_SHR(self): - return self.getToken(Gold.OPERATOR_SHR, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprBitShift" ): - listener.enterExprBitShift(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprBitShift" ): - listener.exitExprBitShift(self) - - - class ExprNegationContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.copyFrom(ctx) - - def OPERATOR_MINUS(self): - return self.getToken(Gold.OPERATOR_MINUS, 0) - def expr(self): - return self.getTypedRuleContext(Gold.ExprContext,0) - - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprNegation" ): - listener.enterExprNegation(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprNegation" ): - listener.exitExprNegation(self) - - - class ExprBitOrContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.copyFrom(ctx) - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - def OPERATOR_BITOR(self): - return self.getToken(Gold.OPERATOR_BITOR, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprBitOr" ): - listener.enterExprBitOr(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprBitOr" ): - listener.exitExprBitOr(self) - - - class ExprDerefContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.copyFrom(ctx) - - def OPERATOR_DEREF(self): - return self.getToken(Gold.OPERATOR_DEREF, 0) - def expr(self): - return self.getTypedRuleContext(Gold.ExprContext,0) - - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprDeref" ): - listener.enterExprDeref(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprDeref" ): - listener.exitExprDeref(self) - - - class ExprProductContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.op = None # Token - self.copyFrom(ctx) - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - def OPERATOR_TIMES(self): - return self.getToken(Gold.OPERATOR_TIMES, 0) - def OPERATOR_DIVIDE(self): - return self.getToken(Gold.OPERATOR_DIVIDE, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprProduct" ): - listener.enterExprProduct(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprProduct" ): - listener.exitExprProduct(self) - - - class ExprCompareContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.op = None # Token - self.copyFrom(ctx) - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - def OPERATOR_EQ(self): - return self.getToken(Gold.OPERATOR_EQ, 0) - def OPERATOR_NE(self): - return self.getToken(Gold.OPERATOR_NE, 0) - def OPERATOR_LE(self): - return self.getToken(Gold.OPERATOR_LE, 0) - def OPERATOR_GE(self): - return self.getToken(Gold.OPERATOR_GE, 0) - def OPERATOR_LT(self): - return self.getToken(Gold.OPERATOR_LT, 0) - def OPERATOR_GT(self): - return self.getToken(Gold.OPERATOR_GT, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprCompare" ): - listener.enterExprCompare(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprCompare" ): - listener.exitExprCompare(self) - - - class ExprFunCallContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.fun = None # ExprContext - self._expr = None # ExprContext - self.args = list() # of ExprContexts - self.copyFrom(ctx) - - def PAREN_OPEN(self): - return self.getToken(Gold.PAREN_OPEN, 0) - def PAREN_CLOSE(self): - return self.getToken(Gold.PAREN_CLOSE, 0) - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - def PUNCT_COMMA(self, i:int=None): - if i is None: - return self.getTokens(Gold.PUNCT_COMMA) - else: - return self.getToken(Gold.PUNCT_COMMA, i) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprFunCall" ): - listener.enterExprFunCall(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprFunCall" ): - listener.exitExprFunCall(self) - - - class ExprNumberContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.value = None # Token - self.copyFrom(ctx) - - def NUMERIC(self): - return self.getToken(Gold.NUMERIC, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprNumber" ): - listener.enterExprNumber(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprNumber" ): - listener.exitExprNumber(self) - - - class ExprBitAndContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.copyFrom(ctx) - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - def OPERATOR_BITAND(self): - return self.getToken(Gold.OPERATOR_BITAND, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprBitAnd" ): - listener.enterExprBitAnd(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprBitAnd" ): - listener.exitExprBitAnd(self) - - - class ExprBitNotContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.copyFrom(ctx) - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - def OPERATOR_BITNOT(self): - return self.getToken(Gold.OPERATOR_BITNOT, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprBitNot" ): - listener.enterExprBitNot(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprBitNot" ): - listener.exitExprBitNot(self) - - - class ExprIdContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.name = None # Token - self.copyFrom(ctx) - - def IDENTIFIER(self): - return self.getToken(Gold.IDENTIFIER, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprId" ): - listener.enterExprId(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprId" ): - listener.exitExprId(self) - - - class ExprMemberContext(ExprContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.ExprContext - super().__init__(parser) - self.member = None # Token - self.copyFrom(ctx) - - def expr(self): - return self.getTypedRuleContext(Gold.ExprContext,0) - - def OPERATOR_DOT(self): - return self.getToken(Gold.OPERATOR_DOT, 0) - def IDENTIFIER(self): - return self.getToken(Gold.IDENTIFIER, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterExprMember" ): - listener.enterExprMember(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitExprMember" ): - listener.exitExprMember(self) - - - - def expr(self, _p:int=0): - _parentctx = self._ctx - _parentState = self.state - localctx = Gold.ExprContext(self, self._ctx, _parentState) - _prevctx = localctx - _startState = 0 - self.enterRecursionRule(localctx, 0, self.RULE_expr, _p) - self._la = 0 # Token type - try: - self.enterOuterAlt(localctx, 1) - self.state = 49 - token = self._input.LA(1) - if token in [Gold.OPERATOR_DEREF]: - localctx = Gold.ExprDerefContext(self, localctx) - self._ctx = localctx - _prevctx = localctx - - self.state = 39 - self.match(Gold.OPERATOR_DEREF) - self.state = 40 - self.expr(12) - - elif token in [Gold.OPERATOR_MINUS]: - localctx = Gold.ExprNegationContext(self, localctx) - self._ctx = localctx - _prevctx = localctx - self.state = 41 - self.match(Gold.OPERATOR_MINUS) - self.state = 42 - self.expr(11) - - elif token in [Gold.PAREN_OPEN]: - localctx = Gold.ExprParenContext(self, localctx) - self._ctx = localctx - _prevctx = localctx - self.state = 43 - self.match(Gold.PAREN_OPEN) - self.state = 44 - self.expr(0) - self.state = 45 - self.match(Gold.PAREN_CLOSE) - - elif token in [Gold.NUMERIC]: - localctx = Gold.ExprNumberContext(self, localctx) - self._ctx = localctx - _prevctx = localctx - self.state = 47 - localctx.value = self.match(Gold.NUMERIC) - - elif token in [Gold.IDENTIFIER]: - localctx = Gold.ExprIdContext(self, localctx) - self._ctx = localctx - _prevctx = localctx - self.state = 48 - localctx.name = self.match(Gold.IDENTIFIER) - - else: - raise NoViableAltException(self) - - self._ctx.stop = self._input.LT(-1) - self.state = 98 - self._errHandler.sync(self) - _alt = self._interp.adaptivePredict(self._input,4,self._ctx) - while _alt!=2 and _alt!=ATN.INVALID_ALT_NUMBER: - if _alt==1: - if self._parseListeners is not None: - self.triggerExitRuleEvent() - _prevctx = localctx - self.state = 96 - self._errHandler.sync(self); - la_ = self._interp.adaptivePredict(self._input,3,self._ctx) - if la_ == 1: - localctx = Gold.ExprBitNotContext(self, Gold.ExprContext(self, _parentctx, _parentState)) - self.pushNewRecursionContext(localctx, _startState, self.RULE_expr) - self.state = 51 - if not self.precpred(self._ctx, 10): - from antlr4.error.Errors import FailedPredicateException - raise FailedPredicateException(self, "self.precpred(self._ctx, 10)") - self.state = 52 - self.match(Gold.OPERATOR_BITNOT) - self.state = 53 - self.expr(11) - pass - - elif la_ == 2: - localctx = Gold.ExprBitAndContext(self, Gold.ExprContext(self, _parentctx, _parentState)) - self.pushNewRecursionContext(localctx, _startState, self.RULE_expr) - self.state = 54 - if not self.precpred(self._ctx, 9): - from antlr4.error.Errors import FailedPredicateException - raise FailedPredicateException(self, "self.precpred(self._ctx, 9)") - self.state = 55 - self.match(Gold.OPERATOR_BITAND) - self.state = 56 - self.expr(10) - pass - - elif la_ == 3: - localctx = Gold.ExprBitOrContext(self, Gold.ExprContext(self, _parentctx, _parentState)) - self.pushNewRecursionContext(localctx, _startState, self.RULE_expr) - self.state = 57 - if not self.precpred(self._ctx, 8): - from antlr4.error.Errors import FailedPredicateException - raise FailedPredicateException(self, "self.precpred(self._ctx, 8)") - self.state = 58 - self.match(Gold.OPERATOR_BITOR) - self.state = 59 - self.expr(9) - pass - - elif la_ == 4: - localctx = Gold.ExprBitXorContext(self, Gold.ExprContext(self, _parentctx, _parentState)) - self.pushNewRecursionContext(localctx, _startState, self.RULE_expr) - self.state = 60 - if not self.precpred(self._ctx, 7): - from antlr4.error.Errors import FailedPredicateException - raise FailedPredicateException(self, "self.precpred(self._ctx, 7)") - self.state = 61 - self.match(Gold.OPERATOR_BITXOR) - self.state = 62 - self.expr(8) - pass - - elif la_ == 5: - localctx = Gold.ExprBitShiftContext(self, Gold.ExprContext(self, _parentctx, _parentState)) - self.pushNewRecursionContext(localctx, _startState, self.RULE_expr) - self.state = 63 - if not self.precpred(self._ctx, 6): - from antlr4.error.Errors import FailedPredicateException - raise FailedPredicateException(self, "self.precpred(self._ctx, 6)") - self.state = 64 - localctx.op = self._input.LT(1) - _la = self._input.LA(1) - if not(_la==Gold.OPERATOR_SHR or _la==Gold.OPERATOR_SHL): - localctx.op = self._errHandler.recoverInline(self) - else: - self.consume() - self.state = 65 - self.expr(7) - pass - - elif la_ == 6: - localctx = Gold.ExprProductContext(self, Gold.ExprContext(self, _parentctx, _parentState)) - self.pushNewRecursionContext(localctx, _startState, self.RULE_expr) - self.state = 66 - if not self.precpred(self._ctx, 5): - from antlr4.error.Errors import FailedPredicateException - raise FailedPredicateException(self, "self.precpred(self._ctx, 5)") - self.state = 67 - localctx.op = self._input.LT(1) - _la = self._input.LA(1) - if not(_la==Gold.OPERATOR_TIMES or _la==Gold.OPERATOR_DIVIDE): - localctx.op = self._errHandler.recoverInline(self) - else: - self.consume() - self.state = 68 - self.expr(6) - pass - - elif la_ == 7: - localctx = Gold.ExprSumContext(self, Gold.ExprContext(self, _parentctx, _parentState)) - self.pushNewRecursionContext(localctx, _startState, self.RULE_expr) - self.state = 69 - if not self.precpred(self._ctx, 4): - from antlr4.error.Errors import FailedPredicateException - raise FailedPredicateException(self, "self.precpred(self._ctx, 4)") - self.state = 70 - localctx.op = self._input.LT(1) - _la = self._input.LA(1) - if not(_la==Gold.OPERATOR_PLUS or _la==Gold.OPERATOR_MINUS): - localctx.op = self._errHandler.recoverInline(self) - else: - self.consume() - self.state = 71 - self.expr(5) - pass - - elif la_ == 8: - localctx = Gold.ExprCompareContext(self, Gold.ExprContext(self, _parentctx, _parentState)) - self.pushNewRecursionContext(localctx, _startState, self.RULE_expr) - self.state = 72 - if not self.precpred(self._ctx, 3): - from antlr4.error.Errors import FailedPredicateException - raise FailedPredicateException(self, "self.precpred(self._ctx, 3)") - self.state = 73 - localctx.op = self._input.LT(1) - _la = self._input.LA(1) - if not((((_la) & ~0x3f) == 0 and ((1 << _la) & ((1 << Gold.OPERATOR_NE) | (1 << Gold.OPERATOR_EQ) | (1 << Gold.OPERATOR_LE) | (1 << Gold.OPERATOR_GE) | (1 << Gold.OPERATOR_LT) | (1 << Gold.OPERATOR_GT))) != 0)): - localctx.op = self._errHandler.recoverInline(self) - else: - self.consume() - self.state = 74 - self.expr(4) - pass - - elif la_ == 9: - localctx = Gold.ExprMemberContext(self, Gold.ExprContext(self, _parentctx, _parentState)) - self.pushNewRecursionContext(localctx, _startState, self.RULE_expr) - self.state = 75 - if not self.precpred(self._ctx, 15): - from antlr4.error.Errors import FailedPredicateException - raise FailedPredicateException(self, "self.precpred(self._ctx, 15)") - self.state = 76 - self.match(Gold.OPERATOR_DOT) - self.state = 77 - localctx.member = self.match(Gold.IDENTIFIER) - pass - - elif la_ == 10: - localctx = Gold.ExprIndexContext(self, Gold.ExprContext(self, _parentctx, _parentState)) - self.pushNewRecursionContext(localctx, _startState, self.RULE_expr) - self.state = 78 - if not self.precpred(self._ctx, 14): - from antlr4.error.Errors import FailedPredicateException - raise FailedPredicateException(self, "self.precpred(self._ctx, 14)") - self.state = 79 - self.match(Gold.BRACKET_OPEN) - self.state = 80 - self.expr(0) - self.state = 81 - self.match(Gold.BRACKET_CLOSE) - pass - - elif la_ == 11: - localctx = Gold.ExprFunCallContext(self, Gold.ExprContext(self, _parentctx, _parentState)) - localctx.fun = _prevctx - self.pushNewRecursionContext(localctx, _startState, self.RULE_expr) - self.state = 83 - if not self.precpred(self._ctx, 13): - from antlr4.error.Errors import FailedPredicateException - raise FailedPredicateException(self, "self.precpred(self._ctx, 13)") - self.state = 84 - self.match(Gold.PAREN_OPEN) - self.state = 93 - _la = self._input.LA(1) - if (((_la) & ~0x3f) == 0 and ((1 << _la) & ((1 << Gold.IDENTIFIER) | (1 << Gold.NUMERIC) | (1 << Gold.OPERATOR_MINUS) | (1 << Gold.OPERATOR_DEREF) | (1 << Gold.PAREN_OPEN))) != 0): - self.state = 85 - localctx._expr = self.expr(0) - localctx.args.append(localctx._expr) - self.state = 90 - self._errHandler.sync(self) - _la = self._input.LA(1) - while _la==Gold.PUNCT_COMMA: - self.state = 86 - self.match(Gold.PUNCT_COMMA) - self.state = 87 - localctx._expr = self.expr(0) - localctx.args.append(localctx._expr) - self.state = 92 - self._errHandler.sync(self) - _la = self._input.LA(1) - - - - self.state = 95 - self.match(Gold.PAREN_CLOSE) - pass - - - self.state = 100 - self._errHandler.sync(self) - _alt = self._interp.adaptivePredict(self._input,4,self._ctx) - - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.unrollRecursionContexts(_parentctx) - return localctx - - class ArrayContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - def BRACKET_OPEN(self): - return self.getToken(Gold.BRACKET_OPEN, 0) - - def BRACKET_CLOSE(self): - return self.getToken(Gold.BRACKET_CLOSE, 0) - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - - def PUNCT_COMMA(self, i:int=None): - if i is None: - return self.getTokens(Gold.PUNCT_COMMA) - else: - return self.getToken(Gold.PUNCT_COMMA, i) - - def getRuleIndex(self): - return Gold.RULE_array - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterArray" ): - listener.enterArray(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitArray" ): - listener.exitArray(self) - - - - - def array(self): - - localctx = Gold.ArrayContext(self, self._ctx, self.state) - self.enterRule(localctx, 2, self.RULE_array) - self._la = 0 # Token type - try: - self.enterOuterAlt(localctx, 1) - self.state = 101 - self.match(Gold.BRACKET_OPEN) - self.state = 110 - _la = self._input.LA(1) - if (((_la) & ~0x3f) == 0 and ((1 << _la) & ((1 << Gold.IDENTIFIER) | (1 << Gold.NUMERIC) | (1 << Gold.OPERATOR_MINUS) | (1 << Gold.OPERATOR_DEREF) | (1 << Gold.PAREN_OPEN))) != 0): - self.state = 102 - self.expr(0) - self.state = 107 - self._errHandler.sync(self) - _la = self._input.LA(1) - while _la==Gold.PUNCT_COMMA: - self.state = 103 - self.match(Gold.PUNCT_COMMA) - self.state = 104 - self.expr(0) - self.state = 109 - self._errHandler.sync(self) - _la = self._input.LA(1) - - - - self.state = 112 - self.match(Gold.BRACKET_CLOSE) - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class StringContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - self._STRING = None # Token - self.s = list() # of Tokens - - def STRING(self, i:int=None): - if i is None: - return self.getTokens(Gold.STRING) - else: - return self.getToken(Gold.STRING, i) - - def getRuleIndex(self): - return Gold.RULE_string - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterString" ): - listener.enterString(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitString" ): - listener.exitString(self) - - - - - def string(self): - - localctx = Gold.StringContext(self, self._ctx, self.state) - self.enterRule(localctx, 4, self.RULE_string) - self._la = 0 # Token type - try: - self.enterOuterAlt(localctx, 1) - self.state = 115 - self._errHandler.sync(self) - _la = self._input.LA(1) - while True: - self.state = 114 - localctx._STRING = self.match(Gold.STRING) - localctx.s.append(localctx._STRING) - self.state = 117 - self._errHandler.sync(self) - _la = self._input.LA(1) - if not (_la==Gold.STRING): - break - - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class StorageContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - self.storage_class = None # Token - - def STORAGE_MUT(self): - return self.getToken(Gold.STORAGE_MUT, 0) - - def STORAGE_STASH(self): - return self.getToken(Gold.STORAGE_STASH, 0) - - def getRuleIndex(self): - return Gold.RULE_storage - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterStorage" ): - listener.enterStorage(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitStorage" ): - listener.exitStorage(self) - - - - - def storage(self): - - localctx = Gold.StorageContext(self, self._ctx, self.state) - self.enterRule(localctx, 6, self.RULE_storage) - self._la = 0 # Token type - try: - self.enterOuterAlt(localctx, 1) - self.state = 119 - localctx.storage_class = self._input.LT(1) - _la = self._input.LA(1) - if not(_la==Gold.STORAGE_MUT or _la==Gold.STORAGE_STASH): - localctx.storage_class = self._errHandler.recoverInline(self) - else: - self.consume() - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class TypeIdContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - - def getRuleIndex(self): - return Gold.RULE_typeId - - - def copyFrom(self, ctx:ParserRuleContext): - super().copyFrom(ctx) - - - - class TypeArrayContext(TypeIdContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.TypeIdContext - super().__init__(parser) - self.copyFrom(ctx) - - def BRACKET_OPEN(self): - return self.getToken(Gold.BRACKET_OPEN, 0) - def typeId(self): - return self.getTypedRuleContext(Gold.TypeIdContext,0) - - def PUNCT_SEMICOLON(self): - return self.getToken(Gold.PUNCT_SEMICOLON, 0) - def BRACKET_CLOSE(self): - return self.getToken(Gold.BRACKET_CLOSE, 0) - def expr(self): - return self.getTypedRuleContext(Gold.ExprContext,0) - - def rangeTo(self): - return self.getTypedRuleContext(Gold.RangeToContext,0) - - def storage(self): - return self.getTypedRuleContext(Gold.StorageContext,0) - - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterTypeArray" ): - listener.enterTypeArray(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitTypeArray" ): - listener.exitTypeArray(self) - - - class TypeSliceContext(TypeIdContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.TypeIdContext - super().__init__(parser) - self.copyFrom(ctx) - - def OPERATOR_REF(self): - return self.getToken(Gold.OPERATOR_REF, 0) - def BRACKET_OPEN(self): - return self.getToken(Gold.BRACKET_OPEN, 0) - def typeId(self): - return self.getTypedRuleContext(Gold.TypeIdContext,0) - - def BRACKET_CLOSE(self): - return self.getToken(Gold.BRACKET_CLOSE, 0) - def storage(self): - return self.getTypedRuleContext(Gold.StorageContext,0) - - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterTypeSlice" ): - listener.enterTypeSlice(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitTypeSlice" ): - listener.exitTypeSlice(self) - - - class TypePointerContext(TypeIdContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.TypeIdContext - super().__init__(parser) - self.copyFrom(ctx) - - def OPERATOR_REF(self): - return self.getToken(Gold.OPERATOR_REF, 0) - def typeId(self): - return self.getTypedRuleContext(Gold.TypeIdContext,0) - - def storage(self): - return self.getTypedRuleContext(Gold.StorageContext,0) - - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterTypePointer" ): - listener.enterTypePointer(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitTypePointer" ): - listener.exitTypePointer(self) - - - class TypePrimitiveContext(TypeIdContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.TypeIdContext - super().__init__(parser) - self.name = None # Token - self.copyFrom(ctx) - - def IDENTIFIER(self): - return self.getToken(Gold.IDENTIFIER, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterTypePrimitive" ): - listener.enterTypePrimitive(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitTypePrimitive" ): - listener.exitTypePrimitive(self) - - - - def typeId(self): - - localctx = Gold.TypeIdContext(self, self._ctx, self.state) - self.enterRule(localctx, 8, self.RULE_typeId) - self._la = 0 # Token type - try: - self.state = 147 - self._errHandler.sync(self); - la_ = self._interp.adaptivePredict(self._input,12,self._ctx) - if la_ == 1: - localctx = Gold.TypePrimitiveContext(self, localctx) - self.enterOuterAlt(localctx, 1) - self.state = 121 - localctx.name = self.match(Gold.IDENTIFIER) - pass - - elif la_ == 2: - localctx = Gold.TypeSliceContext(self, localctx) - self.enterOuterAlt(localctx, 2) - self.state = 122 - self.match(Gold.OPERATOR_REF) - self.state = 123 - self.match(Gold.BRACKET_OPEN) - self.state = 125 - _la = self._input.LA(1) - if _la==Gold.STORAGE_MUT or _la==Gold.STORAGE_STASH: - self.state = 124 - self.storage() - - - self.state = 127 - self.typeId() - self.state = 128 - self.match(Gold.BRACKET_CLOSE) - pass - - elif la_ == 3: - localctx = Gold.TypePointerContext(self, localctx) - self.enterOuterAlt(localctx, 3) - self.state = 130 - self.match(Gold.OPERATOR_REF) - self.state = 132 - _la = self._input.LA(1) - if _la==Gold.STORAGE_MUT or _la==Gold.STORAGE_STASH: - self.state = 131 - self.storage() - - - self.state = 134 - self.typeId() - pass - - elif la_ == 4: - localctx = Gold.TypeArrayContext(self, localctx) - self.enterOuterAlt(localctx, 4) - self.state = 135 - self.match(Gold.BRACKET_OPEN) - self.state = 137 - _la = self._input.LA(1) - if _la==Gold.STORAGE_MUT or _la==Gold.STORAGE_STASH: - self.state = 136 - self.storage() - - - self.state = 139 - self.typeId() - self.state = 140 - self.match(Gold.PUNCT_SEMICOLON) - self.state = 143 - self._errHandler.sync(self); - la_ = self._interp.adaptivePredict(self._input,11,self._ctx) - if la_ == 1: - self.state = 141 - self.expr(0) - pass - - elif la_ == 2: - self.state = 142 - self.rangeTo() - pass - - - self.state = 145 - self.match(Gold.BRACKET_CLOSE) - pass - - - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class RangeToContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - - def PUNCT_TO(self): - return self.getToken(Gold.PUNCT_TO, 0) - - def getRuleIndex(self): - return Gold.RULE_rangeTo - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterRangeTo" ): - listener.enterRangeTo(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitRangeTo" ): - listener.exitRangeTo(self) - - - - - def rangeTo(self): - - localctx = Gold.RangeToContext(self, self._ctx, self.state) - self.enterRule(localctx, 10, self.RULE_rangeTo) - try: - self.enterOuterAlt(localctx, 1) - self.state = 149 - self.expr(0) - self.state = 150 - self.match(Gold.PUNCT_TO) - self.state = 151 - self.expr(0) - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class DeclarationContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - self.name = None # Token - - def PUNCT_COLON(self): - return self.getToken(Gold.PUNCT_COLON, 0) - - def typeId(self): - return self.getTypedRuleContext(Gold.TypeIdContext,0) - - - def IDENTIFIER(self): - return self.getToken(Gold.IDENTIFIER, 0) - - def getRuleIndex(self): - return Gold.RULE_declaration - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterDeclaration" ): - listener.enterDeclaration(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitDeclaration" ): - listener.exitDeclaration(self) - - - - - def declaration(self): - - localctx = Gold.DeclarationContext(self, self._ctx, self.state) - self.enterRule(localctx, 12, self.RULE_declaration) - try: - self.enterOuterAlt(localctx, 1) - self.state = 153 - localctx.name = self.match(Gold.IDENTIFIER) - self.state = 154 - self.match(Gold.PUNCT_COLON) - self.state = 155 - self.typeId() - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class StmtConstantContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - def STMT_CONSTANT(self): - return self.getToken(Gold.STMT_CONSTANT, 0) - - def declaration(self): - return self.getTypedRuleContext(Gold.DeclarationContext,0) - - - def OPERATOR_ASSIGN(self): - return self.getToken(Gold.OPERATOR_ASSIGN, 0) - - def expr(self): - return self.getTypedRuleContext(Gold.ExprContext,0) - - - def array(self): - return self.getTypedRuleContext(Gold.ArrayContext,0) - - - def getRuleIndex(self): - return Gold.RULE_stmtConstant - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterStmtConstant" ): - listener.enterStmtConstant(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitStmtConstant" ): - listener.exitStmtConstant(self) - - - - - def stmtConstant(self): - - localctx = Gold.StmtConstantContext(self, self._ctx, self.state) - self.enterRule(localctx, 14, self.RULE_stmtConstant) - try: - self.enterOuterAlt(localctx, 1) - self.state = 157 - self.match(Gold.STMT_CONSTANT) - self.state = 158 - self.declaration() - self.state = 159 - self.match(Gold.OPERATOR_ASSIGN) - self.state = 162 - token = self._input.LA(1) - if token in [Gold.IDENTIFIER, Gold.NUMERIC, Gold.OPERATOR_MINUS, Gold.OPERATOR_DEREF, Gold.PAREN_OPEN]: - self.state = 160 - self.expr(0) - - elif token in [Gold.BRACKET_OPEN]: - self.state = 161 - self.array() - - else: - raise NoViableAltException(self) - - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class StmtUseContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - self.unitId = None # Token - - def STMT_USE(self): - return self.getToken(Gold.STMT_USE, 0) - - def IDENTIFIER(self): - return self.getToken(Gold.IDENTIFIER, 0) - - def getRuleIndex(self): - return Gold.RULE_stmtUse - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterStmtUse" ): - listener.enterStmtUse(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitStmtUse" ): - listener.exitStmtUse(self) - - - - - def stmtUse(self): - - localctx = Gold.StmtUseContext(self, self._ctx, self.state) - self.enterRule(localctx, 16, self.RULE_stmtUse) - try: - self.enterOuterAlt(localctx, 1) - self.state = 164 - self.match(Gold.STMT_USE) - self.state = 165 - localctx.unitId = self.match(Gold.IDENTIFIER) - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class StmtLetContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - def STMT_LET(self): - return self.getToken(Gold.STMT_LET, 0) - - def declaration(self): - return self.getTypedRuleContext(Gold.DeclarationContext,0) - - - def OPERATOR_ASSIGN(self): - return self.getToken(Gold.OPERATOR_ASSIGN, 0) - - def expr(self): - return self.getTypedRuleContext(Gold.ExprContext,0) - - - def array(self): - return self.getTypedRuleContext(Gold.ArrayContext,0) - - - def string(self): - return self.getTypedRuleContext(Gold.StringContext,0) - - - def storage(self): - return self.getTypedRuleContext(Gold.StorageContext,0) - - - def getRuleIndex(self): - return Gold.RULE_stmtLet - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterStmtLet" ): - listener.enterStmtLet(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitStmtLet" ): - listener.exitStmtLet(self) - - - - - def stmtLet(self): - - localctx = Gold.StmtLetContext(self, self._ctx, self.state) - self.enterRule(localctx, 18, self.RULE_stmtLet) - self._la = 0 # Token type - try: - self.enterOuterAlt(localctx, 1) - self.state = 167 - self.match(Gold.STMT_LET) - self.state = 169 - _la = self._input.LA(1) - if _la==Gold.STORAGE_MUT or _la==Gold.STORAGE_STASH: - self.state = 168 - self.storage() - - - self.state = 171 - self.declaration() - self.state = 172 - self.match(Gold.OPERATOR_ASSIGN) - self.state = 176 - token = self._input.LA(1) - if token in [Gold.IDENTIFIER, Gold.NUMERIC, Gold.OPERATOR_MINUS, Gold.OPERATOR_DEREF, Gold.PAREN_OPEN]: - self.state = 173 - self.expr(0) - - elif token in [Gold.BRACKET_OPEN]: - self.state = 174 - self.array() - - elif token in [Gold.STRING]: - self.state = 175 - self.string() - - else: - raise NoViableAltException(self) - - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class StmtWhileContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - def STMT_WHILE(self): - return self.getToken(Gold.STMT_WHILE, 0) - - def expr(self): - return self.getTypedRuleContext(Gold.ExprContext,0) - - - def PUNCT_DO(self): - return self.getToken(Gold.PUNCT_DO, 0) - - def block(self): - return self.getTypedRuleContext(Gold.BlockContext,0) - - - def PUNCT_END(self): - return self.getToken(Gold.PUNCT_END, 0) - - def getRuleIndex(self): - return Gold.RULE_stmtWhile - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterStmtWhile" ): - listener.enterStmtWhile(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitStmtWhile" ): - listener.exitStmtWhile(self) - - - - - def stmtWhile(self): - - localctx = Gold.StmtWhileContext(self, self._ctx, self.state) - self.enterRule(localctx, 20, self.RULE_stmtWhile) - try: - self.enterOuterAlt(localctx, 1) - self.state = 178 - self.match(Gold.STMT_WHILE) - self.state = 179 - self.expr(0) - self.state = 180 - self.match(Gold.PUNCT_DO) - self.state = 181 - self.block() - self.state = 182 - self.match(Gold.PUNCT_END) - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class StmtForContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - def STMT_FOR(self): - return self.getToken(Gold.STMT_FOR, 0) - - def declaration(self): - return self.getTypedRuleContext(Gold.DeclarationContext,0) - - - def PUNCT_IN(self): - return self.getToken(Gold.PUNCT_IN, 0) - - def PUNCT_DO(self): - return self.getToken(Gold.PUNCT_DO, 0) - - def block(self): - return self.getTypedRuleContext(Gold.BlockContext,0) - - - def PUNCT_END(self): - return self.getToken(Gold.PUNCT_END, 0) - - def rangeTo(self): - return self.getTypedRuleContext(Gold.RangeToContext,0) - - - def expr(self): - return self.getTypedRuleContext(Gold.ExprContext,0) - - - def getRuleIndex(self): - return Gold.RULE_stmtFor - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterStmtFor" ): - listener.enterStmtFor(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitStmtFor" ): - listener.exitStmtFor(self) - - - - - def stmtFor(self): - - localctx = Gold.StmtForContext(self, self._ctx, self.state) - self.enterRule(localctx, 22, self.RULE_stmtFor) - try: - self.enterOuterAlt(localctx, 1) - self.state = 184 - self.match(Gold.STMT_FOR) - self.state = 185 - self.declaration() - self.state = 186 - self.match(Gold.PUNCT_IN) - self.state = 189 - self._errHandler.sync(self); - la_ = self._interp.adaptivePredict(self._input,16,self._ctx) - if la_ == 1: - self.state = 187 - self.rangeTo() - pass - - elif la_ == 2: - self.state = 188 - self.expr(0) - pass - - - self.state = 191 - self.match(Gold.PUNCT_DO) - self.state = 192 - self.block() - self.state = 193 - self.match(Gold.PUNCT_END) - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class StmtIfContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - def STMT_IF(self): - return self.getToken(Gold.STMT_IF, 0) - - def expr(self): - return self.getTypedRuleContext(Gold.ExprContext,0) - - - def PUNCT_THEN(self): - return self.getToken(Gold.PUNCT_THEN, 0) - - def block(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.BlockContext) - else: - return self.getTypedRuleContext(Gold.BlockContext,i) - - - def PUNCT_END(self): - return self.getToken(Gold.PUNCT_END, 0) - - def PUNCT_ELSEIF(self, i:int=None): - if i is None: - return self.getTokens(Gold.PUNCT_ELSEIF) - else: - return self.getToken(Gold.PUNCT_ELSEIF, i) - - def PUNCT_ELSE(self): - return self.getToken(Gold.PUNCT_ELSE, 0) - - def getRuleIndex(self): - return Gold.RULE_stmtIf - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterStmtIf" ): - listener.enterStmtIf(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitStmtIf" ): - listener.exitStmtIf(self) - - - - - def stmtIf(self): - - localctx = Gold.StmtIfContext(self, self._ctx, self.state) - self.enterRule(localctx, 24, self.RULE_stmtIf) - self._la = 0 # Token type - try: - self.enterOuterAlt(localctx, 1) - self.state = 195 - self.match(Gold.STMT_IF) - self.state = 196 - self.expr(0) - self.state = 197 - self.match(Gold.PUNCT_THEN) - self.state = 198 - self.block() - self.state = 203 - self._errHandler.sync(self) - _la = self._input.LA(1) - while _la==Gold.PUNCT_ELSEIF: - self.state = 199 - self.match(Gold.PUNCT_ELSEIF) - self.state = 200 - self.block() - self.state = 205 - self._errHandler.sync(self) - _la = self._input.LA(1) - - self.state = 208 - _la = self._input.LA(1) - if _la==Gold.PUNCT_ELSE: - self.state = 206 - self.match(Gold.PUNCT_ELSE) - self.state = 207 - self.block() - - - self.state = 210 - self.match(Gold.PUNCT_END) - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class StmtIsrContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - def STMT_ISR(self): - return self.getToken(Gold.STMT_ISR, 0) - - def IDENTIFIER(self): - return self.getToken(Gold.IDENTIFIER, 0) - - def block(self): - return self.getTypedRuleContext(Gold.BlockContext,0) - - - def PUNCT_ENDISR(self): - return self.getToken(Gold.PUNCT_ENDISR, 0) - - def getRuleIndex(self): - return Gold.RULE_stmtIsr - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterStmtIsr" ): - listener.enterStmtIsr(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitStmtIsr" ): - listener.exitStmtIsr(self) - - - - - def stmtIsr(self): - - localctx = Gold.StmtIsrContext(self, self._ctx, self.state) - self.enterRule(localctx, 26, self.RULE_stmtIsr) - try: - self.enterOuterAlt(localctx, 1) - self.state = 212 - self.match(Gold.STMT_ISR) - self.state = 213 - self.match(Gold.IDENTIFIER) - self.state = 214 - self.block() - self.state = 215 - self.match(Gold.PUNCT_ENDISR) - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class StmtFunContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - self.name = None # Token - self._declaration = None # DeclarationContext - self.args = list() # of DeclarationContexts - self.ret = None # TypeIdContext - - def STMT_FUN(self): - return self.getToken(Gold.STMT_FUN, 0) - - def PAREN_OPEN(self): - return self.getToken(Gold.PAREN_OPEN, 0) - - def PAREN_CLOSE(self): - return self.getToken(Gold.PAREN_CLOSE, 0) - - def block(self): - return self.getTypedRuleContext(Gold.BlockContext,0) - - - def PUNCT_ENDFUN(self): - return self.getToken(Gold.PUNCT_ENDFUN, 0) - - def IDENTIFIER(self): - return self.getToken(Gold.IDENTIFIER, 0) - - def PUNCT_ARROWR(self): - return self.getToken(Gold.PUNCT_ARROWR, 0) - - def declaration(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.DeclarationContext) - else: - return self.getTypedRuleContext(Gold.DeclarationContext,i) - - - def typeId(self): - return self.getTypedRuleContext(Gold.TypeIdContext,0) - - - def PUNCT_COMMA(self, i:int=None): - if i is None: - return self.getTokens(Gold.PUNCT_COMMA) - else: - return self.getToken(Gold.PUNCT_COMMA, i) - - def getRuleIndex(self): - return Gold.RULE_stmtFun - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterStmtFun" ): - listener.enterStmtFun(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitStmtFun" ): - listener.exitStmtFun(self) - - - - - def stmtFun(self): - - localctx = Gold.StmtFunContext(self, self._ctx, self.state) - self.enterRule(localctx, 28, self.RULE_stmtFun) - self._la = 0 # Token type - try: - self.enterOuterAlt(localctx, 1) - self.state = 217 - self.match(Gold.STMT_FUN) - self.state = 218 - localctx.name = self.match(Gold.IDENTIFIER) - self.state = 219 - self.match(Gold.PAREN_OPEN) - self.state = 228 - _la = self._input.LA(1) - if _la==Gold.IDENTIFIER: - self.state = 220 - localctx._declaration = self.declaration() - localctx.args.append(localctx._declaration) - self.state = 225 - self._errHandler.sync(self) - _la = self._input.LA(1) - while _la==Gold.PUNCT_COMMA: - self.state = 221 - self.match(Gold.PUNCT_COMMA) - self.state = 222 - localctx._declaration = self.declaration() - localctx.args.append(localctx._declaration) - self.state = 227 - self._errHandler.sync(self) - _la = self._input.LA(1) - - - - self.state = 230 - self.match(Gold.PAREN_CLOSE) - self.state = 233 - _la = self._input.LA(1) - if _la==Gold.PUNCT_ARROWR: - self.state = 231 - self.match(Gold.PUNCT_ARROWR) - self.state = 232 - localctx.ret = self.typeId() - - - self.state = 235 - self.block() - self.state = 236 - self.match(Gold.PUNCT_ENDFUN) - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class StmtReturnContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - def STMT_RETURN(self): - return self.getToken(Gold.STMT_RETURN, 0) - - def expr(self): - return self.getTypedRuleContext(Gold.ExprContext,0) - - - def getRuleIndex(self): - return Gold.RULE_stmtReturn - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterStmtReturn" ): - listener.enterStmtReturn(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitStmtReturn" ): - listener.exitStmtReturn(self) - - - - - def stmtReturn(self): - - localctx = Gold.StmtReturnContext(self, self._ctx, self.state) - self.enterRule(localctx, 30, self.RULE_stmtReturn) - try: - self.enterOuterAlt(localctx, 1) - self.state = 238 - self.match(Gold.STMT_RETURN) - self.state = 240 - self._errHandler.sync(self); - la_ = self._interp.adaptivePredict(self._input,22,self._ctx) - if la_ == 1: - self.state = 239 - self.expr(0) - - - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class StmtAssignContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - - def getRuleIndex(self): - return Gold.RULE_stmtAssign - - - def copyFrom(self, ctx:ParserRuleContext): - super().copyFrom(ctx) - - - - class StmtAssignIncContext(StmtAssignContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.StmtAssignContext - super().__init__(parser) - self.copyFrom(ctx) - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - def OPERATOR_ASSIGN_INC(self): - return self.getToken(Gold.OPERATOR_ASSIGN_INC, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterStmtAssignInc" ): - listener.enterStmtAssignInc(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitStmtAssignInc" ): - listener.exitStmtAssignInc(self) - - - class StmtAssignDecContext(StmtAssignContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.StmtAssignContext - super().__init__(parser) - self.copyFrom(ctx) - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - def OPERATOR_ASSIGN_DEC(self): - return self.getToken(Gold.OPERATOR_ASSIGN_DEC, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterStmtAssignDec" ): - listener.enterStmtAssignDec(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitStmtAssignDec" ): - listener.exitStmtAssignDec(self) - - - class StmtAssignValContext(StmtAssignContext): - - def __init__(self, parser, ctx:ParserRuleContext): # actually a Gold.StmtAssignContext - super().__init__(parser) - self.copyFrom(ctx) - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - def OPERATOR_ASSIGN(self): - return self.getToken(Gold.OPERATOR_ASSIGN, 0) - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterStmtAssignVal" ): - listener.enterStmtAssignVal(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitStmtAssignVal" ): - listener.exitStmtAssignVal(self) - - - - def stmtAssign(self): - - localctx = Gold.StmtAssignContext(self, self._ctx, self.state) - self.enterRule(localctx, 32, self.RULE_stmtAssign) - try: - self.state = 254 - self._errHandler.sync(self); - la_ = self._interp.adaptivePredict(self._input,23,self._ctx) - if la_ == 1: - localctx = Gold.StmtAssignValContext(self, localctx) - self.enterOuterAlt(localctx, 1) - self.state = 242 - self.expr(0) - self.state = 243 - self.match(Gold.OPERATOR_ASSIGN) - self.state = 244 - self.expr(0) - pass - - elif la_ == 2: - localctx = Gold.StmtAssignIncContext(self, localctx) - self.enterOuterAlt(localctx, 2) - self.state = 246 - self.expr(0) - self.state = 247 - self.match(Gold.OPERATOR_ASSIGN_INC) - self.state = 248 - self.expr(0) - pass - - elif la_ == 3: - localctx = Gold.StmtAssignDecContext(self, localctx) - self.enterOuterAlt(localctx, 3) - self.state = 250 - self.expr(0) - self.state = 251 - self.match(Gold.OPERATOR_ASSIGN_DEC) - self.state = 252 - self.expr(0) - pass - - - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class BlockContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - def stmtConstant(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.StmtConstantContext) - else: - return self.getTypedRuleContext(Gold.StmtConstantContext,i) - - - def stmtFor(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.StmtForContext) - else: - return self.getTypedRuleContext(Gold.StmtForContext,i) - - - def stmtIf(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.StmtIfContext) - else: - return self.getTypedRuleContext(Gold.StmtIfContext,i) - - - def stmtLet(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.StmtLetContext) - else: - return self.getTypedRuleContext(Gold.StmtLetContext,i) - - - def stmtReturn(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.StmtReturnContext) - else: - return self.getTypedRuleContext(Gold.StmtReturnContext,i) - - - def stmtWhile(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.StmtWhileContext) - else: - return self.getTypedRuleContext(Gold.StmtWhileContext,i) - - - def stmtAssign(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.StmtAssignContext) - else: - return self.getTypedRuleContext(Gold.StmtAssignContext,i) - - - def expr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.ExprContext) - else: - return self.getTypedRuleContext(Gold.ExprContext,i) - - - def getRuleIndex(self): - return Gold.RULE_block - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterBlock" ): - listener.enterBlock(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitBlock" ): - listener.exitBlock(self) - - - - - def block(self): - - localctx = Gold.BlockContext(self, self._ctx, self.state) - self.enterRule(localctx, 34, self.RULE_block) - self._la = 0 # Token type - try: - self.enterOuterAlt(localctx, 1) - self.state = 266 - self._errHandler.sync(self) - _la = self._input.LA(1) - while (((_la) & ~0x3f) == 0 and ((1 << _la) & ((1 << Gold.IDENTIFIER) | (1 << Gold.NUMERIC) | (1 << Gold.OPERATOR_MINUS) | (1 << Gold.OPERATOR_DEREF) | (1 << Gold.STMT_CONSTANT) | (1 << Gold.STMT_FOR) | (1 << Gold.STMT_IF) | (1 << Gold.STMT_LET) | (1 << Gold.STMT_RETURN) | (1 << Gold.STMT_WHILE) | (1 << Gold.PAREN_OPEN))) != 0): - self.state = 264 - self._errHandler.sync(self); - la_ = self._interp.adaptivePredict(self._input,24,self._ctx) - if la_ == 1: - self.state = 256 - self.stmtConstant() - pass - - elif la_ == 2: - self.state = 257 - self.stmtFor() - pass - - elif la_ == 3: - self.state = 258 - self.stmtIf() - pass - - elif la_ == 4: - self.state = 259 - self.stmtLet() - pass - - elif la_ == 5: - self.state = 260 - self.stmtReturn() - pass - - elif la_ == 6: - self.state = 261 - self.stmtWhile() - pass - - elif la_ == 7: - self.state = 262 - self.stmtAssign() - pass - - elif la_ == 8: - self.state = 263 - self.expr(0) - pass - - - self.state = 268 - self._errHandler.sync(self) - _la = self._input.LA(1) - - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - class UnitContext(ParserRuleContext): - - def __init__(self, parser, parent:ParserRuleContext=None, invokingState:int=-1): - super().__init__(parent, invokingState) - self.parser = parser - - def EOF(self): - return self.getToken(Gold.EOF, 0) - - def stmtConstant(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.StmtConstantContext) - else: - return self.getTypedRuleContext(Gold.StmtConstantContext,i) - - - def stmtIsr(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.StmtIsrContext) - else: - return self.getTypedRuleContext(Gold.StmtIsrContext,i) - - - def stmtLet(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.StmtLetContext) - else: - return self.getTypedRuleContext(Gold.StmtLetContext,i) - - - def stmtUse(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.StmtUseContext) - else: - return self.getTypedRuleContext(Gold.StmtUseContext,i) - - - def stmtFun(self, i:int=None): - if i is None: - return self.getTypedRuleContexts(Gold.StmtFunContext) - else: - return self.getTypedRuleContext(Gold.StmtFunContext,i) - - - def getRuleIndex(self): - return Gold.RULE_unit - - def enterRule(self, listener:ParseTreeListener): - if hasattr( listener, "enterUnit" ): - listener.enterUnit(self) - - def exitRule(self, listener:ParseTreeListener): - if hasattr( listener, "exitUnit" ): - listener.exitUnit(self) - - - - - def unit(self): - - localctx = Gold.UnitContext(self, self._ctx, self.state) - self.enterRule(localctx, 36, self.RULE_unit) - self._la = 0 # Token type - try: - self.enterOuterAlt(localctx, 1) - self.state = 276 - self._errHandler.sync(self) - _la = self._input.LA(1) - while (((_la) & ~0x3f) == 0 and ((1 << _la) & ((1 << Gold.STMT_CONSTANT) | (1 << Gold.STMT_FUN) | (1 << Gold.STMT_ISR) | (1 << Gold.STMT_LET) | (1 << Gold.STMT_USE))) != 0): - self.state = 274 - token = self._input.LA(1) - if token in [Gold.STMT_CONSTANT]: - self.state = 269 - self.stmtConstant() - - elif token in [Gold.STMT_ISR]: - self.state = 270 - self.stmtIsr() - - elif token in [Gold.STMT_LET]: - self.state = 271 - self.stmtLet() - - elif token in [Gold.STMT_USE]: - self.state = 272 - self.stmtUse() - - elif token in [Gold.STMT_FUN]: - self.state = 273 - self.stmtFun() - - else: - raise NoViableAltException(self) - - self.state = 278 - self._errHandler.sync(self) - _la = self._input.LA(1) - - self.state = 279 - self.match(Gold.EOF) - except RecognitionException as re: - localctx.exception = re - self._errHandler.reportError(self, re) - self._errHandler.recover(self, re) - finally: - self.exitRule() - return localctx - - - - def sempred(self, localctx:RuleContext, ruleIndex:int, predIndex:int): - if self._predicates == None: - self._predicates = dict() - self._predicates[0] = self.expr_sempred - pred = self._predicates.get(ruleIndex, None) - if pred is None: - raise Exception("No predicate with index:" + str(ruleIndex)) - else: - return pred(localctx, predIndex) - - def expr_sempred(self, localctx:ExprContext, predIndex:int): - if predIndex == 0: - return self.precpred(self._ctx, 10) - - - if predIndex == 1: - return self.precpred(self._ctx, 9) - - - if predIndex == 2: - return self.precpred(self._ctx, 8) - - - if predIndex == 3: - return self.precpred(self._ctx, 7) - - - if predIndex == 4: - return self.precpred(self._ctx, 6) - - - if predIndex == 5: - return self.precpred(self._ctx, 5) - - - if predIndex == 6: - return self.precpred(self._ctx, 4) - - - if predIndex == 7: - return self.precpred(self._ctx, 3) - - - if predIndex == 8: - return self.precpred(self._ctx, 15) - - - if predIndex == 9: - return self.precpred(self._ctx, 14) - - - if predIndex == 10: - return self.precpred(self._ctx, 13) - - - - - diff --git a/jeff65/gold/grammar/Gold.tokens b/jeff65/gold/grammar/Gold.tokens deleted file mode 100644 index e32d277..0000000 --- a/jeff65/gold/grammar/Gold.tokens +++ /dev/null @@ -1,64 +0,0 @@ -IDENTIFIER=1 -NUMERIC=2 -STRING=3 -OPERATOR_PLUS=4 -OPERATOR_MINUS=5 -OPERATOR_TIMES=6 -OPERATOR_DIVIDE=7 -OPERATOR_NOT=8 -OPERATOR_AND=9 -OPERATOR_OR=10 -OPERATOR_SHR=11 -OPERATOR_SHL=12 -OPERATOR_BITNOT=13 -OPERATOR_BITAND=14 -OPERATOR_BITOR=15 -OPERATOR_BITXOR=16 -OPERATOR_NE=17 -OPERATOR_EQ=18 -OPERATOR_LE=19 -OPERATOR_GE=20 -OPERATOR_LT=21 -OPERATOR_GT=22 -OPERATOR_ASSIGN=23 -OPERATOR_ASSIGN_INC=24 -OPERATOR_ASSIGN_DEC=25 -OPERATOR_DOT=26 -OPERATOR_DEREF=27 -OPERATOR_REF=28 -STMT_CONSTANT=29 -STMT_FOR=30 -STMT_FUN=31 -STMT_IF=32 -STMT_ISR=33 -STMT_LET=34 -STMT_RETURN=35 -STMT_USE=36 -STMT_WHILE=37 -STORAGE_MUT=38 -STORAGE_STASH=39 -PUNCT_DO=40 -PUNCT_ELSE=41 -PUNCT_ELSEIF=42 -PUNCT_END=43 -PUNCT_ENDFUN=44 -PUNCT_ENDISR=45 -PUNCT_IN=46 -PUNCT_THEN=47 -PUNCT_TO=48 -PUNCT_COLON=49 -PUNCT_SEMICOLON=50 -PUNCT_COMMA=51 -PUNCT_ARROWR=52 -PAREN_OPEN=53 -PAREN_CLOSE=54 -BRACKET_OPEN=55 -BRACKET_CLOSE=56 -BRACE_OPEN=57 -BRACE_CLOSE=58 -STRING_DELIM=59 -COMMENT_OPEN=60 -COMMENT_CLOSE=61 -COMMENT_TEXT=62 -WHITESPACE=63 -MYSTERY=64 diff --git a/jeff65/gold/grammar/GoldListener.py b/jeff65/gold/grammar/GoldListener.py deleted file mode 100644 index a02e0d7..0000000 --- a/jeff65/gold/grammar/GoldListener.py +++ /dev/null @@ -1,361 +0,0 @@ -# Generated from jeff65/gold/grammar/Gold.g4 by ANTLR 4.5.2 -from antlr4 import * -if __name__ is not None and "." in __name__: - from .Gold import Gold -else: - from Gold import Gold - -# This class defines a complete listener for a parse tree produced by Gold. -class GoldListener(ParseTreeListener): - - # Enter a parse tree produced by Gold#ExprParen. - def enterExprParen(self, ctx:Gold.ExprParenContext): - pass - - # Exit a parse tree produced by Gold#ExprParen. - def exitExprParen(self, ctx:Gold.ExprParenContext): - pass - - - # Enter a parse tree produced by Gold#ExprBitXor. - def enterExprBitXor(self, ctx:Gold.ExprBitXorContext): - pass - - # Exit a parse tree produced by Gold#ExprBitXor. - def exitExprBitXor(self, ctx:Gold.ExprBitXorContext): - pass - - - # Enter a parse tree produced by Gold#ExprSum. - def enterExprSum(self, ctx:Gold.ExprSumContext): - pass - - # Exit a parse tree produced by Gold#ExprSum. - def exitExprSum(self, ctx:Gold.ExprSumContext): - pass - - - # Enter a parse tree produced by Gold#ExprIndex. - def enterExprIndex(self, ctx:Gold.ExprIndexContext): - pass - - # Exit a parse tree produced by Gold#ExprIndex. - def exitExprIndex(self, ctx:Gold.ExprIndexContext): - pass - - - # Enter a parse tree produced by Gold#ExprBitShift. - def enterExprBitShift(self, ctx:Gold.ExprBitShiftContext): - pass - - # Exit a parse tree produced by Gold#ExprBitShift. - def exitExprBitShift(self, ctx:Gold.ExprBitShiftContext): - pass - - - # Enter a parse tree produced by Gold#ExprNegation. - def enterExprNegation(self, ctx:Gold.ExprNegationContext): - pass - - # Exit a parse tree produced by Gold#ExprNegation. - def exitExprNegation(self, ctx:Gold.ExprNegationContext): - pass - - - # Enter a parse tree produced by Gold#ExprBitOr. - def enterExprBitOr(self, ctx:Gold.ExprBitOrContext): - pass - - # Exit a parse tree produced by Gold#ExprBitOr. - def exitExprBitOr(self, ctx:Gold.ExprBitOrContext): - pass - - - # Enter a parse tree produced by Gold#ExprDeref. - def enterExprDeref(self, ctx:Gold.ExprDerefContext): - pass - - # Exit a parse tree produced by Gold#ExprDeref. - def exitExprDeref(self, ctx:Gold.ExprDerefContext): - pass - - - # Enter a parse tree produced by Gold#ExprProduct. - def enterExprProduct(self, ctx:Gold.ExprProductContext): - pass - - # Exit a parse tree produced by Gold#ExprProduct. - def exitExprProduct(self, ctx:Gold.ExprProductContext): - pass - - - # Enter a parse tree produced by Gold#ExprCompare. - def enterExprCompare(self, ctx:Gold.ExprCompareContext): - pass - - # Exit a parse tree produced by Gold#ExprCompare. - def exitExprCompare(self, ctx:Gold.ExprCompareContext): - pass - - - # Enter a parse tree produced by Gold#ExprFunCall. - def enterExprFunCall(self, ctx:Gold.ExprFunCallContext): - pass - - # Exit a parse tree produced by Gold#ExprFunCall. - def exitExprFunCall(self, ctx:Gold.ExprFunCallContext): - pass - - - # Enter a parse tree produced by Gold#ExprNumber. - def enterExprNumber(self, ctx:Gold.ExprNumberContext): - pass - - # Exit a parse tree produced by Gold#ExprNumber. - def exitExprNumber(self, ctx:Gold.ExprNumberContext): - pass - - - # Enter a parse tree produced by Gold#ExprBitAnd. - def enterExprBitAnd(self, ctx:Gold.ExprBitAndContext): - pass - - # Exit a parse tree produced by Gold#ExprBitAnd. - def exitExprBitAnd(self, ctx:Gold.ExprBitAndContext): - pass - - - # Enter a parse tree produced by Gold#ExprBitNot. - def enterExprBitNot(self, ctx:Gold.ExprBitNotContext): - pass - - # Exit a parse tree produced by Gold#ExprBitNot. - def exitExprBitNot(self, ctx:Gold.ExprBitNotContext): - pass - - - # Enter a parse tree produced by Gold#ExprId. - def enterExprId(self, ctx:Gold.ExprIdContext): - pass - - # Exit a parse tree produced by Gold#ExprId. - def exitExprId(self, ctx:Gold.ExprIdContext): - pass - - - # Enter a parse tree produced by Gold#ExprMember. - def enterExprMember(self, ctx:Gold.ExprMemberContext): - pass - - # Exit a parse tree produced by Gold#ExprMember. - def exitExprMember(self, ctx:Gold.ExprMemberContext): - pass - - - # Enter a parse tree produced by Gold#array. - def enterArray(self, ctx:Gold.ArrayContext): - pass - - # Exit a parse tree produced by Gold#array. - def exitArray(self, ctx:Gold.ArrayContext): - pass - - - # Enter a parse tree produced by Gold#string. - def enterString(self, ctx:Gold.StringContext): - pass - - # Exit a parse tree produced by Gold#string. - def exitString(self, ctx:Gold.StringContext): - pass - - - # Enter a parse tree produced by Gold#storage. - def enterStorage(self, ctx:Gold.StorageContext): - pass - - # Exit a parse tree produced by Gold#storage. - def exitStorage(self, ctx:Gold.StorageContext): - pass - - - # Enter a parse tree produced by Gold#TypePrimitive. - def enterTypePrimitive(self, ctx:Gold.TypePrimitiveContext): - pass - - # Exit a parse tree produced by Gold#TypePrimitive. - def exitTypePrimitive(self, ctx:Gold.TypePrimitiveContext): - pass - - - # Enter a parse tree produced by Gold#TypeSlice. - def enterTypeSlice(self, ctx:Gold.TypeSliceContext): - pass - - # Exit a parse tree produced by Gold#TypeSlice. - def exitTypeSlice(self, ctx:Gold.TypeSliceContext): - pass - - - # Enter a parse tree produced by Gold#TypePointer. - def enterTypePointer(self, ctx:Gold.TypePointerContext): - pass - - # Exit a parse tree produced by Gold#TypePointer. - def exitTypePointer(self, ctx:Gold.TypePointerContext): - pass - - - # Enter a parse tree produced by Gold#TypeArray. - def enterTypeArray(self, ctx:Gold.TypeArrayContext): - pass - - # Exit a parse tree produced by Gold#TypeArray. - def exitTypeArray(self, ctx:Gold.TypeArrayContext): - pass - - - # Enter a parse tree produced by Gold#rangeTo. - def enterRangeTo(self, ctx:Gold.RangeToContext): - pass - - # Exit a parse tree produced by Gold#rangeTo. - def exitRangeTo(self, ctx:Gold.RangeToContext): - pass - - - # Enter a parse tree produced by Gold#declaration. - def enterDeclaration(self, ctx:Gold.DeclarationContext): - pass - - # Exit a parse tree produced by Gold#declaration. - def exitDeclaration(self, ctx:Gold.DeclarationContext): - pass - - - # Enter a parse tree produced by Gold#stmtConstant. - def enterStmtConstant(self, ctx:Gold.StmtConstantContext): - pass - - # Exit a parse tree produced by Gold#stmtConstant. - def exitStmtConstant(self, ctx:Gold.StmtConstantContext): - pass - - - # Enter a parse tree produced by Gold#stmtUse. - def enterStmtUse(self, ctx:Gold.StmtUseContext): - pass - - # Exit a parse tree produced by Gold#stmtUse. - def exitStmtUse(self, ctx:Gold.StmtUseContext): - pass - - - # Enter a parse tree produced by Gold#stmtLet. - def enterStmtLet(self, ctx:Gold.StmtLetContext): - pass - - # Exit a parse tree produced by Gold#stmtLet. - def exitStmtLet(self, ctx:Gold.StmtLetContext): - pass - - - # Enter a parse tree produced by Gold#stmtWhile. - def enterStmtWhile(self, ctx:Gold.StmtWhileContext): - pass - - # Exit a parse tree produced by Gold#stmtWhile. - def exitStmtWhile(self, ctx:Gold.StmtWhileContext): - pass - - - # Enter a parse tree produced by Gold#stmtFor. - def enterStmtFor(self, ctx:Gold.StmtForContext): - pass - - # Exit a parse tree produced by Gold#stmtFor. - def exitStmtFor(self, ctx:Gold.StmtForContext): - pass - - - # Enter a parse tree produced by Gold#stmtIf. - def enterStmtIf(self, ctx:Gold.StmtIfContext): - pass - - # Exit a parse tree produced by Gold#stmtIf. - def exitStmtIf(self, ctx:Gold.StmtIfContext): - pass - - - # Enter a parse tree produced by Gold#stmtIsr. - def enterStmtIsr(self, ctx:Gold.StmtIsrContext): - pass - - # Exit a parse tree produced by Gold#stmtIsr. - def exitStmtIsr(self, ctx:Gold.StmtIsrContext): - pass - - - # Enter a parse tree produced by Gold#stmtFun. - def enterStmtFun(self, ctx:Gold.StmtFunContext): - pass - - # Exit a parse tree produced by Gold#stmtFun. - def exitStmtFun(self, ctx:Gold.StmtFunContext): - pass - - - # Enter a parse tree produced by Gold#stmtReturn. - def enterStmtReturn(self, ctx:Gold.StmtReturnContext): - pass - - # Exit a parse tree produced by Gold#stmtReturn. - def exitStmtReturn(self, ctx:Gold.StmtReturnContext): - pass - - - # Enter a parse tree produced by Gold#stmtAssignVal. - def enterStmtAssignVal(self, ctx:Gold.StmtAssignValContext): - pass - - # Exit a parse tree produced by Gold#stmtAssignVal. - def exitStmtAssignVal(self, ctx:Gold.StmtAssignValContext): - pass - - - # Enter a parse tree produced by Gold#stmtAssignInc. - def enterStmtAssignInc(self, ctx:Gold.StmtAssignIncContext): - pass - - # Exit a parse tree produced by Gold#stmtAssignInc. - def exitStmtAssignInc(self, ctx:Gold.StmtAssignIncContext): - pass - - - # Enter a parse tree produced by Gold#stmtAssignDec. - def enterStmtAssignDec(self, ctx:Gold.StmtAssignDecContext): - pass - - # Exit a parse tree produced by Gold#stmtAssignDec. - def exitStmtAssignDec(self, ctx:Gold.StmtAssignDecContext): - pass - - - # Enter a parse tree produced by Gold#block. - def enterBlock(self, ctx:Gold.BlockContext): - pass - - # Exit a parse tree produced by Gold#block. - def exitBlock(self, ctx:Gold.BlockContext): - pass - - - # Enter a parse tree produced by Gold#unit. - def enterUnit(self, ctx:Gold.UnitContext): - pass - - # Exit a parse tree produced by Gold#unit. - def exitUnit(self, ctx:Gold.UnitContext): - pass - - diff --git a/jeff65/gold/grammar/__init__.py b/jeff65/gold/grammar/__init__.py deleted file mode 100644 index 9efe776..0000000 --- a/jeff65/gold/grammar/__init__.py +++ /dev/null @@ -1,23 +0,0 @@ -# jeff65 gold-syntax parser module -# Copyright (C) 2018 jeff65 maintainers -# -# This program is free software: you can redistribute it and/or modify -# it under the terms of the GNU General Public License as published by -# the Free Software Foundation, either version 3 of the License, or -# (at your option) any later version. -# -# This program is distributed in the hope that it will be useful, -# but WITHOUT ANY WARRANTY; without even the implied warranty of -# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -# GNU General Public License for more details. -# -# You should have received a copy of the GNU General Public License -# along with this program. If not, see . - -from .Gold import Gold as Parser -from .GoldListener import GoldListener as ParseListener - -__all__ = [ - 'Parser', - 'ParseListener', -] diff --git a/jeff65/gold/lexer.py b/jeff65/gold/lexer.py deleted file mode 100644 index 80631b5..0000000 --- a/jeff65/gold/lexer.py +++ /dev/null @@ -1,345 +0,0 @@ -# jeff65 gold-syntax lexer -# Copyright (C) 2017 jeff65 maintainers -# -# This program is free software: you can redistribute it and/or modify -# it under the terms of the GNU General Public License as published by -# the Free Software Foundation, either version 3 of the License, or -# (at your option) any later version. -# -# This program is distributed in the hope that it will be useful, -# but WITHOUT ANY WARRANTY; without even the implied warranty of -# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -# GNU General Public License for more details. -# -# You should have received a copy of the GNU General Public License -# along with this program. If not, see . - -import re -from . import ast -from .grammar import Parser -from antlr4.CommonTokenFactory import CommonTokenFactory -from antlr4.Token import Token - - -known_words = { - # arithmetic operators - '+': Parser.OPERATOR_PLUS, - '-': Parser.OPERATOR_MINUS, - '*': Parser.OPERATOR_TIMES, - '/': Parser.OPERATOR_DIVIDE, - - # logical operators - 'not': Parser.OPERATOR_NOT, - 'and': Parser.OPERATOR_AND, - 'or': Parser.OPERATOR_OR, - - # bitwise operators - '>>': Parser.OPERATOR_SHR, - '<<': Parser.OPERATOR_SHL, - 'bitand': Parser.OPERATOR_BITAND, - 'bitor': Parser.OPERATOR_BITOR, - 'bitxor': Parser.OPERATOR_BITXOR, - - # comparison operators - '!=': Parser.OPERATOR_NE, - '==': Parser.OPERATOR_EQ, - '<=': Parser.OPERATOR_LE, - '>=': Parser.OPERATOR_GE, - '<': Parser.OPERATOR_LT, - '>': Parser.OPERATOR_GT, - - # assignment operators - '=': Parser.OPERATOR_ASSIGN, - '+=': Parser.OPERATOR_ASSIGN_INC, - '-=': Parser.OPERATOR_ASSIGN_DEC, - - # member access operators - '.': Parser.OPERATOR_DOT, - - # pointer operators - '@': Parser.OPERATOR_DEREF, - '&': Parser.OPERATOR_REF, - - # statement leaders - 'constant': Parser.STMT_CONSTANT, - 'for': Parser.STMT_FOR, - 'fun': Parser.STMT_FUN, - 'if': Parser.STMT_IF, - 'isr': Parser.STMT_ISR, - 'let': Parser.STMT_LET, - 'return': Parser.STMT_RETURN, - 'use': Parser.STMT_USE, - 'while': Parser.STMT_WHILE, - - # storage classes - 'mut': Parser.STORAGE_MUT, - 'stash': Parser.STORAGE_STASH, - - # assorted punctuation - 'do': Parser.PUNCT_DO, - 'else': Parser.PUNCT_ELSE, - 'elseif': Parser.PUNCT_ELSEIF, - 'end': Parser.PUNCT_END, - 'endfun': Parser.PUNCT_ENDFUN, - 'endisr': Parser.PUNCT_ENDISR, - 'in': Parser.PUNCT_IN, - 'then': Parser.PUNCT_THEN, - 'to': Parser.PUNCT_TO, - ':': Parser.PUNCT_COLON, - ';': Parser.PUNCT_SEMICOLON, - ',': Parser.PUNCT_COMMA, - '->': Parser.PUNCT_ARROWR, - - # delimiters - '/*': Parser.COMMENT_OPEN, # see also Lexer.__m_comment_open - '*/': Parser.COMMENT_CLOSE, # see also Lexer.__m_comment_close - '"': Parser.STRING_DELIM, # see also Lexer.__m_string_delim - '(': Parser.PAREN_OPEN, - ')': Parser.PAREN_CLOSE, - '[': Parser.BRACKET_OPEN, - ']': Parser.BRACKET_CLOSE, - '{': Parser.BRACE_OPEN, - '}': Parser.BRACE_CLOSE, -} - - -# this class is way over-encapulated for a normal Python class, mostly as a -# safeguard against antlr4 doing weird things like accessing members beginning -# with underscores. -class Lexer: - # non-whitespace characters which can end tokens. - __specials = re.escape(r'()[]{}:;.,"\@&') - - # matches one or more whitespace characters, including newlines - __m_whitespace = re.compile(r'\s+', re.M) - - # matches a digit, followed by zero or more non-token-ending characters - __m_numeric = re.compile(r'\d[^\s{}]*'.format(__specials)) - - # matches a letter, followed by zero or more non-token-ending characters. - # Note that as written, this will actually match numbers as well, but the - # 'numeric' regex is always run first, which removes tokens beginning with - # numbers. - __m_word = re.compile(r'\w[^\s{}]*'.format(__specials)) - - # match comment-open and comment-close characters, respectively. This must - # be a separate rule from the sprinkle rule because a sprinkle prefixed - # with a comment-open sequence starts a comment. - # These have to agree with the values in known_words. - __m_comment_open = re.compile(re.escape('/*')) - __m_comment_close = re.compile(re.escape('*/')) - - # Matches either comment-open or comment-close - __m_comment_nest = re.compile(r'{}|{}'.format(__m_comment_open.pattern, - __m_comment_close.pattern)) - - # matches a non-alphanumeric character, including a special, followed by - # zero or more non-token-ending characters. Note that this means that only - # one special can ever be consumed at a time, and they will always break - # off into their own tokens, even when adjacent. - __m_sprinkle = re.compile(r'[^\w\s][^\w\s{}]*'.format(__specials)) - - # match the string escape character followed by one character, and string - # delimiter, respectively. These have to agree with the values in - # known_words. - __m_str_escape = re.compile(r'\\.', re.M) - __m_str_delim = re.compile(re.escape(r'"')) - - # matches characters that affect lexing of strings - __m_str_control = re.compile(r'{}|{}'.format(__m_str_escape.pattern, - __m_str_delim.pattern)) - - def __init__(self, stream, name='', factory=None): - self.__stream = stream - self.__name = name - self.__current = None - self.__line = 0 - self.__column = 0 - self.__factory = factory or CommonTokenFactory.DEFAULT - self.__comments = [] - self.__string_start = None - - # Interface functions for ANTLR4 - @property - def _factory(self): - return self.__factory - - def setTokenFactory(self, factory): - self.__factory = factory # pragma: no cover - - def getInputStream(self): - return self.__stream # pragma: no cover - - def getSourceName(self): - return self.__name # pragma: no cover - - @property - def line(self): - return self.__line - - @property - def column(self): - return self.__column - - def nextToken(self) -> Token: - # Advance to the next line if necessary - if self.__current is None or self.__column >= len(self.__current): - try: - self.__current = next(self.__stream) - self.__line += 1 - self.__column = 0 - except StopIteration: - # If we're in comment mode or string mode, we are NOT expecting - # this kind of behavior and will kick up a fuss. - if len(self.__comments) == 1: - raise ast.ParseError( - "Premature end of input while parsing comment " + - "starting at {}:{}".format(*self.__comments[0])) - elif len(self.__comments) > 1: - locs = ", ".join("{}:{}".format(line, column) - for line, column in self.__comments) - raise ast.ParseError( - "Premature end of input while parsing nested " + - "comments, starting at {}".format(locs)) - return self.__make_token(Parser.EOF, '<$EOF>') - - # Comment mode means that we parse until either a begin or end comment - if len(self.__comments) > 0: - m = self.__m_comment_nest.search(self.__current, self.__column) - if not m: - # the rest of the line is a comment - token = self.__make_token(Parser.COMMENT_TEXT, - self.__current[self.__column:], - Token.HIDDEN_CHANNEL) - self.__column = len(self.__current) - return token - elif m.start() == self.__column: - # the comment delimiter is right here! - here = self.__here() - token = self.__produce(Parser.MYSTERY, m, Token.HIDDEN_CHANNEL) - if token.type == Parser.COMMENT_OPEN: - self.__comments.append(here) - elif token.type == Parser.COMMENT_CLOSE: - self.__comments.pop() - return token - else: - # comment the text before the delimiter - token = self.__make_token(Parser.COMMENT_TEXT, - self.__current[self.__column: - m.start()], - Token.HIDDEN_CHANNEL) - self.__column = m.start() - return token - - # String mode emits a sequence of STRING tokens, which will be - # concatenated by the parser. - if self.__string_start: - m = self.__m_str_control.search(self.__current, self.__column) - if not m: - # the rest of the line is a string - token = self.__make_token(Parser.STRING, - self.__current[self.__column:]) - self.__column = len(self.__current) - return token - elif m.start() == self.__column: - # the string control character is right here! - token = self.__produce(Parser.MYSTERY, m) - if token.type == Parser.STRING_DELIM: - # ending a string produces another empty string token to be - # concatenated. - self.__string_start = None - return self.__make_token(Parser.STRING, "") - # it must be an escape character - return self.__recast_token(token, Parser.STRING, token.text[1]) - else: - # string the text before the control - token = self.__make_token(Parser.STRING, - self.__current[self.__column: - m.start()]) - self.__column = m.start() - return token - - # Whitespace is sent to the hidden channel - m = self.__match_with(self.__m_whitespace) - if m: - return self.__produce(Parser.WHITESPACE, m, Token.HIDDEN_CHANNEL) - - # this MUST be run before the word match, see above - m = self.__match_with(self.__m_numeric) - if m: - return self.__produce(Parser.NUMERIC, m) - - # this MUST be run after the number match, see above - m = self.__match_with(self.__m_word) - if m: - return self.__produce(Parser.IDENTIFIER, m) - - # comments require special handling. They can't be lumped in with - # sprinkles because if a comment sequence begins what would otherwise - # be a sprinkle, we switch into comment mode. - m = self.__match_with(self.__m_comment_open) - if m: - self.__comments.append(self.__here()) - return self.__produce(Parser.COMMENT_OPEN, m, Token.HIDDEN_CHANNEL) - - # non-alphanumeric words, mostly operators, delimiters, etc. We call - # these "sprinkles" for whimsy value. - m = self.__match_with(self.__m_sprinkle) - if m: - token = self.__produce(Parser.MYSTERY, m) - if token.type == Parser.STRING_DELIM: - # enter string mode, starting by emitting an empty string - # token. The parser concatenates sequences of string tokens - # automatically, so we can do this to allow for the fact that - # we MUST emit a token but don't want to duplicate logic. - self.__string_start = (token.line, token.column) - return self.__recast_token(token, Parser.STRING, "") - - return token - - # We literally didn't match anything (???) so go ahead and emit an - # OFFICIAL TOKEN OF MYSTERY containing the next character to the lucky - # winner. Mystery tokens are a surefire way of putting the parser into - # FABULOUS PRIZES MODE. - token = self.__make_token(Parser.MYSTERY, - self.__current[self.__column]) - self.__column += 1 - # (note that the prizes in question are parse errors. If you don't like - # parse errors, then you may not enjoy this mode very much.) - return token - - # Helper functions - def __here(self): - return (self.__line, self.__column) - - def __match_with(self, regex): - return regex.match(self.__current, self.__column) - - def __produce(self, default_sym, match, channel=None) -> Token: - # see if the symbol is in the table - if match.group() in known_words: - sym = known_words[match.group()] - else: - sym = default_sym - token = self.__make_token(sym, match.group(), channel) - self.__column = match.end() - return token - - def __recast_token(self, token: Token, sym, text, channel=None) -> Token: - return self.__factory.create( - (self, self.__stream), - sym, - text, - channel or token.channel, - token.start, token.stop, - token.line, token.column) - - def __make_token(self, sym, text, channel=None) -> Token: - return self.__factory.create( - (self, self.__stream), - sym, - text, - channel or Token.DEFAULT_CHANNEL, - -1, -1, # start, stop - self.__line, - self.__column) diff --git a/jeff65/gold/passes/simplify.py b/jeff65/gold/passes/simplify.py new file mode 100644 index 0000000..b1e92bd --- /dev/null +++ b/jeff65/gold/passes/simplify.py @@ -0,0 +1,298 @@ +# jeff64 gold-syntax CST -> AST simplification +# Copyright (C) 2018 jeff65 maintainers +# +# This program is free software: you can redistribute it and/or modify +# it under the terms of the GNU General Public License as published by +# the Free Software Foundation, either version 3 of the License, or +# (at your option) any later version. +# +# This program is distributed in the hope that it will be useful, +# but WITHOUT ANY WARRANTY; without even the implied warranty of +# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +# GNU General Public License for more details. +# +# You should have received a copy of the GNU General Public License +# along with this program. If not, see . + +from .. import ast, pattern +from ..grammar import T +from ..pattern import Predicate as P +from ... import parsing + + +def require_token(t): + return P.require(lambda n, c: n.t == t) + + +def token(t, key=None): + return P(key, lambda n, c: n.t == t) + + +def unop(operator, sym): + @pattern.match( + ast.AstNode('expr', P('position'), children=[ + token(operator), P('rhs'), + ])) + def name_unop(self, position, rhs): + return ast.AstNode(sym, position, children=[rhs]) + + return name_unop + + +def binop(operator, sym): + @pattern.match( + ast.AstNode('expr', P('position'), children=[ + P('lhs'), token(operator), P('rhs'), + ])) + def name_binop(self, position, lhs, rhs): + return ast.AstNode(sym, position, children=[lhs, rhs]) + + return name_binop + + +def left_recursion(sym): + @pattern.match( + ast.AstNode(sym, P('position'), children=[ + ast.AstNode(sym, P.any(), children=[ + P.zero_or_more_nodes('children0') + ]), + P.zero_or_more_nodes('children1'), + ])) + def collapse_left_recursion(self, position, children0, children1): + return ast.AstNode(sym, position, children=children0+children1) + + return collapse_left_recursion + + +@pattern.transform(pattern.Order.Ascending) +class Simplify: + transform_attrs = False + + @pattern.match( + ast.AstNode('expr', P.any(), children=[ + P.any_node('node'), + ])) + def remove_single_expr(self, node): + return node + + collapse_unit = left_recursion('unit') + collapse_block = left_recursion('block') + + @pattern.match( + ast.AstNode('alist_inner', P('position'), children=[ + ast.AstNode('alist_inner', P.any(), children=[ + P.zero_or_more_nodes('children0') + ]), + require_token(T.PUNCT_COMMA), + P.zero_or_more_nodes('children1'), + ])) + def collapse_alist_inner(self, position, children0, children1): + return ast.AstNode('alist_inner', position, + children=children0+children1) + + @pattern.match( + ast.AstNode('alist', P('position'), children=[ + ast.AstNode('alist_inner', P.any(), children=[ + P.zero_or_more_nodes('children'), + ]) + ])) + def collapse_alist(self, position, children): + return ast.AstNode('alist', position, children=children) + + @pattern.match( + ast.AstNode('stmt_use', P('position'), children=[ + require_token(T.STMT_USE), + P('unit_name'), + ])) + def collapse_stmt_use(self, position, unit_name): + return ast.AstNode('use', position, attrs={ + 'name': unit_name.text, + }) + + @pattern.match( + ast.AstNode('stmt_constant', P('position'), children=[ + require_token(T.STMT_CONSTANT), + ast.AstNode('declaration', P.any(), children=[ + P('name'), + require_token(T.PUNCT_COLON), + P('ty'), + ]), + require_token(T.OPERATOR_ASSIGN), + P('rhs'), + ])) + def collapse_stmt_constant(self, position, name, ty, rhs): + return ast.AstNode('constant', position, attrs={ + 'name': name.text, + 'type': ty, + }, children=[rhs]) + + @pattern.match( + ast.AstNode('stmt_let', P('position'), children=[ + require_token(T.STMT_LET), + ast.AstNode('storage', P.any(), children=[ + P.zero_or_more_nodes('storage'), + ]), + ast.AstNode('declaration', P.any(), children=[ + P('name'), + require_token(T.PUNCT_COLON), + P('ty'), + ]), + require_token(T.OPERATOR_ASSIGN), + P('rhs'), + ])) + def collapse_stmt_let(self, position, storage, name, ty, rhs): + return ast.AstNode('let', position, attrs={ + 'name': name.text, + 'type': ty, + **{'storage': s.text for s in storage}, + }, children=[rhs]) + + @pattern.match( + ast.AstNode('stmt_assign', P('position'), children=[ + P('lhs'), + require_token(T.OPERATOR_ASSIGN), + P('rhs'), + ])) + def collapse_stmt_assign(self, position, lhs, rhs): + return ast.AstNode('set', position, children=[lhs, rhs]) + + # TODO: handle arguments, return values + @pattern.match( + ast.AstNode('stmt_fun', P('position'), children=[ + require_token(T.STMT_FUN), + P('name'), + require_token(T.PAREN_OPEN), + P.any(), # plist + require_token(T.PAREN_CLOSE), + ast.AstNode('block', P.any(), children=[ + P.zero_or_more_nodes('body'), + ]), + require_token(T.PUNCT_ENDFUN), + ])) + def collapse_stmt_fun(self, position, name, body): + return ast.AstNode('fun', position, attrs={ + 'name': name.text, + 'return': None, + 'args': [], + }, children=body) + + @pattern.match(ast.AstNode('type_id', P.any(), children=[P('ty')])) + def simple_type(self, ty): + return ty.text + + @pattern.match( + ast.AstNode('type_id', P('position'), children=[ + token(T.OPERATOR_REF), + ast.AstNode('storage', P.any(), children=[ + P.zero_or_more_nodes('storage'), + ]), + P('ty'), + ])) + def ref_type(self, position, storage, ty): + return ast.AstNode('type_ref', position, attrs={ + 'type': ty, + **{'storage': s.text for s in storage}, + }) + + @pattern.match( + ast.AstNode('expr', P('position'), children=[token(T.NUMERIC, 'n')])) + def numeric(self, position, n): + try: + if n.text.startswith('0x'): + value = int(n.text[2:], 16) + elif n.text.startswith('0o'): + value = int(n.text[2:], 8) + elif n.text.startswith('0b'): + value = int(n.text[2:], 2) + else: + value = int(n.text) + except ValueError as e: + raise parsing.ParseError(str(e)) + + return ast.AstNode('numeric', position, attrs={'value': value}) + + @pattern.match( + ast.AstNode('expr', P('position'), children=[ + token(T.IDENTIFIER, 'id'), + ])) + def identifier(self, position, id): + return ast.AstNode('identifier', position, attrs={ + 'name': id.text, + }) + + @pattern.match( + ast.AstNode('expr', P.any(), children=[ + token(T.PAREN_OPEN), P('inner'), token(T.PAREN_CLOSE), + ])) + def drop_expr_parens(self, inner): + return inner + + name_negate = unop(T.OPERATOR_MINUS, 'negate') + name_deref = unop(T.OPERATOR_DEREF, 'deref') + name_add = binop(T.OPERATOR_PLUS, 'add') + name_sub = binop(T.OPERATOR_MINUS, 'sub') + name_mul = binop(T.OPERATOR_TIMES, 'mul') + name_div = binop(T.OPERATOR_DIVIDE, 'div') + + @pattern.match( + ast.AstNode('expr', P('position'), children=[ + P('namespace'), + token(T.OPERATOR_DOT), + ast.AstNode('member', P.any(), children=[ + P('member'), + ]), + ])) + def name_member_access(self, position, namespace, member): + return ast.AstNode('member_access', position, attrs={ + 'member': member.text, + }, children=[namespace]) + + @pattern.match( + ast.AstNode('expr', P('position'), children=[ + P('function'), + token(T.PAREN_OPEN), + ast.AstNode('alist', P.any(), children=[ + P.zero_or_more_nodes('args'), + ]), + token(T.PAREN_CLOSE), + ])) + def name_call(self, position, function, args): + return ast.AstNode('call', position, attrs={ + 'target': function, + }, children=args) + + # Collapse left-recursion on strings. Note that the list we use to build + # the string is wrapped in another list to protect it from being spliced + # directly into the node children. + @pattern.match(ast.AstNode('string_inner', P.any(), children=[])) + def string_inner_empty(self): + return [[]] + + @pattern.match( + ast.AstNode('string_inner', P.any(), children=[ + P('string0'), + token(T.STRING, 'string1'), + ])) + def string_inner_segment(self, string0, string1): + string0.append(string1.text) + return [string0] + + @pattern.match( + ast.AstNode('string_inner', P.any(), children=[ + P('string0'), + token(T.STRING_ESCAPE, 'string1'), + ])) + def string_inner_escape(self, string0, string1): + string0.append(string1.text[1]) + return [string0] + + @pattern.match( + ast.AstNode('string', P('position'), children=[ + require_token(T.STRING_DELIM), + P('value'), + require_token(T.STRING_DELIM), + ])) + def collapse_string(self, position, value): + return ast.AstNode('string', position, attrs={ + 'value': "".join(value), + }) diff --git a/jeff65/gold/pattern.py b/jeff65/gold/pattern.py index 78ecb68..cd19272 100644 --- a/jeff65/gold/pattern.py +++ b/jeff65/gold/pattern.py @@ -21,6 +21,7 @@ """ import enum +import inspect from collections import deque from . import ast @@ -75,7 +76,7 @@ def _decorate_transform(cls): else: _, pattern, template = value if isinstance(pattern, ast.AstNode): - predicates = pattern.transform(analyser) + predicates = pattern.transform(analyser, always_list=True) else: # do the non-recursive transform predicates = [analyser.make_predicate(pattern)] @@ -193,11 +194,10 @@ def any_node(cls, key=None, with_children=None): @classmethod def node(cls, pt, pp, pa, pcs, key=None): def _node_predicate(node, captures): - if not pt._match(node.t, captures): - return False - if not pp._match(node.position, captures): - return False - if not pa._match(node.attrs, captures): + if not (isinstance(node, ast.AstNode) + and pt._match(node.t, captures) + and pp._match(node.position, captures) + and pa._match(node.attrs, captures)): return False cq = deque(node.children) pcq = deque(pcs) @@ -210,11 +210,22 @@ def _node_predicate(node, captures): return cls(key, _node_predicate) @classmethod - def require(cls, value, exc=None): + def require(cls, value_or_predicate, exc=None): exc = exc or MatchError + if callable(value_or_predicate): + predicate = value_or_predicate + try: + value = inspect.getsource(value_or_predicate) + except OSError: + value = '' + else: + def predicate(v, c): + return v == value_or_predicate + value = value_or_predicate + def _p_require(v, captures): - if value != v: + if not predicate(v, captures): raise exc(f"Expected {value} got {v}") return True return cls(None, _p_require) diff --git a/jeff65/parsing.py b/jeff65/parsing.py new file mode 100644 index 0000000..d66e272 --- /dev/null +++ b/jeff65/parsing.py @@ -0,0 +1,883 @@ +# jeff65 parser generator +# Copyright (C) 2018 jeff65 maintainers +# +# This program is free software: you can redistribute it and/or modify +# it under the terms of the GNU General Public License as published by +# the Free Software Foundation, either version 3 of the License, or +# (at your option) any later version. +# +# This program is distributed in the hope that it will be useful, +# but WITHOUT ANY WARRANTY; without even the implied warranty of +# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +# GNU General Public License for more details. +# +# You should have received a copy of the GNU General Public License +# along with this program. If not, see . + +import attr +import re +import time +from itertools import chain + + +class ParseError(Exception): + def __init__(self, *args, **kwargs): + super().__init__(*args, **kwargs) + + +@attr.s(slots=True, frozen=True) +class TextSpan: + start_line = attr.ib() + start_column = attr.ib() + end_line = attr.ib() + end_column = attr.ib() + + def __attrs_post_init__(self): + if self.start > self.end: + t = self.start_line + object.__setattr__(self, 'start_line', self.end_line) + object.__setattr__(self, 'end_line', t) + t = self.start_column + object.__setattr__(self, 'start_column', self.end_column) + object.__setattr__(self, 'end_column', t) + + @property + def start(self): + return (self.start_line, self.start_column) + + @property + def end(self): + return (self.end_line, self.end_column) + + def __bool__(self): + return self.start < self.end + + def __contains__(self, other): + return ( + isinstance(other, TextSpan) + and self.start <= other.start + and other.end <= self.end) + + @staticmethod + def cover(spans): + """Return a TextSpan covering all of the given spans. + + The result is the shortest span t such that every given is contained in + it. Note that because TextSpans are always contiguous, there may exist + spans which are not contained in any of the given spans, but are + contained in the cover span. + """ + return TextSpan( + *min(s.start for s in spans), + *max(s.end for s in spans)) + + def __str__(self): + start = f'{self.start_line}:{self.start_column}' + end = f'{self.end_line}:{self.end_column}' + return f'{start}-{end}' + + +@attr.s(slots=True, frozen=True) +class Token: + t = attr.ib() + text = attr.ib() + channel = attr.ib(default=0, cmp=False) + span = attr.ib(default=None, cmp=False) + + def _pretty(self, indent): + yield (indent, f'{self.t}={self.text!r} {self.span}') + + +class ReStream: + """Regex-matchable stream.""" + + CHANNEL_ALL = -1 + CHANNEL_DEFAULT = 0 + CHANNEL_HIDDEN = 1 + + def __init__(self, stream): + self.stream = iter(stream) + self.current = None + self.line = 0 + self.column = 0 + + try: + self.advance_line() + except StopIteration: + self.current = "" + self.line = 1 + + def advance_line(self): + """Advance the stream position to the beginning of the next line.""" + try: + self.current = next(self.stream) + except StopIteration: + raise + else: + self.line += 1 + self.column = 0 + + def assure_line(self): + """Assures that at least one character remains in the current line.""" + if self.column == len(self.current): + self.advance_line() + + def match(self, regex): + """Match the given regex at the current stream position. + + In order to actually advance the position, call ReStream.produce() with + the returned match object. + + Returns a match object if successful, None otherwise. + """ + + self.assure_line() + return regex.match(self.current, self.column) + + def produce(self, symbol, match, channel=CHANNEL_DEFAULT): + """Produce a token and advance the position.""" + + token = Token(symbol, match.group(), channel, + TextSpan( + self.line, self.column, + self.line, match.end())) + self.column = match.end() + return token + + def rewind(self, token: Token): + """Rewinds by one token. + + This may only be called if the last method to be called on the ReStream + object was the produce() call which returned the given token. + """ + + assert token.span.end == (self.line, self.column) + self.column = token.span.start_column + + def produce_eof(self, symbol): + """Produce an EOF token.""" + return Token(symbol, None, self.CHANNEL_ALL, + TextSpan(self.line, self.column, self.line, self.column)) + + +class Lexer: + def __init__(self, eof, rules): + """Create a lexer callable. + + rules should be a list of tuples of one of the following forms: + (pattern, token_type) + (mode, pattern, token_type) + (mode, pattern, token_type, channel) + """ + + self.eof = eof + self.mode_rules = {} + for mptc in rules: + mode, channel = Parser.NORMAL_MODE, ReStream.CHANNEL_DEFAULT + if len(mptc) == 2: + pattern, tt = mptc + elif len(mptc) == 3: + mode, pattern, tt = mptc + else: + mode, pattern, tt, channel = mptc + rs = self.mode_rules.setdefault(mode, []) + rs.append((re.compile(pattern), tt, channel)) + + def __call__(self, stream: ReStream, mode: int) -> Token: + try: + stream.assure_line() + except StopIteration: + return stream.produce_eof(self.eof) + + for regex, tt, channel in self.mode_rules[mode]: + m = stream.match(regex) + if m: + return stream.produce(tt, m, channel) + assert False, "no match!" # TODO: proper exception + + +def _convert_lhs(lhs): + if not isinstance(lhs, Symbol): + return Symbol(lhs) + return lhs + + +def _convert_rhs(rhs): + result = [] + for sym in rhs: + if isinstance(sym, tuple): + # alternations are tuples + sym = frozenset(_convert_lhs(s) for s in sym) + elif isinstance(sym, frozenset): + # already converted + pass + else: + sym = frozenset({_convert_lhs(sym)}) + result.append(sym) + return tuple(result) + + +@attr.s(slots=True, frozen=True, repr=False) +class Symbol: + value = attr.ib() + + @property + def is_terminal(self): + # we represent bare nonterminals as strings + return not isinstance(self.value, str) + + def __repr__(self): + return f"`{self.value}" + + def extend(self, start, end): + return ExtendedSymbol(self.value, start, end) + + @property + def parent(self): + return Symbol(self.value) + + +@attr.s(slots=True, frozen=True, repr=False) +class ExtendedSymbol(Symbol): + start = attr.ib() + end = attr.ib() + + def __repr__(self): + return f"`{self.start}_{self.value!r}_{self.end}" + + +@attr.s(slots=True, frozen=True, repr=False) +class Rule: + lhs = attr.ib(converter=_convert_lhs) + rhs = attr.ib(converter=_convert_rhs) + prec = attr.ib(default=None) + rassoc = attr.ib(default=False) + mode = attr.ib(default=0) # Parser.NORMAL_MODE + pointer = attr.ib(default=None) + parent = attr.ib(default=None) + + def with_pointer(self, pointer): + return attr.evolve(self, pointer=pointer) + + @property + def next_symbols(self): + if self.pointer is None: + raise Exception('Rule has no pointer') + elif self.pointer == len(self.rhs): + return frozenset() + return self.rhs[self.pointer] + + @property + def advanced(self): + if self.pointer is None: + raise Exception('Rule has no pointer') + elif self.pointer == len(self.rhs): + raise Exception('Rule cannot be advanced') + return self.with_pointer(self.pointer + 1) + + def __repr__(self): + syms = [] + for sym in self.rhs: + if len(sym) == 1: + syms.append(str(next(iter(sym)))) + else: + alts = ' | '.join(str(s) for s in sym) + syms.append(f'({alts})') + if self.pointer is not None: + syms.insert(self.pointer, '.') + rhs = ' '.join(syms) + if self.prec is not None: + return f'{self.lhs} -> {rhs} ({self.prec})' + return f'{self.lhs} -> {rhs}' + + +class ItemSet: + def __init__(self, grammar, items): + self.items = set(items) + + # complete the itemset by repeatedly finding all of the productions + # which come after pointers in the set, and adding all the rules that + # produce them recursively. + while True: + old_size = len(self.items) + nexts = set( + s for s in chain.from_iterable( + r.next_symbols for r in self.items) + if not s.is_terminal) + self.items.update( + grammar.rules[r].with_pointer(0) + for r in grammar.find_rule_indices(nexts)) + if len(self.items) == old_size: + break + + @property + def next_symbols(self): + """Gets a list of possible next symbols.""" + return set(chain.from_iterable(r.next_symbols for r in self.items)) + + def advance(self, symbol): + """Advances the itemset by the given symbol. + + Returns a frozenset of items where items which can be advanced by the + given symbol have been, and items which cannot have been dropped. + """ + return frozenset( + item.advanced for item in self.items + if symbol in item.next_symbols) + + @property + def mode(self): + """Gets the lexer mode for this itemset.""" + + # A simple example of rules using lexer modes: + # + # R -> n S z (mode U) + # S -> x y (mode V) + # + # where n is a mode-0 token and x, y, z are mode U tokens. In this + # case, we want to accept n, shift to mode V, accept tokens x, y, z, + # then shift back to mode U. The itemsets for the above rules are: + # + # 0. R -> . n S z + # + # 1. R -> n . S z + # + S -> . x y + # + # 2. S -> x . y + # + # 3. S -> x y . + # + # 4. R -> n S . z + # + # 5. R -> n S z . + # + # Clearly, in set 0 we want mode U so we can get n, shifting us to set + # 1. The set stack is now [0, 1], and we want to be in mode V so we can + # get x for our lookahead. + # + # Now we shift set 2, making our set stack [0, 1, 2]. We still want + # mode V to get y. This lets us shift set 3, set stack [0, 1, 2, 3]. We + # still want mode V, so we can get z. + # + # At this point, we reduce by S, which makes our set stack [0, 1, 4]. + # We don't get a new lookahead after a reduce, so we don't care about + # the mode. + # + # Then we shift by 5, set stack [0, 1, 4, 5]. At this point, we need to + # be back in mode U for whatever comes after R. + # + # From the above we can derive the following set-mode associations. + # Pairs marked (I) indicates that the mode has the same mode as the + # previous one on the stack (ignoring set 4, which doesn't really have + # a mode): 0=U, 1=V, 2=V (I), 3=V (I), 5=U + # + # In sets 0 and 1, we're at position 0 in a rule with the appropriate + # mode, so we assign the mode based on that. Set 2 can inherit. In set + # 5, we're at the end of a rule with the appropriate mode. Assigning + # based on that also assigns mode V to set 3, which is not necessary, + # but harmless. + # + # Therefore, we only care about rules where the pointer is at the + # beginning or end. + modes = {r.mode for r in self.items + if r.pointer == 0 or len(r.next_symbols) == 0} + + # If there are no such rules, we can inherit. Note that we can't assign + # based on the rule that we're in the middle of, because then we'd be + # trying to assign mode U to set 1, which we're already assigning mode + # V to. + if len(modes) == 0: + return Parser.INHERIT_MODE + + # If we end up with two rules giving us conflicting modes, we will + # consider that an error in the grammar. + assert len(modes) == 1, f"mode/mode conflict: {self.items}" + return modes.pop() + + +class Grammar: + EMPTY = Symbol(object()) + END = object() + + def __init__(self, start_symbol, end_symbols, rules): + self.rules = rules + self.start_symbol = _convert_lhs(start_symbol) + self.end_symbols = frozenset(_convert_lhs(s) for s in end_symbols) + + @property + def symbols(self): + ts = set() + for rule in self.rules: + ts.add(rule.lhs) + for syms in rule.rhs: + ts.update(syms) + return ts + + def find_rule_indices(self, symbols): + """Returns a list of rule indices which produce the given symbols.""" + return [k for k, r in enumerate(self.rules) if r.lhs in symbols] + + def find_starting_rule_index(self): + """Finds the starting rule given the start symbol.""" + starts = self.find_rule_indices([self.start_symbol]) + if len(starts) == 0: + raise Exception('No starting rule found') + elif len(starts) > 1: + raise Exception('Multiple starting rules found') + elif len(self.rules[starts[0]].rhs) != 1: + raise Exception('Starting rule must have one token') + else: + return starts[0] + + def build_firstsets(self): + """Builds the First sets for every extended symbol. + + The First set is the set of all terminals which can grammatically + appear at the beginning of a given symbol. + """ + + start_time = time.perf_counter() + firstsets = {} + + # pre-populate with empty firstsets (for nonterminals) and identity + # firstsets (for terminals) + for sym in self.symbols: + if sym.is_terminal: + firstsets[sym] = {sym.parent} + else: + firstsets[sym] = set() + + # 1. if V -> x, then First(V) contains x + # 2. if V -> (), then First(V) contains () + nzrules = [] + for rule in self.rules: + if len(rule.rhs) == 0: + firstsets[rule.lhs].add(self.EMPTY) + continue + for sym in rule.rhs[0]: + if sym.is_terminal: + firstsets[rule.lhs].update(firstsets[sym]) + else: + # cache rules that rule 3 applies to in advance + nzrules.append(rule) + + # 3. if V -> A B C, then First(V) contains First(A) - (). If First(A) + # contains (), then First(V) also contains First(B), etc. If A, B, + # and C all contain (), then First(V) contains (). + # + # Since rules can be (mutually) left-recursive, we may have to apply + # this rule multiple times to catch everything. + updated = True + count = 0 + while updated: + count += 1 + updated = False + for rule in nzrules: + # we know in advance that these rules begin with a nonterminal + # on the right-hand side, because they're the ones we cached + # when applied rules 1 & 2. + old_len = len(firstsets[rule.lhs]) + for symbols in rule.rhs: + fs = frozenset(chain.from_iterable( + firstsets[s] for s in symbols)) + if self.EMPTY not in fs: + firstsets[rule.lhs].update(fs) + break + firstsets[rule.lhs].update(fs - {self.EMPTY}) + else: + firstsets[rule.lhs].add(self.EMPTY) + if len(firstsets[rule.lhs]) > old_len: + updated = True + + end_time = time.perf_counter() + elapsed_ms = (end_time - start_time) * 1000 + print(f'Built firstsets ({count} cycles) in {elapsed_ms:.2f}ms') + return firstsets + + def build_followsets(self): + """Builds the Follow sets for every extended symbol. + + The Follow set is the set of all terminals which can grammatically + appear after the given symbol. + """ + + firstsets = self.build_firstsets() + start_time = time.perf_counter() + followsets = {} + + # pre-populate with empty followsets + for sym in self.symbols: + if sym == self.start_symbol: + followsets[sym] = {s.parent for s in self.end_symbols} + else: + followsets[sym] = set() + + # suppose we have a rule R -> a*Db. Then we add First(b) to Follow(D). + for rule in self.rules: + for k in range(len(rule.rhs) - 1): + for s in rule.rhs[k]: + if not s.is_terminal: + for t in rule.rhs[k+1]: + followsets[s].update(firstsets[t]) + + # suppose we have a rule R -> a*D. Then we add Follow(R) to Follow(D). + # Because we can end up with irritating things like two follow sets + # mutually depending on each other, we've handled this by just applying + # the rule until we reach a fixed state. + updated = True + count = 0 + while updated: + count += 1 + updated = False + for rule in self.rules: + + # empty rules don't tell us anything for this pass + if len(rule.rhs) == 0: + continue + + for s in rule.rhs[-1]: + if not s.is_terminal: + old_len = len(followsets[s]) + followsets[s].update( + followsets[rule.lhs]) + if len(followsets[s]) > old_len: + updated = True + + end_time = time.perf_counter() + elapsed_ms = (end_time - start_time) * 1000 + print(f'Built followsets ({count} cycles) in {elapsed_ms:.2f}ms') + return followsets + + def build_parser(self, hidden=None, channel=ReStream.CHANNEL_DEFAULT): + print(f'Grammar has {len(self.rules)} rules') + + start_time_t = time.perf_counter() + translation_table = TranslationTable(self) + extended_grammar = translation_table.build_extended_grammar() + modes = translation_table.build_modes() + followsets = extended_grammar.build_followsets() + start_time = time.perf_counter() + + # Build the action/goto table. This is what the parse function actually + # uses. In the action part of the table (where the input is a + # terminal), there are two possible actions: shift, and reduce. These + # are represented by an (action, index) tuple. In response to a reduce, + # the parser will execute a goto by providing a nonterminal as input. + # These are represented as integers. + agtable = {} + + # copy the nonterminal entries in the translation table over as gotos + # and the terminal entries as shifts. + for (f, s), t in translation_table.items(): + if s.is_terminal: + agtable[(f, s.value)] = ('shift', None, t) + else: + agtable[(f, s.value)] = t # goto + + # construct the final sets by merging extended rules which are based on + # the same rule and have the same end point. + finalset_rules = [None] * len(translation_table.itemsets) + finalset_followsets = [set() for _ in translation_table.itemsets] + for rule in extended_grammar.rules: + if len(rule.rhs) == 0: + # if the rule has no rhs, then the starting point is the same + # as the ending point. + final = rule.lhs.start + else: + finals = {s.end for s in rule.rhs[-1]} + assert len(finals) == 1 + final = finals.pop() + if finalset_rules[final] is not None: + assert finalset_rules[final] == rule.parent, ( + f'reduce/reduce:\n' + + f' {finalset_rules[final]}\n' + + f' {rule.parent}') + finalset_rules[final] = rule.parent + finalset_followsets[final].update(followsets[rule.lhs]) + + # add the merged reductions to the table + for k, followset in enumerate(finalset_followsets): + for symbol in followset: + if (k, symbol.value) in agtable: + # This is a shift/reduce conflict. We decide how to resolve + # this based on the precedence of the rules involved. + + # Note that the shift index is a state number, not a rule + # number. State numbers correspond to item sets. In + # particular, we're looking for the rule that has already + # been partially applied. + _, _, shift_index = agtable[(k, symbol.value)] + partials = [ + i for i + in translation_table.itemsets[shift_index].items + if i.pointer > 0] + assert len(partials) == 1, 'shift/reduce (GENERATOR BUG)' + shift_rule = partials[0] + + # If one of them is missing a precedence, go ahead and + # hard-fail. + assert shift_rule.prec is not None \ + and finalset_rules[k].prec is not None, \ + f'shift/reduce:\n {shift_rule}\n {finalset_rules[k]}' + + # If the shifting rule is right-associative, then we should + # break ties in favour of the shift. Otherwise, in favour + # of the reduce. Note because we look at the shift rule's + # associativity for this decision, a right-associative rule + # will bind more tightly than a left-associative rule with + # the same precedence. + if (shift_rule.prec > finalset_rules[k].prec + or (shift_rule.rassoc + and shift_rule.prec == finalset_rules[k].prec)): + continue + + # Check to see if this is actually the accept state + if finalset_rules[k].lhs == self.start_symbol \ + and symbol in self.end_symbols: + agtable[(k, symbol.value)] = ('accept', None, None) + else: + agtable[(k, symbol.value)] = ( + 'reduce', + finalset_rules[k].lhs.value, + len(finalset_rules[k].rhs)) + + # build the hidden-channel parsers + hidden_parsers = { + channel: aux_grammar.build_parser(channel=channel) + for channel, aux_grammar in (hidden or {}).items() + } + + parser = Parser(agtable, modes, hidden_parsers, channel) + end_time = time.perf_counter() + elapsed_ms = (end_time - start_time) * 1000 + elapsed_t_ms = (end_time - start_time_t) * 1000 + print(f'Built action/goto table ({len(agtable)} entries)', + f'in {elapsed_ms:.2f}ms') + print(f'Built parser in {elapsed_t_ms:.2f}ms total') + print(f'Symbols: {len(self.symbols)},', + f'States: {len(translation_table.itemsets)}') + return parser + + +class TranslationTable: + """A table of itemset/state transitions.""" + + def __init__(self, grammar): + self.end_symbols = grammar.end_symbols + self.translation_table = {} + self.itemsets = [] + self.itemset_index = {} + + start_time = time.perf_counter() + + # The first item set is based around the start rule + start = grammar.find_starting_rule_index() + startitem = grammar.rules[start].with_pointer(0) + self.itemsets.append(ItemSet(grammar, {startitem})) + self.itemset_index[frozenset({startitem})] = 0 + + # next, we work our way down the itemsets, advancing them using the + # allowed productions. The resulting items are used to construct new + # itemsets. We also build the translation table as we go + current = 0 + while current < len(self.itemsets): + for symbol in self.itemsets[current].next_symbols: + key = self.itemsets[current].advance(symbol) + if key in self.itemset_index: + itemset = self.itemset_index[key] + else: + itemset = len(self.itemsets) + self.itemset_index[key] = itemset + self.itemsets.append(ItemSet(grammar, key)) + self.translation_table[(current, symbol)] = itemset + current += 1 + + end_time = time.perf_counter() + elapsed_ms = (end_time - start_time) * 1000 + print(f'Built {current} itemsets in {elapsed_ms:.2f}ms') + + def items(self): + return self.translation_table.items() + + def build_extended_grammar(self): + """Builds the extended rule set. + + This produces a set of rules where each symbol sym has been replaced + with the triple (s0, sym, s1) where s0 is the state/itemset preceding + that symbol, and s1 is the state/itemset following it. If the rule can + be applied from multiple states (i.e. it shows up in multiple + itemsets), it will show up multiple times with different state numbers. + """ + start_time = time.perf_counter() + extended_rules = set() + + for current, itemset in enumerate(self.itemsets): + rules_to_process = list(itemset.items) + while len(rules_to_process) > 0: + rule = rules_to_process.pop() + if rule.pointer != 0: + continue + prev = None + state = current + rhs = [] + abort = False + parent = rule.parent + if parent is None: + parent = rule + for k, symbols in enumerate(rule.rhs): + prev = state + states = {self.translation_table[(state, s)] + for s in symbols} + if len(states) == 1: + state = states.pop() + rhs.append(tuple( + s.extend(prev, state) for s in symbols)) + continue + + # our alternation goes to different places, so split + # the rule, and try again. + for s in symbols: + rhs = list(rule.rhs) + rhs[k] = s + rules_to_process.append( + attr.evolve(rule, rhs=rhs, parent=rule)) + abort = True + break + if abort: + continue + try: + lhs = rule.lhs.extend( + current, self.translation_table[(current, rule.lhs)]) + except KeyError: + lhs = rule.lhs.extend(current, Grammar.END) + start_symbol = lhs + extended_rules.add( + attr.evolve(rule, lhs=lhs, rhs=rhs, pointer=None, + parent=parent.with_pointer(None))) + + extended_grammar = Grammar( + start_symbol, + [s.extend(None, None) for s in self.end_symbols], + extended_rules) + end_time = time.perf_counter() + elapsed_ms = (end_time - start_time) * 1000 + sz = len(extended_rules) + print(f'Built extended grammar ({sz} rules) in {elapsed_ms:.2f}ms') + return extended_grammar + + def build_modes(self): + """Builds the lexer mode table. + + Depending on what rule we are currently following, we ask the lexer to + operate in different modes. Each itemset/state is associated with one + mode, that of the rule(s) which are currently in-progress. + """ + + return [s.mode for s in self.itemsets] + + +class Parser: + NORMAL_MODE = 0 + INHERIT_MODE = -1 + + def __init__(self, agtable, modes, hidden, channel): + self.agtable = agtable + self.modes = modes + self.hidden = hidden + self.channel = channel + + def select_mode(self, set_stack): + return next((self.modes[s] + for s in reversed(set_stack) + if self.modes[s] != self.INHERIT_MODE), + self.NORMAL_MODE) + + def next_token_skip_hidden(self, stream, next_token, set_stack): + while True: + lookahead = next_token(stream, self.select_mode(set_stack)) + if lookahead.channel == self.channel \ + or lookahead.channel == ReStream.CHANNEL_ALL: + return lookahead + + # When a token comes in on a channel other than the one we're + # handling, we delegate to another parser for that channel, which + # consumes the input. This is useful for things like comments, + # which can show up anywhere -- handling them in the main grammar + # would be impossible. + stream.rewind(lookahead) + p = self.hidden[lookahead.channel] + p(stream, next_token, lambda t, s, c, m: None) + + def __call__(self, stream, next_token, make_node): + """Parses a given input. + + This method may be called multiple times and does not modify the + object. + + 'next_token' must be a callable which takes two arguments: the + 'stream', and an int for the mode, which is 0 initially. It must return + a Token. + + 'make_node' must be a callable, which is called every time a reduction + is performed. It is passed three arguments: the nonterminal being + reduced, a span covering the tokens involved in the reduction, and an + iterable of the children of the reduction, which are a mix of Tokens + and values returned from make_node. + """ + + # start_time = time.perf_counter() + output = [] + set_stack = [0] + lookahead = self.next_token_skip_hidden(stream, next_token, set_stack) + + while True: + try: + action, sym, arg = self.agtable[(set_stack[-1], lookahead.t)] + except KeyError: + msg = [f"Got {lookahead.t} but expected one of:"] + for state, token in self.agtable: + if state == set_stack[-1]: + msg.append(f" {token}") + raise ParseError("\n".join(msg)) + + if action == 'shift': + output.append((lookahead, lookahead.span)) + set_stack.append(arg) + lookahead = self.next_token_skip_hidden( + stream, next_token, set_stack) + elif action == 'reduce': + if arg > 0: + children, spans = zip(*output[-arg:]) + span = TextSpan.cover(spans) + del output[-arg:] + del set_stack[-arg:] + else: + children = [] + # Since we are reducing an empty rule, we know by [vigorous + # handwaving] that the lack-of-tokens we're trying to + # reduce is bounded on the left by the last item in the + # output stack (if present) and on the right by the + # lookahead token. Note that this approach may result in + # the span corresponding to a block of whitespace or a + # comment. + end = lookahead.span.start + if len(output) > 0: + start = output[-1][1].end + else: + start = end + span = TextSpan(*start, *end) + set_stack.append(self.agtable[(set_stack[-1], sym)]) + output.append((make_node(sym, span, children, + self.modes[set_stack[-1]]), + span)) + else: + assert action == 'accept' + break + + assert len(output) == 1 + + # end_time = time.perf_counter() + # elapsed_ms = (end_time - start_time) * 1000 + # TODO: log to debug log + # print(f'Parsed input in {elapsed_ms:.2f}ms') + return output[0][0] diff --git a/requirements.txt b/requirements.txt index ef117da..6de1f98 100644 --- a/requirements.txt +++ b/requirements.txt @@ -1,6 +1,6 @@ nose==1.3.7 flake8==3.5.0 coverage==4.5.1 -antlr4-python3-runtime==4.7.1 coveralls==1.3.0 hypothesis==3.66.30 +attrs==18.1.0 diff --git a/setup.cfg b/setup.cfg index e387ab5..942c369 100644 --- a/setup.cfg +++ b/setup.cfg @@ -2,8 +2,6 @@ exclude = .git, __pycache__, - jeff65/gold/grammar/Gold.py, - jeff65/gold/grammar/GoldListener.py, [nosetests] with-coverage = 1 @@ -12,15 +10,9 @@ cover-erase = 1 [coverage:run] branch = True -omit = - jeff65/gold/grammar/Gold.py - jeff65/gold/grammar/GoldListener.py [coverage:report] exclude_lines = pragma: no cover def __repr__ raise NotImplementedError -omit = - jeff65/gold/grammar/Gold.py - jeff65/gold/grammar/GoldListener.py diff --git a/setup.py b/setup.py index ba01f66..3268ed0 100644 --- a/setup.py +++ b/setup.py @@ -5,7 +5,7 @@ version='0.1', packages=find_packages(), install_requires=[ - 'antlr4-python3-runtime>=4.5.2', + 'attrs>=18.1.0', ], entry_points={ 'console_scripts': [ diff --git a/tests/test_ast.py b/tests/test_ast.py index 3f1f5a1..53a46cf 100644 --- a/tests/test_ast.py +++ b/tests/test_ast.py @@ -5,7 +5,9 @@ assert_is_none, assert_raises, nottest) +from hypothesis import given, strategies as st from jeff65 import gold +from jeff65 import parsing sys.stderr = sys.stdout @@ -51,11 +53,11 @@ def test_comments_multiline(): def test_comments_unclosed(): - assert_raises(gold.ParseError, parse, "/* oh no") + assert_raises(parsing.ParseError, parse, "/* oh no") def test_comments_unopened(): - assert_raises(gold.ParseError, parse, "oh no */") + assert_raises(parsing.ParseError, parse, "oh no */") def test_nested_comment(): @@ -65,7 +67,7 @@ def test_nested_comment(): def test_nested_comments_unclosed(): - assert_raises(gold.ParseError, parse, "/* /* oh no") + assert_raises(parsing.ParseError, parse, "/* /* oh no") def test_comment_before_statement(): @@ -123,11 +125,30 @@ def test_parentheses_with_sign(): def test_unmatched_open_parentheses(): - assert_raises(gold.ParseError, parse, "constant x: u8 = (1 + 2") + assert_raises(parsing.ParseError, parse, "constant x: u8 = (1 + 2") def test_unmatched_close_parentheses(): - assert_raises(gold.ParseError, parse, "constant x: u8 = 1 + 2)") + assert_raises(parsing.ParseError, parse, "constant x: u8 = 1 + 2)") + + +def test_member_access(): + a = parse("let a: u8 = foo.bar") + print(a.pretty()) + assert_equal( + gold.ast.AstNode('let', None, attrs={ + 'name': 'a', + 'type': 'u8', + }, children=[ + gold.ast.AstNode('member_access', None, attrs={ + 'member': 'bar', + }, children=[ + gold.ast.AstNode('identifier', None, attrs={ + 'name': 'foo', + }), + ]), + ]), + a.children[0]) def test_let_with_mut_storage_class(): @@ -174,8 +195,96 @@ def test_let_without_storage_class(): assert_equal(7, n.attrs['value']) +def test_complex_type(): + a = parse("let a: &u8 = 0") + print(a.pretty()) + assert_equal( + gold.ast.AstNode('let', None, attrs={ + 'name': 'a', + 'type': gold.ast.AstNode('type_ref', None, attrs={ + 'type': 'u8', + }), + }, children=[ + gold.ast.AstNode('numeric', None, attrs={ + 'value': 0, + }), + ]), + a.children[0]) + + +@given(st.characters(('Lu', 'Ll', 'Lt', 'Lm', 'Lo')), + st.text(st.characters(blacklist_characters='()[]{}:;.,"\@&', + blacklist_categories=('Zs', 'Zl', 'Zp', 'Cc')))) +def test_identifiers(name0, name): + name = name0 + name + a = parse(f"let a: u8 = {name}") + print(a.pretty()) + assert_equal(gold.ast.AstNode('let', None, attrs={ + 'name': 'a', + 'type': 'u8', + }, children=[ + gold.ast.AstNode('identifier', None, attrs={ + 'name': name, + }) + ]), a.children[0]) + + +@given(st.integers()) +def test_numeric_hex_valid(n): + a = parse(f"let a: u8 = 0x{n:x}") + print(a.pretty()) + assert_equal(gold.ast.AstNode('let', None, attrs={ + 'name': 'a', + 'type': 'u8', + }, children=[ + gold.ast.AstNode('numeric', None, attrs={ + 'value': n, + }) + ]), a.children[0]) + + +def test_numeric_hex_invalid(): + assert_raises(parsing.ParseError, parse, "let a: u8 = 0xcage") + + +@given(st.integers()) +def test_numeric_oct_valid(n): + a = parse(f"let a: u8 = 0o{n:o}") + print(a.pretty()) + assert_equal(gold.ast.AstNode('let', None, attrs={ + 'name': 'a', + 'type': 'u8', + }, children=[ + gold.ast.AstNode('numeric', None, attrs={ + 'value': n, + }) + ]), a.children[0]) + + +def test_numeric_oct_invalid(): + assert_raises(parsing.ParseError, parse, "let a: u8 = 0o18") + + +@given(st.integers()) +def test_numeric_bin_valid(n): + a = parse(f"let a: u8 = 0b{n:b}") + print(a.pretty()) + assert_equal(gold.ast.AstNode('let', None, attrs={ + 'name': 'a', + 'type': 'u8', + }, children=[ + gold.ast.AstNode('numeric', None, attrs={ + 'value': n, + }) + ]), a.children[0]) + + +def test_numeric_bin_invalid(): + assert_raises(parsing.ParseError, parse, "let a: u8 = 0b012") + + def test_let_with_invalid_storage_class(): - assert_raises(gold.ParseError, parse, "let bogus a: u8 = 7") + assert_raises(parsing.ParseError, parse, "let bogus a: u8 = 7") def test_let_multistatement(): @@ -276,11 +385,11 @@ def test_array_multidimensional(): def test_array_unmatched_open_bracket(): - assert_raises(gold.ParseError, parse, "let x: [u8; 3] = [0, 1, 2") + assert_raises(parsing.ParseError, parse, "let x: [u8; 3] = [0, 1, 2") def test_array_unmatched_close_bracket(): - assert_raises(gold.ParseError, parse, "let x: [u8; 3] = 0, 1, 2]") + assert_raises(parsing.ParseError, parse, "let x: [u8; 3] = 0, 1, 2]") def test_string_literal(): @@ -292,6 +401,15 @@ def test_string_literal(): assert_equal("this is a string", s.attrs['value']) +def test_string_literal_with_space_after(): + a = parse('let a: [u8; 5] = "this is a string" ') + assert_equal(1, len(a.children)) + print(a.pretty()) + s = a.children[0].children[0] + assert_equal('string', s.t) + assert_equal("this is a string", s.attrs['value']) + + def test_string_multiline(): a = parse(''' let a: [u8; 5] = "this is a @@ -315,39 +433,66 @@ def test_string_escaped(): pass -@nottest def test_fun_call_empty(): - # a = parse("foo()") - # assert_equal(1, len(a.statements)) - # c = a.statements[0] - # assert_is_instance(c, ast.FunctionCallNode) - # assert_equal("foo", c.fun.text) - # assert_is_none(c.args) - pass + a = parse("let a: u8 = foo()") + print(a.pretty()) + assert_equal( + gold.ast.AstNode('let', None, attrs={ + 'name': 'a', + 'type': 'u8', + }, children=[ + gold.ast.AstNode('call', None, attrs={ + 'target': gold.ast.AstNode('identifier', None, attrs={ + 'name': 'foo', + }), + }, children=[]), + ]), + a.children[0]) -@nottest def test_fun_call_one(): - # a = parse("foo(1)") - # assert_equal(1, len(a.statements)) - # c = a.statements[0] - # assert_is_instance(c, ast.FunctionCallNode) - # assert_equal("foo", c.fun.text) - # assert_equal("1", c.args.text) - pass + a = parse("let a: u8 = foo(7)") + print(a.pretty()) + assert_equal( + gold.ast.AstNode('let', None, attrs={ + 'name': 'a', + 'type': 'u8', + }, children=[ + gold.ast.AstNode('call', None, attrs={ + 'target': gold.ast.AstNode('identifier', None, attrs={ + 'name': 'foo', + }), + }, children=[ + gold.ast.AstNode('numeric', None, attrs={ + 'value': 7, + }), + ]), + ]), + a.children[0]) -@nottest def test_fun_call_many(): - # a = parse("foo(1, 2, 3)") - # assert_equal(1, len(a.statements)) - # c = a.statements[0] - # assert_is_instance(c, ast.FunctionCallNode) - # assert_equal("foo", c.fun.text) - # assert_equal("1", c.args.lhs.text) - # assert_equal("2", c.args.rhs.lhs.text) - # assert_equal("3", c.args.rhs.rhs.text) - pass + a = parse('let a: u8 = foo(7, "hello")') + print(a.pretty()) + assert_equal( + gold.ast.AstNode('let', None, attrs={ + 'name': 'a', + 'type': 'u8', + }, children=[ + gold.ast.AstNode('call', None, attrs={ + 'target': gold.ast.AstNode('identifier', None, attrs={ + 'name': 'foo', + }), + }, children=[ + gold.ast.AstNode('numeric', None, attrs={ + 'value': 7, + }), + gold.ast.AstNode('string', None, attrs={ + 'value': "hello", + }), + ]), + ]), + a.children[0]) @nottest @@ -472,7 +617,19 @@ def test_isr_def(): def test_use(): a = parse("use mem") + print(a.pretty()) assert_equal(1, len(a.children)) u = a.children[0] assert_equal('use', u.t) assert_equal("mem", u.attrs['name']) + + +def test_assign(): + a = parse("fun foo() a = 7 endfun") + print(a.pretty()) + assert_equal( + gold.ast.AstNode('set', None, children=[ + gold.ast.AstNode('identifier', None, attrs={'name': 'a'}), + gold.ast.AstNode('numeric', None, attrs={'value': 7}), + ]), + a.children[0].children[0])