summaryrefslogtreecommitdiff
path: root/src/mem/slicc/parser
diff options
context:
space:
mode:
Diffstat (limited to 'src/mem/slicc/parser')
-rw-r--r--src/mem/slicc/parser/lexer.ll118
-rw-r--r--src/mem/slicc/parser/parser.py572
-rw-r--r--src/mem/slicc/parser/parser.yy352
3 files changed, 1042 insertions, 0 deletions
diff --git a/src/mem/slicc/parser/lexer.ll b/src/mem/slicc/parser/lexer.ll
new file mode 100644
index 000000000..a4af2ac51
--- /dev/null
+++ b/src/mem/slicc/parser/lexer.ll
@@ -0,0 +1,118 @@
+/*
+ * Copyright (c) 1999-2008 Mark D. Hill and David A. Wood
+ * All rights reserved.
+ *
+ * Redistribution and use in source and binary forms, with or without
+ * modification, are permitted provided that the following conditions are
+ * met: redistributions of source code must retain the above copyright
+ * notice, this list of conditions and the following disclaimer;
+ * redistributions in binary form must reproduce the above copyright
+ * notice, this list of conditions and the following disclaimer in the
+ * documentation and/or other materials provided with the distribution;
+ * neither the name of the copyright holders nor the names of its
+ * contributors may be used to endorse or promote products derived from
+ * this software without specific prior written permission.
+ *
+ * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+ * "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+ * LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
+ * A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
+ * OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
+ * SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
+ * LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
+ * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
+ * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
+ * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
+ * OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
+ */
+
+%{
+
+#include <assert.h>
+#include "mem/slicc/ast/ASTs.hh"
+#include "mem/slicc/parser/parser.hh"
+#include <string>
+
+extern "C" int yylex();
+extern "C" void yyerror();
+extern "C" int yywrap()
+{
+ return 1;
+}
+
+%}
+%x CMNT
+%x IMBEDED
+%%
+
+[\t ]+ /* Ignore whitespace */
+[\n] { g_line_number++; }
+"//".*[\n] { g_line_number++; } /* C++ style comments */
+
+"/*" BEGIN CMNT;
+<CMNT>. ;
+<CMNT>\n { g_line_number++; }
+<CMNT>"*/" { BEGIN INITIAL; }
+
+true { yylval.str_ptr = new string(yytext); return LIT_BOOL; }
+false { yylval.str_ptr = new string(yytext); return LIT_BOOL; }
+global { return GLOBAL_DECL; }
+machine { return MACHINE_DECL; }
+in_port { return IN_PORT_DECL; }
+out_port { return OUT_PORT_DECL; }
+action { return ACTION_DECL; }
+transition { return TRANSITION_DECL; }
+structure { return STRUCT_DECL; }
+external_type { return EXTERN_TYPE_DECL; }
+enumeration { return ENUM_DECL; }
+peek { return PEEK; }
+enqueue { return ENQUEUE; }
+copy_head { return COPY_HEAD; }
+check_allocate { return CHECK_ALLOCATE; }
+check_stop_slots { return CHECK_STOP_SLOTS; }
+if { return IF; }
+else { return ELSE; }
+return { return RETURN; }
+THIS { return THIS; }
+CHIP { return CHIP; }
+void { yylval.str_ptr = new string(yytext); return VOID; }
+
+== { yylval.str_ptr = new string(yytext); return EQ; }
+!= { yylval.str_ptr = new string(yytext); return NE; }
+[<] { yylval.str_ptr = new string(yytext); return '<'; }
+[>] { yylval.str_ptr = new string(yytext); return '>'; }
+[<][<] { yylval.str_ptr = new string(yytext); return LEFTSHIFT; }
+[>][>] { yylval.str_ptr = new string(yytext); return RIGHTSHIFT; }
+[<][=] { yylval.str_ptr = new string(yytext); return LE; }
+[>][=] { yylval.str_ptr = new string(yytext); return GE; }
+[!] { yylval.str_ptr = new string(yytext); return NOT; }
+[&][&] { yylval.str_ptr = new string(yytext); return AND; }
+[|][|] { yylval.str_ptr = new string(yytext); return OR; }
+[+] { yylval.str_ptr = new string(yytext); return PLUS; }
+[-] { yylval.str_ptr = new string(yytext); return DASH; }
+[*] { yylval.str_ptr = new string(yytext); return STAR; }
+[/] { yylval.str_ptr = new string(yytext); return SLASH; }
+:: { return DOUBLE_COLON; }
+[:] { return ':'; }
+[;] { return SEMICOLON; }
+[[] { return '['; }
+[]] { return ']'; }
+[{] { return '{'; }
+[}] { return '}'; }
+[(] { return '('; }
+[)] { return ')'; }
+[,] { return ','; }
+[=] { return '='; }
+:= { return ASSIGN; }
+[.] { return DOT; }
+
+[0-9]*[.][0-9]* { yylval.str_ptr = new string(yytext); return FLOATNUMBER; }
+[0-9]* { yylval.str_ptr = new string(yytext); return NUMBER; }
+[a-zA-Z_][a-zA-Z_0-9]{0,50} { yylval.str_ptr = new string(yytext); return IDENT; }
+\"[^"\n]*\" { yytext[strlen(yytext)-1] = '\0'; yylval.str_ptr = new string(yytext+1); return STRING; }
+\'[^'\n]*\' { yytext[strlen(yytext)-1] = '\0'; yylval.str_ptr = new string(yytext+1); return STRING; }
+
+. { return OTHER; } /* Need so that we handle all characters */
+
+%%
+
diff --git a/src/mem/slicc/parser/parser.py b/src/mem/slicc/parser/parser.py
new file mode 100644
index 000000000..ac2dd294a
--- /dev/null
+++ b/src/mem/slicc/parser/parser.py
@@ -0,0 +1,572 @@
+# Copyright (c) 2009 The Hewlett-Packard Development Company
+# All rights reserved.
+#
+# Redistribution and use in source and binary forms, with or without
+# modification, are permitted provided that the following conditions are
+# met: redistributions of source code must retain the above copyright
+# notice, this list of conditions and the following disclaimer;
+# redistributions in binary form must reproduce the above copyright
+# notice, this list of conditions and the following disclaimer in the
+# documentation and/or other materials provided with the distribution;
+# neither the name of the copyright holders nor the names of its
+# contributors may be used to endorse or promote products derived from
+# this software without specific prior written permission.
+#
+# THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+# "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+# LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
+# A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
+# OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
+# SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
+# LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
+# DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
+# THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
+# (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
+# OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
+#
+# Authors: Nathan Binkert
+
+from ply import lex, yacc
+import re
+
+t_ignore = '\t '
+
+# C or C++ comment (ignore)
+def t_c_comment(t):
+ r'/\*(.|\n)*?\*/'
+ t.lexer.lineno += t.value.count('\n')
+
+def t_cpp_comment(t):
+ r'//.*'
+ pass
+
+# Define a rule so we can track line numbers
+def t_newline(t):
+ r'\n+'
+ t.lexer.lineno += len(t.value)
+
+reserved = {
+ 'global' : 'GLOBAL',
+ 'machine' : 'MACHINE',
+ 'in_port' : 'IN_PORT',
+ 'out_port' : 'OUT_PORT',
+ 'action' : 'ACTION',
+ 'transition' : 'TRANS',
+ 'structure' : 'STRUCT',
+ 'external_type' : 'EXTERN_TYPE',
+ 'enumeration' : 'ENUM',
+ 'peek' : 'PEEK',
+ 'enqueue' : 'ENQUEUE',
+ 'copy_head' : 'COPY_HEAD',
+ 'check_allocate' : 'CHECK_ALLOCATE',
+ 'check_stop_slots' : 'CHECK_STOP_SLOTS',
+ 'if' : 'IF',
+ 'else' : 'ELSE',
+ 'return' : 'RETURN',
+ 'THIS' : 'THIS',
+ 'CHIP' : 'CHIP',
+ 'void' : 'VOID',
+}
+
+literals = ':[]{}(),='
+
+tokens = [ 'EQ', 'NE', 'LT', 'GT', 'LE', 'GE',
+ 'LEFTSHIFT', 'RIGHTSHIFT',
+ 'NOT', 'AND', 'OR',
+ 'PLUS', 'DASH', 'STAR', 'SLASH',
+ 'DOUBLE_COLON', 'SEMICOLON',
+ 'ASSIGN', 'DOT',
+ 'IDENT', 'LIT_BOOL', 'FLOATNUMBER', 'NUMBER', 'STRING' ]
+tokens += reserved.values()
+
+t_EQ = r'=='
+t_NE = r'!='
+t_LT = r'<'
+t_GT = r'>'
+t_LE = r'<='
+t_GE = r'>='
+t_LEFTSHIFT = r'<<'
+t_RIGHTSHIFT = r'>>'
+t_NOT = r'!'
+t_AND = r'&&'
+t_OR = r'\|\|'
+t_PLUS = r'\+'
+t_DASH = r'-'
+t_STAR = r'\*'
+t_SLASH = r'/'
+t_DOUBLE_COLON = r'::'
+t_SEMICOLON = r';'
+t_ASSIGN = r':='
+t_DOT = r'\.'
+
+class TokenError(Exception): pass
+class ParseError(Exception): pass
+
+def t_error(t):
+ raise TokenError("Illegal character", t)
+
+def t_IDENT(t):
+ r'[a-zA-Z_][a-zA-Z_0-9]*'
+ if t.value == 'true':
+ t.type = 'LIT_BOOL'
+ t.value = True
+ return t
+
+ if t.value == 'false':
+ t.type = 'LIT_BOOL'
+ t.value = False
+ return t
+
+ t.type = reserved.get(t.value, 'IDENT') # Check for reserved words
+ return t
+
+def t_FLOATNUMBER(t):
+ '[0-9]+[.][0-9]+'
+ try:
+ t.value = float(t.value)
+ except ValueError:
+ raise TokenError("Illegal float", t)
+ return t
+
+def t_NUMBER(t):
+ r'[0-9]+'
+ try:
+ t.value = int(t.value)
+ except ValueError:
+ raise TokenError("Illegal number", t)
+ return t
+
+def t_STRING1(t):
+ r'\"[^"\n]*\"'
+ t.type = 'STRING'
+ return t
+
+def t_STRING2(t):
+ r"\'[^'\n]*\'"
+ t.type = 'STRING'
+ return t
+
+
+def p_file(p):
+ "file : decl_l"
+ p[0] = [ x for x in p[1] if x is not None ]
+
+def p_error(t):
+ raise ParseError(t)
+
+def p_empty(p):
+ "empty :"
+ pass
+
+def p_decl_l(p):
+ "decl_l : decls"
+ p[0] = p[1]
+
+def p_decls(p):
+ """decls : decl decls
+ | empty"""
+ if len(p) == 3:
+ p[0] = [ p[1] ] + p[2]
+ elif len(p) == 2:
+ p[0] = []
+
+def p_decl(p):
+ """decl : d_machine
+ | d_action
+ | d_in_port
+ | d_out_port
+ | t_trans
+ | d_extern
+ | d_global
+ | d_struct
+ | d_enum
+ | d_object
+ | d_func_decl
+ | d_func_def"""
+ p[0] = p[1]
+
+def p_d_machine(p):
+ "d_machine : MACHINE '(' ident pair_l ')' '{' decl_l '}'"
+ decls = [ x for x in p[7] if x is not None ]
+ p[0] = Machine(p[3], decls)
+
+def p_d_action(p):
+ "d_action : ACTION '(' ident pair_l ')' statement_l"
+ p[0] = Action(p[3])
+
+def p_d_in_port(p):
+ "d_in_port : IN_PORT '(' ident ',' type ',' var pair_l ')' statement_l"
+ p[0] = InPort(p[3])
+
+def p_d_out_port(p):
+ "d_out_port : OUT_PORT '(' ident ',' type ',' var pair_l ')' SEMICOLON"
+ p[0] = OutPort(p[3])
+
+def p_t_trans(p):
+ """t_trans : TRANS '(' ident_l ',' ident_l ',' ident pair_l ')' ident_l
+ | TRANS '(' ident_l ',' ident_l pair_l ')' ident_l"""
+ p[0] = Transition("transition")
+
+def p_d_extern(p):
+ """d_extern : EXTERN_TYPE '(' type pair_l ')' SEMICOLON
+ | EXTERN_TYPE '(' type pair_l ')' '{' type_methods '}'"""
+ p[0] = Extern(p[3])
+
+def p_d_global(p):
+ "d_global : GLOBAL '(' type pair_l ')' '{' type_members '}'"
+ p[0] = Global(p[3])
+
+def p_d_struct(p):
+ "d_struct : STRUCT '(' type pair_l ')' '{' type_members '}'"
+ p[0] = Struct(p[3])
+
+def p_d_enum(p):
+ "d_enum : ENUM '(' type pair_l ')' '{' type_enums '}'"
+ p[0] = Enum(p[3])
+
+def p_d_object(p):
+ "d_object : type ident pair_l SEMICOLON"
+ p[0] = Object(p[2])
+
+def p_d_func_decl(p):
+ """d_func_decl : void ident '(' param_l ')' pair_l SEMICOLON
+ | type ident '(' param_l ')' pair_l SEMICOLON"""
+ pass
+
+def p_d_func_def(p):
+ """d_func_def : void ident '(' param_l ')' pair_l statement_l
+ | type ident '(' param_l ')' pair_l statement_l"""
+ p[0] = Function(p[2])
+
+# Type fields
+def p_type_members(p):
+ """type_members : type_member type_members
+ | empty"""
+ pass
+
+def p_type_member(p):
+ """type_member : type ident pair_l SEMICOLON
+ | type ident ASSIGN expr SEMICOLON"""
+ pass
+
+# Methods
+def p_type_methods(p):
+ """type_methods : type_method type_methods
+ | empty"""
+ pass
+
+def p_type_method(p):
+ "type_method : type_or_void ident '(' type_l ')' pair_l SEMICOLON"
+ pass
+
+# Enum fields
+def p_type_enums(p):
+ """type_enums : type_enum type_enums
+ | empty"""
+ pass
+
+def p_type_enum(p):
+ "type_enum : ident pair_l SEMICOLON"
+ pass
+
+# Type
+def p_type_l(p):
+ """type_l : types
+ | empty"""
+ pass
+
+def p_types(p):
+ """types : type ',' types
+ | type"""
+ pass
+
+def p_type(p):
+ "type : ident"
+ p[0] = p[1]
+
+def p_void(p):
+ "void : VOID"
+ p[0] = None
+
+def p_type_or_void(p):
+ """type_or_void : type
+ | void"""
+ p[0] = p[1]
+
+# Formal Param
+def p_param_l(p):
+ """param_l : params
+ | empty"""
+ pass
+
+def p_params(p):
+ """params : param ',' params
+ | param"""
+ pass
+
+def p_param(p):
+ "param : type ident"
+ pass
+
+# Idents and lists
+def p_ident(p):
+ "ident : IDENT"
+ p[0] = p[1]
+
+def p_ident_l(p):
+ """ident_l : '{' idents '}'
+ | ident"""
+ p[0] = p[1]
+
+def p_idents(p):
+ """idents : ident SEMICOLON idents
+ | ident ',' idents
+ | ident idents
+ | empty"""
+ pass
+
+# Pair and pair lists
+def p_pair_l(p):
+ """pair_l : ',' pairs
+ | empty"""
+ if len(p) == 3:
+ p[0] = p[2]
+ elif len(p) == 2:
+ p[0] = None
+
+def p_pairs(p):
+ """pairs : pair ',' pairs
+ | pair"""
+ if len(p) == 4:
+ p[3].append(p[1])
+ p[0] = p[3]
+ elif len(p) == 2:
+ p[0] = [ p[1] ]
+
+def p_pair(p):
+ """pair : ident '=' STRING
+ | ident '=' ident
+ | STRING"""
+ if len(p) == 4:
+ p[0] = p[1], p[3]
+ elif len(p) == 2:
+ p[0] = "short", p[1]
+
+# Below are the rules for action descriptions
+def p_statement_l(p):
+ "statement_l : '{' statements '}'"
+ pass
+
+def p_statements(p):
+ """statements : statement statements
+ | empty"""
+ pass
+
+def p_expr_l(p):
+ """expr_l : expr ',' expr_l
+ | expr
+ | empty"""
+ pass
+
+def p_statement(p):
+ """statement : expr SEMICOLON
+ | expr ASSIGN expr SEMICOLON
+ | ENQUEUE '(' var ',' type pair_l ')' statement_l
+ | PEEK '(' var ',' type ')' statement_l
+ | COPY_HEAD '(' var ',' var pair_l ')' SEMICOLON
+ | CHECK_ALLOCATE '(' var ')' SEMICOLON
+ | CHECK_STOP_SLOTS '(' var ',' STRING ',' STRING ')' SEMICOLON
+ | if_statement
+ | RETURN expr SEMICOLON"""
+ pass
+
+def p_if_statement(p):
+ """if_statement : IF '(' expr ')' statement_l ELSE statement_l
+ | IF '(' expr ')' statement_l
+ | IF '(' expr ')' statement_l ELSE if_statement"""
+ pass
+
+def p_expr(p):
+ """expr : var
+ | literal
+ | enumeration
+ | ident '(' expr_l ')'
+ | THIS DOT var '[' expr ']' DOT var DOT ident '(' expr_l ')'
+ | THIS DOT var '[' expr ']' DOT var DOT ident
+ | CHIP '[' expr ']' DOT var '[' expr ']' DOT var DOT ident '(' expr_l ')'
+ | CHIP '[' expr ']' DOT var '[' expr ']' DOT var DOT ident
+ | expr DOT ident
+ | expr DOT ident '(' expr_l ')'
+ | type DOUBLE_COLON ident '(' expr_l ')'
+ | expr '[' expr_l ']'
+ | expr STAR expr
+ | expr SLASH expr
+ | expr PLUS expr
+ | expr DASH expr
+ | expr LT expr
+ | expr GT expr
+ | expr LE expr
+ | expr GE expr
+ | expr EQ expr
+ | expr NE expr
+ | expr AND expr
+ | expr OR expr
+ | NOT expr
+ | expr RIGHTSHIFT expr
+ | expr LEFTSHIFT expr
+ | '(' expr ')'"""
+ pass
+
+def p_literal(p):
+ """literal : STRING
+ | NUMBER
+ | FLOATNUMBER
+ | LIT_BOOL"""
+ pass
+
+def p_enumeration(p):
+ "enumeration : ident ':' ident"
+ pass
+
+def p_var(p):
+ "var : ident"
+ pass
+
+lex.lex()
+yacc.yacc(write_tables=0)
+
+slicc_generated_cc = set([
+ 'AccessModeType.cc',
+ 'AccessPermission.cc',
+ 'AccessType.cc',
+ 'AllocationStrategy.cc',
+ 'CacheMsg.cc',
+ 'CacheRequestType.cc',
+ 'Chip.cc',
+ 'CoherenceRequestType.cc',
+ 'DetermGETXGeneratorStatus.cc',
+ 'DetermInvGeneratorStatus.cc',
+ 'DetermSeriesGETSGeneratorStatus.cc',
+ 'GenericMachineType.cc',
+ 'GenericRequestType.cc',
+ 'LinkType.cc',
+ 'LockStatus.cc',
+ 'MachineType.cc',
+ 'MaskPredictorIndex.cc',
+ 'MaskPredictorTraining.cc',
+ 'MaskPredictorType.cc',
+ 'MemoryMsg.cc',
+ 'MemoryRequestType.cc',
+ 'MessageSizeType.cc',
+ 'PrefetchBit.cc',
+ 'Protocol.cc',
+ 'RequestGeneratorStatus.cc',
+ 'SearchMechanism.cc',
+ 'SequencerStatus.cc',
+ 'SpecifiedGeneratorType.cc',
+ 'TesterStatus.cc',
+ 'TopologyType.cc',
+ 'TransientRequestType.cc',
+ 'TransitionResult.cc'])
+
+slicc_generated_hh = set([
+ 'AccessType.hh',
+ 'AccessModeType.hh',
+ 'AccessPermission.hh',
+ 'AllocationStrategy.hh',
+ 'CacheMsg.hh',
+ 'CacheRequestType.hh',
+ 'Chip.hh',
+ 'CoherenceRequestType.hh',
+ 'DetermGETXGeneratorStatus.hh',
+ 'DetermInvGeneratorStatus.hh',
+ 'DetermSeriesGETSGeneratorStatus.hh',
+ 'GenericMachineType.hh',
+ 'GenericRequestType.hh',
+ 'LinkType.hh',
+ 'LockStatus.hh',
+ 'MachineType.hh',
+ 'MaskPredictorIndex.hh',
+ 'MaskPredictorTraining.hh',
+ 'MaskPredictorType.hh',
+ 'MemoryMsg.hh',
+ 'MemoryRequestType.hh',
+ 'MessageSizeType.hh',
+ 'PrefetchBit.hh',
+ 'Protocol.hh',
+ 'RequestGeneratorStatus.hh',
+ 'SearchMechanism.hh',
+ 'SequencerStatus.hh',
+ 'SpecifiedGeneratorType.hh',
+ 'TesterStatus.hh',
+ 'TopologyType.hh',
+ 'TransientRequestType.hh',
+ 'TransitionResult.hh',
+ 'Types.hh',
+ 'protocol_name.hh' ])
+
+class Machine(object):
+ def __init__(self, name, decls):
+ self.name = name
+ self.decls = decls
+
+ def add(self, hh, cc):
+ hh.add('%s_Controller.hh' % self.name)
+ hh.add('%s_Profiler.hh' % self.name)
+
+ cc.add('%s_Controller.cc' % self.name)
+ cc.add('%s_Profiler.cc' % self.name)
+ cc.add('%s_Transitions.cc' % self.name)
+ cc.add('%s_Wakeup.cc' % self.name)
+
+ for decl in self.decls:
+ decl.add(hh, cc, self.name)
+
+class Declaration(object):
+ hh = False
+ cc = False
+ def __init__(self, name):
+ self.name = name
+
+ def add(self, hh, cc, name=None):
+ #print '>>>', type(self).__name__, self.name
+ if name:
+ name += '_'
+ else:
+ name = ""
+ if self.hh:
+ hh.add('%s%s.hh' % (name, self.name))
+ if self.cc:
+ cc.add('%s%s.cc' % (name, self.name))
+
+class Action(Declaration): pass
+class InPort(Declaration): pass
+class OutPort(Declaration): pass
+class Transition(Declaration): pass
+class Extern(Declaration): pass
+class Global(Declaration): pass
+class Struct(Declaration):
+ hh = True
+ cc = True
+class Enum(Declaration):
+ hh = True
+ cc = True
+class Object(Declaration): pass
+class Function(Declaration):
+ cc = True
+
+def scan(filenames):
+ hh = slicc_generated_hh.copy()
+ cc = slicc_generated_cc.copy()
+
+ for filename in filenames:
+ lex.lexer.lineno = 1
+ try:
+ results = yacc.parse(file(filename, 'r').read())
+ except (TokenError, ParseError), e:
+ raise type(e), tuple([filename] + [ i for i in e ])
+
+ for result in results:
+ result.add(hh, cc)
+
+ return list(hh), list(cc)
diff --git a/src/mem/slicc/parser/parser.yy b/src/mem/slicc/parser/parser.yy
new file mode 100644
index 000000000..8090b88f7
--- /dev/null
+++ b/src/mem/slicc/parser/parser.yy
@@ -0,0 +1,352 @@
+/*
+ * Copyright (c) 1999-2008 Mark D. Hill and David A. Wood
+ * All rights reserved.
+ *
+ * Redistribution and use in source and binary forms, with or without
+ * modification, are permitted provided that the following conditions are
+ * met: redistributions of source code must retain the above copyright
+ * notice, this list of conditions and the following disclaimer;
+ * redistributions in binary form must reproduce the above copyright
+ * notice, this list of conditions and the following disclaimer in the
+ * documentation and/or other materials provided with the distribution;
+ * neither the name of the copyright holders nor the names of its
+ * contributors may be used to endorse or promote products derived from
+ * this software without specific prior written permission.
+ *
+ * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+ * "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+ * LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
+ * A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
+ * OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
+ * SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
+ * LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
+ * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
+ * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
+ * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
+ * OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
+ */
+
+%{
+#include <string>
+#include <stdio.h>
+#include <assert.h>
+#include "mem/slicc/ast/ASTs.hh"
+
+#define YYMAXDEPTH 100000
+#define YYERROR_VERBOSE
+
+extern char* yytext;
+
+extern "C" void yyerror(char*);
+extern "C" int yylex();
+
+%}
+
+%union {
+ string* str_ptr;
+ Vector<string>* string_vector_ptr;
+
+ // Decls
+ DeclAST* decl_ptr;
+ DeclListAST* decl_list_ptr;
+ Vector<DeclAST*>* decl_vector_ptr;
+
+ // TypeField
+ TypeFieldAST* type_field_ptr;
+ Vector<TypeFieldAST*>* type_field_vector_ptr;
+
+ // Type
+ TypeAST* type_ptr;
+ Vector<TypeAST*>* type_vector_ptr;
+
+ // Formal Params
+ FormalParamAST* formal_param_ptr;
+ Vector<FormalParamAST*>* formal_param_vector_ptr;
+
+ // Statements
+ StatementAST* statement_ptr;
+ StatementListAST* statement_list_ptr;
+ Vector<StatementAST*>* statement_vector_ptr;
+
+ // Pairs
+ PairAST* pair_ptr;
+ PairListAST* pair_list_ptr;
+
+ // Expressions
+ VarExprAST* var_expr_ptr;
+ ExprAST* expr_ptr;
+ Vector<ExprAST*>* expr_vector_ptr;
+}
+
+%type <type_ptr> type void type_or_void
+%type <type_vector_ptr> types type_list
+
+ // Formal Params
+%type <formal_param_ptr> formal_param
+%type <formal_param_vector_ptr> formal_params formal_param_list
+
+%type <str_ptr> ident field
+%type <string_vector_ptr> ident_list idents
+
+%type <statement_ptr> statement if_statement
+%type <statement_list_ptr> statement_list
+%type <statement_vector_ptr> statements
+
+%type <decl_ptr> decl
+%type <decl_list_ptr> decl_list
+%type <decl_vector_ptr> decls
+
+%type <type_field_vector_ptr> type_members type_enums type_methods
+%type <type_field_ptr> type_member type_enum type_method
+
+%type <var_expr_ptr> var
+%type <expr_ptr> expr literal enumeration
+%type <expr_vector_ptr> expr_list
+
+%type <pair_ptr> pair
+%type <pair_list_ptr> pair_list pairs
+
+%token <str_ptr> IDENT STRING NUMBER FLOATNUMBER LIT_BOOL VOID
+%token <str_ptr> IMBED IMBED_TYPE
+%token CHIP THIS
+%token ASSIGN DOUBLE_COLON DOT SEMICOLON COLON
+%token GLOBAL_DECL MACHINE_DECL IN_PORT_DECL OUT_PORT_DECL
+%token PEEK ENQUEUE COPY_HEAD CHECK_ALLOCATE CHECK_STOP_SLOTS
+//%token DEQUEUE REMOVE_EARLY SKIP_EARLY PEEK_EARLY
+%token DEBUG_EXPR_TOKEN DEBUG_MSG_TOKEN
+%token ACTION_DECL TRANSITION_DECL TYPE_DECL STRUCT_DECL EXTERN_TYPE_DECL ENUM_DECL
+%token TYPE_FIELD OTHER IF ELSE RETURN
+
+%token <str_ptr> EQ NE '<' '>' LE GE NOT AND OR PLUS DASH STAR SLASH RIGHTSHIFT LEFTSHIFT
+
+%left OR
+%left AND
+%nonassoc EQ NE
+%nonassoc '<' '>' GE LE
+%left PLUS DASH
+%left STAR SLASH
+%nonassoc NOT
+%nonassoc DOUBLE_COLON DOT '['
+
+%%
+
+file: decl_list { g_decl_list_ptr = $1; }
+
+decl_list: decls { $$ = new DeclListAST($1); }
+
+decls: decl decls { $2->insertAtTop($1); $$ = $2; }
+ | { $$ = new Vector<DeclAST*>; }
+ ;
+
+decl: MACHINE_DECL '(' ident pair_list ')' '{' decl_list '}' { $$ = new MachineAST($3, $4, $7); }
+ | ACTION_DECL '(' ident pair_list ')' statement_list { $$ = new ActionDeclAST($3, $4, $6); }
+ | IN_PORT_DECL '(' ident ',' type ',' var pair_list ')' statement_list { $$ = new InPortDeclAST($3, $5, $7, $8, $10); }
+ | OUT_PORT_DECL '(' ident ',' type ',' var pair_list ')' SEMICOLON { $$ = new OutPortDeclAST($3, $5, $7, $8); }
+ | TRANSITION_DECL '(' ident_list ',' ident_list ',' ident pair_list ')' ident_list { $$ = new TransitionDeclAST($3, $5, $7, $8, $10); }
+ | TRANSITION_DECL '(' ident_list ',' ident_list pair_list ')' ident_list { $$ = new TransitionDeclAST($3, $5, NULL, $6, $8); }
+ | EXTERN_TYPE_DECL '(' type pair_list ')' SEMICOLON { $4->addPair(new PairAST("external", "yes")); $$ = new TypeDeclAST($3, $4, NULL); }
+ | EXTERN_TYPE_DECL '(' type pair_list ')' '{' type_methods '}' { $4->addPair(new PairAST("external", "yes")); $$ = new TypeDeclAST($3, $4, $7); }
+ | GLOBAL_DECL '(' type pair_list ')' '{' type_members '}' { $4->addPair(new PairAST("global", "yes"));$$ = new TypeDeclAST($3, $4, $7); }
+ | STRUCT_DECL '(' type pair_list ')' '{' type_members '}' { $$ = new TypeDeclAST($3, $4, $7); }
+ | ENUM_DECL '(' type pair_list ')' '{' type_enums '}' { $4->addPair(new PairAST("enumeration", "yes")); $$ = new EnumDeclAST($3, $4, $7); }
+ | type ident pair_list SEMICOLON { $$ = new ObjDeclAST($1, $2, $3); }
+ | type ident '(' formal_param_list ')' pair_list SEMICOLON { $$ = new FuncDeclAST($1, $2, $4, $6, NULL); } // non-void function
+ | void ident '(' formal_param_list ')' pair_list SEMICOLON { $$ = new FuncDeclAST($1, $2, $4, $6, NULL); } // void function
+ | type ident '(' formal_param_list ')' pair_list statement_list { $$ = new FuncDeclAST($1, $2, $4, $6, $7); } // non-void function
+ | void ident '(' formal_param_list ')' pair_list statement_list { $$ = new FuncDeclAST($1, $2, $4, $6, $7); } // void function
+ ;
+
+// Type fields
+
+type_members: type_member type_members { $2->insertAtTop($1); $$ = $2; }
+ | { $$ = new Vector<TypeFieldAST*>; }
+ ;
+
+type_member: type ident pair_list SEMICOLON { $$ = new TypeFieldMemberAST($1, $2, $3, NULL); }
+ | type ident ASSIGN expr SEMICOLON { $$ = new TypeFieldMemberAST($1, $2, new PairListAST(), $4); }
+ ;
+
+// Methods
+type_methods: type_method type_methods { $2->insertAtTop($1); $$ = $2; }
+ | { $$ = new Vector<TypeFieldAST*>; }
+ ;
+
+type_method: type_or_void ident '(' type_list ')' pair_list SEMICOLON { $$ = new TypeFieldMethodAST($1, $2, $4, $6); }
+ ;
+
+// Enum fields
+type_enums: type_enum type_enums { $2->insertAtTop($1); $$ = $2; }
+ | { $$ = new Vector<TypeFieldAST*>; }
+ ;
+
+type_enum: ident pair_list SEMICOLON { $$ = new TypeFieldEnumAST($1, $2); }
+ ;
+
+// Type
+type_list : types { $$ = $1; }
+ | { $$ = new Vector<TypeAST*>; }
+ ;
+
+types : type ',' types { $3->insertAtTop($1); $$ = $3; }
+ | type { $$ = new Vector<TypeAST*>; $$->insertAtTop($1); }
+ ;
+
+type: ident { $$ = new TypeAST($1); }
+ ;
+
+void: VOID { $$ = new TypeAST($1); }
+ ;
+
+type_or_void: type { $$ = $1; }
+ | void { $$ = $1; }
+ ;
+
+// Formal Param
+formal_param_list : formal_params { $$ = $1; }
+ | { $$ = new Vector<FormalParamAST*>; }
+ ;
+
+formal_params : formal_param ',' formal_params { $3->insertAtTop($1); $$ = $3; }
+ | formal_param { $$ = new Vector<FormalParamAST*>; $$->insertAtTop($1); }
+ ;
+
+formal_param : type ident { $$ = new FormalParamAST($1, $2); }
+ ;
+
+// Idents and lists
+ident: IDENT { $$ = $1; } ;
+
+ident_list: '{' idents '}' { $$ = $2; }
+ | ident { $$ = new Vector<string>; $$->insertAtTop(*($1)); delete $1; }
+ ;
+
+idents: ident SEMICOLON idents { $3->insertAtTop(*($1)); $$ = $3; delete $1; }
+ | ident ',' idents { $3->insertAtTop(*($1)); $$ = $3; delete $1; }
+ | ident idents { $2->insertAtTop(*($1)); $$ = $2; delete $1; }
+ | { $$ = new Vector<string>; }
+ ;
+
+// Pair and pair lists
+pair_list: ',' pairs { $$ = $2; }
+ | { $$ = new PairListAST(); }
+
+pairs : pair ',' pairs { $3->addPair($1); $$ = $3; }
+ | pair { $$ = new PairListAST(); $$->addPair($1); }
+ ;
+
+pair : ident '=' STRING { $$ = new PairAST($1, $3); }
+ | ident '=' ident { $$ = new PairAST($1, $3); }
+ | STRING { $$ = new PairAST(new string("short"), $1); }
+ ;
+
+// Below are the rules for action descriptions
+
+statement_list: '{' statements '}' { $$ = new StatementListAST($2); }
+ ;
+
+statements: statement statements { $2->insertAtTop($1); $$ = $2; }
+ | { $$ = new Vector<StatementAST*>; }
+ ;
+
+expr_list: expr ',' expr_list { $3->insertAtTop($1); $$ = $3; }
+ | expr { $$ = new Vector<ExprAST*>; $$->insertAtTop($1); }
+ | { $$ = new Vector<ExprAST*>; }
+ ;
+
+statement: expr SEMICOLON { $$ = new ExprStatementAST($1); }
+ | expr ASSIGN expr SEMICOLON { $$ = new AssignStatementAST($1, $3); }
+ | ENQUEUE '(' var ',' type pair_list ')' statement_list { $$ = new EnqueueStatementAST($3, $5, $6, $8); }
+ | PEEK '(' var ',' type ')' statement_list { $$ = new PeekStatementAST($3, $5, $7, "peek"); }
+// | PEEK_EARLY '(' var ',' type ')' statement_list { $$ = new PeekStatementAST($3, $5, $7, "peekEarly"); }
+ | COPY_HEAD '(' var ',' var pair_list ')' SEMICOLON { $$ = new CopyHeadStatementAST($3, $5, $6); }
+ | CHECK_ALLOCATE '(' var ')' SEMICOLON { $$ = new CheckAllocateStatementAST($3); }
+ | CHECK_STOP_SLOTS '(' var ',' STRING ',' STRING ')' SEMICOLON { $$ = new CheckStopSlotsStatementAST($3, $5, $7); }
+ | if_statement { $$ = $1; }
+ | RETURN expr SEMICOLON { $$ = new ReturnStatementAST($2); }
+ ;
+
+if_statement: IF '(' expr ')' statement_list ELSE statement_list { $$ = new IfStatementAST($3, $5, $7); }
+ | IF '(' expr ')' statement_list { $$ = new IfStatementAST($3, $5, NULL); }
+ | IF '(' expr ')' statement_list ELSE if_statement { $$ = new IfStatementAST($3, $5, new StatementListAST($7)); }
+ ;
+
+expr: var { $$ = $1; }
+ | literal { $$ = $1; }
+ | enumeration { $$ = $1; }
+ | ident '(' expr_list ')' { $$ = new FuncCallExprAST($1, $3); }
+
+
+// globally access a local chip component and call a method
+ | THIS DOT var '[' expr ']' DOT var DOT ident '(' expr_list ')' { $$ = new ChipComponentAccessAST($3, $5, $8, $10, $12 ); }
+// globally access a local chip component and access a data member
+ | THIS DOT var '[' expr ']' DOT var DOT field { $$ = new ChipComponentAccessAST($3, $5, $8, $10 ); }
+// globally access a specified chip component and call a method
+ | CHIP '[' expr ']' DOT var '[' expr ']' DOT var DOT ident '(' expr_list ')' { $$ = new ChipComponentAccessAST($3, $6, $8, $11, $13, $15 ); }
+// globally access a specified chip component and access a data member
+ | CHIP '[' expr ']' DOT var '[' expr ']' DOT var DOT field { $$ = new ChipComponentAccessAST($3, $6, $8, $11, $13 ); }
+
+
+ | expr DOT field { $$ = new MemberExprAST($1, $3); }
+ | expr DOT ident '(' expr_list ')' { $$ = new MethodCallExprAST($1, $3, $5); }
+ | type DOUBLE_COLON ident '(' expr_list ')' { $$ = new MethodCallExprAST($1, $3, $5); }
+ | expr '[' expr_list ']' { $$ = new MethodCallExprAST($1, new string("lookup"), $3); }
+ | expr STAR expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+ | expr SLASH expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+ | expr PLUS expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+ | expr DASH expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+ | expr '<' expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+ | expr '>' expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+ | expr LE expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+ | expr GE expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+ | expr EQ expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+ | expr NE expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+ | expr AND expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+ | expr OR expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+ | expr RIGHTSHIFT expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+ | expr LEFTSHIFT expr { $$ = new InfixOperatorExprAST($1, $2, $3); }
+// | NOT expr { $$ = NULL; } // FIXME - unary not
+// | DASH expr %prec NOT { $$ = NULL; } // FIXME - unary minus
+ | '(' expr ')' { $$ = $2; }
+ ;
+
+literal: STRING { $$ = new LiteralExprAST($1, "string"); }
+ | NUMBER { $$ = new LiteralExprAST($1, "int"); }
+ | FLOATNUMBER { $$ = new LiteralExprAST($1, "int"); }
+ | LIT_BOOL { $$ = new LiteralExprAST($1, "bool"); }
+ ;
+
+enumeration: ident ':' ident { $$ = new EnumExprAST(new TypeAST($1), $3); }
+ ;
+
+var: ident { $$ = new VarExprAST($1); }
+ ;
+
+field: ident { $$ = $1; }
+ ;
+
+%%
+
+extern FILE *yyin;
+
+DeclListAST* parse(string filename)
+{
+ FILE *file;
+ file = fopen(filename.c_str(), "r");
+ if (!file) {
+ cerr << "Error: Could not open file: " << filename << endl;
+ exit(1);
+ }
+ g_line_number = 1;
+ g_file_name = filename;
+ yyin = file;
+ g_decl_list_ptr = NULL;
+ yyparse();
+ return g_decl_list_ptr;
+}
+
+extern "C" void yyerror(char* s)
+{
+ fprintf(stderr, "%s:%d: %s at %s\n", g_file_name.c_str(), g_line_number, s, yytext);
+ exit(1);
+}
+