OSDN Git Service

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