OSDN Git Service

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