OSDN Git Service

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