OSDN Git Service

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