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