OSDN Git Service

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