1####################################################
2#                                                  #
3#                *** WARNING ***                   #
4#                                                  #
5# This test will try to parse a full C++ grammar,  #
6# so it will use a huge ammount of CPU and memory. #
7#                                                  #
8# So, be patient, specially for test #2...         #
9#                                                  #
10####################################################
11$^W=0;
12
13# Before `make install' is performed this script should be runnable with
14# `make test'. After `make install' it should work as `perl test.pl'
15
16######################### We start with some black magic to print on failure.
17
18# Change 1..1 below to 1..last_test_to_print .
19# (It may become useful if the test is moved to ./t subdirectory.)
20
21BEGIN { $| = 1; print "1..10\n"; }
22END {print "not ok 1\n" unless $loaded;}
23use Parse::Yapp;
24$loaded = 1;
25print "ok 1\n";
26
27######################### End of black magic.
28
29# Insert your test code below (better if it prints "ok 13"
30# (correspondingly "not ok 13") depending on the success of chunk 13
31# of the test code):
32
33use Parse::Yapp;
34
35my($testnum)=2;
36my($parser,$grammar);
37my($yapptxt);
38
39#Test 2
40eval  {
41	$grammar=join('',<DATA>);
42	$parser=new Parse::Yapp(input => $grammar);
43};
44
45	$@
46and	do {
47	print "not ok $testnum\n";
48	print "Object not created. Cannot continue test suite: aborting\n";
49	exit(1);
50};
51print "ok ", $testnum++, "\n";
52
53#Test 3
54    keys(%{$parser->{GRAMMAR}{NULLABLE}}) == 43
55or  print "not ";
56print "ok ", $testnum++, "\n";
57
58#Test 4
59    keys(%{$parser->{GRAMMAR}{NTERM}}) == 233
60or  print "not ";
61print "ok ", $testnum++, "\n";
62
63#Test 5
64    @{$parser->{GRAMMAR}{UUTERM}} == 3
65or  print "not ";
66print "ok ", $testnum++, "\n";
67
68#Test 6
69    keys(%{$parser->{GRAMMAR}{TERM}}) == 108
70or  print "not ";
71print "ok ", $testnum++, "\n";
72
73#Test 7
74    @{$parser->{GRAMMAR}{RULES}} ==  825
75or  print "not ";
76print "ok ", $testnum++, "\n";
77
78#Test 8
79    @{$parser->{STATES}} ==  1611
80or  print "not ";
81print "ok ", $testnum++, "\n";
82
83#Test 9
84    keys(%{$parser->{CONFLICTS}{SOLVED}}) == 115
85or  print "not ";
86print "ok ", $testnum++, "\n";
87
88#Test 10
89    (    $parser->{CONFLICTS}{FORCED}{TOTAL}[0] == 30
90     and $parser->{CONFLICTS}{FORCED}{TOTAL}[1] == 42 )
91or  print "not ";
92print "ok ", $testnum++, "\n";
93
94
95__DATA__
96/* 
97   This grammar is a stripped form of the original C++ grammar
98   from the GNU CC compiler :
99
100   YACC parser for C++ syntax.
101   Copyright (C) 1988, 89, 93-98, 1999 Free Software Foundation, Inc.
102   Hacked by Michael Tiemann (tiemann@cygnus.com)
103
104   The full gcc compiler an the original grammar file are freely
105   available under the GPL license at :
106
107   ftp://ftp.gnu.org/gnu/gcc/
108*/
109
110%{
111
112$language_string = "GNU C++";
113
114%}
115
116%start program
117
118/* All identifiers that are not reserved words
119   and are not declared typedefs in the current block */
120%token IDENTIFIER
121
122/* All identifiers that are declared typedefs in the current block.
123   In some contexts, they are treated just like IDENTIFIER,
124   but they can also serve as typespecs in declarations.  */
125%token TYPENAME
126%token SELFNAME
127
128/* A template function.  */
129%token PFUNCNAME
130
131/* Reserved words that specify storage class.
132   yylval contains an IDENTIFIER_NODE which indicates which one.  */
133%token SCSPEC
134
135/* Reserved words that specify type.
136   yylval contains an IDENTIFIER_NODE which indicates which one.  */
137%token TYPESPEC
138
139/* Reserved words that qualify type: "const" or "volatile".
140   yylval contains an IDENTIFIER_NODE which indicates which one.  */
141%token CV_QUALIFIER
142
143/* Character or numeric constants.
144   yylval is the node for the constant.  */
145%token CONSTANT
146
147/* String constants in raw form.
148   yylval is a STRING_CST node.  */
149%token STRING
150
151/* "...", used for functions with variable arglists.  */
152%token ELLIPSIS
153
154/* the reserved words */
155/* SCO include files test "ASM", so use something else.  */
156%token SIZEOF ENUM /* STRUCT UNION */ IF ELSE WHILE DO FOR SWITCH CASE DEFAULT
157%token BREAK CONTINUE RETURN_KEYWORD GOTO ASM_KEYWORD TYPEOF ALIGNOF
158%token SIGOF
159%token ATTRIBUTE EXTENSION LABEL
160%token REALPART IMAGPART
161
162/* the reserved words... C++ extensions */
163%token AGGR
164%token VISSPEC
165%token DELETE NEW THIS OPERATOR CXX_TRUE CXX_FALSE
166%token NAMESPACE TYPENAME_KEYWORD USING
167%token LEFT_RIGHT TEMPLATE
168%token TYPEID DYNAMIC_CAST STATIC_CAST REINTERPRET_CAST CONST_CAST
169%token SCOPE
170
171/* Define the operator tokens and their precedences.
172   The value is an integer because, if used, it is the tree code
173   to use in the expression made from the operator.  */
174
175%left EMPTY			/* used to resolve s/r with epsilon */
176
177%left error
178
179/* Add precedence rules to solve dangling else s/r conflict */
180%nonassoc IF
181%nonassoc ELSE
182
183%left IDENTIFIER PFUNCNAME TYPENAME SELFNAME PTYPENAME SCSPEC TYPESPEC CV_QUALIFIER ENUM AGGR ELLIPSIS TYPEOF SIGOF OPERATOR NSNAME TYPENAME_KEYWORD
184
185%left '{' ',' ';'
186
187%nonassoc THROW
188%right ':'
189%right ASSIGN '='
190%right '?'
191%left OROR
192%left ANDAND
193%left '|'
194%left '^'
195%left '&'
196%left MIN_MAX
197%left EQCOMPARE
198%left ARITHCOMPARE '<' '>'
199%left LSHIFT RSHIFT
200%left '+' '-'
201%left '*' '/' '%'
202%left POINTSAT_STAR DOT_STAR
203%right UNARY PLUSPLUS MINUSMINUS '~'
204%left HYPERUNARY
205%left PAREN_STAR_PAREN LEFT_RIGHT
206%left POINTSAT '.' '(' '['
207
208%right SCOPE			/* C++ extension */
209%nonassoc NEW DELETE TRY CATCH
210
211/* C++ extensions */
212/* Not needed by yapp : already defined in the first %left directive */ 
213/* %token PTYPENAME */
214%token PRE_PARSED_FUNCTION_DECL EXTERN_LANG_STRING ALL
215%token PRE_PARSED_CLASS_DECL DEFARG DEFARG_MARKER
216/* in order to recognize aggr tags as defining and thus shadowing.  */
217%token TYPENAME_DEFN IDENTIFIER_DEFN PTYPENAME_DEFN
218
219/* Not needed by yapp : already defined in the first %left directive */ 
220/* %token NSNAME */
221
222/* Used in lex.c for parsing pragmas.  */
223%token END_OF_LINE
224
225/* lex.c and pt.c depend on this being the last token.  Define
226   any new tokens before this one!  */
227%token END_OF_SAVED_INPUT
228
229%{
230/* Deleted everything */
231%}
232
233%%
234program:
235	  /* empty */
236	| extdefs
237	;
238
239/* the reason for the strange actions in this rule
240 is so that notype_initdecls when reached via datadef
241 can find a valid list of type and sc specs in $0.  */
242
243extdefs:
244	  lang_extdef
245	| extdefs lang_extdef
246	;
247
248extdefs_opt:
249	  extdefs
250	| /* empty */
251	;
252
253dot_hush_warning:
254	;
255dot_warning_ok:
256	;
257
258extension:
259	EXTENSION
260	;
261
262asm_keyword:
263	  ASM_KEYWORD
264	;
265
266lang_extdef:
267	  extdef
268	;
269
270extdef:
271	  fndef eat_saved_input
272	| datadef
273	| template_def
274	| asm_keyword '(' string ')' ';'
275	| extern_lang_string '{' extdefs_opt '}'
276	| extern_lang_string dot_hush_warning fndef dot_warning_ok eat_saved_input
277	| extern_lang_string dot_hush_warning datadef dot_warning_ok
278	| NAMESPACE identifier '{'
279	  extdefs_opt '}'
280	| NAMESPACE '{'
281	  extdefs_opt '}'
282	| namespace_alias
283	| using_decl ';'
284	| using_directive
285	| extension extdef
286	;
287
288namespace_alias:
289          NAMESPACE identifier '=' 
290          any_id ';'
291	;
292
293using_decl:
294	  USING qualified_id
295	| USING global_scope qualified_id
296	| USING global_scope unqualified_id
297	;
298
299namespace_using_decl:
300	  USING namespace_qualifier identifier
301	| USING global_scope identifier
302	| USING global_scope namespace_qualifier identifier
303	;
304
305using_directive:
306	  USING NAMESPACE
307	  any_id ';'
308	;
309
310namespace_qualifier:
311	  NSNAME SCOPE
312	| namespace_qualifier NSNAME SCOPE
313	;
314
315any_id:
316	  unqualified_id
317	| qualified_id
318	| global_scope qualified_id
319	| global_scope unqualified_id
320	;
321
322extern_lang_string:
323	EXTERN_LANG_STRING
324	| extern_lang_string EXTERN_LANG_STRING
325	;
326
327template_header:
328	  TEMPLATE '<'
329	  template_parm_list '>'
330	| TEMPLATE '<' '>'
331	;
332
333template_parm_list:
334	  template_parm
335	| template_parm_list ',' template_parm
336	;
337
338maybe_identifier:
339	  identifier
340	|	/* empty */
341	;
342
343template_type_parm:
344	  aggr maybe_identifier
345	| TYPENAME_KEYWORD maybe_identifier
346	;
347
348template_template_parm:
349	  template_header aggr maybe_identifier
350	;
351
352template_parm:
353	/* The following rules introduce a new reduce/reduce
354	   conflict on the ',' and '>' input tokens: they are valid
355	   prefixes for a `structsp', which means they could match a
356	   nameless parameter.  See 14.6, paragraph 3.
357	   By putting them before the `parm' rule, we get
358	   their match before considering them nameless parameter
359	   declarations.  */
360	  template_type_parm
361	| template_type_parm '=' type_id
362	| parm
363	| parm '=' expr_no_commas  %prec ARITHCOMPARE
364	| template_template_parm
365	| template_template_parm '=' template_arg
366	;
367
368template_def:
369	  template_header template_extdef
370	| template_header error  %prec EMPTY
371	;
372
373template_extdef:
374	  fndef eat_saved_input
375	| template_datadef
376	| template_def
377	| extern_lang_string dot_hush_warning fndef dot_warning_ok eat_saved_input
378	| extern_lang_string dot_hush_warning template_datadef dot_warning_ok
379	| extension template_extdef
380	;
381
382template_datadef:
383	  nomods_initdecls ';'
384	| declmods notype_initdecls ';'
385	| typed_declspecs initdecls ';'
386	| structsp ';'
387	;
388
389datadef:
390	  nomods_initdecls ';'
391	| declmods notype_initdecls ';'
392	| typed_declspecs initdecls ';'
393        | declmods ';'
394	| explicit_instantiation ';'
395	| typed_declspecs ';'
396	| error ';'
397	| error '}'
398	| ';'
399	;
400
401ctor_initializer_opt:
402	  nodecls
403	| base_init
404	;
405
406maybe_return_init:
407	  /* empty */
408	| return_init
409	| return_init ';'
410	;
411
412eat_saved_input:
413	  /* empty */
414	| END_OF_SAVED_INPUT
415	;
416
417fndef:
418	  fn_dot_def1 maybe_return_init ctor_initializer_opt compstmt_or_error
419	| fn_dot_def1 maybe_return_init function_try_block
420	| fn_dot_def1 maybe_return_init error
421	;
422
423constructor_declarator:
424	  nested_name_specifier SELFNAME '(' 
425	  parmlist ')' cv_qualifiers exception_specification_opt
426	| nested_name_specifier SELFNAME LEFT_RIGHT cv_qualifiers exception_specification_opt
427	| global_scope nested_name_specifier SELFNAME '(' 
428	 parmlist ')' cv_qualifiers exception_specification_opt
429	| global_scope nested_name_specifier SELFNAME LEFT_RIGHT cv_qualifiers exception_specification_opt
430	| nested_name_specifier self_template_type '(' 
431	  parmlist ')' cv_qualifiers exception_specification_opt
432	| nested_name_specifier self_template_type LEFT_RIGHT cv_qualifiers exception_specification_opt
433	| global_scope nested_name_specifier self_template_type '(' 
434	 parmlist ')' cv_qualifiers exception_specification_opt
435	| global_scope nested_name_specifier self_template_type LEFT_RIGHT cv_qualifiers exception_specification_opt
436	;
437
438fn_dot_def1:
439	  typed_declspecs declarator
440	| declmods notype_declarator
441	| notype_declarator
442	| declmods constructor_declarator
443	| constructor_declarator
444	;
445
446component_constructor_declarator:
447	  SELFNAME '(' parmlist ')' cv_qualifiers exception_specification_opt
448	| SELFNAME LEFT_RIGHT cv_qualifiers exception_specification_opt
449	| self_template_type '(' parmlist ')' cv_qualifiers exception_specification_opt
450	| self_template_type LEFT_RIGHT cv_qualifiers exception_specification_opt
451	;
452
453/* more C++ complexity.  See component_decl for a comment on the
454   reduce/reduce conflict introduced by these rules.  */
455fn_dot_def2:
456	  declmods component_constructor_declarator
457	| component_constructor_declarator
458	| typed_declspecs declarator
459	| declmods notype_declarator
460	| notype_declarator
461	| declmods constructor_declarator
462	| constructor_declarator
463	;
464
465return_id:
466	  RETURN_KEYWORD IDENTIFIER
467	;
468
469return_init:
470	  return_id maybe_init
471	| return_id '(' nonnull_exprlist ')'
472	| return_id LEFT_RIGHT
473	;
474
475base_init:
476	  ':' dot_set_base_init member_init_list
477	;
478
479dot_set_base_init:
480	  /* empty */
481	;
482
483member_init_list:
484	  /* empty */
485	| member_init
486	| member_init_list ',' member_init
487	| member_init_list error
488	;
489
490member_init:
491	  '(' nonnull_exprlist ')'
492	| LEFT_RIGHT
493	| notype_identifier '(' nonnull_exprlist ')'
494	| notype_identifier LEFT_RIGHT
495	| nonnested_type '(' nonnull_exprlist ')'
496	| nonnested_type LEFT_RIGHT
497	| typename_sub '(' nonnull_exprlist ')'
498	| typename_sub LEFT_RIGHT
499	;
500
501identifier:
502	  IDENTIFIER
503	| TYPENAME
504	| SELFNAME
505	| PTYPENAME
506	| NSNAME
507	;
508
509notype_identifier:
510	  IDENTIFIER
511	| PTYPENAME 
512	| NSNAME  %prec EMPTY
513	;
514
515identifier_defn:
516	  IDENTIFIER_DEFN
517	| TYPENAME_DEFN
518	| PTYPENAME_DEFN
519	;
520
521explicit_instantiation:
522	  TEMPLATE begin_explicit_instantiation typespec ';'
523          end_explicit_instantiation
524	| TEMPLATE begin_explicit_instantiation typed_declspecs declarator
525          end_explicit_instantiation
526	| TEMPLATE begin_explicit_instantiation notype_declarator
527          end_explicit_instantiation
528	| TEMPLATE begin_explicit_instantiation constructor_declarator
529          end_explicit_instantiation
530	| SCSPEC TEMPLATE begin_explicit_instantiation typespec ';'
531          end_explicit_instantiation
532	| SCSPEC TEMPLATE begin_explicit_instantiation typed_declspecs 
533          declarator
534          end_explicit_instantiation
535	| SCSPEC TEMPLATE begin_explicit_instantiation notype_declarator
536          end_explicit_instantiation
537	| SCSPEC TEMPLATE begin_explicit_instantiation constructor_declarator
538          end_explicit_instantiation
539	;
540
541begin_explicit_instantiation: 
542	;
543
544end_explicit_instantiation: 
545	;
546
547/* The TYPENAME expansions are to deal with use of a template class name as
548  a template within the class itself, where the template decl is hidden by
549  a type decl.  Got all that?  */
550
551template_type:
552	  PTYPENAME '<' template_arg_list_opt template_close_bracket
553	    dot_finish_template_type
554	| TYPENAME  '<' template_arg_list_opt template_close_bracket
555	    dot_finish_template_type
556	| self_template_type
557	;
558
559apparent_template_type:
560	  template_type
561	| identifier '<' template_arg_list_opt '>'
562	    dot_finish_template_type
563	;
564
565self_template_type:
566	  SELFNAME  '<' template_arg_list_opt template_close_bracket
567	    dot_finish_template_type
568	;
569
570dot_finish_template_type:
571	;
572
573template_close_bracket:
574	  '>'
575	| RSHIFT 
576	;
577
578template_arg_list_opt:
579         /* empty */
580       | template_arg_list
581       ;
582
583template_arg_list:
584        template_arg
585	| template_arg_list ',' template_arg
586	;
587
588template_arg:
589	  type_id
590	| PTYPENAME
591	| expr_no_commas  %prec ARITHCOMPARE
592	;
593
594unop:
595	  '-'
596	| '+'
597	| PLUSPLUS
598	| MINUSMINUS
599	| '!'
600	;
601
602expr:
603	  nontrivial_exprlist
604	| expr_no_commas
605	;
606
607paren_expr_or_null:
608	LEFT_RIGHT
609	| '(' expr ')'
610	;
611
612paren_cond_or_null:
613	LEFT_RIGHT
614	| '(' condition ')'
615	;
616
617xcond:
618	  /* empty */
619	| condition
620	| error
621	;
622
623condition:
624	  type_specifier_seq declarator maybeasm maybe_attribute '='
625	| expr
626	;
627
628compstmtend:
629	  '}'
630	| maybe_label_decls stmts '}'
631	| maybe_label_decls stmts error '}'
632	| maybe_label_decls error '}'
633	;
634
635already_scoped_stmt:
636	  '{'
637	  compstmtend
638	| simple_stmt
639	;
640
641
642nontrivial_exprlist:
643	  expr_no_commas ',' expr_no_commas
644	| expr_no_commas ',' error
645	| nontrivial_exprlist ',' expr_no_commas
646	| nontrivial_exprlist ',' error
647	;
648
649nonnull_exprlist:
650	  expr_no_commas
651	| nontrivial_exprlist
652	;
653
654unary_expr:
655	  primary  %prec UNARY
656	/* __extension__ turns off -pedantic for following primary.  */
657	| extension cast_expr  	  %prec UNARY
658	| '*' cast_expr   %prec UNARY
659	| '&' cast_expr   %prec UNARY
660	| '~' cast_expr
661	| unop cast_expr  %prec UNARY
662	/* Refer to the address of a label as a pointer.  */
663	| ANDAND identifier
664	| SIZEOF unary_expr  %prec UNARY
665	| SIZEOF '(' type_id ')'  %prec HYPERUNARY
666	| ALIGNOF unary_expr  %prec UNARY
667	| ALIGNOF '(' type_id ')'  %prec HYPERUNARY
668
669	/* The %prec EMPTY's here are required by the = init initializer
670	   syntax extension; see below.  */
671	| new new_type_id  %prec EMPTY
672	| new new_type_id new_initializer
673	| new new_placement new_type_id  %prec EMPTY
674	| new new_placement new_type_id new_initializer
675        /* The dot_begin_new_placement in the following rules is
676	   necessary to avoid shift/reduce conflicts that lead to
677	   mis-parsing some expressions.  Of course, these constructs
678	   are not really new-placement and it is bogus to call
679	   begin_new_placement.  But, the parser cannot always tell at this
680	   point whether the next thing is an expression or a type-id,
681	   so there is nothing we can do.  Fortunately,
682	   begin_new_placement does nothing harmful.  When we rewrite
683	   the parser, this lossage should be removed, of course.  */
684	| new '(' dot_begin_new_placement type_id dot_finish_new_placement
685            %prec EMPTY
686	| new '(' dot_begin_new_placement type_id dot_finish_new_placement
687            new_initializer
688	| new new_placement '(' dot_begin_new_placement type_id
689	    dot_finish_new_placement   %prec EMPTY
690	| new new_placement '(' dot_begin_new_placement type_id
691	    dot_finish_new_placement  new_initializer
692
693	| delete cast_expr  %prec UNARY
694	| delete '[' ']' cast_expr  %prec UNARY
695	| delete '[' expr ']' cast_expr  %prec UNARY
696	| REALPART cast_expr %prec UNARY
697	| IMAGPART cast_expr %prec UNARY
698	;
699
700        /* Note this rule is not suitable for use in new_placement
701	   since it uses NULL_TREE as the argument to
702	   finish_new_placement.  This rule serves only to avoid
703	   reduce/reduce conflicts in unary_expr.  See the comments
704	   there on the use of begin/finish_new_placement.  */
705dot_finish_new_placement:
706	  ')'
707	;
708
709dot_begin_new_placement:
710	;
711
712new_placement:
713	  '(' dot_begin_new_placement nonnull_exprlist ')'
714	| '{' dot_begin_new_placement nonnull_exprlist '}'
715	;
716
717new_initializer:
718	  '(' nonnull_exprlist ')'
719	| LEFT_RIGHT
720	| '(' typespec ')'
721	/* GNU extension so people can use initializer lists.  Note that
722	   this alters the meaning of `new int = 1', which was previously
723	   syntactically valid but semantically invalid.  */
724	| '=' init
725	;
726
727/* This is necessary to postpone reduction of `int ((int)(int)(int))'.  */
728regcast_or_absdcl:
729	  '(' type_id ')'  %prec EMPTY
730	| regcast_or_absdcl '(' type_id ')'  %prec EMPTY
731	;
732
733cast_expr:
734	  unary_expr
735	| regcast_or_absdcl unary_expr  %prec UNARY
736	| regcast_or_absdcl '{' initlist maybecomma '}'  %prec UNARY
737	;
738
739expr_no_commas:
740	  cast_expr
741	/* Handle general members.  */
742	| expr_no_commas POINTSAT_STAR expr_no_commas
743	| expr_no_commas DOT_STAR expr_no_commas
744	| expr_no_commas '+' expr_no_commas
745	| expr_no_commas '-' expr_no_commas
746	| expr_no_commas '*' expr_no_commas
747	| expr_no_commas '/' expr_no_commas
748	| expr_no_commas '%' expr_no_commas
749	| expr_no_commas LSHIFT expr_no_commas
750	| expr_no_commas RSHIFT expr_no_commas
751	| expr_no_commas ARITHCOMPARE expr_no_commas
752	| expr_no_commas '<' expr_no_commas
753	| expr_no_commas '>' expr_no_commas
754	| expr_no_commas EQCOMPARE expr_no_commas
755	| expr_no_commas MIN_MAX expr_no_commas
756	| expr_no_commas '&' expr_no_commas
757	| expr_no_commas '|' expr_no_commas
758	| expr_no_commas '^' expr_no_commas
759	| expr_no_commas ANDAND expr_no_commas
760	| expr_no_commas OROR expr_no_commas
761	| expr_no_commas '?' xexpr ':' expr_no_commas
762	| expr_no_commas '=' expr_no_commas
763	| expr_no_commas ASSIGN expr_no_commas
764	| THROW
765	| THROW expr_no_commas
766/* These extensions are not defined.  The second arg to build_m_component_ref
767   is old, build_m_component_ref now does an implicit
768   build_indirect_ref (x, NULL_PTR) on the second argument.
769	| object '&' expr_no_commas  %prec UNARY
770		{ $$ = build_m_component_ref ($$, build_x_unary_op (ADDR_EXPR, $3)); }
771	| object unop expr_no_commas  %prec UNARY
772		{ $$ = build_m_component_ref ($$, build_x_unary_op ($2, $3)); }
773	| object '(' type_id ')' expr_no_commas  %prec UNARY
774		{ tree type = groktypename ($3.t);
775		  $$ = build_m_component_ref ($$, build_c_cast (type, $5)); }
776	| object primary_no_id  %prec UNARY
777		{ $$ = build_m_component_ref ($$, $2); }
778*/
779	;
780
781notype_unqualified_id:
782	  '~' see_typename identifier
783	| '~' see_typename template_type
784        | template_id
785	| operator_name
786	| IDENTIFIER
787	| PTYPENAME
788	| NSNAME  %prec EMPTY
789	;
790
791do_id:
792	;
793
794template_id:
795          PFUNCNAME '<' do_id template_arg_list_opt template_close_bracket 
796        | operator_name '<' do_id template_arg_list_opt template_close_bracket
797	;
798
799object_template_id:
800        TEMPLATE identifier '<' template_arg_list_opt template_close_bracket
801        | TEMPLATE PFUNCNAME '<' template_arg_list_opt template_close_bracket
802        | TEMPLATE operator_name '<' template_arg_list_opt 
803          template_close_bracket
804        ;
805
806unqualified_id:
807	  notype_unqualified_id
808	| TYPENAME
809	| SELFNAME
810	;
811
812expr_or_declarator_intern:
813	  expr_or_declarator
814	| attributes expr_or_declarator
815	;
816
817expr_or_declarator:
818	  notype_unqualified_id
819	| '*' expr_or_declarator_intern  %prec UNARY
820	| '&' expr_or_declarator_intern  %prec UNARY
821	| '(' expr_or_declarator_intern ')'
822	;
823
824notype_template_declarator:
825	  IDENTIFIER '<' template_arg_list_opt template_close_bracket
826	| NSNAME '<' template_arg_list template_close_bracket
827	;
828		
829direct_notype_declarator:
830	  complex_direct_notype_declarator
831	/* This precedence declaration is to prefer this reduce
832	   to the Koenig lookup shift in primary, below.  I hate yacc.  */
833	| notype_unqualified_id %prec '('
834	| notype_template_declarator
835	| '(' expr_or_declarator_intern ')'
836	;
837
838primary:
839	  notype_unqualified_id
840	| CONSTANT
841	| boolean_dot_literal
842	| string
843	| '(' expr ')'
844	| '(' expr_or_declarator_intern ')'
845	| '(' error ')'
846	| '('
847	  compstmt ')'
848        /* Koenig lookup support
849           We could store lastiddecl in $1 to avoid another lookup,
850           but that would result in many additional reduce/reduce conflicts. */
851        | notype_unqualified_id '(' nonnull_exprlist ')'
852        | notype_unqualified_id LEFT_RIGHT
853	| primary '(' nonnull_exprlist ')'
854	| primary LEFT_RIGHT
855	| primary '[' expr ']'
856	| primary PLUSPLUS
857	| primary MINUSMINUS
858	/* C++ extensions */
859	| THIS
860	| CV_QUALIFIER '(' nonnull_exprlist ')'
861	| functional_cast
862	| DYNAMIC_CAST '<' type_id '>' '(' expr ')'
863	| STATIC_CAST '<' type_id '>' '(' expr ')'
864	| REINTERPRET_CAST '<' type_id '>' '(' expr ')'
865	| CONST_CAST '<' type_id '>' '(' expr ')'
866	| TYPEID '(' expr ')'
867	| TYPEID '(' type_id ')'
868	| global_scope IDENTIFIER
869	| global_scope template_id
870	| global_scope operator_name
871	| overqualified_id  %prec HYPERUNARY
872	| overqualified_id '(' nonnull_exprlist ')'
873	| overqualified_id LEFT_RIGHT
874        | object object_template_id %prec UNARY
875        | object object_template_id '(' nonnull_exprlist ')'
876	| object object_template_id LEFT_RIGHT
877	| object unqualified_id  %prec UNARY
878	| object overqualified_id  %prec UNARY
879	| object unqualified_id '(' nonnull_exprlist ')'
880	| object unqualified_id LEFT_RIGHT
881	| object overqualified_id '(' nonnull_exprlist ')'
882	| object overqualified_id LEFT_RIGHT
883	/* p->int::~int() is valid -- 12.4 */
884	| object '~' TYPESPEC LEFT_RIGHT
885	| object TYPESPEC SCOPE '~' TYPESPEC LEFT_RIGHT
886	| object error
887	;
888
889/* Not needed for now.
890
891primary_no_id:
892	  '(' expr ')'
893	| '(' error ')'
894	| '('
895	| primary_no_id '(' nonnull_exprlist ')'
896	| primary_no_id LEFT_RIGHT
897	| primary_no_id '[' expr ']'
898	| primary_no_id PLUSPLUS
899	| primary_no_id MINUSMINUS
900	| SCOPE IDENTIFIER
901	| SCOPE operator_name
902	;
903*/
904
905new:
906	  NEW
907	| global_scope NEW
908	;
909
910delete:
911	  DELETE
912	| global_scope delete
913	;
914
915boolean_dot_literal:
916	  CXX_TRUE
917	| CXX_FALSE
918	;
919
920/* Produces a STRING_CST with perhaps more STRING_CSTs chained onto it.  */
921string:
922	  STRING
923	| string STRING
924	;
925
926nodecls:
927	  /* empty */
928	;
929
930object:
931	  primary '.'
932	| primary POINTSAT
933	;
934
935decl:
936	  typespec initdecls ';'
937	| typed_declspecs initdecls ';'
938	| declmods notype_initdecls ';'
939	| typed_declspecs ';'
940	| declmods ';'
941	| extension decl
942	;
943
944/* Any kind of declarator (thus, all declarators allowed
945   after an explicit typespec).  */
946
947declarator:
948	  after_type_declarator  %prec EMPTY
949	| notype_declarator  %prec EMPTY
950	;
951
952/* This is necessary to postpone reduction of `int()()()()'.  */
953fcast_or_absdcl:
954	  LEFT_RIGHT  %prec EMPTY
955	| fcast_or_absdcl LEFT_RIGHT  %prec EMPTY
956	;
957
958/* ANSI type-id (8.1) */
959type_id:
960	  typed_typespecs absdcl
961	| nonempty_cv_qualifiers absdcl
962	| typespec absdcl
963	| typed_typespecs  %prec EMPTY
964	| nonempty_cv_qualifiers  %prec EMPTY
965	;
966
967/* Declspecs which contain at least one type specifier or typedef name.
968   (Just `const' or `volatile' is not enough.)
969   A typedef'd name following these is taken as a name to be declared.
970   In the result, declspecs have a non-NULL TREE_VALUE, attributes do not.  */
971
972typed_declspecs:
973	  typed_typespecs  %prec EMPTY
974	| typed_declspecs1
975	;
976
977typed_declspecs1:
978	  declmods typespec
979	| typespec reserved_declspecs  %prec HYPERUNARY
980	| typespec reserved_typespecquals reserved_declspecs
981	| declmods typespec reserved_declspecs
982	| declmods typespec reserved_typespecquals
983	| declmods typespec reserved_typespecquals reserved_declspecs
984	;
985
986reserved_declspecs:
987	  SCSPEC
988	| reserved_declspecs typespecqual_reserved
989	| reserved_declspecs SCSPEC
990	| reserved_declspecs attributes
991	| attributes
992	;
993
994/* List of just storage classes and type modifiers.
995   A declaration can start with just this, but then it cannot be used
996   to redeclare a typedef-name.
997   In the result, declspecs have a non-NULL TREE_VALUE, attributes do not.  */
998
999/* We use hash_tree_cons for lists of typeless declspecs so that they end
1000   up on a persistent obstack.  Otherwise, they could appear at the
1001   beginning of something like
1002
1003      static const struct { int foo () { } } b;
1004
1005   and would be discarded after we finish compiling foo.  We don't need to
1006   worry once we see a type.  */
1007
1008declmods:
1009	  nonempty_cv_qualifiers  %prec EMPTY
1010		{ $$ = $1.t; TREE_STATIC ($$) = 1; }
1011	| SCSPEC
1012		{ $$ = hash_tree_cons (NULL_TREE, $$, NULL_TREE); }
1013	| declmods CV_QUALIFIER
1014		{ $$ = hash_tree_cons (NULL_TREE, $2, $$);
1015		  TREE_STATIC ($$) = 1; }
1016	| declmods SCSPEC
1017		{ if (extra_warnings && TREE_STATIC ($$))
1018		    warning ("`%s' is not at beginning of declaration",
1019			     IDENTIFIER_POINTER ($2));
1020		  $$ = hash_tree_cons (NULL_TREE, $2, $$);
1021		  TREE_STATIC ($$) = TREE_STATIC ($1); }
1022	| declmods attributes
1023		{ $$ = hash_tree_cons ($2, NULL_TREE, $1); }
1024	| attributes  %prec EMPTY
1025		{ $$ = hash_tree_cons ($1, NULL_TREE, NULL_TREE); }
1026	;
1027
1028/* Used instead of declspecs where storage classes are not allowed
1029   (that is, for typenames and structure components).
1030
1031   C++ can takes storage classes for structure components.
1032   Don't accept a typedef-name if anything but a modifier precedes it.  */
1033
1034typed_typespecs:
1035	  typespec  %prec EMPTY
1036	| nonempty_cv_qualifiers typespec
1037	| typespec reserved_typespecquals
1038	| nonempty_cv_qualifiers typespec reserved_typespecquals
1039	;
1040
1041reserved_typespecquals:
1042	  typespecqual_reserved
1043	| reserved_typespecquals typespecqual_reserved
1044	;
1045
1046/* A typespec (but not a type qualifier).
1047   Once we have seen one of these in a declaration,
1048   if a typedef name appears then it is being redeclared.  */
1049
1050typespec:
1051	  structsp
1052	| TYPESPEC  %prec EMPTY
1053	| complete_type_name
1054	| TYPEOF '(' expr ')'
1055	| TYPEOF '(' type_id ')'
1056	| SIGOF '(' expr ')'
1057	| SIGOF '(' type_id ')'
1058	;
1059
1060/* A typespec that is a reserved word, or a type qualifier.  */
1061
1062typespecqual_reserved:
1063	  TYPESPEC
1064	| CV_QUALIFIER
1065	| structsp
1066	;
1067
1068initdecls:
1069	  initdcl0
1070	| initdecls ',' initdcl
1071	;
1072
1073notype_initdecls:
1074	  notype_initdcl0
1075	| notype_initdecls ',' initdcl
1076	;
1077
1078nomods_initdecls:
1079	  nomods_initdcl0
1080	| nomods_initdecls ',' initdcl
1081	;
1082
1083maybeasm:
1084	  /* empty */
1085	| asm_keyword '(' string ')'
1086	;
1087
1088initdcl:
1089	  declarator maybeasm maybe_attribute '='
1090	  init
1091/* Note how the declaration of the variable is in effect while its init is parsed! */
1092	| declarator maybeasm maybe_attribute
1093	;
1094
1095        /* This rule assumes a certain configuration of the parser stack.
1096	   In particular, $0, the element directly before the beginning of
1097	   this rule on the stack, must be a maybeasm.  $-1 must be a
1098	   declarator or notype_declarator.  And $-2 must be some declmods
1099	   or declspecs.  We can't move the maybeasm into this rule because
1100	   we need that reduce so we prefer fn_dot_def1 when appropriate.  */
1101initdcl0_innards:
1102	  maybe_attribute '='
1103          /* Note how the declaration of the variable is in effect
1104	     while its init is parsed! */ 
1105	  init
1106	| maybe_attribute
1107  	;
1108  
1109initdcl0:
1110	  declarator maybeasm initdcl0_innards
1111	;
1112  
1113notype_initdcl0:
1114          notype_declarator maybeasm initdcl0_innards
1115        ;
1116  
1117nomods_initdcl0:
1118          notype_declarator maybeasm
1119          initdcl0_innards 
1120	| constructor_declarator maybeasm maybe_attribute
1121	;
1122
1123/* the * rules are dummies to accept the Apollo extended syntax
1124   so that the header files compile.  */
1125maybe_attribute:
1126	  /* empty */
1127	| attributes
1128	;
1129 
1130attributes:
1131      attribute
1132	| attributes attribute
1133	;
1134
1135attribute:
1136      ATTRIBUTE '(' '(' attribute_list ')' ')'
1137	;
1138
1139attribute_list:
1140      attrib
1141	| attribute_list ',' attrib
1142	;
1143 
1144attrib:
1145	  /* empty */
1146	| any_word
1147	| any_word '(' IDENTIFIER ')'
1148	| any_word '(' IDENTIFIER ',' nonnull_exprlist ')'
1149	| any_word '(' nonnull_exprlist ')'
1150	;
1151
1152/* This still leaves out most reserved keywords,
1153   shouldn't we include them?  */
1154
1155any_word:
1156	  identifier
1157	| SCSPEC
1158	| TYPESPEC
1159	| CV_QUALIFIER
1160	;
1161
1162/* A nonempty list of identifiers, including typenames.  */
1163identifiers_or_typenames:
1164	  identifier
1165	| identifiers_or_typenames ',' identifier
1166	;
1167
1168maybe_init:
1169	  /* empty */  %prec EMPTY
1170	| '=' init
1171	;
1172
1173/* If we are processing a template, we don't want to expand this
1174   initializer yet.  */
1175
1176init:
1177	  expr_no_commas  %prec '='
1178	| '{' '}'
1179	| '{' initlist '}'
1180	| '{' initlist ',' '}'
1181	| error
1182	;
1183
1184/* This chain is built in reverse order,
1185   and put in forward order where initlist is used.  */
1186initlist:
1187	  init
1188	| initlist ',' init
1189	/* These are for labeled elements.  */
1190	| '[' expr_no_commas ']' init
1191	| identifier ':' init
1192	| initlist ',' identifier ':' init
1193	;
1194
1195fn_dot_defpen:
1196	PRE_PARSED_FUNCTION_DECL
1197	;
1198
1199pending_inline:
1200	  fn_dot_defpen maybe_return_init ctor_initializer_opt compstmt_or_error
1201	| fn_dot_defpen maybe_return_init function_try_block
1202	| fn_dot_defpen maybe_return_init error
1203	;
1204
1205pending_inlines:
1206	/* empty */
1207	| pending_inlines pending_inline eat_saved_input
1208	;
1209
1210/* A regurgitated default argument.  The value of DEFARG_MARKER will be
1211   the TREE_LIST node for the parameter in question.  */
1212defarg_again:
1213	DEFARG_MARKER expr_no_commas END_OF_SAVED_INPUT
1214	| DEFARG_MARKER error END_OF_SAVED_INPUT
1215	;
1216
1217pending_defargs:
1218	  /* empty */ %prec EMPTY
1219	| pending_defargs defarg_again
1220	| pending_defargs error
1221	;
1222
1223structsp:
1224	  ENUM identifier '{'
1225	  enumlist maybecomma_warn '}'
1226	| ENUM identifier '{' '}'
1227	| ENUM '{'
1228	  enumlist maybecomma_warn '}'
1229	| ENUM '{' '}'
1230	| ENUM identifier
1231	| ENUM complex_type_name
1232	| TYPENAME_KEYWORD typename_sub
1233	/* C++ extensions, merged with C to avoid shift/reduce conflicts */
1234	| class_head '{'
1235          opt_dot_component_decl_list '}' maybe_attribute
1236	  pending_defargs
1237	  pending_inlines
1238	| class_head  %prec EMPTY
1239	;
1240
1241maybecomma:
1242	  /* empty */
1243	| ','
1244	;
1245
1246maybecomma_warn:
1247	  /* empty */
1248	| ','
1249	;
1250
1251aggr:
1252	  AGGR
1253	| aggr SCSPEC
1254	| aggr TYPESPEC
1255	| aggr CV_QUALIFIER
1256	| aggr AGGR
1257	| aggr attributes
1258	;
1259
1260named_class_head_sans_basetype:
1261	  aggr identifier
1262	;
1263
1264named_class_head_sans_basetype_defn:
1265	  aggr identifier_defn  %prec EMPTY
1266	| named_class_head_sans_basetype '{'
1267	| named_class_head_sans_basetype ':'
1268	;
1269
1270named_complex_class_head_sans_basetype:
1271	  aggr nested_name_specifier identifier
1272	| aggr global_scope nested_name_specifier identifier
1273	| aggr global_scope identifier
1274	| aggr apparent_template_type
1275	| aggr nested_name_specifier apparent_template_type
1276	;
1277
1278named_class_head:
1279	  named_class_head_sans_basetype  %prec EMPTY
1280	| named_class_head_sans_basetype_defn 
1281          /* Class name is unqualified, so we look for base classes
1282             in the current scope.  */
1283          maybe_base_class_list  %prec EMPTY
1284	| named_complex_class_head_sans_basetype 
1285	  maybe_base_class_list
1286	;
1287
1288unnamed_class_head:
1289	  aggr '{'
1290	;
1291
1292/* The tree output of this nonterminal a declarationf or the type
1293   named.  If NEW_TYPE_FLAG is set, then the name used in this
1294   class-head was explicitly qualified, e.g.:  `struct X::Y'.  We have
1295   already called push_scope for X.  */
1296class_head:
1297	  unnamed_class_head
1298	| named_class_head
1299	;
1300
1301maybe_base_class_list:
1302	  /* empty */  %prec EMPTY
1303	| ':' see_typename  %prec EMPTY
1304	| ':' see_typename base_class_list  %prec EMPTY
1305	;
1306
1307base_class_list:
1308	  base_class
1309	| base_class_list ',' see_typename base_class
1310	;
1311
1312base_class:
1313	  base_class_dot_1
1314	| base_class_access_list see_typename base_class_dot_1
1315	;
1316
1317base_class_dot_1:
1318	  typename_sub
1319	| nonnested_type
1320	| SIGOF '(' expr ')'
1321	| SIGOF '(' type_id ')'
1322	;
1323
1324base_class_access_list:
1325	  VISSPEC see_typename
1326	| SCSPEC see_typename
1327	| base_class_access_list VISSPEC see_typename
1328	| base_class_access_list SCSPEC see_typename
1329	;
1330
1331opt_dot_component_decl_list:
1332	| component_decl_list
1333	| opt_dot_component_decl_list access_specifier component_decl_list
1334	| opt_dot_component_decl_list access_specifier 
1335	;
1336
1337access_specifier:
1338	  VISSPEC ':'
1339	;
1340
1341/* Note: we no longer warn about the semicolon after a component_decl_list.
1342   ARM $9.2 says that the semicolon is optional, and therefore allowed.  */
1343component_decl_list:
1344	  component_decl
1345	| component_decl_list component_decl
1346	;
1347
1348component_decl:
1349	  component_decl_1 ';'
1350	| component_decl_1 '}'
1351	/* C++: handle constructors, destructors and inline functions */
1352	/* note that INLINE is like a TYPESPEC */
1353	| fn_dot_def2 ':' /* base_init compstmt */
1354	| fn_dot_def2 TRY /* base_init compstmt */
1355	| fn_dot_def2 RETURN_KEYWORD /* base_init compstmt */
1356	| fn_dot_def2 '{' /* nodecls compstmt */
1357	| ';'
1358	| extension component_decl
1359        | template_header component_decl
1360	| template_header typed_declspecs ';'
1361	;
1362
1363component_decl_1:
1364	/* Do not add a "typed_declspecs declarator" rule here for
1365	   speed; we need to call grok_x_components for enums, so the
1366	   speedup would be insignificant.  */
1367	  typed_declspecs components
1368	| declmods notype_components
1369	| notype_declarator maybeasm maybe_attribute maybe_init
1370	| constructor_declarator maybeasm maybe_attribute maybe_init
1371	| ':' expr_no_commas
1372	| error
1373
1374	/* These rules introduce a reduce/reduce conflict; in
1375		typedef int foo, bar;
1376		class A {
1377		  foo (bar);
1378		};
1379	   should "A::foo" be declared as a function or "A::bar" as a data
1380	   member? In other words, is "bar" an after_type_declarator or a
1381	   parmlist? */
1382	| declmods component_constructor_declarator maybeasm maybe_attribute maybe_init
1383	| component_constructor_declarator maybeasm maybe_attribute maybe_init
1384	| using_decl
1385	;
1386
1387/* The case of exactly one component is handled directly by component_decl.  */
1388/* ??? Huh? ^^^ */
1389components:
1390	  /* empty: possibly anonymous */
1391	| component_declarator0
1392	| components ',' component_declarator
1393	;
1394
1395notype_components:
1396	  /* empty: possibly anonymous */
1397	| notype_component_declarator0
1398	| notype_components ',' notype_component_declarator
1399	;
1400
1401component_declarator0:
1402	  after_type_component_declarator0
1403	| notype_component_declarator0
1404	;
1405
1406component_declarator:
1407	  after_type_component_declarator
1408	| notype_component_declarator
1409	;
1410
1411after_type_component_declarator0:
1412	  after_type_declarator maybeasm maybe_attribute maybe_init
1413	| TYPENAME ':' expr_no_commas maybe_attribute
1414	;
1415
1416notype_component_declarator0:
1417	  notype_declarator maybeasm maybe_attribute maybe_init
1418	| constructor_declarator maybeasm maybe_attribute maybe_init
1419	| IDENTIFIER ':' expr_no_commas maybe_attribute
1420	| ':' expr_no_commas maybe_attribute
1421	;
1422
1423after_type_component_declarator:
1424	  after_type_declarator maybeasm maybe_attribute maybe_init
1425	| TYPENAME ':' expr_no_commas maybe_attribute
1426	;
1427
1428notype_component_declarator:
1429	  notype_declarator maybeasm maybe_attribute maybe_init
1430	| IDENTIFIER ':' expr_no_commas maybe_attribute
1431	| ':' expr_no_commas maybe_attribute
1432	;
1433
1434/* We chain the enumerators in reverse order.
1435   Because of the way enums are built, the order is
1436   insignificant.  Take advantage of this fact.  */
1437
1438enumlist:
1439	  enumerator
1440	| enumlist ',' enumerator
1441	;
1442
1443enumerator:
1444	  identifier
1445	| identifier '=' expr_no_commas
1446	;
1447
1448/* ANSI new-type-id (5.3.4) */
1449new_type_id:
1450	  type_specifier_seq new_declarator
1451	| type_specifier_seq  %prec EMPTY
1452	/* GNU extension to allow arrays of arbitrary types with
1453	   non-constant dimension.  For the use of begin_new_placement
1454	   here, see the comments in unary_expr above.  */
1455	| '(' dot_begin_new_placement type_id dot_finish_new_placement
1456	      '[' expr ']'
1457	;
1458
1459cv_qualifiers:
1460	  /* empty */  %prec EMPTY
1461	| cv_qualifiers CV_QUALIFIER
1462	;
1463
1464nonempty_cv_qualifiers:
1465	  CV_QUALIFIER
1466	| nonempty_cv_qualifiers CV_QUALIFIER
1467	;
1468
1469/* These rules must follow the rules for function declarations
1470   and component declarations.  That way, longer rules are preferred.  */
1471
1472suspend_mom:
1473	  /* empty */
1474	;
1475
1476/* An expression which will not live on the momentary obstack.  */
1477nonmomentary_expr:
1478	  suspend_mom expr
1479	;
1480
1481/* An expression which will not live on the momentary obstack.  */
1482maybe_parmlist:
1483	  suspend_mom '(' nonnull_exprlist ')'
1484	| suspend_mom '(' parmlist ')'
1485	| suspend_mom LEFT_RIGHT
1486	| suspend_mom '(' error ')'
1487	;
1488
1489/* A declarator that is allowed only after an explicit typespec.  */
1490
1491after_type_declarator_intern:
1492	  after_type_declarator
1493	| attributes after_type_declarator
1494	;
1495
1496/* may all be followed by prec '.' */
1497after_type_declarator:
1498	  '*' nonempty_cv_qualifiers after_type_declarator_intern  %prec UNARY
1499	| '&' nonempty_cv_qualifiers after_type_declarator_intern  %prec UNARY
1500	| '*' after_type_declarator_intern  %prec UNARY
1501	| '&' after_type_declarator_intern  %prec UNARY
1502	| ptr_to_mem cv_qualifiers after_type_declarator_intern
1503	| direct_after_type_declarator
1504	;
1505
1506direct_after_type_declarator:
1507	  direct_after_type_declarator maybe_parmlist cv_qualifiers exception_specification_opt  %prec '.'
1508	| direct_after_type_declarator '[' nonmomentary_expr ']'
1509	| direct_after_type_declarator '[' ']'
1510	| '(' after_type_declarator_intern ')'
1511	| nested_name_specifier type_name  %prec EMPTY
1512	| type_name  %prec EMPTY
1513	;
1514
1515nonnested_type:
1516	  type_name  %prec EMPTY
1517	| global_scope type_name
1518	;
1519
1520complete_type_name:
1521	  nonnested_type
1522	| nested_type
1523	| global_scope nested_type
1524	;
1525
1526nested_type:
1527	  nested_name_specifier type_name  %prec EMPTY
1528	;
1529
1530/* A declarator allowed whether or not there has been
1531   an explicit typespec.  These cannot redeclare a typedef-name.  */
1532
1533notype_declarator_intern:
1534	  notype_declarator
1535	| attributes notype_declarator
1536	;
1537	
1538notype_declarator:
1539	  '*' nonempty_cv_qualifiers notype_declarator_intern  %prec UNARY
1540	| '&' nonempty_cv_qualifiers notype_declarator_intern  %prec UNARY
1541	| '*' notype_declarator_intern  %prec UNARY
1542	| '&' notype_declarator_intern  %prec UNARY
1543	| ptr_to_mem cv_qualifiers notype_declarator_intern
1544	| direct_notype_declarator
1545	;
1546
1547complex_notype_declarator:
1548	  '*' nonempty_cv_qualifiers notype_declarator_intern  %prec UNARY
1549	| '&' nonempty_cv_qualifiers notype_declarator_intern  %prec UNARY
1550	| '*' complex_notype_declarator  %prec UNARY
1551	| '&' complex_notype_declarator  %prec UNARY
1552	| ptr_to_mem cv_qualifiers notype_declarator_intern
1553	| complex_direct_notype_declarator
1554	;
1555
1556complex_direct_notype_declarator:
1557	  direct_notype_declarator maybe_parmlist cv_qualifiers exception_specification_opt  %prec '.'
1558	| '(' complex_notype_declarator ')'
1559	| direct_notype_declarator '[' nonmomentary_expr ']'
1560	| direct_notype_declarator '[' ']'
1561	| notype_qualified_id
1562        | nested_name_specifier notype_template_declarator
1563	;
1564
1565qualified_id:
1566	  nested_name_specifier unqualified_id
1567        | nested_name_specifier object_template_id
1568	;
1569
1570notype_qualified_id:
1571	  nested_name_specifier notype_unqualified_id
1572        | nested_name_specifier object_template_id
1573	;
1574
1575overqualified_id:
1576	  notype_qualified_id
1577	| global_scope notype_qualified_id
1578	;
1579
1580functional_cast:
1581	  typespec '(' nonnull_exprlist ')'
1582	| typespec '(' expr_or_declarator_intern ')'
1583	| typespec fcast_or_absdcl  %prec EMPTY
1584	;
1585type_name:
1586	  TYPENAME
1587	| SELFNAME
1588	| template_type  %prec EMPTY
1589	;
1590
1591nested_name_specifier:
1592	  nested_name_specifier_1
1593	| nested_name_specifier nested_name_specifier_1
1594	| nested_name_specifier TEMPLATE explicit_template_type SCOPE
1595	;
1596
1597/* Why the @#$%^& do type_name and notype_identifier need to be expanded
1598   inline here?!?  (jason) */
1599nested_name_specifier_1:
1600	  TYPENAME SCOPE
1601	| SELFNAME SCOPE
1602	| NSNAME SCOPE
1603	| template_type SCOPE
1604/* 	These break 'const i;'
1605	| IDENTIFIER SCOPE
1606		{
1607		 failed_scope:
1608		  cp_error ("`%D' is not an aggregate typedef", 
1609			    lastiddecl ? lastiddecl : $$);
1610		  $$ = error_mark_node;
1611		}
1612	| PTYPENAME SCOPE
1613		{ goto failed_scope; } */
1614	;
1615
1616typename_sub:
1617	  typename_sub0
1618	| global_scope typename_sub0
1619	;
1620
1621typename_sub0:
1622	  typename_sub1 identifier %prec EMPTY
1623	| typename_sub1 template_type %prec EMPTY
1624	| typename_sub1 explicit_template_type %prec EMPTY
1625	| typename_sub1 TEMPLATE explicit_template_type %prec EMPTY
1626	;
1627
1628typename_sub1:
1629	  typename_sub2
1630	| typename_sub1 typename_sub2
1631	| typename_sub1 explicit_template_type SCOPE
1632	| typename_sub1 TEMPLATE explicit_template_type SCOPE
1633	;
1634
1635typename_sub2:
1636	  TYPENAME SCOPE
1637	| SELFNAME SCOPE
1638	| template_type SCOPE
1639	| PTYPENAME SCOPE
1640	| IDENTIFIER SCOPE
1641	| NSNAME SCOPE
1642	;
1643
1644explicit_template_type:
1645	  identifier '<' template_arg_list_opt template_close_bracket
1646	;
1647
1648complex_type_name:
1649	  global_scope type_name
1650	| nested_type
1651	| global_scope nested_type
1652	;
1653
1654ptr_to_mem:
1655	  nested_name_specifier '*'
1656	| global_scope nested_name_specifier '*'
1657	;
1658
1659/* All uses of explicit global scope must go through this nonterminal so
1660   that got_scope will be set before yylex is called to get the next token.  */
1661global_scope:
1662	  SCOPE
1663	;
1664
1665/* ANSI new-declarator (5.3.4) */
1666new_declarator:
1667	  '*' cv_qualifiers new_declarator
1668	| '*' cv_qualifiers  %prec EMPTY
1669	| '&' cv_qualifiers new_declarator  %prec EMPTY
1670	| '&' cv_qualifiers  %prec EMPTY
1671	| ptr_to_mem cv_qualifiers  %prec EMPTY
1672	| ptr_to_mem cv_qualifiers new_declarator
1673	| direct_new_declarator  %prec EMPTY
1674	;
1675
1676/* ANSI direct-new-declarator (5.3.4) */
1677direct_new_declarator:
1678	  '[' expr ']'
1679	| direct_new_declarator '[' nonmomentary_expr ']'
1680	;
1681
1682absdcl_intern:
1683	  absdcl
1684	| attributes absdcl
1685	;
1686	
1687/* ANSI abstract-declarator (8.1) */
1688absdcl:
1689	  '*' nonempty_cv_qualifiers absdcl_intern
1690	| '*' absdcl_intern
1691	| '*' nonempty_cv_qualifiers  %prec EMPTY
1692	| '*'  %prec EMPTY
1693	| '&' nonempty_cv_qualifiers absdcl_intern
1694	| '&' absdcl_intern
1695	| '&' nonempty_cv_qualifiers  %prec EMPTY
1696	| '&'  %prec EMPTY
1697	| ptr_to_mem cv_qualifiers  %prec EMPTY
1698	| ptr_to_mem cv_qualifiers absdcl_intern
1699	| direct_abstract_declarator  %prec EMPTY
1700	;
1701
1702/* ANSI direct-abstract-declarator (8.1) */
1703direct_abstract_declarator:
1704	  '(' absdcl_intern ')'
1705	  /* `(typedef)1' is `int'.  */
1706	| PAREN_STAR_PAREN
1707	| direct_abstract_declarator '(' parmlist ')' cv_qualifiers exception_specification_opt  %prec '.'
1708	| direct_abstract_declarator LEFT_RIGHT cv_qualifiers exception_specification_opt  %prec '.'
1709	| direct_abstract_declarator '[' nonmomentary_expr ']'  %prec '.'
1710	| direct_abstract_declarator '[' ']'  %prec '.'
1711	| '(' complex_parmlist ')' cv_qualifiers exception_specification_opt  %prec '.'
1712	| regcast_or_absdcl cv_qualifiers exception_specification_opt  %prec '.'
1713	| fcast_or_absdcl cv_qualifiers exception_specification_opt  %prec '.'
1714	| '[' nonmomentary_expr ']'  %prec '.'
1715	| '[' ']'  %prec '.'
1716	;
1717
1718/* For C++, decls and stmts can be intermixed, so we don't need to
1719   have a special rule that won't start parsing the stmt section
1720   until we have a stmt that parses without errors.  */
1721
1722stmts:
1723	  stmt
1724	| errstmt
1725	| stmts stmt
1726	| stmts errstmt
1727	;
1728
1729errstmt:
1730	  error ';'
1731	;
1732
1733/* Read zero or more forward-declarations for labels
1734   that nested functions can jump to.  */
1735maybe_label_decls:
1736	  /* empty */
1737	| label_decls
1738	;
1739
1740label_decls:
1741	  label_decl
1742	| label_decls label_decl
1743	;
1744
1745label_decl:
1746	  LABEL identifiers_or_typenames ';'
1747	;
1748
1749/* This is the body of a function definition.
1750   It causes syntax errors to ignore to the next openbrace.  */
1751compstmt_or_error:
1752	  compstmt
1753	| error compstmt
1754	;
1755
1756compstmt:
1757	  '{'
1758	  compstmtend 
1759	;
1760
1761simple_if:
1762	  IF
1763            paren_cond_or_null
1764	    implicitly_scoped_stmt
1765	;
1766
1767implicitly_scoped_stmt:
1768	  compstmt
1769	| simple_stmt 
1770	;
1771
1772stmt:
1773	  compstmt
1774	| simple_stmt
1775	;
1776
1777simple_stmt:
1778	  decl
1779	| expr ';'
1780	| simple_if ELSE
1781	  implicitly_scoped_stmt
1782	| simple_if  %prec IF
1783	| WHILE
1784	  paren_cond_or_null
1785	  already_scoped_stmt
1786	| DO
1787	  implicitly_scoped_stmt WHILE
1788	  paren_expr_or_null ';'
1789	| FOR
1790	  '(' for_dot_init_dot_statement
1791	  xcond ';'
1792	  xexpr ')'
1793	  already_scoped_stmt
1794	| SWITCH 
1795	    '(' condition ')'
1796	  implicitly_scoped_stmt
1797	| CASE expr_no_commas ':'
1798	  stmt
1799	| CASE expr_no_commas ELLIPSIS expr_no_commas ':'
1800	  stmt
1801	| DEFAULT ':'
1802	  stmt
1803	| BREAK ';'
1804	| CONTINUE ';'
1805	| RETURN_KEYWORD ';'
1806	| RETURN_KEYWORD expr ';'
1807	| asm_keyword maybe_cv_qualifier '(' string ')' ';'
1808	/* This is the case with just output operands.  */
1809	| asm_keyword maybe_cv_qualifier '(' string ':' asm_operands ')' ';'
1810	/* This is the case with input operands as well.  */
1811	| asm_keyword maybe_cv_qualifier '(' string ':' asm_operands ':' asm_operands ')' ';'
1812	/* This is the case with clobbered registers as well.  */
1813	| asm_keyword maybe_cv_qualifier '(' string ':' asm_operands ':'
1814	  asm_operands ':' asm_clobbers ')' ';'
1815	| GOTO '*' expr ';'
1816	| GOTO identifier ';'
1817	| label_colon stmt
1818	| label_colon '}'
1819	| ';'
1820	| try_block
1821	| using_directive
1822	| namespace_using_decl
1823	| namespace_alias
1824	;
1825
1826function_try_block:
1827	  TRY
1828	  ctor_initializer_opt compstmt
1829	  handler_seq
1830	;
1831
1832try_block:
1833	  TRY
1834	  compstmt
1835	  handler_seq
1836	;
1837
1838handler_seq:
1839	  handler
1840	| handler_seq handler
1841	;
1842
1843handler:
1844	  CATCH
1845          handler_args
1846	  compstmt
1847	;
1848
1849type_specifier_seq:
1850	  typed_typespecs  %prec EMPTY
1851	| nonempty_cv_qualifiers  %prec EMPTY
1852	;
1853
1854handler_args:
1855	  '(' ELLIPSIS ')'
1856	/* This doesn't allow reference parameters, the below does.
1857	| '(' type_specifier_seq absdcl ')'
1858	| '(' type_specifier_seq ')'
1859	| '(' type_specifier_seq notype_declarator ')'
1860	| '(' typed_typespecs after_type_declarator ')'
1861	This allows reference parameters...  */
1862	| '(' parm ')'
1863	;
1864
1865label_colon:
1866	  IDENTIFIER ':'
1867	| PTYPENAME ':'
1868	| TYPENAME ':'
1869	| SELFNAME ':'
1870	;
1871
1872for_dot_init_dot_statement:
1873	  xexpr ';'
1874	| decl
1875	| '{' compstmtend
1876	;
1877
1878/* Either a type-qualifier or nothing.  First thing in an `asm' statement.  */
1879
1880maybe_cv_qualifier:
1881	  /* empty */
1882	| CV_QUALIFIER
1883	;
1884
1885xexpr:
1886	  /* empty */
1887	| expr
1888	| error
1889	;
1890
1891/* These are the operands other than the first string and colon
1892   in  asm ("addextend %2,%1": "=dm" (x), "0" (y), "g" (*x))  */
1893asm_operands:
1894	  /* empty */
1895	| nonnull_asm_operands
1896	;
1897
1898nonnull_asm_operands:
1899	  asm_operand
1900	| nonnull_asm_operands ',' asm_operand
1901	;
1902
1903asm_operand:
1904	  STRING '(' expr ')'
1905	;
1906
1907asm_clobbers:
1908	  STRING
1909	| asm_clobbers ',' STRING
1910	;
1911
1912/* This is what appears inside the parens in a function declarator.
1913   Its value is represented in the format that grokdeclarator expects.
1914
1915   In C++, declaring a function with no parameters
1916   means that that function takes *no* parameters.  */
1917
1918parmlist:
1919	  /* empty */
1920	| complex_parmlist
1921	| type_id
1922	;
1923
1924/* This nonterminal does not include the common sequence '(' type_id ')',
1925   as it is ambiguous and must be disambiguated elsewhere.  */
1926complex_parmlist:
1927	  parms
1928	| parms_comma ELLIPSIS
1929	/* C++ allows an ellipsis without a separating ',' */
1930	| parms ELLIPSIS
1931	| type_id ELLIPSIS
1932	| ELLIPSIS
1933	| parms ':'
1934	| type_id ':'
1935	;
1936
1937/* A default argument to a */
1938defarg:
1939	  '='
1940	  defarg1
1941	;
1942
1943defarg1:
1944	  DEFARG
1945	| init
1946	;
1947
1948/* A nonempty list of parameter declarations or type names.  */
1949parms:
1950	  named_parm
1951	| parm defarg
1952	| parms_comma full_parm
1953	| parms_comma bad_parm
1954	| parms_comma bad_parm '=' init
1955	;
1956
1957parms_comma:
1958	  parms ','
1959	| type_id ','
1960	;
1961
1962/* A single parameter declaration or parameter type name,
1963   as found in a parmlist.  */
1964named_parm:
1965	/* Here we expand typed_declspecs inline to avoid mis-parsing of
1966	   TYPESPEC IDENTIFIER.  */
1967	  typed_declspecs1 declarator
1968	| typed_typespecs declarator
1969	| typespec declarator
1970	| typed_declspecs1 absdcl
1971	| typed_declspecs1  %prec EMPTY
1972	| declmods notype_declarator
1973	;
1974
1975full_parm:
1976	  parm
1977	| parm defarg
1978	;
1979
1980parm:
1981	  named_parm
1982	| type_id
1983	;
1984
1985see_typename:
1986	  /* empty */  %prec EMPTY
1987	;
1988
1989bad_parm:
1990	  /* empty */ %prec EMPTY
1991	| notype_declarator
1992	;
1993
1994exception_specification_opt:
1995	  /* empty */  %prec EMPTY
1996	| THROW '(' ansi_raise_identifiers  ')'  %prec EMPTY
1997	| THROW LEFT_RIGHT  %prec EMPTY
1998	;
1999
2000ansi_raise_identifier:
2001	  type_id
2002	;
2003
2004ansi_raise_identifiers:
2005	  ansi_raise_identifier
2006	| ansi_raise_identifiers ',' ansi_raise_identifier
2007	;
2008
2009conversion_declarator:
2010	  /* empty */  %prec EMPTY
2011	| '*' cv_qualifiers conversion_declarator
2012	| '&' cv_qualifiers conversion_declarator
2013	| ptr_to_mem cv_qualifiers conversion_declarator
2014	;
2015
2016operator:
2017	  OPERATOR
2018	;
2019
2020operator_name:
2021	  operator '*'
2022	| operator '/'
2023	| operator '%'
2024	| operator '+'
2025	| operator '-'
2026	| operator '&'
2027	| operator '|'
2028	| operator '^'
2029	| operator '~'
2030	| operator ','
2031	| operator ARITHCOMPARE
2032	| operator '<'
2033	| operator '>'
2034	| operator EQCOMPARE
2035	| operator ASSIGN
2036	| operator '='
2037	| operator LSHIFT
2038	| operator RSHIFT
2039	| operator PLUSPLUS
2040	| operator MINUSMINUS
2041	| operator ANDAND
2042	| operator OROR
2043	| operator '!'
2044	| operator '?' ':'
2045	| operator MIN_MAX
2046	| operator POINTSAT  %prec EMPTY
2047	| operator POINTSAT_STAR  %prec EMPTY
2048	| operator LEFT_RIGHT
2049	| operator '[' ']'
2050	| operator NEW  %prec EMPTY
2051	| operator DELETE  %prec EMPTY
2052	| operator NEW '[' ']'
2053	| operator DELETE '[' ']'
2054	/* Names here should be looked up in class scope ALSO.  */
2055	| operator type_specifier_seq conversion_declarator
2056	| operator error
2057	;
2058
2059%%
2060