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