OSDN Git Service

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