OSDN Git Service

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