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