OSDN Git Service

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