OSDN Git Service

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