Introduce ORIGINAL_REGNO macro
[official-gcc.git] / gcc / c-parse.in
blobf944ac3bd45e69c3fb3e3d96bd3b5dfd97933e53
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 stmt label
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           save_filename save_lineno compstmt_or_error
369                 { DECL_SOURCE_FILE (current_function_decl) = $7;
370                   DECL_SOURCE_LINE (current_function_decl) = $8;
371                   finish_function (0); 
372                   current_declspecs = TREE_VALUE (declspec_stack);
373                   prefix_attributes = TREE_PURPOSE (declspec_stack);
374                   declspec_stack = TREE_CHAIN (declspec_stack); }
375         | typed_declspecs setspecs declarator error
376                 { current_declspecs = TREE_VALUE (declspec_stack);
377                   prefix_attributes = TREE_PURPOSE (declspec_stack);
378                   declspec_stack = TREE_CHAIN (declspec_stack); }
379         | declmods setspecs notype_declarator
380                 { if (! start_function (current_declspecs, $3,
381                                         prefix_attributes, NULL_TREE))
382                     YYERROR1;
383                 }
384           old_style_parm_decls
385                 { store_parm_decls (); }
386           save_filename save_lineno compstmt_or_error
387                 { DECL_SOURCE_FILE (current_function_decl) = $7;
388                   DECL_SOURCE_LINE (current_function_decl) = $8;
389                   finish_function (0); 
390                   current_declspecs = TREE_VALUE (declspec_stack);
391                   prefix_attributes = TREE_PURPOSE (declspec_stack);
392                   declspec_stack = TREE_CHAIN (declspec_stack); }
393         | declmods setspecs notype_declarator error
394                 { current_declspecs = TREE_VALUE (declspec_stack);
395                   prefix_attributes = TREE_PURPOSE (declspec_stack);
396                   declspec_stack = TREE_CHAIN (declspec_stack); }
397         | setspecs notype_declarator
398                 { if (! start_function (NULL_TREE, $2,
399                                         prefix_attributes, NULL_TREE))
400                     YYERROR1;
401                 }
402           old_style_parm_decls
403                 { store_parm_decls (); }
404           save_filename save_lineno compstmt_or_error
405                 { DECL_SOURCE_FILE (current_function_decl) = $6;
406                   DECL_SOURCE_LINE (current_function_decl) = $7;
407                   finish_function (0); 
408                   current_declspecs = TREE_VALUE (declspec_stack);
409                   prefix_attributes = TREE_PURPOSE (declspec_stack);
410                   declspec_stack = TREE_CHAIN (declspec_stack); }
411         | setspecs notype_declarator error
412                 { current_declspecs = TREE_VALUE (declspec_stack);
413                   prefix_attributes = TREE_PURPOSE (declspec_stack);
414                   declspec_stack = TREE_CHAIN (declspec_stack); }
415         ;
417 identifier:
418         IDENTIFIER
419         | TYPENAME
420 ifobjc
421         | OBJECTNAME
422         | CLASSNAME
423 end ifobjc
424         ;
426 unop:     '&'
427                 { $$ = ADDR_EXPR; }
428         | '-'
429                 { $$ = NEGATE_EXPR; }
430         | '+'
431                 { $$ = CONVERT_EXPR;
433   if (warn_traditional && !in_system_header)
434     warning ("traditional C rejects the unary plus operator");
435 end ifc
436                 }
437         | PLUSPLUS
438                 { $$ = PREINCREMENT_EXPR; }
439         | MINUSMINUS
440                 { $$ = PREDECREMENT_EXPR; }
441         | '~'
442                 { $$ = BIT_NOT_EXPR; }
443         | '!'
444                 { $$ = TRUTH_NOT_EXPR; }
445         ;
447 expr:   nonnull_exprlist
448                 { $$ = build_compound_expr ($1); }
449         ;
451 exprlist:
452           /* empty */
453                 { $$ = NULL_TREE; }
454         | nonnull_exprlist
455         ;
457 nonnull_exprlist:
458         expr_no_commas
459                 { $$ = build_tree_list (NULL_TREE, $1); }
460         | nonnull_exprlist ',' expr_no_commas
461                 { chainon ($1, build_tree_list (NULL_TREE, $3)); }
462         ;
464 unary_expr:
465         primary
466         | '*' cast_expr   %prec UNARY
467                 { $$ = build_indirect_ref ($2, "unary *"); }
468         /* __extension__ turns off -pedantic for following primary.  */
469         | extension cast_expr     %prec UNARY
470                 { $$ = $2;
471                   RESTORE_WARN_FLAGS ($1); }
472         | unop cast_expr  %prec UNARY
473                 { $$ = build_unary_op ($1, $2, 0);
474                   overflow_warning ($$); }
475         /* Refer to the address of a label as a pointer.  */
476         | ANDAND identifier
477                 { tree label = lookup_label ($2);
478                   if (pedantic)
479                     pedwarn ("ISO C forbids `&&'");
480                   if (label == 0)
481                     $$ = null_pointer_node;
482                   else
483                     {
484                       TREE_USED (label) = 1;
485                       $$ = build1 (ADDR_EXPR, ptr_type_node, label);
486                       TREE_CONSTANT ($$) = 1;
487                     }
488                 }
489 /* This seems to be impossible on some machines, so let's turn it off.
490    You can use __builtin_next_arg to find the anonymous stack args.
491         | '&' ELLIPSIS
492                 { tree types = TYPE_ARG_TYPES (TREE_TYPE (current_function_decl));
493                   $$ = error_mark_node;
494                   if (TREE_VALUE (tree_last (types)) == void_type_node)
495                     error ("`&...' used in function with fixed number of arguments");
496                   else
497                     {
498                       if (pedantic)
499                         pedwarn ("ISO C forbids `&...'");
500                       $$ = tree_last (DECL_ARGUMENTS (current_function_decl));
501                       $$ = build_unary_op (ADDR_EXPR, $$, 0);
502                     } }
504         | sizeof unary_expr  %prec UNARY
505                 { skip_evaluation--;
506                   if (TREE_CODE ($2) == COMPONENT_REF
507                       && DECL_C_BIT_FIELD (TREE_OPERAND ($2, 1)))
508                     error ("`sizeof' applied to a bit-field");
509                   $$ = c_sizeof (TREE_TYPE ($2)); }
510         | sizeof '(' typename ')'  %prec HYPERUNARY
511                 { skip_evaluation--;
512                   $$ = c_sizeof (groktypename ($3)); }
513         | alignof unary_expr  %prec UNARY
514                 { skip_evaluation--;
515                   $$ = c_alignof_expr ($2); }
516         | alignof '(' typename ')'  %prec HYPERUNARY
517                 { skip_evaluation--;
518                   $$ = c_alignof (groktypename ($3)); }
519         | REALPART cast_expr %prec UNARY
520                 { $$ = build_unary_op (REALPART_EXPR, $2, 0); }
521         | IMAGPART cast_expr %prec UNARY
522                 { $$ = build_unary_op (IMAGPART_EXPR, $2, 0); }
523         ;
525 sizeof:
526         SIZEOF { skip_evaluation++; }
527         ;
529 alignof:
530         ALIGNOF { skip_evaluation++; }
531         ;
533 cast_expr:
534         unary_expr
535         | '(' typename ')' cast_expr  %prec UNARY
536                 { tree type;
537                   int SAVED_warn_strict_prototypes = warn_strict_prototypes;
538                   /* This avoids warnings about unprototyped casts on
539                      integers.  E.g. "#define SIG_DFL (void(*)())0".  */
540                   if (TREE_CODE ($4) == INTEGER_CST)
541                     warn_strict_prototypes = 0;
542                   type = groktypename ($2);
543                   warn_strict_prototypes = SAVED_warn_strict_prototypes;
544                   $$ = build_c_cast (type, $4); }
545         | '(' typename ')' '{' 
546                 { start_init (NULL_TREE, NULL, 0);
547                   $2 = groktypename ($2);
548                   really_start_incremental_init ($2); }
549           initlist_maybe_comma '}'  %prec UNARY
550                 { const char *name;
551                   tree result = pop_init_level (0);
552                   tree type = $2;
553                   finish_init ();
555                   if (pedantic && ! flag_isoc99)
556                     pedwarn ("ISO C89 forbids constructor expressions");
557                   if (TYPE_NAME (type) != 0)
558                     {
559                       if (TREE_CODE (TYPE_NAME (type)) == IDENTIFIER_NODE)
560                         name = IDENTIFIER_POINTER (TYPE_NAME (type));
561                       else
562                         name = IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (type)));
563                     }
564                   else
565                     name = "";
566                   $$ = result;
567                   if (TREE_CODE (type) == ARRAY_TYPE && !COMPLETE_TYPE_P (type))
568                     {
569                       int failure = complete_array_type (type, $$, 1);
570                       if (failure)
571                         abort ();
572                     }
573                 }
574         ;
576 expr_no_commas:
577           cast_expr
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 '/' expr_no_commas
585                 { $$ = parser_build_binary_op ($2, $1, $3); }
586         | expr_no_commas '%' expr_no_commas
587                 { $$ = parser_build_binary_op ($2, $1, $3); }
588         | expr_no_commas LSHIFT expr_no_commas
589                 { $$ = parser_build_binary_op ($2, $1, $3); }
590         | expr_no_commas RSHIFT expr_no_commas
591                 { $$ = parser_build_binary_op ($2, $1, $3); }
592         | expr_no_commas ARITHCOMPARE expr_no_commas
593                 { $$ = parser_build_binary_op ($2, $1, $3); }
594         | expr_no_commas EQCOMPARE 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 '|' expr_no_commas
599                 { $$ = parser_build_binary_op ($2, $1, $3); }
600         | expr_no_commas '^' expr_no_commas
601                 { $$ = parser_build_binary_op ($2, $1, $3); }
602         | expr_no_commas ANDAND
603                 { $1 = truthvalue_conversion (default_conversion ($1));
604                   skip_evaluation += $1 == boolean_false_node; }
605           expr_no_commas
606                 { skip_evaluation -= $1 == boolean_false_node;
607                   $$ = parser_build_binary_op (TRUTH_ANDIF_EXPR, $1, $4); }
608         | expr_no_commas OROR
609                 { $1 = truthvalue_conversion (default_conversion ($1));
610                   skip_evaluation += $1 == boolean_true_node; }
611           expr_no_commas
612                 { skip_evaluation -= $1 == boolean_true_node;
613                   $$ = parser_build_binary_op (TRUTH_ORIF_EXPR, $1, $4); }
614         | expr_no_commas '?'
615                 { $1 = truthvalue_conversion (default_conversion ($1));
616                   skip_evaluation += $1 == boolean_false_node; }
617           expr ':'
618                 { skip_evaluation += (($1 == boolean_true_node)
619                                       - ($1 == boolean_false_node)); }
620           expr_no_commas
621                 { skip_evaluation -= $1 == boolean_true_node;
622                   $$ = build_conditional_expr ($1, $4, $7); }
623         | expr_no_commas '?'
624                 { if (pedantic)
625                     pedwarn ("ISO C forbids omitting the middle term of a ?: expression");
626                   /* Make sure first operand is calculated only once.  */
627                   $<ttype>2 = save_expr ($1);
628                   $1 = truthvalue_conversion (default_conversion ($<ttype>2));
629                   skip_evaluation += $1 == boolean_true_node; }
630           ':' expr_no_commas
631                 { skip_evaluation -= $1 == boolean_true_node;
632                   $$ = build_conditional_expr ($1, $<ttype>2, $5); }
633         | expr_no_commas '=' expr_no_commas
634                 { char class;
635                   $$ = build_modify_expr ($1, NOP_EXPR, $3);
636                   class = TREE_CODE_CLASS (TREE_CODE ($$));
637                   if (class == 'e' || class == '1'
638                       || class == '2' || class == '<')
639                     C_SET_EXP_ORIGINAL_CODE ($$, MODIFY_EXPR);
640                 }
641         | expr_no_commas ASSIGN expr_no_commas
642                 { char class;
643                   $$ = build_modify_expr ($1, $2, $3);
644                   /* This inhibits warnings in truthvalue_conversion.  */
645                   class = TREE_CODE_CLASS (TREE_CODE ($$));
646                   if (class == 'e' || class == '1'
647                       || class == '2' || class == '<')
648                     C_SET_EXP_ORIGINAL_CODE ($$, ERROR_MARK);
649                 }
650         ;
652 primary:
653         IDENTIFIER
654                 {
655                   if (yychar == YYEMPTY)
656                     yychar = YYLEX;
657                   $$ = build_external_ref ($1, yychar == '(');
658                 }
659         | CONSTANT
660         | string
661                 { $$ = combine_strings ($1); }
662         | '(' expr ')'
663                 { char class = TREE_CODE_CLASS (TREE_CODE ($2));
664                   if (class == 'e' || class == '1'
665                       || class == '2' || class == '<')
666                     C_SET_EXP_ORIGINAL_CODE ($2, ERROR_MARK);
667                   $$ = $2; }
668         | '(' error ')'
669                 { $$ = error_mark_node; }
670         | compstmt_primary_start compstmt_nostart ')'
671                  { tree saved_last_tree;
673                    if (pedantic)
674                      pedwarn ("ISO C forbids braced-groups within expressions");
675                   pop_label_level ();
677                   saved_last_tree = COMPOUND_BODY ($1);
678                   RECHAIN_STMTS ($1, COMPOUND_BODY ($1));
679                   last_tree = saved_last_tree;
680                   TREE_CHAIN (last_tree) = NULL_TREE;
681                   if (!last_expr_type)
682                     last_expr_type = void_type_node;
683                   $$ = build1 (STMT_EXPR, last_expr_type, $1);
684                   TREE_SIDE_EFFECTS ($$) = 1;
685                 }
686         | compstmt_primary_start error ')'
687                 {
688                   pop_label_level ();
689                   last_tree = COMPOUND_BODY ($1);
690                   TREE_CHAIN (last_tree) = NULL_TREE;
691                   $$ = error_mark_node;
692                 }
693         | primary '(' exprlist ')'   %prec '.'
694                 { $$ = build_function_call ($1, $3); }
695         | VA_ARG '(' expr_no_commas ',' typename ')'
696                 { $$ = build_va_arg ($3, groktypename ($5)); }
697         | primary '[' expr ']'   %prec '.'
698                 { $$ = build_array_ref ($1, $3); }
699         | primary '.' identifier
700                 {
701 ifobjc
702                   if (doing_objc_thang)
703                     {
704                       if (is_public ($1, $3))
705                         $$ = build_component_ref ($1, $3);
706                       else
707                         $$ = error_mark_node;
708                     }
709                   else
710 end ifobjc
711                     $$ = build_component_ref ($1, $3);
712                 }
713         | primary POINTSAT identifier
714                 {
715                   tree expr = build_indirect_ref ($1, "->");
717 ifobjc
718                   if (doing_objc_thang)
719                     {
720                       if (is_public (expr, $3))
721                         $$ = build_component_ref (expr, $3);
722                       else
723                         $$ = error_mark_node;
724                     }
725                   else
726 end ifobjc
727                     $$ = build_component_ref (expr, $3);
728                 }
729         | primary PLUSPLUS
730                 { $$ = build_unary_op (POSTINCREMENT_EXPR, $1, 0); }
731         | primary MINUSMINUS
732                 { $$ = build_unary_op (POSTDECREMENT_EXPR, $1, 0); }
733 ifobjc
734         | objcmessageexpr
735                 { $$ = build_message_expr ($1); }
736         | objcselectorexpr
737                 { $$ = build_selector_expr ($1); }
738         | objcprotocolexpr
739                 { $$ = build_protocol_expr ($1); }
740         | objcencodeexpr
741                 { $$ = build_encode_expr ($1); }
742         | objc_string
743                 { $$ = build_objc_string_object ($1); }
744 end ifobjc
745         ;
747 /* Produces a STRING_CST with perhaps more STRING_CSTs chained onto it.  */
748 string:
749           STRING
750         | string STRING
751                 {
753                   static int last_lineno = 0;
754                   static const char *last_input_filename = 0;
755 end ifc
756                   $$ = chainon ($1, $2);
758                   if (warn_traditional && !in_system_header
759                       && (lineno != last_lineno || !last_input_filename ||
760                           strcmp (last_input_filename, input_filename)))
761                     {
762                       warning ("traditional C rejects string concatenation");
763                       last_lineno = lineno;
764                       last_input_filename = input_filename;
765                     }
766 end ifc
767                 }
768         ;
770 ifobjc
771 /* Produces an STRING_CST with perhaps more STRING_CSTs chained
772    onto it, which is to be read as an ObjC string object.  */
773 objc_string:
774           OBJC_STRING
775         | objc_string OBJC_STRING
776                 { $$ = chainon ($1, $2); }
777         ;
778 end ifobjc
780 old_style_parm_decls:
781         /* empty */
782         | datadecls
783         | datadecls ELLIPSIS
784                 /* ... is used here to indicate a varargs function.  */
785                 { c_mark_varargs ();
786                   if (pedantic)
787                     pedwarn ("ISO C does not permit use of `varargs.h'"); }
788         ;
790 /* The following are analogous to lineno_decl, decls and decl
791    except that they do not allow nested functions.
792    They are used for old-style parm decls.  */
793 lineno_datadecl:
794           save_filename save_lineno datadecl
795                 { }
796         ;
798 datadecls:
799         lineno_datadecl
800         | errstmt
801         | datadecls lineno_datadecl
802         | lineno_datadecl errstmt
803         ;
805 /* We don't allow prefix attributes here because they cause reduce/reduce
806    conflicts: we can't know whether we're parsing a function decl with
807    attribute suffix, or function defn with attribute prefix on first old
808    style parm.  */
809 datadecl:
810         typed_declspecs_no_prefix_attr setspecs initdecls ';'
811                 { current_declspecs = TREE_VALUE (declspec_stack);
812                   prefix_attributes = TREE_PURPOSE (declspec_stack);
813                   declspec_stack = TREE_CHAIN (declspec_stack); }
814         | declmods_no_prefix_attr setspecs notype_initdecls ';'
815                 { current_declspecs = TREE_VALUE (declspec_stack);      
816                   prefix_attributes = TREE_PURPOSE (declspec_stack);
817                   declspec_stack = TREE_CHAIN (declspec_stack); }
818         | typed_declspecs_no_prefix_attr ';'
819                 { shadow_tag_warned ($1, 1);
820                   pedwarn ("empty declaration"); }
821         | declmods_no_prefix_attr ';'
822                 { pedwarn ("empty declaration"); }
823         ;
825 /* This combination which saves a lineno before a decl
826    is the normal thing to use, rather than decl itself.
827    This is to avoid shift/reduce conflicts in contexts
828    where statement labels are allowed.  */
829 lineno_decl:
830           save_filename save_lineno decl
831                 { }
832         ;
834 /* records the type and storage class specs to use for processing
835    the declarators that follow.
836    Maintains a stack of outer-level values of current_declspecs,
837    for the sake of parm declarations nested in function declarators.  */
838 setspecs: /* empty */
839                 { pending_xref_error ();
840                   declspec_stack = tree_cons (prefix_attributes,
841                                               current_declspecs,
842                                               declspec_stack);
843                   split_specs_attrs ($<ttype>0,
844                                      &current_declspecs, &prefix_attributes); }
845         ;
847 /* ??? Yuck.  See after_type_declarator.  */
848 setattrs: /* empty */
849                 { prefix_attributes = chainon (prefix_attributes, $<ttype>0); }
850         ;
852 decl:
853         typed_declspecs setspecs initdecls ';'
854                 { current_declspecs = TREE_VALUE (declspec_stack);
855                   prefix_attributes = TREE_PURPOSE (declspec_stack);
856                   declspec_stack = TREE_CHAIN (declspec_stack); }
857         | declmods setspecs notype_initdecls ';'
858                 { current_declspecs = TREE_VALUE (declspec_stack);
859                   prefix_attributes = TREE_PURPOSE (declspec_stack);
860                   declspec_stack = TREE_CHAIN (declspec_stack); }
861         | typed_declspecs setspecs nested_function
862                 { current_declspecs = TREE_VALUE (declspec_stack);
863                   prefix_attributes = TREE_PURPOSE (declspec_stack);
864                   declspec_stack = TREE_CHAIN (declspec_stack); }
865         | declmods setspecs notype_nested_function
866                 { current_declspecs = TREE_VALUE (declspec_stack);
867                   prefix_attributes = TREE_PURPOSE (declspec_stack);
868                   declspec_stack = TREE_CHAIN (declspec_stack); }
869         | typed_declspecs ';'
870                 { shadow_tag ($1); }
871         | declmods ';'
872                 { pedwarn ("empty declaration"); }
873         | extension decl
874                 { RESTORE_WARN_FLAGS ($1); }
875         ;
877 /* Declspecs which contain at least one type specifier or typedef name.
878    (Just `const' or `volatile' is not enough.)
879    A typedef'd name following these is taken as a name to be declared.
880    Declspecs have a non-NULL TREE_VALUE, attributes do not.  */
882 typed_declspecs:
883           typespec reserved_declspecs
884                 { $$ = tree_cons (NULL_TREE, $1, $2); }
885         | declmods typespec reserved_declspecs
886                 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
887         ;
889 reserved_declspecs:  /* empty */
890                 { $$ = NULL_TREE; }
891         | reserved_declspecs typespecqual_reserved
892                 { $$ = tree_cons (NULL_TREE, $2, $1); }
893         | reserved_declspecs SCSPEC
894                 { if (extra_warnings)
895                     warning ("`%s' is not at beginning of declaration",
896                              IDENTIFIER_POINTER ($2));
897                   $$ = tree_cons (NULL_TREE, $2, $1); }
898         | reserved_declspecs attributes
899                 { $$ = tree_cons ($2, NULL_TREE, $1); }
900         ;
902 typed_declspecs_no_prefix_attr:
903           typespec reserved_declspecs_no_prefix_attr
904                 { $$ = tree_cons (NULL_TREE, $1, $2); }
905         | declmods_no_prefix_attr typespec reserved_declspecs_no_prefix_attr
906                 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
907         ;
909 reserved_declspecs_no_prefix_attr:
910           /* empty */
911                 { $$ = NULL_TREE; }
912         | reserved_declspecs_no_prefix_attr typespecqual_reserved
913                 { $$ = tree_cons (NULL_TREE, $2, $1); }
914         | reserved_declspecs_no_prefix_attr SCSPEC
915                 { if (extra_warnings)
916                     warning ("`%s' is not at beginning of declaration",
917                              IDENTIFIER_POINTER ($2));
918                   $$ = tree_cons (NULL_TREE, $2, $1); }
919         ;
921 /* List of just storage classes, type modifiers, and prefix attributes.
922    A declaration can start with just this, but then it cannot be used
923    to redeclare a typedef-name.
924    Declspecs have a non-NULL TREE_VALUE, attributes do not.  */
926 declmods:
927           declmods_no_prefix_attr
928                 { $$ = $1; }
929         | attributes
930                 { $$ = tree_cons ($1, NULL_TREE, NULL_TREE); }
931         | declmods declmods_no_prefix_attr
932                 { $$ = chainon ($2, $1); }
933         | declmods attributes
934                 { $$ = tree_cons ($2, NULL_TREE, $1); }
935         ;
937 declmods_no_prefix_attr:
938           TYPE_QUAL
939                 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
940                   TREE_STATIC ($$) = 1; }
941         | SCSPEC
942                 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
943         | declmods_no_prefix_attr TYPE_QUAL
944                 { $$ = tree_cons (NULL_TREE, $2, $1);
945                   TREE_STATIC ($$) = 1; }
946         | declmods_no_prefix_attr SCSPEC
947                 { if (extra_warnings && TREE_STATIC ($1))
948                     warning ("`%s' is not at beginning of declaration",
949                              IDENTIFIER_POINTER ($2));
950                   $$ = tree_cons (NULL_TREE, $2, $1);
951                   TREE_STATIC ($$) = TREE_STATIC ($1); }
952         ;
955 /* Used instead of declspecs where storage classes are not allowed
956    (that is, for typenames and structure components).
957    Don't accept a typedef-name if anything but a modifier precedes it.  */
959 typed_typespecs:
960           typespec reserved_typespecquals
961                 { $$ = tree_cons (NULL_TREE, $1, $2); }
962         | nonempty_type_quals typespec reserved_typespecquals
963                 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
964         ;
966 reserved_typespecquals:  /* empty */
967                 { $$ = NULL_TREE; }
968         | reserved_typespecquals typespecqual_reserved
969                 { $$ = tree_cons (NULL_TREE, $2, $1); }
970         ;
972 /* A typespec (but not a type qualifier).
973    Once we have seen one of these in a declaration,
974    if a typedef name appears then it is being redeclared.  */
976 typespec: TYPESPEC
977         | structsp
978         | TYPENAME
979                 { /* For a typedef name, record the meaning, not the name.
980                      In case of `foo foo, bar;'.  */
981                   $$ = lookup_name ($1); }
982 ifobjc
983         | CLASSNAME protocolrefs
984                 { $$ = get_static_reference ($1, $2); }
985         | OBJECTNAME protocolrefs
986                 { $$ = get_object_reference ($2); }
988 /* Make "<SomeProtocol>" equivalent to "id <SomeProtocol>"
989    - nisse@lysator.liu.se */
990         | non_empty_protocolrefs
991                 { $$ = get_object_reference ($1); }
992 end ifobjc
993         | TYPEOF '(' expr ')'
994                 { $$ = TREE_TYPE ($3); }
995         | TYPEOF '(' typename ')'
996                 { $$ = groktypename ($3); }
997         ;
999 /* A typespec that is a reserved word, or a type qualifier.  */
1001 typespecqual_reserved: TYPESPEC
1002         | TYPE_QUAL
1003         | structsp
1004         ;
1006 initdecls:
1007         initdcl
1008         | initdecls ',' initdcl
1009         ;
1011 notype_initdecls:
1012         notype_initdcl
1013         | notype_initdecls ',' initdcl
1014         ;
1016 maybeasm:
1017           /* empty */
1018                 { $$ = NULL_TREE; }
1019         | ASM_KEYWORD '(' string ')'
1020                 { if (TREE_CHAIN ($3)) $3 = combine_strings ($3);
1021                   $$ = $3;
1022                 }
1023         ;
1025 initdcl:
1026           declarator maybeasm maybe_attribute '='
1027                 { $<ttype>$ = start_decl ($1, current_declspecs, 1,
1028                                           $3, prefix_attributes);
1029                   start_init ($<ttype>$, $2, global_bindings_p ()); }
1030           init
1031 /* Note how the declaration of the variable is in effect while its init is parsed! */
1032                 { finish_init ();
1033                   finish_decl ($<ttype>5, $6, $2); }
1034         | declarator maybeasm maybe_attribute
1035                 { tree d = start_decl ($1, current_declspecs, 0,
1036                                        $3, prefix_attributes);
1037                   finish_decl (d, NULL_TREE, $2); 
1038                 }
1039         ;
1041 notype_initdcl:
1042           notype_declarator maybeasm maybe_attribute '='
1043                 { $<ttype>$ = start_decl ($1, current_declspecs, 1,
1044                                           $3, prefix_attributes);
1045                   start_init ($<ttype>$, $2, global_bindings_p ()); }
1046           init
1047 /* Note how the declaration of the variable is in effect while its init is parsed! */
1048                 { finish_init ();
1049                   decl_attributes ($<ttype>5, $3, prefix_attributes);
1050                   finish_decl ($<ttype>5, $6, $2); }
1051         | notype_declarator maybeasm maybe_attribute
1052                 { tree d = start_decl ($1, current_declspecs, 0,
1053                                        $3, prefix_attributes);
1054                   finish_decl (d, NULL_TREE, $2); }
1055         ;
1056 /* the * rules are dummies to accept the Apollo extended syntax
1057    so that the header files compile. */
1058 maybe_attribute:
1059       /* empty */
1060                 { $$ = NULL_TREE; }
1061         | attributes
1062                 { $$ = $1; }
1063         ;
1065 attributes:
1066       attribute
1067                 { $$ = $1; }
1068         | attributes attribute
1069                 { $$ = chainon ($1, $2); }
1070         ;
1072 attribute:
1073       ATTRIBUTE '(' '(' attribute_list ')' ')'
1074                 { $$ = $4; }
1075         ;
1077 attribute_list:
1078       attrib
1079                 { $$ = $1; }
1080         | attribute_list ',' attrib
1081                 { $$ = chainon ($1, $3); }
1082         ;
1084 attrib:
1085     /* empty */
1086                 { $$ = NULL_TREE; }
1087         | any_word
1088                 { $$ = build_tree_list ($1, NULL_TREE); }
1089         | any_word '(' IDENTIFIER ')'
1090                 { $$ = build_tree_list ($1, build_tree_list (NULL_TREE, $3)); }
1091         | any_word '(' IDENTIFIER ',' nonnull_exprlist ')'
1092                 { $$ = build_tree_list ($1, tree_cons (NULL_TREE, $3, $5)); }
1093         | any_word '(' exprlist ')'
1094                 { $$ = build_tree_list ($1, $3); }
1095         ;
1097 /* This still leaves out most reserved keywords,
1098    shouldn't we include them?  */
1100 any_word:
1101           identifier
1102         | SCSPEC
1103         | TYPESPEC
1104         | TYPE_QUAL
1105         ;
1107 /* Initializers.  `init' is the entry point.  */
1109 init:
1110         expr_no_commas
1111         | '{'
1112                 { really_start_incremental_init (NULL_TREE); }
1113           initlist_maybe_comma '}'
1114                 { $$ = pop_init_level (0); }
1115         | error
1116                 { $$ = error_mark_node; }
1117         ;
1119 /* `initlist_maybe_comma' is the guts of an initializer in braces.  */
1120 initlist_maybe_comma:
1121           /* empty */
1122                 { if (pedantic)
1123                     pedwarn ("ISO C forbids empty initializer braces"); }
1124         | initlist1 maybecomma
1125         ;
1127 initlist1:
1128           initelt
1129         | initlist1 ',' initelt
1130         ;
1132 /* `initelt' is a single element of an initializer.
1133    It may use braces.  */
1134 initelt:
1135           designator_list '=' initval
1136                 { if (pedantic && ! flag_isoc99)
1137                     pedwarn ("ISO C89 forbids specifying subobject to initialize"); }
1138         | designator initval
1139                 { if (pedantic)
1140                     pedwarn ("obsolete use of designated initializer without `='"); }
1141         | identifier ':'
1142                 { set_init_label ($1);
1143                   if (pedantic)
1144                     pedwarn ("obsolete use of designated initializer with `:'"); }
1145           initval
1146         | initval
1147         ;
1149 initval:
1150           '{'
1151                 { push_init_level (0); }
1152           initlist_maybe_comma '}'
1153                 { process_init_element (pop_init_level (0)); }
1154         | expr_no_commas
1155                 { process_init_element ($1); }
1156         | error
1157         ;
1159 designator_list:
1160           designator
1161         | designator_list designator
1162         ;
1164 designator:
1165           '.' identifier
1166                 { set_init_label ($2); }
1167         /* These are for labeled elements.  The syntax for an array element
1168            initializer conflicts with the syntax for an Objective-C message,
1169            so don't include these productions in the Objective-C grammar.  */
1171         | '[' expr_no_commas ELLIPSIS expr_no_commas ']'
1172                 { set_init_index ($2, $4);
1173                   if (pedantic)
1174                     pedwarn ("ISO C forbids specifying range of elements to initialize"); }
1175         | '[' expr_no_commas ']'
1176                 { set_init_index ($2, NULL_TREE); }
1177 end ifc
1178         ;
1180 nested_function:
1181           declarator
1182                 { if (pedantic)
1183                     pedwarn ("ISO C forbids nested functions");
1185                   push_function_context ();
1186                   if (! start_function (current_declspecs, $1,
1187                                         prefix_attributes, NULL_TREE))
1188                     {
1189                       pop_function_context ();
1190                       YYERROR1;
1191                     }
1192                 }
1193            old_style_parm_decls
1194                 { store_parm_decls (); }
1195 /* This used to use compstmt_or_error.
1196    That caused a bug with input `f(g) int g {}',
1197    where the use of YYERROR1 above caused an error
1198    which then was handled by compstmt_or_error.
1199    There followed a repeated execution of that same rule,
1200    which called YYERROR1 again, and so on.  */
1201           save_filename save_lineno compstmt
1202                 { tree decl = current_function_decl;
1203                   DECL_SOURCE_FILE (decl) = $5;
1204                   DECL_SOURCE_LINE (decl) = $6;
1205                   finish_function (1);
1206                   pop_function_context (); 
1207                   add_decl_stmt (decl); }
1208         ;
1210 notype_nested_function:
1211           notype_declarator
1212                 { if (pedantic)
1213                     pedwarn ("ISO C forbids nested functions");
1215                   push_function_context ();
1216                   if (! start_function (current_declspecs, $1,
1217                                         prefix_attributes, NULL_TREE))
1218                     {
1219                       pop_function_context ();
1220                       YYERROR1;
1221                     }
1222                 }
1223           old_style_parm_decls
1224                 { store_parm_decls (); }
1225 /* This used to use compstmt_or_error.
1226    That caused a bug with input `f(g) int g {}',
1227    where the use of YYERROR1 above caused an error
1228    which then was handled by compstmt_or_error.
1229    There followed a repeated execution of that same rule,
1230    which called YYERROR1 again, and so on.  */
1231           save_filename save_lineno compstmt
1232                 { tree decl = current_function_decl;
1233                   DECL_SOURCE_FILE (decl) = $5;
1234                   DECL_SOURCE_LINE (decl) = $6;
1235                   finish_function (1);
1236                   pop_function_context (); 
1237                   add_decl_stmt (decl); }
1238         ;
1240 /* Any kind of declarator (thus, all declarators allowed
1241    after an explicit typespec).  */
1243 declarator:
1244           after_type_declarator
1245         | notype_declarator
1246         ;
1248 /* A declarator that is allowed only after an explicit typespec.  */
1250 after_type_declarator:
1251           '(' after_type_declarator ')'
1252                 { $$ = $2; }
1253         | after_type_declarator '(' parmlist_or_identifiers  %prec '.'
1254                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1255 /*      | after_type_declarator '(' error ')'  %prec '.'
1256                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1257                   poplevel (0, 0, 0); }  */
1258         | after_type_declarator '[' expr ']'  %prec '.'
1259                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1260         | after_type_declarator '[' ']'  %prec '.'
1261                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1262         | '*' type_quals after_type_declarator  %prec UNARY
1263                 { $$ = make_pointer_declarator ($2, $3); }
1264         /* ??? Yuck.  setattrs is a quick hack.  We can't use
1265            prefix_attributes because $1 only applies to this
1266            declarator.  We assume setspecs has already been done.
1267            setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
1268            attributes could be recognized here or in `attributes').  */
1269         | attributes setattrs after_type_declarator
1270                 { $$ = $3; }
1271         | TYPENAME
1272 ifobjc
1273         | OBJECTNAME
1274 end ifobjc
1275         ;
1277 /* Kinds of declarator that can appear in a parameter list
1278    in addition to notype_declarator.  This is like after_type_declarator
1279    but does not allow a typedef name in parentheses as an identifier
1280    (because it would conflict with a function with that typedef as arg).  */
1282 parm_declarator:
1283           parm_declarator '(' parmlist_or_identifiers  %prec '.'
1284                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1285 /*      | parm_declarator '(' error ')'  %prec '.'
1286                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1287                   poplevel (0, 0, 0); }  */
1289         | parm_declarator '[' '*' ']'  %prec '.'
1290                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE);
1291                   if (! flag_isoc99)
1292                     error ("`[*]' in parameter declaration only allowed in ISO C 99");
1293                 }
1294 end ifc
1295         | parm_declarator '[' expr ']'  %prec '.'
1296                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1297         | parm_declarator '[' ']'  %prec '.'
1298                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1299         | '*' type_quals parm_declarator  %prec UNARY
1300                 { $$ = make_pointer_declarator ($2, $3); }
1301         /* ??? Yuck.  setattrs is a quick hack.  We can't use
1302            prefix_attributes because $1 only applies to this
1303            declarator.  We assume setspecs has already been done.
1304            setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
1305            attributes could be recognized here or in `attributes').  */
1306         | attributes setattrs parm_declarator
1307                 { $$ = $3; }
1308         | TYPENAME
1309         ;
1311 /* A declarator allowed whether or not there has been
1312    an explicit typespec.  These cannot redeclare a typedef-name.  */
1314 notype_declarator:
1315           notype_declarator '(' parmlist_or_identifiers  %prec '.'
1316                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1317 /*      | notype_declarator '(' error ')'  %prec '.'
1318                 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1319                   poplevel (0, 0, 0); }  */
1320         | '(' notype_declarator ')'
1321                 { $$ = $2; }
1322         | '*' type_quals notype_declarator  %prec UNARY
1323                 { $$ = make_pointer_declarator ($2, $3); }
1325         | notype_declarator '[' '*' ']'  %prec '.'
1326                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE);
1327                   if (! flag_isoc99)
1328                     error ("`[*]' in parameter declaration only allowed in ISO C 99");
1329                 }
1330 end ifc
1331         | notype_declarator '[' expr ']'  %prec '.'
1332                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1333         | notype_declarator '[' ']'  %prec '.'
1334                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1335         /* ??? Yuck.  setattrs is a quick hack.  We can't use
1336            prefix_attributes because $1 only applies to this
1337            declarator.  We assume setspecs has already been done.
1338            setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
1339            attributes could be recognized here or in `attributes').  */
1340         | attributes setattrs notype_declarator
1341                 { $$ = $3; }
1342         | IDENTIFIER
1343         ;
1345 struct_head:
1346           STRUCT
1347                 { $$ = NULL_TREE; }
1348         | STRUCT attributes
1349                 { $$ = $2; }
1350         ;
1352 union_head:
1353           UNION
1354                 { $$ = NULL_TREE; }
1355         | UNION attributes
1356                 { $$ = $2; }
1357         ;
1359 enum_head:
1360           ENUM
1361                 { $$ = NULL_TREE; }
1362         | ENUM attributes
1363                 { $$ = $2; }
1364         ;
1366 structsp:
1367           struct_head identifier '{'
1368                 { $$ = start_struct (RECORD_TYPE, $2);
1369                   /* Start scope of tag before parsing components.  */
1370                 }
1371           component_decl_list '}' maybe_attribute 
1372                 { $$ = finish_struct ($<ttype>4, $5, chainon ($1, $7)); }
1373         | struct_head '{' component_decl_list '}' maybe_attribute
1374                 { $$ = finish_struct (start_struct (RECORD_TYPE, NULL_TREE),
1375                                       $3, chainon ($1, $5));
1376                 }
1377         | struct_head identifier
1378                 { $$ = xref_tag (RECORD_TYPE, $2); }
1379         | union_head identifier '{'
1380                 { $$ = start_struct (UNION_TYPE, $2); }
1381           component_decl_list '}' maybe_attribute
1382                 { $$ = finish_struct ($<ttype>4, $5, chainon ($1, $7)); }
1383         | union_head '{' component_decl_list '}' maybe_attribute
1384                 { $$ = finish_struct (start_struct (UNION_TYPE, NULL_TREE),
1385                                       $3, chainon ($1, $5));
1386                 }
1387         | union_head identifier
1388                 { $$ = xref_tag (UNION_TYPE, $2); }
1389         | enum_head identifier '{'
1390                 { $$ = start_enum ($2); }
1391           enumlist maybecomma_warn '}' maybe_attribute
1392                 { $$ = finish_enum ($<ttype>4, nreverse ($5),
1393                                     chainon ($1, $8)); }
1394         | enum_head '{'
1395                 { $$ = start_enum (NULL_TREE); }
1396           enumlist maybecomma_warn '}' maybe_attribute
1397                 { $$ = finish_enum ($<ttype>3, nreverse ($4),
1398                                     chainon ($1, $7)); }
1399         | enum_head identifier
1400                 { $$ = xref_tag (ENUMERAL_TYPE, $2); }
1401         ;
1403 maybecomma:
1404           /* empty */
1405         | ','
1406         ;
1408 maybecomma_warn:
1409           /* empty */
1410         | ','
1411                 { if (pedantic && ! flag_isoc99)
1412                     pedwarn ("comma at end of enumerator list"); }
1413         ;
1415 component_decl_list:
1416           component_decl_list2
1417                 { $$ = $1; }
1418         | component_decl_list2 component_decl
1419                 { $$ = chainon ($1, $2);
1420                   pedwarn ("no semicolon at end of struct or union"); }
1421         ;
1423 component_decl_list2:   /* empty */
1424                 { $$ = NULL_TREE; }
1425         | component_decl_list2 component_decl ';'
1426                 { $$ = chainon ($1, $2); }
1427         | component_decl_list2 ';'
1428                 { if (pedantic)
1429                     pedwarn ("extra semicolon in struct or union specified"); }
1430 ifobjc
1431         /* foo(sizeof(struct{ @defs(ClassName)})); */
1432         | DEFS '(' CLASSNAME ')'
1433                 {
1434                   tree interface = lookup_interface ($3);
1436                   if (interface)
1437                     $$ = get_class_ivars (interface);
1438                   else
1439                     {
1440                       error ("Cannot find interface declaration for `%s'",
1441                              IDENTIFIER_POINTER ($3));
1442                       $$ = NULL_TREE;
1443                     }
1444                 }
1445 end ifobjc
1446         ;
1448 /* There is a shift-reduce conflict here, because `components' may
1449    start with a `typename'.  It happens that shifting (the default resolution)
1450    does the right thing, because it treats the `typename' as part of
1451    a `typed_typespecs'.
1453    It is possible that this same technique would allow the distinction
1454    between `notype_initdecls' and `initdecls' to be eliminated.
1455    But I am being cautious and not trying it.  */
1457 component_decl:
1458           typed_typespecs setspecs components
1459                 { $$ = $3;
1460                   current_declspecs = TREE_VALUE (declspec_stack);
1461                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1462                   declspec_stack = TREE_CHAIN (declspec_stack); }
1463         | typed_typespecs setspecs save_filename save_lineno maybe_attribute
1464                 {
1465                   /* Support for unnamed structs or unions as members of 
1466                      structs or unions (which is [a] useful and [b] supports 
1467                      MS P-SDK).  */
1468                   if (pedantic)
1469                     pedwarn ("ISO C doesn't support unnamed structs/unions");
1471                   $$ = grokfield($3, $4, NULL, current_declspecs, NULL_TREE);
1472                   current_declspecs = TREE_VALUE (declspec_stack);
1473                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1474                   declspec_stack = TREE_CHAIN (declspec_stack);
1475                 }
1476     | nonempty_type_quals setspecs components
1477                 { $$ = $3;
1478                   current_declspecs = TREE_VALUE (declspec_stack);
1479                   prefix_attributes = TREE_PURPOSE (declspec_stack);
1480                   declspec_stack = TREE_CHAIN (declspec_stack); }
1481         | nonempty_type_quals
1482                 { if (pedantic)
1483                     pedwarn ("ISO C forbids member declarations with no members");
1484                   shadow_tag($1);
1485                   $$ = NULL_TREE; }
1486         | error
1487                 { $$ = NULL_TREE; }
1488         | extension component_decl
1489                 { $$ = $2;
1490                   RESTORE_WARN_FLAGS ($1); }
1491         ;
1493 components:
1494           component_declarator
1495         | components ',' component_declarator
1496                 { $$ = chainon ($1, $3); }
1497         ;
1499 component_declarator:
1500           save_filename save_lineno declarator maybe_attribute
1501                 { $$ = grokfield ($1, $2, $3, current_declspecs, NULL_TREE);
1502                   decl_attributes ($$, $4, prefix_attributes); }
1503         | save_filename save_lineno
1504           declarator ':' expr_no_commas maybe_attribute
1505                 { $$ = grokfield ($1, $2, $3, current_declspecs, $5);
1506                   decl_attributes ($$, $6, prefix_attributes); }
1507         | save_filename save_lineno ':' expr_no_commas maybe_attribute
1508                 { $$ = grokfield ($1, $2, NULL_TREE, current_declspecs, $4);
1509                   decl_attributes ($$, $5, prefix_attributes); }
1510         ;
1512 /* We chain the enumerators in reverse order.
1513    They are put in forward order where enumlist is used.
1514    (The order used to be significant, but no longer is so.
1515    However, we still maintain the order, just to be clean.)  */
1517 enumlist:
1518           enumerator
1519         | enumlist ',' enumerator
1520                 { if ($1 == error_mark_node)
1521                     $$ = $1;
1522                   else
1523                     $$ = chainon ($3, $1); }
1524         | error
1525                 { $$ = error_mark_node; }
1526         ;
1529 enumerator:
1530           identifier
1531                 { $$ = build_enumerator ($1, NULL_TREE); }
1532         | identifier '=' expr_no_commas
1533                 { $$ = build_enumerator ($1, $3); }
1534         ;
1536 typename:
1537         typed_typespecs absdcl
1538                 { $$ = build_tree_list ($1, $2); }
1539         | nonempty_type_quals absdcl
1540                 { $$ = build_tree_list ($1, $2); }
1541         ;
1543 absdcl:   /* an absolute declarator */
1544         /* empty */
1545                 { $$ = NULL_TREE; }
1546         | absdcl1
1547         ;
1549 nonempty_type_quals:
1550           TYPE_QUAL
1551                 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
1552         | nonempty_type_quals TYPE_QUAL
1553                 { $$ = tree_cons (NULL_TREE, $2, $1); }
1554         ;
1556 type_quals:
1557           /* empty */
1558                 { $$ = NULL_TREE; }
1559         | type_quals TYPE_QUAL
1560                 { $$ = tree_cons (NULL_TREE, $2, $1); }
1561         ;
1563 absdcl1:  /* a nonempty absolute declarator */
1564           '(' absdcl1 ')'
1565                 { $$ = $2; }
1566           /* `(typedef)1' is `int'.  */
1567         | '*' type_quals absdcl1  %prec UNARY
1568                 { $$ = make_pointer_declarator ($2, $3); }
1569         | '*' type_quals  %prec UNARY
1570                 { $$ = make_pointer_declarator ($2, NULL_TREE); }
1571         | absdcl1 '(' parmlist  %prec '.'
1572                 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1573         | absdcl1 '[' expr ']'  %prec '.'
1574                 { $$ = build_nt (ARRAY_REF, $1, $3); }
1575         | absdcl1 '[' ']'  %prec '.'
1576                 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1577         | '(' parmlist  %prec '.'
1578                 { $$ = build_nt (CALL_EXPR, NULL_TREE, $2, NULL_TREE); }
1579         | '[' expr ']'  %prec '.'
1580                 { $$ = build_nt (ARRAY_REF, NULL_TREE, $2); }
1581         | '[' ']'  %prec '.'
1582                 { $$ = build_nt (ARRAY_REF, NULL_TREE, NULL_TREE); }
1583         /* ??? It appears we have to support attributes here, however
1584            using prefix_attributes is wrong.  */
1585         | attributes setattrs absdcl1
1586                 { $$ = $3; }
1587         ;
1589 /* A nonempty series of declarations and statements (possibly followed by
1590    some labels) that can form the body of a compound statement.
1591    NOTE: we don't allow labels on declarations; this might seem like a
1592    natural extension, but there would be a conflict between attributes
1593    on the label and prefix attributes on the declaration.  */
1595 stmts_and_decls:
1596           lineno_stmt_decl_or_labels_ending_stmt
1597         | lineno_stmt_decl_or_labels_ending_decl
1598         | lineno_stmt_decl_or_labels_ending_label
1599                 {
1600                   pedwarn ("deprecated use of label at end of compound statement");
1601                 }
1602         | lineno_stmt_decl_or_labels_ending_error
1603         ;
1605 lineno_stmt_decl_or_labels_ending_stmt:
1606           lineno_stmt
1607         | lineno_stmt_decl_or_labels_ending_stmt lineno_stmt
1608         | lineno_stmt_decl_or_labels_ending_decl lineno_stmt
1609         | lineno_stmt_decl_or_labels_ending_label lineno_stmt
1610         | lineno_stmt_decl_or_labels_ending_error lineno_stmt
1611         ;
1613 lineno_stmt_decl_or_labels_ending_decl:
1614           lineno_decl
1615         | lineno_stmt_decl_or_labels_ending_stmt lineno_decl
1616                 { if (pedantic && !flag_isoc99)
1617                     pedwarn ("ISO C89 forbids mixed declarations and code"); }
1618         | lineno_stmt_decl_or_labels_ending_decl lineno_decl
1619         | lineno_stmt_decl_or_labels_ending_error lineno_decl
1620         ;
1622 lineno_stmt_decl_or_labels_ending_label:
1623           lineno_label
1624         | lineno_stmt_decl_or_labels_ending_stmt lineno_label
1625         | lineno_stmt_decl_or_labels_ending_decl lineno_label
1626         | lineno_stmt_decl_or_labels_ending_label lineno_label
1627         | lineno_stmt_decl_or_labels_ending_error lineno_label
1628         ;
1630 lineno_stmt_decl_or_labels_ending_error:
1631         errstmt
1632         | lineno_stmt_decl_or_labels errstmt
1633         ;
1635 lineno_stmt_decl_or_labels:
1636           lineno_stmt_decl_or_labels_ending_stmt
1637         | lineno_stmt_decl_or_labels_ending_decl
1638         | lineno_stmt_decl_or_labels_ending_label
1639         | lineno_stmt_decl_or_labels_ending_error
1640         ;
1642 errstmt:  error ';'
1643         ;
1645 pushlevel:  /* empty */
1646                 { pushlevel (0);
1647                   clear_last_expr ();
1648                   add_scope_stmt (/*begin_p=*/1, /*partial_p=*/0);
1649 ifobjc
1650                   if (objc_method_context)
1651                     add_objc_decls ();
1652 end ifobjc
1653                 }
1654         ;
1656 poplevel:  /* empty */
1657                 { $$ = add_scope_stmt (/*begin_p=*/0, /*partial_p=*/0); }
1659 /* Start and end blocks created for the new scopes of C99.  */
1660 c99_block_start: /* empty */
1661                 { if (flag_isoc99)
1662                     {
1663                       $$ = c_begin_compound_stmt ();
1664                       pushlevel (0);
1665                       clear_last_expr ();
1666                       add_scope_stmt (/*begin_p=*/1, /*partial_p=*/0);
1667 ifobjc
1668                       if (objc_method_context)
1669                         add_objc_decls ();
1670 end ifobjc
1671                     }
1672                   else
1673                     $$ = NULL_TREE;
1674                 }
1675         ;
1677 /* Productions using c99_block_start and c99_block_end will need to do what's
1678    in compstmt: RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); $$ = $2; where
1679    $1 is the value of c99_block_start and $2 of c99_block_end.  */
1680 c99_block_end: /* empty */
1681                 { if (flag_isoc99)
1682                     {
1683                       tree scope_stmt = add_scope_stmt (/*begin_p=*/0, /*partial_p=*/0);
1684                       $$ = poplevel (kept_level_p (), 0, 0); 
1685                       SCOPE_STMT_BLOCK (TREE_PURPOSE (scope_stmt)) 
1686                         = SCOPE_STMT_BLOCK (TREE_VALUE (scope_stmt))
1687                         = $$;
1688                     }
1689                   else
1690                     $$ = NULL_TREE; }
1691         ;
1693 /* Read zero or more forward-declarations for labels
1694    that nested functions can jump to.  */
1695 maybe_label_decls:
1696           /* empty */
1697         | label_decls
1698                 { if (pedantic)
1699                     pedwarn ("ISO C forbids label declarations"); }
1700         ;
1702 label_decls:
1703           label_decl
1704         | label_decls label_decl
1705         ;
1707 label_decl:
1708           LABEL identifiers_or_typenames ';'
1709                 { tree link;
1710                   for (link = $2; link; link = TREE_CHAIN (link))
1711                     {
1712                       tree label = shadow_label (TREE_VALUE (link));
1713                       C_DECLARED_LABEL_FLAG (label) = 1;
1714                       add_decl_stmt (label);
1715                     }
1716                 }
1717         ;
1719 /* This is the body of a function definition.
1720    It causes syntax errors to ignore to the next openbrace.  */
1721 compstmt_or_error:
1722           compstmt
1723                 {}
1724         | error compstmt
1725         ;
1727 compstmt_start: '{' { compstmt_count++;
1728                       $$ = c_begin_compound_stmt (); } 
1730 compstmt_nostart: '}'
1731                 { $$ = convert (void_type_node, integer_zero_node); }
1732         | pushlevel maybe_label_decls compstmt_contents_nonempty '}' poplevel
1733                 { $$ = poplevel (kept_level_p (), 1, 0); 
1734                   SCOPE_STMT_BLOCK (TREE_PURPOSE ($5)) 
1735                     = SCOPE_STMT_BLOCK (TREE_VALUE ($5))
1736                     = $$; }
1737         ;
1739 compstmt_contents_nonempty:
1740           stmts_and_decls
1741         | error
1742         ;
1744 compstmt_primary_start:
1745         '(' '{'
1746                 { if (current_function_decl == 0)
1747                     {
1748                       error ("braced-group within expression allowed only inside a function");
1749                       YYERROR;
1750                     }
1751                   /* We must force a BLOCK for this level
1752                      so that, if it is not expanded later,
1753                      there is a way to turn off the entire subtree of blocks
1754                      that are contained in it.  */
1755                   keep_next_level ();
1756                   push_label_level ();
1757                   compstmt_count++;
1758                   $$ = add_stmt (build_stmt (COMPOUND_STMT, last_tree));
1759                 }
1761 compstmt: compstmt_start compstmt_nostart
1762                 { RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); 
1763                   $$ = $1; }
1764         ;
1766 /* Value is number of statements counted as of the closeparen.  */
1767 simple_if:
1768           if_prefix c99_block_lineno_labeled_stmt
1769                 { c_finish_then (); }
1770 /* Make sure c_expand_end_cond is run once
1771    for each call to c_expand_start_cond.
1772    Otherwise a crash is likely.  */
1773         | if_prefix error
1774         ;
1776 if_prefix:
1777           IF '(' expr ')'
1778                 { c_expand_start_cond (truthvalue_conversion ($3), 
1779                                        compstmt_count);
1780                   $<itype>$ = stmt_count;
1781                   if_stmt_file = $<filename>-2;
1782                   if_stmt_line = $<lineno>-1; }
1783         ;
1785 /* This is a subroutine of stmt.
1786    It is used twice, once for valid DO statements
1787    and once for catching errors in parsing the end test.  */
1788 do_stmt_start:
1789           DO
1790                 { stmt_count++;
1791                   compstmt_count++;
1792                   $<ttype>$ 
1793                     = add_stmt (build_stmt (DO_STMT, NULL_TREE,
1794                                             NULL_TREE));
1795                   /* In the event that a parse error prevents
1796                      parsing the complete do-statement, set the
1797                      condition now.  Otherwise, we can get crashes at
1798                      RTL-generation time.  */
1799                   DO_COND ($<ttype>$) = error_mark_node; }
1800           c99_block_lineno_labeled_stmt WHILE
1801                 { $$ = $<ttype>2;
1802                   RECHAIN_STMTS ($$, DO_BODY ($$)); }
1803         ;
1805 /* The forced readahead in here is because we might be at the end of a
1806    line, and the line and file won't be bumped until yylex absorbs the
1807    first token on the next line.  */
1808 save_filename:
1809                 { if (yychar == YYEMPTY)
1810                     yychar = YYLEX;
1811                   $$ = input_filename; }
1812         ;
1814 save_lineno:
1815                 { if (yychar == YYEMPTY)
1816                     yychar = YYLEX;
1817                   $$ = lineno; }
1818         ;
1820 lineno_labeled_stmt:
1821           lineno_stmt
1822         | lineno_label lineno_labeled_stmt
1823         ;
1825 /* Like lineno_labeled_stmt, but a block in C99.  */
1826 c99_block_lineno_labeled_stmt:
1827           c99_block_start lineno_labeled_stmt c99_block_end
1828                 { if (flag_isoc99)
1829                     RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); }
1830         ;
1832 lineno_stmt:
1833           save_filename save_lineno stmt
1834                 { if ($3)
1835                     {
1836                       STMT_LINENO ($3) = $2;
1837                       /* ??? We currently have no way of recording
1838                          the filename for a statement.  This probably
1839                          matters little in practice at the moment,
1840                          but I suspect that problems will ocurr when
1841                          doing inlining at the tree level.  */
1842                     }
1843                 }
1844         ;
1846 lineno_label:
1847           save_filename save_lineno label
1848                 { if ($3)
1849                     {
1850                       STMT_LINENO ($3) = $2;
1851                     }
1852                 }
1853         ;
1855 select_or_iter_stmt:
1856           simple_if ELSE
1857                 { c_expand_start_else ();
1858                   $<itype>1 = stmt_count; }
1859           c99_block_lineno_labeled_stmt
1860                 { c_finish_else ();
1861                   c_expand_end_cond ();
1862                   if (extra_warnings && stmt_count == $<itype>1)
1863                     warning ("empty body in an else-statement"); }
1864         | simple_if %prec IF
1865                 { c_expand_end_cond ();
1866                   /* This warning is here instead of in simple_if, because we
1867                      do not want a warning if an empty if is followed by an
1868                      else statement.  Increment stmt_count so we don't
1869                      give a second error if this is a nested `if'.  */
1870                   if (extra_warnings && stmt_count++ == $<itype>1)
1871                     warning_with_file_and_line (if_stmt_file, if_stmt_line,
1872                                                 "empty body in an if-statement"); }
1873 /* Make sure c_expand_end_cond is run once
1874    for each call to c_expand_start_cond.
1875    Otherwise a crash is likely.  */
1876         | simple_if ELSE error
1877                 { c_expand_end_cond (); }
1878         | WHILE
1879                 { stmt_count++; }
1880           '(' expr ')'
1881                 { $4 = truthvalue_conversion ($4);
1882                   $<ttype>$ 
1883                     = add_stmt (build_stmt (WHILE_STMT, $4, NULL_TREE)); }
1884           c99_block_lineno_labeled_stmt
1885                 { RECHAIN_STMTS ($<ttype>6, WHILE_BODY ($<ttype>6)); }
1886         | do_stmt_start
1887           '(' expr ')' ';'
1888                 { DO_COND ($1) = truthvalue_conversion ($3); }
1889         | do_stmt_start error
1890                 { }
1891         | FOR
1892                 { $<ttype>$ = build_stmt (FOR_STMT, NULL_TREE, NULL_TREE,
1893                                           NULL_TREE, NULL_TREE);
1894                   add_stmt ($<ttype>$); } 
1895           '(' for_init_stmt
1896                 { stmt_count++;
1897                   RECHAIN_STMTS ($<ttype>2, FOR_INIT_STMT ($<ttype>2)); }
1898           xexpr ';'
1899                 { if ($6) 
1900                     FOR_COND ($<ttype>2) = truthvalue_conversion ($6); }
1901           xexpr ')'
1902                 { FOR_EXPR ($<ttype>2) = $9; }
1903           c99_block_lineno_labeled_stmt
1904                 { RECHAIN_STMTS ($<ttype>2, FOR_BODY ($<ttype>2)); }
1905         | SWITCH '(' expr ')'
1906                 { stmt_count++;
1907                   $<ttype>$ = c_start_case ($3); }
1908           c99_block_lineno_labeled_stmt
1909                 { c_finish_case (); }
1910         ;
1912 for_init_stmt:
1913           xexpr ';'
1914                 { add_stmt (build_stmt (EXPR_STMT, $1)); } 
1915         | decl
1916                 { check_for_loop_decls (); }
1917         ;
1919 /* Parse a single real statement, not including any labels.  */
1920 stmt:
1921           compstmt
1922                 { stmt_count++; $$ = $1; }
1923         | expr ';'
1924                 { stmt_count++;
1925                   $$ = c_expand_expr_stmt ($1); }
1926         | c99_block_start select_or_iter_stmt c99_block_end
1927                 { if (flag_isoc99)
1928                     RECHAIN_STMTS ($1, COMPOUND_BODY ($1));
1929                   $$ = NULL_TREE; }
1930         | BREAK ';'
1931                 { stmt_count++;
1932                   $$ = add_stmt (build_break_stmt ()); }
1933         | CONTINUE ';'
1934                 { stmt_count++;
1935                   $$ = add_stmt (build_continue_stmt ()); }
1936         | RETURN ';'
1937                 { stmt_count++;
1938                   $$ = c_expand_return (NULL_TREE); }
1939         | RETURN expr ';'
1940                 { stmt_count++;
1941                   $$ = c_expand_return ($2); }
1942         | ASM_KEYWORD maybe_type_qual '(' expr ')' ';'
1943                 { stmt_count++;
1944                   STRIP_NOPS ($4);
1945                   if ((TREE_CODE ($4) == ADDR_EXPR
1946                        && TREE_CODE (TREE_OPERAND ($4, 0)) == STRING_CST)
1947                       || TREE_CODE ($4) == STRING_CST)
1948                     {
1949                       if (TREE_CODE ($4) == ADDR_EXPR)
1950                         $4 = TREE_OPERAND ($4, 0);
1951                       if (TREE_CHAIN ($4))
1952                         $4 = combine_strings ($4);
1953                       $$ = add_stmt (build_stmt (ASM_STMT, NULL_TREE, $4,
1954                                                  NULL_TREE, NULL_TREE,
1955                                                  NULL_TREE));
1956                     }
1957                   else
1958                     {
1959                       error ("argument of `asm' is not a constant string");
1960                       $$ = NULL_TREE;
1961                     }
1962                 }
1963         /* This is the case with just output operands.  */
1964         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ')' ';'
1965                 { stmt_count++;
1966                   $$ = build_asm_stmt ($2, $4, $6, NULL_TREE, NULL_TREE); }
1967         /* This is the case with input operands as well.  */
1968         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':'
1969           asm_operands ')' ';'
1970                 { stmt_count++;
1971                   $$ = build_asm_stmt ($2, $4, $6, $8, NULL_TREE); }
1972         /* This is the case with clobbered registers as well.  */
1973         | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':'
1974           asm_operands ':' asm_clobbers ')' ';'
1975                 { stmt_count++;
1976                   $$ = build_asm_stmt ($2, $4, $6, $8, $10); }
1977         | GOTO identifier ';'
1978                 { tree decl;
1979                   stmt_count++;
1980                   decl = lookup_label ($2);
1981                   if (decl != 0)
1982                     {
1983                       TREE_USED (decl) = 1;
1984                       $$ = add_stmt (build_stmt (GOTO_STMT, decl));
1985                     }
1986                   else
1987                     $$ = NULL_TREE;
1988                 }
1989         | GOTO '*' expr ';'
1990                 { if (pedantic)
1991                     pedwarn ("ISO C forbids `goto *expr;'");
1992                   stmt_count++;
1993                   $3 = convert (ptr_type_node, $3);
1994                   $$ = add_stmt (build_stmt (GOTO_STMT, $3)); }
1995         | ';'
1996                 { $$ = NULL_TREE; }
1997         ;
1999 /* Any kind of label, including jump labels and case labels.
2000    ANSI C accepts labels only before statements, but we allow them
2001    also at the end of a compound statement.  */
2003 label:    CASE expr_no_commas ':'
2004                 { stmt_count++;
2005                   $$ = do_case ($2, NULL_TREE); }
2006         | CASE expr_no_commas ELLIPSIS expr_no_commas ':'
2007                 { stmt_count++;
2008                   $$ = do_case ($2, $4); }
2009         | DEFAULT ':'
2010                 { stmt_count++;
2011                   $$ = do_case (NULL_TREE, NULL_TREE); }
2012         | identifier save_filename save_lineno ':' maybe_attribute
2013                 { tree label = define_label ($2, $3, $1);
2014                   stmt_count++;
2015                   if (label)
2016                     {
2017                       decl_attributes (label, $5, NULL_TREE);
2018                       $$ = add_stmt (build_stmt (LABEL_STMT, label));
2019                     }
2020                   else
2021                     $$ = NULL_TREE;
2022                 }
2023         ;
2025 /* Either a type-qualifier or nothing.  First thing in an `asm' statement.  */
2027 maybe_type_qual:
2028         /* empty */
2029                 { emit_line_note (input_filename, lineno);
2030                   $$ = NULL_TREE; }
2031         | TYPE_QUAL
2032                 { emit_line_note (input_filename, lineno); }
2033         ;
2035 xexpr:
2036         /* empty */
2037                 { $$ = NULL_TREE; }
2038         | expr
2039         ;
2041 /* These are the operands other than the first string and colon
2042    in  asm ("addextend %2,%1": "=dm" (x), "0" (y), "g" (*x))  */
2043 asm_operands: /* empty */
2044                 { $$ = NULL_TREE; }
2045         | nonnull_asm_operands
2046         ;
2048 nonnull_asm_operands:
2049           asm_operand
2050         | nonnull_asm_operands ',' asm_operand
2051                 { $$ = chainon ($1, $3); }
2052         ;
2054 asm_operand:
2055           STRING '(' expr ')'
2056                 { $$ = build_tree_list ($1, $3); }
2057         ;
2059 asm_clobbers:
2060           string
2061                 { $$ = tree_cons (NULL_TREE, combine_strings ($1), NULL_TREE); }
2062         | asm_clobbers ',' string
2063                 { $$ = tree_cons (NULL_TREE, combine_strings ($3), $1); }
2064         ;
2066 /* This is what appears inside the parens in a function declarator.
2067    Its value is a list of ..._TYPE nodes.  */
2068 parmlist:
2069                 { pushlevel (0);
2070                   clear_parm_order ();
2071                   declare_parm_level (0); }
2072           parmlist_1
2073                 { $$ = $2;
2074                   parmlist_tags_warning ();
2075                   poplevel (0, 0, 0); }
2076         ;
2078 parmlist_1:
2079           parmlist_2 ')'
2080         | parms ';'
2081                 { tree parm;
2082                   if (pedantic)
2083                     pedwarn ("ISO C forbids forward parameter declarations");
2084                   /* Mark the forward decls as such.  */
2085                   for (parm = getdecls (); parm; parm = TREE_CHAIN (parm))
2086                     TREE_ASM_WRITTEN (parm) = 1;
2087                   clear_parm_order (); }
2088           parmlist_1
2089                 { $$ = $4; }
2090         | error ')'
2091                 { $$ = tree_cons (NULL_TREE, NULL_TREE, NULL_TREE); }
2092         ;
2094 /* This is what appears inside the parens in a function declarator.
2095    Is value is represented in the format that grokdeclarator expects.  */
2096 parmlist_2:  /* empty */
2097                 { $$ = get_parm_info (0); }
2098         | ELLIPSIS
2099                 { $$ = get_parm_info (0);
2100                   /* Gcc used to allow this as an extension.  However, it does
2101                      not work for all targets, and thus has been disabled.
2102                      Also, since func (...) and func () are indistinguishable,
2103                      it caused problems with the code in expand_builtin which
2104                      tries to verify that BUILT_IN_NEXT_ARG is being used
2105                      correctly.  */
2106                   error ("ISO C requires a named argument before `...'");
2107                 }
2108         | parms
2109                 { $$ = get_parm_info (1); }
2110         | parms ',' ELLIPSIS
2111                 { $$ = get_parm_info (0); }
2112         ;
2114 parms:
2115         parm
2116                 { push_parm_decl ($1); }
2117         | parms ',' parm
2118                 { push_parm_decl ($3); }
2119         ;
2121 /* A single parameter declaration or parameter type name,
2122    as found in a parmlist.  */
2123 parm:
2124           typed_declspecs setspecs parm_declarator maybe_attribute
2125                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2126                                                          $3),
2127                                         build_tree_list (prefix_attributes,
2128                                                          $4));
2129                   current_declspecs = TREE_VALUE (declspec_stack);
2130                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2131                   declspec_stack = TREE_CHAIN (declspec_stack); }
2132         | typed_declspecs setspecs notype_declarator 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         | typed_declspecs setspecs absdcl maybe_attribute
2141                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2142                                                          $3),
2143                                         build_tree_list (prefix_attributes,
2144                                                          $4));
2145                   current_declspecs = TREE_VALUE (declspec_stack);
2146                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2147                   declspec_stack = TREE_CHAIN (declspec_stack); }
2148         | declmods setspecs notype_declarator maybe_attribute
2149                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2150                                                          $3),
2151                                         build_tree_list (prefix_attributes,
2152                                                          $4));
2153                   current_declspecs = TREE_VALUE (declspec_stack);
2154                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2155                   declspec_stack = TREE_CHAIN (declspec_stack); }
2157         | declmods setspecs absdcl maybe_attribute
2158                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2159                                                          $3),
2160                                         build_tree_list (prefix_attributes,
2161                                                          $4));
2162                   current_declspecs = TREE_VALUE (declspec_stack);
2163                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2164                   declspec_stack = TREE_CHAIN (declspec_stack); }
2165         ;
2167 /* This is used in a function definition
2168    where either a parmlist or an identifier list is ok.
2169    Its value is a list of ..._TYPE nodes or a list of identifiers.  */
2170 parmlist_or_identifiers:
2171                 { pushlevel (0);
2172                   clear_parm_order ();
2173                   declare_parm_level (1); }
2174           parmlist_or_identifiers_1
2175                 { $$ = $2;
2176                   parmlist_tags_warning ();
2177                   poplevel (0, 0, 0); }
2178         ;
2180 parmlist_or_identifiers_1:
2181           parmlist_1
2182         | identifiers ')'
2183                 { tree t;
2184                   for (t = $1; t; t = TREE_CHAIN (t))
2185                     if (TREE_VALUE (t) == NULL_TREE)
2186                       error ("`...' in old-style identifier list");
2187                   $$ = tree_cons (NULL_TREE, NULL_TREE, $1); }
2188         ;
2190 /* A nonempty list of identifiers.  */
2191 identifiers:
2192         IDENTIFIER
2193                 { $$ = build_tree_list (NULL_TREE, $1); }
2194         | identifiers ',' IDENTIFIER
2195                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2196         ;
2198 /* A nonempty list of identifiers, including typenames.  */
2199 identifiers_or_typenames:
2200         identifier
2201                 { $$ = build_tree_list (NULL_TREE, $1); }
2202         | identifiers_or_typenames ',' identifier
2203                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2204         ;
2206 extension:
2207         EXTENSION
2208                 { $$ = SAVE_WARN_FLAGS();
2209                   pedantic = 0;
2210                   warn_pointer_arith = 0; }
2211         ;
2213 ifobjc
2214 /* Objective-C productions.  */
2216 objcdef:
2217           classdef
2218         | classdecl
2219         | aliasdecl
2220         | protocoldef
2221         | methoddef
2222         | END
2223                 {
2224                   if (objc_implementation_context)
2225                     {
2226                       finish_class (objc_implementation_context);
2227                       objc_ivar_chain = NULL_TREE;
2228                       objc_implementation_context = NULL_TREE;
2229                     }
2230                   else
2231                     warning ("`@end' must appear in an implementation context");
2232                 }
2233         ;
2235 /* A nonempty list of identifiers.  */
2236 identifier_list:
2237         identifier
2238                 { $$ = build_tree_list (NULL_TREE, $1); }
2239         | identifier_list ',' identifier
2240                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2241         ;
2243 classdecl:
2244           CLASS identifier_list ';'
2245                 {
2246                   objc_declare_class ($2);
2247                 }
2249 aliasdecl:
2250           ALIAS identifier identifier ';'
2251                 {
2252                   objc_declare_alias ($2, $3);
2253                 }
2255 classdef:
2256           INTERFACE identifier protocolrefs '{'
2257                 {
2258                   objc_interface_context = objc_ivar_context
2259                     = start_class (CLASS_INTERFACE_TYPE, $2, NULL_TREE, $3);
2260                   objc_public_flag = 0;
2261                 }
2262           ivar_decl_list '}'
2263                 {
2264                   continue_class (objc_interface_context);
2265                 }
2266           methodprotolist
2267           END
2268                 {
2269                   finish_class (objc_interface_context);
2270                   objc_interface_context = NULL_TREE;
2271                 }
2273         | INTERFACE identifier protocolrefs
2274                 {
2275                   objc_interface_context
2276                     = start_class (CLASS_INTERFACE_TYPE, $2, NULL_TREE, $3);
2277                   continue_class (objc_interface_context);
2278                 }
2279           methodprotolist
2280           END
2281                 {
2282                   finish_class (objc_interface_context);
2283                   objc_interface_context = NULL_TREE;
2284                 }
2286         | INTERFACE identifier ':' identifier protocolrefs '{'
2287                 {
2288                   objc_interface_context = objc_ivar_context
2289                     = start_class (CLASS_INTERFACE_TYPE, $2, $4, $5);
2290                   objc_public_flag = 0;
2291                 }
2292           ivar_decl_list '}'
2293                 {
2294                   continue_class (objc_interface_context);
2295                 }
2296           methodprotolist
2297           END
2298                 {
2299                   finish_class (objc_interface_context);
2300                   objc_interface_context = NULL_TREE;
2301                 }
2303         | INTERFACE identifier ':' identifier protocolrefs
2304                 {
2305                   objc_interface_context
2306                     = start_class (CLASS_INTERFACE_TYPE, $2, $4, $5);
2307                   continue_class (objc_interface_context);
2308                 }
2309           methodprotolist
2310           END
2311                 {
2312                   finish_class (objc_interface_context);
2313                   objc_interface_context = NULL_TREE;
2314                 }
2316         | IMPLEMENTATION identifier '{'
2317                 {
2318                   objc_implementation_context = objc_ivar_context
2319                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, NULL_TREE, NULL_TREE);
2320                   objc_public_flag = 0;
2321                 }
2322           ivar_decl_list '}'
2323                 {
2324                   objc_ivar_chain
2325                     = continue_class (objc_implementation_context);
2326                 }
2328         | IMPLEMENTATION identifier
2329                 {
2330                   objc_implementation_context
2331                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, NULL_TREE, NULL_TREE);
2332                   objc_ivar_chain
2333                     = continue_class (objc_implementation_context);
2334                 }
2336         | IMPLEMENTATION identifier ':' identifier '{'
2337                 {
2338                   objc_implementation_context = objc_ivar_context
2339                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2340                   objc_public_flag = 0;
2341                 }
2342           ivar_decl_list '}'
2343                 {
2344                   objc_ivar_chain
2345                     = continue_class (objc_implementation_context);
2346                 }
2348         | IMPLEMENTATION identifier ':' identifier
2349                 {
2350                   objc_implementation_context
2351                     = start_class (CLASS_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2352                   objc_ivar_chain
2353                     = continue_class (objc_implementation_context);
2354                 }
2356         | INTERFACE identifier '(' identifier ')' protocolrefs
2357                 {
2358                   objc_interface_context
2359                     = start_class (CATEGORY_INTERFACE_TYPE, $2, $4, $6);
2360                   continue_class (objc_interface_context);
2361                 }
2362           methodprotolist
2363           END
2364                 {
2365                   finish_class (objc_interface_context);
2366                   objc_interface_context = NULL_TREE;
2367                 }
2369         | IMPLEMENTATION identifier '(' identifier ')'
2370                 {
2371                   objc_implementation_context
2372                     = start_class (CATEGORY_IMPLEMENTATION_TYPE, $2, $4, NULL_TREE);
2373                   objc_ivar_chain
2374                     = continue_class (objc_implementation_context);
2375                 }
2376         ;
2378 protocoldef:
2379           PROTOCOL identifier protocolrefs
2380                 {
2381                   remember_protocol_qualifiers ();
2382                   objc_interface_context
2383                     = start_protocol(PROTOCOL_INTERFACE_TYPE, $2, $3);
2384                 }
2385           methodprotolist END
2386                 {
2387                   forget_protocol_qualifiers();
2388                   finish_protocol(objc_interface_context);
2389                   objc_interface_context = NULL_TREE;
2390                 }
2391         ;
2393 protocolrefs:
2394           /* empty */
2395                 {
2396                   $$ = NULL_TREE;
2397                 }
2398         | non_empty_protocolrefs
2399         ;
2401 non_empty_protocolrefs:
2402           ARITHCOMPARE identifier_list ARITHCOMPARE
2403                 {
2404                   if ($1 == LT_EXPR && $3 == GT_EXPR)
2405                     $$ = $2;
2406                   else
2407                     YYERROR1;
2408                 }
2409         ;
2411 ivar_decl_list:
2412           ivar_decl_list visibility_spec ivar_decls
2413         | ivar_decls
2414         ;
2416 visibility_spec:
2417           PRIVATE { objc_public_flag = 2; }
2418         | PROTECTED { objc_public_flag = 0; }
2419         | PUBLIC { objc_public_flag = 1; }
2420         ;
2422 ivar_decls:
2423           /* empty */
2424                 {
2425                   $$ = NULL_TREE;
2426                 }
2427         | ivar_decls ivar_decl ';'
2428         | ivar_decls ';'
2429                 {
2430                   if (pedantic)
2431                     pedwarn ("extra semicolon in struct or union specified");
2432                 }
2433         ;
2436 /* There is a shift-reduce conflict here, because `components' may
2437    start with a `typename'.  It happens that shifting (the default resolution)
2438    does the right thing, because it treats the `typename' as part of
2439    a `typed_typespecs'.
2441    It is possible that this same technique would allow the distinction
2442    between `notype_initdecls' and `initdecls' to be eliminated.
2443    But I am being cautious and not trying it.  */
2445 ivar_decl:
2446         typed_typespecs setspecs ivars
2447                 { $$ = $3;
2448                   current_declspecs = TREE_VALUE (declspec_stack);
2449                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2450                   declspec_stack = TREE_CHAIN (declspec_stack); }
2451         | nonempty_type_quals setspecs ivars
2452                 { $$ = $3;
2453                   current_declspecs = TREE_VALUE (declspec_stack);
2454                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2455                   declspec_stack = TREE_CHAIN (declspec_stack); }
2456         | error
2457                 { $$ = NULL_TREE; }
2458         ;
2460 ivars:
2461           /* empty */
2462                 { $$ = NULL_TREE; }
2463         | ivar_declarator
2464         | ivars ',' ivar_declarator
2465         ;
2467 ivar_declarator:
2468           declarator
2469                 {
2470                   $$ = add_instance_variable (objc_ivar_context,
2471                                               objc_public_flag,
2472                                               $1, current_declspecs,
2473                                               NULL_TREE);
2474                 }
2475         | declarator ':' expr_no_commas
2476                 {
2477                   $$ = add_instance_variable (objc_ivar_context,
2478                                               objc_public_flag,
2479                                               $1, current_declspecs, $3);
2480                 }
2481         | ':' expr_no_commas
2482                 {
2483                   $$ = add_instance_variable (objc_ivar_context,
2484                                               objc_public_flag,
2485                                               NULL_TREE,
2486                                               current_declspecs, $2);
2487                 }
2488         ;
2490 methoddef:
2491           '+'
2492                 {
2493                   remember_protocol_qualifiers ();
2494                   if (objc_implementation_context)
2495                     objc_inherit_code = CLASS_METHOD_DECL;
2496                   else
2497                     fatal ("method definition not in class context");
2498                 }
2499           methoddecl
2500                 {
2501                   forget_protocol_qualifiers ();
2502                   add_class_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                 }
2516         | '-'
2517                 {
2518                   remember_protocol_qualifiers ();
2519                   if (objc_implementation_context)
2520                     objc_inherit_code = INSTANCE_METHOD_DECL;
2521                   else
2522                     fatal ("method definition not in class context");
2523                 }
2524           methoddecl
2525                 {
2526                   forget_protocol_qualifiers ();
2527                   add_instance_method (objc_implementation_context, $3);
2528                   start_method_def ($3);
2529                   objc_method_context = $3;
2530                 }
2531           optarglist
2532                 {
2533                   continue_method_def ();
2534                 }
2535           compstmt_or_error
2536                 {
2537                   finish_method_def ();
2538                   objc_method_context = NULL_TREE;
2539                 }
2540         ;
2542 /* the reason for the strange actions in this rule
2543  is so that notype_initdecls when reached via datadef
2544  can find a valid list of type and sc specs in $0. */
2546 methodprotolist:
2547           /* empty  */
2548         | {$<ttype>$ = NULL_TREE; } methodprotolist2
2549         ;
2551 methodprotolist2:                /* eliminates a shift/reduce conflict */
2552            methodproto
2553         |  datadef
2554         | methodprotolist2 methodproto
2555         | methodprotolist2 {$<ttype>$ = NULL_TREE; } datadef
2556         ;
2558 semi_or_error:
2559           ';'
2560         | error
2561         ;
2563 methodproto:
2564           '+'
2565                 {
2566                   /* Remember protocol qualifiers in prototypes.  */
2567                   remember_protocol_qualifiers ();
2568                   objc_inherit_code = CLASS_METHOD_DECL;
2569                 }
2570           methoddecl
2571                 {
2572                   /* Forget protocol qualifiers here.  */
2573                   forget_protocol_qualifiers ();
2574                   add_class_method (objc_interface_context, $3);
2575                 }
2576           semi_or_error
2578         | '-'
2579                 {
2580                   /* Remember protocol qualifiers in prototypes.  */
2581                   remember_protocol_qualifiers ();
2582                   objc_inherit_code = INSTANCE_METHOD_DECL;
2583                 }
2584           methoddecl
2585                 {
2586                   /* Forget protocol qualifiers here.  */
2587                   forget_protocol_qualifiers ();
2588                   add_instance_method (objc_interface_context, $3);
2589                 }
2590           semi_or_error
2591         ;
2593 methoddecl:
2594           '(' typename ')' unaryselector
2595                 {
2596                   $$ = build_method_decl (objc_inherit_code, $2, $4, NULL_TREE);
2597                 }
2599         | unaryselector
2600                 {
2601                   $$ = build_method_decl (objc_inherit_code, NULL_TREE, $1, NULL_TREE);
2602                 }
2604         | '(' typename ')' keywordselector optparmlist
2605                 {
2606                   $$ = build_method_decl (objc_inherit_code, $2, $4, $5);
2607                 }
2609         | keywordselector optparmlist
2610                 {
2611                   $$ = build_method_decl (objc_inherit_code, NULL_TREE, $1, $2);
2612                 }
2613         ;
2615 /* "optarglist" assumes that start_method_def has already been called...
2616    if it is not, the "xdecls" will not be placed in the proper scope */
2618 optarglist:
2619           /* empty */
2620         | ';' myxdecls
2621         ;
2623 /* to get around the following situation: "int foo (int a) int b; {}" that
2624    is synthesized when parsing "- a:a b:b; id c; id d; { ... }" */
2626 myxdecls:
2627           /* empty */
2628         | mydecls
2629         ;
2631 mydecls:
2632         mydecl
2633         | errstmt
2634         | mydecls mydecl
2635         | mydecl errstmt
2636         ;
2638 mydecl:
2639         typed_declspecs setspecs myparms ';'
2640                 { current_declspecs = TREE_VALUE (declspec_stack);
2641                   prefix_attributes = TREE_PURPOSE (declspec_stack);
2642                   declspec_stack = TREE_CHAIN (declspec_stack); }
2643         | typed_declspecs ';'
2644                 { shadow_tag ($1); }
2645         | declmods ';'
2646                 { pedwarn ("empty declaration"); }
2647         ;
2649 myparms:
2650         myparm
2651                 { push_parm_decl ($1); }
2652         | myparms ',' myparm
2653                 { push_parm_decl ($3); }
2654         ;
2656 /* A single parameter declaration or parameter type name,
2657    as found in a parmlist. DOES NOT ALLOW AN INITIALIZER OR ASMSPEC */
2659 myparm:
2660           parm_declarator maybe_attribute
2661                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2662                                                          $1),
2663                                         build_tree_list (prefix_attributes,
2664                                                          $2)); }
2665         | notype_declarator maybe_attribute
2666                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2667                                                          $1),
2668                                         build_tree_list (prefix_attributes,
2669                                                          $2)); }
2670         | absdcl maybe_attribute
2671                 { $$ = build_tree_list (build_tree_list (current_declspecs,
2672                                                          $1),
2673                                         build_tree_list (prefix_attributes,
2674                                                          $2)); }
2675         ;
2677 optparmlist:
2678           /* empty */
2679                 {
2680                   $$ = NULL_TREE;
2681                 }
2682         | ',' ELLIPSIS
2683                 {
2684                   /* oh what a kludge! */
2685                   $$ = objc_ellipsis_node;
2686                 }
2687         | ','
2688                 {
2689                   pushlevel (0);
2690                 }
2691           parmlist_2
2692                 {
2693                   /* returns a tree list node generated by get_parm_info */
2694                   $$ = $3;
2695                   poplevel (0, 0, 0);
2696                 }
2697         ;
2699 unaryselector:
2700           selector
2701         ;
2703 keywordselector:
2704           keyworddecl
2706         | keywordselector keyworddecl
2707                 {
2708                   $$ = chainon ($1, $2);
2709                 }
2710         ;
2712 selector:
2713           IDENTIFIER
2714         | TYPENAME
2715         | OBJECTNAME
2716         | reservedwords
2717         ;
2719 reservedwords:
2720           ENUM | STRUCT | UNION | IF | ELSE | WHILE | DO | FOR
2721         | SWITCH | CASE | DEFAULT | BREAK | CONTINUE | RETURN
2722         | GOTO | ASM_KEYWORD | SIZEOF | TYPEOF | ALIGNOF
2723         | TYPESPEC | TYPE_QUAL
2724         ;
2726 keyworddecl:
2727           selector ':' '(' typename ')' identifier
2728                 {
2729                   $$ = build_keyword_decl ($1, $4, $6);
2730                 }
2732         | selector ':' identifier
2733                 {
2734                   $$ = build_keyword_decl ($1, NULL_TREE, $3);
2735                 }
2737         | ':' '(' typename ')' identifier
2738                 {
2739                   $$ = build_keyword_decl (NULL_TREE, $3, $5);
2740                 }
2742         | ':' identifier
2743                 {
2744                   $$ = build_keyword_decl (NULL_TREE, NULL_TREE, $2);
2745                 }
2746         ;
2748 messageargs:
2749           selector
2750         | keywordarglist
2751         ;
2753 keywordarglist:
2754           keywordarg
2755         | keywordarglist keywordarg
2756                 {
2757                   $$ = chainon ($1, $2);
2758                 }
2759         ;
2762 keywordexpr:
2763           nonnull_exprlist
2764                 {
2765                   if (TREE_CHAIN ($1) == NULL_TREE)
2766                     /* just return the expr., remove a level of indirection */
2767                     $$ = TREE_VALUE ($1);
2768                   else
2769                     /* we have a comma expr., we will collapse later */
2770                     $$ = $1;
2771                 }
2772         ;
2774 keywordarg:
2775           selector ':' keywordexpr
2776                 {
2777                   $$ = build_tree_list ($1, $3);
2778                 }
2779         | ':' keywordexpr
2780                 {
2781                   $$ = build_tree_list (NULL_TREE, $2);
2782                 }
2783         ;
2785 receiver:
2786           expr
2787         | CLASSNAME
2788                 {
2789                   $$ = get_class_reference ($1);
2790                 }
2791         ;
2793 objcmessageexpr:
2794           '['
2795                 { objc_receiver_context = 1; }
2796           receiver
2797                 { objc_receiver_context = 0; }
2798           messageargs ']'
2799                 {
2800                   $$ = build_tree_list ($3, $5);
2801                 }
2802         ;
2804 selectorarg:
2805           selector
2806         | keywordnamelist
2807         ;
2809 keywordnamelist:
2810           keywordname
2811         | keywordnamelist keywordname
2812                 {
2813                   $$ = chainon ($1, $2);
2814                 }
2815         ;
2817 keywordname:
2818           selector ':'
2819                 {
2820                   $$ = build_tree_list ($1, NULL_TREE);
2821                 }
2822         | ':'
2823                 {
2824                   $$ = build_tree_list (NULL_TREE, NULL_TREE);
2825                 }
2826         ;
2828 objcselectorexpr:
2829           SELECTOR '(' selectorarg ')'
2830                 {
2831                   $$ = $3;
2832                 }
2833         ;
2835 objcprotocolexpr:
2836           PROTOCOL '(' identifier ')'
2837                 {
2838                   $$ = $3;
2839                 }
2840         ;
2842 /* extension to support C-structures in the archiver */
2844 objcencodeexpr:
2845           ENCODE '(' typename ')'
2846                 {
2847                   $$ = groktypename ($3);
2848                 }
2849         ;
2851 end ifobjc
2854 /* yylex() is a thin wrapper around c_lex(), all it does is translate
2855    cpplib.h's token codes into yacc's token codes.  */
2857 static enum cpp_ttype last_token;
2859 /* The reserved keyword table.  */
2860 struct resword
2862   const char *word;
2863   ENUM_BITFIELD(rid) rid : 16;
2864   unsigned int disable   : 16;
2867 /* Disable mask.  Keywords are disabled if (reswords[i].disable & mask) is
2868    _true_.  */
2869 #define D_TRAD  0x01    /* not in traditional C */
2870 #define D_C89   0x02    /* not in C89 */
2871 #define D_EXT   0x04    /* GCC extension */
2872 #define D_EXT89 0x08    /* GCC extension incorporated in C99 */
2873 #define D_OBJC  0x10    /* Objective C only */
2874 #define D_YES   0x20    /* always starts disabled */
2876 static const struct resword reswords[] =
2878   { "_Bool",            RID_BOOL,       0 },
2879   { "_Complex",         RID_COMPLEX,    0 },
2880   { "__alignof",        RID_ALIGNOF,    0 },
2881   { "__alignof__",      RID_ALIGNOF,    0 },
2882   { "__asm",            RID_ASM,        0 },
2883   { "__asm__",          RID_ASM,        0 },
2884   { "__attribute",      RID_ATTRIBUTE,  0 },
2885   { "__attribute__",    RID_ATTRIBUTE,  0 },
2886   { "__bounded",        RID_BOUNDED,    0 },
2887   { "__bounded__",      RID_BOUNDED,    0 },
2888   { "__builtin_va_arg", RID_VA_ARG,     0 },
2889   { "__complex",        RID_COMPLEX,    0 },
2890   { "__complex__",      RID_COMPLEX,    0 },
2891   { "__const",          RID_CONST,      0 },
2892   { "__const__",        RID_CONST,      0 },
2893   { "__extension__",    RID_EXTENSION,  0 },
2894   { "__imag",           RID_IMAGPART,   0 },
2895   { "__imag__",         RID_IMAGPART,   0 },
2896   { "__inline",         RID_INLINE,     0 },
2897   { "__inline__",       RID_INLINE,     0 },
2898   { "__label__",        RID_LABEL,      0 },
2899   { "__ptrbase",        RID_PTRBASE,    0 },
2900   { "__ptrbase__",      RID_PTRBASE,    0 },
2901   { "__ptrextent",      RID_PTREXTENT,  0 },
2902   { "__ptrextent__",    RID_PTREXTENT,  0 },
2903   { "__ptrvalue",       RID_PTRVALUE,   0 },
2904   { "__ptrvalue__",     RID_PTRVALUE,   0 },
2905   { "__real",           RID_REALPART,   0 },
2906   { "__real__",         RID_REALPART,   0 },
2907   { "__restrict",       RID_RESTRICT,   0 },
2908   { "__restrict__",     RID_RESTRICT,   0 },
2909   { "__signed",         RID_SIGNED,     0 },
2910   { "__signed__",       RID_SIGNED,     0 },
2911   { "__typeof",         RID_TYPEOF,     0 },
2912   { "__typeof__",       RID_TYPEOF,     0 },
2913   { "__unbounded",      RID_UNBOUNDED,  0 },
2914   { "__unbounded__",    RID_UNBOUNDED,  0 },
2915   { "__volatile",       RID_VOLATILE,   0 },
2916   { "__volatile__",     RID_VOLATILE,   0 },
2917   { "asm",              RID_ASM,        D_EXT },
2918   { "auto",             RID_AUTO,       0 },
2919   { "break",            RID_BREAK,      0 },
2920   { "case",             RID_CASE,       0 },
2921   { "char",             RID_CHAR,       0 },
2922   { "const",            RID_CONST,      D_TRAD },
2923   { "continue",         RID_CONTINUE,   0 },
2924   { "default",          RID_DEFAULT,    0 },
2925   { "do",               RID_DO,         0 },
2926   { "double",           RID_DOUBLE,     0 },
2927   { "else",             RID_ELSE,       0 },
2928   { "enum",             RID_ENUM,       0 },
2929   { "extern",           RID_EXTERN,     0 },
2930   { "float",            RID_FLOAT,      0 },
2931   { "for",              RID_FOR,        0 },
2932   { "goto",             RID_GOTO,       0 },
2933   { "if",               RID_IF,         0 },
2934   { "inline",           RID_INLINE,     D_TRAD|D_EXT89 },
2935   { "int",              RID_INT,        0 },
2936   { "long",             RID_LONG,       0 },
2937   { "register",         RID_REGISTER,   0 },
2938   { "restrict",         RID_RESTRICT,   D_TRAD|D_C89 },
2939   { "return",           RID_RETURN,     0 },
2940   { "short",            RID_SHORT,      0 },
2941   { "signed",           RID_SIGNED,     D_TRAD },
2942   { "sizeof",           RID_SIZEOF,     0 },
2943   { "static",           RID_STATIC,     0 },
2944   { "struct",           RID_STRUCT,     0 },
2945   { "switch",           RID_SWITCH,     0 },
2946   { "typedef",          RID_TYPEDEF,    0 },
2947   { "typeof",           RID_TYPEOF,     D_TRAD|D_EXT },
2948   { "union",            RID_UNION,      0 },
2949   { "unsigned",         RID_UNSIGNED,   0 },
2950   { "void",             RID_VOID,       0 },
2951   { "volatile",         RID_VOLATILE,   D_TRAD },
2952   { "while",            RID_WHILE,      0 },
2953 ifobjc
2954   { "@class",           RID_AT_CLASS,           D_OBJC },
2955   { "@compatibility_alias", RID_AT_ALIAS,       D_OBJC },
2956   { "@defs",            RID_AT_DEFS,            D_OBJC },
2957   { "@encode",          RID_AT_ENCODE,          D_OBJC },
2958   { "@end",             RID_AT_END,             D_OBJC },
2959   { "@implementation",  RID_AT_IMPLEMENTATION,  D_OBJC },
2960   { "@interface",       RID_AT_INTERFACE,       D_OBJC },
2961   { "@private",         RID_AT_PRIVATE,         D_OBJC },
2962   { "@protected",       RID_AT_PROTECTED,       D_OBJC },
2963   { "@protocol",        RID_AT_PROTOCOL,        D_OBJC },
2964   { "@public",          RID_AT_PUBLIC,          D_OBJC },
2965   { "@selector",        RID_AT_SELECTOR,        D_OBJC },
2966   { "id",               RID_ID,                 D_OBJC },
2967   { "bycopy",           RID_BYCOPY,             D_OBJC|D_YES },
2968   { "byref",            RID_BYREF,              D_OBJC|D_YES },
2969   { "in",               RID_IN,                 D_OBJC|D_YES },
2970   { "inout",            RID_INOUT,              D_OBJC|D_YES },
2971   { "oneway",           RID_ONEWAY,             D_OBJC|D_YES },
2972   { "out",              RID_OUT,                D_OBJC|D_YES },
2973 end ifobjc
2975 #define N_reswords (sizeof reswords / sizeof (struct resword))
2977 /* Table mapping from RID_* constants to yacc token numbers.
2978    Unfortunately we have to have entries for all the keywords in all
2979    three languages.  */
2980 static const short rid_to_yy[RID_MAX] =
2982   /* RID_STATIC */      SCSPEC,
2983   /* RID_UNSIGNED */    TYPESPEC,
2984   /* RID_LONG */        TYPESPEC,
2985   /* RID_CONST */       TYPE_QUAL,
2986   /* RID_EXTERN */      SCSPEC,
2987   /* RID_REGISTER */    SCSPEC,
2988   /* RID_TYPEDEF */     SCSPEC,
2989   /* RID_SHORT */       TYPESPEC,
2990   /* RID_INLINE */      SCSPEC,
2991   /* RID_VOLATILE */    TYPE_QUAL,
2992   /* RID_SIGNED */      TYPESPEC,
2993   /* RID_AUTO */        SCSPEC,
2994   /* RID_RESTRICT */    TYPE_QUAL,
2996   /* C extensions */
2997   /* RID_BOUNDED */     TYPE_QUAL,
2998   /* RID_UNBOUNDED */   TYPE_QUAL,
2999   /* RID_COMPLEX */     TYPESPEC,
3001   /* C++ */
3002   /* RID_FRIEND */      0,
3003   /* RID_VIRTUAL */     0,
3004   /* RID_EXPLICIT */    0,
3005   /* RID_EXPORT */      0,
3006   /* RID_MUTABLE */     0,
3008   /* ObjC */
3009   /* RID_IN */          TYPE_QUAL,
3010   /* RID_OUT */         TYPE_QUAL,
3011   /* RID_INOUT */       TYPE_QUAL,
3012   /* RID_BYCOPY */      TYPE_QUAL,
3013   /* RID_BYREF */       TYPE_QUAL,
3014   /* RID_ONEWAY */      TYPE_QUAL,
3015   
3016   /* C */
3017   /* RID_INT */         TYPESPEC,
3018   /* RID_CHAR */        TYPESPEC,
3019   /* RID_FLOAT */       TYPESPEC,
3020   /* RID_DOUBLE */      TYPESPEC,
3021   /* RID_VOID */        TYPESPEC,
3022   /* RID_ENUM */        ENUM,
3023   /* RID_STRUCT */      STRUCT,
3024   /* RID_UNION */       UNION,
3025   /* RID_IF */          IF,
3026   /* RID_ELSE */        ELSE,
3027   /* RID_WHILE */       WHILE,
3028   /* RID_DO */          DO,
3029   /* RID_FOR */         FOR,
3030   /* RID_SWITCH */      SWITCH,
3031   /* RID_CASE */        CASE,
3032   /* RID_DEFAULT */     DEFAULT,
3033   /* RID_BREAK */       BREAK,
3034   /* RID_CONTINUE */    CONTINUE,
3035   /* RID_RETURN */      RETURN,
3036   /* RID_GOTO */        GOTO,
3037   /* RID_SIZEOF */      SIZEOF,
3039   /* C extensions */
3040   /* RID_ASM */         ASM_KEYWORD,
3041   /* RID_TYPEOF */      TYPEOF,
3042   /* RID_ALIGNOF */     ALIGNOF,
3043   /* RID_ATTRIBUTE */   ATTRIBUTE,
3044   /* RID_VA_ARG */      VA_ARG,
3045   /* RID_EXTENSION */   EXTENSION,
3046   /* RID_IMAGPART */    IMAGPART,
3047   /* RID_REALPART */    REALPART,
3048   /* RID_LABEL */       LABEL,
3049   /* RID_PTRBASE */     PTR_BASE,
3050   /* RID_PTREXTENT */   PTR_EXTENT,
3051   /* RID_PTRVALUE */    PTR_VALUE,
3053   /* C++ */
3054   /* RID_BOOL */        TYPESPEC,
3055   /* RID_WCHAR */       0,
3056   /* RID_CLASS */       0,
3057   /* RID_PUBLIC */      0,
3058   /* RID_PRIVATE */     0,
3059   /* RID_PROTECTED */   0,
3060   /* RID_TEMPLATE */    0,
3061   /* RID_NULL */        0,
3062   /* RID_CATCH */       0,
3063   /* RID_DELETE */      0,
3064   /* RID_FALSE */       0,
3065   /* RID_NAMESPACE */   0,
3066   /* RID_NEW */         0,
3067   /* RID_OPERATOR */    0,
3068   /* RID_THIS */        0,
3069   /* RID_THROW */       0,
3070   /* RID_TRUE */        0,
3071   /* RID_TRY */         0,
3072   /* RID_TYPENAME */    0,
3073   /* RID_TYPEID */      0,
3074   /* RID_USING */       0,
3076   /* casts */
3077   /* RID_CONSTCAST */   0,
3078   /* RID_DYNCAST */     0,
3079   /* RID_REINTCAST */   0,
3080   /* RID_STATCAST */    0,
3082   /* alternate spellings */
3083   /* RID_AND */         0,
3084   /* RID_AND_EQ */      0,
3085   /* RID_NOT */         0,
3086   /* RID_NOT_EQ */      0,
3087   /* RID_OR */          0,
3088   /* RID_OR_EQ */       0,
3089   /* RID_XOR */         0,
3090   /* RID_XOR_EQ */      0,
3091   /* RID_BITAND */      0,
3092   /* RID_BITOR */       0,
3093   /* RID_COMPL */       0,
3095   /* Objective C */
3096   /* RID_ID */                  OBJECTNAME,
3097   /* RID_AT_ENCODE */           ENCODE,
3098   /* RID_AT_END */              END,
3099   /* RID_AT_CLASS */            CLASS,
3100   /* RID_AT_ALIAS */            ALIAS,
3101   /* RID_AT_DEFS */             DEFS,
3102   /* RID_AT_PRIVATE */          PRIVATE,
3103   /* RID_AT_PROTECTED */        PROTECTED,
3104   /* RID_AT_PUBLIC */           PUBLIC,
3105   /* RID_AT_PROTOCOL */         PROTOCOL,
3106   /* RID_AT_SELECTOR */         SELECTOR,
3107   /* RID_AT_INTERFACE */        INTERFACE,
3108   /* RID_AT_IMPLEMENTATION */   IMPLEMENTATION
3111 static void
3112 init_reswords ()
3114   unsigned int i;
3115   tree id;
3116   int mask = ((doing_objc_thang ? 0 : D_OBJC)
3117               | (flag_isoc99 ? 0 : D_C89)
3118               | (flag_traditional ? D_TRAD : 0)
3119               | (flag_no_asm ? (flag_isoc99 ? D_EXT : D_EXT|D_EXT89) : 0));
3121   /* It is not necessary to register ridpointers as a GC root, because
3122      all the trees it points to are permanently interned in the
3123      get_identifier hash anyway.  */
3124   ridpointers = (tree *) xcalloc ((int) RID_MAX, sizeof (tree));
3125   for (i = 0; i < N_reswords; i++)
3126     {
3127       /* If a keyword is disabled, do not enter it into the table
3128          and so create a canonical spelling that isn't a keyword.  */
3129       if (reswords[i].disable & mask)
3130         continue;
3132       id = get_identifier (reswords[i].word);
3133       C_RID_CODE (id) = reswords[i].rid;
3134       ridpointers [(int) reswords[i].rid] = id;
3136       /* Objective C does tricky things with enabling and disabling 
3137          keywords.  So these we must not elide in the test above, but
3138          wait and not mark them reserved now.  */
3139       if (! (reswords[i].disable & D_YES))
3140         C_IS_RESERVED_WORD (id) = 1;
3141     }
3144 const char *
3145 init_parse (filename)
3146      const char *filename;
3148   add_c_tree_codes ();
3150   /* Make identifier nodes long enough for the language-specific slots.  */
3151   set_identifier_size (sizeof (struct lang_identifier));
3153   init_reswords ();
3154   init_pragma ();
3156   return init_c_lex (filename);
3159 void
3160 finish_parse ()
3162   cpp_finish (parse_in);
3163   errorcount += parse_in->errors;
3166 #define NAME(type) cpp_type2name (type)
3168 static void
3169 yyerror (msgid)
3170      const char *msgid;
3172   const char *string = _(msgid);
3174   if (last_token == CPP_EOF)
3175     error ("%s at end of input", string);
3176   else if (last_token == CPP_CHAR || last_token == CPP_WCHAR)
3177     {
3178       unsigned int val = TREE_INT_CST_LOW (yylval.ttype);
3179       const char *ell = (last_token == CPP_CHAR) ? "" : "L";
3180       if (val <= UCHAR_MAX && ISGRAPH (val))
3181         error ("%s before %s'%c'", string, ell, val);
3182       else
3183         error ("%s before %s'\\x%x'", string, ell, val);
3184     }
3185   else if (last_token == CPP_STRING
3186            || last_token == CPP_WSTRING
3187            || last_token == CPP_OSTRING)
3188     error ("%s before string constant", string);
3189   else if (last_token == CPP_NUMBER
3190            || last_token == CPP_INT
3191            || last_token == CPP_FLOAT)
3192     error ("%s before numeric constant", string);
3193   else if (last_token == CPP_NAME)
3194     error ("%s before \"%s\"", string, IDENTIFIER_POINTER (yylval.ttype));
3195   else
3196     error ("%s before '%s' token", string, NAME(last_token));
3199 static inline int
3200 _yylex ()
3202  retry:
3203   last_token = c_lex (&yylval.ttype);
3205   switch (last_token)
3206     {
3207     case CPP_EQ:                                        return '=';
3208     case CPP_NOT:                                       return '!';
3209     case CPP_GREATER:   yylval.code = GT_EXPR;          return ARITHCOMPARE;
3210     case CPP_LESS:      yylval.code = LT_EXPR;          return ARITHCOMPARE;
3211     case CPP_PLUS:      yylval.code = PLUS_EXPR;        return '+';
3212     case CPP_MINUS:     yylval.code = MINUS_EXPR;       return '-';
3213     case CPP_MULT:      yylval.code = MULT_EXPR;        return '*';
3214     case CPP_DIV:       yylval.code = TRUNC_DIV_EXPR;   return '/';
3215     case CPP_MOD:       yylval.code = TRUNC_MOD_EXPR;   return '%';
3216     case CPP_AND:       yylval.code = BIT_AND_EXPR;     return '&';
3217     case CPP_OR:        yylval.code = BIT_IOR_EXPR;     return '|';
3218     case CPP_XOR:       yylval.code = BIT_XOR_EXPR;     return '^';
3219     case CPP_RSHIFT:    yylval.code = RSHIFT_EXPR;      return RSHIFT;
3220     case CPP_LSHIFT:    yylval.code = LSHIFT_EXPR;      return LSHIFT;
3222     case CPP_COMPL:                                     return '~';
3223     case CPP_AND_AND:                                   return ANDAND;
3224     case CPP_OR_OR:                                     return OROR;
3225     case CPP_QUERY:                                     return '?';
3226     case CPP_COLON:                                     return ':';
3227     case CPP_COMMA:                                     return ',';
3228     case CPP_OPEN_PAREN:                                return '(';
3229     case CPP_CLOSE_PAREN:                               return ')';
3230     case CPP_EQ_EQ:     yylval.code = EQ_EXPR;          return EQCOMPARE;
3231     case CPP_NOT_EQ:    yylval.code = NE_EXPR;          return EQCOMPARE;
3232     case CPP_GREATER_EQ:yylval.code = GE_EXPR;          return ARITHCOMPARE;
3233     case CPP_LESS_EQ:   yylval.code = LE_EXPR;          return ARITHCOMPARE;
3235     case CPP_PLUS_EQ:   yylval.code = PLUS_EXPR;        return ASSIGN;
3236     case CPP_MINUS_EQ:  yylval.code = MINUS_EXPR;       return ASSIGN;
3237     case CPP_MULT_EQ:   yylval.code = MULT_EXPR;        return ASSIGN;
3238     case CPP_DIV_EQ:    yylval.code = TRUNC_DIV_EXPR;   return ASSIGN;
3239     case CPP_MOD_EQ:    yylval.code = TRUNC_MOD_EXPR;   return ASSIGN;
3240     case CPP_AND_EQ:    yylval.code = BIT_AND_EXPR;     return ASSIGN;
3241     case CPP_OR_EQ:     yylval.code = BIT_IOR_EXPR;     return ASSIGN;
3242     case CPP_XOR_EQ:    yylval.code = BIT_XOR_EXPR;     return ASSIGN;
3243     case CPP_RSHIFT_EQ: yylval.code = RSHIFT_EXPR;      return ASSIGN;
3244     case CPP_LSHIFT_EQ: yylval.code = LSHIFT_EXPR;      return ASSIGN;
3246     case CPP_OPEN_SQUARE:                               return '[';
3247     case CPP_CLOSE_SQUARE:                              return ']';
3248     case CPP_OPEN_BRACE:                                return '{';
3249     case CPP_CLOSE_BRACE:                               return '}';
3250     case CPP_SEMICOLON:                                 return ';';
3251     case CPP_ELLIPSIS:                                  return ELLIPSIS;
3253     case CPP_PLUS_PLUS:                                 return PLUSPLUS;
3254     case CPP_MINUS_MINUS:                               return MINUSMINUS;
3255     case CPP_DEREF:                                     return POINTSAT;
3256     case CPP_DOT:                                       return '.';
3258     case CPP_EOF:
3259       cpp_pop_buffer (parse_in);
3260       if (! CPP_BUFFER (parse_in))
3261         return 0;
3262       goto retry;
3264     case CPP_NAME:
3265       if (C_IS_RESERVED_WORD (yylval.ttype))
3266         {
3267           enum rid rid_code = C_RID_CODE (yylval.ttype);
3268           /* Return the canonical spelling for this keyword.  */
3269           yylval.ttype = ridpointers[(int) rid_code];
3270           return rid_to_yy[(int) rid_code];
3271         }
3273       if (IDENTIFIER_POINTER (yylval.ttype)[0] == '@')
3274         {
3275           error ("invalid identifier `%s'", IDENTIFIER_POINTER (yylval.ttype));
3276           return IDENTIFIER;
3277         }
3279       {
3280         tree decl;
3282         decl = lookup_name (yylval.ttype);
3284         if (decl)
3285           {
3286             if (TREE_CODE (decl) == TYPE_DECL)
3287               return TYPENAME;
3288             /* A user-invisible read-only initialized variable
3289                should be replaced by its value.
3290                We handle only strings since that's the only case used in C.  */
3291             else if (TREE_CODE (decl) == VAR_DECL
3292                      && DECL_IGNORED_P (decl)
3293                      && TREE_READONLY (decl)
3294                      && DECL_INITIAL (decl) != 0
3295                      && TREE_CODE (DECL_INITIAL (decl)) == STRING_CST)
3296               {
3297                 tree stringval = DECL_INITIAL (decl);
3299                 /* Copy the string value so that we won't clobber anything
3300                    if we put something in the TREE_CHAIN of this one.  */
3301                 yylval.ttype = build_string (TREE_STRING_LENGTH (stringval),
3302                                              TREE_STRING_POINTER (stringval));
3303                 return STRING;
3304               }
3305           }
3306         else if (doing_objc_thang)
3307           {
3308             tree objc_interface_decl = is_class_name (yylval.ttype);
3310             if (objc_interface_decl)
3311               {
3312                 yylval.ttype = objc_interface_decl;
3313                 return CLASSNAME;
3314               }
3315           }
3317         return IDENTIFIER;
3318       }
3320     case CPP_INT:
3321     case CPP_FLOAT:
3322     case CPP_NUMBER:
3323     case CPP_CHAR:
3324     case CPP_WCHAR:
3325       return CONSTANT;
3327     case CPP_STRING:
3328     case CPP_WSTRING:
3329       return STRING;
3330       
3331     case CPP_OSTRING:
3332       return OBJC_STRING;
3334       /* These tokens are C++ specific (and will not be generated
3335          in C mode, but let's be cautious).  */
3336     case CPP_SCOPE:
3337     case CPP_DEREF_STAR:
3338     case CPP_DOT_STAR:
3339     case CPP_MIN_EQ:
3340     case CPP_MAX_EQ:
3341     case CPP_MIN:
3342     case CPP_MAX:
3343       /* These tokens should not survive translation phase 4.  */
3344     case CPP_HASH:
3345     case CPP_PASTE:
3346       error ("syntax error before '%s' token", NAME(last_token));
3347       goto retry;
3349     default:
3350       abort ();
3351     }
3353   /* NOTREACHED */
3356 static int
3357 yylex()
3359   int r;
3360   timevar_push (TV_LEX);
3361   r = _yylex();
3362   timevar_pop (TV_LEX);
3363   return r;
3366 /* Sets the value of the 'yydebug' variable to VALUE.
3367    This is a function so we don't have to have YYDEBUG defined
3368    in order to build the compiler.  */
3370 void
3371 set_yydebug (value)
3372      int value;
3374 #if YYDEBUG != 0
3375   yydebug = value;
3376 #else
3377   warning ("YYDEBUG not defined.");
3378 #endif
3381 /* Function used when yydebug is set, to print a token in more detail.  */
3383 static void
3384 yyprint (file, yychar, yyl)
3385      FILE *file;
3386      int yychar;
3387      YYSTYPE yyl;
3389   tree t = yyl.ttype;
3391   fprintf (file, " [%s]", NAME(last_token));
3392   
3393   switch (yychar)
3394     {
3395     case IDENTIFIER:
3396     case TYPENAME:
3397     case OBJECTNAME:
3398     case TYPESPEC:
3399     case TYPE_QUAL:
3400     case SCSPEC:
3401       if (IDENTIFIER_POINTER (t))
3402         fprintf (file, " `%s'", IDENTIFIER_POINTER (t));
3403       break;
3405     case CONSTANT:
3406       fprintf (file, " %s", GET_MODE_NAME (TYPE_MODE (TREE_TYPE (t))));
3407       if (TREE_CODE (t) == INTEGER_CST)
3408         fprintf (file,
3409 #if HOST_BITS_PER_WIDE_INT == 64
3410 #if HOST_BITS_PER_WIDE_INT == HOST_BITS_PER_INT
3411                  " 0x%x%016x",
3412 #else
3413 #if HOST_BITS_PER_WIDE_INT == HOST_BITS_PER_LONG
3414                  " 0x%lx%016lx",
3415 #else
3416                  " 0x%llx%016llx",
3417 #endif
3418 #endif
3419 #else
3420 #if HOST_BITS_PER_WIDE_INT != HOST_BITS_PER_INT
3421                  " 0x%lx%08lx",
3422 #else
3423                  " 0x%x%08x",
3424 #endif
3425 #endif
3426                  TREE_INT_CST_HIGH (t), TREE_INT_CST_LOW (t));
3427       break;
3428     }
3431 /* This is not the ideal place to put these, but we have to get them out
3432    of c-lex.c because cp/lex.c has its own versions.  */
3434 /* Return something to represent absolute declarators containing a *.
3435    TARGET is the absolute declarator that the * contains.
3436    TYPE_QUALS is a list of modifiers such as const or volatile
3437    to apply to the pointer type, represented as identifiers.
3439    We return an INDIRECT_REF whose "contents" are TARGET
3440    and whose type is the modifier list.  */
3442 tree
3443 make_pointer_declarator (type_quals, target)
3444      tree type_quals, target;
3446   return build1 (INDIRECT_REF, type_quals, target);