OSDN Git Service

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