OSDN Git Service

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