OSDN Git Service

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