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