OSDN Git Service

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