* cse.c (cse_insn): Initialise all regcost variables.
[official-gcc.git] / gcc / c-parse.in
blob5943fa4024a0ae72c0a7a1542248e7be7a40a982
1 /* YACC parser for C syntax and for Objective C.  -*-c-*-
2    Copyright (C) 1987, 1988, 1989, 1992, 1993, 1994, 1995, 1996,
3    1997, 1998, 1999, 2000 Free Software Foundation, Inc.
5 This file is part of GNU CC.
7 GNU CC is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 2, or (at your option)
10 any later version.
12 GNU CC is distributed in the hope that it will be useful,
13 but WITHOUT ANY WARRANTY; without even the implied warranty of
14 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15 GNU General Public License for more details.
17 You should have received a copy of the GNU General Public License
18 along with GNU CC; see the file COPYING.  If not, write to
19 the Free Software Foundation, 59 Temple Place - Suite 330,
20 Boston, MA 02111-1307, USA.  */
22 /* This file defines the grammar of C and that of Objective C.
23    ifobjc ... end ifobjc  conditionals contain code for Objective C only.
24    ifc ... end ifc  conditionals contain code for C only.
25    Sed commands in Makefile.in are used to convert this file into
26    c-parse.y and into objc-parse.y.  */
28 /* To whomever it may concern: I have heard that such a thing was once
29    written by AT&T, but I have never seen it.  */
31 ifobjc
32 %expect 74
33 end ifobjc
34 ifc
35 %expect 53
36 end ifc
39 #include "config.h"
40 #include "system.h"
41 #include <setjmp.h>
42 #include "tree.h"
43 #include "input.h"
44 #include "cpplib.h"
45 #include "intl.h"
46 #include "timevar.h"
47 #include "c-lex.h"
48 #include "c-tree.h"
49 #include "c-pragma.h"
50 #include "flags.h"
51 #include "output.h"
52 #include "toplev.h"
53 #include "ggc.h"
54   
55 #ifdef MULTIBYTE_CHARS
56 #include <locale.h>
57 #endif
59 ifobjc
60 #include "objc-act.h"
61 end ifobjc
63 /* Since parsers are distinct for each language, put the language string
64    definition here.  */
65 ifobjc
66 const char * const language_string = "GNU Objective-C";
67 end ifobjc
68 ifc
69 const char * const language_string = "GNU C";
70 end ifc
72 /* Like YYERROR but do call yyerror.  */
73 #define YYERROR1 { yyerror ("syntax error"); YYERROR; }
75 /* Cause the "yydebug" variable to be defined.  */
76 #define YYDEBUG 1
78 /* Rename the "yyparse" function so that we can override it elsewhere.  */
79 #define yyparse yyparse_1
82 %start program
84 %union {long itype; tree ttype; enum tree_code code;
85         const char *filename; int lineno; }
87 /* All identifiers that are not reserved words
88    and are not declared typedefs in the current block */
89 %token IDENTIFIER
91 /* All identifiers that are declared typedefs in the current block.
92    In some contexts, they are treated just like IDENTIFIER,
93    but they can also serve as typespecs in declarations.  */
94 %token TYPENAME
96 /* Reserved words that specify storage class.
97    yylval contains an IDENTIFIER_NODE which indicates which one.  */
98 %token SCSPEC
100 /* Reserved words that specify type.
101    yylval contains an IDENTIFIER_NODE which indicates which one.  */
102 %token TYPESPEC
104 /* Reserved words that qualify type: "const", "volatile", or "restrict".
105    yylval contains an IDENTIFIER_NODE which indicates which one.  */
106 %token TYPE_QUAL
108 /* Character or numeric constants.
109    yylval is the node for the constant.  */
110 %token CONSTANT
112 /* String constants in raw form.
113    yylval is a STRING_CST node.  */
114 %token STRING
116 /* "...", used for functions with variable arglists.  */
117 %token ELLIPSIS
119 /* the reserved words */
120 /* SCO include files test "ASM", so use something else. */
121 %token SIZEOF ENUM STRUCT UNION IF ELSE WHILE DO FOR SWITCH CASE DEFAULT
122 %token BREAK CONTINUE RETURN GOTO ASM_KEYWORD TYPEOF ALIGNOF
123 %token ATTRIBUTE EXTENSION LABEL
124 %token REALPART IMAGPART VA_ARG
125 %token PTR_VALUE PTR_BASE PTR_EXTENT
127 /* Add precedence rules to solve dangling else s/r conflict */
128 %nonassoc IF
129 %nonassoc ELSE
131 /* Define the operator tokens and their precedences.
132    The value is an integer because, if used, it is the tree code
133    to use in the expression made from the operator.  */
135 %right <code> ASSIGN '='
136 %right <code> '?' ':'
137 %left <code> OROR
138 %left <code> ANDAND
139 %left <code> '|'
140 %left <code> '^'
141 %left <code> '&'
142 %left <code> EQCOMPARE
143 %left <code> ARITHCOMPARE
144 %left <code> LSHIFT RSHIFT
145 %left <code> '+' '-'
146 %left <code> '*' '/' '%'
147 %right <code> UNARY PLUSPLUS MINUSMINUS
148 %left HYPERUNARY
149 %left <code> POINTSAT '.' '(' '['
151 /* The Objective-C keywords.  These are included in C and in
152    Objective C, so that the token codes are the same in both.  */
153 %token INTERFACE IMPLEMENTATION END SELECTOR DEFS ENCODE
154 %token CLASSNAME PUBLIC PRIVATE PROTECTED PROTOCOL OBJECTNAME CLASS ALIAS
156 /* Objective-C string constants in raw form.
157    yylval is an STRING_CST node.  */
158 %token OBJC_STRING
161 %type <code> unop
162 %type <ttype> ENUM STRUCT UNION IF ELSE WHILE DO FOR SWITCH CASE DEFAULT
163 %type <ttype> BREAK CONTINUE RETURN GOTO ASM_KEYWORD SIZEOF TYPEOF ALIGNOF
165 %type <ttype> identifier IDENTIFIER TYPENAME CONSTANT expr nonnull_exprlist exprlist
166 %type <ttype> expr_no_commas cast_expr unary_expr primary string STRING
167 %type <ttype> typed_declspecs reserved_declspecs
168 %type <ttype> typed_typespecs reserved_typespecquals
169 %type <ttype> declmods typespec typespecqual_reserved
170 %type <ttype> typed_declspecs_no_prefix_attr reserved_declspecs_no_prefix_attr
171 %type <ttype> declmods_no_prefix_attr
172 %type <ttype> SCSPEC TYPESPEC TYPE_QUAL nonempty_type_quals maybe_type_qual
173 %type <ttype> initdecls notype_initdecls initdcl notype_initdcl
174 %type <ttype> init maybeasm
175 %type <ttype> asm_operands nonnull_asm_operands asm_operand asm_clobbers
176 %type <ttype> maybe_attribute attributes attribute attribute_list attrib
177 %type <ttype> any_word extension
179 %type <ttype> compstmt compstmt_start compstmt_nostart compstmt_primary_start
180 %type <ttype> do_stmt_start poplevel
182 %type <ttype> c99_block_start c99_block_end
183 %type <ttype> declarator
184 %type <ttype> notype_declarator after_type_declarator
185 %type <ttype> parm_declarator
187 %type <ttype> structsp component_decl_list component_decl_list2
188 %type <ttype> component_decl components component_declarator
189 %type <ttype> enumlist enumerator
190 %type <ttype> struct_head union_head enum_head
191 %type <ttype> typename absdcl absdcl1 type_quals
192 %type <ttype> xexpr parms parm identifiers
194 %type <ttype> parmlist parmlist_1 parmlist_2
195 %type <ttype> parmlist_or_identifiers parmlist_or_identifiers_1
196 %type <ttype> identifiers_or_typenames
198 %type <itype> setspecs
200 %type <filename> save_filename
201 %type <lineno> save_lineno
203 ifobjc
204 /* the Objective-C nonterminals */
206 %type <ttype> ivar_decl_list ivar_decls ivar_decl ivars ivar_declarator
207 %type <ttype> methoddecl unaryselector keywordselector selector
208 %type <ttype> keyworddecl receiver objcmessageexpr messageargs
209 %type <ttype> keywordexpr keywordarglist keywordarg
210 %type <ttype> myparms myparm optparmlist reservedwords objcselectorexpr
211 %type <ttype> selectorarg keywordnamelist keywordname objcencodeexpr
212 %type <ttype> objc_string non_empty_protocolrefs protocolrefs identifier_list objcprotocolexpr
214 %type <ttype> CLASSNAME OBJC_STRING OBJECTNAME
215 end ifobjc
218 /* Number of statements (loosely speaking) and compound statements 
219    seen so far.  */
220 static int stmt_count;
221 static int compstmt_count;
222   
223 /* Input file and line number of the end of the body of last simple_if;
224    used by the stmt-rule immediately after simple_if returns.  */
225 static const char *if_stmt_file;
226 static int if_stmt_line;
228 /* List of types and structure classes of the current declaration.  */
229 static tree current_declspecs = NULL_TREE;
230 static tree prefix_attributes = NULL_TREE;
232 /* Stack of saved values of current_declspecs and prefix_attributes.  */
233 static tree declspec_stack;
235 /* For __extension__, save/restore the warning flags which are
236    controlled by __extension__.  */
237 #define SAVE_WARN_FLAGS()       \
238         size_int (pedantic | (warn_pointer_arith << 1))
239 #define RESTORE_WARN_FLAGS(tval) \
240   do {                                     \
241     int val = tree_low_cst (tval, 0);      \
242     pedantic = val & 1;                    \
243     warn_pointer_arith = (val >> 1) & 1;   \
244   } while (0)
246 ifobjc
247 /* Objective-C specific information */
249 tree objc_interface_context;
250 tree objc_implementation_context;
251 tree objc_method_context;
252 tree objc_ivar_chain;
253 tree objc_ivar_context;
254 enum tree_code objc_inherit_code;
255 int objc_receiver_context;
256 int objc_public_flag;
258 end ifobjc
260 /* Tell yyparse how to print a token's value, if yydebug is set.  */
262 #define YYPRINT(FILE,YYCHAR,YYLVAL) yyprint(FILE,YYCHAR,YYLVAL)
264 static void yyprint       PARAMS ((FILE *, int, YYSTYPE));
265 static void yyerror       PARAMS ((const char *));
266 static inline int _yylex  PARAMS ((void));
267 static int  yylex         PARAMS ((void));
268 static void init_reswords PARAMS ((void));
270 /* Add GC roots for variables local to this file.  */
271 void
272 c_parse_init ()
274   ggc_add_tree_root (&declspec_stack, 1);
275   ggc_add_tree_root (&current_declspecs, 1);
276   ggc_add_tree_root (&prefix_attributes, 1);
277 ifobjc
278   ggc_add_tree_root (&objc_interface_context, 1);
279   ggc_add_tree_root (&objc_implementation_context, 1);
280   ggc_add_tree_root (&objc_method_context, 1);
281   ggc_add_tree_root (&objc_ivar_chain, 1);
282   ggc_add_tree_root (&objc_ivar_context, 1);
283 end ifobjc
289 program: /* empty */
290                 { if (pedantic)
291                     pedwarn ("ISO C forbids an empty source file");
292                   finish_file ();
293                 }
294         | extdefs
295                 {
296                   /* In case there were missing closebraces,
297                      get us back to the global binding level.  */
298                   while (! global_bindings_p ())
299                     poplevel (0, 0, 0);
300                   finish_file ();
301                 }
302         ;
304 /* the reason for the strange actions in this rule
305  is so that notype_initdecls when reached via datadef
306  can find a valid list of type and sc specs in $0. */
308 extdefs:
309         {$<ttype>$ = NULL_TREE; } extdef
310         | extdefs {$<ttype>$ = NULL_TREE; ggc_collect(); } extdef
311         ;
313 extdef:
314         fndef
315         | datadef
316 ifobjc
317         | objcdef
318 end ifobjc
319         | ASM_KEYWORD '(' expr ')' ';'
320                 { STRIP_NOPS ($3);
321                   if ((TREE_CODE ($3) == ADDR_EXPR
322                        && TREE_CODE (TREE_OPERAND ($3, 0)) == STRING_CST)
323                       || TREE_CODE ($3) == STRING_CST)
324                     assemble_asm ($3);
325                   else
326                     error ("argument of `asm' is not a constant string"); }
327         | extension extdef
328                 { RESTORE_WARN_FLAGS ($1); }
329         ;
331 datadef:
332           setspecs notype_initdecls ';'
333                 { if (pedantic)
334                     error ("ISO C forbids data definition with no type or storage class");
335                   else if (!flag_traditional)
336                     warning ("data definition has no type or storage class"); 
338                   current_declspecs = TREE_VALUE (declspec_stack);
339                   prefix_attributes = TREE_PURPOSE (declspec_stack);
340                   declspec_stack = TREE_CHAIN (declspec_stack); }
341         | declmods setspecs notype_initdecls ';'
342                 { current_declspecs = TREE_VALUE (declspec_stack);
343                   prefix_attributes = TREE_PURPOSE (declspec_stack);
344                   declspec_stack = TREE_CHAIN (declspec_stack); }
345         | typed_declspecs setspecs initdecls ';'
346                 { current_declspecs = TREE_VALUE (declspec_stack);
347                   prefix_attributes = TREE_PURPOSE (declspec_stack);
348                   declspec_stack = TREE_CHAIN (declspec_stack); }
349         | declmods ';'
350           { pedwarn ("empty declaration"); }
351         | typed_declspecs ';'
352           { shadow_tag ($1); }
353         | error ';'
354         | error '}'
355         | ';'
356                 { if (pedantic)
357                     pedwarn ("ISO C does not allow extra `;' outside of a function"); }
358         ;
360 fndef:
361           typed_declspecs setspecs declarator
362                 { if (! start_function (current_declspecs, $3,
363                                         prefix_attributes, NULL_TREE))
364                     YYERROR1;
365                 }
366           old_style_parm_decls
367                 { store_parm_decls (); }
368           compstmt_or_error
369                 { finish_function (0); 
370                   current_declspecs = TREE_VALUE (declspec_stack);
371                   prefix_attributes = TREE_PURPOSE (declspec_stack);
372                   declspec_stack = TREE_CHAIN (declspec_stack); }
373         | typed_declspecs setspecs declarator error
374                 { current_declspecs = TREE_VALUE (declspec_stack);
375                   prefix_attributes = TREE_PURPOSE (declspec_stack);
376                   declspec_stack = TREE_CHAIN (declspec_stack); }
377         | declmods setspecs notype_declarator
378                 { if (! start_function (current_declspecs, $3,
379                                         prefix_attributes, NULL_TREE))
380                     YYERROR1;
381                 }
382           old_style_parm_decls
383                 { store_parm_decls (); }
384           compstmt_or_error
385                 { finish_function (0); 
386                   current_declspecs = TREE_VALUE (declspec_stack);
387                   prefix_attributes = TREE_PURPOSE (declspec_stack);
388                   declspec_stack = TREE_CHAIN (declspec_stack); }
389         | declmods setspecs notype_declarator error
390                 { current_declspecs = TREE_VALUE (declspec_stack);
391                   prefix_attributes = TREE_PURPOSE (declspec_stack);
392                   declspec_stack = TREE_CHAIN (declspec_stack); }
393         | setspecs notype_declarator
394                 { if (! start_function (NULL_TREE, $2,
395                                         prefix_attributes, NULL_TREE))
396                     YYERROR1;
397                 }
398           old_style_parm_decls
399                 { store_parm_decls (); }
400           compstmt_or_error
401                 { finish_function (0); 
402                   current_declspecs = TREE_VALUE (declspec_stack);
403                   prefix_attributes = TREE_PURPOSE (declspec_stack);
404                   declspec_stack = TREE_CHAIN (declspec_stack); }
405         | setspecs notype_declarator error
406                 { current_declspecs = TREE_VALUE (declspec_stack);
407                   prefix_attributes = TREE_PURPOSE (declspec_stack);
408                   declspec_stack = TREE_CHAIN (declspec_stack); }
409         ;
411 identifier:
412         IDENTIFIER
413         | TYPENAME
414 ifobjc
415         | OBJECTNAME
416         | CLASSNAME
417 end ifobjc
418         ;
420 unop:     '&'
421                 { $$ = ADDR_EXPR; }
422         | '-'
423                 { $$ = NEGATE_EXPR; }
424         | '+'
425                 { $$ = CONVERT_EXPR;
427   if (warn_traditional && !in_system_header)
428     warning ("traditional C rejects the unary plus operator");
429 end ifc
430                 }
431         | PLUSPLUS
432                 { $$ = PREINCREMENT_EXPR; }
433         | MINUSMINUS
434                 { $$ = PREDECREMENT_EXPR; }
435         | '~'
436                 { $$ = BIT_NOT_EXPR; }
437         | '!'
438                 { $$ = TRUTH_NOT_EXPR; }
439         ;
441 expr:   nonnull_exprlist
442                 { $$ = build_compound_expr ($1); }
443         ;
445 exprlist:
446           /* empty */
447                 { $$ = NULL_TREE; }
448         | nonnull_exprlist
449         ;
451 nonnull_exprlist:
452         expr_no_commas
453                 { $$ = build_tree_list (NULL_TREE, $1); }
454         | nonnull_exprlist ',' expr_no_commas
455                 { chainon ($1, build_tree_list (NULL_TREE, $3)); }
456         ;
458 unary_expr:
459         primary
460         | '*' cast_expr   %prec UNARY
461                 { $$ = build_indirect_ref ($2, "unary *"); }
462         /* __extension__ turns off -pedantic for following primary.  */
463         | extension cast_expr     %prec UNARY
464                 { $$ = $2;
465                   RESTORE_WARN_FLAGS ($1); }
466         | unop cast_expr  %prec UNARY
467                 { $$ = build_unary_op ($1, $2, 0);
468                   overflow_warning ($$); }
469         /* Refer to the address of a label as a pointer.  */
470         | ANDAND identifier
471                 { tree label = lookup_label ($2);
472                   if (pedantic)
473                     pedwarn ("ISO C forbids `&&'");
474                   if (label == 0)
475                     $$ = null_pointer_node;
476                   else
477                     {
478                       TREE_USED (label) = 1;
479                       $$ = build1 (ADDR_EXPR, ptr_type_node, label);
480                       TREE_CONSTANT ($$) = 1;
481                     }
482                 }
483 /* This seems to be impossible on some machines, so let's turn it off.
484    You can use __builtin_next_arg to find the anonymous stack args.
485         | '&' ELLIPSIS
486                 { tree types = TYPE_ARG_TYPES (TREE_TYPE (current_function_decl));
487                   $$ = error_mark_node;
488                   if (TREE_VALUE (tree_last (types)) == void_type_node)
489                     error ("`&...' used in function with fixed number of arguments");
490                   else
491                     {
492                       if (pedantic)
493                         pedwarn ("ISO C forbids `&...'");
494                       $$ = tree_last (DECL_ARGUMENTS (current_function_decl));
495                       $$ = build_unary_op (ADDR_EXPR, $$, 0);
496                     } }
498         | sizeof unary_expr  %prec UNARY
499                 { skip_evaluation--;
500                   if (TREE_CODE ($2) == COMPONENT_REF
501                       && DECL_C_BIT_FIELD (TREE_OPERAND ($2, 1)))
502                     error ("`sizeof' applied to a bit-field");
503                   $$ = c_sizeof (TREE_TYPE ($2)); }
504         | sizeof '(' typename ')'  %prec HYPERUNARY
505                 { skip_evaluation--;
506                   $$ = c_sizeof (groktypename ($3)); }
507         | alignof unary_expr  %prec UNARY
508                 { skip_evaluation--;
509                   $$ = c_alignof_expr ($2); }
510         | alignof '(' typename ')'  %prec HYPERUNARY
511                 { skip_evaluation--;
512                   $$ = c_alignof (groktypename ($3)); }
513         | REALPART cast_expr %prec UNARY
514                 { $$ = build_unary_op (REALPART_EXPR, $2, 0); }
515         | IMAGPART cast_expr %prec UNARY
516                 { $$ = build_unary_op (IMAGPART_EXPR, $2, 0); }
517         | VA_ARG '(' expr_no_commas ',' typename ')'
518                 { $$ = build_va_arg ($3, groktypename ($5)); }
519         ;
521 sizeof:
522         SIZEOF { skip_evaluation++; }
523         ;
525 alignof:
526         ALIGNOF { skip_evaluation++; }
527         ;
529 cast_expr:
530         unary_expr
531         | '(' typename ')' cast_expr  %prec UNARY
532                 { tree type;
533                   int SAVED_warn_strict_prototypes = warn_strict_prototypes;
534                   /* This avoids warnings about unprototyped casts on
535                      integers.  E.g. "#define SIG_DFL (void(*)())0".  */
536                   if (TREE_CODE ($4) == INTEGER_CST)
537                     warn_strict_prototypes = 0;
538                   type = groktypename ($2);
539                   warn_strict_prototypes = SAVED_warn_strict_prototypes;
540                   $$ = build_c_cast (type, $4); }
541         | '(' typename ')' '{' 
542                 { start_init (NULL_TREE, NULL, 0);
543                   $2 = groktypename ($2);
544                   really_start_incremental_init ($2); }
545           initlist_maybe_comma '}'  %prec UNARY
546                 { const char *name;
547                   tree result = pop_init_level (0);
548                   tree type = $2;
549                   finish_init ();
551                   if (pedantic && ! flag_isoc99)
552                     pedwarn ("ISO C89 forbids constructor expressions");
553                   if (TYPE_NAME (type) != 0)
554                     {
555                       if (TREE_CODE (TYPE_NAME (type)) == IDENTIFIER_NODE)
556                         name = IDENTIFIER_POINTER (TYPE_NAME (type));
557                       else
558                         name = IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (type)));
559                     }
560                   else
561                     name = "";
562                   $$ = result;
563                   if (TREE_CODE (type) == ARRAY_TYPE && !COMPLETE_TYPE_P (type))
564                     {
565                       int failure = complete_array_type (type, $$, 1);
566                       if (failure)
567                         abort ();
568                     }
569                 }
570         ;
572 expr_no_commas:
573           cast_expr
574         | expr_no_commas '+' expr_no_commas
575                 { $$ = parser_build_binary_op ($2, $1, $3); }
576         | expr_no_commas '-' expr_no_commas
577                 { $$ = parser_build_binary_op ($2, $1, $3); }
578         | expr_no_commas '*' expr_no_commas
579                 { $$ = parser_build_binary_op ($2, $1, $3); }
580         | expr_no_commas '/' expr_no_commas
581                 { $$ = parser_build_binary_op ($2, $1, $3); }
582         | expr_no_commas '%' expr_no_commas
583                 { $$ = parser_build_binary_op ($2, $1, $3); }
584         | expr_no_commas LSHIFT expr_no_commas
585                 { $$ = parser_build_binary_op ($2, $1, $3); }
586         | expr_no_commas RSHIFT expr_no_commas
587                 { $$ = parser_build_binary_op ($2, $1, $3); }
588         | expr_no_commas ARITHCOMPARE expr_no_commas
589                 { $$ = parser_build_binary_op ($2, $1, $3); }
590         | expr_no_commas EQCOMPARE expr_no_commas
591                 { $$ = parser_build_binary_op ($2, $1, $3); }
592         | expr_no_commas '&' expr_no_commas
593                 { $$ = parser_build_binary_op ($2, $1, $3); }
594         | expr_no_commas '|' expr_no_commas
595                 { $$ = parser_build_binary_op ($2, $1, $3); }
596         | expr_no_commas '^' expr_no_commas
597                 { $$ = parser_build_binary_op ($2, $1, $3); }
598         | expr_no_commas ANDAND
599                 { $1 = truthvalue_conversion (default_conversion ($1));
600                   skip_evaluation += $1 == boolean_false_node; }
601           expr_no_commas
602                 { skip_evaluation -= $1 == boolean_false_node;
603                   $$ = parser_build_binary_op (TRUTH_ANDIF_EXPR, $1, $4); }
604         | expr_no_commas OROR
605                 { $1 = truthvalue_conversion (default_conversion ($1));
606                   skip_evaluation += $1 == boolean_true_node; }
607           expr_no_commas
608                 { skip_evaluation -= $1 == boolean_true_node;
609                   $$ = parser_build_binary_op (TRUTH_ORIF_EXPR, $1, $4); }
610         | expr_no_commas '?'
611                 { $1 = truthvalue_conversion (default_conversion ($1));
612                   skip_evaluation += $1 == boolean_false_node; }
613           expr ':'
614                 { skip_evaluation += (($1 == boolean_true_node)
615                                       - ($1 == boolean_false_node)); }
616           expr_no_commas
617                 { skip_evaluation -= $1 == boolean_true_node;
618                   $$ = build_conditional_expr ($1, $4, $7); }
619         | expr_no_commas '?'
620                 { if (pedantic)
621                     pedwarn ("ISO C forbids omitting the middle term of a ?: expression");
622                   /* Make sure first operand is calculated only once.  */
623                   $<ttype>2 = save_expr ($1);
624                   $1 = truthvalue_conversion (default_conversion ($<ttype>2));
625                   skip_evaluation += $1 == boolean_true_node; }
626           ':' expr_no_commas
627                 { skip_evaluation -= $1 == boolean_true_node;
628                   $$ = build_conditional_expr ($1, $<ttype>2, $5); }
629         | expr_no_commas '=' expr_no_commas
630                 { char class;
631                   $$ = build_modify_expr ($1, NOP_EXPR, $3);
632                   class = TREE_CODE_CLASS (TREE_CODE ($$));
633                   if (class == 'e' || class == '1'
634                       || class == '2' || class == '<')
635                     C_SET_EXP_ORIGINAL_CODE ($$, MODIFY_EXPR);
636                 }
637         | expr_no_commas ASSIGN expr_no_commas
638                 { char class;
639                   $$ = build_modify_expr ($1, $2, $3);
640                   /* This inhibits warnings in truthvalue_conversion.  */
641                   class = TREE_CODE_CLASS (TREE_CODE ($$));
642                   if (class == 'e' || class == '1'
643                       || class == '2' || class == '<')
644                     C_SET_EXP_ORIGINAL_CODE ($$, ERROR_MARK);
645                 }
646         ;
648 primary:
649         IDENTIFIER
650                 {
651                   if (yychar == YYEMPTY)
652                     yychar = YYLEX;
653                   $$ = build_external_ref ($1, yychar == '(');
654                 }
655         | CONSTANT
656         | string
657                 { $$ = combine_strings ($1); }
658         | '(' expr ')'
659                 { char class = TREE_CODE_CLASS (TREE_CODE ($2));
660                   if (class == 'e' || class == '1'
661                       || class == '2' || class == '<')
662                     C_SET_EXP_ORIGINAL_CODE ($2, ERROR_MARK);
663                   $$ = $2; }
664         | '(' error ')'
665                 { $$ = error_mark_node; }
666         | compstmt_primary_start compstmt_nostart ')'
667                  { tree saved_last_tree;
669                    if (pedantic)
670                      pedwarn ("ISO C forbids braced-groups within expressions");
671                   pop_label_level ();
673                   saved_last_tree = COMPOUND_BODY ($1);
674                   RECHAIN_STMTS ($1, COMPOUND_BODY ($1));
675                   last_tree = saved_last_tree;
676                   TREE_CHAIN (last_tree) = NULL_TREE;
677                   if (!last_expr_type)
678                     last_expr_type = void_type_node;
679                   $$ = build1 (STMT_EXPR, last_expr_type, $1);
680                   TREE_SIDE_EFFECTS ($$) = 1;
681                 }
682         | compstmt_primary_start error ')'
683                 {
684                   pop_label_level ();
685                   last_tree = COMPOUND_BODY ($1);
686                   TREE_CHAIN (last_tree) = NULL_TREE;
687                   $$ = error_mark_node;
688                 }
689         | primary '(' exprlist ')'   %prec '.'
690                 { $$ = build_function_call ($1, $3); }
691         | primary '[' expr ']'   %prec '.'
692                 { $$ = build_array_ref ($1, $3); }
693         | primary '.' identifier
694                 {
695 ifobjc
696                   if (doing_objc_thang)
697                     {
698                       if (is_public ($1, $3))
699                         $$ = build_component_ref ($1, $3);
700                       else
701                         $$ = error_mark_node;
702                     }
703                   else
704 end ifobjc
705                     $$ = build_component_ref ($1, $3);
706                 }
707         | primary POINTSAT identifier
708                 {
709                   tree expr = build_indirect_ref ($1, "->");
711 ifobjc
712                   if (doing_objc_thang)
713                     {
714                       if (is_public (expr, $3))
715                         $$ = build_component_ref (expr, $3);
716                       else
717                         $$ = error_mark_node;
718                     }
719                   else
720 end ifobjc
721                     $$ = build_component_ref (expr, $3);
722                 }
723         | primary PLUSPLUS
724                 { $$ = build_unary_op (POSTINCREMENT_EXPR, $1, 0); }
725         | primary MINUSMINUS
726                 { $$ = build_unary_op (POSTDECREMENT_EXPR, $1, 0); }
727 ifobjc
728         | objcmessageexpr
729                 { $$ = build_message_expr ($1); }
730         | objcselectorexpr
731                 { $$ = build_selector_expr ($1); }
732         | objcprotocolexpr
733                 { $$ = build_protocol_expr ($1); }
734         | objcencodeexpr
735                 { $$ = build_encode_expr ($1); }
736         | objc_string
737                 { $$ = build_objc_string_object ($1); }
738 end ifobjc
739         ;
741 /* Produces a STRING_CST with perhaps more STRING_CSTs chained onto it.  */
742 string:
743           STRING
744         | string STRING
745                 {
747                   static int last_lineno = 0;
748                   static const char *last_input_filename = 0;
749 end ifc
750                   $$ = chainon ($1, $2);
752                   if (warn_traditional && !in_system_header
753                       && (lineno != last_lineno || !last_input_filename ||
754                           strcmp (last_input_filename, input_filename)))
755                     {
756                       warning ("traditional C rejects string concatenation");
757                       last_lineno = lineno;
758                       last_input_filename = input_filename;
759                     }
760 end ifc
761                 }
762         ;
764 ifobjc
765 /* Produces an STRING_CST with perhaps more STRING_CSTs chained
766    onto it, which is to be read as an ObjC string object.  */
767 objc_string:
768           OBJC_STRING
769         | objc_string OBJC_STRING
770                 { $$ = chainon ($1, $2); }
771         ;
772 end ifobjc
774 old_style_parm_decls:
775         /* empty */
776         | datadecls
777         | datadecls ELLIPSIS
778                 /* ... is used here to indicate a varargs function.  */
779                 { c_mark_varargs ();
780                   if (pedantic)
781                     pedwarn ("ISO C does not permit use of `varargs.h'"); }
782         ;
784 /* The following are analogous to lineno_decl, decls and decl
785    except that they do not allow nested functions.
786    They are used for old-style parm decls.  */
787 lineno_datadecl:
788           save_filename save_lineno datadecl
789                 { }
790         ;
792 datadecls:
793         lineno_datadecl
794         | errstmt
795         | datadecls lineno_datadecl
796         | lineno_datadecl errstmt
797         ;
799 /* We don't allow prefix attributes here because they cause reduce/reduce
800    conflicts: we can't know whether we're parsing a function decl with
801    attribute suffix, or function defn with attribute prefix on first old
802    style parm.  */
803 datadecl:
804         typed_declspecs_no_prefix_attr setspecs initdecls ';'
805                 { current_declspecs = TREE_VALUE (declspec_stack);
806                   prefix_attributes = TREE_PURPOSE (declspec_stack);
807                   declspec_stack = TREE_CHAIN (declspec_stack); }
808         | declmods_no_prefix_attr setspecs notype_initdecls ';'
809                 { current_declspecs = TREE_VALUE (declspec_stack);      
810                   prefix_attributes = TREE_PURPOSE (declspec_stack);
811                   declspec_stack = TREE_CHAIN (declspec_stack); }
812         | typed_declspecs_no_prefix_attr ';'
813                 { shadow_tag_warned ($1, 1);
814                   pedwarn ("empty declaration"); }
815         | declmods_no_prefix_attr ';'
816                 { pedwarn ("empty declaration"); }
817         ;
819 /* This combination which saves a lineno before a decl
820    is the normal thing to use, rather than decl itself.
821    This is to avoid shift/reduce conflicts in contexts
822    where statement labels are allowed.  */
823 lineno_decl:
824           save_filename save_lineno decl
825                 { }
826         ;
828 /* records the type and storage class specs to use for processing
829    the declarators that follow.
830    Maintains a stack of outer-level values of current_declspecs,
831    for the sake of parm declarations nested in function declarators.  */
832 setspecs: /* empty */
833                 { pending_xref_error ();
834                   declspec_stack = tree_cons (prefix_attributes,
835                                               current_declspecs,
836                                               declspec_stack);
837                   split_specs_attrs ($<ttype>0,
838                                      &current_declspecs, &prefix_attributes); }
839         ;
841 /* ??? Yuck.  See after_type_declarator.  */
842 setattrs: /* empty */
843                 { prefix_attributes = chainon (prefix_attributes, $<ttype>0); }
844         ;
846 decl:
847         typed_declspecs setspecs initdecls ';'
848                 { current_declspecs = TREE_VALUE (declspec_stack);
849                   prefix_attributes = TREE_PURPOSE (declspec_stack);
850                   declspec_stack = TREE_CHAIN (declspec_stack); }
851         | declmods setspecs notype_initdecls ';'
852                 { current_declspecs = TREE_VALUE (declspec_stack);
853                   prefix_attributes = TREE_PURPOSE (declspec_stack);
854                   declspec_stack = TREE_CHAIN (declspec_stack); }
855         | typed_declspecs setspecs nested_function
856                 { current_declspecs = TREE_VALUE (declspec_stack);
857                   prefix_attributes = TREE_PURPOSE (declspec_stack);
858                   declspec_stack = TREE_CHAIN (declspec_stack); }
859         | declmods setspecs notype_nested_function
860                 { current_declspecs = TREE_VALUE (declspec_stack);
861                   prefix_attributes = TREE_PURPOSE (declspec_stack);
862                   declspec_stack = TREE_CHAIN (declspec_stack); }
863         | typed_declspecs ';'
864                 { shadow_tag ($1); }
865         | declmods ';'
866                 { pedwarn ("empty declaration"); }
867         | extension decl
868                 { RESTORE_WARN_FLAGS ($1); }
869         ;
871 /* Declspecs which contain at least one type specifier or typedef name.
872    (Just `const' or `volatile' is not enough.)
873    A typedef'd name following these is taken as a name to be declared.
874    Declspecs have a non-NULL TREE_VALUE, attributes do not.  */
876 typed_declspecs:
877           typespec reserved_declspecs
878                 { $$ = tree_cons (NULL_TREE, $1, $2); }
879         | declmods typespec reserved_declspecs
880                 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
881         ;
883 reserved_declspecs:  /* empty */
884                 { $$ = NULL_TREE; }
885         | reserved_declspecs typespecqual_reserved
886                 { $$ = tree_cons (NULL_TREE, $2, $1); }
887         | reserved_declspecs SCSPEC
888                 { if (extra_warnings)
889                     warning ("`%s' is not at beginning of declaration",
890                              IDENTIFIER_POINTER ($2));
891                   $$ = tree_cons (NULL_TREE, $2, $1); }
892         | reserved_declspecs attributes
893                 { $$ = tree_cons ($2, NULL_TREE, $1); }
894         ;
896 typed_declspecs_no_prefix_attr:
897           typespec reserved_declspecs_no_prefix_attr
898                 { $$ = tree_cons (NULL_TREE, $1, $2); }
899         | declmods_no_prefix_attr typespec reserved_declspecs_no_prefix_attr
900                 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
901         ;
903 reserved_declspecs_no_prefix_attr:
904           /* empty */
905                 { $$ = NULL_TREE; }
906         | reserved_declspecs_no_prefix_attr typespecqual_reserved
907                 { $$ = tree_cons (NULL_TREE, $2, $1); }
908         | reserved_declspecs_no_prefix_attr SCSPEC
909                 { if (extra_warnings)
910                     warning ("`%s' is not at beginning of declaration",
911                              IDENTIFIER_POINTER ($2));
912                   $$ = tree_cons (NULL_TREE, $2, $1); }
913         ;
915 /* List of just storage classes, type modifiers, and prefix attributes.
916    A declaration can start with just this, but then it cannot be used
917    to redeclare a typedef-name.
918    Declspecs have a non-NULL TREE_VALUE, attributes do not.  */
920 declmods:
921           declmods_no_prefix_attr
922                 { $$ = $1; }
923         | attributes
924                 { $$ = tree_cons ($1, NULL_TREE, NULL_TREE); }
925         | declmods declmods_no_prefix_attr
926                 { $$ = chainon ($2, $1); }
927         | declmods attributes
928                 { $$ = tree_cons ($2, NULL_TREE, $1); }
929         ;
931 declmods_no_prefix_attr:
932           TYPE_QUAL
933                 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
934                   TREE_STATIC ($$) = 1; }
935         | SCSPEC
936                 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
937         | declmods_no_prefix_attr TYPE_QUAL
938                 { $$ = tree_cons (NULL_TREE, $2, $1);
939                   TREE_STATIC ($$) = 1; }
940         | declmods_no_prefix_attr SCSPEC
941                 { if (extra_warnings && TREE_STATIC ($1))
942                     warning ("`%s' is not at beginning of declaration",
943                              IDENTIFIER_POINTER ($2));
944                   $$ = tree_cons (NULL_TREE, $2, $1);
945                   TREE_STATIC ($$) = TREE_STATIC ($1); }
946         ;
949 /* Used instead of declspecs where storage classes are not allowed
950    (that is, for typenames and structure components).
951    Don't accept a typedef-name if anything but a modifier precedes it.  */
953 typed_typespecs:
954           typespec reserved_typespecquals
955                 { $$ = tree_cons (NULL_TREE, $1, $2); }
956         | nonempty_type_quals typespec reserved_typespecquals
957                 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
958         ;
960 reserved_typespecquals:  /* empty */
961                 { $$ = NULL_TREE; }
962         | reserved_typespecquals typespecqual_reserved
963                 { $$ = tree_cons (NULL_TREE, $2, $1); }
964         ;
966 /* A typespec (but not a type qualifier).
967    Once we have seen one of these in a declaration,
968    if a typedef name appears then it is being redeclared.  */
970 typespec: TYPESPEC
971         | structsp
972         | TYPENAME
973                 { /* For a typedef name, record the meaning, not the name.
974                      In case of `foo foo, bar;'.  */
975                   $$ = lookup_name ($1); }
976 ifobjc
977         | CLASSNAME protocolrefs
978                 { $$ = get_static_reference ($1, $2); }
979         | OBJECTNAME protocolrefs
980                 { $$ = get_object_reference ($2); }
982 /* Make "<SomeProtocol>" equivalent to "id <SomeProtocol>"
983    - nisse@lysator.liu.se */
984         | non_empty_protocolrefs
985                 { $$ = get_object_reference ($1); }
986 end ifobjc
987         | TYPEOF '(' expr ')'
988                 { $$ = TREE_TYPE ($3); }
989         | TYPEOF '(' typename ')'
990                 { $$ = groktypename ($3); }
991         ;
993 /* A typespec that is a reserved word, or a type qualifier.  */
995 typespecqual_reserved: TYPESPEC
996         | TYPE_QUAL
997         | structsp
998         ;
1000 initdecls:
1001         initdcl
1002         | initdecls ',' initdcl
1003         ;
1005 notype_initdecls:
1006         notype_initdcl
1007         | notype_initdecls ',' initdcl
1008         ;
1010 maybeasm:
1011           /* empty */
1012                 { $$ = NULL_TREE; }
1013         | ASM_KEYWORD '(' string ')'
1014                 { if (TREE_CHAIN ($3)) $3 = combine_strings ($3);
1015                   $$ = $3;
1016                 }
1017         ;
1019 initdcl:
1020           declarator maybeasm maybe_attribute '='
1021                 { $<ttype>$ = start_decl ($1, current_declspecs, 1,
1022                                           $3, prefix_attributes);
1023                   start_init ($<ttype>$, $2, global_bindings_p ()); }
1024           init
1025 /* Note how the declaration of the variable is in effect while its init is parsed! */
1026                 { finish_init ();
1027                   finish_decl ($<ttype>5, $6, $2); }
1028         | declarator maybeasm maybe_attribute
1029                 { tree d = start_decl ($1, current_declspecs, 0,
1030                                        $3, prefix_attributes);
1031                   finish_decl (d, NULL_TREE, $2); 
1032                 }
1033         ;
1035 notype_initdcl:
1036           notype_declarator maybeasm maybe_attribute '='
1037                 { $<ttype>$ = start_decl ($1, current_declspecs, 1,
1038                                           $3, prefix_attributes);
1039                   start_init ($<ttype>$, $2, global_bindings_p ()); }
1040           init
1041 /* Note how the declaration of the variable is in effect while its init is parsed! */
1042                 { finish_init ();
1043                   decl_attributes ($<ttype>5, $3, prefix_attributes);
1044                   finish_decl ($<ttype>5, $6, $2); }
1045         | notype_declarator maybeasm maybe_attribute
1046                 { tree d = start_decl ($1, current_declspecs, 0,
1047                                        $3, prefix_attributes);
1048                   finish_decl (d, NULL_TREE, $2); }
1049         ;
1050 /* the * rules are dummies to accept the Apollo extended syntax
1051    so that the header files compile. */
1052 maybe_attribute:
1053       /* empty */
1054                 { $$ = NULL_TREE; }
1055         | attributes
1056                 { $$ = $1; }
1057         ;
1059 attributes:
1060       attribute
1061                 { $$ = $1; }
1062         | attributes attribute
1063                 { $$ = chainon ($1, $2); }
1064         ;
1066 attribute:
1067       ATTRIBUTE '(' '(' attribute_list ')' ')'
1068                 { $$ = $4; }
1069         ;
1071 attribute_list:
1072       attrib
1073                 { $$ = $1; }
1074         | attribute_list ',' attrib
1075                 { $$ = chainon ($1, $3); }
1076         ;
1078 attrib:
1079     /* empty */
1080                 { $$ = NULL_TREE; }
1081         | any_word
1082                 { $$ = build_tree_list ($1, NULL_TREE); }
1083         | any_word '(' IDENTIFIER ')'
1084                 { $$ = build_tree_list ($1, build_tree_list (NULL_TREE, $3)); }
1085         | any_word '(' IDENTIFIER ',' nonnull_exprlist ')'
1086                 { $$ = build_tree_list ($1, tree_cons (NULL_TREE, $3, $5)); }
1087         | any_word '(' exprlist ')'
1088                 { $$ = build_tree_list ($1, $3); }
1089         ;
1091 /* This still leaves out most reserved keywords,
1092    shouldn't we include them?  */
1094 any_word:
1095           identifier
1096         | SCSPEC
1097         | TYPESPEC
1098         | TYPE_QUAL
1099         ;
1101 /* Initializers.  `init' is the entry point.  */
1103 init:
1104         expr_no_commas
1105         | '{'
1106                 { really_start_incremental_init (NULL_TREE); }
1107           initlist_maybe_comma '}'
1108                 { $$ = pop_init_level (0); }
1109         | error
1110                 { $$ = error_mark_node; }
1111         ;
1113 /* `initlist_maybe_comma' is the guts of an initializer in braces.  */
1114 initlist_maybe_comma:
1115           /* empty */
1116                 { if (pedantic)
1117                     pedwarn ("ISO C forbids empty initializer braces"); }
1118         | initlist1 maybecomma
1119         ;
1121 initlist1:
1122           initelt
1123         | initlist1 ',' initelt
1124         ;
1126 /* `initelt' is a single element of an initializer.
1127    It may use braces.  */
1128 initelt:
1129           designator_list '=' initval
1130                 { if (pedantic && ! flag_isoc99)
1131                     pedwarn ("ISO C89 forbids specifying subobject to initialize"); }
1132         | designator initval
1133                 { if (pedantic)
1134                     pedwarn ("obsolete use of designated initializer without `='"); }
1135         | identifier ':'
1136                 { set_init_label ($1);
1137                   if (pedantic)
1138                     pedwarn ("obsolete use of designated initializer with `:'"); }
1139           initval
1140         | initval
1141         ;
1143 initval:
1144           '{'
1145                 { push_init_level (0); }
1146           initlist_maybe_comma '}'
1147                 { process_init_element (pop_init_level (0)); }
1148         | expr_no_commas
1149                 { process_init_element ($1); }
1150         | error
1151         ;
1153 designator_list:
1154           designator
1155         | designator_list designator
1156         ;
1158 designator:
1159           '.' identifier
1160                 { set_init_label ($2); }
1161         /* These are for labeled elements.  The syntax for an array element
1162            initializer conflicts with the syntax for an Objective-C message,
1163            so don't include these productions in the Objective-C grammar.  */
1165         | '[' expr_no_commas ELLIPSIS expr_no_commas ']'
1166                 { set_init_index ($2, $4);
1167                   if (pedantic)
1168                     pedwarn ("ISO C forbids specifying range of elements to initialize"); }
1169         | '[' expr_no_commas ']'
1170                 { set_init_index ($2, NULL_TREE); }
1171 end ifc
1172         ;
1174 nested_function:
1175           declarator
1176                 { if (pedantic)
1177                     pedwarn ("ISO C forbids nested functions");
1179                   push_function_context ();
1180                   if (! start_function (current_declspecs, $1,
1181                                         prefix_attributes, NULL_TREE))
1182                     {
1183                       pop_function_context ();
1184                       YYERROR1;
1185                     }
1186                 }
1187            old_style_parm_decls
1188                 { store_parm_decls (); }
1189 /* This used to use compstmt_or_error.
1190    That caused a bug with input `f(g) int g {}',
1191    where the use of YYERROR1 above caused an error
1192    which then was handled by compstmt_or_error.
1193    There followed a repeated execution of that same rule,
1194    which called YYERROR1 again, and so on.  */
1195           compstmt
1196                 { tree decl = current_function_decl;
1197                   finish_function (1);
1198                   pop_function_context (); 
1199                   add_decl_stmt (decl); }
1200         ;
1202 notype_nested_function:
1203           notype_declarator
1204                 { if (pedantic)
1205                     pedwarn ("ISO C forbids nested functions");
1207                   push_function_context ();
1208                   if (! start_function (current_declspecs, $1,
1209                                         prefix_attributes, NULL_TREE))
1210                     {
1211                       pop_function_context ();
1212                       YYERROR1;
1213                     }
1214                 }
1215           old_style_parm_decls
1216                 { store_parm_decls (); }
1217 /* This used to use compstmt_or_error.
1218    That caused a bug with input `f(g) int g {}',
1219    where the use of YYERROR1 above caused an error
1220    which then was handled by compstmt_or_error.
1221    There followed a repeated execution of that same rule,
1222    which called YYERROR1 again, and so on.  */
1223           compstmt
1224                 { tree decl = current_function_decl;
1225                   finish_function (1);
1226                   pop_function_context (); 
1227                   add_decl_stmt (decl); }
1228         ;
1230 /* Any kind of declarator (thus, all declarators allowed
1231    after an explicit typespec).  */
1233 declarator:
1234           after_type_declarator
1235         | notype_declarator
1236         ;
1238 /* A declarator that is allowed only after an explicit typespec.  */
1240 after_type_declarator:
1241           '(' after_type_declarator ')'
1242                 { $$ = $2; }
1243         | after_type_declarator '(' parmlist_or_identifiers  %prec '.'
1244                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1245 /*      | after_type_declarator '(' error ')'  %prec '.'
1246                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1247                   poplevel (0, 0, 0); }  */
1248         | after_type_declarator '[' expr ']'  %prec '.'
1249                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1250         | after_type_declarator '[' ']'  %prec '.'
1251                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1252         | '*' type_quals after_type_declarator  %prec UNARY
1253                 { $$ = make_pointer_declarator ($2, $3); }
1254         /* ??? Yuck.  setattrs is a quick hack.  We can't use
1255            prefix_attributes because $1 only applies to this
1256            declarator.  We assume setspecs has already been done.
1257            setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
1258            attributes could be recognized here or in `attributes').  */
1259         | attributes setattrs after_type_declarator
1260                 { $$ = $3; }
1261         | TYPENAME
1262 ifobjc
1263         | OBJECTNAME
1264 end ifobjc
1265         ;
1267 /* Kinds of declarator that can appear in a parameter list
1268    in addition to notype_declarator.  This is like after_type_declarator
1269    but does not allow a typedef name in parentheses as an identifier
1270    (because it would conflict with a function with that typedef as arg).  */
1272 parm_declarator:
1273           parm_declarator '(' parmlist_or_identifiers  %prec '.'
1274                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1275 /*      | parm_declarator '(' error ')'  %prec '.'
1276                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1277                   poplevel (0, 0, 0); }  */
1279         | parm_declarator '[' '*' ']'  %prec '.'
1280                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE);
1281                   if (! flag_isoc99)
1282                     error ("`[*]' in parameter declaration only allowed in ISO C 99");
1283                 }
1284 end ifc
1285         | parm_declarator '[' expr ']'  %prec '.'
1286                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1287         | parm_declarator '[' ']'  %prec '.'
1288                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1289         | '*' type_quals parm_declarator  %prec UNARY
1290                 { $$ = make_pointer_declarator ($2, $3); }
1291         /* ??? Yuck.  setattrs is a quick hack.  We can't use
1292            prefix_attributes because $1 only applies to this
1293            declarator.  We assume setspecs has already been done.
1294            setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
1295            attributes could be recognized here or in `attributes').  */
1296         | attributes setattrs parm_declarator
1297                 { $$ = $3; }
1298         | TYPENAME
1299         ;
1301 /* A declarator allowed whether or not there has been
1302    an explicit typespec.  These cannot redeclare a typedef-name.  */
1304 notype_declarator:
1305           notype_declarator '(' parmlist_or_identifiers  %prec '.'
1306                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1307 /*      | notype_declarator '(' error ')'  %prec '.'
1308                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1309                   poplevel (0, 0, 0); }  */
1310         | '(' notype_declarator ')'
1311                 { $$ = $2; }
1312         | '*' type_quals notype_declarator  %prec UNARY
1313                 { $$ = make_pointer_declarator ($2, $3); }
1315         | notype_declarator '[' '*' ']'  %prec '.'
1316                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE);
1317                   if (! flag_isoc99)
1318                     error ("`[*]' in parameter declaration only allowed in ISO C 99");
1319                 }
1320 end ifc
1321         | notype_declarator '[' expr ']'  %prec '.'
1322                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1323         | notype_declarator '[' ']'  %prec '.'
1324                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1325         /* ??? Yuck.  setattrs is a quick hack.  We can't use
1326            prefix_attributes because $1 only applies to this
1327            declarator.  We assume setspecs has already been done.
1328            setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
1329            attributes could be recognized here or in `attributes').  */
1330         | attributes setattrs notype_declarator
1331                 { $$ = $3; }
1332         | IDENTIFIER
1333         ;
1335 struct_head:
1336           STRUCT
1337                 { $$ = NULL_TREE; }
1338         | STRUCT attributes
1339                 { $$ = $2; }
1340         ;
1342 union_head:
1343           UNION
1344                 { $$ = NULL_TREE; }
1345         | UNION attributes
1346                 { $$ = $2; }
1347         ;
1349 enum_head:
1350           ENUM
1351                 { $$ = NULL_TREE; }
1352         | ENUM attributes
1353                 { $$ = $2; }
1354         ;
1356 structsp:
1357           struct_head identifier '{'
1358                 { $$ = start_struct (RECORD_TYPE, $2);
1359                   /* Start scope of tag before parsing components.  */
1360                 }
1361           component_decl_list '}' maybe_attribute 
1362                 { $$ = finish_struct ($<ttype>4, $5, chainon ($1, $7)); }
1363         | struct_head '{' component_decl_list '}' maybe_attribute
1364                 { $$ = finish_struct (start_struct (RECORD_TYPE, NULL_TREE),
1365                                       $3, chainon ($1, $5));
1366                 }
1367         | struct_head identifier
1368                 { $$ = xref_tag (RECORD_TYPE, $2); }
1369         | union_head identifier '{'
1370                 { $$ = start_struct (UNION_TYPE, $2); }
1371           component_decl_list '}' maybe_attribute
1372                 { $$ = finish_struct ($<ttype>4, $5, chainon ($1, $7)); }
1373         | union_head '{' component_decl_list '}' maybe_attribute
1374                 { $$ = finish_struct (start_struct (UNION_TYPE, NULL_TREE),
1375                                       $3, chainon ($1, $5));
1376                 }
1377         | union_head identifier
1378                 { $$ = xref_tag (UNION_TYPE, $2); }
1379         | enum_head identifier '{'
1380                 { $$ = start_enum ($2); }
1381           enumlist maybecomma_warn '}' maybe_attribute
1382                 { $$ = finish_enum ($<ttype>4, nreverse ($5),
1383                                     chainon ($1, $8)); }
1384         | enum_head '{'
1385                 { $$ = start_enum (NULL_TREE); }
1386           enumlist maybecomma_warn '}' maybe_attribute
1387                 { $$ = finish_enum ($<ttype>3, nreverse ($4),
1388                                     chainon ($1, $7)); }
1389         | enum_head identifier
1390                 { $$ = xref_tag (ENUMERAL_TYPE, $2); }
1391         ;
1393 maybecomma:
1394           /* empty */
1395         | ','
1396         ;
1398 maybecomma_warn:
1399           /* empty */
1400         | ','
1401                 { if (pedantic && ! flag_isoc99)
1402                     pedwarn ("comma at end of enumerator list"); }
1403         ;
1405 component_decl_list:
1406           component_decl_list2
1407                 { $$ = $1; }
1408         | component_decl_list2 component_decl
1409                 { $$ = chainon ($1, $2);
1410                   pedwarn ("no semicolon at end of struct or union"); }
1411         ;
1413 component_decl_list2:   /* empty */
1414                 { $$ = NULL_TREE; }
1415         | component_decl_list2 component_decl ';'
1416                 { $$ = chainon ($1, $2); }
1417         | component_decl_list2 ';'
1418                 { if (pedantic)
1419                     pedwarn ("extra semicolon in struct or union specified"); }
1420 ifobjc
1421         /* foo(sizeof(struct{ @defs(ClassName)})); */
1422         | DEFS '(' CLASSNAME ')'
1423                 {
1424                   tree interface = lookup_interface ($3);
1426                   if (interface)
1427                     $$ = get_class_ivars (interface);
1428                   else
1429                     {
1430                       error ("Cannot find interface declaration for `%s'",
1431                              IDENTIFIER_POINTER ($3));
1432                       $$ = NULL_TREE;
1433                     }
1434                 }
1435 end ifobjc
1436         ;
1438 /* There is a shift-reduce conflict here, because `components' may
1439    start with a `typename'.  It happens that shifting (the default resolution)
1440    does the right thing, because it treats the `typename' as part of
1441    a `typed_typespecs'.
1443    It is possible that this same technique would allow the distinction
1444    between `notype_initdecls' and `initdecls' to be eliminated.
1445    But I am being cautious and not trying it.  */
1447 component_decl:
1448           typed_typespecs setspecs components
1449                 { $$ = $3;
1450                   current_declspecs = TREE_VALUE (declspec_stack);
1451                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1452                   declspec_stack = TREE_CHAIN (declspec_stack); }
1453         | typed_typespecs setspecs save_filename save_lineno maybe_attribute
1454                 {
1455                   /* Support for unnamed structs or unions as members of 
1456                      structs or unions (which is [a] useful and [b] supports 
1457                      MS P-SDK).  */
1458                   if (pedantic)
1459                     pedwarn ("ISO C doesn't support unnamed structs/unions");
1461                   $$ = grokfield($3, $4, NULL, current_declspecs, NULL_TREE);
1462                   current_declspecs = TREE_VALUE (declspec_stack);
1463                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1464                   declspec_stack = TREE_CHAIN (declspec_stack);
1465                 }
1466     | nonempty_type_quals setspecs components
1467                 { $$ = $3;
1468                   current_declspecs = TREE_VALUE (declspec_stack);
1469                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1470                   declspec_stack = TREE_CHAIN (declspec_stack); }
1471         | nonempty_type_quals
1472                 { if (pedantic)
1473                     pedwarn ("ISO C forbids member declarations with no members");
1474                   shadow_tag($1);
1475                   $$ = NULL_TREE; }
1476         | error
1477                 { $$ = NULL_TREE; }
1478         | extension component_decl
1479                 { $$ = $2;
1480                   RESTORE_WARN_FLAGS ($1); }
1481         ;
1483 components:
1484           component_declarator
1485         | components ',' component_declarator
1486                 { $$ = chainon ($1, $3); }
1487         ;
1489 component_declarator:
1490           save_filename save_lineno declarator maybe_attribute
1491                 { $$ = grokfield ($1, $2, $3, current_declspecs, NULL_TREE);
1492                   decl_attributes ($$, $4, prefix_attributes); }
1493         | save_filename save_lineno
1494           declarator ':' expr_no_commas maybe_attribute
1495                 { $$ = grokfield ($1, $2, $3, current_declspecs, $5);
1496                   decl_attributes ($$, $6, prefix_attributes); }
1497         | save_filename save_lineno ':' expr_no_commas maybe_attribute
1498                 { $$ = grokfield ($1, $2, NULL_TREE, current_declspecs, $4);
1499                   decl_attributes ($$, $5, prefix_attributes); }
1500         ;
1502 /* We chain the enumerators in reverse order.
1503    They are put in forward order where enumlist is used.
1504    (The order used to be significant, but no longer is so.
1505    However, we still maintain the order, just to be clean.)  */
1507 enumlist:
1508           enumerator
1509         | enumlist ',' enumerator
1510                 { if ($1 == error_mark_node)
1511                     $$ = $1;
1512                   else
1513                     $$ = chainon ($3, $1); }
1514         | error
1515                 { $$ = error_mark_node; }
1516         ;
1519 enumerator:
1520           identifier
1521                 { $$ = build_enumerator ($1, NULL_TREE); }
1522         | identifier '=' expr_no_commas
1523                 { $$ = build_enumerator ($1, $3); }
1524         ;
1526 typename:
1527         typed_typespecs absdcl
1528                 { $$ = build_tree_list ($1, $2); }
1529         | nonempty_type_quals absdcl
1530                 { $$ = build_tree_list ($1, $2); }
1531         ;
1533 absdcl:   /* an absolute declarator */
1534         /* empty */
1535                 { $$ = NULL_TREE; }
1536         | absdcl1
1537         ;
1539 nonempty_type_quals:
1540           TYPE_QUAL
1541                 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
1542         | nonempty_type_quals TYPE_QUAL
1543                 { $$ = tree_cons (NULL_TREE, $2, $1); }
1544         ;
1546 type_quals:
1547           /* empty */
1548                 { $$ = NULL_TREE; }
1549         | type_quals TYPE_QUAL
1550                 { $$ = tree_cons (NULL_TREE, $2, $1); }
1551         ;
1553 absdcl1:  /* a nonempty absolute declarator */
1554           '(' absdcl1 ')'
1555                 { $$ = $2; }
1556           /* `(typedef)1' is `int'.  */
1557         | '*' type_quals absdcl1  %prec UNARY
1558                 { $$ = make_pointer_declarator ($2, $3); }
1559         | '*' type_quals  %prec UNARY
1560                 { $$ = make_pointer_declarator ($2, NULL_TREE); }
1561         | absdcl1 '(' parmlist  %prec '.'
1562                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1563         | absdcl1 '[' expr ']'  %prec '.'
1564                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1565         | absdcl1 '[' ']'  %prec '.'
1566                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1567         | '(' parmlist  %prec '.'
1568                 { $$ = build_nt (CALL_EXPR, NULL_TREE, $2, NULL_TREE); }
1569         | '[' expr ']'  %prec '.'
1570                 { $$ = build_nt (ARRAY_REF, NULL_TREE, $2); }
1571         | '[' ']'  %prec '.'
1572                 { $$ = build_nt (ARRAY_REF, NULL_TREE, NULL_TREE); }
1573         /* ??? It appears we have to support attributes here, however
1574            using prefix_attributes is wrong.  */
1575         | attributes setattrs absdcl1
1576                 { $$ = $3; }
1577         ;
1579 /* A nonempty series of declarations and statements (possibly followed by
1580    some labels) that can form the body of a compound statement.
1581    NOTE: we don't allow labels on declarations; this might seem like a
1582    natural extension, but there would be a conflict between attributes
1583    on the label and prefix attributes on the declaration.  */
1585 stmts_and_decls:
1586           lineno_stmt_decl_or_labels_ending_stmt
1587         | lineno_stmt_decl_or_labels_ending_decl
1588         | lineno_stmt_decl_or_labels_ending_label
1589                 {
1590                   pedwarn ("deprecated use of label at end of compound statement");
1591                 }
1592         | lineno_stmt_decl_or_labels_ending_error
1593         ;
1595 lineno_stmt_decl_or_labels_ending_stmt:
1596           lineno_stmt
1597         | lineno_stmt_decl_or_labels_ending_stmt lineno_stmt
1598         | lineno_stmt_decl_or_labels_ending_decl lineno_stmt
1599         | lineno_stmt_decl_or_labels_ending_label lineno_stmt
1600         | lineno_stmt_decl_or_labels_ending_error lineno_stmt
1601         ;
1603 lineno_stmt_decl_or_labels_ending_decl:
1604           lineno_decl
1605         | lineno_stmt_decl_or_labels_ending_stmt lineno_decl
1606                 { if (pedantic && !flag_isoc99)
1607                     pedwarn ("ISO C89 forbids mixed declarations and code"); }
1608         | lineno_stmt_decl_or_labels_ending_decl lineno_decl
1609         | lineno_stmt_decl_or_labels_ending_error lineno_decl
1610         ;
1612 lineno_stmt_decl_or_labels_ending_label:
1613           lineno_label
1614         | lineno_stmt_decl_or_labels_ending_stmt lineno_label
1615         | lineno_stmt_decl_or_labels_ending_decl lineno_label
1616         | lineno_stmt_decl_or_labels_ending_label lineno_label
1617         | lineno_stmt_decl_or_labels_ending_error lineno_label
1618         ;
1620 lineno_stmt_decl_or_labels_ending_error:
1621         errstmt
1622         | lineno_stmt_decl_or_labels errstmt
1623         ;
1625 lineno_stmt_decl_or_labels:
1626           lineno_stmt_decl_or_labels_ending_stmt
1627         | lineno_stmt_decl_or_labels_ending_decl
1628         | lineno_stmt_decl_or_labels_ending_label
1629         | lineno_stmt_decl_or_labels_ending_error
1630         ;
1632 errstmt:  error ';'
1633         ;
1635 pushlevel:  /* empty */
1636                 { pushlevel (0);
1637                   clear_last_expr ();
1638                   add_scope_stmt (/*begin_p=*/1, /*partial_p=*/0);
1639 ifobjc
1640                   if (objc_method_context)
1641                     add_objc_decls ();
1642 end ifobjc
1643                 }
1644         ;
1646 poplevel:  /* empty */
1647                 { $$ = add_scope_stmt (/*begin_p=*/0, /*partial_p=*/0); }
1649 /* Start and end blocks created for the new scopes of C99.  */
1650 c99_block_start: /* empty */
1651                 { if (flag_isoc99)
1652                     {
1653                       $$ = c_begin_compound_stmt ();
1654                       pushlevel (0);
1655                       clear_last_expr ();
1656                       add_scope_stmt (/*begin_p=*/1, /*partial_p=*/0);
1657 ifobjc
1658                       if (objc_method_context)
1659                         add_objc_decls ();
1660 end ifobjc
1661                     }
1662                   else
1663                     $$ = NULL_TREE;
1664                 }
1665         ;
1667 /* Productions using c99_block_start and c99_block_end will need to do what's
1668    in compstmt: RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); $$ = $2; where
1669    $1 is the value of c99_block_start and $2 of c99_block_end.  */
1670 c99_block_end: /* empty */
1671                 { if (flag_isoc99)
1672                     {
1673                       tree scope_stmt = add_scope_stmt (/*begin_p=*/0, /*partial_p=*/0);
1674                       $$ = poplevel (kept_level_p (), 0, 0); 
1675                       SCOPE_STMT_BLOCK (TREE_PURPOSE (scope_stmt)) 
1676                         = SCOPE_STMT_BLOCK (TREE_VALUE (scope_stmt))
1677                         = $$;
1678                     }
1679                   else
1680                     $$ = NULL_TREE; }
1681         ;
1683 /* Read zero or more forward-declarations for labels
1684    that nested functions can jump to.  */
1685 maybe_label_decls:
1686           /* empty */
1687         | label_decls
1688                 { if (pedantic)
1689                     pedwarn ("ISO C forbids label declarations"); }
1690         ;
1692 label_decls:
1693           label_decl
1694         | label_decls label_decl
1695         ;
1697 label_decl:
1698           LABEL identifiers_or_typenames ';'
1699                 { tree link;
1700                   for (link = $2; link; link = TREE_CHAIN (link))
1701                     {
1702                       tree label = shadow_label (TREE_VALUE (link));
1703                       C_DECLARED_LABEL_FLAG (label) = 1;
1704                       add_decl_stmt (label);
1705                     }
1706                 }
1707         ;
1709 /* This is the body of a function definition.
1710    It causes syntax errors to ignore to the next openbrace.  */
1711 compstmt_or_error:
1712           compstmt
1713                 {}
1714         | error compstmt
1715         ;
1717 compstmt_start: '{' { compstmt_count++;
1718                       $$ = c_begin_compound_stmt (); } 
1720 compstmt_nostart: '}'
1721                 { $$ = convert (void_type_node, integer_zero_node); }
1722         | pushlevel maybe_label_decls compstmt_contents_nonempty '}' poplevel
1723                 { $$ = poplevel (kept_level_p (), 1, 0); 
1724                   SCOPE_STMT_BLOCK (TREE_PURPOSE ($5)) 
1725                     = SCOPE_STMT_BLOCK (TREE_VALUE ($5))
1726                     = $$; }
1727         ;
1729 compstmt_contents_nonempty:
1730           stmts_and_decls
1731         | error
1732         ;
1734 compstmt_primary_start:
1735         '(' '{'
1736                 { if (current_function_decl == 0)
1737                     {
1738                       error ("braced-group within expression allowed only inside a function");
1739                       YYERROR;
1740                     }
1741                   /* We must force a BLOCK for this level
1742                      so that, if it is not expanded later,
1743                      there is a way to turn off the entire subtree of blocks
1744                      that are contained in it.  */
1745                   keep_next_level ();
1746                   push_label_level ();
1747                   compstmt_count++;
1748                   $$ = add_stmt (build_stmt (COMPOUND_STMT, last_tree));
1749                 }
1751 compstmt: compstmt_start compstmt_nostart
1752                 { RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); 
1753                   $$ = $2; }
1754         ;
1756 /* Value is number of statements counted as of the closeparen.  */
1757 simple_if:
1758           if_prefix c99_block_lineno_labeled_stmt
1759                 { c_finish_then (); }
1760 /* Make sure c_expand_end_cond is run once
1761    for each call to c_expand_start_cond.
1762    Otherwise a crash is likely.  */
1763         | if_prefix error
1764         ;
1766 if_prefix:
1767           IF '(' expr ')'
1768                 { c_expand_start_cond (truthvalue_conversion ($3), 
1769                                        compstmt_count);
1770                   $<itype>$ = stmt_count;
1771                   if_stmt_file = $<filename>-2;
1772                   if_stmt_line = $<lineno>-1; }
1773         ;
1775 /* This is a subroutine of stmt.
1776    It is used twice, once for valid DO statements
1777    and once for catching errors in parsing the end test.  */
1778 do_stmt_start:
1779           DO
1780                 { stmt_count++;
1781                   compstmt_count++;
1782                   $<ttype>$ 
1783                     = add_stmt (build_stmt (DO_STMT, NULL_TREE,
1784                                             NULL_TREE));
1785                   /* In the event that a parse error prevents
1786                      parsing the complete do-statement, set the
1787                      condition now.  Otherwise, we can get crashes at
1788                      RTL-generation time.  */
1789                   DO_COND ($<ttype>$) = error_mark_node; }
1790           c99_block_lineno_labeled_stmt WHILE
1791                 { $$ = $<ttype>2;
1792                   RECHAIN_STMTS ($$, DO_BODY ($$)); }
1793         ;
1795 /* The forced readahead in here is because we might be at the end of a
1796    line, and the line and file won't be bumped until yylex absorbs the
1797    first token on the next line.  */
1798 save_filename:
1799                 { if (yychar == YYEMPTY)
1800                     yychar = YYLEX;
1801                   $$ = input_filename; }
1802         ;
1804 save_lineno:
1805                 { if (yychar == YYEMPTY)
1806                     yychar = YYLEX;
1807                   $$ = lineno; }
1808         ;
1810 lineno_labeled_stmt:
1811           save_filename save_lineno stmt
1812                 { }
1813 /*      | save_filename save_lineno error
1814                 { }
1816         | save_filename save_lineno label lineno_labeled_stmt
1817                 { }
1818         ;
1820 /* Like lineno_labeled_stmt, but a block in C99.  */
1821 c99_block_lineno_labeled_stmt:
1822           c99_block_start lineno_labeled_stmt c99_block_end
1823                 { if (flag_isoc99)
1824                     RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); }
1825         ;
1827 lineno_stmt:
1828           save_filename save_lineno stmt
1829                 { }
1830         ;
1832 lineno_label:
1833           save_filename save_lineno label
1834                 { }
1835         ;
1837 select_or_iter_stmt:
1838           simple_if ELSE
1839                 { c_expand_start_else ();
1840                   $<itype>1 = stmt_count; }
1841           c99_block_lineno_labeled_stmt
1842                 { c_finish_else ();
1843                   c_expand_end_cond ();
1844                   if (extra_warnings && stmt_count == $<itype>1)
1845                     warning ("empty body in an else-statement"); }
1846         | simple_if %prec IF
1847                 { c_expand_end_cond ();
1848                   /* This warning is here instead of in simple_if, because we
1849                      do not want a warning if an empty if is followed by an
1850                      else statement.  Increment stmt_count so we don't
1851                      give a second error if this is a nested `if'.  */
1852                   if (extra_warnings && stmt_count++ == $<itype>1)
1853                     warning_with_file_and_line (if_stmt_file, if_stmt_line,
1854                                                 "empty body in an if-statement"); }
1855 /* Make sure c_expand_end_cond is run once
1856    for each call to c_expand_start_cond.
1857    Otherwise a crash is likely.  */
1858         | simple_if ELSE error
1859                 { c_expand_end_cond (); }
1860         | WHILE
1861                 { stmt_count++; }
1862           '(' expr ')'
1863                 { $4 = truthvalue_conversion ($4);
1864                   $<ttype>$ 
1865                     = add_stmt (build_stmt (WHILE_STMT, $4, NULL_TREE)); }
1866           c99_block_lineno_labeled_stmt
1867                 { RECHAIN_STMTS ($<ttype>6, WHILE_BODY ($<ttype>6)); }
1868         | do_stmt_start
1869           '(' expr ')' ';'
1870                 { DO_COND ($1) = truthvalue_conversion ($3); }
1871         | do_stmt_start error
1872                 { }
1873         | FOR
1874                 { $<ttype>$ = build_stmt (FOR_STMT, NULL_TREE, NULL_TREE,
1875                                           NULL_TREE, NULL_TREE);
1876                   add_stmt ($<ttype>$); } 
1877           '(' for_init_stmt
1878                 { stmt_count++;
1879                   RECHAIN_STMTS ($<ttype>2, FOR_INIT_STMT ($<ttype>2)); }
1880           xexpr ';'
1881                 { FOR_COND ($<ttype>2) = $6; }
1882           xexpr ')'
1883                 { FOR_EXPR ($<ttype>2) = $9; }
1884           c99_block_lineno_labeled_stmt
1885                 { RECHAIN_STMTS ($<ttype>2, FOR_BODY ($<ttype>2)); }
1886         | SWITCH '(' expr ')'
1887                 { stmt_count++;
1888                   $<ttype>$ = c_start_case ($3); }
1889           c99_block_lineno_labeled_stmt
1890                 { c_finish_case (); }
1891         ;
1893 for_init_stmt:
1894           xexpr ';'
1895                 { add_stmt (build_stmt (EXPR_STMT, $1)); } 
1896         | decl
1897                 { check_for_loop_decls (); }
1898         ;
1900 /* Parse a single real statement, not including any labels.  */
1901 stmt:
1902           compstmt
1903                 { stmt_count++; }
1904         | expr ';'
1905                 { stmt_count++;
1906                   c_expand_expr_stmt ($1); }
1907         | c99_block_start select_or_iter_stmt c99_block_end
1908                 { if (flag_isoc99)
1909                     RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); }
1910         | BREAK ';'
1911                 { stmt_count++;
1912                   add_stmt (build_break_stmt ()); }
1913         | CONTINUE ';'
1914                 { stmt_count++;
1915                   add_stmt (build_continue_stmt ()); }
1916         | RETURN ';'
1917                 { stmt_count++;
1918                   c_expand_return (NULL_TREE); }
1919         | RETURN expr ';'
1920                 { stmt_count++;
1921                   c_expand_return ($2); }
1922         | ASM_KEYWORD maybe_type_qual '(' expr ')' ';'
1923                 { stmt_count++;
1924                   STRIP_NOPS ($4);
1925                   if ((TREE_CODE ($4) == ADDR_EXPR
1926                        && TREE_CODE (TREE_OPERAND ($4, 0)) == STRING_CST)
1927                       || TREE_CODE ($4) == STRING_CST)
1928                     {
1929                       if (TREE_CODE ($4) == ADDR_EXPR)
1930                         $4 = TREE_OPERAND ($4, 0);
1931                       if (TREE_CHAIN ($4))
1932                         $4 = combine_strings ($4);
1933                       add_stmt (build_stmt (ASM_STMT, NULL_TREE, $4,
1934                                             NULL_TREE, NULL_TREE, NULL_TREE));
1935                     }
1936                   else
1937                     error ("argument of `asm' is not a constant string"); }
1938         /* This is the case with just output operands.  */
1939         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ')' ';'
1940                 { stmt_count++;
1941                   c_expand_asm_operands ($4, $6, NULL_TREE, NULL_TREE,
1942                                          $2 == ridpointers[(int)RID_VOLATILE],
1943                                          input_filename, lineno); }
1944         /* This is the case with input operands as well.  */
1945         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':' asm_operands ')' ';'
1946                 { stmt_count++;
1947                   c_expand_asm_operands ($4, $6, $8, NULL_TREE,
1948                                          $2 == ridpointers[(int)RID_VOLATILE],
1949                                          input_filename, lineno); }
1950         /* This is the case with clobbered registers as well.  */
1951         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':'
1952           asm_operands ':' asm_clobbers ')' ';'
1953                 { stmt_count++;
1954                   c_expand_asm_operands ($4, $6, $8, $10,
1955                                          $2 == ridpointers[(int)RID_VOLATILE],
1956                                          input_filename, lineno); }
1957         | GOTO identifier ';'
1958                 { tree decl;
1959                   stmt_count++;
1960                   decl = lookup_label ($2);
1961                   if (decl != 0)
1962                     {
1963                       TREE_USED (decl) = 1;
1964                       add_stmt (build_stmt (GOTO_STMT, decl));
1965                     }
1966                 }
1967         | GOTO '*' expr ';'
1968                 { if (pedantic)
1969                     pedwarn ("ISO C forbids `goto *expr;'");
1970                   stmt_count++;
1971                   $3 = convert (ptr_type_node, $3);
1972                   add_stmt (build_stmt (GOTO_STMT, $3)); }
1973         | ';'
1974         ;
1976 /* Any kind of label, including jump labels and case labels.
1977    ANSI C accepts labels only before statements, but we allow them
1978    also at the end of a compound statement.  */
1980 label:    CASE expr_no_commas ':'
1981                 { stmt_count++;
1982                   do_case ($2, NULL_TREE); }
1983         | CASE expr_no_commas ELLIPSIS expr_no_commas ':'
1984                 { stmt_count++;
1985                   do_case ($2, $4); }
1986         | DEFAULT ':'
1987                 { stmt_count++;
1988                   do_case (NULL_TREE, NULL_TREE); }
1989         | identifier save_filename save_lineno ':' maybe_attribute
1990                 { tree label = define_label ($2, $3, $1);
1991                   stmt_count++;
1992                   if (label)
1993                     {
1994                       decl_attributes (label, $5, NULL_TREE);
1995                       add_stmt (build_stmt (LABEL_STMT, label));
1996                     }
1997                 }
1998         ;
2000 /* Either a type-qualifier or nothing.  First thing in an `asm' statement.  */
2002 maybe_type_qual:
2003         /* empty */
2004                 { emit_line_note (input_filename, lineno);
2005                   $$ = NULL_TREE; }
2006         | TYPE_QUAL
2007                 { emit_line_note (input_filename, lineno); }
2008         ;
2010 xexpr:
2011         /* empty */
2012                 { $$ = NULL_TREE; }
2013         | expr
2014         ;
2016 /* These are the operands other than the first string and colon
2017    in  asm ("addextend %2,%1": "=dm" (x), "0" (y), "g" (*x))  */
2018 asm_operands: /* empty */
2019                 { $$ = NULL_TREE; }
2020         | nonnull_asm_operands
2021         ;
2023 nonnull_asm_operands:
2024           asm_operand
2025         | nonnull_asm_operands ',' asm_operand
2026                 { $$ = chainon ($1, $3); }
2027         ;
2029 asm_operand:
2030           STRING '(' expr ')'
2031                 { $$ = build_tree_list ($1, $3); }
2032         ;
2034 asm_clobbers:
2035           string
2036                 { $$ = tree_cons (NULL_TREE, combine_strings ($1), NULL_TREE); }
2037         | asm_clobbers ',' string
2038                 { $$ = tree_cons (NULL_TREE, combine_strings ($3), $1); }
2039         ;
2041 /* This is what appears inside the parens in a function declarator.
2042    Its value is a list of ..._TYPE nodes.  */
2043 parmlist:
2044                 { pushlevel (0);
2045                   clear_parm_order ();
2046                   declare_parm_level (0); }
2047           parmlist_1
2048                 { $$ = $2;
2049                   parmlist_tags_warning ();
2050                   poplevel (0, 0, 0); }
2051         ;
2053 parmlist_1:
2054           parmlist_2 ')'
2055         | parms ';'
2056                 { tree parm;
2057                   if (pedantic)
2058                     pedwarn ("ISO C forbids forward parameter declarations");
2059                   /* Mark the forward decls as such.  */
2060                   for (parm = getdecls (); parm; parm = TREE_CHAIN (parm))
2061                     TREE_ASM_WRITTEN (parm) = 1;
2062                   clear_parm_order (); }
2063           parmlist_1
2064                 { $$ = $4; }
2065         | error ')'
2066                 { $$ = tree_cons (NULL_TREE, NULL_TREE, NULL_TREE); }
2067         ;
2069 /* This is what appears inside the parens in a function declarator.
2070    Is value is represented in the format that grokdeclarator expects.  */
2071 parmlist_2:  /* empty */
2072                 { $$ = get_parm_info (0); }
2073         | ELLIPSIS
2074                 { $$ = get_parm_info (0);
2075                   /* Gcc used to allow this as an extension.  However, it does
2076                      not work for all targets, and thus has been disabled.
2077                      Also, since func (...) and func () are indistinguishable,
2078                      it caused problems with the code in expand_builtin which
2079                      tries to verify that BUILT_IN_NEXT_ARG is being used
2080                      correctly.  */
2081                   error ("ISO C requires a named argument before `...'");
2082                 }
2083         | parms
2084                 { $$ = get_parm_info (1); }
2085         | parms ',' ELLIPSIS
2086                 { $$ = get_parm_info (0); }
2087         ;
2089 parms:
2090         parm
2091                 { push_parm_decl ($1); }
2092         | parms ',' parm
2093                 { push_parm_decl ($3); }
2094         ;
2096 /* A single parameter declaration or parameter type name,
2097    as found in a parmlist.  */
2098 parm:
2099           typed_declspecs setspecs parm_declarator maybe_attribute
2100                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2101                                                          $3),
2102                                         build_tree_list (prefix_attributes,
2103                                                          $4));
2104                   current_declspecs = TREE_VALUE (declspec_stack);
2105                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2106                   declspec_stack = TREE_CHAIN (declspec_stack); }
2107         | typed_declspecs setspecs notype_declarator maybe_attribute
2108                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2109                                                          $3),
2110                                         build_tree_list (prefix_attributes,
2111                                                          $4)); 
2112                   current_declspecs = TREE_VALUE (declspec_stack);
2113                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2114                   declspec_stack = TREE_CHAIN (declspec_stack); }
2115         | typed_declspecs setspecs absdcl maybe_attribute
2116                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2117                                                          $3),
2118                                         build_tree_list (prefix_attributes,
2119                                                          $4));
2120                   current_declspecs = TREE_VALUE (declspec_stack);
2121                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2122                   declspec_stack = TREE_CHAIN (declspec_stack); }
2123         | declmods setspecs notype_declarator maybe_attribute
2124                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2125                                                          $3),
2126                                         build_tree_list (prefix_attributes,
2127                                                          $4));
2128                   current_declspecs = TREE_VALUE (declspec_stack);
2129                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2130                   declspec_stack = TREE_CHAIN (declspec_stack); }
2132         | declmods setspecs absdcl maybe_attribute
2133                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2134                                                          $3),
2135                                         build_tree_list (prefix_attributes,
2136                                                          $4));
2137                   current_declspecs = TREE_VALUE (declspec_stack);
2138                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2139                   declspec_stack = TREE_CHAIN (declspec_stack); }
2140         ;
2142 /* This is used in a function definition
2143    where either a parmlist or an identifier list is ok.
2144    Its value is a list of ..._TYPE nodes or a list of identifiers.  */
2145 parmlist_or_identifiers:
2146                 { pushlevel (0);
2147                   clear_parm_order ();
2148                   declare_parm_level (1); }
2149           parmlist_or_identifiers_1
2150                 { $$ = $2;
2151                   parmlist_tags_warning ();
2152                   poplevel (0, 0, 0); }
2153         ;
2155 parmlist_or_identifiers_1:
2156           parmlist_1
2157         | identifiers ')'
2158                 { tree t;
2159                   for (t = $1; t; t = TREE_CHAIN (t))
2160                     if (TREE_VALUE (t) == NULL_TREE)
2161                       error ("`...' in old-style identifier list");
2162                   $$ = tree_cons (NULL_TREE, NULL_TREE, $1); }
2163         ;
2165 /* A nonempty list of identifiers.  */
2166 identifiers:
2167         IDENTIFIER
2168                 { $$ = build_tree_list (NULL_TREE, $1); }
2169         | identifiers ',' IDENTIFIER
2170                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2171         ;
2173 /* A nonempty list of identifiers, including typenames.  */
2174 identifiers_or_typenames:
2175         identifier
2176                 { $$ = build_tree_list (NULL_TREE, $1); }
2177         | identifiers_or_typenames ',' identifier
2178                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2179         ;
2181 extension:
2182         EXTENSION
2183                 { $$ = SAVE_WARN_FLAGS();
2184                   pedantic = 0;
2185                   warn_pointer_arith = 0; }
2186         ;
2188 ifobjc
2189 /* Objective-C productions.  */
2191 objcdef:
2192           classdef
2193         | classdecl
2194         | aliasdecl
2195         | protocoldef
2196         | methoddef
2197         | END
2198                 {
2199                   if (objc_implementation_context)
2200                     {
2201                       finish_class (objc_implementation_context);
2202                       objc_ivar_chain = NULL_TREE;
2203                       objc_implementation_context = NULL_TREE;
2204                     }
2205                   else
2206                     warning ("`@end' must appear in an implementation context");
2207                 }
2208         ;
2210 /* A nonempty list of identifiers.  */
2211 identifier_list:
2212         identifier
2213                 { $$ = build_tree_list (NULL_TREE, $1); }
2214         | identifier_list ',' identifier
2215                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2216         ;
2218 classdecl:
2219           CLASS identifier_list ';'
2220                 {
2221                   objc_declare_class ($2);
2222                 }
2224 aliasdecl:
2225           ALIAS identifier identifier ';'
2226                 {
2227                   objc_declare_alias ($2, $3);
2228                 }
2230 classdef:
2231           INTERFACE identifier protocolrefs '{'
2232                 {
2233                   objc_interface_context = objc_ivar_context
2234                     = start_class (CLASS_INTERFACE_TYPE, $2, NULL_TREE, $3);
2235                   objc_public_flag = 0;
2236                 }
2237           ivar_decl_list '}'
2238                 {
2239                   continue_class (objc_interface_context);
2240                 }
2241           methodprotolist
2242           END
2243                 {
2244                   finish_class (objc_interface_context);
2245                   objc_interface_context = NULL_TREE;
2246                 }
2248         | INTERFACE identifier protocolrefs
2249                 {
2250                   objc_interface_context
2251                     = start_class (CLASS_INTERFACE_TYPE, $2, NULL_TREE, $3);
2252                   continue_class (objc_interface_context);
2253                 }
2254           methodprotolist
2255           END
2256                 {
2257                   finish_class (objc_interface_context);
2258                   objc_interface_context = NULL_TREE;
2259                 }
2261         | INTERFACE identifier ':' identifier protocolrefs '{'
2262                 {
2263                   objc_interface_context = objc_ivar_context
2264                     = start_class (CLASS_INTERFACE_TYPE, $2, $4, $5);
2265                   objc_public_flag = 0;
2266                 }
2267           ivar_decl_list '}'
2268                 {
2269                   continue_class (objc_interface_context);
2270                 }
2271           methodprotolist
2272           END
2273                 {
2274                   finish_class (objc_interface_context);
2275                   objc_interface_context = NULL_TREE;
2276                 }
2278         | INTERFACE identifier ':' identifier protocolrefs
2279                 {
2280                   objc_interface_context
2281                     = start_class (CLASS_INTERFACE_TYPE, $2, $4, $5);
2282                   continue_class (objc_interface_context);
2283                 }
2284           methodprotolist
2285           END
2286                 {
2287                   finish_class (objc_interface_context);
2288                   objc_interface_context = NULL_TREE;
2289                 }
2291         | IMPLEMENTATION identifier '{'
2292                 {
2293                   objc_implementation_context = objc_ivar_context
2294                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, NULL_TREE, NULL_TREE);
2295                   objc_public_flag = 0;
2296                 }
2297           ivar_decl_list '}'
2298                 {
2299                   objc_ivar_chain
2300                     = continue_class (objc_implementation_context);
2301                 }
2303         | IMPLEMENTATION identifier
2304                 {
2305                   objc_implementation_context
2306                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, NULL_TREE, NULL_TREE);
2307                   objc_ivar_chain
2308                     = continue_class (objc_implementation_context);
2309                 }
2311         | IMPLEMENTATION identifier ':' identifier '{'
2312                 {
2313                   objc_implementation_context = objc_ivar_context
2314                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2315                   objc_public_flag = 0;
2316                 }
2317           ivar_decl_list '}'
2318                 {
2319                   objc_ivar_chain
2320                     = continue_class (objc_implementation_context);
2321                 }
2323         | IMPLEMENTATION identifier ':' identifier
2324                 {
2325                   objc_implementation_context
2326                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2327                   objc_ivar_chain
2328                     = continue_class (objc_implementation_context);
2329                 }
2331         | INTERFACE identifier '(' identifier ')' protocolrefs
2332                 {
2333                   objc_interface_context
2334                     = start_class (CATEGORY_INTERFACE_TYPE, $2, $4, $6);
2335                   continue_class (objc_interface_context);
2336                 }
2337           methodprotolist
2338           END
2339                 {
2340                   finish_class (objc_interface_context);
2341                   objc_interface_context = NULL_TREE;
2342                 }
2344         | IMPLEMENTATION identifier '(' identifier ')'
2345                 {
2346                   objc_implementation_context
2347                     = start_class (CATEGORY_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2348                   objc_ivar_chain
2349                     = continue_class (objc_implementation_context);
2350                 }
2351         ;
2353 protocoldef:
2354           PROTOCOL identifier protocolrefs
2355                 {
2356                   remember_protocol_qualifiers ();
2357                   objc_interface_context
2358                     = start_protocol(PROTOCOL_INTERFACE_TYPE, $2, $3);
2359                 }
2360           methodprotolist END
2361                 {
2362                   forget_protocol_qualifiers();
2363                   finish_protocol(objc_interface_context);
2364                   objc_interface_context = NULL_TREE;
2365                 }
2366         ;
2368 protocolrefs:
2369           /* empty */
2370                 {
2371                   $$ = NULL_TREE;
2372                 }
2373         | non_empty_protocolrefs
2374         ;
2376 non_empty_protocolrefs:
2377           ARITHCOMPARE identifier_list ARITHCOMPARE
2378                 {
2379                   if ($1 == LT_EXPR && $3 == GT_EXPR)
2380                     $$ = $2;
2381                   else
2382                     YYERROR1;
2383                 }
2384         ;
2386 ivar_decl_list:
2387           ivar_decl_list visibility_spec ivar_decls
2388         | ivar_decls
2389         ;
2391 visibility_spec:
2392           PRIVATE { objc_public_flag = 2; }
2393         | PROTECTED { objc_public_flag = 0; }
2394         | PUBLIC { objc_public_flag = 1; }
2395         ;
2397 ivar_decls:
2398           /* empty */
2399                 {
2400                   $$ = NULL_TREE;
2401                 }
2402         | ivar_decls ivar_decl ';'
2403         | ivar_decls ';'
2404                 {
2405                   if (pedantic)
2406                     pedwarn ("extra semicolon in struct or union specified");
2407                 }
2408         ;
2411 /* There is a shift-reduce conflict here, because `components' may
2412    start with a `typename'.  It happens that shifting (the default resolution)
2413    does the right thing, because it treats the `typename' as part of
2414    a `typed_typespecs'.
2416    It is possible that this same technique would allow the distinction
2417    between `notype_initdecls' and `initdecls' to be eliminated.
2418    But I am being cautious and not trying it.  */
2420 ivar_decl:
2421         typed_typespecs setspecs ivars
2422                 { $$ = $3;
2423                   current_declspecs = TREE_VALUE (declspec_stack);
2424                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2425                   declspec_stack = TREE_CHAIN (declspec_stack); }
2426         | nonempty_type_quals setspecs ivars
2427                 { $$ = $3;
2428                   current_declspecs = TREE_VALUE (declspec_stack);
2429                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2430                   declspec_stack = TREE_CHAIN (declspec_stack); }
2431         | error
2432                 { $$ = NULL_TREE; }
2433         ;
2435 ivars:
2436           /* empty */
2437                 { $$ = NULL_TREE; }
2438         | ivar_declarator
2439         | ivars ',' ivar_declarator
2440         ;
2442 ivar_declarator:
2443           declarator
2444                 {
2445                   $$ = add_instance_variable (objc_ivar_context,
2446                                               objc_public_flag,
2447                                               $1, current_declspecs,
2448                                               NULL_TREE);
2449                 }
2450         | declarator ':' expr_no_commas
2451                 {
2452                   $$ = add_instance_variable (objc_ivar_context,
2453                                               objc_public_flag,
2454                                               $1, current_declspecs, $3);
2455                 }
2456         | ':' expr_no_commas
2457                 {
2458                   $$ = add_instance_variable (objc_ivar_context,
2459                                               objc_public_flag,
2460                                               NULL_TREE,
2461                                               current_declspecs, $2);
2462                 }
2463         ;
2465 methoddef:
2466           '+'
2467                 {
2468                   remember_protocol_qualifiers ();
2469                   if (objc_implementation_context)
2470                     objc_inherit_code = CLASS_METHOD_DECL;
2471                   else
2472                     fatal ("method definition not in class context");
2473                 }
2474           methoddecl
2475                 {
2476                   forget_protocol_qualifiers ();
2477                   add_class_method (objc_implementation_context, $3);
2478                   start_method_def ($3);
2479                   objc_method_context = $3;
2480                 }
2481           optarglist
2482                 {
2483                   continue_method_def ();
2484                 }
2485           compstmt_or_error
2486                 {
2487                   finish_method_def ();
2488                   objc_method_context = NULL_TREE;
2489                 }
2491         | '-'
2492                 {
2493                   remember_protocol_qualifiers ();
2494                   if (objc_implementation_context)
2495                     objc_inherit_code = INSTANCE_METHOD_DECL;
2496                   else
2497                     fatal ("method definition not in class context");
2498                 }
2499           methoddecl
2500                 {
2501                   forget_protocol_qualifiers ();
2502                   add_instance_method (objc_implementation_context, $3);
2503                   start_method_def ($3);
2504                   objc_method_context = $3;
2505                 }
2506           optarglist
2507                 {
2508                   continue_method_def ();
2509                 }
2510           compstmt_or_error
2511                 {
2512                   finish_method_def ();
2513                   objc_method_context = NULL_TREE;
2514                 }
2515         ;
2517 /* the reason for the strange actions in this rule
2518  is so that notype_initdecls when reached via datadef
2519  can find a valid list of type and sc specs in $0. */
2521 methodprotolist:
2522           /* empty  */
2523         | {$<ttype>$ = NULL_TREE; } methodprotolist2
2524         ;
2526 methodprotolist2:                /* eliminates a shift/reduce conflict */
2527            methodproto
2528         |  datadef
2529         | methodprotolist2 methodproto
2530         | methodprotolist2 {$<ttype>$ = NULL_TREE; } datadef
2531         ;
2533 semi_or_error:
2534           ';'
2535         | error
2536         ;
2538 methodproto:
2539           '+'
2540                 {
2541                   /* Remember protocol qualifiers in prototypes.  */
2542                   remember_protocol_qualifiers ();
2543                   objc_inherit_code = CLASS_METHOD_DECL;
2544                 }
2545           methoddecl
2546                 {
2547                   /* Forget protocol qualifiers here.  */
2548                   forget_protocol_qualifiers ();
2549                   add_class_method (objc_interface_context, $3);
2550                 }
2551           semi_or_error
2553         | '-'
2554                 {
2555                   /* Remember protocol qualifiers in prototypes.  */
2556                   remember_protocol_qualifiers ();
2557                   objc_inherit_code = INSTANCE_METHOD_DECL;
2558                 }
2559           methoddecl
2560                 {
2561                   /* Forget protocol qualifiers here.  */
2562                   forget_protocol_qualifiers ();
2563                   add_instance_method (objc_interface_context, $3);
2564                 }
2565           semi_or_error
2566         ;
2568 methoddecl:
2569           '(' typename ')' unaryselector
2570                 {
2571                   $$ = build_method_decl (objc_inherit_code, $2, $4, NULL_TREE);
2572                 }
2574         | unaryselector
2575                 {
2576                   $$ = build_method_decl (objc_inherit_code, NULL_TREE, $1, NULL_TREE);
2577                 }
2579         | '(' typename ')' keywordselector optparmlist
2580                 {
2581                   $$ = build_method_decl (objc_inherit_code, $2, $4, $5);
2582                 }
2584         | keywordselector optparmlist
2585                 {
2586                   $$ = build_method_decl (objc_inherit_code, NULL_TREE, $1, $2);
2587                 }
2588         ;
2590 /* "optarglist" assumes that start_method_def has already been called...
2591    if it is not, the "xdecls" will not be placed in the proper scope */
2593 optarglist:
2594           /* empty */
2595         | ';' myxdecls
2596         ;
2598 /* to get around the following situation: "int foo (int a) int b; {}" that
2599    is synthesized when parsing "- a:a b:b; id c; id d; { ... }" */
2601 myxdecls:
2602           /* empty */
2603         | mydecls
2604         ;
2606 mydecls:
2607         mydecl
2608         | errstmt
2609         | mydecls mydecl
2610         | mydecl errstmt
2611         ;
2613 mydecl:
2614         typed_declspecs setspecs myparms ';'
2615                 { current_declspecs = TREE_VALUE (declspec_stack);
2616                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2617                   declspec_stack = TREE_CHAIN (declspec_stack); }
2618         | typed_declspecs ';'
2619                 { shadow_tag ($1); }
2620         | declmods ';'
2621                 { pedwarn ("empty declaration"); }
2622         ;
2624 myparms:
2625         myparm
2626                 { push_parm_decl ($1); }
2627         | myparms ',' myparm
2628                 { push_parm_decl ($3); }
2629         ;
2631 /* A single parameter declaration or parameter type name,
2632    as found in a parmlist. DOES NOT ALLOW AN INITIALIZER OR ASMSPEC */
2634 myparm:
2635           parm_declarator maybe_attribute
2636                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2637                                                          $1),
2638                                         build_tree_list (prefix_attributes,
2639                                                          $2)); }
2640         | notype_declarator maybe_attribute
2641                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2642                                                          $1),
2643                                         build_tree_list (prefix_attributes,
2644                                                          $2)); }
2645         | absdcl maybe_attribute
2646                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2647                                                          $1),
2648                                         build_tree_list (prefix_attributes,
2649                                                          $2)); }
2650         ;
2652 optparmlist:
2653           /* empty */
2654                 {
2655                   $$ = NULL_TREE;
2656                 }
2657         | ',' ELLIPSIS
2658                 {
2659                   /* oh what a kludge! */
2660                   $$ = objc_ellipsis_node;
2661                 }
2662         | ','
2663                 {
2664                   pushlevel (0);
2665                 }
2666           parmlist_2
2667                 {
2668                   /* returns a tree list node generated by get_parm_info */
2669                   $$ = $3;
2670                   poplevel (0, 0, 0);
2671                 }
2672         ;
2674 unaryselector:
2675           selector
2676         ;
2678 keywordselector:
2679           keyworddecl
2681         | keywordselector keyworddecl
2682                 {
2683                   $$ = chainon ($1, $2);
2684                 }
2685         ;
2687 selector:
2688           IDENTIFIER
2689         | TYPENAME
2690         | OBJECTNAME
2691         | reservedwords
2692         ;
2694 reservedwords:
2695           ENUM | STRUCT | UNION | IF | ELSE | WHILE | DO | FOR
2696         | SWITCH | CASE | DEFAULT | BREAK | CONTINUE | RETURN
2697         | GOTO | ASM_KEYWORD | SIZEOF | TYPEOF | ALIGNOF
2698         | TYPESPEC | TYPE_QUAL
2699         ;
2701 keyworddecl:
2702           selector ':' '(' typename ')' identifier
2703                 {
2704                   $$ = build_keyword_decl ($1, $4, $6);
2705                 }
2707         | selector ':' identifier
2708                 {
2709                   $$ = build_keyword_decl ($1, NULL_TREE, $3);
2710                 }
2712         | ':' '(' typename ')' identifier
2713                 {
2714                   $$ = build_keyword_decl (NULL_TREE, $3, $5);
2715                 }
2717         | ':' identifier
2718                 {
2719                   $$ = build_keyword_decl (NULL_TREE, NULL_TREE, $2);
2720                 }
2721         ;
2723 messageargs:
2724           selector
2725         | keywordarglist
2726         ;
2728 keywordarglist:
2729           keywordarg
2730         | keywordarglist keywordarg
2731                 {
2732                   $$ = chainon ($1, $2);
2733                 }
2734         ;
2737 keywordexpr:
2738           nonnull_exprlist
2739                 {
2740                   if (TREE_CHAIN ($1) == NULL_TREE)
2741                     /* just return the expr., remove a level of indirection */
2742                     $$ = TREE_VALUE ($1);
2743                   else
2744                     /* we have a comma expr., we will collapse later */
2745                     $$ = $1;
2746                 }
2747         ;
2749 keywordarg:
2750           selector ':' keywordexpr
2751                 {
2752                   $$ = build_tree_list ($1, $3);
2753                 }
2754         | ':' keywordexpr
2755                 {
2756                   $$ = build_tree_list (NULL_TREE, $2);
2757                 }
2758         ;
2760 receiver:
2761           expr
2762         | CLASSNAME
2763                 {
2764                   $$ = get_class_reference ($1);
2765                 }
2766         ;
2768 objcmessageexpr:
2769           '['
2770                 { objc_receiver_context = 1; }
2771           receiver
2772                 { objc_receiver_context = 0; }
2773           messageargs ']'
2774                 {
2775                   $$ = build_tree_list ($3, $5);
2776                 }
2777         ;
2779 selectorarg:
2780           selector
2781         | keywordnamelist
2782         ;
2784 keywordnamelist:
2785           keywordname
2786         | keywordnamelist keywordname
2787                 {
2788                   $$ = chainon ($1, $2);
2789                 }
2790         ;
2792 keywordname:
2793           selector ':'
2794                 {
2795                   $$ = build_tree_list ($1, NULL_TREE);
2796                 }
2797         | ':'
2798                 {
2799                   $$ = build_tree_list (NULL_TREE, NULL_TREE);
2800                 }
2801         ;
2803 objcselectorexpr:
2804           SELECTOR '(' selectorarg ')'
2805                 {
2806                   $$ = $3;
2807                 }
2808         ;
2810 objcprotocolexpr:
2811           PROTOCOL '(' identifier ')'
2812                 {
2813                   $$ = $3;
2814                 }
2815         ;
2817 /* extension to support C-structures in the archiver */
2819 objcencodeexpr:
2820           ENCODE '(' typename ')'
2821                 {
2822                   $$ = groktypename ($3);
2823                 }
2824         ;
2826 end ifobjc
2829 /* yylex() is a thin wrapper around c_lex(), all it does is translate
2830    cpplib.h's token codes into yacc's token codes.  */
2832 static enum cpp_ttype last_token;
2833 #if USE_CPPLIB
2834 extern cpp_reader parse_in;
2835 #endif
2837 /* The reserved keyword table.  */
2838 struct resword
2840   const char *word;
2841   ENUM_BITFIELD(rid) rid : 16;
2842   unsigned int disable   : 16;
2845 /* Disable mask.  Keywords are disabled if (reswords[i].disable & mask) is
2846    _true_.  */
2847 #define D_TRAD  0x01    /* not in traditional C */
2848 #define D_C89   0x02    /* not in C89 */
2849 #define D_EXT   0x04    /* GCC extension */
2850 #define D_EXT89 0x08    /* GCC extension incorporated in C99 */
2851 #define D_OBJC  0x10    /* Objective C only */
2852 #define D_YES   0x20    /* always starts disabled */
2854 static const struct resword reswords[] =
2856   { "_Bool",            RID_BOOL,       0 },
2857   { "_Complex",         RID_COMPLEX,    0 },
2858   { "__alignof",        RID_ALIGNOF,    0 },
2859   { "__alignof__",      RID_ALIGNOF,    0 },
2860   { "__asm",            RID_ASM,        0 },
2861   { "__asm__",          RID_ASM,        0 },
2862   { "__attribute",      RID_ATTRIBUTE,  0 },
2863   { "__attribute__",    RID_ATTRIBUTE,  0 },
2864   { "__bounded",        RID_BOUNDED,    0 },
2865   { "__bounded__",      RID_BOUNDED,    0 },
2866   { "__builtin_va_arg", RID_VA_ARG,     0 },
2867   { "__complex",        RID_COMPLEX,    0 },
2868   { "__complex__",      RID_COMPLEX,    0 },
2869   { "__const",          RID_CONST,      0 },
2870   { "__const__",        RID_CONST,      0 },
2871   { "__extension__",    RID_EXTENSION,  0 },
2872   { "__imag",           RID_IMAGPART,   0 },
2873   { "__imag__",         RID_IMAGPART,   0 },
2874   { "__inline",         RID_INLINE,     0 },
2875   { "__inline__",       RID_INLINE,     0 },
2876   { "__label__",        RID_LABEL,      0 },
2877   { "__ptrbase",        RID_PTRBASE,    0 },
2878   { "__ptrbase__",      RID_PTRBASE,    0 },
2879   { "__ptrextent",      RID_PTREXTENT,  0 },
2880   { "__ptrextent__",    RID_PTREXTENT,  0 },
2881   { "__ptrvalue",       RID_PTRVALUE,   0 },
2882   { "__ptrvalue__",     RID_PTRVALUE,   0 },
2883   { "__real",           RID_REALPART,   0 },
2884   { "__real__",         RID_REALPART,   0 },
2885   { "__restrict",       RID_RESTRICT,   0 },
2886   { "__restrict__",     RID_RESTRICT,   0 },
2887   { "__signed",         RID_SIGNED,     0 },
2888   { "__signed__",       RID_SIGNED,     0 },
2889   { "__typeof",         RID_TYPEOF,     0 },
2890   { "__typeof__",       RID_TYPEOF,     0 },
2891   { "__unbounded",      RID_UNBOUNDED,  0 },
2892   { "__unbounded__",    RID_UNBOUNDED,  0 },
2893   { "__volatile",       RID_VOLATILE,   0 },
2894   { "__volatile__",     RID_VOLATILE,   0 },
2895   { "asm",              RID_ASM,        D_EXT },
2896   { "auto",             RID_AUTO,       0 },
2897   { "break",            RID_BREAK,      0 },
2898   { "case",             RID_CASE,       0 },
2899   { "char",             RID_CHAR,       0 },
2900   { "const",            RID_CONST,      D_TRAD },
2901   { "continue",         RID_CONTINUE,   0 },
2902   { "default",          RID_DEFAULT,    0 },
2903   { "do",               RID_DO,         0 },
2904   { "double",           RID_DOUBLE,     0 },
2905   { "else",             RID_ELSE,       0 },
2906   { "enum",             RID_ENUM,       0 },
2907   { "extern",           RID_EXTERN,     0 },
2908   { "float",            RID_FLOAT,      0 },
2909   { "for",              RID_FOR,        0 },
2910   { "goto",             RID_GOTO,       0 },
2911   { "if",               RID_IF,         0 },
2912   { "inline",           RID_INLINE,     D_TRAD|D_EXT89 },
2913   { "int",              RID_INT,        0 },
2914   { "long",             RID_LONG,       0 },
2915   { "register",         RID_REGISTER,   0 },
2916   { "restrict",         RID_RESTRICT,   D_TRAD|D_C89 },
2917   { "return",           RID_RETURN,     0 },
2918   { "short",            RID_SHORT,      0 },
2919   { "signed",           RID_SIGNED,     D_TRAD },
2920   { "sizeof",           RID_SIZEOF,     0 },
2921   { "static",           RID_STATIC,     0 },
2922   { "struct",           RID_STRUCT,     0 },
2923   { "switch",           RID_SWITCH,     0 },
2924   { "typedef",          RID_TYPEDEF,    0 },
2925   { "typeof",           RID_TYPEOF,     D_TRAD|D_EXT },
2926   { "union",            RID_UNION,      0 },
2927   { "unsigned",         RID_UNSIGNED,   0 },
2928   { "void",             RID_VOID,       0 },
2929   { "volatile",         RID_VOLATILE,   D_TRAD },
2930   { "while",            RID_WHILE,      0 },
2931 ifobjc
2932   { "@class",           RID_AT_CLASS,           D_OBJC },
2933   { "@compatibility_alias", RID_AT_ALIAS,       D_OBJC },
2934   { "@defs",            RID_AT_DEFS,            D_OBJC },
2935   { "@encode",          RID_AT_ENCODE,          D_OBJC },
2936   { "@end",             RID_AT_END,             D_OBJC },
2937   { "@implementation",  RID_AT_IMPLEMENTATION,  D_OBJC },
2938   { "@interface",       RID_AT_INTERFACE,       D_OBJC },
2939   { "@private",         RID_AT_PRIVATE,         D_OBJC },
2940   { "@protected",       RID_AT_PROTECTED,       D_OBJC },
2941   { "@protocol",        RID_AT_PROTOCOL,        D_OBJC },
2942   { "@public",          RID_AT_PUBLIC,          D_OBJC },
2943   { "@selector",        RID_AT_SELECTOR,        D_OBJC },
2944   { "id",               RID_ID,                 D_OBJC },
2945   { "bycopy",           RID_BYCOPY,             D_OBJC|D_YES },
2946   { "byref",            RID_BYREF,              D_OBJC|D_YES },
2947   { "in",               RID_IN,                 D_OBJC|D_YES },
2948   { "inout",            RID_INOUT,              D_OBJC|D_YES },
2949   { "oneway",           RID_ONEWAY,             D_OBJC|D_YES },
2950   { "out",              RID_OUT,                D_OBJC|D_YES },
2951 end ifobjc
2953 #define N_reswords (sizeof reswords / sizeof (struct resword))
2955 /* Table mapping from RID_* constants to yacc token numbers.
2956    Unfortunately we have to have entries for all the keywords in all
2957    three languages.  */
2958 static const short rid_to_yy[RID_MAX] =
2960   /* RID_STATIC */      SCSPEC,
2961   /* RID_UNSIGNED */    TYPESPEC,
2962   /* RID_LONG */        TYPESPEC,
2963   /* RID_CONST */       TYPE_QUAL,
2964   /* RID_EXTERN */      SCSPEC,
2965   /* RID_REGISTER */    SCSPEC,
2966   /* RID_TYPEDEF */     SCSPEC,
2967   /* RID_SHORT */       TYPESPEC,
2968   /* RID_INLINE */      SCSPEC,
2969   /* RID_VOLATILE */    TYPE_QUAL,
2970   /* RID_SIGNED */      TYPESPEC,
2971   /* RID_AUTO */        SCSPEC,
2972   /* RID_RESTRICT */    TYPE_QUAL,
2974   /* C extensions */
2975   /* RID_BOUNDED */     TYPE_QUAL,
2976   /* RID_UNBOUNDED */   TYPE_QUAL,
2977   /* RID_COMPLEX */     TYPESPEC,
2979   /* C++ */
2980   /* RID_FRIEND */      0,
2981   /* RID_VIRTUAL */     0,
2982   /* RID_EXPLICIT */    0,
2983   /* RID_EXPORT */      0,
2984   /* RID_MUTABLE */     0,
2986   /* ObjC */
2987   /* RID_IN */          TYPE_QUAL,
2988   /* RID_OUT */         TYPE_QUAL,
2989   /* RID_INOUT */       TYPE_QUAL,
2990   /* RID_BYCOPY */      TYPE_QUAL,
2991   /* RID_BYREF */       TYPE_QUAL,
2992   /* RID_ONEWAY */      TYPE_QUAL,
2993   
2994   /* C */
2995   /* RID_INT */         TYPESPEC,
2996   /* RID_CHAR */        TYPESPEC,
2997   /* RID_FLOAT */       TYPESPEC,
2998   /* RID_DOUBLE */      TYPESPEC,
2999   /* RID_VOID */        TYPESPEC,
3000   /* RID_ENUM */        ENUM,
3001   /* RID_STRUCT */      STRUCT,
3002   /* RID_UNION */       UNION,
3003   /* RID_IF */          IF,
3004   /* RID_ELSE */        ELSE,
3005   /* RID_WHILE */       WHILE,
3006   /* RID_DO */          DO,
3007   /* RID_FOR */         FOR,
3008   /* RID_SWITCH */      SWITCH,
3009   /* RID_CASE */        CASE,
3010   /* RID_DEFAULT */     DEFAULT,
3011   /* RID_BREAK */       BREAK,
3012   /* RID_CONTINUE */    CONTINUE,
3013   /* RID_RETURN */      RETURN,
3014   /* RID_GOTO */        GOTO,
3015   /* RID_SIZEOF */      SIZEOF,
3017   /* C extensions */
3018   /* RID_ASM */         ASM_KEYWORD,
3019   /* RID_TYPEOF */      TYPEOF,
3020   /* RID_ALIGNOF */     ALIGNOF,
3021   /* RID_ATTRIBUTE */   ATTRIBUTE,
3022   /* RID_VA_ARG */      VA_ARG,
3023   /* RID_EXTENSION */   EXTENSION,
3024   /* RID_IMAGPART */    IMAGPART,
3025   /* RID_REALPART */    REALPART,
3026   /* RID_LABEL */       LABEL,
3027   /* RID_PTRBASE */     PTR_BASE,
3028   /* RID_PTREXTENT */   PTR_EXTENT,
3029   /* RID_PTRVALUE */    PTR_VALUE,
3031   /* C++ */
3032   /* RID_BOOL */        TYPESPEC,
3033   /* RID_WCHAR */       0,
3034   /* RID_CLASS */       0,
3035   /* RID_PUBLIC */      0,
3036   /* RID_PRIVATE */     0,
3037   /* RID_PROTECTED */   0,
3038   /* RID_TEMPLATE */    0,
3039   /* RID_NULL */        0,
3040   /* RID_CATCH */       0,
3041   /* RID_DELETE */      0,
3042   /* RID_FALSE */       0,
3043   /* RID_NAMESPACE */   0,
3044   /* RID_NEW */         0,
3045   /* RID_OPERATOR */    0,
3046   /* RID_THIS */        0,
3047   /* RID_THROW */       0,
3048   /* RID_TRUE */        0,
3049   /* RID_TRY */         0,
3050   /* RID_TYPENAME */    0,
3051   /* RID_TYPEID */      0,
3052   /* RID_USING */       0,
3054   /* casts */
3055   /* RID_CONSTCAST */   0,
3056   /* RID_DYNCAST */     0,
3057   /* RID_REINTCAST */   0,
3058   /* RID_STATCAST */    0,
3060   /* alternate spellings */
3061   /* RID_AND */         0,
3062   /* RID_AND_EQ */      0,
3063   /* RID_NOT */         0,
3064   /* RID_NOT_EQ */      0,
3065   /* RID_OR */          0,
3066   /* RID_OR_EQ */       0,
3067   /* RID_XOR */         0,
3068   /* RID_XOR_EQ */      0,
3069   /* RID_BITAND */      0,
3070   /* RID_BITOR */       0,
3071   /* RID_COMPL */       0,
3073   /* Objective C */
3074   /* RID_ID */                  OBJECTNAME,
3075   /* RID_AT_ENCODE */           ENCODE,
3076   /* RID_AT_END */              END,
3077   /* RID_AT_CLASS */            CLASS,
3078   /* RID_AT_ALIAS */            ALIAS,
3079   /* RID_AT_DEFS */             DEFS,
3080   /* RID_AT_PRIVATE */          PRIVATE,
3081   /* RID_AT_PROTECTED */        PROTECTED,
3082   /* RID_AT_PUBLIC */           PUBLIC,
3083   /* RID_AT_PROTOCOL */         PROTOCOL,
3084   /* RID_AT_SELECTOR */         SELECTOR,
3085   /* RID_AT_INTERFACE */        INTERFACE,
3086   /* RID_AT_IMPLEMENTATION */   IMPLEMENTATION
3089 static void
3090 init_reswords ()
3092   unsigned int i;
3093   tree id;
3094   int mask = ((doing_objc_thang ? 0 : D_OBJC)
3095               | (flag_isoc99 ? 0 : D_C89)
3096               | (flag_traditional ? D_TRAD : 0)
3097               | (flag_no_asm ? (flag_isoc99 ? D_EXT : D_EXT|D_EXT89) : 0));
3099   /* It is not necessary to register ridpointers as a GC root, because
3100      all the trees it points to are permanently interned in the
3101      get_identifier hash anyway.  */
3102   ridpointers = (tree *) xcalloc ((int) RID_MAX, sizeof (tree));
3103   for (i = 0; i < N_reswords; i++)
3104     {
3105       /* If a keyword is disabled, do not enter it into the table
3106          and so create a canonical spelling that isn't a keyword.  */
3107       if (reswords[i].disable & mask)
3108         continue;
3110       id = get_identifier (reswords[i].word);
3111       C_RID_CODE (id) = reswords[i].rid;
3112       ridpointers [(int) reswords[i].rid] = id;
3114       /* Objective C does tricky things with enabling and disabling 
3115          keywords.  So these we must not elide in the test above, but
3116          wait and not mark them reserved now.  */
3117       if (! (reswords[i].disable & D_YES))
3118         C_IS_RESERVED_WORD (id) = 1;
3119     }
3122 const char *
3123 init_parse (filename)
3124      const char *filename;
3126   add_c_tree_codes ();
3128   /* Make identifier nodes long enough for the language-specific slots.  */
3129   set_identifier_size (sizeof (struct lang_identifier));
3131   init_reswords ();
3132   init_pragma ();
3134   return init_c_lex (filename);
3137 void
3138 finish_parse ()
3140 #if USE_CPPLIB
3141   cpp_finish (&parse_in);
3142   errorcount += parse_in.errors;
3143 #else
3144   fclose (finput);
3145 #endif
3148 #if USE_CPPLIB
3149 #define NAME(type) cpp_type2name (type)
3150 #else
3151 /* Bleah */
3152 #include "symcat.h"
3153 #define OP(e, s) s,
3154 #define TK(e, s) STRINGX(e),
3156 static const char *type2name[N_TTYPES] = { TTYPE_TABLE };
3157 #define NAME(type) type2name[type]
3158 #endif
3160 static void
3161 yyerror (msgid)
3162      const char *msgid;
3164   const char *string = _(msgid);
3166   if (last_token == CPP_EOF)
3167     error ("%s at end of input", string);
3168   else if (last_token == CPP_CHAR || last_token == CPP_WCHAR)
3169     {
3170       unsigned int val = TREE_INT_CST_LOW (yylval.ttype);
3171       const char *ell = (last_token == CPP_CHAR) ? "" : "L";
3172       if (val <= UCHAR_MAX && ISGRAPH (val))
3173         error ("%s before %s'%c'", string, ell, val);
3174       else
3175         error ("%s before %s'\\x%x'", string, ell, val);
3176     }
3177   else if (last_token == CPP_STRING
3178            || last_token == CPP_WSTRING
3179            || last_token == CPP_OSTRING)
3180     error ("%s before string constant", string);
3181   else if (last_token == CPP_NUMBER
3182            || last_token == CPP_INT
3183            || last_token == CPP_FLOAT)
3184     error ("%s before numeric constant", string);
3185   else if (last_token == CPP_NAME)
3186     error ("%s before \"%s\"", string, IDENTIFIER_POINTER (yylval.ttype));
3187   else
3188     error ("%s before '%s' token", string, NAME(last_token));
3191 static inline int
3192 _yylex ()
3194  retry:
3195   last_token = c_lex (&yylval.ttype);
3197   switch (last_token)
3198     {
3199     case CPP_EQ:                                        return '=';
3200     case CPP_NOT:                                       return '!';
3201     case CPP_GREATER:   yylval.code = GT_EXPR;          return ARITHCOMPARE;
3202     case CPP_LESS:      yylval.code = LT_EXPR;          return ARITHCOMPARE;
3203     case CPP_PLUS:      yylval.code = PLUS_EXPR;        return '+';
3204     case CPP_MINUS:     yylval.code = MINUS_EXPR;       return '-';
3205     case CPP_MULT:      yylval.code = MULT_EXPR;        return '*';
3206     case CPP_DIV:       yylval.code = TRUNC_DIV_EXPR;   return '/';
3207     case CPP_MOD:       yylval.code = TRUNC_MOD_EXPR;   return '%';
3208     case CPP_AND:       yylval.code = BIT_AND_EXPR;     return '&';
3209     case CPP_OR:        yylval.code = BIT_IOR_EXPR;     return '|';
3210     case CPP_XOR:       yylval.code = BIT_XOR_EXPR;     return '^';
3211     case CPP_RSHIFT:    yylval.code = RSHIFT_EXPR;      return RSHIFT;
3212     case CPP_LSHIFT:    yylval.code = LSHIFT_EXPR;      return LSHIFT;
3214     case CPP_COMPL:                                     return '~';
3215     case CPP_AND_AND:                                   return ANDAND;
3216     case CPP_OR_OR:                                     return OROR;
3217     case CPP_QUERY:                                     return '?';
3218     case CPP_COLON:                                     return ':';
3219     case CPP_COMMA:                                     return ',';
3220     case CPP_OPEN_PAREN:                                return '(';
3221     case CPP_CLOSE_PAREN:                               return ')';
3222     case CPP_EQ_EQ:     yylval.code = EQ_EXPR;          return EQCOMPARE;
3223     case CPP_NOT_EQ:    yylval.code = NE_EXPR;          return EQCOMPARE;
3224     case CPP_GREATER_EQ:yylval.code = GE_EXPR;          return ARITHCOMPARE;
3225     case CPP_LESS_EQ:   yylval.code = LE_EXPR;          return ARITHCOMPARE;
3227     case CPP_PLUS_EQ:   yylval.code = PLUS_EXPR;        return ASSIGN;
3228     case CPP_MINUS_EQ:  yylval.code = MINUS_EXPR;       return ASSIGN;
3229     case CPP_MULT_EQ:   yylval.code = MULT_EXPR;        return ASSIGN;
3230     case CPP_DIV_EQ:    yylval.code = TRUNC_DIV_EXPR;   return ASSIGN;
3231     case CPP_MOD_EQ:    yylval.code = TRUNC_MOD_EXPR;   return ASSIGN;
3232     case CPP_AND_EQ:    yylval.code = BIT_AND_EXPR;     return ASSIGN;
3233     case CPP_OR_EQ:     yylval.code = BIT_IOR_EXPR;     return ASSIGN;
3234     case CPP_XOR_EQ:    yylval.code = BIT_XOR_EXPR;     return ASSIGN;
3235     case CPP_RSHIFT_EQ: yylval.code = RSHIFT_EXPR;      return ASSIGN;
3236     case CPP_LSHIFT_EQ: yylval.code = LSHIFT_EXPR;      return ASSIGN;
3238     case CPP_OPEN_SQUARE:                               return '[';
3239     case CPP_CLOSE_SQUARE:                              return ']';
3240     case CPP_OPEN_BRACE:                                return '{';
3241     case CPP_CLOSE_BRACE:                               return '}';
3242     case CPP_SEMICOLON:                                 return ';';
3243     case CPP_ELLIPSIS:                                  return ELLIPSIS;
3245     case CPP_PLUS_PLUS:                                 return PLUSPLUS;
3246     case CPP_MINUS_MINUS:                               return MINUSMINUS;
3247     case CPP_DEREF:                                     return POINTSAT;
3248     case CPP_DOT:                                       return '.';
3250     case CPP_EOF:
3251 #if USE_CPPLIB
3252       cpp_pop_buffer (&parse_in);
3253       if (! CPP_BUFFER (&parse_in))
3254 #endif
3255         return 0;
3256       goto retry;
3258     case CPP_NAME:
3259       if (C_IS_RESERVED_WORD (yylval.ttype))
3260         {
3261           enum rid rid_code = C_RID_CODE (yylval.ttype);
3262           /* Return the canonical spelling for this keyword.  */
3263           yylval.ttype = ridpointers[(int) rid_code];
3264           return rid_to_yy[(int) rid_code];
3265         }
3267       if (IDENTIFIER_POINTER (yylval.ttype)[0] == '@')
3268         {
3269           error ("invalid identifier `%s'", IDENTIFIER_POINTER (yylval.ttype));
3270           return IDENTIFIER;
3271         }
3273       {
3274         tree decl;
3276         decl = lookup_name (yylval.ttype);
3278         if (decl)
3279           {
3280             if (TREE_CODE (decl) == TYPE_DECL)
3281               return TYPENAME;
3282             /* A user-invisible read-only initialized variable
3283                should be replaced by its value.
3284                We handle only strings since that's the only case used in C.  */
3285             else if (TREE_CODE (decl) == VAR_DECL
3286                      && DECL_IGNORED_P (decl)
3287                      && TREE_READONLY (decl)
3288                      && DECL_INITIAL (decl) != 0
3289                      && TREE_CODE (DECL_INITIAL (decl)) == STRING_CST)
3290               {
3291                 tree stringval = DECL_INITIAL (decl);
3293                 /* Copy the string value so that we won't clobber anything
3294                    if we put something in the TREE_CHAIN of this one.  */
3295                 yylval.ttype = build_string (TREE_STRING_LENGTH (stringval),
3296                                              TREE_STRING_POINTER (stringval));
3297                 return STRING;
3298               }
3299           }
3300         else if (doing_objc_thang)
3301           {
3302             tree objc_interface_decl = is_class_name (yylval.ttype);
3304             if (objc_interface_decl)
3305               {
3306                 yylval.ttype = objc_interface_decl;
3307                 return CLASSNAME;
3308               }
3309           }
3311         return IDENTIFIER;
3312       }
3314     case CPP_INT:
3315     case CPP_FLOAT:
3316     case CPP_NUMBER:
3317     case CPP_CHAR:
3318     case CPP_WCHAR:
3319       return CONSTANT;
3321     case CPP_STRING:
3322     case CPP_WSTRING:
3323       return STRING;
3324       
3325     case CPP_OSTRING:
3326       return OBJC_STRING;
3328       /* These tokens are C++ specific (and will not be generated
3329          in C mode, but let's be cautious).  */
3330     case CPP_SCOPE:
3331     case CPP_DEREF_STAR:
3332     case CPP_DOT_STAR:
3333     case CPP_MIN_EQ:
3334     case CPP_MAX_EQ:
3335     case CPP_MIN:
3336     case CPP_MAX:
3337       /* These tokens should not survive translation phase 4.  */
3338     case CPP_HASH:
3339     case CPP_PASTE:
3340       error ("syntax error before '%s' token", NAME(last_token));
3341       goto retry;
3343     default:
3344       abort ();
3345     }
3347   /* NOTREACHED */
3350 static int
3351 yylex()
3353   int r;
3354   timevar_push (TV_LEX);
3355   r = _yylex();
3356   timevar_pop (TV_LEX);
3357   return r;
3360 /* Sets the value of the 'yydebug' variable to VALUE.
3361    This is a function so we don't have to have YYDEBUG defined
3362    in order to build the compiler.  */
3364 void
3365 set_yydebug (value)
3366      int value;
3368 #if YYDEBUG != 0
3369   yydebug = value;
3370 #else
3371   warning ("YYDEBUG not defined.");
3372 #endif
3375 /* Function used when yydebug is set, to print a token in more detail.  */
3377 static void
3378 yyprint (file, yychar, yyl)
3379      FILE *file;
3380      int yychar;
3381      YYSTYPE yyl;
3383   tree t = yyl.ttype;
3385   fprintf (file, " [%s]", NAME(last_token));
3386   
3387   switch (yychar)
3388     {
3389     case IDENTIFIER:
3390     case TYPENAME:
3391     case OBJECTNAME:
3392     case TYPESPEC:
3393     case TYPE_QUAL:
3394     case SCSPEC:
3395       if (IDENTIFIER_POINTER (t))
3396         fprintf (file, " `%s'", IDENTIFIER_POINTER (t));
3397       break;
3399     case CONSTANT:
3400       fprintf (file, " %s", GET_MODE_NAME (TYPE_MODE (TREE_TYPE (t))));
3401       if (TREE_CODE (t) == INTEGER_CST)
3402         fprintf (file,
3403 #if HOST_BITS_PER_WIDE_INT == 64
3404 #if HOST_BITS_PER_WIDE_INT == HOST_BITS_PER_INT
3405                  " 0x%x%016x",
3406 #else
3407 #if HOST_BITS_PER_WIDE_INT == HOST_BITS_PER_LONG
3408                  " 0x%lx%016lx",
3409 #else
3410                  " 0x%llx%016llx",
3411 #endif
3412 #endif
3413 #else
3414 #if HOST_BITS_PER_WIDE_INT != HOST_BITS_PER_INT
3415                  " 0x%lx%08lx",
3416 #else
3417                  " 0x%x%08x",
3418 #endif
3419 #endif
3420                  TREE_INT_CST_HIGH (t), TREE_INT_CST_LOW (t));
3421       break;
3422     }
3425 /* This is not the ideal place to put these, but we have to get them out
3426    of c-lex.c because cp/lex.c has its own versions.  */
3428 /* Return something to represent absolute declarators containing a *.
3429    TARGET is the absolute declarator that the * contains.
3430    TYPE_QUALS is a list of modifiers such as const or volatile
3431    to apply to the pointer type, represented as identifiers.
3433    We return an INDIRECT_REF whose "contents" are TARGET
3434    and whose type is the modifier list.  */
3436 tree
3437 make_pointer_declarator (type_quals, target)
3438      tree type_quals, target;
3440   return build1 (INDIRECT_REF, type_quals, target);