OSDN Git Service

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