OSDN Git Service

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