OSDN Git Service

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