OSDN Git Service

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