OSDN Git Service

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