OSDN Git Service

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