OSDN Git Service

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