OSDN Git Service

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