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