OSDN Git Service

* fix-header.c (main): Fix loop over required_functions_list
[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 35
31 end ifobjc
32 ifc
33 %expect 27
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                   decl_attributes ($<ttype>$, $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                   decl_attributes (d, $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                   decl_attributes ($<ttype>$, $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                   decl_attributes (d, $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 '(' nonnull_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                   store_parm_decls (); }
1198 /* This used to use compstmt_or_error.
1199    That caused a bug with input `f(g) int g {}',
1200    where the use of YYERROR1 above caused an error
1201    which then was handled by compstmt_or_error.
1202    There followed a repeated execution of that same rule,
1203    which called YYERROR1 again, and so on.  */
1204           compstmt
1205                 { finish_function (1);
1206                   pop_c_function_context (); }
1207         ;
1208
1209 notype_nested_function:
1210           notype_declarator
1211                 { push_c_function_context ();
1212                   if (! start_function (current_declspecs, $1,
1213                                         prefix_attributes, 1))
1214                     {
1215                       pop_c_function_context ();
1216                       YYERROR1;
1217                     }
1218                   reinit_parse_for_function ();
1219                   store_parm_decls (); }
1220 /* This used to use compstmt_or_error.
1221    That caused a bug with input `f(g) int g {}',
1222    where the use of YYERROR1 above caused an error
1223    which then was handled by compstmt_or_error.
1224    There followed a repeated execution of that same rule,
1225    which called YYERROR1 again, and so on.  */
1226           compstmt
1227                 { finish_function (1);
1228                   pop_c_function_context (); }
1229         ;
1230
1231 /* Any kind of declarator (thus, all declarators allowed
1232    after an explicit typespec).  */
1233
1234 declarator:
1235           after_type_declarator
1236         | notype_declarator
1237         ;
1238
1239 /* A declarator that is allowed only after an explicit typespec.  */
1240
1241 after_type_declarator:
1242           '(' after_type_declarator ')'
1243                 { $$ = $2; }
1244         | after_type_declarator '(' parmlist_or_identifiers  %prec '.'
1245                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1246 /*      | after_type_declarator '(' error ')'  %prec '.'
1247                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1248                   poplevel (0, 0, 0); }  */
1249         | after_type_declarator '[' expr ']'  %prec '.'
1250                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1251         | after_type_declarator '[' ']'  %prec '.'
1252                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1253         | '*' type_quals after_type_declarator  %prec UNARY
1254                 { $$ = make_pointer_declarator ($2, $3); }
1255         | attributes setattrs after_type_declarator
1256                 { $$ = $3; }
1257         | TYPENAME
1258 ifobjc
1259         | OBJECTNAME
1260 end ifobjc
1261         ;
1262
1263 /* Kinds of declarator that can appear in a parameter list
1264    in addition to notype_declarator.  This is like after_type_declarator
1265    but does not allow a typedef name in parentheses as an identifier
1266    (because it would conflict with a function with that typedef as arg).  */
1267
1268 parm_declarator:
1269           parm_declarator '(' parmlist_or_identifiers  %prec '.'
1270                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1271 /*      | parm_declarator '(' error ')'  %prec '.'
1272                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1273                   poplevel (0, 0, 0); }  */
1274         | parm_declarator '[' expr ']'  %prec '.'
1275                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1276         | parm_declarator '[' ']'  %prec '.'
1277                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1278         | '*' type_quals parm_declarator  %prec UNARY
1279                 { $$ = make_pointer_declarator ($2, $3); }
1280         | attributes setattrs parm_declarator
1281                 { $$ = $3; }
1282         | TYPENAME
1283         ;
1284
1285 /* A declarator allowed whether or not there has been
1286    an explicit typespec.  These cannot redeclare a typedef-name.  */
1287
1288 notype_declarator:
1289           notype_declarator '(' parmlist_or_identifiers  %prec '.'
1290                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1291 /*      | notype_declarator '(' error ')'  %prec '.'
1292                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1293                   poplevel (0, 0, 0); }  */
1294         | '(' notype_declarator ')'
1295                 { $$ = $2; }
1296         | '*' type_quals notype_declarator  %prec UNARY
1297                 { $$ = make_pointer_declarator ($2, $3); }
1298         | notype_declarator '[' expr ']'  %prec '.'
1299                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1300         | notype_declarator '[' ']'  %prec '.'
1301                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1302         | attributes setattrs notype_declarator
1303                 { $$ = $3; }
1304         | IDENTIFIER
1305         ;
1306
1307 structsp:
1308           STRUCT identifier '{'
1309                 { $$ = start_struct (RECORD_TYPE, $2);
1310                   /* Start scope of tag before parsing components.  */
1311                 }
1312           component_decl_list '}' maybe_attribute 
1313                 { $$ = finish_struct ($<ttype>4, $5);
1314                   decl_attributes ($$, $7, NULL_TREE);
1315                   /* Really define the structure.  */
1316                 }
1317         | STRUCT '{' component_decl_list '}' maybe_attribute
1318                 { $$ = finish_struct (start_struct (RECORD_TYPE, NULL_TREE),
1319                                       $3);
1320                   decl_attributes ($$, $5, NULL_TREE);
1321                 }
1322         | STRUCT identifier
1323                 { $$ = xref_tag (RECORD_TYPE, $2); }
1324         | UNION identifier '{'
1325                 { $$ = start_struct (UNION_TYPE, $2); }
1326           component_decl_list '}' maybe_attribute
1327                 { $$ = finish_struct ($<ttype>4, $5);
1328                   decl_attributes ($$, $7, NULL_TREE);
1329                 }
1330         | UNION '{' component_decl_list '}' maybe_attribute
1331                 { $$ = finish_struct (start_struct (UNION_TYPE, NULL_TREE),
1332                                       $3);
1333                   decl_attributes ($$, $5, NULL_TREE);
1334                 }
1335         | UNION identifier
1336                 { $$ = xref_tag (UNION_TYPE, $2); }
1337         | ENUM identifier '{'
1338                 { $<itype>3 = suspend_momentary ();
1339                   $$ = start_enum ($2); }
1340           enumlist maybecomma_warn '}'
1341                 { $$ = finish_enum ($<ttype>4, nreverse ($5));
1342                   resume_momentary ($<itype>3); }
1343         | ENUM '{'
1344                 { $<itype>2 = suspend_momentary ();
1345                   $$ = start_enum (NULL_TREE); }
1346           enumlist maybecomma_warn '}'
1347                 { $$ = finish_enum ($<ttype>3, nreverse ($4));
1348                   resume_momentary ($<itype>2); }
1349         | ENUM identifier
1350                 { $$ = xref_tag (ENUMERAL_TYPE, $2); }
1351         ;
1352
1353 maybecomma:
1354           /* empty */
1355         | ','
1356         ;
1357
1358 maybecomma_warn:
1359           /* empty */
1360         | ','
1361                 { if (pedantic) pedwarn ("comma at end of enumerator list"); }
1362         ;
1363
1364 component_decl_list:
1365           component_decl_list2
1366                 { $$ = $1; }
1367         | component_decl_list2 component_decl
1368                 { $$ = chainon ($1, $2);
1369                   pedwarn ("no semicolon at end of struct or union"); }
1370         ;
1371
1372 component_decl_list2:   /* empty */
1373                 { $$ = NULL_TREE; }
1374         | component_decl_list2 component_decl ';'
1375                 { $$ = chainon ($1, $2); }
1376         | component_decl_list2 ';'
1377                 { if (pedantic)
1378                     pedwarn ("extra semicolon in struct or union specified"); }
1379 ifobjc
1380         /* foo(sizeof(struct{ @defs(ClassName)})); */
1381         | DEFS '(' CLASSNAME ')'
1382                 {
1383                   tree interface = lookup_interface ($3);
1384
1385                   if (interface)
1386                     $$ = get_class_ivars (interface);
1387                   else
1388                     {
1389                       error ("Cannot find interface declaration for `%s'",
1390                              IDENTIFIER_POINTER ($3));
1391                       $$ = NULL_TREE;
1392                     }
1393                 }
1394 end ifobjc
1395         ;
1396
1397 /* There is a shift-reduce conflict here, because `components' may
1398    start with a `typename'.  It happens that shifting (the default resolution)
1399    does the right thing, because it treats the `typename' as part of
1400    a `typed_typespecs'.
1401
1402    It is possible that this same technique would allow the distinction
1403    between `notype_initdecls' and `initdecls' to be eliminated.
1404    But I am being cautious and not trying it.  */
1405
1406 component_decl:
1407           typed_typespecs setspecs components
1408                 { $$ = $3;
1409                   current_declspecs = TREE_VALUE (declspec_stack);
1410                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1411                   declspec_stack = TREE_CHAIN (declspec_stack);
1412                   resume_momentary ($2); }
1413         | typed_typespecs
1414                 { if (pedantic)
1415                     pedwarn ("ANSI C forbids member declarations with no members");
1416                   shadow_tag($1);
1417                   $$ = NULL_TREE; }
1418         | nonempty_type_quals setspecs components
1419                 { $$ = $3;
1420                   current_declspecs = TREE_VALUE (declspec_stack);
1421                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1422                   declspec_stack = TREE_CHAIN (declspec_stack);
1423                   resume_momentary ($2); }
1424         | nonempty_type_quals
1425                 { if (pedantic)
1426                     pedwarn ("ANSI C forbids member declarations with no members");
1427                   shadow_tag($1);
1428                   $$ = NULL_TREE; }
1429         | error
1430                 { $$ = NULL_TREE; }
1431         ;
1432
1433 components:
1434           component_declarator
1435         | components ',' component_declarator
1436                 { $$ = chainon ($1, $3); }
1437         ;
1438
1439 component_declarator:
1440           save_filename save_lineno declarator maybe_attribute
1441                 { $$ = grokfield ($1, $2, $3, current_declspecs, NULL_TREE);
1442                   decl_attributes ($$, $4, prefix_attributes); }
1443         | save_filename save_lineno
1444           declarator ':' expr_no_commas maybe_attribute
1445                 { $$ = grokfield ($1, $2, $3, current_declspecs, $5);
1446                   decl_attributes ($$, $6, prefix_attributes); }
1447         | save_filename save_lineno ':' expr_no_commas maybe_attribute
1448                 { $$ = grokfield ($1, $2, NULL_TREE, current_declspecs, $4);
1449                   decl_attributes ($$, $5, prefix_attributes); }
1450         ;
1451
1452 /* We chain the enumerators in reverse order.
1453    They are put in forward order where enumlist is used.
1454    (The order used to be significant, but no longer is so.
1455    However, we still maintain the order, just to be clean.)  */
1456
1457 enumlist:
1458           enumerator
1459         | enumlist ',' enumerator
1460                 { $$ = chainon ($3, $1); }
1461         | error
1462                 { $$ = error_mark_node; }
1463         ;
1464
1465
1466 enumerator:
1467           identifier
1468                 { $$ = build_enumerator ($1, NULL_TREE); }
1469         | identifier '=' expr_no_commas
1470                 { $$ = build_enumerator ($1, $3); }
1471         ;
1472
1473 typename:
1474         typed_typespecs absdcl
1475                 { $$ = build_tree_list ($1, $2); }
1476         | nonempty_type_quals absdcl
1477                 { $$ = build_tree_list ($1, $2); }
1478         ;
1479
1480 absdcl:   /* an absolute declarator */
1481         /* empty */
1482                 { $$ = NULL_TREE; }
1483         | absdcl1
1484         ;
1485
1486 nonempty_type_quals:
1487           TYPE_QUAL
1488                 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
1489         | nonempty_type_quals TYPE_QUAL
1490                 { $$ = tree_cons (NULL_TREE, $2, $1); }
1491         ;
1492
1493 type_quals:
1494           /* empty */
1495                 { $$ = NULL_TREE; }
1496         | type_quals TYPE_QUAL
1497                 { $$ = tree_cons (NULL_TREE, $2, $1); }
1498         ;
1499
1500 absdcl1:  /* a nonempty absolute declarator */
1501           '(' absdcl1 ')'
1502                 { $$ = $2; }
1503           /* `(typedef)1' is `int'.  */
1504         | '*' type_quals absdcl1  %prec UNARY
1505                 { $$ = make_pointer_declarator ($2, $3); }
1506         | '*' type_quals  %prec UNARY
1507                 { $$ = make_pointer_declarator ($2, NULL_TREE); }
1508         | absdcl1 '(' parmlist  %prec '.'
1509                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1510         | absdcl1 '[' expr ']'  %prec '.'
1511                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1512         | absdcl1 '[' ']'  %prec '.'
1513                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1514         | '(' parmlist  %prec '.'
1515                 { $$ = build_nt (CALL_EXPR, NULL_TREE, $2, NULL_TREE); }
1516         | '[' expr ']'  %prec '.'
1517                 { $$ = build_nt (ARRAY_REF, NULL_TREE, $2); }
1518         | '[' ']'  %prec '.'
1519                 { $$ = build_nt (ARRAY_REF, NULL_TREE, NULL_TREE); }
1520         | attributes setattrs absdcl1
1521                 { $$ = $3; }
1522         ;
1523
1524 /* at least one statement, the first of which parses without error.  */
1525 /* stmts is used only after decls, so an invalid first statement
1526    is actually regarded as an invalid decl and part of the decls.  */
1527
1528 stmts:
1529           lineno_stmt_or_label
1530         | stmts lineno_stmt_or_label
1531         | stmts errstmt
1532         ;
1533
1534 xstmts:
1535         /* empty */
1536         | stmts
1537         ;
1538
1539 errstmt:  error ';'
1540         ;
1541
1542 pushlevel:  /* empty */
1543                 { emit_line_note (input_filename, lineno);
1544                   pushlevel (0);
1545                   clear_last_expr ();
1546                   push_momentary ();
1547                   expand_start_bindings (0);
1548 ifobjc
1549                   if (objc_method_context)
1550                     add_objc_decls ();
1551 end ifobjc
1552                 }
1553         ;
1554
1555 /* Read zero or more forward-declarations for labels
1556    that nested functions can jump to.  */
1557 maybe_label_decls:
1558           /* empty */
1559         | label_decls
1560                 { if (pedantic)
1561                     pedwarn ("ANSI C forbids label declarations"); }
1562         ;
1563
1564 label_decls:
1565           label_decl
1566         | label_decls label_decl
1567         ;
1568
1569 label_decl:
1570           LABEL identifiers_or_typenames ';'
1571                 { tree link;
1572                   for (link = $2; link; link = TREE_CHAIN (link))
1573                     {
1574                       tree label = shadow_label (TREE_VALUE (link));
1575                       C_DECLARED_LABEL_FLAG (label) = 1;
1576                       declare_nonlocal_label (label);
1577                     }
1578                 }
1579         ;
1580
1581 /* This is the body of a function definition.
1582    It causes syntax errors to ignore to the next openbrace.  */
1583 compstmt_or_error:
1584           compstmt
1585                 {}
1586         | error compstmt
1587         ;
1588
1589 compstmt: '{' '}'
1590                 { $$ = convert (void_type_node, integer_zero_node); }
1591         | '{' pushlevel maybe_label_decls decls xstmts '}'
1592                 { emit_line_note (input_filename, lineno);
1593                   expand_end_bindings (getdecls (), 1, 0);
1594                   $$ = poplevel (1, 1, 0);
1595                   if (yychar == CONSTANT || yychar == STRING)
1596                     pop_momentary_nofree ();
1597                   else
1598                     pop_momentary (); }
1599         | '{' pushlevel maybe_label_decls error '}'
1600                 { emit_line_note (input_filename, lineno);
1601                   expand_end_bindings (getdecls (), kept_level_p (), 0);
1602                   $$ = poplevel (kept_level_p (), 0, 0);
1603                   if (yychar == CONSTANT || yychar == STRING)
1604                     pop_momentary_nofree ();
1605                   else
1606                     pop_momentary (); }
1607         | '{' pushlevel maybe_label_decls stmts '}'
1608                 { emit_line_note (input_filename, lineno);
1609                   expand_end_bindings (getdecls (), kept_level_p (), 0);
1610                   $$ = poplevel (kept_level_p (), 0, 0);
1611                   if (yychar == CONSTANT || yychar == STRING)
1612                     pop_momentary_nofree ();
1613                   else
1614                     pop_momentary (); }
1615         ;
1616
1617 /* Value is number of statements counted as of the closeparen.  */
1618 simple_if:
1619           if_prefix lineno_labeled_stmt
1620 /* Make sure expand_end_cond is run once
1621    for each call to expand_start_cond.
1622    Otherwise a crash is likely.  */
1623         | if_prefix error
1624         ;
1625
1626 if_prefix:
1627           IF '(' expr ')'
1628                 { emit_line_note ($<filename>-1, $<lineno>0);
1629                   expand_start_cond (truthvalue_conversion ($3), 0);
1630                   $<itype>$ = stmt_count;
1631                   if_stmt_file = $<filename>-1;
1632                   if_stmt_line = $<lineno>0;
1633                   position_after_white_space (); }
1634         ;
1635
1636 /* This is a subroutine of stmt.
1637    It is used twice, once for valid DO statements
1638    and once for catching errors in parsing the end test.  */
1639 do_stmt_start:
1640           DO
1641                 { stmt_count++;
1642                   emit_line_note ($<filename>-1, $<lineno>0);
1643                   /* See comment in `while' alternative, above.  */
1644                   emit_nop ();
1645                   expand_start_loop_continue_elsewhere (1);
1646                   position_after_white_space (); }
1647           lineno_labeled_stmt WHILE
1648                 { expand_loop_continue_here (); }
1649         ;
1650
1651 save_filename:
1652                 { $$ = input_filename; }
1653         ;
1654
1655 save_lineno:
1656                 { $$ = lineno; }
1657         ;
1658
1659 lineno_labeled_stmt:
1660           save_filename save_lineno stmt
1661                 { }
1662 /*      | save_filename save_lineno error
1663                 { }
1664 */
1665         | save_filename save_lineno label lineno_labeled_stmt
1666                 { }
1667         ;
1668
1669 lineno_stmt_or_label:
1670           save_filename save_lineno stmt_or_label
1671                 { }
1672         ;
1673
1674 stmt_or_label:
1675           stmt
1676         | label
1677                 { int next;
1678                   position_after_white_space ();
1679                   next = getc (finput);
1680                   ungetc (next, finput);
1681                   if (pedantic && next == '}')
1682                     pedwarn ("ANSI C forbids label at end of compound statement");
1683                 }
1684         ;
1685
1686 /* Parse a single real statement, not including any labels.  */
1687 stmt:
1688           compstmt
1689                 { stmt_count++; }
1690         | all_iter_stmt 
1691         | expr ';'
1692                 { stmt_count++;
1693                   emit_line_note ($<filename>-1, $<lineno>0);
1694 /* It appears that this should not be done--that a non-lvalue array
1695    shouldn't get an error if the value isn't used.
1696    Section 3.2.2.1 says that an array lvalue gets converted to a pointer
1697    if it appears as a top-level expression,
1698    but says nothing about non-lvalue arrays.  */
1699 #if 0
1700                   /* Call default_conversion to get an error
1701                      on referring to a register array if pedantic.  */
1702                   if (TREE_CODE (TREE_TYPE ($1)) == ARRAY_TYPE
1703                       || TREE_CODE (TREE_TYPE ($1)) == FUNCTION_TYPE)
1704                     $1 = default_conversion ($1);
1705 #endif
1706                   iterator_expand ($1);
1707                   clear_momentary (); }
1708         | simple_if ELSE
1709                 { expand_start_else ();
1710                   $<itype>1 = stmt_count;
1711                   position_after_white_space (); }
1712           lineno_labeled_stmt
1713                 { expand_end_cond ();
1714                   if (extra_warnings && stmt_count == $<itype>1)
1715                     warning ("empty body in an else-statement"); }
1716         | simple_if %prec IF
1717                 { expand_end_cond ();
1718                   /* This warning is here instead of in simple_if, because we
1719                      do not want a warning if an empty if is followed by an
1720                      else statement.  Increment stmt_count so we don't
1721                      give a second error if this is a nested `if'.  */
1722                   if (extra_warnings && stmt_count++ == $<itype>1)
1723                     warning_with_file_and_line (if_stmt_file, if_stmt_line,
1724                                                 "empty body in an if-statement"); }
1725 /* Make sure expand_end_cond is run once
1726    for each call to expand_start_cond.
1727    Otherwise a crash is likely.  */
1728         | simple_if ELSE error
1729                 { expand_end_cond (); }
1730         | WHILE
1731                 { stmt_count++;
1732                   emit_line_note ($<filename>-1, $<lineno>0);
1733                   /* The emit_nop used to come before emit_line_note,
1734                      but that made the nop seem like part of the preceding line.
1735                      And that was confusing when the preceding line was
1736                      inside of an if statement and was not really executed.
1737                      I think it ought to work to put the nop after the line number.
1738                      We will see.  --rms, July 15, 1991.  */
1739                   emit_nop (); }
1740           '(' expr ')'
1741                 { /* Don't start the loop till we have succeeded
1742                      in parsing the end test.  This is to make sure
1743                      that we end every loop we start.  */
1744                   expand_start_loop (1);
1745                   emit_line_note (input_filename, lineno);
1746                   expand_exit_loop_if_false (NULL_PTR,
1747                                              truthvalue_conversion ($4));
1748                   position_after_white_space (); }
1749           lineno_labeled_stmt
1750                 { expand_end_loop (); }
1751         | do_stmt_start
1752           '(' expr ')' ';'
1753                 { emit_line_note (input_filename, lineno);
1754                   expand_exit_loop_if_false (NULL_PTR,
1755                                              truthvalue_conversion ($3));
1756                   expand_end_loop ();
1757                   clear_momentary (); }
1758 /* This rule is needed to make sure we end every loop we start.  */
1759         | do_stmt_start error
1760                 { expand_end_loop ();
1761                   clear_momentary (); }
1762         | FOR
1763           '(' xexpr ';'
1764                 { stmt_count++;
1765                   emit_line_note ($<filename>-1, $<lineno>0);
1766                   /* See comment in `while' alternative, above.  */
1767                   emit_nop ();
1768                   if ($3) c_expand_expr_stmt ($3);
1769                   /* Next step is to call expand_start_loop_continue_elsewhere,
1770                      but wait till after we parse the entire for (...).
1771                      Otherwise, invalid input might cause us to call that
1772                      fn without calling expand_end_loop.  */
1773                 }
1774           xexpr ';'
1775                 /* Can't emit now; wait till after expand_start_loop...  */
1776                 { $<lineno>7 = lineno;
1777                   $<filename>$ = input_filename; }
1778           xexpr ')'
1779                 { 
1780                   /* Start the loop.  Doing this after parsing
1781                      all the expressions ensures we will end the loop.  */
1782                   expand_start_loop_continue_elsewhere (1);
1783                   /* Emit the end-test, with a line number.  */
1784                   emit_line_note ($<filename>8, $<lineno>7);
1785                   if ($6)
1786                     expand_exit_loop_if_false (NULL_PTR,
1787                                                truthvalue_conversion ($6));
1788                   /* Don't let the tree nodes for $9 be discarded by
1789                      clear_momentary during the parsing of the next stmt.  */
1790                   push_momentary ();
1791                   $<lineno>7 = lineno;
1792                   $<filename>8 = input_filename;
1793                   position_after_white_space (); }
1794           lineno_labeled_stmt
1795                 { /* Emit the increment expression, with a line number.  */
1796                   emit_line_note ($<filename>8, $<lineno>7);
1797                   expand_loop_continue_here ();
1798                   if ($9)
1799                     c_expand_expr_stmt ($9);
1800                   if (yychar == CONSTANT || yychar == STRING)
1801                     pop_momentary_nofree ();
1802                   else
1803                     pop_momentary ();
1804                   expand_end_loop (); }
1805         | SWITCH '(' expr ')'
1806                 { stmt_count++;
1807                   emit_line_note ($<filename>-1, $<lineno>0);
1808                   c_expand_start_case ($3);
1809                   /* Don't let the tree nodes for $3 be discarded by
1810                      clear_momentary during the parsing of the next stmt.  */
1811                   push_momentary ();
1812                   position_after_white_space (); }
1813           lineno_labeled_stmt
1814                 { expand_end_case ($3);
1815                   if (yychar == CONSTANT || yychar == STRING)
1816                     pop_momentary_nofree ();
1817                   else
1818                     pop_momentary (); }
1819         | BREAK ';'
1820                 { stmt_count++;
1821                   emit_line_note ($<filename>-1, $<lineno>0);
1822                   if ( ! expand_exit_something ())
1823                     error ("break statement not within loop or switch"); }
1824         | CONTINUE ';'
1825                 { stmt_count++;
1826                   emit_line_note ($<filename>-1, $<lineno>0);
1827                   if (! expand_continue_loop (NULL_PTR))
1828                     error ("continue statement not within a loop"); }
1829         | RETURN ';'
1830                 { stmt_count++;
1831                   emit_line_note ($<filename>-1, $<lineno>0);
1832                   c_expand_return (NULL_TREE); }
1833         | RETURN expr ';'
1834                 { stmt_count++;
1835                   emit_line_note ($<filename>-1, $<lineno>0);
1836                   c_expand_return ($2); }
1837         | ASM_KEYWORD maybe_type_qual '(' expr ')' ';'
1838                 { stmt_count++;
1839                   emit_line_note ($<filename>-1, $<lineno>0);
1840                   STRIP_NOPS ($4);
1841                   if ((TREE_CODE ($4) == ADDR_EXPR
1842                        && TREE_CODE (TREE_OPERAND ($4, 0)) == STRING_CST)
1843                       || TREE_CODE ($4) == STRING_CST)
1844                     expand_asm ($4);
1845                   else
1846                     error ("argument of `asm' is not a constant string"); }
1847         /* This is the case with just output operands.  */
1848         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ')' ';'
1849                 { stmt_count++;
1850                   emit_line_note ($<filename>-1, $<lineno>0);
1851                   c_expand_asm_operands ($4, $6, NULL_TREE, NULL_TREE,
1852                                          $2 == ridpointers[(int)RID_VOLATILE],
1853                                          input_filename, lineno); }
1854         /* This is the case with input operands as well.  */
1855         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':' asm_operands ')' ';'
1856                 { stmt_count++;
1857                   emit_line_note ($<filename>-1, $<lineno>0);
1858                   c_expand_asm_operands ($4, $6, $8, NULL_TREE,
1859                                          $2 == ridpointers[(int)RID_VOLATILE],
1860                                          input_filename, lineno); }
1861         /* This is the case with clobbered registers as well.  */
1862         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':'
1863           asm_operands ':' asm_clobbers ')' ';'
1864                 { stmt_count++;
1865                   emit_line_note ($<filename>-1, $<lineno>0);
1866                   c_expand_asm_operands ($4, $6, $8, $10,
1867                                          $2 == ridpointers[(int)RID_VOLATILE],
1868                                          input_filename, lineno); }
1869         | GOTO identifier ';'
1870                 { tree decl;
1871                   stmt_count++;
1872                   emit_line_note ($<filename>-1, $<lineno>0);
1873                   decl = lookup_label ($2);
1874                   if (decl != 0)
1875                     {
1876                       TREE_USED (decl) = 1;
1877                       expand_goto (decl);
1878                     }
1879                 }
1880         | GOTO '*' expr ';'
1881                 { stmt_count++;
1882                   emit_line_note ($<filename>-1, $<lineno>0);
1883                   expand_computed_goto (convert (ptr_type_node, $3)); }
1884         | ';'
1885         ;
1886
1887 all_iter_stmt:
1888           all_iter_stmt_simple
1889 /*      | all_iter_stmt_with_decl */
1890         ;
1891
1892 all_iter_stmt_simple:
1893           FOR '(' primary ')' 
1894           {
1895             /* The value returned by this action is  */
1896             /*      1 if everything is OK */ 
1897             /*      0 in case of error or already bound iterator */
1898
1899             $<itype>$ = 0;
1900             if (TREE_CODE ($3) != VAR_DECL)
1901               error ("invalid `for (ITERATOR)' syntax");
1902             else if (! ITERATOR_P ($3))
1903               error ("`%s' is not an iterator",
1904                      IDENTIFIER_POINTER (DECL_NAME ($3)));
1905             else if (ITERATOR_BOUND_P ($3))
1906               error ("`for (%s)' inside expansion of same iterator",
1907                      IDENTIFIER_POINTER (DECL_NAME ($3)));
1908             else
1909               {
1910                 $<itype>$ = 1;
1911                 iterator_for_loop_start ($3);
1912               }
1913           }
1914           lineno_labeled_stmt
1915           {
1916             if ($<itype>5)
1917               iterator_for_loop_end ($3);
1918           }
1919
1920 /*  This really should allow any kind of declaration,
1921     for generality.  Fix it before turning it back on.
1922
1923 all_iter_stmt_with_decl:
1924           FOR '(' ITERATOR pushlevel setspecs iterator_spec ')' 
1925           {
1926 */          /* The value returned by this action is  */
1927             /*      1 if everything is OK */ 
1928             /*      0 in case of error or already bound iterator */
1929 /*
1930             iterator_for_loop_start ($6);
1931           }
1932           lineno_labeled_stmt
1933           {
1934             iterator_for_loop_end ($6);
1935             emit_line_note (input_filename, lineno);
1936             expand_end_bindings (getdecls (), 1, 0);
1937             $<ttype>$ = poplevel (1, 1, 0);
1938             if (yychar == CONSTANT || yychar == STRING)
1939               pop_momentary_nofree ();
1940             else
1941               pop_momentary ();     
1942           }
1943 */
1944
1945 /* Any kind of label, including jump labels and case labels.
1946    ANSI C accepts labels only before statements, but we allow them
1947    also at the end of a compound statement.  */
1948
1949 label:    CASE expr_no_commas ':'
1950                 { register tree value = check_case_value ($2);
1951                   register tree label
1952                     = build_decl (LABEL_DECL, NULL_TREE, NULL_TREE);
1953
1954                   stmt_count++;
1955
1956                   if (value != error_mark_node)
1957                     {
1958                       tree duplicate;
1959                       int success = pushcase (value, convert_and_check,
1960                                               label, &duplicate);
1961                       if (success == 1)
1962                         error ("case label not within a switch statement");
1963                       else if (success == 2)
1964                         {
1965                           error ("duplicate case value");
1966                           error_with_decl (duplicate, "this is the first entry for that value");
1967                         }
1968                       else if (success == 3)
1969                         warning ("case value out of range");
1970                       else if (success == 5)
1971                         error ("case label within scope of cleanup or variable array");
1972                     }
1973                   position_after_white_space (); }
1974         | CASE expr_no_commas ELLIPSIS expr_no_commas ':'
1975                 { register tree value1 = check_case_value ($2);
1976                   register tree value2 = check_case_value ($4);
1977                   register tree label
1978                     = build_decl (LABEL_DECL, NULL_TREE, NULL_TREE);
1979
1980                   stmt_count++;
1981
1982                   if (value1 != error_mark_node && value2 != error_mark_node)
1983                     {
1984                       tree duplicate;
1985                       int success = pushcase_range (value1, value2,
1986                                                     convert_and_check, label,
1987                                                     &duplicate);
1988                       if (success == 1)
1989                         error ("case label not within a switch statement");
1990                       else if (success == 2)
1991                         {
1992                           error ("duplicate case value");
1993                           error_with_decl (duplicate, "this is the first entry for that value");
1994                         }
1995                       else if (success == 3)
1996                         warning ("case value out of range");
1997                       else if (success == 4)
1998                         warning ("empty case range");
1999                       else if (success == 5)
2000                         error ("case label within scope of cleanup or variable array");
2001                     }
2002                   position_after_white_space (); }
2003         | DEFAULT ':'
2004                 {
2005                   tree duplicate;
2006                   register tree label
2007                     = build_decl (LABEL_DECL, NULL_TREE, NULL_TREE);
2008                   int success = pushcase (NULL_TREE, 0, label, &duplicate);
2009                   stmt_count++;
2010                   if (success == 1)
2011                     error ("default label not within a switch statement");
2012                   else if (success == 2)
2013                     {
2014                       error ("multiple default labels in one switch");
2015                       error_with_decl (duplicate, "this is the first default label");
2016                     }
2017                   position_after_white_space (); }
2018         | identifier ':'
2019                 { tree label = define_label (input_filename, lineno, $1);
2020                   stmt_count++;
2021                   emit_nop ();
2022                   if (label)
2023                     expand_label (label);
2024                   position_after_white_space (); }
2025         ;
2026
2027 /* Either a type-qualifier or nothing.  First thing in an `asm' statement.  */
2028
2029 maybe_type_qual:
2030         /* empty */
2031                 { emit_line_note (input_filename, lineno);
2032                   $$ = NULL_TREE; }
2033         | TYPE_QUAL
2034                 { emit_line_note (input_filename, lineno); }
2035         ;
2036
2037 xexpr:
2038         /* empty */
2039                 { $$ = NULL_TREE; }
2040         | expr
2041         ;
2042
2043 /* These are the operands other than the first string and colon
2044    in  asm ("addextend %2,%1": "=dm" (x), "0" (y), "g" (*x))  */
2045 asm_operands: /* empty */
2046                 { $$ = NULL_TREE; }
2047         | nonnull_asm_operands
2048         ;
2049
2050 nonnull_asm_operands:
2051           asm_operand
2052         | nonnull_asm_operands ',' asm_operand
2053                 { $$ = chainon ($1, $3); }
2054         ;
2055
2056 asm_operand:
2057           STRING '(' expr ')'
2058                 { $$ = build_tree_list ($1, $3); }
2059         ;
2060
2061 asm_clobbers:
2062           string
2063                 { $$ = tree_cons (NULL_TREE, combine_strings ($1), NULL_TREE); }
2064         | asm_clobbers ',' string
2065                 { $$ = tree_cons (NULL_TREE, combine_strings ($3), $1); }
2066         ;
2067 \f
2068 /* This is what appears inside the parens in a function declarator.
2069    Its value is a list of ..._TYPE nodes.  */
2070 parmlist:
2071                 { pushlevel (0);
2072                   clear_parm_order ();
2073                   declare_parm_level (0); }
2074           parmlist_1
2075                 { $$ = $2;
2076                   parmlist_tags_warning ();
2077                   poplevel (0, 0, 0); }
2078         ;
2079
2080 parmlist_1:
2081           parmlist_2 ')'
2082         | parms ';'
2083                 { tree parm;
2084                   if (pedantic)
2085                     pedwarn ("ANSI C forbids forward parameter declarations");
2086                   /* Mark the forward decls as such.  */
2087                   for (parm = getdecls (); parm; parm = TREE_CHAIN (parm))
2088                     TREE_ASM_WRITTEN (parm) = 1;
2089                   clear_parm_order (); }
2090           parmlist_1
2091                 { $$ = $4; }
2092         | error ')'
2093                 { $$ = tree_cons (NULL_TREE, NULL_TREE, NULL_TREE); }
2094         ;
2095
2096 /* This is what appears inside the parens in a function declarator.
2097    Is value is represented in the format that grokdeclarator expects.  */
2098 parmlist_2:  /* empty */
2099                 { $$ = get_parm_info (0); }
2100         | ELLIPSIS
2101                 { $$ = get_parm_info (0);
2102                   /* Gcc used to allow this as an extension.  However, it does
2103                      not work for all targets, and thus has been disabled.
2104                      Also, since func (...) and func () are indistinguishable,
2105                      it caused problems with the code in expand_builtin which
2106                      tries to verify that BUILT_IN_NEXT_ARG is being used
2107                      correctly.  */
2108                   error ("ANSI C requires a named argument before `...'");
2109                 }
2110         | parms
2111                 { $$ = get_parm_info (1); }
2112         | parms ',' ELLIPSIS
2113                 { $$ = get_parm_info (0); }
2114         ;
2115
2116 parms:
2117         parm
2118                 { push_parm_decl ($1); }
2119         | parms ',' parm
2120                 { push_parm_decl ($3); }
2121         ;
2122
2123 /* A single parameter declaration or parameter type name,
2124    as found in a parmlist.  */
2125 parm:
2126           typed_declspecs parm_declarator
2127                 { $$ = build_tree_list ($1, $2) ; }
2128         | typed_declspecs notype_declarator
2129                 { $$ = build_tree_list ($1, $2) ; }
2130         | typed_declspecs absdcl
2131                 { $$ = build_tree_list ($1, $2); }
2132         | declmods notype_declarator
2133                 { $$ = build_tree_list ($1, $2) ; }
2134         | declmods absdcl
2135                 { $$ = build_tree_list ($1, $2); }
2136         ;
2137
2138 /* This is used in a function definition
2139    where either a parmlist or an identifier list is ok.
2140    Its value is a list of ..._TYPE nodes or a list of identifiers.  */
2141 parmlist_or_identifiers:
2142                 { pushlevel (0);
2143                   clear_parm_order ();
2144                   declare_parm_level (1); }
2145           parmlist_or_identifiers_1
2146                 { $$ = $2;
2147                   parmlist_tags_warning ();
2148                   poplevel (0, 0, 0); }
2149         ;
2150
2151 parmlist_or_identifiers_1:
2152           parmlist_1
2153         | identifiers ')'
2154                 { tree t;
2155                   for (t = $1; t; t = TREE_CHAIN (t))
2156                     if (TREE_VALUE (t) == NULL_TREE)
2157                       error ("`...' in old-style identifier list");
2158                   $$ = tree_cons (NULL_TREE, NULL_TREE, $1); }
2159         ;
2160
2161 /* A nonempty list of identifiers.  */
2162 identifiers:
2163         IDENTIFIER
2164                 { $$ = build_tree_list (NULL_TREE, $1); }
2165         | identifiers ',' IDENTIFIER
2166                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2167         ;
2168
2169 /* A nonempty list of identifiers, including typenames.  */
2170 identifiers_or_typenames:
2171         identifier
2172                 { $$ = build_tree_list (NULL_TREE, $1); }
2173         | identifiers_or_typenames ',' identifier
2174                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2175         ;
2176 \f
2177 ifobjc
2178 /* Objective-C productions.  */
2179
2180 objcdef:
2181           classdef
2182         | classdecl
2183         | aliasdecl
2184         | protocoldef
2185         | methoddef
2186         | END
2187                 {
2188                   if (objc_implementation_context)
2189                     {
2190                       finish_class (objc_implementation_context);
2191                       objc_ivar_chain = NULL_TREE;
2192                       objc_implementation_context = NULL_TREE;
2193                     }
2194                   else
2195                     warning ("`@end' must appear in an implementation context");
2196                 }
2197         ;
2198
2199 /* A nonempty list of identifiers.  */
2200 identifier_list:
2201         identifier
2202                 { $$ = build_tree_list (NULL_TREE, $1); }
2203         | identifier_list ',' identifier
2204                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2205         ;
2206
2207 classdecl:
2208           CLASS identifier_list ';'
2209                 {
2210                   objc_declare_class ($2);
2211                 }
2212
2213 aliasdecl:
2214           ALIAS identifier identifier ';'
2215                 {
2216                   objc_declare_alias ($2, $3);
2217                 }
2218
2219 classdef:
2220           INTERFACE identifier protocolrefs '{'
2221                 {
2222                   objc_interface_context = objc_ivar_context
2223                     = start_class (CLASS_INTERFACE_TYPE, $2, NULL_TREE, $3);
2224                   objc_public_flag = 0;
2225                 }
2226           ivar_decl_list '}'
2227                 {
2228                   continue_class (objc_interface_context);
2229                 }
2230           methodprotolist
2231           END
2232                 {
2233                   finish_class (objc_interface_context);
2234                   objc_interface_context = NULL_TREE;
2235                 }
2236
2237         | INTERFACE identifier protocolrefs
2238                 {
2239                   objc_interface_context
2240                     = start_class (CLASS_INTERFACE_TYPE, $2, NULL_TREE, $3);
2241                   continue_class (objc_interface_context);
2242                 }
2243           methodprotolist
2244           END
2245                 {
2246                   finish_class (objc_interface_context);
2247                   objc_interface_context = NULL_TREE;
2248                 }
2249
2250         | INTERFACE identifier ':' identifier protocolrefs '{'
2251                 {
2252                   objc_interface_context = objc_ivar_context
2253                     = start_class (CLASS_INTERFACE_TYPE, $2, $4, $5);
2254                   objc_public_flag = 0;
2255                 }
2256           ivar_decl_list '}'
2257                 {
2258                   continue_class (objc_interface_context);
2259                 }
2260           methodprotolist
2261           END
2262                 {
2263                   finish_class (objc_interface_context);
2264                   objc_interface_context = NULL_TREE;
2265                 }
2266
2267         | INTERFACE identifier ':' identifier protocolrefs
2268                 {
2269                   objc_interface_context
2270                     = start_class (CLASS_INTERFACE_TYPE, $2, $4, $5);
2271                   continue_class (objc_interface_context);
2272                 }
2273           methodprotolist
2274           END
2275                 {
2276                   finish_class (objc_interface_context);
2277                   objc_interface_context = NULL_TREE;
2278                 }
2279
2280         | IMPLEMENTATION identifier '{'
2281                 {
2282                   objc_implementation_context = objc_ivar_context
2283                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, NULL_TREE, NULL_TREE);
2284                   objc_public_flag = 0;
2285                 }
2286           ivar_decl_list '}'
2287                 {
2288                   objc_ivar_chain
2289                     = continue_class (objc_implementation_context);
2290                 }
2291
2292         | IMPLEMENTATION identifier
2293                 {
2294                   objc_implementation_context
2295                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, NULL_TREE, NULL_TREE);
2296                   objc_ivar_chain
2297                     = continue_class (objc_implementation_context);
2298                 }
2299
2300         | IMPLEMENTATION identifier ':' identifier '{'
2301                 {
2302                   objc_implementation_context = objc_ivar_context
2303                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2304                   objc_public_flag = 0;
2305                 }
2306           ivar_decl_list '}'
2307                 {
2308                   objc_ivar_chain
2309                     = continue_class (objc_implementation_context);
2310                 }
2311
2312         | IMPLEMENTATION identifier ':' identifier
2313                 {
2314                   objc_implementation_context
2315                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2316                   objc_ivar_chain
2317                     = continue_class (objc_implementation_context);
2318                 }
2319
2320         | INTERFACE identifier '(' identifier ')' protocolrefs
2321                 {
2322                   objc_interface_context
2323                     = start_class (CATEGORY_INTERFACE_TYPE, $2, $4, $6);
2324                   continue_class (objc_interface_context);
2325                 }
2326           methodprotolist
2327           END
2328                 {
2329                   finish_class (objc_interface_context);
2330                   objc_interface_context = NULL_TREE;
2331                 }
2332
2333         | IMPLEMENTATION identifier '(' identifier ')'
2334                 {
2335                   objc_implementation_context
2336                     = start_class (CATEGORY_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2337                   objc_ivar_chain
2338                     = continue_class (objc_implementation_context);
2339                 }
2340         ;
2341
2342 protocoldef:
2343           PROTOCOL identifier protocolrefs
2344                 {
2345                   remember_protocol_qualifiers ();
2346                   objc_interface_context
2347                     = start_protocol(PROTOCOL_INTERFACE_TYPE, $2, $3);
2348                 }
2349           methodprotolist END
2350                 {
2351                   forget_protocol_qualifiers();
2352                   finish_protocol(objc_interface_context);
2353                   objc_interface_context = NULL_TREE;
2354                 }
2355         ;
2356
2357 protocolrefs:
2358           /* empty */
2359                 {
2360                   $$ = NULL_TREE;
2361                 }
2362         | ARITHCOMPARE identifier_list ARITHCOMPARE
2363                 {
2364                   if ($1 == LT_EXPR && $3 == GT_EXPR)
2365                     $$ = $2;
2366                   else
2367                     YYERROR1;
2368                 }
2369         ;
2370
2371 ivar_decl_list:
2372           ivar_decl_list visibility_spec ivar_decls
2373         | ivar_decls
2374         ;
2375
2376 visibility_spec:
2377           PRIVATE { objc_public_flag = 2; }
2378         | PROTECTED { objc_public_flag = 0; }
2379         | PUBLIC { objc_public_flag = 1; }
2380         ;
2381
2382 ivar_decls:
2383           /* empty */
2384                 {
2385                   $$ = NULL_TREE;
2386                 }
2387         | ivar_decls ivar_decl ';'
2388         | ivar_decls ';'
2389                 {
2390                   if (pedantic)
2391                     pedwarn ("extra semicolon in struct or union specified");
2392                 }
2393         ;
2394
2395
2396 /* There is a shift-reduce conflict here, because `components' may
2397    start with a `typename'.  It happens that shifting (the default resolution)
2398    does the right thing, because it treats the `typename' as part of
2399    a `typed_typespecs'.
2400
2401    It is possible that this same technique would allow the distinction
2402    between `notype_initdecls' and `initdecls' to be eliminated.
2403    But I am being cautious and not trying it.  */
2404
2405 ivar_decl:
2406         typed_typespecs setspecs ivars
2407                 {
2408                   $$ = $3;
2409                   resume_momentary ($2);
2410                 }
2411         | nonempty_type_quals setspecs ivars
2412                 {
2413                   $$ = $3;
2414                   resume_momentary ($2);
2415                 }
2416         | error
2417                 { $$ = NULL_TREE; }
2418         ;
2419
2420 ivars:
2421           /* empty */
2422                 { $$ = NULL_TREE; }
2423         | ivar_declarator
2424         | ivars ',' ivar_declarator
2425         ;
2426
2427 ivar_declarator:
2428           declarator
2429                 {
2430                   $$ = add_instance_variable (objc_ivar_context,
2431                                               objc_public_flag,
2432                                               $1, current_declspecs,
2433                                               NULL_TREE);
2434                 }
2435         | declarator ':' expr_no_commas
2436                 {
2437                   $$ = add_instance_variable (objc_ivar_context,
2438                                               objc_public_flag,
2439                                               $1, current_declspecs, $3);
2440                 }
2441         | ':' expr_no_commas
2442                 {
2443                   $$ = add_instance_variable (objc_ivar_context,
2444                                               objc_public_flag,
2445                                               NULL_TREE,
2446                                               current_declspecs, $2);
2447                 }
2448         ;
2449
2450 methoddef:
2451           '+'
2452                 {
2453                   remember_protocol_qualifiers ();
2454                   if (objc_implementation_context)
2455                     objc_inherit_code = CLASS_METHOD_DECL;
2456                   else
2457                     fatal ("method definition not in class context");
2458                 }
2459           methoddecl
2460                 {
2461                   forget_protocol_qualifiers ();
2462                   add_class_method (objc_implementation_context, $3);
2463                   start_method_def ($3);
2464                   objc_method_context = $3;
2465                 }
2466           optarglist
2467                 {
2468                   continue_method_def ();
2469                 }
2470           compstmt_or_error
2471                 {
2472                   finish_method_def ();
2473                   objc_method_context = NULL_TREE;
2474                 }
2475
2476         | '-'
2477                 {
2478                   remember_protocol_qualifiers ();
2479                   if (objc_implementation_context)
2480                     objc_inherit_code = INSTANCE_METHOD_DECL;
2481                   else
2482                     fatal ("method definition not in class context");
2483                 }
2484           methoddecl
2485                 {
2486                   forget_protocol_qualifiers ();
2487                   add_instance_method (objc_implementation_context, $3);
2488                   start_method_def ($3);
2489                   objc_method_context = $3;
2490                 }
2491           optarglist
2492                 {
2493                   continue_method_def ();
2494                 }
2495           compstmt_or_error
2496                 {
2497                   finish_method_def ();
2498                   objc_method_context = NULL_TREE;
2499                 }
2500         ;
2501
2502 /* the reason for the strange actions in this rule
2503  is so that notype_initdecls when reached via datadef
2504  can find a valid list of type and sc specs in $0. */
2505
2506 methodprotolist:
2507           /* empty  */
2508         | {$<ttype>$ = NULL_TREE; } methodprotolist2
2509         ;
2510
2511 methodprotolist2:                /* eliminates a shift/reduce conflict */
2512            methodproto
2513         |  datadef
2514         | methodprotolist2 methodproto
2515         | methodprotolist2 {$<ttype>$ = NULL_TREE; } datadef
2516         ;
2517
2518 semi_or_error:
2519           ';'
2520         | error
2521         ;
2522
2523 methodproto:
2524           '+'
2525                 {
2526                   objc_inherit_code = CLASS_METHOD_DECL;
2527                 }
2528           methoddecl
2529                 {
2530                   add_class_method (objc_interface_context, $3);
2531                 }
2532           semi_or_error
2533
2534         | '-'
2535                 {
2536                   objc_inherit_code = INSTANCE_METHOD_DECL;
2537                 }
2538           methoddecl
2539                 {
2540                   add_instance_method (objc_interface_context, $3);
2541                 }
2542           semi_or_error
2543         ;
2544
2545 methoddecl:
2546           '(' typename ')' unaryselector
2547                 {
2548                   $$ = build_method_decl (objc_inherit_code, $2, $4, NULL_TREE);
2549                 }
2550
2551         | unaryselector
2552                 {
2553                   $$ = build_method_decl (objc_inherit_code, NULL_TREE, $1, NULL_TREE);
2554                 }
2555
2556         | '(' typename ')' keywordselector optparmlist
2557                 {
2558                   $$ = build_method_decl (objc_inherit_code, $2, $4, $5);
2559                 }
2560
2561         | keywordselector optparmlist
2562                 {
2563                   $$ = build_method_decl (objc_inherit_code, NULL_TREE, $1, $2);
2564                 }
2565         ;
2566
2567 /* "optarglist" assumes that start_method_def has already been called...
2568    if it is not, the "xdecls" will not be placed in the proper scope */
2569
2570 optarglist:
2571           /* empty */
2572         | ';' myxdecls
2573         ;
2574
2575 /* to get around the following situation: "int foo (int a) int b; {}" that
2576    is synthesized when parsing "- a:a b:b; id c; id d; { ... }" */
2577
2578 myxdecls:
2579           /* empty */
2580         | mydecls
2581         ;
2582
2583 mydecls:
2584         mydecl
2585         | errstmt
2586         | mydecls mydecl
2587         | mydecl errstmt
2588         ;
2589
2590 mydecl:
2591         typed_declspecs setspecs myparms ';'
2592                 { resume_momentary ($2); }
2593         | typed_declspecs ';'
2594                 { shadow_tag ($1); }
2595         | declmods ';'
2596                 { pedwarn ("empty declaration"); }
2597         ;
2598
2599 myparms:
2600         myparm
2601                 { push_parm_decl ($1); }
2602         | myparms ',' myparm
2603                 { push_parm_decl ($3); }
2604         ;
2605
2606 /* A single parameter declaration or parameter type name,
2607    as found in a parmlist. DOES NOT ALLOW AN INITIALIZER OR ASMSPEC */
2608
2609 myparm:
2610           parm_declarator
2611                 { $$ = build_tree_list (current_declspecs, $1)  ; }
2612         | notype_declarator
2613                 { $$ = build_tree_list (current_declspecs, $1)  ; }
2614         | absdcl
2615                 { $$ = build_tree_list (current_declspecs, $1)  ; }
2616         ;
2617
2618 optparmlist:
2619           /* empty */
2620                 {
2621                   $$ = NULL_TREE;
2622                 }
2623         | ',' ELLIPSIS
2624                 {
2625                   /* oh what a kludge! */
2626                   $$ = (tree)1;
2627                 }
2628         | ','
2629                 {
2630                   pushlevel (0);
2631                 }
2632           parmlist_2
2633                 {
2634                   /* returns a tree list node generated by get_parm_info */
2635                   $$ = $3;
2636                   poplevel (0, 0, 0);
2637                 }
2638         ;
2639
2640 unaryselector:
2641           selector
2642         ;
2643
2644 keywordselector:
2645           keyworddecl
2646
2647         | keywordselector keyworddecl
2648                 {
2649                   $$ = chainon ($1, $2);
2650                 }
2651         ;
2652
2653 selector:
2654           IDENTIFIER
2655         | TYPENAME
2656         | OBJECTNAME
2657         | reservedwords
2658         ;
2659
2660 reservedwords:
2661           ENUM { $$ = get_identifier (token_buffer); }
2662         | STRUCT { $$ = get_identifier (token_buffer); }
2663         | UNION { $$ = get_identifier (token_buffer); }
2664         | IF { $$ = get_identifier (token_buffer); }
2665         | ELSE { $$ = get_identifier (token_buffer); }
2666         | WHILE { $$ = get_identifier (token_buffer); }
2667         | DO { $$ = get_identifier (token_buffer); }
2668         | FOR { $$ = get_identifier (token_buffer); }
2669         | SWITCH { $$ = get_identifier (token_buffer); }
2670         | CASE { $$ = get_identifier (token_buffer); }
2671         | DEFAULT { $$ = get_identifier (token_buffer); }
2672         | BREAK { $$ = get_identifier (token_buffer); }
2673         | CONTINUE { $$ = get_identifier (token_buffer); }
2674         | RETURN  { $$ = get_identifier (token_buffer); }
2675         | GOTO { $$ = get_identifier (token_buffer); }
2676         | ASM_KEYWORD { $$ = get_identifier (token_buffer); }
2677         | SIZEOF { $$ = get_identifier (token_buffer); }
2678         | TYPEOF { $$ = get_identifier (token_buffer); }
2679         | ALIGNOF { $$ = get_identifier (token_buffer); }
2680         | TYPESPEC | TYPE_QUAL
2681         ;
2682
2683 keyworddecl:
2684           selector ':' '(' typename ')' identifier
2685                 {
2686                   $$ = build_keyword_decl ($1, $4, $6);
2687                 }
2688
2689         | selector ':' identifier
2690                 {
2691                   $$ = build_keyword_decl ($1, NULL_TREE, $3);
2692                 }
2693
2694         | ':' '(' typename ')' identifier
2695                 {
2696                   $$ = build_keyword_decl (NULL_TREE, $3, $5);
2697                 }
2698
2699         | ':' identifier
2700                 {
2701                   $$ = build_keyword_decl (NULL_TREE, NULL_TREE, $2);
2702                 }
2703         ;
2704
2705 messageargs:
2706           selector
2707         | keywordarglist
2708         ;
2709
2710 keywordarglist:
2711           keywordarg
2712         | keywordarglist keywordarg
2713                 {
2714                   $$ = chainon ($1, $2);
2715                 }
2716         ;
2717
2718
2719 keywordexpr:
2720           nonnull_exprlist
2721                 {
2722                   if (TREE_CHAIN ($1) == NULL_TREE)
2723                     /* just return the expr., remove a level of indirection */
2724                     $$ = TREE_VALUE ($1);
2725                   else
2726                     /* we have a comma expr., we will collapse later */
2727                     $$ = $1;
2728                 }
2729         ;
2730
2731 keywordarg:
2732           selector ':' keywordexpr
2733                 {
2734                   $$ = build_tree_list ($1, $3);
2735                 }
2736         | ':' keywordexpr
2737                 {
2738                   $$ = build_tree_list (NULL_TREE, $2);
2739                 }
2740         ;
2741
2742 receiver:
2743           expr
2744         | CLASSNAME
2745                 {
2746                   $$ = get_class_reference ($1);
2747                 }
2748         ;
2749
2750 objcmessageexpr:
2751           '['
2752                 { objc_receiver_context = 1; }
2753           receiver
2754                 { objc_receiver_context = 0; }
2755           messageargs ']'
2756                 {
2757                   $$ = build_tree_list ($3, $5);
2758                 }
2759         ;
2760
2761 selectorarg:
2762           selector
2763         | keywordnamelist
2764         ;
2765
2766 keywordnamelist:
2767           keywordname
2768         | keywordnamelist keywordname
2769                 {
2770                   $$ = chainon ($1, $2);
2771                 }
2772         ;
2773
2774 keywordname:
2775           selector ':'
2776                 {
2777                   $$ = build_tree_list ($1, NULL_TREE);
2778                 }
2779         | ':'
2780                 {
2781                   $$ = build_tree_list (NULL_TREE, NULL_TREE);
2782                 }
2783         ;
2784
2785 objcselectorexpr:
2786           SELECTOR '(' selectorarg ')'
2787                 {
2788                   $$ = $3;
2789                 }
2790         ;
2791
2792 objcprotocolexpr:
2793           PROTOCOL '(' identifier ')'
2794                 {
2795                   $$ = $3;
2796                 }
2797         ;
2798
2799 /* extension to support C-structures in the archiver */
2800
2801 objcencodeexpr:
2802           ENCODE '(' typename ')'
2803                 {
2804                   $$ = groktypename ($3);
2805                 }
2806         ;
2807
2808 end ifobjc
2809 %%