OSDN Git Service

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