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