OSDN Git Service

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