Merge branch 'release-2.140.93'
[feisty_meow.git] / examples / cpp_grammar_code / CxxParser.y
1 /* This is a yacc-able parser for the entire ISO C++ grammar with no unresolved conflicts. */
2 /* The parse is SYNTACTICALLY consistent and requires no template or type name assistance.
3  * The grammar in the C++ standard notes that its grammar is a superset of the true
4  * grammar requiring semantic constraints to resolve ambiguities. This grammar is a really big
5  * superset unifying expressions and declarations, eliminating the type/non-type distinction,
6  * and iterating to find a consistent solution to the template/arith,metoic < ambiguity.
7  * As a result the grammar is much simpler, but requires the missing semantic constraints to be
8  * performed in a subsequent semantic pass, which is of course where they belong. This grammar will
9  * support conversion of C++ tokens into an Abstract Syntax Tree. A lot of further work is required to
10  * make that tree useful.
11  *
12  * The principles behind this grammar are described in my thesis on Meta-Compilation for C++, which
13  * may be found via http://www.computing.surrey.ac.uk/research/dsrg/fog/FogThesis.html.
14  *
15  *  Author:         E.D.Willink             Ed.Willink@rrl.co.uk
16  *  Date:           19-Jun-2001
17  */
18 /*StartTester*/
19 %{
20 #include <CxxParsing.hxx>
21 %}
22 /*EndTester*/
23 /*
24  * The lexer (and/or a preprocessor) is expected to identify the following
25  *
26  *  Punctuation:
27  */
28 %type <keyword> '+' '-' '*' '/' '%' '^' '&' '|' '~' '!' '<'  '>' '=' ':' '[' ']' '{' '}' '(' ')'
29 %type <keyword> '?' '.' '\'' '\"' '\\' '@' '$' ';' ','
30 /*
31  *  Punctuation sequences
32  */
33 %term <keyword> ARROW ARROW_STAR DEC EQ GE INC LE LOG_AND LOG_OR NE SHL SHR
34 %term <keyword> ASS_ADD ASS_AND ASS_DIV ASS_MOD ASS_MUL ASS_OR ASS_SHL ASS_SHR ASS_SUB ASS_XOR
35 %term <keyword> DOT_STAR ELLIPSIS SCOPE
36 /*
37  *  Reserved words
38  */
39 %term <access_specifier> PRIVATE PROTECTED PUBLIC
40 %term <built_in_id> BOOL CHAR DOUBLE FLOAT INT LONG SHORT SIGNED UNSIGNED VOID WCHAR_T
41 %term <class_key> CLASS ENUM NAMESPACE STRUCT TYPENAME UNION
42 %term <cv_qualifiers> CONST VOLATILE
43 %term <decl_specifier_id> AUTO EXPLICIT EXPORT EXTERN FRIEND INLINE MUTABLE REGISTER STATIC TEMPLATE TYPEDEF USING VIRTUAL
44 %term <keyword> ASM BREAK CASE CATCH CONST_CAST CONTINUE DEFAULT DELETE DO DYNAMIC_CAST
45 %term <keyword> ELSE FALSE FOR GOTO IF NEW OPERATOR REINTERPRET_CAST RETURN
46 %term <keyword> SIZEOF STATIC_CAST SWITCH THIS THROW TRUE TRY TYPEID WHILE
47 /*
48  *  Parametric values.
49  */
50 %term <character_literal> CharacterLiteral
51 %term <floating_literal> FloatingLiteral
52 %term <identifier> Identifier
53 %term <integer_literal> IntegerLiteral
54 %term <number_literal> NumberLiteral
55 %term <string_literal> StringLiteral
56 /*
57  *  The lexer need not treat '0' as distinct from IntegerLiteral in the hope that pure-specifier can
58  *  be distinguished, It isn't. Semantic rescue from = constant-expression is necessary.
59  *
60  *  The lexer is not required to distinguish template or type names, although a slight simplification to the
61  *  grammar and elaboration of the action rules could make good use of template name information.
62  *
63  *  In return for not needing to use semantic information, the lexer must support back-tracking, which
64  *  is easily achieved by a simple linear buffer, a reference implementation of which may be found in the
65  *  accompanying CxxParsing.cxx. Back-tracking is used to support:
66  *
67  *  Binary search for a consistent parse of the template/arithmetic ambiguity.
68  *      start_search() initialises the search
69  *      advance_search() iterates the search
70  *      end_search() cleans up after a search
71  *      template_test() maintains context during a search
72  *
73  *  Lookahead to resolve the inheritance/anonymous bit-field similarity
74  *      mark() saves the starting context
75  *      unmark() pops it
76  *      rewind_colon() restores the context and forces the missing :
77  *
78  *  Lookahead to resolve type 1 function parameter ambiguities
79  *      mark_type1() potentially marks the starting position
80  *      mark() marks the pre { position
81  *      remark() rewinds to the starting position
82  *      unmark() pops the starting position
83  *
84  *  Note that lookaheads may nest. 
85  */
86
87 /*
88  *  The parsing philosophy is unusual. The major ambiguities are resolved by creating a unified superset
89  *  grammar rather than non-overlapping subgrammars. Thus the grammar for parameter-declaration covers an
90  *  assignment-expression. Minor ambiguities whose resolution by supersetting would create more
91  *  ambiguities are resolved the normal way with partitioned subgrammars.
92  *  This eliminates the traditional expression/declaration and constructor/parenthesised declarator
93  *  ambiguities at the syntactic level. A subsequent semantic level has to sort the problems out.
94  *  The generality introduces four bogus ambiguities and defers the cast ambiguity for resolution
95  *  once semantic information is available.
96  *
97  *  The C++ grammar comprises 561 rules and uses 897 states in yacc, with 0 unresolved conflicts.
98  *  23 conflicts from 10 ambiguities are resolved by 8 %prec's, so that yacc and bison report 0 conflicts.
99  *
100  *  The ambiguities are:
101  *  1) dangling else resolved to inner-most if
102  *      1 conflict in 1 state on else
103  *  2) < as start-template or less-than
104  *      1 conflict in 1 states on <
105  *  3) a :: b :: c resolved to favour a::b::c rather than a::b ::c or a ::b::c
106  *      1 conflicts in 1 state for ::
107  *  4) pointer operators maximised at end of conversion id/new in preference to binary operators
108  *      2 conflicts in 4 states on * and &
109  *  5a) (a)@b resolved to favour binary a@b rather than cast unary (a)(@b)
110  *  5b) (a)(b) resolved to favour cast rather than call
111  *      8 conflicts in 1 state for the 8 prefix operators: 6 unaries and ( and [.
112  *  6) enum name { resolved to enum-specifier rather than function
113  *      1 conflict in 1 state on {
114  *  7) class name { resolved to class-specifier rather than function
115  *      1 conflict in 1 state on {
116  *  8) extern "C" resolved to linkage-specification rather than declaration
117  *      1 conflict in 1 state on StringLiteral
118  *  9) class X : forced to go through base-clause look-ahead
119  *      1 conflict in 1 state on :
120  *  10) id : forced to label_statement rather than constructor_head
121  *      0 conflicts - but causes a double state for 2)
122  *  of which
123  *      1 is a fundamental C conflict - always correctly resolved
124  *          can be removed - see the Java spec
125  *      2, 3, 4 are fundamental C++ conflicts
126  *          2 always consistently resolved by iteration
127  *          3 always correctly resolved
128  *          4 always correctly resolved
129  *      5 is a result of not using type information - deferred for semantic repair
130  *      6,7 are caused by parsing over-generous superset - always correctly resolved
131  *      8 is caused by parsing over-generous superset - always correctly resolved
132  *          can be removed at the expense of 7 rules and 5 states.
133  *      9 is a look-ahead trick - always correctly resolved
134  *          could be removed by marking one token sooner
135  *      10 is caused by parsing over-generous superset - always correctly resolved
136  *
137  *  The hard problem of distinguishing
138  *      class A { class B : C, D, E {           -- A::B privately inherits C, D and E
139  *      class A { class B : C, D, E ;           -- C is width of anon bit-field
140  *  is resolved by using a lookahead that assumes inheritance and rewinds for the bit-field.
141  *
142  *  The potential shift-reduce conflict on > is resolved by flattening part of the expression grammar
143  *  to know when the next > is template end or arithmetic >.
144  *
145  *  The grammar is SYNTACTICALLY context-free with respect to type. No semantic assistance is required
146  *  during syntactic analysis. However the cast ambiguity is deferred and must be recovered
147  *  after syntactic analysis of a statement has completed. 
148  *
149  *  The grammar is SYNTACTICALLY context-free with respect to template-names. This is achieved by
150  *  organising a binary search over all possible template/arithmetic ambiguities with respect to
151  *  the enclosing statement. This is potentially exponentially inefficient but well-behaved in practice.
152  *  Approximately 1% of statements trigger a search and approximately 1% of those are misparsed,
153  *  requiring the semantic analysis to check and correct once template information is available.
154  *  1.5 parse attempts are required on average per ambiguous statement.
155  *
156  *  The grammar supports type I function declarations at severe impediment to efficiency. A lookahead
157  *  has to be performed after almost every non-statement close parenthesis. A one-line plus corollary
158  *  change to postfix_expression is commented and strongly recommended to make this grammar as
159  *  efficient as the rather large number of reduction levels permits.
160  *
161  *  Error recovery occurs mostly at the statement/declaration level. Recovery also occurs at
162  *  the list-element level where this poses no hazard to statement/declaration level recovery. 
163  *  Note that since error propagation interacts with the lookaheads for template iteration or
164  *  type 1 function arguments, introduction of finer grained error recovery may repair a false
165  *  parse and so cause a misparse.
166  *
167  *  The following syntactic analysis errors occur, but are correctable semantically:
168  *  (cast)unary-op expr         is parsed as (parenthesised)binary-op expr
169  *      The semantic test should look for a binary/call with a (type) as its left child.
170  *  (parenthesised)(arguments)  is parsed as (cast)(parenthesised)
171  *      The semantic test should look for a cast with a non-type as its left child.
172  *  template < and arithmetic < may be cross-parsed (unless semnatic help is provided)
173  *      approximately 0.01% are misparsed, and must be sorted out - not easy.
174  *
175  *  The syntactic analysis defers the following ambiguities for semantic resolution:
176  *  declaration/expression is parsed as a unified concept
177  *      Use type and context to complete the parse.
178  *  ~class-name                 is parsed as unary~ name
179  *      The semantic test should look for ~ with a type as its child.
180  *  delete[] expr               is parsed as delete []expr
181  *      The semantic test should look for delete with a [] cast of its child.
182  *  operator new/delete[]       are parsed as array of operator new/delete
183  *      The semantic test should look for array of operator new/delete
184  *      or activate the two extra commented rules in operator
185  *  template of an explicit_instantiation is buried deep in the tree
186  *      dig it out 
187  *  pure-specifier and constant-initializer are covered by assignment-expression
188  *      just another of the deferred declaration/expression ambiguities
189  *  sizeof and typeid don't distinguish type/value syntaxes
190  *      probably makes life polymorphically easier
191  */
192 /*  Action code is supplied by a large number of YACC_xxx macros that can be redefined
193  *  by rewriting the include file rather than the grammar. The number of macros is
194  *  slightly reduced by using the following protocols
195  *
196  *  YACC_LIST(0,0)      create empty list (may safely return 0).
197  *  YACC_LIST(0,E)      create new list with content E (may return 0 if above returned non-0).
198  *  YACC_LIST(L,E)      add E to L
199  *  YACC_LIST(L,0)      error propagation, adding nothing to L.
200  */
201 %type <bang> bang
202 %type <mark> colon_mark mark mark_type1
203 %type <nest> nest
204
205 %type <access_specifier> access_specifier
206 %type <base_specifier> base_specifier
207 %type <base_specifiers> base_specifier_list
208 %type <built_in_id> built_in_type_id built_in_type_specifier
209 %type <_class> class_specifier_head
210 %type <class_key> class_key
211 %type <condition> condition condition.opt
212 %type <cv_qualifiers> cv_qualifier cv_qualifier_seq.opt
213 %type <decl_specifier_id>  decl_specifier_affix decl_specifier_prefix decl_specifier_suffix function_specifier storage_class_specifier
214 %type <declaration> accessibility_specifier asm_definition block_declaration declaration explicit_specialization
215 %type <declaration> looped_declaration looping_declaration namespace_alias_definition
216 %type <declaration> specialised_block_declaration specialised_declaration template_declaration using_directive
217 %type <declarations> compound_declaration declaration_seq.opt
218 %type <declarator> nested_ptr_operator ptr_operator
219 %type <delete_expression> delete_expression
220 %type <enumerator> enumerator_definition
221 %type <enumerators> enumerator_clause enumerator_list enumerator_list_head
222 %type <exception_declaration> exception_declaration
223 %type <exception_specification> exception_specification
224 %type <expression> abstract_declarator.opt abstract_expression abstract_parameter_declaration abstract_pointer_declaration
225 %type <expression> additive_expression and_expression assignment_expression
226 %type <expression> bit_field_declaration bit_field_init_declaration bit_field_width boolean_literal
227 %type <expression> cast_expression conditional_expression constant_expression conversion_type_id ctor_definition
228 %type <expression> direct_abstract_declarator direct_abstract_declarator.opt direct_new_declarator
229 %type <expression> equality_expression exclusive_or_expression expression expression.opt
230 %type <expression> for_init_statement func_definition function_definition 
231 %type <expression> inclusive_or_expression init_declaration literal logical_and_expression logical_or_expression
232 %type <expression> multiplicative_expression new_declarator new_type_id
233 %type <expression> pm_expression postfix_expression primary_expression ptr_operator_seq ptr_operator_seq.opt
234 %type <expression> relational_expression shift_expression simple_declaration special_parameter_declaration
235 %type <expression> templated_throw_expression throw_expression templated_abstract_declaration templated_and_expression 
236 %type <expression>templated_assignment_expression templated_conditional_expression templated_equality_expression
237 %type <expression> templated_exclusive_or_expression templated_expression templated_inclusive_or_expression templated_logical_and_expression
238 %type <expression> templated_logical_or_expression templated_relational_expression type_id unary_expression
239 %type <expressions> constructor_head expression_list expression_list.opt init_declarations
240 %type <expressions> new_initializer.opt templated_expression_list type_id_list
241 %type <function_body> function_block function_body function_try_block try_block
242 %type <handler> handler
243 %type <handlers> handler_seq
244 %type <initializer_clause> braced_initializer initializer_clause looped_initializer_clause looping_initializer_clause
245 %type <initializer_clauses> initializer_list
246 %type <is_template> global_scope
247 %type <keyword> assignment_operator
248 %type <line> start_search start_search1
249 %type <mem_initializer> mem_initializer
250 %type <mem_initializers> ctor_initializer ctor_initializer.opt mem_initializer_list mem_initializer_list_head
251 %type <name> class_specifier conversion_function_id declarator_id destructor_id
252 %type <name> elaborated_class_specifier elaborated_enum_specifier elaborated_type_specifier elaborate_type_specifier
253 %type <name> enum_specifier enumerator id identifier_word id_scope identifier linkage_specification
254 %type <name> namespace_definition nested_id nested_pseudo_destructor_id nested_special_function_id
255 %type <name> mem_initializer_id operator operator_function_id pseudo_destructor_id scoped_id scoped_pseudo_destructor_id scoped_special_function_id
256 %type <name> simple_type_specifier special_function_id suffix_built_in_decl_specifier suffix_named_decl_specifier.bi
257 %type <name> suffix_built_in_decl_specifier.raw suffix_decl_specified_ids suffix_named_decl_specifiers
258 %type <name> suffix_named_decl_specifiers.sf suffix_decl_specified_scope suffix_named_decl_specifier
259 %type <name> template_id type_specifier
260 %type <new_expression> new_expression
261 %type <parameter> parameter_declaration templated_parameter_declaration
262 %type <parameters> parameters_clause parameter_declaration_clause parameter_declaration_list
263 %type <parenthesised> parenthesis_clause
264 %type <pointer_declarator> star_ptr_operator
265 %type <simple_type_parameter> simple_type_parameter
266 %type <statement> compound_statement control_statement declaration_statement iteration_statement jump_statement
267 %type <statement> labeled_statement looped_statement looping_statement selection_statement statement
268 %type <statements> statement_seq.opt
269 %type <strings> string
270 %type <template_argument> template_argument
271 %type <template_arguments> template_argument_list
272 %type <template_parameter> template_parameter
273 %type <template_parameters> template_parameter_clause template_parameter_list
274 %type <templated_type_parameter> templated_type_parameter
275 %type <type1_parameters> type1_parameters
276 %type <utility> util
277
278 /*
279  *  C++ productions replaced by more generalised FOG productions
280  */
281 %type <declaration> looped_member_declaration looping_member_declaration member_declaration using_declaration
282 %type <declarations> member_specification.opt
283 %type <expression> member_init_declaration simple_member_declaration
284 %type <expressions> member_init_declarations
285
286 \f
287 %nonassoc SHIFT_THERE
288 %nonassoc SCOPE ELSE INC DEC '+' '-' '*' '&' '[' '{' '<' ':' StringLiteral
289 %nonassoc REDUCE_HERE_MOSTLY
290 %nonassoc '('
291 /*%nonassoc REDUCE_HERE */
292
293 %start translation_unit
294 %%
295
296 /*
297  *  The %prec resolves a conflict in identifier_word : which is forced to be a shift of a label for
298  *  a labeled-statement rather than a reduction for the name of a bit-field or generalised constructor.
299  *  This is pretty dubious syntactically but correct for all semantic possibilities.
300  *  The shift is only activated when the ambiguity exists at the start of a statement. In this context
301  *  a bit-field declaration or constructor definition are not allowed.
302  */
303 identifier_word:                    Identifier                                                  { $$ = $1; }
304 identifier:                         identifier_word                     %prec SHIFT_THERE
305 /*
306  *  The %prec resolves the $014.2-3 ambiguity:
307  *  Identifier '<' is forced to go through the is-it-a-template-name test
308  *  All names absorb TEMPLATE with the name, so that no template_test is performed for them.
309  *  This requires all potential declarations within an expression to perpetuate this policy
310  *  and thereby guarantee the ultimate coverage of explicit_instantiation.
311  */
312 id:                                 identifier                          %prec SHIFT_THERE       /* Force < through test */ { $$ = YACC_NAME($1); }
313     |                               identifier template_test '+' template_argument_list '>'     { $$ = YACC_TEMPLATE_NAME($1, $4); }
314     |                               identifier template_test '+' '>'                            { $$ = $1; ERRMSG("Empty template-argument-list"); }
315     |                               identifier template_test '-'                                /* requeued < follows */  { $$ = YACC_NAME($1); }
316     |                               template_id 
317 template_test:                      '<'             /* Queue '+' or '-' < as follow on */       { template_test(); }
318 global_scope:                       SCOPE                                                       { $$ = IS_DEFAULT; }
319     |                               TEMPLATE global_scope                                       { $$ = IS_TEMPLATE; }
320 id_scope:                           id SCOPE                                                    { $$ = YACC_NESTED_SCOPE($1); }
321 /*
322  *  A :: B :: C; is ambiguous How much is type and how much name ?
323  *  The %prec maximises the (type) length which is the $07.1-2 semantic constraint.
324  */
325 nested_id:                          id                                  %prec SHIFT_THERE       /* Maximise length */
326     |                               id_scope nested_id                                          { $$ = YACC_NESTED_ID($1, $2); }
327 scoped_id:                          nested_id
328     |                               global_scope nested_id                                      { $$ = YACC_GLOBAL_ID($1, $2); }
329
330 /*
331  *  destructor_id has to be held back to avoid a conflict with a one's complement as per $05.3.1-9,
332  *  It gets put back only when scoped or in a declarator_id, which is only used as an explicit member name.
333  *  Declarations of an unscoped destructor are always parsed as a one's complement.
334  */
335 destructor_id:                      '~' id                                                      { $$ = YACC_DESTRUCTOR_ID($2); }
336     |                               TEMPLATE destructor_id                                      { $$ = YACC_SET_TEMPLATE_ID($2); }
337 special_function_id:                conversion_function_id
338     |                               operator_function_id
339     |                               TEMPLATE special_function_id                                { $$ = YACC_SET_TEMPLATE_ID($2); }
340 nested_special_function_id:         special_function_id
341     |                               id_scope destructor_id                                      { $$ = YACC_NESTED_ID($1, $2); }
342     |                               id_scope nested_special_function_id                         { $$ = YACC_NESTED_ID($1, $2); }
343 scoped_special_function_id:         nested_special_function_id
344     |                               global_scope nested_special_function_id                     { $$ = YACC_GLOBAL_ID($1, $2); }
345
346 /* declarator-id is all names in all scopes, except reserved words */
347 declarator_id:                      scoped_id
348     |                               scoped_special_function_id
349     |                               destructor_id
350
351 /*  The standard defines pseudo-destructors in terms of type-name, which is class/enum/typedef, of which
352  *  class-name is covered by a normal destructor. pseudo-destructors are supposed to support ~int() in
353  *  templates, so the grammar here covers built-in names. Other names are covered by the lack of
354  *  identifier/type discrimination.
355  */
356 built_in_type_id:                   built_in_type_specifier
357     |                               built_in_type_id built_in_type_specifier                    { $$ = YACC_BUILT_IN_IDS($1, $2); }
358 pseudo_destructor_id:               built_in_type_id SCOPE '~' built_in_type_id                 { $$ = YACC_PSEUDO_DESTRUCTOR_ID($1, $4); }
359     |                               '~' built_in_type_id                                        { $$ = YACC_PSEUDO_DESTRUCTOR_ID(0, $2); }
360     |                               TEMPLATE pseudo_destructor_id                               { $$ = YACC_SET_TEMPLATE_ID($2); }
361 nested_pseudo_destructor_id:        pseudo_destructor_id
362     |                               id_scope nested_pseudo_destructor_id                        { $$ = YACC_NESTED_ID($1, $2); }
363 scoped_pseudo_destructor_id:        nested_pseudo_destructor_id
364     |                               global_scope scoped_pseudo_destructor_id                    { $$ = YACC_GLOBAL_ID($1, $2); }
365
366 /*---------------------------------------------------------------------------------------------------
367  * A.2 Lexical conventions
368  *---------------------------------------------------------------------------------------------------*/
369 /*
370  *  String concatenation is a phase 6, not phase 7 activity so does not really belong in the grammar.
371  *  However it may be convenient to have it here to make this grammar fully functional.
372  *  Unfortunately it introduces a conflict with the generalised parsing of extern "C" which
373  *  is correctly resolved to maximise the string length as the token source should do anyway.
374  */
375 string:                             StringLiteral                                               { $$ = $1; }
376 /*string:                           StringLiteral                           %prec SHIFT_THERE   { $$ = YACC_STRINGS($1, 0); } */
377 /*  |                               StringLiteral string  -- Perverse order avoids conflicts -- { $$ = YACC_STRINGS($1, $2); } */
378 literal:                            IntegerLiteral                                              { $$ = YACC_INTEGER_LITERAL_EXPRESSION($1); }
379     |                               CharacterLiteral                                            { $$ = YACC_CHARACTER_LITERAL_EXPRESSION($1); }
380     |                               FloatingLiteral                                             { $$ = YACC_FLOATING_LITERAL_EXPRESSION($1); }
381     |                               string                                                      { $$ = YACC_STRING_LITERAL_EXPRESSION($1); }
382     |                               boolean_literal
383 boolean_literal:                    FALSE                                                       { $$ = YACC_FALSE_EXPRESSION(); }
384     |                               TRUE                                                        { $$ = YACC_TRUE_EXPRESSION(); }
385
386 /*---------------------------------------------------------------------------------------------------
387  * A.3 Basic concepts
388  *---------------------------------------------------------------------------------------------------*/
389 translation_unit:                   declaration_seq.opt                                         { YACC_RESULT($1); }
390
391 /*---------------------------------------------------------------------------------------------------
392  * A.4 Expressions
393  *---------------------------------------------------------------------------------------------------
394  *  primary_expression covers an arbitrary sequence of all names with the exception of an unscoped destructor,
395  *  which is parsed as its unary expression which is the correct disambiguation (when ambiguous).
396  *  This eliminates the traditional A(B) meaning A B ambiguity, since we never have to tack an A onto
397  *  the front of something that might start with (. The name length got maximised ab initio. The downside
398  *  is that semantic interpretation must split the names up again.
399  *
400  *  Unification of the declaration and expression syntax means that unary and binary pointer declarator operators:
401  *      int * * name
402  *  are parsed as binary and unary arithmetic operators (int) * (*name). Since type information is not used
403  *  ambiguities resulting from a cast
404  *      (cast)*(value)
405  *  are resolved to favour the binary rather than the cast unary to ease AST clean-up.
406  *  The cast-call ambiguity must be resolved to the cast to ensure that (a)(b)c can be parsed.
407  *
408  *  The problem of the functional cast ambiguity
409  *      name(arg)
410  *  as call or declaration is avoided by maximising the name within the parsing kernel. So
411  *  primary_id_expression picks up 
412  *      extern long int const var = 5;
413  *  as an assignment to the syntax parsed as "extern long int const var". The presence of two names is
414  *  parsed so that "extern long into const" is distinguished from "var" considerably simplifying subsequent
415  *  semantic resolution.
416  *
417  *  The generalised name is a concatenation of potential type-names (scoped identifiers or built-in sequences)
418  *  plus optionally one of the special names such as an operator-function-id, conversion-function-id or
419  *  destructor as the final name. 
420  */
421 primary_expression:                 literal
422     |                               THIS                                                    { $$ = YACC_THIS_EXPRESSION(); }
423     |                               suffix_decl_specified_ids                               { $$ = $1; }
424 /*  |                               SCOPE identifier                                        -- covered by suffix_decl_specified_ids */
425 /*  |                               SCOPE operator_function_id                              -- covered by suffix_decl_specified_ids */
426 /*  |                               SCOPE qualified_id                                      -- covered by suffix_decl_specified_ids */
427     |                               abstract_expression           %prec REDUCE_HERE_MOSTLY  /* Prefer binary to unary ops, cast to call */
428 /*  |                               id_expression                                           -- covered by suffix_decl_specified_ids */
429
430 /*
431  *  Abstract-expression covers the () and [] of abstract-declarators.
432  */
433 abstract_expression:                parenthesis_clause                                      { $$ = YACC_ABSTRACT_FUNCTION_EXPRESSION($1); }
434     |                               '[' expression.opt ']'                                  { $$ = YACC_ABSTRACT_ARRAY_EXPRESSION($2); }
435     |                               TEMPLATE parenthesis_clause                             { $$ = YACC_SET_TEMPLATE_EXPRESSION(YACC_ABSTRACT_FUNCTION_EXPRESSION($2)); }
436
437 /*  Type I function parameters are ambiguous with respect to the generalised name, so we have to do a lookahead following
438  *  any function-like parentheses. This unfortunately hits normal code, so kill the -- lines and add the ++ lines for efficiency.
439  *  Supporting Type I code under the superset causes perhaps 25% of lookahead parsing. Sometimes complete class definitions
440  *  get traversed since they are valid generalised type I parameters!
441  */
442 type1_parameters:       /*----*/    parameter_declaration_list ';'                          { $$ = YACC_TYPE1_PARAMETERS(0, $1); }
443     |                   /*----*/    type1_parameters parameter_declaration_list ';'         { $$ = YACC_TYPE1_PARAMETERS($1, $2); }
444 mark_type1:                         /* empty */                                             { $$ = mark_type1(); }
445 postfix_expression:                 primary_expression
446 /*  |                   /++++++/    postfix_expression parenthesis_clause                   { $$ = YACC_CALL_EXPRESSION($1, $2); } */
447     |                   /*----*/    postfix_expression parenthesis_clause mark_type1 '-'    { $$ = YACC_CALL_EXPRESSION($1, $2); }
448     |                   /*----*/    postfix_expression parenthesis_clause mark_type1 '+' type1_parameters mark '{' error 
449                         /*----*/                    { yyerrok; remark_type1($6); unmark(); unmark($5); $$ = YACC_TYPE1_EXPRESSION($1, $2, $5); }
450     |                   /*----*/    postfix_expression parenthesis_clause mark_type1 '+' type1_parameters mark error 
451                         /*----*/                    { yyerrok; remark_type1($3); unmark(); unmark(); $$ = YACC_CALL_EXPRESSION($1, $2); }
452     |                   /*----*/    postfix_expression parenthesis_clause mark_type1 '+' error
453                         /*----*/                    { yyerrok; remark_type1($3); unmark(); $$ = YACC_CALL_EXPRESSION($1, $2); }
454     |                               postfix_expression '[' expression.opt ']'               { $$ = YACC_ARRAY_EXPRESSION($1, $3); }
455 /*  |                               destructor_id '[' expression.opt ']'                    -- not semantically valid */
456 /*  |                               destructor_id parenthesis_clause                        -- omitted to resolve known ambiguity */
457 /*  |                               simple_type_specifier '(' expression_list.opt ')'       -- simple_type_specifier is a primary_expression */
458     |                               postfix_expression '.' declarator_id                    { $$ = YACC_DOT_EXPRESSION($1, $3); }
459 /*  |                               postfix_expression '.' TEMPLATE declarator_id           -- TEMPLATE absorbed into declarator_id. */
460     |                               postfix_expression '.' scoped_pseudo_destructor_id      { $$ = YACC_DOT_EXPRESSION($1, $3); }
461     |                               postfix_expression ARROW declarator_id                  { $$ = YACC_ARROW_EXPRESSION($1, $3); }
462 /*  |                               postfix_expression ARROW TEMPLATE declarator_id         -- TEMPLATE absorbed into declarator_id. */
463     |                               postfix_expression ARROW scoped_pseudo_destructor_id    { $$ = YACC_ARROW_EXPRESSION($1, $3); }   
464     |                               postfix_expression INC                                  { $$ = YACC_POST_INCREMENT_EXPRESSION($1); }
465     |                               postfix_expression DEC                                  { $$ = YACC_POST_DECREMENT_EXPRESSION($1); }
466     |                               DYNAMIC_CAST '<' type_id '>' '(' expression ')'         { $$ = YACC_DYNAMIC_CAST_EXPRESSION($3, $6); }
467     |                               STATIC_CAST '<' type_id '>' '(' expression ')'          { $$ = YACC_STATIC_CAST_EXPRESSION($3, $6); }
468     |                               REINTERPRET_CAST '<' type_id '>' '(' expression ')'     { $$ = YACC_REINTERPRET_CAST_EXPRESSION($3, $6); }
469     |                               CONST_CAST '<' type_id '>' '(' expression ')'           { $$ = YACC_CONST_CAST_EXPRESSION($3, $6); }
470     |                               TYPEID parameters_clause                                { $$ = YACC_TYPEID_EXPRESSION($2); }
471 /*  |                               TYPEID '(' expression ')'                               -- covered by parameters_clause */
472 /*  |                               TYPEID '(' type_id ')'                                  -- covered by parameters_clause */
473 expression_list.opt:                /* empty */                                             { $$ = YACC_EXPRESSIONS(0, 0); }
474     |                               expression_list
475 expression_list:                    assignment_expression                                   { $$ = YACC_EXPRESSIONS(0, $1); }
476     |                               expression_list ',' assignment_expression               { $$ = YACC_EXPRESSIONS($1, $3); }
477
478 unary_expression:                   postfix_expression
479     |                               INC cast_expression                                     { $$ = YACC_PRE_INCREMENT_EXPRESSION($2); }
480     |                               DEC cast_expression                                     { $$ = YACC_PRE_DECREMENT_EXPRESSION($2); }
481     |                               ptr_operator cast_expression                            { $$ = YACC_POINTER_EXPRESSION($1, $2); }
482 /*  |                               '*' cast_expression                                     -- covered by ptr_operator */
483 /*  |                               '&' cast_expression                                     -- covered by ptr_operator */
484 /*  |                               decl_specifier_seq '*' cast_expression                  -- covered by binary operator */
485 /*  |                               decl_specifier_seq '&' cast_expression                  -- covered by binary operator */
486     |                               suffix_decl_specified_scope star_ptr_operator cast_expression   /* covers e.g int ::type::* const t = 4 */
487                                                                                             { $$ = YACC_SCOPED_POINTER_EXPRESSION($1, $2, $3); }
488     |                               '+' cast_expression                                     { $$ = YACC_PLUS_EXPRESSION($2); }
489     |                               '-' cast_expression                                     { $$ = YACC_MINUS_EXPRESSION($2); }
490     |                               '!' cast_expression                                     { $$ = YACC_NOT_EXPRESSION($2); }
491     |                               '~' cast_expression                                     { $$ = YACC_COMPLEMENT_EXPRESSION($2); }
492     |                               SIZEOF unary_expression                                 { $$ = YACC_SIZEOF_EXPRESSION($2); }
493 /*  |                               SIZEOF '(' type_id ')'                                  -- covered by unary_expression */
494     |                               new_expression                                          { $$ = $1; }
495     |                               global_scope new_expression                             { $$ = YACC_GLOBAL_EXPRESSION($1, $2); }
496     |                               delete_expression                                       { $$ = $1; }
497     |                               global_scope delete_expression                          { $$ = YACC_GLOBAL_EXPRESSION($1, $2); }
498 /*  |                               DELETE '[' ']' cast_expression       -- covered by DELETE cast_expression since cast_expression covers ... */
499 /*  |                               SCOPE DELETE '[' ']' cast_expression //  ... abstract_expression cast_expression and so [] cast_expression */
500
501 delete_expression:                  DELETE cast_expression                                  /* also covers DELETE[] cast_expression */
502                                                                                             { $$ = YACC_DELETE_EXPRESSION($2); }
503 new_expression:                     NEW new_type_id new_initializer.opt                     { $$ = YACC_NEW_TYPE_ID_EXPRESSION(0, $2, $3); }
504     |                               NEW parameters_clause new_type_id new_initializer.opt   { $$ = YACC_NEW_TYPE_ID_EXPRESSION($2, $3, $4); }
505     |                               NEW parameters_clause                                   { $$ = YACC_NEW_EXPRESSION($2, 0, 0); }
506 /*  |                               NEW '(' type-id ')'                                     -- covered by parameters_clause */
507     |                               NEW parameters_clause parameters_clause new_initializer.opt { $$ = YACC_NEW_EXPRESSION($2, $3, $4); }
508 /*  |                               NEW '(' type-id ')' new_initializer                     -- covered by parameters_clause parameters_clause */
509 /*  |                               NEW parameters_clause '(' type-id ')'                   -- covered by parameters_clause parameters_clause */
510                                                                                 /* ptr_operator_seq.opt production reused to save a %prec */
511 new_type_id:                        type_specifier ptr_operator_seq.opt                     { $$ = YACC_TYPED_EXPRESSION($1, $2); }
512     |                               type_specifier new_declarator                           { $$ = YACC_TYPED_EXPRESSION($1, $2); }
513     |                               type_specifier new_type_id                              { $$ = YACC_TYPED_EXPRESSION($1, $2); }
514 new_declarator:                     ptr_operator new_declarator                             { $$ = YACC_POINTER_EXPRESSION($1, $2); }
515     |                               direct_new_declarator
516 direct_new_declarator:              '[' expression ']'                                      { $$ = YACC_ABSTRACT_ARRAY_EXPRESSION($2); }
517     |                               direct_new_declarator '[' constant_expression ']'       { $$ = YACC_ARRAY_EXPRESSION($1, $3); }
518 new_initializer.opt:                /* empty */                                             { $$ = YACC_EXPRESSIONS(0, 0); }
519     |                               '(' expression_list.opt ')'                             { $$ = $2; }
520
521 /*  cast-expression is generalised to support a [] as well as a () prefix. This covers the omission of DELETE[] which when
522  *  followed by a parenthesised expression was ambiguous. It also covers the gcc indexed array initialisation for free.
523  */
524 cast_expression:                    unary_expression
525     |                               abstract_expression cast_expression                         { $$ = YACC_CAST_EXPRESSION($1, $2); }
526 /*  |                               '(' type_id ')' cast_expression                             -- covered by abstract_expression */
527
528 pm_expression:                      cast_expression
529     |                               pm_expression DOT_STAR cast_expression                      { $$ = YACC_DOT_STAR_EXPRESSION($1, $3); }
530     |                               pm_expression ARROW_STAR cast_expression                    { $$ = YACC_ARROW_STAR_EXPRESSION($1, $3); }
531 multiplicative_expression:          pm_expression
532     |                               multiplicative_expression star_ptr_operator pm_expression   { $$ = YACC_MULTIPLY_EXPRESSION($1, $2, $3); }
533     |                               multiplicative_expression '/' pm_expression                 { $$ = YACC_DIVIDE_EXPRESSION($1, $3); }
534     |                               multiplicative_expression '%' pm_expression                 { $$ = YACC_MODULUS_EXPRESSION($1, $3); }
535 additive_expression:                multiplicative_expression
536     |                               additive_expression '+' multiplicative_expression           { $$ = YACC_ADD_EXPRESSION($1, $3); }
537     |                               additive_expression '-' multiplicative_expression           { $$ = YACC_SUBTRACT_EXPRESSION($1, $3); }
538 shift_expression:                   additive_expression
539     |                               shift_expression SHL additive_expression                    { $$ = YACC_SHIFT_LEFT_EXPRESSION($1, $3); }
540     |                               shift_expression SHR additive_expression                    { $$ = YACC_SHIFT_RIGHT_EXPRESSION($1, $3); }
541 relational_expression:              shift_expression
542     |                               relational_expression '<' shift_expression                  { $$ = YACC_LESS_THAN_EXPRESSION($1, $3); }
543     |                               relational_expression '>' shift_expression                  { $$ = YACC_GREATER_THAN_EXPRESSION($1, $3); }
544     |                               relational_expression LE shift_expression                   { $$ = YACC_LESS_EQUAL_EXPRESSION($1, $3); }
545     |                               relational_expression GE shift_expression                   { $$ = YACC_GREATER_EQUAL_EXPRESSION($1, $3); }
546 equality_expression:                relational_expression
547     |                               equality_expression EQ relational_expression                { $$ = YACC_EQUAL_EXPRESSION($1, $3); }
548     |                               equality_expression NE relational_expression                { $$ = YACC_NOT_EQUAL_EXPRESSION($1, $3); }
549 and_expression:                     equality_expression
550     |                               and_expression '&' equality_expression                      { $$ = YACC_AND_EXPRESSION($1, $3); }
551 exclusive_or_expression:            and_expression
552     |                               exclusive_or_expression '^' and_expression                  { $$ = YACC_EXCLUSIVE_OR_EXPRESSION($1, $3); }
553 inclusive_or_expression:            exclusive_or_expression
554     |                               inclusive_or_expression '|' exclusive_or_expression         { $$ = YACC_INCLUSIVE_OR_EXPRESSION($1, $3); }
555 logical_and_expression:             inclusive_or_expression
556     |                               logical_and_expression LOG_AND inclusive_or_expression      { $$ = YACC_LOGICAL_AND_EXPRESSION($1, $3); }
557 logical_or_expression:              logical_and_expression
558     |                               logical_or_expression LOG_OR logical_and_expression         { $$ = YACC_LOGICAL_OR_EXPRESSION($1, $3); }
559 conditional_expression:             logical_or_expression
560     |                               logical_or_expression '?' expression ':' assignment_expression
561                                                                                                 { $$ = YACC_CONDITIONAL_EXPRESSION($1, $3, $5); }
562
563 /*  assignment-expression is generalised to cover the simple assignment of a braced initializer in order to contribute to the
564  *  coverage of parameter-declaration and init-declaration.
565  */
566 assignment_expression:              conditional_expression
567     |                               logical_or_expression assignment_operator assignment_expression { $$ = YACC_ASSIGNMENT_EXPRESSION($1, $2, $3); }
568     |                               logical_or_expression '=' braced_initializer                    { $$ = YACC_ASSIGNMENT_EXPRESSION($1, $2, $3); }
569     |                               throw_expression
570 assignment_operator:                '=' | ASS_ADD | ASS_AND | ASS_DIV | ASS_MOD | ASS_MUL | ASS_OR | ASS_SHL | ASS_SHR | ASS_SUB | ASS_XOR
571
572 /*  expression is widely used and usually single-element, so the reductions are arranged so that a
573  *  single-element expression is returned as is. Multi-element expressions are parsed as a list that
574  *  may then behave polymorphically as an element or be compacted to an element. */ 
575 expression.opt:                     /* empty */                                                 { $$ = YACC_EXPRESSION(0); }
576     |                               expression
577 expression:                         assignment_expression
578     |                               expression_list ',' assignment_expression                   { $$ = YACC_EXPRESSION(YACC_EXPRESSIONS($1, $3)); }
579 constant_expression:                conditional_expression
580
581 /*  The grammar is repeated for when the parser stack knows that the next > must end a template.
582  */
583 templated_relational_expression:    shift_expression
584     |                               templated_relational_expression '<' shift_expression        { $$ = YACC_LESS_THAN_EXPRESSION($1, $3); }
585     |                               templated_relational_expression LE shift_expression         { $$ = YACC_LESS_EQUAL_EXPRESSION($1, $3); }
586     |                               templated_relational_expression GE shift_expression         { $$ = YACC_GREATER_EQUAL_EXPRESSION($1, $3); }
587 templated_equality_expression:      templated_relational_expression
588     |                               templated_equality_expression EQ templated_relational_expression    { $$ = YACC_EQUAL_EXPRESSION($1, $3); }
589     |                               templated_equality_expression NE templated_relational_expression    { $$ = YACC_NOT_EQUAL_EXPRESSION($1, $3); }
590 templated_and_expression:           templated_equality_expression
591     |                               templated_and_expression '&' templated_equality_expression  { $$ = YACC_AND_EXPRESSION($1, $3); }
592 templated_exclusive_or_expression:  templated_and_expression
593     |                               templated_exclusive_or_expression '^' templated_and_expression
594                                                                                                 { $$ = YACC_EXCLUSIVE_OR_EXPRESSION($1, $3); }
595 templated_inclusive_or_expression:  templated_exclusive_or_expression
596     |                               templated_inclusive_or_expression '|' templated_exclusive_or_expression
597                                                                                                 { $$ = YACC_INCLUSIVE_OR_EXPRESSION($1, $3); }
598 templated_logical_and_expression:   templated_inclusive_or_expression
599     |                               templated_logical_and_expression LOG_AND templated_inclusive_or_expression
600                                                                                                 { $$ = YACC_LOGICAL_AND_EXPRESSION($1, $3); }
601 templated_logical_or_expression:    templated_logical_and_expression
602     |                               templated_logical_or_expression LOG_OR templated_logical_and_expression
603                                                                                                 { $$ = YACC_LOGICAL_OR_EXPRESSION($1, $3); }
604 templated_conditional_expression:   templated_logical_or_expression
605     |                               templated_logical_or_expression '?' templated_expression ':' templated_assignment_expression
606                                                                                                 { $$ = YACC_CONDITIONAL_EXPRESSION($1, $3, $5); }
607 templated_assignment_expression:    templated_conditional_expression
608     |                               templated_logical_or_expression assignment_operator templated_assignment_expression
609                                                                                                 { $$ = YACC_ASSIGNMENT_EXPRESSION($1, $2, $3); }
610     |                               templated_throw_expression
611 templated_expression:               templated_assignment_expression
612     |                               templated_expression_list ',' templated_assignment_expression
613                                                                                                 { $$ = YACC_EXPRESSION(YACC_EXPRESSIONS($1, $3)); }
614 templated_expression_list:          templated_assignment_expression                             { $$ = YACC_EXPRESSIONS(0, $1); }
615     |                               templated_expression_list ',' templated_assignment_expression    { $$ = YACC_EXPRESSIONS($1, $3); }
616
617 /*---------------------------------------------------------------------------------------------------
618  * A.5 Statements
619  *---------------------------------------------------------------------------------------------------
620  *  Parsing statements is easy once simple_declaration has been generalised to cover expression_statement.
621  */
622 looping_statement:                  start_search looped_statement                               { $$ = YACC_LINED_STATEMENT($2, $1); end_search($$); }
623 looped_statement:                   statement
624     |                               advance_search '+' looped_statement                         { $$ = $3; }
625     |                               advance_search '-'                                          { $$ = 0; }
626 statement:                          control_statement
627 /*  |                               expression_statement                                        -- covered by declaration_statement */
628     |                               compound_statement
629     |                               declaration_statement
630     |                               try_block                                                   { $$ = YACC_TRY_BLOCK_STATEMENT($1); }
631 control_statement:                  labeled_statement
632     |                               selection_statement
633     |                               iteration_statement
634     |                               jump_statement
635 labeled_statement:                  identifier_word ':' looping_statement                       { $$ = YACC_LABEL_STATEMENT($1, $3); }
636     |                               CASE constant_expression ':' looping_statement              { $$ = YACC_CASE_STATEMENT($2, $4); }
637     |                               DEFAULT ':' looping_statement                               { $$ = YACC_DEFAULT_STATEMENT($3); }
638 /*expression_statement:             expression.opt ';'                                          -- covered by declaration_statement */
639 compound_statement:                 '{' statement_seq.opt '}'                                   { $$ = YACC_COMPOUND_STATEMENT($2); }
640     |                               '{' statement_seq.opt looping_statement '#' bang error '}'  { $$ = $2; YACC_UNBANG($5, "Bad statement-seq."); }
641 statement_seq.opt:                  /* empty */                                                 { $$ = YACC_STATEMENTS(0, 0); }
642     |                               statement_seq.opt looping_statement                         { $$ = YACC_STATEMENTS($1, YACC_COMPILE_STATEMENT($2)); }
643     |                               statement_seq.opt looping_statement '#' bang error ';'      { $$ = $1; YACC_UNBANG($4, "Bad statement."); }
644 /*
645  *  The dangling else conflict is resolved to the innermost if.
646  */
647 selection_statement:                IF '(' condition ')' looping_statement    %prec SHIFT_THERE { $$ = YACC_IF_STATEMENT($3, $5, 0); }
648     |                               IF '(' condition ')' looping_statement ELSE looping_statement { $$ = YACC_IF_STATEMENT($3, $5, $7); }
649     |                               SWITCH '(' condition ')' looping_statement                  { $$ = YACC_SWITCH_STATEMENT($3, $5); }
650 condition.opt:                      /* empty */                                                 { $$ = YACC_CONDITION(0); }
651     |                               condition
652 condition:                          parameter_declaration_list                                  { $$ = YACC_CONDITION($1); }
653 /*  |                               expression                                                  -- covered by parameter_declaration_list */
654 /*  |                               type_specifier_seq declarator '=' assignment_expression     -- covered by parameter_declaration_list */
655 iteration_statement:                WHILE '(' condition ')' looping_statement                   { $$ = YACC_WHILE_STATEMENT($3, $5); }
656     |                               DO looping_statement WHILE '(' expression ')' ';'           { $$ = YACC_DO_WHILE_STATEMENT($2, $5); }
657     |                               FOR '(' for_init_statement condition.opt ';' expression.opt ')' looping_statement
658                                                                                                 { $$ = YACC_FOR_STATEMENT($3, $4, $6, $8); }
659 for_init_statement:                 simple_declaration
660 /*  |                               expression_statement                                        -- covered by simple_declaration */
661 jump_statement:                     BREAK ';'                                                   { $$ = YACC_BREAK_STATEMENT(); }
662     |                               CONTINUE ';'                                                { $$ = YACC_CONTINUE_STATEMENT(); }
663     |                               RETURN expression.opt ';'                                   { $$ = YACC_RETURN_STATEMENT($2); }
664     |                               GOTO identifier ';'                                         { $$ = YACC_GOTO_STATEMENT($2); }
665 declaration_statement:              block_declaration                                           { $$ = YACC_DECLARATION_STATEMENT($1); }
666
667 /*---------------------------------------------------------------------------------------------------
668  * A.6 Declarations
669  *---------------------------------------------------------------------------------------------------*/
670 compound_declaration:               '{' nest declaration_seq.opt '}'                            { $$ = $3; unnest($2); }
671     |                               '{' nest declaration_seq.opt util looping_declaration '#' bang error '}'
672                                                                                                 { $$ = $3; unnest($2); YACC_UNBANG($7, "Bad declaration-seq."); }
673 declaration_seq.opt:                /* empty */                                                 { $$ = YACC_DECLARATIONS(0, 0); }
674     |                               declaration_seq.opt util looping_declaration                { $$ = YACC_DECLARATIONS($1, YACC_COMPILE_DECLARATION($2, $3)); }
675     |                               declaration_seq.opt util looping_declaration '#' bang error ';' { $$ = $1; YACC_UNBANG($5, "Bad declaration."); }
676 looping_declaration:                start_search1 looped_declaration                            { $$ = YACC_LINED_DECLARATION($2, $1); end_search($$); }
677 looped_declaration:                 declaration
678     |                               advance_search '+' looped_declaration                       { $$ = $3; }
679     |                               advance_search '-'                                          { $$ = 0; }
680 declaration:                        block_declaration
681     |                               function_definition                                         { $$ = YACC_SIMPLE_DECLARATION($1); }
682     |                               template_declaration
683 /*  |                               explicit_instantiation                                      -- covered by relevant declarations */
684     |                               explicit_specialization
685     |                               specialised_declaration
686 specialised_declaration:            linkage_specification                                       { $$ = YACC_LINKAGE_SPECIFICATION($1); }
687     |                               namespace_definition                                        { $$ = YACC_NAMESPACE_DECLARATION($1); }
688     |                               TEMPLATE specialised_declaration                            { $$ = YACC_SET_TEMPLATE_DECLARATION($2); }
689 block_declaration:                  simple_declaration                                          { $$ = YACC_SIMPLE_DECLARATION($1); }
690     |                               specialised_block_declaration
691 specialised_block_declaration:      asm_definition
692     |                               namespace_alias_definition
693     |                               using_declaration
694     |                               using_directive
695     |                               TEMPLATE specialised_block_declaration                      { $$ = YACC_SET_TEMPLATE_DECLARATION($2); }
696 simple_declaration:                 ';'                                                         { $$ = YACC_EXPRESSION(0); }
697     |                               init_declaration ';'
698     |                               init_declarations ';'                                       { $$ = $1; }
699     |                               decl_specifier_prefix simple_declaration                    { $$ = YACC_DECL_SPECIFIER_EXPRESSION($2, $1); }
700
701 /*  A decl-specifier following a ptr_operator provokes a shift-reduce conflict for
702  *      * const name
703  *  which is resolved in favour of the pointer, and implemented by providing versions
704  *  of decl-specifier guaranteed not to start with a cv_qualifier.
705  *
706  *  decl-specifiers are implemented type-centrically. That is the semantic constraint
707  *  that there must be a type is exploited to impose structure, but actually eliminate
708  *  very little syntax. built-in types are multi-name and so need a different policy.
709  *
710  *  non-type decl-specifiers are bound to the left-most type in a decl-specifier-seq,
711  *  by parsing from the right and attaching suffixes to the right-hand type. Finally
712  *  residual prefixes attach to the left.                
713  */
714 suffix_built_in_decl_specifier.raw: built_in_type_specifier                                     { $$ = $1; }
715     |                               suffix_built_in_decl_specifier.raw built_in_type_specifier  { $$ = YACC_BUILT_IN_NAME($1, $2); }
716     |                               suffix_built_in_decl_specifier.raw decl_specifier_suffix    { $$ = YACC_DECL_SPECIFIER_NAME($1, $2); }
717 suffix_built_in_decl_specifier:     suffix_built_in_decl_specifier.raw                          { $$ = $1; }
718     |                               TEMPLATE suffix_built_in_decl_specifier                     { $$ = YACC_SET_TEMPLATE_NAME($2); }
719 suffix_named_decl_specifier:        scoped_id                                                   { $$ = $1; }
720     |                               elaborate_type_specifier                                    { $$ = $1; }
721     |                               suffix_named_decl_specifier decl_specifier_suffix           { $$ = YACC_DECL_SPECIFIER_NAME($1, $2); }
722 suffix_named_decl_specifier.bi:     suffix_named_decl_specifier                                 { $$ = YACC_NAME_EXPRESSION($1); }
723     |                               suffix_named_decl_specifier suffix_built_in_decl_specifier.raw  { $$ = YACC_TYPED_NAME($1, $2); }
724 suffix_named_decl_specifiers:       suffix_named_decl_specifier.bi
725     |                               suffix_named_decl_specifiers suffix_named_decl_specifier.bi { $$ = YACC_TYPED_NAME($1, $2); }
726 suffix_named_decl_specifiers.sf:    scoped_special_function_id          /* operators etc */     { $$ = YACC_NAME_EXPRESSION($1); }
727     |                               suffix_named_decl_specifiers
728     |                               suffix_named_decl_specifiers scoped_special_function_id     { $$ = YACC_TYPED_NAME($1, $2); }
729 suffix_decl_specified_ids:          suffix_built_in_decl_specifier
730     |                               suffix_built_in_decl_specifier suffix_named_decl_specifiers.sf { $$ = YACC_TYPED_NAME($1, $2); }
731     |                               suffix_named_decl_specifiers.sf
732 suffix_decl_specified_scope:        suffix_named_decl_specifiers SCOPE
733     |                               suffix_built_in_decl_specifier suffix_named_decl_specifiers SCOPE { $$ = YACC_TYPED_NAME($1, $2); }
734     |                               suffix_built_in_decl_specifier SCOPE                        { $$ = YACC_NAME_EXPRESSION($1); }
735
736 decl_specifier_affix:               storage_class_specifier
737     |                               function_specifier
738     |                               FRIEND                                                          
739     |                               TYPEDEF
740     |                               cv_qualifier                                                { $$ = $1; }
741
742 decl_specifier_suffix:              decl_specifier_affix
743
744 decl_specifier_prefix:              decl_specifier_affix
745     |                               TEMPLATE decl_specifier_prefix                              { $$ = YACC_SET_TEMPLATE_DECL_SPECIFIER($2); }
746
747 storage_class_specifier:            REGISTER | STATIC | MUTABLE
748     |                               EXTERN                  %prec SHIFT_THERE                   /* Prefer linkage specification */
749     |                               AUTO
750
751 function_specifier:                 EXPLICIT
752     |                               INLINE
753     |                               VIRTUAL
754
755 type_specifier:                     simple_type_specifier
756     |                               elaborate_type_specifier
757     |                               cv_qualifier                                                { $$ = YACC_CV_DECL_SPECIFIER($1); }
758
759 elaborate_type_specifier:           class_specifier
760     |                               enum_specifier
761     |                               elaborated_type_specifier
762     |                               TEMPLATE elaborate_type_specifier                           { $$ = YACC_SET_TEMPLATE_ID($2); }
763 simple_type_specifier:              scoped_id
764     |                               built_in_type_specifier                                     { $$ = YACC_BUILT_IN_ID_ID($1); }
765 built_in_type_specifier:            CHAR | WCHAR_T | BOOL | SHORT | INT | LONG | SIGNED | UNSIGNED | FLOAT | DOUBLE | VOID
766
767 /*
768  *  The over-general use of declaration_expression to cover decl-specifier-seq.opt declarator in a function-definition means that
769  *      class X {};
770  *  could be a function-definition or a class-specifier.
771  *      enum X {};
772  *  could be a function-definition or an enum-specifier.
773  *  The function-definition is not syntactically valid so resolving the false conflict in favour of the
774  *  elaborated_type_specifier is correct.
775  */
776 elaborated_type_specifier:          elaborated_class_specifier
777     |                               elaborated_enum_specifier
778     |                               TYPENAME scoped_id                                          { $$ = YACC_ELABORATED_TYPE_SPECIFIER($1, $2); }
779
780 elaborated_enum_specifier:          ENUM scoped_id               %prec SHIFT_THERE              { $$ = YACC_ELABORATED_TYPE_SPECIFIER($1, $2); }
781 enum_specifier:                     ENUM scoped_id enumerator_clause                            { $$ = YACC_ENUM_SPECIFIER_ID($2, $3); }
782     |                               ENUM enumerator_clause                                      { $$ = YACC_ENUM_SPECIFIER_ID(0, $2); }
783 enumerator_clause:                  '{' enumerator_list_ecarb                                   { $$ = YACC_ENUMERATORS(0, 0); }
784     |                               '{' enumerator_list enumerator_list_ecarb                   { $$ = $2; }
785     |                               '{' enumerator_list ',' enumerator_definition_ecarb         { $$ = $2; }
786 enumerator_list_ecarb:              '}'                                                         { }
787     |                               bang error '}'                                              { YACC_UNBANG($1, "Bad enumerator-list."); }
788 enumerator_definition_ecarb:        '}'                                                         { }
789     |                               bang error '}'                                              { YACC_UNBANG($1, "Bad enumerator-definition."); }
790 enumerator_definition_filler:       /* empty */
791     |                               bang error ','                                              { YACC_UNBANG($1, "Bad enumerator-definition."); }
792 enumerator_list_head:               enumerator_definition_filler                                { $$ = YACC_ENUMERATORS(0, 0); }
793     |                               enumerator_list ',' enumerator_definition_filler
794 enumerator_list:                    enumerator_list_head enumerator_definition                  { $$ = YACC_ENUMERATORS($1, $2); }
795 enumerator_definition:              enumerator                                                  { $$ = YACC_ENUMERATOR($1, 0); }
796     |                               enumerator '=' constant_expression                          { $$ = YACC_ENUMERATOR($1, $3); }
797 enumerator:                         identifier
798
799 namespace_definition:               NAMESPACE scoped_id compound_declaration                    { $$ = YACC_NAMESPACE_DEFINITION($2, $3); }
800     |                               NAMESPACE compound_declaration                              { $$ = YACC_NAMESPACE_DEFINITION(0, $2); }
801 namespace_alias_definition:         NAMESPACE scoped_id '=' scoped_id ';'                       { $$ = YACC_NAMESPACE_ALIAS_DEFINITION($2, $4); }
802
803 using_declaration:                  USING declarator_id ';'                                     { $$ = YACC_USING_DECLARATION(false, $2); }
804     |                               USING TYPENAME declarator_id ';'                            { $$ = YACC_USING_DECLARATION(true, $3); }
805
806 using_directive:                    USING NAMESPACE scoped_id ';'                               { $$ = YACC_USING_DIRECTIVE($3); }
807 asm_definition:                     ASM '(' string ')' ';'                                      { $$ = YACC_ASM_DEFINITION($3); }
808 linkage_specification:              EXTERN string looping_declaration                           { $$ = YACC_LINKAGE_SPECIFIER($2, $3); }
809     |                               EXTERN string compound_declaration                          { $$ = YACC_LINKAGE_SPECIFIER($2, $3); }
810
811 /*---------------------------------------------------------------------------------------------------
812  * A.7 Declarators
813  *---------------------------------------------------------------------------------------------------*/
814 /*init-declarator is named init_declaration to reflect the embedded decl-specifier-seq.opt*/
815 init_declarations:                  assignment_expression ',' init_declaration                  { $$ = YACC_EXPRESSIONS(YACC_EXPRESSIONS(0, $1), $3); }
816     |                               init_declarations ',' init_declaration                      { $$ = YACC_EXPRESSIONS($1, $3); }
817 init_declaration:                   assignment_expression
818 /*  |                               assignment_expression '=' initializer_clause                -- covered by assignment_expression */
819 /*  |                               assignment_expression '(' expression_list ')'               -- covered by another set of call arguments */
820
821 /*declarator:                                                                                   -- covered by assignment_expression */
822 /*direct_declarator:                                                                            -- covered by postfix_expression */
823
824 star_ptr_operator:                  '*'                                                         { $$ = YACC_POINTER_DECLARATOR(); }
825     |                               star_ptr_operator cv_qualifier                              { $$ = YACC_CV_DECLARATOR($1, $2); }
826 nested_ptr_operator:                star_ptr_operator                                           { $$ = $1; }
827     |                               id_scope nested_ptr_operator                                { $$ = YACC_NESTED_DECLARATOR($1, $2); }
828 ptr_operator:                       '&'                                                         { $$ = YACC_REFERENCE_DECLARATOR(); }
829     |                               nested_ptr_operator                                         { $$ = $1; }
830     |                               global_scope nested_ptr_operator                            { $$ = YACC_GLOBAL_DECLARATOR($1, $2); }
831 ptr_operator_seq:                   ptr_operator                                                { $$ = YACC_POINTER_EXPRESSION($1, YACC_EPSILON()); }
832     |                               ptr_operator ptr_operator_seq                               { $$ = YACC_POINTER_EXPRESSION($1, $2); }
833 /* Independently coded to localise the shift-reduce conflict: sharing just needs another %prec */
834 ptr_operator_seq.opt:               /* empty */                         %prec SHIFT_THERE       /* Maximise type length */ { $$ = YACC_EXPRESSION(0); }
835     |                               ptr_operator ptr_operator_seq.opt                           { $$ = YACC_POINTER_EXPRESSION($1, $2); }
836
837 cv_qualifier_seq.opt:               /* empty */                                                 { $$ = YACC_CV_QUALIFIERS(0, 0); }
838     |                               cv_qualifier_seq.opt cv_qualifier                           { $$ = YACC_CV_QUALIFIERS($1, $2); }
839 cv_qualifier:                       CONST | VOLATILE /* | CvQualifier */
840
841 /*type_id                                                                                       -- also covered by parameter declaration */
842 type_id:                            type_specifier abstract_declarator.opt                      { $$ = YACC_TYPED_EXPRESSION($1, $2); }
843     |                               type_specifier type_id                                      { $$ = YACC_TYPED_EXPRESSION($1, $2); }
844
845 /*abstract_declarator:                                                                          -- also covered by parameter declaration */
846 abstract_declarator.opt:            /* empty */                                                 { $$ = YACC_EPSILON(); }
847     |                               ptr_operator abstract_declarator.opt                        { $$ = YACC_POINTER_EXPRESSION($1, $2); }
848     |                               direct_abstract_declarator
849 direct_abstract_declarator.opt:     /* empty */                                                 { $$ = YACC_EPSILON(); }
850     |                               direct_abstract_declarator
851 direct_abstract_declarator:         direct_abstract_declarator.opt parenthesis_clause           { $$ = YACC_CALL_EXPRESSION($1, $2); }
852     |                               direct_abstract_declarator.opt '[' ']'                      { $$ = YACC_ARRAY_EXPRESSION($1, 0); }
853     |                               direct_abstract_declarator.opt '[' constant_expression ']'  { $$ = YACC_ARRAY_EXPRESSION($1, $3); }
854 /*  |                               '(' abstract_declarator ')'                                 -- covered by parenthesis_clause */
855
856 parenthesis_clause:                 parameters_clause cv_qualifier_seq.opt                      { $$ = YACC_PARENTHESISED($1, $2, 0); }
857     |                               parameters_clause cv_qualifier_seq.opt exception_specification  { $$ = YACC_PARENTHESISED($1, $2, $3); }
858 parameters_clause:                  '(' parameter_declaration_clause ')'                        { $$ = $2; }
859 /* parameter_declaration_clause also covers init_declaration, type_id, declarator and abstract_declarator. */
860 parameter_declaration_clause:       /* empty */                                                 { $$ = YACC_PARAMETERS(0, 0); }
861     |                               parameter_declaration_list
862     |                               parameter_declaration_list ELLIPSIS                         { $$ = YACC_PARAMETERS($1, YACC_ELLIPSIS_EXPRESSION()); }
863 parameter_declaration_list:         parameter_declaration                                       { $$ = YACC_PARAMETERS(0, $1); }
864     |                               parameter_declaration_list ',' parameter_declaration        { $$ = YACC_PARAMETERS($1, $3); }
865
866 /* A typed abstract qualifier such as
867  *      Class * ...
868  * looks like a multiply, so pointers are parsed as their binary operation equivalents that
869  * ultimately terminate with a degenerate right hand term.
870  */
871 abstract_pointer_declaration:       ptr_operator_seq
872     |                               multiplicative_expression star_ptr_operator ptr_operator_seq.opt { $$ = YACC_MULTIPLY_EXPRESSION($1, $2, $3); }
873 abstract_parameter_declaration:     abstract_pointer_declaration
874     |                               and_expression '&'                                          { $$ = YACC_AND_EXPRESSION($1, YACC_EPSILON()); }
875     |                               and_expression '&' abstract_pointer_declaration             { $$ = YACC_AND_EXPRESSION($1, $3); }
876 special_parameter_declaration:      abstract_parameter_declaration
877     |                               abstract_parameter_declaration '=' assignment_expression    { $$ = YACC_ASSIGNMENT_EXPRESSION($1, $2, $3); }
878     |                               ELLIPSIS                                                    { $$ = YACC_ELLIPSIS_EXPRESSION(); }
879 parameter_declaration:              assignment_expression                                       { $$ = YACC_EXPRESSION_PARAMETER($1); }
880     |                               special_parameter_declaration                               { $$ = YACC_EXPRESSION_PARAMETER($1); }
881     |                               decl_specifier_prefix parameter_declaration                 { $$ = YACC_DECL_SPECIFIER_PARAMETER($2, $1); }
882
883 /*  The grammar is repeated for use within template <>
884  */
885 templated_parameter_declaration:    templated_assignment_expression                             { $$ = YACC_EXPRESSION_PARAMETER($1); }
886     |                               templated_abstract_declaration                              { $$ = YACC_EXPRESSION_PARAMETER($1); }
887     |                               templated_abstract_declaration '=' templated_assignment_expression
888                                                     { $$ = YACC_EXPRESSION_PARAMETER(YACC_ASSIGNMENT_EXPRESSION($1, $2, $3)); }
889     |                               decl_specifier_prefix templated_parameter_declaration       { $$ = YACC_DECL_SPECIFIER_PARAMETER($2, $1); }
890 templated_abstract_declaration:     abstract_pointer_declaration
891     |                               templated_and_expression '&'                                { $$ = YACC_AND_EXPRESSION($1, 0); }
892     |                               templated_and_expression '&' abstract_pointer_declaration   { $$ = YACC_AND_EXPRESSION($1, $3); }
893
894 /*  function_definition includes constructor, destructor, implicit int definitions too.
895  *  A local destructor is successfully parsed as a function-declaration but the ~ was treated as a unary operator.
896  *  constructor_head is the prefix ambiguity between a constructor and a member-init-list starting with a bit-field.
897  */
898 function_definition:        ctor_definition
899     |                       func_definition
900 func_definition:            assignment_expression function_try_block                    { $$ = YACC_FUNCTION_DEFINITION($1, $2); }
901     |                       assignment_expression function_body                         { $$ = YACC_FUNCTION_DEFINITION($1, $2); }
902     |                       decl_specifier_prefix func_definition                       { $$ = YACC_DECL_SPECIFIER_EXPRESSION($2, $1); }
903 ctor_definition:            constructor_head function_try_block                         { $$ = YACC_CTOR_DEFINITION($1, $2); }
904     |                       constructor_head function_body                              { $$ = YACC_CTOR_DEFINITION($1, $2); }
905     |                       decl_specifier_prefix ctor_definition                       { $$ = YACC_DECL_SPECIFIER_EXPRESSION($2, $1); }
906 constructor_head:           bit_field_init_declaration                                  { $$ = YACC_EXPRESSIONS(0, $1); }
907     |                       constructor_head ',' assignment_expression                  { $$ = YACC_EXPRESSIONS($1, $3); }
908 function_try_block:         TRY function_block handler_seq                              { $$ = YACC_TRY_FUNCTION_BLOCK($2, $3); }
909 function_block:             ctor_initializer.opt function_body                          { $$ = YACC_CTOR_FUNCTION_BLOCK($2, $1); }
910 function_body:              compound_statement                                          { $$ = YACC_FUNCTION_BLOCK($1); }
911
912 /*  An = initializer looks like an extended assignment_expression.
913  *  An () initializer looks like a function call.
914  *  initializer is therefore flattened into its generalised customers.
915  *initializer:              '=' initializer_clause                                      -- flattened into caller
916  *  |                       '(' expression_list ')'                                     -- flattened into caller */
917 initializer_clause:         assignment_expression                                       { $$ = YACC_INITIALIZER_EXPRESSION_CLAUSE($1); }
918     |                       braced_initializer
919 braced_initializer:         '{' initializer_list '}'                                    { $$ = YACC_INITIALIZER_LIST_CLAUSE($2); }
920     |                       '{' initializer_list ',' '}'                                { $$ = YACC_INITIALIZER_LIST_CLAUSE($2); }
921     |                       '{' '}'                                                     { $$ = YACC_INITIALIZER_LIST_CLAUSE(0); }
922     |                       '{' looping_initializer_clause '#' bang error '}'           { $$ = 0; YACC_UNBANG($4, "Bad initializer_clause."); }
923     |                       '{' initializer_list ',' looping_initializer_clause '#' bang error '}'
924                                                                                         { $$ = $2; YACC_UNBANG($6, "Bad initializer_clause."); }
925 initializer_list:           looping_initializer_clause                                  { $$ = YACC_INITIALIZER_CLAUSES(0, $1); }
926     |                       initializer_list ',' looping_initializer_clause             { $$ = YACC_INITIALIZER_CLAUSES($1, $3); }
927 looping_initializer_clause: start_search looped_initializer_clause                      { $$ = $2; end_search($$); }
928 looped_initializer_clause:  initializer_clause
929     |                       advance_search '+' looped_initializer_clause                { $$ = $3; }
930     |                       advance_search '-'                                          { $$ = 0; }
931
932 /*---------------------------------------------------------------------------------------------------
933  * A.8 Classes
934  *---------------------------------------------------------------------------------------------------
935  *
936  *  An anonymous bit-field declaration may look very like inheritance:
937  *      class A : B = 3;
938  *      class A : B ;
939  *  The two usages are too distant to try to create and enforce a common prefix so we have to resort to
940  *  a parser hack by backtracking. Inheritance is much the most likely so we mark the input stream context
941  *  and try to parse a base-clause. If we successfully reach a { the base-clause is ok and inheritance was
942  *  the correct choice so we unmark and continue. If we fail to find the { an error token causes back-tracking
943  *  to the alternative parse in elaborated_class_specifier which regenerates the : and declares unconditional success.
944  */
945 colon_mark:                 ':'                                                         { $$ = mark(); }
946 elaborated_class_specifier: class_key scoped_id                    %prec SHIFT_THERE    { $$ = YACC_ELABORATED_TYPE_SPECIFIER($1, $2); }
947     |                       class_key scoped_id colon_mark error                        { $$ = YACC_ELABORATED_TYPE_SPECIFIER($1, $2); rewind_colon($3, $$); }
948 class_specifier_head:       class_key scoped_id colon_mark base_specifier_list '{'      { unmark($4); $$ = YACC_CLASS_SPECIFIER_ID($1, $2, $4); }
949     |                       class_key ':' base_specifier_list '{'                       { $$ = YACC_CLASS_SPECIFIER_ID($1, 0, $3); }
950     |                       class_key scoped_id '{'                                     { $$ = YACC_CLASS_SPECIFIER_ID($1, $2, 0); }
951     |                       class_key '{'                                               { $$ = YACC_CLASS_SPECIFIER_ID($1, 0, 0); }
952 class_key:                  CLASS | STRUCT | UNION
953 class_specifier:            class_specifier_head member_specification.opt '}'           { $$ = YACC_CLASS_MEMBERS($1, $2); }
954     |                       class_specifier_head member_specification.opt util looping_member_declaration '#' bang error '}'
955                                             { $$ = YACC_CLASS_MEMBERS($1, $2); YACC_UNBANG($6, "Bad member_specification.opt."); }
956 member_specification.opt:   /* empty */                                                 { $$ = YACC_MEMBER_DECLARATIONS(0, 0); }
957     |                       member_specification.opt util looping_member_declaration    { $$ = YACC_MEMBER_DECLARATIONS($1, YACC_COMPILE_DECLARATION($2, $3)); }
958     |                       member_specification.opt util looping_member_declaration '#' bang error ';'
959                                                                                                 { $$ = $1; YACC_UNBANG($5, "Bad member-declaration."); }
960 looping_member_declaration: start_search looped_member_declaration                      { $$ = YACC_LINED_DECLARATION($2, $1); end_search($$); }
961 looped_member_declaration:  member_declaration
962     |                       advance_search '+' looped_member_declaration                { $$ = $3; }
963     |                       advance_search '-'                                          { $$ = 0; }
964 member_declaration:         accessibility_specifier
965     |                       simple_member_declaration                                   { $$ = YACC_SIMPLE_DECLARATION($1); }
966     |                       function_definition                                         { $$ = YACC_SIMPLE_DECLARATION($1); }
967 /*  |                       function_definition ';'                                     -- trailing ; covered by null declaration */
968 /*  |                       qualified_id ';'                                            -- covered by simple_member_declaration */
969     |                       using_declaration
970     |                       template_declaration
971
972 /*  The generality of constructor names (there need be no parenthesised argument list) means that that
973  *          name : f(g), h(i)
974  *  could be the start of a constructor or the start of an anonymous bit-field. An ambiguity is avoided by
975  *  parsing the ctor-initializer of a function_definition as a bit-field.
976  */
977 simple_member_declaration:  ';'                                                         { $$ = YACC_EXPRESSION(0); }
978     |                       assignment_expression ';'
979     |                       constructor_head ';'                                        { $$ = $1; }
980     |                       member_init_declarations ';'                                { $$ = $1; }
981     |                       decl_specifier_prefix simple_member_declaration             { $$ = YACC_DECL_SPECIFIER_EXPRESSION($2, $1); }
982 member_init_declarations:   assignment_expression ',' member_init_declaration           { $$ = YACC_EXPRESSIONS(YACC_EXPRESSIONS(0, $1), $3); }
983     |                       constructor_head ',' bit_field_init_declaration             { $$ = YACC_EXPRESSIONS($1, $3); }
984     |                       member_init_declarations ',' member_init_declaration        { $$ = YACC_EXPRESSIONS($1, $3); }
985 member_init_declaration:    assignment_expression
986 /*  |                       assignment_expression '=' initializer_clause                -- covered by assignment_expression */
987 /*  |                       assignment_expression '(' expression_list ')'               -- covered by another set of call arguments */
988     |                       bit_field_init_declaration
989 accessibility_specifier:    access_specifier ':'                                        { $$ = YACC_ACCESSIBILITY_SPECIFIER($1); }
990 bit_field_declaration:      assignment_expression ':' bit_field_width                   { $$ = YACC_BIT_FIELD_EXPRESSION($1, $3); }
991     |                       ':' bit_field_width                                         { $$ = YACC_BIT_FIELD_EXPRESSION(0, $2); }
992 bit_field_width:            logical_or_expression
993 /*  |                       logical_or_expression '?' expression ':' assignment_expression  -- has SR conflict w.r.t later = */
994     |                       logical_or_expression '?' bit_field_width ':' bit_field_width { $$ = YACC_CONDITIONAL_EXPRESSION($1, $3, $5); }
995 bit_field_init_declaration: bit_field_declaration
996     |                       bit_field_declaration '=' initializer_clause                { $$ = YACC_ASSIGNMENT_EXPRESSION($1, $2, $3); }
997
998 /*---------------------------------------------------------------------------------------------------
999  * A.9 Derived classes
1000  *---------------------------------------------------------------------------------------------------*/
1001 /*base_clause:              ':' base_specifier_list                                     -- flattened */
1002 base_specifier_list:        base_specifier                                              { $$ = YACC_BASE_SPECIFIERS(0, $1); }
1003     |                       base_specifier_list ',' base_specifier                      { $$ = YACC_BASE_SPECIFIERS($1, $3); }
1004 base_specifier:             scoped_id                                                   { $$ = YACC_BASE_SPECIFIER($1); }
1005     |                       access_specifier base_specifier                             { $$ = YACC_ACCESS_BASE_SPECIFIER($2, $1); }
1006     |                       VIRTUAL base_specifier                                      { $$ = YACC_VIRTUAL_BASE_SPECIFIER($2); }
1007 access_specifier:           PRIVATE | PROTECTED | PUBLIC
1008
1009 /*---------------------------------------------------------------------------------------------------
1010  * A.10 Special member functions
1011  *---------------------------------------------------------------------------------------------------*/
1012 conversion_function_id:     OPERATOR conversion_type_id                                 { $$ = YACC_CONVERSION_FUNCTION_ID($2); }
1013 conversion_type_id:         type_specifier ptr_operator_seq.opt                         { $$ = YACC_TYPED_EXPRESSION($1, $2); }
1014     |                       type_specifier conversion_type_id                           { $$ = YACC_TYPED_EXPRESSION($1, $2); }
1015 /*
1016  *  Ctor-initialisers can look like a bit field declaration, given the generalisation of names:
1017  *      Class(Type) : m1(1), m2(2) {}
1018  *      NonClass(bit_field) : int(2), second_variable, ...
1019  *  The grammar below is used within a function_try_block or function_definition.
1020  *  See simple_member_declaration for use in normal member function_definition.
1021  */
1022 ctor_initializer.opt:       /* empty */                                                 { $$ = YACC_MEM_INITIALIZERS(0, 0); }
1023     |                       ctor_initializer
1024 ctor_initializer:           ':' mem_initializer_list                                    { $$ = $2; }
1025     |                       ':' mem_initializer_list bang error                         { $$ = $2; YACC_UNBANG($3, "Bad ctor-initializer."); }
1026 mem_initializer_list:       mem_initializer                                             { $$ = YACC_MEM_INITIALIZERS(0, $1); }
1027     |                       mem_initializer_list_head mem_initializer                   { $$ = YACC_MEM_INITIALIZERS($1, $2); }
1028 mem_initializer_list_head:  mem_initializer_list ','
1029     |                       mem_initializer_list bang error ','                         { YACC_UNBANG($2, "Bad mem-initializer."); }
1030 mem_initializer:            mem_initializer_id '(' expression_list.opt ')'              { $$ = YACC_MEM_INITIALIZER($1, $3); }
1031 mem_initializer_id:         scoped_id
1032
1033 /*---------------------------------------------------------------------------------------------------
1034  * A.11 Overloading
1035  *---------------------------------------------------------------------------------------------------*/
1036 operator_function_id:       OPERATOR operator                                           { $$ = YACC_OPERATOR_FUNCTION_ID($2); }
1037 /*
1038  *  It is not clear from the ANSI standard whether spaces are permitted in delete[]. If not then it can
1039  *  be recognised and returned as DELETE_ARRAY by the lexer. Assuming spaces are permitted there is an
1040  *  ambiguity created by the over generalised nature of expressions. operator new is a valid delarator-id
1041  *  which we may have an undimensioned array of. Semantic rubbish, but syntactically valid. Since the
1042  *  array form is covered by the declarator consideration we can exclude the operator here. The need
1043  *  for a semantic rescue can be eliminated at the expense of a couple of shift-reduce conflicts by
1044  *  removing the comments on the next four lines.
1045  */
1046 operator:             /*++++*/      NEW                                                         { $$ = YACC_OPERATOR_NEW_ID(); }
1047     |                 /*++++*/      DELETE                                                      { $$ = YACC_OPERATOR_DELETE_ID(); }
1048 /*  |                 / ---- /      NEW                 %prec SHIFT_THERE                       { $$ = YACC_OPERATOR_NEW_ID(); }
1049 /*  |                 / ---- /      DELETE              %prec SHIFT_THERE                       { $$ = YACC_OPERATOR_DELETE_ID(); }
1050 /*  |                 / ---- /      NEW '[' ']'                                                 -- Covered by array of OPERATOR NEW */
1051 /*  |                 / ---- /      DELETE '[' ']'                                              -- Covered by array of OPERATOR DELETE */
1052     |                               '+'                                                         { $$ = YACC_OPERATOR_ADD_ID(); }
1053     |                               '-'                                                         { $$ = YACC_OPERATOR_SUB_ID(); }
1054     |                               '*'                                                         { $$ = YACC_OPERATOR_MUL_ID(); }
1055     |                               '/'                                                         { $$ = YACC_OPERATOR_DIV_ID(); }
1056     |                               '%'                                                         { $$ = YACC_OPERATOR_MOD_ID(); }
1057     |                               '^'                                                         { $$ = YACC_OPERATOR_XOR_ID(); }
1058     |                               '&'                                                         { $$ = YACC_OPERATOR_BIT_AND_ID(); }
1059     |                               '|'                                                         { $$ = YACC_OPERATOR_BIT_OR_ID(); }
1060     |                               '~'                                                         { $$ = YACC_OPERATOR_BIT_NOT_ID(); }
1061     |                               '!'                                                         { $$ = YACC_OPERATOR_LOG_NOT_ID(); }
1062     |                               '='                                                         { $$ = YACC_OPERATOR_ASS_ID(); }
1063     |                               '<'                                                         { $$ = YACC_OPERATOR_LT_ID(); }
1064     |                               '>'                                                         { $$ = YACC_OPERATOR_GT_ID(); }
1065     |                               ASS_ADD                                                     { $$ = YACC_OPERATOR_ASS_ADD_ID(); }
1066     |                               ASS_SUB                                                     { $$ = YACC_OPERATOR_ASS_SUB_ID(); }
1067     |                               ASS_MUL                                                     { $$ = YACC_OPERATOR_ASS_MUL_ID(); }
1068     |                               ASS_DIV                                                     { $$ = YACC_OPERATOR_ASS_DIV_ID(); }
1069     |                               ASS_MOD                                                     { $$ = YACC_OPERATOR_ASS_MOD_ID(); }
1070     |                               ASS_XOR                                                     { $$ = YACC_OPERATOR_ASS_XOR_ID(); }
1071     |                               ASS_AND                                                     { $$ = YACC_OPERATOR_ASS_BIT_AND_ID(); }
1072     |                               ASS_OR                                                      { $$ = YACC_OPERATOR_ASS_BIT_OR_ID(); }
1073     |                               SHL                                                         { $$ = YACC_OPERATOR_SHL_ID(); }
1074     |                               SHR                                                         { $$ = YACC_OPERATOR_SHR_ID(); }
1075     |                               ASS_SHR                                                     { $$ = YACC_OPERATOR_ASS_SHR_ID(); }
1076     |                               ASS_SHL                                                     { $$ = YACC_OPERATOR_ASS_SHL_ID(); }
1077     |                               EQ                                                          { $$ = YACC_OPERATOR_EQ_ID(); }
1078     |                               NE                                                          { $$ = YACC_OPERATOR_NE_ID(); }
1079     |                               LE                                                          { $$ = YACC_OPERATOR_LE_ID(); }
1080     |                               GE                                                          { $$ = YACC_OPERATOR_GE_ID(); }
1081     |                               LOG_AND                                                     { $$ = YACC_OPERATOR_LOG_AND_ID(); }
1082     |                               LOG_OR                                                      { $$ = YACC_OPERATOR_LOG_OR_ID(); }
1083     |                               INC                                                         { $$ = YACC_OPERATOR_INC_ID(); }
1084     |                               DEC                                                         { $$ = YACC_OPERATOR_DEC_ID(); }
1085     |                               ','                                                         { $$ = YACC_OPERATOR_COMMA_ID(); }
1086     |                               ARROW_STAR                                                  { $$ = YACC_OPERATOR_ARROW_STAR_ID(); }
1087     |                               ARROW                                                       { $$ = YACC_OPERATOR_ARROW_ID(); }
1088     |                               '(' ')'                                                     { $$ = YACC_OPERATOR_CALL_ID(); }
1089     |                               '[' ']'                                                     { $$ = YACC_OPERATOR_INDEX_ID(); }
1090
1091 /*---------------------------------------------------------------------------------------------------
1092  * A.12 Templates
1093  *---------------------------------------------------------------------------------------------------*/
1094 template_declaration:               template_parameter_clause declaration                       { $$ = YACC_TEMPLATE_DECLARATION($1, $2); }
1095     |                               EXPORT template_declaration                                 { $$ = YACC_DECL_SPECIFIER_DECLARATION($2, $1); }
1096 template_parameter_clause:          TEMPLATE '<' template_parameter_list '>'                    { $$ = $3; }
1097 template_parameter_list:            template_parameter                                          { $$ = YACC_TEMPLATE_PARAMETERS(0, $1); }
1098     |                               template_parameter_list ',' template_parameter              { $$ = YACC_TEMPLATE_PARAMETERS($1, $3); }
1099 template_parameter:                 simple_type_parameter                                       { $$ = YACC_INIT_SIMPLE_TYPE_PARAMETER($1, 0); }
1100     |                               simple_type_parameter '=' type_id                           { $$ = YACC_INIT_SIMPLE_TYPE_PARAMETER($1, $3); }
1101     |                               templated_type_parameter                                    { $$ = YACC_INIT_TEMPLATED_PARAMETER($1, 0); }
1102     |                               templated_type_parameter '=' identifier                     { $$ = YACC_INIT_TEMPLATED_PARAMETER($1, $3); }
1103     |                               templated_parameter_declaration                             { $$ = YACC_TEMPLATE_PARAMETER($1); }
1104     |                               bang error                                                  { $$ = 0; YACC_UNBANG($1, "Bad template-parameter."); }
1105 simple_type_parameter:              CLASS                                                       { $$ = YACC_CLASS_TYPE_PARAMETER(0); }
1106 /*  |                               CLASS identifier                                            -- covered by parameter_declaration */
1107     |                               TYPENAME                                                    { $$ = YACC_TYPENAME_TYPE_PARAMETER(0); }
1108 /*  |                               TYPENAME identifier                                         -- covered by parameter_declaration */
1109 templated_type_parameter:           template_parameter_clause CLASS                             { $$ = YACC_TEMPLATED_TYPE_PARAMETER($1, 0); }
1110     |                               template_parameter_clause CLASS identifier                  { $$ = YACC_TEMPLATED_TYPE_PARAMETER($1, $3); }
1111 template_id:                        TEMPLATE identifier '<' template_argument_list '>'          { $$ = YACC_TEMPLATE_NAME($2, $4); }
1112     |                               TEMPLATE template_id                                        { $$ = $2; }
1113 /*
1114  *  template-argument is evaluated using a templated...expression so that > resolves to end of template.
1115  */
1116 template_argument_list:             template_argument                                           { $$ = YACC_TEMPLATE_ARGUMENTS(0, $1); }
1117     |                               template_argument_list ',' template_argument                { $$ = YACC_TEMPLATE_ARGUMENTS($1, $3); }
1118 template_argument:                  templated_parameter_declaration                             { $$ = YACC_TEMPLATE_ARGUMENT($1); }
1119 /*  |                               type_id                                                     -- covered by templated_parameter_declaration */
1120 /*  |                               template_name                                               -- covered by templated_parameter_declaration */
1121 /*  |                               error                                                       -- must allow template failure to re-search */
1122
1123 /*
1124  *  Generalised naming makes identifier a valid declaration, so TEMPLATE identifier is too.
1125  *  The TEMPLATE prefix is therefore folded into all names, parenthesis_clause and decl_specifier_prefix.
1126  */
1127 /*explicit_instantiation:           TEMPLATE declaration */
1128 explicit_specialization:            TEMPLATE '<' '>' declaration                                { $$ = YACC_EXPLICIT_SPECIALIZATION($4); }
1129
1130 /*---------------------------------------------------------------------------------------------------
1131  * A.13 Exception Handling
1132  *---------------------------------------------------------------------------------------------------*/
1133 try_block:                          TRY compound_statement handler_seq                          { $$ = YACC_TRY_BLOCK($2, $3); }
1134 /*function_try_block:                                                                           -- moved near function_block */
1135 handler_seq:                        handler                                                     { $$ = YACC_HANDLERS(0, $1); }
1136     |                               handler handler_seq                                         { $$ = YACC_HANDLERS($2, $1); }
1137 handler:                            CATCH '(' exception_declaration ')' compound_statement      { $$ = YACC_HANDLER($3, $5); }
1138 exception_declaration:              parameter_declaration                                       { $$ = YACC_EXCEPTION_DECLARATION($1); }
1139 /*                                  ELLIPSIS                                                    -- covered by parameter_declaration */
1140 throw_expression:                   THROW                                                       { $$ = YACC_THROW_EXPRESSION(0); }
1141     |                               THROW assignment_expression                                 { $$ = YACC_THROW_EXPRESSION($2); }
1142 templated_throw_expression:         THROW                                                       { $$ = YACC_THROW_EXPRESSION(0); }
1143     |                               THROW templated_assignment_expression                       { $$ = YACC_THROW_EXPRESSION($2); }
1144 exception_specification:            THROW '(' ')'                                               { $$ = YACC_EXCEPTION_SPECIFICATION(0); }
1145     |                               THROW '(' type_id_list ')'                                  { $$ = YACC_EXCEPTION_SPECIFICATION($3); }
1146 type_id_list:                       type_id                                                     { $$ = YACC_EXPRESSIONS(0, $1); }
1147     |                               type_id_list ',' type_id                                    { $$ = YACC_EXPRESSIONS($1, $3); }
1148
1149 /*---------------------------------------------------------------------------------------------------
1150  * Back-tracking and context support
1151  *---------------------------------------------------------------------------------------------------*/
1152 advance_search:                     error               { yyerrok; advance_search(); } /* Rewind and queue '+' or '-' '#' */       
1153 bang:                               /* empty */         { $$ = YACC_BANG(); }   /* set flag to suppress "parse error" */ 
1154 mark:                               /* empty */         { $$ = mark(); }        /* Push lookahead and input token stream context onto a stack */
1155 nest:                               /* empty */         { $$ = nest(); }        /* Push a declaration nesting depth onto the parse stack */
1156 start_search:                       /* empty */         { $$ = YACC_LINE(); start_search(false); }    /* Create/reset binary search context */
1157 start_search1:                      /* empty */         { $$ = YACC_LINE(); start_search(true); }     /* Create/reset binary search context */
1158 util:                               /* empty */         { $$ = YACC_UTILITY_MODE(); }           /* Get current utility mode */
1159 /*StartTester*/
1160 %%
1161 #include <CxxParsing.cxx>
1162 /*EndTester*/