OSDN Git Service

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