OSDN Git Service

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