source: trunk/third/gcc/c-parse.y @ 8834

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