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