OSDN Git Service

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