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