OSDN Git Service

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