OSDN Git Service

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