OSDN Git Service

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