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