299a5e9b21a505456f398cfaefa7ba01db2e8073
[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 cons_argument_list_opt, cons_argument_list;
200 non terminal ParseNode argument_list_opt, argument_list;
201 //non terminal ParseNode array_creation_init;
202 non terminal ParseNode array_creation_uninit;
203 non terminal ParseNode dim_exprs, dim_expr;
204 non terminal Integer dims_opt, dims;
205 non terminal ParseNode field_access, method_invocation;
206 non terminal ParseNode array_access;
207 non terminal ParseNode postfix_expression;
208 non terminal ParseNode postincrement_expression, postdecrement_expression;
209 non terminal ParseNode unary_expression, unary_expression_not_plus_minus;
210 non terminal ParseNode preincrement_expression, predecrement_expression;
211 non terminal ParseNode cast_expression;
212 non terminal ParseNode multiplicative_expression, additive_expression;
213 non terminal ParseNode shift_expression, relational_expression, equality_expression;
214 non terminal ParseNode and_expression, exclusive_or_expression, inclusive_or_expression;
215 non terminal ParseNode conditional_and_expression, conditional_or_expression;
216 non terminal ParseNode conditional_expression;
217 non terminal ParseNode assignment_expression;
218 non terminal ParseNode assignment;
219 non terminal ParseNode assignment_operator;
220 non terminal ParseNode expression_opt, expression;
221 //non terminal ParseNode constant_expression;
222 //failure aware computation keywords
223 terminal FLAG;
224 terminal OPTIONAL;
225 terminal ISAVAILABLE;
226 terminal EXTERNAL;
227 terminal TAG;
228 terminal TASK;
229 terminal TASKEXIT;
230 non terminal ParseNode flag_declaration;
231 non terminal ParseNode task_declaration;
232 non terminal ParseNode task_parameter_list;
233 non terminal ParseNode task_parameter;
234 non terminal ParseNode flag_expression;
235 non terminal ParseNode flag_andexpression;
236 non terminal ParseNode flag_notexpression;
237 non terminal ParseNode task_exitstatement;
238 non terminal ParseNode flag_effects_opt;
239 non terminal ParseNode flag_effects;
240 non terminal ParseNode flag_effect;
241 non terminal ParseNode flag_list;
242 non terminal ParseNode flag_list_opt;
243 non terminal ParseNode flag_change;
244
245 non terminal ParseNode cons_checks_opt;
246 non terminal ParseNode cons_checks;
247 non terminal ParseNode cons_check;
248
249 non terminal ParseNode tag_variable_declaration_statement;
250 non terminal ParseNode tag_expression_list;
251 non terminal ParseNode tag_expression;
252 non terminal ParseNode tag_list;
253 non terminal ParseNode tag_list_opt;
254 non terminal ParseNode tag_change;
255
256 //distributed transaction keywords
257 terminal ATOMIC;
258 terminal GLOBAL;
259 terminal GETOFFSET;
260 non terminal ParseNode atomic_statement;
261 non terminal ParseNode getoffset_expression;
262
263 //disjointness for Java
264 terminal DISJOINT;
265
266 //coarse-grain parallelization
267 terminal SESE;
268 non terminal ParseNode sese_statement;
269
270
271 start with goal;
272
273
274 // Task declarations
275 task_declaration ::= 
276         TASK IDENTIFIER:id LPAREN task_parameter_list:tpl RPAREN 
277         flag_effects_opt:feo
278         method_body:body 
279         {: 
280         ParseNode pn=new ParseNode("task_declaration");
281         pn.addChild("name").addChild(id);
282         pn.addChild(tpl);
283         pn.addChild(feo);
284         pn.addChild("body").addChild(body);     
285         RESULT=pn;
286         :};
287
288 task_parameter_list ::=
289                 task_parameter:fp {: 
290                 ParseNode pn=new ParseNode("task_parameter_list");
291                 pn.addChild(fp);
292                 RESULT=pn;
293         :}
294         |       task_parameter_list:fpl COMMA task_parameter:fp {: 
295                 fpl.addChild(fp);
296                 RESULT=fpl;
297         :}
298         ;
299
300 task_parameter ::=
301                 type:type variable_declarator_id:name LBRACE flag_expression:exp RBRACE {:
302                 ParseNode pn=new ParseNode("task_parameter");
303                 pn.addChild(type);
304                 pn.addChild(name);
305                 pn.addChild("flag").addChild(exp);
306                 RESULT=pn;
307         :} 
308         | type:type variable_declarator_id:name LBRACE flag_expression:exp RBRACE LBRACE tag_expression_list:texp RBRACE {:
309                 ParseNode pn=new ParseNode("task_parameter");
310                 pn.addChild(type);
311                 pn.addChild(name);
312                 pn.addChild("flag").addChild(exp);
313                 pn.addChild("tag").addChild(texp);
314                 RESULT=pn;
315         :}
316         | type:type variable_declarator_id:name LBRACE RBRACE LBRACE tag_expression_list:texp RBRACE {:
317                 ParseNode pn=new ParseNode("task_parameter");
318                 pn.addChild(type);
319                 pn.addChild(name);
320                 pn.addChild("tag").addChild(texp);
321                 RESULT=pn;
322         :}
323         | OPTIONAL task_parameter:fp {:
324                 ParseNode pn=new ParseNode("task_parameter");
325                 pn.addChild("optional").addChild(fp);
326                 RESULT=pn;
327         :}              
328         
329         ;
330
331 tag_expression_list ::= tag_expression:te {: 
332         ParseNode pn=new ParseNode("tag_expression_list");
333         pn.addChild(te);
334         RESULT=pn;
335         :}
336         | tag_expression_list:tel COMMA tag_expression:te {: 
337         tel.addChild(te);
338         RESULT=tel;
339         :}
340         ;
341
342 tag_expression ::= IDENTIFIER:type IDENTIFIER:id {: 
343                 ParseNode pn=new ParseNode("tag_expression");
344                 pn.addChild("type").addChild(type);
345                 pn.addChild("single").addChild(id);
346                 RESULT=pn;
347         :}
348         ;
349
350 tag_list_opt ::= LBRACE tag_list:fl RBRACE {:RESULT=fl;:}
351         | LBRACE RBRACE {: RESULT = new ParseNode("empty"); :}  
352         | {: RESULT = new ParseNode("empty"); :}
353         ;
354
355 tag_list ::= tag_change:fc {: 
356                 ParseNode pn=new ParseNode("tag_list");
357                 pn.addChild(fc);
358                 RESULT=pn;
359         :}
360         | tag_list:fl COMMA tag_change:fc {: 
361                 fl.addChild(fc);
362                 RESULT=fl;
363         :};
364
365 tag_change ::= IDENTIFIER:id {: 
366                 RESULT=new ParseNode("name").addChild(id).getRoot();
367         :}
368         | NOT IDENTIFIER:id {: 
369                 RESULT=new ParseNode("not").addChild("name").addChild(id).getRoot();
370         :};
371
372 flag_expression ::= 
373         flag_andexpression:exp {: 
374                 RESULT=exp;
375         :}
376         | flag_expression:exp1 OROR flag_andexpression:exp2 {: 
377                 ParseNode pn=new ParseNode("or");
378                 pn.addChild(exp1);
379                 pn.addChild(exp2);
380                 RESULT=pn;
381         :}
382         ;
383
384 flag_andexpression ::= 
385         flag_notexpression:exp {: RESULT=exp; :}
386         | flag_notexpression:exp1 ANDAND flag_andexpression:exp2 {: 
387                 ParseNode pn=new ParseNode("and");
388                 pn.addChild(exp1);
389                 pn.addChild(exp2);
390                 RESULT=pn;
391         :}
392         ;
393
394 flag_notexpression ::=
395         NOT flag_notexpression:exp {: 
396                 ParseNode pn=new ParseNode("not");
397                 pn.addChild(exp);
398                 RESULT=pn;
399         :}
400         | LPAREN flag_expression:exp RPAREN {: 
401                 RESULT=exp;
402         :}
403         | IDENTIFIER:id {:
404                 ParseNode pn=new ParseNode("name");
405                 pn.addChild(id);
406                 RESULT=pn;
407         :}
408         ;
409
410 task_exitstatement ::= TASKEXIT flag_effects_opt:opt cons_checks_opt:cco SEMICOLON {: 
411                 RESULT=(new ParseNode("taskexit")).addChild(opt).getRoot().addChild(cco).getRoot();
412         :};
413
414 cons_checks_opt ::= ASSERT LPAREN cons_checks:cc RPAREN {: RESULT=cc; :}
415         | {: RESULT = new ParseNode("empty"); :}
416         ;
417
418 cons_checks ::= cons_check:cc {: 
419                 ParseNode pn=new ParseNode("cons_checks");
420                 pn.addChild(cc);
421                 RESULT=pn;
422         :}
423         |       cons_checks:ccs COMMA cons_check:cc {: 
424                 ccs.addChild(cc);
425                 RESULT=ccs;
426         :};
427
428 cons_check ::=  IDENTIFIER:name LPAREN cons_argument_list_opt:args RPAREN {: 
429                 ParseNode pn=new ParseNode("cons_check");
430                 pn.addChild("name").addChild("identifier").addChild(name);
431                 pn.addChild(args);
432                 RESULT=pn;
433         :};
434
435 flag_effects_opt ::= LPAREN flag_effects:fe RPAREN {:RESULT=fe;:}
436         | {: RESULT = new ParseNode("empty"); :}
437         ;
438
439 flag_effects ::= flag_effect:fe {: 
440                 ParseNode pn=new ParseNode("flag_effects_list");
441                 pn.addChild(fe);
442                 RESULT=pn;
443         :}
444         |       flag_effects:fes COMMA flag_effect:fe {: 
445                 fes.addChild(fe);
446                 RESULT=fes;
447         :};
448
449 flag_effect ::= IDENTIFIER:id LBRACE flag_list:fl RBRACE tag_list_opt:tlo {: 
450                 ParseNode pn=new ParseNode("flag_effect");
451                 pn.addChild("name").addChild(id);
452                 pn.addChild(fl);
453                 pn.addChild(tlo);
454                 RESULT=pn;
455         :}
456         | IDENTIFIER:id LBRACE RBRACE LBRACE tag_list:tl RBRACE {: 
457                 ParseNode pn=new ParseNode("flag_effect");
458                 pn.addChild("name").addChild(id);
459                 pn.addChild(tl);
460                 RESULT=pn;
461         :};
462
463 flag_list_opt ::= LBRACE flag_list:fl RBRACE {:RESULT=fl;:}
464         | LBRACE RBRACE {: RESULT = new ParseNode("empty"); :}  
465         | 
466         {: RESULT = new ParseNode("empty"); :}
467         ;
468
469 flag_list ::= flag_change:fc {: 
470                 ParseNode pn=new ParseNode("flag_list");
471                 pn.addChild(fc);
472                 RESULT=pn;
473         :}
474         |       flag_list:fl COMMA flag_change:fc {: 
475                 fl.addChild(fc);
476                 RESULT=fl;
477         :};
478
479 flag_change ::= IDENTIFIER:id {: 
480                 RESULT=new ParseNode("name").addChild(id).getRoot();
481         :} |
482         NOT IDENTIFIER:id {: 
483                 RESULT=new ParseNode("not").addChild("name").addChild(id).getRoot();
484         :};
485
486 // 19.2) The Syntactic Grammar
487 goal ::=        compilation_unit:cu
488         {:
489         RESULT = cu;
490         :}
491         ;
492
493 // 19.3) Lexical Structure.
494
495
496 literal ::=     INTEGER_LITERAL:integer_lit
497         {:
498                 ParseNode pn=new ParseNode("literal");
499                 pn.addChild("integer").setLiteral(integer_lit);
500                 RESULT=pn;
501         :}
502         |       FLOATING_POINT_LITERAL:float_lit
503         {:
504                 ParseNode pn=new ParseNode("literal");
505                 pn.addChild("float").setLiteral(float_lit);
506                 RESULT=pn;
507         :}
508         |       BOOLEAN_LITERAL:boolean_lit
509         {:
510                 ParseNode pn=new ParseNode("literal");
511                 pn.addChild("boolean").setLiteral(boolean_lit);
512                 RESULT=pn;
513         :}
514         |       CHARACTER_LITERAL:char_lit
515         {:
516                 ParseNode pn=new ParseNode("literal");
517                 pn.addChild("char").setLiteral(char_lit);
518                 RESULT=pn;
519         :}
520         |       STRING_LITERAL:string_lit
521         {:
522                 ParseNode pn=new ParseNode("literal");
523                 pn.addChild("string").setLiteral(string_lit);
524                 RESULT=pn;
525         :}
526         |       NULL_LITERAL 
527         {:
528                 RESULT=(new ParseNode("literal")).addChild("null").getRoot();
529         :}
530         ;
531
532 // 19.4) Types, Values, and Variables
533 type    ::=     primitive_type:type {: RESULT=type; :}
534         |       reference_type:type {: RESULT=type; :}
535         ;
536
537 primitive_type ::=
538                 numeric_type:type {: RESULT=type; :}
539         |       BOOLEAN {: RESULT=(new ParseNode("type")).addChild("boolean").getRoot(); :}
540         ;
541 numeric_type::= integral_type:type {: RESULT=type; :}
542         |       floating_point_type:type {: RESULT=type; :}
543         ;
544 integral_type ::= 
545                 BYTE {: RESULT=(new ParseNode("type")).addChild("byte").getRoot(); :}
546         |       SHORT  {: RESULT=(new ParseNode("type")).addChild("short").getRoot(); :}
547         |       INT  {: RESULT=(new ParseNode("type")).addChild("int").getRoot(); :}
548         |       LONG  {: RESULT=(new ParseNode("type")).addChild("long").getRoot(); :}
549         |       CHAR  {: RESULT=(new ParseNode("type")).addChild("char").getRoot(); :}
550         ;
551 floating_point_type ::= 
552                 FLOAT  {: RESULT=(new ParseNode("type")).addChild("float").getRoot(); :}
553         |       DOUBLE  {: RESULT=(new ParseNode("type")).addChild("double").getRoot(); :}
554         ;
555
556 reference_type ::=
557                 class_or_interface_type:type {: RESULT=type; :}
558         |       array_type:type {: RESULT=type; :}
559         ;
560 class_or_interface_type ::= name:name {: 
561         RESULT=(new ParseNode("type")).addChild("class").addChild(name).getRoot(); 
562         :};
563
564 class_type ::=  class_or_interface_type:type {: RESULT=type; :};
565 //interface_type ::= class_or_interface_type;
566
567 array_type ::=  primitive_type:prim dims:dims {: 
568                 ParseNode pn=(new ParseNode("type")).addChild("array");
569                 pn.addChild("basetype").addChild(prim);
570                 pn.addChild("dims").setLiteral(dims);
571                 RESULT=pn.getRoot();
572         :}
573         |       name:name dims:dims {: 
574                 ParseNode pn=(new ParseNode("type")).addChild("array");
575                 pn.addChild("basetype").addChild("type").addChild("class").addChild(name);
576                 pn.addChild("dims").setLiteral(dims);
577                 RESULT=pn.getRoot();
578         :}
579         ;
580
581 // 19.5) Names
582 name    ::=     simple_name:name {: RESULT=name; :}
583         |       qualified_name:name {: RESULT=name; :}
584         ;
585 simple_name ::= IDENTIFIER:id {: 
586         RESULT=(new ParseNode("name")).addChild("identifier").addChild(id).getRoot(); 
587         :}
588         ;
589 qualified_name ::= name:name DOT IDENTIFIER:id {: 
590         ParseNode pn=new ParseNode("name");
591         pn.addChild("base").addChild(name);
592         pn.addChild("identifier").addChild(id);
593         RESULT=pn;
594         :}
595         ;
596
597 // 19.6) Packages
598 compilation_unit ::=
599                 package_declaration_opt:pdo
600                 import_declarations_opt:ido
601                 type_declarations_opt:tdo {: 
602                 ParseNode pn=new ParseNode("compilation_unit");
603                 pn.addChild(tdo);
604                 pn.addChild("packages").addChild(pdo);
605                 pn.addChild("imports").addChild(ido);
606                 RESULT=pn;
607                 :}
608                 ;
609 package_declaration_opt ::= package_declaration:pdo {:
610                 RESULT=pdo;
611         :} |
612         {: RESULT=new ParseNode("empty"); :}
613 ;
614
615 import_declarations_opt ::= import_declarations:ido {: 
616                 RESULT=ido;
617         :} | 
618         {: RESULT=new ParseNode("empty"); :}
619 ;
620 type_declarations_opt   ::= type_declarations:tds {:
621                 RESULT=tds;
622                 :}   | 
623         {: RESULT=new ParseNode("empty"); :}
624         ;
625
626 import_declarations ::=
627                import_declaration:id {: 
628                 ParseNode pn=new ParseNode("import_decls_list");
629                 pn.addChild(id);
630                 RESULT=pn;
631         :}
632        |       import_declarations:ids import_declaration:id {: 
633                 ids.addChild(id);
634                 RESULT=ids;
635         :}
636        ;
637
638 type_declarations ::= 
639                 type_declaration:td {:
640                 ParseNode pn=new ParseNode("type_declaration_list");
641                 pn.addChild(td);
642                 RESULT=pn;
643                 :}
644         |       type_declarations:tds type_declaration:td {:
645                 tds.addChild(td);
646                 RESULT=tds;
647                 :}
648         ;
649
650 package_declaration ::=
651                PACKAGE name:name SEMICOLON {: 
652         ParseNode pn=new ParseNode("package");
653         pn.addChild(name);
654         RESULT=pn;
655         :}
656        ;
657 import_declaration ::=
658                single_type_import_declaration:sid {: RESULT=sid; :}
659        |       type_import_on_demand_declaration:iod {: RESULT=iod; :}
660        ;
661 single_type_import_declaration ::=
662                IMPORT name:name SEMICOLON {: 
663         ParseNode pn=new ParseNode("import_single");
664         pn.addChild(name);
665         RESULT=pn;
666 :}
667        ;
668 type_import_on_demand_declaration ::=
669                IMPORT name:name DOT MULT SEMICOLON {:
670         ParseNode pn=new ParseNode("import_ondemand");
671         pn.addChild(name);
672         RESULT=pn;
673         :}       
674         ;
675
676 type_declaration ::=
677                 class_declaration:cd 
678                 {:
679                         RESULT=cd;
680                 :}
681         |       task_declaration:td 
682                 {:
683                         RESULT=td;
684                 :}
685 //      |       interface_declaration
686         |       SEMICOLON {: RESULT=new ParseNode("empty"); :}
687         ;
688
689 // 19.7) Productions used only in the LALR(1) grammar
690 modifiers_opt::=
691         {: RESULT=new ParseNode("empty"); :}
692         |       modifiers:mo {: 
693                 RESULT=mo;
694         :}
695         ;
696 modifiers ::=   modifier:mo {: 
697                 ParseNode pn=new ParseNode("modifier_list");
698                 pn.addChild(mo);
699                 RESULT=pn;
700         :}
701         |       modifiers:mos modifier:mo {: 
702                 mos.addChild(mo);
703                 RESULT=mos;
704         :}
705         ;
706 modifier ::=    
707         PUBLIC {: RESULT=new ParseNode("public"); :}|
708         PROTECTED {: RESULT=new ParseNode("protected"); :}|
709         PRIVATE {: RESULT=new ParseNode("private"); :}|
710         STATIC {: RESULT=new ParseNode("static"); :} |
711 //      ABSTRACT |
712         FINAL {: RESULT=new ParseNode("final"); :}|
713         NATIVE {: RESULT=new ParseNode("native"); :} |
714         SYNCHRONIZED {: RESULT=new ParseNode("synchronized"); :} |
715         ATOMIC {: RESULT=new ParseNode("atomic"); :}
716 //      TRANSIENT | 
717 //      VOLATILE |
718 //      STRICTFP // note that semantic analysis must check that the
719                          // context of the modifier allows strictfp.
720         ;
721
722 // 19.8) Classes
723
724 // 19.8.1) Class Declaration:
725 class_declaration ::= 
726         modifiers_opt:mo CLASS IDENTIFIER:id super_opt:so //interfaces_opt
727 class_body:body 
728         {:
729         ParseNode pn=new ParseNode("class_declaration");
730         pn.addChild("modifiers").addChild(mo);
731         pn.addChild("name").addChild(id);
732         pn.addChild("super").addChild(so);
733         pn.addChild("classbody").addChild(body);
734         RESULT=pn;
735         :}
736         ;
737 super ::=       EXTENDS class_type:classtype {: 
738                 RESULT=classtype;
739         :}
740         ;
741 super_opt ::=   
742         {: RESULT=new ParseNode("empty"); :}
743         |       super:su {: 
744                 RESULT=su;
745         :}
746         ;
747
748 //interfaces ::= IMPLEMENTS interface_type_list
749 //       ;
750 //interfaces_opt::=
751 //       |       interfaces
752 //       ;
753 //interface_type_list ::=
754 //               interface_type
755 //       |       interface_type_list COMMA interface_type
756 //       ;
757
758 class_body ::=  LBRACE class_body_declarations_opt:cbdo RBRACE {: RESULT=cbdo; :}
759         ;
760
761 class_body_declarations_opt ::= 
762         {: RESULT=new ParseNode("empty"); :}
763         |       class_body_declarations:cbd {: RESULT=cbd; :};
764
765 class_body_declarations ::= 
766                 class_body_declaration:cbd {: 
767                         ParseNode pn=new ParseNode("class_body_declaration_list");
768                         pn.addChild(cbd);
769                         RESULT=pn;
770                 :}
771         |       class_body_declarations:cbds class_body_declaration:cbd {: 
772                         cbds.addChild(cbd);
773                         RESULT=cbds;
774                 :}
775         ;
776
777 class_body_declaration ::=
778                 class_member_declaration:member {: 
779                 RESULT=(new ParseNode("member")).addChild(member).getRoot();
780         :}
781 //      |       static_initializer
782         |       constructor_declaration:constructor {: 
783                 RESULT=(new ParseNode("constructor")).addChild(constructor).getRoot();
784         :}
785         |       block:block {:
786                 RESULT=(new ParseNode("block")).addChild(block).getRoot();
787 :}
788         ;
789 class_member_declaration ::=
790         //failure aware computation
791         flag_declaration:flag {: 
792         RESULT=(new ParseNode("flag")).addChild(flag).getRoot(); 
793         :}
794         |
795         field_declaration:field {: 
796         RESULT=(new ParseNode("field")).addChild(field).getRoot(); 
797         :}
798         |       method_declaration:method {:
799         RESULT=(new ParseNode("method")).addChild(method).getRoot(); 
800         :}
801         /* repeat the prod for 'class_declaration' here: */
802 //      |       modifiers_opt CLASS IDENTIFIER super_opt class_body
803 //      |       interface_declaration
804         |       SEMICOLON       {: RESULT=new ParseNode("empty"); :}
805         ;
806
807 //Failure aware computation
808 flag_declaration ::= 
809                 FLAG IDENTIFIER:id SEMICOLON {: 
810                 ParseNode pn=new ParseNode("flag_declaration");
811                 pn.addChild("name").addChild(id);
812                 RESULT=pn;
813         :}      |
814                 EXTERNAL FLAG IDENTIFIER:id SEMICOLON {: 
815                 ParseNode pn=new ParseNode("flag_declaration");
816                 pn.addChild("name").addChild(id);
817                 pn.addChild("external");
818                 RESULT=pn;
819         :}
820         ;
821
822 // 19.8.2) Field Declarations
823 field_declaration ::= 
824                 modifiers_opt:mo type:type variable_declarators:var SEMICOLON {: 
825                 ParseNode pn=new ParseNode("field_declaration");
826                 pn.addChild("modifier").addChild(mo);
827                 pn.addChild("type").addChild(type);
828                 pn.addChild("variables").addChild(var);
829                 RESULT=pn;
830         :} |
831                 modifiers_opt:mo GLOBAL type:type variable_declarators:var SEMICOLON {: 
832                 ParseNode pn=new ParseNode("field_declaration");
833                 pn.addChild("modifier").addChild(mo);
834                 pn.addChild("type").addChild(type);
835                 pn.addChild("variables").addChild(var);
836                 pn.addChild("global");
837                 RESULT=pn;
838         :}
839         ;
840
841 variable_declarators ::=
842                 variable_declarator:vd {: 
843                 ParseNode pn=new ParseNode("variable_declarators_list");
844                 pn.addChild(vd);
845                 RESULT=pn;
846         :}
847         |       variable_declarators:vds COMMA variable_declarator:vd {:
848                 vds.addChild(vd);
849                 RESULT=vds;
850         :}
851         ;
852 variable_declarator ::=
853                 variable_declarator_id:id {:
854                 ParseNode pn=new ParseNode("variable_declarator");
855                 pn.addChild(id);
856                 RESULT=pn;
857         :}
858         |       variable_declarator_id:id EQ variable_initializer:init {: 
859                 ParseNode pn=new ParseNode("variable_declarator");
860                 pn.addChild(id);
861                 pn.addChild("initializer").addChild(init);
862                 RESULT=pn;
863         :}
864         ;
865 variable_declarator_id ::=
866                 IDENTIFIER:id {: 
867                 RESULT=(new ParseNode("single")).addChild(id).getRoot();:}
868         |       variable_declarator_id:id LBRACK RBRACK {:
869                 RESULT=(new ParseNode("array")).addChild(id).getRoot();:}
870         ;
871 variable_initializer ::=
872                 expression:exp {: RESULT=exp; :}
873         |       array_initializer {: RESULT=new ParseNode("array_initializer"); :}
874         ;
875
876 // 19.8.3) Method Declarations
877 method_declaration ::=
878                 method_header:header method_body:body {:
879                 ParseNode pn=new ParseNode("method_declaration");
880                 pn.addChild(header);
881                 pn.addChild("body").addChild(body);
882                 RESULT=pn;
883         :}
884         ;
885 method_header ::=
886                 modifiers_opt:mo type:type method_declarator:decl //throws_opt 
887         {:
888                 ParseNode pn=new ParseNode("method_header");
889                 pn.addChild("modifiers").addChild(mo);
890                 pn.addChild("returntype").addChild(type);
891                 pn.addChild(decl);
892                 RESULT=pn;
893         :}
894         |       modifiers_opt:mo VOID method_declarator:decl //throws_opt
895         {:
896                 ParseNode pn=new ParseNode("method_header");
897                 pn.addChild("modifiers").addChild(mo);
898                 pn.addChild(decl);
899                 RESULT=pn;
900         :}
901         ;
902 method_declarator ::=
903                 IDENTIFIER:id LPAREN formal_parameter_list_opt:params RPAREN {: 
904                 ParseNode pn=new ParseNode("method_declarator");
905                 pn.addChild("name").addChild(id);
906                 pn.addChild("parameters").addChild(params);
907                 RESULT=pn;
908         :}
909 //      |       method_declarator LBRACK RBRACK // deprecated
910 // be careful; the above production also allows 'void foo() []'
911         ;
912 formal_parameter_list_opt ::=
913         {: RESULT=new ParseNode("empty"); :}
914         |       formal_parameter_list:fpl {: 
915                 RESULT=fpl;
916         :}
917         ;
918 formal_parameter_list ::=
919                 formal_parameter:fp {: 
920                 ParseNode pn=new ParseNode("formal_parameter_list");
921                 pn.addChild(fp);
922                 RESULT=pn;
923         :}
924         |       formal_parameter_list:fpl COMMA formal_parameter:fp {: 
925                 fpl.addChild(fp);
926                 RESULT=fpl;
927         :}
928         ;
929 formal_parameter ::=
930                 type:type variable_declarator_id:name {:
931                 ParseNode pn=new ParseNode("formal_parameter");
932                 pn.addChild(type);
933                 pn.addChild(name);
934                 RESULT=pn;
935         :}
936         |
937                 TAG variable_declarator_id:name {:
938                 ParseNode pn=new ParseNode("tag_parameter");
939                 pn.addChild(name);
940                 RESULT=pn;
941         :}
942         |       FINAL type:type variable_declarator_id:name {:
943                 ParseNode pn=new ParseNode("formal_parameter");
944                 pn.addChild(type);
945                 pn.addChild(name);
946                 RESULT=pn;
947         :}
948         ;
949 //throws_opt ::=        
950 //      |       throws
951 //      ;
952 //throws ::=    THROWS class_type_list
953 //      ;
954 //class_type_list ::=
955 //              class_type
956 //      |       class_type_list COMMA class_type
957 //      ;
958 method_body ::= block:block {: 
959                 RESULT=block;
960         :}
961         |       SEMICOLON       {: RESULT=new ParseNode("empty"); :}
962         ;
963
964 // 19.8.4) Static Initializers
965 //static_initializer ::=
966 //              STATIC block
967 //      ;
968
969 // 19.8.5) Constructor Declarations
970 constructor_declaration ::=
971                 modifiers_opt:mo constructor_declarator:cd
972 //throws_opt 
973                         constructor_body:body   {:
974                 ParseNode pn=new ParseNode("constructor_declaration");
975                 pn.addChild("modifiers").addChild(mo);
976                 pn.addChild(cd);
977                 pn.addChild("body").addChild(body);
978                 RESULT=pn;
979         :} |
980                 modifiers_opt:mo GLOBAL constructor_declarator:cd
981 //throws_opt 
982                         constructor_body:body   {:
983                 ParseNode pn=new ParseNode("constructor_declaration");
984                 pn.addChild("global");
985                 pn.addChild("modifiers").addChild(mo);
986                 pn.addChild(cd);
987                 pn.addChild("body").addChild(body);
988                 RESULT=pn;
989         :}
990         ;
991 constructor_declarator ::=
992                 simple_name:name LPAREN formal_parameter_list_opt:fplo RPAREN {: 
993                 ParseNode pn=new ParseNode("constructor_declarator");
994                 pn.addChild(name);
995                 pn.addChild("parameters").addChild(fplo);
996                 RESULT=pn;
997         :}
998         ;
999 constructor_body ::=
1000                 LBRACE explicit_constructor_invocation:eci block_statements:bs RBRACE {: 
1001                         ParseNode pn=new ParseNode("constructor_body");
1002                         pn.addChild(eci);
1003                         pn.addChild(bs);
1004                         RESULT=pn;
1005         :} |
1006                 LBRACE explicit_constructor_invocation:eci RBRACE {: 
1007                         ParseNode pn=new ParseNode("constructor_body");
1008                         pn.addChild(eci);
1009                         RESULT=pn;
1010         :} |
1011                 LBRACE block_statements:block RBRACE {: 
1012                 ParseNode pn=new ParseNode("constructor_body");
1013                 pn.addChild(block);
1014                 RESULT=pn;
1015         :}
1016         |       LBRACE RBRACE {: RESULT=new ParseNode("empty"); :}
1017         ;
1018 explicit_constructor_invocation ::=
1019 //              THIS LPAREN argument_list_opt RPAREN SEMICOLON
1020 //      |       
1021 SUPER LPAREN argument_list_opt:alo RPAREN SEMICOLON {: 
1022         ParseNode pn=new ParseNode("superinvoke");
1023         pn.addChild(alo);
1024         RESULT=pn;
1025 :}
1026 //      |       primary DOT THIS LPAREN argument_list_opt RPAREN SEMICOLON
1027 //      |       primary DOT SUPER LPAREN argument_list_opt RPAREN SEMICOLON
1028         ;
1029
1030 // 19.9) Interfaces
1031
1032 // 19.9.1) Interface Declarations
1033 //interface_declaration ::=
1034 //               modifiers_opt INTERFACE IDENTIFIER extends_interfaces_opt
1035 //                       interface_body
1036 //       ;
1037 //extends_interfaces_opt ::=
1038 //       |       extends_interfaces
1039 //       ;
1040 //extends_interfaces ::=
1041 //               EXTENDS interface_type
1042 //       |       extends_interfaces COMMA interface_type
1043 //       ;
1044 //interface_body ::=
1045 //               LBRACE interface_member_declarations_opt RBRACE
1046 //       ;
1047 //interface_member_declarations_opt ::=
1048 //       |       interface_member_declarations
1049 //       ;
1050 //interface_member_declarations ::=
1051 //               interface_member_declaration
1052 //       |       interface_member_declarations interface_member_declaration
1053 //       ;
1054 //interface_member_declaration ::=
1055 //               constant_declaration
1056 //       |       abstract_method_declaration
1057 //       |       class_declaration
1058 //       |       interface_declaration
1059 //       |       SEMICOLON
1060 //       ;
1061 //constant_declaration ::=
1062 //               field_declaration
1063 //       // need to semantically check that modifiers of field declaration
1064 //       // include only PUBLIC, STATIC, or FINAL.  Other modifiers are
1065 //       // disallowed.
1066 //       ;
1067 //abstract_method_declaration ::=
1068 //               method_header SEMICOLON
1069 //       ;
1070
1071
1072 // 19.10) Arrays
1073 array_initializer ::=
1074                 LBRACE variable_initializers:var_init_list COMMA RBRACE {:
1075                        RESULT=var_init_list;
1076                 :}
1077         |       LBRACE variable_initializers:var_init_list RBRACE {:
1078                        RESULT=var_init_list;
1079                 :}
1080         |       LBRACE COMMA RBRACE {:
1081                        RESULT=new ParseNode("empty");                  
1082                 :}
1083         |       LBRACE RBRACE {:
1084                        RESULT=new ParseNode("empty");
1085                 :}
1086         ;
1087 variable_initializers ::=
1088                 variable_initializer:var_init {:
1089                        ParseNode pn=new ParseNode("var_init_list");
1090                        pn.addChild(var_init);
1091                        RESULT=pn;
1092                 :}
1093         |       variable_initializers:var_init_list COMMA variable_initializer:var_init {:
1094                        var_init_list.addChild(var_init);
1095                        RESULT=var_init_list;
1096                 :}
1097         ;
1098
1099 // 19.11) Blocks and Statements
1100 block ::=       LBRACE block_statements_opt:bso RBRACE {: 
1101         RESULT=bso;
1102         :}
1103         ;
1104 block_statements_opt ::=
1105         {: RESULT=new ParseNode("empty"); :}
1106         |       block_statements:bs {: 
1107         RESULT=bs;
1108         :}
1109         ;
1110 block_statements ::=
1111                 block_statement:bs {:
1112         ParseNode pn=new ParseNode("block_statement_list");
1113         pn.addChild(bs);
1114         RESULT=pn;
1115         :}
1116         |       block_statements:bss block_statement:bs {: 
1117         bss.addChild(bs);
1118         RESULT=bss;
1119         :}
1120         ;
1121 block_statement ::=
1122         tag_variable_declaration_statement:tvds {:
1123                 RESULT=tvds;
1124         :}              
1125         |       local_variable_declaration_statement:lvds {: 
1126                 RESULT=lvds;
1127         :}
1128         |       statement:statement {: 
1129                 RESULT=statement;
1130         :}
1131 //      |       class_declaration
1132 //      |       interface_declaration
1133         ;
1134 tag_variable_declaration_statement ::=
1135                 TAG IDENTIFIER:id EQ NEW TAG LPAREN IDENTIFIER:type RPAREN SEMICOLON {: 
1136                 ParseNode pn=new ParseNode("tag_declaration");
1137                 pn.addChild("single").addChild(id);
1138                 pn.addChild("type").addChild(type);
1139                 RESULT=pn;
1140         :}
1141         ;
1142 local_variable_declaration_statement ::=
1143                 local_variable_declaration:lvd SEMICOLON {: 
1144                 RESULT=lvd;
1145         :}
1146         ;
1147 local_variable_declaration ::=
1148                 type:type variable_declarators:var {: 
1149                 ParseNode pn=new ParseNode("local_variable_declaration");
1150                 pn.addChild(type);
1151                 pn.addChild(var);
1152                 RESULT=pn;
1153         :}
1154         |       FINAL type:type variable_declarators:var {: 
1155                 ParseNode pn=new ParseNode("local_variable_declaration");
1156                 pn.addChild(type);
1157                 pn.addChild(var);
1158                 RESULT=pn;
1159         :}
1160         ;
1161 statement ::=   statement_without_trailing_substatement:st {: 
1162                 RESULT=st;
1163         :}
1164 //      |       labeled_statement:st {: RESULT=st; :}
1165         |       if_then_statement:st {: RESULT=st; :}
1166         |       if_then_else_statement:st {: RESULT=st; :}
1167         |       while_statement:st {: RESULT=st; :}
1168         |       for_statement:st {: RESULT=st; :}
1169         ;
1170 statement_no_short_if ::=
1171                 statement_without_trailing_substatement:st {: RESULT=st; :}
1172 //      |       labeled_statement_no_short_if:st {: RESULT=st; :}
1173         |       if_then_else_statement_no_short_if:st {: RESULT=st; :}
1174         |       while_statement_no_short_if:st {: RESULT=st; :}
1175         |       for_statement_no_short_if:st {: RESULT=st; :}
1176         ;
1177 statement_without_trailing_substatement ::=
1178                 block:st {: RESULT=st; :}
1179         |       empty_statement:st {: RESULT=st; :}
1180         |       expression_statement:st {: RESULT=st; :}
1181 //      |       switch_statement
1182         |       do_statement:dos {:RESULT=dos; :}
1183         |       break_statement:st {: RESULT=st; :}
1184         |       continue_statement:st {: RESULT=st; :}
1185         |       return_statement:st {: RESULT=st; :}
1186         |       task_exitstatement:st {: RESULT=st; :}
1187         |       atomic_statement:st {: RESULT=st; :}
1188         |       sese_statement:st {: RESULT=st; :}
1189 //      |       synchronized_statement
1190 //      |       throw_statement
1191 //      |       try_statement
1192 //      |       assert_statement
1193         ;
1194 empty_statement ::=
1195                 SEMICOLON {: RESULT=new ParseNode("nop"); :}
1196         ;
1197 //labeled_statement ::=
1198 //              IDENTIFIER COLON statement
1199 //      ;
1200 //labeled_statement_no_short_if ::=
1201 //              IDENTIFIER COLON statement_no_short_if
1202 //      ;
1203 expression_statement ::=
1204                 statement_expression:se SEMICOLON {: 
1205                 ParseNode pn=new ParseNode("expression");
1206                 pn.addChild(se);
1207                 RESULT=pn; :}
1208         ;
1209 statement_expression ::=
1210                 assignment:st {: RESULT=st; :}
1211         |       preincrement_expression:st {: RESULT=st; :}
1212         |       predecrement_expression:st {: RESULT=st; :}
1213         |       postincrement_expression:st {: RESULT=st; :}
1214         |       postdecrement_expression:st {: RESULT=st; :}
1215         |       method_invocation:st {: RESULT=st; :}
1216         |       class_instance_creation_expression:st {: RESULT=st; :}
1217         ;
1218 if_then_statement ::=
1219                 IF LPAREN expression:exp RPAREN statement:st {: 
1220                 ParseNode pn=new ParseNode("ifstatement");
1221                 pn.addChild("condition").addChild(exp);
1222                 pn.addChild("statement").addChild(st);
1223                 RESULT=pn;
1224         :}
1225         ;
1226 if_then_else_statement ::=
1227                 IF LPAREN expression:exp RPAREN statement_no_short_if:st
1228                         ELSE statement:else_st {:
1229                 ParseNode pn=new ParseNode("ifstatement");
1230                 pn.addChild("condition").addChild(exp);
1231                 pn.addChild("statement").addChild(st);
1232                 pn.addChild("else_statement").addChild(else_st);
1233                 RESULT=pn;
1234         :}
1235         ;
1236 if_then_else_statement_no_short_if ::=
1237                 IF LPAREN expression:exp RPAREN statement_no_short_if:st
1238                         ELSE statement_no_short_if:else_st {:
1239                 ParseNode pn=new ParseNode("ifstatement");
1240                 pn.addChild("condition").addChild(exp);
1241                 pn.addChild("statement").addChild(st);
1242                 pn.addChild("else_statement").addChild(else_st);
1243                 RESULT=pn;
1244         :}
1245         ;
1246 //switch_statement ::=
1247 //              SWITCH LPAREN expression RPAREN switch_block
1248 //      ;
1249 //switch_block ::=
1250 //              LBRACE switch_block_statement_groups switch_labels RBRACE
1251 //      |       LBRACE switch_block_statement_groups RBRACE
1252 //      |       LBRACE switch_labels RBRACE
1253 //      |       LBRACE RBRACE
1254 //      ;
1255 //switch_block_statement_groups ::=
1256 //              switch_block_statement_group
1257 //      |       switch_block_statement_groups switch_block_statement_group
1258 //      ;
1259 //switch_block_statement_group ::=
1260 //              switch_labels block_statements
1261 //      ;
1262 //switch_labels ::=
1263 //              switch_label
1264 //      |       switch_labels switch_label
1265 //      ;
1266 //switch_label ::=
1267 //              CASE constant_expression COLON
1268 //      |       DEFAULT COLON
1269 //      ;
1270
1271 while_statement ::=
1272                 WHILE LPAREN expression:exp RPAREN statement:st {: 
1273                 ParseNode pn=new ParseNode("whilestatement");
1274                 pn.addChild("condition").addChild(exp);
1275                 pn.addChild("statement").addChild(st);
1276                 RESULT=pn;
1277         :}
1278         ;
1279 while_statement_no_short_if ::=
1280                 WHILE LPAREN expression:exp RPAREN statement_no_short_if:st {:
1281                 ParseNode pn=new ParseNode("whilestatement");
1282                 pn.addChild("condition").addChild(exp);
1283                 pn.addChild("statement").addChild(st);
1284                 RESULT=pn;
1285                 :}
1286         ;
1287 do_statement ::=
1288                 DO statement:st WHILE LPAREN expression:exp RPAREN SEMICOLON {: 
1289                 ParseNode pn=new ParseNode("dowhilestatement");
1290                 pn.addChild("condition").addChild(exp);
1291                 pn.addChild("statement").addChild(st);
1292                 RESULT=pn;
1293         :}
1294         ;
1295 for_statement ::=
1296                 FOR LPAREN for_init_opt:init SEMICOLON expression_opt:exp SEMICOLON
1297                         for_update_opt:update RPAREN statement:st {: 
1298                 ParseNode pn=new ParseNode("forstatement");
1299                 pn.addChild("initializer").addChild(init);
1300                 pn.addChild("condition").addChild(exp);
1301                 pn.addChild("update").addChild(update);
1302                 pn.addChild("statement").addChild(st);
1303                 RESULT=pn;
1304                 :}
1305         ;
1306 for_statement_no_short_if ::=
1307                 FOR LPAREN for_init_opt:init SEMICOLON expression_opt:exp SEMICOLON
1308                         for_update_opt:update RPAREN statement_no_short_if:st {:
1309                 ParseNode pn=new ParseNode("forstatement");
1310                 pn.addChild("initializer").addChild(init);
1311                 pn.addChild("condition").addChild(exp);
1312                 pn.addChild("update").addChild(update);
1313                 pn.addChild("statement").addChild(st);
1314                 RESULT=pn;
1315                 :}
1316         ;
1317 for_init_opt ::=
1318         {: RESULT=new ParseNode("empty"); :}
1319         |       for_init:init {: RESULT=init; :}
1320         ;
1321 for_init ::=    statement_expression_list:list {: RESULT=list; :}
1322         |       local_variable_declaration:decl {: RESULT=decl; :}
1323         ;
1324 for_update_opt ::=
1325         {: RESULT=new ParseNode("empty"); :}
1326         |       for_update:update {: RESULT=update; :}
1327         ;
1328 for_update ::=  statement_expression_list:list {: RESULT=list; :}
1329         ;
1330 statement_expression_list ::=
1331                 statement_expression:expr {: 
1332                 RESULT=(new ParseNode("statement_expression_list")).addChild(expr).getRoot();
1333         :}
1334         |       statement_expression_list:list COMMA statement_expression:expr {: 
1335                 list.addChild(expr);
1336                 RESULT=list;
1337         :}
1338         ;
1339
1340 //identifier_opt ::= 
1341 //      |       IDENTIFIER
1342 //      ;
1343
1344 break_statement ::=
1345                 BREAK
1346 //identifier_opt 
1347 SEMICOLON {: RESULT=new ParseNode("break"); :}
1348         ;
1349
1350 continue_statement ::=
1351                 CONTINUE  
1352 //identifier_opt 
1353 SEMICOLON
1354 {: RESULT=new ParseNode("continue"); :}
1355         ;
1356 return_statement ::=
1357                 RETURN expression_opt:exp SEMICOLON {: 
1358         RESULT=(new ParseNode("return")).addChild(exp).getRoot(); :}
1359         ;
1360 //throw_statement ::=
1361 //              THROW expression SEMICOLON
1362 //      ;
1363 //synchronized_statement ::=
1364 //              SYNCHRONIZED LPAREN expression RPAREN block
1365 //      ;
1366 atomic_statement ::=
1367                 ATOMIC block:blk {: 
1368         RESULT=(new ParseNode("atomic")).addChild(blk).getRoot();
1369         :}
1370         ;
1371 sese_statement ::=
1372
1373 //             SESE variable_declarator_id:id LBRACE statement:st RBRACE {: 
1374
1375                SESE block:blk {: 
1376                ParseNode pn = new ParseNode("sese");
1377
1378 //             pn.addChild("identifier").addChild(id);
1379
1380                pn.addChild("body").addChild(blk);
1381                RESULT=pn;
1382         :}
1383         ;
1384 //try_statement ::=
1385 //              TRY block catches
1386 //      |       TRY block catches_opt finally
1387 //      ;
1388 //catches_opt ::=
1389 //      |       catches
1390 //      ;
1391 //catches ::=   catch_clause
1392 //      |       catches catch_clause
1393 //      ;
1394 //catch_clause ::=
1395 //              CATCH LPAREN formal_parameter RPAREN block
1396 //      ;
1397 //finally ::=   FINALLY block
1398 //      ;
1399 //assert_statement ::=
1400 //              ASSERT expression SEMICOLON
1401 //      |       ASSERT expression COLON expression SEMICOLON
1402 //      ;
1403
1404 // 19.12) Expressions
1405 primary ::=     primary_no_new_array:st {: 
1406                 RESULT=st; :}
1407 //      |       array_creation_init:st {: 
1408 //              RESULT=st;
1409 //      :}
1410         |       array_creation_uninit:st {:
1411                 RESULT=st;
1412         :}
1413         ;
1414 primary_no_new_array ::=
1415                 literal:lit {: RESULT=lit; :}
1416         |       THIS {: RESULT=new ParseNode("this"); :}
1417         |       LPAREN expression:exp RPAREN {: RESULT=exp; :}
1418         |       class_instance_creation_expression:exp {: RESULT=exp; :}
1419         |       field_access:exp {: RESULT=exp; :}
1420         |       method_invocation:exp {: RESULT=exp; :}
1421         |       array_access:exp {: RESULT=exp; :}
1422         |       ISAVAILABLE LPAREN IDENTIFIER:id RPAREN {: 
1423                 ParseNode pn=new ParseNode("isavailable");
1424                 pn.addChild(id);
1425                 RESULT=pn;
1426         :}
1427 //      |       primitive_type DOT CLASS
1428 //      |       VOID DOT CLASS
1429 //      |       array_type DOT CLASS
1430 //      |       name DOT CLASS
1431 //      |       name DOT THIS
1432         ;
1433 class_instance_creation_expression ::=
1434                 NEW class_or_interface_type:type LPAREN argument_list_opt:args RPAREN flag_list_opt:feo {: 
1435                 ParseNode pn=new ParseNode("createobject");
1436                 pn.addChild(type);
1437                 pn.addChild(args);
1438                 pn.addChild(feo);
1439                 RESULT=pn;
1440         :} 
1441         //Global object
1442         | GLOBAL NEW class_or_interface_type:type LPAREN argument_list_opt:args RPAREN flag_list_opt:feo {: 
1443                 ParseNode pn=new ParseNode("createobject");
1444                 pn.addChild(type);
1445                 pn.addChild(args);
1446                 pn.addChild(feo);
1447                 pn.addChild("global");
1448                 RESULT=pn;
1449         :}
1450         // Objects we want to track in disjointness analysis
1451         | DISJOINT IDENTIFIER:id NEW class_or_interface_type:type LPAREN argument_list_opt:args RPAREN flag_list_opt:feo {: 
1452                 ParseNode pn=new ParseNode("createobject");
1453                 pn.addChild(type);
1454                 pn.addChild(args);
1455                 pn.addChild(feo);
1456                 pn.addChild("disjoint").addChild(id);
1457                 RESULT=pn;
1458         :}
1459         | NEW class_or_interface_type:type LPAREN argument_list_opt:args RPAREN LBRACE RBRACE LBRACE tag_list:tl RBRACE {: 
1460                 ParseNode pn=new ParseNode("createobject");
1461                 pn.addChild(type);
1462                 pn.addChild(args);
1463                 pn.addChild(tl);
1464                 RESULT=pn;
1465         :}
1466         | NEW class_or_interface_type:type LPAREN argument_list_opt:args RPAREN LBRACE flag_list:fl RBRACE LBRACE tag_list:tl RBRACE {: 
1467                 ParseNode pn=new ParseNode("createobject");
1468                 pn.addChild(type);
1469                 pn.addChild(args);
1470                 pn.addChild(fl);
1471                 pn.addChild(tl);
1472                 RESULT=pn;
1473         :}
1474
1475 //      |       NEW class_or_interface_type LPAREN argument_list_opt RPAREN class_body
1476 //      |       primary DOT NEW IDENTIFIER
1477 //                      LPAREN argument_list_opt RPAREN {: 
1478 //              
1479 //      :}
1480 //      |       primary DOT NEW IDENTIFIER
1481 //                      LPAREN argument_list_opt RPAREN class_body
1482 //      |       name DOT NEW IDENTIFIER
1483 //                      LPAREN argument_list_opt RPAREN
1484 //      |       name DOT NEW IDENTIFIER
1485 //                      LPAREN argument_list_opt RPAREN class_body
1486         ;
1487 cons_argument_list_opt ::=
1488         {: RESULT=new ParseNode("empty"); :}
1489         |       cons_argument_list:args {: RESULT=args; :}
1490         ;
1491
1492 cons_argument_list ::=
1493                 IDENTIFIER:id COLON expression:exp {:
1494                 ParseNode pn=new ParseNode("cons_argument_list");
1495                 ParseNode pnarg=pn.addChild("binding");
1496                 pnarg.addChild("var").addChild(id);
1497                 pnarg.addChild("exp").addChild(exp);
1498                 RESULT=pn;
1499         :}
1500         |       argument_list:list COMMA IDENTIFIER:id COLON expression:exp {:
1501                 ParseNode pnarg=new ParseNode("binding");
1502                 pnarg.addChild("var").addChild(id);
1503                 pnarg.addChild("exp").addChild(exp);
1504                 list.addChild(pnarg);
1505                 RESULT=list;
1506         :}
1507         ;
1508
1509 argument_list_opt ::=
1510         {: RESULT=new ParseNode("empty"); :}
1511         |       argument_list:args {: RESULT=args; :}
1512         ;
1513
1514 argument_list ::=
1515                 expression:exp {:
1516                 ParseNode pn=new ParseNode("argument_list");
1517                 pn.addChild(exp);
1518                 RESULT=pn;
1519         :}
1520         |       argument_list:list COMMA expression:exp {:
1521                 list.addChild(exp);
1522                 RESULT=list;
1523         :}
1524         ;
1525 array_creation_uninit ::=
1526                 NEW primitive_type:type dim_exprs:dimexpr dims_opt:dims {: 
1527                 ParseNode pn=new ParseNode("createarray");
1528                 pn.addChild(type);
1529                 pn.addChild(dimexpr);
1530                 pn.addChild("dims_opt").setLiteral(dims);
1531                 RESULT=pn;
1532                 :}
1533         |       NEW class_or_interface_type:type dim_exprs:dimexpr dims_opt:dims {: 
1534                 ParseNode pn=new ParseNode("createarray");
1535                 pn.addChild(type);
1536                 pn.addChild(dimexpr);
1537                 pn.addChild("dims_opt").setLiteral(dims);
1538                 RESULT=pn;
1539         :}
1540         |       GLOBAL NEW primitive_type:type dim_exprs:dimexpr dims_opt:dims {: 
1541                 ParseNode pn=new ParseNode("createarray");
1542                 pn.addChild(type);
1543                 pn.addChild(dimexpr);
1544                 pn.addChild("dims_opt").setLiteral(dims);
1545                 pn.addChild("global");
1546                 RESULT=pn;
1547                 :}
1548         |       DISJOINT IDENTIFIER:id NEW primitive_type:type dim_exprs:dimexpr dims_opt:dims {: 
1549                 ParseNode pn=new ParseNode("createarray");
1550                 pn.addChild(type);
1551                 pn.addChild(dimexpr);
1552                 pn.addChild("dims_opt").setLiteral(dims);
1553                 pn.addChild("disjoint").addChild(id);
1554                 RESULT=pn;
1555                 :}
1556         |       GLOBAL NEW class_or_interface_type:type dim_exprs:dimexpr dims_opt:dims {: 
1557                 ParseNode pn=new ParseNode("createarray");
1558                 pn.addChild(type);
1559                 pn.addChild(dimexpr);
1560                 pn.addChild("dims_opt").setLiteral(dims);
1561                 pn.addChild("global");
1562                 RESULT=pn;
1563                 :}
1564         |       DISJOINT IDENTIFIER:id NEW class_or_interface_type:type dim_exprs:dimexpr dims_opt:dims {: 
1565                 ParseNode pn=new ParseNode("createarray");
1566                 pn.addChild(type);
1567                 pn.addChild(dimexpr);
1568                 pn.addChild("dims_opt").setLiteral(dims);
1569                 pn.addChild("disjoint").addChild(id);           
1570                 RESULT=pn;
1571                 :}
1572         ;
1573 //array_creation_init ::=
1574 //              NEW primitive_type dims array_initializer
1575 //      |       NEW class_or_interface_type dims array_initializer
1576 //      ;
1577 dim_exprs ::=   dim_expr:exp {: 
1578                 ParseNode pn=new ParseNode("dim_exprs");
1579                 pn.addChild(exp);
1580                 RESULT=pn; :}
1581         |       dim_exprs:base dim_expr:exp {: 
1582                 base.addChild(exp);
1583                 RESULT=base;
1584         :}
1585         ;
1586 dim_expr ::=    LBRACK expression:exp RBRACK {: RESULT=exp; :}
1587         ;
1588 dims_opt ::= {: RESULT=new Integer(0); :}
1589         |       dims:dims {: RESULT = dims; :}
1590         ;
1591
1592 dims ::=        LBRACK RBRACK {: RESULT=new Integer(1); :}
1593         |       dims:dims LBRACK RBRACK {: RESULT=new Integer(dims.intValue()+1); :}
1594         ;
1595
1596 field_access ::=
1597                 primary:base DOT IDENTIFIER:id {: 
1598                 ParseNode pn=new ParseNode("fieldaccess");
1599                 pn.addChild("base").addChild(base);
1600                 pn.addChild("field").addChild(id);
1601                 RESULT=pn;
1602 :}
1603 //      |       SUPER DOT IDENTIFIER
1604 //      |       name DOT SUPER DOT IDENTIFIER
1605         ;
1606 method_invocation ::=
1607                 name:name LPAREN argument_list_opt:args RPAREN {: 
1608                 ParseNode pn=new ParseNode("methodinvoke1");
1609                 pn.addChild(name);
1610                 pn.addChild(args);
1611                 RESULT=pn;
1612         :}
1613         |       primary:base DOT IDENTIFIER:name LPAREN argument_list_opt:args RPAREN {: 
1614                 ParseNode pn=new ParseNode("methodinvoke2");
1615                 pn.addChild("base").addChild(base);
1616                 pn.addChild("id").addChild(name);
1617                 pn.addChild(args);
1618                 RESULT=pn;
1619         :}
1620         |       SUPER DOT IDENTIFIER:id LPAREN argument_list_opt:args RPAREN {: 
1621                 ParseNode name=new ParseNode("name");
1622                 name.addChild("base").addChild("name").addChild("identifier").addChild("super");
1623                 name.addChild("identifier").addChild(id);
1624                 ParseNode pn=new ParseNode("methodinvoke1");
1625                 pn.addChild(name);
1626                 pn.addChild(args);
1627                 RESULT=pn;
1628         :}
1629 //      |       name DOT SUPER DOT IDENTIFIER LPAREN argument_list_opt RPAREN
1630         ;
1631 array_access ::=
1632                 name:name LBRACK expression:exp RBRACK {: 
1633                 ParseNode pn=new ParseNode("arrayaccess");
1634                 pn.addChild("base").addChild(name);
1635                 pn.addChild("index").addChild(exp);
1636                 RESULT=pn;
1637         :}
1638         |       primary_no_new_array:base LBRACK expression:exp RBRACK {: 
1639                 ParseNode pn=new ParseNode("arrayaccess");
1640                 pn.addChild("base").addChild(base);
1641                 pn.addChild("index").addChild(exp);
1642                 RESULT=pn;
1643         :}
1644 //      |       array_creation_init:init LBRACK expression:exp RBRACK {: 
1645 //              ParseNode pn=new ParseNode("arrayaccess");
1646 //              pn.addChild("init").addChild(init);
1647 //              pn.addChild("index").addChild(exp);
1648 //              RESULT=pn;
1649 //      :}
1650         ;
1651
1652 postfix_expression ::=
1653                 primary:exp {: 
1654         RESULT=exp; :}
1655         |       name:exp {: RESULT=exp; :}
1656         |       postincrement_expression:exp {: RESULT=exp; :}
1657         |       postdecrement_expression:exp {: RESULT=exp; :}
1658         ;
1659 postincrement_expression ::=
1660                 postfix_expression:exp PLUSPLUS 
1661                 {: RESULT=(new ParseNode("postinc")).addChild(exp).getRoot(); :}
1662         ;
1663 postdecrement_expression ::=
1664                 postfix_expression:exp MINUSMINUS
1665                 {: RESULT=(new ParseNode("postdec")).addChild(exp).getRoot(); :}
1666         ;
1667 unary_expression ::=
1668                 preincrement_expression:exp {: RESULT=exp; :}
1669         |       predecrement_expression:exp {: RESULT=exp; :}
1670         |       PLUS unary_expression:exp 
1671         {: RESULT=(new ParseNode("unaryplus")).addChild(exp).getRoot(); :}
1672         |       MINUS unary_expression:exp
1673         {: RESULT=(new ParseNode("unaryminus")).addChild(exp).getRoot(); :}
1674         |       unary_expression_not_plus_minus:exp {: 
1675                         RESULT=exp; :}
1676         ;
1677 preincrement_expression ::=
1678                 PLUSPLUS unary_expression:exp
1679                 {: RESULT=(new ParseNode("preinc")).addChild(exp).getRoot(); :}
1680         ;
1681 predecrement_expression ::=
1682                 MINUSMINUS unary_expression:exp
1683                 {: RESULT=(new ParseNode("predec")).addChild(exp).getRoot(); :}
1684         ;
1685 unary_expression_not_plus_minus ::=
1686                 postfix_expression:exp {: 
1687                 RESULT=exp; :}
1688         |       COMP unary_expression:exp
1689                 {: RESULT=(new ParseNode("comp")).addChild(exp).getRoot(); :}
1690         |       NOT unary_expression:exp 
1691                 {: RESULT=(new ParseNode("not")).addChild(exp).getRoot(); :}
1692         |       cast_expression:exp {: RESULT=exp; :}
1693         ;
1694 cast_expression ::=
1695                 LPAREN primitive_type:type
1696         //dims_opt 
1697                 RPAREN unary_expression:exp {: 
1698                 ParseNode pn=new ParseNode("cast1");
1699                 pn.addChild("type").addChild(type);
1700                 pn.addChild("exp").addChild(exp);
1701                 RESULT=pn;
1702         :}
1703         |       LPAREN expression:type RPAREN unary_expression_not_plus_minus:exp {: 
1704                 ParseNode pn=new ParseNode("cast2");
1705                 pn.addChild("type").addChild(type);
1706                 pn.addChild("exp").addChild(exp);
1707                 RESULT=pn;
1708
1709         :}
1710 //      |       LPAREN name dims RPAREN unary_expression_not_plus_minus
1711         ;
1712 multiplicative_expression ::=
1713                 unary_expression:exp {: 
1714                         RESULT=exp; :}
1715         |       multiplicative_expression:exp1 MULT unary_expression:exp2 {: 
1716                 ParseNode pn=new ParseNode("mult");
1717                 pn.addChild(exp1);
1718                 pn.addChild(exp2);
1719                 RESULT=pn;
1720         :}
1721         |       multiplicative_expression:exp1 DIV unary_expression:exp2 {:
1722                 ParseNode pn=new ParseNode("div");
1723                 pn.addChild(exp1);
1724                 pn.addChild(exp2);
1725                 RESULT=pn;
1726         :}
1727         |       multiplicative_expression:exp1 MOD unary_expression:exp2 {:
1728                 ParseNode pn=new ParseNode("mod");
1729                 pn.addChild(exp1);
1730                 pn.addChild(exp2);
1731                 RESULT=pn;
1732         :}
1733         ;
1734 additive_expression ::=
1735                 multiplicative_expression:exp {: 
1736                         RESULT=exp; :}
1737         |       additive_expression:exp1 PLUS multiplicative_expression:exp2 {: 
1738                 ParseNode pn=new ParseNode("add");
1739                 pn.addChild(exp1);
1740                 pn.addChild(exp2);
1741                 RESULT=pn;
1742         :}
1743         |       additive_expression:exp1 MINUS multiplicative_expression:exp2 {: 
1744                 ParseNode pn=new ParseNode("sub");
1745                 pn.addChild(exp1);
1746                 pn.addChild(exp2);
1747                 RESULT=pn;
1748         :}
1749         ;
1750 shift_expression ::=
1751                 additive_expression:exp {: 
1752                         RESULT=exp; :}
1753         |       shift_expression:exp1 LSHIFT additive_expression:exp2 {: 
1754                 ParseNode pn=new ParseNode("leftshift");
1755                 pn.addChild(exp1);
1756                 pn.addChild(exp2);
1757                 RESULT=pn;
1758         :}
1759         |       shift_expression:exp1 RSHIFT additive_expression:exp2 {: 
1760                 ParseNode pn=new ParseNode("rightshift");
1761                 pn.addChild(exp1);
1762                 pn.addChild(exp2);
1763                 RESULT=pn;
1764         :}
1765         |       shift_expression:exp1 URSHIFT additive_expression:exp2 {:
1766                 ParseNode pn=new ParseNode("urightshift");
1767                 pn.addChild(exp1);      
1768                 pn.addChild(exp2);      
1769                 RESULT=pn;
1770         :}
1771         ;
1772 relational_expression ::=
1773                 shift_expression:exp {: 
1774                         RESULT=exp; :}
1775         |       relational_expression:exp1 LT shift_expression:exp2 {:
1776                 ParseNode pn=new ParseNode("comp_lt");
1777                 pn.addChild(exp1);
1778                 pn.addChild(exp2);
1779                 RESULT=pn;
1780         :}
1781         |       relational_expression:exp1 GT shift_expression:exp2 {:
1782                 ParseNode pn=new ParseNode("comp_gt");
1783                 pn.addChild(exp1);
1784                 pn.addChild(exp2);
1785                 RESULT=pn;
1786         :}
1787         |       relational_expression:exp1 LTEQ shift_expression:exp2 {:
1788                 ParseNode pn=new ParseNode("comp_lte");
1789                 pn.addChild(exp1);
1790                 pn.addChild(exp2);
1791                 RESULT=pn;
1792         :}
1793         |       relational_expression:exp1 GTEQ shift_expression:exp2 {:
1794                 ParseNode pn=new ParseNode("comp_gte");
1795                 pn.addChild(exp1);
1796                 pn.addChild(exp2);
1797                 RESULT=pn;
1798         :}
1799         |       relational_expression:exp INSTANCEOF reference_type:type {: 
1800                 ParseNode pn=new ParseNode("instanceof");
1801                 pn.addChild("exp").addChild(exp);
1802                 pn.addChild(type);
1803                 RESULT=pn;
1804         :}
1805         ;
1806
1807 equality_expression ::=
1808                 relational_expression:exp {: 
1809                         RESULT=exp; :}
1810         |       equality_expression:exp1 EQEQ relational_expression:exp2 {: 
1811                 ParseNode pn=new ParseNode("equal");
1812                 pn.addChild(exp1);
1813                 pn.addChild(exp2);
1814                 RESULT=pn;
1815         :}
1816         |       equality_expression:exp1 NOTEQ relational_expression:exp2 {: 
1817                 ParseNode pn=new ParseNode("not_equal");
1818                 pn.addChild(exp1);
1819                 pn.addChild(exp2);
1820                 RESULT=pn;
1821         :}
1822         ;
1823 and_expression ::=
1824                 equality_expression:exp {: 
1825                 RESULT=exp; :}
1826         |       and_expression:exp1 AND equality_expression:exp2 {: 
1827                 ParseNode pn=new ParseNode("bitwise_and");
1828                 pn.addChild(exp1);
1829                 pn.addChild(exp2);
1830                 RESULT=pn;
1831         :}
1832         ;
1833 exclusive_or_expression ::=
1834                 and_expression:expr {: 
1835                         RESULT=expr;
1836                 :}
1837         |       exclusive_or_expression:exp1 XOR and_expression:exp2 {: 
1838                 ParseNode pn=new ParseNode("bitwise_xor");
1839                 pn.addChild(exp1);
1840                 pn.addChild(exp2);
1841                 RESULT=pn;
1842 :}
1843         ;
1844 inclusive_or_expression ::=
1845                 exclusive_or_expression:exclor {: 
1846                         RESULT=exclor; :}
1847         |       inclusive_or_expression:exp1 OR exclusive_or_expression:exp2 {: 
1848                 ParseNode pn=new ParseNode("bitwise_or");
1849                 pn.addChild(exp1);
1850                 pn.addChild(exp2);
1851                 RESULT=pn;
1852         :}
1853         ;
1854 conditional_and_expression ::=
1855                 inclusive_or_expression:inclor {: 
1856                         RESULT=inclor; :}
1857         |       conditional_and_expression:exp1 ANDAND inclusive_or_expression:exp2 {:
1858                 ParseNode pn=new ParseNode("logical_and");
1859                 pn.addChild(exp1);
1860                 pn.addChild(exp2);
1861                 RESULT=pn;
1862         :}
1863         ;
1864 conditional_or_expression ::=
1865                 conditional_and_expression:condand {: 
1866                         RESULT=condand; :}
1867         |       conditional_or_expression:exp1 OROR conditional_and_expression:exp2 {: 
1868                 ParseNode pn=new ParseNode("logical_or");
1869                 pn.addChild(exp1);
1870                 pn.addChild(exp2);
1871                 RESULT=pn;
1872         :}
1873         ;
1874 conditional_expression ::=
1875                 conditional_or_expression:condor {: 
1876                         RESULT=condor; :}
1877         |       conditional_or_expression:condor QUESTION expression:exptrue
1878                         COLON conditional_expression:expfalse {: 
1879                         ParseNode pn=new ParseNode("tert");
1880                         pn.addChild("cond").addChild(condor);
1881                         pn.addChild("trueexpr").addChild(exptrue);
1882                         pn.addChild("falseexpr").addChild(expfalse);
1883                         RESULT=pn;
1884                         :}
1885         ;
1886 getoffset_expression ::=
1887         GETOFFSET LBRACE class_or_interface_type:type COMMA IDENTIFIER:id RBRACE {:
1888         ParseNode pn = new ParseNode("getoffset");
1889         pn.addChild(type);
1890         pn.addChild("field").addChild(id);
1891         RESULT = pn;
1892       :}
1893    ;
1894  
1895 assignment_expression ::=
1896                 conditional_expression:expr {: 
1897                         RESULT=expr; :} |
1898                 assignment:assign {: 
1899                         RESULT=assign; :}             |
1900         getoffset_expression:expr {:
1901             RESULT=expr; :}
1902         ;
1903 // semantic check necessary here to ensure a valid left-hand side.
1904 // allowing a parenthesized variable here on the lhs was introduced in
1905 // JLS 2; thanks to Eric Blake for pointing this out.
1906 assignment ::=  postfix_expression:lvalue assignment_operator:op assignment_expression:rvalue {:
1907                 ParseNode pn=new ParseNode("assignment");
1908                 pn.addChild("op").addChild(op);
1909                 ParseNode pnargs=pn.addChild("args");
1910                 pnargs.addChild(lvalue);
1911                 pnargs.addChild(rvalue);
1912                 RESULT=pn;
1913          :}
1914         ;
1915 assignment_operator ::=
1916                 EQ {: RESULT=new ParseNode("eq"); :}
1917         |       MULTEQ {: RESULT=new ParseNode("multeq"); :}
1918         |       DIVEQ {: RESULT=new ParseNode("diveq"); :}
1919         |       MODEQ {: RESULT=new ParseNode("modeq"); :}
1920         |       PLUSEQ {: RESULT=new ParseNode("pluseq"); :}
1921         |       MINUSEQ {: RESULT=new ParseNode("minuseq"); :}
1922         |       LSHIFTEQ {: RESULT=new ParseNode("lshifteq"); :}
1923         |       RSHIFTEQ {: RESULT=new ParseNode("rshifteq"); :}
1924         |       URSHIFTEQ {: RESULT=new ParseNode("urshifteq"); :}
1925         |       ANDEQ {: RESULT=new ParseNode("andeq"); :}
1926         |       XOREQ {: RESULT=new ParseNode("xoreq"); :}
1927         |       OREQ {: RESULT=new ParseNode("oreq"); :}
1928         ;
1929 expression_opt ::=
1930         {:      RESULT=new ParseNode("empty"); :}
1931         |       expression:exp {: 
1932                 RESULT=exp; :}
1933         ;
1934 expression ::=  assignment_expression:exp {: 
1935                 RESULT=exp; :}
1936         ;
1937 //constant_expression ::=
1938 //              expression
1939 //      ;