OSDN Git Service

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