OSDN Git Service

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