OSDN Git Service

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