OSDN Git Service

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