OSDN Git Service

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