source: trunk/third/gcc/objc-parse.y @ 8834

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