OSDN Git Service

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