OSDN Git Service

* builtins.c (built_in_class_names, built_in_names): Constify a
[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 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 "c-lex.h"
45 #include "c-tree.h"
46 #include "flags.h"
47 #include "output.h"
48 #include "toplev.h"
49 #include "ggc.h"
50   
51 #ifdef MULTIBYTE_CHARS
52 #include <locale.h>
53 #endif
54
55 ifobjc
56 #include "objc-act.h"
57 end ifobjc
58
59 /* Since parsers are distinct for each language, put the language string
60    definition here.  */
61 ifobjc
62 const char * const language_string = "GNU Obj-C";
63 end ifobjc
64 ifc
65 const char * const language_string = "GNU C";
66 end ifc
67
68 /* Like YYERROR but do call yyerror.  */
69 #define YYERROR1 { yyerror ("syntax error"); YYERROR; }
70
71 /* Cause the `yydebug' variable to be defined.  */
72 #define YYDEBUG 1
73 %}
74
75 %start program
76
77 %union {long itype; tree ttype; enum tree_code code;
78         char *filename; int lineno; int ends_in_label; }
79
80 /* All identifiers that are not reserved words
81    and are not declared typedefs in the current block */
82 %token IDENTIFIER
83
84 /* All identifiers that are declared typedefs in the current block.
85    In some contexts, they are treated just like IDENTIFIER,
86    but they can also serve as typespecs in declarations.  */
87 %token TYPENAME
88
89 /* Reserved words that specify storage class.
90    yylval contains an IDENTIFIER_NODE which indicates which one.  */
91 %token SCSPEC
92
93 /* Reserved words that specify type.
94    yylval contains an IDENTIFIER_NODE which indicates which one.  */
95 %token TYPESPEC
96
97 /* Reserved words that qualify type: "const", "volatile", or "restrict".
98    yylval contains an IDENTIFIER_NODE which indicates which one.  */
99 %token TYPE_QUAL
100
101 /* Character or numeric constants.
102    yylval is the node for the constant.  */
103 %token CONSTANT
104
105 /* String constants in raw form.
106    yylval is a STRING_CST node.  */
107 %token STRING
108
109 /* "...", used for functions with variable arglists.  */
110 %token ELLIPSIS
111
112 /* the reserved words */
113 /* SCO include files test "ASM", so use something else. */
114 %token SIZEOF ENUM STRUCT UNION IF ELSE WHILE DO FOR SWITCH CASE DEFAULT
115 %token BREAK CONTINUE RETURN GOTO ASM_KEYWORD TYPEOF ALIGNOF
116 %token ATTRIBUTE EXTENSION LABEL
117 %token REALPART IMAGPART VA_ARG
118
119 /* Used in c-lex.c for parsing pragmas.  */
120 %token END_OF_LINE
121
122 /* Add precedence rules to solve dangling else s/r conflict */
123 %nonassoc IF
124 %nonassoc ELSE
125
126 /* Define the operator tokens and their precedences.
127    The value is an integer because, if used, it is the tree code
128    to use in the expression made from the operator.  */
129
130 %right <code> ASSIGN '='
131 %right <code> '?' ':'
132 %left <code> OROR
133 %left <code> ANDAND
134 %left <code> '|'
135 %left <code> '^'
136 %left <code> '&'
137 %left <code> EQCOMPARE
138 %left <code> ARITHCOMPARE
139 %left <code> LSHIFT RSHIFT
140 %left <code> '+' '-'
141 %left <code> '*' '/' '%'
142 %right <code> UNARY PLUSPLUS MINUSMINUS
143 %left HYPERUNARY
144 %left <code> POINTSAT '.' '(' '['
145
146 /* The Objective-C keywords.  These are included in C and in
147    Objective C, so that the token codes are the same in both.  */
148 %token INTERFACE IMPLEMENTATION END SELECTOR DEFS ENCODE
149 %token CLASSNAME PUBLIC PRIVATE PROTECTED PROTOCOL OBJECTNAME CLASS ALIAS
150
151 /* Objective-C string constants in raw form.
152    yylval is an OBJC_STRING_CST node.  */
153 %token OBJC_STRING
154
155
156 %type <code> unop
157
158 %type <ttype> identifier IDENTIFIER TYPENAME CONSTANT expr nonnull_exprlist exprlist
159 %type <ttype> expr_no_commas cast_expr unary_expr primary string STRING
160 %type <ttype> typed_declspecs reserved_declspecs
161 %type <ttype> typed_typespecs reserved_typespecquals
162 %type <ttype> declmods typespec typespecqual_reserved
163 %type <ttype> typed_declspecs_no_prefix_attr reserved_declspecs_no_prefix_attr
164 %type <ttype> declmods_no_prefix_attr
165 %type <ttype> SCSPEC TYPESPEC TYPE_QUAL nonempty_type_quals maybe_type_qual
166 %type <ttype> initdecls notype_initdecls initdcl notype_initdcl
167 %type <ttype> init maybeasm
168 %type <ttype> asm_operands nonnull_asm_operands asm_operand asm_clobbers
169 %type <ttype> maybe_attribute attributes attribute attribute_list attrib
170 %type <ttype> any_word extension
171
172 %type <ttype> compstmt compstmt_nostart compstmt_primary_start
173
174 %type <ttype> declarator
175 %type <ttype> notype_declarator after_type_declarator
176 %type <ttype> parm_declarator
177
178 %type <ttype> structsp component_decl_list component_decl_list2
179 %type <ttype> component_decl components component_declarator
180 %type <ttype> enumlist enumerator
181 %type <ttype> struct_head union_head enum_head
182 %type <ttype> typename absdcl absdcl1 type_quals
183 %type <ttype> xexpr parms parm identifiers
184
185 %type <ttype> parmlist parmlist_1 parmlist_2
186 %type <ttype> parmlist_or_identifiers parmlist_or_identifiers_1
187 %type <ttype> identifiers_or_typenames
188
189 %type <itype> setspecs
190
191 %type <ends_in_label> lineno_stmt_or_label lineno_stmt_or_labels stmt_or_label
192
193 %type <filename> save_filename
194 %type <lineno> save_lineno
195 \f
196 ifobjc
197 /* the Objective-C nonterminals */
198
199 %type <ttype> ivar_decl_list ivar_decls ivar_decl ivars ivar_declarator
200 %type <ttype> methoddecl unaryselector keywordselector selector
201 %type <ttype> keyworddecl receiver objcmessageexpr messageargs
202 %type <ttype> keywordexpr keywordarglist keywordarg
203 %type <ttype> myparms myparm optparmlist reservedwords objcselectorexpr
204 %type <ttype> selectorarg keywordnamelist keywordname objcencodeexpr
205 %type <ttype> objc_string non_empty_protocolrefs protocolrefs identifier_list objcprotocolexpr
206
207 %type <ttype> CLASSNAME OBJC_STRING OBJECTNAME
208 end ifobjc
209 \f
210 %{
211 /* Number of statements (loosely speaking) and compound statements 
212    seen so far.  */
213 static int stmt_count;
214 static int compstmt_count;
215   
216 /* Input file and line number of the end of the body of last simple_if;
217    used by the stmt-rule immediately after simple_if returns.  */
218 static char *if_stmt_file;
219 static int if_stmt_line;
220
221 /* List of types and structure classes of the current declaration.  */
222 static tree current_declspecs = NULL_TREE;
223 static tree prefix_attributes = NULL_TREE;
224
225 /* Stack of saved values of current_declspecs and prefix_attributes.  */
226 static tree declspec_stack;
227
228 /* 1 if we explained undeclared var errors.  */
229 static int undeclared_variable_notice;
230
231 /* For __extension__, save/restore the warning flags which are
232    controlled by __extension__.  */
233 #define SAVE_WARN_FLAGS()       \
234         build_int_2 (pedantic | (warn_pointer_arith << 1), 0)
235 #define RESTORE_WARN_FLAGS(tval) \
236   do {                                     \
237     int val = TREE_INT_CST_LOW (tval);     \
238     pedantic = val & 1;                    \
239     warn_pointer_arith = (val >> 1) & 1;   \
240   } while (0)
241
242 ifobjc
243 /* Objective-C specific information */
244
245 tree objc_interface_context;
246 tree objc_implementation_context;
247 tree objc_method_context;
248 tree objc_ivar_chain;
249 tree objc_ivar_context;
250 enum tree_code objc_inherit_code;
251 int objc_receiver_context;
252 int objc_public_flag;
253
254 end ifobjc
255
256 /* Tell yyparse how to print a token's value, if yydebug is set.  */
257
258 #define YYPRINT(FILE,YYCHAR,YYLVAL) yyprint(FILE,YYCHAR,YYLVAL)
259 extern void yyprint                     PARAMS ((FILE *, int, YYSTYPE));
260
261 /* Add GC roots for variables local to this file.  */
262 void
263 c_parse_init ()
264 {
265   ggc_add_tree_root (&declspec_stack, 1);
266   ggc_add_tree_root (&current_declspecs, 1);
267   ggc_add_tree_root (&prefix_attributes, 1);
268 }
269
270 %}
271 \f
272 %%
273 program: /* empty */
274                 { if (pedantic)
275                     pedwarn ("ANSI C forbids an empty source file");
276                   finish_file ();
277                 }
278         | extdefs
279                 {
280                   /* In case there were missing closebraces,
281                      get us back to the global binding level.  */
282                   while (! global_bindings_p ())
283                     poplevel (0, 0, 0);
284                   finish_file ();
285                 }
286         ;
287
288 /* the reason for the strange actions in this rule
289  is so that notype_initdecls when reached via datadef
290  can find a valid list of type and sc specs in $0. */
291
292 extdefs:
293         {$<ttype>$ = NULL_TREE; } extdef
294         | extdefs {$<ttype>$ = NULL_TREE; } extdef
295         ;
296
297 extdef:
298         fndef
299         | datadef
300 ifobjc
301         | objcdef
302 end ifobjc
303         | ASM_KEYWORD '(' expr ')' ';'
304                 { STRIP_NOPS ($3);
305                   if ((TREE_CODE ($3) == ADDR_EXPR
306                        && TREE_CODE (TREE_OPERAND ($3, 0)) == STRING_CST)
307                       || TREE_CODE ($3) == STRING_CST)
308                     assemble_asm ($3);
309                   else
310                     error ("argument of `asm' is not a constant string"); }
311         | extension extdef
312                 { RESTORE_WARN_FLAGS ($1); }
313         ;
314
315 datadef:
316           setspecs notype_initdecls ';'
317                 { if (pedantic)
318                     error ("ANSI C forbids data definition with no type or storage class");
319                   else if (!flag_traditional)
320                     warning ("data definition has no type or storage class"); 
321
322                   current_declspecs = TREE_VALUE (declspec_stack);
323                   prefix_attributes = TREE_PURPOSE (declspec_stack);
324                   declspec_stack = TREE_CHAIN (declspec_stack); }
325         | declmods setspecs notype_initdecls ';'
326                 { current_declspecs = TREE_VALUE (declspec_stack);
327                   prefix_attributes = TREE_PURPOSE (declspec_stack);
328                   declspec_stack = TREE_CHAIN (declspec_stack); }
329         | typed_declspecs setspecs initdecls ';'
330                 { current_declspecs = TREE_VALUE (declspec_stack);
331                   prefix_attributes = TREE_PURPOSE (declspec_stack);
332                   declspec_stack = TREE_CHAIN (declspec_stack); }
333         | declmods ';'
334           { pedwarn ("empty declaration"); }
335         | typed_declspecs ';'
336           { shadow_tag ($1); }
337         | error ';'
338         | error '}'
339         | ';'
340                 { if (pedantic)
341                     pedwarn ("ANSI C does not allow extra `;' outside of a function"); }
342         ;
343 \f
344 fndef:
345           typed_declspecs setspecs declarator
346                 { if (! start_function (current_declspecs, $3,
347                                         prefix_attributes, NULL_TREE))
348                     YYERROR1;
349                   reinit_parse_for_function (); }
350           old_style_parm_decls
351                 { store_parm_decls (); }
352           compstmt_or_error
353                 { finish_function (0); 
354                   current_declspecs = TREE_VALUE (declspec_stack);
355                   prefix_attributes = TREE_PURPOSE (declspec_stack);
356                   declspec_stack = TREE_CHAIN (declspec_stack); }
357         | typed_declspecs setspecs declarator error
358                 { current_declspecs = TREE_VALUE (declspec_stack);
359                   prefix_attributes = TREE_PURPOSE (declspec_stack);
360                   declspec_stack = TREE_CHAIN (declspec_stack); }
361         | declmods setspecs notype_declarator
362                 { if (! start_function (current_declspecs, $3,
363                                         prefix_attributes, NULL_TREE))
364                     YYERROR1;
365                   reinit_parse_for_function (); }
366           old_style_parm_decls
367                 { store_parm_decls (); }
368           compstmt_or_error
369                 { finish_function (0); 
370                   current_declspecs = TREE_VALUE (declspec_stack);
371                   prefix_attributes = TREE_PURPOSE (declspec_stack);
372                   declspec_stack = TREE_CHAIN (declspec_stack); }
373         | declmods setspecs notype_declarator error
374                 { current_declspecs = TREE_VALUE (declspec_stack);
375                   prefix_attributes = TREE_PURPOSE (declspec_stack);
376                   declspec_stack = TREE_CHAIN (declspec_stack); }
377         | setspecs notype_declarator
378                 { if (! start_function (NULL_TREE, $2,
379                                         prefix_attributes, NULL_TREE))
380                     YYERROR1;
381                   reinit_parse_for_function (); }
382           old_style_parm_decls
383                 { store_parm_decls (); }
384           compstmt_or_error
385                 { finish_function (0); 
386                   current_declspecs = TREE_VALUE (declspec_stack);
387                   prefix_attributes = TREE_PURPOSE (declspec_stack);
388                   declspec_stack = TREE_CHAIN (declspec_stack); }
389         | setspecs notype_declarator error
390                 { current_declspecs = TREE_VALUE (declspec_stack);
391                   prefix_attributes = TREE_PURPOSE (declspec_stack);
392                   declspec_stack = TREE_CHAIN (declspec_stack); }
393         ;
394
395 identifier:
396         IDENTIFIER
397         | TYPENAME
398 ifobjc
399         | OBJECTNAME
400         | CLASSNAME
401 end ifobjc
402         ;
403
404 unop:     '&'
405                 { $$ = ADDR_EXPR; }
406         | '-'
407                 { $$ = NEGATE_EXPR; }
408         | '+'
409                 { $$ = CONVERT_EXPR; }
410         | PLUSPLUS
411                 { $$ = PREINCREMENT_EXPR; }
412         | MINUSMINUS
413                 { $$ = PREDECREMENT_EXPR; }
414         | '~'
415                 { $$ = BIT_NOT_EXPR; }
416         | '!'
417                 { $$ = TRUTH_NOT_EXPR; }
418         ;
419
420 expr:   nonnull_exprlist
421                 { $$ = build_compound_expr ($1); }
422         ;
423
424 exprlist:
425           /* empty */
426                 { $$ = NULL_TREE; }
427         | nonnull_exprlist
428         ;
429
430 nonnull_exprlist:
431         expr_no_commas
432                 { $$ = build_tree_list (NULL_TREE, $1); }
433         | nonnull_exprlist ',' expr_no_commas
434                 { chainon ($1, build_tree_list (NULL_TREE, $3)); }
435         ;
436
437 unary_expr:
438         primary
439         | '*' cast_expr   %prec UNARY
440                 { $$ = build_indirect_ref ($2, "unary *"); }
441         /* __extension__ turns off -pedantic for following primary.  */
442         | extension cast_expr     %prec UNARY
443                 { $$ = $2;
444                   RESTORE_WARN_FLAGS ($1); }
445         | unop cast_expr  %prec UNARY
446                 { $$ = build_unary_op ($1, $2, 0);
447                   overflow_warning ($$); }
448         /* Refer to the address of a label as a pointer.  */
449         | ANDAND identifier
450                 { tree label = lookup_label ($2);
451                   if (pedantic)
452                     pedwarn ("ANSI C forbids `&&'");
453                   if (label == 0)
454                     $$ = null_pointer_node;
455                   else
456                     {
457                       TREE_USED (label) = 1;
458                       $$ = build1 (ADDR_EXPR, ptr_type_node, label);
459                       TREE_CONSTANT ($$) = 1;
460                     }
461                 }
462 /* This seems to be impossible on some machines, so let's turn it off.
463    You can use __builtin_next_arg to find the anonymous stack args.
464         | '&' ELLIPSIS
465                 { tree types = TYPE_ARG_TYPES (TREE_TYPE (current_function_decl));
466                   $$ = error_mark_node;
467                   if (TREE_VALUE (tree_last (types)) == void_type_node)
468                     error ("`&...' used in function with fixed number of arguments");
469                   else
470                     {
471                       if (pedantic)
472                         pedwarn ("ANSI C forbids `&...'");
473                       $$ = tree_last (DECL_ARGUMENTS (current_function_decl));
474                       $$ = build_unary_op (ADDR_EXPR, $$, 0);
475                     } }
476 */
477         | sizeof unary_expr  %prec UNARY
478                 { skip_evaluation--;
479                   if (TREE_CODE ($2) == COMPONENT_REF
480                       && DECL_C_BIT_FIELD (TREE_OPERAND ($2, 1)))
481                     error ("`sizeof' applied to a bit-field");
482                   $$ = c_sizeof (TREE_TYPE ($2)); }
483         | sizeof '(' typename ')'  %prec HYPERUNARY
484                 { skip_evaluation--;
485                   $$ = c_sizeof (groktypename ($3)); }
486         | alignof unary_expr  %prec UNARY
487                 { skip_evaluation--;
488                   $$ = c_alignof_expr ($2); }
489         | alignof '(' typename ')'  %prec HYPERUNARY
490                 { skip_evaluation--;
491                   $$ = c_alignof (groktypename ($3)); }
492         | REALPART cast_expr %prec UNARY
493                 { $$ = build_unary_op (REALPART_EXPR, $2, 0); }
494         | IMAGPART cast_expr %prec UNARY
495                 { $$ = build_unary_op (IMAGPART_EXPR, $2, 0); }
496         | VA_ARG '(' expr_no_commas ',' typename ')'
497                 { $$ = build_va_arg ($3, groktypename ($5)); }
498         ;
499
500 sizeof:
501         SIZEOF { skip_evaluation++; }
502         ;
503
504 alignof:
505         ALIGNOF { skip_evaluation++; }
506         ;
507
508 cast_expr:
509         unary_expr
510         | '(' typename ')' cast_expr  %prec UNARY
511                 { tree type = groktypename ($2);
512                   $$ = build_c_cast (type, $4); }
513         | '(' typename ')' '{' 
514                 { start_init (NULL_TREE, NULL, 0);
515                   $2 = groktypename ($2);
516                   really_start_incremental_init ($2); }
517           initlist_maybe_comma '}'  %prec UNARY
518                 { const char *name;
519                   tree result = pop_init_level (0);
520                   tree type = $2;
521                   finish_init ();
522
523                   if (pedantic && ! flag_isoc99)
524                     pedwarn ("ANSI C forbids constructor expressions");
525                   if (TYPE_NAME (type) != 0)
526                     {
527                       if (TREE_CODE (TYPE_NAME (type)) == IDENTIFIER_NODE)
528                         name = IDENTIFIER_POINTER (TYPE_NAME (type));
529                       else
530                         name = IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (type)));
531                     }
532                   else
533                     name = "";
534                   $$ = result;
535                   if (TREE_CODE (type) == ARRAY_TYPE && TYPE_SIZE (type) == 0)
536                     {
537                       int failure = complete_array_type (type, $$, 1);
538                       if (failure)
539                         abort ();
540                     }
541                 }
542         ;
543
544 expr_no_commas:
545           cast_expr
546         | expr_no_commas '+' expr_no_commas
547                 { $$ = parser_build_binary_op ($2, $1, $3); }
548         | expr_no_commas '-' expr_no_commas
549                 { $$ = parser_build_binary_op ($2, $1, $3); }
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 LSHIFT expr_no_commas
557                 { $$ = parser_build_binary_op ($2, $1, $3); }
558         | expr_no_commas RSHIFT expr_no_commas
559                 { $$ = parser_build_binary_op ($2, $1, $3); }
560         | expr_no_commas ARITHCOMPARE expr_no_commas
561                 { $$ = parser_build_binary_op ($2, $1, $3); }
562         | expr_no_commas EQCOMPARE expr_no_commas
563                 { $$ = parser_build_binary_op ($2, $1, $3); }
564         | expr_no_commas '&' expr_no_commas
565                 { $$ = parser_build_binary_op ($2, $1, $3); }
566         | expr_no_commas '|' 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 ANDAND
571                 { $1 = truthvalue_conversion (default_conversion ($1));
572                   skip_evaluation += $1 == boolean_false_node; }
573           expr_no_commas
574                 { skip_evaluation -= $1 == boolean_false_node;
575                   $$ = parser_build_binary_op (TRUTH_ANDIF_EXPR, $1, $4); }
576         | expr_no_commas OROR
577                 { $1 = truthvalue_conversion (default_conversion ($1));
578                   skip_evaluation += $1 == boolean_true_node; }
579           expr_no_commas
580                 { skip_evaluation -= $1 == boolean_true_node;
581                   $$ = parser_build_binary_op (TRUTH_ORIF_EXPR, $1, $4); }
582         | expr_no_commas '?'
583                 { $1 = truthvalue_conversion (default_conversion ($1));
584                   skip_evaluation += $1 == boolean_false_node; }
585           expr ':'
586                 { skip_evaluation += (($1 == boolean_true_node)
587                                       - ($1 == boolean_false_node)); }
588           expr_no_commas
589                 { skip_evaluation -= $1 == boolean_true_node;
590                   $$ = build_conditional_expr ($1, $4, $7); }
591         | expr_no_commas '?'
592                 { if (pedantic)
593                     pedwarn ("ANSI C forbids omitting the middle term of a ?: expression");
594                   /* Make sure first operand is calculated only once.  */
595                   $<ttype>2 = save_expr ($1);
596                   $1 = truthvalue_conversion (default_conversion ($<ttype>2));
597                   skip_evaluation += $1 == boolean_true_node; }
598           ':' expr_no_commas
599                 { skip_evaluation -= $1 == boolean_true_node;
600                   $$ = build_conditional_expr ($1, $<ttype>2, $5); }
601         | expr_no_commas '=' expr_no_commas
602                 { char class;
603                   $$ = build_modify_expr ($1, NOP_EXPR, $3);
604                   class = TREE_CODE_CLASS (TREE_CODE ($$));
605                   if (class == 'e' || class == '1'
606                       || class == '2' || class == '<')
607                     C_SET_EXP_ORIGINAL_CODE ($$, MODIFY_EXPR);
608                 }
609         | expr_no_commas ASSIGN expr_no_commas
610                 { char class;
611                   $$ = build_modify_expr ($1, $2, $3);
612                   /* This inhibits warnings in truthvalue_conversion.  */
613                   class = TREE_CODE_CLASS (TREE_CODE ($$));
614                   if (class == 'e' || class == '1'
615                       || class == '2' || class == '<')
616                     C_SET_EXP_ORIGINAL_CODE ($$, ERROR_MARK);
617                 }
618         ;
619
620 primary:
621         IDENTIFIER
622                 {
623                   $$ = lastiddecl;
624                   if (!$$ || $$ == error_mark_node)
625                     {
626                       if (yychar == YYEMPTY)
627                         yychar = YYLEX;
628                       if (yychar == '(')
629                         {
630 ifobjc
631                           tree decl;
632
633                           if (objc_receiver_context
634                               && ! (objc_receiver_context
635                                     && strcmp (IDENTIFIER_POINTER ($1), "super")))
636                             /* we have a message to super */
637                             $$ = get_super_receiver ();
638                           else if (objc_method_context
639                                    && (decl = is_ivar (objc_ivar_chain, $1)))
640                             {
641                               if (is_private (decl))
642                                 $$ = error_mark_node;
643                               else
644                                 $$ = build_ivar_reference ($1);
645                             }
646                           else
647 end ifobjc
648                             {
649                               /* Ordinary implicit function declaration.  */
650                               $$ = implicitly_declare ($1);
651                               assemble_external ($$);
652                               TREE_USED ($$) = 1;
653                             }
654                         }
655                       else if (current_function_decl == 0)
656                         {
657                           error ("`%s' undeclared here (not in a function)",
658                                  IDENTIFIER_POINTER ($1));
659                           $$ = error_mark_node;
660                         }
661                       else
662                         {
663 ifobjc
664                           tree decl;
665
666                           if (objc_receiver_context
667                               && ! strcmp (IDENTIFIER_POINTER ($1), "super"))
668                             /* we have a message to super */
669                             $$ = get_super_receiver ();
670                           else if (objc_method_context
671                                    && (decl = is_ivar (objc_ivar_chain, $1)))
672                             {
673                               if (is_private (decl))
674                                 $$ = error_mark_node;
675                               else
676                                 $$ = build_ivar_reference ($1);
677                             }
678                           else
679 end ifobjc
680                             {
681                               if (IDENTIFIER_GLOBAL_VALUE ($1) != error_mark_node
682                                   || IDENTIFIER_ERROR_LOCUS ($1) != current_function_decl)
683                                 {
684                                   error ("`%s' undeclared (first use in this function)",
685                                          IDENTIFIER_POINTER ($1));
686
687                                   if (! undeclared_variable_notice)
688                                     {
689                                       error ("(Each undeclared identifier is reported only once");
690                                       error ("for each function it appears in.)");
691                                       undeclared_variable_notice = 1;
692                                     }
693                                 }
694                               $$ = error_mark_node;
695                               /* Prevent repeated error messages.  */
696                               IDENTIFIER_GLOBAL_VALUE ($1) = error_mark_node;
697                               IDENTIFIER_ERROR_LOCUS ($1) = current_function_decl;
698                             }
699                         }
700                     }
701                   else if (TREE_TYPE ($$) == error_mark_node)
702                     $$ = error_mark_node;
703                   else if (C_DECL_ANTICIPATED ($$))
704                     {
705                       /* The first time we see a build-in function used,
706                          if it has not been declared.  */
707                       C_DECL_ANTICIPATED ($$) = 0;
708                       if (yychar == YYEMPTY)
709                         yychar = YYLEX;
710                       if (yychar == '(')
711                         {
712                           /* Omit the implicit declaration we
713                              would ordinarily do, so we don't lose
714                              the actual built in type.
715                              But print a diagnostic for the mismatch.  */
716 ifobjc
717                           if (objc_method_context
718                               && is_ivar (objc_ivar_chain, $1))
719                             error ("Instance variable `%s' implicitly declared as function",
720                                    IDENTIFIER_POINTER (DECL_NAME ($$)));
721                           else
722 end ifobjc
723                             if (TREE_CODE ($$) != FUNCTION_DECL)
724                               error ("`%s' implicitly declared as function",
725                                      IDENTIFIER_POINTER (DECL_NAME ($$)));
726                           else if ((TYPE_MODE (TREE_TYPE (TREE_TYPE ($$)))
727                                     != TYPE_MODE (integer_type_node))
728                                    && (TREE_TYPE (TREE_TYPE ($$))
729                                        != void_type_node))
730                             pedwarn ("type mismatch in implicit declaration for built-in function `%s'",
731                                      IDENTIFIER_POINTER (DECL_NAME ($$)));
732                           /* If it really returns void, change that to int.  */
733                           if (TREE_TYPE (TREE_TYPE ($$)) == void_type_node)
734                             TREE_TYPE ($$)
735                               = build_function_type (integer_type_node,
736                                                      TYPE_ARG_TYPES (TREE_TYPE ($$)));
737                         }
738                       else
739                         pedwarn ("built-in function `%s' used without declaration",
740                                  IDENTIFIER_POINTER (DECL_NAME ($$)));
741
742                       /* Do what we would ordinarily do when a fn is used.  */
743                       assemble_external ($$);
744                       TREE_USED ($$) = 1;
745                     }
746                   else
747                     {
748                       assemble_external ($$);
749                       TREE_USED ($$) = 1;
750 ifobjc
751                       /* we have a definition - still check if iVariable */
752
753                       if (!objc_receiver_context
754                           || (objc_receiver_context
755                               && strcmp (IDENTIFIER_POINTER ($1), "super")))
756                         {
757                           tree decl;
758
759                           if (objc_method_context
760                               && (decl = is_ivar (objc_ivar_chain, $1)))
761                             {
762                               if (IDENTIFIER_LOCAL_VALUE ($1))
763                                 warning ("local declaration of `%s' hides instance variable",
764                                          IDENTIFIER_POINTER ($1));
765                               else
766                                 {
767                                   if (is_private (decl))
768                                     $$ = error_mark_node;
769                                   else
770                                     $$ = build_ivar_reference ($1);
771                                 }
772                             }
773                         }
774                       else /* we have a message to super */
775                         $$ = get_super_receiver ();
776 end ifobjc
777                     }
778
779                   if (TREE_CODE ($$) == CONST_DECL)
780                     {
781                       $$ = DECL_INITIAL ($$);
782                       /* This is to prevent an enum whose value is 0
783                          from being considered a null pointer constant.  */
784                       $$ = build1 (NOP_EXPR, TREE_TYPE ($$), $$);
785                       TREE_CONSTANT ($$) = 1;
786                     }
787                 }
788         | CONSTANT
789         | string
790                 { $$ = combine_strings ($1); }
791         | '(' expr ')'
792                 { char class = TREE_CODE_CLASS (TREE_CODE ($2));
793                   if (class == 'e' || class == '1'
794                       || class == '2' || class == '<')
795                     C_SET_EXP_ORIGINAL_CODE ($2, ERROR_MARK);
796                   $$ = $2; }
797         | '(' error ')'
798                 { $$ = error_mark_node; }
799         | compstmt_primary_start compstmt_nostart ')'
800                 { tree rtl_exp;
801                   if (pedantic)
802                     pedwarn ("ANSI C forbids braced-groups within expressions");
803                   pop_iterator_stack ();
804                   pop_label_level ();
805                   rtl_exp = expand_end_stmt_expr ($1);
806                   /* The statements have side effects, so the group does.  */
807                   TREE_SIDE_EFFECTS (rtl_exp) = 1;
808
809                   if (TREE_CODE ($2) == BLOCK)
810                     {
811                       /* Make a BIND_EXPR for the BLOCK already made.  */
812                       $$ = build (BIND_EXPR, TREE_TYPE (rtl_exp),
813                                   NULL_TREE, rtl_exp, $2);
814                       /* Remove the block from the tree at this point.
815                          It gets put back at the proper place
816                          when the BIND_EXPR is expanded.  */
817                       delete_block ($2);
818                     }
819                   else
820                     $$ = $2;
821                 }
822         | compstmt_primary_start error ')'
823                 {
824                   /* Make sure we call expand_end_stmt_expr.  Otherwise
825                      we are likely to lose sequences and crash later.  */
826                   pop_iterator_stack ();
827                   pop_label_level ();
828                   expand_end_stmt_expr ($1);
829                   $$ = error_mark_node;
830                 }
831         | primary '(' exprlist ')'   %prec '.'
832                 { $$ = build_function_call ($1, $3); }
833         | primary '[' expr ']'   %prec '.'
834                 { $$ = build_array_ref ($1, $3); }
835         | primary '.' identifier
836                 {
837 ifobjc
838                   if (doing_objc_thang)
839                     {
840                       if (is_public ($1, $3))
841                         $$ = build_component_ref ($1, $3);
842                       else
843                         $$ = error_mark_node;
844                     }
845                   else
846 end ifobjc
847                     $$ = build_component_ref ($1, $3);
848                 }
849         | primary POINTSAT identifier
850                 {
851                   tree expr = build_indirect_ref ($1, "->");
852
853 ifobjc
854                   if (doing_objc_thang)
855                     {
856                       if (is_public (expr, $3))
857                         $$ = build_component_ref (expr, $3);
858                       else
859                         $$ = error_mark_node;
860                     }
861                   else
862 end ifobjc
863                     $$ = build_component_ref (expr, $3);
864                 }
865         | primary PLUSPLUS
866                 { $$ = build_unary_op (POSTINCREMENT_EXPR, $1, 0); }
867         | primary MINUSMINUS
868                 { $$ = build_unary_op (POSTDECREMENT_EXPR, $1, 0); }
869 ifobjc
870         | objcmessageexpr
871                 { $$ = build_message_expr ($1); }
872         | objcselectorexpr
873                 { $$ = build_selector_expr ($1); }
874         | objcprotocolexpr
875                 { $$ = build_protocol_expr ($1); }
876         | objcencodeexpr
877                 { $$ = build_encode_expr ($1); }
878         | objc_string
879                 { $$ = build_objc_string_object ($1); }
880 end ifobjc
881         ;
882
883 /* Produces a STRING_CST with perhaps more STRING_CSTs chained onto it.  */
884 string:
885           STRING
886         | string STRING
887                 { $$ = chainon ($1, $2);
888 ifc
889                   if (warn_traditional && !in_system_header)
890                     warning ("Use of ANSI string concatenation");
891 end ifc
892                 }
893         ;
894
895 ifobjc
896 /* Produces an OBJC_STRING_CST with perhaps more OBJC_STRING_CSTs chained
897    onto it.  */
898 objc_string:
899           OBJC_STRING
900         | objc_string OBJC_STRING
901                 { $$ = chainon ($1, $2); }
902         ;
903 end ifobjc
904
905 old_style_parm_decls:
906         /* empty */
907         | datadecls
908         | datadecls ELLIPSIS
909                 /* ... is used here to indicate a varargs function.  */
910                 { c_mark_varargs ();
911                   if (pedantic)
912                     pedwarn ("ANSI C does not permit use of `varargs.h'"); }
913         ;
914
915 /* The following are analogous to lineno_decl, decls and decl
916    except that they do not allow nested functions.
917    They are used for old-style parm decls.  */
918 lineno_datadecl:
919           save_filename save_lineno datadecl
920                 { }
921         ;
922
923 datadecls:
924         lineno_datadecl
925         | errstmt
926         | datadecls lineno_datadecl
927         | lineno_datadecl errstmt
928         ;
929
930 /* We don't allow prefix attributes here because they cause reduce/reduce
931    conflicts: we can't know whether we're parsing a function decl with
932    attribute suffix, or function defn with attribute prefix on first old
933    style parm.  */
934 datadecl:
935         typed_declspecs_no_prefix_attr setspecs initdecls ';'
936                 { current_declspecs = TREE_VALUE (declspec_stack);
937                   prefix_attributes = TREE_PURPOSE (declspec_stack);
938                   declspec_stack = TREE_CHAIN (declspec_stack); }
939         | declmods_no_prefix_attr setspecs notype_initdecls ';'
940                 { current_declspecs = TREE_VALUE (declspec_stack);      
941                   prefix_attributes = TREE_PURPOSE (declspec_stack);
942                   declspec_stack = TREE_CHAIN (declspec_stack); }
943         | typed_declspecs_no_prefix_attr ';'
944                 { shadow_tag_warned ($1, 1);
945                   pedwarn ("empty declaration"); }
946         | declmods_no_prefix_attr ';'
947                 { pedwarn ("empty declaration"); }
948         ;
949
950 /* This combination which saves a lineno before a decl
951    is the normal thing to use, rather than decl itself.
952    This is to avoid shift/reduce conflicts in contexts
953    where statement labels are allowed.  */
954 lineno_decl:
955           save_filename save_lineno decl
956                 { }
957         ;
958
959 decls:
960         lineno_decl
961         | errstmt
962         | decls lineno_decl
963         | lineno_decl errstmt
964         ;
965
966 /* records the type and storage class specs to use for processing
967    the declarators that follow.
968    Maintains a stack of outer-level values of current_declspecs,
969    for the sake of parm declarations nested in function declarators.  */
970 setspecs: /* empty */
971                 { pending_xref_error ();
972                   declspec_stack = tree_cons (prefix_attributes,
973                                               current_declspecs,
974                                               declspec_stack);
975                   split_specs_attrs ($<ttype>0,
976                                      &current_declspecs, &prefix_attributes); }
977         ;
978
979 /* ??? Yuck.  See after_type_declarator.  */
980 setattrs: /* empty */
981                 { prefix_attributes = chainon (prefix_attributes, $<ttype>0); }
982         ;
983
984 decl:
985         typed_declspecs setspecs initdecls ';'
986                 { current_declspecs = TREE_VALUE (declspec_stack);
987                   prefix_attributes = TREE_PURPOSE (declspec_stack);
988                   declspec_stack = TREE_CHAIN (declspec_stack); }
989         | declmods setspecs notype_initdecls ';'
990                 { current_declspecs = TREE_VALUE (declspec_stack);
991                   prefix_attributes = TREE_PURPOSE (declspec_stack);
992                   declspec_stack = TREE_CHAIN (declspec_stack); }
993         | typed_declspecs setspecs nested_function
994                 { current_declspecs = TREE_VALUE (declspec_stack);
995                   prefix_attributes = TREE_PURPOSE (declspec_stack);
996                   declspec_stack = TREE_CHAIN (declspec_stack); }
997         | declmods setspecs notype_nested_function
998                 { current_declspecs = TREE_VALUE (declspec_stack);
999                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1000                   declspec_stack = TREE_CHAIN (declspec_stack); }
1001         | typed_declspecs ';'
1002                 { shadow_tag ($1); }
1003         | declmods ';'
1004                 { pedwarn ("empty declaration"); }
1005         | extension decl
1006                 { RESTORE_WARN_FLAGS ($1); }
1007         ;
1008
1009 /* Declspecs which contain at least one type specifier or typedef name.
1010    (Just `const' or `volatile' is not enough.)
1011    A typedef'd name following these is taken as a name to be declared.
1012    Declspecs have a non-NULL TREE_VALUE, attributes do not.  */
1013
1014 typed_declspecs:
1015           typespec reserved_declspecs
1016                 { $$ = tree_cons (NULL_TREE, $1, $2); }
1017         | declmods typespec reserved_declspecs
1018                 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
1019         ;
1020
1021 reserved_declspecs:  /* empty */
1022                 { $$ = NULL_TREE; }
1023         | reserved_declspecs typespecqual_reserved
1024                 { $$ = tree_cons (NULL_TREE, $2, $1); }
1025         | reserved_declspecs SCSPEC
1026                 { if (extra_warnings)
1027                     warning ("`%s' is not at beginning of declaration",
1028                              IDENTIFIER_POINTER ($2));
1029                   $$ = tree_cons (NULL_TREE, $2, $1); }
1030         | reserved_declspecs attributes
1031                 { $$ = tree_cons ($2, NULL_TREE, $1); }
1032         ;
1033
1034 typed_declspecs_no_prefix_attr:
1035           typespec reserved_declspecs_no_prefix_attr
1036                 { $$ = tree_cons (NULL_TREE, $1, $2); }
1037         | declmods_no_prefix_attr typespec reserved_declspecs_no_prefix_attr
1038                 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
1039         ;
1040
1041 reserved_declspecs_no_prefix_attr:
1042           /* empty */
1043                 { $$ = NULL_TREE; }
1044         | reserved_declspecs_no_prefix_attr typespecqual_reserved
1045                 { $$ = tree_cons (NULL_TREE, $2, $1); }
1046         | reserved_declspecs_no_prefix_attr SCSPEC
1047                 { if (extra_warnings)
1048                     warning ("`%s' is not at beginning of declaration",
1049                              IDENTIFIER_POINTER ($2));
1050                   $$ = tree_cons (NULL_TREE, $2, $1); }
1051         ;
1052
1053 /* List of just storage classes, type modifiers, and prefix attributes.
1054    A declaration can start with just this, but then it cannot be used
1055    to redeclare a typedef-name.
1056    Declspecs have a non-NULL TREE_VALUE, attributes do not.  */
1057
1058 declmods:
1059           declmods_no_prefix_attr
1060                 { $$ = $1; }
1061         | attributes
1062                 { $$ = tree_cons ($1, NULL_TREE, NULL_TREE); }
1063         | declmods declmods_no_prefix_attr
1064                 { $$ = chainon ($2, $1); }
1065         | declmods attributes
1066                 { $$ = tree_cons ($2, NULL_TREE, $1); }
1067         ;
1068
1069 declmods_no_prefix_attr:
1070           TYPE_QUAL
1071                 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
1072                   TREE_STATIC ($$) = 1; }
1073         | SCSPEC
1074                 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
1075         | declmods_no_prefix_attr TYPE_QUAL
1076                 { $$ = tree_cons (NULL_TREE, $2, $1);
1077                   TREE_STATIC ($$) = 1; }
1078         | declmods_no_prefix_attr SCSPEC
1079                 { if (extra_warnings && TREE_STATIC ($1))
1080                     warning ("`%s' is not at beginning of declaration",
1081                              IDENTIFIER_POINTER ($2));
1082                   $$ = tree_cons (NULL_TREE, $2, $1);
1083                   TREE_STATIC ($$) = TREE_STATIC ($1); }
1084         ;
1085
1086
1087 /* Used instead of declspecs where storage classes are not allowed
1088    (that is, for typenames and structure components).
1089    Don't accept a typedef-name if anything but a modifier precedes it.  */
1090
1091 typed_typespecs:
1092           typespec reserved_typespecquals
1093                 { $$ = tree_cons (NULL_TREE, $1, $2); }
1094         | nonempty_type_quals typespec reserved_typespecquals
1095                 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
1096         ;
1097
1098 reserved_typespecquals:  /* empty */
1099                 { $$ = NULL_TREE; }
1100         | reserved_typespecquals typespecqual_reserved
1101                 { $$ = tree_cons (NULL_TREE, $2, $1); }
1102         ;
1103
1104 /* A typespec (but not a type qualifier).
1105    Once we have seen one of these in a declaration,
1106    if a typedef name appears then it is being redeclared.  */
1107
1108 typespec: TYPESPEC
1109         | structsp
1110         | TYPENAME
1111                 { /* For a typedef name, record the meaning, not the name.
1112                      In case of `foo foo, bar;'.  */
1113                   $$ = lookup_name ($1); }
1114 ifobjc
1115         | CLASSNAME protocolrefs
1116                 { $$ = get_static_reference ($1, $2); }
1117         | OBJECTNAME protocolrefs
1118                 { $$ = get_object_reference ($2); }
1119
1120 /* Make "<SomeProtocol>" equivalent to "id <SomeProtocol>"
1121    - nisse@lysator.liu.se */
1122         | non_empty_protocolrefs
1123                 { $$ = get_object_reference ($1); }
1124 end ifobjc
1125         | TYPEOF '(' expr ')'
1126                 { $$ = TREE_TYPE ($3); }
1127         | TYPEOF '(' typename ')'
1128                 { $$ = groktypename ($3); }
1129         ;
1130
1131 /* A typespec that is a reserved word, or a type qualifier.  */
1132
1133 typespecqual_reserved: TYPESPEC
1134         | TYPE_QUAL
1135         | structsp
1136         ;
1137
1138 initdecls:
1139         initdcl
1140         | initdecls ',' initdcl
1141         ;
1142
1143 notype_initdecls:
1144         notype_initdcl
1145         | notype_initdecls ',' initdcl
1146         ;
1147
1148 maybeasm:
1149           /* empty */
1150                 { $$ = NULL_TREE; }
1151         | ASM_KEYWORD '(' string ')'
1152                 { if (TREE_CHAIN ($3)) $3 = combine_strings ($3);
1153                   $$ = $3;
1154                 }
1155         ;
1156
1157 initdcl:
1158           declarator maybeasm maybe_attribute '='
1159                 { $<ttype>$ = start_decl ($1, current_declspecs, 1,
1160                                           $3, prefix_attributes);
1161                   start_init ($<ttype>$, $2, global_bindings_p ()); }
1162           init
1163 /* Note how the declaration of the variable is in effect while its init is parsed! */
1164                 { finish_init ();
1165                   finish_decl ($<ttype>5, $6, $2); }
1166         | declarator maybeasm maybe_attribute
1167                 { tree d = start_decl ($1, current_declspecs, 0,
1168                                        $3, prefix_attributes);
1169                   finish_decl (d, NULL_TREE, $2); 
1170                 }
1171         ;
1172
1173 notype_initdcl:
1174           notype_declarator maybeasm maybe_attribute '='
1175                 { $<ttype>$ = start_decl ($1, current_declspecs, 1,
1176                                           $3, prefix_attributes);
1177                   start_init ($<ttype>$, $2, global_bindings_p ()); }
1178           init
1179 /* Note how the declaration of the variable is in effect while its init is parsed! */
1180                 { finish_init ();
1181                   decl_attributes ($<ttype>5, $3, prefix_attributes);
1182                   finish_decl ($<ttype>5, $6, $2); }
1183         | notype_declarator maybeasm maybe_attribute
1184                 { tree d = start_decl ($1, current_declspecs, 0,
1185                                        $3, prefix_attributes);
1186                   finish_decl (d, NULL_TREE, $2); }
1187         ;
1188 /* the * rules are dummies to accept the Apollo extended syntax
1189    so that the header files compile. */
1190 maybe_attribute:
1191       /* empty */
1192                 { $$ = NULL_TREE; }
1193         | attributes
1194                 { $$ = $1; }
1195         ;
1196  
1197 attributes:
1198       attribute
1199                 { $$ = $1; }
1200         | attributes attribute
1201                 { $$ = chainon ($1, $2); }
1202         ;
1203
1204 attribute:
1205       ATTRIBUTE '(' '(' attribute_list ')' ')'
1206                 { $$ = $4; }
1207         ;
1208
1209 attribute_list:
1210       attrib
1211                 { $$ = $1; }
1212         | attribute_list ',' attrib
1213                 { $$ = chainon ($1, $3); }
1214         ;
1215  
1216 attrib:
1217     /* empty */
1218                 { $$ = NULL_TREE; }
1219         | any_word
1220                 { $$ = build_tree_list ($1, NULL_TREE); }
1221         | any_word '(' IDENTIFIER ')'
1222                 { $$ = build_tree_list ($1, build_tree_list (NULL_TREE, $3)); }
1223         | any_word '(' IDENTIFIER ',' nonnull_exprlist ')'
1224                 { $$ = build_tree_list ($1, tree_cons (NULL_TREE, $3, $5)); }
1225         | any_word '(' exprlist ')'
1226                 { $$ = build_tree_list ($1, $3); }
1227         ;
1228
1229 /* This still leaves out most reserved keywords,
1230    shouldn't we include them?  */
1231
1232 any_word:
1233           identifier
1234         | SCSPEC
1235         | TYPESPEC
1236         | TYPE_QUAL
1237         ;
1238 \f
1239 /* Initializers.  `init' is the entry point.  */
1240
1241 init:
1242         expr_no_commas
1243         | '{'
1244                 { really_start_incremental_init (NULL_TREE); }
1245           initlist_maybe_comma '}'
1246                 { $$ = pop_init_level (0); }
1247         | error
1248                 { $$ = error_mark_node; }
1249         ;
1250
1251 /* `initlist_maybe_comma' is the guts of an initializer in braces.  */
1252 initlist_maybe_comma:
1253           /* empty */
1254                 { if (pedantic)
1255                     pedwarn ("ANSI C forbids empty initializer braces"); }
1256         | initlist1 maybecomma
1257         ;
1258
1259 initlist1:
1260           initelt
1261         | initlist1 ',' initelt
1262         ;
1263
1264 /* `initelt' is a single element of an initializer.
1265    It may use braces.  */
1266 initelt:
1267           designator_list '=' initval
1268         | designator initval
1269         | identifier ':'
1270                 { set_init_label ($1); }
1271           initval
1272         | initval
1273         ;
1274
1275 initval:
1276           '{'
1277                 { push_init_level (0); }
1278           initlist_maybe_comma '}'
1279                 { process_init_element (pop_init_level (0)); }
1280         | expr_no_commas
1281                 { process_init_element ($1); }
1282         | error
1283         ;
1284
1285 designator_list:
1286           designator
1287         | designator_list designator
1288         ;
1289
1290 designator:
1291           '.' identifier
1292                 { set_init_label ($2); }
1293         /* These are for labeled elements.  The syntax for an array element
1294            initializer conflicts with the syntax for an Objective-C message,
1295            so don't include these productions in the Objective-C grammar.  */
1296 ifc
1297         | '[' expr_no_commas ELLIPSIS expr_no_commas ']'
1298                 { set_init_index ($2, $4); }
1299         | '[' expr_no_commas ']'
1300                 { set_init_index ($2, NULL_TREE); }
1301 end ifc
1302         ;
1303 \f
1304 nested_function:
1305           declarator
1306                 { if (pedantic)
1307                     pedwarn ("ANSI C forbids nested functions");
1308
1309                   push_function_context ();
1310                   if (! start_function (current_declspecs, $1,
1311                                         prefix_attributes, NULL_TREE))
1312                     {
1313                       pop_function_context ();
1314                       YYERROR1;
1315                     }
1316                   reinit_parse_for_function (); }
1317            old_style_parm_decls
1318                 { store_parm_decls (); }
1319 /* This used to use compstmt_or_error.
1320    That caused a bug with input `f(g) int g {}',
1321    where the use of YYERROR1 above caused an error
1322    which then was handled by compstmt_or_error.
1323    There followed a repeated execution of that same rule,
1324    which called YYERROR1 again, and so on.  */
1325           compstmt
1326                 { finish_function (1);
1327                   pop_function_context (); }
1328         ;
1329
1330 notype_nested_function:
1331           notype_declarator
1332                 { if (pedantic)
1333                     pedwarn ("ANSI C forbids nested functions");
1334
1335                   push_function_context ();
1336                   if (! start_function (current_declspecs, $1,
1337                                         prefix_attributes, NULL_TREE))
1338                     {
1339                       pop_function_context ();
1340                       YYERROR1;
1341                     }
1342                   reinit_parse_for_function (); }
1343           old_style_parm_decls
1344                 { store_parm_decls (); }
1345 /* This used to use compstmt_or_error.
1346    That caused a bug with input `f(g) int g {}',
1347    where the use of YYERROR1 above caused an error
1348    which then was handled by compstmt_or_error.
1349    There followed a repeated execution of that same rule,
1350    which called YYERROR1 again, and so on.  */
1351           compstmt
1352                 { finish_function (1);
1353                   pop_function_context (); }
1354         ;
1355
1356 /* Any kind of declarator (thus, all declarators allowed
1357    after an explicit typespec).  */
1358
1359 declarator:
1360           after_type_declarator
1361         | notype_declarator
1362         ;
1363
1364 /* A declarator that is allowed only after an explicit typespec.  */
1365
1366 after_type_declarator:
1367           '(' after_type_declarator ')'
1368                 { $$ = $2; }
1369         | after_type_declarator '(' parmlist_or_identifiers  %prec '.'
1370                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1371 /*      | after_type_declarator '(' error ')'  %prec '.'
1372                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1373                   poplevel (0, 0, 0); }  */
1374         | after_type_declarator '[' expr ']'  %prec '.'
1375                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1376         | after_type_declarator '[' ']'  %prec '.'
1377                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1378         | '*' type_quals after_type_declarator  %prec UNARY
1379                 { $$ = make_pointer_declarator ($2, $3); }
1380         /* ??? Yuck.  setattrs is a quick hack.  We can't use
1381            prefix_attributes because $1 only applies to this
1382            declarator.  We assume setspecs has already been done.
1383            setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
1384            attributes could be recognized here or in `attributes').  */
1385         | attributes setattrs after_type_declarator
1386                 { $$ = $3; }
1387         | TYPENAME
1388 ifobjc
1389         | OBJECTNAME
1390 end ifobjc
1391         ;
1392
1393 /* Kinds of declarator that can appear in a parameter list
1394    in addition to notype_declarator.  This is like after_type_declarator
1395    but does not allow a typedef name in parentheses as an identifier
1396    (because it would conflict with a function with that typedef as arg).  */
1397
1398 parm_declarator:
1399           parm_declarator '(' parmlist_or_identifiers  %prec '.'
1400                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1401 /*      | parm_declarator '(' error ')'  %prec '.'
1402                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1403                   poplevel (0, 0, 0); }  */
1404 ifc
1405         | parm_declarator '[' '*' ']'  %prec '.'
1406                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE);
1407                   if (! flag_isoc99)
1408                     error ("`[*]' in parameter declaration only allowed in ISO C 99");
1409                 }
1410 end ifc
1411         | parm_declarator '[' expr ']'  %prec '.'
1412                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1413         | parm_declarator '[' ']'  %prec '.'
1414                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1415         | '*' type_quals parm_declarator  %prec UNARY
1416                 { $$ = make_pointer_declarator ($2, $3); }
1417         /* ??? Yuck.  setattrs is a quick hack.  We can't use
1418            prefix_attributes because $1 only applies to this
1419            declarator.  We assume setspecs has already been done.
1420            setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
1421            attributes could be recognized here or in `attributes').  */
1422         | attributes setattrs parm_declarator
1423                 { $$ = $3; }
1424         | TYPENAME
1425         ;
1426
1427 /* A declarator allowed whether or not there has been
1428    an explicit typespec.  These cannot redeclare a typedef-name.  */
1429
1430 notype_declarator:
1431           notype_declarator '(' parmlist_or_identifiers  %prec '.'
1432                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1433 /*      | notype_declarator '(' error ')'  %prec '.'
1434                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1435                   poplevel (0, 0, 0); }  */
1436         | '(' notype_declarator ')'
1437                 { $$ = $2; }
1438         | '*' type_quals notype_declarator  %prec UNARY
1439                 { $$ = make_pointer_declarator ($2, $3); }
1440 ifc
1441         | notype_declarator '[' '*' ']'  %prec '.'
1442                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE);
1443                   if (! flag_isoc99)
1444                     error ("`[*]' in parameter declaration only allowed in ISO C 99");
1445                 }
1446 end ifc
1447         | notype_declarator '[' expr ']'  %prec '.'
1448                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1449         | notype_declarator '[' ']'  %prec '.'
1450                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1451         /* ??? Yuck.  setattrs is a quick hack.  We can't use
1452            prefix_attributes because $1 only applies to this
1453            declarator.  We assume setspecs has already been done.
1454            setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
1455            attributes could be recognized here or in `attributes').  */
1456         | attributes setattrs notype_declarator
1457                 { $$ = $3; }
1458         | IDENTIFIER
1459         ;
1460
1461 struct_head:
1462           STRUCT
1463                 { $$ = NULL_TREE; }
1464         | STRUCT attributes
1465                 { $$ = $2; }
1466         ;
1467
1468 union_head:
1469           UNION
1470                 { $$ = NULL_TREE; }
1471         | UNION attributes
1472                 { $$ = $2; }
1473         ;
1474
1475 enum_head:
1476           ENUM
1477                 { $$ = NULL_TREE; }
1478         | ENUM attributes
1479                 { $$ = $2; }
1480         ;
1481
1482 structsp:
1483           struct_head identifier '{'
1484                 { $$ = start_struct (RECORD_TYPE, $2);
1485                   /* Start scope of tag before parsing components.  */
1486                 }
1487           component_decl_list '}' maybe_attribute 
1488                 { $$ = finish_struct ($<ttype>4, $5, chainon ($1, $7)); }
1489         | struct_head '{' component_decl_list '}' maybe_attribute
1490                 { $$ = finish_struct (start_struct (RECORD_TYPE, NULL_TREE),
1491                                       $3, chainon ($1, $5));
1492                 }
1493         | struct_head identifier
1494                 { $$ = xref_tag (RECORD_TYPE, $2); }
1495         | union_head identifier '{'
1496                 { $$ = start_struct (UNION_TYPE, $2); }
1497           component_decl_list '}' maybe_attribute
1498                 { $$ = finish_struct ($<ttype>4, $5, chainon ($1, $7)); }
1499         | union_head '{' component_decl_list '}' maybe_attribute
1500                 { $$ = finish_struct (start_struct (UNION_TYPE, NULL_TREE),
1501                                       $3, chainon ($1, $5));
1502                 }
1503         | union_head identifier
1504                 { $$ = xref_tag (UNION_TYPE, $2); }
1505         | enum_head identifier '{'
1506                 { $$ = start_enum ($2); }
1507           enumlist maybecomma_warn '}' maybe_attribute
1508                 { $$ = finish_enum ($<ttype>4, nreverse ($5),
1509                                     chainon ($1, $8)); }
1510         | enum_head '{'
1511                 { $$ = start_enum (NULL_TREE); }
1512           enumlist maybecomma_warn '}' maybe_attribute
1513                 { $$ = finish_enum ($<ttype>3, nreverse ($4),
1514                                     chainon ($1, $7)); }
1515         | enum_head identifier
1516                 { $$ = xref_tag (ENUMERAL_TYPE, $2); }
1517         ;
1518
1519 maybecomma:
1520           /* empty */
1521         | ','
1522         ;
1523
1524 maybecomma_warn:
1525           /* empty */
1526         | ','
1527                 { if (pedantic && ! flag_isoc99)
1528                     pedwarn ("comma at end of enumerator list"); }
1529         ;
1530
1531 component_decl_list:
1532           component_decl_list2
1533                 { $$ = $1; }
1534         | component_decl_list2 component_decl
1535                 { $$ = chainon ($1, $2);
1536                   pedwarn ("no semicolon at end of struct or union"); }
1537         ;
1538
1539 component_decl_list2:   /* empty */
1540                 { $$ = NULL_TREE; }
1541         | component_decl_list2 component_decl ';'
1542                 { $$ = chainon ($1, $2); }
1543         | component_decl_list2 ';'
1544                 { if (pedantic)
1545                     pedwarn ("extra semicolon in struct or union specified"); }
1546 ifobjc
1547         /* foo(sizeof(struct{ @defs(ClassName)})); */
1548         | DEFS '(' CLASSNAME ')'
1549                 {
1550                   tree interface = lookup_interface ($3);
1551
1552                   if (interface)
1553                     $$ = get_class_ivars (interface);
1554                   else
1555                     {
1556                       error ("Cannot find interface declaration for `%s'",
1557                              IDENTIFIER_POINTER ($3));
1558                       $$ = NULL_TREE;
1559                     }
1560                 }
1561 end ifobjc
1562         ;
1563
1564 /* There is a shift-reduce conflict here, because `components' may
1565    start with a `typename'.  It happens that shifting (the default resolution)
1566    does the right thing, because it treats the `typename' as part of
1567    a `typed_typespecs'.
1568
1569    It is possible that this same technique would allow the distinction
1570    between `notype_initdecls' and `initdecls' to be eliminated.
1571    But I am being cautious and not trying it.  */
1572
1573 component_decl:
1574           typed_typespecs setspecs components
1575                 { $$ = $3;
1576                   current_declspecs = TREE_VALUE (declspec_stack);
1577                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1578                   declspec_stack = TREE_CHAIN (declspec_stack); }
1579         | typed_typespecs setspecs save_filename save_lineno maybe_attribute
1580                 {
1581                   /* Support for unnamed structs or unions as members of 
1582                      structs or unions (which is [a] useful and [b] supports 
1583                      MS P-SDK).  */
1584                   if (pedantic)
1585                     pedwarn ("ANSI C doesn't support unnamed structs/unions");
1586
1587                   $$ = grokfield($3, $4, NULL, current_declspecs, NULL_TREE);
1588                   current_declspecs = TREE_VALUE (declspec_stack);
1589                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1590                   declspec_stack = TREE_CHAIN (declspec_stack);
1591                 }
1592     | nonempty_type_quals setspecs components
1593                 { $$ = $3;
1594                   current_declspecs = TREE_VALUE (declspec_stack);
1595                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1596                   declspec_stack = TREE_CHAIN (declspec_stack); }
1597         | nonempty_type_quals
1598                 { if (pedantic)
1599                     pedwarn ("ANSI C forbids member declarations with no members");
1600                   shadow_tag($1);
1601                   $$ = NULL_TREE; }
1602         | error
1603                 { $$ = NULL_TREE; }
1604         | extension component_decl
1605                 { $$ = $2;
1606                   RESTORE_WARN_FLAGS ($1); }
1607         ;
1608
1609 components:
1610           component_declarator
1611         | components ',' component_declarator
1612                 { $$ = chainon ($1, $3); }
1613         ;
1614
1615 component_declarator:
1616           save_filename save_lineno declarator maybe_attribute
1617                 { $$ = grokfield ($1, $2, $3, current_declspecs, NULL_TREE);
1618                   decl_attributes ($$, $4, prefix_attributes); }
1619         | save_filename save_lineno
1620           declarator ':' expr_no_commas maybe_attribute
1621                 { $$ = grokfield ($1, $2, $3, current_declspecs, $5);
1622                   decl_attributes ($$, $6, prefix_attributes); }
1623         | save_filename save_lineno ':' expr_no_commas maybe_attribute
1624                 { $$ = grokfield ($1, $2, NULL_TREE, current_declspecs, $4);
1625                   decl_attributes ($$, $5, prefix_attributes); }
1626         ;
1627
1628 /* We chain the enumerators in reverse order.
1629    They are put in forward order where enumlist is used.
1630    (The order used to be significant, but no longer is so.
1631    However, we still maintain the order, just to be clean.)  */
1632
1633 enumlist:
1634           enumerator
1635         | enumlist ',' enumerator
1636                 { if ($1 == error_mark_node)
1637                     $$ = $1;
1638                   else
1639                     $$ = chainon ($3, $1); }
1640         | error
1641                 { $$ = error_mark_node; }
1642         ;
1643
1644
1645 enumerator:
1646           identifier
1647                 { $$ = build_enumerator ($1, NULL_TREE); }
1648         | identifier '=' expr_no_commas
1649                 { $$ = build_enumerator ($1, $3); }
1650         ;
1651
1652 typename:
1653         typed_typespecs absdcl
1654                 { $$ = build_tree_list ($1, $2); }
1655         | nonempty_type_quals absdcl
1656                 { $$ = build_tree_list ($1, $2); }
1657         ;
1658
1659 absdcl:   /* an absolute declarator */
1660         /* empty */
1661                 { $$ = NULL_TREE; }
1662         | absdcl1
1663         ;
1664
1665 nonempty_type_quals:
1666           TYPE_QUAL
1667                 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
1668         | nonempty_type_quals TYPE_QUAL
1669                 { $$ = tree_cons (NULL_TREE, $2, $1); }
1670         ;
1671
1672 type_quals:
1673           /* empty */
1674                 { $$ = NULL_TREE; }
1675         | type_quals TYPE_QUAL
1676                 { $$ = tree_cons (NULL_TREE, $2, $1); }
1677         ;
1678
1679 absdcl1:  /* a nonempty absolute declarator */
1680           '(' absdcl1 ')'
1681                 { $$ = $2; }
1682           /* `(typedef)1' is `int'.  */
1683         | '*' type_quals absdcl1  %prec UNARY
1684                 { $$ = make_pointer_declarator ($2, $3); }
1685         | '*' type_quals  %prec UNARY
1686                 { $$ = make_pointer_declarator ($2, NULL_TREE); }
1687         | absdcl1 '(' parmlist  %prec '.'
1688                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1689         | absdcl1 '[' expr ']'  %prec '.'
1690                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1691         | absdcl1 '[' ']'  %prec '.'
1692                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1693         | '(' parmlist  %prec '.'
1694                 { $$ = build_nt (CALL_EXPR, NULL_TREE, $2, NULL_TREE); }
1695         | '[' expr ']'  %prec '.'
1696                 { $$ = build_nt (ARRAY_REF, NULL_TREE, $2); }
1697         | '[' ']'  %prec '.'
1698                 { $$ = build_nt (ARRAY_REF, NULL_TREE, NULL_TREE); }
1699         /* ??? It appears we have to support attributes here, however
1700            using prefix_attributes is wrong.  */
1701         | attributes setattrs absdcl1
1702                 { $$ = $3; }
1703         ;
1704
1705 /* at least one statement, the first of which parses without error.  */
1706 /* stmts is used only after decls, so an invalid first statement
1707    is actually regarded as an invalid decl and part of the decls.  */
1708
1709 stmts:
1710         lineno_stmt_or_labels
1711                 {
1712                   if (pedantic && $1)
1713                     pedwarn ("ANSI C forbids label at end of compound statement");
1714                 }
1715         ;
1716
1717 lineno_stmt_or_labels:
1718           lineno_stmt_or_label
1719         | lineno_stmt_or_labels lineno_stmt_or_label
1720                 { $$ = $2; }
1721         | lineno_stmt_or_labels errstmt
1722                 { $$ = 0; }
1723         ;
1724
1725 xstmts:
1726         /* empty */
1727         | stmts
1728         ;
1729
1730 errstmt:  error ';'
1731         ;
1732
1733 pushlevel:  /* empty */
1734                 { emit_line_note (input_filename, lineno);
1735                   pushlevel (0);
1736                   clear_last_expr ();
1737                   expand_start_bindings (0);
1738 ifobjc
1739                   if (objc_method_context)
1740                     add_objc_decls ();
1741 end ifobjc
1742                 }
1743         ;
1744
1745 /* Read zero or more forward-declarations for labels
1746    that nested functions can jump to.  */
1747 maybe_label_decls:
1748           /* empty */
1749         | label_decls
1750                 { if (pedantic)
1751                     pedwarn ("ANSI C forbids label declarations"); }
1752         ;
1753
1754 label_decls:
1755           label_decl
1756         | label_decls label_decl
1757         ;
1758
1759 label_decl:
1760           LABEL identifiers_or_typenames ';'
1761                 { tree link;
1762                   for (link = $2; link; link = TREE_CHAIN (link))
1763                     {
1764                       tree label = shadow_label (TREE_VALUE (link));
1765                       C_DECLARED_LABEL_FLAG (label) = 1;
1766                       declare_nonlocal_label (label);
1767                     }
1768                 }
1769         ;
1770
1771 /* This is the body of a function definition.
1772    It causes syntax errors to ignore to the next openbrace.  */
1773 compstmt_or_error:
1774           compstmt
1775                 {}
1776         | error compstmt
1777         ;
1778
1779 compstmt_start: '{' { compstmt_count++; }
1780
1781 compstmt_nostart: '}'
1782                 { $$ = convert (void_type_node, integer_zero_node); }
1783         | pushlevel maybe_label_decls decls xstmts '}'
1784                 { emit_line_note (input_filename, lineno);
1785                   expand_end_bindings (getdecls (), 1, 0);
1786                   $$ = poplevel (1, 1, 0); }
1787         | pushlevel maybe_label_decls error '}'
1788                 { emit_line_note (input_filename, lineno);
1789                   expand_end_bindings (getdecls (), kept_level_p (), 0);
1790                   $$ = poplevel (kept_level_p (), 0, 0); }
1791         | pushlevel maybe_label_decls stmts '}'
1792                 { emit_line_note (input_filename, lineno);
1793                   expand_end_bindings (getdecls (), kept_level_p (), 0);
1794                   $$ = poplevel (kept_level_p (), 0, 0); }
1795         ;
1796
1797 compstmt_primary_start:
1798         '(' '{'
1799                 { if (current_function_decl == 0)
1800                     {
1801                       error ("braced-group within expression allowed only inside a function");
1802                       YYERROR;
1803                     }
1804                   /* We must force a BLOCK for this level
1805                      so that, if it is not expanded later,
1806                      there is a way to turn off the entire subtree of blocks
1807                      that are contained in it.  */
1808                   keep_next_level ();
1809                   push_iterator_stack ();
1810                   push_label_level ();
1811                   $$ = expand_start_stmt_expr ();
1812                   compstmt_count++;
1813                 }
1814
1815 compstmt: compstmt_start compstmt_nostart
1816                 { $$ = $2; }
1817         ;
1818
1819 /* Value is number of statements counted as of the closeparen.  */
1820 simple_if:
1821           if_prefix lineno_labeled_stmt
1822 /* Make sure c_expand_end_cond is run once
1823    for each call to c_expand_start_cond.
1824    Otherwise a crash is likely.  */
1825         | if_prefix error
1826         ;
1827
1828 if_prefix:
1829           IF '(' expr ')'
1830                 { emit_line_note ($<filename>-1, $<lineno>0);
1831                   c_expand_start_cond (truthvalue_conversion ($3), 0, 
1832                                        compstmt_count);
1833                   $<itype>$ = stmt_count;
1834                   if_stmt_file = $<filename>-1;
1835                   if_stmt_line = $<lineno>0;
1836                   position_after_white_space (); }
1837         ;
1838
1839 /* This is a subroutine of stmt.
1840    It is used twice, once for valid DO statements
1841    and once for catching errors in parsing the end test.  */
1842 do_stmt_start:
1843           DO
1844                 { stmt_count++;
1845                   compstmt_count++;
1846                   emit_line_note ($<filename>-1, $<lineno>0);
1847                   /* See comment in `while' alternative, above.  */
1848                   emit_nop ();
1849                   expand_start_loop_continue_elsewhere (1);
1850                   position_after_white_space (); }
1851           lineno_labeled_stmt WHILE
1852                 { expand_loop_continue_here (); }
1853         ;
1854
1855 save_filename:
1856                 { $$ = input_filename; }
1857         ;
1858
1859 save_lineno:
1860                 { $$ = lineno; }
1861         ;
1862
1863 lineno_labeled_stmt:
1864           save_filename save_lineno stmt
1865                 { }
1866 /*      | save_filename save_lineno error
1867                 { }
1868 */
1869         | save_filename save_lineno label lineno_labeled_stmt
1870                 { }
1871         ;
1872
1873 lineno_stmt_or_label:
1874           save_filename save_lineno stmt_or_label
1875                 { $$ = $3; }
1876         ;
1877
1878 stmt_or_label:
1879           stmt
1880                 { $$ = 0; }
1881         | label
1882                 { $$ = 1; }
1883         ;
1884
1885 /* Parse a single real statement, not including any labels.  */
1886 stmt:
1887           compstmt
1888                 { stmt_count++; }
1889         | all_iter_stmt 
1890         | expr ';'
1891                 { stmt_count++;
1892                   emit_line_note ($<filename>-1, $<lineno>0);
1893 /* It appears that this should not be done--that a non-lvalue array
1894    shouldn't get an error if the value isn't used.
1895    Section 3.2.2.1 says that an array lvalue gets converted to a pointer
1896    if it appears as a top-level expression,
1897    but says nothing about non-lvalue arrays.  */
1898 #if 0
1899                   /* Call default_conversion to get an error
1900                      on referring to a register array if pedantic.  */
1901                   if (TREE_CODE (TREE_TYPE ($1)) == ARRAY_TYPE
1902                       || TREE_CODE (TREE_TYPE ($1)) == FUNCTION_TYPE)
1903                     $1 = default_conversion ($1);
1904 #endif
1905                   iterator_expand ($1); }
1906         | simple_if ELSE
1907                 { c_expand_start_else ();
1908                   $<itype>1 = stmt_count;
1909                   position_after_white_space (); }
1910           lineno_labeled_stmt
1911                 { c_expand_end_cond ();
1912                   if (extra_warnings && stmt_count == $<itype>1)
1913                     warning ("empty body in an else-statement"); }
1914         | simple_if %prec IF
1915                 { c_expand_end_cond ();
1916                   /* This warning is here instead of in simple_if, because we
1917                      do not want a warning if an empty if is followed by an
1918                      else statement.  Increment stmt_count so we don't
1919                      give a second error if this is a nested `if'.  */
1920                   if (extra_warnings && stmt_count++ == $<itype>1)
1921                     warning_with_file_and_line (if_stmt_file, if_stmt_line,
1922                                                 "empty body in an if-statement"); }
1923 /* Make sure c_expand_end_cond is run once
1924    for each call to c_expand_start_cond.
1925    Otherwise a crash is likely.  */
1926         | simple_if ELSE error
1927                 { c_expand_end_cond (); }
1928         | WHILE
1929                 { stmt_count++;
1930                   emit_line_note ($<filename>-1, $<lineno>0);
1931                   /* The emit_nop used to come before emit_line_note,
1932                      but that made the nop seem like part of the preceding line.
1933                      And that was confusing when the preceding line was
1934                      inside of an if statement and was not really executed.
1935                      I think it ought to work to put the nop after the line number.
1936                      We will see.  --rms, July 15, 1991.  */
1937                   emit_nop (); }
1938           '(' expr ')'
1939                 { /* Don't start the loop till we have succeeded
1940                      in parsing the end test.  This is to make sure
1941                      that we end every loop we start.  */
1942                   expand_start_loop (1);
1943                   emit_line_note (input_filename, lineno);
1944                   expand_exit_loop_if_false (NULL_PTR,
1945                                              truthvalue_conversion ($4));
1946                   position_after_white_space (); }
1947           lineno_labeled_stmt
1948                 { expand_end_loop (); }
1949         | do_stmt_start
1950           '(' expr ')' ';'
1951                 { emit_line_note (input_filename, lineno);
1952                   expand_exit_loop_if_false (NULL_PTR,
1953                                              truthvalue_conversion ($3));
1954                   expand_end_loop (); }
1955 /* This rule is needed to make sure we end every loop we start.  */
1956         | do_stmt_start error
1957                 { expand_end_loop (); }
1958         | FOR
1959           '(' xexpr ';'
1960                 { stmt_count++;
1961                   emit_line_note ($<filename>-1, $<lineno>0);
1962                   /* See comment in `while' alternative, above.  */
1963                   emit_nop ();
1964                   if ($3) c_expand_expr_stmt ($3);
1965                   /* Next step is to call expand_start_loop_continue_elsewhere,
1966                      but wait till after we parse the entire for (...).
1967                      Otherwise, invalid input might cause us to call that
1968                      fn without calling expand_end_loop.  */
1969                 }
1970           xexpr ';'
1971                 /* Can't emit now; wait till after expand_start_loop...  */
1972                 { $<lineno>7 = lineno;
1973                   $<filename>$ = input_filename; }
1974           xexpr ')'
1975                 { 
1976                   /* Start the loop.  Doing this after parsing
1977                      all the expressions ensures we will end the loop.  */
1978                   expand_start_loop_continue_elsewhere (1);
1979                   /* Emit the end-test, with a line number.  */
1980                   emit_line_note ($<filename>8, $<lineno>7);
1981                   if ($6)
1982                     expand_exit_loop_if_false (NULL_PTR,
1983                                                truthvalue_conversion ($6));
1984                   $<lineno>7 = lineno;
1985                   $<filename>8 = input_filename;
1986                   position_after_white_space (); }
1987           lineno_labeled_stmt
1988                 { /* Emit the increment expression, with a line number.  */
1989                   emit_line_note ($<filename>8, $<lineno>7);
1990                   expand_loop_continue_here ();
1991                   if ($9)
1992                     c_expand_expr_stmt ($9);
1993                   expand_end_loop (); }
1994         | SWITCH '(' expr ')'
1995                 { stmt_count++;
1996                   emit_line_note ($<filename>-1, $<lineno>0);
1997                   c_expand_start_case ($3);
1998                   position_after_white_space (); }
1999           lineno_labeled_stmt
2000                 { expand_end_case ($3); }
2001         | BREAK ';'
2002                 { stmt_count++;
2003                   emit_line_note ($<filename>-1, $<lineno>0);
2004                   if ( ! expand_exit_something ())
2005                     error ("break statement not within loop or switch"); }
2006         | CONTINUE ';'
2007                 { stmt_count++;
2008                   emit_line_note ($<filename>-1, $<lineno>0);
2009                   if (! expand_continue_loop (NULL_PTR))
2010                     error ("continue statement not within a loop"); }
2011         | RETURN ';'
2012                 { stmt_count++;
2013                   emit_line_note ($<filename>-1, $<lineno>0);
2014                   c_expand_return (NULL_TREE); }
2015         | RETURN expr ';'
2016                 { stmt_count++;
2017                   emit_line_note ($<filename>-1, $<lineno>0);
2018                   c_expand_return ($2); }
2019         | ASM_KEYWORD maybe_type_qual '(' expr ')' ';'
2020                 { stmt_count++;
2021                   emit_line_note ($<filename>-1, $<lineno>0);
2022                   STRIP_NOPS ($4);
2023                   if ((TREE_CODE ($4) == ADDR_EXPR
2024                        && TREE_CODE (TREE_OPERAND ($4, 0)) == STRING_CST)
2025                       || TREE_CODE ($4) == STRING_CST)
2026                     expand_asm ($4);
2027                   else
2028                     error ("argument of `asm' is not a constant string"); }
2029         /* This is the case with just output operands.  */
2030         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ')' ';'
2031                 { stmt_count++;
2032                   emit_line_note ($<filename>-1, $<lineno>0);
2033                   c_expand_asm_operands ($4, $6, NULL_TREE, NULL_TREE,
2034                                          $2 == ridpointers[(int)RID_VOLATILE],
2035                                          input_filename, lineno); }
2036         /* This is the case with input operands as well.  */
2037         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':' asm_operands ')' ';'
2038                 { stmt_count++;
2039                   emit_line_note ($<filename>-1, $<lineno>0);
2040                   c_expand_asm_operands ($4, $6, $8, NULL_TREE,
2041                                          $2 == ridpointers[(int)RID_VOLATILE],
2042                                          input_filename, lineno); }
2043         /* This is the case with clobbered registers as well.  */
2044         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':'
2045           asm_operands ':' asm_clobbers ')' ';'
2046                 { stmt_count++;
2047                   emit_line_note ($<filename>-1, $<lineno>0);
2048                   c_expand_asm_operands ($4, $6, $8, $10,
2049                                          $2 == ridpointers[(int)RID_VOLATILE],
2050                                          input_filename, lineno); }
2051         | GOTO identifier ';'
2052                 { tree decl;
2053                   stmt_count++;
2054                   emit_line_note ($<filename>-1, $<lineno>0);
2055                   decl = lookup_label ($2);
2056                   if (decl != 0)
2057                     {
2058                       TREE_USED (decl) = 1;
2059                       expand_goto (decl);
2060                     }
2061                 }
2062         | GOTO '*' expr ';'
2063                 { if (pedantic)
2064                     pedwarn ("ANSI C forbids `goto *expr;'");
2065                   stmt_count++;
2066                   emit_line_note ($<filename>-1, $<lineno>0);
2067                   expand_computed_goto (convert (ptr_type_node, $3)); }
2068         | ';'
2069         ;
2070
2071 all_iter_stmt:
2072           all_iter_stmt_simple
2073 /*      | all_iter_stmt_with_decl */
2074         ;
2075
2076 all_iter_stmt_simple:
2077           FOR '(' primary ')' 
2078           {
2079             /* The value returned by this action is  */
2080             /*      1 if everything is OK */ 
2081             /*      0 in case of error or already bound iterator */
2082
2083             $<itype>$ = 0;
2084             if (TREE_CODE ($3) != VAR_DECL)
2085               error ("invalid `for (ITERATOR)' syntax");
2086             else if (! ITERATOR_P ($3))
2087               error ("`%s' is not an iterator",
2088                      IDENTIFIER_POINTER (DECL_NAME ($3)));
2089             else if (ITERATOR_BOUND_P ($3))
2090               error ("`for (%s)' inside expansion of same iterator",
2091                      IDENTIFIER_POINTER (DECL_NAME ($3)));
2092             else
2093               {
2094                 $<itype>$ = 1;
2095                 iterator_for_loop_start ($3);
2096               }
2097           }
2098           lineno_labeled_stmt
2099           {
2100             if ($<itype>5)
2101               iterator_for_loop_end ($3);
2102           }
2103
2104 /*  This really should allow any kind of declaration,
2105     for generality.  Fix it before turning it back on.
2106
2107 all_iter_stmt_with_decl:
2108           FOR '(' ITERATOR pushlevel setspecs iterator_spec ')' 
2109           {
2110 */          /* The value returned by this action is  */
2111             /*      1 if everything is OK */ 
2112             /*      0 in case of error or already bound iterator */
2113 /*
2114             iterator_for_loop_start ($6);
2115           }
2116           lineno_labeled_stmt
2117           {
2118             iterator_for_loop_end ($6);
2119             emit_line_note (input_filename, lineno);
2120             expand_end_bindings (getdecls (), 1, 0);
2121             $<ttype>$ = poplevel (1, 1, 0);
2122           }
2123 */
2124
2125 /* Any kind of label, including jump labels and case labels.
2126    ANSI C accepts labels only before statements, but we allow them
2127    also at the end of a compound statement.  */
2128
2129 label:    CASE expr_no_commas ':'
2130                 { register tree value = check_case_value ($2);
2131                   register tree label
2132                     = build_decl (LABEL_DECL, NULL_TREE, NULL_TREE);
2133
2134                   stmt_count++;
2135
2136                   if (value != error_mark_node)
2137                     {
2138                       tree duplicate;
2139                       int success;
2140
2141                       if (pedantic && ! INTEGRAL_TYPE_P (TREE_TYPE (value)))
2142                         pedwarn ("label must have integral type in ANSI C");
2143
2144                       success = pushcase (value, convert_and_check,
2145                                           label, &duplicate);
2146
2147                       if (success == 1)
2148                         error ("case label not within a switch statement");
2149                       else if (success == 2)
2150                         {
2151                           error ("duplicate case value");
2152                           error_with_decl (duplicate, "this is the first entry for that value");
2153                         }
2154                       else if (success == 3)
2155                         warning ("case value out of range");
2156                       else if (success == 5)
2157                         error ("case label within scope of cleanup or variable array");
2158                     }
2159                   position_after_white_space (); }
2160         | CASE expr_no_commas ELLIPSIS expr_no_commas ':'
2161                 { register tree value1 = check_case_value ($2);
2162                   register tree value2 = check_case_value ($4);
2163                   register tree label
2164                     = build_decl (LABEL_DECL, NULL_TREE, NULL_TREE);
2165
2166                   if (pedantic)
2167                     pedwarn ("ANSI C forbids case ranges");
2168                   stmt_count++;
2169
2170                   if (value1 != error_mark_node && value2 != error_mark_node)
2171                     {
2172                       tree duplicate;
2173                       int success = pushcase_range (value1, value2,
2174                                                     convert_and_check, label,
2175                                                     &duplicate);
2176                       if (success == 1)
2177                         error ("case label not within a switch statement");
2178                       else if (success == 2)
2179                         {
2180                           error ("duplicate case value");
2181                           error_with_decl (duplicate, "this is the first entry for that value");
2182                         }
2183                       else if (success == 3)
2184                         warning ("case value out of range");
2185                       else if (success == 4)
2186                         warning ("empty case range");
2187                       else if (success == 5)
2188                         error ("case label within scope of cleanup or variable array");
2189                     }
2190                   position_after_white_space (); }
2191         | DEFAULT ':'
2192                 {
2193                   tree duplicate;
2194                   register tree label
2195                     = build_decl (LABEL_DECL, NULL_TREE, NULL_TREE);
2196                   int success = pushcase (NULL_TREE, 0, label, &duplicate);
2197                   stmt_count++;
2198                   if (success == 1)
2199                     error ("default label not within a switch statement");
2200                   else if (success == 2)
2201                     {
2202                       error ("multiple default labels in one switch");
2203                       error_with_decl (duplicate, "this is the first default label");
2204                     }
2205                   position_after_white_space (); }
2206         | identifier ':' maybe_attribute
2207                 { tree label = define_label (input_filename, lineno, $1);
2208                   stmt_count++;
2209                   emit_nop ();
2210                   if (label)
2211                     {
2212                       expand_label (label);
2213                       decl_attributes (label, $3, NULL_TREE);
2214                     }
2215                   position_after_white_space (); }
2216         ;
2217
2218 /* Either a type-qualifier or nothing.  First thing in an `asm' statement.  */
2219
2220 maybe_type_qual:
2221         /* empty */
2222                 { emit_line_note (input_filename, lineno);
2223                   $$ = NULL_TREE; }
2224         | TYPE_QUAL
2225                 { emit_line_note (input_filename, lineno); }
2226         ;
2227
2228 xexpr:
2229         /* empty */
2230                 { $$ = NULL_TREE; }
2231         | expr
2232         ;
2233
2234 /* These are the operands other than the first string and colon
2235    in  asm ("addextend %2,%1": "=dm" (x), "0" (y), "g" (*x))  */
2236 asm_operands: /* empty */
2237                 { $$ = NULL_TREE; }
2238         | nonnull_asm_operands
2239         ;
2240
2241 nonnull_asm_operands:
2242           asm_operand
2243         | nonnull_asm_operands ',' asm_operand
2244                 { $$ = chainon ($1, $3); }
2245         ;
2246
2247 asm_operand:
2248           STRING '(' expr ')'
2249                 { $$ = build_tree_list ($1, $3); }
2250         ;
2251
2252 asm_clobbers:
2253           string
2254                 { $$ = tree_cons (NULL_TREE, combine_strings ($1), NULL_TREE); }
2255         | asm_clobbers ',' string
2256                 { $$ = tree_cons (NULL_TREE, combine_strings ($3), $1); }
2257         ;
2258 \f
2259 /* This is what appears inside the parens in a function declarator.
2260    Its value is a list of ..._TYPE nodes.  */
2261 parmlist:
2262                 { pushlevel (0);
2263                   clear_parm_order ();
2264                   declare_parm_level (0); }
2265           parmlist_1
2266                 { $$ = $2;
2267                   parmlist_tags_warning ();
2268                   poplevel (0, 0, 0); }
2269         ;
2270
2271 parmlist_1:
2272           parmlist_2 ')'
2273         | parms ';'
2274                 { tree parm;
2275                   if (pedantic)
2276                     pedwarn ("ANSI C forbids forward parameter declarations");
2277                   /* Mark the forward decls as such.  */
2278                   for (parm = getdecls (); parm; parm = TREE_CHAIN (parm))
2279                     TREE_ASM_WRITTEN (parm) = 1;
2280                   clear_parm_order (); }
2281           parmlist_1
2282                 { $$ = $4; }
2283         | error ')'
2284                 { $$ = tree_cons (NULL_TREE, NULL_TREE, NULL_TREE); }
2285         ;
2286
2287 /* This is what appears inside the parens in a function declarator.
2288    Is value is represented in the format that grokdeclarator expects.  */
2289 parmlist_2:  /* empty */
2290                 { $$ = get_parm_info (0); }
2291         | ELLIPSIS
2292                 { $$ = get_parm_info (0);
2293                   /* Gcc used to allow this as an extension.  However, it does
2294                      not work for all targets, and thus has been disabled.
2295                      Also, since func (...) and func () are indistinguishable,
2296                      it caused problems with the code in expand_builtin which
2297                      tries to verify that BUILT_IN_NEXT_ARG is being used
2298                      correctly.  */
2299                   error ("ANSI C requires a named argument before `...'");
2300                 }
2301         | parms
2302                 { $$ = get_parm_info (1); }
2303         | parms ',' ELLIPSIS
2304                 { $$ = get_parm_info (0); }
2305         ;
2306
2307 parms:
2308         parm
2309                 { push_parm_decl ($1); }
2310         | parms ',' parm
2311                 { push_parm_decl ($3); }
2312         ;
2313
2314 /* A single parameter declaration or parameter type name,
2315    as found in a parmlist.  */
2316 parm:
2317           typed_declspecs setspecs parm_declarator maybe_attribute
2318                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2319                                                          $3),
2320                                         build_tree_list (prefix_attributes,
2321                                                          $4));
2322                   current_declspecs = TREE_VALUE (declspec_stack);
2323                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2324                   declspec_stack = TREE_CHAIN (declspec_stack); }
2325         | typed_declspecs setspecs notype_declarator maybe_attribute
2326                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2327                                                          $3),
2328                                         build_tree_list (prefix_attributes,
2329                                                          $4)); 
2330                   current_declspecs = TREE_VALUE (declspec_stack);
2331                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2332                   declspec_stack = TREE_CHAIN (declspec_stack); }
2333         | typed_declspecs setspecs absdcl maybe_attribute
2334                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2335                                                          $3),
2336                                         build_tree_list (prefix_attributes,
2337                                                          $4));
2338                   current_declspecs = TREE_VALUE (declspec_stack);
2339                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2340                   declspec_stack = TREE_CHAIN (declspec_stack); }
2341         | declmods setspecs notype_declarator maybe_attribute
2342                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2343                                                          $3),
2344                                         build_tree_list (prefix_attributes,
2345                                                          $4));
2346                   current_declspecs = TREE_VALUE (declspec_stack);
2347                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2348                   declspec_stack = TREE_CHAIN (declspec_stack); }
2349
2350         | declmods setspecs absdcl maybe_attribute
2351                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2352                                                          $3),
2353                                         build_tree_list (prefix_attributes,
2354                                                          $4));
2355                   current_declspecs = TREE_VALUE (declspec_stack);
2356                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2357                   declspec_stack = TREE_CHAIN (declspec_stack); }
2358         ;
2359
2360 /* This is used in a function definition
2361    where either a parmlist or an identifier list is ok.
2362    Its value is a list of ..._TYPE nodes or a list of identifiers.  */
2363 parmlist_or_identifiers:
2364                 { pushlevel (0);
2365                   clear_parm_order ();
2366                   declare_parm_level (1); }
2367           parmlist_or_identifiers_1
2368                 { $$ = $2;
2369                   parmlist_tags_warning ();
2370                   poplevel (0, 0, 0); }
2371         ;
2372
2373 parmlist_or_identifiers_1:
2374           parmlist_1
2375         | identifiers ')'
2376                 { tree t;
2377                   for (t = $1; t; t = TREE_CHAIN (t))
2378                     if (TREE_VALUE (t) == NULL_TREE)
2379                       error ("`...' in old-style identifier list");
2380                   $$ = tree_cons (NULL_TREE, NULL_TREE, $1); }
2381         ;
2382
2383 /* A nonempty list of identifiers.  */
2384 identifiers:
2385         IDENTIFIER
2386                 { $$ = build_tree_list (NULL_TREE, $1); }
2387         | identifiers ',' IDENTIFIER
2388                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2389         ;
2390
2391 /* A nonempty list of identifiers, including typenames.  */
2392 identifiers_or_typenames:
2393         identifier
2394                 { $$ = build_tree_list (NULL_TREE, $1); }
2395         | identifiers_or_typenames ',' identifier
2396                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2397         ;
2398
2399 extension:
2400         EXTENSION
2401                 { $$ = SAVE_WARN_FLAGS();
2402                   pedantic = 0;
2403                   warn_pointer_arith = 0; }
2404         ;
2405 \f
2406 ifobjc
2407 /* Objective-C productions.  */
2408
2409 objcdef:
2410           classdef
2411         | classdecl
2412         | aliasdecl
2413         | protocoldef
2414         | methoddef
2415         | END
2416                 {
2417                   if (objc_implementation_context)
2418                     {
2419                       finish_class (objc_implementation_context);
2420                       objc_ivar_chain = NULL_TREE;
2421                       objc_implementation_context = NULL_TREE;
2422                     }
2423                   else
2424                     warning ("`@end' must appear in an implementation context");
2425                 }
2426         ;
2427
2428 /* A nonempty list of identifiers.  */
2429 identifier_list:
2430         identifier
2431                 { $$ = build_tree_list (NULL_TREE, $1); }
2432         | identifier_list ',' identifier
2433                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2434         ;
2435
2436 classdecl:
2437           CLASS identifier_list ';'
2438                 {
2439                   objc_declare_class ($2);
2440                 }
2441
2442 aliasdecl:
2443           ALIAS identifier identifier ';'
2444                 {
2445                   objc_declare_alias ($2, $3);
2446                 }
2447
2448 classdef:
2449           INTERFACE identifier protocolrefs '{'
2450                 {
2451                   objc_interface_context = objc_ivar_context
2452                     = start_class (CLASS_INTERFACE_TYPE, $2, NULL_TREE, $3);
2453                   objc_public_flag = 0;
2454                 }
2455           ivar_decl_list '}'
2456                 {
2457                   continue_class (objc_interface_context);
2458                 }
2459           methodprotolist
2460           END
2461                 {
2462                   finish_class (objc_interface_context);
2463                   objc_interface_context = NULL_TREE;
2464                 }
2465
2466         | INTERFACE identifier protocolrefs
2467                 {
2468                   objc_interface_context
2469                     = start_class (CLASS_INTERFACE_TYPE, $2, NULL_TREE, $3);
2470                   continue_class (objc_interface_context);
2471                 }
2472           methodprotolist
2473           END
2474                 {
2475                   finish_class (objc_interface_context);
2476                   objc_interface_context = NULL_TREE;
2477                 }
2478
2479         | INTERFACE identifier ':' identifier protocolrefs '{'
2480                 {
2481                   objc_interface_context = objc_ivar_context
2482                     = start_class (CLASS_INTERFACE_TYPE, $2, $4, $5);
2483                   objc_public_flag = 0;
2484                 }
2485           ivar_decl_list '}'
2486                 {
2487                   continue_class (objc_interface_context);
2488                 }
2489           methodprotolist
2490           END
2491                 {
2492                   finish_class (objc_interface_context);
2493                   objc_interface_context = NULL_TREE;
2494                 }
2495
2496         | INTERFACE identifier ':' identifier protocolrefs
2497                 {
2498                   objc_interface_context
2499                     = start_class (CLASS_INTERFACE_TYPE, $2, $4, $5);
2500                   continue_class (objc_interface_context);
2501                 }
2502           methodprotolist
2503           END
2504                 {
2505                   finish_class (objc_interface_context);
2506                   objc_interface_context = NULL_TREE;
2507                 }
2508
2509         | IMPLEMENTATION identifier '{'
2510                 {
2511                   objc_implementation_context = objc_ivar_context
2512                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, NULL_TREE, NULL_TREE);
2513                   objc_public_flag = 0;
2514                 }
2515           ivar_decl_list '}'
2516                 {
2517                   objc_ivar_chain
2518                     = continue_class (objc_implementation_context);
2519                 }
2520
2521         | IMPLEMENTATION identifier
2522                 {
2523                   objc_implementation_context
2524                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, NULL_TREE, NULL_TREE);
2525                   objc_ivar_chain
2526                     = continue_class (objc_implementation_context);
2527                 }
2528
2529         | IMPLEMENTATION identifier ':' identifier '{'
2530                 {
2531                   objc_implementation_context = objc_ivar_context
2532                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2533                   objc_public_flag = 0;
2534                 }
2535           ivar_decl_list '}'
2536                 {
2537                   objc_ivar_chain
2538                     = continue_class (objc_implementation_context);
2539                 }
2540
2541         | IMPLEMENTATION identifier ':' identifier
2542                 {
2543                   objc_implementation_context
2544                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2545                   objc_ivar_chain
2546                     = continue_class (objc_implementation_context);
2547                 }
2548
2549         | INTERFACE identifier '(' identifier ')' protocolrefs
2550                 {
2551                   objc_interface_context
2552                     = start_class (CATEGORY_INTERFACE_TYPE, $2, $4, $6);
2553                   continue_class (objc_interface_context);
2554                 }
2555           methodprotolist
2556           END
2557                 {
2558                   finish_class (objc_interface_context);
2559                   objc_interface_context = NULL_TREE;
2560                 }
2561
2562         | IMPLEMENTATION identifier '(' identifier ')'
2563                 {
2564                   objc_implementation_context
2565                     = start_class (CATEGORY_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2566                   objc_ivar_chain
2567                     = continue_class (objc_implementation_context);
2568                 }
2569         ;
2570
2571 protocoldef:
2572           PROTOCOL identifier protocolrefs
2573                 {
2574                   remember_protocol_qualifiers ();
2575                   objc_interface_context
2576                     = start_protocol(PROTOCOL_INTERFACE_TYPE, $2, $3);
2577                 }
2578           methodprotolist END
2579                 {
2580                   forget_protocol_qualifiers();
2581                   finish_protocol(objc_interface_context);
2582                   objc_interface_context = NULL_TREE;
2583                 }
2584         ;
2585
2586 protocolrefs:
2587           /* empty */
2588                 {
2589                   $$ = NULL_TREE;
2590                 }
2591         | non_empty_protocolrefs
2592         ;
2593
2594 non_empty_protocolrefs:
2595           ARITHCOMPARE identifier_list ARITHCOMPARE
2596                 {
2597                   if ($1 == LT_EXPR && $3 == GT_EXPR)
2598                     $$ = $2;
2599                   else
2600                     YYERROR1;
2601                 }
2602         ;
2603
2604 ivar_decl_list:
2605           ivar_decl_list visibility_spec ivar_decls
2606         | ivar_decls
2607         ;
2608
2609 visibility_spec:
2610           PRIVATE { objc_public_flag = 2; }
2611         | PROTECTED { objc_public_flag = 0; }
2612         | PUBLIC { objc_public_flag = 1; }
2613         ;
2614
2615 ivar_decls:
2616           /* empty */
2617                 {
2618                   $$ = NULL_TREE;
2619                 }
2620         | ivar_decls ivar_decl ';'
2621         | ivar_decls ';'
2622                 {
2623                   if (pedantic)
2624                     pedwarn ("extra semicolon in struct or union specified");
2625                 }
2626         ;
2627
2628
2629 /* There is a shift-reduce conflict here, because `components' may
2630    start with a `typename'.  It happens that shifting (the default resolution)
2631    does the right thing, because it treats the `typename' as part of
2632    a `typed_typespecs'.
2633
2634    It is possible that this same technique would allow the distinction
2635    between `notype_initdecls' and `initdecls' to be eliminated.
2636    But I am being cautious and not trying it.  */
2637
2638 ivar_decl:
2639         typed_typespecs setspecs ivars
2640                 { $$ = $3;
2641                   current_declspecs = TREE_VALUE (declspec_stack);
2642                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2643                   declspec_stack = TREE_CHAIN (declspec_stack); }
2644         | nonempty_type_quals setspecs ivars
2645                 { $$ = $3;
2646                   current_declspecs = TREE_VALUE (declspec_stack);
2647                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2648                   declspec_stack = TREE_CHAIN (declspec_stack); }
2649         | error
2650                 { $$ = NULL_TREE; }
2651         ;
2652
2653 ivars:
2654           /* empty */
2655                 { $$ = NULL_TREE; }
2656         | ivar_declarator
2657         | ivars ',' ivar_declarator
2658         ;
2659
2660 ivar_declarator:
2661           declarator
2662                 {
2663                   $$ = add_instance_variable (objc_ivar_context,
2664                                               objc_public_flag,
2665                                               $1, current_declspecs,
2666                                               NULL_TREE);
2667                 }
2668         | declarator ':' expr_no_commas
2669                 {
2670                   $$ = add_instance_variable (objc_ivar_context,
2671                                               objc_public_flag,
2672                                               $1, current_declspecs, $3);
2673                 }
2674         | ':' expr_no_commas
2675                 {
2676                   $$ = add_instance_variable (objc_ivar_context,
2677                                               objc_public_flag,
2678                                               NULL_TREE,
2679                                               current_declspecs, $2);
2680                 }
2681         ;
2682
2683 methoddef:
2684           '+'
2685                 {
2686                   remember_protocol_qualifiers ();
2687                   if (objc_implementation_context)
2688                     objc_inherit_code = CLASS_METHOD_DECL;
2689                   else
2690                     fatal ("method definition not in class context");
2691                 }
2692           methoddecl
2693                 {
2694                   forget_protocol_qualifiers ();
2695                   add_class_method (objc_implementation_context, $3);
2696                   start_method_def ($3);
2697                   objc_method_context = $3;
2698                 }
2699           optarglist
2700                 {
2701                   continue_method_def ();
2702                 }
2703           compstmt_or_error
2704                 {
2705                   finish_method_def ();
2706                   objc_method_context = NULL_TREE;
2707                 }
2708
2709         | '-'
2710                 {
2711                   remember_protocol_qualifiers ();
2712                   if (objc_implementation_context)
2713                     objc_inherit_code = INSTANCE_METHOD_DECL;
2714                   else
2715                     fatal ("method definition not in class context");
2716                 }
2717           methoddecl
2718                 {
2719                   forget_protocol_qualifiers ();
2720                   add_instance_method (objc_implementation_context, $3);
2721                   start_method_def ($3);
2722                   objc_method_context = $3;
2723                 }
2724           optarglist
2725                 {
2726                   continue_method_def ();
2727                 }
2728           compstmt_or_error
2729                 {
2730                   finish_method_def ();
2731                   objc_method_context = NULL_TREE;
2732                 }
2733         ;
2734
2735 /* the reason for the strange actions in this rule
2736  is so that notype_initdecls when reached via datadef
2737  can find a valid list of type and sc specs in $0. */
2738
2739 methodprotolist:
2740           /* empty  */
2741         | {$<ttype>$ = NULL_TREE; } methodprotolist2
2742         ;
2743
2744 methodprotolist2:                /* eliminates a shift/reduce conflict */
2745            methodproto
2746         |  datadef
2747         | methodprotolist2 methodproto
2748         | methodprotolist2 {$<ttype>$ = NULL_TREE; } datadef
2749         ;
2750
2751 semi_or_error:
2752           ';'
2753         | error
2754         ;
2755
2756 methodproto:
2757           '+'
2758                 {
2759                   /* Remember protocol qualifiers in prototypes.  */
2760                   remember_protocol_qualifiers ();
2761                   objc_inherit_code = CLASS_METHOD_DECL;
2762                 }
2763           methoddecl
2764                 {
2765                   /* Forget protocol qualifiers here.  */
2766                   forget_protocol_qualifiers ();
2767                   add_class_method (objc_interface_context, $3);
2768                 }
2769           semi_or_error
2770
2771         | '-'
2772                 {
2773                   /* Remember protocol qualifiers in prototypes.  */
2774                   remember_protocol_qualifiers ();
2775                   objc_inherit_code = INSTANCE_METHOD_DECL;
2776                 }
2777           methoddecl
2778                 {
2779                   /* Forget protocol qualifiers here.  */
2780                   forget_protocol_qualifiers ();
2781                   add_instance_method (objc_interface_context, $3);
2782                 }
2783           semi_or_error
2784         ;
2785
2786 methoddecl:
2787           '(' typename ')' unaryselector
2788                 {
2789                   $$ = build_method_decl (objc_inherit_code, $2, $4, NULL_TREE);
2790                 }
2791
2792         | unaryselector
2793                 {
2794                   $$ = build_method_decl (objc_inherit_code, NULL_TREE, $1, NULL_TREE);
2795                 }
2796
2797         | '(' typename ')' keywordselector optparmlist
2798                 {
2799                   $$ = build_method_decl (objc_inherit_code, $2, $4, $5);
2800                 }
2801
2802         | keywordselector optparmlist
2803                 {
2804                   $$ = build_method_decl (objc_inherit_code, NULL_TREE, $1, $2);
2805                 }
2806         ;
2807
2808 /* "optarglist" assumes that start_method_def has already been called...
2809    if it is not, the "xdecls" will not be placed in the proper scope */
2810
2811 optarglist:
2812           /* empty */
2813         | ';' myxdecls
2814         ;
2815
2816 /* to get around the following situation: "int foo (int a) int b; {}" that
2817    is synthesized when parsing "- a:a b:b; id c; id d; { ... }" */
2818
2819 myxdecls:
2820           /* empty */
2821         | mydecls
2822         ;
2823
2824 mydecls:
2825         mydecl
2826         | errstmt
2827         | mydecls mydecl
2828         | mydecl errstmt
2829         ;
2830
2831 mydecl:
2832         typed_declspecs setspecs myparms ';'
2833                 { current_declspecs = TREE_VALUE (declspec_stack);
2834                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2835                   declspec_stack = TREE_CHAIN (declspec_stack); }
2836         | typed_declspecs ';'
2837                 { shadow_tag ($1); }
2838         | declmods ';'
2839                 { pedwarn ("empty declaration"); }
2840         ;
2841
2842 myparms:
2843         myparm
2844                 { push_parm_decl ($1); }
2845         | myparms ',' myparm
2846                 { push_parm_decl ($3); }
2847         ;
2848
2849 /* A single parameter declaration or parameter type name,
2850    as found in a parmlist. DOES NOT ALLOW AN INITIALIZER OR ASMSPEC */
2851
2852 myparm:
2853           parm_declarator maybe_attribute
2854                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2855                                                          $1),
2856                                         build_tree_list (prefix_attributes,
2857                                                          $2)); }
2858         | notype_declarator maybe_attribute
2859                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2860                                                          $1),
2861                                         build_tree_list (prefix_attributes,
2862                                                          $2)); }
2863         | absdcl maybe_attribute
2864                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2865                                                          $1),
2866                                         build_tree_list (prefix_attributes,
2867                                                          $2)); }
2868         ;
2869
2870 optparmlist:
2871           /* empty */
2872                 {
2873                   $$ = NULL_TREE;
2874                 }
2875         | ',' ELLIPSIS
2876                 {
2877                   /* oh what a kludge! */
2878                   $$ = (tree)1;
2879                 }
2880         | ','
2881                 {
2882                   pushlevel (0);
2883                 }
2884           parmlist_2
2885                 {
2886                   /* returns a tree list node generated by get_parm_info */
2887                   $$ = $3;
2888                   poplevel (0, 0, 0);
2889                 }
2890         ;
2891
2892 unaryselector:
2893           selector
2894         ;
2895
2896 keywordselector:
2897           keyworddecl
2898
2899         | keywordselector keyworddecl
2900                 {
2901                   $$ = chainon ($1, $2);
2902                 }
2903         ;
2904
2905 selector:
2906           IDENTIFIER
2907         | TYPENAME
2908         | OBJECTNAME
2909         | reservedwords
2910         ;
2911
2912 reservedwords:
2913           ENUM { $$ = get_identifier (token_buffer); }
2914         | STRUCT { $$ = get_identifier (token_buffer); }
2915         | UNION { $$ = get_identifier (token_buffer); }
2916         | IF { $$ = get_identifier (token_buffer); }
2917         | ELSE { $$ = get_identifier (token_buffer); }
2918         | WHILE { $$ = get_identifier (token_buffer); }
2919         | DO { $$ = get_identifier (token_buffer); }
2920         | FOR { $$ = get_identifier (token_buffer); }
2921         | SWITCH { $$ = get_identifier (token_buffer); }
2922         | CASE { $$ = get_identifier (token_buffer); }
2923         | DEFAULT { $$ = get_identifier (token_buffer); }
2924         | BREAK { $$ = get_identifier (token_buffer); }
2925         | CONTINUE { $$ = get_identifier (token_buffer); }
2926         | RETURN  { $$ = get_identifier (token_buffer); }
2927         | GOTO { $$ = get_identifier (token_buffer); }
2928         | ASM_KEYWORD { $$ = get_identifier (token_buffer); }
2929         | SIZEOF { $$ = get_identifier (token_buffer); }
2930         | TYPEOF { $$ = get_identifier (token_buffer); }
2931         | ALIGNOF { $$ = get_identifier (token_buffer); }
2932         | TYPESPEC | TYPE_QUAL
2933         ;
2934
2935 keyworddecl:
2936           selector ':' '(' typename ')' identifier
2937                 {
2938                   $$ = build_keyword_decl ($1, $4, $6);
2939                 }
2940
2941         | selector ':' identifier
2942                 {
2943                   $$ = build_keyword_decl ($1, NULL_TREE, $3);
2944                 }
2945
2946         | ':' '(' typename ')' identifier
2947                 {
2948                   $$ = build_keyword_decl (NULL_TREE, $3, $5);
2949                 }
2950
2951         | ':' identifier
2952                 {
2953                   $$ = build_keyword_decl (NULL_TREE, NULL_TREE, $2);
2954                 }
2955         ;
2956
2957 messageargs:
2958           selector
2959         | keywordarglist
2960         ;
2961
2962 keywordarglist:
2963           keywordarg
2964         | keywordarglist keywordarg
2965                 {
2966                   $$ = chainon ($1, $2);
2967                 }
2968         ;
2969
2970
2971 keywordexpr:
2972           nonnull_exprlist
2973                 {
2974                   if (TREE_CHAIN ($1) == NULL_TREE)
2975                     /* just return the expr., remove a level of indirection */
2976                     $$ = TREE_VALUE ($1);
2977                   else
2978                     /* we have a comma expr., we will collapse later */
2979                     $$ = $1;
2980                 }
2981         ;
2982
2983 keywordarg:
2984           selector ':' keywordexpr
2985                 {
2986                   $$ = build_tree_list ($1, $3);
2987                 }
2988         | ':' keywordexpr
2989                 {
2990                   $$ = build_tree_list (NULL_TREE, $2);
2991                 }
2992         ;
2993
2994 receiver:
2995           expr
2996         | CLASSNAME
2997                 {
2998                   $$ = get_class_reference ($1);
2999                 }
3000         ;
3001
3002 objcmessageexpr:
3003           '['
3004                 { objc_receiver_context = 1; }
3005           receiver
3006                 { objc_receiver_context = 0; }
3007           messageargs ']'
3008                 {
3009                   $$ = build_tree_list ($3, $5);
3010                 }
3011         ;
3012
3013 selectorarg:
3014           selector
3015         | keywordnamelist
3016         ;
3017
3018 keywordnamelist:
3019           keywordname
3020         | keywordnamelist keywordname
3021                 {
3022                   $$ = chainon ($1, $2);
3023                 }
3024         ;
3025
3026 keywordname:
3027           selector ':'
3028                 {
3029                   $$ = build_tree_list ($1, NULL_TREE);
3030                 }
3031         | ':'
3032                 {
3033                   $$ = build_tree_list (NULL_TREE, NULL_TREE);
3034                 }
3035         ;
3036
3037 objcselectorexpr:
3038           SELECTOR '(' selectorarg ')'
3039                 {
3040                   $$ = $3;
3041                 }
3042         ;
3043
3044 objcprotocolexpr:
3045           PROTOCOL '(' identifier ')'
3046                 {
3047                   $$ = $3;
3048                 }
3049         ;
3050
3051 /* extension to support C-structures in the archiver */
3052
3053 objcencodeexpr:
3054           ENCODE '(' typename ')'
3055                 {
3056                   $$ = groktypename ($3);
3057                 }
3058         ;
3059
3060 end ifobjc
3061 %%