starting towards taints
[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 terminal AT;           // support annotations
89 terminal LOCDEF;          // declaration of location hierarchy
90
91 terminal java.lang.Number INTEGER_LITERAL;
92 terminal java.lang.Number FLOATING_POINT_LITERAL;
93 terminal java.lang.Boolean BOOLEAN_LITERAL;
94 terminal java.lang.Character CHARACTER_LITERAL;
95 terminal java.lang.String STRING_LITERAL;
96 terminal NULL_LITERAL;
97
98 // Reserved but unused:
99 terminal CONST, GOTO;
100 // strictfp keyword, new in Java 1.2
101 terminal STRICTFP;
102 // assert keyword, new in Java 1.4
103 terminal ASSERT; // assert_statement
104 // lexer compatibility with Java 1.5
105 terminal ELLIPSIS;
106 terminal ENUM;
107
108 // added for disjoint reachability analysis
109 terminal GENREACH;
110
111
112 // 19.2) The Syntactic Grammar
113 non terminal ParseNode goal;
114 // 19.3) Lexical Structure
115 non terminal ParseNode literal;
116 // 19.4) Types, Values, and Variables
117 non terminal ParseNode type, primitive_type, numeric_type;
118 non terminal ParseNode integral_type, floating_point_type;
119 non terminal ParseNode reference_type;
120 non terminal ParseNode class_or_interface_type;
121 non terminal ParseNode class_type;
122 non terminal ParseNode interface_type;
123 non terminal ParseNode array_type;
124 // 19.5) Names
125 non terminal ParseNode name, simple_name, qualified_name;
126 // 19.6) Packages
127 non terminal ParseNode compilation_unit;
128 non terminal ParseNode package_declaration_opt, package_declaration;
129 non terminal ParseNode import_declarations_opt, import_declarations;
130 non terminal ParseNode type_declarations_opt, type_declarations;
131 non terminal ParseNode import_declaration;
132 non terminal ParseNode single_type_import_declaration;
133 non terminal ParseNode type_import_on_demand_declaration;
134 non terminal ParseNode type_declaration;
135 // 19.7) Productions used only in the LALR(1) grammar
136 non terminal ParseNode modifiers_opt, modifiers, modifiers_at, modifier;
137 non terminal ParseNode mixed_modifiers, mixed_modifiers_at;
138 // 19.8.1) Class Declaration
139 non terminal ParseNode class_declaration, super, super_opt;
140 non terminal ParseNode interfaces, interfaces_opt, interface_type_list;
141 non terminal ParseNode class_body;
142 non terminal ParseNode class_body_declarations, class_body_declarations_opt;
143 non terminal ParseNode class_body_declaration, class_member_declaration;
144 // 19.8.2) Field Declarations
145 non terminal ParseNode field_declaration, variable_declarators, variable_declarator;
146 non terminal ParseNode variable_declarator_id;
147 non terminal ParseNode variable_initializer;
148 // 19.8.3) Method Declarations
149 non terminal ParseNode method_declaration, method_header, method_declarator;
150 non terminal ParseNode formal_parameter_list_opt, formal_parameter_list;
151 non terminal ParseNode formal_parameter;
152 non terminal ParseNode throws_opt;
153 non terminal ParseNode throws;
154 non terminal ParseNode class_type_list;
155 non terminal ParseNode method_body;
156 // 19.8.4) Static Initializers
157 non terminal ParseNode static_initializer;
158 // 19.8.5) Constructor Declarations
159 non terminal ParseNode constructor_declaration, constructor_declarator;
160 non terminal ParseNode constructor_body;
161 non terminal ParseNode explicit_constructor_invocation;
162 // 19.8.6) Location Hierarchy Declarations
163 non terminal ParseNode location_order_declaration, location_order_list, location_order;
164 // 19.9.1) Interface Declarations
165 non terminal ParseNode interface_declaration;
166 non terminal normal_interface_declaration, annotation_type_declaration;
167 non terminal ParseNode extends_interfaces_opt, extends_interfaces;
168 non terminal ParseNode interface_body;
169 non terminal ParseNode interface_member_declarations_opt, interface_member_declarations;
170 non terminal ParseNode interface_member_declaration, constant_declaration;
171 non terminal ParseNode abstract_method_declaration;
172 // 19.10) Arrays
173 non terminal ParseNode array_initializer;
174 non terminal ParseNode variable_initializers;
175 // 19.11) Blocks and Statements
176 non terminal ParseNode block;
177 non terminal ParseNode block_statements_opt, block_statements, block_statement;
178 non terminal ParseNode local_variable_declaration_statement, local_variable_declaration;
179 non terminal ParseNode statement, statement_no_short_if;
180 non terminal ParseNode statement_without_trailing_substatement;
181 non terminal ParseNode empty_statement;
182 //non terminal ParseNode labeled_statement, labeled_statement_no_short_if;
183 non terminal ParseNode expression_statement, statement_expression;
184 non terminal ParseNode if_then_statement;
185 non terminal ParseNode if_then_else_statement, if_then_else_statement_no_short_if;
186 non terminal ParseNode switch_statement, switch_block;
187 non terminal ParseNode switch_block_statement_groups;
188 non terminal ParseNode switch_block_statement_group;
189 non terminal ParseNode switch_labels, switch_label;
190 non terminal ParseNode while_statement, while_statement_no_short_if;
191 non terminal ParseNode do_statement;
192 non terminal ParseNode for_statement, for_statement_no_short_if;
193 non terminal ParseNode for_init_opt, for_init;
194 non terminal ParseNode for_update_opt, for_update;
195 non terminal ParseNode statement_expression_list;
196 //non terminal ParseNode identifier_opt;
197 non terminal ParseNode break_statement, continue_statement;
198 non terminal ParseNode return_statement;
199 non terminal ParseNode throw_statement;
200 non terminal ParseNode synchronized_statement;
201 non terminal ParseNode try_statement;
202 non terminal ParseNode catches_opt;
203 non terminal ParseNode catches, catch_clause;
204 non terminal ParseNode finally;
205 //non terminal ParseNode assert_statement;
206 non terminal ParseNode genreach_statement;
207 // 19.12) Expressions
208 non terminal ParseNode primary, primary_no_new_array;
209 non terminal ParseNode class_instance_creation_expression;
210 non terminal ParseNode cons_argument_list_opt, cons_argument_list;
211 non terminal ParseNode argument_list_opt, argument_list;
212 non terminal ParseNode array_creation_init;
213 non terminal ParseNode array_creation_uninit;
214 non terminal ParseNode dim_exprs, dim_expr;
215 non terminal Integer dims_opt, dims;
216 non terminal ParseNode field_access, method_invocation;
217 non terminal ParseNode array_access;
218 non terminal ParseNode postfix_expression;
219 non terminal ParseNode postincrement_expression, postdecrement_expression;
220 non terminal ParseNode unary_expression, unary_expression_not_plus_minus;
221 non terminal ParseNode preincrement_expression, predecrement_expression;
222 non terminal ParseNode cast_expression;
223 non terminal ParseNode multiplicative_expression, additive_expression;
224 non terminal ParseNode shift_expression, relational_expression, equality_expression;
225 non terminal ParseNode and_expression, exclusive_or_expression, inclusive_or_expression;
226 non terminal ParseNode conditional_and_expression, conditional_or_expression;
227 non terminal ParseNode conditional_expression;
228 non terminal ParseNode assignment_expression;
229 non terminal ParseNode assignment;
230 non terminal ParseNode assignment_operator;
231 non terminal ParseNode expression_opt, expression;
232 non terminal ParseNode constant_expression;
233 //failure aware computation keywords
234 terminal FLAG;
235 terminal OPTIONAL;
236 terminal ISAVAILABLE;
237 terminal EXTERNAL;
238 terminal TAG;
239 terminal TASK;
240 terminal TASKEXIT;
241 non terminal ParseNode flag_declaration;
242 non terminal ParseNode task_declaration;
243 non terminal ParseNode task_parameter_list;
244 non terminal ParseNode task_parameter;
245 non terminal ParseNode flag_expression;
246 non terminal ParseNode flag_andexpression;
247 non terminal ParseNode flag_notexpression;
248 non terminal ParseNode task_exitstatement;
249 non terminal ParseNode flag_effects_opt;
250 non terminal ParseNode flag_effects;
251 non terminal ParseNode flag_effect;
252 non terminal ParseNode flag_list;
253 non terminal ParseNode flag_list_opt;
254 non terminal ParseNode flag_change;
255
256 non terminal ParseNode cons_checks_opt;
257 non terminal ParseNode cons_checks;
258 non terminal ParseNode cons_check;
259
260 non terminal ParseNode tag_variable_declaration_statement;
261 non terminal ParseNode tag_expression_list;
262 non terminal ParseNode tag_expression;
263 non terminal ParseNode tag_list;
264 non terminal ParseNode tag_list_opt;
265 non terminal ParseNode tag_change;
266
267 //distributed transaction keywords
268 terminal ATOMIC;
269 terminal GLOBAL;
270 terminal SCRATCH;
271 terminal GETOFFSET;
272 non terminal ParseNode atomic_statement;
273 non terminal ParseNode getoffset_expression;
274
275 //disjointness for Java
276 terminal DISJOINT;
277
278 //coarse-grain parallelization
279 terminal SESE;
280 terminal RBLOCK;
281 non terminal ParseNode sese_statement;
282
283 // mgc
284 // JSR-201) Enum Declaration
285 non terminal ParseNode enum_declaration;
286 non terminal ParseNode enum_body, enum_constants_opt, enum_constants, enum_constant;
287 //non terminal ParseNode enum_arguments_opt, enum_body_declarations_opt;
288
289 // annotation expressions
290 non terminal ParseNode annotations_opt, annotations, annotations_at, annotation, annotation_body;
291 non terminal ParseNode normal_annotation_body, marker_annotation_body;
292 non terminal ParseNode single_element_annotation_body;
293 non terminal ParseNode annotation_type_body, annotation_type_element_declarations;
294 non terminal ParseNode annotation_type_element_declarations_opt;
295 non terminal ParseNode annotation_type_element_declaration, default_value_opt, default_value;
296 non terminal ParseNode element_value_pairs_opt, element_value_pairs, element_value_pair;
297 non terminal ParseNode element_values_opt, element_values, element_value, element_value_array_initializer;
298
299 start with goal;
300
301
302 // Task declarations
303 task_declaration ::= 
304         TASK IDENTIFIER:id LPAREN task_parameter_list:tpl RPAREN 
305         flag_effects_opt:feo
306         method_body:body 
307         {: 
308         ParseNode pn=new ParseNode("task_declaration");
309         pn.addChild("name").addChild(id);
310         pn.addChild(tpl);
311         pn.addChild(feo);
312         pn.addChild("body").addChild(body);     
313         RESULT=pn;
314         :};
315
316 task_parameter_list ::=
317                 task_parameter:fp {: 
318                 ParseNode pn=new ParseNode("task_parameter_list");
319                 pn.addChild(fp);
320                 RESULT=pn;
321         :}
322         |       task_parameter_list:fpl COMMA task_parameter:fp {: 
323                 fpl.addChild(fp);
324                 RESULT=fpl;
325         :}
326         ;
327
328 task_parameter ::=
329                 type:type variable_declarator_id:name LBRACE flag_expression:exp RBRACE {:
330                 ParseNode pn=new ParseNode("task_parameter");
331                 pn.addChild(type);
332                 pn.addChild(name);
333                 pn.addChild("flag").addChild(exp);
334                 RESULT=pn;
335         :} 
336         | type:type variable_declarator_id:name LBRACE flag_expression:exp RBRACE LBRACE tag_expression_list:texp RBRACE {:
337                 ParseNode pn=new ParseNode("task_parameter");
338                 pn.addChild(type);
339                 pn.addChild(name);
340                 pn.addChild("flag").addChild(exp);
341                 pn.addChild("tag").addChild(texp);
342                 RESULT=pn;
343         :}
344         | type:type variable_declarator_id:name LBRACE RBRACE LBRACE tag_expression_list:texp RBRACE {:
345                 ParseNode pn=new ParseNode("task_parameter");
346                 pn.addChild(type);
347                 pn.addChild(name);
348                 pn.addChild("tag").addChild(texp);
349                 RESULT=pn;
350         :}
351         | OPTIONAL task_parameter:fp {:
352                 ParseNode pn=new ParseNode("task_parameter");
353                 pn.addChild("optional").addChild(fp);
354                 RESULT=pn;
355         :}              
356         
357         ;
358
359 tag_expression_list ::= tag_expression:te {: 
360         ParseNode pn=new ParseNode("tag_expression_list");
361         pn.addChild(te);
362         RESULT=pn;
363         :}
364         | tag_expression_list:tel COMMA tag_expression:te {: 
365         tel.addChild(te);
366         RESULT=tel;
367         :}
368         ;
369
370 tag_expression ::= IDENTIFIER:type IDENTIFIER:id {: 
371                 ParseNode pn=new ParseNode("tag_expression");
372                 pn.addChild("type").addChild(type);
373                 pn.addChild("single").addChild(id);
374                 RESULT=pn;
375         :}
376         ;
377
378 tag_list_opt ::= LBRACE tag_list:fl RBRACE {:RESULT=fl;:}
379         | LBRACE RBRACE {: RESULT = new ParseNode("empty"); :}  
380         | {: RESULT = new ParseNode("empty"); :}
381         ;
382
383 tag_list ::= tag_change:fc {: 
384                 ParseNode pn=new ParseNode("tag_list");
385                 pn.addChild(fc);
386                 RESULT=pn;
387         :}
388         | tag_list:fl COMMA tag_change:fc {: 
389                 fl.addChild(fc);
390                 RESULT=fl;
391         :};
392
393 tag_change ::= IDENTIFIER:id {: 
394                 RESULT=new ParseNode("name").addChild(id).getRoot();
395         :}
396         | NOT IDENTIFIER:id {: 
397                 RESULT=new ParseNode("not").addChild("name").addChild(id).getRoot();
398         :};
399
400 flag_expression ::= 
401         flag_andexpression:exp {: 
402                 RESULT=exp;
403         :}
404         | flag_expression:exp1 OROR flag_andexpression:exp2 {: 
405                 ParseNode pn=new ParseNode("or");
406                 pn.addChild(exp1);
407                 pn.addChild(exp2);
408                 RESULT=pn;
409         :}
410         ;
411
412 flag_andexpression ::= 
413         flag_notexpression:exp {: RESULT=exp; :}
414         | flag_notexpression:exp1 ANDAND flag_andexpression:exp2 {: 
415                 ParseNode pn=new ParseNode("and");
416                 pn.addChild(exp1);
417                 pn.addChild(exp2);
418                 RESULT=pn;
419         :}
420         ;
421
422 flag_notexpression ::=
423         NOT flag_notexpression:exp {: 
424                 ParseNode pn=new ParseNode("not");
425                 pn.addChild(exp);
426                 RESULT=pn;
427         :}
428         | LPAREN flag_expression:exp RPAREN {: 
429                 RESULT=exp;
430         :}
431         | IDENTIFIER:id {:
432                 ParseNode pn=new ParseNode("name");
433                 pn.addChild(id);
434                 RESULT=pn;
435         :}
436         ;
437
438 task_exitstatement ::= TASKEXIT flag_effects_opt:opt cons_checks_opt:cco SEMICOLON {: 
439                 RESULT=(new ParseNode("taskexit")).addChild(opt).getRoot().addChild(cco).getRoot();
440         :};
441
442 cons_checks_opt ::= ASSERT LPAREN cons_checks:cc RPAREN {: RESULT=cc; :}
443         | {: RESULT = new ParseNode("empty"); :}
444         ;
445
446 cons_checks ::= cons_check:cc {: 
447                 ParseNode pn=new ParseNode("cons_checks");
448                 pn.addChild(cc);
449                 RESULT=pn;
450         :}
451         |       cons_checks:ccs COMMA cons_check:cc {: 
452                 ccs.addChild(cc);
453                 RESULT=ccs;
454         :};
455
456 cons_check ::=  IDENTIFIER:name LPAREN cons_argument_list_opt:args RPAREN {: 
457                 ParseNode pn=new ParseNode("cons_check");
458                 pn.addChild("name").addChild("identifier").addChild(name);
459                 pn.addChild(args);
460                 RESULT=pn;
461         :};
462
463 flag_effects_opt ::= LPAREN flag_effects:fe RPAREN {:RESULT=fe;:}
464         | {: RESULT = new ParseNode("empty"); :}
465         ;
466
467 flag_effects ::= flag_effect:fe {: 
468                 ParseNode pn=new ParseNode("flag_effects_list");
469                 pn.addChild(fe);
470                 RESULT=pn;
471         :}
472         |       flag_effects:fes COMMA flag_effect:fe {: 
473                 fes.addChild(fe);
474                 RESULT=fes;
475         :};
476
477 flag_effect ::= IDENTIFIER:id LBRACE flag_list:fl RBRACE tag_list_opt:tlo {: 
478                 ParseNode pn=new ParseNode("flag_effect");
479                 pn.addChild("name").addChild(id);
480                 pn.addChild(fl);
481                 pn.addChild(tlo);
482                 RESULT=pn;
483         :}
484         | IDENTIFIER:id LBRACE RBRACE LBRACE tag_list:tl RBRACE {: 
485                 ParseNode pn=new ParseNode("flag_effect");
486                 pn.addChild("name").addChild(id);
487                 pn.addChild(tl);
488                 RESULT=pn;
489         :};
490
491 flag_list_opt ::= LBRACE flag_list:fl RBRACE {:RESULT=fl;:}
492         | LBRACE RBRACE {: RESULT = new ParseNode("empty"); :}  
493         | 
494         {: RESULT = new ParseNode("empty"); :}
495         ;
496
497 flag_list ::= flag_change:fc {: 
498                 ParseNode pn=new ParseNode("flag_list");
499                 pn.addChild(fc);
500                 RESULT=pn;
501         :}
502         |       flag_list:fl COMMA flag_change:fc {: 
503                 fl.addChild(fc);
504                 RESULT=fl;
505         :};
506
507 flag_change ::= IDENTIFIER:id {: 
508                 RESULT=new ParseNode("name").addChild(id).getRoot();
509         :} |
510         NOT IDENTIFIER:id {: 
511                 RESULT=new ParseNode("not").addChild("name").addChild(id).getRoot();
512         :};
513
514 // 19.2) The Syntactic Grammar
515 goal ::=        compilation_unit:cu
516         {:
517         RESULT = cu;
518         :}
519         ;
520
521 // 19.3) Lexical Structure.
522
523
524 literal ::=     INTEGER_LITERAL:integer_lit
525         {:
526                 ParseNode pn=new ParseNode("literal");
527                 pn.addChild("integer").setLiteral(integer_lit);
528                 RESULT=pn;
529         :}
530         |       FLOATING_POINT_LITERAL:float_lit
531         {:
532                 ParseNode pn=new ParseNode("literal");
533                 pn.addChild("float").setLiteral(float_lit);
534                 RESULT=pn;
535         :}
536         |       BOOLEAN_LITERAL:boolean_lit
537         {:
538                 ParseNode pn=new ParseNode("literal");
539                 pn.addChild("boolean").setLiteral(boolean_lit);
540                 RESULT=pn;
541         :}
542         |       CHARACTER_LITERAL:char_lit
543         {:
544                 ParseNode pn=new ParseNode("literal");
545                 pn.addChild("char").setLiteral(char_lit);
546                 RESULT=pn;
547         :}
548         |       STRING_LITERAL:string_lit
549         {:
550                 ParseNode pn=new ParseNode("literal");
551                 pn.addChild("string").setLiteral(string_lit);
552                 RESULT=pn;
553         :}
554         |       NULL_LITERAL 
555         {:
556                 RESULT=(new ParseNode("literal")).addChild("null").getRoot();
557         :}
558         ;
559
560 // 19.4) Types, Values, and Variables
561 type    ::=     primitive_type:type {: RESULT=type; :}
562         |       reference_type:type {: RESULT=type; :}
563         ;
564
565 primitive_type ::=
566                 numeric_type:type {: RESULT=type; :}
567         |       BOOLEAN {: RESULT=(new ParseNode("type")).addChild("boolean").getRoot(); :}
568         ;
569 numeric_type::= integral_type:type {: RESULT=type; :}
570         |       floating_point_type:type {: RESULT=type; :}
571         ;
572 integral_type ::= 
573                 BYTE {: RESULT=(new ParseNode("type")).addChild("byte").getRoot(); :}
574         |       SHORT  {: RESULT=(new ParseNode("type")).addChild("short").getRoot(); :}
575         |       INT  {: RESULT=(new ParseNode("type")).addChild("int").getRoot(); :}
576         |       LONG  {: RESULT=(new ParseNode("type")).addChild("long").getRoot(); :}
577         |       CHAR  {: RESULT=(new ParseNode("type")).addChild("char").getRoot(); :}
578         ;
579 floating_point_type ::= 
580                 FLOAT  {: RESULT=(new ParseNode("type")).addChild("float").getRoot(); :}
581         |       DOUBLE  {: RESULT=(new ParseNode("type")).addChild("double").getRoot(); :}
582         ;
583
584 reference_type ::=
585                 class_or_interface_type:type {: RESULT=type; :}
586         |       array_type:type {: RESULT=type; :}
587         ;
588 class_or_interface_type ::= name:name {: 
589         RESULT=(new ParseNode("type")).addChild("class").addChild(name).getRoot(); 
590         :};
591
592 class_type ::=  class_or_interface_type:type {: RESULT=type; :};
593 interface_type ::= class_or_interface_type:type {: RESULT=type; :};
594
595 array_type ::=  primitive_type:prim dims:dims {: 
596                 ParseNode pn=(new ParseNode("type")).addChild("array");
597                 pn.addChild("basetype").addChild(prim);
598                 pn.addChild("dims").setLiteral(dims);
599                 RESULT=pn.getRoot();
600         :}
601         |       name:name dims:dims {: 
602                 ParseNode pn=(new ParseNode("type")).addChild("array");
603                 pn.addChild("basetype").addChild("type").addChild("class").addChild(name);
604                 pn.addChild("dims").setLiteral(dims);
605                 RESULT=pn.getRoot();
606         :}
607         ;
608
609 // 19.5) Names
610 name    ::=     simple_name:name {: RESULT=name; :}
611         |       qualified_name:name {: RESULT=name; :}
612         ;
613 simple_name ::= IDENTIFIER:id {: 
614         RESULT=(new ParseNode("name")).addChild("identifier").addChild(id).getRoot(); 
615         :}
616         ;
617 qualified_name ::= name:name DOT IDENTIFIER:id {: 
618         ParseNode pn=new ParseNode("name");
619         pn.addChild("base").addChild(name);
620         pn.addChild("identifier").addChild(id);
621         RESULT=pn;
622         :}
623         ;
624
625 // 19.6) Packages
626 compilation_unit ::=
627                 package_declaration_opt:pdo
628                 import_declarations_opt:ido
629                 type_declarations_opt:tdo {: 
630                 ParseNode pn=new ParseNode("compilation_unit");
631                 pn.addChild(tdo);
632                 pn.addChild("packages").addChild(pdo);
633                 pn.addChild("imports").addChild(ido);
634                 RESULT=pn;
635                 :}
636                 ;
637 package_declaration_opt ::= package_declaration:pdo {:
638                 RESULT=pdo;
639         :} |
640         {: RESULT=new ParseNode("empty"); :}
641 ;
642
643 import_declarations_opt ::= import_declarations:ido {: 
644                 RESULT=ido;
645         :} | 
646         {: RESULT=new ParseNode("empty"); :}
647 ;
648 type_declarations_opt   ::= type_declarations:tds {:
649                 RESULT=tds;
650                 :}   | 
651         {: RESULT=new ParseNode("empty"); :}
652         ;
653
654 import_declarations ::=
655                import_declaration:id {: 
656                 ParseNode pn=new ParseNode("import_decls_list");
657                 pn.addChild(id);
658                 RESULT=pn;
659         :}
660        |       import_declarations:ids import_declaration:id {: 
661                 ids.addChild(id);
662                 RESULT=ids;
663         :}
664        ;
665
666 type_declarations ::= 
667                 type_declaration:td {:
668                 ParseNode pn=new ParseNode("type_declaration_list");
669                 pn.addChild(td);
670                 RESULT=pn;
671                 :}
672         |       type_declarations:tds type_declaration:td {:
673                 tds.addChild(td);
674                 RESULT=tds;
675                 :}
676         ;
677
678 package_declaration ::=
679                 PACKAGE name:name SEMICOLON {: 
680         ParseNode pn=new ParseNode("package");
681         pn.addChild(name);
682         RESULT=pn;
683         :}
684        ;
685 import_declaration ::=
686                single_type_import_declaration:sid {: RESULT=sid; :}
687        |       type_import_on_demand_declaration:iod {: RESULT=iod; :}
688        ;
689 single_type_import_declaration ::=
690                IMPORT name:name SEMICOLON {: 
691         ParseNode pn=new ParseNode("import_single");
692         pn.addChild(name);
693         RESULT=pn;
694 :}
695        ;
696 type_import_on_demand_declaration ::=
697                IMPORT name:name DOT MULT SEMICOLON {:
698         ParseNode pn=new ParseNode("import_ondemand");
699         pn.addChild(name);
700         RESULT=pn;
701         :}       
702         ;
703
704 type_declaration ::=
705                 class_declaration:cd 
706                 {:
707                         RESULT=cd;
708                 :}
709         |       enum_declaration:ed
710             {:
711                 RESULT=ed;
712             :}
713         |       task_declaration:td 
714                 {:
715                         RESULT=td;
716                 :}
717     |   interface_declaration:in
718         {:
719                         RESULT=in;
720                 :}
721         |       SEMICOLON {: RESULT=new ParseNode("empty"); :}
722         ;
723
724 // 19.7) Productions used only in the LALR(1) grammar
725 modifiers_opt::=
726         {: RESULT=new ParseNode("empty"); :}
727         |       modifiers:mo {: 
728                 RESULT=mo;
729         :}
730         ;
731 modifiers_at ::=
732                 mixed_modifiers_at
733         |       annotations_at
734         ;
735 modifiers ::=   mixed_modifiers : mmo {:
736                 RESULT=mmo; 
737         :}
738         |       annotations : an {:
739                 ParseNode pn=new ParseNode("modifier_list");
740                 pn.addChild(an);
741                 RESULT=pn;
742         :}
743         ;
744 mixed_modifiers_at ::=
745                 mixed_modifiers : mmos AT {:
746                 RESULT=mmos;
747         :}
748         ;
749 mixed_modifiers ::=
750                 modifier : mo {:
751                 ParseNode pn=new ParseNode("modifier_list");
752                 pn.addChild(mo);
753                 RESULT=pn;
754         :}
755         |       annotations:as modifier:mo {:
756                 ParseNode pn=new ParseNode("modifier_list");
757                 pn.addChild(mo);
758                 pn.addChild(as);
759                 RESULT=pn;
760         :}
761         |       mixed_modifiers : mmos modifier : mo {:
762                 mmos.addChild(mo);
763                 RESULT=mmos;
764         :}
765         |       mixed_modifiers_at:mma annotation_body:ab {:
766                 mma.addChild("annotation_list").addChild(ab); 
767                 RESULT=mma;             
768         :}
769         ;
770 modifier ::=    
771         PUBLIC {: RESULT=new ParseNode("public"); :}|
772         PROTECTED {: RESULT=new ParseNode("protected"); :}|
773         PRIVATE {: RESULT=new ParseNode("private"); :}|
774         STATIC {: RESULT=new ParseNode("static"); :} |
775         ABSTRACT {: RESULT=new ParseNode("abstract"); :}  |
776         FINAL {: RESULT=new ParseNode("final"); :}|
777         NATIVE {: RESULT=new ParseNode("native"); :} |
778         SYNCHRONIZED {: RESULT=new ParseNode("synchronized"); :} |
779         ATOMIC {: RESULT=new ParseNode("atomic"); :} |
780         VOLATILE {: RESULT=new ParseNode("volatile"); :} |
781         TRANSIENT {: RESULT=new ParseNode("transient"); :} 
782
783 //      STRICTFP // note that semantic analysis must check that the
784                          // context of the modifier allows strictfp.
785         ;
786 //annotations_opt ::=
787 //      {: RESULT=new ParseNode("empty"); :}
788 //      |       annotations:an {: 
789 //              RESULT=an;
790 //      :}
791 //      ;
792 annotations ::= 
793                 AT annotation_body:ab {:
794                 ParseNode pn=new ParseNode("annotation_list");
795                 pn.addChild(ab);
796                 RESULT=pn;
797         :}
798         |       annotations_at:aat annotation_body:ab {:
799                 aat.addChild(ab);
800                 RESULT=aat;
801         :}
802         ;
803 annotations_at ::=
804                annotations:as AT {:
805                RESULT=as;
806         :}
807         ;
808 annotation ::=
809                AT annotation_body:ab {:
810                RESULT=ab;
811         :}
812         ;
813 annotation_body ::=
814                 normal_annotation_body:nab {:
815                 ParseNode pn=new ParseNode("annotation_body");
816                 pn.addChild(nab);
817                 RESULT = pn;
818         :}
819         |       marker_annotation_body:mab {:
820                 ParseNode pn=new ParseNode("annotation_body");
821                 pn.addChild(mab);
822                 RESULT = pn;
823         :}
824         |       single_element_annotation_body:seab {:
825                 ParseNode pn=new ParseNode("annotation_body");
826                 pn.addChild(seab);
827                 RESULT = pn;
828         :}
829         ;
830 normal_annotation_body ::=
831                 IDENTIFIER LPAREN element_value_pairs_opt RPAREN
832         ;
833 marker_annotation_body ::=
834                 IDENTIFIER:id
835         {:
836         ParseNode pn=new ParseNode("marker_annotation");
837         pn.addChild("name").addChild(id);
838         RESULT=pn;
839         :}
840         ;
841 single_element_annotation_body ::=
842                 IDENTIFIER:id LPAREN STRING_LITERAL:ev RPAREN {:
843                 ParseNode pn=new ParseNode("single_annotation");
844                 pn.addChild("name").addChild(id);
845                 pn.addChild("element_value").addChild(ev);
846                 RESULT=pn;
847         :}
848         ;
849 element_value_pairs_opt ::=
850         |       element_value_pairs
851         ;               
852 element_value_pairs ::=
853                 element_value_pair
854         |       element_value_pairs COMMA element_value_pair
855         ;
856 element_value_pair ::=
857                 IDENTIFIER EQ element_value
858         ;
859 element_value ::=
860                 annotation:an {:
861                 RESULT=an;
862         :}  
863         |       element_value_array_initializer:evai {: 
864                 RESULT=evai;
865         :}
866         |       conditional_expression:ce {:
867                 RESULT=ce;
868         :}
869         ;
870 element_value_array_initializer ::=
871                 LBRACE element_values_opt RBRACE
872         ;
873 element_values_opt ::=
874         |       element_values
875         ;
876 element_values ::=
877                 element_value
878         |       element_values COMMA element_value
879         ;
880 // 19.8) Classes
881
882 // 19.8.1) Class Declaration:
883 class_declaration ::= 
884         modifiers_opt:mo CLASS IDENTIFIER:id super_opt:so interfaces_opt:ifo 
885         class_body:body 
886         {:
887         ParseNode pn=new ParseNode("class_declaration");
888         pn.addChild("modifiers").addChild(mo);
889         pn.addChild("name").addChild(id);
890         pn.addChild("super").addChild(so);
891         pn.addChild("superIF").addChild(ifo);
892         pn.addChild("classbody").addChild(body);
893         RESULT=pn;
894         :}
895         ;
896 super ::=       EXTENDS class_type:classtype {: 
897                 RESULT=classtype;
898         :}
899         ;
900 super_opt ::=   
901         {: RESULT=new ParseNode("empty"); :}
902         |       super:su {: 
903                 RESULT=su;
904         :}
905         ;
906
907 interfaces ::= IMPLEMENTS interface_type_list:iftl {: RESULT=iftl; :}
908        ;
909 interfaces_opt ::=
910        {: RESULT=new ParseNode("empty"); :}
911        |       interfaces:ifs {: RESULT=ifs; :}
912        ;
913 interface_type_list ::=
914                interface_type:ift {: 
915                         ParseNode pn=new ParseNode("interface_type_list");
916                         pn.addChild(ift);
917                         RESULT=pn;
918                 :}
919        |       interface_type_list:iftl COMMA interface_type:ift {: 
920                         iftl.addChild(ift);
921                         RESULT=iftl;
922                 :}
923        ;
924
925 class_body ::=  LBRACE class_body_declarations_opt:cbdo RBRACE {: RESULT=cbdo; :}
926         ;
927
928 class_body_declarations_opt ::= 
929         {: RESULT=new ParseNode("empty"); :}
930         |       class_body_declarations:cbd {: RESULT=cbd; :};
931
932 class_body_declarations ::= 
933                 class_body_declaration:cbd {: 
934                         ParseNode pn=new ParseNode("class_body_declaration_list");
935                         pn.addChild(cbd);
936                         RESULT=pn;
937                 :}
938         |       class_body_declarations:cbds class_body_declaration:cbd {: 
939                         cbds.addChild(cbd);
940                         RESULT=cbds;
941                 :}
942         ;
943
944 class_body_declaration ::=
945                 class_member_declaration:member {: 
946                 RESULT=(new ParseNode("member")).addChild(member).getRoot();
947         :}
948         |       static_initializer:block{:
949                 RESULT=(new ParseNode("static_block")).addChild(block).getRoot();
950         :}
951         |       constructor_declaration:constructor {: 
952                 RESULT=(new ParseNode("constructor")).addChild(constructor).getRoot();
953         :}
954         |       block:block {:
955                 RESULT=(new ParseNode("block")).addChild(block).getRoot();
956         :}
957         |       location_order_declaration:lod {:
958                 RESULT=(new ParseNode("location_order_declaration")).addChild(lod).getRoot();
959         :}
960         ;
961 class_member_declaration ::=
962         //failure aware computation
963         flag_declaration:flag {: 
964         RESULT=(new ParseNode("flag")).addChild(flag).getRoot(); 
965         :}      
966         |
967         field_declaration:field {: 
968         RESULT=(new ParseNode("field")).addChild(field).getRoot(); 
969         :}
970         |       method_declaration:method {:
971         RESULT=(new ParseNode("method")).addChild(method).getRoot(); 
972         :}
973         /* repeat the prod for 'class_declaration' here: */
974         |       modifiers_opt:mo CLASS IDENTIFIER:id super_opt:so interfaces_opt:ifo class_body:body
975         {:
976         ParseNode pn=new ParseNode("inner_class_declaration");
977         pn.addChild("modifiers").addChild(mo);
978         pn.addChild("name").addChild(id);
979         pn.addChild("super").addChild(so);
980         pn.addChild("superIF").addChild(ifo);
981         pn.addChild("classbody").addChild(body);
982         RESULT=pn;
983         :}
984         |       enum_declaration:ed
985         {:
986         RESULT=ed; 
987         :}
988 //    |       interface_declaration:interfaced {: 
989 //      RESULT=(new ParseNode("interface")).addChild(interfaced).getRoot(); 
990 //      :}
991         |       SEMICOLON       {: RESULT=new ParseNode("empty"); :}
992         ;
993         
994 // mgc
995 // JSR-201) Enum Declaration
996 enum_declaration ::=
997                 modifiers_opt:mo ENUM IDENTIFIER:id /*interfaces_opt:io*/ enum_body:body
998                 {:
999                         ParseNode pn=new ParseNode("enum_declaration");
1000                         pn.addChild("modifiers").addChild(mo);
1001                         pn.addChild("name").addChild(id);
1002                         //pn.addChild("superIF").addChild(ifo);
1003                         pn.addChild("enumbody").addChild(body);
1004                         RESULT=pn;
1005                 :}
1006         ;
1007 enum_body ::=
1008                 LBRACE enum_constants_opt:eco /*enum_body_declarations_opt:ebdo*/ RBRACE
1009                 {: RESULT=eco; :}
1010         ;
1011 enum_constants_opt ::=
1012   {: RESULT=new ParseNode("empty"); :}
1013         |       enum_constants:ecs
1014         {: RESULT=ecs; :}
1015         ;
1016 enum_constants ::=
1017                 enum_constant:ec {: 
1018                 ParseNode pn=new ParseNode("enum_constants_list");
1019                 pn.addChild(ec);
1020                 RESULT=pn;
1021         :}
1022         |       enum_constants:ecs COMMA enum_constant:ec {:
1023             ecs.addChild(ec);
1024             RESULT=ecs;
1025         :}
1026         ;
1027 enum_constant ::=
1028                 IDENTIFIER:id /*enum_arguments_opt*/
1029                 {: 
1030                     ParseNode pn=new ParseNode("enum_constant");
1031                     pn.addChild("name").addChild(id);
1032                     RESULT=pn; 
1033                 :}
1034 //      |       IDENTIFIER enum_arguments_opt class_body
1035         ;
1036 //enum_arguments_opt ::=
1037 //      |       LPAREN argument_list_opt RPAREN
1038 //      ;
1039 //enum_body_declarations_opt ::=
1040 //      |       SEMICOLON class_body_declarations_opt:cbdo
1041 //      ;
1042
1043 //Failure aware computation
1044 flag_declaration ::= 
1045                 FLAG IDENTIFIER:id SEMICOLON {: 
1046                 ParseNode pn=new ParseNode("flag_declaration");
1047                 pn.addChild("name").addChild(id);
1048                 RESULT=pn;
1049         :}      |
1050                 EXTERNAL FLAG IDENTIFIER:id SEMICOLON {: 
1051                 ParseNode pn=new ParseNode("flag_declaration");
1052                 pn.addChild("name").addChild(id);
1053                 pn.addChild("external");
1054                 RESULT=pn;
1055         :}
1056         ;
1057
1058 // 19.8.2) Field Declarations
1059 field_declaration ::= 
1060                 modifiers_opt:mo type:type variable_declarators:var SEMICOLON {: 
1061                 ParseNode pn=new ParseNode("field_declaration");
1062                 pn.addChild("modifier").addChild(mo);
1063                 pn.addChild("type").addChild(type);
1064                 pn.addChild("variables").addChild(var);
1065                 RESULT=pn;
1066         :} |
1067                 modifiers_opt:mo GLOBAL type:type variable_declarators:var SEMICOLON {: 
1068                 ParseNode pn=new ParseNode("field_declaration");
1069                 pn.addChild("modifier").addChild(mo);
1070                 pn.addChild("type").addChild(type);
1071                 pn.addChild("variables").addChild(var);
1072                 pn.addChild("global");
1073                 RESULT=pn;
1074         :}
1075         ;
1076
1077 variable_declarators ::=
1078                 variable_declarator:vd {: 
1079                 ParseNode pn=new ParseNode("variable_declarators_list");
1080                 pn.addChild(vd);
1081                 RESULT=pn;
1082         :}
1083         |       variable_declarators:vds COMMA variable_declarator:vd {:
1084                 vds.addChild(vd);
1085                 RESULT=vds;
1086         :}
1087         ;
1088 variable_declarator ::=
1089                 variable_declarator_id:id {:
1090                 ParseNode pn=new ParseNode("variable_declarator");
1091                 pn.addChild(id);
1092                 RESULT=pn;
1093         :}
1094         |       variable_declarator_id:id EQ variable_initializer:init {: 
1095                 ParseNode pn=new ParseNode("variable_declarator");
1096                 pn.addChild(id);
1097                 pn.addChild("initializer").addChild(init);
1098                 RESULT=pn;
1099         :}
1100         ;
1101 variable_declarator_id ::=
1102                 IDENTIFIER:id {: 
1103                 RESULT=(new ParseNode("single")).addChild(id).getRoot();:}
1104         |       variable_declarator_id:id LBRACK RBRACK {:
1105                 RESULT=(new ParseNode("array")).addChild(id).getRoot();:}
1106         ;
1107 variable_initializer ::=
1108                 expression:exp {: RESULT=exp; :}
1109         |       array_initializer:ai {: RESULT=(new ParseNode("array_initializer")).addChild(ai).getRoot(); :}
1110         ;
1111
1112 // 19.8.3) Method Declarations
1113 method_declaration ::=
1114                 method_header:header method_body:body {:
1115                 ParseNode pn=new ParseNode("method_declaration");
1116                 pn.addChild(header);
1117                 pn.addChild("body").addChild(body);
1118                 RESULT=pn;
1119         :}
1120         ;
1121 method_header ::=
1122                 modifiers_opt:mo type:type method_declarator:decl throws_opt:to 
1123         {:
1124                 ParseNode pn=new ParseNode("method_header");
1125                 pn.addChild("modifiers").addChild(mo);
1126                 pn.addChild("returntype").addChild(type);
1127                 pn.addChild("throws").addChild(to);
1128                 pn.addChild(decl);
1129                 RESULT=pn;
1130         :}
1131         |       modifiers_opt:mo VOID method_declarator:decl throws_opt:to
1132         {:
1133                 ParseNode pn=new ParseNode("method_header");
1134                 pn.addChild("modifiers").addChild(mo);
1135                 pn.addChild("throws").addChild(to);
1136                 pn.addChild(decl);
1137                 RESULT=pn;
1138         :}
1139         ;
1140 method_declarator ::=
1141                 IDENTIFIER:id LPAREN formal_parameter_list_opt:params RPAREN {: 
1142                 ParseNode pn=new ParseNode("method_declarator");
1143                 pn.addChild("name").addChild(id);
1144                 pn.addChild("parameters").addChild(params);
1145                 RESULT=pn;
1146         :}
1147 //      |       method_declarator LBRACK RBRACK // deprecated
1148 // be careful; the above production also allows 'void foo() []'
1149         ;
1150 formal_parameter_list_opt ::=
1151         {: RESULT=new ParseNode("empty"); :}
1152         |       formal_parameter_list:fpl {: 
1153                 RESULT=fpl;
1154         :}
1155         ;
1156 formal_parameter_list ::=
1157                 formal_parameter:fp {: 
1158                 ParseNode pn=new ParseNode("formal_parameter_list");
1159                 pn.addChild(fp);
1160                 RESULT=pn;
1161         :}
1162         |       formal_parameter_list:fpl COMMA formal_parameter:fp {: 
1163                 fpl.addChild(fp);
1164                 RESULT=fpl;
1165         :}
1166         ;
1167 formal_parameter ::=
1168                 type:type variable_declarator_id:name {:
1169                 ParseNode pn=new ParseNode("formal_parameter");
1170                 pn.addChild(type);
1171                 pn.addChild(name);
1172                 RESULT=pn;
1173         :}
1174         |
1175                 TAG variable_declarator_id:name {:
1176                 ParseNode pn=new ParseNode("tag_parameter");
1177                 pn.addChild(name);
1178                 RESULT=pn;
1179         :}
1180         |       FINAL type:type variable_declarator_id:name {:
1181                 ParseNode pn=new ParseNode("formal_parameter");
1182                 pn.addChild(type);
1183                 pn.addChild(name);
1184                 RESULT=pn;
1185         :}
1186         ;
1187 throws_opt ::=  
1188         {: RESULT=new ParseNode("empty"); :}
1189         |       throws:trs
1190             {: RESULT=trs; :}
1191         ;
1192 throws ::=      THROWS class_type_list:ctl
1193         {: RESULT=(new ParseNode("throw_list")).addChild(ctl).getRoot(); :}
1194         ;
1195 class_type_list ::=
1196                 class_type:ct
1197                 {: 
1198                 ParseNode pn=new ParseNode("class_type_list");
1199                 pn.addChild(ct);
1200                 RESULT=pn; 
1201                 :}
1202         |       class_type_list:ctl COMMA class_type:ct
1203             {: 
1204             ctl.addChild(ct);
1205             RESULT=ctl; 
1206             :}
1207         ;
1208 method_body ::= block:block {: 
1209                 RESULT=block;
1210         :}
1211         |       SEMICOLON       {: RESULT=new ParseNode("empty"); :}
1212         ;
1213
1214 // 19.8.4) Static Initializers
1215 static_initializer ::=
1216                 STATIC block:body {:
1217                 ParseNode pn=new ParseNode("static_block_declaration");
1218                 pn.addChild("body").addChild(body);
1219                 RESULT=pn;
1220         :}
1221         ;
1222
1223 // 19.8.5) Constructor Declarations
1224 constructor_declaration ::=
1225                 modifiers_opt:mo constructor_declarator:cd throws_opt:to 
1226                         constructor_body:body   {:
1227                 ParseNode pn=new ParseNode("constructor_declaration");
1228                 pn.addChild("modifiers").addChild(mo);
1229                 pn.addChild("throws").addChild(to);
1230                 pn.addChild(cd);
1231                 pn.addChild("body").addChild(body);
1232                 RESULT=pn;
1233         :} |
1234                 modifiers_opt:mo GLOBAL constructor_declarator:cd throws_opt:to 
1235                         constructor_body:body   {:
1236                 ParseNode pn=new ParseNode("constructor_declaration");
1237                 pn.addChild("global");
1238                 pn.addChild("modifiers").addChild(mo);
1239                 pn.addChild("throws").addChild(to);
1240                 pn.addChild(cd);
1241                 pn.addChild("body").addChild(body);
1242                 RESULT=pn;
1243         :}
1244 ;
1245
1246 constructor_declarator ::=
1247                 simple_name:name LPAREN formal_parameter_list_opt:fplo RPAREN {: 
1248                 ParseNode pn=new ParseNode("constructor_declarator");
1249                 pn.addChild(name);
1250                 pn.addChild("parameters").addChild(fplo);
1251                 RESULT=pn;
1252         :}
1253         ;
1254 constructor_body ::=
1255                 LBRACE explicit_constructor_invocation:eci block_statements:bs RBRACE {: 
1256                         ParseNode pn=new ParseNode("constructor_body");
1257                         pn.addChild(eci);
1258                         pn.addChild(bs);
1259                         RESULT=pn;
1260         :} |
1261                 LBRACE explicit_constructor_invocation:eci RBRACE {: 
1262                         ParseNode pn=new ParseNode("constructor_body");
1263                         pn.addChild(eci);
1264                         RESULT=pn;
1265         :} |
1266                 LBRACE block_statements:block RBRACE {: 
1267                 ParseNode pn=new ParseNode("constructor_body");
1268                 pn.addChild(block);
1269                 RESULT=pn;
1270         :}
1271         |       LBRACE RBRACE {: RESULT=new ParseNode("empty"); :}
1272         ;
1273 explicit_constructor_invocation ::=
1274         THIS LPAREN argument_list_opt:alo RPAREN SEMICOLON {:
1275              ParseNode pn=new ParseNode("explconstrinv");
1276              pn.addChild(alo);
1277              RESULT=pn;
1278         :}
1279         |       
1280 SUPER LPAREN argument_list_opt:alo RPAREN SEMICOLON {: 
1281         ParseNode pn=new ParseNode("superinvoke");
1282         pn.addChild(alo);
1283         RESULT=pn;
1284 :}
1285 //      |       primary DOT THIS LPAREN argument_list_opt RPAREN SEMICOLON
1286 //      |       primary DOT SUPER LPAREN argument_list_opt RPAREN SEMICOLON
1287         ;
1288
1289 // 19.8.6) Location Hierarchy Declarations
1290 location_order_declaration ::= LOCDEF LBRACE location_order_list:lol RBRACE {:
1291                 RESULT=lol;                        
1292         :}
1293         ;
1294 location_order_list ::= 
1295                 location_order:lo {:
1296                 ParseNode pn=new ParseNode("location_order_list");
1297                 pn.addChild(lo);
1298                 RESULT=pn;
1299         :}
1300         |       location_order_list:lol COMMA location_order:lo {:
1301                 lol.addChild(lo);
1302                 RESULT=lol;
1303         :}
1304         ;
1305 location_order ::= 
1306                 IDENTIFIER:loc1 LT IDENTIFIER:loc2{:
1307                 ParseNode pn=new ParseNode("location_order");
1308                 pn.addChild(loc1);
1309                 pn.addChild(loc2);
1310                 RESULT=pn;         
1311         :}
1312         ;
1313
1314 // 19.9) Interfaces
1315
1316 // 19.9.1) Interface Declarations
1317 interface_declaration ::=
1318                modifiers_opt:mo INTERFACE IDENTIFIER:id extends_interfaces_opt:io
1319                        interface_body:body
1320        {:
1321         ParseNode pn=new ParseNode("interface_declaration");
1322         pn.addChild("modifiers").addChild(mo);
1323         pn.addChild("name").addChild(id);
1324         pn.addChild("superIF").addChild(io);
1325         pn.addChild("interfacebody").addChild(body);
1326         RESULT=pn;
1327         :}
1328        | annotation_type_declaration
1329        ;
1330 extends_interfaces_opt ::=
1331        {: RESULT=new ParseNode("empty"); :}
1332        |       extends_interfaces:eifs {: RESULT=eifs; :}
1333        ;
1334 extends_interfaces ::=
1335                EXTENDS interface_type:ift 
1336                {: 
1337                ParseNode pn=new ParseNode("extend_interface_list");
1338                pn.addChild(ift);
1339                RESULT=pn; 
1340                :}
1341      |       extends_interfaces:eifs COMMA interface_type:ift
1342              {:
1343              eifs.addChild(ift);
1344              RESULT=eifs;
1345              :}
1346        ;
1347 interface_body ::=
1348                LBRACE interface_member_declarations_opt:imdo RBRACE
1349                {: RESULT=imdo; :}
1350        ;
1351 interface_member_declarations_opt ::=
1352        {: RESULT=new ParseNode("empty"); :}
1353        |       interface_member_declarations:imd {: RESULT=imd; :}
1354        ;
1355 interface_member_declarations ::=
1356                interface_member_declaration:imd {: 
1357                         ParseNode pn=new ParseNode("interface_member_declaration_list");
1358                         pn.addChild(imd);
1359                         RESULT=pn;
1360                 :}
1361        |       interface_member_declarations:imds interface_member_declaration:imd {: 
1362                         imds.addChild(imd);
1363                         RESULT=imds;
1364                 :}
1365        ;
1366 interface_member_declaration ::=
1367                constant_declaration:constant {: 
1368                 RESULT=(new ParseNode("constant")).addChild(constant).getRoot();
1369         :}
1370        |       abstract_method_declaration:method {:
1371         RESULT=(new ParseNode("method")).addChild(method).getRoot(); 
1372         :}
1373            |    enum_declaration:ed {:
1374            RESULT=(new ParseNode("enum_declaration")).addChild(ed).getRoot();
1375            :}
1376 //       |       class_declaration:class 
1377 //       |       interface_declaration:interface 
1378        |       SEMICOLON {: 
1379        RESULT=new ParseNode("empty"); 
1380        :}
1381        ;
1382 constant_declaration ::=
1383                field_declaration:fd {: RESULT=fd; :}
1384        // need to semantically check that modifiers of field declaration
1385        // include only PUBLIC, STATIC, or FINAL.  Other modifiers are
1386        // disallowed.
1387        ;
1388 abstract_method_declaration ::=
1389                method_header:header SEMICOLON {:
1390                 ParseNode pn=new ParseNode("method_declaration");
1391                 pn.addChild("header").addChild(header);
1392                 pn.addChild("body").addChild(new ParseNode("empty"));
1393                 RESULT=pn;
1394         :}
1395        ;
1396
1397 annotation_type_declaration ::=
1398                 AT INTERFACE IDENTIFIER annotation_type_body
1399         |       modifiers_at INTERFACE IDENTIFIER annotation_type_body
1400         ;
1401 annotation_type_body ::=
1402                 LBRACE annotation_type_element_declarations_opt RBRACE
1403         ;
1404 annotation_type_element_declarations_opt ::=
1405         |       annotation_type_element_declarations
1406         ;
1407 annotation_type_element_declarations ::=
1408                 annotation_type_element_declaration
1409         |       annotation_type_element_declarations annotation_type_element_declaration
1410         ;
1411 annotation_type_element_declaration ::=
1412                 constant_declaration
1413         |       modifiers_opt type IDENTIFIER LPAREN RPAREN default_value_opt SEMICOLON
1414         |       class_declaration 
1415         |       enum_declaration 
1416         |       interface_declaration 
1417         |       SEMICOLON
1418         ;
1419
1420 // 19.10) Arrays
1421 array_initializer ::=
1422                 LBRACE variable_initializers:var_init_list COMMA RBRACE {:
1423                        RESULT=var_init_list;
1424                 :}
1425         |       LBRACE variable_initializers:var_init_list RBRACE {:
1426                        RESULT=var_init_list;
1427                 :}
1428         |       LBRACE COMMA RBRACE {:
1429                        RESULT=new ParseNode("empty");                  
1430                 :}
1431         |       LBRACE RBRACE {:
1432                        RESULT=new ParseNode("empty");
1433                 :}
1434         ;
1435 variable_initializers ::=
1436                 variable_initializer:var_init {:
1437                        ParseNode pn=new ParseNode("var_init_list");
1438                        pn.addChild(var_init);
1439                        RESULT=pn;
1440                 :}
1441         |       variable_initializers:var_init_list COMMA variable_initializer:var_init {:
1442                        var_init_list.addChild(var_init);
1443                        RESULT=var_init_list;
1444                 :}
1445         ;
1446
1447 // 19.11) Blocks and Statements
1448 block ::=       LBRACE block_statements_opt:bso RBRACE {: 
1449         RESULT=bso;
1450         :}
1451         ;
1452 block_statements_opt ::=
1453         {: RESULT=new ParseNode("empty"); :}
1454         |       block_statements:bs {: 
1455         RESULT=bs;
1456         :}
1457         ;
1458 block_statements ::=
1459                 block_statement:bs {:
1460         ParseNode pn=new ParseNode("block_statement_list");
1461         pn.addChild(bs);
1462         RESULT=pn;
1463         :}
1464         |       block_statements:bss block_statement:bs {: 
1465         bss.addChild(bs);
1466         RESULT=bss;
1467         :}
1468         ;
1469 block_statement ::=
1470         tag_variable_declaration_statement:tvds {:
1471                 RESULT=tvds;
1472         :}              
1473         |       local_variable_declaration_statement:lvds {: 
1474                 RESULT=lvds;
1475         :}
1476         |       statement:statement {: 
1477                 RESULT=statement;
1478         :}
1479 //      |       enum_declaration:ed {:
1480 //              RESULT=ed;
1481 //      :}
1482 //      |       class_declaration
1483 //      |       interface_declaration
1484         ;
1485 tag_variable_declaration_statement ::=
1486                 TAG IDENTIFIER:id EQ NEW TAG LPAREN IDENTIFIER:type RPAREN SEMICOLON {: 
1487                 ParseNode pn=new ParseNode("tag_declaration");
1488                 pn.addChild("single").addChild(id);
1489                 pn.addChild("type").addChild(type);
1490                 RESULT=pn;
1491         :}
1492         ;
1493 local_variable_declaration_statement ::=
1494                 local_variable_declaration:lvd SEMICOLON {: 
1495                 RESULT=lvd;
1496         :}
1497         ;
1498 local_variable_declaration ::=
1499                 type:type variable_declarators:var {: 
1500                 ParseNode pn=new ParseNode("local_variable_declaration");
1501                 pn.addChild(type);
1502                 pn.addChild(var);
1503                 RESULT=pn;
1504         :}
1505 //      |       FINAL type:type variable_declarators:var {: 
1506          /* CAUTION:  only FINAL and annotations are legal modifiers here */
1507         |       modifiers:mo type:type variable_declarators:var {:
1508                 ParseNode pn=new ParseNode("local_variable_declaration");
1509                 pn.addChild(type);
1510                 pn.addChild(var);
1511                 pn.addChild("modifiers").addChild(mo);
1512                 RESULT=pn;
1513         :}
1514         ;
1515 statement ::=   statement_without_trailing_substatement:st {: 
1516                 RESULT=st;
1517         :}
1518 //      |       labeled_statement:st {: RESULT=st; :}
1519         |       if_then_statement:st {: RESULT=st; :}
1520         |       if_then_else_statement:st {: RESULT=st; :}
1521         |       while_statement:st {: RESULT=st; :}
1522         |       for_statement:st {: RESULT=st; :}
1523         ;
1524 statement_no_short_if ::=
1525                 statement_without_trailing_substatement:st {: RESULT=st; :}
1526 //      |       labeled_statement_no_short_if:st {: RESULT=st; :}
1527         |       if_then_else_statement_no_short_if:st {: RESULT=st; :}
1528         |       while_statement_no_short_if:st {: RESULT=st; :}
1529         |       for_statement_no_short_if:st {: RESULT=st; :}
1530         ;
1531 statement_without_trailing_substatement ::=
1532                 block:st {: RESULT=st; :}
1533         |       empty_statement:st {: RESULT=st; :}
1534         |       expression_statement:st {: RESULT=st; :}
1535         |       switch_statement:st {: RESULT=st; :}
1536         |       do_statement:dos {:RESULT=dos; :}
1537         |       break_statement:st {: RESULT=st; :}
1538         |       continue_statement:st {: RESULT=st; :}
1539         |       return_statement:st {: RESULT=st; :}
1540         |       task_exitstatement:st {: RESULT=st; :}
1541         |       atomic_statement:st {: RESULT=st; :}
1542         |       sese_statement:st {: RESULT=st; :}
1543         |       synchronized_statement:st {: RESULT=st; :}
1544         |       genreach_statement:st {: RESULT=st; :}
1545         |       throw_statement:st {: RESULT=st; :}
1546         |       try_statement:st {: RESULT=st; :}
1547 //      |       assert_statement
1548         ;
1549 empty_statement ::=
1550                 SEMICOLON {: RESULT=new ParseNode("nop"); :}
1551         ;
1552 //labeled_statement ::=
1553 //              IDENTIFIER COLON statement
1554 //      ;
1555 //labeled_statement_no_short_if ::=
1556 //              IDENTIFIER COLON statement_no_short_if
1557 //      ;
1558 expression_statement ::=
1559                 statement_expression:se SEMICOLON {: 
1560                 ParseNode pn=new ParseNode("expression");
1561                 pn.addChild(se);
1562                 RESULT=pn; :}
1563         ;
1564 statement_expression ::=
1565                 assignment:st {: RESULT=st; :}
1566         |       preincrement_expression:st {: RESULT=st; :}
1567         |       predecrement_expression:st {: RESULT=st; :}
1568         |       postincrement_expression:st {: RESULT=st; :}
1569         |       postdecrement_expression:st {: RESULT=st; :}
1570         |       method_invocation:st {: RESULT=st; :}
1571         |       class_instance_creation_expression:st {: RESULT=st; :}
1572         ;
1573 if_then_statement ::=
1574                 IF LPAREN expression:exp RPAREN statement:st {: 
1575                 ParseNode pn=new ParseNode("ifstatement");
1576                 pn.addChild("condition").addChild(exp);
1577                 pn.addChild("statement").addChild(st);
1578                 RESULT=pn;
1579         :}
1580         ;
1581 if_then_else_statement ::=
1582                 IF LPAREN expression:exp RPAREN statement_no_short_if:st
1583                         ELSE statement:else_st {:
1584                 ParseNode pn=new ParseNode("ifstatement");
1585                 pn.addChild("condition").addChild(exp);
1586                 pn.addChild("statement").addChild(st);
1587                 pn.addChild("else_statement").addChild(else_st);
1588                 RESULT=pn;
1589         :}
1590         ;
1591 if_then_else_statement_no_short_if ::=
1592                 IF LPAREN expression:exp RPAREN statement_no_short_if:st
1593                         ELSE statement_no_short_if:else_st {:
1594                 ParseNode pn=new ParseNode("ifstatement");
1595                 pn.addChild("condition").addChild(exp);
1596                 pn.addChild("statement").addChild(st);
1597                 pn.addChild("else_statement").addChild(else_st);
1598                 RESULT=pn;
1599         :}
1600         ;
1601 switch_statement ::=
1602                 SWITCH LPAREN expression:exp RPAREN switch_block:body
1603                 {:
1604                     ParseNode pn=new ParseNode("switch_statement");
1605                     pn.addChild("condition").addChild(exp);
1606                     pn.addChild("statement").addChild(body);
1607                     RESULT=pn;
1608                 :}
1609         ;
1610 switch_block ::=
1611                 LBRACE switch_block_statement_groups:sbsg switch_labels:sl RBRACE
1612                 {: 
1613                     ParseNode pn = new ParseNode("switch_block");
1614                     pn.addChild("switch_labels").addChild(sl);
1615                     pn.addChild("switch_statements").addChild(new ParseNode("empty"));
1616                     sbsg.addChild(pn);
1617                     RESULT=sbsg; 
1618                 :}
1619         |       LBRACE switch_block_statement_groups:sbsg RBRACE
1620             {: 
1621                     RESULT=sbsg; 
1622                 :}
1623         |       LBRACE switch_labels:sl RBRACE 
1624             {: 
1625                 ParseNode pnb = new ParseNode("switch_block_list");
1626                     ParseNode pn = new ParseNode("switch_block");
1627                     pn.addChild("switch_labels").addChild(sl);
1628                     pn.addChild("switch_statements").addChild(new ParseNode("empty"));
1629                     pnb.addChild(pn);
1630                     RESULT=pnb; 
1631                 :}
1632         |       LBRACE RBRACE {: RESULT=new ParseNode("empty"); :}
1633         ;
1634 switch_block_statement_groups ::=
1635                 switch_block_statement_group:sbsg
1636                 {: 
1637                     ParseNode pn = new ParseNode("switch_block_list");
1638                     pn.addChild(sbsg);
1639                     RESULT=pn;
1640                 :}
1641         |       switch_block_statement_groups:sbsgs switch_block_statement_group:sbsg
1642             {:
1643                 sbsgs.addChild(sbsg);
1644                 RESULT=sbsgs;
1645             :}
1646         ;
1647 switch_block_statement_group ::=
1648                 switch_labels:sls block_statements:body
1649                 {: 
1650                     ParseNode pn=new ParseNode("switch_block");
1651                     pn.addChild("switch_labels").addChild(sls);
1652                     pn.addChild("switch_statements").addChild(body);
1653                     RESULT=pn; 
1654                 :}
1655         ;
1656 switch_labels ::=
1657                 switch_label:sl
1658                 {: 
1659                     ParseNode pn=new ParseNode("switch_label_list");
1660                     pn.addChild(sl);
1661                     RESULT=pn; 
1662                 :}
1663         |       switch_labels:sls switch_label:sl
1664             {: 
1665                     sls.addChild(sl); 
1666                     RESULT=sls;
1667                 :}
1668         ;
1669 switch_label ::=
1670                 CASE constant_expression:ce COLON
1671                 {: 
1672                     ParseNode pn=new ParseNode("switch_label");
1673                     pn.addChild(ce);
1674                     RESULT=pn;
1675                 :}
1676         |       DEFAULT COLON
1677             {: 
1678                     RESULT=new ParseNode("default_switch_label"); 
1679                 :}
1680         ;
1681
1682 while_statement ::=
1683                 WHILE LPAREN expression:exp RPAREN statement:st {: 
1684                 ParseNode pn=new ParseNode("whilestatement");
1685                 pn.addChild("condition").addChild(exp);
1686                 pn.addChild("statement").addChild(st);
1687                 RESULT=pn;
1688         :}
1689         ;
1690 while_statement_no_short_if ::=
1691                 WHILE LPAREN expression:exp RPAREN statement_no_short_if:st {:
1692                 ParseNode pn=new ParseNode("whilestatement");
1693                 pn.addChild("condition").addChild(exp);
1694                 pn.addChild("statement").addChild(st);
1695                 RESULT=pn;
1696                 :}
1697         ;
1698 do_statement ::=
1699                 DO statement:st WHILE LPAREN expression:exp RPAREN SEMICOLON {: 
1700                 ParseNode pn=new ParseNode("dowhilestatement");
1701                 pn.addChild("condition").addChild(exp);
1702                 pn.addChild("statement").addChild(st);
1703                 RESULT=pn;
1704         :}
1705         ;
1706 for_statement ::=
1707                 FOR LPAREN for_init_opt:init SEMICOLON expression_opt:exp SEMICOLON
1708                         for_update_opt:update RPAREN statement:st {: 
1709                 ParseNode pn=new ParseNode("forstatement");
1710                 pn.addChild("initializer").addChild(init);
1711                 pn.addChild("condition").addChild(exp);
1712                 pn.addChild("update").addChild(update);
1713                 pn.addChild("statement").addChild(st);
1714                 RESULT=pn;
1715                 :}
1716         ;
1717 for_statement_no_short_if ::=
1718                 FOR LPAREN for_init_opt:init SEMICOLON expression_opt:exp SEMICOLON
1719                         for_update_opt:update RPAREN statement_no_short_if:st {:
1720                 ParseNode pn=new ParseNode("forstatement");
1721                 pn.addChild("initializer").addChild(init);
1722                 pn.addChild("condition").addChild(exp);
1723                 pn.addChild("update").addChild(update);
1724                 pn.addChild("statement").addChild(st);
1725                 RESULT=pn;
1726                 :}
1727         ;
1728 for_init_opt ::=
1729         {: RESULT=new ParseNode("empty"); :}
1730         |       for_init:init {: RESULT=init; :}
1731         ;
1732 for_init ::=    statement_expression_list:list {: RESULT=list; :}
1733         |       local_variable_declaration:decl {: RESULT=decl; :}
1734         ;
1735 for_update_opt ::=
1736         {: RESULT=new ParseNode("empty"); :}
1737         |       for_update:update {: RESULT=update; :}
1738         ;
1739 for_update ::=  statement_expression_list:list {: RESULT=list; :}
1740         ;
1741 statement_expression_list ::=
1742                 statement_expression:expr {: 
1743                 RESULT=(new ParseNode("statement_expression_list")).addChild(expr).getRoot();
1744         :}
1745         |       statement_expression_list:list COMMA statement_expression:expr {: 
1746                 list.addChild(expr);
1747                 RESULT=list;
1748         :}
1749         ;
1750
1751 //identifier_opt ::= 
1752 //      |       IDENTIFIER
1753 //      ;
1754
1755 break_statement ::=
1756                 BREAK
1757 //identifier_opt 
1758 SEMICOLON {: RESULT=new ParseNode("break"); :}
1759         ;
1760
1761 continue_statement ::=
1762                 CONTINUE  
1763 //identifier_opt 
1764 SEMICOLON
1765 {: RESULT=new ParseNode("continue"); :}
1766         ;
1767 return_statement ::=
1768                 RETURN expression_opt:exp SEMICOLON {: 
1769         RESULT=(new ParseNode("return")).addChild(exp).getRoot(); :}
1770         ;
1771 throw_statement ::=
1772                 THROW expression:exp SEMICOLON {:
1773                 RESULT=(new ParseNode("throwstatement")).addChild(exp).getRoot();
1774                 :}
1775         ;
1776 synchronized_statement ::=
1777                 SYNCHRONIZED LPAREN expression:e RPAREN block:b {: 
1778                 ParseNode pn=new ParseNode("synchronized");
1779                 pn.addChild("expr").addChild(e);
1780                 pn.addChild("block").addChild(b);
1781                 RESULT=pn;
1782                 :}
1783         ;
1784 atomic_statement ::=
1785                 ATOMIC block:blk {: 
1786         RESULT=(new ParseNode("atomic")).addChild(blk).getRoot();
1787         :}
1788         ;
1789 sese_statement ::=
1790                SESE block:blk {: 
1791                ParseNode pn = new ParseNode("sese");
1792                pn.addChild("body").addChild(blk);
1793                RESULT=pn;
1794         :}
1795         |      SESE variable_declarator_id:id block:blk {: 
1796                ParseNode pn = new ParseNode("sese");
1797                pn.addChild("body").addChild(blk);
1798                pn.addChild("identifier").addChild(id);
1799                RESULT=pn;
1800         :}
1801         |      RBLOCK block:blk {: 
1802                ParseNode pn = new ParseNode("sese");
1803                pn.addChild("body").addChild(blk);
1804                RESULT=pn;
1805         :}
1806         |      RBLOCK variable_declarator_id:id block:blk {: 
1807                ParseNode pn = new ParseNode("sese");
1808                pn.addChild("body").addChild(blk);
1809                pn.addChild("identifier").addChild(id);
1810                RESULT=pn;
1811         :}
1812         ;
1813 try_statement ::=
1814                 TRY block:bk catches:ca
1815                 {: 
1816                 ParseNode pn=new ParseNode("trycatchstatement");
1817                 pn.addChild("tryblock").addChild(bk); 
1818                 pn.addChild("catchblock").addChild(ca);
1819                 RESULT=pn;
1820                 :}
1821         |       TRY block:bk catches_opt:ca finally:fi
1822             {: 
1823                 ParseNode pn=new ParseNode("trycatchstatement");
1824                 pn.addChild("tryblock").addChild(bk); 
1825                 pn.addChild("catchblock").addChild(ca);
1826                 pn.addChild("finallyblock").addChild(fi);
1827                 RESULT=pn;
1828                 :}
1829         ;
1830 catches_opt ::=
1831     {: RESULT=new ParseNode("empty"); :}
1832         |       catches:ca
1833         {: RESULT=ca; :}
1834         ;
1835 catches ::=     catch_clause:ca
1836         {:
1837         ParseNode pn=new ParseNode("catchlist");
1838         pn.addChild(ca);
1839         RESULT=pn;
1840         :}
1841         |       catches:cas catch_clause:ca 
1842             {:
1843             cas.addChild(ca);
1844             RESULT=cas;
1845             :}
1846         ;
1847 catch_clause ::=
1848                 CATCH LPAREN formal_parameter:fp RPAREN block:bk
1849                 {:
1850                 ParseNode pn=new ParseNode("catchclause");
1851                 pn.addChild("parameter").addChild(fp);
1852                 pn.addChild("block").addChild(bk);
1853                 RESULT=pn;
1854                 :}
1855         ;
1856 finally ::=     FINALLY block:bk
1857     {:
1858     RESULT=bk;
1859     :}
1860         ;
1861 //assert_statement ::=
1862 //              ASSERT expression SEMICOLON
1863 //      |       ASSERT expression COLON expression SEMICOLON
1864 //      ;
1865
1866 // 19.12) Expressions
1867 primary ::=     primary_no_new_array:st {: 
1868                 RESULT=st; :}
1869         |       array_creation_init:st {: 
1870                 RESULT=st;
1871         :}
1872         |       array_creation_uninit:st {:
1873                 RESULT=st;
1874         :}
1875         ;
1876 primary_no_new_array ::=
1877                 literal:lit {: RESULT=lit; :}
1878         |       THIS {: RESULT=new ParseNode("this"); :}
1879         |       LPAREN expression:exp RPAREN {: RESULT=exp; :}
1880         |       class_instance_creation_expression:exp {: RESULT=exp; :}
1881         |       field_access:exp {: RESULT=exp; :}
1882         |       method_invocation:exp {: RESULT=exp; :}
1883         |       array_access:exp {: RESULT=exp; :}
1884         |       ISAVAILABLE LPAREN IDENTIFIER:id RPAREN {: 
1885                 ParseNode pn=new ParseNode("isavailable");
1886                 pn.addChild(id);
1887                 RESULT=pn;
1888         :}
1889 //      |       primitive_type:pt DOT CLASS {:
1890 //          ParseNode pn=new ParseNode("class_type");
1891 //          pn.addChild(pt);
1892 //          RESULT=pn;
1893 //      :}
1894 //      |       VOID DOT CLASS
1895 //      |       array_type:at DOT CLASS {:
1896 //          ParseNode pn=new ParseNode("class_type");
1897 //          pn.addChild(at);
1898 //          RESULT=pn;
1899 //      :}
1900         |       name:name DOT CLASS {:
1901             ParseNode pn=new ParseNode("class_type");
1902             pn.addChild("type").addChild("class").addChild(name);
1903             RESULT=pn;
1904         :}
1905 //      |       name DOT THIS
1906         ;
1907 class_instance_creation_expression ::=
1908                 NEW class_or_interface_type:type LPAREN argument_list_opt:args RPAREN flag_list_opt:feo {: 
1909                 ParseNode pn=new ParseNode("createobject");
1910                 pn.addChild(type);
1911                 pn.addChild(args);
1912                 pn.addChild(feo);
1913                 RESULT=pn;
1914         :} 
1915         //Global object
1916         | GLOBAL NEW class_or_interface_type:type LPAREN argument_list_opt:args RPAREN flag_list_opt:feo {: 
1917                 ParseNode pn=new ParseNode("createobject");
1918                 pn.addChild(type);
1919                 pn.addChild(args);
1920                 pn.addChild(feo);
1921                 pn.addChild("global");
1922                 RESULT=pn;
1923         :}
1924         | SCRATCH NEW class_or_interface_type:type LPAREN argument_list_opt:args RPAREN flag_list_opt:feo {: 
1925                 ParseNode pn=new ParseNode("createobject");
1926                 pn.addChild(type);
1927                 pn.addChild(args);
1928                 pn.addChild(feo);
1929                 pn.addChild("scratch");
1930                 RESULT=pn;
1931         :}
1932         // Objects we want to track in disjointness analysis
1933         | DISJOINT IDENTIFIER:id NEW class_or_interface_type:type LPAREN argument_list_opt:args RPAREN flag_list_opt:feo {: 
1934                 ParseNode pn=new ParseNode("createobject");
1935                 pn.addChild(type);
1936                 pn.addChild(args);
1937                 pn.addChild(feo);
1938                 pn.addChild("disjoint").addChild(id);
1939                 RESULT=pn;
1940         :}
1941         | NEW class_or_interface_type:type LPAREN argument_list_opt:args RPAREN LBRACE RBRACE LBRACE tag_list:tl RBRACE {: 
1942                 ParseNode pn=new ParseNode("createobject");
1943                 pn.addChild(type);
1944                 pn.addChild(args);
1945                 pn.addChild(tl);
1946                 RESULT=pn;
1947         :}
1948         | NEW class_or_interface_type:type LPAREN argument_list_opt:args RPAREN LBRACE flag_list:fl RBRACE LBRACE tag_list:tl RBRACE {: 
1949                 ParseNode pn=new ParseNode("createobject");
1950                 pn.addChild(type);
1951                 pn.addChild(args);
1952                 pn.addChild(fl);
1953                 pn.addChild(tl);
1954                 RESULT=pn;
1955         :}
1956
1957 //      |       NEW class_or_interface_type LPAREN argument_list_opt RPAREN class_body
1958 //      |       primary DOT NEW IDENTIFIER
1959 //                      LPAREN argument_list_opt RPAREN {: 
1960 //              
1961 //      :}
1962 //      |       primary DOT NEW IDENTIFIER
1963 //                      LPAREN argument_list_opt RPAREN class_body
1964 //      |       name DOT NEW IDENTIFIER
1965 //                      LPAREN argument_list_opt RPAREN
1966 //      |       name DOT NEW IDENTIFIER
1967 //                      LPAREN argument_list_opt RPAREN class_body
1968         ;
1969 cons_argument_list_opt ::=
1970         {: RESULT=new ParseNode("empty"); :}
1971         |       cons_argument_list:args {: RESULT=args; :}
1972         ;
1973
1974 cons_argument_list ::=
1975                 IDENTIFIER:id COLON expression:exp {:
1976                 ParseNode pn=new ParseNode("cons_argument_list");
1977                 ParseNode pnarg=pn.addChild("binding");
1978                 pnarg.addChild("var").addChild(id);
1979                 pnarg.addChild("exp").addChild(exp);
1980                 RESULT=pn;
1981         :}
1982         |       argument_list:list COMMA IDENTIFIER:id COLON expression:exp {:
1983                 ParseNode pnarg=new ParseNode("binding");
1984                 pnarg.addChild("var").addChild(id);
1985                 pnarg.addChild("exp").addChild(exp);
1986                 list.addChild(pnarg);
1987                 RESULT=list;
1988         :}
1989         ;
1990
1991 argument_list_opt ::=
1992         {: RESULT=new ParseNode("empty"); :}
1993         |       argument_list:args {: RESULT=args; :}
1994         ;
1995
1996 argument_list ::=
1997                 expression:exp {:
1998                 ParseNode pn=new ParseNode("argument_list");
1999                 pn.addChild(exp);
2000                 RESULT=pn;
2001         :}
2002         |       argument_list:list COMMA expression:exp {:
2003                 list.addChild(exp);
2004                 RESULT=list;
2005         :}
2006         ;
2007 array_creation_uninit ::=
2008                 NEW primitive_type:type dim_exprs:dimexpr dims_opt:dims {: 
2009                 ParseNode pn=new ParseNode("createarray");
2010                 pn.addChild(type);
2011                 pn.addChild(dimexpr);
2012                 pn.addChild("dims_opt").setLiteral(dims);
2013                 RESULT=pn;
2014                 :}
2015         |       NEW class_or_interface_type:type dim_exprs:dimexpr dims_opt:dims {: 
2016                 ParseNode pn=new ParseNode("createarray");
2017                 pn.addChild(type);
2018                 pn.addChild(dimexpr);
2019                 pn.addChild("dims_opt").setLiteral(dims);
2020                 RESULT=pn;
2021         :}
2022         |       GLOBAL NEW primitive_type:type dim_exprs:dimexpr dims_opt:dims {: 
2023                 ParseNode pn=new ParseNode("createarray");
2024                 pn.addChild(type);
2025                 pn.addChild(dimexpr);
2026                 pn.addChild("dims_opt").setLiteral(dims);
2027                 pn.addChild("global");
2028                 RESULT=pn;
2029                 :}
2030         |       SCRATCH NEW primitive_type:type dim_exprs:dimexpr dims_opt:dims {: 
2031                 ParseNode pn=new ParseNode("createarray");
2032                 pn.addChild(type);
2033                 pn.addChild(dimexpr);
2034                 pn.addChild("dims_opt").setLiteral(dims);
2035                 pn.addChild("scratch");
2036                 RESULT=pn;
2037                 :}
2038         |       DISJOINT IDENTIFIER:id NEW primitive_type:type dim_exprs:dimexpr dims_opt:dims {: 
2039                 ParseNode pn=new ParseNode("createarray");
2040                 pn.addChild(type);
2041                 pn.addChild(dimexpr);
2042                 pn.addChild("dims_opt").setLiteral(dims);
2043                 pn.addChild("disjoint").addChild(id);
2044                 RESULT=pn;
2045                 :}
2046         |       GLOBAL NEW class_or_interface_type:type dim_exprs:dimexpr dims_opt:dims {: 
2047                 ParseNode pn=new ParseNode("createarray");
2048                 pn.addChild(type);
2049                 pn.addChild(dimexpr);
2050                 pn.addChild("dims_opt").setLiteral(dims);
2051                 pn.addChild("global");
2052                 RESULT=pn;
2053                 :}
2054         |       SCRATCH NEW class_or_interface_type:type dim_exprs:dimexpr dims_opt:dims {: 
2055                 ParseNode pn=new ParseNode("createarray");
2056                 pn.addChild(type);
2057                 pn.addChild(dimexpr);
2058                 pn.addChild("dims_opt").setLiteral(dims);
2059                 pn.addChild("scratch");
2060                 RESULT=pn;
2061                 :}
2062         |       DISJOINT IDENTIFIER:id NEW class_or_interface_type:type dim_exprs:dimexpr dims_opt:dims {: 
2063                 ParseNode pn=new ParseNode("createarray");
2064                 pn.addChild(type);
2065                 pn.addChild(dimexpr);
2066                 pn.addChild("dims_opt").setLiteral(dims);
2067                 pn.addChild("disjoint").addChild(id);           
2068                 RESULT=pn;
2069                 :}
2070         ;
2071 array_creation_init ::=
2072                 NEW primitive_type:type dims:dims array_initializer:ai {: 
2073                 ParseNode pn=new ParseNode("createarray2");
2074                 pn.addChild(type);
2075                 pn.addChild("dims_opt").setLiteral(dims);
2076                 pn.addChild("initializer").addChild(ai);
2077                 RESULT=pn;
2078                 :}
2079         |       NEW class_or_interface_type:type dims:dims array_initializer:ai {: 
2080                 ParseNode pn=new ParseNode("createarray2");
2081                 pn.addChild(type);
2082                 pn.addChild("dims_opt").setLiteral(dims);
2083                 pn.addChild("initializer").addChild(ai);
2084                 RESULT=pn;
2085                 :}
2086         ;
2087 dim_exprs ::=   dim_expr:exp {: 
2088                 ParseNode pn=new ParseNode("dim_exprs");
2089                 pn.addChild(exp);
2090                 RESULT=pn; :}
2091         |       dim_exprs:base dim_expr:exp {: 
2092                 base.addChild(exp);
2093                 RESULT=base;
2094         :}
2095         ;
2096 dim_expr ::=    LBRACK expression:exp RBRACK {: RESULT=exp; :}
2097         ;
2098 dims_opt ::= {: RESULT=new Integer(0); :}
2099         |       dims:dims {: RESULT = dims; :}
2100         ;
2101
2102 dims ::=        LBRACK RBRACK {: RESULT=new Integer(1); :}
2103         |       dims:dims LBRACK RBRACK {: RESULT=new Integer(dims.intValue()+1); :}
2104         ;
2105
2106 field_access ::=
2107                 primary:base DOT IDENTIFIER:id {: 
2108                 ParseNode pn=new ParseNode("fieldaccess");
2109                 pn.addChild("base").addChild(base);
2110                 pn.addChild("field").addChild(id);
2111                 RESULT=pn;
2112     :}
2113 //      |       SUPER DOT IDENTIFIER
2114 //      |       name DOT SUPER DOT IDENTIFIER
2115         ;
2116 method_invocation ::=
2117                 name:name LPAREN argument_list_opt:args RPAREN {: 
2118                 ParseNode pn=new ParseNode("methodinvoke1");
2119                 pn.addChild(name);
2120                 pn.addChild(args);
2121                 RESULT=pn;
2122         :}
2123         |       primary:base DOT IDENTIFIER:name LPAREN argument_list_opt:args RPAREN {: 
2124                 ParseNode pn=new ParseNode("methodinvoke2");
2125                 pn.addChild("base").addChild(base);
2126                 pn.addChild("id").addChild(name);
2127                 pn.addChild(args);
2128                 RESULT=pn;
2129         :}
2130         |       SUPER DOT IDENTIFIER:id LPAREN argument_list_opt:args RPAREN {: 
2131                 ParseNode name=new ParseNode("name");
2132                 name.addChild("base").addChild("name").addChild("identifier").addChild("super");
2133                 name.addChild("identifier").addChild(id);
2134                 ParseNode pn=new ParseNode("methodinvoke1");
2135                 pn.addChild(name);
2136                 pn.addChild(args);
2137                 RESULT=pn;
2138         :}
2139 //      |       name DOT SUPER DOT IDENTIFIER LPAREN argument_list_opt RPAREN
2140         ;
2141 array_access ::=
2142                 name:name LBRACK expression:exp RBRACK {: 
2143                 ParseNode pn=new ParseNode("arrayaccess");
2144                 pn.addChild("base").addChild(name);
2145                 pn.addChild("index").addChild(exp);
2146                 RESULT=pn;
2147         :}
2148         |       primary_no_new_array:base LBRACK expression:exp RBRACK {: 
2149                 ParseNode pn=new ParseNode("arrayaccess");
2150                 pn.addChild("base").addChild(base);
2151                 pn.addChild("index").addChild(exp);
2152                 RESULT=pn;
2153         :}
2154 //      |       array_creation_init:init LBRACK expression:exp RBRACK {: 
2155 //              ParseNode pn=new ParseNode("arrayaccess");
2156 //              pn.addChild("init").addChild(init);
2157 //              pn.addChild("index").addChild(exp);
2158 //              RESULT=pn;
2159 //      :}
2160         ;
2161
2162 postfix_expression ::=
2163                 primary:exp {: 
2164         RESULT=exp; :}
2165         |       name:exp {: RESULT=exp; :}
2166         |       postincrement_expression:exp {: RESULT=exp; :}
2167         |       postdecrement_expression:exp {: RESULT=exp; :}
2168         ;
2169 postincrement_expression ::=
2170                 postfix_expression:exp PLUSPLUS 
2171                 {: RESULT=(new ParseNode("postinc")).addChild(exp).getRoot(); :}
2172         ;
2173 postdecrement_expression ::=
2174                 postfix_expression:exp MINUSMINUS
2175                 {: RESULT=(new ParseNode("postdec")).addChild(exp).getRoot(); :}
2176         ;
2177 unary_expression ::=
2178                 preincrement_expression:exp {: RESULT=exp; :}
2179         |       predecrement_expression:exp {: RESULT=exp; :}
2180         |       PLUS unary_expression:exp 
2181         {: RESULT=(new ParseNode("unaryplus")).addChild(exp).getRoot(); :}
2182         |       MINUS unary_expression:exp
2183         {: RESULT=(new ParseNode("unaryminus")).addChild(exp).getRoot(); :}
2184         |       unary_expression_not_plus_minus:exp {: 
2185                         RESULT=exp; :}
2186         ;
2187 preincrement_expression ::=
2188                 PLUSPLUS unary_expression:exp
2189                 {: RESULT=(new ParseNode("preinc")).addChild(exp).getRoot(); :}
2190         ;
2191 predecrement_expression ::=
2192                 MINUSMINUS unary_expression:exp
2193                 {: RESULT=(new ParseNode("predec")).addChild(exp).getRoot(); :}
2194         ;
2195 unary_expression_not_plus_minus ::=
2196                 postfix_expression:exp {: 
2197                 RESULT=exp; :}
2198         |       COMP unary_expression:exp
2199                 {: RESULT=(new ParseNode("comp")).addChild(exp).getRoot(); :}
2200         |       NOT unary_expression:exp 
2201                 {: RESULT=(new ParseNode("not")).addChild(exp).getRoot(); :}
2202         |       cast_expression:exp {: RESULT=exp; :}
2203         ;
2204 cast_expression ::=
2205                 LPAREN primitive_type:type dims_opt:dims
2206                 RPAREN unary_expression:exp {: 
2207                 ParseNode pn=new ParseNode("cast1");
2208 if (dims.intValue()==0)
2209                 pn.addChild("type").addChild(type);
2210 else {
2211                 ParseNode arrayt=pn.addChild("type").addChild("type").addChild("array");
2212                 arrayt.addChild("basetype").addChild(type);
2213                 arrayt.addChild("dims").setLiteral(dims);
2214 }
2215                 pn.addChild("exp").addChild(exp);
2216                 RESULT=pn;
2217         :}
2218         |       LPAREN expression:type RPAREN unary_expression_not_plus_minus:exp {: 
2219                 ParseNode pn=new ParseNode("cast2");
2220                 pn.addChild("type").addChild(type);
2221                 pn.addChild("exp").addChild(exp);
2222                 RESULT=pn;
2223
2224         :}
2225         |       LPAREN name:name dims:dims RPAREN unary_expression_not_plus_minus:exp {: 
2226                 ParseNode pn=new ParseNode("cast1");
2227 if (dims.intValue()==0)
2228                 pn.addChild("type").addChild("class").addChild(name);
2229 else {
2230                 ParseNode arrayt=pn.addChild("type").addChild("type").addChild("array");
2231                 arrayt.addChild("basetype").addChild("type").addChild("class").addChild(name);
2232                 arrayt.addChild("dims").setLiteral(dims);
2233 }
2234                 pn.addChild("exp").addChild(exp);
2235                 RESULT=pn;
2236
2237         :}
2238         ;
2239 multiplicative_expression ::=
2240                 unary_expression:exp {: 
2241                         RESULT=exp; :}
2242         |       multiplicative_expression:exp1 MULT unary_expression:exp2 {: 
2243                 ParseNode pn=new ParseNode("mult");
2244                 pn.addChild(exp1);
2245                 pn.addChild(exp2);
2246                 RESULT=pn;
2247         :}
2248         |       multiplicative_expression:exp1 DIV unary_expression:exp2 {:
2249                 ParseNode pn=new ParseNode("div");
2250                 pn.addChild(exp1);
2251                 pn.addChild(exp2);
2252                 RESULT=pn;
2253         :}
2254         |       multiplicative_expression:exp1 MOD unary_expression:exp2 {:
2255                 ParseNode pn=new ParseNode("mod");
2256                 pn.addChild(exp1);
2257                 pn.addChild(exp2);
2258                 RESULT=pn;
2259         :}
2260         ;
2261 additive_expression ::=
2262                 multiplicative_expression:exp {: 
2263                         RESULT=exp; :}
2264         |       additive_expression:exp1 PLUS multiplicative_expression:exp2 {: 
2265                 ParseNode pn=new ParseNode("add");
2266                 pn.addChild(exp1);
2267                 pn.addChild(exp2);
2268                 RESULT=pn;
2269         :}
2270         |       additive_expression:exp1 MINUS multiplicative_expression:exp2 {: 
2271                 ParseNode pn=new ParseNode("sub");
2272                 pn.addChild(exp1);
2273                 pn.addChild(exp2);
2274                 RESULT=pn;
2275         :}
2276         ;
2277 shift_expression ::=
2278                 additive_expression:exp {: 
2279                         RESULT=exp; :}
2280         |       shift_expression:exp1 LSHIFT additive_expression:exp2 {: 
2281                 ParseNode pn=new ParseNode("leftshift");
2282                 pn.addChild(exp1);
2283                 pn.addChild(exp2);
2284                 RESULT=pn;
2285         :}
2286         |       shift_expression:exp1 RSHIFT additive_expression:exp2 {: 
2287                 ParseNode pn=new ParseNode("rightshift");
2288                 pn.addChild(exp1);
2289                 pn.addChild(exp2);
2290                 RESULT=pn;
2291         :}
2292         |       shift_expression:exp1 URSHIFT additive_expression:exp2 {:
2293                 ParseNode pn=new ParseNode("urightshift");
2294                 pn.addChild(exp1);      
2295                 pn.addChild(exp2);      
2296                 RESULT=pn;
2297         :}
2298         ;
2299 relational_expression ::=
2300                 shift_expression:exp {: 
2301                         RESULT=exp; :}
2302         |       relational_expression:exp1 LT shift_expression:exp2 {:
2303                 ParseNode pn=new ParseNode("comp_lt");
2304                 pn.addChild(exp1);
2305                 pn.addChild(exp2);
2306                 RESULT=pn;
2307         :}
2308         |       relational_expression:exp1 GT shift_expression:exp2 {:
2309                 ParseNode pn=new ParseNode("comp_gt");
2310                 pn.addChild(exp1);
2311                 pn.addChild(exp2);
2312                 RESULT=pn;
2313         :}
2314         |       relational_expression:exp1 LTEQ shift_expression:exp2 {:
2315                 ParseNode pn=new ParseNode("comp_lte");
2316                 pn.addChild(exp1);
2317                 pn.addChild(exp2);
2318                 RESULT=pn;
2319         :}
2320         |       relational_expression:exp1 GTEQ shift_expression:exp2 {:
2321                 ParseNode pn=new ParseNode("comp_gte");
2322                 pn.addChild(exp1);
2323                 pn.addChild(exp2);
2324                 RESULT=pn;
2325         :}
2326         |       relational_expression:exp INSTANCEOF reference_type:type {: 
2327                 ParseNode pn=new ParseNode("instanceof");
2328                 pn.addChild("exp").addChild(exp);
2329                 pn.addChild(type);
2330                 RESULT=pn;
2331         :}
2332         ;
2333
2334 equality_expression ::=
2335                 relational_expression:exp {: 
2336                         RESULT=exp; :}
2337         |       equality_expression:exp1 EQEQ relational_expression:exp2 {: 
2338                 ParseNode pn=new ParseNode("equal");
2339                 pn.addChild(exp1);
2340                 pn.addChild(exp2);
2341                 RESULT=pn;
2342         :}
2343         |       equality_expression:exp1 NOTEQ relational_expression:exp2 {: 
2344                 ParseNode pn=new ParseNode("not_equal");
2345                 pn.addChild(exp1);
2346                 pn.addChild(exp2);
2347                 RESULT=pn;
2348         :}
2349         ;
2350 and_expression ::=
2351                 equality_expression:exp {: 
2352                 RESULT=exp; :}
2353         |       and_expression:exp1 AND equality_expression:exp2 {: 
2354                 ParseNode pn=new ParseNode("bitwise_and");
2355                 pn.addChild(exp1);
2356                 pn.addChild(exp2);
2357                 RESULT=pn;
2358         :}
2359         ;
2360 exclusive_or_expression ::=
2361                 and_expression:expr {: 
2362                         RESULT=expr;
2363                 :}
2364         |       exclusive_or_expression:exp1 XOR and_expression:exp2 {: 
2365                 ParseNode pn=new ParseNode("bitwise_xor");
2366                 pn.addChild(exp1);
2367                 pn.addChild(exp2);
2368                 RESULT=pn;
2369 :}
2370         ;
2371 inclusive_or_expression ::=
2372                 exclusive_or_expression:exclor {: 
2373                         RESULT=exclor; :}
2374         |       inclusive_or_expression:exp1 OR exclusive_or_expression:exp2 {: 
2375                 ParseNode pn=new ParseNode("bitwise_or");
2376                 pn.addChild(exp1);
2377                 pn.addChild(exp2);
2378                 RESULT=pn;
2379         :}
2380         ;
2381 conditional_and_expression ::=
2382                 inclusive_or_expression:inclor {: 
2383                         RESULT=inclor; :}
2384         |       conditional_and_expression:exp1 ANDAND inclusive_or_expression:exp2 {:
2385                 ParseNode pn=new ParseNode("logical_and");
2386                 pn.addChild(exp1);
2387                 pn.addChild(exp2);
2388                 RESULT=pn;
2389         :}
2390         ;
2391 conditional_or_expression ::=
2392                 conditional_and_expression:condand {: 
2393                         RESULT=condand; :}
2394         |       conditional_or_expression:exp1 OROR conditional_and_expression:exp2 {: 
2395                 ParseNode pn=new ParseNode("logical_or");
2396                 pn.addChild(exp1);
2397                 pn.addChild(exp2);
2398                 RESULT=pn;
2399         :}
2400         ;
2401 conditional_expression ::=
2402                 conditional_or_expression:condor {: 
2403                         RESULT=condor; :}
2404         |       conditional_or_expression:condor QUESTION expression:exptrue
2405                         COLON conditional_expression:expfalse {: 
2406                         ParseNode pn=new ParseNode("tert");
2407                         pn.addChild("cond").addChild(condor);
2408                         pn.addChild("trueexpr").addChild(exptrue);
2409                         pn.addChild("falseexpr").addChild(expfalse);
2410                         RESULT=pn;
2411                         :}
2412         ;
2413 getoffset_expression ::=
2414         GETOFFSET LBRACE class_or_interface_type:type COMMA IDENTIFIER:id RBRACE {:
2415         ParseNode pn = new ParseNode("getoffset");
2416         pn.addChild(type);
2417         pn.addChild("field").addChild(id);
2418         RESULT = pn;
2419       :}
2420    ;
2421  
2422 assignment_expression ::=
2423                 conditional_expression:expr {: 
2424                         RESULT=expr; :} |
2425                 assignment:assign {: 
2426                         RESULT=assign; :}             |
2427         getoffset_expression:expr {:
2428             RESULT=expr; :}
2429         ;
2430 // semantic check necessary here to ensure a valid left-hand side.
2431 // allowing a parenthesized variable here on the lhs was introduced in
2432 // JLS 2; thanks to Eric Blake for pointing this out.
2433 assignment ::=  postfix_expression:lvalue assignment_operator:op assignment_expression:rvalue {:
2434                 ParseNode pn=new ParseNode("assignment");
2435                 pn.addChild("op").addChild(op);
2436                 ParseNode pnargs=pn.addChild("args");
2437                 pnargs.addChild(lvalue);
2438                 pnargs.addChild(rvalue);
2439                 RESULT=pn;
2440          :}
2441         ;
2442 assignment_operator ::=
2443                 EQ {: RESULT=new ParseNode("eq"); :}
2444         |       MULTEQ {: RESULT=new ParseNode("multeq"); :}
2445         |       DIVEQ {: RESULT=new ParseNode("diveq"); :}
2446         |       MODEQ {: RESULT=new ParseNode("modeq"); :}
2447         |       PLUSEQ {: RESULT=new ParseNode("pluseq"); :}
2448         |       MINUSEQ {: RESULT=new ParseNode("minuseq"); :}
2449         |       LSHIFTEQ {: RESULT=new ParseNode("lshifteq"); :}
2450         |       RSHIFTEQ {: RESULT=new ParseNode("rshifteq"); :}
2451         |       URSHIFTEQ {: RESULT=new ParseNode("urshifteq"); :}
2452         |       ANDEQ {: RESULT=new ParseNode("andeq"); :}
2453         |       XOREQ {: RESULT=new ParseNode("xoreq"); :}
2454         |       OREQ {: RESULT=new ParseNode("oreq"); :}
2455         ;
2456 expression_opt ::=
2457         {:      RESULT=new ParseNode("empty"); :}
2458         |       expression:exp {: 
2459                 RESULT=exp; :}
2460         ;
2461 expression ::=  assignment_expression:exp {: 
2462                 RESULT=exp; :}
2463         ;
2464 // note that this constraint must be enforced during semantic checking
2465 // 'constant_expression' should include enumerated constants.
2466 constant_expression ::=
2467                 expression:exp 
2468                 {:
2469                     ParseNode pn = new ParseNode("constant_expression");
2470                     pn.addChild(exp);
2471                     RESULT=pn;
2472                 :}
2473         ;
2474
2475
2476 genreach_statement ::=
2477                 GENREACH IDENTIFIER:graphName SEMICOLON {: 
2478                 ParseNode pn=new ParseNode("genreach");
2479                 pn.addChild("graphName").addChild(graphName);
2480                 RESULT=pn; :}
2481         ;