1d296fae5b6af7042598862b249ef4fa37d35776
[IRC.git] / Robust / src / Parse / java14.cup
1 package Parse;
2
3 import java_cup.runtime.*;
4 import Lex.Lexer;
5 import IR.Tree.*;
6
7 /* Java 1.4 parser for CUP.  
8  * Copyright (C) 2002-2003 C. Scott Ananian <cananian@alumni.princeton.edu>
9  * This program is released under the terms of the GPL; see the file
10  * COPYING for more details.  There is NO WARRANTY on this code.
11  */
12
13 /*
14 JDK 1.4 Features added:
15   assertion statement.
16   statement_without_trailing_substatement ::= ...
17      |          assert_statement ;
18   assert_statement ::=
19                 ASSERT expression SEMICOLON
20         |       ASSERT expression COLON expression SEMICOLON
21         ;
22 */
23 parser code  {: 
24   Lexer lexer;
25
26   public Parser(Lexer l) {
27     this();
28     lexer=l;
29   }
30
31   public void syntax_error(java_cup.runtime.Symbol current) {
32     report_error("Syntax error (" + current.sym + ")", current);
33   }
34   public void report_error(String message, java_cup.runtime.Symbol info) {
35     lexer.errorMsg(message, info);
36   }
37 :};
38
39 scan with {: return lexer.nextToken(); :};
40
41 terminal BOOLEAN; // primitive_type
42 terminal BYTE, SHORT, INT, LONG, CHAR; // integral_type
43 terminal FLOAT, DOUBLE; // floating_point_type
44 terminal LBRACK, RBRACK; // array_type
45 terminal java.lang.String IDENTIFIER; // name
46 terminal DOT; // qualified_name
47 terminal SEMICOLON, MULT, COMMA, LBRACE, RBRACE, EQ, LPAREN, RPAREN, COLON;
48 terminal PACKAGE; // package_declaration
49 terminal IMPORT; // import_declaration
50 terminal PUBLIC, PROTECTED, PRIVATE; // modifier
51 terminal STATIC; // modifier
52 terminal ABSTRACT, FINAL, NATIVE, SYNCHRONIZED, TRANSIENT, VOLATILE;
53 terminal CLASS; // class_declaration
54 terminal EXTENDS; // super
55 //terminal IMPLEMENTS; // interfaces
56 terminal VOID; // method_header
57 terminal THROWS; // throws
58 terminal THIS, SUPER; // explicit_constructor_invocation
59 //terminal INTERFACE; // interface_declaration
60 terminal IF, ELSE; // if_then_statement, if_then_else_statement
61 terminal SWITCH; // switch_statement
62 terminal CASE, DEFAULT; // switch_label
63 terminal DO, WHILE; // while_statement, do_statement
64 terminal FOR; // for_statement
65 terminal BREAK; // break_statement
66 terminal CONTINUE; // continue_statement
67 terminal RETURN; // return_statement
68 terminal THROW; // throw_statement
69 terminal TRY; // try_statement
70 terminal CATCH; // catch_clause
71 terminal FINALLY; // finally
72 terminal NEW; // class_instance_creation_expression
73 terminal PLUSPLUS; // postincrement_expression
74 terminal MINUSMINUS; // postdecrement_expression
75 terminal PLUS, MINUS, COMP, NOT, DIV, MOD;
76 terminal LSHIFT, RSHIFT, URSHIFT; // shift_expression
77 terminal LT, GT, LTEQ, GTEQ, INSTANCEOF; // relational_expression
78 terminal EQEQ, NOTEQ; // equality_expression
79 terminal AND; // and_expression
80 terminal XOR; // exclusive_or_expression
81 terminal OR;  // inclusive_or_expression
82 terminal ANDAND; // conditional_and_expression
83 terminal OROR; // conditional_or_expression
84 terminal QUESTION; // conditional_expression
85 terminal MULTEQ, DIVEQ, MODEQ, PLUSEQ, MINUSEQ; // assignment_operator
86 terminal LSHIFTEQ, RSHIFTEQ, URSHIFTEQ; // assignment_operator
87 terminal ANDEQ, XOREQ, OREQ; // assignment_operator
88
89 terminal java.lang.Number INTEGER_LITERAL;
90 terminal java.lang.Number FLOATING_POINT_LITERAL;
91 terminal java.lang.Boolean BOOLEAN_LITERAL;
92 terminal java.lang.Character CHARACTER_LITERAL;
93 terminal java.lang.String STRING_LITERAL;
94 terminal NULL_LITERAL;
95
96 // Reserved but unused:
97 terminal CONST, GOTO;
98 // strictfp keyword, new in Java 1.2
99 terminal STRICTFP;
100 // assert keyword, new in Java 1.4
101 terminal ASSERT; // assert_statement
102 // lexer compatibility with Java 1.5
103 terminal ELLIPSIS;
104 terminal ENUM;
105
106
107 // 19.2) The Syntactic Grammar
108 non terminal ParseNode goal;
109 // 19.3) Lexical Structure
110 non terminal ParseNode literal;
111 // 19.4) Types, Values, and Variables
112 non terminal ParseNode type, primitive_type, numeric_type;
113 non terminal ParseNode integral_type, floating_point_type;
114 non terminal ParseNode reference_type;
115 non terminal ParseNode class_or_interface_type;
116 non terminal ParseNode class_type;
117 //non terminal ParseNode interface_type;
118 non terminal ParseNode array_type;
119 // 19.5) Names
120 non terminal ParseNode name, simple_name, qualified_name;
121 // 19.6) Packages
122 non terminal ParseNode compilation_unit;
123 //non terminal ParseNode package_declaration_opt, package_declaration;
124 //non terminal ParseNode import_declarations_opt, import_declarations;
125 non terminal ParseNode type_declarations_opt, type_declarations;
126 //non terminal ParseNode import_declaration;
127 //non terminal ParseNode single_type_import_declaration;
128 //non terminal ParseNode type_import_on_demand_declaration;
129 non terminal ParseNode type_declaration;
130 // 19.7) Productions used only in the LALR(1) grammar
131 non terminal ParseNode modifiers_opt, modifiers, modifier;
132 // 19.8.1) Class Declaration
133 non terminal ParseNode class_declaration, super, super_opt;
134 //non terminal interfaces, interfaces_opt, interface_type_list;
135 non terminal ParseNode class_body;
136 non terminal ParseNode class_body_declarations, class_body_declarations_opt;
137 non terminal ParseNode class_body_declaration, class_member_declaration;
138 // 19.8.2) Field Declarations
139 non terminal ParseNode field_declaration, variable_declarators, variable_declarator;
140 non terminal ParseNode variable_declarator_id;
141 non terminal ParseNode variable_initializer;
142 // 19.8.3) Method Declarations
143 non terminal ParseNode method_declaration, method_header, method_declarator;
144 non terminal ParseNode formal_parameter_list_opt, formal_parameter_list;
145 non terminal ParseNode formal_parameter;
146 //non terminal ParseNode throws_opt;
147 //non terminal ParseNode throws;
148 //non terminal ParseNode class_type_list;
149 non terminal ParseNode method_body;
150 // 19.8.4) Static Initializers
151 //non terminal ParseNode static_initializer;
152 // 19.8.5) Constructor Declarations
153 non terminal ParseNode constructor_declaration, constructor_declarator;
154 non terminal ParseNode constructor_body;
155 //non terminal ParseNode explicit_constructor_invocation;
156 // 19.9.1) Interface Declarations
157 //non terminal ParseNode interface_declaration;
158 //non terminal ParseNode extends_interfaces_opt, extends_interfaces;
159 //non terminal ParseNode interface_body;
160 //non terminal ParseNode interface_member_declarations_opt, interface_member_declarations;
161 //non terminal ParseNode interface_member_declaration, constant_declaration;
162 //non terminal ParseNode abstract_method_declaration;
163 // 19.10) Arrays
164 //non terminal ParseNode array_initializer;
165 //non terminal ParseNode variable_initializers;
166 // 19.11) Blocks and Statements
167 non terminal ParseNode block;
168 non terminal ParseNode block_statements_opt, block_statements, block_statement;
169 non terminal ParseNode local_variable_declaration_statement, local_variable_declaration;
170 non terminal ParseNode statement, statement_no_short_if;
171 non terminal ParseNode statement_without_trailing_substatement;
172 non terminal ParseNode empty_statement;
173 //non terminal ParseNode labeled_statement, labeled_statement_no_short_if;
174 non terminal ParseNode expression_statement, statement_expression;
175 non terminal ParseNode if_then_statement;
176 non terminal ParseNode if_then_else_statement, if_then_else_statement_no_short_if;
177 //non terminal ParseNode switch_statement, switch_block;
178 //non terminal ParseNode switch_block_statement_groups;
179 //non terminal ParseNode switch_block_statement_group;
180 //non terminal ParseNode switch_labels, switch_label;
181 non terminal ParseNode while_statement, while_statement_no_short_if;
182 non terminal ParseNode do_statement;
183 non terminal ParseNode for_statement, for_statement_no_short_if;
184 non terminal ParseNode for_init_opt, for_init;
185 non terminal ParseNode for_update_opt, for_update;
186 non terminal ParseNode statement_expression_list;
187 //non terminal ParseNode identifier_opt;
188 non terminal ParseNode break_statement, continue_statement;
189 non terminal ParseNode return_statement;
190 //non terminal ParseNode throw_statement;
191 //non terminal ParseNode synchronized_statement, try_statement;
192 //non terminal ParseNode catches_opt;
193 //non terminal ParseNode catches, catch_clause;
194 //non terminal ParseNode finally;
195 //non terminal ParseNode assert_statement;
196 // 19.12) Expressions
197 non terminal ParseNode primary, primary_no_new_array;
198 non terminal ParseNode class_instance_creation_expression;
199 non terminal ParseNode argument_list_opt, argument_list;
200 //non terminal ParseNode array_creation_init;
201 non terminal ParseNode array_creation_uninit;
202 non terminal ParseNode dim_exprs, dim_expr;
203 non terminal Integer dims_opt, dims;
204 non terminal ParseNode field_access, method_invocation;
205 non terminal ParseNode array_access;
206 non terminal ParseNode postfix_expression;
207 non terminal ParseNode postincrement_expression, postdecrement_expression;
208 non terminal ParseNode unary_expression, unary_expression_not_plus_minus;
209 non terminal ParseNode preincrement_expression, predecrement_expression;
210 non terminal ParseNode cast_expression;
211 non terminal ParseNode multiplicative_expression, additive_expression;
212 non terminal ParseNode shift_expression, relational_expression, equality_expression;
213 non terminal ParseNode and_expression, exclusive_or_expression, inclusive_or_expression;
214 non terminal ParseNode conditional_and_expression, conditional_or_expression;
215 non terminal ParseNode conditional_expression;
216 non terminal ParseNode assignment_expression;
217 non terminal ParseNode assignment;
218 non terminal ParseNode assignment_operator;
219 non terminal ParseNode expression_opt, expression;
220 //non terminal ParseNode constant_expression;
221 //failure aware computation keywords
222 terminal FLAG;
223 terminal TAG;
224 terminal TASK;
225 terminal TASKEXIT;
226 non terminal ParseNode flag_declaration;
227 non terminal ParseNode task_declaration;
228 non terminal ParseNode task_parameter_list;
229 non terminal ParseNode task_parameter;
230 non terminal ParseNode flag_expression;
231 non terminal ParseNode flag_andexpression;
232 non terminal ParseNode flag_notexpression;
233 non terminal ParseNode task_exitstatement;
234 non terminal ParseNode flag_effects_opt;
235 non terminal ParseNode flag_effects;
236 non terminal ParseNode flag_effect;
237 non terminal ParseNode flag_list;
238 non terminal ParseNode flag_change;
239
240 start with goal;
241
242
243 // Task declarations
244 task_declaration ::= 
245         TASK IDENTIFIER:id LPAREN task_parameter_list:tpl RPAREN 
246         flag_effects_opt:feo
247         method_body:body 
248         {: 
249         ParseNode pn=new ParseNode("task_declaration");
250         pn.addChild("name").addChild(id);
251         pn.addChild(tpl);
252         pn.addChild(feo);
253         pn.addChild("body").addChild(body);     
254         RESULT=pn;
255         :};
256
257 task_parameter_list ::=
258                 task_parameter:fp {: 
259                 ParseNode pn=new ParseNode("task_parameter_list");
260                 pn.addChild(fp);
261                 RESULT=pn;
262         :}
263         |       task_parameter_list:fpl COMMA task_parameter:fp {: 
264                 fpl.addChild(fp);
265                 RESULT=fpl;
266         :}
267         ;
268
269 task_parameter ::=
270                 type:type variable_declarator_id:name LBRACE flag_expression:exp RBRACE {:
271                 ParseNode pn=new ParseNode("task_parameter");
272                 pn.addChild(type);
273                 pn.addChild(name);
274                 pn.addChild(exp);
275                 RESULT=pn;
276         :}
277         ;
278
279 flag_expression ::= 
280         flag_andexpression:exp {: 
281                 RESULT=exp;
282         :}
283         | flag_expression:exp1 OROR flag_andexpression:exp2 {: 
284                 ParseNode pn=new ParseNode("or");
285                 pn.addChild(exp1);
286                 pn.addChild(exp2);
287                 RESULT=pn;
288         :}
289         ;
290
291 flag_andexpression ::= 
292         flag_notexpression:exp {: RESULT=exp; :}
293         | flag_notexpression:exp1 ANDAND flag_andexpression:exp2 {: 
294                 ParseNode pn=new ParseNode("and");
295                 pn.addChild(exp1);
296                 pn.addChild(exp2);
297                 RESULT=pn;
298         :}
299         ;
300
301 flag_notexpression ::=
302         NOT flag_notexpression:exp {: 
303                 ParseNode pn=new ParseNode("not");
304                 pn.addChild(exp);
305                 RESULT=pn;
306         :}
307         | LPAREN flag_expression:exp RPAREN {: 
308                 RESULT=exp;
309         :}
310         | IDENTIFIER:id {:
311                 ParseNode pn=new ParseNode("name");
312                 pn.addChild(id);
313                 RESULT=pn;
314         :}
315         ;
316
317 task_exitstatement ::= TASKEXIT flag_effects_opt SEMICOLON{: 
318                 RESULT=new ParseNode("taskexit");
319         :};
320
321 flag_effects_opt ::= LPAREN flag_effects:fe RPAREN {:RESULT=fe;:}
322         | {: RESULT = null; :}
323         ;
324
325 flag_effects ::= flag_effect:fe {: 
326                 ParseNode pn=new ParseNode("flag_effects_list");
327                 pn.addChild(fe);
328                 RESULT=pn;
329         :}
330         |       flag_effects:fes COMMA flag_effect:fe {: 
331                 fes.addChild(fe);
332                 RESULT=fes;
333         :};
334
335 flag_effect ::= IDENTIFIER:id LBRACE flag_list:fl RBRACE {: 
336                 ParseNode pn=new ParseNode("flag_effect");
337                 pn.addChild(fl);
338                 RESULT=pn;
339         :};
340
341 flag_list ::= flag_change:fc {: 
342                 ParseNode pn=new ParseNode("flag_list");
343                 pn.addChild(fc);
344                 RESULT=pn;
345         :}
346         |       flag_list:fl COMMA flag_change:fc {: 
347                 fl.addChild(fc);
348                 RESULT=fl;
349         :};
350
351 flag_change ::= IDENTIFIER:id {: 
352                 RESULT=new ParseNode("name").addChild(id).getRoot();
353         :} |
354         NOT IDENTIFIER:id {: 
355                 RESULT=new ParseNode("not").addChild("name").addChild(id).getRoot();
356         :};
357
358 // 19.2) The Syntactic Grammar
359 goal ::=        compilation_unit:cu
360         {:
361         RESULT = cu;
362         :}
363         ;
364
365 // 19.3) Lexical Structure.
366
367
368 literal ::=     INTEGER_LITERAL:integer_lit
369         {:
370                 ParseNode pn=new ParseNode("literal");
371                 pn.addChild("integer").setLiteral(integer_lit);
372                 RESULT=pn;
373         :}
374         |       FLOATING_POINT_LITERAL:float_lit
375         {:
376                 ParseNode pn=new ParseNode("literal");
377                 pn.addChild("float").setLiteral(float_lit);
378                 RESULT=pn;
379         :}
380         |       BOOLEAN_LITERAL:boolean_lit
381         {:
382                 ParseNode pn=new ParseNode("literal");
383                 pn.addChild("boolean").setLiteral(boolean_lit);
384                 RESULT=pn;
385         :}
386         |       CHARACTER_LITERAL:char_lit
387         {:
388                 ParseNode pn=new ParseNode("literal");
389                 pn.addChild("char").setLiteral(char_lit);
390                 RESULT=pn;
391         :}
392         |       STRING_LITERAL:string_lit
393         {:
394                 ParseNode pn=new ParseNode("literal");
395                 pn.addChild("string").setLiteral(string_lit);
396                 RESULT=pn;
397         :}
398         |       NULL_LITERAL 
399         {:
400                 RESULT=(new ParseNode("literal")).addChild("null").getRoot();
401         :}
402         ;
403
404 // 19.4) Types, Values, and Variables
405 type    ::=     primitive_type:type {: RESULT=type; :}
406         |       reference_type:type {: RESULT=type; :}
407         ;
408
409 primitive_type ::=
410                 numeric_type:type {: RESULT=type; :}
411         |       BOOLEAN {: RESULT=(new ParseNode("type")).addChild("boolean").getRoot(); :}
412         ;
413 numeric_type::= integral_type:type {: RESULT=type; :}
414         |       floating_point_type:type {: RESULT=type; :}
415         ;
416 integral_type ::= 
417                 BYTE {: RESULT=(new ParseNode("type")).addChild("byte").getRoot(); :}
418         |       SHORT  {: RESULT=(new ParseNode("type")).addChild("short").getRoot(); :}
419         |       INT  {: RESULT=(new ParseNode("type")).addChild("int").getRoot(); :}
420         |       LONG  {: RESULT=(new ParseNode("type")).addChild("long").getRoot(); :}
421         |       CHAR  {: RESULT=(new ParseNode("type")).addChild("char").getRoot(); :}
422         ;
423 floating_point_type ::= 
424                 FLOAT  {: RESULT=(new ParseNode("type")).addChild("float").getRoot(); :}
425         |       DOUBLE  {: RESULT=(new ParseNode("type")).addChild("double").getRoot(); :}
426         ;
427
428 reference_type ::=
429                 class_or_interface_type:type {: RESULT=type; :}
430         |       array_type:type {: RESULT=type; :}
431         ;
432 class_or_interface_type ::= name:name {: 
433         RESULT=(new ParseNode("type")).addChild("class").addChild(name).getRoot(); 
434         :};
435
436 class_type ::=  class_or_interface_type:type {: RESULT=type; :};
437 //interface_type ::= class_or_interface_type;
438
439 array_type ::=  primitive_type:prim dims:dims {: 
440                 ParseNode pn=(new ParseNode("type")).addChild("array");
441                 pn.addChild("basetype").addChild(prim);
442                 pn.addChild("dims").setLiteral(dims);
443                 RESULT=pn;
444         :}
445         |       name:name dims:dims {: 
446                 ParseNode pn=(new ParseNode("type")).addChild("array");
447                 pn.addChild("basetype").addChild("type").addChild("class").addChild(name);
448                 pn.addChild("dims").setLiteral(dims);
449                 RESULT=pn;
450         :}
451         ;
452
453 // 19.5) Names
454 name    ::=     simple_name:name {: RESULT=name; :}
455         |       qualified_name:name {: RESULT=name; :}
456         ;
457 simple_name ::= IDENTIFIER:id {: 
458         RESULT=(new ParseNode("name")).addChild("identifier").addChild(id).getRoot(); 
459         :}
460         ;
461 qualified_name ::= name:name DOT IDENTIFIER:id {: 
462         ParseNode pn=new ParseNode("name");
463         pn.addChild("base").addChild(name);
464         pn.addChild("identifier").addChild(id);
465         RESULT=pn;
466         :}
467         ;
468
469 // 19.6) Packages
470 compilation_unit ::=
471 //              package_declaration_opt
472 //              import_declarations_opt
473                 type_declarations_opt:tdo {: 
474                 ParseNode pn=new ParseNode("compilation_unit");
475                 pn.addChild(tdo);
476                 RESULT=pn;
477                 :}
478                 ;
479 //package_declaration_opt ::= package_declaration | ;
480 //import_declarations_opt ::= import_declarations | ;
481 type_declarations_opt   ::= type_declarations:tds {:
482                 RESULT=tds;
483                 :}   | 
484         {: RESULT=new ParseNode("empty"); :}
485         ;
486
487 //import_declarations ::=
488 //               import_declaration
489 //       |       import_declarations import_declaration
490 //       ;
491
492 type_declarations ::= 
493                 type_declaration:td {:
494                 ParseNode pn=new ParseNode("type_declaration_list");
495                 pn.addChild(td);
496                 RESULT=pn;
497                 :}
498         |       type_declarations:tds type_declaration:td {:
499                 tds.addChild(td);
500                 RESULT=tds;
501                 :}
502         ;
503
504 //package_declaration ::=
505 //               PACKAGE name SEMICOLON
506 //       ;
507 //import_declaration ::=
508 //               single_type_import_declaration
509 //       |       type_import_on_demand_declaration
510 //       ;
511 //single_type_import_declaration ::=
512 //               IMPORT name SEMICOLON
513 //       ;
514 //type_import_on_demand_declaration ::=
515 //               IMPORT name DOT MULT SEMICOLON
516 //       ;
517
518 type_declaration ::=
519                 class_declaration:cd 
520                 {:
521                         RESULT=cd;
522                 :}
523         |       task_declaration:td 
524                 {:
525                         RESULT=td;
526                 :}
527 //      |       interface_declaration
528         |       SEMICOLON {: RESULT=new ParseNode("empty"); :}
529         ;
530
531 // 19.7) Productions used only in the LALR(1) grammar
532 modifiers_opt::=
533         {: RESULT=new ParseNode("empty"); :}
534         |       modifiers:mo {: 
535                 RESULT=mo;
536         :}
537         ;
538 modifiers ::=   modifier:mo {: 
539                 ParseNode pn=new ParseNode("modifier_list");
540                 pn.addChild(mo);
541                 RESULT=pn;
542         :}
543         |       modifiers:mos modifier:mo {: 
544                 mos.addChild(mo);
545                 RESULT=mos;
546         :}
547         ;
548 modifier ::=    
549         PUBLIC {: RESULT=new ParseNode("public"); :}|
550         PROTECTED {: RESULT=new ParseNode("protected"); :}|
551         PRIVATE {: RESULT=new ParseNode("private"); :}|
552         STATIC {: RESULT=new ParseNode("static"); :} |
553 //      ABSTRACT |
554         FINAL {: RESULT=new ParseNode("final"); :}|
555         NATIVE {: RESULT=new ParseNode("native"); :}
556 //      SYNCHRONIZED | 
557 //      TRANSIENT | 
558 //      VOLATILE |
559 //      STRICTFP // note that semantic analysis must check that the
560                          // context of the modifier allows strictfp.
561         ;
562
563 // 19.8) Classes
564
565 // 19.8.1) Class Declaration:
566 class_declaration ::= 
567         modifiers_opt:mo CLASS IDENTIFIER:id super_opt:so //interfaces_opt
568 class_body:body 
569         {:
570         ParseNode pn=new ParseNode("class_declaration");
571         pn.addChild("modifiers").addChild(mo);
572         pn.addChild("name").addChild(id);
573         pn.addChild("super").addChild(so);
574         pn.addChild("classbody").addChild(body);
575         RESULT=pn;
576         :}
577         ;
578 super ::=       EXTENDS class_type:classtype {: 
579                 RESULT=classtype;
580         :}
581         ;
582 super_opt ::=   
583         {: RESULT=new ParseNode("empty"); :}
584         |       super:su {: 
585                 RESULT=su;
586         :}
587         ;
588
589 //interfaces ::= IMPLEMENTS interface_type_list
590 //       ;
591 //interfaces_opt::=
592 //       |       interfaces
593 //       ;
594 //interface_type_list ::=
595 //               interface_type
596 //       |       interface_type_list COMMA interface_type
597 //       ;
598
599 class_body ::=  LBRACE class_body_declarations_opt:cbdo RBRACE {: RESULT=cbdo; :}
600         ;
601
602 class_body_declarations_opt ::= 
603         {: RESULT=new ParseNode("empty"); :}
604         |       class_body_declarations:cbd {: RESULT=cbd; :};
605
606 class_body_declarations ::= 
607                 class_body_declaration:cbd {: 
608                         ParseNode pn=new ParseNode("class_body_declaration_list");
609                         pn.addChild(cbd);
610                         RESULT=pn;
611                 :}
612         |       class_body_declarations:cbds class_body_declaration:cbd {: 
613                         cbds.addChild(cbd);
614                         RESULT=cbds;
615                 :}
616         ;
617
618 class_body_declaration ::=
619                 class_member_declaration:member {: 
620                 RESULT=(new ParseNode("member")).addChild(member).getRoot();
621         :}
622 //      |       static_initializer
623         |       constructor_declaration:constructor {: 
624                 RESULT=(new ParseNode("constructor")).addChild(constructor).getRoot();
625         :}
626         |       block:block {:
627                 RESULT=(new ParseNode("block")).addChild(block).getRoot();
628 :}
629         ;
630 class_member_declaration ::=
631         //failure aware computation
632         flag_declaration:flag {: 
633         RESULT=(new ParseNode("flag")).addChild(flag).getRoot(); 
634         :}
635         |
636         field_declaration:field {: 
637         RESULT=(new ParseNode("field")).addChild(field).getRoot(); 
638         :}
639         |       method_declaration:method {:
640         RESULT=(new ParseNode("method")).addChild(method).getRoot(); 
641         :}
642         /* repeat the prod for 'class_declaration' here: */
643 //      |       modifiers_opt CLASS IDENTIFIER super_opt class_body
644 //      |       interface_declaration
645         |       SEMICOLON       {: RESULT=new ParseNode("empty"); :}
646         ;
647
648 //Failure aware computation
649 flag_declaration ::= 
650                 FLAG IDENTIFIER:id SEMICOLON {: 
651                 ParseNode pn=new ParseNode("flag_declaration");
652                 pn.addChild("name").addChild(id);
653                 RESULT=pn;
654         :}
655         ;
656
657 // 19.8.2) Field Declarations
658 field_declaration ::= 
659                 modifiers_opt:mo type:type variable_declarators:var SEMICOLON {: 
660                 ParseNode pn=new ParseNode("field_declaration");
661                 pn.addChild("modifier").addChild(mo);
662                 pn.addChild("type").addChild(type);
663                 pn.addChild("variables").addChild(var);
664                 RESULT=pn;
665         :}
666         ;
667
668 variable_declarators ::=
669                 variable_declarator:vd {: 
670                 ParseNode pn=new ParseNode("variable_declarators_list");
671                 pn.addChild(vd);
672                 RESULT=pn;
673         :}
674         |       variable_declarators:vds COMMA variable_declarator:vd {:
675                 vds.addChild(vd);
676                 RESULT=vds;
677         :}
678         ;
679 variable_declarator ::=
680                 variable_declarator_id:id {:
681                 ParseNode pn=new ParseNode("variable_declarator");
682                 pn.addChild(id);
683                 RESULT=pn;
684         :}
685         |       variable_declarator_id:id EQ variable_initializer:init {: 
686                 ParseNode pn=new ParseNode("variable_declarator");
687                 pn.addChild(id);
688                 pn.addChild("initializer").addChild(init);
689                 RESULT=pn;
690         :}
691         ;
692 variable_declarator_id ::=
693                 IDENTIFIER:id {: 
694                 RESULT=(new ParseNode("single")).addChild(id).getRoot();:}
695         |       variable_declarator_id:id LBRACK RBRACK {:
696                 RESULT=(new ParseNode("array")).addChild(id).getRoot();:}
697         ;
698 variable_initializer ::=
699                 expression:exp {: RESULT=exp; :}
700 //      |       array_initializer
701         ;
702
703 // 19.8.3) Method Declarations
704 method_declaration ::=
705                 method_header:header method_body:body {:
706                 ParseNode pn=new ParseNode("method_declaration");
707                 pn.addChild(header);
708                 pn.addChild("body").addChild(body);
709                 RESULT=pn;
710         :}
711         ;
712 method_header ::=
713                 modifiers_opt:mo type:type method_declarator:decl //throws_opt 
714         {:
715                 ParseNode pn=new ParseNode("method_header");
716                 pn.addChild("modifiers").addChild(mo);
717                 pn.addChild("returntype").addChild(type);
718                 pn.addChild(decl);
719                 RESULT=pn;
720         :}
721         |       modifiers_opt:mo VOID method_declarator:decl //throws_opt
722         {:
723                 ParseNode pn=new ParseNode("method_header");
724                 pn.addChild("modifiers").addChild(mo);
725                 pn.addChild(decl);
726                 RESULT=pn;
727         :}
728         ;
729 method_declarator ::=
730                 IDENTIFIER:id LPAREN formal_parameter_list_opt:params RPAREN {: 
731                 ParseNode pn=new ParseNode("method_declarator");
732                 pn.addChild("name").addChild(id);
733                 pn.addChild("parameters").addChild(params);
734                 RESULT=pn;
735         :}
736 //      |       method_declarator LBRACK RBRACK // deprecated
737 // be careful; the above production also allows 'void foo() []'
738         ;
739 formal_parameter_list_opt ::=
740         {: RESULT=new ParseNode("empty"); :}
741         |       formal_parameter_list:fpl {: 
742                 RESULT=fpl;
743         :}
744         ;
745 formal_parameter_list ::=
746                 formal_parameter:fp {: 
747                 ParseNode pn=new ParseNode("formal_parameter_list");
748                 pn.addChild(fp);
749                 RESULT=pn;
750         :}
751         |       formal_parameter_list:fpl COMMA formal_parameter:fp {: 
752                 fpl.addChild(fp);
753                 RESULT=fpl;
754         :}
755         ;
756 formal_parameter ::=
757                 type:type variable_declarator_id:name {:
758                 ParseNode pn=new ParseNode("formal_parameter");
759                 pn.addChild(type);
760                 pn.addChild(name);
761                 RESULT=pn;
762         :}
763 //      |       FINAL type variable_declarator_id
764         ;
765 //throws_opt ::=        
766 //      |       throws
767 //      ;
768 //throws ::=    THROWS class_type_list
769 //      ;
770 //class_type_list ::=
771 //              class_type
772 //      |       class_type_list COMMA class_type
773 //      ;
774 method_body ::= block:block {: 
775                 RESULT=block;
776         :}
777         |       SEMICOLON       {: RESULT=new ParseNode("empty"); :}
778         ;
779
780 // 19.8.4) Static Initializers
781 //static_initializer ::=
782 //              STATIC block
783 //      ;
784
785 // 19.8.5) Constructor Declarations
786 constructor_declaration ::=
787                 modifiers_opt:mo constructor_declarator:cd
788 //throws_opt 
789                         constructor_body:body   {:
790                 ParseNode pn=new ParseNode("constructor_declaration");
791                 pn.addChild("modifiers").addChild(mo);
792                 pn.addChild(cd);
793                 pn.addChild("body").addChild(body);
794                 RESULT=pn;
795         :}
796         ;
797 constructor_declarator ::=
798                 simple_name:name LPAREN formal_parameter_list_opt:fplo RPAREN {: 
799                 ParseNode pn=new ParseNode("constructor_declarator");
800                 pn.addChild(name);
801                 pn.addChild("parameters").addChild(fplo);
802                 RESULT=pn;
803         :}
804         ;
805 constructor_body ::=
806 //              LBRACE explicit_constructor_invocation:eci block_statements:bs RBRACE |
807 //              LBRACE explicit_constructor_invocation RBRACE |
808                 LBRACE block_statements:block RBRACE {: 
809                 ParseNode pn=new ParseNode("constructor_body");
810                 pn.addChild(block);
811                 RESULT=pn;
812         :}
813         |       LBRACE RBRACE {: RESULT=new ParseNode("empty"); :}
814         ;
815 //explicit_constructor_invocation ::=
816 //              THIS LPAREN argument_list_opt RPAREN SEMICOLON
817 //      |       SUPER LPAREN argument_list_opt RPAREN SEMICOLON
818 //      |       primary DOT THIS LPAREN argument_list_opt RPAREN SEMICOLON
819 //      |       primary DOT SUPER LPAREN argument_list_opt RPAREN SEMICOLON
820 //      ;
821
822 // 19.9) Interfaces
823
824 // 19.9.1) Interface Declarations
825 //interface_declaration ::=
826 //               modifiers_opt INTERFACE IDENTIFIER extends_interfaces_opt
827 //                       interface_body
828 //       ;
829 //extends_interfaces_opt ::=
830 //       |       extends_interfaces
831 //       ;
832 //extends_interfaces ::=
833 //               EXTENDS interface_type
834 //       |       extends_interfaces COMMA interface_type
835 //       ;
836 //interface_body ::=
837 //               LBRACE interface_member_declarations_opt RBRACE
838 //       ;
839 //interface_member_declarations_opt ::=
840 //       |       interface_member_declarations
841 //       ;
842 //interface_member_declarations ::=
843 //               interface_member_declaration
844 //       |       interface_member_declarations interface_member_declaration
845 //       ;
846 //interface_member_declaration ::=
847 //               constant_declaration
848 //       |       abstract_method_declaration
849 //       |       class_declaration
850 //       |       interface_declaration
851 //       |       SEMICOLON
852 //       ;
853 //constant_declaration ::=
854 //               field_declaration
855 //       // need to semantically check that modifiers of field declaration
856 //       // include only PUBLIC, STATIC, or FINAL.  Other modifiers are
857 //       // disallowed.
858 //       ;
859 //abstract_method_declaration ::=
860 //               method_header SEMICOLON
861 //       ;
862
863
864 // 19.10) Arrays
865 //array_initializer ::=
866 //              LBRACE variable_initializers COMMA RBRACE
867 //      |       LBRACE variable_initializers RBRACE
868 //      |       LBRACE COMMA RBRACE
869 //      |       LBRACE RBRACE
870 //      ;
871 //variable_initializers ::=
872 //              variable_initializer
873 //      |       variable_initializers COMMA variable_initializer
874 //      ;
875
876 // 19.11) Blocks and Statements
877 block ::=       LBRACE block_statements_opt:bso RBRACE {: 
878         RESULT=bso;
879         :}
880         ;
881 block_statements_opt ::=
882         {: RESULT=new ParseNode("empty"); :}
883         |       block_statements:bs {: 
884         RESULT=bs;
885         :}
886         ;
887 block_statements ::=
888                 block_statement:bs {:
889         ParseNode pn=new ParseNode("block_statement_list");
890         pn.addChild(bs);
891         RESULT=pn;
892         :}
893         |       block_statements:bss block_statement:bs {: 
894         bss.addChild(bs);
895         RESULT=bss;
896         :}
897         ;
898 block_statement ::=
899                 local_variable_declaration_statement:lvds {: 
900                 RESULT=lvds;
901         :}
902         |       statement:statement {: 
903                 RESULT=statement;
904         :}
905 //      |       class_declaration
906 //      |       interface_declaration
907         ;
908 local_variable_declaration_statement ::=
909                 local_variable_declaration:lvd SEMICOLON {: 
910                 RESULT=lvd;
911         :}
912         ;
913 local_variable_declaration ::=
914                 type:type variable_declarators:var {: 
915                 ParseNode pn=new ParseNode("local_variable_declaration");
916                 pn.addChild(type);
917                 pn.addChild(var);
918                 RESULT=pn;
919 :}
920 //      |       FINAL type variable_declarators
921         ;
922 statement ::=   statement_without_trailing_substatement:st {: 
923                 RESULT=st;
924         :}
925 //      |       labeled_statement:st {: RESULT=st; :}
926         |       if_then_statement:st {: RESULT=st; :}
927         |       if_then_else_statement:st {: RESULT=st; :}
928         |       while_statement:st {: RESULT=st; :}
929         |       for_statement:st {: RESULT=st; :}
930         ;
931 statement_no_short_if ::=
932                 statement_without_trailing_substatement:st {: RESULT=st; :}
933 //      |       labeled_statement_no_short_if:st {: RESULT=st; :}
934         |       if_then_else_statement_no_short_if:st {: RESULT=st; :}
935         |       while_statement_no_short_if:st {: RESULT=st; :}
936         |       for_statement_no_short_if:st {: RESULT=st; :}
937         ;
938 statement_without_trailing_substatement ::=
939                 block:st {: RESULT=st; :}
940         |       empty_statement:st {: RESULT=st; :}
941         |       expression_statement:st {: RESULT=st; :}
942 //      |       switch_statement
943         |       do_statement
944         |       break_statement:st {: RESULT=st; :}
945         |       continue_statement:st {: RESULT=st; :}
946         |       return_statement:st {: RESULT=st; :}
947         |       task_exitstatement:st {: RESULT=st; :}
948 //      |       synchronized_statement
949 //      |       throw_statement
950 //      |       try_statement
951 //      |       assert_statement
952         ;
953 empty_statement ::=
954                 SEMICOLON {: RESULT=new ParseNode("nop"); :}
955         ;
956 //labeled_statement ::=
957 //              IDENTIFIER COLON statement
958 //      ;
959 //labeled_statement_no_short_if ::=
960 //              IDENTIFIER COLON statement_no_short_if
961 //      ;
962 expression_statement ::=
963                 statement_expression:se SEMICOLON {: 
964                 ParseNode pn=new ParseNode("expression");
965                 pn.addChild(se);
966                 RESULT=pn; :}
967         ;
968 statement_expression ::=
969                 assignment:st {: RESULT=st; :}
970         |       preincrement_expression:st {: RESULT=st; :}
971         |       predecrement_expression:st {: RESULT=st; :}
972         |       postincrement_expression:st {: RESULT=st; :}
973         |       postdecrement_expression:st {: RESULT=st; :}
974         |       method_invocation:st {: RESULT=st; :}
975         |       class_instance_creation_expression:st {: RESULT=st; :}
976         ;
977 if_then_statement ::=
978                 IF LPAREN expression:exp RPAREN statement:st {: 
979                 ParseNode pn=new ParseNode("ifstatement");
980                 pn.addChild("condition").addChild(exp);
981                 pn.addChild("statement").addChild(st);
982                 RESULT=pn;
983         :}
984         ;
985 if_then_else_statement ::=
986                 IF LPAREN expression:exp RPAREN statement_no_short_if:st
987                         ELSE statement:else_st {:
988                 ParseNode pn=new ParseNode("ifstatement");
989                 pn.addChild("condition").addChild(exp);
990                 pn.addChild("statement").addChild(st);
991                 pn.addChild("else_statement").addChild(else_st);
992                 RESULT=pn;
993         :}
994         ;
995 if_then_else_statement_no_short_if ::=
996                 IF LPAREN expression:exp RPAREN statement_no_short_if:st
997                         ELSE statement_no_short_if:else_st {:
998                 ParseNode pn=new ParseNode("ifstatement");
999                 pn.addChild("condition").addChild(exp);
1000                 pn.addChild("statement").addChild(st);
1001                 pn.addChild("else_statement").addChild(else_st);
1002                 RESULT=pn;
1003         :}
1004         ;
1005 //switch_statement ::=
1006 //              SWITCH LPAREN expression RPAREN switch_block
1007 //      ;
1008 //switch_block ::=
1009 //              LBRACE switch_block_statement_groups switch_labels RBRACE
1010 //      |       LBRACE switch_block_statement_groups RBRACE
1011 //      |       LBRACE switch_labels RBRACE
1012 //      |       LBRACE RBRACE
1013 //      ;
1014 //switch_block_statement_groups ::=
1015 //              switch_block_statement_group
1016 //      |       switch_block_statement_groups switch_block_statement_group
1017 //      ;
1018 //switch_block_statement_group ::=
1019 //              switch_labels block_statements
1020 //      ;
1021 //switch_labels ::=
1022 //              switch_label
1023 //      |       switch_labels switch_label
1024 //      ;
1025 //switch_label ::=
1026 //              CASE constant_expression COLON
1027 //      |       DEFAULT COLON
1028 //      ;
1029
1030 while_statement ::=
1031                 WHILE LPAREN expression:exp RPAREN statement:st {: 
1032                 ParseNode pn=new ParseNode("whilestatement");
1033                 pn.addChild("condition").addChild(exp);
1034                 pn.addChild("statement").addChild(st);
1035                 RESULT=pn;
1036         :}
1037         ;
1038 while_statement_no_short_if ::=
1039                 WHILE LPAREN expression:exp RPAREN statement_no_short_if:st {:
1040                 ParseNode pn=new ParseNode("whilestatement");
1041                 pn.addChild("condition").addChild(exp);
1042                 pn.addChild("statement").addChild(st);
1043                 RESULT=pn;
1044                 :}
1045         ;
1046 do_statement ::=
1047                 DO statement:st WHILE LPAREN expression:exp RPAREN SEMICOLON {: 
1048                 ParseNode pn=new ParseNode("dowhilestatement");
1049                 pn.addChild("condition").addChild(exp);
1050                 pn.addChild("statement").addChild(st);
1051                 RESULT=pn;
1052         :}
1053         ;
1054 for_statement ::=
1055                 FOR LPAREN for_init_opt:init SEMICOLON expression_opt:exp SEMICOLON
1056                         for_update_opt:update RPAREN statement:st {: 
1057                 ParseNode pn=new ParseNode("forstatement");
1058                 pn.addChild("initializer").addChild(init);
1059                 pn.addChild("condition").addChild(exp);
1060                 pn.addChild("update").addChild(update);
1061                 pn.addChild("statement").addChild(st);
1062                 RESULT=pn;
1063                 :}
1064         ;
1065 for_statement_no_short_if ::=
1066                 FOR LPAREN for_init_opt:init SEMICOLON expression_opt:exp SEMICOLON
1067                         for_update_opt:update RPAREN statement_no_short_if:st {:
1068                 ParseNode pn=new ParseNode("forstatement");
1069                 pn.addChild("initializer").addChild(init);
1070                 pn.addChild("condition").addChild(exp);
1071                 pn.addChild("update").addChild(update);
1072                 pn.addChild("statement").addChild(st);
1073                 RESULT=pn;
1074                 :}
1075         ;
1076 for_init_opt ::=
1077         {: RESULT=new ParseNode("empty"); :}
1078         |       for_init:init {: RESULT=init; :}
1079         ;
1080 for_init ::=    statement_expression_list:list {: RESULT=list; :}
1081         |       local_variable_declaration:decl {: RESULT=decl; :}
1082         ;
1083 for_update_opt ::=
1084         {: RESULT=new ParseNode("empty"); :}
1085         |       for_update:update {: RESULT=update; :}
1086         ;
1087 for_update ::=  statement_expression_list:list {: RESULT=list; :}
1088         ;
1089 statement_expression_list ::=
1090                 statement_expression:expr {: 
1091                 RESULT=(new ParseNode("statement_expression_list")).addChild(expr).getRoot();
1092         :}
1093         |       statement_expression_list:list COMMA statement_expression:expr {: 
1094                 list.addChild(expr);
1095                 RESULT=list;
1096         :}
1097         ;
1098
1099 //identifier_opt ::= 
1100 //      |       IDENTIFIER
1101 //      ;
1102
1103 break_statement ::=
1104                 BREAK
1105 //identifier_opt 
1106 SEMICOLON {: RESULT=new ParseNode("break"); :}
1107         ;
1108
1109 continue_statement ::=
1110                 CONTINUE  
1111 //identifier_opt 
1112 SEMICOLON
1113 {: RESULT=new ParseNode("continue"); :}
1114         ;
1115 return_statement ::=
1116                 RETURN expression_opt:exp SEMICOLON {: 
1117         RESULT=(new ParseNode("return")).addChild(exp).getRoot(); :}
1118         ;
1119 //throw_statement ::=
1120 //              THROW expression SEMICOLON
1121 //      ;
1122 //synchronized_statement ::=
1123 //              SYNCHRONIZED LPAREN expression RPAREN block
1124 //      ;
1125 //try_statement ::=
1126 //              TRY block catches
1127 //      |       TRY block catches_opt finally
1128 //      ;
1129 //catches_opt ::=
1130 //      |       catches
1131 //      ;
1132 //catches ::=   catch_clause
1133 //      |       catches catch_clause
1134 //      ;
1135 //catch_clause ::=
1136 //              CATCH LPAREN formal_parameter RPAREN block
1137 //      ;
1138 //finally ::=   FINALLY block
1139 //      ;
1140 //assert_statement ::=
1141 //              ASSERT expression SEMICOLON
1142 //      |       ASSERT expression COLON expression SEMICOLON
1143 //      ;
1144
1145 // 19.12) Expressions
1146 primary ::=     primary_no_new_array:st {: 
1147                 RESULT=st; :}
1148 //      |       array_creation_init:st {: 
1149 //              RESULT=st;
1150 //      :}
1151         |       array_creation_uninit:st {:
1152                 RESULT=st;
1153         :}
1154         ;
1155 primary_no_new_array ::=
1156                 literal:lit {: RESULT=lit; :}
1157         |       THIS {: RESULT=new ParseNode("this"); :}
1158         |       LPAREN expression:exp RPAREN {: RESULT=exp; :}
1159         |       class_instance_creation_expression:exp {: RESULT=exp; :}
1160         |       field_access:exp {: RESULT=exp; :}
1161         |       method_invocation:exp {: RESULT=exp; :}
1162         |       array_access:exp {: RESULT=exp; :}
1163 //      |       primitive_type DOT CLASS
1164 //      |       VOID DOT CLASS
1165 //      |       array_type DOT CLASS
1166 //      |       name DOT CLASS
1167 //      |       name DOT THIS
1168         ;
1169 class_instance_creation_expression ::=
1170                 NEW class_or_interface_type:type LPAREN argument_list_opt:args RPAREN {: 
1171                 ParseNode pn=new ParseNode("createobject");
1172                 pn.addChild(type);
1173                 pn.addChild(args);
1174                 RESULT=pn;
1175         :}
1176 //      |       NEW class_or_interface_type LPAREN argument_list_opt RPAREN class_body
1177 //      |       primary DOT NEW IDENTIFIER
1178 //                      LPAREN argument_list_opt RPAREN {: 
1179 //              
1180 //      :}
1181 //      |       primary DOT NEW IDENTIFIER
1182 //                      LPAREN argument_list_opt RPAREN class_body
1183 //      |       name DOT NEW IDENTIFIER
1184 //                      LPAREN argument_list_opt RPAREN
1185 //      |       name DOT NEW IDENTIFIER
1186 //                      LPAREN argument_list_opt RPAREN class_body
1187         ;
1188 argument_list_opt ::=
1189         {: RESULT=new ParseNode("empty"); :}
1190         |       argument_list:args {: RESULT=args; :}
1191         ;
1192 argument_list ::=
1193                 expression:exp {:
1194                 ParseNode pn=new ParseNode("argument_list");
1195                 pn.addChild(exp);
1196                 RESULT=pn;
1197         :}
1198         |       argument_list:list COMMA expression:exp {:
1199                 list.addChild(exp);
1200                 RESULT=list;
1201         :}
1202         ;
1203 array_creation_uninit ::=
1204                 NEW primitive_type:type dim_exprs:dimexpr dims_opt:dims {: 
1205                 ParseNode pn=new ParseNode("createarray");
1206                 pn.addChild(type);
1207                 pn.addChild(dimexpr);
1208                 pn.addChild("dims_opt").setLiteral(dims);
1209                 RESULT=pn;
1210                 :}
1211         |       NEW class_or_interface_type:type dim_exprs:dimexpr dims_opt:dims {: 
1212                 ParseNode pn=new ParseNode("createarray");
1213                 pn.addChild(type);
1214                 pn.addChild(dimexpr);
1215                 pn.addChild("dims_opt").setLiteral(dims);
1216                 RESULT=pn;
1217         :}
1218         ;
1219 //array_creation_init ::=
1220 //              NEW primitive_type dims array_initializer
1221 //      |       NEW class_or_interface_type dims array_initializer
1222 //      ;
1223 dim_exprs ::=   dim_expr:exp {: 
1224                 ParseNode pn=new ParseNode("dim_exprs");
1225                 pn.addChild(exp);
1226                 RESULT=pn; :}
1227         |       dim_exprs:base dim_expr:exp {: 
1228                 base.addChild(exp);
1229                 RESULT=base;
1230         :}
1231         ;
1232 dim_expr ::=    LBRACK expression:exp RBRACK {: RESULT=exp; :}
1233         ;
1234 dims_opt ::= {: RESULT=null; :}
1235         |       dims:dims {: RESULT = dims; :}
1236         ;
1237
1238 dims ::=        LBRACK RBRACK {: RESULT=new Integer(0); :}
1239         |       dims:dims LBRACK RBRACK {: RESULT=new Integer(dims.intValue()+1); :}
1240         ;
1241
1242 field_access ::=
1243                 primary:base DOT IDENTIFIER:id {: 
1244                 ParseNode pn=new ParseNode("fieldaccess");
1245                 pn.addChild("base").addChild(base);
1246                 pn.addChild("field").addChild(id);
1247                 RESULT=pn;
1248 :}
1249 //      |       SUPER DOT IDENTIFIER
1250 //      |       name DOT SUPER DOT IDENTIFIER
1251         ;
1252 method_invocation ::=
1253                 name:name LPAREN argument_list_opt:args RPAREN {: 
1254                 ParseNode pn=new ParseNode("methodinvoke1");
1255                 pn.addChild(name);
1256                 pn.addChild(args);
1257                 RESULT=pn;
1258         :}
1259         |       primary:base DOT IDENTIFIER:name LPAREN argument_list_opt:args RPAREN {: 
1260                 ParseNode pn=new ParseNode("methodinvoke2");
1261                 pn.addChild("base").addChild(base);
1262                 pn.addChild("id").addChild(name);
1263                 pn.addChild(args);
1264                 RESULT=pn;
1265         :}
1266 //      |       SUPER DOT IDENTIFIER LPAREN argument_list_opt RPAREN
1267 //      |       name DOT SUPER DOT IDENTIFIER LPAREN argument_list_opt RPAREN
1268         ;
1269 array_access ::=
1270                 name:name LBRACK expression:exp RBRACK {: 
1271                 ParseNode pn=new ParseNode("arrayaccess");
1272                 pn.addChild("base").addChild(name);
1273                 pn.addChild("index").addChild(exp);
1274                 RESULT=pn;
1275         :}
1276         |       primary_no_new_array:base LBRACK expression:exp RBRACK {: 
1277                 ParseNode pn=new ParseNode("arrayaccess");
1278                 pn.addChild("base").addChild(base);
1279                 pn.addChild("index").addChild(exp);
1280                 RESULT=pn;
1281         :}
1282 //      |       array_creation_init:init LBRACK expression:exp RBRACK {: 
1283 //              ParseNode pn=new ParseNode("arrayaccess");
1284 //              pn.addChild("init").addChild(init);
1285 //              pn.addChild("index").addChild(exp);
1286 //              RESULT=pn;
1287 //      :}
1288         ;
1289 postfix_expression ::=
1290                 primary:exp {: 
1291         RESULT=exp; :}
1292         |       name:exp {: RESULT=exp; :}
1293         |       postincrement_expression:exp {: RESULT=exp; :}
1294         |       postdecrement_expression:exp {: RESULT=exp; :}
1295         ;
1296 postincrement_expression ::=
1297                 postfix_expression:exp PLUSPLUS 
1298                 {: RESULT=(new ParseNode("postinc")).addChild(exp).getRoot(); :}
1299         ;
1300 postdecrement_expression ::=
1301                 postfix_expression:exp MINUSMINUS
1302                 {: RESULT=(new ParseNode("postdec")).addChild(exp).getRoot(); :}
1303         ;
1304 unary_expression ::=
1305                 preincrement_expression:exp {: RESULT=exp; :}
1306         |       predecrement_expression:exp {: RESULT=exp; :}
1307         |       PLUS unary_expression:exp 
1308         {: RESULT=(new ParseNode("unaryplus")).addChild(exp).getRoot(); :}
1309         |       MINUS unary_expression:exp
1310         {: RESULT=(new ParseNode("unaryminus")).addChild(exp).getRoot(); :}
1311         |       unary_expression_not_plus_minus:exp {: 
1312                         RESULT=exp; :}
1313         ;
1314 preincrement_expression ::=
1315                 PLUSPLUS unary_expression:exp
1316                 {: RESULT=(new ParseNode("preinc")).addChild(exp).getRoot(); :}
1317         ;
1318 predecrement_expression ::=
1319                 MINUSMINUS unary_expression:exp
1320                 {: RESULT=(new ParseNode("predec")).addChild(exp).getRoot(); :}
1321         ;
1322 unary_expression_not_plus_minus ::=
1323                 postfix_expression:exp {: 
1324                 RESULT=exp; :}
1325 //      |       COMP unary_expression
1326         |       NOT unary_expression:exp 
1327                 {: RESULT=(new ParseNode("not")).addChild(exp).getRoot(); :}
1328         |       cast_expression:exp {: RESULT=exp; :}
1329         ;
1330 cast_expression ::=
1331                 LPAREN primitive_type:type
1332         //dims_opt 
1333                 RPAREN unary_expression:exp {: 
1334                 ParseNode pn=new ParseNode("cast1");
1335                 pn.addChild("type").addChild(type);
1336                 pn.addChild("exp").addChild(exp);
1337                 RESULT=pn;
1338         :}
1339         |       LPAREN expression:type RPAREN unary_expression_not_plus_minus:exp {: 
1340                 ParseNode pn=new ParseNode("cast2");
1341                 pn.addChild("type").addChild(type);
1342                 pn.addChild("exp").addChild(exp);
1343                 RESULT=pn;
1344
1345         :}
1346 //      |       LPAREN name dims RPAREN unary_expression_not_plus_minus
1347         ;
1348 multiplicative_expression ::=
1349                 unary_expression:exp {: 
1350                         RESULT=exp; :}
1351         |       multiplicative_expression:exp1 MULT unary_expression:exp2 {: 
1352                 ParseNode pn=new ParseNode("mult");
1353                 pn.addChild(exp1);
1354                 pn.addChild(exp2);
1355                 RESULT=pn;
1356         :}
1357         |       multiplicative_expression:exp1 DIV unary_expression:exp2 {:
1358                 ParseNode pn=new ParseNode("div");
1359                 pn.addChild(exp1);
1360                 pn.addChild(exp2);
1361                 RESULT=pn;
1362         :}
1363         |       multiplicative_expression:exp1 MOD unary_expression:exp2 {:
1364                 ParseNode pn=new ParseNode("mod");
1365                 pn.addChild(exp1);
1366                 pn.addChild(exp2);
1367                 RESULT=pn;
1368         :}
1369         ;
1370 additive_expression ::=
1371                 multiplicative_expression:exp {: 
1372                         RESULT=exp; :}
1373         |       additive_expression:exp1 PLUS multiplicative_expression:exp2 {: 
1374                 ParseNode pn=new ParseNode("add");
1375                 pn.addChild(exp1);
1376                 pn.addChild(exp2);
1377                 RESULT=pn;
1378         :}
1379         |       additive_expression:exp1 MINUS multiplicative_expression:exp2 {: 
1380                 ParseNode pn=new ParseNode("sub");
1381                 pn.addChild(exp1);
1382                 pn.addChild(exp2);
1383                 RESULT=pn;
1384         :}
1385         ;
1386 shift_expression ::=
1387                 additive_expression:exp {: 
1388                         RESULT=exp; :}
1389         |       shift_expression:exp1 LSHIFT additive_expression:exp2 {: 
1390                 ParseNode pn=new ParseNode("leftshift");
1391                 pn.addChild(exp1);
1392                 pn.addChild(exp2);
1393                 RESULT=pn;
1394         :}
1395         |       shift_expression:exp1 RSHIFT additive_expression:exp2 {: 
1396                 ParseNode pn=new ParseNode("rightshift");
1397                 pn.addChild(exp1);
1398                 pn.addChild(exp2);
1399                 RESULT=pn;
1400         :}
1401 //      |       shift_expression URSHIFT additive_expression
1402         ;
1403 relational_expression ::=
1404                 shift_expression:exp {: 
1405                         RESULT=exp; :}
1406         |       relational_expression:exp1 LT shift_expression:exp2 {:
1407                 ParseNode pn=new ParseNode("comp_lt");
1408                 pn.addChild(exp1);
1409                 pn.addChild(exp2);
1410                 RESULT=pn;
1411         :}
1412         |       relational_expression:exp1 GT shift_expression:exp2 {:
1413                 ParseNode pn=new ParseNode("comp_gt");
1414                 pn.addChild(exp1);
1415                 pn.addChild(exp2);
1416                 RESULT=pn;
1417         :}
1418         |       relational_expression:exp1 LTEQ shift_expression:exp2 {:
1419                 ParseNode pn=new ParseNode("comp_lte");
1420                 pn.addChild(exp1);
1421                 pn.addChild(exp2);
1422                 RESULT=pn;
1423         :}
1424         |       relational_expression:exp1 GTEQ shift_expression:exp2 {:
1425                 ParseNode pn=new ParseNode("comp_gte");
1426                 pn.addChild(exp1);
1427                 pn.addChild(exp2);
1428                 RESULT=pn;
1429         :}
1430 //      |       relational_expression INSTANCEOF reference_type
1431         ;
1432
1433 equality_expression ::=
1434                 relational_expression:exp {: 
1435                         RESULT=exp; :}
1436         |       equality_expression:exp1 EQEQ relational_expression:exp2 {: 
1437                 ParseNode pn=new ParseNode("equal");
1438                 pn.addChild(exp1);
1439                 pn.addChild(exp2);
1440                 RESULT=pn;
1441         :}
1442         |       equality_expression:exp1 NOTEQ relational_expression:exp2 {: 
1443                 ParseNode pn=new ParseNode("not_equal");
1444                 pn.addChild(exp1);
1445                 pn.addChild(exp2);
1446                 RESULT=pn;
1447         :}
1448         ;
1449 and_expression ::=
1450                 equality_expression:exp {: 
1451                 RESULT=exp; :}
1452         |       and_expression:exp1 AND equality_expression:exp2 {: 
1453                 ParseNode pn=new ParseNode("bitwise_and");
1454                 pn.addChild(exp1);
1455                 pn.addChild(exp2);
1456                 RESULT=pn;
1457         :}
1458         ;
1459 exclusive_or_expression ::=
1460                 and_expression:expr {: 
1461                         RESULT=expr;
1462                 :}
1463         |       exclusive_or_expression:exp1 XOR and_expression:exp2 {: 
1464                 ParseNode pn=new ParseNode("bitwise_xor");
1465                 pn.addChild(exp1);
1466                 pn.addChild(exp2);
1467                 RESULT=pn;
1468 :}
1469         ;
1470 inclusive_or_expression ::=
1471                 exclusive_or_expression:exclor {: 
1472                         RESULT=exclor; :}
1473         |       inclusive_or_expression:exp1 OR exclusive_or_expression:exp2 {: 
1474                 ParseNode pn=new ParseNode("bitwise_or");
1475                 pn.addChild(exp1);
1476                 pn.addChild(exp2);
1477                 RESULT=pn;
1478         :}
1479         ;
1480 conditional_and_expression ::=
1481                 inclusive_or_expression:inclor {: 
1482                         RESULT=inclor; :}
1483         |       conditional_and_expression:exp1 ANDAND inclusive_or_expression:exp2 {:
1484                 ParseNode pn=new ParseNode("logical_and");
1485                 pn.addChild(exp1);
1486                 pn.addChild(exp2);
1487                 RESULT=pn;
1488         :}
1489         ;
1490 conditional_or_expression ::=
1491                 conditional_and_expression:condand {: 
1492                         RESULT=condand; :}
1493         |       conditional_or_expression:exp1 OROR conditional_and_expression:exp2 {: 
1494                 ParseNode pn=new ParseNode("logical_or");
1495                 pn.addChild(exp1);
1496                 pn.addChild(exp2);
1497                 RESULT=pn;
1498         :}
1499         ;
1500 conditional_expression ::=
1501                 conditional_or_expression:condor {: 
1502                         RESULT=condor; :}
1503 //      |       conditional_or_expression QUESTION expression 
1504 //                      COLON conditional_expression
1505         ;
1506 assignment_expression ::=
1507                 conditional_expression:expr {: 
1508                         RESULT=expr; :} |
1509                 assignment:assign {: 
1510                         RESULT=assign; :}
1511         ;
1512 // semantic check necessary here to ensure a valid left-hand side.
1513 // allowing a parenthesized variable here on the lhs was introduced in
1514 // JLS 2; thanks to Eric Blake for pointing this out.
1515 assignment ::=  postfix_expression:lvalue assignment_operator:op assignment_expression:rvalue {:
1516                 ParseNode pn=new ParseNode("assignment");
1517                 pn.addChild("op").addChild(op);
1518                 ParseNode pnargs=pn.addChild("args");
1519                 pnargs.addChild(lvalue);
1520                 pnargs.addChild(rvalue);
1521                 RESULT=pn;
1522          :}
1523         ;
1524 assignment_operator ::=
1525                 EQ {: RESULT=new ParseNode("eq"); :}
1526         |       MULTEQ {: RESULT=new ParseNode("multeq"); :}
1527         |       DIVEQ {: RESULT=new ParseNode("diveq"); :}
1528         |       MODEQ {: RESULT=new ParseNode("modeq"); :}
1529         |       PLUSEQ {: RESULT=new ParseNode("pluseq"); :}
1530         |       MINUSEQ {: RESULT=new ParseNode("minuseq"); :}
1531         |       LSHIFTEQ {: RESULT=new ParseNode("lshifteq"); :}
1532         |       RSHIFTEQ {: RESULT=new ParseNode("rshifteq"); :}
1533 //      |       URSHIFTEQ {: RESULT=new ParseNode("urshifteq"); :}
1534         |       ANDEQ {: RESULT=new ParseNode("andeq"); :}
1535         |       XOREQ {: RESULT=new ParseNode("xoreq"); :}
1536         |       OREQ {: RESULT=new ParseNode("oreq"); :}
1537         ;
1538 expression_opt ::=
1539         {:      RESULT=new ParseNode("empty"); :}
1540         |       expression:exp {: 
1541                 RESULT=exp; :}
1542         ;
1543 expression ::=  assignment_expression:exp {: 
1544                 RESULT=exp; :}
1545         ;
1546 //constant_expression ::=
1547 //              expression
1548 //      ;