OSDN Git Service

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