OSDN Git Service

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