source: trunk/yao/share/antlr-2.7.7/examples/cpp/flexLexer/java.g @ 1

Last change on this file since 1 was 1, checked in by lnalod, 15 years ago

Initial import of YAO sources

File size: 27.2 KB
Line 
1options {
2        language="Cpp";
3}
4
5/** Java 1.3 Recognizer
6 *
7 * Run 'java Main [-showtree] directory-full-of-java-files'
8 *
9 * [The -showtree option pops up a Swing frame that shows
10 *  the AST constructed from the parser.]
11 *
12 * Run 'java Main <directory full of java files>'
13 *
14 * Contributing authors:
15 *              John Mitchell           johnm@non.net
16 *              Terence Parr            parrt@magelang.com
17 *              John Lilley                     jlilley@empathy.com
18 *              Scott Stanchfield       thetick@magelang.com
19 *              Markus Mohnen       mohnen@informatik.rwth-aachen.de
20 *      Peter Williams      pete.williams@sun.com
21 *      Allan Jacobs        Allan.Jacobs@eng.sun.com
22 *      Steve Messick       messick@redhills.com
23 *      John Pybus                      john@pybus.org
24 *
25 * Version 1.00 December 9, 1997 -- initial release
26 * Version 1.01 December 10, 1997
27 *              fixed bug in octal def (0..7 not 0..8)
28 * Version 1.10 August 1998 (parrt)
29 *              added tree construction
30 *              fixed definition of WS,comments for mac,pc,unix newlines
31 *              added unary plus
32 * Version 1.11 (Nov 20, 1998)
33 *              Added "shutup" option to turn off last ambig warning.
34 *              Fixed inner class def to allow named class defs as statements
35 *              synchronized requires compound not simple statement
36 *              add [] after builtInType DOT class in primaryExpression
37 *              "const" is reserved but not valid..removed from modifiers
38 * Version 1.12 (Feb 2, 1999)
39 *              Changed LITERAL_xxx to xxx in tree grammar.
40 *              Updated java.g to use tokens {...} now for 2.6.0 (new feature).
41 *
42 * Version 1.13 (Apr 23, 1999)
43 *              Didn't have (stat)? for else clause in tree parser.
44 *              Didn't gen ASTs for interface extends.  Updated tree parser too.
45 *              Updated to 2.6.0.
46 * Version 1.14 (Jun 20, 1999)
47 *              Allowed final/abstract on local classes.
48 *              Removed local interfaces from methods
49 *              Put instanceof precedence where it belongs...in relationalExpr
50 *                      It also had expr not type as arg; fixed it.
51 *              Missing ! on SEMI in classBlock
52 *              fixed: (expr) + "string" was parsed incorrectly (+ as unary plus).
53 *              fixed: didn't like Object[].class in parser or tree parser
54 * Version 1.15 (Jun 26, 1999)
55 *              Screwed up rule with instanceof in it. :(  Fixed.
56 *              Tree parser didn't like (expr).something; fixed.
57 *              Allowed multiple inheritance in tree grammar. oops.
58 * Version 1.16 (August 22, 1999)
59 *              Extending an interface built a wacky tree: had extra EXTENDS.
60 *              Tree grammar didn't allow multiple superinterfaces.
61 *              Tree grammar didn't allow empty var initializer: {}
62 * Version 1.17 (October 12, 1999)
63 *              ESC lexer rule allowed 399 max not 377 max.
64 *              java.tree.g didn't handle the expression of synchronized
65 *              statements.
66 * Version 1.18 (August 12, 2001)
67 *              Terence updated to Java 2 Version 1.3 by
68 *              observing/combining work of Allan Jacobs and Steve
69 *              Messick.  Handles 1.3 src.  Summary:
70 *              o  primary didn't include boolean.class kind of thing
71 *              o  constructor calls parsed explicitly now:
72 *                 see explicitConstructorInvocation
73 *              o  add strictfp modifier
74 *              o  missing objBlock after new expression in tree grammar
75 *              o  merged local class definition alternatives, moved after declaration
76 *              o  fixed problem with ClassName.super.field
77 *              o  reordered some alternatives to make things more efficient
78 *              o  long and double constants were not differentiated from int/float
79 *              o  whitespace rule was inefficient: matched only one char
80 *              o  add an examples directory with some nasty 1.3 cases
81 *              o  made Main.java use buffered IO and a Reader for Unicode support
82 *              o  supports UNICODE?
83 *                 Using Unicode charVocabulay makes code file big, but only
84 *                 in the bitsets at the end. I need to make ANTLR generate
85 *                 unicode bitsets more efficiently.
86 * Version 1.19 (April 25, 2002)
87 *              Terence added in nice fixes by John Pybus concerning floating
88 *              constants and problems with super() calls.  John did a nice
89 *              reorg of the primary/postfix expression stuff to read better
90 *              and makes f.g.super() parse properly (it was METHOD_CALL not
91 *              a SUPER_CTOR_CALL).  Also:
92 *
93 *              o  "finally" clause was a root...made it a child of "try"
94 *              o  Added stuff for asserts too for Java 1.4, but *commented out*
95 *                 as it is not backward compatible.
96 *
97 * Version 1.20 (October 27, 2002)
98 *
99 *      Terence ended up reorging John Pybus' stuff to
100 *      remove some nondeterminisms and some syntactic predicates.
101 *      Note that the grammar is stricter now; e.g., this(...) must
102 *      be the first statement.
103 *
104 *      Trinary ?: operator wasn't working as array name:
105 *          (isBig ? bigDigits : digits)[i];
106 *
107 *      Checked parser/tree parser on source for
108 *          Resin-2.0.5, jive-2.1.1, jdk 1.3.1, Lucene, antlr 2.7.2a4,
109 *          and the 110k-line jGuru server source.
110 *
111 * Version 1.21 (October 17, 2003)
112 *      Fixed lots of problems including:
113 *      Ray Waldin: add typeDefinition to interfaceBlock in java.tree.g
114 *  He found a problem/fix with floating point that start with 0
115 *  Ray also fixed problem that (int.class) was not recognized.
116 *  Thorsten van Ellen noticed that \n are allowed incorrectly in strings.
117 *  TJP fixed CHAR_LITERAL analogously.
118 *
119 * This grammar is in the PUBLIC DOMAIN
120 */
121class JavaRecognizer extends Parser;
122options {
123        k = 2;                           // two token lookahead
124        exportVocab=Java;                // Call its vocabulary "Java"
125        codeGenMakeSwitchThreshold = 2;  // Some optimizations
126        codeGenBitsetTestThreshold = 3;
127        defaultErrorHandler = false;     // Don't generate parser error handlers
128        buildAST = true;
129}
130
131tokens {
132        BLOCK; MODIFIERS; OBJBLOCK; SLIST; CTOR_DEF; METHOD_DEF; VARIABLE_DEF;
133        INSTANCE_INIT; STATIC_INIT; TYPE; CLASS_DEF; INTERFACE_DEF;
134        PACKAGE_DEF; ARRAY_DECLARATOR; EXTENDS_CLAUSE; IMPLEMENTS_CLAUSE;
135        PARAMETERS; PARAMETER_DEF; LABELED_STAT; TYPECAST; INDEX_OP;
136        POST_INC; POST_DEC; METHOD_CALL; EXPR; ARRAY_INIT;
137        IMPORT; UNARY_MINUS; UNARY_PLUS; CASE_GROUP; ELIST; FOR_INIT; FOR_CONDITION;
138        FOR_ITERATOR; EMPTY_STAT; FINAL="final"; ABSTRACT="abstract";
139        STRICTFP="strictfp"; SUPER_CTOR_CALL; CTOR_CALL;
140}
141
142// Compilation Unit: In Java, this is a single file.  This is the start
143//   rule for this parser
144compilationUnit
145        :       // A compilation unit starts with an optional package definition
146                (       packageDefinition
147                |       /* nothing */
148                )
149
150                // Next we have a series of zero or more import statements
151                ( importDefinition )*
152
153                // Wrapping things up with any number of class or interface
154                //    definitions
155                ( typeDefinition )*
156
157                EOF!
158        ;
159
160// Package statement: "package" followed by an identifier.
161packageDefinition
162        options {defaultErrorHandler = true;} // let ANTLR handle errors
163        :       p:"package"^ {#p->setType(PACKAGE_DEF);} identifier SEMI!
164        ;
165
166// Import statement: import followed by a package or class name
167importDefinition
168        options {defaultErrorHandler = true;}
169        :       i:"import"^ {#i->setType(IMPORT);} identifierStar SEMI!
170        ;
171
172// A type definition in a file is either a class or interface definition.
173typeDefinition
174        options {defaultErrorHandler = true;}
175        :       m:modifiers!
176                ( classDefinition[#m]
177                | interfaceDefinition[#m]
178                )
179        |       SEMI!
180        ;
181
182/** A declaration is the creation of a reference or primitive-type variable
183 *  Create a separate Type/Var tree for each var in the var list.
184 */
185declaration!
186        :       m:modifiers t:typeSpec[false] v:variableDefinitions[#m,#t]
187                {#declaration = #v;}
188        ;
189
190// A type specification is a type name with possible brackets afterwards
191//   (which would make it an array type).
192typeSpec[bool addImagNode]
193        : classTypeSpec[addImagNode]
194        | builtInTypeSpec[addImagNode]
195        ;
196
197// A class type specification is a class type with possible brackets afterwards
198//   (which would make it an array type).
199classTypeSpec[bool addImagNode]
200        :       identifier (lb:LBRACK^ {#lb->setType(ARRAY_DECLARATOR);} RBRACK!)*
201                {
202                        if ( addImagNode ) {
203                                #classTypeSpec = #(#[TYPE,"TYPE"], #classTypeSpec);
204                        }
205                }
206        ;
207
208// A builtin type specification is a builtin type with possible brackets
209// afterwards (which would make it an array type).
210builtInTypeSpec[bool addImagNode]
211        :       builtInType (lb:LBRACK^ {#lb->setType(ARRAY_DECLARATOR);} RBRACK!)*
212                {
213                        if ( addImagNode ) {
214                                #builtInTypeSpec = #(#[TYPE,"TYPE"], #builtInTypeSpec);
215                        }
216                }
217        ;
218
219// A type name. which is either a (possibly qualified) class name or
220//   a primitive (builtin) type
221type
222        :       identifier
223        |       builtInType
224        ;
225
226// The primitive types.
227builtInType
228        :       "void"
229        |       "boolean"
230        |       "byte"
231        |       "char"
232        |       "short"
233        |       "int"
234        |       "float"
235        |       "long"
236        |       "double"
237        ;
238
239// A (possibly-qualified) java identifier.  We start with the first IDENT
240//   and expand its name by adding dots and following IDENTS
241identifier
242        :       IDENT  ( DOT^ IDENT )*
243        ;
244
245identifierStar
246        :       IDENT
247                ( DOT^ IDENT )*
248                ( DOT^ STAR  )?
249        ;
250
251// A list of zero or more modifiers.  We could have used (modifier)* in
252//   place of a call to modifiers, but I thought it was a good idea to keep
253//   this rule separate so they can easily be collected in a Vector if
254//   someone so desires
255modifiers
256        :       ( modifier )*
257                {#modifiers = #([MODIFIERS, "MODIFIERS"], #modifiers);}
258        ;
259
260// modifiers for Java classes, interfaces, class/instance vars and methods
261modifier
262        :       "private"
263        |       "public"
264        |       "protected"
265        |       "static"
266        |       "transient"
267        |       "final"
268        |       "abstract"
269        |       "native"
270        |       "threadsafe"
271        |       "synchronized"
272//      |       "const"                 // reserved word, but not valid
273        |       "volatile"
274        |       "strictfp"
275        ;
276
277// Definition of a Java class
278classDefinition![ANTLR_USE_NAMESPACE(antlr)RefAST modifiers]
279        :       "class" IDENT
280                // it _might_ have a superclass...
281                sc:superClassClause
282                // it might implement some interfaces...
283                ic:implementsClause
284                // now parse the body of the class
285                cb:classBlock
286                {#classDefinition = #(#[CLASS_DEF,"CLASS_DEF"],
287                                                           modifiers,IDENT,sc,ic,cb);}
288        ;
289
290superClassClause!
291        :       ( "extends" id:identifier )?
292                {#superClassClause = #(#[EXTENDS_CLAUSE,"EXTENDS_CLAUSE"],id);}
293        ;
294
295// Definition of a Java Interface
296interfaceDefinition![ANTLR_USE_NAMESPACE(antlr)RefAST modifiers]
297        :       "interface" IDENT
298                // it might extend some other interfaces
299                ie:interfaceExtends
300                // now parse the body of the interface (looks like a class...)
301                cb:classBlock
302                {#interfaceDefinition = #(#[INTERFACE_DEF,"INTERFACE_DEF"],
303                                                                        modifiers,IDENT,ie,cb);}
304        ;
305
306// This is the body of a class.  You can have fields and extra semicolons,
307// That's about it (until you see what a field is...)
308classBlock
309        :       LCURLY!
310                        ( field | SEMI! )*
311                RCURLY!
312                {#classBlock = #([OBJBLOCK, "OBJBLOCK"], #classBlock);}
313        ;
314
315// An interface can extend several other interfaces...
316interfaceExtends
317        :       (
318                e:"extends"!
319                identifier ( COMMA! identifier )*
320                )?
321                {#interfaceExtends = #(#[EXTENDS_CLAUSE,"EXTENDS_CLAUSE"],
322                                                        #interfaceExtends);}
323        ;
324
325// A class can implement several interfaces...
326implementsClause
327        :       (
328                        i:"implements"! identifier ( COMMA! identifier )*
329                )?
330                {#implementsClause = #(#[IMPLEMENTS_CLAUSE,"IMPLEMENTS_CLAUSE"],
331                                                                 #implementsClause);}
332        ;
333
334// Now the various things that can be defined inside a class or interface...
335// Note that not all of these are really valid in an interface (constructors,
336//   for example), and if this grammar were used for a compiler there would
337//   need to be some semantic checks to make sure we're doing the right thing...
338field!
339        :       // method, constructor, or variable declaration
340                mods:modifiers
341                (       h:ctorHead s:constructorBody // constructor
342                        {#field = #(#[CTOR_DEF,"CTOR_DEF"], mods, h, s);}
343
344                |       cd:classDefinition[#mods]       // inner class
345                        {#field = #cd;}
346
347                |       id:interfaceDefinition[#mods]   // inner interface
348                        {#field = #id;}
349
350                |       t:typeSpec[false]  // method or variable declaration(s)
351                        (       IDENT  // the name of the method
352
353                                // parse the formal parameter declarations.
354                                LPAREN! param:parameterDeclarationList RPAREN!
355
356                                rt:declaratorBrackets[#t]
357
358                                // get the list of exceptions that this method is
359                                // declared to throw
360                                (tc:throwsClause)?
361
362                                ( s2:compoundStatement | SEMI )
363                                {#field = #(#[METHOD_DEF,"METHOD_DEF"],
364                                                     mods,
365                                                         #(#[TYPE,"TYPE"],rt),
366                                                         IDENT,
367                                                         param,
368                                                         tc,
369                                                         s2);}
370                        |       v:variableDefinitions[#mods,#t] SEMI
371//                              {#field = #(#[VARIABLE_DEF,"VARIABLE_DEF"], v);}
372                                {#field = #v;}
373                        )
374                )
375
376    // "static { ... }" class initializer
377        |       "static" s3:compoundStatement
378                {#field = #(#[STATIC_INIT,"STATIC_INIT"], s3);}
379
380    // "{ ... }" instance initializer
381        |       s4:compoundStatement
382                {#field = #(#[INSTANCE_INIT,"INSTANCE_INIT"], s4);}
383        ;
384
385constructorBody
386    :   lc:LCURLY^ {#lc->setType(SLIST);}
387            ( options { greedy=true; } : explicitConstructorInvocation)?
388            (statement)*
389        RCURLY!
390    ;
391
392/** Catch obvious constructor calls, but not the expr.super(...) calls */
393explicitConstructorInvocation
394    :   "this"! lp1:LPAREN^ argList RPAREN! SEMI!
395                {#lp1->setType(CTOR_CALL);}
396    |   "super"! lp2:LPAREN^ argList RPAREN! SEMI!
397                {#lp2->setType(SUPER_CTOR_CALL);}
398    ;
399
400variableDefinitions[ANTLR_USE_NAMESPACE(antlr)RefAST mods, ANTLR_USE_NAMESPACE(antlr)RefAST t]
401        :       variableDeclarator[getASTFactory()->dupTree(mods),
402                                                   getASTFactory()->dupTree(t)]
403                (       COMMA!
404                        variableDeclarator[getASTFactory()->dupTree(mods),
405                                                           getASTFactory()->dupTree(t)]
406                )*
407        ;
408
409/** Declaration of a variable.  This can be a class/instance variable,
410 *   or a local variable in a method
411 * It can also include possible initialization.
412 */
413variableDeclarator![ANTLR_USE_NAMESPACE(antlr)RefAST mods, ANTLR_USE_NAMESPACE(antlr)RefAST t]
414        :       id:IDENT d:declaratorBrackets[t] v:varInitializer
415                {#variableDeclarator = #(#[VARIABLE_DEF,"VARIABLE_DEF"], mods, #(#[TYPE,"TYPE"],d), id, v);}
416        ;
417
418declaratorBrackets[ANTLR_USE_NAMESPACE(antlr)RefAST typ]
419        :       {#declaratorBrackets=typ;}
420                (lb:LBRACK^ {#lb->setType(ARRAY_DECLARATOR);} RBRACK!)*
421        ;
422
423varInitializer
424        :       ( ASSIGN^ initializer )?
425        ;
426
427// This is an initializer used to set up an array.
428arrayInitializer
429        :       lc:LCURLY^ {#lc->setType(ARRAY_INIT);}
430                        (       initializer
431                                (
432                                        // CONFLICT: does a COMMA after an initializer start a new
433                                        //           initializer or start the option ',' at end?
434                                        //           ANTLR generates proper code by matching
435                                        //                       the comma as soon as possible.
436                                        options {
437                                                warnWhenFollowAmbig = false;
438                                        }
439                                :
440                                        COMMA! initializer
441                                )*
442                                (COMMA!)?
443                        )?
444                RCURLY!
445        ;
446
447// The two "things" that can initialize an array element are an expression
448//   and another (nested) array initializer.
449initializer
450        :       expression
451        |       arrayInitializer
452        ;
453
454// This is the header of a method.  It includes the name and parameters
455//   for the method.
456//   This also watches for a list of exception classes in a "throws" clause.
457ctorHead
458        :       IDENT  // the name of the method
459
460                // parse the formal parameter declarations.
461                LPAREN! parameterDeclarationList RPAREN!
462
463                // get the list of exceptions that this method is declared to throw
464                (throwsClause)?
465        ;
466
467// This is a list of exception classes that the method is declared to throw
468throwsClause
469        :       "throws"^ identifier ( COMMA! identifier )*
470        ;
471
472// A list of formal parameters
473parameterDeclarationList
474        :       ( parameterDeclaration ( COMMA! parameterDeclaration )* )?
475                {#parameterDeclarationList = #(#[PARAMETERS,"PARAMETERS"],
476                                                                        #parameterDeclarationList);}
477        ;
478
479// A formal parameter.
480parameterDeclaration!
481        :       pm:parameterModifier t:typeSpec[false] id:IDENT
482                pd:declaratorBrackets[#t]
483                {#parameterDeclaration = #(#[PARAMETER_DEF,"PARAMETER_DEF"],
484                                                                        pm, #([TYPE,"TYPE"],pd), id);}
485        ;
486
487parameterModifier
488        :       (f:"final")?
489                {#parameterModifier = #(#[MODIFIERS,"MODIFIERS"], f);}
490        ;
491
492// Compound statement.  This is used in many contexts:
493//   Inside a class definition prefixed with "static":
494//      it is a class initializer
495//   Inside a class definition without "static":
496//      it is an instance initializer
497//   As the body of a method
498//   As a completely indepdent braced block of code inside a method
499//      it starts a new scope for variable definitions
500
501compoundStatement
502        :       lc:LCURLY^ {#lc->setType(SLIST);}
503                        // include the (possibly-empty) list of statements
504                        (statement)*
505                RCURLY!
506        ;
507
508statement
509        // A list of statements in curly braces -- start a new scope!
510        :       compoundStatement
511
512        // declarations are ambiguous with "ID DOT" relative to expression
513        // statements.  Must backtrack to be sure.  Could use a semantic
514        // predicate to test symbol table to see what the type was coming
515        // up, but that's pretty hard without a symbol table ;)
516        |       (declaration)=> declaration SEMI!
517
518        // An expression statement.  This could be a method call,
519        // assignment statement, or any other expression evaluated for
520        // side-effects.
521        |       expression SEMI!
522
523        // class definition
524        |       m:modifiers! classDefinition[#m]
525
526        // Attach a label to the front of a statement
527        |       IDENT c:COLON^ {#c->setType(LABELED_STAT);} statement
528
529        // If-else statement
530        |       "if"^ LPAREN! expression RPAREN! statement
531                (
532                        // CONFLICT: the old "dangling-else" problem...
533                        //           ANTLR generates proper code matching
534                        //                       as soon as possible.  Hush warning.
535                        options {
536                                warnWhenFollowAmbig = false;
537                        }
538                :
539                        "else"! statement
540                )?
541
542        // For statement
543        |       "for"^
544                        LPAREN!
545                                forInit SEMI!   // initializer
546                                forCond SEMI!   // condition test
547                                forIter         // updater
548                        RPAREN!
549                        statement                     // statement to loop over
550
551        // While statement
552        |       "while"^ LPAREN! expression RPAREN! statement
553
554        // do-while statement
555        |       "do"^ statement "while"! LPAREN! expression RPAREN! SEMI!
556
557        // get out of a loop (or switch)
558        |       "break"^ (IDENT)? SEMI!
559
560        // do next iteration of a loop
561        |       "continue"^ (IDENT)? SEMI!
562
563        // Return an expression
564        |       "return"^ (expression)? SEMI!
565
566        // switch/case statement
567        |       "switch"^ LPAREN! expression RPAREN! LCURLY!
568                        ( casesGroup )*
569                RCURLY!
570
571        // exception try-catch block
572        |       tryBlock
573
574        // throw an exception
575        |       "throw"^ expression SEMI!
576
577        // synchronize a statement
578        |       "synchronized"^ LPAREN! expression RPAREN! compoundStatement
579
580        // asserts (uncomment if you want 1.4 compatibility)
581        // |    "assert"^ expression ( COLON! expression )? SEMI!
582
583        // empty statement
584        |       s:SEMI {#s->setType(EMPTY_STAT);}
585        ;
586
587casesGroup
588        :       (       // CONFLICT: to which case group do the statements bind?
589                        //           ANTLR generates proper code: it groups the
590                        //           many "case"/"default" labels together then
591                        //           follows them with the statements
592                        options {
593                                greedy = true;
594                        }
595                        :
596                        aCase
597                )+
598                caseSList
599                {#casesGroup = #([CASE_GROUP, "CASE_GROUP"], #casesGroup);}
600        ;
601
602aCase
603        :       ("case"^ expression | "default") COLON!
604        ;
605
606caseSList
607        :       (statement)*
608                {#caseSList = #(#[SLIST,"SLIST"],#caseSList);}
609        ;
610
611// The initializer for a for loop
612forInit
613                // if it looks like a declaration, it is
614        :       (       (declaration)=> declaration
615                // otherwise it could be an expression list...
616                |       expressionList
617                )?
618                {#forInit = #(#[FOR_INIT,"FOR_INIT"],#forInit);}
619        ;
620
621forCond
622        :       (expression)?
623                {#forCond = #(#[FOR_CONDITION,"FOR_CONDITION"],#forCond);}
624        ;
625
626forIter
627        :       (expressionList)?
628                {#forIter = #(#[FOR_ITERATOR,"FOR_ITERATOR"],#forIter);}
629        ;
630
631// an exception handler try/catch block
632tryBlock
633        :       "try"^ compoundStatement
634                (handler)*
635                ( finallyClause )?
636        ;
637
638finallyClause
639        :       "finally"^ compoundStatement
640        ;
641
642// an exception handler
643handler
644        :       "catch"^ LPAREN! parameterDeclaration RPAREN! compoundStatement
645        ;
646
647// expressions
648// Note that most of these expressions follow the pattern
649//   thisLevelExpression :
650//       nextHigherPrecedenceExpression
651//           (OPERATOR nextHigherPrecedenceExpression)*
652// which is a standard recursive definition for a parsing an expression.
653// The operators in java have the following precedences:
654//    lowest  (13)  = *= /= %= += -= <<= >>= >>>= &= ^= |=
655//            (12)  ?:
656//            (11)  ||
657//            (10)  &&
658//            ( 9)  |
659//            ( 8)  ^
660//            ( 7)  &
661//            ( 6)  == !=
662//            ( 5)  < <= > >=
663//            ( 4)  << >>
664//            ( 3)  +(binary) -(binary)
665//            ( 2)  * / %
666//            ( 1)  ++ -- +(unary) -(unary)  ~  !  (type)
667//                  []   () (method call)  . (dot -- identifier qualification)
668//                  new   ()  (explicit parenthesis)
669//
670// the last two are not usually on a precedence chart; I put them in
671// to point out that new has a higher precedence than '.', so you
672// can validy use
673//     new Frame().show()
674//
675// Note that the above precedence levels map to the rules below...
676// Once you have a precedence chart, writing the appropriate rules as below
677//   is usually very straightfoward
678
679// the mother of all expressions
680expression
681        :       assignmentExpression
682                {#expression = #(#[EXPR,"EXPR"],#expression);}
683        ;
684
685// This is a list of expressions.
686expressionList
687        :       expression (COMMA! expression)*
688                {#expressionList = #(#[ELIST,"ELIST"], expressionList);}
689        ;
690
691// assignment expression (level 13)
692assignmentExpression
693        :       conditionalExpression
694                (       (       ASSIGN^
695            |   PLUS_ASSIGN^
696            |   MINUS_ASSIGN^
697            |   STAR_ASSIGN^
698            |   DIV_ASSIGN^
699            |   MOD_ASSIGN^
700            |   SR_ASSIGN^
701            |   BSR_ASSIGN^
702            |   SL_ASSIGN^
703            |   BAND_ASSIGN^
704            |   BXOR_ASSIGN^
705            |   BOR_ASSIGN^
706            )
707                        assignmentExpression
708                )?
709        ;
710
711// conditional test (level 12)
712conditionalExpression
713        :       logicalOrExpression
714                ( QUESTION^ assignmentExpression COLON! conditionalExpression )?
715        ;
716
717// logical or (||)  (level 11)
718logicalOrExpression
719        :       logicalAndExpression (LOR^ logicalAndExpression)*
720        ;
721
722// logical and (&&)  (level 10)
723logicalAndExpression
724        :       inclusiveOrExpression (LAND^ inclusiveOrExpression)*
725        ;
726
727// bitwise or non-short-circuiting or (|)  (level 9)
728inclusiveOrExpression
729        :       exclusiveOrExpression (BOR^ exclusiveOrExpression)*
730        ;
731
732// exclusive or (^)  (level 8)
733exclusiveOrExpression
734        :       andExpression (BXOR^ andExpression)*
735        ;
736
737// bitwise or non-short-circuiting and (&)  (level 7)
738andExpression
739        :       equalityExpression (BAND^ equalityExpression)*
740        ;
741
742// equality/inequality (==/!=) (level 6)
743equalityExpression
744        :       relationalExpression ((NOT_EQUAL^ | EQUAL^) relationalExpression)*
745        ;
746
747// boolean relational expressions (level 5)
748relationalExpression
749        :       shiftExpression
750                (       (       (       LT_^
751                                |       GT^
752                                |       LE^
753                                |       GE^
754                                )
755                                shiftExpression
756                        )*
757                |       "instanceof"^ typeSpec[true]
758                )
759        ;
760
761// bit shift expressions (level 4)
762shiftExpression
763        :       additiveExpression ((SL^ | SR^ | BSR^) additiveExpression)*
764        ;
765
766// binary addition/subtraction (level 3)
767additiveExpression
768        :       multiplicativeExpression ((PLUS^ | MINUS^) multiplicativeExpression)*
769        ;
770
771// multiplication/division/modulo (level 2)
772multiplicativeExpression
773        :       unaryExpression ((STAR^ | DIV^ | MOD^ ) unaryExpression)*
774        ;
775
776unaryExpression
777        :       INC^ unaryExpression
778        |       DEC^ unaryExpression
779        |       MINUS^ {#MINUS->setType(UNARY_MINUS);} unaryExpression
780        |       PLUS^  {#PLUS->setType(UNARY_PLUS);} unaryExpression
781        |       unaryExpressionNotPlusMinus
782        ;
783
784unaryExpressionNotPlusMinus
785        :       BNOT^ unaryExpression
786        |       LNOT^ unaryExpression
787                // use predicate to skip cases like: (int.class)
788        |       (LPAREN builtInTypeSpec[true] RPAREN) =>
789                lpb:LPAREN^ {#lpb->setType(TYPECAST);}
790                        builtInTypeSpec[true]
791                RPAREN!
792                unaryExpression
793
794                // Have to backtrack to see if operator follows.  If no operator
795                // follows, it's a typecast.  No semantic checking needed to parse.
796                // if it _looks_ like a cast, it _is_ a cast; else it's a "(expr)"
797        |       (LPAREN classTypeSpec[true] RPAREN unaryExpressionNotPlusMinus)=>
798                        lp:LPAREN^ {#lp->setType(TYPECAST);} classTypeSpec[true] RPAREN!
799                        unaryExpressionNotPlusMinus
800        |       postfixExpression
801        ;
802
803// qualified names, array expressions, method invocation, post inc/dec
804postfixExpression
805        :
806    /*
807    "this"! lp1:LPAREN^ argList RPAREN!
808                {#lp1->setType(CTOR_CALL);}
809
810    |   "super"! lp2:LPAREN^ argList RPAREN!
811                {#lp2->setType(SUPER_CTOR_CALL);}
812    |
813    */
814        primaryExpression
815
816                (
817            /*
818            options {
819                                // the use of postfixExpression in SUPER_CTOR_CALL adds DOT
820                                // to the lookahead set, and gives loads of false non-det
821                                // warnings.
822                                // shut them off.
823                                generateAmbigWarnings=false;
824                        }
825                :       */
826            DOT^ IDENT
827                        (       lp:LPAREN^ {#lp->setType(METHOD_CALL);}
828                                argList
829                                RPAREN!
830                        )?
831                |       DOT^ "this"
832
833                |       DOT^ "super"
834            (   // (new Outer()).super()  (create enclosing instance)
835                lp3:LPAREN^ argList RPAREN!
836                {#lp3->setType(SUPER_CTOR_CALL);}
837                        |   DOT^ IDENT
838                (       lps:LPAREN^ {#lps->setType(METHOD_CALL);}
839                    argList
840                    RPAREN!
841                )?
842            )
843                |       DOT^ newExpression
844                |       lb:LBRACK^ {#lb->setType(INDEX_OP);} expression RBRACK!
845                )*
846
847                (   // possibly add on a post-increment or post-decrement.
848            // allows INC/DEC on too much, but semantics can check
849                        in:INC^ {#in->setType(POST_INC);}
850                |       de:DEC^ {#de->setType(POST_DEC);}
851                )?
852        ;
853
854// the basic element of an expression
855primaryExpression
856        :       identPrimary ( options {greedy=true;} : DOT^ "class" )?
857    |   constant
858        |       "true"
859        |       "false"
860        |       "null"
861    |   newExpression
862        |       "this"
863        |       "super"
864        |       LPAREN! assignmentExpression RPAREN!
865                // look for int.class and int[].class
866        |       builtInType
867                ( lbt:LBRACK^ {#lbt->setType(ARRAY_DECLARATOR);} RBRACK! )*
868                DOT^ "class"
869        ;
870
871/** Match a, a.b.c refs, a.b.c(...) refs, a.b.c[], a.b.c[].class,
872 *  and a.b.c.class refs.  Also this(...) and super(...).  Match
873 *  this or super.
874 */
875identPrimary
876        :       IDENT
877                (
878            options {
879                                // .ident could match here or in postfixExpression.
880                                // We do want to match here.  Turn off warning.
881                                greedy=true;
882                        }
883                :       DOT^ IDENT
884                )*
885                (
886            options {
887                                // ARRAY_DECLARATOR here conflicts with INDEX_OP in
888                                // postfixExpression on LBRACK RBRACK.
889                                // We want to match [] here, so greedy.  This overcomes
890                // limitation of linear approximate lookahead.
891                                greedy=true;
892                    }
893                :   ( lp:LPAREN^ {#lp->setType(METHOD_CALL);} argList RPAREN! )
894                |       ( options {greedy=true;} :
895              lbc:LBRACK^ {#lbc->setType(ARRAY_DECLARATOR);} RBRACK!
896            )+
897                )?
898    ;
899
900/** object instantiation.
901 *  Trees are built as illustrated by the following input/tree pairs:
902 *
903 *  new T()
904 *
905 *  new
906 *   |
907 *   T --  ELIST
908 *           |
909 *          arg1 -- arg2 -- .. -- argn
910 *
911 *  new int[]
912 *
913 *  new
914 *   |
915 *  int -- ARRAY_DECLARATOR
916 *
917 *  new int[] {1,2}
918 *
919 *  new
920 *   |
921 *  int -- ARRAY_DECLARATOR -- ARRAY_INIT
922 *                                  |
923 *                                EXPR -- EXPR
924 *                                  |      |
925 *                                  1      2
926 *
927 *  new int[3]
928 *  new
929 *   |
930 *  int -- ARRAY_DECLARATOR
931 *                |
932 *              EXPR
933 *                |
934 *                3
935 *
936 *  new int[1][2]
937 *
938 *  new
939 *   |
940 *  int -- ARRAY_DECLARATOR
941 *               |
942 *         ARRAY_DECLARATOR -- EXPR
943 *               |              |
944 *             EXPR             1
945 *               |
946 *               2
947 *
948 */
949newExpression
950        :       "new"^ type
951                (       LPAREN! argList RPAREN! (classBlock)?
952
953                        //java 1.1
954                        // Note: This will allow bad constructs like
955                        //    new int[4][][3] {exp,exp}.
956                        //    There needs to be a semantic check here...
957                        // to make sure:
958                        //   a) [ expr ] and [ ] are not mixed
959                        //   b) [ expr ] and an init are not used together
960
961                |       newArrayDeclarator (arrayInitializer)?
962                )
963        ;
964
965argList
966        :       (       expressionList
967                |       /*nothing*/
968                        {#argList = #[ELIST,"ELIST"];}
969                )
970        ;
971
972newArrayDeclarator
973        :       (
974                        // CONFLICT:
975                        // newExpression is a primaryExpression which can be
976                        // followed by an array index reference.  This is ok,
977                        // as the generated code will stay in this loop as
978                        // long as it sees an LBRACK (proper behavior)
979                        options {
980                                warnWhenFollowAmbig = false;
981                        }
982                :
983                        lb:LBRACK^ {#lb->setType(ARRAY_DECLARATOR);}
984                                (expression)?
985                        RBRACK!
986                )+
987        ;
988
989constant
990        :       NUM_INT
991        |       CHAR_LITERAL
992        |       STRING_LITERAL
993        |       NUM_FLOAT
994        |       NUM_LONG
995        |       NUM_DOUBLE
996        ;
Note: See TracBrowser for help on using the repository browser.