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