OSDN Git Service

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