OSDN Git Service

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