OSDN Git Service

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