OSDN Git Service

* extend.texi (C++ Signatures): Remove node.
[pf3gnuchains/gcc-fork.git] / gcc / cp / parse.y
1 /* YACC parser for C++ syntax.
2    Copyright (C) 1988, 89, 93-98, 1999 Free Software Foundation, Inc.
3    Hacked by Michael Tiemann (tiemann@cygnus.com)
4
5 This file is part of GNU CC.
6
7 GNU CC is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 2, or (at your option)
10 any later version.
11
12 GNU CC is distributed in the hope that it will be useful,
13 but WITHOUT ANY WARRANTY; without even the implied warranty of
14 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15 GNU General Public License for more details.
16
17 You should have received a copy of the GNU General Public License
18 along with GNU CC; see the file COPYING.  If not, write to
19 the Free Software Foundation, 59 Temple Place - Suite 330,
20 Boston, MA 02111-1307, USA.  */
21
22
23 /* This grammar is based on the GNU CC grammar.  */
24
25 /* Note: Bison automatically applies a default action of "$$ = $1" for
26    all derivations; this is applied before the explicit action, if one
27    is given.  Keep this in mind when reading the actions.  */
28
29 %{
30 /* Cause the `yydebug' variable to be defined.  */
31 #define YYDEBUG 1
32
33 #include "config.h"
34
35 #include "system.h"
36
37 #include "tree.h"
38 #include "input.h"
39 #include "flags.h"
40 #include "lex.h"
41 #include "cp-tree.h"
42 #include "output.h"
43 #include "except.h"
44 #include "toplev.h"
45
46 /* Since parsers are distinct for each language, put the language string
47    definition here.  (fnf) */
48 char *language_string = "GNU C++";
49
50 extern struct obstack permanent_obstack;
51
52 extern int end_of_file;
53
54 /* Like YYERROR but do call yyerror.  */
55 #define YYERROR1 { yyerror ("syntax error"); YYERROR; }
56
57 #define OP0(NODE) (TREE_OPERAND (NODE, 0))
58 #define OP1(NODE) (TREE_OPERAND (NODE, 1))
59
60 /* Contains the statement keyword (if/while/do) to include in an
61    error message if the user supplies an empty conditional expression.  */
62 static const char *cond_stmt_keyword;
63
64 static tree empty_parms PROTO((void));
65 static int parse_decl PROTO((tree, tree, tree, int, tree *));
66
67 /* Nonzero if we have an `extern "C"' acting as an extern specifier.  */
68 int have_extern_spec;
69 int used_extern_spec;
70
71 /* Cons up an empty parameter list.  */
72 #ifdef __GNUC__
73 __inline
74 #endif
75 static tree
76 empty_parms ()
77 {
78   tree parms;
79
80   if (strict_prototype
81       || current_class_type != NULL)
82     parms = void_list_node;
83   else
84     parms = NULL_TREE;
85   return parms;
86 }
87
88 %}
89
90 %start program
91
92 %union {long itype; tree ttype; char *strtype; enum tree_code code; flagged_type_tree ftype; }
93
94 /* All identifiers that are not reserved words
95    and are not declared typedefs in the current block */
96 %token IDENTIFIER
97
98 /* All identifiers that are declared typedefs in the current block.
99    In some contexts, they are treated just like IDENTIFIER,
100    but they can also serve as typespecs in declarations.  */
101 %token TYPENAME
102 %token SELFNAME
103
104 /* A template function.  */
105 %token PFUNCNAME
106
107 /* Reserved words that specify storage class.
108    yylval contains an IDENTIFIER_NODE which indicates which one.  */
109 %token SCSPEC
110
111 /* Reserved words that specify type.
112    yylval contains an IDENTIFIER_NODE which indicates which one.  */
113 %token TYPESPEC
114
115 /* Reserved words that qualify type: "const" or "volatile".
116    yylval contains an IDENTIFIER_NODE which indicates which one.  */
117 %token CV_QUALIFIER
118
119 /* Character or numeric constants.
120    yylval is the node for the constant.  */
121 %token CONSTANT
122
123 /* String constants in raw form.
124    yylval is a STRING_CST node.  */
125 %token STRING
126
127 /* "...", used for functions with variable arglists.  */
128 %token ELLIPSIS
129
130 /* the reserved words */
131 /* SCO include files test "ASM", so use something else.  */
132 %token SIZEOF ENUM /* STRUCT UNION */ IF ELSE WHILE DO FOR SWITCH CASE DEFAULT
133 %token BREAK CONTINUE RETURN_KEYWORD GOTO ASM_KEYWORD TYPEOF ALIGNOF
134 %token SIGOF
135 %token ATTRIBUTE EXTENSION LABEL
136 %token REALPART IMAGPART VA_ARG
137
138 /* the reserved words... C++ extensions */
139 %token <ttype> AGGR
140 %token <ttype> VISSPEC
141 %token DELETE NEW THIS OPERATOR CXX_TRUE CXX_FALSE
142 %token NAMESPACE TYPENAME_KEYWORD USING
143 %token LEFT_RIGHT TEMPLATE
144 %token TYPEID DYNAMIC_CAST STATIC_CAST REINTERPRET_CAST CONST_CAST
145 %token <itype> SCOPE
146
147 /* Define the operator tokens and their precedences.
148    The value is an integer because, if used, it is the tree code
149    to use in the expression made from the operator.  */
150
151 %left EMPTY                     /* used to resolve s/r with epsilon */
152
153 %left error
154
155 /* Add precedence rules to solve dangling else s/r conflict */
156 %nonassoc IF
157 %nonassoc ELSE
158
159 %left IDENTIFIER PFUNCNAME TYPENAME SELFNAME PTYPENAME SCSPEC TYPESPEC CV_QUALIFIER ENUM AGGR ELLIPSIS TYPEOF SIGOF OPERATOR NSNAME TYPENAME_KEYWORD
160
161 %left '{' ',' ';'
162
163 %nonassoc THROW
164 %right <code> ':'
165 %right <code> ASSIGN '='
166 %right <code> '?'
167 %left <code> OROR
168 %left <code> ANDAND
169 %left <code> '|'
170 %left <code> '^'
171 %left <code> '&'
172 %left <code> MIN_MAX
173 %left <code> EQCOMPARE
174 %left <code> ARITHCOMPARE '<' '>'
175 %left <code> LSHIFT RSHIFT
176 %left <code> '+' '-'
177 %left <code> '*' '/' '%'
178 %left <code> POINTSAT_STAR DOT_STAR
179 %right <code> UNARY PLUSPLUS MINUSMINUS '~'
180 %left HYPERUNARY
181 %left <ttype> LEFT_RIGHT
182 %left <code> POINTSAT '.' '(' '['
183
184 %right SCOPE                    /* C++ extension */
185 %nonassoc NEW DELETE TRY CATCH
186
187 %type <code> unop
188
189 %type <ttype> identifier IDENTIFIER TYPENAME CONSTANT expr nonnull_exprlist
190 %type <ttype> PFUNCNAME maybe_identifier
191 %type <ttype> paren_expr_or_null nontrivial_exprlist SELFNAME
192 %type <ttype> expr_no_commas cast_expr unary_expr primary string STRING
193 %type <ttype> reserved_declspecs boolean.literal
194 %type <ttype> reserved_typespecquals
195 %type <ttype> declmods 
196 %type <ttype> SCSPEC TYPESPEC CV_QUALIFIER maybe_cv_qualifier
197 %type <itype> initdecls notype_initdecls initdcl        /* C++ modification */
198 %type <ttype> init initlist maybeasm maybe_init defarg defarg1
199 %type <ttype> asm_operands nonnull_asm_operands asm_operand asm_clobbers
200 %type <ttype> maybe_attribute attributes attribute attribute_list attrib
201 %type <ttype> any_word
202
203 %type <ttype> compstmt implicitly_scoped_stmt
204
205 %type <ttype> declarator notype_declarator after_type_declarator
206 %type <ttype> notype_declarator_intern absdcl_intern
207 %type <ttype> after_type_declarator_intern
208 %type <ttype> direct_notype_declarator direct_after_type_declarator
209 %type <itype> components notype_components
210 %type <ttype> component_decl component_decl_1 
211 %type <ttype> component_declarator component_declarator0
212 %type <ttype> notype_component_declarator notype_component_declarator0
213 %type <ttype> after_type_component_declarator after_type_component_declarator0
214 %type <ttype> enumlist_opt enumlist enumerator
215 %type <ttype> absdcl cv_qualifiers
216 %type <ttype> direct_abstract_declarator conversion_declarator
217 %type <ttype> new_declarator direct_new_declarator
218 %type <ttype> xexpr parmlist parms bad_parm 
219 %type <ttype> identifiers_or_typenames
220 %type <ttype> fcast_or_absdcl regcast_or_absdcl
221 %type <ttype> expr_or_declarator expr_or_declarator_intern
222 %type <ttype> complex_notype_declarator
223 %type <ttype> notype_unqualified_id unqualified_id qualified_id
224 %type <ttype> template_id do_id object_template_id notype_template_declarator
225 %type <ttype> overqualified_id notype_qualified_id any_id
226 %type <ttype> complex_direct_notype_declarator functional_cast
227 %type <ttype> complex_parmlist parms_comma 
228 %type <ttype> namespace_qualifier namespace_using_decl
229
230 %type <ftype> type_id new_type_id typed_typespecs typespec typed_declspecs
231 %type <ftype> typed_declspecs1 type_specifier_seq nonempty_cv_qualifiers
232 %type <ftype> structsp typespecqual_reserved parm named_parm full_parm
233
234 /* C++ extensions */
235 %token <ttype> PTYPENAME
236 %token <ttype> PRE_PARSED_FUNCTION_DECL EXTERN_LANG_STRING ALL
237 %token <ttype> PRE_PARSED_CLASS_DECL DEFARG DEFARG_MARKER
238 %type <ttype> component_constructor_declarator
239 %type <ttype> fn.def2 return_id fn.defpen constructor_declarator
240 %type <itype> ctor_initializer_opt function_try_block
241 %type <ttype> named_class_head_sans_basetype
242 %type <ftype> class_head named_class_head 
243 %type <ftype> named_complex_class_head_sans_basetype 
244 %type <ttype> unnamed_class_head
245 %type <ttype> base_class_list
246 %type <ttype> base_class_access_list
247 %type <ttype> base_class maybe_base_class_list base_class.1
248 %type <ttype> exception_specification_opt ansi_raise_identifier ansi_raise_identifiers
249 %type <ttype> operator_name
250 %type <ttype> object aggr
251 %type <itype> new delete .begin_new_placement
252 /* %type <ttype> primary_no_id */
253 %type <ttype> nonmomentary_expr maybe_parmlist
254 %type <itype> initdcl0 notype_initdcl0 member_init_list initdcl0_innards
255 %type <ttype> template_header template_parm_list template_parm
256 %type <ttype> template_type_parm template_template_parm
257 %type <code>  template_close_bracket
258 %type <ttype> apparent_template_type
259 %type <ttype> template_type template_arg_list template_arg_list_opt
260 %type <ttype> template_arg
261 %type <ttype> condition xcond paren_cond_or_null
262 %type <ttype> type_name nested_name_specifier nested_type ptr_to_mem
263 %type <ttype> complete_type_name notype_identifier nonnested_type
264 %type <ttype> complex_type_name nested_name_specifier_1
265 %type <ttype> new_initializer new_placement
266 %type <ttype> using_decl
267 %type <ttype> typename_sub typename_sub0 typename_sub1 typename_sub2
268 %type <ttype> explicit_template_type
269 /* in order to recognize aggr tags as defining and thus shadowing.  */
270 %token TYPENAME_DEFN IDENTIFIER_DEFN PTYPENAME_DEFN
271 %type <ttype> named_class_head_sans_basetype_defn
272 %type <ttype> identifier_defn IDENTIFIER_DEFN TYPENAME_DEFN PTYPENAME_DEFN
273
274 %type <ttype> self_template_type .finish_template_type
275
276 %token NSNAME
277 %type <ttype> NSNAME
278
279 /* Used in lex.c for parsing pragmas.  */
280 %token END_OF_LINE
281
282 /* lex.c and pt.c depend on this being the last token.  Define
283    any new tokens before this one!  */
284 %token END_OF_SAVED_INPUT
285 \f
286 %{
287 /* List of types and structure classes of the current declaration.  */
288 static tree current_declspecs;
289
290 /* List of prefix attributes in effect.
291    Prefix attributes are parsed by the reserved_declspecs and declmods
292    rules.  They create a list that contains *both* declspecs and attrs.  */
293 /* ??? It is not clear yet that all cases where an attribute can now appear in
294    a declspec list have been updated.  */
295 static tree prefix_attributes;
296
297 /* When defining an aggregate, this is the kind of the most recent one
298    being defined.  (For example, this might be class_type_node.)  */
299 static tree current_aggr;
300
301 /* When defining an enumeration, this is the type of the enumeration.  */
302 static tree current_enum_type;
303
304 /* Tell yyparse how to print a token's value, if yydebug is set.  */
305
306 #define YYPRINT(FILE,YYCHAR,YYLVAL) yyprint(FILE,YYCHAR,YYLVAL)
307 extern void yyprint                     PROTO((FILE *, int, YYSTYPE));
308 extern tree combine_strings             PROTO((tree));
309
310 static int
311 parse_decl(declarator, specs_attrs, attributes, initialized, decl)
312   tree declarator;
313   tree specs_attrs;
314   tree attributes;
315   int initialized;
316   tree* decl;
317 {
318   int  sm;
319
320   split_specs_attrs (specs_attrs, &current_declspecs, &prefix_attributes);
321   if (current_declspecs
322       && TREE_CODE (current_declspecs) != TREE_LIST)
323     current_declspecs = build_decl_list (NULL_TREE, current_declspecs);
324   if (have_extern_spec && !used_extern_spec)
325     {
326       current_declspecs = decl_tree_cons (NULL_TREE, 
327                                           get_identifier ("extern"), 
328                                           current_declspecs);
329       used_extern_spec = 1;
330     }
331   sm = suspend_momentary ();
332   *decl = start_decl (declarator, current_declspecs, initialized,
333                       attributes, prefix_attributes);
334   return sm;
335 }
336 %}
337 \f
338 %%
339 program:
340           /* empty */
341         | extdefs
342                { finish_translation_unit (); }
343         ;
344
345 /* the reason for the strange actions in this rule
346  is so that notype_initdecls when reached via datadef
347  can find a valid list of type and sc specs in $0.  */
348
349 extdefs:
350                 { $<ttype>$ = NULL_TREE; }
351           lang_extdef
352                 { $<ttype>$ = NULL_TREE; }
353         | extdefs lang_extdef
354                 { $<ttype>$ = NULL_TREE; }
355         ;
356
357 extdefs_opt:
358           extdefs
359         | /* empty */
360         ;
361
362 .hush_warning:
363                 { have_extern_spec = 1;
364                   used_extern_spec = 0;
365                   $<ttype>$ = NULL_TREE; }
366         ;
367 .warning_ok:
368                 { have_extern_spec = 0; }
369         ;
370
371 extension:
372         EXTENSION
373                 { $<itype>$ = pedantic;
374                   pedantic = 0; }
375         ;
376
377 asm_keyword:
378           ASM_KEYWORD
379         ;
380
381 lang_extdef:
382                 { if (pending_lang_change) do_pending_lang_change(); }
383           extdef
384                 { if (! toplevel_bindings_p () && ! pseudo_global_level_p())
385                   pop_everything (); }
386         ;
387
388 extdef:
389           fndef eat_saved_input
390                 { if (pending_inlines) do_pending_inlines (); }
391         | datadef
392                 { if (pending_inlines) do_pending_inlines (); }
393         | template_def
394                 { if (pending_inlines) do_pending_inlines (); }
395         | asm_keyword '(' string ')' ';'
396                 { if (TREE_CHAIN ($3)) $3 = combine_strings ($3);
397                   assemble_asm ($3); }
398         | extern_lang_string '{' extdefs_opt '}'
399                 { pop_lang_context (); }
400         | extern_lang_string .hush_warning fndef .warning_ok eat_saved_input
401                 { if (pending_inlines) do_pending_inlines ();
402                   pop_lang_context (); }
403         | extern_lang_string .hush_warning datadef .warning_ok
404                 { if (pending_inlines) do_pending_inlines ();
405                   pop_lang_context (); }
406         | NAMESPACE identifier '{'
407                 { push_namespace ($2); }
408           extdefs_opt '}'
409                 { pop_namespace (); }
410         | NAMESPACE '{'
411                 { push_namespace (NULL_TREE); }
412           extdefs_opt '}'
413                 { pop_namespace (); }
414         | namespace_alias
415         | using_decl ';'
416                 { do_toplevel_using_decl ($1); }
417         | using_directive
418         | extension extdef
419                 { pedantic = $<itype>1; }
420         ;
421
422 namespace_alias:
423           NAMESPACE identifier '=' 
424                 { begin_only_namespace_names (); }
425           any_id ';'
426                 {
427                   end_only_namespace_names ();
428                   if (lastiddecl)
429                     $5 = lastiddecl;
430                   do_namespace_alias ($2, $5);
431                 }
432         ;
433
434 using_decl:
435           USING qualified_id
436                 { $$ = $2; }
437         | USING global_scope qualified_id
438                 { $$ = $3; }
439         | USING global_scope unqualified_id
440                 { $$ = $3; }
441         ;
442
443 namespace_using_decl:
444           USING namespace_qualifier identifier
445                 { $$ = build_parse_node (SCOPE_REF, $2, $3); }
446         | USING global_scope identifier
447                 { $$ = build_parse_node (SCOPE_REF, global_namespace, $3); }
448         | USING global_scope namespace_qualifier identifier
449                 { $$ = build_parse_node (SCOPE_REF, $3, $4); }
450         ;
451
452 using_directive:
453           USING NAMESPACE
454                 { begin_only_namespace_names (); }
455           any_id ';'
456                 {
457                   end_only_namespace_names ();
458                   /* If no declaration was found, the using-directive is
459                      invalid. Since that was not reported, we need the
460                      identifier for the error message. */
461                   if (TREE_CODE ($4) == IDENTIFIER_NODE && lastiddecl)
462                     $4 = lastiddecl;
463                   do_using_directive ($4);
464                 }
465         ;
466
467 namespace_qualifier:
468           NSNAME SCOPE
469                 {
470                   if (TREE_CODE ($$) == IDENTIFIER_NODE)
471                     $$ = lastiddecl;
472                   got_scope = $$;
473                 }
474         | namespace_qualifier NSNAME SCOPE
475                 {
476                   $$ = $2;
477                   if (TREE_CODE ($$) == IDENTIFIER_NODE)
478                     $$ = lastiddecl;
479                   got_scope = $$;
480                 }
481
482 any_id:
483           unqualified_id
484         | qualified_id
485         | global_scope qualified_id
486                 { $$ = $2; }
487         | global_scope unqualified_id
488                 { $$ = $2; }
489         ;
490
491 extern_lang_string:
492         EXTERN_LANG_STRING
493                 { push_lang_context ($1); }
494         | extern_lang_string EXTERN_LANG_STRING
495                 { if (current_lang_name != $2)
496                     cp_error ("use of linkage spec `%D' is different from previous spec `%D'", $2, current_lang_name);
497                   pop_lang_context (); push_lang_context ($2); }
498         ;
499
500 template_header:
501           TEMPLATE '<'
502                 { begin_template_parm_list (); }
503           template_parm_list '>'
504                 { $$ = end_template_parm_list ($4); }
505         | TEMPLATE '<' '>'
506                 { begin_specialization(); 
507                   $$ = NULL_TREE; }
508         ;
509
510 template_parm_list:
511           template_parm
512                 { $$ = process_template_parm (NULL_TREE, $1); }
513         | template_parm_list ',' template_parm
514                 { $$ = process_template_parm ($1, $3); }
515         ;
516
517 maybe_identifier:
518           identifier
519                 { $$ = $1; }
520         |       /* empty */
521                 { $$ = NULL_TREE; }
522
523 template_type_parm:
524           aggr maybe_identifier
525                 { $$ = finish_template_type_parm ($1, $2); }
526         | TYPENAME_KEYWORD maybe_identifier
527                 { $$ = finish_template_type_parm (class_type_node, $2); }
528         ;
529
530 template_template_parm:
531           template_header aggr maybe_identifier
532                 { $$ = finish_template_template_parm ($2, $3); }
533         ;
534
535 template_parm:
536         /* The following rules introduce a new reduce/reduce
537            conflict on the ',' and '>' input tokens: they are valid
538            prefixes for a `structsp', which means they could match a
539            nameless parameter.  See 14.6, paragraph 3.
540            By putting them before the `parm' rule, we get
541            their match before considering them nameless parameter
542            declarations.  */
543           template_type_parm
544                 { $$ = build_tree_list (NULL_TREE, $1); }
545         | template_type_parm '=' type_id
546                 { $$ = build_tree_list (groktypename ($3.t), $1); }
547         | parm
548                 { $$ = build_tree_list (NULL_TREE, $1.t); }
549         | parm '=' expr_no_commas  %prec ARITHCOMPARE
550                 { $$ = build_tree_list ($3, $1.t); }
551         | template_template_parm
552                 { $$ = build_tree_list (NULL_TREE, $1); }
553         | template_template_parm '=' template_arg
554                 {
555                   if (TREE_CODE ($3) != TEMPLATE_DECL
556                       && TREE_CODE ($3) != TEMPLATE_TEMPLATE_PARM
557                       && TREE_CODE ($3) != TYPE_DECL)
558                     {
559                       error ("invalid default template argument");
560                       $3 = error_mark_node;
561                     }
562                   $$ = build_tree_list ($3, $1);
563                 }
564         ;
565
566 template_def:
567           template_header template_extdef
568                 { finish_template_decl ($1); }
569         | template_header error  %prec EMPTY
570                 { finish_template_decl ($1); }
571         ;
572
573 template_extdef:
574           fndef eat_saved_input
575                 { if (pending_inlines) do_pending_inlines (); }
576         | template_datadef
577                 { if (pending_inlines) do_pending_inlines (); }
578         | template_def
579                 { if (pending_inlines) do_pending_inlines (); }
580         | extern_lang_string .hush_warning fndef .warning_ok eat_saved_input
581                 { if (pending_inlines) do_pending_inlines ();
582                   pop_lang_context (); }
583         | extern_lang_string .hush_warning template_datadef .warning_ok
584                 { if (pending_inlines) do_pending_inlines ();
585                   pop_lang_context (); }
586         | extension template_extdef
587                 { pedantic = $<itype>1; }
588         ;
589
590 template_datadef:
591           nomods_initdecls ';'
592         | declmods notype_initdecls ';'
593                 {}
594         | typed_declspecs initdecls ';'
595                 { note_list_got_semicolon ($1.t); }
596         | structsp ';'
597                 { maybe_process_partial_specialization ($1.t);
598                   note_got_semicolon ($1.t); }
599         ;
600
601 datadef:
602           nomods_initdecls ';'
603         | declmods notype_initdecls ';'
604                 {}
605         | typed_declspecs initdecls ';'
606                 { note_list_got_semicolon ($1.t); }
607         | declmods ';'
608                 { pedwarn ("empty declaration"); }
609         | explicit_instantiation ';'
610         | typed_declspecs ';'
611                 {
612                   tree t, attrs;
613                   split_specs_attrs ($1.t, &t, &attrs);
614                   shadow_tag (t);
615                   note_list_got_semicolon ($1.t);
616                 }
617         | error ';'
618         | error '}'
619         | ';'
620         ;
621
622 ctor_initializer_opt:
623           nodecls
624                 { $$ = 0; }
625         | base_init
626                 { $$ = 1; }
627         ;
628
629 maybe_return_init:
630           /* empty */
631         | return_init
632         | return_init ';'
633         ;
634
635 eat_saved_input:
636           /* empty */
637         | END_OF_SAVED_INPUT
638         ;
639
640 fndef:
641           fn.def1 maybe_return_init ctor_initializer_opt compstmt_or_error
642                 { finish_function (lineno, (int)$3, 0); }
643         | fn.def1 maybe_return_init function_try_block
644                 { 
645                   int nested = (hack_decl_function_context
646                                 (current_function_decl) != NULL_TREE);
647                   finish_function (lineno, (int)$3, nested); 
648                 }
649         | fn.def1 maybe_return_init error
650                 { }
651         ;
652
653 constructor_declarator:
654           nested_name_specifier SELFNAME '(' 
655                 { $$ = begin_constructor_declarator ($1, $2); }
656           parmlist ')' cv_qualifiers exception_specification_opt
657                 { $$ = make_call_declarator ($<ttype>4, $5, $7, $8); }
658         | nested_name_specifier SELFNAME LEFT_RIGHT cv_qualifiers exception_specification_opt
659                 { $$ = begin_constructor_declarator ($1, $2); 
660                   $$ = make_call_declarator ($$, empty_parms (), $4, $5);
661                 }
662         | global_scope nested_name_specifier SELFNAME '(' 
663                 { $$ = begin_constructor_declarator ($2, $3); }
664          parmlist ')' cv_qualifiers exception_specification_opt
665                 { $$ = make_call_declarator ($<ttype>5, $6, $8, $9); }
666         | global_scope nested_name_specifier SELFNAME LEFT_RIGHT cv_qualifiers exception_specification_opt
667                 { $$ = begin_constructor_declarator ($2, $3);
668                   $$ = make_call_declarator ($$, empty_parms (), $5, $6);
669                 }
670         | nested_name_specifier self_template_type '(' 
671                 { $$ = begin_constructor_declarator ($1, $2); }
672           parmlist ')' cv_qualifiers exception_specification_opt
673                 { $$ = make_call_declarator ($<ttype>4, $5, $7, $8); }
674         | nested_name_specifier self_template_type LEFT_RIGHT cv_qualifiers exception_specification_opt
675                 { $$ = begin_constructor_declarator ($1, $2);
676                   $$ = make_call_declarator ($$, empty_parms (), $4, $5);
677                 }
678         | global_scope nested_name_specifier self_template_type '(' 
679                 { $$ = begin_constructor_declarator ($2, $3); }
680          parmlist ')' cv_qualifiers exception_specification_opt
681                 { $$ = make_call_declarator ($<ttype>5, $6, $8, $9); }
682         | global_scope nested_name_specifier self_template_type LEFT_RIGHT cv_qualifiers exception_specification_opt
683                 { $$ = begin_constructor_declarator ($2, $3); 
684                   $$ = make_call_declarator ($$, empty_parms (), $5, $6);
685                 }
686         ;
687
688 fn.def1:
689           typed_declspecs declarator
690                 { if (!begin_function_definition ($1.t, $2))
691                     YYERROR1; }
692         | declmods notype_declarator
693                 { if (!begin_function_definition ($1, $2))
694                     YYERROR1; }
695         | notype_declarator
696                 { if (!begin_function_definition (NULL_TREE, $1))
697                     YYERROR1; }
698         | declmods constructor_declarator
699                 { if (!begin_function_definition ($1, $2))
700                     YYERROR1; }
701         | constructor_declarator
702                 { if (!begin_function_definition (NULL_TREE, $1))
703                     YYERROR1; }
704         ;
705
706 component_constructor_declarator:
707           SELFNAME '(' parmlist ')' cv_qualifiers exception_specification_opt
708                 { $$ = make_call_declarator ($1, $3, $5, $6); }
709         | SELFNAME LEFT_RIGHT cv_qualifiers exception_specification_opt
710                 { $$ = make_call_declarator ($1, empty_parms (), $3, $4); }
711         | self_template_type '(' parmlist ')' cv_qualifiers exception_specification_opt
712                 { $$ = make_call_declarator ($1, $3, $5, $6); }
713         | self_template_type LEFT_RIGHT cv_qualifiers exception_specification_opt
714                 { $$ = make_call_declarator ($1, empty_parms (), $3, $4); }
715         ;
716
717 /* more C++ complexity.  See component_decl for a comment on the
718    reduce/reduce conflict introduced by these rules.  */
719 fn.def2:
720           declmods component_constructor_declarator
721                 { tree specs, attrs;
722                   split_specs_attrs ($1, &specs, &attrs);
723                   attrs = build_tree_list (attrs, NULL_TREE);
724                   $$ = start_method (specs, $2, attrs);
725                  rest_of_mdef:
726                   if (! $$)
727                     YYERROR1;
728                   if (yychar == YYEMPTY)
729                     yychar = YYLEX;
730                   reinit_parse_for_method (yychar, $$); }
731         | component_constructor_declarator
732                 { $$ = start_method (NULL_TREE, $1, NULL_TREE); 
733                   goto rest_of_mdef; }
734         | typed_declspecs declarator
735                 { tree specs, attrs;
736                   split_specs_attrs ($1.t, &specs, &attrs);
737                   attrs = build_tree_list (attrs, NULL_TREE);
738                   $$ = start_method (specs, $2, attrs); goto rest_of_mdef; }
739         | declmods notype_declarator
740                 { tree specs, attrs;
741                   split_specs_attrs ($1, &specs, &attrs);
742                   attrs = build_tree_list (attrs, NULL_TREE);
743                   $$ = start_method (specs, $2, attrs); goto rest_of_mdef; }
744         | notype_declarator
745                 { $$ = start_method (NULL_TREE, $$, NULL_TREE); 
746                   goto rest_of_mdef; }
747         | declmods constructor_declarator
748                 { tree specs, attrs;
749                   split_specs_attrs ($1, &specs, &attrs);
750                   attrs = build_tree_list (attrs, NULL_TREE);
751                   $$ = start_method (specs, $2, attrs); goto rest_of_mdef; }
752         | constructor_declarator
753                 { $$ = start_method (NULL_TREE, $$, NULL_TREE); 
754                   goto rest_of_mdef; }
755         ;
756
757 return_id:
758           RETURN_KEYWORD IDENTIFIER
759                 {
760                   if (! current_function_parms_stored)
761                     store_parm_decls ();
762                   $$ = $2;
763                 }
764         ;
765
766 return_init:
767           return_id maybe_init
768                 { store_return_init ($<ttype>$, $2); }
769         | return_id '(' nonnull_exprlist ')'
770                 { store_return_init ($<ttype>$, $3); }
771         | return_id LEFT_RIGHT
772                 { store_return_init ($<ttype>$, NULL_TREE); }
773         ;
774
775 base_init:
776           ':' .set_base_init member_init_list
777                 {
778                   if ($3 == 0)
779                     error ("no base initializers given following ':'");
780                   setup_vtbl_ptr ();
781                   /* Always keep the BLOCK node associated with the outermost
782                      pair of curley braces of a function.  These are needed
783                      for correct operation of dwarfout.c.  */
784                   keep_next_level ();
785                 }
786         ;
787
788 .set_base_init:
789           /* empty */
790                 {
791                   if (! current_function_parms_stored)
792                     store_parm_decls ();
793
794                   if (DECL_CONSTRUCTOR_P (current_function_decl))
795                     {
796                       /* Make a contour for the initializer list.  */
797                       pushlevel (0);
798                       clear_last_expr ();
799                       expand_start_bindings (0);
800                     }
801                   else if (current_class_type == NULL_TREE)
802                     error ("base initializers not allowed for non-member functions");
803                   else if (! DECL_CONSTRUCTOR_P (current_function_decl))
804                     error ("only constructors take base initializers");
805                 }
806         ;
807
808 member_init_list:
809           /* empty */
810                 { $$ = 0; }
811         | member_init
812                 { $$ = 1; }
813         | member_init_list ',' member_init
814         | member_init_list error
815         ;
816
817 member_init:
818           '(' nonnull_exprlist ')'
819                 {
820                   if (current_class_name)
821                     pedwarn ("anachronistic old style base class initializer");
822                   expand_member_init (current_class_ref, NULL_TREE, $2);
823                 }
824         | LEFT_RIGHT
825                 {
826                   if (current_class_name)
827                     pedwarn ("anachronistic old style base class initializer");
828                   expand_member_init (current_class_ref, NULL_TREE, void_type_node);
829                 }
830         | notype_identifier '(' nonnull_exprlist ')'
831                 { expand_member_init (current_class_ref, $1, $3); }
832         | notype_identifier LEFT_RIGHT
833                 { expand_member_init (current_class_ref, $1, void_type_node); }
834         | nonnested_type '(' nonnull_exprlist ')'
835                 { expand_member_init (current_class_ref, $1, $3); }
836         | nonnested_type LEFT_RIGHT
837                 { expand_member_init (current_class_ref, $1, void_type_node); }
838         | typename_sub '(' nonnull_exprlist ')'
839                 { expand_member_init (current_class_ref, TYPE_MAIN_DECL ($1),
840                                       $3); }
841         | typename_sub LEFT_RIGHT
842                 { expand_member_init (current_class_ref, TYPE_MAIN_DECL ($1),
843                                       void_type_node); }
844         ;
845
846 identifier:
847           IDENTIFIER
848         | TYPENAME
849         | SELFNAME
850         | PTYPENAME
851         | NSNAME
852         ;
853
854 notype_identifier:
855           IDENTIFIER
856         | PTYPENAME 
857         | NSNAME  %prec EMPTY
858         ;
859
860 identifier_defn:
861           IDENTIFIER_DEFN
862         | TYPENAME_DEFN
863         | PTYPENAME_DEFN
864         ;
865
866 explicit_instantiation:
867           TEMPLATE begin_explicit_instantiation typespec ';'
868                 { do_type_instantiation ($3.t, NULL_TREE);
869                   yyungetc (';', 1); }
870           end_explicit_instantiation
871         | TEMPLATE begin_explicit_instantiation typed_declspecs declarator
872                 { tree specs = strip_attrs ($3.t);
873                   do_decl_instantiation (specs, $4, NULL_TREE); }
874           end_explicit_instantiation
875         | TEMPLATE begin_explicit_instantiation notype_declarator
876                 { do_decl_instantiation (NULL_TREE, $3, NULL_TREE); }
877           end_explicit_instantiation
878         | TEMPLATE begin_explicit_instantiation constructor_declarator
879                 { do_decl_instantiation (NULL_TREE, $3, NULL_TREE); }
880           end_explicit_instantiation
881         | SCSPEC TEMPLATE begin_explicit_instantiation typespec ';'
882                 { do_type_instantiation ($4.t, $1);
883                   yyungetc (';', 1); }
884           end_explicit_instantiation
885         | SCSPEC TEMPLATE begin_explicit_instantiation typed_declspecs 
886           declarator
887                 { tree specs = strip_attrs ($4.t);
888                   do_decl_instantiation (specs, $5, $1); }
889           end_explicit_instantiation
890         | SCSPEC TEMPLATE begin_explicit_instantiation notype_declarator
891                 { do_decl_instantiation (NULL_TREE, $4, $1); }
892           end_explicit_instantiation
893         | SCSPEC TEMPLATE begin_explicit_instantiation constructor_declarator
894                 { do_decl_instantiation (NULL_TREE, $4, $1); }
895           end_explicit_instantiation
896         ;
897
898 begin_explicit_instantiation: 
899       { begin_explicit_instantiation(); }
900
901 end_explicit_instantiation: 
902       { end_explicit_instantiation(); }
903
904 /* The TYPENAME expansions are to deal with use of a template class name as
905   a template within the class itself, where the template decl is hidden by
906   a type decl.  Got all that?  */
907
908 template_type:
909           PTYPENAME '<' template_arg_list_opt template_close_bracket
910             .finish_template_type
911                 { $$ = $5; }
912         | TYPENAME  '<' template_arg_list_opt template_close_bracket
913             .finish_template_type
914                 { $$ = $5; }
915         | self_template_type
916         ;
917
918 apparent_template_type:
919           template_type
920         | identifier '<' template_arg_list_opt '>'
921             .finish_template_type
922                 { $$ = $5; }
923
924 self_template_type:
925           SELFNAME  '<' template_arg_list_opt template_close_bracket
926             .finish_template_type
927                 { $$ = $5; }
928         ;
929
930 .finish_template_type:
931                 { 
932                   if (yychar == YYEMPTY)
933                     yychar = YYLEX;
934
935                   $$ = finish_template_type ($<ttype>-3, $<ttype>-1, 
936                                              yychar == SCOPE);
937                 }
938
939 template_close_bracket:
940           '>'
941         | RSHIFT 
942                 {
943                   /* Handle `Class<Class<Type>>' without space in the `>>' */
944                   pedwarn ("`>>' should be `> >' in template class name");
945                   yyungetc ('>', 1);
946                 }
947         ;
948
949 template_arg_list_opt:
950          /* empty */
951                  { $$ = NULL_TREE; }
952        | template_arg_list
953        ;
954
955 template_arg_list:
956         template_arg
957                 { $$ = build_tree_list (NULL_TREE, $$); }
958         | template_arg_list ',' template_arg
959                 { $$ = chainon ($$, build_tree_list (NULL_TREE, $3)); }
960         ;
961
962 template_arg:
963           type_id
964                 { $$ = groktypename ($1.t); }
965         | PTYPENAME
966                 { $$ = lastiddecl; }
967         | expr_no_commas  %prec ARITHCOMPARE
968         ;
969
970 unop:
971           '-'
972                 { $$ = NEGATE_EXPR; }
973         | '+'
974                 { $$ = CONVERT_EXPR; }
975         | PLUSPLUS
976                 { $$ = PREINCREMENT_EXPR; }
977         | MINUSMINUS
978                 { $$ = PREDECREMENT_EXPR; }
979         | '!'
980                 { $$ = TRUTH_NOT_EXPR; }
981         ;
982
983 expr:
984           nontrivial_exprlist
985                 { $$ = build_x_compound_expr ($$); }
986         | expr_no_commas
987         ;
988
989 paren_expr_or_null:
990         LEFT_RIGHT
991                 { error ("ANSI C++ forbids an empty condition for `%s'",
992                          cond_stmt_keyword);
993                   $$ = integer_zero_node; }
994         | '(' expr ')'
995                 { $$ = $2; }
996         ;
997
998 paren_cond_or_null:
999         LEFT_RIGHT
1000                 { error ("ANSI C++ forbids an empty condition for `%s'",
1001                          cond_stmt_keyword);
1002                   $$ = integer_zero_node; }
1003         | '(' condition ')'
1004                 { $$ = $2; }
1005         ;
1006
1007 xcond:
1008           /* empty */
1009                 { $$ = NULL_TREE; }
1010         | condition
1011         | error
1012                 { $$ = NULL_TREE; }
1013         ;
1014
1015 condition:
1016           type_specifier_seq declarator maybeasm maybe_attribute '='
1017                 { {
1018                   tree d;
1019                   for (d = getdecls (); d; d = TREE_CHAIN (d))
1020                     if (TREE_CODE (d) == TYPE_DECL) {
1021                       tree s = TREE_TYPE (d);
1022                       if (TREE_CODE (s) == RECORD_TYPE)
1023                         cp_error ("definition of class `%T' in condition", s);
1024                       else if (TREE_CODE (s) == ENUMERAL_TYPE)
1025                         cp_error ("definition of enum `%T' in condition", s);
1026                     }
1027                   }
1028                   current_declspecs = $1.t;
1029                   $<itype>5 = suspend_momentary ();
1030                   $<ttype>$ = start_decl ($<ttype>2, current_declspecs, 1,
1031                                           $4, /*prefix_attributes*/ NULL_TREE);
1032                 }
1033           init
1034                 { 
1035                   cp_finish_decl ($<ttype>6, $7, $4, 1, LOOKUP_ONLYCONVERTING);
1036                   resume_momentary ($<itype>5);
1037                   $$ = convert_from_reference ($<ttype>6); 
1038                   if (TREE_CODE (TREE_TYPE ($$)) == ARRAY_TYPE)
1039                     cp_error ("definition of array `%#D' in condition", $$); 
1040                 }
1041         | expr
1042         ;
1043
1044 compstmtend:
1045           '}'
1046         | maybe_label_decls stmts '}'
1047         | maybe_label_decls stmts error '}'
1048         | maybe_label_decls error '}'
1049         ;
1050
1051 already_scoped_stmt:
1052           '{'
1053                 { $<ttype>$ = begin_compound_stmt (1); }
1054           compstmtend
1055                 { finish_compound_stmt (1, $<ttype>2); }
1056         | simple_stmt
1057         ;
1058
1059
1060 nontrivial_exprlist:
1061           expr_no_commas ',' expr_no_commas
1062                 { $$ = expr_tree_cons (NULL_TREE, $$, 
1063                                   build_expr_list (NULL_TREE, $3)); }
1064         | expr_no_commas ',' error
1065                 { $$ = expr_tree_cons (NULL_TREE, $$, 
1066                                   build_expr_list (NULL_TREE, error_mark_node)); }
1067         | nontrivial_exprlist ',' expr_no_commas
1068                 { chainon ($$, build_expr_list (NULL_TREE, $3)); }
1069         | nontrivial_exprlist ',' error
1070                 { chainon ($$, build_expr_list (NULL_TREE, error_mark_node)); }
1071         ;
1072
1073 nonnull_exprlist:
1074           expr_no_commas
1075                 { $$ = build_expr_list (NULL_TREE, $$); }
1076         | nontrivial_exprlist
1077         ;
1078
1079 unary_expr:
1080           primary  %prec UNARY
1081                 { $$ = $1; }
1082         /* __extension__ turns off -pedantic for following primary.  */
1083         | extension cast_expr     %prec UNARY
1084                 { $$ = $2;
1085                   pedantic = $<itype>1; }
1086         | '*' cast_expr   %prec UNARY
1087                 { $$ = build_x_indirect_ref ($2, "unary *"); }
1088         | '&' cast_expr   %prec UNARY
1089                 { $$ = build_x_unary_op (ADDR_EXPR, $2); }
1090         | '~' cast_expr
1091                 { $$ = build_x_unary_op (BIT_NOT_EXPR, $2); }
1092         | unop cast_expr  %prec UNARY
1093                 { $$ = finish_unary_op_expr ($1, $2); }
1094         /* Refer to the address of a label as a pointer.  */
1095         | ANDAND identifier
1096                 { if (pedantic)
1097                     pedwarn ("ANSI C++ forbids `&&'");
1098                   $$ = finish_label_address_expr ($2); }
1099         | SIZEOF unary_expr  %prec UNARY
1100                 { $$ = expr_sizeof ($2); }
1101         | SIZEOF '(' type_id ')'  %prec HYPERUNARY
1102                 { $$ = c_sizeof (groktypename ($3.t));
1103                   check_for_new_type ("sizeof", $3); }
1104         | ALIGNOF unary_expr  %prec UNARY
1105                 { $$ = grok_alignof ($2); }
1106         | ALIGNOF '(' type_id ')'  %prec HYPERUNARY
1107                 { $$ = c_alignof (groktypename ($3.t)); 
1108                   check_for_new_type ("alignof", $3); }
1109
1110         /* The %prec EMPTY's here are required by the = init initializer
1111            syntax extension; see below.  */
1112         | new new_type_id  %prec EMPTY
1113                 { $$ = build_new (NULL_TREE, $2.t, NULL_TREE, $1); 
1114                   check_for_new_type ("new", $2); }
1115         | new new_type_id new_initializer
1116                 { $$ = build_new (NULL_TREE, $2.t, $3, $1); 
1117                   check_for_new_type ("new", $2); }
1118         | new new_placement new_type_id  %prec EMPTY
1119                 { $$ = build_new ($2, $3.t, NULL_TREE, $1); 
1120                   check_for_new_type ("new", $3); }
1121         | new new_placement new_type_id new_initializer
1122                 { $$ = build_new ($2, $3.t, $4, $1); 
1123                   check_for_new_type ("new", $3); }
1124         /* The .begin_new_placement in the following rules is
1125            necessary to avoid shift/reduce conflicts that lead to
1126            mis-parsing some expressions.  Of course, these constructs
1127            are not really new-placement and it is bogus to call
1128            begin_new_placement.  But, the parser cannot always tell at this
1129            point whether the next thing is an expression or a type-id,
1130            so there is nothing we can do.  Fortunately,
1131            begin_new_placement does nothing harmful.  When we rewrite
1132            the parser, this lossage should be removed, of course.  */
1133         | new '(' .begin_new_placement type_id .finish_new_placement
1134             %prec EMPTY
1135                 { $$ = build_new (NULL_TREE, groktypename($4.t),
1136                                   NULL_TREE, $1); 
1137                   check_for_new_type ("new", $4); }
1138         | new '(' .begin_new_placement type_id .finish_new_placement
1139             new_initializer
1140                 { $$ = build_new (NULL_TREE, groktypename($4.t), $6, $1); 
1141                   check_for_new_type ("new", $4); }
1142         | new new_placement '(' .begin_new_placement type_id
1143             .finish_new_placement   %prec EMPTY
1144                 { $$ = build_new ($2, groktypename($5.t), NULL_TREE, $1); 
1145                   check_for_new_type ("new", $5); }
1146         | new new_placement '(' .begin_new_placement type_id
1147             .finish_new_placement  new_initializer
1148                 { $$ = build_new ($2, groktypename($5.t), $7, $1); 
1149                   check_for_new_type ("new", $5); }
1150
1151         | delete cast_expr  %prec UNARY
1152                 { $$ = delete_sanity ($2, NULL_TREE, 0, $1); }
1153         | delete '[' ']' cast_expr  %prec UNARY
1154                 { $$ = delete_sanity ($4, NULL_TREE, 1, $1);
1155                   if (yychar == YYEMPTY)
1156                     yychar = YYLEX; }
1157         | delete '[' expr ']' cast_expr  %prec UNARY
1158                 { $$ = delete_sanity ($5, $3, 2, $1);
1159                   if (yychar == YYEMPTY)
1160                     yychar = YYLEX; }
1161         | REALPART cast_expr %prec UNARY
1162                 { $$ = build_x_unary_op (REALPART_EXPR, $2); }
1163         | IMAGPART cast_expr %prec UNARY
1164                 { $$ = build_x_unary_op (IMAGPART_EXPR, $2); }
1165         | VA_ARG '(' expr_no_commas ',' type_id ')'
1166                 { $$ = build_va_arg ($3, groktypename ($5.t));
1167                   check_for_new_type ("__builtin_va_arg", $5); }
1168         ;
1169
1170         /* Note this rule is not suitable for use in new_placement
1171            since it uses NULL_TREE as the argument to
1172            finish_new_placement.  This rule serves only to avoid
1173            reduce/reduce conflicts in unary_expr.  See the comments
1174            there on the use of begin/finish_new_placement.  */
1175 .finish_new_placement:
1176           ')'
1177                 { finish_new_placement (NULL_TREE, $<itype>-1); }
1178
1179 .begin_new_placement:
1180                 { $$ = begin_new_placement (); }
1181
1182 new_placement:
1183           '(' .begin_new_placement nonnull_exprlist ')'
1184                 { $$ = finish_new_placement ($3, $2); }
1185         | '{' .begin_new_placement nonnull_exprlist '}'
1186                 { cp_pedwarn ("old style placement syntax, use () instead");
1187                   $$ = finish_new_placement ($3, $2); }
1188         ;
1189
1190 new_initializer:
1191           '(' nonnull_exprlist ')'
1192                 { $$ = $2; }
1193         | LEFT_RIGHT
1194                 { $$ = NULL_TREE; }
1195         | '(' typespec ')'
1196                 {
1197                   cp_error ("`%T' is not a valid expression", $2.t);
1198                   $$ = error_mark_node;
1199                 }
1200         /* GNU extension so people can use initializer lists.  Note that
1201            this alters the meaning of `new int = 1', which was previously
1202            syntactically valid but semantically invalid.  */
1203         | '=' init
1204                 {
1205                   if (pedantic)
1206                     pedwarn ("ANSI C++ forbids initialization of new expression with `='");
1207                   if (TREE_CODE ($2) != TREE_LIST
1208                       && TREE_CODE ($2) != CONSTRUCTOR)
1209                     $$ = build_expr_list (NULL_TREE, $2);
1210                   else
1211                     $$ = $2;
1212                 }
1213         ;
1214
1215 /* This is necessary to postpone reduction of `int ((int)(int)(int))'.  */
1216 regcast_or_absdcl:
1217           '(' type_id ')'  %prec EMPTY
1218                 { $2.t = finish_parmlist (build_tree_list (NULL_TREE, $2.t), 0);
1219                   $$ = make_call_declarator (NULL_TREE, $2.t, NULL_TREE, NULL_TREE);
1220                   check_for_new_type ("cast", $2); }
1221         | regcast_or_absdcl '(' type_id ')'  %prec EMPTY
1222                 { $3.t = finish_parmlist (build_tree_list (NULL_TREE, $3.t), 0); 
1223                   $$ = make_call_declarator ($$, $3.t, NULL_TREE, NULL_TREE);
1224                   check_for_new_type ("cast", $3); }
1225         ;
1226
1227 cast_expr:
1228           unary_expr
1229         | regcast_or_absdcl unary_expr  %prec UNARY
1230                 { $$ = reparse_absdcl_as_casts ($$, $2); }
1231         | regcast_or_absdcl '{' initlist maybecomma '}'  %prec UNARY
1232                 { 
1233                   tree init = build_nt (CONSTRUCTOR, NULL_TREE,
1234                                         nreverse ($3)); 
1235                   if (pedantic)
1236                     pedwarn ("ANSI C++ forbids constructor-expressions");
1237                   /* Indicate that this was a GNU C constructor expression.  */
1238                   TREE_HAS_CONSTRUCTOR (init) = 1;
1239
1240                   $$ = reparse_absdcl_as_casts ($$, init);
1241                 }
1242         ;
1243
1244 expr_no_commas:
1245           cast_expr
1246         /* Handle general members.  */
1247         | expr_no_commas POINTSAT_STAR expr_no_commas
1248                 { $$ = build_x_binary_op (MEMBER_REF, $$, $3); }
1249         | expr_no_commas DOT_STAR expr_no_commas
1250                 { $$ = build_m_component_ref ($$, $3); }
1251         | expr_no_commas '+' expr_no_commas
1252                 { $$ = build_x_binary_op ($2, $$, $3); }
1253         | expr_no_commas '-' expr_no_commas
1254                 { $$ = build_x_binary_op ($2, $$, $3); }
1255         | expr_no_commas '*' expr_no_commas
1256                 { $$ = build_x_binary_op ($2, $$, $3); }
1257         | expr_no_commas '/' expr_no_commas
1258                 { $$ = build_x_binary_op ($2, $$, $3); }
1259         | expr_no_commas '%' expr_no_commas
1260                 { $$ = build_x_binary_op ($2, $$, $3); }
1261         | expr_no_commas LSHIFT expr_no_commas
1262                 { $$ = build_x_binary_op ($2, $$, $3); }
1263         | expr_no_commas RSHIFT expr_no_commas
1264                 { $$ = build_x_binary_op ($2, $$, $3); }
1265         | expr_no_commas ARITHCOMPARE expr_no_commas
1266                 { $$ = build_x_binary_op ($2, $$, $3); }
1267         | expr_no_commas '<' expr_no_commas
1268                 { $$ = build_x_binary_op (LT_EXPR, $$, $3); }
1269         | expr_no_commas '>' expr_no_commas
1270                 { $$ = build_x_binary_op (GT_EXPR, $$, $3); }
1271         | expr_no_commas EQCOMPARE expr_no_commas
1272                 { $$ = build_x_binary_op ($2, $$, $3); }
1273         | expr_no_commas MIN_MAX expr_no_commas
1274                 { $$ = build_x_binary_op ($2, $$, $3); }
1275         | expr_no_commas '&' expr_no_commas
1276                 { $$ = build_x_binary_op ($2, $$, $3); }
1277         | expr_no_commas '|' expr_no_commas
1278                 { $$ = build_x_binary_op ($2, $$, $3); }
1279         | expr_no_commas '^' expr_no_commas
1280                 { $$ = build_x_binary_op ($2, $$, $3); }
1281         | expr_no_commas ANDAND expr_no_commas
1282                 { $$ = build_x_binary_op (TRUTH_ANDIF_EXPR, $$, $3); }
1283         | expr_no_commas OROR expr_no_commas
1284                 { $$ = build_x_binary_op (TRUTH_ORIF_EXPR, $$, $3); }
1285         | expr_no_commas '?' xexpr ':' expr_no_commas
1286                 { $$ = build_x_conditional_expr ($$, $3, $5); }
1287         | expr_no_commas '=' expr_no_commas
1288                 { $$ = build_x_modify_expr ($$, NOP_EXPR, $3);
1289                   if ($$ != error_mark_node)
1290                     C_SET_EXP_ORIGINAL_CODE ($$, MODIFY_EXPR); }
1291         | expr_no_commas ASSIGN expr_no_commas
1292                 { $$ = build_x_modify_expr ($$, $2, $3); }
1293         | THROW
1294                 { $$ = build_throw (NULL_TREE); }
1295         | THROW expr_no_commas
1296                 { $$ = build_throw ($2); }
1297 /* These extensions are not defined.  The second arg to build_m_component_ref
1298    is old, build_m_component_ref now does an implicit
1299    build_indirect_ref (x, NULL_PTR) on the second argument.
1300         | object '&' expr_no_commas  %prec UNARY
1301                 { $$ = build_m_component_ref ($$, build_x_unary_op (ADDR_EXPR, $3)); }
1302         | object unop expr_no_commas  %prec UNARY
1303                 { $$ = build_m_component_ref ($$, build_x_unary_op ($2, $3)); }
1304         | object '(' type_id ')' expr_no_commas  %prec UNARY
1305                 { tree type = groktypename ($3.t);
1306                   $$ = build_m_component_ref ($$, build_c_cast (type, $5)); }
1307         | object primary_no_id  %prec UNARY
1308                 { $$ = build_m_component_ref ($$, $2); }
1309 */
1310         ;
1311
1312 notype_unqualified_id:
1313           '~' see_typename identifier
1314                 { $$ = build_parse_node (BIT_NOT_EXPR, $3); }
1315         | '~' see_typename template_type
1316                 { $$ = build_parse_node (BIT_NOT_EXPR, $3); }
1317         | template_id
1318         | operator_name
1319         | IDENTIFIER
1320         | PTYPENAME
1321         | NSNAME  %prec EMPTY
1322         ;
1323
1324 do_id:
1325                 {
1326                   /* If lastiddecl is a TREE_LIST, it's a baselink, which
1327                      means that we're in an expression like S::f<int>, so
1328                      don't do_identifier; we only do that for unqualified
1329                      identifiers.  */
1330                   if (lastiddecl && TREE_CODE (lastiddecl) != TREE_LIST)
1331                     $$ = do_identifier ($<ttype>-1, 1, NULL_TREE);
1332                   else
1333                     $$ = $<ttype>-1;
1334                 }
1335
1336 template_id:
1337           PFUNCNAME '<' do_id template_arg_list_opt template_close_bracket 
1338                 { $$ = lookup_template_function ($3, $4); }
1339         | operator_name '<' do_id template_arg_list_opt template_close_bracket
1340                 { $$ = lookup_template_function ($3, $4); }
1341         ;
1342
1343 object_template_id:
1344         TEMPLATE identifier '<' template_arg_list_opt template_close_bracket
1345                 { $$ = lookup_template_function ($2, $4); }
1346         | TEMPLATE PFUNCNAME '<' template_arg_list_opt template_close_bracket
1347                 { $$ = lookup_template_function ($2, $4); }
1348         | TEMPLATE operator_name '<' template_arg_list_opt 
1349           template_close_bracket
1350                 { $$ = lookup_template_function ($2, $4); }
1351         ;
1352
1353 unqualified_id:
1354           notype_unqualified_id
1355         | TYPENAME
1356         | SELFNAME
1357         ;
1358
1359 expr_or_declarator_intern:
1360           expr_or_declarator
1361         | attributes expr_or_declarator
1362                 {
1363                   /* Provide support for '(' attributes '*' declarator ')'
1364                      etc */
1365                   $$ = decl_tree_cons ($1, $2, NULL_TREE);
1366                 }
1367         ;
1368
1369 expr_or_declarator:
1370           notype_unqualified_id
1371         | '*' expr_or_declarator_intern  %prec UNARY
1372                 { $$ = build_parse_node (INDIRECT_REF, $2); }
1373         | '&' expr_or_declarator_intern  %prec UNARY
1374                 { $$ = build_parse_node (ADDR_EXPR, $2); }
1375         | '(' expr_or_declarator_intern ')'
1376                 { $$ = $2; }
1377         ;
1378
1379 notype_template_declarator:
1380           IDENTIFIER '<' template_arg_list_opt template_close_bracket
1381                 { $$ = lookup_template_function ($1, $3); }
1382         | NSNAME '<' template_arg_list template_close_bracket
1383                 { $$ = lookup_template_function ($1, $3); }
1384         ;
1385                 
1386 direct_notype_declarator:
1387           complex_direct_notype_declarator
1388         /* This precedence declaration is to prefer this reduce
1389            to the Koenig lookup shift in primary, below.  I hate yacc.  */
1390         | notype_unqualified_id %prec '('
1391         | notype_template_declarator
1392         | '(' expr_or_declarator_intern ')'
1393                 { $$ = finish_decl_parsing ($2); }
1394         ;
1395
1396 primary:
1397           notype_unqualified_id
1398                 {
1399                   if (TREE_CODE ($1) == BIT_NOT_EXPR)
1400                     $$ = build_x_unary_op (BIT_NOT_EXPR, TREE_OPERAND ($1, 0));
1401                   else 
1402                     $$ = finish_id_expr ($1);
1403                 }               
1404         | CONSTANT
1405         | boolean.literal
1406         | string
1407                 {
1408                   if (processing_template_decl)
1409                     push_obstacks (&permanent_obstack, &permanent_obstack);
1410                   $$ = combine_strings ($$);
1411                   /* combine_strings doesn't set up TYPE_MAIN_VARIANT of
1412                      a const array the way we want, so fix it.  */
1413                   if (flag_const_strings)
1414                     TREE_TYPE ($$) = build_cplus_array_type
1415                       (TREE_TYPE (TREE_TYPE ($$)),
1416                        TYPE_DOMAIN (TREE_TYPE ($$)));
1417                   if (processing_template_decl)
1418                     pop_obstacks ();
1419                 }
1420         | '(' expr ')'
1421                 { $$ = finish_parenthesized_expr ($2); }
1422         | '(' expr_or_declarator_intern ')'
1423                 { $2 = reparse_decl_as_expr (NULL_TREE, $2);
1424                   $$ = finish_parenthesized_expr ($2); }
1425         | '(' error ')'
1426                 { $$ = error_mark_node; }
1427         | '('
1428                 { tree scope = current_scope ();
1429                   if (!scope || TREE_CODE (scope) != FUNCTION_DECL)
1430                     {
1431                       error ("braced-group within expression allowed only inside a function");
1432                       YYERROR;
1433                     }
1434                   if (pedantic)
1435                     pedwarn ("ANSI C++ forbids braced-groups within expressions");  
1436                   $<ttype>$ = begin_stmt_expr (); 
1437                 }
1438           compstmt ')'
1439                { $$ = finish_stmt_expr ($<ttype>2, $3); }
1440         /* Koenig lookup support
1441            We could store lastiddecl in $1 to avoid another lookup,
1442            but that would result in many additional reduce/reduce conflicts. */
1443         | notype_unqualified_id '(' nonnull_exprlist ')'
1444                { $$ = finish_call_expr ($1, $3, 1); }
1445         | notype_unqualified_id LEFT_RIGHT
1446                { $$ = finish_call_expr ($1, NULL_TREE, 1); }
1447         | primary '(' nonnull_exprlist ')'
1448                { $$ = finish_call_expr ($1, $3, 0); }
1449         | primary LEFT_RIGHT
1450                { $$ = finish_call_expr ($1, NULL_TREE, 0); }
1451         | primary '[' expr ']'
1452                 { $$ = grok_array_decl ($$, $3); }
1453         | primary PLUSPLUS
1454                 { $$ = finish_increment_expr ($1, POSTINCREMENT_EXPR); }
1455         | primary MINUSMINUS
1456                 { $$ = finish_increment_expr ($1, POSTDECREMENT_EXPR); }
1457         /* C++ extensions */
1458         | THIS
1459                 { $$ = finish_this_expr (); }
1460         | CV_QUALIFIER '(' nonnull_exprlist ')'
1461                 {
1462                   /* This is a C cast in C++'s `functional' notation
1463                      using the "implicit int" extension so that:
1464                      `const (3)' is equivalent to `const int (3)'.  */
1465                   tree type;
1466
1467                   if ($3 == error_mark_node)
1468                     {
1469                       $$ = error_mark_node;
1470                       break;
1471                     }
1472
1473                   type = cp_build_qualified_type (integer_type_node,
1474                                                   cp_type_qual_from_rid ($1));
1475                   $$ = build_c_cast (type, build_compound_expr ($3));
1476                 }
1477         | functional_cast
1478         | DYNAMIC_CAST '<' type_id '>' '(' expr ')'
1479                 { tree type = groktypename ($3.t);
1480                   check_for_new_type ("dynamic_cast", $3);
1481                   $$ = build_dynamic_cast (type, $6); }
1482         | STATIC_CAST '<' type_id '>' '(' expr ')'
1483                 { tree type = groktypename ($3.t);
1484                   check_for_new_type ("static_cast", $3);
1485                   $$ = build_static_cast (type, $6); }
1486         | REINTERPRET_CAST '<' type_id '>' '(' expr ')'
1487                 { tree type = groktypename ($3.t);
1488                   check_for_new_type ("reinterpret_cast", $3);
1489                   $$ = build_reinterpret_cast (type, $6); }
1490         | CONST_CAST '<' type_id '>' '(' expr ')'
1491                 { tree type = groktypename ($3.t);
1492                   check_for_new_type ("const_cast", $3);
1493                   $$ = build_const_cast (type, $6); }
1494         | TYPEID '(' expr ')'
1495                 { $$ = build_x_typeid ($3); }
1496         | TYPEID '(' type_id ')'
1497                 { tree type = groktypename ($3.t);
1498                   check_for_new_type ("typeid", $3);
1499                   $$ = get_typeid (TYPE_MAIN_VARIANT (type)); }
1500         | global_scope IDENTIFIER
1501                 { $$ = do_scoped_id ($2, 1); }
1502         | global_scope template_id
1503                 { $$ = $2; }
1504         | global_scope operator_name
1505                 {
1506                   got_scope = NULL_TREE;
1507                   if (TREE_CODE ($2) == IDENTIFIER_NODE)
1508                     $$ = do_scoped_id ($2, 1);
1509                   else
1510                     $$ = $2;
1511                 }
1512         | overqualified_id  %prec HYPERUNARY
1513                 { $$ = build_offset_ref (OP0 ($$), OP1 ($$)); }
1514         | overqualified_id '(' nonnull_exprlist ')'
1515                 { $$ = finish_qualified_call_expr ($1, $3); }
1516         | overqualified_id LEFT_RIGHT
1517                 { $$ = finish_qualified_call_expr ($1, NULL_TREE); }
1518         | object object_template_id %prec UNARY
1519                 { 
1520                   $$ = build_x_component_ref ($$, $2, NULL_TREE, 1); 
1521                 }
1522         | object object_template_id '(' nonnull_exprlist ')'
1523                 { $$ = finish_object_call_expr ($2, $1, $4); }
1524         | object object_template_id LEFT_RIGHT
1525                 { $$ = finish_object_call_expr ($2, $1, NULL_TREE); }
1526         | object unqualified_id  %prec UNARY
1527                 { $$ = build_x_component_ref ($$, $2, NULL_TREE, 1); }
1528         | object overqualified_id  %prec UNARY
1529                 { if (processing_template_decl)
1530                     $$ = build_min_nt (COMPONENT_REF, $1, copy_to_permanent ($2));
1531                   else
1532                     $$ = build_object_ref ($$, OP0 ($2), OP1 ($2)); }
1533         | object unqualified_id '(' nonnull_exprlist ')'
1534                 { $$ = finish_object_call_expr ($2, $1, $4); }
1535         | object unqualified_id LEFT_RIGHT
1536                 { $$ = finish_object_call_expr ($2, $1, NULL_TREE); }
1537         | object overqualified_id '(' nonnull_exprlist ')'
1538                 { $$ = finish_qualified_object_call_expr ($2, $1, $4); }
1539         | object overqualified_id LEFT_RIGHT
1540                 { $$ = finish_qualified_object_call_expr ($2, $1, NULL_TREE); }
1541         /* p->int::~int() is valid -- 12.4 */
1542         | object '~' TYPESPEC LEFT_RIGHT
1543                 { $$ = finish_pseudo_destructor_call_expr ($1, NULL_TREE, $3); }
1544         | object TYPESPEC SCOPE '~' TYPESPEC LEFT_RIGHT
1545                 { $$ = finish_pseudo_destructor_call_expr ($1, $2, $5); }
1546         | object error
1547                 {
1548                   $$ = error_mark_node;
1549                 }
1550         ;
1551
1552 /* Not needed for now.
1553
1554 primary_no_id:
1555           '(' expr ')'
1556                 { $$ = $2; }
1557         | '(' error ')'
1558                 { $$ = error_mark_node; }
1559         | '('
1560                 { if (current_function_decl == 0)
1561                     {
1562                       error ("braced-group within expression allowed only inside a function");
1563                       YYERROR;
1564                     }
1565                   $<ttype>$ = expand_start_stmt_expr (); }
1566           compstmt ')'
1567                 { if (pedantic)
1568                     pedwarn ("ANSI C++ forbids braced-groups within expressions");
1569                   $$ = expand_end_stmt_expr ($<ttype>2); }
1570         | primary_no_id '(' nonnull_exprlist ')'
1571                 { $$ = build_x_function_call ($$, $3, current_class_ref); }
1572         | primary_no_id LEFT_RIGHT
1573                 { $$ = build_x_function_call ($$, NULL_TREE, current_class_ref); }
1574         | primary_no_id '[' expr ']'
1575                 { goto do_array; }
1576         | primary_no_id PLUSPLUS
1577                 { $$ = build_x_unary_op (POSTINCREMENT_EXPR, $$); }
1578         | primary_no_id MINUSMINUS
1579                 { $$ = build_x_unary_op (POSTDECREMENT_EXPR, $$); }
1580         | SCOPE IDENTIFIER
1581                 { goto do_scoped_id; }
1582         | SCOPE operator_name
1583                 { if (TREE_CODE ($2) == IDENTIFIER_NODE)
1584                     goto do_scoped_id;
1585                   goto do_scoped_operator;
1586                 }
1587         ;
1588 */
1589
1590 new:
1591           NEW
1592                 { $$ = 0; }
1593         | global_scope NEW
1594                 { got_scope = NULL_TREE; $$ = 1; }
1595         ;
1596
1597 delete:
1598           DELETE
1599                 { $$ = 0; }
1600         | global_scope delete
1601                 { got_scope = NULL_TREE; $$ = 1; }
1602         ;
1603
1604 boolean.literal:
1605           CXX_TRUE
1606                 { $$ = boolean_true_node; }
1607         | CXX_FALSE
1608                 { $$ = boolean_false_node; }
1609         ;
1610
1611 /* Produces a STRING_CST with perhaps more STRING_CSTs chained onto it.  */
1612 string:
1613           STRING
1614         | string STRING
1615                 { $$ = chainon ($$, $2); }
1616         ;
1617
1618 nodecls:
1619           /* empty */
1620                 {
1621                   if (! current_function_parms_stored)
1622                     store_parm_decls ();
1623                   setup_vtbl_ptr ();
1624                   /* Always keep the BLOCK node associated with the outermost
1625                      pair of curley braces of a function.  These are needed
1626                      for correct operation of dwarfout.c.  */
1627                   keep_next_level ();
1628                 }
1629         ;
1630
1631 object:
1632           primary '.'
1633                 { got_object = TREE_TYPE ($$); }
1634         | primary POINTSAT
1635                 {
1636                   $$ = build_x_arrow ($$); 
1637                   got_object = TREE_TYPE ($$);
1638                 }
1639         ;
1640
1641 decl:
1642           typespec initdecls ';'
1643                 {
1644                   resume_momentary ($2);
1645                   if ($1.t && IS_AGGR_TYPE_CODE (TREE_CODE ($1.t)))
1646                     note_got_semicolon ($1.t);
1647                 }
1648         | typed_declspecs initdecls ';'
1649                 {
1650                   resume_momentary ($2);
1651                   note_list_got_semicolon ($1.t);
1652                 }
1653         | declmods notype_initdecls ';'
1654                 { resume_momentary ($2); }
1655         | typed_declspecs ';'
1656                 {
1657                   shadow_tag ($1.t);
1658                   note_list_got_semicolon ($1.t);
1659                 }
1660         | declmods ';'
1661                 { warning ("empty declaration"); }
1662         | extension decl
1663                 { pedantic = $<itype>1; }
1664         ;
1665
1666 /* Any kind of declarator (thus, all declarators allowed
1667    after an explicit typespec).  */
1668
1669 declarator:
1670           after_type_declarator  %prec EMPTY
1671         | notype_declarator  %prec EMPTY
1672         ;
1673
1674 /* This is necessary to postpone reduction of `int()()()()'.  */
1675 fcast_or_absdcl:
1676           LEFT_RIGHT  %prec EMPTY
1677                 { $$ = make_call_declarator (NULL_TREE, empty_parms (),
1678                                              NULL_TREE, NULL_TREE); }
1679         | fcast_or_absdcl LEFT_RIGHT  %prec EMPTY
1680                 { $$ = make_call_declarator ($$, empty_parms (), NULL_TREE,
1681                                              NULL_TREE); }
1682         ;
1683
1684 /* ANSI type-id (8.1) */
1685 type_id:
1686           typed_typespecs absdcl
1687                 { $$.t = build_decl_list ($1.t, $2); 
1688                   $$.new_type_flag = $1.new_type_flag; }
1689         | nonempty_cv_qualifiers absdcl
1690                 { $$.t = build_decl_list ($1.t, $2); 
1691                   $$.new_type_flag = $1.new_type_flag; }
1692         | typespec absdcl
1693                 { $$.t = build_decl_list (build_decl_list (NULL_TREE, $1.t),
1694                                           $2); 
1695                   $$.new_type_flag = $1.new_type_flag; }
1696         | typed_typespecs  %prec EMPTY
1697                 { $$.t = build_decl_list ($1.t, NULL_TREE);
1698                   $$.new_type_flag = $1.new_type_flag;  }
1699         | nonempty_cv_qualifiers  %prec EMPTY
1700                 { $$.t = build_decl_list ($1.t, NULL_TREE); 
1701                   $$.new_type_flag = $1.new_type_flag; }
1702         ;
1703
1704 /* Declspecs which contain at least one type specifier or typedef name.
1705    (Just `const' or `volatile' is not enough.)
1706    A typedef'd name following these is taken as a name to be declared.
1707    In the result, declspecs have a non-NULL TREE_VALUE, attributes do not.  */
1708
1709 typed_declspecs:
1710           typed_typespecs  %prec EMPTY
1711         | typed_declspecs1
1712         ;
1713
1714 typed_declspecs1:
1715           declmods typespec
1716                 { $$.t = decl_tree_cons (NULL_TREE, $2.t, $1); 
1717                   $$.new_type_flag = $2.new_type_flag; }
1718         | typespec reserved_declspecs  %prec HYPERUNARY
1719                 { $$.t = decl_tree_cons (NULL_TREE, $1.t, $2); 
1720                   $$.new_type_flag = $1.new_type_flag; }
1721         | typespec reserved_typespecquals reserved_declspecs
1722                 { $$.t = decl_tree_cons (NULL_TREE, $1.t, chainon ($2, $3)); 
1723                   $$.new_type_flag = $1.new_type_flag; }
1724         | declmods typespec reserved_declspecs
1725                 { $$.t = decl_tree_cons (NULL_TREE, $2.t, chainon ($3, $1)); 
1726                   $$.new_type_flag = $2.new_type_flag; }
1727         | declmods typespec reserved_typespecquals
1728                 { $$.t = decl_tree_cons (NULL_TREE, $2.t, chainon ($3, $1)); 
1729                   $$.new_type_flag = $2.new_type_flag; }
1730         | declmods typespec reserved_typespecquals reserved_declspecs
1731                 { $$.t = decl_tree_cons (NULL_TREE, $2.t,
1732                                          chainon ($3, chainon ($4, $1))); 
1733                   $$.new_type_flag = $2.new_type_flag; }
1734         ;
1735
1736 reserved_declspecs:
1737           SCSPEC
1738                 { if (extra_warnings)
1739                     warning ("`%s' is not at beginning of declaration",
1740                              IDENTIFIER_POINTER ($$));
1741                   $$ = build_decl_list (NULL_TREE, $$); }
1742         | reserved_declspecs typespecqual_reserved
1743                 { $$ = decl_tree_cons (NULL_TREE, $2.t, $$); }
1744         | reserved_declspecs SCSPEC
1745                 { if (extra_warnings)
1746                     warning ("`%s' is not at beginning of declaration",
1747                              IDENTIFIER_POINTER ($2));
1748                   $$ = decl_tree_cons (NULL_TREE, $2, $$); }
1749         | reserved_declspecs attributes
1750                 { $$ = decl_tree_cons ($2, NULL_TREE, $1); }
1751         | attributes
1752                 { $$ = decl_tree_cons ($1, NULL_TREE, NULL_TREE); }
1753         ;
1754
1755 /* List of just storage classes and type modifiers.
1756    A declaration can start with just this, but then it cannot be used
1757    to redeclare a typedef-name.
1758    In the result, declspecs have a non-NULL TREE_VALUE, attributes do not.  */
1759
1760 /* We use hash_tree_cons for lists of typeless declspecs so that they end
1761    up on a persistent obstack.  Otherwise, they could appear at the
1762    beginning of something like
1763
1764       static const struct { int foo () { } } b;
1765
1766    and would be discarded after we finish compiling foo.  We don't need to
1767    worry once we see a type.  */
1768
1769 declmods:
1770           nonempty_cv_qualifiers  %prec EMPTY
1771                 { $$ = $1.t; TREE_STATIC ($$) = 1; }
1772         | SCSPEC
1773                 { $$ = hash_tree_cons (NULL_TREE, $$, NULL_TREE); }
1774         | declmods CV_QUALIFIER
1775                 { $$ = hash_tree_cons (NULL_TREE, $2, $$);
1776                   TREE_STATIC ($$) = 1; }
1777         | declmods SCSPEC
1778                 { if (extra_warnings && TREE_STATIC ($$))
1779                     warning ("`%s' is not at beginning of declaration",
1780                              IDENTIFIER_POINTER ($2));
1781                   $$ = hash_tree_cons (NULL_TREE, $2, $$);
1782                   TREE_STATIC ($$) = TREE_STATIC ($1); }
1783         | declmods attributes
1784                 { $$ = hash_tree_cons ($2, NULL_TREE, $1); }
1785         | attributes  %prec EMPTY
1786                 { $$ = hash_tree_cons ($1, NULL_TREE, NULL_TREE); }
1787         ;
1788
1789 /* Used instead of declspecs where storage classes are not allowed
1790    (that is, for typenames and structure components).
1791
1792    C++ can takes storage classes for structure components.
1793    Don't accept a typedef-name if anything but a modifier precedes it.  */
1794
1795 typed_typespecs:
1796           typespec  %prec EMPTY
1797                 { $$.t = build_decl_list (NULL_TREE, $1.t); 
1798                   $$.new_type_flag = $1.new_type_flag; }
1799         | nonempty_cv_qualifiers typespec
1800                 { $$.t = decl_tree_cons (NULL_TREE, $2.t, $1.t); 
1801                   $$.new_type_flag = $2.new_type_flag; }
1802         | typespec reserved_typespecquals
1803                 { $$.t = decl_tree_cons (NULL_TREE, $1.t, $2); 
1804                   $$.new_type_flag = $1.new_type_flag; }
1805         | nonempty_cv_qualifiers typespec reserved_typespecquals
1806                 { $$.t = decl_tree_cons (NULL_TREE, $2.t, chainon ($3, $1.t)); 
1807                   $$.new_type_flag = $1.new_type_flag; }
1808         ;
1809
1810 reserved_typespecquals:
1811           typespecqual_reserved
1812                 { $$ = build_decl_list (NULL_TREE, $1.t); }
1813         | reserved_typespecquals typespecqual_reserved
1814                 { $$ = decl_tree_cons (NULL_TREE, $2.t, $1); }
1815         ;
1816
1817 /* A typespec (but not a type qualifier).
1818    Once we have seen one of these in a declaration,
1819    if a typedef name appears then it is being redeclared.  */
1820
1821 typespec:
1822           structsp
1823         | TYPESPEC  %prec EMPTY
1824                 { $$.t = $1; $$.new_type_flag = 0; }
1825         | complete_type_name
1826                 { $$.t = $1; $$.new_type_flag = 0; }
1827         | TYPEOF '(' expr ')'
1828                 { $$.t = finish_typeof ($3);
1829                   $$.new_type_flag = 0; }
1830         | TYPEOF '(' type_id ')'
1831                 { $$.t = groktypename ($3.t);
1832                   $$.new_type_flag = 0; }
1833         | SIGOF '(' expr ')'
1834                 { tree type = TREE_TYPE ($3);
1835
1836                   $$.new_type_flag = 0;
1837                   if (IS_AGGR_TYPE (type))
1838                     {
1839                       sorry ("sigof type specifier");
1840                       $$.t = type;
1841                     }
1842                   else
1843                     {
1844                       error ("`sigof' applied to non-aggregate expression");
1845                       $$.t = error_mark_node;
1846                     }
1847                 }
1848         | SIGOF '(' type_id ')'
1849                 { tree type = groktypename ($3.t);
1850
1851                   $$.new_type_flag = 0;
1852                   if (IS_AGGR_TYPE (type))
1853                     {
1854                       sorry ("sigof type specifier");
1855                       $$.t = type;
1856                     }
1857                   else
1858                     {
1859                       error("`sigof' applied to non-aggregate type");
1860                       $$.t = error_mark_node;
1861                     }
1862                 }
1863         ;
1864
1865 /* A typespec that is a reserved word, or a type qualifier.  */
1866
1867 typespecqual_reserved:
1868           TYPESPEC
1869                 { $$.t = $1; $$.new_type_flag = 0; }
1870         | CV_QUALIFIER
1871                 { $$.t = $1; $$.new_type_flag = 0; }
1872         | structsp
1873         ;
1874
1875 initdecls:
1876           initdcl0
1877         | initdecls ',' initdcl
1878             { check_multiple_declarators (); }
1879         ;
1880
1881 notype_initdecls:
1882           notype_initdcl0
1883         | notype_initdecls ',' initdcl
1884             { check_multiple_declarators (); }
1885         ;
1886
1887 nomods_initdecls:
1888           nomods_initdcl0
1889         | nomods_initdecls ',' initdcl
1890             { check_multiple_declarators (); }
1891         ;
1892
1893 maybeasm:
1894           /* empty */
1895                 { $$ = NULL_TREE; }
1896         | asm_keyword '(' string ')'
1897                 { if (TREE_CHAIN ($3)) $3 = combine_strings ($3); $$ = $3; }
1898         ;
1899
1900 initdcl:
1901           declarator maybeasm maybe_attribute '='
1902                 { $<ttype>$ = start_decl ($<ttype>1, current_declspecs, 1,
1903                                           $3, prefix_attributes); }
1904           init
1905 /* Note how the declaration of the variable is in effect while its init is parsed! */
1906                 { cp_finish_decl ($<ttype>5, $6, $2, 1, LOOKUP_ONLYCONVERTING); }
1907         | declarator maybeasm maybe_attribute
1908                 { $<ttype>$ = start_decl ($<ttype>1, current_declspecs, 0,
1909                                           $3, prefix_attributes);
1910                   cp_finish_decl ($<ttype>$, NULL_TREE, $2, 1, 0); }
1911         ;
1912
1913         /* This rule assumes a certain configuration of the parser stack.
1914            In particular, $0, the element directly before the beginning of
1915            this rule on the stack, must be a maybeasm.  $-1 must be a
1916            declarator or notype_declarator.  And $-2 must be some declmods
1917            or declspecs.  We can't move the maybeasm into this rule because
1918            we need that reduce so we prefer fn.def1 when appropriate.  */
1919 initdcl0_innards:
1920           maybe_attribute '='
1921                 { $<itype>2 = parse_decl ($<ttype>-1, $<ttype>-2, 
1922                                            $1, 1, &$<ttype>$); }
1923           /* Note how the declaration of the variable is in effect
1924              while its init is parsed! */ 
1925           init
1926                 { cp_finish_decl ($<ttype>3, $4, $<ttype>0, 1,
1927                                   LOOKUP_ONLYCONVERTING);
1928                   $$ = $<itype>2; }
1929         | maybe_attribute
1930                 { tree d;
1931                   $$ = parse_decl ($<ttype>-1, $<ttype>-2, $1, 0, &d);
1932                   cp_finish_decl (d, NULL_TREE, $<ttype>0, 1, 0); }
1933         ;
1934   
1935 initdcl0:
1936           declarator maybeasm initdcl0_innards
1937             { $$ = $3; }
1938   
1939 notype_initdcl0:
1940           notype_declarator maybeasm initdcl0_innards
1941             { $$ = $3; }
1942         ;
1943   
1944 nomods_initdcl0:
1945           notype_declarator maybeasm
1946             { /* Set things up as initdcl0_innards expects.  */
1947               $<ttype>2 = $1; 
1948               $1 = NULL_TREE; }
1949           initdcl0_innards 
1950             {}
1951         | constructor_declarator maybeasm maybe_attribute
1952                 { tree d;
1953                   parse_decl($1, NULL_TREE, $3, 0, &d);
1954                   cp_finish_decl (d, NULL_TREE, $2, 1, 0); }
1955         ;
1956
1957 /* the * rules are dummies to accept the Apollo extended syntax
1958    so that the header files compile.  */
1959 maybe_attribute:
1960           /* empty */
1961                 { $$ = NULL_TREE; }
1962         | attributes
1963                 { $$ = $1; }
1964         ;
1965  
1966 attributes:
1967       attribute
1968                 { $$ = $1; }
1969         | attributes attribute
1970                 { $$ = chainon ($1, $2); }
1971         ;
1972
1973 attribute:
1974       ATTRIBUTE '(' '(' attribute_list ')' ')'
1975                 { $$ = $4; }
1976         ;
1977
1978 attribute_list:
1979       attrib
1980                 { $$ = $1; }
1981         | attribute_list ',' attrib
1982                 { $$ = chainon ($1, $3); }
1983         ;
1984  
1985 attrib:
1986           /* empty */
1987                 { $$ = NULL_TREE; }
1988         | any_word
1989                 { $$ = build_tree_list ($1, NULL_TREE); }
1990         | any_word '(' IDENTIFIER ')'
1991                 { $$ = build_tree_list ($1, build_tree_list (NULL_TREE, $3)); }
1992         | any_word '(' IDENTIFIER ',' nonnull_exprlist ')'
1993                 { $$ = build_tree_list ($1, tree_cons (NULL_TREE, $3, $5)); }
1994         | any_word '(' nonnull_exprlist ')'
1995                 { $$ = build_tree_list ($1, $3); }
1996         ;
1997
1998 /* This still leaves out most reserved keywords,
1999    shouldn't we include them?  */
2000
2001 any_word:
2002           identifier
2003         | SCSPEC
2004         | TYPESPEC
2005         | CV_QUALIFIER
2006         ;
2007
2008 /* A nonempty list of identifiers, including typenames.  */
2009 identifiers_or_typenames:
2010           identifier
2011                 { $$ = build_tree_list (NULL_TREE, $1); }
2012         | identifiers_or_typenames ',' identifier
2013                 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
2014         ;
2015
2016 maybe_init:
2017           /* empty */  %prec EMPTY
2018                 { $$ = NULL_TREE; }
2019         | '=' init
2020                 { $$ = $2; }
2021
2022 /* If we are processing a template, we don't want to expand this
2023    initializer yet.  */
2024
2025 init:
2026           expr_no_commas  %prec '='
2027         | '{' '}'
2028                 { $$ = build_nt (CONSTRUCTOR, NULL_TREE, NULL_TREE);
2029                   TREE_HAS_CONSTRUCTOR ($$) = 1; }
2030         | '{' initlist '}'
2031                 { $$ = build_nt (CONSTRUCTOR, NULL_TREE, nreverse ($2));
2032                   TREE_HAS_CONSTRUCTOR ($$) = 1; }
2033         | '{' initlist ',' '}'
2034                 { $$ = build_nt (CONSTRUCTOR, NULL_TREE, nreverse ($2));
2035                   TREE_HAS_CONSTRUCTOR ($$) = 1; }
2036         | error
2037                 { $$ = NULL_TREE; }
2038         ;
2039
2040 /* This chain is built in reverse order,
2041    and put in forward order where initlist is used.  */
2042 initlist:
2043           init
2044                 { $$ = build_tree_list (NULL_TREE, $$); }
2045         | initlist ',' init
2046                 { $$ = expr_tree_cons (NULL_TREE, $3, $$); }
2047         /* These are for labeled elements.  */
2048         | '[' expr_no_commas ']' init
2049                 { $$ = build_expr_list ($2, $4); }
2050         | identifier ':' init
2051                 { $$ = build_expr_list ($$, $3); }
2052         | initlist ',' identifier ':' init
2053                 { $$ = expr_tree_cons ($3, $5, $$); }
2054         ;
2055
2056 fn.defpen:
2057         PRE_PARSED_FUNCTION_DECL
2058                 { start_function (NULL_TREE, TREE_VALUE ($1),
2059                                   NULL_TREE, 2);
2060                   reinit_parse_for_function (); }
2061
2062 pending_inline:
2063           fn.defpen maybe_return_init ctor_initializer_opt compstmt_or_error
2064                 {
2065                   int nested = (hack_decl_function_context
2066                                 (current_function_decl) != NULL_TREE);
2067                   finish_function (lineno, (int)$3 | 2, nested);
2068                   process_next_inline ($1);
2069                 }
2070         | fn.defpen maybe_return_init function_try_block
2071                 { 
2072                   int nested = (hack_decl_function_context
2073                                 (current_function_decl) != NULL_TREE);
2074                   finish_function (lineno, (int)$3 | 2, nested); 
2075                   process_next_inline ($1);
2076                 }
2077         | fn.defpen maybe_return_init error
2078                 { process_next_inline ($1); }
2079         ;
2080
2081 pending_inlines:
2082         /* empty */
2083         | pending_inlines pending_inline eat_saved_input
2084         ;
2085
2086 /* A regurgitated default argument.  The value of DEFARG_MARKER will be
2087    the TREE_LIST node for the parameter in question.  */
2088 defarg_again:
2089         DEFARG_MARKER expr_no_commas END_OF_SAVED_INPUT
2090                 { replace_defarg ($1, $2); }
2091         | DEFARG_MARKER error END_OF_SAVED_INPUT
2092                 { replace_defarg ($1, error_mark_node); }
2093
2094 pending_defargs:
2095           /* empty */ %prec EMPTY
2096         | pending_defargs defarg_again
2097                 { do_pending_defargs (); }
2098         | pending_defargs error
2099                 { do_pending_defargs (); }
2100         ;
2101
2102 structsp:
2103           ENUM identifier '{'
2104                 { $<itype>3 = suspend_momentary ();
2105                   $<ttype>$ = current_enum_type;
2106                   current_enum_type = start_enum ($2); }
2107           enumlist_opt '}'
2108                 { TYPE_VALUES (current_enum_type) = $5;
2109                   $$.t = finish_enum (current_enum_type);
2110                   $$.new_type_flag = 1;
2111                   current_enum_type = $<ttype>4;
2112                   resume_momentary ((int) $<itype>3);
2113                   check_for_missing_semicolon ($$.t); }
2114         | ENUM '{'
2115                 { $<itype>2 = suspend_momentary ();
2116                   $<ttype>$ = current_enum_type;
2117                   current_enum_type = start_enum (make_anon_name ()); }
2118           enumlist_opt '}'
2119                 { TYPE_VALUES (current_enum_type) = $4;
2120                   $$.t = finish_enum (current_enum_type);
2121                   $$.new_type_flag = 1;
2122                   current_enum_type = $<ttype>3;
2123                   resume_momentary ((int) $<itype>1);
2124                   check_for_missing_semicolon ($$.t); }
2125         | ENUM identifier
2126                 { $$.t = xref_tag (enum_type_node, $2, 1); 
2127                   $$.new_type_flag = 0; }
2128         | ENUM complex_type_name
2129                 { $$.t = xref_tag (enum_type_node, $2, 1); 
2130                   $$.new_type_flag = 0; }
2131         | TYPENAME_KEYWORD typename_sub
2132                 { $$.t = $2;
2133                   $$.new_type_flag = 0; 
2134                   if (!processing_template_decl)
2135                     cp_pedwarn ("using `typename' outside of template"); }
2136         /* C++ extensions, merged with C to avoid shift/reduce conflicts */
2137         | class_head '{'
2138                 { $1.t = begin_class_definition ($1.t); }
2139           opt.component_decl_list '}' maybe_attribute
2140                 { 
2141                   int semi;
2142
2143                   if (yychar == YYEMPTY)
2144                     yychar = YYLEX;
2145                   semi = yychar == ';';
2146
2147                   $<ttype>$ = finish_class_definition ($1.t, $6, semi,
2148                                                        $1.new_type_flag); 
2149                 }
2150           pending_defargs
2151                 {
2152                   begin_inline_definitions ();
2153                 }
2154           pending_inlines
2155                 {
2156                   finish_inline_definitions ();
2157                   $$.t = $<ttype>7;
2158                   $$.new_type_flag = 1; 
2159                 }
2160         | class_head  %prec EMPTY
2161                 {
2162                   if ($1.new_type_flag && $1.t != error_mark_node)
2163                     pop_scope (CP_DECL_CONTEXT (TYPE_MAIN_DECL ($1.t)));
2164                   $$.new_type_flag = 0;
2165                   if ($1.t == error_mark_node)
2166                     $$.t = $1.t;
2167                   else if (TYPE_BINFO ($1.t) == NULL_TREE)
2168                     {
2169                       cp_error ("%T is not a class type", $1.t);
2170                       $$.t = error_mark_node;
2171                     } 
2172                   else
2173                     {
2174                       $$.t = $1.t;
2175                       /* struct B: public A; is not accepted by the WP grammar.  */
2176                       if (TYPE_BINFO_BASETYPES ($$.t) && !TYPE_SIZE ($$.t)
2177                           && ! TYPE_BEING_DEFINED ($$.t))
2178                         cp_error ("base clause without member specification for `%#T'",
2179                                   $$.t);
2180                     }
2181                 }
2182         ;
2183
2184 maybecomma:
2185           /* empty */
2186         | ','
2187         ;
2188
2189 maybecomma_warn:
2190           /* empty */
2191         | ','
2192                 { if (pedantic && !in_system_header)
2193                     pedwarn ("comma at end of enumerator list"); }
2194         ;
2195
2196 aggr:
2197           AGGR
2198         | aggr SCSPEC
2199                 { error ("storage class specifier `%s' not allowed after struct or class", IDENTIFIER_POINTER ($2)); }
2200         | aggr TYPESPEC
2201                 { error ("type specifier `%s' not allowed after struct or class", IDENTIFIER_POINTER ($2)); }
2202         | aggr CV_QUALIFIER
2203                 { error ("type qualifier `%s' not allowed after struct or class", IDENTIFIER_POINTER ($2)); }
2204         | aggr AGGR
2205                 { error ("no body nor ';' separates two class, struct or union declarations"); }
2206         | aggr attributes
2207                 { $$ = build_decl_list ($2, $1); }
2208         ;
2209
2210 named_class_head_sans_basetype:
2211           aggr identifier
2212                 { 
2213                   current_aggr = $1; 
2214                   $$ = $2; 
2215                 }
2216         ;
2217
2218 named_class_head_sans_basetype_defn:
2219           aggr identifier_defn  %prec EMPTY
2220                 { current_aggr = $$; $$ = $2; }
2221         | named_class_head_sans_basetype '{'
2222                 { yyungetc ('{', 1); }
2223         | named_class_head_sans_basetype ':'
2224                 { yyungetc (':', 1); }
2225         ;
2226
2227 named_complex_class_head_sans_basetype:
2228           aggr nested_name_specifier identifier
2229                 {
2230                   current_aggr = $1;
2231                   $$.t = handle_class_head ($1, $2, $3);
2232                   $$.new_type_flag = 1;
2233                 }
2234         | aggr global_scope nested_name_specifier identifier
2235                 {
2236                   current_aggr = $1;
2237                   $$.t = handle_class_head ($1, $3, $4);
2238                   $$.new_type_flag = 1;
2239                 }
2240         | aggr global_scope identifier
2241                 {
2242                   current_aggr = $1;
2243                   $$.t = handle_class_head ($1, NULL_TREE, $3);
2244                   $$.new_type_flag = 1;
2245                 }
2246         | aggr apparent_template_type
2247                 { 
2248                   current_aggr = $1; 
2249                   $$.t = $2;
2250                   $$.new_type_flag = 0;
2251                 }
2252         | aggr nested_name_specifier apparent_template_type
2253                 { 
2254                   current_aggr = $1; 
2255                   $$.t = $3;
2256                   if (CP_DECL_CONTEXT ($$.t))
2257                     push_scope (CP_DECL_CONTEXT ($$.t));
2258                   $$.new_type_flag = 1;
2259                 }
2260         ;
2261
2262 named_class_head:
2263           named_class_head_sans_basetype  %prec EMPTY
2264                 { 
2265                   $$.t = xref_tag (current_aggr, $1, 1); 
2266                   $$.new_type_flag = 0;
2267                 }
2268         | named_class_head_sans_basetype_defn 
2269                 { $<ttype>$ = xref_tag (current_aggr, $1, 0); }
2270           /* Class name is unqualified, so we look for base classes
2271              in the current scope.  */
2272           maybe_base_class_list  %prec EMPTY
2273                 { 
2274                   $$.t = $<ttype>2;
2275                   $$.new_type_flag = 0;
2276                   if ($3)
2277                     xref_basetypes (current_aggr, $1, $<ttype>2, $3); 
2278                 }
2279         | named_complex_class_head_sans_basetype 
2280           maybe_base_class_list
2281                 { 
2282                   if ($1.t != error_mark_node)
2283                     {
2284                       $$.t = TREE_TYPE ($1.t);
2285                       $$.new_type_flag = $1.new_type_flag;
2286                       if (current_aggr == union_type_node
2287                           && TREE_CODE ($$.t) != UNION_TYPE)
2288                         cp_pedwarn ("`union' tag used in declaring `%#T'", 
2289                                     $$.t);
2290                       else if (TREE_CODE ($$.t) == UNION_TYPE
2291                                && current_aggr != union_type_node)
2292                         cp_pedwarn ("non-`union' tag used in declaring `%#T'", $$);
2293                       else if (TREE_CODE ($$.t) == RECORD_TYPE)
2294                         /* We might be specializing a template with a different
2295                            class-key; deal.  */
2296                         CLASSTYPE_DECLARED_CLASS ($$.t) 
2297                           = (current_aggr == class_type_node);
2298                       if ($2)
2299                         {
2300                           maybe_process_partial_specialization ($$.t);
2301                           xref_basetypes (current_aggr, $1.t, $$.t, $2); 
2302                         }
2303                     }
2304                 }
2305         ;
2306
2307 unnamed_class_head:
2308           aggr '{'
2309                 { $$ = xref_tag ($$, make_anon_name (), 0);
2310                   yyungetc ('{', 1); }
2311         ;
2312
2313 /* The tree output of this nonterminal a declarationf or the type
2314    named.  If NEW_TYPE_FLAG is set, then the name used in this
2315    class-head was explicitly qualified, e.g.:  `struct X::Y'.  We have
2316    already called push_scope for X.  */
2317 class_head:
2318           unnamed_class_head
2319                 {
2320                   $$.t = $1;
2321                   $$.new_type_flag = 0;
2322                 }
2323         | named_class_head
2324         ;
2325
2326 maybe_base_class_list:
2327           /* empty */  %prec EMPTY
2328                 { $$ = NULL_TREE; }
2329         | ':' see_typename  %prec EMPTY
2330                 { yyungetc(':', 1); $$ = NULL_TREE; }
2331         | ':' see_typename base_class_list  %prec EMPTY
2332                 { $$ = $3; }
2333         ;
2334
2335 base_class_list:
2336           base_class
2337         | base_class_list ',' see_typename base_class
2338                 { $$ = chainon ($$, $4); }
2339         ;
2340
2341 base_class:
2342           base_class.1
2343                 { $$ = finish_base_specifier (access_default_node, $1); }
2344         | base_class_access_list see_typename base_class.1
2345                 { $$ = finish_base_specifier ($1, $3); }
2346         ;
2347
2348 base_class.1:
2349           typename_sub
2350                 { if ($$ != error_mark_node) $$ = TYPE_MAIN_DECL ($1); }
2351         | nonnested_type
2352         ;
2353
2354 base_class_access_list:
2355           VISSPEC see_typename
2356         | SCSPEC see_typename
2357                 { if ($1 != ridpointers[(int)RID_VIRTUAL])
2358                     cp_error ("`%D' access", $1);
2359                   $$ = access_default_virtual_node; }
2360         | base_class_access_list VISSPEC see_typename
2361                 {
2362                   if ($1 != access_default_virtual_node)
2363                     error ("multiple access specifiers");
2364                   else if ($2 == access_public_node)
2365                     $$ = access_public_virtual_node;
2366                   else if ($2 == access_protected_node)
2367                     $$ = access_protected_virtual_node;
2368                   else /* $2 == access_private_node */
2369                     $$ = access_private_virtual_node;
2370                 }
2371         | base_class_access_list SCSPEC see_typename
2372                 { if ($2 != ridpointers[(int)RID_VIRTUAL])
2373                     cp_error ("`%D' access", $2);
2374                   else if ($$ == access_public_node)
2375                     $$ = access_public_virtual_node;
2376                   else if ($$ == access_protected_node)
2377                     $$ = access_protected_virtual_node;
2378                   else if ($$ == access_private_node)
2379                     $$ = access_private_virtual_node;
2380                   else
2381                     error ("multiple `virtual' specifiers");
2382                 }
2383         ;
2384
2385 opt.component_decl_list:
2386         | component_decl_list
2387         | opt.component_decl_list access_specifier component_decl_list
2388         | opt.component_decl_list access_specifier 
2389         ;
2390
2391 access_specifier:
2392           VISSPEC ':'
2393                 {
2394                   current_access_specifier = $1;
2395                 }
2396         ;
2397
2398 /* Note: we no longer warn about the semicolon after a component_decl_list.
2399    ARM $9.2 says that the semicolon is optional, and therefore allowed.  */
2400 component_decl_list:
2401           component_decl
2402                 { 
2403                   finish_member_declaration ($1);
2404                 }
2405         | component_decl_list component_decl
2406                 { 
2407                   finish_member_declaration ($2);
2408                 }
2409         ;
2410
2411 component_decl:
2412           component_decl_1 ';'
2413         | component_decl_1 '}'
2414                 { error ("missing ';' before right brace");
2415                   yyungetc ('}', 0); }
2416         /* C++: handle constructors, destructors and inline functions */
2417         /* note that INLINE is like a TYPESPEC */
2418         | fn.def2 ':' /* base_init compstmt */
2419                 { $$ = finish_method ($$); }
2420         | fn.def2 TRY /* base_init compstmt */
2421                 { $$ = finish_method ($$); }
2422         | fn.def2 RETURN_KEYWORD /* base_init compstmt */
2423                 { $$ = finish_method ($$); }
2424         | fn.def2 '{' /* nodecls compstmt */
2425                 { $$ = finish_method ($$); }
2426         | ';'
2427                 { $$ = NULL_TREE; }
2428         | extension component_decl
2429                 { $$ = $2;
2430                   pedantic = $<itype>1; }
2431         | template_header component_decl
2432                 {  
2433                   if ($2)
2434                     $$ = finish_member_template_decl ($2);
2435                   else
2436                     /* The component was already processed.  */
2437                     $$ = NULL_TREE;
2438
2439                   finish_template_decl ($1);
2440                 }
2441         | template_header typed_declspecs ';'
2442                 { 
2443                   $$ = finish_member_class_template ($2.t); 
2444                   finish_template_decl ($1);
2445                 }
2446         ;
2447
2448 component_decl_1:
2449         /* Do not add a "typed_declspecs declarator" rule here for
2450            speed; we need to call grok_x_components for enums, so the
2451            speedup would be insignificant.  */
2452           typed_declspecs components
2453                 {
2454                   /* Most of the productions for component_decl only
2455                      allow the creation of one new member, so we call
2456                      finish_member_declaration in component_decl_list.
2457                      For this rule and the next, however, there can be
2458                      more than one member, e.g.:
2459
2460                        int i, j;
2461
2462                      and we need the first member to be fully
2463                      registered before the second is processed.
2464                      Therefore, the rules for components take care of
2465                      this processing.  To avoid registering the
2466                      components more than once, we send NULL_TREE up
2467                      here; that lets finish_member_declaration know
2468                      that there is nothing to do.  */
2469                   if (!$2)
2470                     grok_x_components ($1.t);
2471                   $$ = NULL_TREE;
2472                 }
2473         | declmods notype_components
2474                 { 
2475                   if (!$2)
2476                     grok_x_components ($1);
2477                   $$ = NULL_TREE; 
2478                 }
2479         | notype_declarator maybeasm maybe_attribute maybe_init
2480                 { $$ = grokfield ($$, NULL_TREE, $4, $2,
2481                                   build_tree_list ($3, NULL_TREE)); }
2482         | constructor_declarator maybeasm maybe_attribute maybe_init
2483                 { $$ = grokfield ($$, NULL_TREE, $4, $2,
2484                                   build_tree_list ($3, NULL_TREE)); }
2485         | ':' expr_no_commas
2486                 { $$ = grokbitfield (NULL_TREE, NULL_TREE, $2); }
2487         | error
2488                 { $$ = NULL_TREE; }
2489
2490         /* These rules introduce a reduce/reduce conflict; in
2491                 typedef int foo, bar;
2492                 class A {
2493                   foo (bar);
2494                 };
2495            should "A::foo" be declared as a function or "A::bar" as a data
2496            member? In other words, is "bar" an after_type_declarator or a
2497            parmlist? */
2498         | declmods component_constructor_declarator maybeasm maybe_attribute maybe_init
2499                 { tree specs, attrs;
2500                   split_specs_attrs ($1, &specs, &attrs);
2501                   $$ = grokfield ($2, specs, $5, $3,
2502                                   build_tree_list ($4, attrs)); }
2503         | component_constructor_declarator maybeasm maybe_attribute maybe_init
2504                 { $$ = grokfield ($$, NULL_TREE, $4, $2,
2505                                   build_tree_list ($3, NULL_TREE)); }
2506         | using_decl
2507                 { $$ = do_class_using_decl ($1); }
2508
2509 /* The case of exactly one component is handled directly by component_decl.  */
2510 /* ??? Huh? ^^^ */
2511 components:
2512           /* empty: possibly anonymous */
2513                 { $$ = 0; }
2514         | component_declarator0
2515                 { 
2516                   if (PROCESSING_REAL_TEMPLATE_DECL_P ())
2517                     $1 = finish_member_template_decl ($1);
2518                   finish_member_declaration ($1); 
2519                   $$ = 1;
2520                 }
2521         | components ',' component_declarator
2522                 { 
2523                   check_multiple_declarators ();
2524                   if (PROCESSING_REAL_TEMPLATE_DECL_P ())
2525                     $3 = finish_member_template_decl ($3);
2526                   finish_member_declaration ($3);
2527                   $$ = 2;
2528                 }
2529         ;
2530
2531 notype_components:
2532           /* empty: possibly anonymous */
2533                 { $$ = 0; }
2534         | notype_component_declarator0
2535                 { 
2536                   if (PROCESSING_REAL_TEMPLATE_DECL_P ())
2537                     $1 = finish_member_template_decl ($1);
2538                   finish_member_declaration ($1);
2539                   $$ = 1;
2540                 }
2541         | notype_components ',' notype_component_declarator
2542                 { 
2543                   check_multiple_declarators ();
2544                   if (PROCESSING_REAL_TEMPLATE_DECL_P ())
2545                     $3 = finish_member_template_decl ($3);
2546                   finish_member_declaration ($3); 
2547                   $$ = 2;
2548                 }
2549         ;
2550
2551 component_declarator0:
2552           after_type_component_declarator0
2553         | notype_component_declarator0
2554         ;
2555
2556 component_declarator:
2557           after_type_component_declarator
2558         | notype_component_declarator
2559         ;
2560
2561 after_type_component_declarator0:
2562           after_type_declarator maybeasm maybe_attribute maybe_init
2563                 { split_specs_attrs ($<ttype>0, &current_declspecs,
2564                                      &prefix_attributes);
2565                   $<ttype>0 = current_declspecs;
2566                   $$ = grokfield ($$, current_declspecs, $4, $2,
2567                                   build_tree_list ($3, prefix_attributes)); }
2568         | TYPENAME ':' expr_no_commas maybe_attribute
2569                 { split_specs_attrs ($<ttype>0, &current_declspecs,
2570                                      &prefix_attributes);
2571                   $<ttype>0 = current_declspecs;
2572                   $$ = grokbitfield ($$, current_declspecs, $3);
2573                   cplus_decl_attributes ($$, $4, prefix_attributes); }
2574         ;
2575
2576 notype_component_declarator0:
2577           notype_declarator maybeasm maybe_attribute maybe_init
2578                 { split_specs_attrs ($<ttype>0, &current_declspecs,
2579                                      &prefix_attributes);
2580                   $<ttype>0 = current_declspecs;
2581                   $$ = grokfield ($$, current_declspecs, $4, $2,
2582                                   build_tree_list ($3, prefix_attributes)); }
2583         | constructor_declarator maybeasm maybe_attribute maybe_init
2584                 { split_specs_attrs ($<ttype>0, &current_declspecs,
2585                                      &prefix_attributes);
2586                   $<ttype>0 = current_declspecs;
2587                   $$ = grokfield ($$, current_declspecs, $4, $2,
2588                                   build_tree_list ($3, prefix_attributes)); }
2589         | IDENTIFIER ':' expr_no_commas maybe_attribute
2590                 { split_specs_attrs ($<ttype>0, &current_declspecs,
2591                                      &prefix_attributes);
2592                   $<ttype>0 = current_declspecs;
2593                   $$ = grokbitfield ($$, current_declspecs, $3);
2594                   cplus_decl_attributes ($$, $4, prefix_attributes); }
2595         | ':' expr_no_commas maybe_attribute
2596                 { split_specs_attrs ($<ttype>0, &current_declspecs,
2597                                      &prefix_attributes);
2598                   $<ttype>0 = current_declspecs;
2599                   $$ = grokbitfield (NULL_TREE, current_declspecs, $2);
2600                   cplus_decl_attributes ($$, $3, prefix_attributes); }
2601         ;
2602
2603 after_type_component_declarator:
2604           after_type_declarator maybeasm maybe_attribute maybe_init
2605                 { $$ = grokfield ($$, current_declspecs, $4, $2,
2606                                   build_tree_list ($3, prefix_attributes)); }
2607         | TYPENAME ':' expr_no_commas maybe_attribute
2608                 { $$ = grokbitfield ($$, current_declspecs, $3);
2609                   cplus_decl_attributes ($$, $4, prefix_attributes); }
2610         ;
2611
2612 notype_component_declarator:
2613           notype_declarator maybeasm maybe_attribute maybe_init
2614                 { $$ = grokfield ($$, current_declspecs, $4, $2,
2615                                   build_tree_list ($3, prefix_attributes)); }
2616         | IDENTIFIER ':' expr_no_commas maybe_attribute
2617                 { $$ = grokbitfield ($$, current_declspecs, $3);
2618                   cplus_decl_attributes ($$, $4, prefix_attributes); }
2619         | ':' expr_no_commas maybe_attribute
2620                 { $$ = grokbitfield (NULL_TREE, current_declspecs, $2);
2621                   cplus_decl_attributes ($$, $3, prefix_attributes); }
2622         ;
2623
2624 enumlist_opt:
2625           enumlist maybecomma_warn
2626         | maybecomma_warn
2627           { $$ = NULL_TREE; }
2628         ;
2629
2630 /* We chain the enumerators in reverse order.
2631    Because of the way enums are built, the order is
2632    insignificant.  Take advantage of this fact.  */
2633
2634 enumlist:
2635           enumerator
2636         | enumlist ',' enumerator
2637                 { TREE_CHAIN ($3) = $$; $$ = $3; }
2638         ;
2639
2640 enumerator:
2641           identifier
2642                 { $$ = build_enumerator ($$, NULL_TREE, current_enum_type); }
2643         | identifier '=' expr_no_commas
2644                 { $$ = build_enumerator ($$, $3, current_enum_type); }
2645         ;
2646
2647 /* ANSI new-type-id (5.3.4) */
2648 new_type_id:
2649           type_specifier_seq new_declarator
2650                 { $$.t = build_decl_list ($1.t, $2); 
2651                   $$.new_type_flag = $1.new_type_flag; }
2652         | type_specifier_seq  %prec EMPTY
2653                 { $$.t = build_decl_list ($1.t, NULL_TREE); 
2654                   $$.new_type_flag = $1.new_type_flag; }
2655         /* GNU extension to allow arrays of arbitrary types with
2656            non-constant dimension.  For the use of begin_new_placement
2657            here, see the comments in unary_expr above.  */
2658         | '(' .begin_new_placement type_id .finish_new_placement
2659               '[' expr ']'
2660                 {
2661                   if (pedantic)
2662                     pedwarn ("ANSI C++ forbids array dimensions with parenthesized type in new");
2663                   $$.t = build_parse_node (ARRAY_REF, TREE_VALUE ($3.t), $6);
2664                   $$.t = build_decl_list (TREE_PURPOSE ($3.t), $$.t);
2665                   $$.new_type_flag = $3.new_type_flag;
2666                 }
2667         ;
2668
2669 cv_qualifiers:
2670           /* empty */  %prec EMPTY
2671                 { $$ = NULL_TREE; }
2672         | cv_qualifiers CV_QUALIFIER
2673                 { $$ = decl_tree_cons (NULL_TREE, $2, $$); }
2674         ;
2675
2676 nonempty_cv_qualifiers:
2677           CV_QUALIFIER
2678                 { $$.t = hash_tree_cons (NULL_TREE, $1, NULL_TREE);
2679                   $$.new_type_flag = 0; }
2680         | nonempty_cv_qualifiers CV_QUALIFIER
2681                 { $$.t = hash_tree_cons (NULL_TREE, $2, $1.t); 
2682                   $$.new_type_flag = $1.new_type_flag; }
2683         ;
2684
2685 /* These rules must follow the rules for function declarations
2686    and component declarations.  That way, longer rules are preferred.  */
2687
2688 suspend_mom:
2689           /* empty */
2690                 { $<itype>$ = suspend_momentary (); } 
2691
2692 /* An expression which will not live on the momentary obstack.  */
2693 nonmomentary_expr:
2694           suspend_mom expr
2695                 { resume_momentary ((int) $<itype>1); $$ = $2; }
2696         ;
2697
2698 /* An expression which will not live on the momentary obstack.  */
2699 maybe_parmlist:
2700           suspend_mom '(' nonnull_exprlist ')'
2701                 { resume_momentary ((int) $<itype>1); $$ = $3; }
2702         | suspend_mom '(' parmlist ')'
2703                 { resume_momentary ((int) $<itype>1); $$ = $3; }
2704         | suspend_mom LEFT_RIGHT
2705                 { resume_momentary ((int) $<itype>1); $$ = empty_parms (); }
2706         | suspend_mom '(' error ')'
2707                 { resume_momentary ((int) $<itype>1); $$ = NULL_TREE; }
2708         ;
2709
2710 /* A declarator that is allowed only after an explicit typespec.  */
2711
2712 after_type_declarator_intern:
2713           after_type_declarator
2714         | attributes after_type_declarator
2715                 {
2716                   /* Provide support for '(' attributes '*' declarator ')'
2717                      etc */
2718                   $$ = decl_tree_cons ($1, $2, NULL_TREE);
2719                 }
2720         ;
2721
2722 /* may all be followed by prec '.' */
2723 after_type_declarator:
2724           '*' nonempty_cv_qualifiers after_type_declarator_intern  %prec UNARY
2725                 { $$ = make_pointer_declarator ($2.t, $3); }
2726         | '&' nonempty_cv_qualifiers after_type_declarator_intern  %prec UNARY
2727                 { $$ = make_reference_declarator ($2.t, $3); }
2728         | '*' after_type_declarator_intern  %prec UNARY
2729                 { $$ = make_pointer_declarator (NULL_TREE, $2); }
2730         | '&' after_type_declarator_intern  %prec UNARY
2731                 { $$ = make_reference_declarator (NULL_TREE, $2); }
2732         | ptr_to_mem cv_qualifiers after_type_declarator_intern
2733                 { tree arg = make_pointer_declarator ($2, $3);
2734                   $$ = build_parse_node (SCOPE_REF, $1, arg);
2735                 }
2736         | direct_after_type_declarator
2737         ;
2738
2739 direct_after_type_declarator:
2740           direct_after_type_declarator maybe_parmlist cv_qualifiers exception_specification_opt  %prec '.'
2741                 { $$ = make_call_declarator ($$, $2, $3, $4); }
2742         | direct_after_type_declarator '[' nonmomentary_expr ']'
2743                 { $$ = build_parse_node (ARRAY_REF, $$, $3); }
2744         | direct_after_type_declarator '[' ']'
2745                 { $$ = build_parse_node (ARRAY_REF, $$, NULL_TREE); }
2746         | '(' after_type_declarator_intern ')'
2747                 { $$ = $2; }
2748         | nested_name_specifier type_name  %prec EMPTY
2749                 { push_nested_class ($1, 3);
2750                   $$ = build_parse_node (SCOPE_REF, $$, $2);
2751                   TREE_COMPLEXITY ($$) = current_class_depth; }
2752         | type_name  %prec EMPTY
2753         ;
2754
2755 nonnested_type:
2756           type_name  %prec EMPTY
2757                 {
2758                   if (TREE_CODE ($1) == IDENTIFIER_NODE)
2759                     {
2760                       $$ = lookup_name ($1, 1);
2761                       maybe_note_name_used_in_class ($1, $$);
2762                     }
2763                   else
2764                     $$ = $1;
2765                 }
2766         | global_scope type_name
2767                 {
2768                   if (TREE_CODE ($2) == IDENTIFIER_NODE)
2769                     $$ = IDENTIFIER_GLOBAL_VALUE ($2);
2770                   else
2771                     $$ = $2;
2772                   got_scope = NULL_TREE;
2773                 }
2774         ;
2775
2776 complete_type_name:
2777           nonnested_type
2778         | nested_type
2779         | global_scope nested_type
2780                 { $$ = $2; }
2781         ;
2782
2783 nested_type:
2784           nested_name_specifier type_name  %prec EMPTY
2785                 { $$ = get_type_decl ($2); }
2786         ;
2787
2788 /* A declarator allowed whether or not there has been
2789    an explicit typespec.  These cannot redeclare a typedef-name.  */
2790
2791 notype_declarator_intern:
2792           notype_declarator
2793         | attributes notype_declarator
2794                 {
2795                   /* Provide support for '(' attributes '*' declarator ')'
2796                      etc */
2797                   $$ = decl_tree_cons ($1, $2, NULL_TREE);
2798                 }
2799         ;
2800         
2801 notype_declarator:
2802           '*' nonempty_cv_qualifiers notype_declarator_intern  %prec UNARY
2803                 { $$ = make_pointer_declarator ($2.t, $3); }
2804         | '&' nonempty_cv_qualifiers notype_declarator_intern  %prec UNARY
2805                 { $$ = make_reference_declarator ($2.t, $3); }
2806         | '*' notype_declarator_intern  %prec UNARY
2807                 { $$ = make_pointer_declarator (NULL_TREE, $2); }
2808         | '&' notype_declarator_intern  %prec UNARY
2809                 { $$ = make_reference_declarator (NULL_TREE, $2); }
2810         | ptr_to_mem cv_qualifiers notype_declarator_intern
2811                 { tree arg = make_pointer_declarator ($2, $3);
2812                   $$ = build_parse_node (SCOPE_REF, $1, arg);
2813                 }
2814         | direct_notype_declarator
2815         ;
2816
2817 complex_notype_declarator:
2818           '*' nonempty_cv_qualifiers notype_declarator_intern  %prec UNARY
2819                 { $$ = make_pointer_declarator ($2.t, $3); }
2820         | '&' nonempty_cv_qualifiers notype_declarator_intern  %prec UNARY
2821                 { $$ = make_reference_declarator ($2.t, $3); }
2822         | '*' complex_notype_declarator  %prec UNARY
2823                 { $$ = make_pointer_declarator (NULL_TREE, $2); }
2824         | '&' complex_notype_declarator  %prec UNARY
2825                 { $$ = make_reference_declarator (NULL_TREE, $2); }
2826         | ptr_to_mem cv_qualifiers notype_declarator_intern
2827                 { tree arg = make_pointer_declarator ($2, $3);
2828                   $$ = build_parse_node (SCOPE_REF, $1, arg);
2829                 }
2830         | complex_direct_notype_declarator
2831         ;
2832
2833 complex_direct_notype_declarator:
2834           direct_notype_declarator maybe_parmlist cv_qualifiers exception_specification_opt  %prec '.'
2835                 { $$ = make_call_declarator ($$, $2, $3, $4); }
2836         | '(' complex_notype_declarator ')'
2837                 { $$ = $2; }
2838         | direct_notype_declarator '[' nonmomentary_expr ']'
2839                 { $$ = build_parse_node (ARRAY_REF, $$, $3); }
2840         | direct_notype_declarator '[' ']'
2841                 { $$ = build_parse_node (ARRAY_REF, $$, NULL_TREE); }
2842         | notype_qualified_id
2843                 { enter_scope_of ($1); }
2844         | nested_name_specifier notype_template_declarator
2845                 { got_scope = NULL_TREE;
2846                   $$ = build_parse_node (SCOPE_REF, $1, $2);
2847                   enter_scope_of ($$);
2848                 }
2849         ;
2850
2851 qualified_id:
2852           nested_name_specifier unqualified_id
2853                 { got_scope = NULL_TREE;
2854                   $$ = build_parse_node (SCOPE_REF, $$, $2); }
2855         | nested_name_specifier object_template_id
2856                 { got_scope = NULL_TREE;
2857                   $$ = build_parse_node (SCOPE_REF, $1, $2); }
2858         ;
2859
2860 notype_qualified_id:
2861           nested_name_specifier notype_unqualified_id
2862                 { got_scope = NULL_TREE;
2863                   $$ = build_parse_node (SCOPE_REF, $$, $2); }
2864         | nested_name_specifier object_template_id
2865                 { got_scope = NULL_TREE;
2866                   $$ = build_parse_node (SCOPE_REF, $1, $2); }
2867         ;
2868
2869 overqualified_id:
2870           notype_qualified_id
2871         | global_scope notype_qualified_id
2872                 { $$ = $2; }
2873         ;
2874
2875 functional_cast:
2876           typespec '(' nonnull_exprlist ')'
2877                 { $$ = build_functional_cast ($1.t, $3); }
2878         | typespec '(' expr_or_declarator_intern ')'
2879                 { $$ = reparse_decl_as_expr ($1.t, $3); }
2880         | typespec fcast_or_absdcl  %prec EMPTY
2881                 { $$ = reparse_absdcl_as_expr ($1.t, $2); }
2882         ;
2883 type_name:
2884           TYPENAME
2885         | SELFNAME
2886         | template_type  %prec EMPTY
2887         ;
2888
2889 nested_name_specifier:
2890           nested_name_specifier_1
2891         | nested_name_specifier nested_name_specifier_1
2892                 { $$ = $2; }
2893         | nested_name_specifier TEMPLATE explicit_template_type SCOPE
2894                 { got_scope = $$ = make_typename_type ($1, $3); }
2895         ;
2896
2897 /* Why the @#$%^& do type_name and notype_identifier need to be expanded
2898    inline here?!?  (jason) */
2899 nested_name_specifier_1:
2900           TYPENAME SCOPE
2901                 {
2902                   if (TREE_CODE ($1) == IDENTIFIER_NODE)
2903                     {
2904                       $$ = lastiddecl;
2905                       maybe_note_name_used_in_class ($1, $$);
2906                     }
2907                   got_scope = $$ =
2908                     complete_type (TYPE_MAIN_VARIANT (TREE_TYPE ($$)));
2909                 }
2910         | SELFNAME SCOPE
2911                 {
2912                   if (TREE_CODE ($1) == IDENTIFIER_NODE)
2913                     $$ = lastiddecl;
2914                   got_scope = $$ = TREE_TYPE ($$);
2915                 }
2916         | NSNAME SCOPE
2917                 {
2918                   if (TREE_CODE ($$) == IDENTIFIER_NODE)
2919                     $$ = lastiddecl;
2920                   got_scope = $$;
2921                 }
2922         | template_type SCOPE
2923                 { got_scope = $$ = complete_type (TREE_TYPE ($1)); }
2924 /*      These break 'const i;'
2925         | IDENTIFIER SCOPE
2926                 {
2927                  failed_scope:
2928                   cp_error ("`%D' is not an aggregate typedef", 
2929                             lastiddecl ? lastiddecl : $$);
2930                   $$ = error_mark_node;
2931                 }
2932         | PTYPENAME SCOPE
2933                 { goto failed_scope; } */
2934         ;
2935
2936 typename_sub:
2937           typename_sub0
2938         | global_scope typename_sub0
2939                 { $$ = $2; }
2940         ;
2941
2942 typename_sub0:
2943           typename_sub1 identifier %prec EMPTY
2944                 {
2945                   if (TREE_CODE_CLASS (TREE_CODE ($1)) == 't')
2946                     $$ = make_typename_type ($1, $2);
2947                   else if (TREE_CODE ($2) == IDENTIFIER_NODE)
2948                     cp_error ("`%T' is not a class or namespace", $2);
2949                   else
2950                     {
2951                       $$ = $2;
2952                       if (TREE_CODE ($$) == TYPE_DECL)
2953                         $$ = TREE_TYPE ($$);
2954                     }
2955                 }
2956         | typename_sub1 template_type %prec EMPTY
2957                 { $$ = TREE_TYPE ($2); }
2958         | typename_sub1 explicit_template_type %prec EMPTY
2959                 { $$ = make_typename_type ($1, $2); }
2960         | typename_sub1 TEMPLATE explicit_template_type %prec EMPTY
2961                 { $$ = make_typename_type ($1, $3); }
2962         ;
2963
2964 typename_sub1:
2965           typename_sub2
2966                 {
2967                   if (TREE_CODE ($1) == IDENTIFIER_NODE)
2968                     cp_error ("`%T' is not a class or namespace", $1);
2969                 }
2970         | typename_sub1 typename_sub2
2971                 {
2972                   if (TREE_CODE_CLASS (TREE_CODE ($1)) == 't')
2973                     $$ = make_typename_type ($1, $2);
2974                   else if (TREE_CODE ($2) == IDENTIFIER_NODE)
2975                     cp_error ("`%T' is not a class or namespace", $2);
2976                   else
2977                     {
2978                       $$ = $2;
2979                       if (TREE_CODE ($$) == TYPE_DECL)
2980                         $$ = TREE_TYPE ($$);
2981                     }
2982                 }
2983         | typename_sub1 explicit_template_type SCOPE
2984                 { got_scope = $$ = make_typename_type ($1, $2); }
2985         | typename_sub1 TEMPLATE explicit_template_type SCOPE
2986                 { got_scope = $$ = make_typename_type ($1, $3); }
2987         ;
2988
2989 typename_sub2:
2990           TYPENAME SCOPE
2991                 {
2992                   if (TREE_CODE ($1) != IDENTIFIER_NODE)
2993                     $1 = lastiddecl;
2994
2995                   /* Retrieve the type for the identifier, which might involve
2996                      some computation. */
2997                   got_scope = $$ = complete_type (IDENTIFIER_TYPE_VALUE ($1));
2998
2999                   if ($$ == error_mark_node)
3000                     cp_error ("`%T' is not a class or namespace", $1);
3001                 }
3002         | SELFNAME SCOPE
3003                 {
3004                   if (TREE_CODE ($1) != IDENTIFIER_NODE)
3005                     $$ = lastiddecl;
3006                   got_scope = $$ = complete_type (TREE_TYPE ($$));
3007                 }
3008         | template_type SCOPE
3009                 { got_scope = $$ = complete_type (TREE_TYPE ($$)); }
3010         | PTYPENAME SCOPE
3011         | IDENTIFIER SCOPE
3012         | NSNAME SCOPE
3013                 {
3014                   if (TREE_CODE ($$) == IDENTIFIER_NODE)
3015                     $$ = lastiddecl;
3016                   got_scope = $$;
3017                 }
3018         ;
3019
3020 explicit_template_type:
3021           identifier '<' template_arg_list_opt template_close_bracket
3022                 { $$ = build_min_nt (TEMPLATE_ID_EXPR, $1, $3); }
3023         ;
3024
3025 complex_type_name:
3026           global_scope type_name
3027                 {
3028                   if (TREE_CODE ($2) == IDENTIFIER_NODE)
3029                     $$ = IDENTIFIER_GLOBAL_VALUE ($2);
3030                   else
3031                     $$ = $2;
3032                   got_scope = NULL_TREE;
3033                 }
3034         | nested_type
3035         | global_scope nested_type
3036                 { $$ = $2; }
3037         ;
3038
3039 ptr_to_mem:
3040           nested_name_specifier '*'
3041                 { got_scope = NULL_TREE; }
3042         | global_scope nested_name_specifier '*'
3043                 { $$ = $2; got_scope = NULL_TREE; }
3044         ;
3045
3046 /* All uses of explicit global scope must go through this nonterminal so
3047    that got_scope will be set before yylex is called to get the next token.  */
3048 global_scope:
3049           SCOPE
3050                 { got_scope = void_type_node; }
3051         ;
3052
3053 /* ANSI new-declarator (5.3.4) */
3054 new_declarator:
3055           '*' cv_qualifiers new_declarator
3056                 { $$ = make_pointer_declarator ($2, $3); }
3057         | '*' cv_qualifiers  %prec EMPTY
3058                 { $$ = make_pointer_declarator ($2, NULL_TREE); }
3059         | '&' cv_qualifiers new_declarator  %prec EMPTY
3060                 { $$ = make_reference_declarator ($2, $3); }
3061         | '&' cv_qualifiers  %prec EMPTY
3062                 { $$ = make_reference_declarator ($2, NULL_TREE); }
3063         | ptr_to_mem cv_qualifiers  %prec EMPTY
3064                 { tree arg = make_pointer_declarator ($2, NULL_TREE);
3065                   $$ = build_parse_node (SCOPE_REF, $1, arg);
3066                 }
3067         | ptr_to_mem cv_qualifiers new_declarator
3068                 { tree arg = make_pointer_declarator ($2, $3);
3069                   $$ = build_parse_node (SCOPE_REF, $1, arg);
3070                 }
3071         | direct_new_declarator  %prec EMPTY
3072         ;
3073
3074 /* ANSI direct-new-declarator (5.3.4) */
3075 direct_new_declarator:
3076           '[' expr ']'
3077                 { $$ = build_parse_node (ARRAY_REF, NULL_TREE, $2); }
3078         | direct_new_declarator '[' nonmomentary_expr ']'
3079                 { $$ = build_parse_node (ARRAY_REF, $$, $3); }
3080         ;
3081
3082 absdcl_intern:
3083           absdcl
3084         | attributes absdcl
3085                 {
3086                   /* Provide support for '(' attributes '*' declarator ')'
3087                      etc */
3088                   $$ = decl_tree_cons ($1, $2, NULL_TREE);
3089                 }
3090         ;
3091         
3092 /* ANSI abstract-declarator (8.1) */
3093 absdcl:
3094           '*' nonempty_cv_qualifiers absdcl_intern
3095                 { $$ = make_pointer_declarator ($2.t, $3); }
3096         | '*' absdcl_intern
3097                 { $$ = make_pointer_declarator (NULL_TREE, $2); }
3098         | '*' nonempty_cv_qualifiers  %prec EMPTY
3099                 { $$ = make_pointer_declarator ($2.t, NULL_TREE); }
3100         | '*'  %prec EMPTY
3101                 { $$ = make_pointer_declarator (NULL_TREE, NULL_TREE); }
3102         | '&' nonempty_cv_qualifiers absdcl_intern
3103                 { $$ = make_reference_declarator ($2.t, $3); }
3104         | '&' absdcl_intern
3105                 { $$ = make_reference_declarator (NULL_TREE, $2); }
3106         | '&' nonempty_cv_qualifiers  %prec EMPTY
3107                 { $$ = make_reference_declarator ($2.t, NULL_TREE); }
3108         | '&'  %prec EMPTY
3109                 { $$ = make_reference_declarator (NULL_TREE, NULL_TREE); }
3110         | ptr_to_mem cv_qualifiers  %prec EMPTY
3111                 { tree arg = make_pointer_declarator ($2, NULL_TREE);
3112                   $$ = build_parse_node (SCOPE_REF, $1, arg);
3113                 }
3114         | ptr_to_mem cv_qualifiers absdcl_intern
3115                 { tree arg = make_pointer_declarator ($2, $3);
3116                   $$ = build_parse_node (SCOPE_REF, $1, arg);
3117                 }
3118         | direct_abstract_declarator  %prec EMPTY
3119         ;
3120
3121 /* ANSI direct-abstract-declarator (8.1) */
3122 direct_abstract_declarator:
3123           '(' absdcl_intern ')'
3124                 { $$ = $2; }
3125           /* `(typedef)1' is `int'.  */
3126         | direct_abstract_declarator '(' parmlist ')' cv_qualifiers exception_specification_opt  %prec '.'
3127                 { $$ = make_call_declarator ($$, $3, $5, $6); }
3128         | direct_abstract_declarator LEFT_RIGHT cv_qualifiers exception_specification_opt  %prec '.'
3129                 { $$ = make_call_declarator ($$, empty_parms (), $3, $4); }
3130         | direct_abstract_declarator '[' nonmomentary_expr ']'  %prec '.'
3131                 { $$ = build_parse_node (ARRAY_REF, $$, $3); }
3132         | direct_abstract_declarator '[' ']'  %prec '.'
3133                 { $$ = build_parse_node (ARRAY_REF, $$, NULL_TREE); }
3134         | '(' complex_parmlist ')' cv_qualifiers exception_specification_opt  %prec '.'
3135                 { $$ = make_call_declarator (NULL_TREE, $2, $4, $5); }
3136         | regcast_or_absdcl cv_qualifiers exception_specification_opt  %prec '.'
3137                 { set_quals_and_spec ($$, $2, $3); }
3138         | fcast_or_absdcl cv_qualifiers exception_specification_opt  %prec '.'
3139                 { set_quals_and_spec ($$, $2, $3); }
3140         | '[' nonmomentary_expr ']'  %prec '.'
3141                 { $$ = build_parse_node (ARRAY_REF, NULL_TREE, $2); }
3142         | '[' ']'  %prec '.'
3143                 { $$ = build_parse_node (ARRAY_REF, NULL_TREE, NULL_TREE); }
3144         ;
3145
3146 /* For C++, decls and stmts can be intermixed, so we don't need to
3147    have a special rule that won't start parsing the stmt section
3148    until we have a stmt that parses without errors.  */
3149
3150 stmts:
3151           stmt
3152         | errstmt
3153         | stmts stmt
3154         | stmts errstmt
3155         ;
3156
3157 errstmt:
3158           error ';'
3159         ;
3160
3161 /* Read zero or more forward-declarations for labels
3162    that nested functions can jump to.  */
3163 maybe_label_decls:
3164           /* empty */
3165         | label_decls
3166                 { if (pedantic)
3167                     pedwarn ("ANSI C++ forbids label declarations"); }
3168         ;
3169
3170 label_decls:
3171           label_decl
3172         | label_decls label_decl
3173         ;
3174
3175 label_decl:
3176           LABEL identifiers_or_typenames ';'
3177                 { tree link;
3178                   for (link = $2; link; link = TREE_CHAIN (link))
3179                     {
3180                       tree label = shadow_label (TREE_VALUE (link));
3181                       C_DECLARED_LABEL_FLAG (label) = 1;
3182                       declare_nonlocal_label (label);
3183                     }
3184                 }
3185         ;
3186
3187 /* This is the body of a function definition.
3188    It causes syntax errors to ignore to the next openbrace.  */
3189 compstmt_or_error:
3190           compstmt
3191                 {}
3192         | error compstmt
3193         ;
3194
3195 compstmt:
3196           '{'
3197                 { $<ttype>$ = begin_compound_stmt (0); }
3198           compstmtend 
3199                 { $$ = finish_compound_stmt (0, $<ttype>2); }
3200         ;
3201
3202 simple_if:
3203           IF
3204                 {
3205                   $<ttype>$ = begin_if_stmt ();
3206                   cond_stmt_keyword = "if";
3207                 }
3208             paren_cond_or_null
3209                 { finish_if_stmt_cond ($3, $<ttype>2); }
3210             implicitly_scoped_stmt
3211                 { $<ttype>$ = finish_then_clause ($<ttype>2); }
3212         ;
3213
3214 implicitly_scoped_stmt:
3215           compstmt
3216         |       { $<ttype>$ = begin_compound_stmt (0); }
3217           simple_stmt 
3218                 { $$ = finish_compound_stmt (0, $<ttype>1); }
3219         ;
3220
3221 stmt:
3222           compstmt
3223                 {}
3224         | simple_stmt
3225         ;
3226
3227 simple_stmt:
3228           decl
3229                 { finish_stmt (); }
3230         | expr ';'
3231                 { finish_expr_stmt ($1); }
3232         | simple_if ELSE
3233                 { begin_else_clause (); }
3234           implicitly_scoped_stmt
3235                 { 
3236                   finish_else_clause ($<ttype>1); 
3237                   finish_if_stmt ();
3238                 }
3239         | simple_if  %prec IF
3240                 { finish_if_stmt (); }
3241         | WHILE
3242                 {
3243                   $<ttype>$ = begin_while_stmt ();
3244                   cond_stmt_keyword = "while";
3245                 }
3246           paren_cond_or_null
3247                 { finish_while_stmt_cond ($3, $<ttype>2); }
3248           already_scoped_stmt
3249                 { finish_while_stmt ($<ttype>2); }
3250         | DO
3251                 { $<ttype>$ = begin_do_stmt (); }
3252           implicitly_scoped_stmt WHILE
3253                 {
3254                   finish_do_body ($<ttype>2);
3255                   cond_stmt_keyword = "do";
3256                 }
3257           paren_expr_or_null ';'
3258                 { finish_do_stmt ($6, $<ttype>2); }
3259         | FOR
3260                 { $<ttype>$ = begin_for_stmt (); }
3261           '(' for.init.statement
3262                 { finish_for_init_stmt ($<ttype>2); }
3263           xcond ';'
3264                 { finish_for_cond ($6, $<ttype>2); }
3265           xexpr ')'
3266                 { finish_for_expr ($9, $<ttype>2); }
3267           already_scoped_stmt
3268                 { finish_for_stmt ($9, $<ttype>2); }
3269         | SWITCH 
3270                 { begin_switch_stmt (); }
3271             '(' condition ')'
3272                 { $<ttype>$ = finish_switch_cond ($4); }
3273           implicitly_scoped_stmt
3274                 { finish_switch_stmt ($4, $<ttype>6); }
3275         | CASE expr_no_commas ':'
3276                 { finish_case_label ($2, NULL_TREE); }
3277           stmt
3278         | CASE expr_no_commas ELLIPSIS expr_no_commas ':'
3279                 { finish_case_label ($2, $4); }
3280           stmt
3281         | DEFAULT ':'
3282                 { finish_case_label (NULL_TREE, NULL_TREE); }
3283           stmt
3284         | BREAK ';'
3285                 { finish_break_stmt (); }
3286         | CONTINUE ';'
3287                 { finish_continue_stmt (); }
3288         | RETURN_KEYWORD ';'
3289                 { finish_return_stmt (NULL_TREE); }
3290         | RETURN_KEYWORD expr ';'
3291                 { finish_return_stmt ($2); }
3292         | asm_keyword maybe_cv_qualifier '(' string ')' ';'
3293                 { 
3294                   finish_asm_stmt ($2, $4, NULL_TREE, NULL_TREE,
3295                                    NULL_TREE); 
3296                 }
3297         /* This is the case with just output operands.  */
3298         | asm_keyword maybe_cv_qualifier '(' string ':' asm_operands ')' ';'
3299                 { 
3300                   finish_asm_stmt ($2, $4, $6, NULL_TREE,
3301                                    NULL_TREE); 
3302                 }
3303         /* This is the case with input operands as well.  */
3304         | asm_keyword maybe_cv_qualifier '(' string ':' asm_operands ':' asm_operands ')' ';'
3305                 { finish_asm_stmt ($2, $4, $6, $8, NULL_TREE); }
3306         /* This is the case with clobbered registers as well.  */
3307         | asm_keyword maybe_cv_qualifier '(' string ':' asm_operands ':'
3308           asm_operands ':' asm_clobbers ')' ';'
3309                 { finish_asm_stmt ($2, $4, $6, $8, $10); }
3310         | GOTO '*' expr ';'
3311                 { 
3312                   if (pedantic)
3313                     pedwarn ("ANSI C++ forbids computed gotos");
3314                   finish_goto_stmt ($3);
3315                 }
3316         | GOTO identifier ';'
3317                 { finish_goto_stmt ($2); }
3318         | label_colon stmt
3319                 { finish_stmt (); }
3320         | label_colon '}'
3321                 { error ("label must be followed by statement");
3322                   yyungetc ('}', 0);
3323                   finish_stmt (); }
3324         | ';'
3325                 { finish_stmt (); }
3326         | try_block
3327         | using_directive
3328         | namespace_using_decl
3329                 { do_local_using_decl ($1); }
3330         | namespace_alias
3331         ;
3332
3333 function_try_block:
3334           TRY
3335                 { $<ttype>$ = begin_function_try_block (); }
3336           ctor_initializer_opt compstmt
3337                 { finish_function_try_block ($<ttype>2); }
3338           handler_seq
3339                 {
3340                   finish_function_handler_sequence ($<ttype>2);
3341                   $$ = $3;
3342                 }
3343         ;
3344
3345 try_block:
3346           TRY
3347                 { $<ttype>$ = begin_try_block (); }
3348           compstmt
3349                 { finish_try_block ($<ttype>2); }
3350           handler_seq
3351                 { finish_handler_sequence ($<ttype>2); }
3352         ;
3353
3354 handler_seq:
3355           handler
3356         | handler_seq handler
3357         ;
3358
3359 handler:
3360           CATCH
3361                 { $<ttype>$ = begin_handler(); }
3362           handler_args
3363                 { finish_handler_parms ($<ttype>2); }
3364           compstmt
3365                 { finish_handler ($<ttype>2); }
3366         ;
3367
3368 type_specifier_seq:
3369           typed_typespecs  %prec EMPTY
3370         | nonempty_cv_qualifiers  %prec EMPTY
3371         ;
3372
3373 handler_args:
3374           '(' ELLIPSIS ')'
3375                 { expand_start_catch_block (NULL_TREE, NULL_TREE); }
3376         /* This doesn't allow reference parameters, the below does.
3377         | '(' type_specifier_seq absdcl ')'
3378                 { check_for_new_type ("inside exception declarations", $2);
3379                   expand_start_catch_block ($2.t, $3); }
3380         | '(' type_specifier_seq ')'
3381                 { check_for_new_type ("inside exception declarations", $2);
3382                   expand_start_catch_block ($2.t, NULL_TREE); }
3383         | '(' type_specifier_seq notype_declarator ')'
3384                 { check_for_new_type ("inside exception declarations", $2);
3385                   expand_start_catch_block ($2.t, $3); }
3386         | '(' typed_typespecs after_type_declarator ')'
3387                 { check_for_new_type ("inside exception declarations", $2);
3388                   expand_start_catch_block ($2.t, $3); }
3389         This allows reference parameters...  */
3390         | '(' parm ')'
3391                 { check_for_new_type ("inside exception declarations", $2);
3392                   expand_start_catch_block (TREE_PURPOSE ($2.t),
3393                                             TREE_VALUE ($2.t)); }
3394         ;
3395
3396 label_colon:
3397           IDENTIFIER ':'
3398                 { tree label;
3399                 do_label:
3400                   label = define_label (input_filename, lineno, $1);
3401                   if (label && ! minimal_parse_mode)
3402                     expand_label (label);
3403                 }
3404         | PTYPENAME ':'
3405                 { goto do_label; }
3406         | TYPENAME ':'
3407                 { goto do_label; }
3408         | SELFNAME ':'
3409                 { goto do_label; }
3410         ;
3411
3412 for.init.statement:
3413           xexpr ';'
3414                 { if ($1) cplus_expand_expr_stmt ($1); }
3415         | decl
3416         | '{' compstmtend
3417                 { if (pedantic)
3418                     pedwarn ("ANSI C++ forbids compound statements inside for initializations");
3419                 }
3420         ;
3421
3422 /* Either a type-qualifier or nothing.  First thing in an `asm' statement.  */
3423
3424 maybe_cv_qualifier:
3425           /* empty */
3426                 { emit_line_note (input_filename, lineno);
3427                   $$ = NULL_TREE; }
3428         | CV_QUALIFIER
3429                 { emit_line_note (input_filename, lineno); }
3430         ;
3431
3432 xexpr:
3433           /* empty */
3434                 { $$ = NULL_TREE; }
3435         | expr
3436         | error
3437                 { $$ = NULL_TREE; }
3438         ;
3439
3440 /* These are the operands other than the first string and colon
3441    in  asm ("addextend %2,%1": "=dm" (x), "0" (y), "g" (*x))  */
3442 asm_operands:
3443           /* empty */
3444                 { $$ = NULL_TREE; }
3445         | nonnull_asm_operands
3446         ;
3447
3448 nonnull_asm_operands:
3449           asm_operand
3450         | nonnull_asm_operands ',' asm_operand
3451                 { $$ = chainon ($$, $3); }
3452         ;
3453
3454 asm_operand:
3455           STRING '(' expr ')'
3456                 { $$ = build_tree_list ($$, $3); }
3457         ;
3458
3459 asm_clobbers:
3460           STRING
3461                 { $$ = tree_cons (NULL_TREE, $$, NULL_TREE); }
3462         | asm_clobbers ',' STRING
3463                 { $$ = tree_cons (NULL_TREE, $3, $$); }
3464         ;
3465
3466 /* This is what appears inside the parens in a function declarator.
3467    Its value is represented in the format that grokdeclarator expects.
3468
3469    In C++, declaring a function with no parameters
3470    means that that function takes *no* parameters.  */
3471
3472 parmlist:
3473           /* empty */
3474                 {
3475                   $$ = empty_parms();
3476                 }
3477         | complex_parmlist
3478         | type_id
3479                 { $$ = finish_parmlist (build_tree_list (NULL_TREE, $1.t), 0);
3480                   check_for_new_type ("inside parameter list", $1); }
3481         ;
3482
3483 /* This nonterminal does not include the common sequence '(' type_id ')',
3484    as it is ambiguous and must be disambiguated elsewhere.  */
3485 complex_parmlist:
3486           parms
3487                 { $$ = finish_parmlist ($$, 0); }
3488         | parms_comma ELLIPSIS
3489                 { $$ = finish_parmlist ($1, 1); }
3490         /* C++ allows an ellipsis without a separating ',' */
3491         | parms ELLIPSIS
3492                 { $$ = finish_parmlist ($1, 1); }
3493         | type_id ELLIPSIS
3494                 { $$ = finish_parmlist (build_tree_list (NULL_TREE,
3495                                                          $1.t), 1); } 
3496         | ELLIPSIS
3497                 { $$ = finish_parmlist (NULL_TREE, 1); }
3498         | parms ':'
3499                 {
3500                   /* This helps us recover from really nasty
3501                      parse errors, for example, a missing right
3502                      parenthesis.  */
3503                   yyerror ("possibly missing ')'");
3504                   $$ = finish_parmlist ($1, 0);
3505                   yyungetc (':', 0);
3506                   yychar = ')';
3507                 }
3508         | type_id ':'
3509                 {
3510                   /* This helps us recover from really nasty
3511                      parse errors, for example, a missing right
3512                      parenthesis.  */
3513                   yyerror ("possibly missing ')'");
3514                   $$ = finish_parmlist (build_tree_list (NULL_TREE,
3515                                                          $1.t), 0); 
3516                   yyungetc (':', 0);
3517                   yychar = ')';
3518                 }
3519         ;
3520
3521 /* A default argument to a */
3522 defarg:
3523           '='
3524                 { maybe_snarf_defarg (); }
3525           defarg1
3526                 { $$ = $3; }
3527         ;
3528
3529 defarg1:
3530           DEFARG
3531         | init
3532         ;
3533
3534 /* A nonempty list of parameter declarations or type names.  */
3535 parms:
3536           named_parm
3537                 { check_for_new_type ("in a parameter list", $1);
3538                   $$ = build_tree_list (NULL_TREE, $1.t); }
3539         | parm defarg
3540                 { check_for_new_type ("in a parameter list", $1);
3541                   $$ = build_tree_list ($2, $1.t); }
3542         | parms_comma full_parm
3543                 { check_for_new_type ("in a parameter list", $2);
3544                   $$ = chainon ($$, $2.t); }
3545         | parms_comma bad_parm
3546                 { $$ = chainon ($$, build_tree_list (NULL_TREE, $2)); }
3547         | parms_comma bad_parm '=' init
3548                 { $$ = chainon ($$, build_tree_list ($4, $2)); }
3549         ;
3550
3551 parms_comma:
3552           parms ','
3553         | type_id ','
3554                 { check_for_new_type ("in a parameter list", $1);
3555                   $$ = build_tree_list (NULL_TREE, $1.t); }
3556         ;
3557
3558 /* A single parameter declaration or parameter type name,
3559    as found in a parmlist.  */
3560 named_parm:
3561         /* Here we expand typed_declspecs inline to avoid mis-parsing of
3562            TYPESPEC IDENTIFIER.  */
3563           typed_declspecs1 declarator
3564                 { tree specs = strip_attrs ($1.t);
3565                   $$.new_type_flag = $1.new_type_flag;
3566                   $$.t = build_tree_list (specs, $2); }
3567         | typed_typespecs declarator
3568                 { $$.t = build_tree_list ($1.t, $2); 
3569                   $$.new_type_flag = $1.new_type_flag; }
3570         | typespec declarator
3571                 { $$.t = build_tree_list (build_decl_list (NULL_TREE, $1.t),
3572                                           $2); 
3573                   $$.new_type_flag = $1.new_type_flag; }
3574         | typed_declspecs1 absdcl
3575                 { tree specs = strip_attrs ($1.t);
3576                   $$.t = build_tree_list (specs, $2);
3577                   $$.new_type_flag = $1.new_type_flag; }
3578         | typed_declspecs1  %prec EMPTY
3579                 { tree specs = strip_attrs ($1.t);
3580                   $$.t = build_tree_list (specs, NULL_TREE); 
3581                   $$.new_type_flag = $1.new_type_flag; }
3582         | declmods notype_declarator
3583                 { tree specs = strip_attrs ($1);
3584                   $$.t = build_tree_list (specs, $2); 
3585                   $$.new_type_flag = 0; }
3586         ;
3587
3588 full_parm:
3589           parm
3590                 { $$.t = build_tree_list (NULL_TREE, $1.t);
3591                   $$.new_type_flag = $1.new_type_flag;  }
3592         | parm defarg
3593                 { $$.t = build_tree_list ($2, $1.t);
3594                   $$.new_type_flag = $1.new_type_flag;  }
3595         ;
3596
3597 parm:
3598           named_parm
3599         | type_id
3600         ;
3601
3602 see_typename:
3603           /* empty */  %prec EMPTY
3604                 { see_typename (); }
3605         ;
3606
3607 bad_parm:
3608           /* empty */ %prec EMPTY
3609                 {
3610                   error ("type specifier omitted for parameter");
3611                   $$ = build_tree_list (integer_type_node, NULL_TREE);
3612                 }
3613         | notype_declarator
3614                 {
3615                   error ("type specifier omitted for parameter");
3616                   if (TREE_CODE ($$) == SCOPE_REF
3617                       && (TREE_CODE (TREE_OPERAND ($$, 0)) == TEMPLATE_TYPE_PARM
3618                           || TREE_CODE (TREE_OPERAND ($$, 0)) == TEMPLATE_TEMPLATE_PARM))
3619                     cp_error ("  perhaps you want `typename %E' to make it a type", $$);
3620                   $$ = build_tree_list (integer_type_node, $$);
3621                 }
3622         ;
3623
3624 exception_specification_opt:
3625           /* empty */  %prec EMPTY
3626                 { $$ = NULL_TREE; }
3627         | THROW '(' ansi_raise_identifiers  ')'  %prec EMPTY
3628                 { $$ = $3; }
3629         | THROW LEFT_RIGHT  %prec EMPTY
3630                 { $$ = empty_except_spec; }
3631         ;
3632
3633 ansi_raise_identifier:
3634           type_id
3635                 {
3636                   check_for_new_type ("exception specifier", $1);
3637                   $$ = groktypename ($1.t);
3638                 }
3639         ;
3640
3641 ansi_raise_identifiers:
3642           ansi_raise_identifier
3643                 { $$ = add_exception_specifier (NULL_TREE, $1, 1); }
3644         | ansi_raise_identifiers ',' ansi_raise_identifier
3645                 { $$ = add_exception_specifier ($1, $3, 1); }
3646         ;
3647
3648 conversion_declarator:
3649           /* empty */  %prec EMPTY
3650                 { $$ = NULL_TREE; }
3651         | '*' cv_qualifiers conversion_declarator
3652                 { $$ = make_pointer_declarator ($2, $3); }
3653         | '&' cv_qualifiers conversion_declarator
3654                 { $$ = make_reference_declarator ($2, $3); }
3655         | ptr_to_mem cv_qualifiers conversion_declarator
3656                 { tree arg = make_pointer_declarator ($2, $3);
3657                   $$ = build_parse_node (SCOPE_REF, $1, arg);
3658                 }
3659         ;
3660
3661 operator:
3662           OPERATOR
3663                 { got_scope = NULL_TREE; }
3664         ;
3665
3666 operator_name:
3667           operator '*'
3668                 { $$ = ansi_opname[MULT_EXPR]; }
3669         | operator '/'
3670                 { $$ = ansi_opname[TRUNC_DIV_EXPR]; }
3671         | operator '%'
3672                 { $$ = ansi_opname[TRUNC_MOD_EXPR]; }
3673         | operator '+'
3674                 { $$ = ansi_opname[PLUS_EXPR]; }
3675         | operator '-'
3676                 { $$ = ansi_opname[MINUS_EXPR]; }
3677         | operator '&'
3678                 { $$ = ansi_opname[BIT_AND_EXPR]; }
3679         | operator '|'
3680                 { $$ = ansi_opname[BIT_IOR_EXPR]; }
3681         | operator '^'
3682                 { $$ = ansi_opname[BIT_XOR_EXPR]; }
3683         | operator '~'
3684                 { $$ = ansi_opname[BIT_NOT_EXPR]; }
3685         | operator ','
3686                 { $$ = ansi_opname[COMPOUND_EXPR]; }
3687         | operator ARITHCOMPARE
3688                 { $$ = ansi_opname[$2]; }
3689         | operator '<'
3690                 { $$ = ansi_opname[LT_EXPR]; }
3691         | operator '>'
3692                 { $$ = ansi_opname[GT_EXPR]; }
3693         | operator EQCOMPARE
3694                 { $$ = ansi_opname[$2]; }
3695         | operator ASSIGN
3696                 { $$ = ansi_assopname[$2]; }
3697         | operator '='
3698                 { $$ = ansi_opname [MODIFY_EXPR]; }
3699         | operator LSHIFT
3700                 { $$ = ansi_opname[$2]; }
3701         | operator RSHIFT
3702                 { $$ = ansi_opname[$2]; }
3703         | operator PLUSPLUS
3704                 { $$ = ansi_opname[POSTINCREMENT_EXPR]; }
3705         | operator MINUSMINUS
3706                 { $$ = ansi_opname[PREDECREMENT_EXPR]; }
3707         | operator ANDAND
3708                 { $$ = ansi_opname[TRUTH_ANDIF_EXPR]; }
3709         | operator OROR
3710                 { $$ = ansi_opname[TRUTH_ORIF_EXPR]; }
3711         | operator '!'
3712                 { $$ = ansi_opname[TRUTH_NOT_EXPR]; }
3713         | operator '?' ':'
3714                 { $$ = ansi_opname[COND_EXPR]; }
3715         | operator MIN_MAX
3716                 { $$ = ansi_opname[$2]; }
3717         | operator POINTSAT  %prec EMPTY
3718                 { $$ = ansi_opname[COMPONENT_REF]; }
3719         | operator POINTSAT_STAR  %prec EMPTY
3720                 { $$ = ansi_opname[MEMBER_REF]; }
3721         | operator LEFT_RIGHT
3722                 { $$ = ansi_opname[CALL_EXPR]; }
3723         | operator '[' ']'
3724                 { $$ = ansi_opname[ARRAY_REF]; }
3725         | operator NEW  %prec EMPTY
3726                 { $$ = ansi_opname[NEW_EXPR]; }
3727         | operator DELETE  %prec EMPTY
3728                 { $$ = ansi_opname[DELETE_EXPR]; }
3729         | operator NEW '[' ']'
3730                 { $$ = ansi_opname[VEC_NEW_EXPR]; }
3731         | operator DELETE '[' ']'
3732                 { $$ = ansi_opname[VEC_DELETE_EXPR]; }
3733         /* Names here should be looked up in class scope ALSO.  */
3734         | operator type_specifier_seq conversion_declarator
3735                 { $$ = grokoptypename ($2.t, $3); }
3736         | operator error
3737                 { $$ = ansi_opname[ERROR_MARK]; }
3738         ;
3739
3740 %%
3741
3742 #ifdef SPEW_DEBUG
3743 const char *
3744 debug_yytranslate (value)
3745     int value;
3746 {
3747   return yytname[YYTRANSLATE (value)];
3748 }
3749
3750 #endif