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