OSDN Git Service

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