source: translator/Parser/cfa.y @ 2c2242c

ADTaaron-thesisarm-ehast-experimentalcleanup-dtorsctordeferred_resndemanglerenumforall-pointer-decaygc_noraiijacob/cs343-translationjenkins-sandboxmemorynew-astnew-ast-unique-exprnew-envno_listpersistent-indexerpthread-emulationqualifiedEnumresolv-newstringwith_gc
Last change on this file since 2c2242c was 6c3744e, checked in by Peter A. Buhr <pabuhr@…>, 10 years ago

add list initializer, formatting changes

  • Property mode set to 100644
File size: 99.7 KB
Line 
1/*                               -*- Mode: C -*-
2 *
3 * CForall Grammar Version 1.0, Copyright (C) Peter A. Buhr 2001 -- Permission is granted to copy this
4 *      grammar and to use it within software systems.  THIS GRAMMAR IS PROVIDED "AS IS" AND WITHOUT
5 *      ANY EXPRESS OR IMPLIED WARRANTIES.
6 *
7 * cfa.y --
8 *
9 * Author           : Peter A. Buhr
10 * Created On       : Sat Sep  1 20:22:55 2001
11 * Last Modified By : Peter A. Buhr
12 * Last Modified On : Sat Jan 17 09:23:45 2015
13 * Update Count     : 908
14 */
15
16/* This grammar is based on the ANSI99/11 C grammar, specifically parts of EXPRESSION and STATEMENTS, and on
17   the C grammar by James A. Roskind, specifically parts of DECLARATIONS and EXTERNAL DEFINITIONS.  While
18   parts have been copied, important changes have been made in all sections; these changes are sufficient to
19   constitute a new grammar.  In particular, this grammar attempts to be more syntactically precise, i.e., it
20   parses less incorrect language syntax that must be subsequently rejected by semantic checks.  Nevertheless,
21   there are still several semantic checks required and many are noted in the grammar. Finally, the grammar is
22   extended with GCC and CFA language extensions. */
23
24/* Acknowledgments to Richard Bilson, Glen Ditchfield, and Rodolfo Gabriel Esteves who all helped when I got
25   stuck with the grammar. */
26
27/* The root language for this grammar is ANSI99/11 C. All of ANSI99/11 is parsed, except for:
28
29   1. designation with '=' (use ':' instead)
30
31   Most of the syntactic extensions from ANSI90 to ANSI11 C are marked with the comment "C99/C11". This grammar
32   also has two levels of extensions. The first extensions cover most of the GCC C extensions, except for:
33
34   1. nested functions
35   2. generalized lvalues
36   3. designation with and without '=' (use ':' instead)
37   4. attributes not allowed in parenthesis of declarator
38
39   All of the syntactic extensions for GCC C are marked with the comment "GCC". The second extensions are for
40   Cforall (CFA), which fixes several of C's outstanding problems and extends C with many modern language
41   concepts. All of the syntactic extensions for CFA C are marked with the comment "CFA". As noted above,
42   there is one unreconcileable parsing problem between C99 and CFA with respect to designators; this is
43   discussed in detail before the "designation" grammar rule. */
44
45%{
46#define YYDEBUG_LEXER_TEXT (yylval)                     /* lexer loads this up each time */
47#define YYDEBUG 1                                       /* get the pretty debugging code to compile*/
48
49#undef __GNUC_MINOR__
50
51#include <cstdio>
52#include <stack>
53#include "TypedefTable.h"
54#include "lex.h"
55#include "ParseNode.h"
56#include "LinkageSpec.h"
57
58DeclarationNode *theTree = 0;                           /* the resulting parse tree */
59LinkageSpec::Type linkage = LinkageSpec::Cforall;
60std::stack< LinkageSpec::Type > linkageStack;
61TypedefTable typedefTable;
62%}
63
64/************************* TERMINAL TOKENS ********************************/
65
66/* keywords */
67%token TYPEDEF
68%token AUTO EXTERN REGISTER STATIC
69%token INLINE                                           /* C99 */
70%token FORTRAN                                          /* C99, extension ISO/IEC 9899:1999 Section J.5.9(1) */
71%token CONST VOLATILE
72%token RESTRICT                                         /* C99 */
73%token FORALL LVALUE                                    /* CFA */
74%token VOID CHAR SHORT INT LONG FLOAT DOUBLE SIGNED UNSIGNED
75%token BOOL COMPLEX IMAGINARY                           /* C99 */
76%token TYPEOF LABEL                                     /* GCC */
77%token ENUM STRUCT UNION
78%token TYPE FTYPE DTYPE CONTEXT                         /* CFA */
79%token SIZEOF
80%token ATTRIBUTE EXTENSION                              /* GCC */
81%token IF ELSE SWITCH CASE DEFAULT DO WHILE FOR BREAK CONTINUE GOTO RETURN
82%token CHOOSE FALLTHRU TRY CATCH FINALLY THROW          /* CFA */
83%token ASM                                              /* C99, extension ISO/IEC 9899:1999 Section J.5.10(1) */
84%token ALIGNAS ALIGNOF ATOMIC GENERIC NORETURN STATICASSERT THREADLOCAL /* C11 */
85
86/* names and constants: lexer differentiates between identifier and typedef names */
87%token<tok> IDENTIFIER          QUOTED_IDENTIFIER       TYPEDEFname             TYPEGENname
88%token<tok> ATTR_IDENTIFIER     ATTR_TYPEDEFname        ATTR_TYPEGENname
89%token<tok> INTEGERconstant     FLOATINGconstant        CHARACTERconstant       STRINGliteral
90%token<tok> ZERO                ONE                     /* CFA */
91
92/* multi-character operators */
93%token ARROW                    /* ->                           */
94%token ICR DECR                 /* ++   --                      */
95%token LS RS                    /* <<   >>                      */
96%token LE GE EQ NE              /* <=   >=      ==      !=      */
97%token ANDAND OROR              /* &&   ||                      */
98%token ELLIPSIS                 /* ...                          */
99
100%token MULTassign       DIVassign       MODassign       /* *=   /=      %=      */
101%token PLUSassign       MINUSassign                     /* +=   -=              */
102%token LSassign         RSassign                        /* <<=  >>=             */
103%token ANDassign        ERassign        ORassign        /* &=   ^=      |=      */
104
105/* Types declaration */
106%union
107{
108  Token tok;
109  ParseNode *pn;
110  ExpressionNode *en;
111  DeclarationNode *decl;
112  DeclarationNode::TyCon aggKey;
113  DeclarationNode::TypeClass tclass;
114  StatementNode *sn;
115  ConstantNode *constant;
116  InitializerNode *in;
117}
118
119%type<tok> zero_one  identifier  no_attr_identifier  no_01_identifier
120%type<tok> identifier_or_typedef_name  no_attr_identifier_or_typedef_name  no_01_identifier_or_typedef_name
121%type<constant> string_literal_list
122
123/* expressions */
124%type<constant> constant
125%type<en> tuple                         tuple_expression_list
126%type<en> unary_operator                assignment_operator
127%type<en> primary_expression            postfix_expression              unary_expression
128%type<en> cast_expression               multiplicative_expression       additive_expression     shift_expression
129%type<en> relational_expression         equality_expression             AND_expression          exclusive_OR_expression
130%type<en> inclusive_OR_expression       logical_AND_expression          logical_OR_expression   conditional_expression
131%type<en> constant_expression           assignment_expression           assignment_expression_opt
132%type<en> comma_expression              comma_expression_opt
133%type<en> argument_expression_list      argument_expression             for_control_expression  assignment_opt
134%type<en> subrange
135
136/* statements */
137%type<sn> labeled_statement     compound_statement      expression_statement    selection_statement
138%type<sn> iteration_statement   jump_statement          exception_statement     asm_statement
139%type<sn> fall_through_opt      fall_through
140%type<sn> statement             statement_list
141%type<sn> block_item_list       block_item
142%type<sn> case_clause
143%type<en> case_value            case_value_list
144%type<sn> case_label            case_label_list
145%type<sn> switch_clause_list_opt switch_clause_list     choose_clause_list_opt  choose_clause_list
146%type<pn> handler_list          handler_clause          finally_clause
147
148/* declarations */
149%type<decl> abstract_array abstract_declarator abstract_function abstract_parameter_array
150%type<decl> abstract_parameter_declaration abstract_parameter_declarator abstract_parameter_function
151%type<decl> abstract_parameter_ptr abstract_ptr
152
153%type<aggKey> aggregate_key
154%type<decl>  aggregate_name
155
156%type<decl> array_dimension array_parameter_1st_dimension array_parameter_dimension multi_array_dimension
157
158%type<decl> assertion assertion_list_opt
159
160%type<en>   bit_subrange_size_opt bit_subrange_size
161
162%type<decl> basic_declaration_specifier basic_type_name basic_type_specifier direct_type_name indirect_type_name
163
164%type<decl> context_declaration context_declaration_list context_declaring_list context_specifier
165
166%type<decl> declaration declaration_list declaration_list_opt declaration_qualifier_list
167%type<decl> declaration_specifier declarator declaring_list
168
169%type<decl> elaborated_type_name
170
171%type<decl> enumerator_list enum_name
172%type<en> enumerator_value_opt
173
174%type<decl> exception_declaration external_definition external_definition_list external_definition_list_opt
175
176%type<decl> field_declaration field_declaration_list field_declarator field_declaring_list
177%type<en> field field_list
178
179%type<decl> function_array function_declarator function_definition function_no_ptr function_ptr
180
181%type<decl> identifier_parameter_array identifier_parameter_declarator identifier_parameter_function
182%type<decl> identifier_parameter_ptr identifier_list
183
184%type<decl> new_abstract_array new_abstract_declarator_no_tuple new_abstract_declarator_tuple
185%type<decl> new_abstract_function new_abstract_parameter_declaration new_abstract_parameter_list
186%type<decl> new_abstract_ptr new_abstract_tuple
187
188%type<decl> new_array_parameter_1st_dimension
189
190%type<decl> new_context_declaring_list new_declaration new_field_declaring_list
191%type<decl> new_function_declaration new_function_return new_function_specifier
192
193%type<decl> new_identifier_parameter_array new_identifier_parameter_declarator_no_tuple
194%type<decl> new_identifier_parameter_declarator_tuple new_identifier_parameter_ptr
195
196%type<decl> new_parameter_declaration new_parameter_list new_parameter_type_list new_parameter_type_list_opt
197
198%type<decl> new_typedef_declaration new_variable_declaration new_variable_specifier
199
200%type<decl> old_declaration old_declaration_list old_declaration_list_opt old_function_array
201%type<decl> old_function_declarator old_function_no_ptr old_function_ptr
202
203%type<decl> parameter_declaration parameter_list parameter_type_list
204%type<decl> parameter_type_list_opt
205
206%type<decl> paren_identifier paren_typedef
207
208%type<decl> storage_class storage_class_name storage_class_list
209
210%type<decl> sue_declaration_specifier sue_type_specifier
211
212%type<tclass> type_class
213%type<decl> type_declarator type_declarator_name type_declaring_list
214
215%type<decl> typedef typedef_array typedef_declaration typedef_declaration_specifier typedef_expression
216%type<decl> typedef_function typedef_parameter_array typedef_parameter_function typedef_parameter_ptr
217%type<decl> typedef_parameter_redeclarator typedef_ptr typedef_redeclarator typedef_type_specifier
218%type<decl> typegen_declaration_specifier typegen_type_specifier
219
220%type<decl> type_name type_name_no_function
221%type<decl> type_parameter type_parameter_list
222
223%type<en> type_name_list
224
225%type<decl> type_qualifier type_qualifier_name type_qualifier_list type_qualifier_list_opt type_specifier
226
227%type<decl> variable_abstract_array variable_abstract_declarator variable_abstract_function
228%type<decl> variable_abstract_ptr variable_array variable_declarator variable_function variable_ptr
229
230/* initializers */
231%type<in>  initializer initializer_list initializer_opt
232
233/* designators */
234%type<en>  designator designator_list designation
235
236
237/* Handle single shift/reduce conflict for dangling else by shifting the ELSE token. For example, this string
238   is ambiguous:
239   .---------.                  matches IF '(' comma_expression ')' statement
240   if ( C ) S1 else S2
241   `-----------------'  matches IF '(' comma_expression ')' statement ELSE statement */
242
243%nonassoc THEN  /* rule precedence for IF '(' comma_expression ')' statement */
244%nonassoc ELSE  /* token precedence for start of else clause in IF statement */
245
246%start translation_unit                                 /* parse-tree root */
247
248%%
249/************************* Namespace Management ********************************/
250
251/* The grammar in the ANSI C standard is not strictly context-free, since it relies upon the distinct terminal
252   symbols "identifier" and "TYPEDEFname" that are lexically identical.  While it is possible to write a
253   purely context-free grammar, such a grammar would obscure the relationship between syntactic and semantic
254   constructs.  Hence, this grammar uses the ANSI style.
255
256   Cforall compounds this problem by introducing type names local to the scope of a declaration (for instance,
257   those introduced through "forall" qualifiers), and by introducing "type generators" -- parametrized types.
258   This latter type name creates a third class of identifiers that must be distinguished by the scanner.
259
260   Since the scanner cannot distinguish among the different classes of identifiers without some context
261   information, it accesses a data structure (the TypedefTable) to allow classification of an identifier that
262   it has just read.  Semantic actions during the parser update this data structure when the class of
263   identifiers change.
264
265   Because the Cforall language is block-scoped, there is the possibility that an identifier can change its
266   class in a local scope; it must revert to its original class at the end of the block.  Since type names can
267   be local to a particular declaration, each declaration is itself a scope.  This requires distinguishing
268   between type names that are local to the current declaration scope and those that persist past the end of
269   the declaration (i.e., names defined in "typedef" or "type" declarations).
270
271   The non-terminals "push" and "pop" derive the empty string; their only use is to denote the opening and
272   closing of scopes.  Every push must have a matching pop, although it is regrettable the matching pairs do
273   not always occur within the same rule.  These non-terminals may appear in more contexts than strictly
274   necessary from a semantic point of view.  Unfortunately, these extra rules are necessary to prevent parsing
275   conflicts -- the parser may not have enough context and look-ahead information to decide whether a new
276   scope is necessary, so the effect of these extra rules is to open a new scope unconditionally.  As the
277   grammar evolves, it may be neccesary to add or move around "push" and "pop" nonterminals to resolve
278   conflicts of this sort.  */
279
280push:
281                {
282                    typedefTable.enterScope();
283                }
284        ;
285
286pop:
287                {
288                    typedefTable.leaveScope();
289                }
290        ;
291
292/************************* CONSTANTS ********************************/
293
294constant:
295                /* ENUMERATIONconstant is not included here; it is treated as a variable with type
296                   "enumeration constant". */
297        INTEGERconstant                                 { $$ = new ConstantNode(ConstantNode::Integer,   $1); }
298        | FLOATINGconstant                              { $$ = new ConstantNode(ConstantNode::Float,     $1); }
299        | CHARACTERconstant                             { $$ = new ConstantNode(ConstantNode::Character, $1); }
300        ;
301
302identifier:
303        IDENTIFIER
304        | ATTR_IDENTIFIER                               /* CFA */
305        | zero_one                                      /* CFA */
306        ;
307
308no_01_identifier:
309        IDENTIFIER
310        | ATTR_IDENTIFIER                               /* CFA */
311        ;
312
313no_attr_identifier:
314        IDENTIFIER
315        ;
316
317zero_one:                                               /* CFA */
318        ZERO
319        | ONE
320        ;
321
322string_literal_list:                                    /* juxtaposed strings are concatenated */
323        STRINGliteral                                   { $$ = new ConstantNode(ConstantNode::String, $1); }
324        | string_literal_list STRINGliteral             { $$ = $1->append( $2 ); }
325        ;
326
327/************************* EXPRESSIONS ********************************/
328
329primary_expression:
330        IDENTIFIER                                      /* typedef name cannot be used as a variable name */
331                { $$ = new VarRefNode($1); }
332        | zero_one
333                { $$ = new VarRefNode($1); }
334        | constant
335                { $$ = $1; }
336        | string_literal_list
337                { $$ = $1; }
338        | '(' comma_expression ')'
339                { $$ = $2; }
340        | '(' compound_statement ')'                    /* GCC, lambda expression */
341                { $$ = new ValofExprNode($2); }
342        ;
343
344postfix_expression:
345        primary_expression
346        | postfix_expression '[' push assignment_expression pop ']'
347                 /* CFA, comma_expression disallowed in the context because it results in a commom user error:
348                    subscripting a matrix with x[i,j] instead of x[i][j]. While this change is not backwards
349                    compatible, there seems to be little advantage to this feature and many disadvantages. It
350                    is possible to write x[(i,j)] in CFA, which is equivalent to the old x[i,j]. */
351                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Index), $1, $4); }
352        | postfix_expression '(' argument_expression_list ')'
353                { $$ = new CompositeExprNode($1, $3); }
354        | postfix_expression '.' no_attr_identifier
355                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::FieldSel), $1, new VarRefNode($3)); }
356        | postfix_expression '.' '[' push field_list pop ']' /* CFA, tuple field selector */
357        | postfix_expression ARROW no_attr_identifier
358                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::PFieldSel), $1, new VarRefNode($3)); }
359        | postfix_expression ARROW '[' push field_list pop ']' /* CFA, tuple field selector */
360        | postfix_expression ICR
361                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::IncrPost), $1); }
362        | postfix_expression DECR
363                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::DecrPost), $1); }
364                /* GCC has priority: cast_expression */
365        | '(' type_name_no_function ')' '{' initializer_list comma_opt '}' /* C99 */
366                { $$ = 0; }
367        ;
368
369argument_expression_list:
370        argument_expression
371        | argument_expression_list ',' argument_expression
372                                                        { $$ = (ExpressionNode *)($1->set_link($3)); }
373        ;
374
375argument_expression:
376        /* empty */                                     /* use default argument */
377                { $$ = 0; }
378        | assignment_expression
379        | no_attr_identifier ':' assignment_expression
380                                                        { $$ = $3->set_asArgName($1); }
381                /* Only a list of no_attr_identifier_or_typedef_name is allowed in this context. However, there
382                   is insufficient look ahead to distinguish between this list of parameter names and a tuple,
383                   so the tuple form must be used with an appropriate semantic check. */
384        | '[' push assignment_expression pop ']' ':' assignment_expression
385                                                { $$ = $7->set_asArgName($3); }
386        | '[' push assignment_expression ',' tuple_expression_list pop ']' ':' assignment_expression
387                                                { $$ = $9->set_asArgName(new CompositeExprNode( new OperatorNode( OperatorNode::TupleC ), (ExpressionNode *)$3->set_link( flattenCommas( $5 )))); }
388        ;
389
390field_list:                                             /* CFA, tuple field selector */
391        field
392        | field_list ',' field                          { $$ = (ExpressionNode *)$1->set_link( $3 ); }
393        ;
394
395field:                                                  /* CFA, tuple field selector */
396        no_attr_identifier
397                                                        { $$ = new VarRefNode( $1 ); }
398        | no_attr_identifier '.' field
399                                                        { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::FieldSel), new VarRefNode( $1 ), $3); }
400        | no_attr_identifier '.' '[' push field_list pop ']'
401                                                        { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::FieldSel), new VarRefNode( $1 ), $5); }
402        | no_attr_identifier ARROW field
403                                                        { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::PFieldSel), new VarRefNode( $1 ), $3); }
404        | no_attr_identifier ARROW '[' push field_list pop ']'
405                                                        { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::PFieldSel), new VarRefNode( $1 ), $5); }
406        ;
407
408unary_expression:
409        postfix_expression
410        | ICR unary_expression
411                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Incr), $2); }
412        | DECR unary_expression
413                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Decr), $2); }
414        | EXTENSION cast_expression                     /* GCC */
415                { $$ = $2; }
416        | unary_operator cast_expression
417                { $$ = new CompositeExprNode($1, $2); }
418        | '!' cast_expression
419                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Neg), $2); }
420        | '*' cast_expression                           /* CFA */
421                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::PointTo), $2); }
422                /* '*' is is separated from unary_operator because of shift/reduce conflict in:
423                        { * X; } // dereference X
424                        { * int X; } // CFA declaration of pointer to int
425                   '&' must be moved here if C++ reference variables are supported. */
426        | SIZEOF unary_expression
427                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::SizeOf), $2); }
428        | SIZEOF '(' type_name_no_function ')'
429                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::SizeOf), new TypeValueNode($3)); }
430        | ATTR_IDENTIFIER
431                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Attr), new VarRefNode($1)); }
432        | ATTR_IDENTIFIER '(' type_name ')'
433                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Attr), new VarRefNode($1), new TypeValueNode($3)); }
434        | ATTR_IDENTIFIER '(' argument_expression ')'
435                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Attr), new VarRefNode($1), $3); }
436        | ALIGNOF unary_expression                      /* GCC, variable alignment */
437                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::AlignOf), $2); }
438        | ALIGNOF '(' type_name_no_function ')'         /* GCC, type alignment */
439                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::AlignOf), new TypeValueNode($3)); }
440        | ANDAND no_attr_identifier                     /* GCC, address of label */
441                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::LabelAddress), new VarRefNode($2, true)); }
442        ;
443
444unary_operator:
445        '&'                                             { $$ = new OperatorNode(OperatorNode::AddressOf); }
446        | '+'                                           { $$ = new OperatorNode(OperatorNode::UnPlus); }
447        | '-'                                           { $$ = new OperatorNode(OperatorNode::UnMinus); }
448        | '~'                                           { $$ = new OperatorNode(OperatorNode::BitNeg); }
449        ;
450
451cast_expression:
452        unary_expression
453        | '(' type_name_no_function ')' cast_expression
454                                                        { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Cast), new TypeValueNode($2), $4); }
455        | '(' type_name_no_function ')' tuple
456                                                        { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Cast), new TypeValueNode($2), $4); }
457        ;
458
459multiplicative_expression:
460        cast_expression
461        | multiplicative_expression '*' cast_expression
462                                                        { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Mul),$1,$3); }
463        | multiplicative_expression '/' cast_expression
464                                                        { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Div),$1,$3); }
465        | multiplicative_expression '%' cast_expression
466                                                        { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Mod),$1,$3); }
467        ;
468
469additive_expression:
470        multiplicative_expression
471        | additive_expression '+' multiplicative_expression
472                                                        { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Plus),$1,$3); }
473        | additive_expression '-' multiplicative_expression
474                                                        { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Minus),$1,$3); }
475        ;
476
477shift_expression:
478        additive_expression
479        | shift_expression LS additive_expression
480                                                        { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::LShift),$1,$3); }
481        | shift_expression RS additive_expression
482                                                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::RShift),$1,$3); }
483        ;
484
485relational_expression:
486        shift_expression
487        | relational_expression '<' shift_expression
488                                                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::LThan),$1,$3); }
489        | relational_expression '>' shift_expression
490                                                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::GThan),$1,$3); }
491        | relational_expression LE shift_expression
492                                                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::LEThan),$1,$3); }
493        | relational_expression GE shift_expression
494                                                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::GEThan),$1,$3); }
495        ;
496
497equality_expression:
498        relational_expression
499        | equality_expression EQ relational_expression
500                                                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Eq), $1, $3); }
501        | equality_expression NE relational_expression
502                                                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Neq), $1, $3); }
503        ;
504
505AND_expression:
506        equality_expression
507        | AND_expression '&' equality_expression
508                                                { $$ =new CompositeExprNode(new OperatorNode(OperatorNode::BitAnd), $1, $3); }
509        ;
510
511exclusive_OR_expression:
512        AND_expression
513        | exclusive_OR_expression '^' AND_expression
514                                                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Xor), $1, $3); }
515        ;
516
517inclusive_OR_expression:
518        exclusive_OR_expression
519        | inclusive_OR_expression '|' exclusive_OR_expression
520                                                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::BitOr), $1, $3); }
521        ;
522
523logical_AND_expression:
524        inclusive_OR_expression
525        | logical_AND_expression ANDAND inclusive_OR_expression
526                                                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::And), $1, $3); }
527        ;
528
529logical_OR_expression:
530        logical_AND_expression
531        | logical_OR_expression OROR logical_AND_expression
532                                                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Or), $1, $3); }
533        ;
534
535conditional_expression:
536        logical_OR_expression
537        | logical_OR_expression '?' comma_expression ':' conditional_expression
538                                                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Cond),
539                                                                       (ExpressionNode *)mkList((*$1,*$3,*$5))); }
540        | logical_OR_expression '?' /* empty */ ':' conditional_expression /* GCC, omitted first operand */
541                                                { $$=new CompositeExprNode(new OperatorNode(OperatorNode::NCond),$1,$4); }
542        | logical_OR_expression '?' comma_expression ':' tuple /* CFA, tuple expression */
543                                                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Cond),
544                                                                       (ExpressionNode *)mkList(( *$1, *$3, *$5 ))); }
545        ;
546
547constant_expression:
548        conditional_expression
549        ;
550
551assignment_expression:
552                /* CFA, assignment is separated from assignment_operator to ensure no assignment operations
553                   for tuples */
554        conditional_expression
555        | unary_expression '=' assignment_expression
556                                                        { $$ =new CompositeExprNode(new OperatorNode(OperatorNode::Assign), $1, $3); }
557        | unary_expression assignment_operator assignment_expression
558                                                        { $$ =new CompositeExprNode($2, $1, $3); }
559        | tuple assignment_opt                          /* CFA, tuple expression */
560                {
561                  if ( $2 == 0 ) {
562                    $$ = $1;
563                  } else {
564                    $$ = new CompositeExprNode( new OperatorNode( OperatorNode::Assign ), $1, $2 );
565                  }
566                }
567        ;
568
569assignment_expression_opt:
570        /* empty */
571                { $$ = new NullExprNode; }
572        | assignment_expression
573        ;
574
575tuple:                                                  /* CFA, tuple */
576                /* CFA, one assignment_expression is factored out of comma_expression to eliminate a
577                   shift/reduce conflict with comma_expression in new_identifier_parameter_array and
578                   new_abstract_array */
579        '[' push pop ']'
580                { $$ = new CompositeExprNode( new OperatorNode( OperatorNode::TupleC ) ); }
581        | '[' push assignment_expression pop ']'
582                { $$ = new CompositeExprNode( new OperatorNode( OperatorNode::TupleC ), $3 ); }
583        | '[' push ',' tuple_expression_list pop ']'
584                { $$ = new CompositeExprNode( new OperatorNode( OperatorNode::TupleC ), (ExpressionNode *)(new NullExprNode)->set_link( $4 ) ); }
585        | '[' push assignment_expression ',' tuple_expression_list pop ']'
586                { $$ = new CompositeExprNode( new OperatorNode( OperatorNode::TupleC ), (ExpressionNode *)$3->set_link( flattenCommas( $5 ) ) ); }
587        ;
588
589tuple_expression_list:
590        assignment_expression_opt
591        | tuple_expression_list ',' assignment_expression_opt
592                { $$ = (ExpressionNode *)$1->set_link( $3 ); }
593        ;
594
595assignment_operator:
596        MULTassign                                      { $$ = new OperatorNode(OperatorNode::MulAssn);   }
597        | DIVassign                                     { $$ = new OperatorNode(OperatorNode::DivAssn);   }
598        | MODassign                                     { $$ = new OperatorNode(OperatorNode::ModAssn);   }
599        | PLUSassign                                    { $$ = new OperatorNode(OperatorNode::PlusAssn);  }
600        | MINUSassign                                   { $$ = new OperatorNode(OperatorNode::MinusAssn); }
601        | LSassign                                      { $$ = new OperatorNode(OperatorNode::LSAssn);    }
602        | RSassign                                      { $$ = new OperatorNode(OperatorNode::RSAssn);    }
603        | ANDassign                                     { $$ = new OperatorNode(OperatorNode::AndAssn);   }
604        | ERassign                                      { $$ = new OperatorNode(OperatorNode::ERAssn);    }
605        | ORassign                                      { $$ = new OperatorNode(OperatorNode::OrAssn);    }
606        ;
607
608comma_expression:
609        assignment_expression
610        | comma_expression ',' assignment_expression    /* { $$ = (ExpressionNode *)$1->add_to_list($3); } */
611                               { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Comma),$1,$3); }
612        ;
613
614comma_expression_opt:
615        /* empty */                                     { $$ = 0; }
616        | comma_expression
617        ;
618
619/*************************** STATEMENTS *******************************/
620
621statement:
622        labeled_statement
623        | compound_statement
624        | expression_statement                          { $$ = $1; }
625        | selection_statement
626        | iteration_statement
627        | jump_statement
628        | exception_statement
629        | asm_statement
630        ;
631
632labeled_statement:
633        no_attr_identifier ':' attribute_list_opt statement
634                { $$ = $4->add_label($1);}
635        ;
636
637compound_statement:
638        '{' '}'
639                { $$ = new CompoundStmtNode( (StatementNode *)0 ); }
640        | '{'
641                /* Two scopes are necessary because the block itself has a scope, but every declaration within
642                   the block also requires its own scope */
643          push push
644          label_declaration_opt                         /* GCC, local labels */
645          block_item_list pop '}'                       /* C99, intermix declarations and statements */
646                { $$ = new CompoundStmtNode( $5 ); }
647        ;
648
649block_item_list:                                        /* C99 */
650        block_item
651        | block_item_list push block_item
652                { if ($1 != 0) { $1->set_link($3); $$ = $1; } }
653        ;
654
655block_item:
656        declaration                                     /* CFA, new & old style declarations */
657                { $$ = new StatementNode( $1 ); }
658        | EXTENSION declaration                         /* GCC */
659                { $$ = new StatementNode( $2 ); }
660        | statement pop
661        ;
662
663statement_list:
664        statement
665        | statement_list statement
666                { if ($1 != 0) { $1->set_link($2); $$ = $1; } }
667        ;
668
669expression_statement:
670        comma_expression_opt ';'
671                { $$ = new StatementNode(StatementNode::Exp, $1, 0); }
672        ;
673
674selection_statement:
675        IF '(' comma_expression ')' statement           %prec THEN
676                /* explicitly deal with the shift/reduce conflict on if/else */
677                { $$ = new StatementNode(StatementNode::If, $3, $5); }
678        | IF '(' comma_expression ')' statement ELSE statement
679                { $$ = new StatementNode(StatementNode::If, $3, (StatementNode *)mkList((*$5, *$7)) ); }
680        | SWITCH '(' comma_expression ')' case_clause   /* CFA */
681                { $$ = new StatementNode(StatementNode::Switch, $3, $5); }
682        | SWITCH '(' comma_expression ')' '{' push declaration_list_opt switch_clause_list_opt '}' /* CFA */
683                { $$ = new StatementNode(StatementNode::Switch, $3, $8); /* xxx */ }
684                /* The semantics of the declaration list is changed to include any associated initialization,
685                   which is performed *before* the transfer to the appropriate case clause.  Statements after
686                   the initial declaration list can never be executed, and therefore, are removed from the
687                   grammar even though C allows it. */
688        | CHOOSE '(' comma_expression ')' case_clause   /* CFA */
689                { $$ = new StatementNode(StatementNode::Choose, $3, $5); }
690        | CHOOSE '(' comma_expression ')' '{' push declaration_list_opt choose_clause_list_opt '}' /* CFA */
691                { $$ = new StatementNode(StatementNode::Choose, $3, $8); }
692        ;
693
694/* CASE and DEFAULT clauses are only allowed in the SWITCH statement, precluding Duff's device. In addition, a
695   case clause allows a list of values and subranges. */
696
697case_value:                                             /* CFA */
698        constant_expression                     { $$ = $1; }
699        | constant_expression ELLIPSIS constant_expression /* GCC, subrange */
700                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Range),$1,$3); }
701        | subrange                                      /* CFA, subrange */
702        ;
703
704case_value_list:                                        /* CFA */
705        case_value
706        | case_value_list ',' case_value
707                {  $$ = new CompositeExprNode(new OperatorNode( OperatorNode::TupleC ), (ExpressionNode *)(tupleContents($1))->set_link($3) ); }
708        ;
709
710case_label:                                             /* CFA */
711        CASE case_value_list ':'                {  $$ = new StatementNode(StatementNode::Case, $2, 0); }
712        | DEFAULT ':'                           {  $$ = new StatementNode(StatementNode::Default);     }
713                /* A semantic check is required to ensure only one default clause per switch/choose
714                   statement. */
715        ;
716
717case_label_list:                                        /* CFA */
718        case_label
719        | case_label_list case_label            { $$ = (StatementNode *)($1->set_link($2)); }
720        ;
721
722case_clause:                                            /* CFA */
723        case_label_list statement               {  $$ = $1->append_last_case($2); }
724        ;
725
726switch_clause_list_opt:                                 /* CFA */
727        /* empty */                             { $$ = 0; }
728        | switch_clause_list
729        ;
730
731switch_clause_list:                                     /* CFA */
732        case_label_list statement_list
733                                                { $$ = $1->append_last_case($2); }
734        | switch_clause_list case_label_list statement_list
735                                                { $$ = (StatementNode *)($1->set_link($2->append_last_case($3))); }
736        ;
737
738choose_clause_list_opt:                                 /* CFA */
739        /* empty */                             { $$ = 0; }
740        | choose_clause_list
741        ;
742
743choose_clause_list:                                     /* CFA */
744        case_label_list fall_through
745                  { $$ = $1->append_last_case($2); }
746        | case_label_list statement_list fall_through_opt
747                  { $$ = $1->append_last_case((StatementNode *)mkList((*$2,*$3))); }
748        | choose_clause_list case_label_list fall_through
749                  { $$ = (StatementNode *)($1->set_link($2->append_last_case($3))); }
750        | choose_clause_list case_label_list statement_list fall_through_opt
751                  { $$ = (StatementNode *)($1->set_link($2->append_last_case((StatementNode *)mkList((*$3,*$4))))); }
752        ;
753
754fall_through_opt:                                       /* CFA */
755        /* empty */                             { $$ = 0; }
756        | fall_through
757        ;
758
759fall_through:                                           /* CFA */
760        FALLTHRU                                { $$ = new StatementNode(StatementNode::Fallthru, 0, 0); }
761        | FALLTHRU ';'                          { $$ = new StatementNode(StatementNode::Fallthru, 0, 0); }
762        ;
763
764iteration_statement:
765        WHILE '(' comma_expression ')' statement
766                                                { $$ = new StatementNode(StatementNode::While, $3, $5); }
767        | DO statement WHILE '(' comma_expression ')' ';'
768                                                { $$ = new StatementNode(StatementNode::Do, $5, $2); }
769        | FOR '(' push for_control_expression ')' statement
770                                                { $$ = new StatementNode(StatementNode::For, $4, $6); }
771        ;
772
773for_control_expression:
774        comma_expression_opt pop ';' comma_expression_opt ';' comma_expression_opt
775                                                { $$ = new ForCtlExprNode($1, $4, $6); }
776        | declaration comma_expression_opt ';' comma_expression_opt /* C99 */
777                /* Like C++, the loop index can be declared local to the loop. */
778                                                { $$ = new ForCtlExprNode($1, $2, $4); }
779        ;
780
781jump_statement:
782        GOTO no_attr_identifier ';'
783                                                { $$ = new StatementNode(StatementNode::Goto, $2); }
784        | GOTO '*' comma_expression ';'         /* GCC, computed goto */
785                /* The syntax for the GCC computed goto violates normal expression precedence, e.g.,
786                   goto *i+3; => goto *(i+3); whereas normal operator precedence yields goto (*i)+3; */
787                                                { $$ = new StatementNode(StatementNode::Goto, $3); }
788        | CONTINUE ';'
789                /* A semantic check is required to ensure this statement appears only in the body of an
790                   iteration statement. */
791                                                { $$ = new StatementNode(StatementNode::Continue, 0, 0); }
792        | CONTINUE no_attr_identifier ';'       /* CFA, multi-level continue */
793                /* A semantic check is required to ensure this statement appears only in the body of an
794                   iteration statement, and the target of the transfer appears only at the start of an
795                   iteration statement. */
796                                                { $$ = new StatementNode(StatementNode::Continue, $2); }
797        | BREAK ';'
798                /* A semantic check is required to ensure this statement appears only in the body of an
799                   iteration statement. */
800                                                { $$ = new StatementNode(StatementNode::Break, 0, 0); }
801        | BREAK no_attr_identifier ';'  /* CFA, multi-level exit */
802                /* A semantic check is required to ensure this statement appears only in the body of an
803                   iteration statement, and the target of the transfer appears only at the start of an
804                   iteration statement. */
805                                                { $$ = new StatementNode(StatementNode::Break, $2 ); }
806        | RETURN comma_expression_opt ';'
807                                                { $$ = new StatementNode(StatementNode::Return, $2, 0); }
808        | THROW assignment_expression ';'
809                                                { $$ = new StatementNode(StatementNode::Throw, $2, 0); }
810        | THROW ';'
811                                                { $$ = new StatementNode(StatementNode::Throw, 0, 0); }
812        ;
813
814exception_statement:
815        TRY compound_statement handler_list
816                             { $$ = new StatementNode(StatementNode::Try, 0,(StatementNode *)(mkList((*$2,*$3)))); }
817        | TRY compound_statement finally_clause
818                             { $$ = new StatementNode(StatementNode::Try, 0,(StatementNode *)(mkList((*$2,*$3)))); }
819        | TRY compound_statement handler_list finally_clause
820                             {
821                               $3->set_link($4);
822                               $$ = new StatementNode(StatementNode::Try, 0,(StatementNode *)(mkList((*$2,*$3))));
823                             }
824        ;
825
826handler_list:
827                /* There must be at least one catch clause */
828        handler_clause
829                /* ISO/IEC 9899:1999 Section 15.3(6) If present, a "..." handler shall be the last handler for
830                   its try block. */
831        | CATCH '(' ELLIPSIS ')' compound_statement
832                                                { $$ = StatementNode::newCatchStmt( 0, $5, true ); }
833        | handler_clause CATCH '(' ELLIPSIS ')' compound_statement
834                                                { $$ = $1->set_link( StatementNode::newCatchStmt( 0, $6, true ) ); }
835        ;
836
837handler_clause:
838        CATCH '(' push push exception_declaration pop ')' compound_statement pop
839                                                { $$ = StatementNode::newCatchStmt($5, $8); }
840        | handler_clause CATCH '(' push push exception_declaration pop ')' compound_statement pop
841                                                { $$ = $1->set_link( StatementNode::newCatchStmt($6, $9) );   }
842        ;
843
844finally_clause:
845        FINALLY compound_statement
846                                                { $$ = new StatementNode(StatementNode::Finally, 0, $2);
847                                                  std::cout << "Just created a finally node" << std::endl;
848                                                }
849        ;
850
851exception_declaration:
852                /* A semantic check is required to ensure type_specifier does not create a new type, e.g.:
853
854                        catch ( struct { int i; } x ) ...
855
856                   This new type cannot catch any thrown type because of name equivalence among types. */
857        type_specifier
858        | type_specifier declarator
859                {
860                    typedefTable.addToEnclosingScope( TypedefTable::ID );
861                    $$ = $2->addType( $1 );
862                }
863        | type_specifier variable_abstract_declarator
864                {   $$ = $2->addType( $1 ); }
865        | new_abstract_declarator_tuple no_attr_identifier /* CFA */
866                {
867                    typedefTable.addToEnclosingScope( TypedefTable::ID );
868                    $$ = $1->addName( $2 );
869                }
870        | new_abstract_declarator_tuple                 /* CFA */
871        ;
872
873asm_statement:
874        ASM type_qualifier_list_opt '(' constant_expression ')' ';'
875                                                { $$ = new StatementNode(StatementNode::Asm, 0, 0); }
876        | ASM type_qualifier_list_opt '(' constant_expression ':' asm_operands_opt ')' ';' /* remaining GCC */
877                                                { $$ = new StatementNode(StatementNode::Asm, 0, 0); }
878        | ASM type_qualifier_list_opt '(' constant_expression ':' asm_operands_opt ':' asm_operands_opt ')' ';'
879                                                { $$ = new StatementNode(StatementNode::Asm, 0, 0); }
880        | ASM type_qualifier_list_opt '(' constant_expression ':' asm_operands_opt ':' asm_operands_opt ':'
881                        asm_clobbers_list ')' ';'
882                                                { $$ = new StatementNode(StatementNode::Asm, 0, 0); }
883        ;
884
885asm_operands_opt:                                       /* GCC */
886        /* empty */
887        | asm_operands_list
888        ;
889
890asm_operands_list:                                      /* GCC */
891        asm_operand
892        | asm_operands_list ',' asm_operand
893        ;
894
895asm_operand:                                            /* GCC */
896        STRINGliteral '(' constant_expression ')'       {}
897        ;
898
899asm_clobbers_list:                                      /* GCC */
900        STRINGliteral                           {}
901        | asm_clobbers_list ',' STRINGliteral
902        ;
903
904/******************************* DECLARATIONS *********************************/
905
906declaration_list_opt:                                   /* used at beginning of switch statement */
907        pop
908                { $$ = 0; }
909        | declaration_list
910        ;
911
912declaration_list:
913        declaration
914        | declaration_list push declaration
915                { $$ = $1->appendList( $3 ); }
916        ;
917
918old_declaration_list_opt:                               /* used to declare parameter types in K&R style functions */
919        pop
920                { $$ = 0; }
921        | old_declaration_list
922        ;
923
924old_declaration_list:
925        old_declaration
926        | old_declaration_list push old_declaration
927                { $$ = $1->appendList( $3 ); }
928        ;
929
930label_declaration_opt:                                  /* GCC, local label */
931        /* empty */
932        | label_declaration_list
933        ;
934
935label_declaration_list:                                 /* GCC, local label */
936        LABEL label_list ';'
937        | label_declaration_list LABEL label_list ';'
938        ;
939
940label_list:                                             /* GCC, local label */
941        no_attr_identifier_or_typedef_name              {}
942        | label_list ',' no_attr_identifier_or_typedef_name {}
943        ;
944
945declaration:                                            /* CFA, new & old style declarations */
946        new_declaration
947        | old_declaration
948        ;
949
950/* C declaration syntax is notoriously confusing and error prone. Cforall provides its own type, variable and
951   function declarations. CFA declarations use the same declaration tokens as in C; however, CFA places
952   declaration modifiers to the left of the base type, while C declarations place modifiers to the right of
953   the base type. CFA declaration modifiers are interpreted from left to right and the entire type
954   specification is distributed across all variables in the declaration list (as in Pascal).  ANSI C and the
955   new CFA declarations may appear together in the same program block, but cannot be mixed within a specific
956   declaration.
957
958            CFA             C
959        [10] int x;     int x[10];      // array of 10 integers
960        [10] * char y;  char *y[10];    // array of 10 pointers to char
961   */
962
963new_declaration:                                        /* CFA */
964        new_variable_declaration pop ';'
965        | new_typedef_declaration pop ';'
966        | new_function_declaration pop ';'
967        | type_declaring_list pop ';'
968        | context_specifier pop ';'
969        ;
970
971new_variable_declaration:                               /* CFA */
972        new_variable_specifier initializer_opt
973                {
974                        typedefTable.addToEnclosingScope( TypedefTable::ID);
975                        $$ = $1;
976                }
977        | declaration_qualifier_list new_variable_specifier initializer_opt
978                /* declaration_qualifier_list also includes type_qualifier_list, so a semantic check is
979                   necessary to preclude them as a type_qualifier cannot appear in that context. */
980                {
981                        typedefTable.addToEnclosingScope( TypedefTable::ID);
982                        $$ = $2->addQualifiers( $1 );
983                }
984        | new_variable_declaration pop ',' push identifier_or_typedef_name initializer_opt
985                {
986                        typedefTable.addToEnclosingScope( *$5, TypedefTable::ID);
987                        $$ = $1->appendList( $1->cloneType( $5 ) );
988                }
989        ;
990
991new_variable_specifier:                                 /* CFA */
992                /* A semantic check is required to ensure asm_name only appears on declarations with implicit
993                   or explicit static storage-class */
994        new_abstract_declarator_no_tuple identifier_or_typedef_name asm_name_opt
995                {
996                        typedefTable.setNextIdentifier( *$2 );
997                        $$ = $1->addName( $2 );
998                }
999        | new_abstract_tuple identifier_or_typedef_name asm_name_opt
1000                {
1001                        typedefTable.setNextIdentifier( *$2 );
1002                        $$ = $1->addName( $2 );
1003                }
1004        | type_qualifier_list new_abstract_tuple identifier_or_typedef_name asm_name_opt
1005                {
1006                        typedefTable.setNextIdentifier( *$3 );
1007                        $$ = $2->addQualifiers( $1 )->addName( $3 );
1008                }
1009        ;
1010
1011new_function_declaration:                               /* CFA */
1012        new_function_specifier
1013                {
1014                        typedefTable.addToEnclosingScope( TypedefTable::ID);
1015                        $$ = $1;
1016                }
1017        | declaration_qualifier_list new_function_specifier
1018                /* declaration_qualifier_list also includes type_qualifier_list, so a semantic check is
1019                   necessary to preclude them as a type_qualifier cannot appear in this context. */
1020                {
1021                        typedefTable.addToEnclosingScope( TypedefTable::ID);
1022                        $$ = $2->addQualifiers( $1 );
1023                }
1024        | new_function_declaration pop ',' push identifier_or_typedef_name
1025                {
1026                        typedefTable.addToEnclosingScope( *$5, TypedefTable::ID);
1027                        $$ = $1->appendList( $1->cloneType( $5 ) );
1028                }
1029        ;
1030
1031new_function_specifier:                                 /* CFA */
1032        '[' push pop ']' identifier '(' push new_parameter_type_list_opt pop ')'
1033                {
1034                        typedefTable.setNextIdentifier( *($5) );
1035                        $$ = DeclarationNode::newFunction( $5, DeclarationNode::newTuple( 0 ), $8, 0, true );
1036                }
1037        | '[' push pop ']' TYPEDEFname '(' push new_parameter_type_list_opt pop ')'
1038                {
1039                        typedefTable.setNextIdentifier( *($5) );
1040                        $$ = DeclarationNode::newFunction( $5, DeclarationNode::newTuple( 0 ), $8, 0, true );
1041                }
1042                /* identifier_or_typedef_name must be broken apart because of the sequence:
1043
1044                   '[' ']' identifier_or_typedef_name '(' new_parameter_type_list_opt ')'
1045                   '[' ']' type_specifier
1046
1047                   type_specifier can resolve to just TYPEDEFname (e.g. typedef int T; int f( T );). Therefore
1048                   this must be flattened to allow lookahead to the '(' without having to reduce
1049                   identifier_or_typedef_name. */
1050        | new_abstract_tuple identifier_or_typedef_name '(' push new_parameter_type_list_opt pop ')'
1051                /* To obtain LR(1), this rule must be factored out from function return type (see
1052                   new_abstract_declarator). */
1053                {
1054                        $$ = DeclarationNode::newFunction( $2, $1, $5, 0, true );
1055                }
1056        | new_function_return identifier_or_typedef_name '(' push new_parameter_type_list_opt pop ')'
1057                {
1058                        $$ = DeclarationNode::newFunction( $2, $1, $5, 0, true );
1059                }
1060        ;
1061
1062new_function_return:                                    /* CFA */
1063        '[' push new_parameter_list pop ']'
1064                { $$ = DeclarationNode::newTuple( $3 ); }
1065        | '[' push new_parameter_list pop ',' push new_abstract_parameter_list pop ']'
1066                /* To obtain LR(1), the last new_abstract_parameter_list is added into this flattened rule to
1067                   lookahead to the ']'. */
1068                { $$ = DeclarationNode::newTuple( $3->appendList( $7 ) ); }
1069        ;
1070
1071new_typedef_declaration:                                /* CFA */
1072        TYPEDEF new_variable_specifier
1073                {
1074                        typedefTable.addToEnclosingScope( TypedefTable::TD);
1075                        $$ = $2->addTypedef();
1076                }
1077        | TYPEDEF new_function_specifier
1078                {
1079                        typedefTable.addToEnclosingScope( TypedefTable::TD);
1080                        $$ = $2->addTypedef();
1081                }
1082        | new_typedef_declaration pop ',' push no_attr_identifier
1083                {
1084                        typedefTable.addToEnclosingScope( *$5, TypedefTable::TD);
1085                        $$ = $1->appendList( $1->cloneType( $5 ) );
1086                }
1087        ;
1088
1089/* Traditionally typedef is part of storage-class specifier for syntactic convenience only. Here, it is
1090   factored out as a separate form of declaration, which syntactically precludes storage-class specifiers and
1091   initialization. */
1092
1093typedef_declaration:
1094        TYPEDEF type_specifier declarator
1095                {
1096                        typedefTable.addToEnclosingScope( TypedefTable::TD);
1097                        $$ = $3->addType( $2 )->addTypedef();
1098                }
1099        | typedef_declaration pop ',' push declarator
1100                {
1101                        typedefTable.addToEnclosingScope( TypedefTable::TD);
1102                        $$ = $1->appendList( $1->cloneBaseType( $5 )->addTypedef() );
1103                }
1104        | type_qualifier_list TYPEDEF type_specifier declarator /* remaining OBSOLESCENT (see 2) */
1105                {
1106                        typedefTable.addToEnclosingScope( TypedefTable::TD);
1107                        $$ = $4->addType( $3 )->addQualifiers( $1 )->addTypedef();
1108                }
1109        | type_specifier TYPEDEF declarator
1110                {
1111                        typedefTable.addToEnclosingScope( TypedefTable::TD);
1112                        $$ = $3->addType( $1 )->addTypedef();
1113                }
1114        | type_specifier TYPEDEF type_qualifier_list declarator
1115                {
1116                        typedefTable.addToEnclosingScope( TypedefTable::TD);
1117                        $$ = $4->addQualifiers($1)->addTypedef()->addType($1);
1118                }
1119        ;
1120
1121typedef_expression:                                     /* GCC, naming expression type */
1122        TYPEDEF no_attr_identifier '=' assignment_expression
1123                {
1124                        typedefTable.addToEnclosingScope(*($2), TypedefTable::TD);
1125                        $$ = DeclarationNode::newName( 0 ); // XXX
1126                }
1127        | typedef_expression pop ',' push no_attr_identifier '=' assignment_expression
1128                {
1129                        typedefTable.addToEnclosingScope(*($5), TypedefTable::TD);
1130                        $$ = DeclarationNode::newName( 0 ); // XXX
1131                }
1132        ;
1133
1134old_declaration:
1135        declaring_list pop ';'
1136        | typedef_declaration pop ';'
1137        | typedef_expression pop ';'                    /* GCC, naming expression type */
1138        | sue_declaration_specifier pop ';'
1139        ;
1140
1141declaring_list:
1142                /* A semantic check is required to ensure asm_name only appears on declarations with implicit
1143                   or explicit static storage-class */
1144        declaration_specifier declarator asm_name_opt initializer_opt
1145                {
1146                        typedefTable.addToEnclosingScope( TypedefTable::ID);
1147                        $$ = ($2->addType( $1 ))->addInitializer($4);
1148                }
1149        | declaring_list ',' attribute_list_opt declarator asm_name_opt initializer_opt
1150                {
1151                        typedefTable.addToEnclosingScope( TypedefTable::ID);
1152                        $$ = $1->appendList( $1->cloneBaseType( $4->addInitializer($6) ) );
1153                }
1154        ;
1155
1156declaration_specifier:                                  /* type specifier + storage class */
1157        basic_declaration_specifier
1158        | sue_declaration_specifier
1159        | typedef_declaration_specifier
1160        | typegen_declaration_specifier
1161        ;
1162
1163type_specifier:                                         /* declaration specifier - storage class */
1164        basic_type_specifier
1165        | sue_type_specifier
1166        | typedef_type_specifier
1167        | typegen_type_specifier
1168        ;
1169
1170type_qualifier_list_opt:                                /* GCC, used in asm_statement */
1171        /* empty */
1172                { $$ = 0; }
1173        | type_qualifier_list
1174        ;
1175
1176type_qualifier_list:
1177                /* A semantic check is necessary to ensure a type qualifier is appropriate for the kind of
1178                   declaration.
1179
1180                   ISO/IEC 9899:1999 Section 6.7.3(4) : If the same qualifier appears more than once in the
1181                   same specifier-qualifier-list, either directly or via one or more typedefs, the behavior is
1182                   the same as if it appeared only once. */
1183        type_qualifier
1184        | type_qualifier_list type_qualifier
1185                { $$ = $1->addQualifiers( $2 ); }
1186        ;
1187
1188type_qualifier:
1189        type_qualifier_name
1190        | attribute
1191                { $$ = DeclarationNode::newQualifier( DeclarationNode::Const ); }
1192        ;
1193
1194type_qualifier_name:
1195        CONST
1196                { $$ = DeclarationNode::newQualifier( DeclarationNode::Const ); }
1197        | RESTRICT
1198                { $$ = DeclarationNode::newQualifier( DeclarationNode::Restrict ); }
1199        | VOLATILE
1200                { $$ = DeclarationNode::newQualifier( DeclarationNode::Volatile ); }
1201        | LVALUE                                        /* CFA */
1202                { $$ = DeclarationNode::newQualifier( DeclarationNode::Lvalue ); }
1203        | FORALL '('
1204                {
1205                        typedefTable.enterScope();
1206                }
1207          type_parameter_list ')'                       /* CFA */
1208                {
1209                        typedefTable.leaveScope();
1210                        $$ = DeclarationNode::newForall( $4 );
1211                }
1212        ;
1213
1214declaration_qualifier_list:
1215        storage_class_list
1216        | type_qualifier_list storage_class_list        /* remaining OBSOLESCENT (see 2) */
1217                { $$ = $1->addQualifiers( $2 ); }
1218        | declaration_qualifier_list type_qualifier_list storage_class_list
1219                { $$ = $1->addQualifiers( $2 )->addQualifiers( $3 ); }
1220        ;
1221
1222storage_class_list:
1223                /* A semantic check is necessary to ensure a storage class is appropriate for the kind of
1224                   declaration and that only one of each is specified, except for inline, which can appear
1225                   with the others.
1226
1227                   ISO/IEC 9899:1999 Section 6.7.1(2) : At most, one storage-class specifier may be given in
1228                   the declaration specifiers in a declaration. */
1229        storage_class
1230        | storage_class_list storage_class
1231                { $$ = $1->addQualifiers( $2 ); }
1232        ;
1233
1234storage_class:
1235        storage_class_name
1236        ;
1237
1238storage_class_name:
1239        AUTO
1240                { $$ = DeclarationNode::newStorageClass( DeclarationNode::Auto ); }
1241        | EXTERN
1242                { $$ = DeclarationNode::newStorageClass( DeclarationNode::Extern ); }
1243        | REGISTER
1244                { $$ = DeclarationNode::newStorageClass( DeclarationNode::Register ); }
1245        | STATIC
1246                { $$ = DeclarationNode::newStorageClass( DeclarationNode::Static ); }
1247        | INLINE                                        /* C99 */
1248                /* INLINE is essentially a storage class specifier for functions, and hence, belongs here. */
1249                { $$ = DeclarationNode::newStorageClass( DeclarationNode::Inline ); }
1250        | FORTRAN                                       /* C99 */
1251                { $$ = DeclarationNode::newStorageClass( DeclarationNode::Fortran ); }
1252        ;
1253
1254basic_type_name:
1255        CHAR
1256                { $$ = DeclarationNode::newBasicType( DeclarationNode::Char ); }
1257        | DOUBLE
1258                { $$ = DeclarationNode::newBasicType( DeclarationNode::Double ); }
1259        | FLOAT
1260                { $$ = DeclarationNode::newBasicType( DeclarationNode::Float ); }
1261        | INT
1262                { $$ = DeclarationNode::newBasicType( DeclarationNode::Int ); }
1263        | LONG
1264                { $$ = DeclarationNode::newModifier( DeclarationNode::Long ); }
1265        | SHORT
1266                { $$ = DeclarationNode::newModifier( DeclarationNode::Short ); }
1267        | SIGNED
1268                { $$ = DeclarationNode::newModifier( DeclarationNode::Signed ); }
1269        | UNSIGNED
1270                { $$ = DeclarationNode::newModifier( DeclarationNode::Unsigned ); }
1271        | VOID
1272                { $$ = DeclarationNode::newBasicType( DeclarationNode::Void ); }
1273        | BOOL                                          /* C99 */
1274                { $$ = DeclarationNode::newBasicType( DeclarationNode::Bool ); }
1275        | COMPLEX                                       /* C99 */
1276                { $$ = DeclarationNode::newBasicType( DeclarationNode::Complex ); }
1277        | IMAGINARY                                     /* C99 */
1278                { $$ = DeclarationNode::newBasicType( DeclarationNode::Imaginary ); }
1279        ;
1280
1281basic_declaration_specifier:
1282                /* A semantic check is necessary for conflicting storage classes. */
1283        basic_type_specifier
1284        | declaration_qualifier_list basic_type_specifier
1285                { $$ = $2->addQualifiers( $1 ); }
1286        | basic_declaration_specifier storage_class     /* remaining OBSOLESCENT (see 2) */
1287                { $$ = $1->addQualifiers( $2 ); }
1288        | basic_declaration_specifier storage_class type_qualifier_list
1289                { $$ = $1->addQualifiers( $2 )->addQualifiers( $3 ); }
1290        | basic_declaration_specifier storage_class basic_type_specifier
1291                { $$ = $3->addQualifiers( $2 )->addType( $1 ); }
1292        ;
1293
1294basic_type_specifier:
1295        direct_type_name
1296        | type_qualifier_list_opt indirect_type_name type_qualifier_list_opt
1297                { $$ = $2->addQualifiers( $1 )->addQualifiers( $3 ); }
1298        ;
1299
1300direct_type_name:
1301                /* A semantic check is necessary for conflicting type qualifiers. */
1302        basic_type_name
1303        | type_qualifier_list basic_type_name
1304                { $$ = $2->addQualifiers( $1 ); }
1305        | direct_type_name type_qualifier
1306                { $$ = $1->addQualifiers( $2 ); }
1307        | direct_type_name basic_type_name
1308                { $$ = $1->addType( $2 ); }
1309        ;
1310
1311indirect_type_name:
1312        TYPEOF '(' type_name ')'                        /* GCC: typeof(x) y; */
1313                { $$ = $3; }
1314        | TYPEOF '(' comma_expression ')'               /* GCC: typeof(a+b) y; */
1315                { $$ = DeclarationNode::newTypeof( $3 ); }
1316        | ATTR_TYPEGENname '(' type_name ')'            /* CFA: e.g., @type(x) y; */
1317                { $$ = DeclarationNode::newAttr( $1, $3 ); }
1318        | ATTR_TYPEGENname '(' comma_expression ')'     /* CFA: e.g., @type(a+b) y; */
1319                { $$ = DeclarationNode::newAttr( $1, $3 ); }
1320        ;
1321
1322sue_declaration_specifier:
1323        sue_type_specifier
1324        | declaration_qualifier_list sue_type_specifier
1325                { $$ = $2->addQualifiers( $1 ); }
1326        | sue_declaration_specifier storage_class       /* remaining OBSOLESCENT (see 2) */
1327                { $$ = $1->addQualifiers( $2 ); }
1328        | sue_declaration_specifier storage_class type_qualifier_list
1329                { $$ = $1->addQualifiers( $2 )->addQualifiers( $3 ); }
1330        ;
1331
1332sue_type_specifier:
1333        elaborated_type_name                            /* struct, union, enum */
1334        | type_qualifier_list elaborated_type_name
1335                { $$ = $2->addQualifiers( $1 ); }
1336        | sue_type_specifier type_qualifier
1337                { $$ = $1->addQualifiers( $2 ); }
1338        ;
1339
1340typedef_declaration_specifier:
1341        typedef_type_specifier
1342        | declaration_qualifier_list typedef_type_specifier
1343                { $$ = $2->addQualifiers( $1 ); }
1344        | typedef_declaration_specifier storage_class   /* remaining OBSOLESCENT (see 2) */
1345                { $$ = $1->addQualifiers( $2 ); }
1346        | typedef_declaration_specifier storage_class type_qualifier_list
1347                { $$ = $1->addQualifiers( $2 )->addQualifiers( $3 ); }
1348        ;
1349
1350typedef_type_specifier:                                 /* typedef types */
1351        TYPEDEFname
1352                { $$ = DeclarationNode::newFromTypedef( $1 ); }
1353        | type_qualifier_list TYPEDEFname
1354                { $$ = DeclarationNode::newFromTypedef( $2 )->addQualifiers( $1 ); }
1355        | typedef_type_specifier type_qualifier
1356                { $$ = $1->addQualifiers( $2 ); }
1357        ;
1358
1359elaborated_type_name:
1360        aggregate_name
1361        | enum_name
1362        ;
1363
1364aggregate_name:
1365        aggregate_key '{' field_declaration_list '}'
1366                { $$ = DeclarationNode::newAggregate( $1, 0, 0, 0, $3 ); }
1367        | aggregate_key no_attr_identifier_or_typedef_name
1368                { $$ = DeclarationNode::newAggregate( $1, $2, 0, 0, 0 ); }
1369        | aggregate_key no_attr_identifier_or_typedef_name '{' field_declaration_list '}'
1370                { $$ = DeclarationNode::newAggregate( $1, $2, 0, 0, $4 ); }
1371        | aggregate_key '(' push type_parameter_list pop ')' '{' field_declaration_list '}' /* CFA */
1372                { $$ = DeclarationNode::newAggregate( $1, 0, $4, 0, $8 ); }
1373        | aggregate_key '(' push type_parameter_list pop ')' no_attr_identifier_or_typedef_name /* CFA */
1374                { $$ = DeclarationNode::newAggregate( $1, $7, $4, 0, 0 ); }
1375        | aggregate_key '(' push type_parameter_list pop ')' no_attr_identifier_or_typedef_name '{' field_declaration_list '}' /* CFA */
1376                { $$ = DeclarationNode::newAggregate( $1, $7, $4, 0, $9 ); }
1377        | aggregate_key '(' push type_parameter_list pop ')' '(' type_name_list ')' '{' field_declaration_list '}' /* CFA */
1378                { $$ = DeclarationNode::newAggregate( $1, 0, $4, $8, $11 ); }
1379        | aggregate_key '(' push type_name_list pop ')' no_attr_identifier_or_typedef_name /* CFA */
1380                /* push and pop are only to prevent S/R conflicts */
1381                { $$ = DeclarationNode::newAggregate( $1, $7, 0, $4, 0 ); }
1382        | aggregate_key '(' push type_parameter_list pop ')' '(' type_name_list ')' no_attr_identifier_or_typedef_name '{' field_declaration_list '}' /* CFA */
1383                { $$ = DeclarationNode::newAggregate( $1, $10, $4, $8, $12 ); }
1384        ;
1385
1386aggregate_key:
1387        STRUCT attribute_list_opt
1388                { $$ = DeclarationNode::Struct; }
1389        | UNION attribute_list_opt
1390                { $$ = DeclarationNode::Union; }
1391        ;
1392
1393field_declaration_list:
1394        field_declaration
1395                { $$ = $1; }
1396        | field_declaration_list field_declaration
1397                { $$ = $1->appendList( $2 ); }
1398        ;
1399
1400field_declaration:
1401        new_field_declaring_list ';'                    /* CFA, new style field declaration */
1402        | EXTENSION new_field_declaring_list ';'        /* GCC */
1403                { $$ = $2; }
1404        | field_declaring_list ';'
1405        | EXTENSION field_declaring_list ';'            /* GCC */
1406                { $$ = $2; }
1407        ;
1408
1409new_field_declaring_list:                               /* CFA, new style field declaration */
1410        new_abstract_declarator_tuple                   /* CFA, no field name */
1411        | new_abstract_declarator_tuple no_attr_identifier_or_typedef_name
1412                { $$ = $1->addName( $2 ); }
1413        | new_field_declaring_list ',' no_attr_identifier_or_typedef_name
1414                { $$ = $1->appendList( $1->cloneType( $3 ) ); }
1415        | new_field_declaring_list ','                  /* CFA, no field name */
1416                { $$ = $1->appendList( $1->cloneType( 0 ) ); }
1417        ;
1418
1419field_declaring_list:
1420        type_specifier field_declarator
1421                { $$ = $2->addType( $1 ); }
1422        | field_declaring_list ',' attribute_list_opt field_declarator
1423                { $$ = $1->appendList( $1->cloneBaseType( $4 ) ); }
1424        ;
1425
1426field_declarator:
1427        /* empty */                                     /* CFA, no field name */
1428                { $$ = DeclarationNode::newName( 0 ); /* XXX */ }
1429        | bit_subrange_size                             /* no field name */
1430                { $$ = DeclarationNode::newBitfield( $1 ); }
1431        | variable_declarator bit_subrange_size_opt
1432                /* A semantic check is required to ensure bit_subrange only appears on base type int. */
1433                { $$ = $1->addBitfield( $2 ); }
1434        | typedef_redeclarator bit_subrange_size_opt
1435                /* A semantic check is required to ensure bit_subrange only appears on base type int. */
1436                { $$ = $1->addBitfield( $2 ); }
1437        | variable_abstract_declarator                  /* CFA, no field name */
1438        ;
1439
1440bit_subrange_size_opt:
1441        /* empty */
1442                { $$ = 0; }
1443        | bit_subrange_size
1444                { $$ = $1; }
1445        ;
1446
1447bit_subrange_size:
1448        ':' constant_expression
1449                { $$ = $2; }
1450        ;
1451
1452enum_key:
1453        ENUM attribute_list_opt
1454        ;
1455
1456enum_name:
1457        enum_key '{' enumerator_list comma_opt '}'
1458                { $$ = DeclarationNode::newEnum( 0, $3 ); }
1459        | enum_key no_attr_identifier_or_typedef_name '{' enumerator_list comma_opt '}'
1460                { $$ = DeclarationNode::newEnum( $2, $4 ); }
1461        | enum_key no_attr_identifier_or_typedef_name
1462                { $$ = DeclarationNode::newEnum( $2, 0 ); }
1463        ;
1464
1465enumerator_list:
1466        no_attr_identifier_or_typedef_name enumerator_value_opt
1467                { $$ = DeclarationNode::newEnumConstant( $1, $2 ); }
1468        | enumerator_list ',' no_attr_identifier_or_typedef_name enumerator_value_opt
1469                { $$ = $1->appendList( DeclarationNode::newEnumConstant( $3, $4 ) ); }
1470        ;
1471
1472enumerator_value_opt:
1473        /* empty */
1474                { $$ = 0; }
1475        | '=' constant_expression
1476                { $$ = $2; }
1477        ;
1478
1479/* Minimum of one parameter after which ellipsis is allowed only at the end. */
1480
1481new_parameter_type_list_opt:                            /* CFA */
1482        /* empty */
1483                { $$ = 0; }
1484        | new_parameter_type_list
1485        ;
1486
1487new_parameter_type_list:                                /* CFA, abstract + real */
1488        new_abstract_parameter_list
1489        | new_parameter_list
1490        | new_parameter_list pop ',' push new_abstract_parameter_list
1491                { $$ = $1->appendList( $5 ); }
1492        | new_abstract_parameter_list pop ',' push ELLIPSIS
1493                { $$ = $1->addVarArgs(); }
1494        | new_parameter_list pop ',' push ELLIPSIS
1495                { $$ = $1->addVarArgs(); }
1496        ;
1497
1498new_parameter_list:                                     /* CFA */
1499                /* To obtain LR(1) between new_parameter_list and new_abstract_tuple, the last
1500                   new_abstract_parameter_list is factored out from new_parameter_list, flattening the rules
1501                   to get lookahead to the ']'. */
1502        new_parameter_declaration
1503        | new_abstract_parameter_list pop ',' push new_parameter_declaration
1504                { $$ = $1->appendList( $5 ); }
1505        | new_parameter_list pop ',' push new_parameter_declaration
1506                { $$ = $1->appendList( $5 ); }
1507        | new_parameter_list pop ',' push new_abstract_parameter_list pop ',' push new_parameter_declaration
1508                { $$ = $1->appendList( $5 )->appendList( $9 ); }
1509        ;
1510
1511new_abstract_parameter_list:                            /* CFA, new & old style abstract */
1512        new_abstract_parameter_declaration
1513        | new_abstract_parameter_list pop ',' push new_abstract_parameter_declaration
1514                { $$ = $1->appendList( $5 ); }
1515        ;
1516
1517parameter_type_list_opt:
1518        /* empty */
1519                { $$ = 0; }
1520        | parameter_type_list
1521        ;
1522
1523parameter_type_list:
1524        parameter_list
1525        | parameter_list pop ',' push ELLIPSIS
1526                { $$ = $1->addVarArgs(); }
1527        ;
1528
1529parameter_list:                                         /* abstract + real */
1530        abstract_parameter_declaration
1531        | parameter_declaration
1532        | parameter_list pop ',' push abstract_parameter_declaration
1533                { $$ = $1->appendList( $5 ); }
1534        | parameter_list pop ',' push parameter_declaration
1535                { $$ = $1->appendList( $5 ); }
1536        ;
1537
1538/* Provides optional identifier names (abstract_declarator/variable_declarator), no initialization, different
1539   semantics for typedef name by using typedef_parameter_redeclarator instead of typedef_redeclarator, and
1540   function prototypes. */
1541
1542new_parameter_declaration:                              /* CFA, new & old style parameter declaration */
1543        parameter_declaration
1544        | new_identifier_parameter_declarator_no_tuple identifier_or_typedef_name assignment_opt
1545                { $$ = $1->addName( $2 ); }
1546        | new_abstract_tuple identifier_or_typedef_name assignment_opt
1547                /* To obtain LR(1), these rules must be duplicated here (see new_abstract_declarator). */
1548                { $$ = $1->addName( $2 ); }
1549        | type_qualifier_list new_abstract_tuple identifier_or_typedef_name assignment_opt
1550                { $$ = $2->addName( $3 )->addQualifiers( $1 ); }
1551        | new_function_specifier
1552        ;
1553
1554new_abstract_parameter_declaration:                     /* CFA, new & old style parameter declaration */
1555        abstract_parameter_declaration
1556        | new_identifier_parameter_declarator_no_tuple
1557        | new_abstract_tuple
1558                /* To obtain LR(1), these rules must be duplicated here (see new_abstract_declarator). */
1559        | type_qualifier_list new_abstract_tuple
1560                { $$ = $2->addQualifiers( $1 ); }
1561        | new_abstract_function
1562        ;
1563
1564parameter_declaration:
1565        declaration_specifier identifier_parameter_declarator assignment_opt
1566                {
1567                    typedefTable.addToEnclosingScope( TypedefTable::ID);
1568                    $$ = $2->addType( $1 )->addInitializer( new InitializerNode($3) );
1569                }
1570        | declaration_specifier typedef_parameter_redeclarator assignment_opt
1571                {
1572                    typedefTable.addToEnclosingScope( TypedefTable::ID);
1573                    $$ = $2->addType( $1 )->addInitializer( new InitializerNode($3) );
1574                }
1575        ;
1576
1577abstract_parameter_declaration:
1578        declaration_specifier
1579        | declaration_specifier abstract_parameter_declarator
1580                { $$ = $2->addType( $1 ); }
1581        ;
1582
1583/* ISO/IEC 9899:1999 Section 6.9.1(6) : "An identifier declared as a typedef name shall not be redeclared as a
1584   parameter." Because the scope of the K&R-style parameter-list sees the typedef first, the following is
1585   based only on identifiers.  The ANSI-style parameter-list can redefine a typedef name. */
1586
1587identifier_list:                                        /* K&R-style parameter list => no types */
1588        no_attr_identifier
1589                { $$ = DeclarationNode::newName( $1 ); }
1590        | identifier_list ',' no_attr_identifier
1591                { $$ = $1->appendList( DeclarationNode::newName( $3 ) ); }
1592        ;
1593
1594identifier_or_typedef_name:
1595        identifier
1596        | TYPEDEFname
1597        | TYPEGENname
1598        ;
1599
1600no_01_identifier_or_typedef_name:
1601        no_01_identifier
1602        | TYPEDEFname
1603        | TYPEGENname
1604        ;
1605
1606no_attr_identifier_or_typedef_name:
1607        no_attr_identifier
1608        | TYPEDEFname
1609        | TYPEGENname
1610        ;
1611
1612type_name_no_function:                                  /* sizeof, alignof, cast (constructor) */
1613        new_abstract_declarator_tuple                   /* CFA */
1614        | type_specifier
1615        | type_specifier variable_abstract_declarator
1616                { $$ = $2->addType( $1 ); }
1617        ;
1618
1619type_name:                                              /* typeof, assertion */
1620        new_abstract_declarator_tuple                   /* CFA */
1621        | new_abstract_function                         /* CFA */
1622        | type_specifier
1623        | type_specifier abstract_declarator
1624                { $$ = $2->addType( $1 ); }
1625        ;
1626
1627initializer_opt:
1628        /* empty */                                     { $$ = 0; }
1629        | '=' initializer                               { $$ = $2; }
1630        ;
1631
1632initializer:
1633        assignment_expression                           { $$ = new InitializerNode($1); }
1634        | '{' initializer_list comma_opt '}'            { $$ = new InitializerNode($2, true); }
1635        ;
1636
1637initializer_list:
1638        initializer
1639        | designation initializer                       { $$ = $2->set_designators( $1 ); }
1640        | initializer_list ',' initializer              { $$ = (InitializerNode *)( $1->set_link($3) ); }
1641        | initializer_list ',' designation initializer
1642                                                        { $$ = (InitializerNode *)( $1->set_link( $4->set_designators($3) ) ); }
1643        ;
1644
1645/* There is an unreconcileable parsing problem between C99 and CFA with respect to designators. The problem
1646   is use of '=' to separator the designator from the initializer value, as in:
1647
1648        int x[10] = { [1] = 3 };
1649
1650   The string "[1] = 3" can be parsed as a designator assignment or a tuple assignment.  To disambiguate this
1651   case, CFA changes the syntax from "=" to ":" as the separator between the designator and initializer. GCC
1652   does uses ":" for field selection. The optional use of the "=" in GCC, or in this case ":", cannot be
1653   supported either due to shift/reduce conflicts */
1654
1655designation:
1656        designator_list ':'                             /* C99, CFA uses ":" instead of "=" */
1657        | no_attr_identifier_or_typedef_name ':'        /* GCC, field name */
1658                                                        { $$ = new VarRefNode( $1 ); }
1659        ;
1660
1661designator_list:                                        /* C99 */
1662        designator
1663        | designator_list designator                    { $$ = (ExpressionNode *)($1->set_link( $2 )); }
1664        ;
1665
1666designator:
1667        '.' no_attr_identifier_or_typedef_name          /* C99, field name */
1668                                                        { $$ = new VarRefNode( $2 ); }
1669        | '[' push assignment_expression pop ']'        /* C99, single array element */
1670                /* assignment_expression used instead of constant_expression because of shift/reduce conflicts
1671                   with tuple. */
1672                                                        { $$ = $3; }
1673        | '[' push subrange pop ']'                     /* CFA, multiple array elements */
1674                                                        { $$ = $3; }
1675        | '[' push constant_expression ELLIPSIS constant_expression pop ']' /* GCC, multiple array elements */
1676                                                        { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Range), $3, $5); }
1677        | '.' '[' push field_list pop ']'               /* CFA, tuple field selector */
1678                                                        { $$ = $4; }
1679        ;
1680
1681/* The CFA type system is based on parametric polymorphism, the ability to declare functions with type
1682   parameters, rather than an object-oriented type system. This required four groups of extensions:
1683
1684   Overloading: function, data, and operator identifiers may be overloaded.
1685
1686   Type declarations: "type" is used to generate new types for declaring objects. Similarly, "dtype" is used
1687       for object and incomplete types, and "ftype" is used for function types. Type declarations with
1688       initializers provide definitions of new types. Type declarations with storage class "extern" provide
1689       opaque types.
1690
1691   Polymorphic functions: A forall clause declares a type parameter. The corresponding argument is inferred at
1692       the call site. A polymorphic function is not a template; it is a function, with an address and a type.
1693
1694   Specifications and Assertions: Specifications are collections of declarations parameterized by one or more
1695       types. They serve many of the purposes of abstract classes, and specification hierarchies resemble
1696       subclass hierarchies. Unlike classes, they can define relationships between types.  Assertions declare
1697       that a type or types provide the operations declared by a specification.  Assertions are normally used
1698       to declare requirements on type arguments of polymorphic functions.  */
1699
1700typegen_declaration_specifier:                          /* CFA */
1701        typegen_type_specifier
1702        | declaration_qualifier_list typegen_type_specifier
1703                { $$ = $2->addQualifiers( $1 ); }
1704        | typegen_declaration_specifier storage_class   /* remaining OBSOLESCENT (see 2) */
1705                { $$ = $1->addQualifiers( $2 ); }
1706        | typegen_declaration_specifier storage_class type_qualifier_list
1707                { $$ = $1->addQualifiers( $2 )->addQualifiers( $3 ); }
1708        ;
1709
1710typegen_type_specifier:                                 /* CFA */
1711        TYPEGENname '(' type_name_list ')'
1712                { $$ = DeclarationNode::newFromTypeGen( $1, $3 ); }
1713        | type_qualifier_list TYPEGENname '(' type_name_list ')'
1714                { $$ = DeclarationNode::newFromTypeGen( $2, $4 )->addQualifiers( $1 ); }
1715        | typegen_type_specifier type_qualifier
1716                { $$ = $1->addQualifiers( $2 ); }
1717        ;
1718
1719type_parameter_list:                                    /* CFA */
1720        type_parameter assignment_opt
1721        | type_parameter_list ',' type_parameter assignment_opt
1722                { $$ = $1->appendList( $3 ); }
1723        ;
1724
1725type_parameter:                                         /* CFA */
1726        type_class no_attr_identifier_or_typedef_name
1727                { typedefTable.addToEnclosingScope(*($2), TypedefTable::TD); }
1728          assertion_list_opt
1729                { $$ = DeclarationNode::newTypeParam( $1, $2 )->addAssertions( $4 ); }
1730        | type_specifier identifier_parameter_declarator
1731        ;
1732
1733type_class:                                             /* CFA */
1734        TYPE
1735                { $$ = DeclarationNode::Type; }
1736        | DTYPE
1737                { $$ = DeclarationNode::Ftype; }
1738        | FTYPE
1739                { $$ = DeclarationNode::Dtype; }
1740        ;
1741
1742assertion_list_opt:                                     /* CFA */
1743        /* empty */
1744                { $$ = 0; }
1745        | assertion_list_opt assertion
1746                { $$ = $1 == 0 ? $2 : $1->appendList( $2 ); }
1747        ;
1748
1749assertion:                                              /* CFA */
1750        '|' no_attr_identifier_or_typedef_name '(' type_name_list ')'
1751                {
1752                    typedefTable.openContext( *($2) );
1753                    $$ = DeclarationNode::newContextUse( $2, $4 );
1754                }
1755        | '|' '{' push context_declaration_list '}'
1756                { $$ = $4; }
1757        | '|' '(' push type_parameter_list pop ')' '{' push context_declaration_list '}' '(' type_name_list ')'
1758                { $$ = 0; }
1759        ;
1760
1761type_name_list:                                         /* CFA */
1762        type_name
1763                { $$ = new TypeValueNode( $1 ); }
1764        | assignment_expression
1765        | type_name_list ',' type_name
1766                { $$ = (ExpressionNode *)($1->set_link(new TypeValueNode( $3 ))); }
1767        | type_name_list ',' assignment_expression
1768                { $$ = (ExpressionNode *)($1->set_link($3)); }
1769        ;
1770
1771type_declaring_list:                                    /* CFA */
1772        TYPE type_declarator
1773                { $$ = $2; }
1774        | storage_class_list TYPE type_declarator
1775                { $$ = $3->addQualifiers( $1 ); }
1776        | type_declaring_list ',' type_declarator
1777                { $$ = $1->appendList( $3->copyStorageClasses( $1 ) ); }
1778        ;
1779
1780type_declarator:                                        /* CFA */
1781        type_declarator_name assertion_list_opt
1782                { $$ = $1->addAssertions( $2 ); }
1783        | type_declarator_name assertion_list_opt '=' type_name
1784                { $$ = $1->addAssertions( $2 )->addType( $4 ); }
1785        ;
1786
1787type_declarator_name:                                   /* CFA */
1788        no_attr_identifier_or_typedef_name
1789                {
1790                    typedefTable.addToEnclosingScope(*($1), TypedefTable::TD);
1791                    $$ = DeclarationNode::newTypeDecl( $1, 0 );
1792                }
1793        | no_01_identifier_or_typedef_name '(' push type_parameter_list pop ')'
1794                {
1795                    typedefTable.addToEnclosingScope(*($1), TypedefTable::TG);
1796                    $$ = DeclarationNode::newTypeDecl( $1, $4 );
1797                }
1798        ;
1799
1800context_specifier:                                      /* CFA */
1801        CONTEXT no_attr_identifier_or_typedef_name '(' push type_parameter_list pop ')' '{' '}'
1802                {
1803                    typedefTable.addToEnclosingScope(*($2), TypedefTable::ID);
1804                    $$ = DeclarationNode::newContext( $2, $5, 0 );
1805                }
1806        | CONTEXT no_attr_identifier_or_typedef_name '(' push type_parameter_list pop ')' '{'
1807                {
1808                    typedefTable.enterContext( *($2) );
1809                    typedefTable.enterScope();
1810                }
1811          context_declaration_list '}'
1812                {
1813                    typedefTable.leaveContext();
1814                    typedefTable.addToEnclosingScope(*($2), TypedefTable::ID);
1815                    $$ = DeclarationNode::newContext( $2, $5, $10 );
1816                }
1817        ;
1818
1819context_declaration_list:                               /* CFA */
1820        context_declaration
1821        | context_declaration_list push context_declaration
1822                { $$ = $1->appendList( $3 ); }
1823        ;
1824
1825context_declaration:                                    /* CFA */
1826        new_context_declaring_list pop ';'
1827        | context_declaring_list pop ';'
1828        ;
1829
1830new_context_declaring_list:                             /* CFA */
1831        new_variable_specifier
1832                {
1833                    typedefTable.addToEnclosingScope2( TypedefTable::ID );
1834                    $$ = $1;
1835                }
1836        | new_function_specifier
1837                {
1838                    typedefTable.addToEnclosingScope2( TypedefTable::ID );
1839                    $$ = $1;
1840                }
1841        | new_context_declaring_list pop ',' push identifier_or_typedef_name
1842                {
1843                    typedefTable.addToEnclosingScope2( *($5), TypedefTable::ID );
1844                    $$ = $1->appendList( $1->cloneType( $5 ) );
1845                }
1846        ;
1847
1848context_declaring_list:                                 /* CFA */
1849        type_specifier declarator
1850                {
1851                    typedefTable.addToEnclosingScope2( TypedefTable::ID);
1852                    $$ = $2->addType( $1 );
1853                }
1854        | context_declaring_list pop ',' push declarator
1855                {
1856                    typedefTable.addToEnclosingScope2( TypedefTable::ID);
1857                    $$ = $1->appendList( $1->cloneBaseType( $5 ) );
1858                }
1859        ;
1860
1861/***************************** EXTERNAL DEFINITIONS *****************************/
1862
1863translation_unit:
1864        /* empty */                                     /* empty input file */
1865                {}
1866        | external_definition_list
1867                {
1868                  if ( theTree ) {
1869                    theTree->appendList( $1 );
1870                  } else {
1871                    theTree = $1;
1872                  }
1873                }
1874        ;
1875
1876external_definition_list:
1877        external_definition
1878        | external_definition_list push external_definition
1879                {
1880                  if ( $1 ) {
1881                    $$ = $1->appendList( $3 );
1882                  } else {
1883                    $$ = $3;
1884                  }
1885                }
1886        ;
1887
1888external_definition_list_opt:
1889        /* empty */
1890                {
1891                  $$ = 0;
1892                }
1893        | external_definition_list
1894        ;
1895
1896external_definition:
1897        declaration
1898        | function_definition
1899        | asm_statement                                 /* GCC, global assembler statement */
1900                {}
1901        | EXTERN STRINGliteral
1902                {
1903                  linkageStack.push( linkage );
1904                  linkage = LinkageSpec::fromString( *$2 );
1905                }
1906          '{' external_definition_list_opt '}'          /* C++-style linkage specifier */
1907                {
1908                  linkage = linkageStack.top();
1909                  linkageStack.pop();
1910                  $$ = $5;
1911                }
1912        | EXTENSION external_definition
1913                { $$ = $2; }
1914        ;
1915
1916function_definition:
1917        new_function_specifier compound_statement       /* CFA */
1918                {
1919                    typedefTable.addToEnclosingScope( TypedefTable::ID );
1920                    typedefTable.leaveScope();
1921                    $$ = $1->addFunctionBody( $2 );
1922                }
1923        | declaration_qualifier_list new_function_specifier compound_statement /* CFA */
1924                /* declaration_qualifier_list also includes type_qualifier_list, so a semantic check is
1925                   necessary to preclude them as a type_qualifier cannot appear in this context. */
1926                {
1927                    typedefTable.addToEnclosingScope( TypedefTable::ID );
1928                    typedefTable.leaveScope();
1929                    $$ = $2->addFunctionBody( $3 )->addQualifiers( $1 );
1930                }
1931
1932        | declaration_specifier function_declarator compound_statement
1933                {
1934                    typedefTable.addToEnclosingScope( TypedefTable::ID );
1935                    typedefTable.leaveScope();
1936                    $$ = $2->addFunctionBody( $3 )->addType( $1 );
1937                }
1938
1939                /* These rules are a concession to the "implicit int" type_specifier because there is a
1940                   significant amount of code with functions missing a type-specifier on the return type.
1941                   Parsing is possible because function_definition does not appear in the context of an
1942                   expression (nested functions would preclude this concession). A function prototype
1943                   declaration must still have a type_specifier. OBSOLESCENT (see 1) */
1944        | function_declarator compound_statement
1945                {
1946                    typedefTable.addToEnclosingScope( TypedefTable::ID );
1947                    typedefTable.leaveScope();
1948                    $$ = $1->addFunctionBody( $2 );
1949                }
1950        | type_qualifier_list function_declarator compound_statement
1951                {
1952                    typedefTable.addToEnclosingScope( TypedefTable::ID );
1953                    typedefTable.leaveScope();
1954                    $$ = $2->addFunctionBody( $3 )->addQualifiers( $1 );
1955                }
1956        | declaration_qualifier_list function_declarator compound_statement
1957                {
1958                    typedefTable.addToEnclosingScope( TypedefTable::ID );
1959                    typedefTable.leaveScope();
1960                    $$ = $2->addFunctionBody( $3 )->addQualifiers( $1 );
1961                }
1962        | declaration_qualifier_list type_qualifier_list function_declarator compound_statement
1963                {
1964                    typedefTable.addToEnclosingScope( TypedefTable::ID );
1965                    typedefTable.leaveScope();
1966                    $$ = $3->addFunctionBody( $4 )->addQualifiers( $2 )->addQualifiers( $1 );
1967                }
1968
1969                /* Old-style K&R function definition, OBSOLESCENT (see 4) */
1970        | declaration_specifier old_function_declarator push old_declaration_list_opt compound_statement
1971                {
1972                    typedefTable.addToEnclosingScope( TypedefTable::ID );
1973                    typedefTable.leaveScope();
1974                    $$ = $2->addOldDeclList( $4 )->addFunctionBody( $5 )->addType( $1 );
1975                }
1976        | old_function_declarator push old_declaration_list_opt compound_statement
1977                {
1978                    typedefTable.addToEnclosingScope( TypedefTable::ID );
1979                    typedefTable.leaveScope();
1980                    $$ = $1->addOldDeclList( $3 )->addFunctionBody( $4 );
1981                }
1982        | type_qualifier_list old_function_declarator push old_declaration_list_opt compound_statement
1983                {
1984                    typedefTable.addToEnclosingScope( TypedefTable::ID );
1985                    typedefTable.leaveScope();
1986                    $$ = $2->addOldDeclList( $4 )->addFunctionBody( $5 )->addQualifiers( $1 );
1987                }
1988
1989                /* Old-style K&R function definition with "implicit int" type_specifier, OBSOLESCENT (see 4) */
1990        | declaration_qualifier_list old_function_declarator push old_declaration_list_opt compound_statement
1991                {
1992                    typedefTable.addToEnclosingScope( TypedefTable::ID );
1993                    typedefTable.leaveScope();
1994                    $$ = $2->addOldDeclList( $4 )->addFunctionBody( $5 )->addQualifiers( $1 );
1995                }
1996        | declaration_qualifier_list type_qualifier_list old_function_declarator push old_declaration_list_opt
1997                        compound_statement
1998                {
1999                    typedefTable.addToEnclosingScope( TypedefTable::ID );
2000                    typedefTable.leaveScope();
2001                    $$ = $3->addOldDeclList( $5 )->addFunctionBody( $6 )->addQualifiers( $2 )->addQualifiers( $1 );
2002                }
2003        ;
2004
2005declarator:
2006        variable_declarator
2007        | function_declarator
2008        | typedef_redeclarator
2009        ;
2010
2011subrange:
2012        constant_expression '~' constant_expression     /* CFA, integer subrange */
2013                { $$ = new CompositeExprNode(new OperatorNode(OperatorNode::Range), $1, $3); }
2014        ;
2015
2016asm_name_opt:                                           /* GCC */
2017        /* empty */
2018        | ASM '(' string_literal_list ')' attribute_list_opt
2019        ;
2020
2021attribute_list_opt:                                     /* GCC */
2022        /* empty */
2023        | attribute_list
2024        ;
2025
2026attribute_list:                                         /* GCC */
2027        attribute
2028        | attribute_list attribute
2029        ;
2030
2031attribute:                                              /* GCC */
2032        ATTRIBUTE '(' '(' attribute_parameter_list ')' ')'
2033        ;
2034
2035attribute_parameter_list:                               /* GCC */
2036        attrib
2037        | attribute_parameter_list ',' attrib
2038        ;
2039
2040attrib:                                                 /* GCC */
2041        /* empty */
2042        | any_word
2043        | any_word '(' comma_expression_opt ')'
2044        ;
2045
2046any_word:                                               /* GCC */
2047        identifier_or_typedef_name {}
2048        | storage_class_name {}
2049        | basic_type_name {}
2050        | type_qualifier {}
2051        ;
2052
2053/* ============================================================================
2054   The following sections are a series of grammar patterns used to parse declarators. Multiple patterns are
2055   necessary because the type of an identifier in wrapped around the identifier in the same form as its usage
2056   in an expression, as in:
2057
2058        int (*f())[10] { ... };
2059        ... (*f())[3] += 1;     // definition mimics usage
2060
2061   Because these patterns are highly recursive, changes at a lower level in the recursion require copying some
2062   or all of the pattern. Each of these patterns has some subtle variation to ensure correct syntax in a
2063   particular context.
2064   ============================================================================ */
2065
2066/* ----------------------------------------------------------------------------
2067   The set of valid declarators before a compound statement for defining a function is less than the set of
2068   declarators to define a variable or function prototype, e.g.:
2069
2070        valid declaration       invalid definition
2071        -----------------       ------------------
2072        int f;                  int f {}
2073        int *f;                 int *f {}
2074        int f[10];              int f[10] {}
2075        int (*f)(int);          int (*f)(int) {}
2076
2077   To preclude this syntactic anomaly requires separating the grammar rules for variable and function
2078   declarators, hence variable_declarator and function_declarator.
2079   ---------------------------------------------------------------------------- */
2080
2081/* This pattern parses a declaration of a variable that is not redefining a typedef name. The pattern
2082   precludes declaring an array of functions versus a pointer to an array of functions. */
2083
2084variable_declarator:
2085        paren_identifier attribute_list_opt
2086        | variable_ptr
2087        | variable_array attribute_list_opt
2088        | variable_function attribute_list_opt
2089        ;
2090
2091paren_identifier:
2092        identifier
2093                {
2094                    typedefTable.setNextIdentifier( *($1) );
2095                    $$ = DeclarationNode::newName( $1 );
2096                }
2097        | '(' paren_identifier ')'                      /* redundant parenthesis */
2098                { $$ = $2; }
2099        ;
2100
2101variable_ptr:
2102        '*' variable_declarator
2103                { $$ = $2->addPointer( DeclarationNode::newPointer( 0 ) ); }
2104        | '*' type_qualifier_list variable_declarator
2105                { $$ = $3->addPointer( DeclarationNode::newPointer( $2 ) ); }
2106        | '(' variable_ptr ')'
2107                { $$ = $2; }
2108        ;
2109
2110variable_array:
2111        paren_identifier array_dimension
2112                { $$ = $1->addArray( $2 ); }
2113        | '(' variable_ptr ')' array_dimension
2114                { $$ = $2->addArray( $4 ); }
2115        | '(' variable_array ')' multi_array_dimension  /* redundant parenthesis */
2116                { $$ = $2->addArray( $4 ); }
2117        | '(' variable_array ')'                        /* redundant parenthesis */
2118                { $$ = $2; }
2119        ;
2120
2121variable_function:
2122        '(' variable_ptr ')' '(' push parameter_type_list_opt pop ')' /* empty parameter list OBSOLESCENT (see 3) */
2123                { $$ = $2->addParamList( $6 ); }
2124        | '(' variable_function ')'                     /* redundant parenthesis */
2125                { $$ = $2; }
2126        ;
2127
2128/* This pattern parses a function declarator that is not redefining a typedef name. Because functions cannot
2129   be nested, there is no context where a function definition can redefine a typedef name. To allow nested
2130   functions requires further separation of variable and function declarators in typedef_redeclarator.  The
2131   pattern precludes returning arrays and functions versus pointers to arrays and functions. */
2132
2133function_declarator:
2134        function_no_ptr attribute_list_opt
2135        | function_ptr
2136        | function_array attribute_list_opt
2137        ;
2138
2139function_no_ptr:
2140        paren_identifier '(' push parameter_type_list_opt pop ')' /* empty parameter list OBSOLESCENT (see 3) */
2141                { $$ = $1->addParamList( $4 ); }
2142        | '(' function_ptr ')' '(' push parameter_type_list_opt pop ')'
2143                { $$ = $2->addParamList( $6 ); }
2144        | '(' function_no_ptr ')'                       /* redundant parenthesis */
2145                { $$ = $2; }
2146        ;
2147
2148function_ptr:
2149        '*' function_declarator
2150                { $$ = $2->addPointer( DeclarationNode::newPointer( 0 ) ); }
2151        | '*' type_qualifier_list function_declarator
2152                { $$ = $3->addPointer( DeclarationNode::newPointer( $2 ) ); }
2153        | '(' function_ptr ')'
2154                { $$ = $2; }
2155        ;
2156
2157function_array:
2158        '(' function_ptr ')' array_dimension
2159                { $$ = $2->addArray( $4 ); }
2160        | '(' function_array ')' multi_array_dimension  /* redundant parenthesis */
2161                { $$ = $2->addArray( $4 ); }
2162        | '(' function_array ')'                        /* redundant parenthesis */
2163                { $$ = $2; }
2164        ;
2165
2166/* This pattern parses an old-style K&R function declarator (OBSOLESCENT, see 4) that is not redefining a
2167   typedef name (see function_declarator for additional comments). The pattern precludes returning arrays and
2168   functions versus pointers to arrays and functions. */
2169
2170old_function_declarator:
2171        old_function_no_ptr
2172        | old_function_ptr
2173        | old_function_array
2174        ;
2175
2176old_function_no_ptr:
2177        paren_identifier '(' identifier_list ')'        /* function_declarator handles empty parameter */
2178                { $$ = $1->addIdList( $3 ); }
2179        | '(' old_function_ptr ')' '(' identifier_list ')'
2180                { $$ = $2->addIdList( $5 ); }
2181        | '(' old_function_no_ptr ')'                   /* redundant parenthesis */
2182                { $$ = $2; }
2183        ;
2184
2185old_function_ptr:
2186        '*' old_function_declarator
2187                { $$ = $2->addPointer( DeclarationNode::newPointer( 0 ) ); }
2188        | '*' type_qualifier_list old_function_declarator
2189                { $$ = $3->addPointer( DeclarationNode::newPointer( $2 ) ); }
2190        | '(' old_function_ptr ')'
2191                { $$ = $2; }
2192        ;
2193
2194old_function_array:
2195        '(' old_function_ptr ')' array_dimension
2196                { $$ = $2->addArray( $4 ); }
2197        | '(' old_function_array ')' multi_array_dimension /* redundant parenthesis */
2198                { $$ = $2->addArray( $4 ); }
2199        | '(' old_function_array ')'                    /* redundant parenthesis */
2200                { $$ = $2; }
2201        ;
2202
2203/* This pattern parses a declaration for a variable or function prototype that redefines a typedef name, e.g.:
2204
2205        typedef int foo;
2206        {
2207           int foo; // redefine typedef name in new scope
2208        }
2209
2210   The pattern precludes declaring an array of functions versus a pointer to an array of functions, and
2211   returning arrays and functions versus pointers to arrays and functions. */
2212
2213typedef_redeclarator:
2214        paren_typedef attribute_list_opt
2215        | typedef_ptr
2216        | typedef_array attribute_list_opt
2217        | typedef_function attribute_list_opt
2218        ;
2219
2220paren_typedef:
2221        TYPEDEFname
2222                {
2223                typedefTable.setNextIdentifier( *($1) );
2224                $$ = DeclarationNode::newName( $1 );
2225                }
2226        | '(' paren_typedef ')'
2227                { $$ = $2; }
2228        ;
2229
2230typedef_ptr:
2231        '*' typedef_redeclarator
2232                { $$ = $2->addPointer( DeclarationNode::newPointer( 0 ) ); }
2233        | '*' type_qualifier_list typedef_redeclarator
2234                { $$ = $3->addPointer( DeclarationNode::newPointer( $2 ) ); }
2235        | '(' typedef_ptr ')'
2236                { $$ = $2; }
2237        ;
2238
2239typedef_array:
2240        paren_typedef array_dimension
2241                { $$ = $1->addArray( $2 ); }
2242        | '(' typedef_ptr ')' array_dimension
2243                { $$ = $2->addArray( $4 ); }
2244        | '(' typedef_array ')' multi_array_dimension   /* redundant parenthesis */
2245                { $$ = $2->addArray( $4 ); }
2246        | '(' typedef_array ')'                         /* redundant parenthesis */
2247                { $$ = $2; }
2248        ;
2249
2250typedef_function:
2251        paren_typedef '(' push parameter_type_list_opt pop ')' /* empty parameter list OBSOLESCENT (see 3) */
2252                { $$ = $1->addParamList( $4 ); }
2253        | '(' typedef_ptr ')' '(' push parameter_type_list_opt pop ')' /* empty parameter list OBSOLESCENT (see 3) */
2254                { $$ = $2->addParamList( $6 ); }
2255        | '(' typedef_function ')'                      /* redundant parenthesis */
2256                { $$ = $2; }
2257        ;
2258
2259/* This pattern parses a declaration for a parameter variable or function prototype that is not redefining a
2260   typedef name and allows the C99 array options, which can only appear in a parameter list.  The pattern
2261   precludes declaring an array of functions versus a pointer to an array of functions, and returning arrays
2262   and functions versus pointers to arrays and functions. */
2263
2264identifier_parameter_declarator:
2265        paren_identifier attribute_list_opt
2266        | identifier_parameter_ptr
2267        | identifier_parameter_array attribute_list_opt
2268        | identifier_parameter_function attribute_list_opt
2269        ;
2270
2271identifier_parameter_ptr:
2272        '*' identifier_parameter_declarator
2273                { $$ = $2->addPointer( DeclarationNode::newPointer( 0 ) ); }
2274        | '*' type_qualifier_list identifier_parameter_declarator
2275                { $$ = $3->addPointer( DeclarationNode::newPointer( $2 ) ); }
2276        | '(' identifier_parameter_ptr ')'
2277                { $$ = $2; }
2278        ;
2279
2280identifier_parameter_array:
2281        paren_identifier array_parameter_dimension
2282                { $$ = $1->addArray( $2 ); }
2283        | '(' identifier_parameter_ptr ')' array_dimension
2284                { $$ = $2->addArray( $4 ); }
2285        | '(' identifier_parameter_array ')' multi_array_dimension /* redundant parenthesis */
2286                { $$ = $2->addArray( $4 ); }
2287        | '(' identifier_parameter_array ')'            /* redundant parenthesis */
2288                { $$ = $2; }
2289        ;
2290
2291identifier_parameter_function:
2292        paren_identifier '(' push parameter_type_list_opt pop ')' /* empty parameter list OBSOLESCENT (see 3) */
2293                { $$ = $1->addParamList( $4 ); }
2294        | '(' identifier_parameter_ptr ')' '(' push parameter_type_list_opt pop ')' /* empty parameter list OBSOLESCENT (see 3) */
2295                { $$ = $2->addParamList( $6 ); }
2296        | '(' identifier_parameter_function ')'         /* redundant parenthesis */
2297                { $$ = $2; }
2298        ;
2299
2300/* This pattern parses a declaration for a parameter variable or function prototype that is redefining a
2301   typedef name, e.g.:
2302
2303        typedef int foo;
2304        int f( int foo ); // redefine typedef name in new scope
2305
2306   and allows the C99 array options, which can only appear in a parameter list.  In addition, the pattern
2307   handles the special meaning of parenthesis around a typedef name:
2308
2309        ISO/IEC 9899:1999 Section 6.7.5.3(11) : "In a parameter declaration, a single typedef name in
2310        parentheses is taken to be an abstract declarator that specifies a function with a single parameter,
2311        not as redundant parentheses around the identifier."
2312
2313   which precludes the following cases:
2314
2315        typedef float T;
2316        int f( int ( T [5] ) );                 // see abstract_parameter_declarator
2317        int g( int ( T ( int ) ) );             // see abstract_parameter_declarator
2318        int f( int f1( T a[5] ) );              // see identifier_parameter_declarator
2319        int g( int g1( T g2( int p ) ) );       // see identifier_parameter_declarator
2320
2321   In essence, a '(' immediately to the left of typedef name, T, is interpreted as starting a parameter type
2322   list, and not as redundant parentheses around a redeclaration of T. Finally, the pattern also precludes
2323   declaring an array of functions versus a pointer to an array of functions, and returning arrays and
2324   functions versus pointers to arrays and functions. */
2325
2326typedef_parameter_redeclarator:
2327        typedef attribute_list_opt
2328        | typedef_parameter_ptr
2329        | typedef_parameter_array attribute_list_opt
2330        | typedef_parameter_function attribute_list_opt
2331        ;
2332
2333typedef:
2334        TYPEDEFname
2335                {
2336                    typedefTable.setNextIdentifier( *($1) );
2337                    $$ = DeclarationNode::newName( $1 );
2338                }
2339        ;
2340
2341typedef_parameter_ptr:
2342        '*' typedef_parameter_redeclarator
2343                { $$ = $2->addPointer( DeclarationNode::newPointer( 0 ) ); }
2344        | '*' type_qualifier_list typedef_parameter_redeclarator
2345                { $$ = $3->addPointer( DeclarationNode::newPointer( $2 ) ); }
2346        | '(' typedef_parameter_ptr ')'
2347                { $$ = $2; }
2348        ;
2349
2350typedef_parameter_array:
2351        typedef array_parameter_dimension
2352                { $$ = $1->addArray( $2 ); }
2353        | '(' typedef_parameter_ptr ')' array_parameter_dimension
2354                { $$ = $2->addArray( $4 ); }
2355        ;
2356
2357typedef_parameter_function:
2358        typedef '(' push parameter_type_list_opt pop ')' /* empty parameter list OBSOLESCENT (see 3) */
2359                { $$ = $1->addParamList( $4 ); }
2360        | '(' typedef_parameter_ptr ')' '(' push parameter_type_list_opt pop ')' /* empty parameter list OBSOLESCENT (see 3) */
2361                { $$ = $2->addParamList( $6 ); }
2362        ;
2363
2364/* This pattern parses a declaration of an abstract variable or function prototype, i.e., there is no
2365   identifier to which the type applies, e.g.:
2366
2367        sizeof( int );
2368        sizeof( int [10] );
2369
2370   The pattern precludes declaring an array of functions versus a pointer to an array of functions, and
2371   returning arrays and functions versus pointers to arrays and functions. */
2372
2373abstract_declarator:
2374        abstract_ptr
2375        | abstract_array attribute_list_opt
2376        | abstract_function attribute_list_opt
2377        ;
2378
2379abstract_ptr:
2380        '*'
2381                { $$ = DeclarationNode::newPointer( 0 ); }
2382        | '*' type_qualifier_list
2383                { $$ = DeclarationNode::newPointer( $2 ); }
2384        | '*' abstract_declarator
2385                { $$ = $2->addPointer( DeclarationNode::newPointer( 0 ) ); }
2386        | '*' type_qualifier_list abstract_declarator
2387                { $$ = $3->addPointer( DeclarationNode::newPointer( $2 ) ); }
2388        | '(' abstract_ptr ')'
2389                { $$ = $2; }
2390        ;
2391
2392abstract_array:
2393        array_dimension
2394        | '(' abstract_ptr ')' array_dimension
2395                { $$ = $2->addArray( $4 ); }
2396        | '(' abstract_array ')' multi_array_dimension  /* redundant parenthesis */
2397                { $$ = $2->addArray( $4 ); }
2398        | '(' abstract_array ')'                        /* redundant parenthesis */
2399                { $$ = $2; }
2400        ;
2401
2402abstract_function:
2403        '(' push parameter_type_list_opt pop ')'        /* empty parameter list OBSOLESCENT (see 3) */
2404                { $$ = DeclarationNode::newFunction( 0, 0, $3, 0 ); }
2405        | '(' abstract_ptr ')' '(' push parameter_type_list_opt pop ')' /* empty parameter list OBSOLESCENT (see 3) */
2406                { $$ = $2->addParamList( $6 ); }
2407        | '(' abstract_function ')'                     /* redundant parenthesis */
2408                { $$ = $2; }
2409        ;
2410
2411array_dimension:
2412                /* Only the first dimension can be empty. */
2413        '[' push pop ']'
2414                { $$ = DeclarationNode::newArray( 0, 0, false ); }
2415        | '[' push pop ']' multi_array_dimension
2416                { $$ = DeclarationNode::newArray( 0, 0, false )->addArray( $5 ); }
2417        | multi_array_dimension
2418        ;
2419
2420multi_array_dimension:
2421        '[' push assignment_expression pop ']'
2422                { $$ = DeclarationNode::newArray( $3, 0, false ); }
2423        | '[' push '*' pop ']'                          /* C99 */
2424                { $$ = DeclarationNode::newVarArray( 0 ); }
2425        | multi_array_dimension '[' push assignment_expression pop ']'
2426                { $$ = $1->addArray( DeclarationNode::newArray( $4, 0, false ) ); }
2427        | multi_array_dimension '[' push '*' pop ']'    /* C99 */
2428                { $$ = $1->addArray( DeclarationNode::newVarArray( 0 ) ); }
2429        ;
2430
2431/* This pattern parses a declaration of a parameter abstract variable or function prototype, i.e., there is no
2432   identifier to which the type applies, e.g.:
2433
2434        int f( int );           // abstract variable parameter; no parameter name specified
2435        int f( int (int) );     // abstract function-prototype parameter; no parameter name specified
2436
2437   The pattern precludes declaring an array of functions versus a pointer to an array of functions, and
2438   returning arrays and functions versus pointers to arrays and functions. */
2439
2440abstract_parameter_declarator:
2441        abstract_parameter_ptr
2442        | abstract_parameter_array attribute_list_opt
2443        | abstract_parameter_function attribute_list_opt
2444        ;
2445
2446abstract_parameter_ptr:
2447        '*'
2448                { $$ = DeclarationNode::newPointer( 0 ); }
2449        | '*' type_qualifier_list
2450                { $$ = DeclarationNode::newPointer( $2 ); }
2451        | '*' abstract_parameter_declarator
2452                { $$ = $2->addPointer( DeclarationNode::newPointer( 0 ) ); }
2453        | '*' type_qualifier_list abstract_parameter_declarator
2454                { $$ = $3->addPointer( DeclarationNode::newPointer( $2 ) ); }
2455        | '(' abstract_parameter_ptr ')'
2456                { $$ = $2; }
2457        ;
2458
2459abstract_parameter_array:
2460        array_parameter_dimension
2461        | '(' abstract_parameter_ptr ')' array_parameter_dimension
2462                { $$ = $2->addArray( $4 ); }
2463        | '(' abstract_parameter_array ')' multi_array_dimension /* redundant parenthesis */
2464                { $$ = $2->addArray( $4 ); }
2465        | '(' abstract_parameter_array ')'              /* redundant parenthesis */
2466                { $$ = $2; }
2467        ;
2468
2469abstract_parameter_function:
2470        '(' push parameter_type_list_opt pop ')'        /* empty parameter list OBSOLESCENT (see 3) */
2471                { $$ = DeclarationNode::newFunction( 0, 0, $3, 0 ); }
2472        | '(' abstract_parameter_ptr ')' '(' push parameter_type_list_opt pop ')' /* empty parameter list OBSOLESCENT (see 3) */
2473                { $$ = $2->addParamList( $6 ); }
2474        | '(' abstract_parameter_function ')'           /* redundant parenthesis */
2475                { $$ = $2; }
2476        ;
2477
2478array_parameter_dimension:
2479                /* Only the first dimension can be empty or have qualifiers. */
2480        array_parameter_1st_dimension
2481        | array_parameter_1st_dimension multi_array_dimension
2482                { $$ = $1->addArray( $2 ); }
2483        | multi_array_dimension
2484        ;
2485
2486/* The declaration of an array parameter has additional syntax over arrays in normal variable declarations:
2487
2488        ISO/IEC 9899:1999 Section 6.7.5.2(1) : "The optional type qualifiers and the keyword static shall
2489        appear only in a declaration of a function parameter with an array type, and then only in the
2490        outermost array type derivation." */
2491
2492array_parameter_1st_dimension:
2493        '[' push pop ']'
2494                { $$ = DeclarationNode::newArray( 0, 0, false ); }
2495        // multi_array_dimension handles the '[' '*' ']' case
2496        | '[' push type_qualifier_list '*' pop ']'      /* remaining C99 */
2497                { $$ = DeclarationNode::newVarArray( $3 ); }
2498        | '[' push type_qualifier_list pop ']'
2499                { $$ = DeclarationNode::newArray( 0, $3, false ); }
2500        // multi_array_dimension handles the '[' assignment_expression ']' case
2501        | '[' push type_qualifier_list assignment_expression pop ']'
2502                { $$ = DeclarationNode::newArray( $4, $3, false ); }
2503        | '[' push STATIC type_qualifier_list_opt assignment_expression pop ']'
2504                { $$ = DeclarationNode::newArray( $5, $4, true ); }
2505        | '[' push type_qualifier_list STATIC assignment_expression pop ']'
2506                { $$ = DeclarationNode::newArray( $5, $3, true ); }
2507        ;
2508
2509/* This pattern parses a declaration of an abstract variable, i.e., there is no identifier to which the type
2510   applies, e.g.:
2511
2512        sizeof( int ); // abstract variable; no identifier name specified
2513
2514   The pattern precludes declaring an array of functions versus a pointer to an array of functions, and
2515   returning arrays and functions versus pointers to arrays and functions. */
2516
2517variable_abstract_declarator:
2518        variable_abstract_ptr
2519        | variable_abstract_array attribute_list_opt
2520        | variable_abstract_function attribute_list_opt
2521        ;
2522
2523variable_abstract_ptr:
2524        '*'
2525                { $$ = DeclarationNode::newPointer( 0 ); }
2526        | '*' type_qualifier_list
2527                { $$ = DeclarationNode::newPointer( $2 ); }
2528        | '*' variable_abstract_declarator
2529                { $$ = $2->addPointer( DeclarationNode::newPointer( 0 ) ); }
2530        | '*' type_qualifier_list variable_abstract_declarator
2531                { $$ = $3->addPointer( DeclarationNode::newPointer( $2 ) ); }
2532        | '(' variable_abstract_ptr ')'
2533                { $$ = $2; }
2534        ;
2535
2536variable_abstract_array:
2537        array_dimension
2538        | '(' variable_abstract_ptr ')' array_dimension
2539                { $$ = $2->addArray( $4 ); }
2540        | '(' variable_abstract_array ')' multi_array_dimension /* redundant parenthesis */
2541                { $$ = $2->addArray( $4 ); }
2542        | '(' variable_abstract_array ')'               /* redundant parenthesis */
2543                { $$ = $2; }
2544        ;
2545
2546variable_abstract_function:
2547        '(' variable_abstract_ptr ')' '(' push parameter_type_list_opt pop ')' /* empty parameter list OBSOLESCENT (see 3) */
2548                { $$ = $2->addParamList( $6 ); }
2549        | '(' variable_abstract_function ')'            /* redundant parenthesis */
2550                { $$ = $2; }
2551        ;
2552
2553/* This pattern parses a new-style declaration for a parameter variable or function prototype that is either
2554   an identifier or typedef name and allows the C99 array options, which can only appear in a parameter
2555   list. */
2556
2557new_identifier_parameter_declarator_tuple:              /* CFA */
2558        new_identifier_parameter_declarator_no_tuple
2559        | new_abstract_tuple
2560        | type_qualifier_list new_abstract_tuple
2561                { $$ = $2->addQualifiers( $1 ); }
2562        ;
2563
2564new_identifier_parameter_declarator_no_tuple:           /* CFA */
2565        new_identifier_parameter_ptr
2566        | new_identifier_parameter_array
2567        ;
2568
2569new_identifier_parameter_ptr:                           /* CFA */
2570        '*' type_specifier
2571                { $$ = $2->addNewPointer( DeclarationNode::newPointer( 0 ) ); }
2572        | type_qualifier_list '*' type_specifier
2573                { $$ = $3->addNewPointer( DeclarationNode::newPointer( $1 ) ); }
2574        | '*' new_abstract_function
2575                { $$ = $2->addNewPointer( DeclarationNode::newPointer( 0 ) ); }
2576        | type_qualifier_list '*' new_abstract_function
2577                { $$ = $3->addNewPointer( DeclarationNode::newPointer( $1 ) ); }
2578        | '*' new_identifier_parameter_declarator_tuple
2579                { $$ = $2->addNewPointer( DeclarationNode::newPointer( 0 ) ); }
2580        | type_qualifier_list '*' new_identifier_parameter_declarator_tuple
2581                { $$ = $3->addNewPointer( DeclarationNode::newPointer( $1 ) ); }
2582        ;
2583
2584new_identifier_parameter_array:                         /* CFA */
2585                /* Only the first dimension can be empty or have qualifiers. Empty dimension must be factored
2586                   out due to shift/reduce conflict with new-style empty (void) function return type. */
2587        '[' push pop ']' type_specifier
2588                { $$ = $5->addNewArray( DeclarationNode::newArray( 0, 0, false ) ); }
2589        | new_array_parameter_1st_dimension type_specifier
2590                { $$ = $2->addNewArray( $1 ); }
2591        | '[' push pop ']' multi_array_dimension type_specifier
2592                { $$ = $6->addNewArray( $5 )->addNewArray( DeclarationNode::newArray( 0, 0, false ) ); }
2593        | new_array_parameter_1st_dimension multi_array_dimension type_specifier
2594                { $$ = $3->addNewArray( $2 )->addNewArray( $1 ); }
2595        | multi_array_dimension type_specifier
2596                { $$ = $2->addNewArray( $1 ); }
2597        | '[' push pop ']' new_identifier_parameter_ptr
2598                { $$ = $5->addNewArray( DeclarationNode::newArray( 0, 0, false ) ); }
2599        | new_array_parameter_1st_dimension new_identifier_parameter_ptr
2600                { $$ = $2->addNewArray( $1 ); }
2601        | '[' push pop ']' multi_array_dimension new_identifier_parameter_ptr
2602                { $$ = $6->addNewArray( $5 )->addNewArray( DeclarationNode::newArray( 0, 0, false ) ); }
2603        | new_array_parameter_1st_dimension multi_array_dimension new_identifier_parameter_ptr
2604                { $$ = $3->addNewArray( $2 )->addNewArray( $1 ); }
2605        | multi_array_dimension new_identifier_parameter_ptr
2606                { $$ = $2->addNewArray( $1 ); }
2607        ;
2608
2609new_array_parameter_1st_dimension:
2610        '[' push type_qualifier_list '*' pop ']'        /* remaining C99 */
2611                { $$ = DeclarationNode::newVarArray( $3 ); }
2612        | '[' push type_qualifier_list assignment_expression pop ']'
2613                { $$ = DeclarationNode::newArray( $4, $3, false ); }
2614        | '[' push declaration_qualifier_list assignment_expression pop ']'
2615                /* declaration_qualifier_list must be used because of shift/reduce conflict with
2616                   assignment_expression, so a semantic check is necessary to preclude them as a
2617                   type_qualifier cannot appear in this context. */
2618                { $$ = DeclarationNode::newArray( $4, $3, true ); }
2619        | '[' push declaration_qualifier_list type_qualifier_list assignment_expression pop ']'
2620                { $$ = DeclarationNode::newArray( $5, $4->addQualifiers( $3 ), true ); }
2621        ;
2622
2623/* This pattern parses a new-style declaration of an abstract variable or function prototype, i.e., there is
2624   no identifier to which the type applies, e.g.:
2625
2626        [int] f( int );         // abstract variable parameter; no parameter name specified
2627        [int] f( [int] (int) ); // abstract function-prototype parameter; no parameter name specified
2628
2629   These rules need LR(3):
2630
2631        new_abstract_tuple identifier_or_typedef_name
2632        '[' new_parameter_list ']' identifier_or_typedef_name '(' new_parameter_type_list_opt ')'
2633
2634   since a function return type can be syntactically identical to a tuple type:
2635
2636        [int, int] t;
2637        [int, int] f( int );
2638
2639   Therefore, it is necessary to look at the token after identifier_or_typedef_name to know when to reduce
2640   new_abstract_tuple. To make this LR(1), several rules have to be flattened (lengthened) to allow
2641   the necessary lookahead. To accomplish this, new_abstract_declarator has an entry point without tuple, and
2642   tuple declarations are duplicated when appearing with new_function_specifier. */
2643
2644new_abstract_declarator_tuple:                          /* CFA */
2645        new_abstract_tuple
2646        | type_qualifier_list new_abstract_tuple
2647                { $$ = $2->addQualifiers( $1 ); }
2648        | new_abstract_declarator_no_tuple
2649        ;
2650
2651new_abstract_declarator_no_tuple:                       /* CFA */
2652        new_abstract_ptr
2653        | new_abstract_array
2654        ;
2655
2656new_abstract_ptr:                                       /* CFA */
2657        '*' type_specifier
2658                { $$ = $2->addNewPointer( DeclarationNode::newPointer( 0 ) ); }
2659        | type_qualifier_list '*' type_specifier
2660                { $$ = $3->addNewPointer( DeclarationNode::newPointer( $1 ) ); }
2661        | '*' new_abstract_function
2662                { $$ = $2->addNewPointer( DeclarationNode::newPointer( 0 ) ); }
2663        | type_qualifier_list '*' new_abstract_function
2664                { $$ = $3->addNewPointer( DeclarationNode::newPointer( $1 ) ); }
2665        | '*' new_abstract_declarator_tuple
2666                { $$ = $2->addNewPointer( DeclarationNode::newPointer( 0 ) ); }
2667        | type_qualifier_list '*' new_abstract_declarator_tuple
2668                { $$ = $3->addNewPointer( DeclarationNode::newPointer( $1 ) ); }
2669        ;
2670
2671new_abstract_array:                                     /* CFA */
2672                /* Only the first dimension can be empty. Empty dimension must be factored out due to
2673                   shift/reduce conflict with empty (void) function return type. */
2674        '[' push pop ']' type_specifier
2675                { $$ = $5->addNewArray( DeclarationNode::newArray( 0, 0, false ) ); }
2676        | '[' push pop ']' multi_array_dimension type_specifier
2677                { $$ = $6->addNewArray( $5 )->addNewArray( DeclarationNode::newArray( 0, 0, false ) ); }
2678        | multi_array_dimension type_specifier
2679                { $$ = $2->addNewArray( $1 ); }
2680        | '[' push pop ']' new_abstract_ptr
2681                { $$ = $5->addNewArray( DeclarationNode::newArray( 0, 0, false ) ); }
2682        | '[' push pop ']' multi_array_dimension new_abstract_ptr
2683                { $$ = $6->addNewArray( $5 )->addNewArray( DeclarationNode::newArray( 0, 0, false ) ); }
2684        | multi_array_dimension new_abstract_ptr
2685                { $$ = $2->addNewArray( $1 ); }
2686        ;
2687
2688new_abstract_tuple:                                     /* CFA */
2689        '[' push new_abstract_parameter_list pop ']'
2690                { $$ = DeclarationNode::newTuple( $3 ); }
2691        ;
2692
2693new_abstract_function:                                  /* CFA */
2694        '[' push pop ']' '(' new_parameter_type_list_opt ')'
2695                { $$ = DeclarationNode::newFunction( 0, DeclarationNode::newTuple( 0 ), $6, 0 ); }
2696        | new_abstract_tuple '(' push new_parameter_type_list_opt pop ')'
2697                { $$ = DeclarationNode::newFunction( 0, $1, $4, 0 ); }
2698        | new_function_return '(' push new_parameter_type_list_opt pop ')'
2699                { $$ = DeclarationNode::newFunction( 0, $1, $4, 0 ); }
2700        ;
2701
2702/* 1) ISO/IEC 9899:1999 Section 6.7.2(2) : "At least one type specifier shall be given in the declaration
2703      specifiers in each declaration, and in the specifier-qualifier list in each structure declaration and
2704      type name."
2705
2706   2) ISO/IEC 9899:1999 Section 6.11.5(1) : "The placement of a storage-class specifier other than at the
2707      beginning of the declaration specifiers in a declaration is an obsolescent feature."
2708
2709   3) ISO/IEC 9899:1999 Section 6.11.6(1) : "The use of function declarators with empty parentheses (not
2710      prototype-format parameter type declarators) is an obsolescent feature."
2711
2712   4) ISO/IEC 9899:1999 Section 6.11.7(1) : "The use of function definitions with separate parameter
2713      identifier and declaration lists (not prototype-format parameter type and identifier declarators) is
2714      an obsolescent feature."  */
2715
2716/************************* MISCELLANEOUS ********************************/
2717
2718comma_opt:                                              /* redundant comma */
2719        /* empty */
2720        | ','
2721        ;
2722
2723assignment_opt:
2724        /* empty */
2725                { $$ = 0; }
2726        | '=' assignment_expression
2727                { $$ = $2; }
2728        ;
2729
2730%%
2731/* ----end of grammar----*/
2732
2733void yyerror( char *string ) {
2734    using std::cout;
2735    using std::endl;
2736    cout << "Error ";
2737    if ( yyfilename ) {
2738        cout << "in file " << yyfilename << " ";
2739    }
2740    cout << "at line " << yylineno << " reading token \"" << *(yylval.tok.str) << "\"" << endl;
2741}
2742
2743/* Local Variables: */
2744/* fill-column: 110 */
2745/* compile-command: "make install" */
2746/* End: */
Note: See TracBrowser for help on using the repository browser.