OSDN Git Service

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