OSDN Git Service

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