OSDN Git Service

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