OSDN Git Service

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