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