OSDN Git Service

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