OSDN Git Service

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