OSDN Git Service

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