source: translator/Parser.old/cfa.y @ 3c70d38

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 3c70d38 was 51b7345, checked in by Peter A. Buhr <pabuhr@…>, 10 years ago

initial commit

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