OSDN Git Service

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