OSDN Git Service

* config/i386/sol2.h (PREFERRED_DEBUGGING_TYPE): Use stabs.
[pf3gnuchains/gcc-fork.git] / gcc / c-parse.y
1 /*WARNING: This file is automatically generated!*/
2 /* YACC parser for C syntax and for Objective C.  -*-c-*-
3    Copyright (C) 1987, 88, 89, 92-98, 1999 Free Software Foundation, Inc.
4
5 This file is part of GNU CC.
6
7 GNU CC is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 2, or (at your option)
10 any later version.
11
12 GNU CC is distributed in the hope that it will be useful,
13 but WITHOUT ANY WARRANTY; without even the implied warranty of
14 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15 GNU General Public License for more details.
16
17 You should have received a copy of the GNU General Public License
18 along with GNU CC; see the file COPYING.  If not, write to
19 the Free Software Foundation, 59 Temple Place - Suite 330,
20 Boston, MA 02111-1307, USA.  */
21
22 /* This file defines the grammar of C and that of Objective C.
23    ifobjc ... end ifobjc  conditionals contain code for Objective C only.
24    ifc ... end ifc  conditionals contain code for C only.
25    Sed commands in Makefile.in are used to convert this file into
26    c-parse.y and into objc-parse.y.  */
27
28 /* To whomever it may concern: I have heard that such a thing was once
29    written by AT&T, but I have never seen it.  */
30
31 %expect 52
32
33 %{
34 #include "config.h"
35 #include "system.h"
36 #include <setjmp.h>
37 #include "tree.h"
38 #include "input.h"
39 #include "c-lex.h"
40 #include "c-tree.h"
41 #include "flags.h"
42 #include "output.h"
43 #include "toplev.h"
44 #include "ggc.h"
45   
46 #ifdef MULTIBYTE_CHARS
47 #include <locale.h>
48 #endif
49
50
51 /* Since parsers are distinct for each language, put the language string
52    definition here.  */
53 const char * const language_string = "GNU C";
54
55 /* Like YYERROR but do call yyerror.  */
56 #define YYERROR1 { yyerror ("syntax error"); YYERROR; }
57
58 /* Cause the `yydebug' variable to be defined.  */
59 #define YYDEBUG 1
60 %}
61
62 %start program
63
64 %union {long itype; tree ttype; enum tree_code code;
65         char *filename; int lineno; int ends_in_label; }
66
67 /* All identifiers that are not reserved words
68    and are not declared typedefs in the current block */
69 %token IDENTIFIER
70
71 /* All identifiers that are declared typedefs in the current block.
72    In some contexts, they are treated just like IDENTIFIER,
73    but they can also serve as typespecs in declarations.  */
74 %token TYPENAME
75
76 /* Reserved words that specify storage class.
77    yylval contains an IDENTIFIER_NODE which indicates which one.  */
78 %token SCSPEC
79
80 /* Reserved words that specify type.
81    yylval contains an IDENTIFIER_NODE which indicates which one.  */
82 %token TYPESPEC
83
84 /* Reserved words that qualify type: "const", "volatile", or "restrict".
85    yylval contains an IDENTIFIER_NODE which indicates which one.  */
86 %token TYPE_QUAL
87
88 /* Character or numeric constants.
89    yylval is the node for the constant.  */
90 %token CONSTANT
91
92 /* String constants in raw form.
93    yylval is a STRING_CST node.  */
94 %token STRING
95
96 /* "...", used for functions with variable arglists.  */
97 %token ELLIPSIS
98
99 /* the reserved words */
100 /* SCO include files test "ASM", so use something else. */
101 %token SIZEOF ENUM STRUCT UNION IF ELSE WHILE DO FOR SWITCH CASE DEFAULT
102 %token BREAK CONTINUE RETURN GOTO ASM_KEYWORD TYPEOF ALIGNOF
103 %token ATTRIBUTE EXTENSION LABEL
104 %token REALPART IMAGPART VA_ARG
105
106 /* Used in c-lex.c for parsing pragmas.  */
107 %token END_OF_LINE
108
109 /* Add precedence rules to solve dangling else s/r conflict */
110 %nonassoc IF
111 %nonassoc ELSE
112
113 /* Define the operator tokens and their precedences.
114    The value is an integer because, if used, it is the tree code
115    to use in the expression made from the operator.  */
116
117 %right <code> ASSIGN '='
118 %right <code> '?' ':'
119 %left <code> OROR
120 %left <code> ANDAND
121 %left <code> '|'
122 %left <code> '^'
123 %left <code> '&'
124 %left <code> EQCOMPARE
125 %left <code> ARITHCOMPARE
126 %left <code> LSHIFT RSHIFT
127 %left <code> '+' '-'
128 %left <code> '*' '/' '%'
129 %right <code> UNARY PLUSPLUS MINUSMINUS
130 %left HYPERUNARY
131 %left <code> POINTSAT '.' '(' '['
132
133 /* The Objective-C keywords.  These are included in C and in
134    Objective C, so that the token codes are the same in both.  */
135 %token INTERFACE IMPLEMENTATION END SELECTOR DEFS ENCODE
136 %token CLASSNAME PUBLIC PRIVATE PROTECTED PROTOCOL OBJECTNAME CLASS ALIAS
137
138 /* Objective-C string constants in raw form.
139    yylval is an OBJC_STRING_CST node.  */
140 %token OBJC_STRING
141
142
143 %type <code> unop
144
145 %type <ttype> identifier IDENTIFIER TYPENAME CONSTANT expr nonnull_exprlist exprlist
146 %type <ttype> expr_no_commas cast_expr unary_expr primary string STRING
147 %type <ttype> typed_declspecs reserved_declspecs
148 %type <ttype> typed_typespecs reserved_typespecquals
149 %type <ttype> declmods typespec typespecqual_reserved
150 %type <ttype> typed_declspecs_no_prefix_attr reserved_declspecs_no_prefix_attr
151 %type <ttype> declmods_no_prefix_attr
152 %type <ttype> SCSPEC TYPESPEC TYPE_QUAL nonempty_type_quals maybe_type_qual
153 %type <ttype> initdecls notype_initdecls initdcl notype_initdcl
154 %type <ttype> init maybeasm
155 %type <ttype> asm_operands nonnull_asm_operands asm_operand asm_clobbers
156 %type <ttype> maybe_attribute attributes attribute attribute_list attrib
157 %type <ttype> any_word
158
159 %type <ttype> compstmt compstmt_nostart compstmt_primary_start
160
161 %type <ttype> declarator
162 %type <ttype> notype_declarator after_type_declarator
163 %type <ttype> parm_declarator
164
165 %type <ttype> structsp component_decl_list component_decl_list2
166 %type <ttype> component_decl components component_declarator
167 %type <ttype> enumlist enumerator
168 %type <ttype> struct_head union_head enum_head
169 %type <ttype> typename absdcl absdcl1 type_quals
170 %type <ttype> xexpr parms parm identifiers
171
172 %type <ttype> parmlist parmlist_1 parmlist_2
173 %type <ttype> parmlist_or_identifiers parmlist_or_identifiers_1
174 %type <ttype> identifiers_or_typenames
175
176 %type <itype> setspecs
177
178 %type <ends_in_label> lineno_stmt_or_label lineno_stmt_or_labels stmt_or_label
179
180 %type <filename> save_filename
181 %type <lineno> save_lineno
182 \f
183 \f
184 %{
185 /* Number of statements (loosely speaking) and compound statements 
186    seen so far.  */
187 static int stmt_count;
188 static int compstmt_count;
189   
190 /* Input file and line number of the end of the body of last simple_if;
191    used by the stmt-rule immediately after simple_if returns.  */
192 static char *if_stmt_file;
193 static int if_stmt_line;
194
195 /* List of types and structure classes of the current declaration.  */
196 static tree current_declspecs = NULL_TREE;
197 static tree prefix_attributes = NULL_TREE;
198
199 /* Stack of saved values of current_declspecs and prefix_attributes.  */
200 static tree declspec_stack;
201
202 /* 1 if we explained undeclared var errors.  */
203 static int undeclared_variable_notice;
204
205
206 /* Tell yyparse how to print a token's value, if yydebug is set.  */
207
208 #define YYPRINT(FILE,YYCHAR,YYLVAL) yyprint(FILE,YYCHAR,YYLVAL)
209 extern void yyprint                     PROTO ((FILE *, int, YYSTYPE));
210
211 /* Add GC roots for variables local to this file.  */
212 void
213 c_parse_init ()
214 {
215   ggc_add_tree_root (&declspec_stack, 1);
216   ggc_add_tree_root (&current_declspecs, 1);
217   ggc_add_tree_root (&prefix_attributes, 1);
218 }
219
220 %}
221 \f
222 %%
223 program: /* empty */
224                 { if (pedantic)
225                     pedwarn ("ANSI C forbids an empty source file");
226                   finish_file ();
227                 }
228         | extdefs
229                 {
230                   /* In case there were missing closebraces,
231                      get us back to the global binding level.  */
232                   while (! global_bindings_p ())
233                     poplevel (0, 0, 0);
234                   finish_file ();
235                 }
236         ;
237
238 /* the reason for the strange actions in this rule
239  is so that notype_initdecls when reached via datadef
240  can find a valid list of type and sc specs in $0. */
241
242 extdefs:
243         {$<ttype>$ = NULL_TREE; } extdef
244         | extdefs {$<ttype>$ = NULL_TREE; } extdef
245         ;
246
247 extdef:
248         fndef
249         | datadef
250         | ASM_KEYWORD '(' expr ')' ';'
251                 { STRIP_NOPS ($3);
252                   if ((TREE_CODE ($3) == ADDR_EXPR
253                        && TREE_CODE (TREE_OPERAND ($3, 0)) == STRING_CST)
254                       || TREE_CODE ($3) == STRING_CST)
255                     assemble_asm ($3);
256                   else
257                     error ("argument of `asm' is not a constant string"); }
258         | extension extdef
259                 { pedantic = $<itype>1; }
260         ;
261
262 datadef:
263           setspecs notype_initdecls ';'
264                 { if (pedantic)
265                     error ("ANSI C forbids data definition with no type or storage class");
266                   else if (!flag_traditional)
267                     warning ("data definition has no type or storage class"); 
268
269                   current_declspecs = TREE_VALUE (declspec_stack);
270                   prefix_attributes = TREE_PURPOSE (declspec_stack);
271                   declspec_stack = TREE_CHAIN (declspec_stack);
272                   resume_momentary ($1); }
273         | declmods setspecs notype_initdecls ';'
274                 { current_declspecs = TREE_VALUE (declspec_stack);
275                   prefix_attributes = TREE_PURPOSE (declspec_stack);
276                   declspec_stack = TREE_CHAIN (declspec_stack);
277                   resume_momentary ($2); }
278         | typed_declspecs setspecs initdecls ';'
279                 { current_declspecs = TREE_VALUE (declspec_stack);
280                   prefix_attributes = TREE_PURPOSE (declspec_stack);
281                   declspec_stack = TREE_CHAIN (declspec_stack);
282                   resume_momentary ($2);  }
283         | declmods ';'
284           { pedwarn ("empty declaration"); }
285         | typed_declspecs ';'
286           { shadow_tag ($1); }
287         | error ';'
288         | error '}'
289         | ';'
290                 { if (pedantic)
291                     pedwarn ("ANSI C does not allow extra `;' outside of a function"); }
292         ;
293 \f
294 fndef:
295           typed_declspecs setspecs declarator
296                 { if (! start_function (current_declspecs, $3,
297                                         prefix_attributes, NULL_TREE, 0))
298                     YYERROR1;
299                   reinit_parse_for_function (); }
300           old_style_parm_decls
301                 { store_parm_decls (); }
302           compstmt_or_error
303                 { finish_function (0); 
304                   current_declspecs = TREE_VALUE (declspec_stack);
305                   prefix_attributes = TREE_PURPOSE (declspec_stack);
306                   declspec_stack = TREE_CHAIN (declspec_stack);
307                   resume_momentary ($2); }
308         | typed_declspecs setspecs declarator error
309                 { current_declspecs = TREE_VALUE (declspec_stack);
310                   prefix_attributes = TREE_PURPOSE (declspec_stack);
311                   declspec_stack = TREE_CHAIN (declspec_stack);
312                   resume_momentary ($2); }
313         | declmods setspecs notype_declarator
314                 { if (! start_function (current_declspecs, $3,
315                                         prefix_attributes, NULL_TREE, 0))
316                     YYERROR1;
317                   reinit_parse_for_function (); }
318           old_style_parm_decls
319                 { store_parm_decls (); }
320           compstmt_or_error
321                 { finish_function (0); 
322                   current_declspecs = TREE_VALUE (declspec_stack);
323                   prefix_attributes = TREE_PURPOSE (declspec_stack);
324                   declspec_stack = TREE_CHAIN (declspec_stack);
325                   resume_momentary ($2); }
326         | declmods setspecs notype_declarator error
327                 { current_declspecs = TREE_VALUE (declspec_stack);
328                   prefix_attributes = TREE_PURPOSE (declspec_stack);
329                   declspec_stack = TREE_CHAIN (declspec_stack);
330                   resume_momentary ($2); }
331         | setspecs notype_declarator
332                 { if (! start_function (NULL_TREE, $2,
333                                         prefix_attributes, NULL_TREE, 0))
334                     YYERROR1;
335                   reinit_parse_for_function (); }
336           old_style_parm_decls
337                 { store_parm_decls (); }
338           compstmt_or_error
339                 { finish_function (0); 
340                   current_declspecs = TREE_VALUE (declspec_stack);
341                   prefix_attributes = TREE_PURPOSE (declspec_stack);
342                   declspec_stack = TREE_CHAIN (declspec_stack);
343                   resume_momentary ($1); }
344         | setspecs notype_declarator error
345                 { current_declspecs = TREE_VALUE (declspec_stack);
346                   prefix_attributes = TREE_PURPOSE (declspec_stack);
347                   declspec_stack = TREE_CHAIN (declspec_stack);
348                   resume_momentary ($1); }
349         ;
350
351 identifier:
352         IDENTIFIER
353         | TYPENAME
354         ;
355
356 unop:     '&'
357                 { $$ = ADDR_EXPR; }
358         | '-'
359                 { $$ = NEGATE_EXPR; }
360         | '+'
361                 { $$ = CONVERT_EXPR; }
362         | PLUSPLUS
363                 { $$ = PREINCREMENT_EXPR; }
364         | MINUSMINUS
365                 { $$ = PREDECREMENT_EXPR; }
366         | '~'
367                 { $$ = BIT_NOT_EXPR; }
368         | '!'
369                 { $$ = TRUTH_NOT_EXPR; }
370         ;
371
372 expr:   nonnull_exprlist
373                 { $$ = build_compound_expr ($1); }
374         ;
375
376 exprlist:
377           /* empty */
378                 { $$ = NULL_TREE; }
379         | nonnull_exprlist
380         ;
381
382 nonnull_exprlist:
383         expr_no_commas
384                 { $$ = build_tree_list (NULL_TREE, $1); }
385         | nonnull_exprlist ',' expr_no_commas
386                 { chainon ($1, build_tree_list (NULL_TREE, $3)); }
387         ;
388
389 unary_expr:
390         primary
391         | '*' cast_expr   %prec UNARY
392                 { $$ = build_indirect_ref ($2, "unary *"); }
393         /* __extension__ turns off -pedantic for following primary.  */
394         | extension cast_expr     %prec UNARY
395                 { $$ = $2;
396                   pedantic = $<itype>1; }
397         | unop cast_expr  %prec UNARY
398                 { $$ = build_unary_op ($1, $2, 0);
399                   overflow_warning ($$); }
400         /* Refer to the address of a label as a pointer.  */
401         | ANDAND identifier
402                 { tree label = lookup_label ($2);
403                   if (pedantic)
404                     pedwarn ("ANSI C forbids `&&'");
405                   if (label == 0)
406                     $$ = null_pointer_node;
407                   else
408                     {
409                       TREE_USED (label) = 1;
410                       $$ = build1 (ADDR_EXPR, ptr_type_node, label);
411                       TREE_CONSTANT ($$) = 1;
412                     }
413                 }
414 /* This seems to be impossible on some machines, so let's turn it off.
415    You can use __builtin_next_arg to find the anonymous stack args.
416         | '&' ELLIPSIS
417                 { tree types = TYPE_ARG_TYPES (TREE_TYPE (current_function_decl));
418                   $$ = error_mark_node;
419                   if (TREE_VALUE (tree_last (types)) == void_type_node)
420                     error ("`&...' used in function with fixed number of arguments");
421                   else
422                     {
423                       if (pedantic)
424                         pedwarn ("ANSI C forbids `&...'");
425                       $$ = tree_last (DECL_ARGUMENTS (current_function_decl));
426                       $$ = build_unary_op (ADDR_EXPR, $$, 0);
427                     } }
428 */
429         | sizeof unary_expr  %prec UNARY
430                 { skip_evaluation--;
431                   if (TREE_CODE ($2) == COMPONENT_REF
432                       && DECL_C_BIT_FIELD (TREE_OPERAND ($2, 1)))
433                     error ("`sizeof' applied to a bit-field");
434                   $$ = c_sizeof (TREE_TYPE ($2)); }
435         | sizeof '(' typename ')'  %prec HYPERUNARY
436                 { skip_evaluation--;
437                   $$ = c_sizeof (groktypename ($3)); }
438         | alignof unary_expr  %prec UNARY
439                 { skip_evaluation--;
440                   $$ = c_alignof_expr ($2); }
441         | alignof '(' typename ')'  %prec HYPERUNARY
442                 { skip_evaluation--;
443                   $$ = c_alignof (groktypename ($3)); }
444         | REALPART cast_expr %prec UNARY
445                 { $$ = build_unary_op (REALPART_EXPR, $2, 0); }
446         | IMAGPART cast_expr %prec UNARY
447                 { $$ = build_unary_op (IMAGPART_EXPR, $2, 0); }
448         | VA_ARG '(' expr_no_commas ',' typename ')'
449                 { $$ = build_va_arg ($3, groktypename ($5)); }
450         ;
451
452 sizeof:
453         SIZEOF { skip_evaluation++; }
454         ;
455
456 alignof:
457         ALIGNOF { skip_evaluation++; }
458         ;
459
460 cast_expr:
461         unary_expr
462         | '(' typename ')' cast_expr  %prec UNARY
463                 { tree type = groktypename ($2);
464                   $$ = build_c_cast (type, $4); }
465         | '(' typename ')' '{' 
466                 { start_init (NULL_TREE, NULL, 0);
467                   $2 = groktypename ($2);
468                   really_start_incremental_init ($2); }
469           initlist_maybe_comma '}'  %prec UNARY
470                 { char *name;
471                   tree result = pop_init_level (0);
472                   tree type = $2;
473                   finish_init ();
474
475                   if (pedantic && ! flag_isoc9x)
476                     pedwarn ("ANSI C forbids constructor expressions");
477                   if (TYPE_NAME (type) != 0)
478                     {
479                       if (TREE_CODE (TYPE_NAME (type)) == IDENTIFIER_NODE)
480                         name = IDENTIFIER_POINTER (TYPE_NAME (type));
481                       else
482                         name = IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (type)));
483                     }
484                   else
485                     name = "";
486                   $$ = result;
487                   if (TREE_CODE (type) == ARRAY_TYPE && TYPE_SIZE (type) == 0)
488                     {
489                       int failure = complete_array_type (type, $$, 1);
490                       if (failure)
491                         abort ();
492                     }
493                 }
494         ;
495
496 expr_no_commas:
497           cast_expr
498         | expr_no_commas '+' expr_no_commas
499                 { $$ = parser_build_binary_op ($2, $1, $3); }
500         | expr_no_commas '-' expr_no_commas
501                 { $$ = parser_build_binary_op ($2, $1, $3); }
502         | expr_no_commas '*' expr_no_commas
503                 { $$ = parser_build_binary_op ($2, $1, $3); }
504         | expr_no_commas '/' expr_no_commas
505                 { $$ = parser_build_binary_op ($2, $1, $3); }
506         | expr_no_commas '%' expr_no_commas
507                 { $$ = parser_build_binary_op ($2, $1, $3); }
508         | expr_no_commas LSHIFT expr_no_commas
509                 { $$ = parser_build_binary_op ($2, $1, $3); }
510         | expr_no_commas RSHIFT expr_no_commas
511                 { $$ = parser_build_binary_op ($2, $1, $3); }
512         | expr_no_commas ARITHCOMPARE expr_no_commas
513                 { $$ = parser_build_binary_op ($2, $1, $3); }
514         | expr_no_commas EQCOMPARE expr_no_commas
515                 { $$ = parser_build_binary_op ($2, $1, $3); }
516         | expr_no_commas '&' expr_no_commas
517                 { $$ = parser_build_binary_op ($2, $1, $3); }
518         | expr_no_commas '|' expr_no_commas
519                 { $$ = parser_build_binary_op ($2, $1, $3); }
520         | expr_no_commas '^' expr_no_commas
521                 { $$ = parser_build_binary_op ($2, $1, $3); }
522         | expr_no_commas ANDAND
523                 { $1 = truthvalue_conversion (default_conversion ($1));
524                   skip_evaluation += $1 == boolean_false_node; }
525           expr_no_commas
526                 { skip_evaluation -= $1 == boolean_false_node;
527                   $$ = parser_build_binary_op (TRUTH_ANDIF_EXPR, $1, $4); }
528         | expr_no_commas OROR
529                 { $1 = truthvalue_conversion (default_conversion ($1));
530                   skip_evaluation += $1 == boolean_true_node; }
531           expr_no_commas
532                 { skip_evaluation -= $1 == boolean_true_node;
533                   $$ = parser_build_binary_op (TRUTH_ORIF_EXPR, $1, $4); }
534         | expr_no_commas '?'
535                 { $1 = truthvalue_conversion (default_conversion ($1));
536                   skip_evaluation += $1 == boolean_false_node; }
537           expr ':'
538                 { skip_evaluation += (($1 == boolean_true_node)
539                                       - ($1 == boolean_false_node)); }
540           expr_no_commas
541                 { skip_evaluation -= $1 == boolean_true_node;
542                   $$ = build_conditional_expr ($1, $4, $7); }
543         | expr_no_commas '?'
544                 { if (pedantic)
545                     pedwarn ("ANSI C forbids omitting the middle term of a ?: expression");
546                   /* Make sure first operand is calculated only once.  */
547                   $<ttype>2 = save_expr ($1);
548                   $1 = truthvalue_conversion (default_conversion ($<ttype>2));
549                   skip_evaluation += $1 == boolean_true_node; }
550           ':' expr_no_commas
551                 { skip_evaluation -= $1 == boolean_true_node;
552                   $$ = build_conditional_expr ($1, $<ttype>2, $5); }
553         | expr_no_commas '=' expr_no_commas
554                 { char class;
555                   $$ = build_modify_expr ($1, NOP_EXPR, $3);
556                   class = TREE_CODE_CLASS (TREE_CODE ($$));
557                   if (class == 'e' || class == '1'
558                       || class == '2' || class == '<')
559                     C_SET_EXP_ORIGINAL_CODE ($$, MODIFY_EXPR);
560                 }
561         | expr_no_commas ASSIGN expr_no_commas
562                 { char class;
563                   $$ = build_modify_expr ($1, $2, $3);
564                   /* This inhibits warnings in truthvalue_conversion.  */
565                   class = TREE_CODE_CLASS (TREE_CODE ($$));
566                   if (class == 'e' || class == '1'
567                       || class == '2' || class == '<')
568                     C_SET_EXP_ORIGINAL_CODE ($$, ERROR_MARK);
569                 }
570         ;
571
572 primary:
573         IDENTIFIER
574                 {
575                   $$ = lastiddecl;
576                   if (!$$ || $$ == error_mark_node)
577                     {
578                       if (yychar == YYEMPTY)
579                         yychar = YYLEX;
580                       if (yychar == '(')
581                         {
582                             {
583                               /* Ordinary implicit function declaration.  */
584                               $$ = implicitly_declare ($1);
585                               assemble_external ($$);
586                               TREE_USED ($$) = 1;
587                             }
588                         }
589                       else if (current_function_decl == 0)
590                         {
591                           error ("`%s' undeclared here (not in a function)",
592                                  IDENTIFIER_POINTER ($1));
593                           $$ = error_mark_node;
594                         }
595                       else
596                         {
597                             {
598                               if (IDENTIFIER_GLOBAL_VALUE ($1) != error_mark_node
599                                   || IDENTIFIER_ERROR_LOCUS ($1) != current_function_decl)
600                                 {
601                                   error ("`%s' undeclared (first use in this function)",
602                                          IDENTIFIER_POINTER ($1));
603
604                                   if (! undeclared_variable_notice)
605                                     {
606                                       error ("(Each undeclared identifier is reported only once");
607                                       error ("for each function it appears in.)");
608                                       undeclared_variable_notice = 1;
609                                     }
610                                 }
611                               $$ = error_mark_node;
612                               /* Prevent repeated error messages.  */
613                               IDENTIFIER_GLOBAL_VALUE ($1) = error_mark_node;
614                               IDENTIFIER_ERROR_LOCUS ($1) = current_function_decl;
615                             }
616                         }
617                     }
618                   else if (TREE_TYPE ($$) == error_mark_node)
619                     $$ = error_mark_node;
620                   else if (C_DECL_ANTICIPATED ($$))
621                     {
622                       /* The first time we see a build-in function used,
623                          if it has not been declared.  */
624                       C_DECL_ANTICIPATED ($$) = 0;
625                       if (yychar == YYEMPTY)
626                         yychar = YYLEX;
627                       if (yychar == '(')
628                         {
629                           /* Omit the implicit declaration we
630                              would ordinarily do, so we don't lose
631                              the actual built in type.
632                              But print a diagnostic for the mismatch.  */
633                             if (TREE_CODE ($$) != FUNCTION_DECL)
634                               error ("`%s' implicitly declared as function",
635                                      IDENTIFIER_POINTER (DECL_NAME ($$)));
636                           else if ((TYPE_MODE (TREE_TYPE (TREE_TYPE ($$)))
637                                     != TYPE_MODE (integer_type_node))
638                                    && (TREE_TYPE (TREE_TYPE ($$))
639                                        != void_type_node))
640                             pedwarn ("type mismatch in implicit declaration for built-in function `%s'",
641                                      IDENTIFIER_POINTER (DECL_NAME ($$)));
642                           /* If it really returns void, change that to int.  */
643                           if (TREE_TYPE (TREE_TYPE ($$)) == void_type_node)
644                             TREE_TYPE ($$)
645                               = build_function_type (integer_type_node,
646                                                      TYPE_ARG_TYPES (TREE_TYPE ($$)));
647                         }
648                       else
649                         pedwarn ("built-in function `%s' used without declaration",
650                                  IDENTIFIER_POINTER (DECL_NAME ($$)));
651
652                       /* Do what we would ordinarily do when a fn is used.  */
653                       assemble_external ($$);
654                       TREE_USED ($$) = 1;
655                     }
656                   else
657                     {
658                       assemble_external ($$);
659                       TREE_USED ($$) = 1;
660                     }
661
662                   if (TREE_CODE ($$) == CONST_DECL)
663                     {
664                       $$ = DECL_INITIAL ($$);
665                       /* This is to prevent an enum whose value is 0
666                          from being considered a null pointer constant.  */
667                       $$ = build1 (NOP_EXPR, TREE_TYPE ($$), $$);
668                       TREE_CONSTANT ($$) = 1;
669                     }
670                 }
671         | CONSTANT
672         | string
673                 { $$ = combine_strings ($1); }
674         | '(' expr ')'
675                 { char class = TREE_CODE_CLASS (TREE_CODE ($2));
676                   if (class == 'e' || class == '1'
677                       || class == '2' || class == '<')
678                     C_SET_EXP_ORIGINAL_CODE ($2, ERROR_MARK);
679                   $$ = $2; }
680         | '(' error ')'
681                 { $$ = error_mark_node; }
682         | compstmt_primary_start compstmt_nostart ')'
683                 { tree rtl_exp;
684                   if (pedantic)
685                     pedwarn ("ANSI C forbids braced-groups within expressions");
686                   pop_iterator_stack ();
687                   pop_label_level ();
688                   rtl_exp = expand_end_stmt_expr ($1);
689                   /* The statements have side effects, so the group does.  */
690                   TREE_SIDE_EFFECTS (rtl_exp) = 1;
691
692                   if (TREE_CODE ($2) == BLOCK)
693                     {
694                       /* Make a BIND_EXPR for the BLOCK already made.  */
695                       $$ = build (BIND_EXPR, TREE_TYPE (rtl_exp),
696                                   NULL_TREE, rtl_exp, $2);
697                       /* Remove the block from the tree at this point.
698                          It gets put back at the proper place
699                          when the BIND_EXPR is expanded.  */
700                       delete_block ($2);
701                     }
702                   else
703                     $$ = $2;
704                 }
705         | compstmt_primary_start error ')'
706                 {
707                   /* Make sure we call expand_end_stmt_expr.  Otherwise
708                      we are likely to lose sequences and crash later.  */
709                   pop_iterator_stack ();
710                   pop_label_level ();
711                   expand_end_stmt_expr ($1);
712                   $$ = error_mark_node;
713                 }
714         | primary '(' exprlist ')'   %prec '.'
715                 { $$ = build_function_call ($1, $3); }
716         | primary '[' expr ']'   %prec '.'
717                 { $$ = build_array_ref ($1, $3); }
718         | primary '.' identifier
719                 {
720                     $$ = build_component_ref ($1, $3);
721                 }
722         | primary POINTSAT identifier
723                 {
724                   tree expr = build_indirect_ref ($1, "->");
725
726                     $$ = build_component_ref (expr, $3);
727                 }
728         | primary PLUSPLUS
729                 { $$ = build_unary_op (POSTINCREMENT_EXPR, $1, 0); }
730         | primary MINUSMINUS
731                 { $$ = build_unary_op (POSTDECREMENT_EXPR, $1, 0); }
732         ;
733
734 /* Produces a STRING_CST with perhaps more STRING_CSTs chained onto it.  */
735 string:
736           STRING
737         | string STRING
738                 { $$ = chainon ($1, $2); }
739         ;
740
741
742 old_style_parm_decls:
743         /* empty */
744         | datadecls
745         | datadecls ELLIPSIS
746                 /* ... is used here to indicate a varargs function.  */
747                 { c_mark_varargs ();
748                   if (pedantic)
749                     pedwarn ("ANSI C does not permit use of `varargs.h'"); }
750         ;
751
752 /* The following are analogous to lineno_decl, decls and decl
753    except that they do not allow nested functions.
754    They are used for old-style parm decls.  */
755 lineno_datadecl:
756           save_filename save_lineno datadecl
757                 { }
758         ;
759
760 datadecls:
761         lineno_datadecl
762         | errstmt
763         | datadecls lineno_datadecl
764         | lineno_datadecl errstmt
765         ;
766
767 /* We don't allow prefix attributes here because they cause reduce/reduce
768    conflicts: we can't know whether we're parsing a function decl with
769    attribute suffix, or function defn with attribute prefix on first old
770    style parm.  */
771 datadecl:
772         typed_declspecs_no_prefix_attr setspecs initdecls ';'
773                 { current_declspecs = TREE_VALUE (declspec_stack);
774                   prefix_attributes = TREE_PURPOSE (declspec_stack);
775                   declspec_stack = TREE_CHAIN (declspec_stack);
776                   resume_momentary ($2); }
777         | declmods_no_prefix_attr setspecs notype_initdecls ';'
778                 { current_declspecs = TREE_VALUE (declspec_stack);      
779                   prefix_attributes = TREE_PURPOSE (declspec_stack);
780                   declspec_stack = TREE_CHAIN (declspec_stack);
781                   resume_momentary ($2); }
782         | typed_declspecs_no_prefix_attr ';'
783                 { shadow_tag_warned ($1, 1);
784                   pedwarn ("empty declaration"); }
785         | declmods_no_prefix_attr ';'
786                 { pedwarn ("empty declaration"); }
787         ;
788
789 /* This combination which saves a lineno before a decl
790    is the normal thing to use, rather than decl itself.
791    This is to avoid shift/reduce conflicts in contexts
792    where statement labels are allowed.  */
793 lineno_decl:
794           save_filename save_lineno decl
795                 { }
796         ;
797
798 decls:
799         lineno_decl
800         | errstmt
801         | decls lineno_decl
802         | lineno_decl errstmt
803         ;
804
805 /* records the type and storage class specs to use for processing
806    the declarators that follow.
807    Maintains a stack of outer-level values of current_declspecs,
808    for the sake of parm declarations nested in function declarators.  */
809 setspecs: /* empty */
810                 { $$ = suspend_momentary ();
811                   pending_xref_error ();
812                   declspec_stack = tree_cons (prefix_attributes,
813                                               current_declspecs,
814                                               declspec_stack);
815                   split_specs_attrs ($<ttype>0,
816                                      &current_declspecs, &prefix_attributes); }
817         ;
818
819 /* ??? Yuck.  See after_type_declarator.  */
820 setattrs: /* empty */
821                 { prefix_attributes = chainon (prefix_attributes, $<ttype>0); }
822         ;
823
824 decl:
825         typed_declspecs setspecs initdecls ';'
826                 { current_declspecs = TREE_VALUE (declspec_stack);
827                   prefix_attributes = TREE_PURPOSE (declspec_stack);
828                   declspec_stack = TREE_CHAIN (declspec_stack);
829                   resume_momentary ($2); }
830         | declmods setspecs notype_initdecls ';'
831                 { current_declspecs = TREE_VALUE (declspec_stack);
832                   prefix_attributes = TREE_PURPOSE (declspec_stack);
833                   declspec_stack = TREE_CHAIN (declspec_stack);
834                   resume_momentary ($2); }
835         | typed_declspecs setspecs nested_function
836                 { current_declspecs = TREE_VALUE (declspec_stack);
837                   prefix_attributes = TREE_PURPOSE (declspec_stack);
838                   declspec_stack = TREE_CHAIN (declspec_stack);
839                   resume_momentary ($2); }
840         | declmods setspecs notype_nested_function
841                 { current_declspecs = TREE_VALUE (declspec_stack);
842                   prefix_attributes = TREE_PURPOSE (declspec_stack);
843                   declspec_stack = TREE_CHAIN (declspec_stack);
844                   resume_momentary ($2); }
845         | typed_declspecs ';'
846                 { shadow_tag ($1); }
847         | declmods ';'
848                 { pedwarn ("empty declaration"); }
849         | extension decl
850                 { pedantic = $<itype>1; }
851         ;
852
853 /* Declspecs which contain at least one type specifier or typedef name.
854    (Just `const' or `volatile' is not enough.)
855    A typedef'd name following these is taken as a name to be declared.
856    Declspecs have a non-NULL TREE_VALUE, attributes do not.  */
857
858 typed_declspecs:
859           typespec reserved_declspecs
860                 { $$ = tree_cons (NULL_TREE, $1, $2); }
861         | declmods typespec reserved_declspecs
862                 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
863         ;
864
865 reserved_declspecs:  /* empty */
866                 { $$ = NULL_TREE; }
867         | reserved_declspecs typespecqual_reserved
868                 { $$ = tree_cons (NULL_TREE, $2, $1); }
869         | reserved_declspecs SCSPEC
870                 { if (extra_warnings)
871                     warning ("`%s' is not at beginning of declaration",
872                              IDENTIFIER_POINTER ($2));
873                   $$ = tree_cons (NULL_TREE, $2, $1); }
874         | reserved_declspecs attributes
875                 { $$ = tree_cons ($2, NULL_TREE, $1); }
876         ;
877
878 typed_declspecs_no_prefix_attr:
879           typespec reserved_declspecs_no_prefix_attr
880                 { $$ = tree_cons (NULL_TREE, $1, $2); }
881         | declmods_no_prefix_attr typespec reserved_declspecs_no_prefix_attr
882                 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
883         ;
884
885 reserved_declspecs_no_prefix_attr:
886           /* empty */
887                 { $$ = NULL_TREE; }
888         | reserved_declspecs_no_prefix_attr typespecqual_reserved
889                 { $$ = tree_cons (NULL_TREE, $2, $1); }
890         | reserved_declspecs_no_prefix_attr SCSPEC
891                 { if (extra_warnings)
892                     warning ("`%s' is not at beginning of declaration",
893                              IDENTIFIER_POINTER ($2));
894                   $$ = tree_cons (NULL_TREE, $2, $1); }
895         ;
896
897 /* List of just storage classes, type modifiers, and prefix attributes.
898    A declaration can start with just this, but then it cannot be used
899    to redeclare a typedef-name.
900    Declspecs have a non-NULL TREE_VALUE, attributes do not.  */
901
902 declmods:
903           declmods_no_prefix_attr
904                 { $$ = $1; }
905         | attributes
906                 { $$ = tree_cons ($1, NULL_TREE, NULL_TREE); }
907         | declmods declmods_no_prefix_attr
908                 { $$ = chainon ($2, $1); }
909         | declmods attributes
910                 { $$ = tree_cons ($2, NULL_TREE, $1); }
911         ;
912
913 declmods_no_prefix_attr:
914           TYPE_QUAL
915                 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
916                   TREE_STATIC ($$) = 1; }
917         | SCSPEC
918                 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
919         | declmods_no_prefix_attr TYPE_QUAL
920                 { $$ = tree_cons (NULL_TREE, $2, $1);
921                   TREE_STATIC ($$) = 1; }
922         | declmods_no_prefix_attr SCSPEC
923                 { if (extra_warnings && TREE_STATIC ($1))
924                     warning ("`%s' is not at beginning of declaration",
925                              IDENTIFIER_POINTER ($2));
926                   $$ = tree_cons (NULL_TREE, $2, $1);
927                   TREE_STATIC ($$) = TREE_STATIC ($1); }
928         ;
929
930
931 /* Used instead of declspecs where storage classes are not allowed
932    (that is, for typenames and structure components).
933    Don't accept a typedef-name if anything but a modifier precedes it.  */
934
935 typed_typespecs:
936           typespec reserved_typespecquals
937                 { $$ = tree_cons (NULL_TREE, $1, $2); }
938         | nonempty_type_quals typespec reserved_typespecquals
939                 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
940         ;
941
942 reserved_typespecquals:  /* empty */
943                 { $$ = NULL_TREE; }
944         | reserved_typespecquals typespecqual_reserved
945                 { $$ = tree_cons (NULL_TREE, $2, $1); }
946         ;
947
948 /* A typespec (but not a type qualifier).
949    Once we have seen one of these in a declaration,
950    if a typedef name appears then it is being redeclared.  */
951
952 typespec: TYPESPEC
953         | structsp
954         | TYPENAME
955                 { /* For a typedef name, record the meaning, not the name.
956                      In case of `foo foo, bar;'.  */
957                   $$ = lookup_name ($1); }
958         | TYPEOF '(' expr ')'
959                 { $$ = TREE_TYPE ($3); }
960         | TYPEOF '(' typename ')'
961                 { $$ = groktypename ($3); }
962         ;
963
964 /* A typespec that is a reserved word, or a type qualifier.  */
965
966 typespecqual_reserved: TYPESPEC
967         | TYPE_QUAL
968         | structsp
969         ;
970
971 initdecls:
972         initdcl
973         | initdecls ',' initdcl
974         ;
975
976 notype_initdecls:
977         notype_initdcl
978         | notype_initdecls ',' initdcl
979         ;
980
981 maybeasm:
982           /* empty */
983                 { $$ = NULL_TREE; }
984         | ASM_KEYWORD '(' string ')'
985                 { if (TREE_CHAIN ($3)) $3 = combine_strings ($3);
986                   $$ = $3;
987                 }
988         ;
989
990 initdcl:
991           declarator maybeasm maybe_attribute '='
992                 { $<ttype>$ = start_decl ($1, current_declspecs, 1,
993                                           $3, prefix_attributes);
994                   start_init ($<ttype>$, $2, global_bindings_p ()); }
995           init
996 /* Note how the declaration of the variable is in effect while its init is parsed! */
997                 { finish_init ();
998                   finish_decl ($<ttype>5, $6, $2); }
999         | declarator maybeasm maybe_attribute
1000                 { tree d = start_decl ($1, current_declspecs, 0,
1001                                        $3, prefix_attributes);
1002                   finish_decl (d, NULL_TREE, $2); 
1003                 }
1004         ;
1005
1006 notype_initdcl:
1007           notype_declarator maybeasm maybe_attribute '='
1008                 { $<ttype>$ = start_decl ($1, current_declspecs, 1,
1009                                           $3, prefix_attributes);
1010                   start_init ($<ttype>$, $2, global_bindings_p ()); }
1011           init
1012 /* Note how the declaration of the variable is in effect while its init is parsed! */
1013                 { finish_init ();
1014                   decl_attributes ($<ttype>5, $3, prefix_attributes);
1015                   finish_decl ($<ttype>5, $6, $2); }
1016         | notype_declarator maybeasm maybe_attribute
1017                 { tree d = start_decl ($1, current_declspecs, 0,
1018                                        $3, prefix_attributes);
1019                   finish_decl (d, NULL_TREE, $2); }
1020         ;
1021 /* the * rules are dummies to accept the Apollo extended syntax
1022    so that the header files compile. */
1023 maybe_attribute:
1024       /* empty */
1025                 { $$ = NULL_TREE; }
1026         | attributes
1027                 { $$ = $1; }
1028         ;
1029  
1030 attributes:
1031       attribute
1032                 { $$ = $1; }
1033         | attributes attribute
1034                 { $$ = chainon ($1, $2); }
1035         ;
1036
1037 attribute:
1038       ATTRIBUTE '(' '(' attribute_list ')' ')'
1039                 { $$ = $4; }
1040         ;
1041
1042 attribute_list:
1043       attrib
1044                 { $$ = $1; }
1045         | attribute_list ',' attrib
1046                 { $$ = chainon ($1, $3); }
1047         ;
1048  
1049 attrib:
1050     /* empty */
1051                 { $$ = NULL_TREE; }
1052         | any_word
1053                 { $$ = build_tree_list ($1, NULL_TREE); }
1054         | any_word '(' IDENTIFIER ')'
1055                 { $$ = build_tree_list ($1, build_tree_list (NULL_TREE, $3)); }
1056         | any_word '(' IDENTIFIER ',' nonnull_exprlist ')'
1057                 { $$ = build_tree_list ($1, tree_cons (NULL_TREE, $3, $5)); }
1058         | any_word '(' exprlist ')'
1059                 { $$ = build_tree_list ($1, $3); }
1060         ;
1061
1062 /* This still leaves out most reserved keywords,
1063    shouldn't we include them?  */
1064
1065 any_word:
1066           identifier
1067         | SCSPEC
1068         | TYPESPEC
1069         | TYPE_QUAL
1070         ;
1071 \f
1072 /* Initializers.  `init' is the entry point.  */
1073
1074 init:
1075         expr_no_commas
1076         | '{'
1077                 { really_start_incremental_init (NULL_TREE);
1078                   /* Note that the call to clear_momentary
1079                      is in process_init_element.  */
1080                   push_momentary (); }
1081           initlist_maybe_comma '}'
1082                 { $$ = pop_init_level (0);
1083                   if ($$ == error_mark_node
1084                       && ! (yychar == STRING || yychar == CONSTANT))
1085                     pop_momentary ();
1086                   else
1087                     pop_momentary_nofree (); }
1088
1089         | error
1090                 { $$ = error_mark_node; }
1091         ;
1092
1093 /* `initlist_maybe_comma' is the guts of an initializer in braces.  */
1094 initlist_maybe_comma:
1095           /* empty */
1096                 { if (pedantic)
1097                     pedwarn ("ANSI C forbids empty initializer braces"); }
1098         | initlist1 maybecomma
1099         ;
1100
1101 initlist1:
1102           initelt
1103         | initlist1 ',' initelt
1104         ;
1105
1106 /* `initelt' is a single element of an initializer.
1107    It may use braces.  */
1108 initelt:
1109           designator_list '=' initval
1110         | designator initval
1111         | identifier ':'
1112                 { set_init_label ($1); }
1113           initval
1114         | initval
1115         ;
1116
1117 initval:
1118           '{'
1119                 { push_init_level (0); }
1120           initlist_maybe_comma '}'
1121                 { process_init_element (pop_init_level (0)); }
1122         | expr_no_commas
1123                 { process_init_element ($1); }
1124         | error
1125         ;
1126
1127 designator_list:
1128           designator
1129         | designator_list designator
1130         ;
1131
1132 designator:
1133           '.' identifier
1134                 { set_init_label ($2); }
1135         /* These are for labeled elements.  The syntax for an array element
1136            initializer conflicts with the syntax for an Objective-C message,
1137            so don't include these productions in the Objective-C grammar.  */
1138         | '[' expr_no_commas ELLIPSIS expr_no_commas ']'
1139                 { set_init_index ($2, $4); }
1140         | '[' expr_no_commas ']'
1141                 { set_init_index ($2, NULL_TREE); }
1142         ;
1143 \f
1144 nested_function:
1145           declarator
1146                 { if (pedantic)
1147                     pedwarn ("ANSI C forbids nested functions");
1148
1149                   push_function_context ();
1150                   if (! start_function (current_declspecs, $1,
1151                                         prefix_attributes, NULL_TREE, 1))
1152                     {
1153                       pop_function_context ();
1154                       YYERROR1;
1155                     }
1156                   reinit_parse_for_function (); }
1157            old_style_parm_decls
1158                 { store_parm_decls (); }
1159 /* This used to use compstmt_or_error.
1160    That caused a bug with input `f(g) int g {}',
1161    where the use of YYERROR1 above caused an error
1162    which then was handled by compstmt_or_error.
1163    There followed a repeated execution of that same rule,
1164    which called YYERROR1 again, and so on.  */
1165           compstmt
1166                 { finish_function (1);
1167                   pop_function_context (); }
1168         ;
1169
1170 notype_nested_function:
1171           notype_declarator
1172                 { if (pedantic)
1173                     pedwarn ("ANSI C forbids nested functions");
1174
1175                   push_function_context ();
1176                   if (! start_function (current_declspecs, $1,
1177                                         prefix_attributes, NULL_TREE, 1))
1178                     {
1179                       pop_function_context ();
1180                       YYERROR1;
1181                     }
1182                   reinit_parse_for_function (); }
1183           old_style_parm_decls
1184                 { store_parm_decls (); }
1185 /* This used to use compstmt_or_error.
1186    That caused a bug with input `f(g) int g {}',
1187    where the use of YYERROR1 above caused an error
1188    which then was handled by compstmt_or_error.
1189    There followed a repeated execution of that same rule,
1190    which called YYERROR1 again, and so on.  */
1191           compstmt
1192                 { finish_function (1);
1193                   pop_function_context (); }
1194         ;
1195
1196 /* Any kind of declarator (thus, all declarators allowed
1197    after an explicit typespec).  */
1198
1199 declarator:
1200           after_type_declarator
1201         | notype_declarator
1202         ;
1203
1204 /* A declarator that is allowed only after an explicit typespec.  */
1205
1206 after_type_declarator:
1207           '(' after_type_declarator ')'
1208                 { $$ = $2; }
1209         | after_type_declarator '(' parmlist_or_identifiers  %prec '.'
1210                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1211 /*      | after_type_declarator '(' error ')'  %prec '.'
1212                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1213                   poplevel (0, 0, 0); }  */
1214         | after_type_declarator '[' expr ']'  %prec '.'
1215                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1216         | after_type_declarator '[' ']'  %prec '.'
1217                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1218         | '*' type_quals after_type_declarator  %prec UNARY
1219                 { $$ = make_pointer_declarator ($2, $3); }
1220         /* ??? Yuck.  setattrs is a quick hack.  We can't use
1221            prefix_attributes because $1 only applies to this
1222            declarator.  We assume setspecs has already been done.
1223            setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
1224            attributes could be recognized here or in `attributes').  */
1225         | attributes setattrs after_type_declarator
1226                 { $$ = $3; }
1227         | TYPENAME
1228         ;
1229
1230 /* Kinds of declarator that can appear in a parameter list
1231    in addition to notype_declarator.  This is like after_type_declarator
1232    but does not allow a typedef name in parentheses as an identifier
1233    (because it would conflict with a function with that typedef as arg).  */
1234
1235 parm_declarator:
1236           parm_declarator '(' parmlist_or_identifiers  %prec '.'
1237                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1238 /*      | parm_declarator '(' error ')'  %prec '.'
1239                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1240                   poplevel (0, 0, 0); }  */
1241         | parm_declarator '[' '*' ']'  %prec '.'
1242                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE);
1243                   if (! flag_isoc9x)
1244                     error ("`[*]' in parameter declaration only allowed in ISO C 9x");
1245                 }
1246         | parm_declarator '[' expr ']'  %prec '.'
1247                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1248         | parm_declarator '[' ']'  %prec '.'
1249                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1250         | '*' type_quals parm_declarator  %prec UNARY
1251                 { $$ = make_pointer_declarator ($2, $3); }
1252         /* ??? Yuck.  setattrs is a quick hack.  We can't use
1253            prefix_attributes because $1 only applies to this
1254            declarator.  We assume setspecs has already been done.
1255            setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
1256            attributes could be recognized here or in `attributes').  */
1257         | attributes setattrs parm_declarator
1258                 { $$ = $3; }
1259         | TYPENAME
1260         ;
1261
1262 /* A declarator allowed whether or not there has been
1263    an explicit typespec.  These cannot redeclare a typedef-name.  */
1264
1265 notype_declarator:
1266           notype_declarator '(' parmlist_or_identifiers  %prec '.'
1267                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1268 /*      | notype_declarator '(' error ')'  %prec '.'
1269                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1270                   poplevel (0, 0, 0); }  */
1271         | '(' notype_declarator ')'
1272                 { $$ = $2; }
1273         | '*' type_quals notype_declarator  %prec UNARY
1274                 { $$ = make_pointer_declarator ($2, $3); }
1275         | notype_declarator '[' '*' ']'  %prec '.'
1276                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE);
1277                   if (! flag_isoc9x)
1278                     error ("`[*]' in parameter declaration only allowed in ISO C 9x");
1279                 }
1280         | notype_declarator '[' expr ']'  %prec '.'
1281                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1282         | notype_declarator '[' ']'  %prec '.'
1283                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1284         /* ??? Yuck.  setattrs is a quick hack.  We can't use
1285            prefix_attributes because $1 only applies to this
1286            declarator.  We assume setspecs has already been done.
1287            setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
1288            attributes could be recognized here or in `attributes').  */
1289         | attributes setattrs notype_declarator
1290                 { $$ = $3; }
1291         | IDENTIFIER
1292         ;
1293
1294 struct_head:
1295           STRUCT
1296                 { $$ = NULL_TREE; }
1297         | STRUCT attributes
1298                 { $$ = $2; }
1299         ;
1300
1301 union_head:
1302           UNION
1303                 { $$ = NULL_TREE; }
1304         | UNION attributes
1305                 { $$ = $2; }
1306         ;
1307
1308 enum_head:
1309           ENUM
1310                 { $$ = NULL_TREE; }
1311         | ENUM attributes
1312                 { $$ = $2; }
1313         ;
1314
1315 structsp:
1316           struct_head identifier '{'
1317                 { $$ = start_struct (RECORD_TYPE, $2);
1318                   /* Start scope of tag before parsing components.  */
1319                 }
1320           component_decl_list '}' maybe_attribute 
1321                 { $$ = finish_struct ($<ttype>4, $5, chainon ($1, $7)); }
1322         | struct_head '{' component_decl_list '}' maybe_attribute
1323                 { $$ = finish_struct (start_struct (RECORD_TYPE, NULL_TREE),
1324                                       $3, chainon ($1, $5));
1325                 }
1326         | struct_head identifier
1327                 { $$ = xref_tag (RECORD_TYPE, $2); }
1328         | union_head identifier '{'
1329                 { $$ = start_struct (UNION_TYPE, $2); }
1330           component_decl_list '}' maybe_attribute
1331                 { $$ = finish_struct ($<ttype>4, $5, chainon ($1, $7)); }
1332         | union_head '{' component_decl_list '}' maybe_attribute
1333                 { $$ = finish_struct (start_struct (UNION_TYPE, NULL_TREE),
1334                                       $3, chainon ($1, $5));
1335                 }
1336         | union_head identifier
1337                 { $$ = xref_tag (UNION_TYPE, $2); }
1338         | enum_head identifier '{'
1339                 { $<itype>3 = suspend_momentary ();
1340                   $$ = start_enum ($2); }
1341           enumlist maybecomma_warn '}' maybe_attribute
1342                 { $$= finish_enum ($<ttype>4, nreverse ($5), chainon ($1, $8));
1343                   resume_momentary ($<itype>3); }
1344         | enum_head '{'
1345                 { $<itype>2 = suspend_momentary ();
1346                   $$ = start_enum (NULL_TREE); }
1347           enumlist maybecomma_warn '}' maybe_attribute
1348                 { $$= finish_enum ($<ttype>3, nreverse ($4), chainon ($1, $7));
1349                   resume_momentary ($<itype>2); }
1350         | enum_head identifier
1351                 { $$ = xref_tag (ENUMERAL_TYPE, $2); }
1352         ;
1353
1354 maybecomma:
1355           /* empty */
1356         | ','
1357         ;
1358
1359 maybecomma_warn:
1360           /* empty */
1361         | ','
1362                 { if (pedantic && ! flag_isoc9x)
1363                     pedwarn ("comma at end of enumerator list"); }
1364         ;
1365
1366 component_decl_list:
1367           component_decl_list2
1368                 { $$ = $1; }
1369         | component_decl_list2 component_decl
1370                 { $$ = chainon ($1, $2);
1371                   pedwarn ("no semicolon at end of struct or union"); }
1372         ;
1373
1374 component_decl_list2:   /* empty */
1375                 { $$ = NULL_TREE; }
1376         | component_decl_list2 component_decl ';'
1377                 { $$ = chainon ($1, $2); }
1378         | component_decl_list2 ';'
1379                 { if (pedantic)
1380                     pedwarn ("extra semicolon in struct or union specified"); }
1381         ;
1382
1383 /* There is a shift-reduce conflict here, because `components' may
1384    start with a `typename'.  It happens that shifting (the default resolution)
1385    does the right thing, because it treats the `typename' as part of
1386    a `typed_typespecs'.
1387
1388    It is possible that this same technique would allow the distinction
1389    between `notype_initdecls' and `initdecls' to be eliminated.
1390    But I am being cautious and not trying it.  */
1391
1392 component_decl:
1393           typed_typespecs setspecs components
1394                 { $$ = $3;
1395                   current_declspecs = TREE_VALUE (declspec_stack);
1396                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1397                   declspec_stack = TREE_CHAIN (declspec_stack);
1398                   resume_momentary ($2); }
1399         | typed_typespecs
1400                 { if (pedantic)
1401                     pedwarn ("ANSI C forbids member declarations with no members");
1402                   shadow_tag($1);
1403                   $$ = NULL_TREE; }
1404         | nonempty_type_quals setspecs components
1405                 { $$ = $3;
1406                   current_declspecs = TREE_VALUE (declspec_stack);
1407                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1408                   declspec_stack = TREE_CHAIN (declspec_stack);
1409                   resume_momentary ($2); }
1410         | nonempty_type_quals
1411                 { if (pedantic)
1412                     pedwarn ("ANSI C forbids member declarations with no members");
1413                   shadow_tag($1);
1414                   $$ = NULL_TREE; }
1415         | error
1416                 { $$ = NULL_TREE; }
1417         | extension component_decl
1418                 { $$ = $2;
1419                   pedantic = $<itype>1; }
1420         ;
1421
1422 components:
1423           component_declarator
1424         | components ',' component_declarator
1425                 { $$ = chainon ($1, $3); }
1426         ;
1427
1428 component_declarator:
1429           save_filename save_lineno declarator maybe_attribute
1430                 { $$ = grokfield ($1, $2, $3, current_declspecs, NULL_TREE);
1431                   decl_attributes ($$, $4, prefix_attributes); }
1432         | save_filename save_lineno
1433           declarator ':' expr_no_commas maybe_attribute
1434                 { $$ = grokfield ($1, $2, $3, current_declspecs, $5);
1435                   decl_attributes ($$, $6, prefix_attributes); }
1436         | save_filename save_lineno ':' expr_no_commas maybe_attribute
1437                 { $$ = grokfield ($1, $2, NULL_TREE, current_declspecs, $4);
1438                   decl_attributes ($$, $5, prefix_attributes); }
1439         ;
1440
1441 /* We chain the enumerators in reverse order.
1442    They are put in forward order where enumlist is used.
1443    (The order used to be significant, but no longer is so.
1444    However, we still maintain the order, just to be clean.)  */
1445
1446 enumlist:
1447           enumerator
1448         | enumlist ',' enumerator
1449                 { if ($1 == error_mark_node)
1450                     $$ = $1;
1451                   else
1452                     $$ = chainon ($3, $1); }
1453         | error
1454                 { $$ = error_mark_node; }
1455         ;
1456
1457
1458 enumerator:
1459           identifier
1460                 { $$ = build_enumerator ($1, NULL_TREE); }
1461         | identifier '=' expr_no_commas
1462                 { $$ = build_enumerator ($1, $3); }
1463         ;
1464
1465 typename:
1466         typed_typespecs absdcl
1467                 { $$ = build_tree_list ($1, $2); }
1468         | nonempty_type_quals absdcl
1469                 { $$ = build_tree_list ($1, $2); }
1470         ;
1471
1472 absdcl:   /* an absolute declarator */
1473         /* empty */
1474                 { $$ = NULL_TREE; }
1475         | absdcl1
1476         ;
1477
1478 nonempty_type_quals:
1479           TYPE_QUAL
1480                 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
1481         | nonempty_type_quals TYPE_QUAL
1482                 { $$ = tree_cons (NULL_TREE, $2, $1); }
1483         ;
1484
1485 type_quals:
1486           /* empty */
1487                 { $$ = NULL_TREE; }
1488         | type_quals TYPE_QUAL
1489                 { $$ = tree_cons (NULL_TREE, $2, $1); }
1490         ;
1491
1492 absdcl1:  /* a nonempty absolute declarator */
1493           '(' absdcl1 ')'
1494                 { $$ = $2; }
1495           /* `(typedef)1' is `int'.  */
1496         | '*' type_quals absdcl1  %prec UNARY
1497                 { $$ = make_pointer_declarator ($2, $3); }
1498         | '*' type_quals  %prec UNARY
1499                 { $$ = make_pointer_declarator ($2, NULL_TREE); }
1500         | absdcl1 '(' parmlist  %prec '.'
1501                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1502         | absdcl1 '[' expr ']'  %prec '.'
1503                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1504         | absdcl1 '[' ']'  %prec '.'
1505                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1506         | '(' parmlist  %prec '.'
1507                 { $$ = build_nt (CALL_EXPR, NULL_TREE, $2, NULL_TREE); }
1508         | '[' expr ']'  %prec '.'
1509                 { $$ = build_nt (ARRAY_REF, NULL_TREE, $2); }
1510         | '[' ']'  %prec '.'
1511                 { $$ = build_nt (ARRAY_REF, NULL_TREE, NULL_TREE); }
1512         /* ??? It appears we have to support attributes here, however
1513            using prefix_attributes is wrong.  */
1514         | attributes setattrs absdcl1
1515                 { $$ = $3; }
1516         ;
1517
1518 /* at least one statement, the first of which parses without error.  */
1519 /* stmts is used only after decls, so an invalid first statement
1520    is actually regarded as an invalid decl and part of the decls.  */
1521
1522 stmts:
1523         lineno_stmt_or_labels
1524                 {
1525                   if (pedantic && $1)
1526                     pedwarn ("ANSI C forbids label at end of compound statement");
1527                 }
1528         ;
1529
1530 lineno_stmt_or_labels:
1531           lineno_stmt_or_label
1532         | lineno_stmt_or_labels lineno_stmt_or_label
1533                 { $$ = $2; }
1534         | lineno_stmt_or_labels errstmt
1535                 { $$ = 0; }
1536         ;
1537
1538 xstmts:
1539         /* empty */
1540         | stmts
1541         ;
1542
1543 errstmt:  error ';'
1544         ;
1545
1546 pushlevel:  /* empty */
1547                 { emit_line_note (input_filename, lineno);
1548                   pushlevel (0);
1549                   clear_last_expr ();
1550                   push_momentary ();
1551                   expand_start_bindings (0);
1552                 }
1553         ;
1554
1555 /* Read zero or more forward-declarations for labels
1556    that nested functions can jump to.  */
1557 maybe_label_decls:
1558           /* empty */
1559         | label_decls
1560                 { if (pedantic)
1561                     pedwarn ("ANSI C forbids label declarations"); }
1562         ;
1563
1564 label_decls:
1565           label_decl
1566         | label_decls label_decl
1567         ;
1568
1569 label_decl:
1570           LABEL identifiers_or_typenames ';'
1571                 { tree link;
1572                   for (link = $2; link; link = TREE_CHAIN (link))
1573                     {
1574                       tree label = shadow_label (TREE_VALUE (link));
1575                       C_DECLARED_LABEL_FLAG (label) = 1;
1576                       declare_nonlocal_label (label);
1577                     }
1578                 }
1579         ;
1580
1581 /* This is the body of a function definition.
1582    It causes syntax errors to ignore to the next openbrace.  */
1583 compstmt_or_error:
1584           compstmt
1585                 {}
1586         | error compstmt
1587         ;
1588
1589 compstmt_start: '{' { compstmt_count++; }
1590
1591 compstmt_nostart: '}'
1592                 { $$ = convert (void_type_node, integer_zero_node); }
1593         | pushlevel maybe_label_decls decls xstmts '}'
1594                 { emit_line_note (input_filename, lineno);
1595                   expand_end_bindings (getdecls (), 1, 0);
1596                   $$ = poplevel (1, 1, 0);
1597                   if (yychar == CONSTANT || yychar == STRING)
1598                     pop_momentary_nofree ();
1599                   else
1600                     pop_momentary (); }
1601         | pushlevel maybe_label_decls error '}'
1602                 { emit_line_note (input_filename, lineno);
1603                   expand_end_bindings (getdecls (), kept_level_p (), 0);
1604                   $$ = poplevel (kept_level_p (), 0, 0);
1605                   if (yychar == CONSTANT || yychar == STRING)
1606                     pop_momentary_nofree ();
1607                   else
1608                     pop_momentary (); }
1609         | pushlevel maybe_label_decls stmts '}'
1610                 { emit_line_note (input_filename, lineno);
1611                   expand_end_bindings (getdecls (), kept_level_p (), 0);
1612                   $$ = poplevel (kept_level_p (), 0, 0);
1613                   if (yychar == CONSTANT || yychar == STRING)
1614                     pop_momentary_nofree ();
1615                   else
1616                     pop_momentary (); }
1617         ;
1618
1619 compstmt_primary_start:
1620         '(' '{'
1621                 { if (current_function_decl == 0)
1622                     {
1623                       error ("braced-group within expression allowed only inside a function");
1624                       YYERROR;
1625                     }
1626                   /* We must force a BLOCK for this level
1627                      so that, if it is not expanded later,
1628                      there is a way to turn off the entire subtree of blocks
1629                      that are contained in it.  */
1630                   keep_next_level ();
1631                   push_iterator_stack ();
1632                   push_label_level ();
1633                   $$ = expand_start_stmt_expr ();
1634                   compstmt_count++;
1635                 }
1636
1637 compstmt: compstmt_start compstmt_nostart
1638                 { $$ = $2; }
1639         ;
1640
1641 /* Value is number of statements counted as of the closeparen.  */
1642 simple_if:
1643           if_prefix lineno_labeled_stmt
1644 /* Make sure c_expand_end_cond is run once
1645    for each call to c_expand_start_cond.
1646    Otherwise a crash is likely.  */
1647         | if_prefix error
1648         ;
1649
1650 if_prefix:
1651           IF '(' expr ')'
1652                 { emit_line_note ($<filename>-1, $<lineno>0);
1653                   c_expand_start_cond (truthvalue_conversion ($3), 0, 
1654                                        compstmt_count);
1655                   $<itype>$ = stmt_count;
1656                   if_stmt_file = $<filename>-1;
1657                   if_stmt_line = $<lineno>0;
1658                   position_after_white_space (); }
1659         ;
1660
1661 /* This is a subroutine of stmt.
1662    It is used twice, once for valid DO statements
1663    and once for catching errors in parsing the end test.  */
1664 do_stmt_start:
1665           DO
1666                 { stmt_count++;
1667                   compstmt_count++;
1668                   emit_line_note ($<filename>-1, $<lineno>0);
1669                   /* See comment in `while' alternative, above.  */
1670                   emit_nop ();
1671                   expand_start_loop_continue_elsewhere (1);
1672                   position_after_white_space (); }
1673           lineno_labeled_stmt WHILE
1674                 { expand_loop_continue_here (); }
1675         ;
1676
1677 save_filename:
1678                 { $$ = input_filename; }
1679         ;
1680
1681 save_lineno:
1682                 { $$ = lineno; }
1683         ;
1684
1685 lineno_labeled_stmt:
1686           save_filename save_lineno stmt
1687                 { }
1688 /*      | save_filename save_lineno error
1689                 { }
1690 */
1691         | save_filename save_lineno label lineno_labeled_stmt
1692                 { }
1693         ;
1694
1695 lineno_stmt_or_label:
1696           save_filename save_lineno stmt_or_label
1697                 { $$ = $3; }
1698         ;
1699
1700 stmt_or_label:
1701           stmt
1702                 { $$ = 0; }
1703         | label
1704                 { $$ = 1; }
1705         ;
1706
1707 /* Parse a single real statement, not including any labels.  */
1708 stmt:
1709           compstmt
1710                 { stmt_count++; }
1711         | all_iter_stmt 
1712         | expr ';'
1713                 { stmt_count++;
1714                   emit_line_note ($<filename>-1, $<lineno>0);
1715 /* It appears that this should not be done--that a non-lvalue array
1716    shouldn't get an error if the value isn't used.
1717    Section 3.2.2.1 says that an array lvalue gets converted to a pointer
1718    if it appears as a top-level expression,
1719    but says nothing about non-lvalue arrays.  */
1720 #if 0
1721                   /* Call default_conversion to get an error
1722                      on referring to a register array if pedantic.  */
1723                   if (TREE_CODE (TREE_TYPE ($1)) == ARRAY_TYPE
1724                       || TREE_CODE (TREE_TYPE ($1)) == FUNCTION_TYPE)
1725                     $1 = default_conversion ($1);
1726 #endif
1727                   iterator_expand ($1);
1728                   clear_momentary (); }
1729         | simple_if ELSE
1730                 { c_expand_start_else ();
1731                   $<itype>1 = stmt_count;
1732                   position_after_white_space (); }
1733           lineno_labeled_stmt
1734                 { c_expand_end_cond ();
1735                   if (extra_warnings && stmt_count == $<itype>1)
1736                     warning ("empty body in an else-statement"); }
1737         | simple_if %prec IF
1738                 { c_expand_end_cond ();
1739                   /* This warning is here instead of in simple_if, because we
1740                      do not want a warning if an empty if is followed by an
1741                      else statement.  Increment stmt_count so we don't
1742                      give a second error if this is a nested `if'.  */
1743                   if (extra_warnings && stmt_count++ == $<itype>1)
1744                     warning_with_file_and_line (if_stmt_file, if_stmt_line,
1745                                                 "empty body in an if-statement"); }
1746 /* Make sure c_expand_end_cond is run once
1747    for each call to c_expand_start_cond.
1748    Otherwise a crash is likely.  */
1749         | simple_if ELSE error
1750                 { c_expand_end_cond (); }
1751         | WHILE
1752                 { stmt_count++;
1753                   emit_line_note ($<filename>-1, $<lineno>0);
1754                   /* The emit_nop used to come before emit_line_note,
1755                      but that made the nop seem like part of the preceding line.
1756                      And that was confusing when the preceding line was
1757                      inside of an if statement and was not really executed.
1758                      I think it ought to work to put the nop after the line number.
1759                      We will see.  --rms, July 15, 1991.  */
1760                   emit_nop (); }
1761           '(' expr ')'
1762                 { /* Don't start the loop till we have succeeded
1763                      in parsing the end test.  This is to make sure
1764                      that we end every loop we start.  */
1765                   expand_start_loop (1);
1766                   emit_line_note (input_filename, lineno);
1767                   expand_exit_loop_if_false (NULL_PTR,
1768                                              truthvalue_conversion ($4));
1769                   position_after_white_space (); }
1770           lineno_labeled_stmt
1771                 { expand_end_loop (); }
1772         | do_stmt_start
1773           '(' expr ')' ';'
1774                 { emit_line_note (input_filename, lineno);
1775                   expand_exit_loop_if_false (NULL_PTR,
1776                                              truthvalue_conversion ($3));
1777                   expand_end_loop ();
1778                   clear_momentary (); }
1779 /* This rule is needed to make sure we end every loop we start.  */
1780         | do_stmt_start error
1781                 { expand_end_loop ();
1782                   clear_momentary (); }
1783         | FOR
1784           '(' xexpr ';'
1785                 { stmt_count++;
1786                   emit_line_note ($<filename>-1, $<lineno>0);
1787                   /* See comment in `while' alternative, above.  */
1788                   emit_nop ();
1789                   if ($3) c_expand_expr_stmt ($3);
1790                   /* Next step is to call expand_start_loop_continue_elsewhere,
1791                      but wait till after we parse the entire for (...).
1792                      Otherwise, invalid input might cause us to call that
1793                      fn without calling expand_end_loop.  */
1794                 }
1795           xexpr ';'
1796                 /* Can't emit now; wait till after expand_start_loop...  */
1797                 { $<lineno>7 = lineno;
1798                   $<filename>$ = input_filename; }
1799           xexpr ')'
1800                 { 
1801                   /* Start the loop.  Doing this after parsing
1802                      all the expressions ensures we will end the loop.  */
1803                   expand_start_loop_continue_elsewhere (1);
1804                   /* Emit the end-test, with a line number.  */
1805                   emit_line_note ($<filename>8, $<lineno>7);
1806                   if ($6)
1807                     expand_exit_loop_if_false (NULL_PTR,
1808                                                truthvalue_conversion ($6));
1809                   /* Don't let the tree nodes for $9 be discarded by
1810                      clear_momentary during the parsing of the next stmt.  */
1811                   push_momentary ();
1812                   $<lineno>7 = lineno;
1813                   $<filename>8 = input_filename;
1814                   position_after_white_space (); }
1815           lineno_labeled_stmt
1816                 { /* Emit the increment expression, with a line number.  */
1817                   emit_line_note ($<filename>8, $<lineno>7);
1818                   expand_loop_continue_here ();
1819                   if ($9)
1820                     c_expand_expr_stmt ($9);
1821                   if (yychar == CONSTANT || yychar == STRING)
1822                     pop_momentary_nofree ();
1823                   else
1824                     pop_momentary ();
1825                   expand_end_loop (); }
1826         | SWITCH '(' expr ')'
1827                 { stmt_count++;
1828                   emit_line_note ($<filename>-1, $<lineno>0);
1829                   c_expand_start_case ($3);
1830                   /* Don't let the tree nodes for $3 be discarded by
1831                      clear_momentary during the parsing of the next stmt.  */
1832                   push_momentary ();
1833                   position_after_white_space (); }
1834           lineno_labeled_stmt
1835                 { expand_end_case ($3);
1836                   if (yychar == CONSTANT || yychar == STRING)
1837                     pop_momentary_nofree ();
1838                   else
1839                     pop_momentary (); }
1840         | BREAK ';'
1841                 { stmt_count++;
1842                   emit_line_note ($<filename>-1, $<lineno>0);
1843                   if ( ! expand_exit_something ())
1844                     error ("break statement not within loop or switch"); }
1845         | CONTINUE ';'
1846                 { stmt_count++;
1847                   emit_line_note ($<filename>-1, $<lineno>0);
1848                   if (! expand_continue_loop (NULL_PTR))
1849                     error ("continue statement not within a loop"); }
1850         | RETURN ';'
1851                 { stmt_count++;
1852                   emit_line_note ($<filename>-1, $<lineno>0);
1853                   c_expand_return (NULL_TREE); }
1854         | RETURN expr ';'
1855                 { stmt_count++;
1856                   emit_line_note ($<filename>-1, $<lineno>0);
1857                   c_expand_return ($2); }
1858         | ASM_KEYWORD maybe_type_qual '(' expr ')' ';'
1859                 { stmt_count++;
1860                   emit_line_note ($<filename>-1, $<lineno>0);
1861                   STRIP_NOPS ($4);
1862                   if ((TREE_CODE ($4) == ADDR_EXPR
1863                        && TREE_CODE (TREE_OPERAND ($4, 0)) == STRING_CST)
1864                       || TREE_CODE ($4) == STRING_CST)
1865                     expand_asm ($4);
1866                   else
1867                     error ("argument of `asm' is not a constant string"); }
1868         /* This is the case with just output operands.  */
1869         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ')' ';'
1870                 { stmt_count++;
1871                   emit_line_note ($<filename>-1, $<lineno>0);
1872                   c_expand_asm_operands ($4, $6, NULL_TREE, NULL_TREE,
1873                                          $2 == ridpointers[(int)RID_VOLATILE],
1874                                          input_filename, lineno); }
1875         /* This is the case with input operands as well.  */
1876         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':' asm_operands ')' ';'
1877                 { stmt_count++;
1878                   emit_line_note ($<filename>-1, $<lineno>0);
1879                   c_expand_asm_operands ($4, $6, $8, NULL_TREE,
1880                                          $2 == ridpointers[(int)RID_VOLATILE],
1881                                          input_filename, lineno); }
1882         /* This is the case with clobbered registers as well.  */
1883         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':'
1884           asm_operands ':' asm_clobbers ')' ';'
1885                 { stmt_count++;
1886                   emit_line_note ($<filename>-1, $<lineno>0);
1887                   c_expand_asm_operands ($4, $6, $8, $10,
1888                                          $2 == ridpointers[(int)RID_VOLATILE],
1889                                          input_filename, lineno); }
1890         | GOTO identifier ';'
1891                 { tree decl;
1892                   stmt_count++;
1893                   emit_line_note ($<filename>-1, $<lineno>0);
1894                   decl = lookup_label ($2);
1895                   if (decl != 0)
1896                     {
1897                       TREE_USED (decl) = 1;
1898                       expand_goto (decl);
1899                     }
1900                 }
1901         | GOTO '*' expr ';'
1902                 { if (pedantic)
1903                     pedwarn ("ANSI C forbids `goto *expr;'");
1904                   stmt_count++;
1905                   emit_line_note ($<filename>-1, $<lineno>0);
1906                   expand_computed_goto (convert (ptr_type_node, $3)); }
1907         | ';'
1908         ;
1909
1910 all_iter_stmt:
1911           all_iter_stmt_simple
1912 /*      | all_iter_stmt_with_decl */
1913         ;
1914
1915 all_iter_stmt_simple:
1916           FOR '(' primary ')' 
1917           {
1918             /* The value returned by this action is  */
1919             /*      1 if everything is OK */ 
1920             /*      0 in case of error or already bound iterator */
1921
1922             $<itype>$ = 0;
1923             if (TREE_CODE ($3) != VAR_DECL)
1924               error ("invalid `for (ITERATOR)' syntax");
1925             else if (! ITERATOR_P ($3))
1926               error ("`%s' is not an iterator",
1927                      IDENTIFIER_POINTER (DECL_NAME ($3)));
1928             else if (ITERATOR_BOUND_P ($3))
1929               error ("`for (%s)' inside expansion of same iterator",
1930                      IDENTIFIER_POINTER (DECL_NAME ($3)));
1931             else
1932               {
1933                 $<itype>$ = 1;
1934                 iterator_for_loop_start ($3);
1935               }
1936           }
1937           lineno_labeled_stmt
1938           {
1939             if ($<itype>5)
1940               iterator_for_loop_end ($3);
1941           }
1942
1943 /*  This really should allow any kind of declaration,
1944     for generality.  Fix it before turning it back on.
1945
1946 all_iter_stmt_with_decl:
1947           FOR '(' ITERATOR pushlevel setspecs iterator_spec ')' 
1948           {
1949 */          /* The value returned by this action is  */
1950             /*      1 if everything is OK */ 
1951             /*      0 in case of error or already bound iterator */
1952 /*
1953             iterator_for_loop_start ($6);
1954           }
1955           lineno_labeled_stmt
1956           {
1957             iterator_for_loop_end ($6);
1958             emit_line_note (input_filename, lineno);
1959             expand_end_bindings (getdecls (), 1, 0);
1960             $<ttype>$ = poplevel (1, 1, 0);
1961             if (yychar == CONSTANT || yychar == STRING)
1962               pop_momentary_nofree ();
1963             else
1964               pop_momentary ();     
1965           }
1966 */
1967
1968 /* Any kind of label, including jump labels and case labels.
1969    ANSI C accepts labels only before statements, but we allow them
1970    also at the end of a compound statement.  */
1971
1972 label:    CASE expr_no_commas ':'
1973                 { register tree value = check_case_value ($2);
1974                   register tree label
1975                     = build_decl (LABEL_DECL, NULL_TREE, NULL_TREE);
1976
1977                   stmt_count++;
1978
1979                   if (value != error_mark_node)
1980                     {
1981                       tree duplicate;
1982                       int success;
1983
1984                       if (pedantic && ! INTEGRAL_TYPE_P (TREE_TYPE (value)))
1985                         pedwarn ("label must have integral type in ANSI C");
1986
1987                       success = pushcase (value, convert_and_check,
1988                                           label, &duplicate);
1989
1990                       if (success == 1)
1991                         error ("case label not within a switch statement");
1992                       else if (success == 2)
1993                         {
1994                           error ("duplicate case value");
1995                           error_with_decl (duplicate, "this is the first entry for that value");
1996                         }
1997                       else if (success == 3)
1998                         warning ("case value out of range");
1999                       else if (success == 5)
2000                         error ("case label within scope of cleanup or variable array");
2001                     }
2002                   position_after_white_space (); }
2003         | CASE expr_no_commas ELLIPSIS expr_no_commas ':'
2004                 { register tree value1 = check_case_value ($2);
2005                   register tree value2 = check_case_value ($4);
2006                   register tree label
2007                     = build_decl (LABEL_DECL, NULL_TREE, NULL_TREE);
2008
2009                   if (pedantic)
2010                     pedwarn ("ANSI C forbids case ranges");
2011                   stmt_count++;
2012
2013                   if (value1 != error_mark_node && value2 != error_mark_node)
2014                     {
2015                       tree duplicate;
2016                       int success = pushcase_range (value1, value2,
2017                                                     convert_and_check, label,
2018                                                     &duplicate);
2019                       if (success == 1)
2020                         error ("case label not within a switch statement");
2021                       else if (success == 2)
2022                         {
2023                           error ("duplicate case value");
2024                           error_with_decl (duplicate, "this is the first entry for that value");
2025                         }
2026                       else if (success == 3)
2027                         warning ("case value out of range");
2028                       else if (success == 4)
2029                         warning ("empty case range");
2030                       else if (success == 5)
2031                         error ("case label within scope of cleanup or variable array");
2032                     }
2033                   position_after_white_space (); }
2034         | DEFAULT ':'
2035                 {
2036                   tree duplicate;
2037                   register tree label
2038                     = build_decl (LABEL_DECL, NULL_TREE, NULL_TREE);
2039                   int success = pushcase (NULL_TREE, 0, label, &duplicate);
2040                   stmt_count++;
2041                   if (success == 1)
2042                     error ("default label not within a switch statement");
2043                   else if (success == 2)
2044                     {
2045                       error ("multiple default labels in one switch");
2046                       error_with_decl (duplicate, "this is the first default label");
2047                     }
2048                   position_after_white_space (); }
2049         | identifier ':' maybe_attribute
2050                 { tree label = define_label (input_filename, lineno, $1);
2051                   stmt_count++;
2052                   emit_nop ();
2053                   if (label)
2054                     {
2055                       expand_label (label);
2056                       decl_attributes (label, $3, NULL_TREE);
2057                     }
2058                   position_after_white_space (); }
2059         ;
2060
2061 /* Either a type-qualifier or nothing.  First thing in an `asm' statement.  */
2062
2063 maybe_type_qual:
2064         /* empty */
2065                 { emit_line_note (input_filename, lineno);
2066                   $$ = NULL_TREE; }
2067         | TYPE_QUAL
2068                 { emit_line_note (input_filename, lineno); }
2069         ;
2070
2071 xexpr:
2072         /* empty */
2073                 { $$ = NULL_TREE; }
2074         | expr
2075         ;
2076
2077 /* These are the operands other than the first string and colon
2078    in  asm ("addextend %2,%1": "=dm" (x), "0" (y), "g" (*x))  */
2079 asm_operands: /* empty */
2080                 { $$ = NULL_TREE; }
2081         | nonnull_asm_operands
2082         ;
2083
2084 nonnull_asm_operands:
2085           asm_operand
2086         | nonnull_asm_operands ',' asm_operand
2087                 { $$ = chainon ($1, $3); }
2088         ;
2089
2090 asm_operand:
2091           STRING '(' expr ')'
2092                 { $$ = build_tree_list ($1, $3); }
2093         ;
2094
2095 asm_clobbers:
2096           string
2097                 { $$ = tree_cons (NULL_TREE, combine_strings ($1), NULL_TREE); }
2098         | asm_clobbers ',' string
2099                 { $$ = tree_cons (NULL_TREE, combine_strings ($3), $1); }
2100         ;
2101 \f
2102 /* This is what appears inside the parens in a function declarator.
2103    Its value is a list of ..._TYPE nodes.  */
2104 parmlist:
2105                 { pushlevel (0);
2106                   clear_parm_order ();
2107                   declare_parm_level (0); }
2108           parmlist_1
2109                 { $$ = $2;
2110                   parmlist_tags_warning ();
2111                   poplevel (0, 0, 0); }
2112         ;
2113
2114 parmlist_1:
2115           parmlist_2 ')'
2116         | parms ';'
2117                 { tree parm;
2118                   if (pedantic)
2119                     pedwarn ("ANSI C forbids forward parameter declarations");
2120                   /* Mark the forward decls as such.  */
2121                   for (parm = getdecls (); parm; parm = TREE_CHAIN (parm))
2122                     TREE_ASM_WRITTEN (parm) = 1;
2123                   clear_parm_order (); }
2124           parmlist_1
2125                 { $$ = $4; }
2126         | error ')'
2127                 { $$ = tree_cons (NULL_TREE, NULL_TREE, NULL_TREE); }
2128         ;
2129
2130 /* This is what appears inside the parens in a function declarator.
2131    Is value is represented in the format that grokdeclarator expects.  */
2132 parmlist_2:  /* empty */
2133                 { $$ = get_parm_info (0); }
2134         | ELLIPSIS
2135                 { $$ = get_parm_info (0);
2136                   /* Gcc used to allow this as an extension.  However, it does
2137                      not work for all targets, and thus has been disabled.
2138                      Also, since func (...) and func () are indistinguishable,
2139                      it caused problems with the code in expand_builtin which
2140                      tries to verify that BUILT_IN_NEXT_ARG is being used
2141                      correctly.  */
2142                   error ("ANSI C requires a named argument before `...'");
2143                 }
2144         | parms
2145                 { $$ = get_parm_info (1); }
2146         | parms ',' ELLIPSIS
2147                 { $$ = get_parm_info (0); }
2148         ;
2149
2150 parms:
2151         parm
2152                 { push_parm_decl ($1); }
2153         | parms ',' parm
2154                 { push_parm_decl ($3); }
2155         ;
2156
2157 /* A single parameter declaration or parameter type name,
2158    as found in a parmlist.  */
2159 parm:
2160           typed_declspecs setspecs parm_declarator maybe_attribute
2161                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2162                                                          $3),
2163                                         build_tree_list (prefix_attributes,
2164                                                          $4));
2165                   current_declspecs = TREE_VALUE (declspec_stack);
2166                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2167                   declspec_stack = TREE_CHAIN (declspec_stack);
2168                   resume_momentary ($2); }
2169         | typed_declspecs setspecs notype_declarator maybe_attribute
2170                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2171                                                          $3),
2172                                         build_tree_list (prefix_attributes,
2173                                                          $4)); 
2174                   current_declspecs = TREE_VALUE (declspec_stack);
2175                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2176                   declspec_stack = TREE_CHAIN (declspec_stack);
2177                   resume_momentary ($2); }
2178         | typed_declspecs setspecs absdcl maybe_attribute
2179                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2180                                                          $3),
2181                                         build_tree_list (prefix_attributes,
2182                                                          $4));
2183                   current_declspecs = TREE_VALUE (declspec_stack);
2184                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2185                   declspec_stack = TREE_CHAIN (declspec_stack);
2186                   resume_momentary ($2); }
2187         | declmods setspecs notype_declarator maybe_attribute
2188                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2189                                                          $3),
2190                                         build_tree_list (prefix_attributes,
2191                                                          $4));
2192                   current_declspecs = TREE_VALUE (declspec_stack);
2193                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2194                   declspec_stack = TREE_CHAIN (declspec_stack);
2195                   resume_momentary ($2);  }
2196
2197         | declmods setspecs absdcl maybe_attribute
2198                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2199                                                          $3),
2200                                         build_tree_list (prefix_attributes,
2201                                                          $4));
2202                   current_declspecs = TREE_VALUE (declspec_stack);
2203                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2204                   declspec_stack = TREE_CHAIN (declspec_stack);
2205                   resume_momentary ($2);  }
2206         ;
2207
2208 /* This is used in a function definition
2209    where either a parmlist or an identifier list is ok.
2210    Its value is a list of ..._TYPE nodes or a list of identifiers.  */
2211 parmlist_or_identifiers:
2212                 { pushlevel (0);
2213                   clear_parm_order ();
2214                   declare_parm_level (1); }
2215           parmlist_or_identifiers_1
2216                 { $$ = $2;
2217                   parmlist_tags_warning ();
2218                   poplevel (0, 0, 0); }
2219         ;
2220
2221 parmlist_or_identifiers_1:
2222           parmlist_1
2223         | identifiers ')'
2224                 { tree t;
2225                   for (t = $1; t; t = TREE_CHAIN (t))
2226                     if (TREE_VALUE (t) == NULL_TREE)
2227                       error ("`...' in old-style identifier list");
2228                   $$ = tree_cons (NULL_TREE, NULL_TREE, $1); }
2229         ;
2230
2231 /* A nonempty list of identifiers.  */
2232 identifiers:
2233         IDENTIFIER
2234                 { $$ = build_tree_list (NULL_TREE, $1); }
2235         | identifiers ',' IDENTIFIER
2236                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2237         ;
2238
2239 /* A nonempty list of identifiers, including typenames.  */
2240 identifiers_or_typenames:
2241         identifier
2242                 { $$ = build_tree_list (NULL_TREE, $1); }
2243         | identifiers_or_typenames ',' identifier
2244                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2245         ;
2246
2247 extension:
2248         EXTENSION
2249                 { $<itype>$ = pedantic;
2250                   pedantic = 0; }
2251         ;
2252 \f
2253 %%