OSDN Git Service

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