OSDN Git Service

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