OSDN Git Service

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