OSDN Git Service

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