OSDN Git Service

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