OSDN Git Service

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