xref: /openbsd/gnu/usr.bin/gcc/gcc/c-parse.in (revision a67f0032)
1/* YACC parser for C syntax and for Objective C.  -*-c-*-
2   Copyright (C) 1987, 1988, 1989, 1992, 1993, 1994, 1995, 1996,
3   1997, 1998, 1999, 2000, 2001, 2002 Free Software Foundation, Inc.
4
5This file is part of GCC.
6
7GCC is free software; you can redistribute it and/or modify it under
8the terms of the GNU General Public License as published by the Free
9Software Foundation; either version 2, or (at your option) any later
10version.
11
12GCC is distributed in the hope that it will be useful, but WITHOUT ANY
13WARRANTY; without even the implied warranty of MERCHANTABILITY or
14FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
15for more details.
16
17You should have received a copy of the GNU General Public License
18along with GCC; see the file COPYING.  If not, write to the Free
19Software Foundation, 59 Temple Place - Suite 330, Boston, MA
2002111-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
31ifc
32%expect 10 /* shift/reduce conflicts, and no reduce/reduce conflicts.  */
33end ifc
34
35%{
36#include "config.h"
37#include "system.h"
38#include "tree.h"
39#include "input.h"
40#include "cpplib.h"
41#include "intl.h"
42#include "timevar.h"
43#include "c-pragma.h"		/* For YYDEBUG definition, and parse_in.  */
44#include "c-tree.h"
45#include "flags.h"
46#include "output.h"
47#include "toplev.h"
48#include "ggc.h"
49
50#ifdef MULTIBYTE_CHARS
51#include <locale.h>
52#endif
53
54ifobjc
55#include "objc-act.h"
56end ifobjc
57
58/* Like YYERROR but do call yyerror.  */
59#define YYERROR1 { yyerror ("syntax error"); YYERROR; }
60
61/* Like the default stack expander, except (1) use realloc when possible,
62   (2) impose no hard maxiumum on stack size, (3) REALLY do not use alloca.
63
64   Irritatingly, YYSTYPE is defined after this %{ %} block, so we cannot
65   give malloced_yyvs its proper type.  This is ok since all we need from
66   it is to be able to free it.  */
67
68static short *malloced_yyss;
69static void *malloced_yyvs;
70
71#define yyoverflow(MSG, SS, SSSIZE, VS, VSSIZE, YYSSZ)			\
72do {									\
73  size_t newsize;							\
74  short *newss;								\
75  YYSTYPE *newvs;							\
76  newsize = *(YYSSZ) *= 2;						\
77  if (malloced_yyss)							\
78    {									\
79      newss = (short *)							\
80	really_call_realloc (*(SS), newsize * sizeof (short));		\
81      newvs = (YYSTYPE *)						\
82	really_call_realloc (*(VS), newsize * sizeof (YYSTYPE));	\
83    }									\
84  else									\
85    {									\
86      newss = (short *) really_call_malloc (newsize * sizeof (short));	\
87      newvs = (YYSTYPE *) really_call_malloc (newsize * sizeof (YYSTYPE)); \
88      if (newss)							\
89        memcpy (newss, *(SS), (SSSIZE));				\
90      if (newvs)							\
91        memcpy (newvs, *(VS), (VSSIZE));				\
92    }									\
93  if (!newss || !newvs)							\
94    {									\
95      yyerror (MSG);							\
96      return 2;								\
97    }									\
98  *(SS) = newss;							\
99  *(VS) = newvs;							\
100  malloced_yyss = newss;						\
101  malloced_yyvs = (void *) newvs;					\
102} while (0)
103%}
104
105%start program
106
107%union {long itype; tree ttype; enum tree_code code;
108	const char *filename; int lineno; }
109
110/* All identifiers that are not reserved words
111   and are not declared typedefs in the current block */
112%token IDENTIFIER
113
114/* All identifiers that are declared typedefs in the current block.
115   In some contexts, they are treated just like IDENTIFIER,
116   but they can also serve as typespecs in declarations.  */
117%token TYPENAME
118
119/* Reserved words that specify storage class.
120   yylval contains an IDENTIFIER_NODE which indicates which one.  */
121%token SCSPEC			/* Storage class other than static.  */
122%token STATIC			/* Static storage class.  */
123
124/* Reserved words that specify type.
125   yylval contains an IDENTIFIER_NODE which indicates which one.  */
126%token TYPESPEC
127
128/* Reserved words that qualify type: "const", "volatile", or "restrict".
129   yylval contains an IDENTIFIER_NODE which indicates which one.  */
130%token TYPE_QUAL
131
132/* Character or numeric constants.
133   yylval is the node for the constant.  */
134%token CONSTANT
135
136/* String constants in raw form.
137   yylval is a STRING_CST node.  */
138%token STRING
139
140/* "...", used for functions with variable arglists.  */
141%token ELLIPSIS
142
143/* the reserved words */
144/* SCO include files test "ASM", so use something else. */
145%token SIZEOF ENUM STRUCT UNION IF ELSE WHILE DO FOR SWITCH CASE DEFAULT
146%token BREAK CONTINUE RETURN GOTO ASM_KEYWORD TYPEOF ALIGNOF
147%token ATTRIBUTE EXTENSION LABEL
148%token REALPART IMAGPART VA_ARG CHOOSE_EXPR TYPES_COMPATIBLE_P
149%token PTR_VALUE PTR_BASE PTR_EXTENT
150
151/* function name can be a string const or a var decl. */
152%token STRING_FUNC_NAME VAR_FUNC_NAME
153
154/* Add precedence rules to solve dangling else s/r conflict */
155%nonassoc IF
156%nonassoc ELSE
157
158/* Define the operator tokens and their precedences.
159   The value is an integer because, if used, it is the tree code
160   to use in the expression made from the operator.  */
161
162%right <code> ASSIGN '='
163%right <code> '?' ':'
164%left <code> OROR
165%left <code> ANDAND
166%left <code> '|'
167%left <code> '^'
168%left <code> '&'
169%left <code> EQCOMPARE
170%left <code> ARITHCOMPARE
171%left <code> LSHIFT RSHIFT
172%left <code> '+' '-'
173%left <code> '*' '/' '%'
174%right <code> UNARY PLUSPLUS MINUSMINUS
175%left HYPERUNARY
176%left <code> POINTSAT '.' '(' '['
177
178/* The Objective-C keywords.  These are included in C and in
179   Objective C, so that the token codes are the same in both.  */
180%token INTERFACE IMPLEMENTATION END SELECTOR DEFS ENCODE
181%token CLASSNAME PUBLIC PRIVATE PROTECTED PROTOCOL OBJECTNAME CLASS ALIAS
182
183%type <code> unop
184%type <ttype> ENUM STRUCT UNION IF ELSE WHILE DO FOR SWITCH CASE DEFAULT
185%type <ttype> BREAK CONTINUE RETURN GOTO ASM_KEYWORD SIZEOF TYPEOF ALIGNOF
186
187%type <ttype> identifier IDENTIFIER TYPENAME CONSTANT expr nonnull_exprlist exprlist
188%type <ttype> expr_no_commas cast_expr unary_expr primary STRING
189%type <ttype> declspecs_nosc_nots_nosa_noea declspecs_nosc_nots_nosa_ea
190%type <ttype> declspecs_nosc_nots_sa_noea declspecs_nosc_nots_sa_ea
191%type <ttype> declspecs_nosc_ts_nosa_noea declspecs_nosc_ts_nosa_ea
192%type <ttype> declspecs_nosc_ts_sa_noea declspecs_nosc_ts_sa_ea
193%type <ttype> declspecs_sc_nots_nosa_noea declspecs_sc_nots_nosa_ea
194%type <ttype> declspecs_sc_nots_sa_noea declspecs_sc_nots_sa_ea
195%type <ttype> declspecs_sc_ts_nosa_noea declspecs_sc_ts_nosa_ea
196%type <ttype> declspecs_sc_ts_sa_noea declspecs_sc_ts_sa_ea
197%type <ttype> declspecs_ts declspecs_nots
198%type <ttype> declspecs_ts_nosa declspecs_nots_nosa
199%type <ttype> declspecs_nosc_ts declspecs_nosc_nots declspecs_nosc declspecs
200%type <ttype> maybe_type_quals_attrs typespec_nonattr typespec_attr
201%type <ttype> typespec_reserved_nonattr typespec_reserved_attr
202%type <ttype> typespec_nonreserved_nonattr
203
204%type <ttype> scspec SCSPEC STATIC TYPESPEC TYPE_QUAL maybe_type_qual
205%type <ttype> initdecls notype_initdecls initdcl notype_initdcl
206%type <ttype> init maybeasm
207%type <ttype> asm_operands nonnull_asm_operands asm_operand asm_clobbers
208%type <ttype> maybe_attribute attributes attribute attribute_list attrib
209%type <ttype> any_word extension
210
211%type <ttype> compstmt compstmt_start compstmt_nostart compstmt_primary_start
212%type <ttype> do_stmt_start poplevel stmt label
213
214%type <ttype> c99_block_start c99_block_end
215%type <ttype> declarator
216%type <ttype> notype_declarator after_type_declarator
217%type <ttype> parm_declarator
218%type <ttype> parm_declarator_starttypename parm_declarator_nostarttypename
219%type <ttype> array_declarator
220
221%type <ttype> structsp_attr structsp_nonattr
222%type <ttype> component_decl_list component_decl_list2
223%type <ttype> component_decl components components_notype component_declarator
224%type <ttype> component_notype_declarator
225%type <ttype> enumlist enumerator
226%type <ttype> struct_head union_head enum_head
227%type <ttype> typename absdcl absdcl1 absdcl1_ea absdcl1_noea
228%type <ttype> direct_absdcl1 absdcl_maybe_attribute
229%type <ttype> xexpr parms parm firstparm identifiers
230
231%type <ttype> parmlist parmlist_1 parmlist_2
232%type <ttype> parmlist_or_identifiers parmlist_or_identifiers_1
233%type <ttype> identifiers_or_typenames
234
235%type <itype> setspecs setspecs_fp
236
237%type <filename> save_filename
238%type <lineno> save_lineno
239
240ifobjc
241/* the Objective-C nonterminals */
242
243%type <ttype> ivar_decl_list ivar_decls ivar_decl ivars ivar_declarator
244%type <ttype> methoddecl unaryselector keywordselector selector
245%type <ttype> keyworddecl receiver objcmessageexpr messageargs
246%type <ttype> keywordexpr keywordarglist keywordarg
247%type <ttype> myparms myparm optparmlist reservedwords objcselectorexpr
248%type <ttype> selectorarg keywordnamelist keywordname objcencodeexpr
249%type <ttype> objc_string non_empty_protocolrefs protocolrefs identifier_list objcprotocolexpr
250
251%type <ttype> CLASSNAME OBJECTNAME
252end ifobjc
253
254%{
255/* Number of statements (loosely speaking) and compound statements
256   seen so far.  */
257static int stmt_count;
258static int compstmt_count;
259
260/* Input file and line number of the end of the body of last simple_if;
261   used by the stmt-rule immediately after simple_if returns.  */
262static const char *if_stmt_file;
263static int if_stmt_line;
264
265/* List of types and structure classes of the current declaration.  */
266static GTY(()) tree current_declspecs;
267static GTY(()) tree prefix_attributes;
268
269/* List of all the attributes applying to the identifier currently being
270   declared; includes prefix_attributes and possibly some more attributes
271   just after a comma.  */
272static GTY(()) tree all_prefix_attributes;
273
274/* Stack of saved values of current_declspecs, prefix_attributes and
275   all_prefix_attributes.  */
276static GTY(()) tree declspec_stack;
277
278/* PUSH_DECLSPEC_STACK is called from setspecs; POP_DECLSPEC_STACK
279   should be called from the productions making use of setspecs.  */
280#define PUSH_DECLSPEC_STACK						 \
281  do {									 \
282    declspec_stack = tree_cons (build_tree_list (prefix_attributes,	 \
283						 all_prefix_attributes), \
284				current_declspecs,			 \
285				declspec_stack);			 \
286  } while (0)
287
288#define POP_DECLSPEC_STACK						\
289  do {									\
290    current_declspecs = TREE_VALUE (declspec_stack);			\
291    prefix_attributes = TREE_PURPOSE (TREE_PURPOSE (declspec_stack));	\
292    all_prefix_attributes = TREE_VALUE (TREE_PURPOSE (declspec_stack));	\
293    declspec_stack = TREE_CHAIN (declspec_stack);			\
294  } while (0)
295
296/* For __extension__, save/restore the warning flags which are
297   controlled by __extension__.  */
298#define SAVE_EXT_FLAGS()			\
299	size_int (pedantic			\
300		  | (warn_pointer_arith << 1)	\
301		  | (warn_traditional << 2)	\
302		  | (flag_iso << 3))
303
304#define RESTORE_EXT_FLAGS(tval)			\
305  do {						\
306    int val = tree_low_cst (tval, 0);		\
307    pedantic = val & 1;				\
308    warn_pointer_arith = (val >> 1) & 1;	\
309    warn_traditional = (val >> 2) & 1;		\
310    flag_iso = (val >> 3) & 1;			\
311  } while (0)
312
313ifobjc
314/* Objective-C specific parser/lexer information */
315
316static enum tree_code objc_inherit_code;
317static int objc_pq_context = 0, objc_public_flag = 0;
318
319/* The following flag is needed to contextualize ObjC lexical analysis.
320   In some cases (e.g., 'int NSObject;'), it is undesirable to bind
321   an identifier to an ObjC class, even if a class with that name
322   exists.  */
323static int objc_need_raw_identifier;
324#define OBJC_NEED_RAW_IDENTIFIER(VAL)	objc_need_raw_identifier = VAL
325end ifobjc
326
327ifc
328#define OBJC_NEED_RAW_IDENTIFIER(VAL)	/* nothing */
329end ifc
330
331static bool parsing_iso_function_signature;
332
333/* Tell yyparse how to print a token's value, if yydebug is set.  */
334
335#define YYPRINT(FILE,YYCHAR,YYLVAL) yyprint(FILE,YYCHAR,YYLVAL)
336
337static void yyprint	  PARAMS ((FILE *, int, YYSTYPE));
338static void yyerror	  PARAMS ((const char *));
339static int yylexname	  PARAMS ((void));
340static int yylexstring	  PARAMS ((void));
341static inline int _yylex  PARAMS ((void));
342static int  yylex	  PARAMS ((void));
343static void init_reswords PARAMS ((void));
344
345  /* Initialisation routine for this file.  */
346void
347c_parse_init ()
348{
349  init_reswords ();
350}
351
352%}
353
354%%
355program: /* empty */
356		{ if (pedantic)
357		    pedwarn ("ISO C forbids an empty source file");
358		  finish_file ();
359		}
360	| extdefs
361		{
362		  /* In case there were missing closebraces,
363		     get us back to the global binding level.  */
364		  while (! global_bindings_p ())
365		    poplevel (0, 0, 0);
366		  /* __FUNCTION__ is defined at file scope ("").  This
367		     call may not be necessary as my tests indicate it
368		     still works without it.  */
369		  finish_fname_decls ();
370                  finish_file ();
371		}
372	;
373
374/* the reason for the strange actions in this rule
375 is so that notype_initdecls when reached via datadef
376 can find a valid list of type and sc specs in $0. */
377
378extdefs:
379	{$<ttype>$ = NULL_TREE; } extdef
380	| extdefs {$<ttype>$ = NULL_TREE; ggc_collect(); } extdef
381	;
382
383extdef:
384	extdef_1
385	{ parsing_iso_function_signature = false; } /* Reset after any external definition.  */
386	;
387
388extdef_1:
389	fndef
390	| datadef
391ifobjc
392	| objcdef
393end ifobjc
394	| ASM_KEYWORD '(' expr ')' ';'
395		{ STRIP_NOPS ($3);
396		  if ((TREE_CODE ($3) == ADDR_EXPR
397		       && TREE_CODE (TREE_OPERAND ($3, 0)) == STRING_CST)
398		      || TREE_CODE ($3) == STRING_CST)
399		    assemble_asm ($3);
400		  else
401		    error ("argument of `asm' is not a constant string"); }
402	| extension extdef
403		{ RESTORE_EXT_FLAGS ($1); }
404	;
405
406datadef:
407	  setspecs notype_initdecls ';'
408		{ if (pedantic)
409		    error ("ISO C forbids data definition with no type or storage class");
410		  else
411		    warning ("data definition has no type or storage class");
412
413		  POP_DECLSPEC_STACK; }
414        | declspecs_nots setspecs notype_initdecls ';'
415		{ POP_DECLSPEC_STACK; }
416	| declspecs_ts setspecs initdecls ';'
417		{ POP_DECLSPEC_STACK; }
418	| declspecs ';'
419	  { shadow_tag ($1); }
420	| error ';'
421	| error '}'
422	| ';'
423		{ if (pedantic)
424		    pedwarn ("ISO C does not allow extra `;' outside of a function"); }
425	;
426
427fndef:
428	  declspecs_ts setspecs declarator
429		{ if (! start_function (current_declspecs, $3,
430					all_prefix_attributes))
431		    YYERROR1;
432		}
433	  old_style_parm_decls
434		{ store_parm_decls (); }
435	  save_filename save_lineno compstmt_or_error
436		{ DECL_SOURCE_FILE (current_function_decl) = $7;
437		  DECL_SOURCE_LINE (current_function_decl) = $8;
438		  finish_function (0, 1);
439		  POP_DECLSPEC_STACK; }
440	| declspecs_ts setspecs declarator error
441		{ POP_DECLSPEC_STACK; }
442	| declspecs_nots setspecs notype_declarator
443		{ if (! start_function (current_declspecs, $3,
444					all_prefix_attributes))
445		    YYERROR1;
446		}
447	  old_style_parm_decls
448		{ store_parm_decls (); }
449	  save_filename save_lineno compstmt_or_error
450		{ DECL_SOURCE_FILE (current_function_decl) = $7;
451		  DECL_SOURCE_LINE (current_function_decl) = $8;
452		  finish_function (0, 1);
453		  POP_DECLSPEC_STACK; }
454	| declspecs_nots setspecs notype_declarator error
455		{ POP_DECLSPEC_STACK; }
456	| setspecs notype_declarator
457		{ if (! start_function (NULL_TREE, $2,
458					all_prefix_attributes))
459		    YYERROR1;
460		}
461	  old_style_parm_decls
462		{ store_parm_decls (); }
463	  save_filename save_lineno compstmt_or_error
464		{ DECL_SOURCE_FILE (current_function_decl) = $6;
465		  DECL_SOURCE_LINE (current_function_decl) = $7;
466		  finish_function (0, 1);
467		  POP_DECLSPEC_STACK; }
468	| setspecs notype_declarator error
469		{ POP_DECLSPEC_STACK; }
470	;
471
472identifier:
473	IDENTIFIER
474	| TYPENAME
475ifobjc
476	| OBJECTNAME
477	| CLASSNAME
478end ifobjc
479	;
480
481unop:     '&'
482		{ $$ = ADDR_EXPR; }
483	| '-'
484		{ $$ = NEGATE_EXPR; }
485	| '+'
486		{ $$ = CONVERT_EXPR;
487ifc
488  if (warn_traditional && !in_system_header)
489    warning ("traditional C rejects the unary plus operator");
490end ifc
491		}
492	| PLUSPLUS
493		{ $$ = PREINCREMENT_EXPR; }
494	| MINUSMINUS
495		{ $$ = PREDECREMENT_EXPR; }
496	| '~'
497		{ $$ = BIT_NOT_EXPR; }
498	| '!'
499		{ $$ = TRUTH_NOT_EXPR; }
500	;
501
502expr:	nonnull_exprlist
503		{ $$ = build_compound_expr ($1); }
504	;
505
506exprlist:
507	  /* empty */
508		{ $$ = NULL_TREE; }
509	| nonnull_exprlist
510	;
511
512nonnull_exprlist:
513	expr_no_commas
514		{ $$ = build_tree_list (NULL_TREE, $1); }
515	| nonnull_exprlist ',' expr_no_commas
516		{ chainon ($1, build_tree_list (NULL_TREE, $3)); }
517	;
518
519unary_expr:
520	primary
521	| '*' cast_expr   %prec UNARY
522		{ $$ = build_indirect_ref ($2, "unary *"); }
523	/* __extension__ turns off -pedantic for following primary.  */
524	| extension cast_expr	  %prec UNARY
525		{ $$ = $2;
526		  RESTORE_EXT_FLAGS ($1); }
527	| unop cast_expr  %prec UNARY
528		{ $$ = build_unary_op ($1, $2, 0);
529		  overflow_warning ($$); }
530	/* Refer to the address of a label as a pointer.  */
531	| ANDAND identifier
532		{ $$ = finish_label_address_expr ($2); }
533	| sizeof unary_expr  %prec UNARY
534		{ skip_evaluation--;
535		  if (TREE_CODE ($2) == COMPONENT_REF
536		      && DECL_C_BIT_FIELD (TREE_OPERAND ($2, 1)))
537		    error ("`sizeof' applied to a bit-field");
538		  $$ = c_sizeof (TREE_TYPE ($2)); }
539	| sizeof '(' typename ')'  %prec HYPERUNARY
540		{ skip_evaluation--;
541		  $$ = c_sizeof (groktypename ($3)); }
542	| alignof unary_expr  %prec UNARY
543		{ skip_evaluation--;
544		  $$ = c_alignof_expr ($2); }
545	| alignof '(' typename ')'  %prec HYPERUNARY
546		{ skip_evaluation--;
547		  $$ = c_alignof (groktypename ($3)); }
548	| REALPART cast_expr %prec UNARY
549		{ $$ = build_unary_op (REALPART_EXPR, $2, 0); }
550	| IMAGPART cast_expr %prec UNARY
551		{ $$ = build_unary_op (IMAGPART_EXPR, $2, 0); }
552	;
553
554sizeof:
555	SIZEOF { skip_evaluation++; }
556	;
557
558alignof:
559	ALIGNOF { skip_evaluation++; }
560	;
561
562typeof:
563	TYPEOF { skip_evaluation++; }
564	;
565
566cast_expr:
567	unary_expr
568	| '(' typename ')' cast_expr  %prec UNARY
569		{ $$ = c_cast_expr ($2, $4); }
570	;
571
572expr_no_commas:
573	  cast_expr
574	| expr_no_commas '+' expr_no_commas
575		{ $$ = parser_build_binary_op ($2, $1, $3); }
576	| expr_no_commas '-' expr_no_commas
577		{ $$ = parser_build_binary_op ($2, $1, $3); }
578	| expr_no_commas '*' expr_no_commas
579		{ $$ = parser_build_binary_op ($2, $1, $3); }
580	| expr_no_commas '/' expr_no_commas
581		{ $$ = parser_build_binary_op ($2, $1, $3); }
582	| expr_no_commas '%' expr_no_commas
583		{ $$ = parser_build_binary_op ($2, $1, $3); }
584	| expr_no_commas LSHIFT expr_no_commas
585		{ $$ = parser_build_binary_op ($2, $1, $3); }
586	| expr_no_commas RSHIFT expr_no_commas
587		{ $$ = parser_build_binary_op ($2, $1, $3); }
588	| expr_no_commas ARITHCOMPARE expr_no_commas
589		{ $$ = parser_build_binary_op ($2, $1, $3); }
590	| expr_no_commas EQCOMPARE expr_no_commas
591		{ $$ = parser_build_binary_op ($2, $1, $3); }
592	| expr_no_commas '&' expr_no_commas
593		{ $$ = parser_build_binary_op ($2, $1, $3); }
594	| expr_no_commas '|' expr_no_commas
595		{ $$ = parser_build_binary_op ($2, $1, $3); }
596	| expr_no_commas '^' expr_no_commas
597		{ $$ = parser_build_binary_op ($2, $1, $3); }
598	| expr_no_commas ANDAND
599		{ $1 = c_common_truthvalue_conversion
600		    (default_conversion ($1));
601		  skip_evaluation += $1 == boolean_false_node; }
602	  expr_no_commas
603		{ skip_evaluation -= $1 == boolean_false_node;
604		  $$ = parser_build_binary_op (TRUTH_ANDIF_EXPR, $1, $4); }
605	| expr_no_commas OROR
606		{ $1 = c_common_truthvalue_conversion
607		    (default_conversion ($1));
608		  skip_evaluation += $1 == boolean_true_node; }
609	  expr_no_commas
610		{ skip_evaluation -= $1 == boolean_true_node;
611		  $$ = parser_build_binary_op (TRUTH_ORIF_EXPR, $1, $4); }
612	| expr_no_commas '?'
613		{ $1 = c_common_truthvalue_conversion
614		    (default_conversion ($1));
615		  skip_evaluation += $1 == boolean_false_node; }
616          expr ':'
617		{ skip_evaluation += (($1 == boolean_true_node)
618				      - ($1 == boolean_false_node)); }
619	  expr_no_commas
620		{ skip_evaluation -= $1 == boolean_true_node;
621		  $$ = build_conditional_expr ($1, $4, $7); }
622	| expr_no_commas '?'
623		{ if (pedantic)
624		    pedwarn ("ISO C forbids omitting the middle term of a ?: expression");
625		  /* Make sure first operand is calculated only once.  */
626		  $<ttype>2 = save_expr ($1);
627		  $1 = c_common_truthvalue_conversion
628		    (default_conversion ($<ttype>2));
629		  skip_evaluation += $1 == boolean_true_node; }
630	  ':' expr_no_commas
631		{ skip_evaluation -= $1 == boolean_true_node;
632		  $$ = build_conditional_expr ($1, $<ttype>2, $5); }
633	| expr_no_commas '=' expr_no_commas
634		{ char class;
635		  $$ = build_modify_expr ($1, NOP_EXPR, $3);
636		  class = TREE_CODE_CLASS (TREE_CODE ($$));
637		  if (IS_EXPR_CODE_CLASS (class))
638		    C_SET_EXP_ORIGINAL_CODE ($$, MODIFY_EXPR);
639		}
640	| expr_no_commas ASSIGN expr_no_commas
641		{ char class;
642		  $$ = build_modify_expr ($1, $2, $3);
643		  /* This inhibits warnings in
644		     c_common_truthvalue_conversion.  */
645		  class = TREE_CODE_CLASS (TREE_CODE ($$));
646		  if (IS_EXPR_CODE_CLASS (class))
647		    C_SET_EXP_ORIGINAL_CODE ($$, ERROR_MARK);
648		}
649	;
650
651primary:
652	IDENTIFIER
653		{
654		  if (yychar == YYEMPTY)
655		    yychar = YYLEX;
656		  $$ = build_external_ref ($1, yychar == '(');
657		}
658	| CONSTANT
659	| STRING
660		{ $$ = fix_string_type ($$); }
661	| VAR_FUNC_NAME
662		{ $$ = fname_decl (C_RID_CODE ($$), $$); }
663	| '(' typename ')' '{'
664		{ start_init (NULL_TREE, NULL, 0);
665		  $2 = groktypename ($2);
666		  really_start_incremental_init ($2); }
667	  initlist_maybe_comma '}'  %prec UNARY
668		{ tree constructor = pop_init_level (0);
669		  tree type = $2;
670		  finish_init ();
671
672		  if (pedantic && ! flag_isoc99)
673		    pedwarn ("ISO C89 forbids compound literals");
674		  $$ = build_compound_literal (type, constructor);
675		}
676	| '(' expr ')'
677		{ char class = TREE_CODE_CLASS (TREE_CODE ($2));
678		  if (IS_EXPR_CODE_CLASS (class))
679		    C_SET_EXP_ORIGINAL_CODE ($2, ERROR_MARK);
680		  $$ = $2; }
681	| '(' error ')'
682		{ $$ = error_mark_node; }
683	| compstmt_primary_start compstmt_nostart ')'
684                 { tree saved_last_tree;
685
686		   if (pedantic)
687		     pedwarn ("ISO C forbids braced-groups within expressions");
688		  pop_label_level ();
689
690		  saved_last_tree = COMPOUND_BODY ($1);
691		  RECHAIN_STMTS ($1, COMPOUND_BODY ($1));
692		  last_tree = saved_last_tree;
693		  TREE_CHAIN (last_tree) = NULL_TREE;
694		  if (!last_expr_type)
695		    last_expr_type = void_type_node;
696		  $$ = build1 (STMT_EXPR, last_expr_type, $1);
697		  TREE_SIDE_EFFECTS ($$) = 1;
698		}
699	| compstmt_primary_start error ')'
700		{
701		  pop_label_level ();
702		  last_tree = COMPOUND_BODY ($1);
703		  TREE_CHAIN (last_tree) = NULL_TREE;
704		  $$ = error_mark_node;
705		}
706	| primary '(' exprlist ')'   %prec '.'
707		{ $$ = build_function_call ($1, $3); }
708	| VA_ARG '(' expr_no_commas ',' typename ')'
709		{ $$ = build_va_arg ($3, groktypename ($5)); }
710
711      | CHOOSE_EXPR '(' expr_no_commas ',' expr_no_commas ',' expr_no_commas ')'
712		{
713                  tree c;
714
715                  c = fold ($3);
716                  STRIP_NOPS (c);
717                  if (TREE_CODE (c) != INTEGER_CST)
718                    error ("first argument to __builtin_choose_expr not a constant");
719                  $$ = integer_zerop (c) ? $7 : $5;
720		}
721      | TYPES_COMPATIBLE_P '(' typename ',' typename ')'
722		{
723		  tree e1, e2;
724
725		  e1 = TYPE_MAIN_VARIANT (groktypename ($3));
726		  e2 = TYPE_MAIN_VARIANT (groktypename ($5));
727
728		  $$ = comptypes (e1, e2)
729		    ? build_int_2 (1, 0) : build_int_2 (0, 0);
730		}
731	| primary '[' expr ']'   %prec '.'
732		{ $$ = build_array_ref ($1, $3); }
733	| primary '.' identifier
734		{
735ifobjc
736		    if (!is_public ($1, $3))
737		      $$ = error_mark_node;
738		    else
739end ifobjc
740		      $$ = build_component_ref ($1, $3);
741		}
742	| primary POINTSAT identifier
743		{
744                  tree expr = build_indirect_ref ($1, "->");
745
746ifobjc
747		      if (!is_public (expr, $3))
748			$$ = error_mark_node;
749		      else
750end ifobjc
751			$$ = build_component_ref (expr, $3);
752		}
753	| primary PLUSPLUS
754		{ $$ = build_unary_op (POSTINCREMENT_EXPR, $1, 0); }
755	| primary MINUSMINUS
756		{ $$ = build_unary_op (POSTDECREMENT_EXPR, $1, 0); }
757ifobjc
758	| objcmessageexpr
759		{ $$ = build_message_expr ($1); }
760	| objcselectorexpr
761		{ $$ = build_selector_expr ($1); }
762	| objcprotocolexpr
763		{ $$ = build_protocol_expr ($1); }
764	| objcencodeexpr
765		{ $$ = build_encode_expr ($1); }
766	| objc_string
767		{ $$ = build_objc_string_object ($1); }
768end ifobjc
769	;
770
771ifobjc
772/* Produces an STRING_CST with perhaps more STRING_CSTs chained
773   onto it, which is to be read as an ObjC string object.  */
774objc_string:
775	  '@' STRING
776		{ $$ = $2; }
777	| objc_string '@' STRING
778		{ $$ = chainon ($1, $3); }
779	;
780end ifobjc
781
782old_style_parm_decls:
783	old_style_parm_decls_1
784	{
785	  parsing_iso_function_signature = false; /* Reset after decls.  */
786	}
787	;
788
789old_style_parm_decls_1:
790	/* empty */
791	{
792	  if (warn_traditional && !in_system_header
793	      && parsing_iso_function_signature)
794	    warning ("traditional C rejects ISO C style function definitions");
795	  parsing_iso_function_signature = false; /* Reset after warning.  */
796	}
797	| datadecls
798	;
799
800/* The following are analogous to lineno_decl, decls and decl
801   except that they do not allow nested functions.
802   They are used for old-style parm decls.  */
803lineno_datadecl:
804	  save_filename save_lineno datadecl
805		{ }
806	;
807
808datadecls:
809	lineno_datadecl
810	| errstmt
811	| datadecls lineno_datadecl
812	| lineno_datadecl errstmt
813	;
814
815/* We don't allow prefix attributes here because they cause reduce/reduce
816   conflicts: we can't know whether we're parsing a function decl with
817   attribute suffix, or function defn with attribute prefix on first old
818   style parm.  */
819datadecl:
820	declspecs_ts_nosa setspecs initdecls ';'
821		{ POP_DECLSPEC_STACK; }
822	| declspecs_nots_nosa setspecs notype_initdecls ';'
823		{ POP_DECLSPEC_STACK; }
824	| declspecs_ts_nosa ';'
825		{ shadow_tag_warned ($1, 1);
826		  pedwarn ("empty declaration"); }
827	| declspecs_nots_nosa ';'
828		{ pedwarn ("empty declaration"); }
829	;
830
831/* This combination which saves a lineno before a decl
832   is the normal thing to use, rather than decl itself.
833   This is to avoid shift/reduce conflicts in contexts
834   where statement labels are allowed.  */
835lineno_decl:
836	  save_filename save_lineno decl
837		{ }
838	;
839
840/* records the type and storage class specs to use for processing
841   the declarators that follow.
842   Maintains a stack of outer-level values of current_declspecs,
843   for the sake of parm declarations nested in function declarators.  */
844setspecs: /* empty */
845		{ pending_xref_error ();
846		  PUSH_DECLSPEC_STACK;
847		  split_specs_attrs ($<ttype>0,
848				     &current_declspecs, &prefix_attributes);
849		  all_prefix_attributes = prefix_attributes; }
850	;
851
852/* Possibly attributes after a comma, which should reset all_prefix_attributes
853   to prefix_attributes with these ones chained on the front.  */
854maybe_resetattrs:
855	  maybe_attribute
856		{ all_prefix_attributes = chainon ($1, prefix_attributes); }
857	;
858
859decl:
860	declspecs_ts setspecs initdecls ';'
861		{ POP_DECLSPEC_STACK; }
862	| declspecs_nots setspecs notype_initdecls ';'
863		{ POP_DECLSPEC_STACK; }
864	| declspecs_ts setspecs nested_function
865		{ POP_DECLSPEC_STACK; }
866	| declspecs_nots setspecs notype_nested_function
867		{ POP_DECLSPEC_STACK; }
868	| declspecs ';'
869		{ shadow_tag ($1); }
870	| extension decl
871		{ RESTORE_EXT_FLAGS ($1); }
872	;
873
874/* A list of declaration specifiers.  These are:
875
876   - Storage class specifiers (scspec), which for GCC currently includes
877   function specifiers ("inline").
878
879   - Type specifiers (typespec_*).
880
881   - Type qualifiers (TYPE_QUAL).
882
883   - Attribute specifier lists (attributes).
884
885   These are stored as a TREE_LIST; the head of the list is the last
886   item in the specifier list.  Each entry in the list has either a
887   TREE_PURPOSE that is an attribute specifier list, or a TREE_VALUE that
888   is a single other specifier or qualifier; and a TREE_CHAIN that is the
889   rest of the list.  TREE_STATIC is set on the list if something other
890   than a storage class specifier or attribute has been seen; this is used
891   to warn for the obsolescent usage of storage class specifiers other than
892   at the start of the list.  (Doing this properly would require function
893   specifiers to be handled separately from storage class specifiers.)
894
895   The various cases below are classified according to:
896
897   (a) Whether a storage class specifier is included or not; some
898   places in the grammar disallow storage class specifiers (_sc or _nosc).
899
900   (b) Whether a type specifier has been seen; after a type specifier,
901   a typedef name is an identifier to redeclare (_ts or _nots).
902
903   (c) Whether the list starts with an attribute; in certain places,
904   the grammar requires specifiers that don't start with an attribute
905   (_sa or _nosa).
906
907   (d) Whether the list ends with an attribute (or a specifier such that
908   any following attribute would have been parsed as part of that specifier);
909   this avoids shift-reduce conflicts in the parsing of attributes
910   (_ea or _noea).
911
912   TODO:
913
914   (i) Distinguish between function specifiers and storage class specifiers,
915   at least for the purpose of warnings about obsolescent usage.
916
917   (ii) Halve the number of productions here by eliminating the _sc/_nosc
918   distinction and instead checking where required that storage class
919   specifiers aren't present.  */
920
921/* Declspecs which contain at least one type specifier or typedef name.
922   (Just `const' or `volatile' is not enough.)
923   A typedef'd name following these is taken as a name to be declared.
924   Declspecs have a non-NULL TREE_VALUE, attributes do not.  */
925
926declspecs_nosc_nots_nosa_noea:
927	  TYPE_QUAL
928		{ $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
929		  TREE_STATIC ($$) = 1; }
930	| declspecs_nosc_nots_nosa_noea TYPE_QUAL
931		{ $$ = tree_cons (NULL_TREE, $2, $1);
932		  TREE_STATIC ($$) = 1; }
933	| declspecs_nosc_nots_nosa_ea TYPE_QUAL
934		{ $$ = tree_cons (NULL_TREE, $2, $1);
935		  TREE_STATIC ($$) = 1; }
936	;
937
938declspecs_nosc_nots_nosa_ea:
939	  declspecs_nosc_nots_nosa_noea attributes
940		{ $$ = tree_cons ($2, NULL_TREE, $1);
941		  TREE_STATIC ($$) = TREE_STATIC ($1); }
942	;
943
944declspecs_nosc_nots_sa_noea:
945	  declspecs_nosc_nots_sa_noea TYPE_QUAL
946		{ $$ = tree_cons (NULL_TREE, $2, $1);
947		  TREE_STATIC ($$) = 1; }
948	| declspecs_nosc_nots_sa_ea TYPE_QUAL
949		{ $$ = tree_cons (NULL_TREE, $2, $1);
950		  TREE_STATIC ($$) = 1; }
951	;
952
953declspecs_nosc_nots_sa_ea:
954	  attributes
955		{ $$ = tree_cons ($1, NULL_TREE, NULL_TREE);
956		  TREE_STATIC ($$) = 0; }
957	| declspecs_nosc_nots_sa_noea attributes
958		{ $$ = tree_cons ($2, NULL_TREE, $1);
959		  TREE_STATIC ($$) = TREE_STATIC ($1); }
960	;
961
962declspecs_nosc_ts_nosa_noea:
963	  typespec_nonattr
964		{ $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
965		  TREE_STATIC ($$) = 1; }
966	| declspecs_nosc_ts_nosa_noea TYPE_QUAL
967		{ $$ = tree_cons (NULL_TREE, $2, $1);
968		  TREE_STATIC ($$) = 1; }
969	| declspecs_nosc_ts_nosa_ea TYPE_QUAL
970		{ $$ = tree_cons (NULL_TREE, $2, $1);
971		  TREE_STATIC ($$) = 1; }
972	| declspecs_nosc_ts_nosa_noea typespec_reserved_nonattr
973		{ $$ = tree_cons (NULL_TREE, $2, $1);
974		  TREE_STATIC ($$) = 1; }
975	| declspecs_nosc_ts_nosa_ea typespec_reserved_nonattr
976		{ $$ = tree_cons (NULL_TREE, $2, $1);
977		  TREE_STATIC ($$) = 1; }
978	| declspecs_nosc_nots_nosa_noea typespec_nonattr
979		{ $$ = tree_cons (NULL_TREE, $2, $1);
980		  TREE_STATIC ($$) = 1; }
981	| declspecs_nosc_nots_nosa_ea typespec_nonattr
982		{ $$ = tree_cons (NULL_TREE, $2, $1);
983		  TREE_STATIC ($$) = 1; }
984	;
985
986declspecs_nosc_ts_nosa_ea:
987	  typespec_attr
988		{ $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
989		  TREE_STATIC ($$) = 1; }
990	| declspecs_nosc_ts_nosa_noea attributes
991		{ $$ = tree_cons ($2, NULL_TREE, $1);
992		  TREE_STATIC ($$) = TREE_STATIC ($1); }
993	| declspecs_nosc_ts_nosa_noea typespec_reserved_attr
994		{ $$ = tree_cons (NULL_TREE, $2, $1);
995		  TREE_STATIC ($$) = 1; }
996	| declspecs_nosc_ts_nosa_ea typespec_reserved_attr
997		{ $$ = tree_cons (NULL_TREE, $2, $1);
998		  TREE_STATIC ($$) = 1; }
999	| declspecs_nosc_nots_nosa_noea typespec_attr
1000		{ $$ = tree_cons (NULL_TREE, $2, $1);
1001		  TREE_STATIC ($$) = 1; }
1002	| declspecs_nosc_nots_nosa_ea typespec_attr
1003		{ $$ = tree_cons (NULL_TREE, $2, $1);
1004		  TREE_STATIC ($$) = 1; }
1005	;
1006
1007declspecs_nosc_ts_sa_noea:
1008	  declspecs_nosc_ts_sa_noea TYPE_QUAL
1009		{ $$ = tree_cons (NULL_TREE, $2, $1);
1010		  TREE_STATIC ($$) = 1; }
1011	| declspecs_nosc_ts_sa_ea TYPE_QUAL
1012		{ $$ = tree_cons (NULL_TREE, $2, $1);
1013		  TREE_STATIC ($$) = 1; }
1014	| declspecs_nosc_ts_sa_noea typespec_reserved_nonattr
1015		{ $$ = tree_cons (NULL_TREE, $2, $1);
1016		  TREE_STATIC ($$) = 1; }
1017	| declspecs_nosc_ts_sa_ea typespec_reserved_nonattr
1018		{ $$ = tree_cons (NULL_TREE, $2, $1);
1019		  TREE_STATIC ($$) = 1; }
1020	| declspecs_nosc_nots_sa_noea typespec_nonattr
1021		{ $$ = tree_cons (NULL_TREE, $2, $1);
1022		  TREE_STATIC ($$) = 1; }
1023	| declspecs_nosc_nots_sa_ea typespec_nonattr
1024		{ $$ = tree_cons (NULL_TREE, $2, $1);
1025		  TREE_STATIC ($$) = 1; }
1026	;
1027
1028declspecs_nosc_ts_sa_ea:
1029	  declspecs_nosc_ts_sa_noea attributes
1030		{ $$ = tree_cons ($2, NULL_TREE, $1);
1031		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1032	| declspecs_nosc_ts_sa_noea typespec_reserved_attr
1033		{ $$ = tree_cons (NULL_TREE, $2, $1);
1034		  TREE_STATIC ($$) = 1; }
1035	| declspecs_nosc_ts_sa_ea typespec_reserved_attr
1036		{ $$ = tree_cons (NULL_TREE, $2, $1);
1037		  TREE_STATIC ($$) = 1; }
1038	| declspecs_nosc_nots_sa_noea typespec_attr
1039		{ $$ = tree_cons (NULL_TREE, $2, $1);
1040		  TREE_STATIC ($$) = 1; }
1041	| declspecs_nosc_nots_sa_ea typespec_attr
1042		{ $$ = tree_cons (NULL_TREE, $2, $1);
1043		  TREE_STATIC ($$) = 1; }
1044	;
1045
1046declspecs_sc_nots_nosa_noea:
1047	  scspec
1048		{ $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
1049		  TREE_STATIC ($$) = 0; }
1050	| declspecs_sc_nots_nosa_noea TYPE_QUAL
1051		{ $$ = tree_cons (NULL_TREE, $2, $1);
1052		  TREE_STATIC ($$) = 1; }
1053	| declspecs_sc_nots_nosa_ea TYPE_QUAL
1054		{ $$ = tree_cons (NULL_TREE, $2, $1);
1055		  TREE_STATIC ($$) = 1; }
1056	| declspecs_nosc_nots_nosa_noea scspec
1057		{ if (extra_warnings && TREE_STATIC ($1))
1058		    warning ("`%s' is not at beginning of declaration",
1059			     IDENTIFIER_POINTER ($2));
1060		  $$ = tree_cons (NULL_TREE, $2, $1);
1061		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1062	| declspecs_nosc_nots_nosa_ea scspec
1063		{ if (extra_warnings && TREE_STATIC ($1))
1064		    warning ("`%s' is not at beginning of declaration",
1065			     IDENTIFIER_POINTER ($2));
1066		  $$ = tree_cons (NULL_TREE, $2, $1);
1067		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1068	| declspecs_sc_nots_nosa_noea scspec
1069		{ if (extra_warnings && TREE_STATIC ($1))
1070		    warning ("`%s' is not at beginning of declaration",
1071			     IDENTIFIER_POINTER ($2));
1072		  $$ = tree_cons (NULL_TREE, $2, $1);
1073		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1074	| declspecs_sc_nots_nosa_ea scspec
1075		{ if (extra_warnings && TREE_STATIC ($1))
1076		    warning ("`%s' is not at beginning of declaration",
1077			     IDENTIFIER_POINTER ($2));
1078		  $$ = tree_cons (NULL_TREE, $2, $1);
1079		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1080	;
1081
1082declspecs_sc_nots_nosa_ea:
1083	  declspecs_sc_nots_nosa_noea attributes
1084		{ $$ = tree_cons ($2, NULL_TREE, $1);
1085		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1086	;
1087
1088declspecs_sc_nots_sa_noea:
1089	  declspecs_sc_nots_sa_noea TYPE_QUAL
1090		{ $$ = tree_cons (NULL_TREE, $2, $1);
1091		  TREE_STATIC ($$) = 1; }
1092	| declspecs_sc_nots_sa_ea TYPE_QUAL
1093		{ $$ = tree_cons (NULL_TREE, $2, $1);
1094		  TREE_STATIC ($$) = 1; }
1095	| declspecs_nosc_nots_sa_noea scspec
1096		{ if (extra_warnings && TREE_STATIC ($1))
1097		    warning ("`%s' is not at beginning of declaration",
1098			     IDENTIFIER_POINTER ($2));
1099		  $$ = tree_cons (NULL_TREE, $2, $1);
1100		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1101	| declspecs_nosc_nots_sa_ea scspec
1102		{ if (extra_warnings && TREE_STATIC ($1))
1103		    warning ("`%s' is not at beginning of declaration",
1104			     IDENTIFIER_POINTER ($2));
1105		  $$ = tree_cons (NULL_TREE, $2, $1);
1106		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1107	| declspecs_sc_nots_sa_noea scspec
1108		{ if (extra_warnings && TREE_STATIC ($1))
1109		    warning ("`%s' is not at beginning of declaration",
1110			     IDENTIFIER_POINTER ($2));
1111		  $$ = tree_cons (NULL_TREE, $2, $1);
1112		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1113	| declspecs_sc_nots_sa_ea scspec
1114		{ if (extra_warnings && TREE_STATIC ($1))
1115		    warning ("`%s' is not at beginning of declaration",
1116			     IDENTIFIER_POINTER ($2));
1117		  $$ = tree_cons (NULL_TREE, $2, $1);
1118		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1119	;
1120
1121declspecs_sc_nots_sa_ea:
1122	  declspecs_sc_nots_sa_noea attributes
1123		{ $$ = tree_cons ($2, NULL_TREE, $1);
1124		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1125	;
1126
1127declspecs_sc_ts_nosa_noea:
1128	  declspecs_sc_ts_nosa_noea TYPE_QUAL
1129		{ $$ = tree_cons (NULL_TREE, $2, $1);
1130		  TREE_STATIC ($$) = 1; }
1131	| declspecs_sc_ts_nosa_ea TYPE_QUAL
1132		{ $$ = tree_cons (NULL_TREE, $2, $1);
1133		  TREE_STATIC ($$) = 1; }
1134	| declspecs_sc_ts_nosa_noea typespec_reserved_nonattr
1135		{ $$ = tree_cons (NULL_TREE, $2, $1);
1136		  TREE_STATIC ($$) = 1; }
1137	| declspecs_sc_ts_nosa_ea typespec_reserved_nonattr
1138		{ $$ = tree_cons (NULL_TREE, $2, $1);
1139		  TREE_STATIC ($$) = 1; }
1140	| declspecs_sc_nots_nosa_noea typespec_nonattr
1141		{ $$ = tree_cons (NULL_TREE, $2, $1);
1142		  TREE_STATIC ($$) = 1; }
1143	| declspecs_sc_nots_nosa_ea typespec_nonattr
1144		{ $$ = tree_cons (NULL_TREE, $2, $1);
1145		  TREE_STATIC ($$) = 1; }
1146	| declspecs_nosc_ts_nosa_noea scspec
1147		{ if (extra_warnings && TREE_STATIC ($1))
1148		    warning ("`%s' is not at beginning of declaration",
1149			     IDENTIFIER_POINTER ($2));
1150		  $$ = tree_cons (NULL_TREE, $2, $1);
1151		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1152	| declspecs_nosc_ts_nosa_ea scspec
1153		{ if (extra_warnings && TREE_STATIC ($1))
1154		    warning ("`%s' is not at beginning of declaration",
1155			     IDENTIFIER_POINTER ($2));
1156		  $$ = tree_cons (NULL_TREE, $2, $1);
1157		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1158	| declspecs_sc_ts_nosa_noea scspec
1159		{ if (extra_warnings && TREE_STATIC ($1))
1160		    warning ("`%s' is not at beginning of declaration",
1161			     IDENTIFIER_POINTER ($2));
1162		  $$ = tree_cons (NULL_TREE, $2, $1);
1163		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1164	| declspecs_sc_ts_nosa_ea scspec
1165		{ if (extra_warnings && TREE_STATIC ($1))
1166		    warning ("`%s' is not at beginning of declaration",
1167			     IDENTIFIER_POINTER ($2));
1168		  $$ = tree_cons (NULL_TREE, $2, $1);
1169		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1170	;
1171
1172declspecs_sc_ts_nosa_ea:
1173	  declspecs_sc_ts_nosa_noea attributes
1174		{ $$ = tree_cons ($2, NULL_TREE, $1);
1175		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1176	| declspecs_sc_ts_nosa_noea typespec_reserved_attr
1177		{ $$ = tree_cons (NULL_TREE, $2, $1);
1178		  TREE_STATIC ($$) = 1; }
1179	| declspecs_sc_ts_nosa_ea typespec_reserved_attr
1180		{ $$ = tree_cons (NULL_TREE, $2, $1);
1181		  TREE_STATIC ($$) = 1; }
1182	| declspecs_sc_nots_nosa_noea typespec_attr
1183		{ $$ = tree_cons (NULL_TREE, $2, $1);
1184		  TREE_STATIC ($$) = 1; }
1185	| declspecs_sc_nots_nosa_ea typespec_attr
1186		{ $$ = tree_cons (NULL_TREE, $2, $1);
1187		  TREE_STATIC ($$) = 1; }
1188	;
1189
1190declspecs_sc_ts_sa_noea:
1191	  declspecs_sc_ts_sa_noea TYPE_QUAL
1192		{ $$ = tree_cons (NULL_TREE, $2, $1);
1193		  TREE_STATIC ($$) = 1; }
1194	| declspecs_sc_ts_sa_ea TYPE_QUAL
1195		{ $$ = tree_cons (NULL_TREE, $2, $1);
1196		  TREE_STATIC ($$) = 1; }
1197	| declspecs_sc_ts_sa_noea typespec_reserved_nonattr
1198		{ $$ = tree_cons (NULL_TREE, $2, $1);
1199		  TREE_STATIC ($$) = 1; }
1200	| declspecs_sc_ts_sa_ea typespec_reserved_nonattr
1201		{ $$ = tree_cons (NULL_TREE, $2, $1);
1202		  TREE_STATIC ($$) = 1; }
1203	| declspecs_sc_nots_sa_noea typespec_nonattr
1204		{ $$ = tree_cons (NULL_TREE, $2, $1);
1205		  TREE_STATIC ($$) = 1; }
1206	| declspecs_sc_nots_sa_ea typespec_nonattr
1207		{ $$ = tree_cons (NULL_TREE, $2, $1);
1208		  TREE_STATIC ($$) = 1; }
1209	| declspecs_nosc_ts_sa_noea scspec
1210		{ if (extra_warnings && TREE_STATIC ($1))
1211		    warning ("`%s' is not at beginning of declaration",
1212			     IDENTIFIER_POINTER ($2));
1213		  $$ = tree_cons (NULL_TREE, $2, $1);
1214		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1215	| declspecs_nosc_ts_sa_ea scspec
1216		{ if (extra_warnings && TREE_STATIC ($1))
1217		    warning ("`%s' is not at beginning of declaration",
1218			     IDENTIFIER_POINTER ($2));
1219		  $$ = tree_cons (NULL_TREE, $2, $1);
1220		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1221	| declspecs_sc_ts_sa_noea scspec
1222		{ if (extra_warnings && TREE_STATIC ($1))
1223		    warning ("`%s' is not at beginning of declaration",
1224			     IDENTIFIER_POINTER ($2));
1225		  $$ = tree_cons (NULL_TREE, $2, $1);
1226		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1227	| declspecs_sc_ts_sa_ea scspec
1228		{ if (extra_warnings && TREE_STATIC ($1))
1229		    warning ("`%s' is not at beginning of declaration",
1230			     IDENTIFIER_POINTER ($2));
1231		  $$ = tree_cons (NULL_TREE, $2, $1);
1232		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1233	;
1234
1235declspecs_sc_ts_sa_ea:
1236	  declspecs_sc_ts_sa_noea attributes
1237		{ $$ = tree_cons ($2, NULL_TREE, $1);
1238		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1239	| declspecs_sc_ts_sa_noea typespec_reserved_attr
1240		{ $$ = tree_cons (NULL_TREE, $2, $1);
1241		  TREE_STATIC ($$) = 1; }
1242	| declspecs_sc_ts_sa_ea typespec_reserved_attr
1243		{ $$ = tree_cons (NULL_TREE, $2, $1);
1244		  TREE_STATIC ($$) = 1; }
1245	| declspecs_sc_nots_sa_noea typespec_attr
1246		{ $$ = tree_cons (NULL_TREE, $2, $1);
1247		  TREE_STATIC ($$) = 1; }
1248	| declspecs_sc_nots_sa_ea typespec_attr
1249		{ $$ = tree_cons (NULL_TREE, $2, $1);
1250		  TREE_STATIC ($$) = 1; }
1251	;
1252
1253/* Particular useful classes of declspecs.  */
1254declspecs_ts:
1255	  declspecs_nosc_ts_nosa_noea
1256	| declspecs_nosc_ts_nosa_ea
1257	| declspecs_nosc_ts_sa_noea
1258	| declspecs_nosc_ts_sa_ea
1259	| declspecs_sc_ts_nosa_noea
1260	| declspecs_sc_ts_nosa_ea
1261	| declspecs_sc_ts_sa_noea
1262	| declspecs_sc_ts_sa_ea
1263	;
1264
1265declspecs_nots:
1266	  declspecs_nosc_nots_nosa_noea
1267	| declspecs_nosc_nots_nosa_ea
1268	| declspecs_nosc_nots_sa_noea
1269	| declspecs_nosc_nots_sa_ea
1270	| declspecs_sc_nots_nosa_noea
1271	| declspecs_sc_nots_nosa_ea
1272	| declspecs_sc_nots_sa_noea
1273	| declspecs_sc_nots_sa_ea
1274	;
1275
1276declspecs_ts_nosa:
1277	  declspecs_nosc_ts_nosa_noea
1278	| declspecs_nosc_ts_nosa_ea
1279	| declspecs_sc_ts_nosa_noea
1280	| declspecs_sc_ts_nosa_ea
1281	;
1282
1283declspecs_nots_nosa:
1284	  declspecs_nosc_nots_nosa_noea
1285	| declspecs_nosc_nots_nosa_ea
1286	| declspecs_sc_nots_nosa_noea
1287	| declspecs_sc_nots_nosa_ea
1288	;
1289
1290declspecs_nosc_ts:
1291	  declspecs_nosc_ts_nosa_noea
1292	| declspecs_nosc_ts_nosa_ea
1293	| declspecs_nosc_ts_sa_noea
1294	| declspecs_nosc_ts_sa_ea
1295	;
1296
1297declspecs_nosc_nots:
1298	  declspecs_nosc_nots_nosa_noea
1299	| declspecs_nosc_nots_nosa_ea
1300	| declspecs_nosc_nots_sa_noea
1301	| declspecs_nosc_nots_sa_ea
1302	;
1303
1304declspecs_nosc:
1305	  declspecs_nosc_ts_nosa_noea
1306	| declspecs_nosc_ts_nosa_ea
1307	| declspecs_nosc_ts_sa_noea
1308	| declspecs_nosc_ts_sa_ea
1309	| declspecs_nosc_nots_nosa_noea
1310	| declspecs_nosc_nots_nosa_ea
1311	| declspecs_nosc_nots_sa_noea
1312	| declspecs_nosc_nots_sa_ea
1313	;
1314
1315declspecs:
1316	  declspecs_nosc_nots_nosa_noea
1317	| declspecs_nosc_nots_nosa_ea
1318	| declspecs_nosc_nots_sa_noea
1319	| declspecs_nosc_nots_sa_ea
1320	| declspecs_nosc_ts_nosa_noea
1321	| declspecs_nosc_ts_nosa_ea
1322	| declspecs_nosc_ts_sa_noea
1323	| declspecs_nosc_ts_sa_ea
1324	| declspecs_sc_nots_nosa_noea
1325	| declspecs_sc_nots_nosa_ea
1326	| declspecs_sc_nots_sa_noea
1327	| declspecs_sc_nots_sa_ea
1328	| declspecs_sc_ts_nosa_noea
1329	| declspecs_sc_ts_nosa_ea
1330	| declspecs_sc_ts_sa_noea
1331	| declspecs_sc_ts_sa_ea
1332	;
1333
1334/* A (possibly empty) sequence of type qualifiers and attributes.  */
1335maybe_type_quals_attrs:
1336	  /* empty */
1337		{ $$ = NULL_TREE; }
1338	| declspecs_nosc_nots
1339		{ $$ = $1; }
1340	;
1341
1342/* A type specifier (but not a type qualifier).
1343   Once we have seen one of these in a declaration,
1344   if a typedef name appears then it is being redeclared.
1345
1346   The _reserved versions start with a reserved word and may appear anywhere
1347   in the declaration specifiers; the _nonreserved versions may only
1348   appear before any other type specifiers, and after that are (if names)
1349   being redeclared.
1350
1351   FIXME: should the _nonreserved version be restricted to names being
1352   redeclared only?  The other entries there relate only the GNU extensions
1353   and Objective C, and are historically parsed thus, and don't make sense
1354   after other type specifiers, but it might be cleaner to count them as
1355   _reserved.
1356
1357   _attr means: specifiers that either end with attributes,
1358   or are such that any following attributes would
1359   be parsed as part of the specifier.
1360
1361   _nonattr: specifiers.  */
1362
1363typespec_nonattr:
1364	  typespec_reserved_nonattr
1365	| typespec_nonreserved_nonattr
1366	;
1367
1368typespec_attr:
1369	  typespec_reserved_attr
1370	;
1371
1372typespec_reserved_nonattr:
1373	  TYPESPEC
1374		{ OBJC_NEED_RAW_IDENTIFIER (1);	}
1375	| structsp_nonattr
1376	;
1377
1378typespec_reserved_attr:
1379	  structsp_attr
1380	;
1381
1382typespec_nonreserved_nonattr:
1383	  TYPENAME
1384		{ /* For a typedef name, record the meaning, not the name.
1385		     In case of `foo foo, bar;'.  */
1386		  $$ = lookup_name ($1); }
1387ifobjc
1388	| CLASSNAME protocolrefs
1389		{ $$ = get_static_reference ($1, $2); }
1390	| OBJECTNAME protocolrefs
1391		{ $$ = get_object_reference ($2); }
1392
1393/* Make "<SomeProtocol>" equivalent to "id <SomeProtocol>"
1394   - nisse@lysator.liu.se */
1395        | non_empty_protocolrefs
1396                { $$ = get_object_reference ($1); }
1397end ifobjc
1398	| typeof '(' expr ')'
1399		{ skip_evaluation--; $$ = TREE_TYPE ($3); }
1400	| typeof '(' typename ')'
1401		{ skip_evaluation--; $$ = groktypename ($3); }
1402	;
1403
1404/* typespec_nonreserved_attr does not exist.  */
1405
1406initdecls:
1407	initdcl
1408	| initdecls ',' maybe_resetattrs initdcl
1409	;
1410
1411notype_initdecls:
1412	notype_initdcl
1413	| notype_initdecls ',' maybe_resetattrs notype_initdcl
1414	;
1415
1416maybeasm:
1417	  /* empty */
1418		{ $$ = NULL_TREE; }
1419	| ASM_KEYWORD '(' STRING ')'
1420		{ $$ = $3; }
1421	;
1422
1423initdcl:
1424	  declarator maybeasm maybe_attribute '='
1425		{ $<ttype>$ = start_decl ($1, current_declspecs, 1,
1426					  chainon ($3, all_prefix_attributes));
1427		  start_init ($<ttype>$, $2, global_bindings_p ()); }
1428	  init
1429/* Note how the declaration of the variable is in effect while its init is parsed! */
1430		{ finish_init ();
1431		  finish_decl ($<ttype>5, $6, $2); }
1432	| declarator maybeasm maybe_attribute
1433		{ tree d = start_decl ($1, current_declspecs, 0,
1434				       chainon ($3, all_prefix_attributes));
1435		  finish_decl (d, NULL_TREE, $2);
1436                }
1437	;
1438
1439notype_initdcl:
1440	  notype_declarator maybeasm maybe_attribute '='
1441		{ $<ttype>$ = start_decl ($1, current_declspecs, 1,
1442					  chainon ($3, all_prefix_attributes));
1443		  start_init ($<ttype>$, $2, global_bindings_p ()); }
1444	  init
1445/* Note how the declaration of the variable is in effect while its init is parsed! */
1446		{ finish_init ();
1447		  finish_decl ($<ttype>5, $6, $2); }
1448	| notype_declarator maybeasm maybe_attribute
1449		{ tree d = start_decl ($1, current_declspecs, 0,
1450				       chainon ($3, all_prefix_attributes));
1451		  finish_decl (d, NULL_TREE, $2); }
1452	;
1453/* the * rules are dummies to accept the Apollo extended syntax
1454   so that the header files compile. */
1455maybe_attribute:
1456      /* empty */
1457  		{ $$ = NULL_TREE; }
1458	| attributes
1459		{ $$ = $1; }
1460	;
1461
1462attributes:
1463      attribute
1464		{ $$ = $1; }
1465	| attributes attribute
1466		{ $$ = chainon ($1, $2); }
1467	;
1468
1469attribute:
1470      ATTRIBUTE '(' '(' attribute_list ')' ')'
1471		{ $$ = $4; }
1472	;
1473
1474attribute_list:
1475      attrib
1476		{ $$ = $1; }
1477	| attribute_list ',' attrib
1478		{ $$ = chainon ($1, $3); }
1479	;
1480
1481attrib:
1482    /* empty */
1483		{ $$ = NULL_TREE; }
1484	| any_word
1485		{ $$ = build_tree_list ($1, NULL_TREE); }
1486	| any_word '(' IDENTIFIER ')'
1487		{ $$ = build_tree_list ($1, build_tree_list (NULL_TREE, $3)); }
1488	| any_word '(' IDENTIFIER ',' nonnull_exprlist ')'
1489		{ $$ = build_tree_list ($1, tree_cons (NULL_TREE, $3, $5)); }
1490	| any_word '(' exprlist ')'
1491		{ $$ = build_tree_list ($1, $3); }
1492	;
1493
1494/* This still leaves out most reserved keywords,
1495   shouldn't we include them?  */
1496
1497any_word:
1498	  identifier
1499	| scspec
1500	| TYPESPEC
1501	| TYPE_QUAL
1502	;
1503
1504scspec:
1505	  STATIC
1506	| SCSPEC
1507	;
1508
1509/* Initializers.  `init' is the entry point.  */
1510
1511init:
1512	expr_no_commas
1513	| '{'
1514		{ really_start_incremental_init (NULL_TREE); }
1515	  initlist_maybe_comma '}'
1516		{ $$ = pop_init_level (0); }
1517	| error
1518		{ $$ = error_mark_node; }
1519	;
1520
1521/* `initlist_maybe_comma' is the guts of an initializer in braces.  */
1522initlist_maybe_comma:
1523	  /* empty */
1524		{ if (pedantic)
1525		    pedwarn ("ISO C forbids empty initializer braces"); }
1526	| initlist1 maybecomma
1527	;
1528
1529initlist1:
1530	  initelt
1531	| initlist1 ',' initelt
1532	;
1533
1534/* `initelt' is a single element of an initializer.
1535   It may use braces.  */
1536initelt:
1537	  designator_list '=' initval
1538		{ if (pedantic && ! flag_isoc99)
1539		    pedwarn ("ISO C89 forbids specifying subobject to initialize"); }
1540	| designator initval
1541		{ if (pedantic)
1542		    pedwarn ("obsolete use of designated initializer without `='"); }
1543	| identifier ':'
1544		{ set_init_label ($1);
1545		  if (pedantic)
1546		    pedwarn ("obsolete use of designated initializer with `:'"); }
1547	  initval
1548		{}
1549	| initval
1550	;
1551
1552initval:
1553	  '{'
1554		{ push_init_level (0); }
1555	  initlist_maybe_comma '}'
1556		{ process_init_element (pop_init_level (0)); }
1557	| expr_no_commas
1558		{ process_init_element ($1); }
1559	| error
1560	;
1561
1562designator_list:
1563	  designator
1564	| designator_list designator
1565	;
1566
1567designator:
1568	  '.' identifier
1569		{ set_init_label ($2); }
1570	| '[' expr_no_commas ELLIPSIS expr_no_commas ']'
1571		{ set_init_index ($2, $4);
1572		  if (pedantic)
1573		    pedwarn ("ISO C forbids specifying range of elements to initialize"); }
1574	| '[' expr_no_commas ']'
1575		{ set_init_index ($2, NULL_TREE); }
1576	;
1577
1578nested_function:
1579	  declarator
1580		{ if (pedantic)
1581		    pedwarn ("ISO C forbids nested functions");
1582
1583		  push_function_context ();
1584		  if (! start_function (current_declspecs, $1,
1585					all_prefix_attributes))
1586		    {
1587		      pop_function_context ();
1588		      YYERROR1;
1589		    }
1590		  parsing_iso_function_signature = false; /* Don't warn about nested functions.  */
1591		}
1592	   old_style_parm_decls
1593		{ store_parm_decls (); }
1594/* This used to use compstmt_or_error.
1595   That caused a bug with input `f(g) int g {}',
1596   where the use of YYERROR1 above caused an error
1597   which then was handled by compstmt_or_error.
1598   There followed a repeated execution of that same rule,
1599   which called YYERROR1 again, and so on.  */
1600	  save_filename save_lineno compstmt
1601		{ tree decl = current_function_decl;
1602		  DECL_SOURCE_FILE (decl) = $5;
1603		  DECL_SOURCE_LINE (decl) = $6;
1604		  finish_function (1, 1);
1605		  pop_function_context ();
1606		  add_decl_stmt (decl); }
1607	;
1608
1609notype_nested_function:
1610	  notype_declarator
1611		{ if (pedantic)
1612		    pedwarn ("ISO C forbids nested functions");
1613
1614		  push_function_context ();
1615		  if (! start_function (current_declspecs, $1,
1616					all_prefix_attributes))
1617		    {
1618		      pop_function_context ();
1619		      YYERROR1;
1620		    }
1621		  parsing_iso_function_signature = false; /* Don't warn about nested functions.  */
1622		}
1623	  old_style_parm_decls
1624		{ store_parm_decls (); }
1625/* This used to use compstmt_or_error.
1626   That caused a bug with input `f(g) int g {}',
1627   where the use of YYERROR1 above caused an error
1628   which then was handled by compstmt_or_error.
1629   There followed a repeated execution of that same rule,
1630   which called YYERROR1 again, and so on.  */
1631	  save_filename save_lineno compstmt
1632		{ tree decl = current_function_decl;
1633		  DECL_SOURCE_FILE (decl) = $5;
1634		  DECL_SOURCE_LINE (decl) = $6;
1635		  finish_function (1, 1);
1636		  pop_function_context ();
1637		  add_decl_stmt (decl); }
1638	;
1639
1640/* Any kind of declarator (thus, all declarators allowed
1641   after an explicit typespec).  */
1642
1643declarator:
1644	  after_type_declarator
1645	| notype_declarator
1646	;
1647
1648/* A declarator that is allowed only after an explicit typespec.  */
1649
1650after_type_declarator:
1651	  '(' maybe_attribute after_type_declarator ')'
1652		{ $$ = $2 ? tree_cons ($2, $3, NULL_TREE) : $3; }
1653	| after_type_declarator '(' parmlist_or_identifiers  %prec '.'
1654		{ $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1655/*	| after_type_declarator '(' error ')'  %prec '.'
1656		{ $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1657		  poplevel (0, 0, 0); }  */
1658	| after_type_declarator array_declarator  %prec '.'
1659		{ $$ = set_array_declarator_type ($2, $1, 0); }
1660	| '*' maybe_type_quals_attrs after_type_declarator  %prec UNARY
1661		{ $$ = make_pointer_declarator ($2, $3); }
1662	| TYPENAME
1663ifobjc
1664	| OBJECTNAME
1665end ifobjc
1666	;
1667
1668/* Kinds of declarator that can appear in a parameter list
1669   in addition to notype_declarator.  This is like after_type_declarator
1670   but does not allow a typedef name in parentheses as an identifier
1671   (because it would conflict with a function with that typedef as arg).  */
1672parm_declarator:
1673	  parm_declarator_starttypename
1674	| parm_declarator_nostarttypename
1675	;
1676
1677parm_declarator_starttypename:
1678	  parm_declarator_starttypename '(' parmlist_or_identifiers  %prec '.'
1679		{ $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1680/*	| parm_declarator_starttypename '(' error ')'  %prec '.'
1681		{ $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1682		  poplevel (0, 0, 0); }  */
1683	| parm_declarator_starttypename array_declarator  %prec '.'
1684		{ $$ = set_array_declarator_type ($2, $1, 0); }
1685	| TYPENAME
1686ifobjc
1687	| OBJECTNAME
1688end ifobjc
1689	;
1690
1691parm_declarator_nostarttypename:
1692	  parm_declarator_nostarttypename '(' parmlist_or_identifiers  %prec '.'
1693		{ $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1694/*	| parm_declarator_nostarttypename '(' error ')'  %prec '.'
1695		{ $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1696		  poplevel (0, 0, 0); }  */
1697	| parm_declarator_nostarttypename array_declarator  %prec '.'
1698		{ $$ = set_array_declarator_type ($2, $1, 0); }
1699	| '*' maybe_type_quals_attrs parm_declarator_starttypename  %prec UNARY
1700		{ $$ = make_pointer_declarator ($2, $3); }
1701	| '*' maybe_type_quals_attrs parm_declarator_nostarttypename  %prec UNARY
1702		{ $$ = make_pointer_declarator ($2, $3); }
1703	| '(' maybe_attribute parm_declarator_nostarttypename ')'
1704		{ $$ = $2 ? tree_cons ($2, $3, NULL_TREE) : $3; }
1705	;
1706
1707/* A declarator allowed whether or not there has been
1708   an explicit typespec.  These cannot redeclare a typedef-name.  */
1709
1710notype_declarator:
1711	  notype_declarator '(' parmlist_or_identifiers  %prec '.'
1712		{ $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1713/*	| notype_declarator '(' error ')'  %prec '.'
1714		{ $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1715		  poplevel (0, 0, 0); }  */
1716	| '(' maybe_attribute notype_declarator ')'
1717		{ $$ = $2 ? tree_cons ($2, $3, NULL_TREE) : $3; }
1718	| '*' maybe_type_quals_attrs notype_declarator  %prec UNARY
1719		{ $$ = make_pointer_declarator ($2, $3); }
1720	| notype_declarator array_declarator  %prec '.'
1721		{ $$ = set_array_declarator_type ($2, $1, 0); }
1722	| IDENTIFIER
1723	;
1724
1725struct_head:
1726	  STRUCT
1727		{ $$ = NULL_TREE; }
1728	| STRUCT attributes
1729		{ $$ = $2; }
1730	;
1731
1732union_head:
1733	  UNION
1734		{ $$ = NULL_TREE; }
1735	| UNION attributes
1736		{ $$ = $2; }
1737	;
1738
1739enum_head:
1740	  ENUM
1741		{ $$ = NULL_TREE; }
1742	| ENUM attributes
1743		{ $$ = $2; }
1744	;
1745
1746/* structsp_attr: struct/union/enum specifiers that either
1747   end with attributes, or are such that any following attributes would
1748   be parsed as part of the struct/union/enum specifier.
1749
1750   structsp_nonattr: other struct/union/enum specifiers.  */
1751
1752structsp_attr:
1753	  struct_head identifier '{'
1754		{ $$ = start_struct (RECORD_TYPE, $2);
1755		  /* Start scope of tag before parsing components.  */
1756		}
1757	  component_decl_list '}' maybe_attribute
1758		{ $$ = finish_struct ($<ttype>4, $5, chainon ($1, $7)); }
1759	| struct_head '{' component_decl_list '}' maybe_attribute
1760		{ $$ = finish_struct (start_struct (RECORD_TYPE, NULL_TREE),
1761				      $3, chainon ($1, $5));
1762		}
1763	| union_head identifier '{'
1764		{ $$ = start_struct (UNION_TYPE, $2); }
1765	  component_decl_list '}' maybe_attribute
1766		{ $$ = finish_struct ($<ttype>4, $5, chainon ($1, $7)); }
1767	| union_head '{' component_decl_list '}' maybe_attribute
1768		{ $$ = finish_struct (start_struct (UNION_TYPE, NULL_TREE),
1769				      $3, chainon ($1, $5));
1770		}
1771	| enum_head identifier '{'
1772		{ $$ = start_enum ($2); }
1773	  enumlist maybecomma_warn '}' maybe_attribute
1774		{ $$ = finish_enum ($<ttype>4, nreverse ($5),
1775				    chainon ($1, $8)); }
1776	| enum_head '{'
1777		{ $$ = start_enum (NULL_TREE); }
1778	  enumlist maybecomma_warn '}' maybe_attribute
1779		{ $$ = finish_enum ($<ttype>3, nreverse ($4),
1780				    chainon ($1, $7)); }
1781	;
1782
1783structsp_nonattr:
1784	  struct_head identifier
1785		{ $$ = xref_tag (RECORD_TYPE, $2); }
1786	| union_head identifier
1787		{ $$ = xref_tag (UNION_TYPE, $2); }
1788	| enum_head identifier
1789		{ $$ = xref_tag (ENUMERAL_TYPE, $2);
1790		  /* In ISO C, enumerated types can be referred to
1791		     only if already defined.  */
1792		  if (pedantic && !COMPLETE_TYPE_P ($$))
1793		    pedwarn ("ISO C forbids forward references to `enum' types"); }
1794	;
1795
1796maybecomma:
1797	  /* empty */
1798	| ','
1799	;
1800
1801maybecomma_warn:
1802	  /* empty */
1803	| ','
1804		{ if (pedantic && ! flag_isoc99)
1805		    pedwarn ("comma at end of enumerator list"); }
1806	;
1807
1808component_decl_list:
1809	  component_decl_list2
1810		{ $$ = $1; }
1811	| component_decl_list2 component_decl
1812		{ $$ = chainon ($1, $2);
1813		  pedwarn ("no semicolon at end of struct or union"); }
1814	;
1815
1816component_decl_list2:	/* empty */
1817		{ $$ = NULL_TREE; }
1818	| component_decl_list2 component_decl ';'
1819		{ $$ = chainon ($1, $2); }
1820	| component_decl_list2 ';'
1821		{ if (pedantic)
1822		    pedwarn ("extra semicolon in struct or union specified"); }
1823ifobjc
1824	/* foo(sizeof(struct{ @defs(ClassName)})); */
1825	| DEFS '(' CLASSNAME ')'
1826		{
1827		  tree interface = lookup_interface ($3);
1828
1829		  if (interface)
1830		    $$ = get_class_ivars (interface);
1831		  else
1832		    {
1833		      error ("cannot find interface declaration for `%s'",
1834			     IDENTIFIER_POINTER ($3));
1835		      $$ = NULL_TREE;
1836		    }
1837		}
1838end ifobjc
1839	;
1840
1841component_decl:
1842	  declspecs_nosc_ts setspecs components
1843		{ $$ = $3;
1844		  POP_DECLSPEC_STACK; }
1845	| declspecs_nosc_ts setspecs save_filename save_lineno
1846		{
1847		  /* Support for unnamed structs or unions as members of
1848		     structs or unions (which is [a] useful and [b] supports
1849		     MS P-SDK).  */
1850		  if (pedantic)
1851		    pedwarn ("ISO C doesn't support unnamed structs/unions");
1852
1853		  $$ = grokfield($3, $4, NULL, current_declspecs, NULL_TREE);
1854		  POP_DECLSPEC_STACK; }
1855	| declspecs_nosc_nots setspecs components_notype
1856		{ $$ = $3;
1857		  POP_DECLSPEC_STACK; }
1858	| declspecs_nosc_nots
1859		{ if (pedantic)
1860		    pedwarn ("ISO C forbids member declarations with no members");
1861		  shadow_tag($1);
1862		  $$ = NULL_TREE; }
1863	| error
1864		{ $$ = NULL_TREE; }
1865	| extension component_decl
1866		{ $$ = $2;
1867		  RESTORE_EXT_FLAGS ($1); }
1868	;
1869
1870components:
1871	  component_declarator
1872	| components ',' maybe_resetattrs component_declarator
1873		{ $$ = chainon ($1, $4); }
1874	;
1875
1876components_notype:
1877	  component_notype_declarator
1878	| components_notype ',' maybe_resetattrs component_notype_declarator
1879		{ $$ = chainon ($1, $4); }
1880	;
1881
1882component_declarator:
1883	  save_filename save_lineno declarator maybe_attribute
1884		{ $$ = grokfield ($1, $2, $3, current_declspecs, NULL_TREE);
1885		  decl_attributes (&$$, chainon ($4, all_prefix_attributes), 0); }
1886	| save_filename save_lineno
1887	  declarator ':' expr_no_commas maybe_attribute
1888		{ $$ = grokfield ($1, $2, $3, current_declspecs, $5);
1889		  decl_attributes (&$$, chainon ($6, all_prefix_attributes), 0); }
1890	| save_filename save_lineno ':' expr_no_commas maybe_attribute
1891		{ $$ = grokfield ($1, $2, NULL_TREE, current_declspecs, $4);
1892		  decl_attributes (&$$, chainon ($5, all_prefix_attributes), 0); }
1893	;
1894
1895component_notype_declarator:
1896	  save_filename save_lineno notype_declarator maybe_attribute
1897		{ $$ = grokfield ($1, $2, $3, current_declspecs, NULL_TREE);
1898		  decl_attributes (&$$, chainon ($4, all_prefix_attributes), 0); }
1899	| save_filename save_lineno
1900	  notype_declarator ':' expr_no_commas maybe_attribute
1901		{ $$ = grokfield ($1, $2, $3, current_declspecs, $5);
1902		  decl_attributes (&$$, chainon ($6, all_prefix_attributes), 0); }
1903	| save_filename save_lineno ':' expr_no_commas maybe_attribute
1904		{ $$ = grokfield ($1, $2, NULL_TREE, current_declspecs, $4);
1905		  decl_attributes (&$$, chainon ($5, all_prefix_attributes), 0); }
1906	;
1907
1908/* We chain the enumerators in reverse order.
1909   They are put in forward order where enumlist is used.
1910   (The order used to be significant, but no longer is so.
1911   However, we still maintain the order, just to be clean.)  */
1912
1913enumlist:
1914	  enumerator
1915	| enumlist ',' enumerator
1916		{ if ($1 == error_mark_node)
1917		    $$ = $1;
1918		  else
1919		    $$ = chainon ($3, $1); }
1920	| error
1921		{ $$ = error_mark_node; }
1922	;
1923
1924
1925enumerator:
1926	  identifier
1927		{ $$ = build_enumerator ($1, NULL_TREE); }
1928	| identifier '=' expr_no_commas
1929		{ $$ = build_enumerator ($1, $3); }
1930	;
1931
1932typename:
1933	  declspecs_nosc
1934		{ pending_xref_error ();
1935		  $<ttype>$ = $1; }
1936	  absdcl
1937		{ $$ = build_tree_list ($<ttype>2, $3); }
1938	;
1939
1940absdcl:   /* an absolute declarator */
1941	/* empty */
1942		{ $$ = NULL_TREE; }
1943	| absdcl1
1944	;
1945
1946absdcl_maybe_attribute:   /* absdcl maybe_attribute, but not just attributes */
1947	/* empty */
1948		{ $$ = build_tree_list (build_tree_list (current_declspecs,
1949							 NULL_TREE),
1950					all_prefix_attributes); }
1951	| absdcl1
1952		{ $$ = build_tree_list (build_tree_list (current_declspecs,
1953							 $1),
1954					all_prefix_attributes); }
1955	| absdcl1_noea attributes
1956		{ $$ = build_tree_list (build_tree_list (current_declspecs,
1957							 $1),
1958					chainon ($2, all_prefix_attributes)); }
1959	;
1960
1961absdcl1:  /* a nonempty absolute declarator */
1962	  absdcl1_ea
1963	| absdcl1_noea
1964	;
1965
1966absdcl1_noea:
1967	  direct_absdcl1
1968	| '*' maybe_type_quals_attrs absdcl1_noea
1969		{ $$ = make_pointer_declarator ($2, $3); }
1970	;
1971
1972absdcl1_ea:
1973	  '*' maybe_type_quals_attrs
1974		{ $$ = make_pointer_declarator ($2, NULL_TREE); }
1975	| '*' maybe_type_quals_attrs absdcl1_ea
1976		{ $$ = make_pointer_declarator ($2, $3); }
1977	;
1978
1979direct_absdcl1:
1980	  '(' maybe_attribute absdcl1 ')'
1981		{ $$ = $2 ? tree_cons ($2, $3, NULL_TREE) : $3; }
1982	| direct_absdcl1 '(' parmlist
1983		{ $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1984	| direct_absdcl1 array_declarator
1985		{ $$ = set_array_declarator_type ($2, $1, 1); }
1986	| '(' parmlist
1987		{ $$ = build_nt (CALL_EXPR, NULL_TREE, $2, NULL_TREE); }
1988	| array_declarator
1989		{ $$ = set_array_declarator_type ($1, NULL_TREE, 1); }
1990	;
1991
1992/* The [...] part of a declarator for an array type.  */
1993
1994array_declarator:
1995	'[' maybe_type_quals_attrs expr ']'
1996		{ $$ = build_array_declarator ($3, $2, 0, 0); }
1997	| '[' maybe_type_quals_attrs ']'
1998		{ $$ = build_array_declarator (NULL_TREE, $2, 0, 0); }
1999	| '[' maybe_type_quals_attrs '*' ']'
2000		{ $$ = build_array_declarator (NULL_TREE, $2, 0, 1); }
2001	| '[' STATIC maybe_type_quals_attrs expr ']'
2002		{ $$ = build_array_declarator ($4, $3, 1, 0); }
2003	/* declspecs_nosc_nots is a synonym for type_quals_attrs.  */
2004	| '[' declspecs_nosc_nots STATIC expr ']'
2005		{ $$ = build_array_declarator ($4, $2, 1, 0); }
2006	;
2007
2008/* A nonempty series of declarations and statements (possibly followed by
2009   some labels) that can form the body of a compound statement.
2010   NOTE: we don't allow labels on declarations; this might seem like a
2011   natural extension, but there would be a conflict between attributes
2012   on the label and prefix attributes on the declaration.  */
2013
2014stmts_and_decls:
2015	  lineno_stmt_decl_or_labels_ending_stmt
2016	| lineno_stmt_decl_or_labels_ending_decl
2017	| lineno_stmt_decl_or_labels_ending_label
2018		{
2019		  pedwarn ("deprecated use of label at end of compound statement");
2020		}
2021	| lineno_stmt_decl_or_labels_ending_error
2022	;
2023
2024lineno_stmt_decl_or_labels_ending_stmt:
2025	  lineno_stmt
2026	| lineno_stmt_decl_or_labels_ending_stmt lineno_stmt
2027	| lineno_stmt_decl_or_labels_ending_decl lineno_stmt
2028	| lineno_stmt_decl_or_labels_ending_label lineno_stmt
2029	| lineno_stmt_decl_or_labels_ending_error lineno_stmt
2030	;
2031
2032lineno_stmt_decl_or_labels_ending_decl:
2033	  lineno_decl
2034	| lineno_stmt_decl_or_labels_ending_stmt lineno_decl
2035		{ if (pedantic && !flag_isoc99)
2036		    pedwarn ("ISO C89 forbids mixed declarations and code"); }
2037	| lineno_stmt_decl_or_labels_ending_decl lineno_decl
2038	| lineno_stmt_decl_or_labels_ending_error lineno_decl
2039	;
2040
2041lineno_stmt_decl_or_labels_ending_label:
2042	  lineno_label
2043	| lineno_stmt_decl_or_labels_ending_stmt lineno_label
2044	| lineno_stmt_decl_or_labels_ending_decl lineno_label
2045	| lineno_stmt_decl_or_labels_ending_label lineno_label
2046	| lineno_stmt_decl_or_labels_ending_error lineno_label
2047	;
2048
2049lineno_stmt_decl_or_labels_ending_error:
2050	errstmt
2051	| lineno_stmt_decl_or_labels errstmt
2052	;
2053
2054lineno_stmt_decl_or_labels:
2055	  lineno_stmt_decl_or_labels_ending_stmt
2056	| lineno_stmt_decl_or_labels_ending_decl
2057	| lineno_stmt_decl_or_labels_ending_label
2058	| lineno_stmt_decl_or_labels_ending_error
2059	;
2060
2061errstmt:  error ';'
2062	;
2063
2064pushlevel:  /* empty */
2065		{ pushlevel (0);
2066		  clear_last_expr ();
2067		  add_scope_stmt (/*begin_p=*/1, /*partial_p=*/0);
2068ifobjc
2069		  if (objc_method_context)
2070		    add_objc_decls ();
2071end ifobjc
2072		}
2073	;
2074
2075poplevel:  /* empty */
2076                { $$ = add_scope_stmt (/*begin_p=*/0, /*partial_p=*/0); }
2077        ;
2078
2079/* Start and end blocks created for the new scopes of C99.  */
2080c99_block_start: /* empty */
2081		{ if (flag_isoc99)
2082		    {
2083		      $$ = c_begin_compound_stmt ();
2084		      pushlevel (0);
2085		      clear_last_expr ();
2086		      add_scope_stmt (/*begin_p=*/1, /*partial_p=*/0);
2087ifobjc
2088		      if (objc_method_context)
2089			add_objc_decls ();
2090end ifobjc
2091		    }
2092		  else
2093		    $$ = NULL_TREE;
2094		}
2095	;
2096
2097/* Productions using c99_block_start and c99_block_end will need to do what's
2098   in compstmt: RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); $$ = $2; where
2099   $1 is the value of c99_block_start and $2 of c99_block_end.  */
2100c99_block_end: /* empty */
2101                { if (flag_isoc99)
2102		    {
2103		      tree scope_stmt = add_scope_stmt (/*begin_p=*/0, /*partial_p=*/0);
2104		      $$ = poplevel (kept_level_p (), 0, 0);
2105		      SCOPE_STMT_BLOCK (TREE_PURPOSE (scope_stmt))
2106			= SCOPE_STMT_BLOCK (TREE_VALUE (scope_stmt))
2107			= $$;
2108		    }
2109		  else
2110		    $$ = NULL_TREE; }
2111	;
2112
2113/* Read zero or more forward-declarations for labels
2114   that nested functions can jump to.  */
2115maybe_label_decls:
2116	  /* empty */
2117	| label_decls
2118		{ if (pedantic)
2119		    pedwarn ("ISO C forbids label declarations"); }
2120	;
2121
2122label_decls:
2123	  label_decl
2124	| label_decls label_decl
2125	;
2126
2127label_decl:
2128	  LABEL identifiers_or_typenames ';'
2129		{ tree link;
2130		  for (link = $2; link; link = TREE_CHAIN (link))
2131		    {
2132		      tree label = shadow_label (TREE_VALUE (link));
2133		      C_DECLARED_LABEL_FLAG (label) = 1;
2134		      add_decl_stmt (label);
2135		    }
2136		}
2137	;
2138
2139/* This is the body of a function definition.
2140   It causes syntax errors to ignore to the next openbrace.  */
2141compstmt_or_error:
2142	  compstmt
2143		{}
2144	| error compstmt
2145	;
2146
2147compstmt_start: '{' { compstmt_count++;
2148                      $$ = c_begin_compound_stmt (); }
2149        ;
2150
2151compstmt_nostart: '}'
2152		{ $$ = convert (void_type_node, integer_zero_node); }
2153	| pushlevel maybe_label_decls compstmt_contents_nonempty '}' poplevel
2154		{ $$ = poplevel (kept_level_p (), 1, 0);
2155		  SCOPE_STMT_BLOCK (TREE_PURPOSE ($5))
2156		    = SCOPE_STMT_BLOCK (TREE_VALUE ($5))
2157		    = $$; }
2158	;
2159
2160compstmt_contents_nonempty:
2161	  stmts_and_decls
2162	| error
2163	;
2164
2165compstmt_primary_start:
2166	'(' '{'
2167		{ if (current_function_decl == 0)
2168		    {
2169		      error ("braced-group within expression allowed only inside a function");
2170		      YYERROR;
2171		    }
2172		  /* We must force a BLOCK for this level
2173		     so that, if it is not expanded later,
2174		     there is a way to turn off the entire subtree of blocks
2175		     that are contained in it.  */
2176		  keep_next_level ();
2177		  push_label_level ();
2178		  compstmt_count++;
2179		  $$ = add_stmt (build_stmt (COMPOUND_STMT, last_tree));
2180		  last_expr_type = NULL_TREE;
2181		}
2182        ;
2183
2184compstmt: compstmt_start compstmt_nostart
2185		{ RECHAIN_STMTS ($1, COMPOUND_BODY ($1));
2186		  last_expr_type = NULL_TREE;
2187                  $$ = $1; }
2188	;
2189
2190/* Value is number of statements counted as of the closeparen.  */
2191simple_if:
2192	  if_prefix c99_block_lineno_labeled_stmt
2193                { c_finish_then (); }
2194/* Make sure c_expand_end_cond is run once
2195   for each call to c_expand_start_cond.
2196   Otherwise a crash is likely.  */
2197	| if_prefix error
2198	;
2199
2200if_prefix:
2201	  /* We must build the IF_STMT node before parsing its
2202	     condition so that STMT_LINENO refers to the line
2203	     containing the "if", and not the line containing
2204	     the close-parenthesis.
2205
2206	     c_begin_if_stmt returns the IF_STMT node, which
2207	     we later pass to c_expand_start_cond to fill
2208	     in the condition and other tidbits.  */
2209          IF
2210                { $<ttype>$ = c_begin_if_stmt (); }
2211            '(' expr ')'
2212		{ c_expand_start_cond (c_common_truthvalue_conversion ($4),
2213				       compstmt_count,$<ttype>2);
2214		  $<itype>$ = stmt_count;
2215		  if_stmt_file = $<filename>-2;
2216		  if_stmt_line = $<lineno>-1; }
2217        ;
2218
2219/* This is a subroutine of stmt.
2220   It is used twice, once for valid DO statements
2221   and once for catching errors in parsing the end test.  */
2222do_stmt_start:
2223	  DO
2224		{ stmt_count++;
2225		  compstmt_count++;
2226		  $<ttype>$
2227		    = add_stmt (build_stmt (DO_STMT, NULL_TREE,
2228					    NULL_TREE));
2229		  /* In the event that a parse error prevents
2230		     parsing the complete do-statement, set the
2231		     condition now.  Otherwise, we can get crashes at
2232		     RTL-generation time.  */
2233		  DO_COND ($<ttype>$) = error_mark_node; }
2234	  c99_block_lineno_labeled_stmt WHILE
2235		{ $$ = $<ttype>2;
2236		  RECHAIN_STMTS ($$, DO_BODY ($$)); }
2237	;
2238
2239/* The forced readahead in here is because we might be at the end of a
2240   line, and the line and file won't be bumped until yylex absorbs the
2241   first token on the next line.  */
2242save_filename:
2243		{ if (yychar == YYEMPTY)
2244		    yychar = YYLEX;
2245		  $$ = input_filename; }
2246	;
2247
2248save_lineno:
2249		{ if (yychar == YYEMPTY)
2250		    yychar = YYLEX;
2251		  $$ = lineno; }
2252	;
2253
2254lineno_labeled_stmt:
2255	  lineno_stmt
2256	| lineno_label lineno_labeled_stmt
2257	;
2258
2259/* Like lineno_labeled_stmt, but a block in C99.  */
2260c99_block_lineno_labeled_stmt:
2261	  c99_block_start lineno_labeled_stmt c99_block_end
2262		{ if (flag_isoc99)
2263		    RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); }
2264	;
2265
2266lineno_stmt:
2267	  save_filename save_lineno stmt
2268		{ if ($3)
2269		    {
2270		      STMT_LINENO ($3) = $2;
2271		      /* ??? We currently have no way of recording
2272			 the filename for a statement.  This probably
2273			 matters little in practice at the moment,
2274			 but I suspect that problems will occur when
2275			 doing inlining at the tree level.  */
2276		    }
2277		}
2278	;
2279
2280lineno_label:
2281	  save_filename save_lineno label
2282		{ if ($3)
2283		    {
2284		      STMT_LINENO ($3) = $2;
2285		    }
2286		}
2287	;
2288
2289select_or_iter_stmt:
2290	  simple_if ELSE
2291		{ c_expand_start_else ();
2292		  $<itype>1 = stmt_count; }
2293	  c99_block_lineno_labeled_stmt
2294                { c_finish_else ();
2295		  c_expand_end_cond ();
2296		  if (extra_warnings && stmt_count == $<itype>1)
2297		    warning ("empty body in an else-statement"); }
2298	| simple_if %prec IF
2299		{ c_expand_end_cond ();
2300		  /* This warning is here instead of in simple_if, because we
2301		     do not want a warning if an empty if is followed by an
2302		     else statement.  Increment stmt_count so we don't
2303		     give a second error if this is a nested `if'.  */
2304		  if (extra_warnings && stmt_count++ == $<itype>1)
2305		    warning_with_file_and_line (if_stmt_file, if_stmt_line,
2306						"empty body in an if-statement"); }
2307/* Make sure c_expand_end_cond is run once
2308   for each call to c_expand_start_cond.
2309   Otherwise a crash is likely.  */
2310	| simple_if ELSE error
2311		{ c_expand_end_cond (); }
2312       /* We must build the WHILE_STMT node before parsing its
2313	  condition so that STMT_LINENO refers to the line
2314	  containing the "while", and not the line containing
2315	  the close-parenthesis.
2316
2317	  c_begin_while_stmt returns the WHILE_STMT node, which
2318	  we later pass to c_finish_while_stmt_cond to fill
2319	  in the condition and other tidbits.  */
2320	| WHILE
2321                { stmt_count++;
2322		  $<ttype>$ = c_begin_while_stmt (); }
2323	  '(' expr ')'
2324                { $4 = c_common_truthvalue_conversion ($4);
2325		  c_finish_while_stmt_cond
2326		    (c_common_truthvalue_conversion ($4), $<ttype>2);
2327		  $<ttype>$ = add_stmt ($<ttype>2); }
2328	  c99_block_lineno_labeled_stmt
2329		{ RECHAIN_STMTS ($<ttype>6, WHILE_BODY ($<ttype>6)); }
2330	| do_stmt_start
2331	  '(' expr ')' ';'
2332                { DO_COND ($1) = c_common_truthvalue_conversion ($3); }
2333	| do_stmt_start error
2334 		{ }
2335	| FOR
2336		{ $<ttype>$ = build_stmt (FOR_STMT, NULL_TREE, NULL_TREE,
2337					  NULL_TREE, NULL_TREE);
2338		  add_stmt ($<ttype>$); }
2339	  '(' for_init_stmt
2340		{ stmt_count++;
2341		  RECHAIN_STMTS ($<ttype>2, FOR_INIT_STMT ($<ttype>2)); }
2342	  xexpr ';'
2343                { if ($6)
2344		    FOR_COND ($<ttype>2)
2345		      = c_common_truthvalue_conversion ($6); }
2346	  xexpr ')'
2347		{ FOR_EXPR ($<ttype>2) = $9; }
2348	  c99_block_lineno_labeled_stmt
2349                { RECHAIN_STMTS ($<ttype>2, FOR_BODY ($<ttype>2)); }
2350	| SWITCH '(' expr ')'
2351		{ stmt_count++;
2352		  $<ttype>$ = c_start_case ($3); }
2353	  c99_block_lineno_labeled_stmt
2354                { c_finish_case (); }
2355	;
2356
2357for_init_stmt:
2358	  xexpr ';'
2359		{ add_stmt (build_stmt (EXPR_STMT, $1)); }
2360	| decl
2361		{ check_for_loop_decls (); }
2362	;
2363
2364/* Parse a single real statement, not including any labels.  */
2365stmt:
2366	  compstmt
2367		{ stmt_count++; $$ = $1; }
2368	| expr ';'
2369		{ stmt_count++;
2370		  $$ = c_expand_expr_stmt ($1); }
2371	| c99_block_start select_or_iter_stmt c99_block_end
2372		{ if (flag_isoc99)
2373		    RECHAIN_STMTS ($1, COMPOUND_BODY ($1));
2374		  $$ = NULL_TREE; }
2375	| BREAK ';'
2376	        { stmt_count++;
2377		  $$ = add_stmt (build_break_stmt ()); }
2378	| CONTINUE ';'
2379                { stmt_count++;
2380		  $$ = add_stmt (build_continue_stmt ()); }
2381	| RETURN ';'
2382                { stmt_count++;
2383		  $$ = c_expand_return (NULL_TREE); }
2384	| RETURN expr ';'
2385                { stmt_count++;
2386		  $$ = c_expand_return ($2); }
2387	| ASM_KEYWORD maybe_type_qual '(' expr ')' ';'
2388		{ stmt_count++;
2389		  $$ = simple_asm_stmt ($4); }
2390	/* This is the case with just output operands.  */
2391	| ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ')' ';'
2392		{ stmt_count++;
2393		  $$ = build_asm_stmt ($2, $4, $6, NULL_TREE, NULL_TREE); }
2394	/* This is the case with input operands as well.  */
2395	| ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':'
2396	  asm_operands ')' ';'
2397		{ stmt_count++;
2398		  $$ = build_asm_stmt ($2, $4, $6, $8, NULL_TREE); }
2399	/* This is the case with clobbered registers as well.  */
2400	| ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':'
2401  	  asm_operands ':' asm_clobbers ')' ';'
2402		{ stmt_count++;
2403		  $$ = build_asm_stmt ($2, $4, $6, $8, $10); }
2404	| GOTO identifier ';'
2405		{ tree decl;
2406		  stmt_count++;
2407		  decl = lookup_label ($2);
2408		  if (decl != 0)
2409		    {
2410		      TREE_USED (decl) = 1;
2411		      $$ = add_stmt (build_stmt (GOTO_STMT, decl));
2412		    }
2413		  else
2414		    $$ = NULL_TREE;
2415		}
2416	| GOTO '*' expr ';'
2417		{ if (pedantic)
2418		    pedwarn ("ISO C forbids `goto *expr;'");
2419		  stmt_count++;
2420		  $3 = convert (ptr_type_node, $3);
2421		  $$ = add_stmt (build_stmt (GOTO_STMT, $3)); }
2422	| ';'
2423		{ $$ = NULL_TREE; }
2424	;
2425
2426/* Any kind of label, including jump labels and case labels.
2427   ANSI C accepts labels only before statements, but we allow them
2428   also at the end of a compound statement.  */
2429
2430label:	  CASE expr_no_commas ':'
2431                { stmt_count++;
2432		  $$ = do_case ($2, NULL_TREE); }
2433	| CASE expr_no_commas ELLIPSIS expr_no_commas ':'
2434                { stmt_count++;
2435		  $$ = do_case ($2, $4); }
2436	| DEFAULT ':'
2437                { stmt_count++;
2438		  $$ = do_case (NULL_TREE, NULL_TREE); }
2439	| identifier save_filename save_lineno ':' maybe_attribute
2440		{ tree label = define_label ($2, $3, $1);
2441		  stmt_count++;
2442		  if (label)
2443		    {
2444		      decl_attributes (&label, $5, 0);
2445		      $$ = add_stmt (build_stmt (LABEL_STMT, label));
2446		    }
2447		  else
2448		    $$ = NULL_TREE;
2449		}
2450	;
2451
2452/* Either a type-qualifier or nothing.  First thing in an `asm' statement.  */
2453
2454maybe_type_qual:
2455	/* empty */
2456		{ emit_line_note (input_filename, lineno);
2457		  $$ = NULL_TREE; }
2458	| TYPE_QUAL
2459		{ emit_line_note (input_filename, lineno); }
2460	;
2461
2462xexpr:
2463	/* empty */
2464		{ $$ = NULL_TREE; }
2465	| expr
2466	;
2467
2468/* These are the operands other than the first string and colon
2469   in  asm ("addextend %2,%1": "=dm" (x), "0" (y), "g" (*x))  */
2470asm_operands: /* empty */
2471		{ $$ = NULL_TREE; }
2472	| nonnull_asm_operands
2473	;
2474
2475nonnull_asm_operands:
2476	  asm_operand
2477	| nonnull_asm_operands ',' asm_operand
2478		{ $$ = chainon ($1, $3); }
2479	;
2480
2481asm_operand:
2482	  STRING '(' expr ')'
2483		{ $$ = build_tree_list (build_tree_list (NULL_TREE, $1), $3); }
2484	| '[' identifier ']' STRING '(' expr ')'
2485		{ $2 = build_string (IDENTIFIER_LENGTH ($2),
2486				     IDENTIFIER_POINTER ($2));
2487		  $$ = build_tree_list (build_tree_list ($2, $4), $6); }
2488	;
2489
2490asm_clobbers:
2491	  STRING
2492		{ $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
2493	| asm_clobbers ',' STRING
2494		{ $$ = tree_cons (NULL_TREE, $3, $1); }
2495	;
2496
2497/* This is what appears inside the parens in a function declarator.
2498   Its value is a list of ..._TYPE nodes.  Attributes must appear here
2499   to avoid a conflict with their appearance after an open parenthesis
2500   in an abstract declarator, as in
2501   "void bar (int (__attribute__((__mode__(SI))) int foo));".  */
2502parmlist:
2503	  maybe_attribute
2504		{ pushlevel (0);
2505		  clear_parm_order ();
2506		  declare_parm_level (0); }
2507	  parmlist_1
2508		{ $$ = $3;
2509		  parmlist_tags_warning ();
2510		  poplevel (0, 0, 0); }
2511	;
2512
2513parmlist_1:
2514	  parmlist_2 ')'
2515	| parms ';'
2516		{ tree parm;
2517		  if (pedantic)
2518		    pedwarn ("ISO C forbids forward parameter declarations");
2519		  /* Mark the forward decls as such.  */
2520		  for (parm = getdecls (); parm; parm = TREE_CHAIN (parm))
2521		    TREE_ASM_WRITTEN (parm) = 1;
2522		  clear_parm_order (); }
2523	  maybe_attribute
2524		{ /* Dummy action so attributes are in known place
2525		     on parser stack.  */ }
2526	  parmlist_1
2527		{ $$ = $6; }
2528	| error ')'
2529		{ $$ = tree_cons (NULL_TREE, NULL_TREE, NULL_TREE); }
2530	;
2531
2532/* This is what appears inside the parens in a function declarator.
2533   Is value is represented in the format that grokdeclarator expects.  */
2534parmlist_2:  /* empty */
2535		{ $$ = get_parm_info (0); }
2536	| ELLIPSIS
2537		{ $$ = get_parm_info (0);
2538		  /* Gcc used to allow this as an extension.  However, it does
2539		     not work for all targets, and thus has been disabled.
2540		     Also, since func (...) and func () are indistinguishable,
2541		     it caused problems with the code in expand_builtin which
2542		     tries to verify that BUILT_IN_NEXT_ARG is being used
2543		     correctly.  */
2544		  error ("ISO C requires a named argument before `...'");
2545		}
2546	| parms
2547		{ $$ = get_parm_info (1);
2548		  parsing_iso_function_signature = true;
2549		}
2550	| parms ',' ELLIPSIS
2551		{ $$ = get_parm_info (0); }
2552	;
2553
2554parms:
2555	firstparm
2556		{ push_parm_decl ($1); }
2557	| parms ',' parm
2558		{ push_parm_decl ($3); }
2559	;
2560
2561/* A single parameter declaration or parameter type name,
2562   as found in a parmlist.  */
2563parm:
2564	  declspecs_ts setspecs parm_declarator maybe_attribute
2565		{ $$ = build_tree_list (build_tree_list (current_declspecs,
2566							 $3),
2567					chainon ($4, all_prefix_attributes));
2568		  POP_DECLSPEC_STACK; }
2569	| declspecs_ts setspecs notype_declarator maybe_attribute
2570		{ $$ = build_tree_list (build_tree_list (current_declspecs,
2571							 $3),
2572					chainon ($4, all_prefix_attributes));
2573		  POP_DECLSPEC_STACK; }
2574	| declspecs_ts setspecs absdcl_maybe_attribute
2575		{ $$ = $3;
2576		  POP_DECLSPEC_STACK; }
2577	| declspecs_nots setspecs notype_declarator maybe_attribute
2578		{ $$ = build_tree_list (build_tree_list (current_declspecs,
2579							 $3),
2580					chainon ($4, all_prefix_attributes));
2581		  POP_DECLSPEC_STACK; }
2582
2583	| declspecs_nots setspecs absdcl_maybe_attribute
2584		{ $$ = $3;
2585		  POP_DECLSPEC_STACK; }
2586	;
2587
2588/* The first parm, which must suck attributes from off the top of the parser
2589   stack.  */
2590firstparm:
2591	  declspecs_ts_nosa setspecs_fp parm_declarator maybe_attribute
2592		{ $$ = build_tree_list (build_tree_list (current_declspecs,
2593							 $3),
2594					chainon ($4, all_prefix_attributes));
2595		  POP_DECLSPEC_STACK; }
2596	| declspecs_ts_nosa setspecs_fp notype_declarator maybe_attribute
2597		{ $$ = build_tree_list (build_tree_list (current_declspecs,
2598							 $3),
2599					chainon ($4, all_prefix_attributes));
2600		  POP_DECLSPEC_STACK; }
2601	| declspecs_ts_nosa setspecs_fp absdcl_maybe_attribute
2602		{ $$ = $3;
2603		  POP_DECLSPEC_STACK; }
2604	| declspecs_nots_nosa setspecs_fp notype_declarator maybe_attribute
2605		{ $$ = build_tree_list (build_tree_list (current_declspecs,
2606							 $3),
2607					chainon ($4, all_prefix_attributes));
2608		  POP_DECLSPEC_STACK; }
2609
2610	| declspecs_nots_nosa setspecs_fp absdcl_maybe_attribute
2611		{ $$ = $3;
2612		  POP_DECLSPEC_STACK; }
2613	;
2614
2615setspecs_fp:
2616	  setspecs
2617		{ prefix_attributes = chainon (prefix_attributes, $<ttype>-2);
2618		  all_prefix_attributes = prefix_attributes; }
2619	;
2620
2621/* This is used in a function definition
2622   where either a parmlist or an identifier list is ok.
2623   Its value is a list of ..._TYPE nodes or a list of identifiers.  */
2624parmlist_or_identifiers:
2625	  maybe_attribute
2626		{ pushlevel (0);
2627		  clear_parm_order ();
2628		  declare_parm_level (1); }
2629	  parmlist_or_identifiers_1
2630		{ $$ = $3;
2631		  parmlist_tags_warning ();
2632		  poplevel (0, 0, 0); }
2633	;
2634
2635parmlist_or_identifiers_1:
2636	  parmlist_1
2637	| identifiers ')'
2638		{ tree t;
2639		  for (t = $1; t; t = TREE_CHAIN (t))
2640		    if (TREE_VALUE (t) == NULL_TREE)
2641		      error ("`...' in old-style identifier list");
2642		  $$ = tree_cons (NULL_TREE, NULL_TREE, $1);
2643
2644		  /* Make sure we have a parmlist after attributes.  */
2645		  if ($<ttype>-1 != 0
2646		      && (TREE_CODE ($$) != TREE_LIST
2647			  || TREE_PURPOSE ($$) == 0
2648			  || TREE_CODE (TREE_PURPOSE ($$)) != PARM_DECL))
2649		    YYERROR1;
2650		}
2651	;
2652
2653/* A nonempty list of identifiers.  */
2654identifiers:
2655	IDENTIFIER
2656		{ $$ = build_tree_list (NULL_TREE, $1); }
2657	| identifiers ',' IDENTIFIER
2658		{ $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2659	;
2660
2661/* A nonempty list of identifiers, including typenames.  */
2662identifiers_or_typenames:
2663	identifier
2664		{ $$ = build_tree_list (NULL_TREE, $1); }
2665	| identifiers_or_typenames ',' identifier
2666		{ $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2667	;
2668
2669extension:
2670	EXTENSION
2671		{ $$ = SAVE_EXT_FLAGS();
2672		  pedantic = 0;
2673		  warn_pointer_arith = 0;
2674		  warn_traditional = 0;
2675		  flag_iso = 0; }
2676	;
2677
2678ifobjc
2679/* Objective-C productions.  */
2680
2681objcdef:
2682	  classdef
2683	| classdecl
2684	| aliasdecl
2685	| protocoldef
2686	| methoddef
2687	| END
2688		{
2689		  if (objc_implementation_context)
2690                    {
2691		      finish_class (objc_implementation_context);
2692		      objc_ivar_chain = NULL_TREE;
2693		      objc_implementation_context = NULL_TREE;
2694		    }
2695		  else
2696		    warning ("`@end' must appear in an implementation context");
2697		}
2698	;
2699
2700/* A nonempty list of identifiers.  */
2701identifier_list:
2702	identifier
2703		{ $$ = build_tree_list (NULL_TREE, $1); }
2704	| identifier_list ',' identifier
2705		{ $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2706	;
2707
2708classdecl:
2709	  CLASS identifier_list ';'
2710		{
2711		  objc_declare_class ($2);
2712		}
2713	;
2714
2715aliasdecl:
2716	  ALIAS identifier identifier ';'
2717		{
2718		  objc_declare_alias ($2, $3);
2719		}
2720	;
2721
2722classdef:
2723	  INTERFACE identifier protocolrefs '{'
2724		{
2725		  objc_interface_context = objc_ivar_context
2726		    = start_class (CLASS_INTERFACE_TYPE, $2, NULL_TREE, $3);
2727                  objc_public_flag = 0;
2728		}
2729	  ivar_decl_list '}'
2730		{
2731                  continue_class (objc_interface_context);
2732		}
2733	  methodprotolist
2734	  END
2735		{
2736		  finish_class (objc_interface_context);
2737		  objc_interface_context = NULL_TREE;
2738		}
2739
2740	| INTERFACE identifier protocolrefs
2741		{
2742		  objc_interface_context
2743		    = start_class (CLASS_INTERFACE_TYPE, $2, NULL_TREE, $3);
2744                  continue_class (objc_interface_context);
2745		}
2746	  methodprotolist
2747	  END
2748		{
2749		  finish_class (objc_interface_context);
2750		  objc_interface_context = NULL_TREE;
2751		}
2752
2753	| INTERFACE identifier ':' identifier protocolrefs '{'
2754		{
2755		  objc_interface_context = objc_ivar_context
2756		    = start_class (CLASS_INTERFACE_TYPE, $2, $4, $5);
2757                  objc_public_flag = 0;
2758		}
2759	  ivar_decl_list '}'
2760		{
2761                  continue_class (objc_interface_context);
2762		}
2763	  methodprotolist
2764	  END
2765		{
2766		  finish_class (objc_interface_context);
2767		  objc_interface_context = NULL_TREE;
2768		}
2769
2770	| INTERFACE identifier ':' identifier protocolrefs
2771		{
2772		  objc_interface_context
2773		    = start_class (CLASS_INTERFACE_TYPE, $2, $4, $5);
2774                  continue_class (objc_interface_context);
2775		}
2776	  methodprotolist
2777	  END
2778		{
2779		  finish_class (objc_interface_context);
2780		  objc_interface_context = NULL_TREE;
2781		}
2782
2783	| IMPLEMENTATION identifier '{'
2784		{
2785		  objc_implementation_context = objc_ivar_context
2786		    = start_class (CLASS_IMPLEMENTATION_TYPE, $2, NULL_TREE, NULL_TREE);
2787                  objc_public_flag = 0;
2788		}
2789	  ivar_decl_list '}'
2790		{
2791                  objc_ivar_chain
2792		    = continue_class (objc_implementation_context);
2793		}
2794
2795	| IMPLEMENTATION identifier
2796		{
2797		  objc_implementation_context
2798		    = start_class (CLASS_IMPLEMENTATION_TYPE, $2, NULL_TREE, NULL_TREE);
2799                  objc_ivar_chain
2800		    = continue_class (objc_implementation_context);
2801		}
2802
2803	| IMPLEMENTATION identifier ':' identifier '{'
2804		{
2805		  objc_implementation_context = objc_ivar_context
2806		    = start_class (CLASS_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2807                  objc_public_flag = 0;
2808		}
2809	  ivar_decl_list '}'
2810		{
2811                  objc_ivar_chain
2812		    = continue_class (objc_implementation_context);
2813		}
2814
2815	| IMPLEMENTATION identifier ':' identifier
2816		{
2817		  objc_implementation_context
2818		    = start_class (CLASS_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2819                  objc_ivar_chain
2820		    = continue_class (objc_implementation_context);
2821		}
2822
2823	| INTERFACE identifier '(' identifier ')' protocolrefs
2824		{
2825		  objc_interface_context
2826		    = start_class (CATEGORY_INTERFACE_TYPE, $2, $4, $6);
2827                  continue_class (objc_interface_context);
2828		}
2829	  methodprotolist
2830	  END
2831		{
2832		  finish_class (objc_interface_context);
2833		  objc_interface_context = NULL_TREE;
2834		}
2835
2836	| IMPLEMENTATION identifier '(' identifier ')'
2837		{
2838		  objc_implementation_context
2839		    = start_class (CATEGORY_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2840                  objc_ivar_chain
2841		    = continue_class (objc_implementation_context);
2842		}
2843	;
2844
2845protocoldef:
2846	  PROTOCOL identifier protocolrefs
2847		{
2848		  objc_pq_context = 1;
2849		  objc_interface_context
2850		    = start_protocol(PROTOCOL_INTERFACE_TYPE, $2, $3);
2851		}
2852	  methodprotolist END
2853		{
2854		  objc_pq_context = 0;
2855		  finish_protocol(objc_interface_context);
2856		  objc_interface_context = NULL_TREE;
2857		}
2858	/* The @protocol forward-declaration production introduces a
2859	   reduce/reduce conflict on ';', which should be resolved in
2860	   favor of the production 'identifier_list -> identifier'.  */
2861	| PROTOCOL identifier_list ';'
2862		{
2863		  objc_declare_protocols ($2);
2864		}
2865	;
2866
2867protocolrefs:
2868	  /* empty */
2869		{
2870		  $$ = NULL_TREE;
2871		}
2872	| non_empty_protocolrefs
2873	;
2874
2875non_empty_protocolrefs:
2876	  ARITHCOMPARE identifier_list ARITHCOMPARE
2877		{
2878		  if ($1 == LT_EXPR && $3 == GT_EXPR)
2879		    $$ = $2;
2880		  else
2881		    YYERROR1;
2882		}
2883	;
2884
2885ivar_decl_list:
2886          ivar_decl_list visibility_spec ivar_decls
2887        | ivar_decls
2888        ;
2889
2890visibility_spec:
2891	  PRIVATE { objc_public_flag = 2; }
2892	| PROTECTED { objc_public_flag = 0; }
2893	| PUBLIC { objc_public_flag = 1; }
2894	;
2895
2896ivar_decls:
2897          /* empty */
2898		{
2899                  $$ = NULL_TREE;
2900                }
2901	| ivar_decls ivar_decl ';'
2902	| ivar_decls ';'
2903		{
2904                  if (pedantic)
2905		    pedwarn ("extra semicolon in struct or union specified");
2906                }
2907	;
2908
2909
2910/* There is a shift-reduce conflict here, because `components' may
2911   start with a `typename'.  It happens that shifting (the default resolution)
2912   does the right thing, because it treats the `typename' as part of
2913   a `typed_typespecs'.
2914
2915   It is possible that this same technique would allow the distinction
2916   between `notype_initdecls' and `initdecls' to be eliminated.
2917   But I am being cautious and not trying it.  */
2918
2919ivar_decl:
2920	declspecs_nosc_ts setspecs ivars
2921	        { $$ = $3;
2922		  POP_DECLSPEC_STACK; }
2923	| declspecs_nosc_nots setspecs ivars
2924		{ $$ = $3;
2925		  POP_DECLSPEC_STACK; }
2926	| error
2927		{ $$ = NULL_TREE; }
2928	;
2929
2930ivars:
2931	  /* empty */
2932		{ $$ = NULL_TREE; }
2933	| ivar_declarator
2934	| ivars ',' maybe_resetattrs ivar_declarator
2935	;
2936
2937ivar_declarator:
2938	  declarator
2939		{
2940		  $$ = add_instance_variable (objc_ivar_context,
2941					      objc_public_flag,
2942					      $1, current_declspecs,
2943					      NULL_TREE);
2944                }
2945	| declarator ':' expr_no_commas
2946		{
2947		  $$ = add_instance_variable (objc_ivar_context,
2948					      objc_public_flag,
2949					      $1, current_declspecs, $3);
2950                }
2951	| ':' expr_no_commas
2952		{
2953		  $$ = add_instance_variable (objc_ivar_context,
2954					      objc_public_flag,
2955					      NULL_TREE,
2956					      current_declspecs, $2);
2957                }
2958	;
2959
2960methodtype:
2961	  '+'
2962		{ objc_inherit_code = CLASS_METHOD_DECL; }
2963	| '-'
2964		{ objc_inherit_code = INSTANCE_METHOD_DECL; }
2965	;
2966
2967methoddef:
2968	  methodtype
2969		{
2970		  objc_pq_context = 1;
2971		  if (!objc_implementation_context)
2972		    fatal_error ("method definition not in class context");
2973		}
2974	  methoddecl
2975		{
2976		  objc_pq_context = 0;
2977		  if (objc_inherit_code == CLASS_METHOD_DECL)
2978		    add_class_method (objc_implementation_context, $3);
2979		  else
2980		    add_instance_method (objc_implementation_context, $3);
2981		  start_method_def ($3);
2982		}
2983	  optarglist
2984		{
2985		  continue_method_def ();
2986		}
2987	  compstmt_or_error
2988		{
2989		  finish_method_def ();
2990		}
2991	;
2992
2993/* the reason for the strange actions in this rule
2994 is so that notype_initdecls when reached via datadef
2995 can find a valid list of type and sc specs in $0. */
2996
2997methodprotolist:
2998	  /* empty  */
2999	| {$<ttype>$ = NULL_TREE; } methodprotolist2
3000	;
3001
3002methodprotolist2:		 /* eliminates a shift/reduce conflict */
3003	   methodproto
3004	|  datadef
3005	| methodprotolist2 methodproto
3006	| methodprotolist2 {$<ttype>$ = NULL_TREE; } datadef
3007	;
3008
3009semi_or_error:
3010	  ';'
3011	| error
3012	;
3013
3014methodproto:
3015	  methodtype
3016		{
3017		  /* Remember protocol qualifiers in prototypes.  */
3018		  objc_pq_context = 1;
3019		}
3020	  methoddecl
3021		{
3022		  /* Forget protocol qualifiers here.  */
3023		  objc_pq_context = 0;
3024		  if (objc_inherit_code == CLASS_METHOD_DECL)
3025		    add_class_method (objc_interface_context, $3);
3026		  else
3027		    add_instance_method (objc_interface_context, $3);
3028		}
3029	  semi_or_error
3030	;
3031
3032methoddecl:
3033	  '(' typename ')' unaryselector
3034		{
3035		  $$ = build_method_decl (objc_inherit_code, $2, $4, NULL_TREE);
3036		}
3037
3038	| unaryselector
3039		{
3040		  $$ = build_method_decl (objc_inherit_code, NULL_TREE, $1, NULL_TREE);
3041		}
3042
3043	| '(' typename ')' keywordselector optparmlist
3044		{
3045		  $$ = build_method_decl (objc_inherit_code, $2, $4, $5);
3046		}
3047
3048	| keywordselector optparmlist
3049		{
3050		  $$ = build_method_decl (objc_inherit_code, NULL_TREE, $1, $2);
3051		}
3052	;
3053
3054/* "optarglist" assumes that start_method_def has already been called...
3055   if it is not, the "xdecls" will not be placed in the proper scope */
3056
3057optarglist:
3058	  /* empty */
3059	| ';' myxdecls
3060	;
3061
3062/* to get around the following situation: "int foo (int a) int b; {}" that
3063   is synthesized when parsing "- a:a b:b; id c; id d; { ... }" */
3064
3065myxdecls:
3066	  /* empty */
3067	| mydecls
3068	;
3069
3070mydecls:
3071	mydecl
3072	| errstmt
3073	| mydecls mydecl
3074	| mydecl errstmt
3075	;
3076
3077mydecl:
3078	declspecs_ts setspecs myparms ';'
3079		{ POP_DECLSPEC_STACK; }
3080	| declspecs_ts ';'
3081		{ shadow_tag ($1); }
3082	| declspecs_nots ';'
3083		{ pedwarn ("empty declaration"); }
3084	;
3085
3086myparms:
3087	myparm
3088		{ push_parm_decl ($1); }
3089	| myparms ',' myparm
3090		{ push_parm_decl ($3); }
3091	;
3092
3093/* A single parameter declaration or parameter type name,
3094   as found in a parmlist. DOES NOT ALLOW AN INITIALIZER OR ASMSPEC */
3095
3096myparm:
3097	  parm_declarator maybe_attribute
3098		{ $$ = build_tree_list (build_tree_list (current_declspecs,
3099							 $1),
3100					chainon ($2, all_prefix_attributes)); }
3101	| notype_declarator maybe_attribute
3102		{ $$ = build_tree_list (build_tree_list (current_declspecs,
3103							 $1),
3104					chainon ($2, all_prefix_attributes)); }
3105	| absdcl_maybe_attribute
3106		{ $$ = $1; }
3107	;
3108
3109optparmlist:
3110	  /* empty */
3111		{
3112	    	  $$ = NULL_TREE;
3113		}
3114	| ',' ELLIPSIS
3115		{
3116		  /* oh what a kludge! */
3117		  $$ = objc_ellipsis_node;
3118		}
3119	| ','
3120		{
3121		  pushlevel (0);
3122		}
3123	  parmlist_2
3124		{
3125	  	  /* returns a tree list node generated by get_parm_info */
3126		  $$ = $3;
3127		  poplevel (0, 0, 0);
3128		}
3129	;
3130
3131unaryselector:
3132	  selector
3133	;
3134
3135keywordselector:
3136	  keyworddecl
3137
3138	| keywordselector keyworddecl
3139		{
3140		  $$ = chainon ($1, $2);
3141		}
3142	;
3143
3144selector:
3145	  IDENTIFIER
3146	| TYPENAME
3147	| CLASSNAME
3148	| OBJECTNAME
3149	| reservedwords
3150	;
3151
3152reservedwords:
3153	  ENUM | STRUCT	| UNION	| IF | ELSE | WHILE | DO | FOR
3154	| SWITCH | CASE | DEFAULT | BREAK | CONTINUE | RETURN
3155	| GOTO | ASM_KEYWORD | SIZEOF | TYPEOF | ALIGNOF
3156	| TYPESPEC | TYPE_QUAL
3157	;
3158
3159keyworddecl:
3160	  selector ':' '(' typename ')' identifier
3161		{
3162		  $$ = build_keyword_decl ($1, $4, $6);
3163		}
3164
3165	| selector ':' identifier
3166		{
3167		  $$ = build_keyword_decl ($1, NULL_TREE, $3);
3168		}
3169
3170	| ':' '(' typename ')' identifier
3171		{
3172		  $$ = build_keyword_decl (NULL_TREE, $3, $5);
3173		}
3174
3175	| ':' identifier
3176		{
3177		  $$ = build_keyword_decl (NULL_TREE, NULL_TREE, $2);
3178		}
3179	;
3180
3181messageargs:
3182	  selector
3183        | keywordarglist
3184	;
3185
3186keywordarglist:
3187	  keywordarg
3188	| keywordarglist keywordarg
3189		{
3190		  $$ = chainon ($1, $2);
3191		}
3192	;
3193
3194
3195keywordexpr:
3196	  nonnull_exprlist
3197		{
3198		  if (TREE_CHAIN ($1) == NULL_TREE)
3199		    /* just return the expr., remove a level of indirection */
3200		    $$ = TREE_VALUE ($1);
3201                  else
3202		    /* we have a comma expr., we will collapse later */
3203		    $$ = $1;
3204		}
3205	;
3206
3207keywordarg:
3208	  selector ':' keywordexpr
3209		{
3210		  $$ = build_tree_list ($1, $3);
3211		}
3212	| ':' keywordexpr
3213		{
3214		  $$ = build_tree_list (NULL_TREE, $2);
3215		}
3216	;
3217
3218receiver:
3219	  expr
3220	| CLASSNAME
3221		{
3222		  $$ = get_class_reference ($1);
3223		}
3224	;
3225
3226objcmessageexpr:
3227	  '[' receiver messageargs ']'
3228		{ $$ = build_tree_list ($2, $3); }
3229	;
3230
3231selectorarg:
3232	  selector
3233        | keywordnamelist
3234	;
3235
3236keywordnamelist:
3237	  keywordname
3238	| keywordnamelist keywordname
3239		{
3240		  $$ = chainon ($1, $2);
3241		}
3242	;
3243
3244keywordname:
3245	  selector ':'
3246		{
3247		  $$ = build_tree_list ($1, NULL_TREE);
3248		}
3249	| ':'
3250		{
3251		  $$ = build_tree_list (NULL_TREE, NULL_TREE);
3252		}
3253	;
3254
3255objcselectorexpr:
3256	  SELECTOR '(' selectorarg ')'
3257		{
3258		  $$ = $3;
3259		}
3260	;
3261
3262objcprotocolexpr:
3263	  PROTOCOL '(' identifier ')'
3264		{
3265		  $$ = $3;
3266		}
3267	;
3268
3269/* extension to support C-structures in the archiver */
3270
3271objcencodeexpr:
3272	  ENCODE '(' typename ')'
3273		{
3274		  $$ = groktypename ($3);
3275		}
3276	;
3277
3278end ifobjc
3279%%
3280
3281/* yylex() is a thin wrapper around c_lex(), all it does is translate
3282   cpplib.h's token codes into yacc's token codes.  */
3283
3284static enum cpp_ttype last_token;
3285
3286/* The reserved keyword table.  */
3287struct resword
3288{
3289  const char *word;
3290  ENUM_BITFIELD(rid) rid : 16;
3291  unsigned int disable   : 16;
3292};
3293
3294/* Disable mask.  Keywords are disabled if (reswords[i].disable & mask) is
3295   _true_.  */
3296#define D_C89	0x01	/* not in C89 */
3297#define D_EXT	0x02	/* GCC extension */
3298#define D_EXT89	0x04	/* GCC extension incorporated in C99 */
3299#define D_OBJC	0x08	/* Objective C only */
3300
3301static const struct resword reswords[] =
3302{
3303  { "_Bool",		RID_BOOL,	0 },
3304  { "_Complex",		RID_COMPLEX,	0 },
3305  { "__FUNCTION__",	RID_FUNCTION_NAME, 0 },
3306  { "__PRETTY_FUNCTION__", RID_PRETTY_FUNCTION_NAME, 0 },
3307  { "__alignof",	RID_ALIGNOF,	0 },
3308  { "__alignof__",	RID_ALIGNOF,	0 },
3309  { "__asm",		RID_ASM,	0 },
3310  { "__asm__",		RID_ASM,	0 },
3311  { "__attribute",	RID_ATTRIBUTE,	0 },
3312  { "__attribute__",	RID_ATTRIBUTE,	0 },
3313  { "__bounded",	RID_BOUNDED,	0 },
3314  { "__bounded__",	RID_BOUNDED,	0 },
3315  { "__builtin_choose_expr", RID_CHOOSE_EXPR, 0 },
3316  { "__builtin_types_compatible_p", RID_TYPES_COMPATIBLE_P, 0 },
3317  { "__builtin_va_arg",	RID_VA_ARG,	0 },
3318  { "__complex",	RID_COMPLEX,	0 },
3319  { "__complex__",	RID_COMPLEX,	0 },
3320  { "__const",		RID_CONST,	0 },
3321  { "__const__",	RID_CONST,	0 },
3322  { "__extension__",	RID_EXTENSION,	0 },
3323  { "__func__",		RID_C99_FUNCTION_NAME, 0 },
3324  { "__imag",		RID_IMAGPART,	0 },
3325  { "__imag__",		RID_IMAGPART,	0 },
3326  { "__inline",		RID_INLINE,	0 },
3327  { "__inline__",	RID_INLINE,	0 },
3328  { "__label__",	RID_LABEL,	0 },
3329  { "__ptrbase",	RID_PTRBASE,	0 },
3330  { "__ptrbase__",	RID_PTRBASE,	0 },
3331  { "__ptrextent",	RID_PTREXTENT,	0 },
3332  { "__ptrextent__",	RID_PTREXTENT,	0 },
3333  { "__ptrvalue",	RID_PTRVALUE,	0 },
3334  { "__ptrvalue__",	RID_PTRVALUE,	0 },
3335  { "__real",		RID_REALPART,	0 },
3336  { "__real__",		RID_REALPART,	0 },
3337  { "__restrict",	RID_RESTRICT,	0 },
3338  { "__restrict__",	RID_RESTRICT,	0 },
3339  { "__signed",		RID_SIGNED,	0 },
3340  { "__signed__",	RID_SIGNED,	0 },
3341  { "__thread",		RID_THREAD,	0 },
3342  { "__typeof",		RID_TYPEOF,	0 },
3343  { "__typeof__",	RID_TYPEOF,	0 },
3344  { "__unbounded",	RID_UNBOUNDED,	0 },
3345  { "__unbounded__",	RID_UNBOUNDED,	0 },
3346  { "__volatile",	RID_VOLATILE,	0 },
3347  { "__volatile__",	RID_VOLATILE,	0 },
3348  { "asm",		RID_ASM,	D_EXT },
3349  { "auto",		RID_AUTO,	0 },
3350  { "break",		RID_BREAK,	0 },
3351  { "case",		RID_CASE,	0 },
3352  { "char",		RID_CHAR,	0 },
3353  { "const",		RID_CONST,	0 },
3354  { "continue",		RID_CONTINUE,	0 },
3355  { "default",		RID_DEFAULT,	0 },
3356  { "do",		RID_DO,		0 },
3357  { "double",		RID_DOUBLE,	0 },
3358  { "else",		RID_ELSE,	0 },
3359  { "enum",		RID_ENUM,	0 },
3360  { "extern",		RID_EXTERN,	0 },
3361  { "float",		RID_FLOAT,	0 },
3362  { "for",		RID_FOR,	0 },
3363  { "goto",		RID_GOTO,	0 },
3364  { "if",		RID_IF,		0 },
3365  { "inline",		RID_INLINE,	D_EXT89 },
3366  { "int",		RID_INT,	0 },
3367  { "long",		RID_LONG,	0 },
3368  { "register",		RID_REGISTER,	0 },
3369  { "restrict",		RID_RESTRICT,	D_C89 },
3370  { "return",		RID_RETURN,	0 },
3371  { "short",		RID_SHORT,	0 },
3372  { "signed",		RID_SIGNED,	0 },
3373  { "sizeof",		RID_SIZEOF,	0 },
3374  { "static",		RID_STATIC,	0 },
3375  { "struct",		RID_STRUCT,	0 },
3376  { "switch",		RID_SWITCH,	0 },
3377  { "typedef",		RID_TYPEDEF,	0 },
3378  { "typeof",		RID_TYPEOF,	D_EXT },
3379  { "union",		RID_UNION,	0 },
3380  { "unsigned",		RID_UNSIGNED,	0 },
3381  { "void",		RID_VOID,	0 },
3382  { "volatile",		RID_VOLATILE,	0 },
3383  { "while",		RID_WHILE,	0 },
3384ifobjc
3385  { "id",		RID_ID,			D_OBJC },
3386
3387  /* These objc keywords are recognized only immediately after
3388     an '@'.  */
3389  { "class",		RID_AT_CLASS,		D_OBJC },
3390  { "compatibility_alias", RID_AT_ALIAS,	D_OBJC },
3391  { "defs",		RID_AT_DEFS,		D_OBJC },
3392  { "encode",		RID_AT_ENCODE,		D_OBJC },
3393  { "end",		RID_AT_END,		D_OBJC },
3394  { "implementation",	RID_AT_IMPLEMENTATION,	D_OBJC },
3395  { "interface",	RID_AT_INTERFACE,	D_OBJC },
3396  { "private",		RID_AT_PRIVATE,		D_OBJC },
3397  { "protected",	RID_AT_PROTECTED,	D_OBJC },
3398  { "protocol",		RID_AT_PROTOCOL,	D_OBJC },
3399  { "public",		RID_AT_PUBLIC,		D_OBJC },
3400  { "selector",		RID_AT_SELECTOR,	D_OBJC },
3401
3402  /* These are recognized only in protocol-qualifier context
3403     (see above) */
3404  { "bycopy",		RID_BYCOPY,		D_OBJC },
3405  { "byref",		RID_BYREF,		D_OBJC },
3406  { "in",		RID_IN,			D_OBJC },
3407  { "inout",		RID_INOUT,		D_OBJC },
3408  { "oneway",		RID_ONEWAY,		D_OBJC },
3409  { "out",		RID_OUT,		D_OBJC },
3410end ifobjc
3411};
3412#define N_reswords (sizeof reswords / sizeof (struct resword))
3413
3414/* Table mapping from RID_* constants to yacc token numbers.
3415   Unfortunately we have to have entries for all the keywords in all
3416   three languages.  */
3417static const short rid_to_yy[RID_MAX] =
3418{
3419  /* RID_STATIC */	STATIC,
3420  /* RID_UNSIGNED */	TYPESPEC,
3421  /* RID_LONG */	TYPESPEC,
3422  /* RID_CONST */	TYPE_QUAL,
3423  /* RID_EXTERN */	SCSPEC,
3424  /* RID_REGISTER */	SCSPEC,
3425  /* RID_TYPEDEF */	SCSPEC,
3426  /* RID_SHORT */	TYPESPEC,
3427  /* RID_INLINE */	SCSPEC,
3428  /* RID_VOLATILE */	TYPE_QUAL,
3429  /* RID_SIGNED */	TYPESPEC,
3430  /* RID_AUTO */	SCSPEC,
3431  /* RID_RESTRICT */	TYPE_QUAL,
3432
3433  /* C extensions */
3434  /* RID_BOUNDED */	TYPE_QUAL,
3435  /* RID_UNBOUNDED */	TYPE_QUAL,
3436  /* RID_COMPLEX */	TYPESPEC,
3437  /* RID_THREAD */	SCSPEC,
3438
3439  /* C++ */
3440  /* RID_FRIEND */	0,
3441  /* RID_VIRTUAL */	0,
3442  /* RID_EXPLICIT */	0,
3443  /* RID_EXPORT */	0,
3444  /* RID_MUTABLE */	0,
3445
3446  /* ObjC */
3447  /* RID_IN */		TYPE_QUAL,
3448  /* RID_OUT */		TYPE_QUAL,
3449  /* RID_INOUT */	TYPE_QUAL,
3450  /* RID_BYCOPY */	TYPE_QUAL,
3451  /* RID_BYREF */	TYPE_QUAL,
3452  /* RID_ONEWAY */	TYPE_QUAL,
3453
3454  /* C */
3455  /* RID_INT */		TYPESPEC,
3456  /* RID_CHAR */	TYPESPEC,
3457  /* RID_FLOAT */	TYPESPEC,
3458  /* RID_DOUBLE */	TYPESPEC,
3459  /* RID_VOID */	TYPESPEC,
3460  /* RID_ENUM */	ENUM,
3461  /* RID_STRUCT */	STRUCT,
3462  /* RID_UNION */	UNION,
3463  /* RID_IF */		IF,
3464  /* RID_ELSE */	ELSE,
3465  /* RID_WHILE */	WHILE,
3466  /* RID_DO */		DO,
3467  /* RID_FOR */		FOR,
3468  /* RID_SWITCH */	SWITCH,
3469  /* RID_CASE */	CASE,
3470  /* RID_DEFAULT */	DEFAULT,
3471  /* RID_BREAK */	BREAK,
3472  /* RID_CONTINUE */	CONTINUE,
3473  /* RID_RETURN */	RETURN,
3474  /* RID_GOTO */	GOTO,
3475  /* RID_SIZEOF */	SIZEOF,
3476
3477  /* C extensions */
3478  /* RID_ASM */		ASM_KEYWORD,
3479  /* RID_TYPEOF */	TYPEOF,
3480  /* RID_ALIGNOF */	ALIGNOF,
3481  /* RID_ATTRIBUTE */	ATTRIBUTE,
3482  /* RID_VA_ARG */	VA_ARG,
3483  /* RID_EXTENSION */	EXTENSION,
3484  /* RID_IMAGPART */	IMAGPART,
3485  /* RID_REALPART */	REALPART,
3486  /* RID_LABEL */	LABEL,
3487  /* RID_PTRBASE */	PTR_BASE,
3488  /* RID_PTREXTENT */	PTR_EXTENT,
3489  /* RID_PTRVALUE */	PTR_VALUE,
3490
3491  /* RID_CHOOSE_EXPR */			CHOOSE_EXPR,
3492  /* RID_TYPES_COMPATIBLE_P */		TYPES_COMPATIBLE_P,
3493
3494  /* RID_FUNCTION_NAME */		STRING_FUNC_NAME,
3495  /* RID_PRETTY_FUNCTION_NAME */	STRING_FUNC_NAME,
3496  /* RID_C99_FUNCTION_NAME */		VAR_FUNC_NAME,
3497
3498  /* C++ */
3499  /* RID_BOOL */	TYPESPEC,
3500  /* RID_WCHAR */	0,
3501  /* RID_CLASS */	0,
3502  /* RID_PUBLIC */	0,
3503  /* RID_PRIVATE */	0,
3504  /* RID_PROTECTED */	0,
3505  /* RID_TEMPLATE */	0,
3506  /* RID_NULL */	0,
3507  /* RID_CATCH */	0,
3508  /* RID_DELETE */	0,
3509  /* RID_FALSE */	0,
3510  /* RID_NAMESPACE */	0,
3511  /* RID_NEW */		0,
3512  /* RID_OPERATOR */	0,
3513  /* RID_THIS */	0,
3514  /* RID_THROW */	0,
3515  /* RID_TRUE */	0,
3516  /* RID_TRY */		0,
3517  /* RID_TYPENAME */	0,
3518  /* RID_TYPEID */	0,
3519  /* RID_USING */	0,
3520
3521  /* casts */
3522  /* RID_CONSTCAST */	0,
3523  /* RID_DYNCAST */	0,
3524  /* RID_REINTCAST */	0,
3525  /* RID_STATCAST */	0,
3526
3527  /* Objective C */
3528  /* RID_ID */			OBJECTNAME,
3529  /* RID_AT_ENCODE */		ENCODE,
3530  /* RID_AT_END */		END,
3531  /* RID_AT_CLASS */		CLASS,
3532  /* RID_AT_ALIAS */		ALIAS,
3533  /* RID_AT_DEFS */		DEFS,
3534  /* RID_AT_PRIVATE */		PRIVATE,
3535  /* RID_AT_PROTECTED */	PROTECTED,
3536  /* RID_AT_PUBLIC */		PUBLIC,
3537  /* RID_AT_PROTOCOL */		PROTOCOL,
3538  /* RID_AT_SELECTOR */		SELECTOR,
3539  /* RID_AT_INTERFACE */	INTERFACE,
3540  /* RID_AT_IMPLEMENTATION */	IMPLEMENTATION
3541};
3542
3543static void
3544init_reswords ()
3545{
3546  unsigned int i;
3547  tree id;
3548  int mask = (flag_isoc99 ? 0 : D_C89)
3549	      | (flag_no_asm ? (flag_isoc99 ? D_EXT : D_EXT|D_EXT89) : 0);
3550
3551  if (!flag_objc)
3552     mask |= D_OBJC;
3553
3554  /* It is not necessary to register ridpointers as a GC root, because
3555     all the trees it points to are permanently interned in the
3556     get_identifier hash anyway.  */
3557  ridpointers = (tree *) xcalloc ((int) RID_MAX, sizeof (tree));
3558  for (i = 0; i < N_reswords; i++)
3559    {
3560      /* If a keyword is disabled, do not enter it into the table
3561	 and so create a canonical spelling that isn't a keyword.  */
3562      if (reswords[i].disable & mask)
3563	continue;
3564
3565      id = get_identifier (reswords[i].word);
3566      C_RID_CODE (id) = reswords[i].rid;
3567      C_IS_RESERVED_WORD (id) = 1;
3568      ridpointers [(int) reswords[i].rid] = id;
3569    }
3570}
3571
3572#define NAME(type) cpp_type2name (type)
3573
3574static void
3575yyerror (msgid)
3576     const char *msgid;
3577{
3578  const char *string = _(msgid);
3579
3580  if (last_token == CPP_EOF)
3581    error ("%s at end of input", string);
3582  else if (last_token == CPP_CHAR || last_token == CPP_WCHAR)
3583    {
3584      unsigned int val = TREE_INT_CST_LOW (yylval.ttype);
3585      const char *const ell = (last_token == CPP_CHAR) ? "" : "L";
3586      if (val <= UCHAR_MAX && ISGRAPH (val))
3587	error ("%s before %s'%c'", string, ell, val);
3588      else
3589	error ("%s before %s'\\x%x'", string, ell, val);
3590    }
3591  else if (last_token == CPP_STRING
3592	   || last_token == CPP_WSTRING)
3593    error ("%s before string constant", string);
3594  else if (last_token == CPP_NUMBER)
3595    error ("%s before numeric constant", string);
3596  else if (last_token == CPP_NAME)
3597    error ("%s before \"%s\"", string, IDENTIFIER_POINTER (yylval.ttype));
3598  else
3599    error ("%s before '%s' token", string, NAME(last_token));
3600}
3601
3602static int
3603yylexname ()
3604{
3605  tree decl;
3606
3607ifobjc
3608  int objc_force_identifier = objc_need_raw_identifier;
3609  OBJC_NEED_RAW_IDENTIFIER (0);
3610end ifobjc
3611
3612  if (C_IS_RESERVED_WORD (yylval.ttype))
3613    {
3614      enum rid rid_code = C_RID_CODE (yylval.ttype);
3615
3616ifobjc
3617      /* Turn non-typedefed refs to "id" into plain identifiers; this
3618	 allows constructs like "void foo(id id);" to work.  */
3619      if (rid_code == RID_ID)
3620      {
3621	decl = lookup_name (yylval.ttype);
3622	if (decl == NULL_TREE || TREE_CODE (decl) != TYPE_DECL)
3623	  return IDENTIFIER;
3624      }
3625
3626      if (!OBJC_IS_AT_KEYWORD (rid_code)
3627	  && (!OBJC_IS_PQ_KEYWORD (rid_code) || objc_pq_context))
3628end ifobjc
3629      {
3630	int yycode = rid_to_yy[(int) rid_code];
3631	if (yycode == STRING_FUNC_NAME)
3632	  {
3633	    /* __FUNCTION__ and __PRETTY_FUNCTION__ get converted
3634	       to string constants.  */
3635	    const char *name = fname_string (rid_code);
3636
3637	    yylval.ttype = build_string (strlen (name) + 1, name);
3638	    C_ARTIFICIAL_STRING_P (yylval.ttype) = 1;
3639	    last_token = CPP_STRING;  /* so yyerror won't choke */
3640	    return STRING;
3641	  }
3642
3643	/* Return the canonical spelling for this keyword.  */
3644	yylval.ttype = ridpointers[(int) rid_code];
3645	return yycode;
3646      }
3647    }
3648
3649  decl = lookup_name (yylval.ttype);
3650  if (decl)
3651    {
3652      if (TREE_CODE (decl) == TYPE_DECL)
3653	return TYPENAME;
3654    }
3655ifobjc
3656  else
3657    {
3658      tree objc_interface_decl = is_class_name (yylval.ttype);
3659      /* ObjC class names are in the same namespace as variables and
3660	 typedefs, and hence are shadowed by local declarations.  */
3661      if (objc_interface_decl
3662	  && (global_bindings_p ()
3663	      || (!objc_force_identifier && !decl)))
3664	{
3665	  yylval.ttype = objc_interface_decl;
3666	  return CLASSNAME;
3667	}
3668    }
3669end ifobjc
3670
3671  return IDENTIFIER;
3672}
3673
3674/* Concatenate strings before returning them to the parser.  This isn't quite
3675   as good as having it done in the lexer, but it's better than nothing.  */
3676
3677static int
3678yylexstring ()
3679{
3680  enum cpp_ttype next_type;
3681  tree orig = yylval.ttype;
3682
3683  next_type = c_lex (&yylval.ttype);
3684  if (next_type == CPP_STRING
3685      || next_type == CPP_WSTRING
3686      || (next_type == CPP_NAME && yylexname () == STRING))
3687    {
3688      varray_type strings;
3689
3690ifc
3691      static int last_lineno = 0;
3692      static const char *last_input_filename = 0;
3693      if (warn_traditional && !in_system_header
3694	  && (lineno != last_lineno || !last_input_filename ||
3695	      strcmp (last_input_filename, input_filename)))
3696	{
3697	  warning ("traditional C rejects string concatenation");
3698	  last_lineno = lineno;
3699	  last_input_filename = input_filename;
3700	}
3701end ifc
3702
3703      VARRAY_TREE_INIT (strings, 32, "strings");
3704      VARRAY_PUSH_TREE (strings, orig);
3705
3706      do
3707	{
3708	  VARRAY_PUSH_TREE (strings, yylval.ttype);
3709	  next_type = c_lex (&yylval.ttype);
3710	}
3711      while (next_type == CPP_STRING
3712	     || next_type == CPP_WSTRING
3713	     || (next_type == CPP_NAME && yylexname () == STRING));
3714
3715      yylval.ttype = combine_strings (strings);
3716    }
3717  else
3718    yylval.ttype = orig;
3719
3720  /* We will have always read one token too many.  */
3721  _cpp_backup_tokens (parse_in, 1);
3722
3723  return STRING;
3724}
3725
3726static inline int
3727_yylex ()
3728{
3729 get_next:
3730  last_token = c_lex (&yylval.ttype);
3731  switch (last_token)
3732    {
3733    case CPP_EQ:					return '=';
3734    case CPP_NOT:					return '!';
3735    case CPP_GREATER:	yylval.code = GT_EXPR;		return ARITHCOMPARE;
3736    case CPP_LESS:	yylval.code = LT_EXPR;		return ARITHCOMPARE;
3737    case CPP_PLUS:	yylval.code = PLUS_EXPR;	return '+';
3738    case CPP_MINUS:	yylval.code = MINUS_EXPR;	return '-';
3739    case CPP_MULT:	yylval.code = MULT_EXPR;	return '*';
3740    case CPP_DIV:	yylval.code = TRUNC_DIV_EXPR;	return '/';
3741    case CPP_MOD:	yylval.code = TRUNC_MOD_EXPR;	return '%';
3742    case CPP_AND:	yylval.code = BIT_AND_EXPR;	return '&';
3743    case CPP_OR:	yylval.code = BIT_IOR_EXPR;	return '|';
3744    case CPP_XOR:	yylval.code = BIT_XOR_EXPR;	return '^';
3745    case CPP_RSHIFT:	yylval.code = RSHIFT_EXPR;	return RSHIFT;
3746    case CPP_LSHIFT:	yylval.code = LSHIFT_EXPR;	return LSHIFT;
3747
3748    case CPP_COMPL:					return '~';
3749    case CPP_AND_AND:					return ANDAND;
3750    case CPP_OR_OR:					return OROR;
3751    case CPP_QUERY:					return '?';
3752    case CPP_OPEN_PAREN:				return '(';
3753    case CPP_EQ_EQ:	yylval.code = EQ_EXPR;		return EQCOMPARE;
3754    case CPP_NOT_EQ:	yylval.code = NE_EXPR;		return EQCOMPARE;
3755    case CPP_GREATER_EQ:yylval.code = GE_EXPR;		return ARITHCOMPARE;
3756    case CPP_LESS_EQ:	yylval.code = LE_EXPR;		return ARITHCOMPARE;
3757
3758    case CPP_PLUS_EQ:	yylval.code = PLUS_EXPR;	return ASSIGN;
3759    case CPP_MINUS_EQ:	yylval.code = MINUS_EXPR;	return ASSIGN;
3760    case CPP_MULT_EQ:	yylval.code = MULT_EXPR;	return ASSIGN;
3761    case CPP_DIV_EQ:	yylval.code = TRUNC_DIV_EXPR;	return ASSIGN;
3762    case CPP_MOD_EQ:	yylval.code = TRUNC_MOD_EXPR;	return ASSIGN;
3763    case CPP_AND_EQ:	yylval.code = BIT_AND_EXPR;	return ASSIGN;
3764    case CPP_OR_EQ:	yylval.code = BIT_IOR_EXPR;	return ASSIGN;
3765    case CPP_XOR_EQ:	yylval.code = BIT_XOR_EXPR;	return ASSIGN;
3766    case CPP_RSHIFT_EQ:	yylval.code = RSHIFT_EXPR;	return ASSIGN;
3767    case CPP_LSHIFT_EQ:	yylval.code = LSHIFT_EXPR;	return ASSIGN;
3768
3769    case CPP_OPEN_SQUARE:				return '[';
3770    case CPP_CLOSE_SQUARE:				return ']';
3771    case CPP_OPEN_BRACE:				return '{';
3772    case CPP_CLOSE_BRACE:				return '}';
3773    case CPP_ELLIPSIS:					return ELLIPSIS;
3774
3775    case CPP_PLUS_PLUS:					return PLUSPLUS;
3776    case CPP_MINUS_MINUS:				return MINUSMINUS;
3777    case CPP_DEREF:					return POINTSAT;
3778    case CPP_DOT:					return '.';
3779
3780      /* The following tokens may affect the interpretation of any
3781	 identifiers following, if doing Objective-C.  */
3782    case CPP_COLON:		OBJC_NEED_RAW_IDENTIFIER (0);	return ':';
3783    case CPP_COMMA:		OBJC_NEED_RAW_IDENTIFIER (0);	return ',';
3784    case CPP_CLOSE_PAREN:	OBJC_NEED_RAW_IDENTIFIER (0);	return ')';
3785    case CPP_SEMICOLON:		OBJC_NEED_RAW_IDENTIFIER (0);	return ';';
3786
3787    case CPP_EOF:
3788      return 0;
3789
3790    case CPP_NAME:
3791      {
3792	int ret = yylexname ();
3793	if (ret == STRING)
3794	  return yylexstring ();
3795	else
3796	  return ret;
3797      }
3798
3799    case CPP_NUMBER:
3800    case CPP_CHAR:
3801    case CPP_WCHAR:
3802      return CONSTANT;
3803
3804    case CPP_STRING:
3805    case CPP_WSTRING:
3806      return yylexstring ();
3807
3808      /* This token is Objective-C specific.  It gives the next token
3809	 special significance.  */
3810    case CPP_ATSIGN:
3811ifobjc
3812      {
3813	tree after_at;
3814	enum cpp_ttype after_at_type;
3815
3816	after_at_type = c_lex (&after_at);
3817
3818	if (after_at_type == CPP_NAME
3819	    && C_IS_RESERVED_WORD (after_at)
3820	    && OBJC_IS_AT_KEYWORD (C_RID_CODE (after_at)))
3821	  {
3822	    yylval.ttype = after_at;
3823	    last_token = after_at_type;
3824	    return rid_to_yy [(int) C_RID_CODE (after_at)];
3825	  }
3826	_cpp_backup_tokens (parse_in, 1);
3827	return '@';
3828      }
3829end ifobjc
3830
3831      /* These tokens are C++ specific (and will not be generated
3832         in C mode, but let's be cautious).  */
3833    case CPP_SCOPE:
3834    case CPP_DEREF_STAR:
3835    case CPP_DOT_STAR:
3836    case CPP_MIN_EQ:
3837    case CPP_MAX_EQ:
3838    case CPP_MIN:
3839    case CPP_MAX:
3840      /* These tokens should not survive translation phase 4.  */
3841    case CPP_HASH:
3842    case CPP_PASTE:
3843      error ("syntax error at '%s' token", NAME(last_token));
3844      goto get_next;
3845
3846    default:
3847      abort ();
3848    }
3849  /* NOTREACHED */
3850}
3851
3852static int
3853yylex()
3854{
3855  int r;
3856  timevar_push (TV_LEX);
3857  r = _yylex();
3858  timevar_pop (TV_LEX);
3859  return r;
3860}
3861
3862/* Function used when yydebug is set, to print a token in more detail.  */
3863
3864static void
3865yyprint (file, yychar, yyl)
3866     FILE *file;
3867     int yychar;
3868     YYSTYPE yyl;
3869{
3870  tree t = yyl.ttype;
3871
3872  fprintf (file, " [%s]", NAME(last_token));
3873
3874  switch (yychar)
3875    {
3876    case IDENTIFIER:
3877    case TYPENAME:
3878    case OBJECTNAME:
3879    case TYPESPEC:
3880    case TYPE_QUAL:
3881    case SCSPEC:
3882    case STATIC:
3883      if (IDENTIFIER_POINTER (t))
3884	fprintf (file, " `%s'", IDENTIFIER_POINTER (t));
3885      break;
3886
3887    case CONSTANT:
3888      fprintf (file, " %s", GET_MODE_NAME (TYPE_MODE (TREE_TYPE (t))));
3889      if (TREE_CODE (t) == INTEGER_CST)
3890	fprintf (file,
3891#if HOST_BITS_PER_WIDE_INT == 64
3892#if HOST_BITS_PER_WIDE_INT == HOST_BITS_PER_INT
3893		 " 0x%x%016x",
3894#else
3895#if HOST_BITS_PER_WIDE_INT == HOST_BITS_PER_LONG
3896		 " 0x%lx%016lx",
3897#else
3898		 " 0x%llx%016llx",
3899#endif
3900#endif
3901#else
3902#if HOST_BITS_PER_WIDE_INT != HOST_BITS_PER_INT
3903		 " 0x%lx%08lx",
3904#else
3905		 " 0x%x%08x",
3906#endif
3907#endif
3908		 TREE_INT_CST_HIGH (t), TREE_INT_CST_LOW (t));
3909      break;
3910    }
3911}
3912
3913/* This is not the ideal place to put these, but we have to get them out
3914   of c-lex.c because cp/lex.c has its own versions.  */
3915
3916/* Free malloced parser stacks if necessary.  */
3917
3918void
3919free_parser_stacks ()
3920{
3921  if (malloced_yyss)
3922    {
3923      free (malloced_yyss);
3924      free (malloced_yyvs);
3925    }
3926}
3927
3928#include "gt-c-parse.h"
3929