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