OSDN Git Service

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