source: src/Parser/parser.yy@ d96d4f0

stuck-waitfor-destruct
Last change on this file since d96d4f0 was 253d0b4, checked in by Peter A. Buhr <pabuhr@…>, 19 months ago

change error message header, simplify forCtrl to have only identifier in initialization

  • Property mode set to 100644
File size: 178.1 KB
RevLine 
[b87a5ed]1//
2// Cforall Version 1.0.0 Copyright (C) 2015 University of Waterloo
3//
4// The contents of this file are covered under the licence agreement in the
5// file "LICENCE" distributed with Cforall.
6//
[9335ecc]7// parser.yy --
[974906e2]8//
[c11e31c]9// Author : Peter A. Buhr
10// Created On : Sat Sep 1 20:22:55 2001
[04c78215]11// Last Modified By : Peter A. Buhr
[253d0b4]12// Last Modified On : Mon Jun 24 22:45:20 2024
13// Update Count : 6684
[974906e2]14//
[c11e31c]15
[de62360d]16// This grammar is based on the ANSI99/11 C grammar, specifically parts of EXPRESSION and STATEMENTS, and on the C
17// grammar by James A. Roskind, specifically parts of DECLARATIONS and EXTERNAL DEFINITIONS. While parts have been
18// copied, important changes have been made in all sections; these changes are sufficient to constitute a new grammar.
19// In particular, this grammar attempts to be more syntactically precise, i.e., it parses less incorrect language syntax
20// that must be subsequently rejected by semantic checks. Nevertheless, there are still several semantic checks
21// required and many are noted in the grammar. Finally, the grammar is extended with GCC and CFA language extensions.
[c11e31c]22
[de62360d]23// Acknowledgments to Richard Bilson, Glen Ditchfield, and Rodolfo Gabriel Esteves who all helped when I got stuck with
24// the grammar.
[c11e31c]25
26// The root language for this grammar is ANSI99/11 C. All of ANSI99/11 is parsed, except for:
27//
[9380add]28// designation with '=' (use ':' instead)
[c11e31c]29//
[9380add]30// This incompatibility is discussed in detail before the "designation" grammar rule. Most of the syntactic extensions
31// from ANSI90 to ANSI11 C are marked with the comment "C99/C11".
[f9c3100]32
[e16eb460]33// This grammar also has two levels of extensions. The first extensions cover most of the GCC C extensions. All of the
[9380add]34// syntactic extensions for GCC C are marked with the comment "GCC". The second extensions are for Cforall (CFA), which
35// fixes several of C's outstanding problems and extends C with many modern language concepts. All of the syntactic
36// extensions for CFA C are marked with the comment "CFA".
[51b73452]37
38%{
[ec3f9c8]39#define YYDEBUG_LEXER_TEXT( yylval ) // lexer loads this up each time
[b87a5ed]40#define YYDEBUG 1 // get the pretty debugging code to compile
[201aeb9]41#define YYERROR_VERBOSE // more information in syntax errors
[51b73452]42
43#undef __GNUC_MINOR__
44
45#include <cstdio>
[9feb34b]46#include <sstream>
[51b73452]47#include <stack>
[9ed4f94]48using namespace std;
49
[c92bdcc]50#include "DeclarationNode.hpp" // for DeclarationNode, ...
51#include "ExpressionNode.hpp" // for ExpressionNode, ...
52#include "InitializerNode.hpp" // for InitializerNode, ...
53#include "ParserTypes.hpp"
54#include "StatementNode.hpp" // for build_...
55#include "TypedefTable.hpp"
56#include "TypeData.hpp"
[7a780ad]57#include "AST/Type.hpp" // for BasicType, BasicKind
[c92bdcc]58#include "Common/SemanticError.hpp" // error_str
59#include "Common/Utility.hpp" // for maybeMoveBuild, maybeBuild, CodeLo...
[51b73452]60
[ae2f2ae]61// lex uses __null in a boolean context, it's fine.
[0bd46fd]62#ifdef __clang__
[09f34a84]63#pragma GCC diagnostic ignored "-Wparentheses-equality"
[0bd46fd]64#endif
[ae2f2ae]65
[cbaee0d]66extern DeclarationNode * parseTree;
[bb7422a]67extern ast::Linkage::Spec linkage;
[0da3e2c]68extern TypedefTable typedefTable;
69
[bb7422a]70stack<ast::Linkage::Spec> linkageStack;
[7bf7fb9]71
[15697ff]72bool appendStr( string & to, string & from ) {
73 // 1. Multiple strings are concatenated into a single string but not combined internally. The reason is that
[ea0c5e3]74 // "\x12" "3" is treated as 2 characters versus 1 because "escape sequences are converted into single members of
[15697ff]75 // the execution character set just prior to adjacent string literal concatenation" (C11, Section 6.4.5-8). It is
76 // easier to let the C compiler handle this case.
77 //
78 // 2. String encodings are transformed into canonical form (one encoding at start) so the encoding can be found
79 // without searching the string, e.g.: "abc" L"def" L"ghi" => L"abc" "def" "ghi". Multiple encodings must match,
[efc8f3e]80 // e.g., u"a" U"b" L"c" is disallowed.
[15697ff]81
82 if ( from[0] != '"' ) { // encoding ?
83 if ( to[0] != '"' ) { // encoding ?
[ea0c5e3]84 if ( to[0] != from[0] || to[1] != from[1] ) { // different encodings ?
[15697ff]85 yyerror( "non-matching string encodings for string-literal concatenation" );
86 return false; // parse error, must call YYERROR in action
[ea0c5e3]87 } else if ( from[1] == '8' ) {
88 from.erase( 0, 1 ); // remove 2nd encoding
[15697ff]89 } // if
90 } else {
[ea0c5e3]91 if ( from[1] == '8' ) { // move encoding to start
92 to = "u8" + to;
93 from.erase( 0, 1 ); // remove 2nd encoding
94 } else {
95 to = from[0] + to;
96 } // if
[15697ff]97 } // if
98 from.erase( 0, 1 ); // remove 2nd encoding
99 } // if
100 to += " " + from; // concatenated into single string
101 return true;
[7bf7fb9]102} // appendStr
[c0aa336]103
[d8454b9]104DeclarationNode * distAttr( DeclarationNode * typeSpec, DeclarationNode * declList ) {
[4eb3a7c5]105 // Distribute type specifier across all declared variables, e.g., static, const, __attribute__.
[d8454b9]106 assert( declList );
107
[4eb3a7c5]108 // Do not distribute attributes for aggregates because the attributes surrounding the aggregate belong it not the
109 // variables in the declaration list, e.g.,
110 //
111 // struct __attribute__(( aligned(128) )) S { ...
112 // } v1 __attribute__(( aligned(64) )), v2 __attribute__(( aligned(32) )), v3;
113 // struct S v4;
114 //
115 // v1 => 64, v2 =>32, v3 => 128, v2 => 128
116 //
117 // Anonymous aggregates are a special case because there is no aggregate to bind the attribute to; hence it floats
118 // to the declaration list.
119 //
120 // struct __attribute__(( aligned(128) )) /*anonymous */ { ... } v1;
121 //
122 // v1 => 128
123
124 bool copyattr = ! (typeSpec->type && typeSpec->type->kind == TypeData::Aggregate && ! typeSpec->type->aggregate.anon );
125
126 // addType copies the type information for the aggregate instances from typeSpec into cl's aggInst.aggregate.
127 DeclarationNode * cl = (new DeclarationNode)->addType( typeSpec ); // typeSpec IS DELETED!!!
128
[647e2ea]129 // Start at second variable in declaration list and clone the type specifiers for each variable.
[44adf1b]130 for ( DeclarationNode * cur = declList->next ; cur != nullptr; cur = cur->next ) {
[4eb3a7c5]131 cl->cloneBaseType( cur, copyattr ); // cur is modified
[c0aa336]132 } // for
[4eb3a7c5]133
134 // Add first variable in declaration list with hidden type information in aggInst.aggregate, which is used by
135 // extractType to recover the type for the aggregate instances.
136 declList->addType( cl, copyattr ); // cl IS DELETED!!!
[c0aa336]137 return declList;
138} // distAttr
139
140void distExt( DeclarationNode * declaration ) {
141 // distribute EXTENSION across all declarations
[44adf1b]142 for ( DeclarationNode *iter = declaration ; iter != nullptr ; iter = iter->next ) {
[c0aa336]143 iter->set_extension( true );
144 } // for
145} // distExt
[fdca7c6]146
[e07caa2]147void distInl( DeclarationNode * declaration ) {
[5695645]148 // distribute INLINE across all declarations
[44adf1b]149 for ( DeclarationNode *iter = declaration ; iter != nullptr ; iter = iter->next ) {
[e07caa2]150 iter->set_inLine( true );
151 } // for
152} // distInl
153
[4c3ee8d]154void distQual( DeclarationNode * declaration, DeclarationNode * qualifiers ) {
[284da8c]155 // distribute qualifiers across all non-variable declarations in a distribution statemement
[44adf1b]156 for ( DeclarationNode * iter = declaration ; iter != nullptr ; iter = iter->next ) {
[284da8c]157 // SKULLDUGGERY: Distributions are parsed inside out, so qualifiers are added to declarations inside out. Since
158 // addQualifiers appends to the back of the list, the forall clauses are in the wrong order (right to left). To
159 // get the qualifiers in the correct order and still use addQualifiers (otherwise, 90% of addQualifiers has to
160 // be copied to add to front), the appropriate forall pointers are interchanged before calling addQualifiers.
161 DeclarationNode * clone = qualifiers->clone();
162 if ( qualifiers->type ) { // forall clause ? (handles SC)
163 if ( iter->type->kind == TypeData::Aggregate ) { // struct/union ?
164 swap( clone->type->forall, iter->type->aggregate.params );
165 iter->addQualifiers( clone );
166 } else if ( iter->type->kind == TypeData::AggregateInst && iter->type->aggInst.aggregate->aggregate.body ) { // struct/union ?
167 // Create temporary node to hold aggregate, call addQualifiers as above, then put nodes back together.
168 DeclarationNode newnode;
169 swap( newnode.type, iter->type->aggInst.aggregate );
170 swap( clone->type->forall, newnode.type->aggregate.params );
171 newnode.addQualifiers( clone );
172 swap( newnode.type, iter->type->aggInst.aggregate );
173 } else if ( iter->type->kind == TypeData::Function ) { // routines ?
174 swap( clone->type->forall, iter->type->forall );
175 iter->addQualifiers( clone );
176 } // if
177 } else { // just SC qualifiers
178 iter->addQualifiers( clone );
179 } // if
[4c3ee8d]180 } // for
[284da8c]181 delete qualifiers;
182} // distQual
[4c3ee8d]183
[c38ae92]184// There is an ambiguity for inline generic-routine return-types and generic routines.
185// forall( otype T ) struct S { int i; } bar( T ) {}
186// Does the forall bind to the struct or the routine, and how would it be possible to explicitly specify the binding.
187// forall( otype T ) struct S { int T; } forall( otype W ) bar( W ) {}
[7fdb94e1]188// Currently, the forall is associated with the routine, and the generic type has to be separately defined:
189// forall( otype T ) struct S { int T; };
190// forall( otype W ) bar( W ) {}
[c38ae92]191
192void rebindForall( DeclarationNode * declSpec, DeclarationNode * funcDecl ) {
[7fdb94e1]193 if ( declSpec->type->kind == TypeData::Aggregate ) { // ignore aggregate definition
[c38ae92]194 funcDecl->type->forall = declSpec->type->aggregate.params; // move forall from aggregate to function type
195 declSpec->type->aggregate.params = nullptr;
196 } // if
197} // rebindForall
198
[60a8062]199string * build_postfix_name( string * name ) {
200 *name = string("__postfix_func_") + *name;
201 return name;
[dc7db63]202} // build_postfix_name
203
[f7e4db27]204DeclarationNode * fieldDecl( DeclarationNode * typeSpec, DeclarationNode * fieldList ) {
[67467a3]205 if ( nullptr == fieldList ) {
206 if ( !( typeSpec->type && typeSpec->type->kind == TypeData::Aggregate ) ) {
[f7e4db27]207 stringstream ss;
[d8454b9]208 // printf( "fieldDecl1 typeSpec %p\n", typeSpec ); typeSpec->type->print( std::cout );
[f7e4db27]209 SemanticWarning( yylloc, Warning::SuperfluousDecl, ss.str().c_str() );
210 return nullptr;
211 } // if
[d8454b9]212 // printf( "fieldDecl2 typeSpec %p\n", typeSpec ); typeSpec->type->print( std::cout );
[f7e4db27]213 fieldList = DeclarationNode::newName( nullptr );
214 } // if
[d8454b9]215
216 // printf( "fieldDecl3 typeSpec %p\n", typeSpec ); typeSpec->print( std::cout, 0 );
[4eb3a7c5]217 DeclarationNode * temp = distAttr( typeSpec, fieldList ); // mark all fields in list
[d8454b9]218 // printf( "fieldDecl4 temp %p\n", temp ); temp->print( std::cout, 0 );
219 return temp;
[f7e4db27]220} // fieldDecl
221
[bb7422a]222#define NEW_ZERO new ExpressionNode( build_constantInteger( yylloc, *new string( "0" ) ) )
223#define NEW_ONE new ExpressionNode( build_constantInteger( yylloc, *new string( "1" ) ) )
[52be5948]224#define UPDOWN( compop, left, right ) (compop == OperKinds::LThan || compop == OperKinds::LEThan ? left : right)
[253d0b4]225#define MISSING_ANON_FIELD "illegal syntax, missing loop fields with an anonymous loop index is meaningless as loop index is unavailable in loop body."
226#define MISSING_LOW "illegal syntax, missing low value for up-to range so index is uninitialized."
227#define MISSING_HIGH "illegal syntax, missing high value for down-to range so index is uninitialized."
228
229static ForCtrl * makeForCtrl( const CodeLocation & location, DeclarationNode * init, enum OperKinds compop,
230 ExpressionNode * comp, ExpressionNode * inc ) {
[1cdc052]231 // Wrap both comp/inc if they are non-null.
[bb7422a]232 if ( comp ) comp = new ExpressionNode( build_binary_val( location,
[1cdc052]233 compop,
[bb7422a]234 new ExpressionNode( build_varref( location, new string( *init->name ) ) ),
[1cdc052]235 comp ) );
[bb7422a]236 if ( inc ) inc = new ExpressionNode( build_binary_val( location,
[1cdc052]237 // choose += or -= for upto/downto
238 compop == OperKinds::LThan || compop == OperKinds::LEThan ? OperKinds::PlusAssn : OperKinds::MinusAssn,
[bb7422a]239 new ExpressionNode( build_varref( location, new string( *init->name ) ) ),
[1cdc052]240 inc ) );
241 // The StatementNode call frees init->name, it must happen later.
242 return new ForCtrl( new StatementNode( init ), comp, inc );
243}
244
[bb7422a]245ForCtrl * forCtrl( const CodeLocation & location, DeclarationNode * index, ExpressionNode * start, enum OperKinds compop, ExpressionNode * comp, ExpressionNode * inc ) {
[d78c238]246 if ( index->initializer ) {
[253d0b4]247 SemanticError( yylloc, "illegal syntax, direct initialization disallowed. Use instead: type var; initialization ~ comparison ~ increment." );
[d78c238]248 } // if
249 if ( index->next ) {
[253d0b4]250 SemanticError( yylloc, "illegal syntax, multiple loop indexes disallowed in for-loop declaration." );
[d78c238]251 } // if
[1cdc052]252 DeclarationNode * initDecl = index->addInitializer( new InitializerNode( start ) );
[bb7422a]253 return makeForCtrl( location, initDecl, compop, comp, inc );
[d78c238]254} // forCtrl
255
[bb7422a]256ForCtrl * forCtrl( const CodeLocation & location, ExpressionNode * type, string * index, ExpressionNode * start, enum OperKinds compop, ExpressionNode * comp, ExpressionNode * inc ) {
257 ast::ConstantExpr * constant = dynamic_cast<ast::ConstantExpr *>(type->expr.get());
258 if ( constant && (constant->rep == "0" || constant->rep == "1") ) {
[7a780ad]259 type = new ExpressionNode( new ast::CastExpr( location, maybeMoveBuild(type), new ast::BasicType( ast::BasicKind::SignedInt ) ) );
[0982a05]260 } // if
[1cdc052]261 DeclarationNode * initDecl = distAttr(
262 DeclarationNode::newTypeof( type, true ),
263 DeclarationNode::newName( index )->addInitializer( new InitializerNode( start ) )
264 );
[bb7422a]265 return makeForCtrl( location, initDecl, compop, comp, inc );
[f271bdd]266} // forCtrl
267
[253d0b4]268#define MISSING_LOOP_INDEX "illegal syntax, only a single identifier or declaration allowed in initialization, e.g., for ( i; ... ) or for ( int i; ... ). Expression disallowed."
269
[bb7422a]270ForCtrl * forCtrl( const CodeLocation & location, ExpressionNode * type, ExpressionNode * index, ExpressionNode * start, enum OperKinds compop, ExpressionNode * comp, ExpressionNode * inc ) {
271 if ( auto identifier = dynamic_cast<ast::NameExpr *>(index->expr.get()) ) {
272 return forCtrl( location, type, new string( identifier->name ), start, compop, comp, inc );
[253d0b4]273 // } else if ( auto commaExpr = dynamic_cast<ast::CommaExpr *>( index->expr.get() ) ) {
274 // if ( auto identifier = commaExpr->arg2.as<ast::NameExpr>() ) {
275 // return forCtrl( location, type, new string( identifier->name ), start, compop, comp, inc );
276 // } else {
277 // SemanticError( yylloc, "illegal syntax, loop-index name missing. Expression disallowed." ); return nullptr;
278 // } // if
[f1aeede]279 } else {
[253d0b4]280 SemanticError( yylloc, MISSING_LOOP_INDEX ); return nullptr;
[f1aeede]281 } // if
[f271bdd]282} // forCtrl
283
[525f7ad]284ForCtrl * enumRangeCtrl( ExpressionNode * index_expr, ExpressionNode * range_over_expr ) {
285 if ( auto identifier = dynamic_cast<ast::NameExpr *>(index_expr->expr.get()) ) {
[253d0b4]286 DeclarationNode * indexDecl = DeclarationNode::newName( new std::string(identifier->name) );
[525f7ad]287 assert( range_over_expr );
[253d0b4]288 return new ForCtrl( new StatementNode( indexDecl ), range_over_expr );
289 // } else if (auto commaExpr = dynamic_cast<ast::CommaExpr *>( index_expr->expr.get() )) {
290 // if ( auto identifier = commaExpr->arg1.as<ast::NameExpr>() ) {
291 // assert( range_over_expr );
292 // DeclarationNode * indexDecl = distAttr(
293 // DeclarationNode::newTypeof( range_over_expr, true ),
294 // DeclarationNode::newName( new std::string( identifier->name) ) );
295 // return new ForCtrl( new StatementNode( indexDecl ), range_over_expr );
296 // } else {
297 // SemanticError( yylloc, "illegal syntax, loop-index name missing. Comma expression disallowed." ); return nullptr;
298 // } // if
[525f7ad]299 } else {
[253d0b4]300 SemanticError( yylloc, MISSING_LOOP_INDEX ); return nullptr;
[525f7ad]301 } // if
302} // enumRangeCtrl
303
[996c8ed]304static void IdentifierBeforeIdentifier( string & identifier1, string & identifier2, const char * kind ) {
[253d0b4]305 SemanticError( yylloc, "illegal syntax, adjacent identifiers \"%s\" and \"%s\" are not meaningful in an %s.\n"
[b1f2007d]306 "Possible cause is misspelled type name or missing generic parameter.",
307 identifier1.c_str(), identifier2.c_str(), kind );
[996c8ed]308} // IdentifierBeforeIdentifier
309
310static void IdentifierBeforeType( string & identifier, const char * kind ) {
[253d0b4]311 SemanticError( yylloc, "illegal syntax, identifier \"%s\" cannot appear before a %s.\n"
[b1f2007d]312 "Possible cause is misspelled storage/CV qualifier, misspelled typename, or missing generic parameter.",
313 identifier.c_str(), kind );
[996c8ed]314} // IdentifierBeforeType
315
[24711a3]316bool forall = false; // aggregate have one or more forall qualifiers ?
[d48e529]317
[201aeb9]318// https://www.gnu.org/software/bison/manual/bison.html#Location-Type
319#define YYLLOC_DEFAULT(Cur, Rhs, N) \
320if ( N ) { \
321 (Cur).first_line = YYRHSLOC( Rhs, 1 ).first_line; \
322 (Cur).first_column = YYRHSLOC( Rhs, 1 ).first_column; \
323 (Cur).last_line = YYRHSLOC( Rhs, N ).last_line; \
324 (Cur).last_column = YYRHSLOC( Rhs, N ).last_column; \
325 (Cur).filename = YYRHSLOC( Rhs, 1 ).filename; \
326} else { \
327 (Cur).first_line = (Cur).last_line = YYRHSLOC( Rhs, 0 ).last_line; \
328 (Cur).first_column = (Cur).last_column = YYRHSLOC( Rhs, 0 ).last_column; \
329 (Cur).filename = YYRHSLOC( Rhs, 0 ).filename; \
330}
[51b73452]331%}
332
[15697ff]333%define parse.error verbose
334
[201aeb9]335// Types declaration for productions
[7cf8006]336
[0982a05]337%union {
[6cef439]338 // A raw token can be used.
[a67b60e]339 Token tok;
[6cef439]340
341 // The general node types hold some generic node or list of nodes.
[a67b60e]342 DeclarationNode * decl;
[6cef439]343 InitializerNode * init;
344 ExpressionNode * expr;
[32d6fdc]345 StatementNode * stmt;
[6611177]346 ClauseNode * clause;
[6cef439]347 TypeData * type;
348
349 // Special "nodes" containing compound information.
[473d1da0]350 CondCtl * ifctl;
[32d6fdc]351 ForCtrl * forctl;
352 LabelNode * labels;
[6cef439]353
354 // Various flags and single values that become fields later.
355 ast::AggregateDecl::Aggregate aggKey;
356 ast::TypeDecl::Kind tclass;
[32d6fdc]357 OperKinds oper;
358 bool is_volatile;
359 EnumHiding enum_hiding;
360 ast::ExceptionKind except_kind;
[6cef439]361 // String passes ownership with it.
362 std::string * str;
363
364 // Narrower node types are used to avoid constant unwrapping.
365 ast::WaitForStmt * wfs;
366 ast::WaitUntilStmt::ClauseNode * wucn;
[bb7422a]367 ast::GenericExpr * genexpr;
[a67b60e]368}
369
[bb7422a]370// ************************ TERMINAL TOKENS ********************************
[51b73452]371
[c11e31c]372// keywords
[51b73452]373%token TYPEDEF
[a7c90d4]374%token EXTERN STATIC AUTO REGISTER
[59c7e3e]375%token THREADLOCALGCC THREADLOCALC11 // GCC, C11
[a7c90d4]376%token INLINE FORTRAN // C99, extension ISO/IEC 9899:1999 Section J.5.9(1)
377%token NORETURN // C11
[51b73452]378%token CONST VOLATILE
[b87a5ed]379%token RESTRICT // C99
[a7c90d4]380%token ATOMIC // C11
[1f652a7]381%token FORALL MUTEX VIRTUAL VTABLE COERCE // CFA
[72457b6]382%token VOID CHAR SHORT INT LONG FLOAT DOUBLE SIGNED UNSIGNED
[b87a5ed]383%token BOOL COMPLEX IMAGINARY // C99
[f1da02c]384%token INT128 UINT128 uuFLOAT80 uuFLOAT128 // GCC
[e15853c]385%token uFLOAT16 uFLOAT32 uFLOAT32X uFLOAT64 uFLOAT64X uFLOAT128 // GCC
[15f769c]386%token DECIMAL32 DECIMAL64 DECIMAL128 // GCC
[72457b6]387%token ZERO_T ONE_T // CFA
[a8ced63]388%token SIZEOF TYPEOF VA_LIST VA_ARG AUTO_TYPE COUNTOF // GCC
[1f652a7]389%token OFFSETOF BASETYPEOF TYPEID // CFA
[51b73452]390%token ENUM STRUCT UNION
[c27fb59]391%token EXCEPTION // CFA
[553772b]392%token GENERATOR COROUTINE MONITOR THREAD // CFA
[a7c90d4]393%token OTYPE FTYPE DTYPE TTYPE TRAIT // CFA
[25744d2]394// %token RESUME // CFA
[1f652a7]395%token LABEL // GCC
[25744d2]396%token SUSPEND // CFA
[b87a5ed]397%token ATTRIBUTE EXTENSION // GCC
[51b73452]398%token IF ELSE SWITCH CASE DEFAULT DO WHILE FOR BREAK CONTINUE GOTO RETURN
[466787a]399%token CHOOSE FALLTHRU FALLTHROUGH WITH WHEN WAITFOR WAITUNTIL // CFA
[11ab0b4a]400%token CORUN COFOR
[4744074]401%token DISABLE ENABLE TRY THROW THROWRESUME AT // CFA
[b87a5ed]402%token ASM // C99, extension ISO/IEC 9899:1999 Section J.5.10(1)
[a7c90d4]403%token ALIGNAS ALIGNOF GENERIC STATICASSERT // C11
[51b73452]404
[c11e31c]405// names and constants: lexer differentiates between identifier and typedef names
[9fd9d015]406%token<tok> IDENTIFIER TYPEDIMname TYPEDEFname TYPEGENname
[12f1156]407%token<tok> TIMEOUT WAND WOR CATCH RECOVER CATCHRESUME FIXUP FINALLY // CFA
[9fb1367]408%token<tok> INTEGERconstant CHARACTERconstant STRINGliteral
[61fc4f6]409%token<tok> DIRECTIVE
[1b29996]410// Floating point constant is broken into three kinds of tokens because of the ambiguity with tuple indexing and
411// overloading constants 0/1, e.g., x.1 is lexed as (x)(.1), where (.1) is a factional constant, but is semantically
412// converted into the tuple index (.)(1). e.g., 3.x
[930f69e]413%token<tok> FLOATING_DECIMALconstant FLOATING_FRACTIONconstant FLOATINGconstant
[51b73452]414
[c11e31c]415// multi-character operators
[b87a5ed]416%token ARROW // ->
417%token ICR DECR // ++ --
418%token LS RS // << >>
419%token LE GE EQ NE // <= >= == !=
420%token ANDAND OROR // && ||
[647e2ea]421%token ATTR ELLIPSIS // @@ ...
[b87a5ed]422
[e5f2a67]423%token EXPassign MULTassign DIVassign MODassign // \= *= /= %=
[b87a5ed]424%token PLUSassign MINUSassign // += -=
425%token LSassign RSassign // <<= >>=
426%token ANDassign ERassign ORassign // &= ^= |=
[51b73452]427
[d69f4bb4]428%token ErangeUpEq ErangeDown ErangeDownEq // ~= -~ -~=
[e7aed49]429%token ATassign // @=
[097e2b0]430
[e16eb460]431%type<tok> identifier identifier_at identifier_or_type_name attr_name
[5b2edbc]432%type<tok> quasi_keyword
[32d6fdc]433%type<expr> string_literal
[ab57786]434%type<str> string_literal_list
[51b73452]435
[71a422a]436%type<enum_hiding> hide_opt visible_hide_opt
[7cf8006]437
[c11e31c]438// expressions
[32d6fdc]439%type<expr> constant
[71a422a]440%type<expr> tuple tuple_expression_list
[32d6fdc]441%type<oper> ptrref_operator unary_operator assignment_operator simple_assignment_operator compound_assignment_operator
442%type<expr> primary_expression postfix_expression unary_expression
[71a422a]443%type<expr> cast_expression_list cast_expression exponential_expression multiplicative_expression additive_expression
444%type<expr> shift_expression relational_expression equality_expression
[32d6fdc]445%type<expr> AND_expression exclusive_OR_expression inclusive_OR_expression
446%type<expr> logical_AND_expression logical_OR_expression
447%type<expr> conditional_expression constant_expression assignment_expression assignment_expression_opt
[71a422a]448%type<expr> comma_expression comma_expression_opt
449%type<expr> argument_expression_list_opt argument_expression_list argument_expression default_initializer_opt
[473d1da0]450%type<ifctl> conditional_declaration
[71a422a]451%type<forctl> for_control_expression for_control_expression_list
[32d6fdc]452%type<oper> upupeq updown updowneq downupdowneq
453%type<expr> subrange
[c0aa336]454%type<decl> asm_name_opt
[71a422a]455%type<expr> asm_operands_opt asm_operands_list asm_operand
[32d6fdc]456%type<labels> label_list
457%type<expr> asm_clobbers_list_opt
458%type<is_volatile> asm_volatile_opt
459%type<expr> handler_predicate_opt
[67d4e37]460%type<genexpr> generic_association generic_assoc_list
[51b73452]461
[c11e31c]462// statements
[71a422a]463%type<stmt> statement labeled_statement compound_statement
[32d6fdc]464%type<stmt> statement_decl statement_decl_list statement_list_nodecl
[647e2ea]465%type<stmt> selection_statement
[71a422a]466%type<clause> switch_clause_list_opt switch_clause_list
[32d6fdc]467%type<expr> case_value
[71a422a]468%type<clause> case_clause case_value_list case_label case_label_list
[32d6fdc]469%type<stmt> iteration_statement jump_statement
[71a422a]470%type<stmt> expression_statement asm_statement
[32d6fdc]471%type<stmt> with_statement
472%type<expr> with_clause_opt
[11ab0b4a]473%type<stmt> corun_statement cofor_statement
[32d6fdc]474%type<stmt> exception_statement
[6611177]475%type<clause> handler_clause finally_clause
[32d6fdc]476%type<except_kind> handler_key
477%type<stmt> mutex_statement
478%type<expr> when_clause when_clause_opt waitfor waituntil timeout
[71a422a]479%type<stmt> waitfor_statement waituntil_statement
[c86b08d]480%type<wfs> wor_waitfor_clause
[6e1e2d0]481%type<wucn> waituntil_clause wand_waituntil_clause wor_waituntil_clause
[51b73452]482
[c11e31c]483// declarations
[c0aa336]484%type<decl> abstract_declarator abstract_ptr abstract_array abstract_function array_dimension multi_array_dimension
[59c7e3e]485%type<decl> abstract_parameter_declarator_opt abstract_parameter_declarator abstract_parameter_ptr abstract_parameter_array abstract_parameter_function array_parameter_dimension array_parameter_1st_dimension
[c0aa336]486%type<decl> abstract_parameter_declaration
[51b73452]487
[e307e12]488%type<aggKey> aggregate_key aggregate_data aggregate_control
[d0ffed1]489%type<decl> aggregate_type aggregate_type_nobody
[51b73452]490
[9997fee]491%type<decl> assertion assertion_list assertion_list_opt
[51b73452]492
[32d6fdc]493%type<expr> bit_subrange_size_opt bit_subrange_size
[51b73452]494
[84d58c5]495%type<decl> basic_declaration_specifier basic_type_name basic_type_specifier direct_type indirect_type
[6cef439]496%type<type> basic_type_name_type
497%type<type> vtable vtable_opt default_opt
[51b73452]498
[4040425]499%type<decl> trait_declaration trait_declaration_list trait_declaring_list trait_specifier
[51b73452]500
501%type<decl> declaration declaration_list declaration_list_opt declaration_qualifier_list
[d0ffed1]502%type<decl> declaration_specifier declaration_specifier_nobody declarator declaring_list
[51b73452]503
[d0ffed1]504%type<decl> elaborated_type elaborated_type_nobody
[51b73452]505
[a8ced63]506%type<decl> enumerator_list enum_type enum_type_nobody enum_key enumerator_type
[32d6fdc]507%type<init> enumerator_value_opt
[51b73452]508
[3d56d15b]509%type<decl> external_definition external_definition_list external_definition_list_opt
510
511%type<decl> exception_declaration
[51b73452]512
[12f1156]513%type<decl> field_declaration_list_opt field_declaration field_declaring_list_opt field_declarator field_abstract_list_opt field_abstract
[32d6fdc]514%type<expr> field field_name_list field_name fraction_constants_opt
[51b73452]515
[4d51835]516%type<decl> external_function_definition function_definition function_array function_declarator function_no_ptr function_ptr
[51b73452]517
[d3bc0ad]518%type<decl> identifier_parameter_declarator identifier_parameter_ptr identifier_parameter_array identifier_parameter_function
519%type<decl> identifier_list
[51b73452]520
[c0aa336]521%type<decl> cfa_abstract_array cfa_abstract_declarator_no_tuple cfa_abstract_declarator_tuple
522%type<decl> cfa_abstract_function cfa_abstract_parameter_declaration cfa_abstract_parameter_list
523%type<decl> cfa_abstract_ptr cfa_abstract_tuple
[51b73452]524
[c0aa336]525%type<decl> cfa_array_parameter_1st_dimension
[51b73452]526
[679e644]527%type<decl> cfa_trait_declaring_list cfa_declaration cfa_field_declaring_list cfa_field_abstract_list
[c0aa336]528%type<decl> cfa_function_declaration cfa_function_return cfa_function_specifier
[51b73452]529
[c0aa336]530%type<decl> cfa_identifier_parameter_array cfa_identifier_parameter_declarator_no_tuple
531%type<decl> cfa_identifier_parameter_declarator_tuple cfa_identifier_parameter_ptr
[51b73452]532
[647e2ea]533%type<decl> cfa_parameter_declaration cfa_parameter_list cfa_parameter_list_ellipsis_opt
[51b73452]534
[c0aa336]535%type<decl> cfa_typedef_declaration cfa_variable_declaration cfa_variable_specifier
[51b73452]536
[b9be000b]537%type<decl> c_declaration static_assert
[c0aa336]538%type<decl> KR_function_declarator KR_function_no_ptr KR_function_ptr KR_function_array
[35718a9]539%type<decl> KR_parameter_list KR_parameter_list_opt
[51b73452]540
[647e2ea]541%type<decl> parameter_declaration parameter_list parameter_list_ellipsis_opt
[51b73452]542
[2871210]543%type<decl> paren_identifier paren_type
[51b73452]544
[0da3e2c]545%type<decl> storage_class storage_class_list
[51b73452]546
[d0ffed1]547%type<decl> sue_declaration_specifier sue_declaration_specifier_nobody sue_type_specifier sue_type_specifier_nobody
[51b73452]548
[5a51798]549%type<tclass> type_class new_type_class
[51b73452]550%type<decl> type_declarator type_declarator_name type_declaring_list
551
[6cef439]552%type<decl> type_declaration_specifier type_type_specifier
553%type<type> type_name typegen_name
[f9c3100]554%type<decl> typedef_name typedef_declaration typedef_expression
[c0aa336]555
[1f771fc]556%type<decl> variable_type_redeclarator variable_type_ptr variable_type_array variable_type_function
557%type<decl> general_function_declarator function_type_redeclarator function_type_array function_type_no_ptr function_type_ptr
[c0aa336]558
559%type<decl> type_parameter_redeclarator type_parameter_ptr type_parameter_array type_parameter_function
[51b73452]560
[84d58c5]561%type<decl> type type_no_function
562%type<decl> type_parameter type_parameter_list type_initializer_opt
[51b73452]563
[647e2ea]564%type<expr> type_parameters_opt type_list array_type_list // array_dimension_list
[51b73452]565
[6cef439]566%type<decl> type_qualifier forall type_qualifier_list_opt type_qualifier_list
567%type<type> type_qualifier_name
[f9c3100]568%type<decl> type_specifier type_specifier_nobody
[51b73452]569
[c0aa336]570%type<decl> variable_declarator variable_ptr variable_array variable_function
571%type<decl> variable_abstract_declarator variable_abstract_ptr variable_abstract_array variable_abstract_function
[51b73452]572
[f9c3100]573%type<decl> attribute_list_opt attribute_list attribute attribute_name_list attribute_name
[1db21619]574
[c11e31c]575// initializers
[32d6fdc]576%type<init> initializer initializer_list_opt initializer_opt
[51b73452]577
[c11e31c]578// designators
[32d6fdc]579%type<expr> designator designator_list designation
[51b73452]580
581
[65d6de4]582// Handle shift/reduce conflict for dangling else by shifting the ELSE token. For example, this string is ambiguous:
583// .---------. matches IF '(' comma_expression ')' statement . (reduce)
584// if ( C ) S1 else S2
585// `-----------------' matches IF '(' comma_expression ')' statement . (shift) ELSE statement */
[5b2edbc]586// Similar issues exit with the waitfor statement.
[51b73452]587
[9fd9d015]588// Order of these lines matters (low-to-high precedence). THEN is left associative over WAND/WOR/TIMEOUT/ELSE, WAND/WOR
589// is left associative over TIMEOUT/ELSE, and TIMEOUT is left associative over ELSE.
[9fb1367]590%precedence THEN // rule precedence for IF/WAITFOR statement
[9fd9d015]591%precedence ANDAND // token precedence for start of WAND in WAITFOR statement
592%precedence WAND // token precedence for start of WAND in WAITFOR statement
593%precedence OROR // token precedence for start of WOR in WAITFOR statement
[9fb1367]594%precedence WOR // token precedence for start of WOR in WAITFOR statement
595%precedence TIMEOUT // token precedence for start of TIMEOUT in WAITFOR statement
596%precedence CATCH // token precedence for start of TIMEOUT in WAITFOR statement
597%precedence RECOVER // token precedence for start of TIMEOUT in WAITFOR statement
598%precedence CATCHRESUME // token precedence for start of TIMEOUT in WAITFOR statement
599%precedence FIXUP // token precedence for start of TIMEOUT in WAITFOR statement
600%precedence FINALLY // token precedence for start of TIMEOUT in WAITFOR statement
601%precedence ELSE // token precedence for start of else clause in IF/WAITFOR statement
602
[51b73452]603
[65d6de4]604// Handle shift/reduce conflict for generic type by shifting the '(' token. For example, this string is ambiguous:
605// forall( otype T ) struct Foo { T v; };
606// .-----. matches pointer to function returning a generic (which is impossible without a type)
607// Foo ( *fp )( int );
608// `---' matches start of TYPEGENname '('
[fc20514]609// must be:
[a16a7ec]610// Foo( int ) ( *fp )( int );
[fc20514]611// The same problem occurs here:
612// forall( otype T ) struct Foo { T v; } ( *fp )( int );
613// must be:
614// forall( otype T ) struct Foo { T v; } ( int ) ( *fp )( int );
[65d6de4]615
616// Order of these lines matters (low-to-high precedence).
617%precedence TYPEGENname
[284da8c]618%precedence '}'
[65d6de4]619%precedence '('
620
[c786e1d]621// %precedence RESUME
622// %precedence '{'
623// %precedence ')'
624
[f38e7d7]625%locations // support location tracking for error messages
[930f69e]626
[b87a5ed]627%start translation_unit // parse-tree root
[51b73452]628
629%%
[e1d66c84]630// ************************ Namespace Management ********************************
[c11e31c]631
[3d26610]632// The C grammar is not context free because it relies on the distinct terminal symbols "identifier" and "TYPEDEFname",
633// which are lexically identical.
[c11e31c]634//
[3d26610]635// typedef int foo; // identifier foo must now be scanned as TYPEDEFname
636// foo f; // to allow it to appear in this context
[c11e31c]637//
[3d26610]638// While it may be possible to write a purely context-free grammar, such a grammar would obscure the relationship
639// between syntactic and semantic constructs. Cforall compounds this problem by introducing type names local to the
640// scope of a declaration (for instance, those introduced through "forall" qualifiers), and by introducing "type
641// generators" -- parameterized types. This latter type name creates a third class of identifiers, "TYPEGENname", which
642// must be distinguished by the lexical scanner.
[c11e31c]643//
[3d26610]644// Since the scanner cannot distinguish among the different classes of identifiers without some context information,
645// there is a type table (typedefTable), which holds type names and identifiers that override type names, for each named
646// scope. During parsing, semantic actions update the type table by adding new identifiers in the current scope. For
647// each context that introduces a name scope, a new level is created in the type table and that level is popped on
648// exiting the scope. Since type names can be local to a particular declaration, each declaration is itself a scope.
649// This requires distinguishing between type names that are local to the current declaration scope and those that
650// persist past the end of the declaration (i.e., names defined in "typedef" or "otype" declarations).
[c11e31c]651//
[3d26610]652// The non-terminals "push" and "pop" denote the opening and closing of named scopes. Every push has a matching pop in
653// the production rule. There are multiple lists of declarations, where each declaration is a named scope, so pop/push
654// around the list separator.
655//
[71a422a]656// XXXXXXXXXXXXXXXXXXXXXXXXXXXXXX
[3d26610]657// push pop push pop
[51b73452]658
659push:
[ab57786]660 { typedefTable.enterScope(); }
[4d51835]661 ;
[51b73452]662
663pop:
[ab57786]664 { typedefTable.leaveScope(); }
[4d51835]665 ;
[51b73452]666
[e1d66c84]667// ************************ CONSTANTS ********************************
[51b73452]668
669constant:
[de62360d]670 // ENUMERATIONconstant is not included here; it is treated as a variable with type "enumeration constant".
[bb7422a]671 INTEGERconstant { $$ = new ExpressionNode( build_constantInteger( yylloc, *$1 ) ); }
672 | FLOATING_DECIMALconstant { $$ = new ExpressionNode( build_constantFloat( yylloc, *$1 ) ); }
673 | FLOATING_FRACTIONconstant { $$ = new ExpressionNode( build_constantFloat( yylloc, *$1 ) ); }
674 | FLOATINGconstant { $$ = new ExpressionNode( build_constantFloat( yylloc, *$1 ) ); }
675 | CHARACTERconstant { $$ = new ExpressionNode( build_constantChar( yylloc, *$1 ) ); }
[4d51835]676 ;
[51b73452]677
[5b2edbc]678quasi_keyword: // CFA
679 TIMEOUT
[9fd9d015]680 | WAND
[5b2edbc]681 | WOR
[9fb1367]682 | CATCH
683 | RECOVER
684 | CATCHRESUME
685 | FIXUP
686 | FINALLY
[5b2edbc]687 ;
688
[033ff37]689identifier:
[4d51835]690 IDENTIFIER
[5b2edbc]691 | quasi_keyword
[e16eb460]692 ;
693
694identifier_at:
695 identifier
[679e644]696 | '@' // CFA
697 { Token tok = { new string( DeclarationNode::anonymous.newName() ), yylval.tok.loc }; $$ = tok; }
[4d51835]698 ;
[51b73452]699
[12f1156]700identifier_or_type_name:
701 identifier
702 | TYPEDEFname
703 | TYPEGENname
704 ;
705
[ab57786]706string_literal:
[32d6fdc]707 string_literal_list { $$ = new ExpressionNode( build_constantStr( yylloc, *$1 ) ); }
[ab57786]708 ;
709
[b87a5ed]710string_literal_list: // juxtaposed strings are concatenated
[ab57786]711 STRINGliteral { $$ = $1; } // conversion from tok to str
[7bf7fb9]712 | string_literal_list STRINGliteral
713 {
[15697ff]714 if ( ! appendStr( *$1, *$2 ) ) YYERROR; // append 2nd juxtaposed string to 1st
[7bf7fb9]715 delete $2; // allocated by lexer
[ab57786]716 $$ = $1; // conversion from tok to str
[7bf7fb9]717 }
[4d51835]718 ;
[51b73452]719
[e1d66c84]720// ************************ EXPRESSIONS ********************************
[51b73452]721
722primary_expression:
[4d51835]723 IDENTIFIER // typedef name cannot be used as a variable name
[bb7422a]724 { $$ = new ExpressionNode( build_varref( yylloc, $1 ) ); }
[5b2edbc]725 | quasi_keyword
[bb7422a]726 { $$ = new ExpressionNode( build_varref( yylloc, $1 ) ); }
[6e50a6b]727 | TYPEDIMname // CFA, generic length argument
[bb7422a]728 { $$ = new ExpressionNode( build_dimensionref( yylloc, $1 ) ); }
[1b29996]729 | tuple
[4d51835]730 | '(' comma_expression ')'
731 { $$ = $2; }
732 | '(' compound_statement ')' // GCC, lambda expression
[bb7422a]733 { $$ = new ExpressionNode( new ast::StmtExpr( yylloc, dynamic_cast<ast::CompoundStmt *>( maybeMoveBuild( $2 ) ) ) ); }
[033ff37]734 | type_name '.' identifier // CFA, nested type
[6cef439]735 { $$ = new ExpressionNode( build_qualified_expr( yylloc, DeclarationNode::newFromTypeData( $1 ), build_varref( yylloc, $3 ) ) ); }
[679e644]736 | type_name '.' '[' field_name_list ']' // CFA, nested type / tuple field selector
[203c667]737 { SemanticError( yylloc, "Qualified name is currently unimplemented." ); $$ = nullptr; }
[24c3b67]738 | GENERIC '(' assignment_expression ',' generic_assoc_list ')' // C11
[d807ca28]739 {
740 // add the missing control expression to the GenericExpr and return it
[702e826]741 $5->control = maybeMoveBuild( $3 );
[d807ca28]742 $$ = new ExpressionNode( $5 );
743 }
[c786e1d]744 // | RESUME '(' comma_expression ')'
745 // { SemanticError( yylloc, "Resume expression is currently unimplemented." ); $$ = nullptr; }
746 // | RESUME '(' comma_expression ')' compound_statement
747 // { SemanticError( yylloc, "Resume expression is currently unimplemented." ); $$ = nullptr; }
[65ef0cd]748 | IDENTIFIER IDENTIFIER // invalid syntax rule
[b1f2007d]749 { IdentifierBeforeIdentifier( *$1.str, *$2.str, "expression" ); $$ = nullptr; }
[65ef0cd]750 | IDENTIFIER type_qualifier // invalid syntax rule
[996c8ed]751 { IdentifierBeforeType( *$1.str, "type qualifier" ); $$ = nullptr; }
[65ef0cd]752 | IDENTIFIER storage_class // invalid syntax rule
[996c8ed]753 { IdentifierBeforeType( *$1.str, "storage class" ); $$ = nullptr; }
[65ef0cd]754 | IDENTIFIER basic_type_name // invalid syntax rule
[996c8ed]755 { IdentifierBeforeType( *$1.str, "type" ); $$ = nullptr; }
[65ef0cd]756 | IDENTIFIER TYPEDEFname // invalid syntax rule
[996c8ed]757 { IdentifierBeforeType( *$1.str, "type" ); $$ = nullptr; }
[65ef0cd]758 | IDENTIFIER TYPEGENname // invalid syntax rule
[996c8ed]759 { IdentifierBeforeType( *$1.str, "type" ); $$ = nullptr; }
[24c3b67]760 ;
761
762generic_assoc_list: // C11
[d807ca28]763 generic_association
[24c3b67]764 | generic_assoc_list ',' generic_association
[d807ca28]765 {
766 // steal the association node from the singleton and delete the wrapper
[bb7422a]767 assert( 1 == $3->associations.size() );
768 $1->associations.push_back( $3->associations.front() );
[d807ca28]769 delete $3;
770 $$ = $1;
771 }
[24c3b67]772 ;
773
774generic_association: // C11
775 type_no_function ':' assignment_expression
[d807ca28]776 {
777 // create a GenericExpr wrapper with one association pair
[bb7422a]778 $$ = new ast::GenericExpr( yylloc, nullptr, { { maybeMoveBuildType( $1 ), maybeMoveBuild( $3 ) } } );
[d807ca28]779 }
[24c3b67]780 | DEFAULT ':' assignment_expression
[bb7422a]781 { $$ = new ast::GenericExpr( yylloc, nullptr, { { maybeMoveBuild( $3 ) } } ); }
[4d51835]782 ;
[51b73452]783
784postfix_expression:
[4d51835]785 primary_expression
[1d71208]786 | postfix_expression '[' assignment_expression ',' tuple_expression_list ']'
[59c7e3e]787 // Historic, transitional: Disallow commas in subscripts.
788 // Switching to this behaviour may help check if a C compatibilty case uses comma-exprs in subscripts.
789 // Current: Commas in subscripts make tuples.
[b93c544]790 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::Index, $1, new ExpressionNode( build_tuple( yylloc, $3->set_last( $5 ) ) ) ) ); }
[7fdb94e1]791 | postfix_expression '[' assignment_expression ']'
[c6b1105]792 // CFA, comma_expression disallowed in this context because it results in a common user error: subscripting a
[de62360d]793 // matrix with x[i,j] instead of x[i][j]. While this change is not backwards compatible, there seems to be
794 // little advantage to this feature and many disadvantages. It is possible to write x[(i,j)] in CFA, which is
795 // equivalent to the old x[i,j].
[bb7422a]796 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::Index, $1, $3 ) ); }
[d824715]797 | constant '[' assignment_expression ']' // 3[a], 'a'[a], 3.5[a]
[bb7422a]798 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::Index, $1, $3 ) ); }
[d824715]799 | string_literal '[' assignment_expression ']' // "abc"[3], 3["abc"]
[32d6fdc]800 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::Index, $1, $3 ) ); }
[cbbd8fd7]801 | postfix_expression '{' argument_expression_list_opt '}' // CFA, constructor call
[bd3d9e4]802 {
803 Token fn;
804 fn.str = new std::string( "?{}" ); // location undefined - use location of '{'?
[b93c544]805 $$ = new ExpressionNode( new ast::ConstructorExpr( yylloc, build_func( yylloc, new ExpressionNode( build_varref( yylloc, fn ) ), $1->set_last( $3 ) ) ) );
[bd3d9e4]806 }
[cbbd8fd7]807 | postfix_expression '(' argument_expression_list_opt ')'
[bb7422a]808 { $$ = new ExpressionNode( build_func( yylloc, $1, $3 ) ); }
[59c7e3e]809 | VA_ARG '(' primary_expression ',' declaration_specifier_nobody abstract_parameter_declarator_opt ')'
810 // { SemanticError( yylloc, "va_arg is currently unimplemented." ); $$ = nullptr; }
[b93c544]811 { $$ = new ExpressionNode( build_func( yylloc, new ExpressionNode( build_varref( yylloc, new string( "__builtin_va_arg" ) ) ),
812 $3->set_last( (ExpressionNode *)($6 ? $6->addType( $5 ) : $5) ) ) ); }
[948fdef]813 | postfix_expression '`' identifier // CFA, postfix call
[bb7422a]814 { $$ = new ExpressionNode( build_func( yylloc, new ExpressionNode( build_varref( yylloc, build_postfix_name( $3 ) ) ), $1 ) ); }
[948fdef]815 | constant '`' identifier // CFA, postfix call
[bb7422a]816 { $$ = new ExpressionNode( build_func( yylloc, new ExpressionNode( build_varref( yylloc, build_postfix_name( $3 ) ) ), $1 ) ); }
[948fdef]817 | string_literal '`' identifier // CFA, postfix call
[32d6fdc]818 { $$ = new ExpressionNode( build_func( yylloc, new ExpressionNode( build_varref( yylloc, build_postfix_name( $3 ) ) ), $1 ) ); }
[4eb3a7c5]819
820 // SKULLDUGGERY: The typedef table used for parsing does not store fields in structures. To parse a qualified
821 // name, it is assumed all name-tokens after the first are identifiers, regardless of how the lexer identifies
822 // them. For example:
823 //
824 // struct S;
825 // forall(T) struct T;
826 // union U;
827 // enum E { S, T, E };
828 // struct Z { int S, T, Z, E, U; };
829 // void fred () {
830 // Z z;
831 // z.S; // lexer returns S is TYPEDEFname
832 // z.T; // lexer returns T is TYPEGENname
833 // z.Z; // lexer returns Z is TYPEDEFname
834 // z.U; // lexer returns U is TYPEDEFname
835 // z.E; // lexer returns E is TYPEDEFname
836 // }
[12f1156]837 | postfix_expression '.' identifier_or_type_name
[4eb3a7c5]838 { $$ = new ExpressionNode( build_fieldSel( yylloc, $1, build_varref( yylloc, $3 ) ) ); }
839
[df22130]840 | postfix_expression '.' INTEGERconstant // CFA, tuple index
[bb7422a]841 { $$ = new ExpressionNode( build_fieldSel( yylloc, $1, build_constantInteger( yylloc, *$3 ) ) ); }
[930f69e]842 | postfix_expression FLOATING_FRACTIONconstant // CFA, tuple index
[bb7422a]843 { $$ = new ExpressionNode( build_fieldSel( yylloc, $1, build_field_name_FLOATING_FRACTIONconstant( yylloc, *$2 ) ) ); }
[679e644]844 | postfix_expression '.' '[' field_name_list ']' // CFA, tuple field selector
[bb7422a]845 { $$ = new ExpressionNode( build_fieldSel( yylloc, $1, build_tuple( yylloc, $4 ) ) ); }
[e307e12]846 | postfix_expression '.' aggregate_control
[bb7422a]847 { $$ = new ExpressionNode( build_keyword_cast( yylloc, $3, $1 ) ); }
[033ff37]848 | postfix_expression ARROW identifier
[bb7422a]849 { $$ = new ExpressionNode( build_pfieldSel( yylloc, $1, build_varref( yylloc, $3 ) ) ); }
[861799c7]850 | postfix_expression ARROW INTEGERconstant // CFA, tuple index
[bb7422a]851 { $$ = new ExpressionNode( build_pfieldSel( yylloc, $1, build_constantInteger( yylloc, *$3 ) ) ); }
[679e644]852 | postfix_expression ARROW '[' field_name_list ']' // CFA, tuple field selector
[bb7422a]853 { $$ = new ExpressionNode( build_pfieldSel( yylloc, $1, build_tuple( yylloc, $4 ) ) ); }
[4d51835]854 | postfix_expression ICR
[bb7422a]855 { $$ = new ExpressionNode( build_unary_val( yylloc, OperKinds::IncrPost, $1 ) ); }
[4d51835]856 | postfix_expression DECR
[bb7422a]857 { $$ = new ExpressionNode( build_unary_val( yylloc, OperKinds::DecrPost, $1 ) ); }
[7fdb94e1]858 | '(' type_no_function ')' '{' initializer_list_opt comma_opt '}' // C99, compound-literal
[bb7422a]859 { $$ = new ExpressionNode( build_compoundLiteral( yylloc, $2, new InitializerNode( $5, true ) ) ); }
[7fdb94e1]860 | '(' type_no_function ')' '@' '{' initializer_list_opt comma_opt '}' // CFA, explicit C compound-literal
[bb7422a]861 { $$ = new ExpressionNode( build_compoundLiteral( yylloc, $2, (new InitializerNode( $6, true ))->set_maybeConstructed( false ) ) ); }
[cbbd8fd7]862 | '^' primary_expression '{' argument_expression_list_opt '}' // CFA, destructor call
[097e2b0]863 {
[9706554]864 Token fn;
[ecb27a7]865 fn.str = new string( "^?{}" ); // location undefined
[b93c544]866 $$ = new ExpressionNode( build_func( yylloc, new ExpressionNode( build_varref( yylloc, fn ) ), $2->set_last( $4 ) ) );
[097e2b0]867 }
[4d51835]868 ;
[51b73452]869
[cbbd8fd7]870argument_expression_list_opt:
[757ffed]871 // empty
872 { $$ = nullptr; }
[e16eb460]873 | argument_expression_list
874 ;
875
876argument_expression_list:
877 argument_expression
[cbbd8fd7]878 | argument_expression_list_opt ',' argument_expression
[b93c544]879 { $$ = $1->set_last( $3 ); }
[4d51835]880 ;
[51b73452]881
882argument_expression:
[757ffed]883 '@' // CFA, default parameter
[679e644]884 { SemanticError( yylloc, "Default parameter for argument is currently unimplemented." ); $$ = nullptr; }
[9fd9d015]885 // { $$ = new ExpressionNode( build_constantInteger( *new string( "2" ) ) ); }
[4d51835]886 | assignment_expression
887 ;
[b87a5ed]888
[679e644]889field_name_list: // CFA, tuple field selector
[4d51835]890 field
[b93c544]891 | field_name_list ',' field { $$ = $1->set_last( $3 ); }
[4d51835]892 ;
[b87a5ed]893
894field: // CFA, tuple field selector
[faddbd8]895 field_name
[930f69e]896 | FLOATING_DECIMALconstant field
[bb7422a]897 { $$ = new ExpressionNode( build_fieldSel( yylloc, new ExpressionNode( build_field_name_FLOATING_DECIMALconstant( yylloc, *$1 ) ), maybeMoveBuild( $2 ) ) ); }
[679e644]898 | FLOATING_DECIMALconstant '[' field_name_list ']'
[bb7422a]899 { $$ = new ExpressionNode( build_fieldSel( yylloc, new ExpressionNode( build_field_name_FLOATING_DECIMALconstant( yylloc, *$1 ) ), build_tuple( yylloc, $3 ) ) ); }
[faddbd8]900 | field_name '.' field
[bb7422a]901 { $$ = new ExpressionNode( build_fieldSel( yylloc, $1, maybeMoveBuild( $3 ) ) ); }
[679e644]902 | field_name '.' '[' field_name_list ']'
[bb7422a]903 { $$ = new ExpressionNode( build_fieldSel( yylloc, $1, build_tuple( yylloc, $4 ) ) ); }
[faddbd8]904 | field_name ARROW field
[bb7422a]905 { $$ = new ExpressionNode( build_pfieldSel( yylloc, $1, maybeMoveBuild( $3 ) ) ); }
[679e644]906 | field_name ARROW '[' field_name_list ']'
[bb7422a]907 { $$ = new ExpressionNode( build_pfieldSel( yylloc, $1, build_tuple( yylloc, $4 ) ) ); }
[4d51835]908 ;
[51b73452]909
[faddbd8]910field_name:
[df22130]911 INTEGERconstant fraction_constants_opt
[bb7422a]912 { $$ = new ExpressionNode( build_field_name_fraction_constants( yylloc, build_constantInteger( yylloc, *$1 ), $2 ) ); }
[df22130]913 | FLOATINGconstant fraction_constants_opt
[bb7422a]914 { $$ = new ExpressionNode( build_field_name_fraction_constants( yylloc, build_field_name_FLOATINGconstant( yylloc, *$1 ), $2 ) ); }
[e16eb460]915 | identifier_at fraction_constants_opt // CFA, allow anonymous fields
[4cb935e]916 {
[bb7422a]917 $$ = new ExpressionNode( build_field_name_fraction_constants( yylloc, build_varref( yylloc, $1 ), $2 ) );
[84d58c5]918 }
[1b29996]919 ;
920
[df22130]921fraction_constants_opt:
[1b29996]922 // empty
[8780e30]923 { $$ = nullptr; }
[df22130]924 | fraction_constants_opt FLOATING_FRACTIONconstant
[8780e30]925 {
[bb7422a]926 ast::Expr * constant = build_field_name_FLOATING_FRACTIONconstant( yylloc, *$2 );
927 $$ = $1 != nullptr ? new ExpressionNode( build_fieldSel( yylloc, $1, constant ) ) : new ExpressionNode( constant );
[8780e30]928 }
[faddbd8]929 ;
930
[51b73452]931unary_expression:
[4d51835]932 postfix_expression
[c6b1105]933 // first location where constant/string can have operator applied: sizeof 3/sizeof "abc" still requires
934 // semantics checks, e.g., ++3, 3--, *3, &&3
[51b1202]935 | constant
[ab57786]936 | string_literal
[32d6fdc]937 { $$ = $1; }
[4d51835]938 | EXTENSION cast_expression // GCC
[e04ef3a]939 { $$ = $2->set_extension( true ); }
[c6b1105]940 // '*' ('&') is separated from unary_operator because of shift/reduce conflict in:
941 // { * X; } // dereference X
942 // { * int X; } // CFA declaration of pointer to int
[51e076e]943 | ptrref_operator cast_expression // CFA
[9706554]944 {
945 switch ( $1 ) {
[bb7422a]946 case OperKinds::AddressOf:
947 $$ = new ExpressionNode( new ast::AddressExpr( maybeMoveBuild( $2 ) ) );
[9706554]948 break;
[bb7422a]949 case OperKinds::PointTo:
950 $$ = new ExpressionNode( build_unary_val( yylloc, $1, $2 ) );
[9706554]951 break;
[bb7422a]952 case OperKinds::And:
953 $$ = new ExpressionNode( new ast::AddressExpr( new ast::AddressExpr( maybeMoveBuild( $2 ) ) ) );
[5809461]954 break;
[bb7422a]955 default:
[9706554]956 assert( false );
957 }
958 }
[4d51835]959 | unary_operator cast_expression
[bb7422a]960 { $$ = new ExpressionNode( build_unary_val( yylloc, $1, $2 ) ); }
[dd51906]961 | ICR unary_expression
[bb7422a]962 { $$ = new ExpressionNode( build_unary_val( yylloc, OperKinds::Incr, $2 ) ); }
[dd51906]963 | DECR unary_expression
[bb7422a]964 { $$ = new ExpressionNode( build_unary_val( yylloc, OperKinds::Decr, $2 ) ); }
[4d51835]965 | SIZEOF unary_expression
[bb7422a]966 { $$ = new ExpressionNode( new ast::SizeofExpr( yylloc, maybeMoveBuild( $2 ) ) ); }
[84d58c5]967 | SIZEOF '(' type_no_function ')'
[bb7422a]968 { $$ = new ExpressionNode( new ast::SizeofExpr( yylloc, maybeMoveBuildType( $3 ) ) ); }
[d1625f8]969 | ALIGNOF unary_expression // GCC, variable alignment
[bb7422a]970 { $$ = new ExpressionNode( new ast::AlignofExpr( yylloc, maybeMoveBuild( $2 ) ) ); }
[a2e0687]971 | ALIGNOF '(' type_no_function ')' // GCC, type alignment
[bb7422a]972 { $$ = new ExpressionNode( new ast::AlignofExpr( yylloc, maybeMoveBuildType( $3 ) ) ); }
[7e13b11]973
974 // Cannot use rule "type", which includes cfa_abstract_function, for sizeof/alignof, because of S/R problems on
975 // look ahead, so the cfa_abstract_function is factored out.
976 | SIZEOF '(' cfa_abstract_function ')'
977 { $$ = new ExpressionNode( new ast::SizeofExpr( yylloc, maybeMoveBuildType( $3 ) ) ); }
978 | ALIGNOF '(' cfa_abstract_function ')' // GCC, type alignment
979 { $$ = new ExpressionNode( new ast::AlignofExpr( yylloc, maybeMoveBuildType( $3 ) ) ); }
980
[033ff37]981 | OFFSETOF '(' type_no_function ',' identifier ')'
[bb7422a]982 { $$ = new ExpressionNode( build_offsetOf( yylloc, $3, build_varref( yylloc, $5 ) ) ); }
[7e13b11]983 | TYPEID '(' type ')'
[1f652a7]984 {
985 SemanticError( yylloc, "typeid name is currently unimplemented." ); $$ = nullptr;
986 // $$ = new ExpressionNode( build_offsetOf( $3, build_varref( $5 ) ) );
987 }
[a8ced63]988 | COUNTOF '(' type_no_function ')'
989 { $$ = new ExpressionNode( new ast::CountExpr( yylloc, maybeMoveBuildType( $3 ) ) ); }
990 | COUNTOF unary_expression
991 { SemanticError( yylloc, "countof for expressions is currently unimplemented. "); $$ = nullptr; }
[4d51835]992 ;
[51b73452]993
[dd51906]994ptrref_operator:
[d9e2280]995 '*' { $$ = OperKinds::PointTo; }
996 | '&' { $$ = OperKinds::AddressOf; }
[c6b1105]997 // GCC, address of label must be handled by semantic check for ref,ref,label
[9f07232]998 | ANDAND { $$ = OperKinds::And; }
[dd51906]999 ;
1000
[51b73452]1001unary_operator:
[d9e2280]1002 '+' { $$ = OperKinds::UnPlus; }
1003 | '-' { $$ = OperKinds::UnMinus; }
1004 | '!' { $$ = OperKinds::Neg; }
1005 | '~' { $$ = OperKinds::BitNeg; }
[4d51835]1006 ;
[51b73452]1007
1008cast_expression:
[4d51835]1009 unary_expression
[84d58c5]1010 | '(' type_no_function ')' cast_expression
[bb7422a]1011 { $$ = new ExpressionNode( build_cast( yylloc, $2, $4 ) ); }
[e307e12]1012 | '(' aggregate_control '&' ')' cast_expression // CFA
[bb7422a]1013 { $$ = new ExpressionNode( build_keyword_cast( yylloc, $2, $5 ) ); }
[24711a3]1014 | '(' aggregate_control '*' ')' cast_expression // CFA
[bb7422a]1015 { $$ = new ExpressionNode( build_keyword_cast( yylloc, $2, $5 ) ); }
[fae90d5f]1016 | '(' VIRTUAL ')' cast_expression // CFA
[6cef439]1017 { $$ = new ExpressionNode( new ast::VirtualCastExpr( yylloc, maybeMoveBuild( $4 ), nullptr ) ); }
[fae90d5f]1018 | '(' VIRTUAL type_no_function ')' cast_expression // CFA
[bb7422a]1019 { $$ = new ExpressionNode( new ast::VirtualCastExpr( yylloc, maybeMoveBuild( $5 ), maybeMoveBuildType( $3 ) ) ); }
[1528a2c]1020 | '(' RETURN type_no_function ')' cast_expression // CFA
[24d6572]1021 { $$ = new ExpressionNode( build_cast( yylloc, $3, $5, ast::CastExpr::Return ) ); }
[1528a2c]1022 | '(' COERCE type_no_function ')' cast_expression // CFA
1023 { SemanticError( yylloc, "Coerce cast is currently unimplemented." ); $$ = nullptr; }
1024 | '(' qualifier_cast_list ')' cast_expression // CFA
1025 { SemanticError( yylloc, "Qualifier cast is currently unimplemented." ); $$ = nullptr; }
[84d58c5]1026// | '(' type_no_function ')' tuple
[bb7422a]1027// { $$ = new ast::ExpressionNode( build_cast( yylloc, $2, $4 ) ); }
[4d51835]1028 ;
[51b73452]1029
[1528a2c]1030qualifier_cast_list:
1031 cast_modifier type_qualifier_name
1032 | cast_modifier MUTEX
1033 | qualifier_cast_list cast_modifier type_qualifier_name
1034 | qualifier_cast_list cast_modifier MUTEX
1035 ;
1036
1037cast_modifier:
1038 '-'
1039 | '+'
1040 ;
1041
[994d080]1042exponential_expression:
[4d51835]1043 cast_expression
[994d080]1044 | exponential_expression '\\' cast_expression
[bb7422a]1045 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::Exp, $1, $3 ) ); }
[994d080]1046 ;
1047
1048multiplicative_expression:
1049 exponential_expression
1050 | multiplicative_expression '*' exponential_expression
[bb7422a]1051 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::Mul, $1, $3 ) ); }
[994d080]1052 | multiplicative_expression '/' exponential_expression
[bb7422a]1053 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::Div, $1, $3 ) ); }
[994d080]1054 | multiplicative_expression '%' exponential_expression
[bb7422a]1055 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::Mod, $1, $3 ) ); }
[4d51835]1056 ;
[51b73452]1057
1058additive_expression:
[4d51835]1059 multiplicative_expression
1060 | additive_expression '+' multiplicative_expression
[bb7422a]1061 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::Plus, $1, $3 ) ); }
[4d51835]1062 | additive_expression '-' multiplicative_expression
[bb7422a]1063 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::Minus, $1, $3 ) ); }
[4d51835]1064 ;
[51b73452]1065
1066shift_expression:
[4d51835]1067 additive_expression
1068 | shift_expression LS additive_expression
[bb7422a]1069 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::LShift, $1, $3 ) ); }
[4d51835]1070 | shift_expression RS additive_expression
[bb7422a]1071 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::RShift, $1, $3 ) ); }
[4d51835]1072 ;
[51b73452]1073
1074relational_expression:
[4d51835]1075 shift_expression
1076 | relational_expression '<' shift_expression
[bb7422a]1077 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::LThan, $1, $3 ) ); }
[4d51835]1078 | relational_expression '>' shift_expression
[bb7422a]1079 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::GThan, $1, $3 ) ); }
[4d51835]1080 | relational_expression LE shift_expression
[bb7422a]1081 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::LEThan, $1, $3 ) ); }
[4d51835]1082 | relational_expression GE shift_expression
[bb7422a]1083 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::GEThan, $1, $3 ) ); }
[4d51835]1084 ;
[51b73452]1085
1086equality_expression:
[4d51835]1087 relational_expression
1088 | equality_expression EQ relational_expression
[bb7422a]1089 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::Eq, $1, $3 ) ); }
[4d51835]1090 | equality_expression NE relational_expression
[bb7422a]1091 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::Neq, $1, $3 ) ); }
[4d51835]1092 ;
[51b73452]1093
1094AND_expression:
[4d51835]1095 equality_expression
1096 | AND_expression '&' equality_expression
[bb7422a]1097 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::BitAnd, $1, $3 ) ); }
[4d51835]1098 ;
[51b73452]1099
1100exclusive_OR_expression:
[4d51835]1101 AND_expression
1102 | exclusive_OR_expression '^' AND_expression
[bb7422a]1103 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::Xor, $1, $3 ) ); }
[4d51835]1104 ;
[51b73452]1105
1106inclusive_OR_expression:
[4d51835]1107 exclusive_OR_expression
1108 | inclusive_OR_expression '|' exclusive_OR_expression
[bb7422a]1109 { $$ = new ExpressionNode( build_binary_val( yylloc, OperKinds::BitOr, $1, $3 ) ); }
[4d51835]1110 ;
[51b73452]1111
1112logical_AND_expression:
[4d51835]1113 inclusive_OR_expression
1114 | logical_AND_expression ANDAND inclusive_OR_expression
[bb7422a]1115 { $$ = new ExpressionNode( build_and_or( yylloc, $1, $3, ast::AndExpr ) ); }
[4d51835]1116 ;
[51b73452]1117
1118logical_OR_expression:
[4d51835]1119 logical_AND_expression
1120 | logical_OR_expression OROR logical_AND_expression
[bb7422a]1121 { $$ = new ExpressionNode( build_and_or( yylloc, $1, $3, ast::OrExpr ) ); }
[4d51835]1122 ;
[51b73452]1123
1124conditional_expression:
[4d51835]1125 logical_OR_expression
1126 | logical_OR_expression '?' comma_expression ':' conditional_expression
[bb7422a]1127 { $$ = new ExpressionNode( build_cond( yylloc, $1, $3, $5 ) ); }
[4d51835]1128 | logical_OR_expression '?' /* empty */ ':' conditional_expression // GCC, omitted first operand
[2810700]1129 { $$ = new ExpressionNode( build_cond( yylloc, $1, nullptr, $4 ) ); }
[4d51835]1130 ;
[51b73452]1131
1132constant_expression:
[4d51835]1133 conditional_expression
1134 ;
[51b73452]1135
1136assignment_expression:
[4d51835]1137 // CFA, assignment is separated from assignment_operator to ensure no assignment operations for tuples
1138 conditional_expression
1139 | unary_expression assignment_operator assignment_expression
[9867cdb]1140 {
[25744d2]1141// if ( $2 == OperKinds::AtAssn ) {
1142// SemanticError( yylloc, "C @= assignment is currently unimplemented." ); $$ = nullptr;
1143// } else {
[bb7422a]1144 $$ = new ExpressionNode( build_binary_val( yylloc, $2, $1, $3 ) );
[25744d2]1145// } // if
[9867cdb]1146 }
[7fdb94e1]1147 | unary_expression '=' '{' initializer_list_opt comma_opt '}'
[fae90d5f]1148 { SemanticError( yylloc, "Initializer assignment is currently unimplemented." ); $$ = nullptr; }
[4d51835]1149 ;
[51b73452]1150
1151assignment_expression_opt:
[4d51835]1152 // empty
[d1625f8]1153 { $$ = nullptr; }
[4d51835]1154 | assignment_expression
1155 ;
[b87a5ed]1156
[9706554]1157assignment_operator:
[f9c3100]1158 simple_assignment_operator
1159 | compound_assignment_operator
1160 ;
1161
1162simple_assignment_operator:
[d9e2280]1163 '=' { $$ = OperKinds::Assign; }
[f9c3100]1164 | ATassign { $$ = OperKinds::AtAssn; } // CFA
1165 ;
1166
1167compound_assignment_operator:
1168 EXPassign { $$ = OperKinds::ExpAssn; }
[d9e2280]1169 | MULTassign { $$ = OperKinds::MulAssn; }
1170 | DIVassign { $$ = OperKinds::DivAssn; }
1171 | MODassign { $$ = OperKinds::ModAssn; }
1172 | PLUSassign { $$ = OperKinds::PlusAssn; }
1173 | MINUSassign { $$ = OperKinds::MinusAssn; }
1174 | LSassign { $$ = OperKinds::LSAssn; }
1175 | RSassign { $$ = OperKinds::RSAssn; }
1176 | ANDassign { $$ = OperKinds::AndAssn; }
1177 | ERassign { $$ = OperKinds::ERAssn; }
1178 | ORassign { $$ = OperKinds::OrAssn; }
[413ad05]1179 ;
[9706554]1180
[b87a5ed]1181tuple: // CFA, tuple
[de62360d]1182 // CFA, one assignment_expression is factored out of comma_expression to eliminate a shift/reduce conflict with
[c0aa336]1183 // comma_expression in cfa_identifier_parameter_array and cfa_abstract_array
[1b29996]1184// '[' ']'
1185// { $$ = new ExpressionNode( build_tuple() ); }
[13e8427]1186// | '[' push assignment_expression pop ']'
[1b29996]1187// { $$ = new ExpressionNode( build_tuple( $3 ) ); }
[17238fd]1188 '[' ',' tuple_expression_list ']'
[b93c544]1189 { $$ = new ExpressionNode( build_tuple( yylloc, (new ExpressionNode( nullptr ))->set_last( $3 ) ) ); }
[17238fd]1190 | '[' push assignment_expression pop ',' tuple_expression_list ']'
[b93c544]1191 { $$ = new ExpressionNode( build_tuple( yylloc, $3->set_last( $6 ) ) ); }
[4d51835]1192 ;
[51b73452]1193
1194tuple_expression_list:
[0a6d8204]1195 assignment_expression
1196 | '@' // CFA
1197 { SemanticError( yylloc, "Eliding tuple element with '@' is currently unimplemented." ); $$ = nullptr; }
1198 | tuple_expression_list ',' assignment_expression
[b93c544]1199 { $$ = $1->set_last( $3 ); }
[0a6d8204]1200 | tuple_expression_list ',' '@'
1201 { SemanticError( yylloc, "Eliding tuple element with '@' is currently unimplemented." ); $$ = nullptr; }
[4d51835]1202 ;
[51b73452]1203
1204comma_expression:
[4d51835]1205 assignment_expression
[9706554]1206 | comma_expression ',' assignment_expression
[bb7422a]1207 { $$ = new ExpressionNode( new ast::CommaExpr( yylloc, maybeMoveBuild( $1 ), maybeMoveBuild( $3 ) ) ); }
[4d51835]1208 ;
[51b73452]1209
1210comma_expression_opt:
[4d51835]1211 // empty
[58dd019]1212 { $$ = nullptr; }
[4d51835]1213 | comma_expression
1214 ;
[51b73452]1215
[e1d66c84]1216// ************************** STATEMENTS *******************************
[51b73452]1217
1218statement:
[4d51835]1219 labeled_statement
1220 | compound_statement
[c0a33d2]1221 | expression_statement
[4d51835]1222 | selection_statement
1223 | iteration_statement
1224 | jump_statement
[8b47e50]1225 | with_statement
[b6b3c42]1226 | mutex_statement
[5b2edbc]1227 | waitfor_statement
[9fd9d015]1228 | waituntil_statement
[11ab0b4a]1229 | corun_statement
1230 | cofor_statement
[4d51835]1231 | exception_statement
[2a8427c6]1232 | enable_disable_statement
[fae90d5f]1233 { SemanticError( yylloc, "enable/disable statement is currently unimplemented." ); $$ = nullptr; }
[4d51835]1234 | asm_statement
[61fc4f6]1235 | DIRECTIVE
[bb7422a]1236 { $$ = new StatementNode( build_directive( yylloc, $1 ) ); }
[b9be000b]1237 ;
[51b73452]1238
1239labeled_statement:
[033ff37]1240 // labels cannot be identifiers 0 or 1
[44a81853]1241 identifier_or_type_name ':' attribute_list_opt statement
[bb7422a]1242 { $$ = $4->add_label( yylloc, $1, $3 ); }
[0442f93f]1243 | identifier_or_type_name ':' attribute_list_opt error // invalid syntax rule
[afe9e45]1244 {
[b1f2007d]1245 SemanticError( yylloc, "syntx error, label \"%s\" must be associated with a statement, "
1246 "where a declaration, case, or default is not a statement.\n"
1247 "Move the label or terminate with a semicolon.", $1.str->c_str() );
[afe9e45]1248 $$ = nullptr;
1249 }
[4d51835]1250 ;
[51b73452]1251
1252compound_statement:
[4d51835]1253 '{' '}'
[bb7422a]1254 { $$ = new StatementNode( build_compound( yylloc, (StatementNode *)0 ) ); }
[35718a9]1255 | '{' push
[5e25953]1256 local_label_declaration_opt // GCC, local labels appear at start of block
[9bd6105]1257 statement_decl_list // C99, intermix declarations and statements
[c0aa336]1258 pop '}'
[bb7422a]1259 { $$ = new StatementNode( build_compound( yylloc, $4 ) ); }
[4d51835]1260 ;
[b87a5ed]1261
[9bd6105]1262statement_decl_list: // C99
1263 statement_decl
[35718a9]1264 | statement_decl_list statement_decl
[6d01d89]1265 { assert( $1 ); $1->set_last( $2 ); $$ = $1; }
[4d51835]1266 ;
[51b73452]1267
[9bd6105]1268statement_decl:
[4d51835]1269 declaration // CFA, new & old style declarations
[e82aa9df]1270 { $$ = new StatementNode( $1 ); }
[4d51835]1271 | EXTENSION declaration // GCC
[6d01d89]1272 { distExt( $2 ); $$ = new StatementNode( $2 ); }
[4d51835]1273 | function_definition
[e82aa9df]1274 { $$ = new StatementNode( $1 ); }
[c0aa336]1275 | EXTENSION function_definition // GCC
[6d01d89]1276 { distExt( $2 ); $$ = new StatementNode( $2 ); }
[35718a9]1277 | statement
[4d51835]1278 ;
[51b73452]1279
[9bd6105]1280statement_list_nodecl:
[4d51835]1281 statement
[9bd6105]1282 | statement_list_nodecl statement
[6d01d89]1283 { assert( $1 ); $1->set_last( $2 ); $$ = $1; }
[0442f93f]1284 | statement_list_nodecl error // invalid syntax rule
[253d0b4]1285 { SemanticError( yylloc, "illegal syntax, declarations only allowed at the start of the switch body,"
[7e13b11]1286 " i.e., after the '{'." ); $$ = nullptr; }
[4d51835]1287 ;
[51b73452]1288
1289expression_statement:
[4d51835]1290 comma_expression_opt ';'
[bb7422a]1291 { $$ = new StatementNode( build_expr( yylloc, $1 ) ); }
[4d51835]1292 ;
[51b73452]1293
[7e13b11]1294// "if", "switch", and "choose" require parenthesis around the conditional. See the following ambiguities without
1295// parenthesis:
1296//
[446740a]1297// if x + y + z; => if ( x ) + y + z or if ( x + y ) + z
[647e2ea]1298//
[7e13b11]1299// switch O { }
1300//
1301// O{} => object-constructor for conditional, switch body ???
1302// O{} => O for conditional followed by switch body
1303//
1304// C++ has this problem, as it has the same constructor syntax.
1305//
1306// switch sizeof ( T ) { }
1307//
1308// sizeof ( T ) => sizeof of T for conditional followed by switch body
1309// sizeof ( T ) => sizeof of compound literal (T){ }, closing parenthesis ???
1310//
1311// Note the two grammar rules for sizeof (alignof)
1312//
1313// | SIZEOF unary_expression
1314// | SIZEOF '(' type_no_function ')'
1315//
1316// where the first DOES NOT require parenthesis! And C++ inherits this problem from C.
[647e2ea]1317
[51b73452]1318selection_statement:
[647e2ea]1319 IF '(' conditional_declaration ')' statement %prec THEN
1320 // explicitly deal with the shift/reduce conflict on if/else
1321 { $$ = new StatementNode( build_if( yylloc, $3, maybe_build_compound( yylloc, $5 ), nullptr ) ); }
1322 | IF '(' conditional_declaration ')' statement ELSE statement
1323 { $$ = new StatementNode( build_if( yylloc, $3, maybe_build_compound( yylloc, $5 ), maybe_build_compound( yylloc, $7 ) ) ); }
[4cc585b]1324 | SWITCH '(' comma_expression ')' case_clause
[bb7422a]1325 { $$ = new StatementNode( build_switch( yylloc, true, $3, $5 ) ); }
[35718a9]1326 | SWITCH '(' comma_expression ')' '{' push declaration_list_opt switch_clause_list_opt pop '}' // CFA
[4e06c1e]1327 {
[bb7422a]1328 StatementNode *sw = new StatementNode( build_switch( yylloc, true, $3, $8 ) );
[4e06c1e]1329 // The semantics of the declaration list is changed to include associated initialization, which is performed
1330 // *before* the transfer to the appropriate case clause by hoisting the declarations into a compound
1331 // statement around the switch. Statements after the initial declaration list can never be executed, and
[8688ce1]1332 // therefore, are removed from the grammar even though C allows it. The change also applies to choose
1333 // statement.
[b93c544]1334 $$ = $7 ? new StatementNode( build_compound( yylloc, (new StatementNode( $7 ))->set_last( sw ) ) ) : sw;
[4e06c1e]1335 }
[0442f93f]1336 | SWITCH '(' comma_expression ')' '{' error '}' // CFA, invalid syntax rule error
[55266c7]1337 { SemanticError( yylloc, "synatx error, declarations can only appear before the list of case clauses." ); $$ = nullptr; }
[4d51835]1338 | CHOOSE '(' comma_expression ')' case_clause // CFA
[bb7422a]1339 { $$ = new StatementNode( build_switch( yylloc, false, $3, $5 ) ); }
[35718a9]1340 | CHOOSE '(' comma_expression ')' '{' push declaration_list_opt switch_clause_list_opt pop '}' // CFA
[4e06c1e]1341 {
[bb7422a]1342 StatementNode *sw = new StatementNode( build_switch( yylloc, false, $3, $8 ) );
[b93c544]1343 $$ = $7 ? new StatementNode( build_compound( yylloc, (new StatementNode( $7 ))->set_last( sw ) ) ) : sw;
[4e06c1e]1344 }
[0442f93f]1345 | CHOOSE '(' comma_expression ')' '{' error '}' // CFA, invalid syntax rule
[253d0b4]1346 { SemanticError( yylloc, "illegal syntax, declarations can only appear before the list of case clauses." ); $$ = nullptr; }
[4d51835]1347 ;
[b87a5ed]1348
[473d1da0]1349conditional_declaration:
[35718a9]1350 comma_expression
[473d1da0]1351 { $$ = new CondCtl( nullptr, $1 ); }
[35718a9]1352 | c_declaration // no semi-colon
[473d1da0]1353 { $$ = new CondCtl( $1, nullptr ); }
[35718a9]1354 | cfa_declaration // no semi-colon
[473d1da0]1355 { $$ = new CondCtl( $1, nullptr ); }
[6d49ea3]1356 | declaration comma_expression // semi-colon separated
[473d1da0]1357 { $$ = new CondCtl( $1, $2 ); }
[9fd9d015]1358 ;
[936e9f4]1359
[de62360d]1360// CASE and DEFAULT clauses are only allowed in the SWITCH statement, precluding Duff's device. In addition, a case
1361// clause allows a list of values and subranges.
[b87a5ed]1362
1363case_value: // CFA
[4d51835]1364 constant_expression { $$ = $1; }
1365 | constant_expression ELLIPSIS constant_expression // GCC, subrange
[bb7422a]1366 { $$ = new ExpressionNode( new ast::RangeExpr( yylloc, maybeMoveBuild( $1 ), maybeMoveBuild( $3 ) ) ); }
[4d51835]1367 | subrange // CFA, subrange
1368 ;
[b87a5ed]1369
1370case_value_list: // CFA
[6611177]1371 case_value { $$ = new ClauseNode( build_case( yylloc, $1 ) ); }
[064e3ff]1372 // convert case list, e.g., "case 1, 3, 5:" into "case 1: case 3: case 5"
[6611177]1373 | case_value_list ',' case_value { $$ = $1->set_last( new ClauseNode( build_case( yylloc, $3 ) ) ); }
[4d51835]1374 ;
[b87a5ed]1375
1376case_label: // CFA
[0442f93f]1377 CASE error // invalid syntax rule
[253d0b4]1378 { SemanticError( yylloc, "illegal syntax, case list missing after case." ); $$ = nullptr; }
[5c216b4]1379 | CASE case_value_list ':' { $$ = $2; }
[0442f93f]1380 | CASE case_value_list error // invalid syntax rule
[253d0b4]1381 { SemanticError( yylloc, "illegal syntax, colon missing after case list." ); $$ = nullptr; }
[6611177]1382 | DEFAULT ':' { $$ = new ClauseNode( build_default( yylloc ) ); }
[4d51835]1383 // A semantic check is required to ensure only one default clause per switch/choose statement.
[65ef0cd]1384 | DEFAULT error // invalid syntax rule
[253d0b4]1385 { SemanticError( yylloc, "illegal syntax, colon missing after default." ); $$ = nullptr; }
[4d51835]1386 ;
[b87a5ed]1387
1388case_label_list: // CFA
[4d51835]1389 case_label
[6611177]1390 | case_label_list case_label { $$ = $1->set_last( $2 ); }
[4d51835]1391 ;
[b87a5ed]1392
1393case_clause: // CFA
[bb7422a]1394 case_label_list statement { $$ = $1->append_last_case( maybe_build_compound( yylloc, $2 ) ); }
[4d51835]1395 ;
[b87a5ed]1396
1397switch_clause_list_opt: // CFA
[4d51835]1398 // empty
[58dd019]1399 { $$ = nullptr; }
[4d51835]1400 | switch_clause_list
1401 ;
[b87a5ed]1402
1403switch_clause_list: // CFA
[9bd6105]1404 case_label_list statement_list_nodecl
[bb7422a]1405 { $$ = $1->append_last_case( new StatementNode( build_compound( yylloc, $2 ) ) ); }
[9bd6105]1406 | switch_clause_list case_label_list statement_list_nodecl
[6611177]1407 { $$ = $1->set_last( $2->append_last_case( new StatementNode( build_compound( yylloc, $3 ) ) ) ); }
[4d51835]1408 ;
[b87a5ed]1409
[51b73452]1410iteration_statement:
[5695645]1411 WHILE '(' ')' statement %prec THEN // CFA => while ( 1 )
[bb7422a]1412 { $$ = new StatementNode( build_while( yylloc, new CondCtl( nullptr, NEW_ONE ), maybe_build_compound( yylloc, $4 ) ) ); }
[5695645]1413 | WHILE '(' ')' statement ELSE statement // CFA
[86b8d16]1414 {
[bb7422a]1415 $$ = new StatementNode( build_while( yylloc, new CondCtl( nullptr, NEW_ONE ), maybe_build_compound( yylloc, $4 ) ) );
[3d937e2]1416 SemanticWarning( yylloc, Warning::SuperfluousElse );
[86b8d16]1417 }
[473d1da0]1418 | WHILE '(' conditional_declaration ')' statement %prec THEN
[bb7422a]1419 { $$ = new StatementNode( build_while( yylloc, $3, maybe_build_compound( yylloc, $5 ) ) ); }
[473d1da0]1420 | WHILE '(' conditional_declaration ')' statement ELSE statement // CFA
[bb7422a]1421 { $$ = new StatementNode( build_while( yylloc, $3, maybe_build_compound( yylloc, $5 ), $7 ) ); }
[f271bdd]1422 | DO statement WHILE '(' ')' ';' // CFA => do while( 1 )
[bb7422a]1423 { $$ = new StatementNode( build_do_while( yylloc, NEW_ONE, maybe_build_compound( yylloc, $2 ) ) ); }
[5695645]1424 | DO statement WHILE '(' ')' ELSE statement // CFA
[86b8d16]1425 {
[bb7422a]1426 $$ = new StatementNode( build_do_while( yylloc, NEW_ONE, maybe_build_compound( yylloc, $2 ) ) );
[3d937e2]1427 SemanticWarning( yylloc, Warning::SuperfluousElse );
[86b8d16]1428 }
1429 | DO statement WHILE '(' comma_expression ')' ';'
[bb7422a]1430 { $$ = new StatementNode( build_do_while( yylloc, $5, maybe_build_compound( yylloc, $2 ) ) ); }
[efc8f3e]1431 | DO statement WHILE '(' comma_expression ')' ELSE statement // CFA
[bb7422a]1432 { $$ = new StatementNode( build_do_while( yylloc, $5, maybe_build_compound( yylloc, $2 ), $8 ) ); }
[86b8d16]1433 | FOR '(' ')' statement %prec THEN // CFA => for ( ;; )
[bb7422a]1434 { $$ = new StatementNode( build_for( yylloc, new ForCtrl( nullptr, nullptr, nullptr ), maybe_build_compound( yylloc, $4 ) ) ); }
[86b8d16]1435 | FOR '(' ')' statement ELSE statement // CFA
1436 {
[bb7422a]1437 $$ = new StatementNode( build_for( yylloc, new ForCtrl( nullptr, nullptr, nullptr ), maybe_build_compound( yylloc, $4 ) ) );
[3d937e2]1438 SemanticWarning( yylloc, Warning::SuperfluousElse );
[86b8d16]1439 }
[efc8f3e]1440 | FOR '(' for_control_expression_list ')' statement %prec THEN
[bb7422a]1441 { $$ = new StatementNode( build_for( yylloc, $3, maybe_build_compound( yylloc, $5 ) ) ); }
[efc8f3e]1442 | FOR '(' for_control_expression_list ')' statement ELSE statement // CFA
[bb7422a]1443 { $$ = new StatementNode( build_for( yylloc, $3, maybe_build_compound( yylloc, $5 ), $7 ) ); }
[a73c16e]1444 ;
1445
[6d01d89]1446for_control_expression_list:
1447 for_control_expression
1448 | for_control_expression_list ':' for_control_expression
[67d4e37]1449 // ForCtrl + ForCtrl:
1450 // init + init => multiple declaration statements that are hoisted
1451 // condition + condition => (expression) && (expression)
1452 // change + change => (expression), (expression)
1453 {
1454 $1->init->set_last( $3->init );
1455 if ( $1->condition ) {
1456 if ( $3->condition ) {
[bb7422a]1457 $1->condition->expr.reset( new ast::LogicalExpr( yylloc, $1->condition->expr.release(), $3->condition->expr.release(), ast::AndExpr ) );
[67d4e37]1458 } // if
1459 } else $1->condition = $3->condition;
1460 if ( $1->change ) {
1461 if ( $3->change ) {
[bb7422a]1462 $1->change->expr.reset( new ast::CommaExpr( yylloc, $1->change->expr.release(), $3->change->expr.release() ) );
[67d4e37]1463 } // if
1464 } else $1->change = $3->change;
1465 $$ = $1;
1466 }
[6d01d89]1467 ;
1468
[51b73452]1469for_control_expression:
[6d01d89]1470 ';' comma_expression_opt ';' comma_expression_opt
[1cdc052]1471 { $$ = new ForCtrl( nullptr, $2, $4 ); }
[6d01d89]1472 | comma_expression ';' comma_expression_opt ';' comma_expression_opt
[1cdc052]1473 {
[253d0b4]1474 $$ = new ForCtrl( $1 ? new StatementNode( new ast::ExprStmt( yylloc, maybeMoveBuild( $1 ) ) ) : nullptr, $3, $5 );
[1cdc052]1475 }
[6d01d89]1476 | declaration comma_expression_opt ';' comma_expression_opt // C99, declaration has ';'
[1cdc052]1477 { $$ = new ForCtrl( new StatementNode( $1 ), $2, $4 ); }
[67d4e37]1478
[aa122e9]1479 | '@' ';' comma_expression // CFA, empty loop-index
[1cdc052]1480 { $$ = new ForCtrl( nullptr, $3, nullptr ); }
[aa122e9]1481 | '@' ';' comma_expression ';' comma_expression // CFA, empty loop-index
[1cdc052]1482 { $$ = new ForCtrl( nullptr, $3, $5 ); }
[51fbba5]1483
[aa122e9]1484 | comma_expression // CFA, anonymous loop-index
[bb7422a]1485 { $$ = forCtrl( yylloc, $1, new string( DeclarationNode::anonymous.newName() ), NEW_ZERO, OperKinds::LThan, $1->clone(), NEW_ONE ); }
[aa122e9]1486 | downupdowneq comma_expression // CFA, anonymous loop-index
[bb7422a]1487 { $$ = forCtrl( yylloc, $2, new string( DeclarationNode::anonymous.newName() ), UPDOWN( $1, NEW_ZERO, $2->clone() ), $1, UPDOWN( $1, $2->clone(), NEW_ZERO ), NEW_ONE ); }
[52be5948]1488
[aa122e9]1489 | comma_expression updowneq comma_expression // CFA, anonymous loop-index
[bb7422a]1490 { $$ = forCtrl( yylloc, $1, new string( DeclarationNode::anonymous.newName() ), UPDOWN( $2, $1->clone(), $3 ), $2, UPDOWN( $2, $3->clone(), $1->clone() ), NEW_ONE ); }
[aa122e9]1491 | '@' updowneq comma_expression // CFA, anonymous loop-index
[dbedd71]1492 {
[4fee301]1493 if ( $2 == OperKinds::LThan || $2 == OperKinds::LEThan ) { SemanticError( yylloc, MISSING_LOW ); $$ = nullptr; }
[bb7422a]1494 else $$ = forCtrl( yylloc, $3, new string( DeclarationNode::anonymous.newName() ), $3->clone(), $2, nullptr, NEW_ONE );
[dbedd71]1495 }
[aa122e9]1496 | comma_expression updowneq '@' // CFA, anonymous loop-index
[dbedd71]1497 {
[4fee301]1498 if ( $2 == OperKinds::LThan || $2 == OperKinds::LEThan ) { SemanticError( yylloc, MISSING_ANON_FIELD ); $$ = nullptr; }
[ed9a1ae]1499 else { SemanticError( yylloc, MISSING_HIGH ); $$ = nullptr; }
[dbedd71]1500 }
[aa122e9]1501 | comma_expression updowneq comma_expression '~' comma_expression // CFA, anonymous loop-index
[bb7422a]1502 { $$ = forCtrl( yylloc, $1, new string( DeclarationNode::anonymous.newName() ), UPDOWN( $2, $1->clone(), $3 ), $2, UPDOWN( $2, $3->clone(), $1->clone() ), $5 ); }
[aa122e9]1503 | '@' updowneq comma_expression '~' comma_expression // CFA, anonymous loop-index
[dbedd71]1504 {
[4fee301]1505 if ( $2 == OperKinds::LThan || $2 == OperKinds::LEThan ) { SemanticError( yylloc, MISSING_LOW ); $$ = nullptr; }
[bb7422a]1506 else $$ = forCtrl( yylloc, $3, new string( DeclarationNode::anonymous.newName() ), $3->clone(), $2, nullptr, $5 );
[dbedd71]1507 }
[aa122e9]1508 | comma_expression updowneq '@' '~' comma_expression // CFA, anonymous loop-index
[dbedd71]1509 {
[4fee301]1510 if ( $2 == OperKinds::LThan || $2 == OperKinds::LEThan ) { SemanticError( yylloc, MISSING_ANON_FIELD ); $$ = nullptr; }
[ed9a1ae]1511 else { SemanticError( yylloc, MISSING_HIGH ); $$ = nullptr; }
[dbedd71]1512 }
[65ef0cd]1513 | comma_expression updowneq comma_expression '~' '@' // CFA, invalid syntax rule
[4fee301]1514 { SemanticError( yylloc, MISSING_ANON_FIELD ); $$ = nullptr; }
[65ef0cd]1515 | '@' updowneq '@' // CFA, invalid syntax rule
[4fee301]1516 { SemanticError( yylloc, MISSING_ANON_FIELD ); $$ = nullptr; }
[65ef0cd]1517 | '@' updowneq comma_expression '~' '@' // CFA, invalid syntax rule
[4fee301]1518 { SemanticError( yylloc, MISSING_ANON_FIELD ); $$ = nullptr; }
[65ef0cd]1519 | comma_expression updowneq '@' '~' '@' // CFA, invalid syntax rule
[4fee301]1520 { SemanticError( yylloc, MISSING_ANON_FIELD ); $$ = nullptr; }
[65ef0cd]1521 | '@' updowneq '@' '~' '@' // CFA, invalid syntax rule
[4fee301]1522 { SemanticError( yylloc, MISSING_ANON_FIELD ); $$ = nullptr; }
[52be5948]1523
[f1aeede]1524 | comma_expression ';' comma_expression // CFA
[bb7422a]1525 { $$ = forCtrl( yylloc, $3, $1, NEW_ZERO, OperKinds::LThan, $3->clone(), NEW_ONE ); }
[d78c238]1526 | comma_expression ';' downupdowneq comma_expression // CFA
[bb7422a]1527 { $$ = forCtrl( yylloc, $4, $1, UPDOWN( $3, NEW_ZERO, $4->clone() ), $3, UPDOWN( $3, $4->clone(), NEW_ZERO ), NEW_ONE ); }
[52be5948]1528
[d78c238]1529 | comma_expression ';' comma_expression updowneq comma_expression // CFA
[bb7422a]1530 { $$ = forCtrl( yylloc, $3, $1, UPDOWN( $4, $3->clone(), $5 ), $4, UPDOWN( $4, $5->clone(), $3->clone() ), NEW_ONE ); }
[dbedd71]1531 | comma_expression ';' '@' updowneq comma_expression // CFA
1532 {
[4fee301]1533 if ( $4 == OperKinds::LThan || $4 == OperKinds::LEThan ) { SemanticError( yylloc, MISSING_LOW ); $$ = nullptr; }
[bb7422a]1534 else $$ = forCtrl( yylloc, $5, $1, $5->clone(), $4, nullptr, NEW_ONE );
[dbedd71]1535 }
[52be5948]1536 | comma_expression ';' comma_expression updowneq '@' // CFA
1537 {
[4fee301]1538 if ( $4 == OperKinds::GThan || $4 == OperKinds::GEThan ) { SemanticError( yylloc, MISSING_HIGH ); $$ = nullptr; }
[253d0b4]1539 else if ( $4 == OperKinds::LEThan ) { SemanticError( yylloc, "illegal syntax, equality with missing high value is meaningless. Use \"~\"." ); $$ = nullptr; }
[bb7422a]1540 else $$ = forCtrl( yylloc, $3, $1, $3->clone(), $4, nullptr, NEW_ONE );
[52be5948]1541 }
[65ef0cd]1542 | comma_expression ';' '@' updowneq '@' // CFA, invalid syntax rule
[253d0b4]1543 { SemanticError( yylloc, "illegal syntax, missing low/high value for up/down-to range so index is uninitialized." ); $$ = nullptr; }
[d78c238]1544
1545 | comma_expression ';' comma_expression updowneq comma_expression '~' comma_expression // CFA
[bb7422a]1546 { $$ = forCtrl( yylloc, $3, $1, UPDOWN( $4, $3->clone(), $5 ), $4, UPDOWN( $4, $5->clone(), $3->clone() ), $7 ); }
[65ef0cd]1547 | comma_expression ';' '@' updowneq comma_expression '~' comma_expression // CFA, invalid syntax rule
[dbedd71]1548 {
[4fee301]1549 if ( $4 == OperKinds::LThan || $4 == OperKinds::LEThan ) { SemanticError( yylloc, MISSING_LOW ); $$ = nullptr; }
[bb7422a]1550 else $$ = forCtrl( yylloc, $5, $1, $5->clone(), $4, nullptr, $7 );
[dbedd71]1551 }
[52be5948]1552 | comma_expression ';' comma_expression updowneq '@' '~' comma_expression // CFA
1553 {
[4fee301]1554 if ( $4 == OperKinds::GThan || $4 == OperKinds::GEThan ) { SemanticError( yylloc, MISSING_HIGH ); $$ = nullptr; }
[253d0b4]1555 else if ( $4 == OperKinds::LEThan ) { SemanticError( yylloc, "illegal syntax, equality with missing high value is meaningless. Use \"~\"." ); $$ = nullptr; }
[bb7422a]1556 else $$ = forCtrl( yylloc, $3, $1, $3->clone(), $4, nullptr, $7 );
[52be5948]1557 }
1558 | comma_expression ';' comma_expression updowneq comma_expression '~' '@' // CFA
[bb7422a]1559 { $$ = forCtrl( yylloc, $3, $1, UPDOWN( $4, $3->clone(), $5 ), $4, UPDOWN( $4, $5->clone(), $3->clone() ), nullptr ); }
[65ef0cd]1560 | comma_expression ';' '@' updowneq comma_expression '~' '@' // CFA, invalid syntax rule
[dbedd71]1561 {
[4fee301]1562 if ( $4 == OperKinds::LThan || $4 == OperKinds::LEThan ) { SemanticError( yylloc, MISSING_LOW ); $$ = nullptr; }
[bb7422a]1563 else $$ = forCtrl( yylloc, $5, $1, $5->clone(), $4, nullptr, nullptr );
[dbedd71]1564 }
[52be5948]1565 | comma_expression ';' comma_expression updowneq '@' '~' '@' // CFA
[d78c238]1566 {
[4fee301]1567 if ( $4 == OperKinds::GThan || $4 == OperKinds::GEThan ) { SemanticError( yylloc, MISSING_HIGH ); $$ = nullptr; }
[253d0b4]1568 else if ( $4 == OperKinds::LEThan ) { SemanticError( yylloc, "illegal syntax, equality with missing high value is meaningless. Use \"~\"." ); $$ = nullptr; }
[bb7422a]1569 else $$ = forCtrl( yylloc, $3, $1, $3->clone(), $4, nullptr, nullptr );
[d78c238]1570 }
[dbedd71]1571 | comma_expression ';' '@' updowneq '@' '~' '@' // CFA
[253d0b4]1572 { SemanticError( yylloc, "illegal syntax, missing low/high value for up/down-to range so index is uninitialized." ); $$ = nullptr; }
[d78c238]1573
1574 | declaration comma_expression // CFA
[bb7422a]1575 { $$ = forCtrl( yylloc, $1, NEW_ZERO, OperKinds::LThan, $2, NEW_ONE ); }
[d78c238]1576 | declaration downupdowneq comma_expression // CFA
[bb7422a]1577 { $$ = forCtrl( yylloc, $1, UPDOWN( $2, NEW_ZERO, $3 ), $2, UPDOWN( $2, $3->clone(), NEW_ZERO ), NEW_ONE ); }
[52be5948]1578
[d78c238]1579 | declaration comma_expression updowneq comma_expression // CFA
[bb7422a]1580 { $$ = forCtrl( yylloc, $1, UPDOWN( $3, $2->clone(), $4 ), $3, UPDOWN( $3, $4->clone(), $2->clone() ), NEW_ONE ); }
[dbedd71]1581 | declaration '@' updowneq comma_expression // CFA
1582 {
[4fee301]1583 if ( $3 == OperKinds::LThan || $3 == OperKinds::LEThan ) { SemanticError( yylloc, MISSING_LOW ); $$ = nullptr; }
[bb7422a]1584 else $$ = forCtrl( yylloc, $1, $4, $3, nullptr, NEW_ONE );
[dbedd71]1585 }
[52be5948]1586 | declaration comma_expression updowneq '@' // CFA
1587 {
[4fee301]1588 if ( $3 == OperKinds::GThan || $3 == OperKinds::GEThan ) { SemanticError( yylloc, MISSING_HIGH ); $$ = nullptr; }
[253d0b4]1589 else if ( $3 == OperKinds::LEThan ) { SemanticError( yylloc, "illegal syntax, equality with missing high value is meaningless. Use \"~\"." ); $$ = nullptr; }
[bb7422a]1590 else $$ = forCtrl( yylloc, $1, $2, $3, nullptr, NEW_ONE );
[52be5948]1591 }
[d78c238]1592
1593 | declaration comma_expression updowneq comma_expression '~' comma_expression // CFA
[bb7422a]1594 { $$ = forCtrl( yylloc, $1, UPDOWN( $3, $2, $4 ), $3, UPDOWN( $3, $4->clone(), $2->clone() ), $6 ); }
[dbedd71]1595 | declaration '@' updowneq comma_expression '~' comma_expression // CFA
1596 {
[4fee301]1597 if ( $3 == OperKinds::LThan || $3 == OperKinds::LEThan ) { SemanticError( yylloc, MISSING_LOW ); $$ = nullptr; }
[bb7422a]1598 else $$ = forCtrl( yylloc, $1, $4, $3, nullptr, $6 );
[dbedd71]1599 }
[52be5948]1600 | declaration comma_expression updowneq '@' '~' comma_expression // CFA
1601 {
[4fee301]1602 if ( $3 == OperKinds::GThan || $3 == OperKinds::GEThan ) { SemanticError( yylloc, MISSING_HIGH ); $$ = nullptr; }
[253d0b4]1603 else if ( $3 == OperKinds::LEThan ) { SemanticError( yylloc, "illegal syntax, equality with missing high value is meaningless. Use \"~\"." ); $$ = nullptr; }
[bb7422a]1604 else $$ = forCtrl( yylloc, $1, $2, $3, nullptr, $6 );
[52be5948]1605 }
1606 | declaration comma_expression updowneq comma_expression '~' '@' // CFA
[bb7422a]1607 { $$ = forCtrl( yylloc, $1, UPDOWN( $3, $2, $4 ), $3, UPDOWN( $3, $4->clone(), $2->clone() ), nullptr ); }
[dbedd71]1608 | declaration '@' updowneq comma_expression '~' '@' // CFA
1609 {
[4fee301]1610 if ( $3 == OperKinds::LThan || $3 == OperKinds::LEThan ) { SemanticError( yylloc, MISSING_LOW ); $$ = nullptr; }
[bb7422a]1611 else $$ = forCtrl( yylloc, $1, $4, $3, nullptr, nullptr );
[dbedd71]1612 }
[52be5948]1613 | declaration comma_expression updowneq '@' '~' '@' // CFA
[d78c238]1614 {
[4fee301]1615 if ( $3 == OperKinds::GThan || $3 == OperKinds::GEThan ) { SemanticError( yylloc, MISSING_HIGH ); $$ = nullptr; }
[253d0b4]1616 else if ( $3 == OperKinds::LEThan ) { SemanticError( yylloc, "illegal syntax, equality with missing high value is meaningless. Use \"~\"." ); $$ = nullptr; }
[bb7422a]1617 else $$ = forCtrl( yylloc, $1, $2, $3, nullptr, nullptr );
[d78c238]1618 }
[65ef0cd]1619 | declaration '@' updowneq '@' '~' '@' // CFA, invalid syntax rule
[253d0b4]1620 { SemanticError( yylloc, "illegal syntax, missing low/high value for up/down-to range so index is uninitialized." ); $$ = nullptr; }
[67d4e37]1621
[a8ced63]1622 | comma_expression ';' enum_key // CFA, enum type
[ca33b15]1623 {
[a8ced63]1624 $$ = enumRangeCtrl( $1, new ExpressionNode( new ast::TypeExpr( yylloc, $3->buildType() ) ) );
[ca33b15]1625 }
[a8ced63]1626 | comma_expression ';' downupdowneq enum_key // CFA, enum type, reverse direction
[d78c238]1627 {
[55266c7]1628 if ( $3 == OperKinds::LEThan || $3 == OperKinds::GEThan ) {
[253d0b4]1629 SemanticError( yylloc, "illegal syntax, all enumeration ranges are equal (all values). Remove \"=~\"." ); $$ = nullptr;
[55266c7]1630 }
[d78c238]1631 SemanticError( yylloc, "Type iterator is currently unimplemented." ); $$ = nullptr;
1632 }
[9fd9d015]1633 ;
[98337569]1634
[a8ced63]1635enum_key:
1636 type_name
1637 { $$ = DeclarationNode::newEnum( $1->symbolic.name, nullptr, false, false ); }
1638 | ENUM identifier
1639 { $$ = DeclarationNode::newEnum( $2, nullptr, false, false ); }
1640 | ENUM type_name
1641 { $$ = DeclarationNode::newEnum( $2->symbolic.name, nullptr, false, false ); }
1642 ;
1643
[d78c238]1644downupdowneq:
1645 ErangeDown
1646 { $$ = OperKinds::GThan; }
1647 | ErangeUpEq
1648 { $$ = OperKinds::LEThan; }
1649 | ErangeDownEq
1650 { $$ = OperKinds::GEThan; }
[9fd9d015]1651 ;
[51b73452]1652
[d78c238]1653updown:
[cc22003]1654 '~'
1655 { $$ = OperKinds::LThan; }
[d69f4bb4]1656 | ErangeDown
1657 { $$ = OperKinds::GThan; }
[9fd9d015]1658 ;
[d78c238]1659
1660updowneq:
1661 updown
1662 | ErangeUpEq
1663 { $$ = OperKinds::LEThan; }
[d69f4bb4]1664 | ErangeDownEq
1665 { $$ = OperKinds::GEThan; }
[9fd9d015]1666 ;
[cc22003]1667
[51b73452]1668jump_statement:
[44a81853]1669 GOTO identifier_or_type_name ';'
[bb7422a]1670 { $$ = new StatementNode( build_branch( yylloc, $2, ast::BranchStmt::Goto ) ); }
[4d51835]1671 | GOTO '*' comma_expression ';' // GCC, computed goto
[4e06c1e]1672 // The syntax for the GCC computed goto violates normal expression precedence, e.g., goto *i+3; => goto *(i+3);
[de62360d]1673 // whereas normal operator precedence yields goto (*i)+3;
[e82aa9df]1674 { $$ = new StatementNode( build_computedgoto( $3 ) ); }
[6a276a0]1675 // A semantic check is required to ensure fallthru appears only in the body of a choose statement.
[ec3f9c8]1676 | fall_through_name ';' // CFA
[bb7422a]1677 { $$ = new StatementNode( build_branch( yylloc, ast::BranchStmt::FallThrough ) ); }
[ec3f9c8]1678 | fall_through_name identifier_or_type_name ';' // CFA
[bb7422a]1679 { $$ = new StatementNode( build_branch( yylloc, $2, ast::BranchStmt::FallThrough ) ); }
[6a276a0]1680 | fall_through_name DEFAULT ';' // CFA
[bb7422a]1681 { $$ = new StatementNode( build_branch( yylloc, ast::BranchStmt::FallThroughDefault ) ); }
[4d51835]1682 | CONTINUE ';'
[de62360d]1683 // A semantic check is required to ensure this statement appears only in the body of an iteration statement.
[bb7422a]1684 { $$ = new StatementNode( build_branch( yylloc, ast::BranchStmt::Continue ) ); }
[44a81853]1685 | CONTINUE identifier_or_type_name ';' // CFA, multi-level continue
[de62360d]1686 // A semantic check is required to ensure this statement appears only in the body of an iteration statement, and
1687 // the target of the transfer appears only at the start of an iteration statement.
[bb7422a]1688 { $$ = new StatementNode( build_branch( yylloc, $2, ast::BranchStmt::Continue ) ); }
[4d51835]1689 | BREAK ';'
[de62360d]1690 // A semantic check is required to ensure this statement appears only in the body of an iteration statement.
[bb7422a]1691 { $$ = new StatementNode( build_branch( yylloc, ast::BranchStmt::Break ) ); }
[44a81853]1692 | BREAK identifier_or_type_name ';' // CFA, multi-level exit
[de62360d]1693 // A semantic check is required to ensure this statement appears only in the body of an iteration statement, and
1694 // the target of the transfer appears only at the start of an iteration statement.
[bb7422a]1695 { $$ = new StatementNode( build_branch( yylloc, $2, ast::BranchStmt::Break ) ); }
[4d51835]1696 | RETURN comma_expression_opt ';'
[bb7422a]1697 { $$ = new StatementNode( build_return( yylloc, $2 ) ); }
[c786e1d]1698 | RETURN '{' initializer_list_opt comma_opt '}' ';'
[fae90d5f]1699 { SemanticError( yylloc, "Initializer return is currently unimplemented." ); $$ = nullptr; }
[37cdd97]1700 | SUSPEND ';'
[bb7422a]1701 { $$ = new StatementNode( build_suspend( yylloc, nullptr, ast::SuspendStmt::None ) ); }
[9306559f]1702 | SUSPEND compound_statement
[bb7422a]1703 { $$ = new StatementNode( build_suspend( yylloc, $2, ast::SuspendStmt::None ) ); }
[37cdd97]1704 | SUSPEND COROUTINE ';'
[bb7422a]1705 { $$ = new StatementNode( build_suspend( yylloc, nullptr, ast::SuspendStmt::Coroutine ) ); }
[37cdd97]1706 | SUSPEND COROUTINE compound_statement
[bb7422a]1707 { $$ = new StatementNode( build_suspend( yylloc, $3, ast::SuspendStmt::Coroutine ) ); }
[37cdd97]1708 | SUSPEND GENERATOR ';'
[bb7422a]1709 { $$ = new StatementNode( build_suspend( yylloc, nullptr, ast::SuspendStmt::Generator ) ); }
[37cdd97]1710 | SUSPEND GENERATOR compound_statement
[bb7422a]1711 { $$ = new StatementNode( build_suspend( yylloc, $3, ast::SuspendStmt::Generator ) ); }
[8cc5cb0]1712 | THROW assignment_expression_opt ';' // handles rethrow
[bb7422a]1713 { $$ = new StatementNode( build_throw( yylloc, $2 ) ); }
[8cc5cb0]1714 | THROWRESUME assignment_expression_opt ';' // handles reresume
[bb7422a]1715 { $$ = new StatementNode( build_resume( yylloc, $2 ) ); }
[8cc5cb0]1716 | THROWRESUME assignment_expression_opt AT assignment_expression ';' // handles reresume
[daf1af8]1717 { $$ = new StatementNode( build_resume_at( $2, $4 ) ); }
[4d51835]1718 ;
[51b73452]1719
[6a276a0]1720fall_through_name: // CFA
1721 FALLTHRU
1722 | FALLTHROUGH
1723 ;
1724
[8b47e50]1725with_statement:
[e78966e]1726 WITH '(' type_list ')' statement // support scoped enumeration
[bb7422a]1727 { $$ = new StatementNode( build_with( yylloc, $3, $5 ) ); }
[5b2edbc]1728 ;
1729
[bf20567]1730// If MUTEX becomes a general qualifier, there are shift/reduce conflicts, so possibly change syntax to "with mutex".
[b6b3c42]1731mutex_statement:
[bf20567]1732 MUTEX '(' argument_expression_list_opt ')' statement
1733 {
[253d0b4]1734 if ( ! $3 ) { SemanticError( yylloc, "illegal syntax, mutex argument list cannot be empty." ); $$ = nullptr; }
[bb7422a]1735 $$ = new StatementNode( build_mutex( yylloc, $3, $5 ) );
[bf20567]1736 }
[b6b3c42]1737 ;
1738
[51d6d6a]1739when_clause:
[6a276a0]1740 WHEN '(' comma_expression ')' { $$ = $3; }
[51d6d6a]1741 ;
1742
[5b2edbc]1743when_clause_opt:
1744 // empty
[135b431]1745 { $$ = nullptr; }
[51d6d6a]1746 | when_clause
[5b2edbc]1747 ;
1748
[4a063df]1749cast_expression_list:
1750 cast_expression
1751 | cast_expression_list ',' cast_expression
[a491a3c]1752 { SemanticError( yylloc, "List of mutex member is currently unimplemented." ); $$ = nullptr; }
[5b2edbc]1753 ;
1754
1755timeout:
[9fd9d015]1756 TIMEOUT '(' comma_expression ')' { $$ = $3; }
[5b2edbc]1757 ;
1758
[9fd9d015]1759wor:
1760 OROR
1761 | WOR
1762
1763waitfor:
1764 WAITFOR '(' cast_expression ')'
1765 { $$ = $3; }
1766 | WAITFOR '(' cast_expression_list ':' argument_expression_list_opt ')'
[b93c544]1767 { $$ = $3->set_last( $5 ); }
[5b2edbc]1768 ;
1769
[9fd9d015]1770wor_waitfor_clause:
[51d6d6a]1771 when_clause_opt waitfor statement %prec THEN
[9fd9d015]1772 // Called first: create header for WaitForStmt.
[bb7422a]1773 { $$ = build_waitfor( yylloc, new ast::WaitForStmt( yylloc ), $1, $2, maybe_build_compound( yylloc, $3 ) ); }
[70056ed]1774 | wor_waitfor_clause wor when_clause_opt waitfor statement
[bb7422a]1775 { $$ = build_waitfor( yylloc, $1, $3, $4, maybe_build_compound( yylloc, $5 ) ); }
[9fd9d015]1776 | wor_waitfor_clause wor when_clause_opt ELSE statement
[bb7422a]1777 { $$ = build_waitfor_else( yylloc, $1, $3, maybe_build_compound( yylloc, $5 ) ); }
[9fd9d015]1778 | wor_waitfor_clause wor when_clause_opt timeout statement %prec THEN
[bb7422a]1779 { $$ = build_waitfor_timeout( yylloc, $1, $3, $4, maybe_build_compound( yylloc, $5 ) ); }
[afe9e45]1780 // "else" must be conditional after timeout or timeout is never triggered (i.e., it is meaningless)
[65ef0cd]1781 | wor_waitfor_clause wor when_clause_opt timeout statement wor ELSE statement // invalid syntax rule
[253d0b4]1782 { SemanticError( yylloc, "illegal syntax, else clause must be conditional after timeout or timeout never triggered." ); $$ = nullptr; }
[9fd9d015]1783 | wor_waitfor_clause wor when_clause_opt timeout statement wor when_clause ELSE statement
[bb7422a]1784 { $$ = build_waitfor_else( yylloc, build_waitfor_timeout( yylloc, $1, $3, $4, maybe_build_compound( yylloc, $5 ) ), $7, maybe_build_compound( yylloc, $9 ) ); }
[5b2edbc]1785 ;
1786
1787waitfor_statement:
[9fd9d015]1788 wor_waitfor_clause %prec THEN
1789 { $$ = new StatementNode( $1 ); }
1790 ;
1791
1792wand:
1793 ANDAND
1794 | WAND
1795 ;
1796
1797waituntil:
[04c78215]1798 WAITUNTIL '(' comma_expression ')'
[9fd9d015]1799 { $$ = $3; }
1800 ;
1801
1802waituntil_clause:
1803 when_clause_opt waituntil statement
[c86b08d]1804 { $$ = build_waituntil_clause( yylloc, $1, $2, maybe_build_compound( yylloc, $3 ) ); }
[9fd9d015]1805 | '(' wor_waituntil_clause ')'
[c86b08d]1806 { $$ = $2; }
[9fd9d015]1807 ;
1808
1809wand_waituntil_clause:
1810 waituntil_clause %prec THEN
[c86b08d]1811 { $$ = $1; }
[9fd9d015]1812 | waituntil_clause wand wand_waituntil_clause
[c86b08d]1813 { $$ = new ast::WaitUntilStmt::ClauseNode( ast::WaitUntilStmt::ClauseNode::Op::AND, $1, $3 ); }
[9fd9d015]1814 ;
1815
1816wor_waituntil_clause:
1817 wand_waituntil_clause
[c86b08d]1818 { $$ = $1; }
[70056ed]1819 | wor_waituntil_clause wor wand_waituntil_clause
[c86b08d]1820 { $$ = new ast::WaitUntilStmt::ClauseNode( ast::WaitUntilStmt::ClauseNode::Op::OR, $1, $3 ); }
[9fd9d015]1821 | wor_waituntil_clause wor when_clause_opt ELSE statement
[c86b08d]1822 { $$ = new ast::WaitUntilStmt::ClauseNode( ast::WaitUntilStmt::ClauseNode::Op::LEFT_OR, $1, build_waituntil_else( yylloc, $3, maybe_build_compound( yylloc, $5 ) ) ); }
[9fd9d015]1823 ;
1824
1825waituntil_statement:
1826 wor_waituntil_clause %prec THEN
[f259682]1827 { $$ = new StatementNode( build_waituntil_stmt( yylloc, $1 ) ); }
[8b47e50]1828 ;
1829
[11ab0b4a]1830corun_statement:
1831 CORUN statement
[eb779d5]1832 { $$ = new StatementNode( build_corun( yylloc, $2 ) ); }
[11ab0b4a]1833 ;
1834
1835cofor_statement:
1836 COFOR '(' for_control_expression_list ')' statement
[3d9d017]1837 { $$ = new StatementNode( build_cofor( yylloc, $3, maybe_build_compound( yylloc, $5 ) ) ); }
[11ab0b4a]1838 ;
1839
[51b73452]1840exception_statement:
[bb7422a]1841 TRY compound_statement handler_clause %prec THEN
1842 { $$ = new StatementNode( build_try( yylloc, $2, $3, nullptr ) ); }
[4d51835]1843 | TRY compound_statement finally_clause
[bb7422a]1844 { $$ = new StatementNode( build_try( yylloc, $2, nullptr, $3 ) ); }
[cfaabe2c]1845 | TRY compound_statement handler_clause finally_clause
[bb7422a]1846 { $$ = new StatementNode( build_try( yylloc, $2, $3, $4 ) ); }
[4d51835]1847 ;
[51b73452]1848
1849handler_clause:
[098f7ff]1850 handler_key '(' push exception_declaration pop handler_predicate_opt ')' compound_statement
[6611177]1851 { $$ = new ClauseNode( build_catch( yylloc, $1, $4, $6, $8 ) ); }
[098f7ff]1852 | handler_clause handler_key '(' push exception_declaration pop handler_predicate_opt ')' compound_statement
[6611177]1853 { $$ = $1->set_last( new ClauseNode( build_catch( yylloc, $2, $5, $7, $9 ) ) ); }
[994d080]1854 ;
1855
1856handler_predicate_opt:
[7fdb94e1]1857 // empty
[cbce272]1858 { $$ = nullptr; }
[6a276a0]1859 | ';' conditional_expression { $$ = $2; }
[307a732]1860 ;
1861
1862handler_key:
[bb7422a]1863 CATCH { $$ = ast::Terminate; }
1864 | RECOVER { $$ = ast::Terminate; }
1865 | CATCHRESUME { $$ = ast::Resume; }
1866 | FIXUP { $$ = ast::Resume; }
[4d51835]1867 ;
[51b73452]1868
1869finally_clause:
[6611177]1870 FINALLY compound_statement { $$ = new ClauseNode( build_finally( yylloc, $2 ) ); }
[4d51835]1871 ;
[51b73452]1872
1873exception_declaration:
[d0ffed1]1874 // No SUE declaration in parameter list.
1875 type_specifier_nobody
1876 | type_specifier_nobody declarator
[c0a33d2]1877 { $$ = $2->addType( $1 ); }
[d0ffed1]1878 | type_specifier_nobody variable_abstract_declarator
[4d51835]1879 { $$ = $2->addType( $1 ); }
[033ff37]1880 | cfa_abstract_declarator_tuple identifier // CFA
[c0a33d2]1881 { $$ = $1->addName( $2 ); }
[c0aa336]1882 | cfa_abstract_declarator_tuple // CFA
[4d51835]1883 ;
[51b73452]1884
[2a8427c6]1885enable_disable_statement:
1886 enable_disable_key identifier_list compound_statement
1887 ;
1888
1889enable_disable_key:
1890 ENABLE
1891 | DISABLE
1892 ;
1893
[51b73452]1894asm_statement:
[ab57786]1895 ASM asm_volatile_opt '(' string_literal ')' ';'
[bb7422a]1896 { $$ = new StatementNode( build_asm( yylloc, $2, $4, nullptr ) ); }
[ab57786]1897 | ASM asm_volatile_opt '(' string_literal ':' asm_operands_opt ')' ';' // remaining GCC
[bb7422a]1898 { $$ = new StatementNode( build_asm( yylloc, $2, $4, $6 ) ); }
[ab57786]1899 | ASM asm_volatile_opt '(' string_literal ':' asm_operands_opt ':' asm_operands_opt ')' ';'
[bb7422a]1900 { $$ = new StatementNode( build_asm( yylloc, $2, $4, $6, $8 ) ); }
[ab57786]1901 | ASM asm_volatile_opt '(' string_literal ':' asm_operands_opt ':' asm_operands_opt ':' asm_clobbers_list_opt ')' ';'
[bb7422a]1902 { $$ = new StatementNode( build_asm( yylloc, $2, $4, $6, $8, $10 ) ); }
[ab57786]1903 | ASM asm_volatile_opt GOTO '(' string_literal ':' ':' asm_operands_opt ':' asm_clobbers_list_opt ':' label_list ')' ';'
[bb7422a]1904 { $$ = new StatementNode( build_asm( yylloc, $2, $5, nullptr, $8, $10, $12 ) ); }
[7f5566b]1905 ;
1906
1907asm_volatile_opt: // GCC
1908 // empty
1909 { $$ = false; }
1910 | VOLATILE
1911 { $$ = true; }
[4d51835]1912 ;
[b87a5ed]1913
1914asm_operands_opt: // GCC
[4d51835]1915 // empty
[58dd019]1916 { $$ = nullptr; } // use default argument
[4d51835]1917 | asm_operands_list
1918 ;
[b87a5ed]1919
1920asm_operands_list: // GCC
[4d51835]1921 asm_operand
1922 | asm_operands_list ',' asm_operand
[b93c544]1923 { $$ = $1->set_last( $3 ); }
[4d51835]1924 ;
[b87a5ed]1925
1926asm_operand: // GCC
[ab57786]1927 string_literal '(' constant_expression ')'
[32d6fdc]1928 { $$ = new ExpressionNode( new ast::AsmExpr( yylloc, "", maybeMoveBuild( $1 ), maybeMoveBuild( $3 ) ) ); }
[665f432]1929 | '[' IDENTIFIER ']' string_literal '(' constant_expression ')'
[bb7422a]1930 {
[32d6fdc]1931 $$ = new ExpressionNode( new ast::AsmExpr( yylloc, *$2.str, maybeMoveBuild( $4 ), maybeMoveBuild( $6 ) ) );
[bb7422a]1932 delete $2.str;
1933 }
[7f5566b]1934 ;
1935
[4e06c1e]1936asm_clobbers_list_opt: // GCC
[7f5566b]1937 // empty
[58dd019]1938 { $$ = nullptr; } // use default argument
[ab57786]1939 | string_literal
[32d6fdc]1940 { $$ = $1; }
[ab57786]1941 | asm_clobbers_list_opt ',' string_literal
[b93c544]1942 { $$ = $1->set_last( $3 ); }
[4d51835]1943 ;
[b87a5ed]1944
[7f5566b]1945label_list:
[033ff37]1946 identifier
[ab57786]1947 {
[bb7422a]1948 $$ = new LabelNode(); $$->labels.emplace_back( yylloc, *$1 );
[ab57786]1949 delete $1; // allocated by lexer
1950 }
[033ff37]1951 | label_list ',' identifier
[ab57786]1952 {
[bb7422a]1953 $$ = $1; $1->labels.emplace_back( yylloc, *$3 );
[ab57786]1954 delete $3; // allocated by lexer
1955 }
[4d51835]1956 ;
[51b73452]1957
[e1d66c84]1958// ****************************** DECLARATIONS *********************************
[51b73452]1959
[b87a5ed]1960declaration_list_opt: // used at beginning of switch statement
[35718a9]1961 // empty
[58dd019]1962 { $$ = nullptr; }
[4d51835]1963 | declaration_list
1964 ;
[51b73452]1965
1966declaration_list:
[4d51835]1967 declaration
[647e2ea]1968 | declaration_list declaration
1969 { $$ = $1->set_last( $2 ); }
[4d51835]1970 ;
[51b73452]1971
[407bde5]1972KR_parameter_list_opt: // used to declare parameter types in K&R style functions
[4cc585b]1973 // empty
[58dd019]1974 { $$ = nullptr; }
[35718a9]1975 | KR_parameter_list
[4d51835]1976 ;
[51b73452]1977
[35718a9]1978KR_parameter_list:
[c25f16b]1979 c_declaration ';'
1980 { $$ = $1; }
1981 | KR_parameter_list c_declaration ';'
[dc3fbe5]1982 { $$ = $1->set_last( $2 ); }
[4d51835]1983 ;
[b87a5ed]1984
[51b1202]1985local_label_declaration_opt: // GCC, local label
[4d51835]1986 // empty
[51b1202]1987 | local_label_declaration_list
[4d51835]1988 ;
[b87a5ed]1989
[51b1202]1990local_label_declaration_list: // GCC, local label
1991 LABEL local_label_list ';'
1992 | local_label_declaration_list LABEL local_label_list ';'
[4d51835]1993 ;
[b87a5ed]1994
[51b1202]1995local_label_list: // GCC, local label
[033ff37]1996 identifier_or_type_name
1997 | local_label_list ',' identifier_or_type_name
[4d51835]1998 ;
[b87a5ed]1999
[936e9f4]2000declaration: // old & new style declarations
[35718a9]2001 c_declaration ';'
2002 | cfa_declaration ';' // CFA
[b47b827]2003 | static_assert // C11
[4d51835]2004 ;
[b87a5ed]2005
[b9be000b]2006static_assert:
2007 STATICASSERT '(' constant_expression ',' string_literal ')' ';' // C11
[32d6fdc]2008 { $$ = DeclarationNode::newStaticAssert( $3, maybeMoveBuild( $5 ) ); }
[b47b827]2009 | STATICASSERT '(' constant_expression ')' ';' // CFA
[bb7422a]2010 { $$ = DeclarationNode::newStaticAssert( $3, build_constantStr( yylloc, *new string( "\"\"" ) ) ); }
[b9be000b]2011
[de62360d]2012// C declaration syntax is notoriously confusing and error prone. Cforall provides its own type, variable and function
2013// declarations. CFA declarations use the same declaration tokens as in C; however, CFA places declaration modifiers to
2014// the left of the base type, while C declarations place modifiers to the right of the base type. CFA declaration
2015// modifiers are interpreted from left to right and the entire type specification is distributed across all variables in
2016// the declaration list (as in Pascal). ANSI C and the new CFA declarations may appear together in the same program
2017// block, but cannot be mixed within a specific declaration.
[c11e31c]2018//
[b87a5ed]2019// CFA C
2020// [10] int x; int x[10]; // array of 10 integers
2021// [10] * char y; char *y[10]; // array of 10 pointers to char
2022
[c0aa336]2023cfa_declaration: // CFA
[4cc585b]2024 cfa_variable_declaration
2025 | cfa_typedef_declaration
2026 | cfa_function_declaration
2027 | type_declaring_list
[2501ae5]2028 { SemanticError( yylloc, "otype declaration is currently unimplemented." ); $$ = nullptr; }
[4cc585b]2029 | trait_specifier
[4d51835]2030 ;
[b87a5ed]2031
[c0aa336]2032cfa_variable_declaration: // CFA
2033 cfa_variable_specifier initializer_opt
[7fdb94e1]2034 { $$ = $1->addInitializer( $2 ); }
[c0aa336]2035 | declaration_qualifier_list cfa_variable_specifier initializer_opt
[de62360d]2036 // declaration_qualifier_list also includes type_qualifier_list, so a semantic check is necessary to preclude
2037 // them as a type_qualifier cannot appear in that context.
[7fdb94e1]2038 { $$ = $2->addQualifiers( $1 )->addInitializer( $3 ); }
[c0aa336]2039 | cfa_variable_declaration pop ',' push identifier_or_type_name initializer_opt
[dc3fbe5]2040 { $$ = $1->set_last( $1->cloneType( $5 )->addInitializer( $6 ) ); }
[4d51835]2041 ;
[b87a5ed]2042
[c0aa336]2043cfa_variable_specifier: // CFA
[de62360d]2044 // A semantic check is required to ensure asm_name only appears on declarations with implicit or explicit static
2045 // storage-class
[c0aa336]2046 cfa_abstract_declarator_no_tuple identifier_or_type_name asm_name_opt
[7fdb94e1]2047 { $$ = $1->addName( $2 )->addAsmName( $3 ); }
[c0aa336]2048 | cfa_abstract_tuple identifier_or_type_name asm_name_opt
[7fdb94e1]2049 { $$ = $1->addName( $2 )->addAsmName( $3 ); }
[c0aa336]2050 | type_qualifier_list cfa_abstract_tuple identifier_or_type_name asm_name_opt
[7fdb94e1]2051 { $$ = $2->addQualifiers( $1 )->addName( $3 )->addAsmName( $4 ); }
[2ab31fd]2052
2053 // [ int s, int t ]; // declare s and t
2054 // [ int, int ] f();
2055 // [] g( int );
2056 // [ int x, int y ] = f(); // declare x and y, initialize each from f
2057 // g( x + y );
2058 | cfa_function_return asm_name_opt
2059 { SemanticError( yylloc, "tuple-element declarations is currently unimplemented." ); $$ = nullptr; }
2060 | type_qualifier_list cfa_function_return asm_name_opt
2061 { SemanticError( yylloc, "tuple variable declaration is currently unimplemented." ); $$ = nullptr; }
[4d51835]2062 ;
[b87a5ed]2063
[c0aa336]2064cfa_function_declaration: // CFA
2065 cfa_function_specifier
2066 | type_qualifier_list cfa_function_specifier
[7fdb94e1]2067 { $$ = $2->addQualifiers( $1 ); }
[c0aa336]2068 | declaration_qualifier_list cfa_function_specifier
[7fdb94e1]2069 { $$ = $2->addQualifiers( $1 ); }
[c0aa336]2070 | declaration_qualifier_list type_qualifier_list cfa_function_specifier
[7fdb94e1]2071 { $$ = $3->addQualifiers( $1 )->addQualifiers( $2 ); }
[647e2ea]2072 | cfa_function_declaration ',' identifier_or_type_name '(' push cfa_parameter_list_ellipsis_opt pop ')'
[4d51835]2073 {
[481115f]2074 // Append the return type at the start (left-hand-side) to each identifier in the list.
2075 DeclarationNode * ret = new DeclarationNode;
[5bf685f]2076 ret->type = maybeCopy( $1->type->base );
[dc3fbe5]2077 $$ = $1->set_last( DeclarationNode::newFunction( $3, ret, $6, nullptr ) );
[4d51835]2078 }
2079 ;
[b87a5ed]2080
[c0aa336]2081cfa_function_specifier: // CFA
[647e2ea]2082 '[' ']' identifier '(' push cfa_parameter_list_ellipsis_opt pop ')' attribute_list_opt
2083 { $$ = DeclarationNode::newFunction( $3, DeclarationNode::newTuple( nullptr ), $6, nullptr )->addQualifiers( $9 ); }
2084 | '[' ']' TYPEDEFname '(' push cfa_parameter_list_ellipsis_opt pop ')' attribute_list_opt
2085 { $$ = DeclarationNode::newFunction( $3, DeclarationNode::newTuple( nullptr ), $6, nullptr )->addQualifiers( $9 ); }
2086 // | '[' ']' TYPEGENname '(' push cfa_parameter_list_ellipsis_opt pop ')' attribute_list_opt
2087 // { $$ = DeclarationNode::newFunction( $3, DeclarationNode::newTuple( nullptr ), $6, nullptr )->addQualifiers( $9 ); }
2088
[2871210]2089 // identifier_or_type_name must be broken apart because of the sequence:
[4d51835]2090 //
[647e2ea]2091 // '[' ']' identifier_or_type_name '(' cfa_parameter_list_ellipsis_opt ')'
[4d51835]2092 // '[' ']' type_specifier
2093 //
[2871210]2094 // type_specifier can resolve to just TYPEDEFname (e.g., typedef int T; int f( T );). Therefore this must be
2095 // flattened to allow lookahead to the '(' without having to reduce identifier_or_type_name.
[647e2ea]2096 | cfa_abstract_tuple identifier_or_type_name '(' push cfa_parameter_list_ellipsis_opt pop ')' attribute_list_opt
[c0aa336]2097 // To obtain LR(1 ), this rule must be factored out from function return type (see cfa_abstract_declarator).
[a5f9444]2098 { $$ = DeclarationNode::newFunction( $2, $1, $5, nullptr )->addQualifiers( $8 ); }
[647e2ea]2099 | cfa_function_return identifier_or_type_name '(' push cfa_parameter_list_ellipsis_opt pop ')' attribute_list_opt
[a5f9444]2100 { $$ = DeclarationNode::newFunction( $2, $1, $5, nullptr )->addQualifiers( $8 ); }
[4d51835]2101 ;
[b87a5ed]2102
[c0aa336]2103cfa_function_return: // CFA
[c0a33d2]2104 '[' push cfa_parameter_list pop ']'
2105 { $$ = DeclarationNode::newTuple( $3 ); }
[647e2ea]2106 | '[' push cfa_parameter_list ',' cfa_abstract_parameter_list pop ']'
[b048dc3]2107 // To obtain LR(1 ), the last cfa_abstract_parameter_list is added into this flattened rule to lookahead to the ']'.
[647e2ea]2108 { $$ = DeclarationNode::newTuple( $3->set_last( $5 ) ); }
[4d51835]2109 ;
[b87a5ed]2110
[c0aa336]2111cfa_typedef_declaration: // CFA
2112 TYPEDEF cfa_variable_specifier
[4d51835]2113 {
[71a422a]2114 typedefTable.addToEnclosingScope( *$2->name, TYPEDEFname, "cfa_typedef_declaration 1" );
[4d51835]2115 $$ = $2->addTypedef();
2116 }
[c0aa336]2117 | TYPEDEF cfa_function_specifier
[4d51835]2118 {
[71a422a]2119 typedefTable.addToEnclosingScope( *$2->name, TYPEDEFname, "cfa_typedef_declaration 2" );
[4d51835]2120 $$ = $2->addTypedef();
2121 }
[647e2ea]2122 | cfa_typedef_declaration ',' identifier
[4d51835]2123 {
[647e2ea]2124 typedefTable.addToEnclosingScope( *$3, TYPEDEFname, "cfa_typedef_declaration 3" );
2125 $$ = $1->set_last( $1->cloneType( $3 ) );
[4d51835]2126 }
2127 ;
[b87a5ed]2128
[de62360d]2129// Traditionally typedef is part of storage-class specifier for syntactic convenience only. Here, it is factored out as
2130// a separate form of declaration, which syntactically precludes storage-class specifiers and initialization.
[51b73452]2131
2132typedef_declaration:
[4d51835]2133 TYPEDEF type_specifier declarator
2134 {
[71a422a]2135 typedefTable.addToEnclosingScope( *$3->name, TYPEDEFname, "typedef_declaration 1" );
[ac235a8]2136 if ( $2->type->forall || ($2->type->kind == TypeData::Aggregate && $2->type->aggregate.params) ) {
2137 SemanticError( yylloc, "forall qualifier in typedef is currently unimplemented." ); $$ = nullptr;
2138 } else $$ = $3->addType( $2 )->addTypedef(); // watchout frees $2 and $3
[4d51835]2139 }
[c25f16b]2140 | typedef_declaration ',' declarator
[4d51835]2141 {
[c25f16b]2142 typedefTable.addToEnclosingScope( *$3->name, TYPEDEFname, "typedef_declaration 2" );
[dc3fbe5]2143 $$ = $1->set_last( $1->cloneBaseType( $3 )->addTypedef() );
[4d51835]2144 }
[de62360d]2145 | type_qualifier_list TYPEDEF type_specifier declarator // remaining OBSOLESCENT (see 2 )
[ac235a8]2146 { SemanticError( yylloc, "Type qualifiers/specifiers before TYPEDEF is deprecated, move after TYPEDEF." ); $$ = nullptr; }
[4d51835]2147 | type_specifier TYPEDEF declarator
[ac235a8]2148 { SemanticError( yylloc, "Type qualifiers/specifiers before TYPEDEF is deprecated, move after TYPEDEF." ); $$ = nullptr; }
[4d51835]2149 | type_specifier TYPEDEF type_qualifier_list declarator
[ac235a8]2150 { SemanticError( yylloc, "Type qualifiers/specifiers before TYPEDEF is deprecated, move after TYPEDEF." ); $$ = nullptr; }
[4d51835]2151 ;
[b87a5ed]2152
[721f17a]2153typedef_expression:
[25744d2]2154 // deprecated GCC, naming expression type: typedef name = exp; gives a name to the type of an expression
[033ff37]2155 TYPEDEF identifier '=' assignment_expression
[4d51835]2156 {
[ac235a8]2157 SemanticError( yylloc, "TYPEDEF expression is deprecated, use typeof(...) instead." ); $$ = nullptr;
[4d51835]2158 }
[c25f16b]2159 | typedef_expression ',' identifier '=' assignment_expression
[4d51835]2160 {
[ac235a8]2161 SemanticError( yylloc, "TYPEDEF expression is deprecated, use typeof(...) instead." ); $$ = nullptr;
[4d51835]2162 }
2163 ;
[51b73452]2164
[c0aa336]2165c_declaration:
[4cc585b]2166 declaration_specifier declaring_list
[7fdb94e1]2167 { $$ = distAttr( $1, $2 ); }
[4cc585b]2168 | typedef_declaration
[25744d2]2169 | typedef_expression // deprecated GCC, naming expression type
[4cc585b]2170 | sue_declaration_specifier
[0bcd707]2171 {
2172 assert( $1->type );
[1a73dbb]2173 if ( $1->type->qualifiers.any() ) { // CV qualifiers ?
[253d0b4]2174 SemanticError( yylloc, "illegal syntax, useless type qualifier(s) in empty declaration." ); $$ = nullptr;
[1a73dbb]2175 }
2176 // enums are never empty declarations because there must have at least one enumeration.
2177 if ( $1->type->kind == TypeData::AggregateInst && $1->storageClasses.any() ) { // storage class ?
[253d0b4]2178 SemanticError( yylloc, "illegal syntax, useless storage qualifier(s) in empty aggregate declaration." ); $$ = nullptr;
[0bcd707]2179 }
2180 }
[4d51835]2181 ;
[51b73452]2182
2183declaring_list:
[de62360d]2184 // A semantic check is required to ensure asm_name only appears on declarations with implicit or explicit static
2185 // storage-class
[1f771fc]2186 variable_declarator asm_name_opt initializer_opt
[7fdb94e1]2187 { $$ = $1->addAsmName( $2 )->addInitializer( $3 ); }
[1f771fc]2188 | variable_type_redeclarator asm_name_opt initializer_opt
[7fdb94e1]2189 { $$ = $1->addAsmName( $2 )->addInitializer( $3 ); }
[1f771fc]2190
2191 | general_function_declarator asm_name_opt
2192 { $$ = $1->addAsmName( $2 )->addInitializer( nullptr ); }
2193 | general_function_declarator asm_name_opt '=' VOID
2194 { $$ = $1->addAsmName( $2 )->addInitializer( new InitializerNode( true ) ); }
2195
[4d51835]2196 | declaring_list ',' attribute_list_opt declarator asm_name_opt initializer_opt
[dc3fbe5]2197 { $$ = $1->set_last( $4->addQualifiers( $3 )->addAsmName( $5 )->addInitializer( $6 ) ); }
[4d51835]2198 ;
[b87a5ed]2199
[1f771fc]2200general_function_declarator:
2201 function_type_redeclarator
2202 | function_declarator
2203 ;
2204
[b87a5ed]2205declaration_specifier: // type specifier + storage class
[4d51835]2206 basic_declaration_specifier
[84d58c5]2207 | type_declaration_specifier
[79a6b17]2208 | sue_declaration_specifier
[0442f93f]2209 | sue_declaration_specifier invalid_types // invalid syntax rule
[79a6b17]2210 {
[253d0b4]2211 SemanticError( yylloc, "illegal syntax, expecting ';' at end of \"%s\" declaration.",
[67467a3]2212 ast::AggregateDecl::aggrString( $1->type->aggregate.kind ) );
[79a6b17]2213 $$ = nullptr;
2214 }
2215 ;
2216
2217invalid_types:
2218 aggregate_key
2219 | basic_type_name
2220 | indirect_type
[4d51835]2221 ;
[b87a5ed]2222
[d0ffed1]2223declaration_specifier_nobody: // type specifier + storage class - {...}
2224 // Preclude SUE declarations in restricted scopes:
2225 //
2226 // int f( struct S { int i; } s1, Struct S s2 ) { struct S s3; ... }
2227 //
2228 // because it is impossible to call f due to name equivalence.
2229 basic_declaration_specifier
2230 | sue_declaration_specifier_nobody
[84d58c5]2231 | type_declaration_specifier
[d0ffed1]2232 ;
2233
2234type_specifier: // type specifier
[4d51835]2235 basic_type_specifier
2236 | sue_type_specifier
[84d58c5]2237 | type_type_specifier
[4d51835]2238 ;
[b87a5ed]2239
[d0ffed1]2240type_specifier_nobody: // type specifier - {...}
2241 // Preclude SUE declarations in restricted scopes:
2242 //
2243 // int f( struct S { int i; } s1, Struct S s2 ) { struct S s3; ... }
2244 //
2245 // because it is impossible to call f due to name equivalence.
2246 basic_type_specifier
2247 | sue_type_specifier_nobody
[84d58c5]2248 | type_type_specifier
[d0ffed1]2249 ;
2250
[b87a5ed]2251type_qualifier_list_opt: // GCC, used in asm_statement
[4d51835]2252 // empty
[58dd019]2253 { $$ = nullptr; }
[4d51835]2254 | type_qualifier_list
2255 ;
[51b73452]2256
2257type_qualifier_list:
[de62360d]2258 // A semantic check is necessary to ensure a type qualifier is appropriate for the kind of declaration.
[4d51835]2259 //
[de62360d]2260 // ISO/IEC 9899:1999 Section 6.7.3(4 ) : If the same qualifier appears more than once in the same
2261 // specifier-qualifier-list, either directly or via one or more typedefs, the behavior is the same as if it
2262 // appeared only once.
[4d51835]2263 type_qualifier
2264 | type_qualifier_list type_qualifier
2265 { $$ = $1->addQualifiers( $2 ); }
2266 ;
[51b73452]2267
2268type_qualifier:
[4d51835]2269 type_qualifier_name
[6cef439]2270 { $$ = DeclarationNode::newFromTypeData( $1 ); }
[b1f2007d]2271 | attribute // trick handles most attribute locations
[4d51835]2272 ;
[51b73452]2273
2274type_qualifier_name:
[4d51835]2275 CONST
[6cef439]2276 { $$ = build_type_qualifier( ast::CV::Const ); }
[4d51835]2277 | RESTRICT
[6cef439]2278 { $$ = build_type_qualifier( ast::CV::Restrict ); }
[4d51835]2279 | VOLATILE
[6cef439]2280 { $$ = build_type_qualifier( ast::CV::Volatile ); }
[4d51835]2281 | ATOMIC
[6cef439]2282 { $$ = build_type_qualifier( ast::CV::Atomic ); }
[7e13b11]2283
[446740a]2284 // forall is a CV qualifier because it can appear in places where SC qualifiers are disallowed.
[7e13b11]2285 //
2286 // void foo( forall( T ) T (*)( T ) ); // forward declaration
2287 // void bar( static int ); // static disallowed (gcc/CFA)
[a16a7ec]2288 | forall
[6cef439]2289 { $$ = build_forall( $1 ); }
[a16a7ec]2290 ;
2291
2292forall:
[35718a9]2293 FORALL '(' type_parameter_list ')' // CFA
[7a24d76]2294 { $$ = $3; }
[4d51835]2295 ;
[51b73452]2296
2297declaration_qualifier_list:
[4d51835]2298 storage_class_list
[de62360d]2299 | type_qualifier_list storage_class_list // remaining OBSOLESCENT (see 2 )
[4d51835]2300 { $$ = $1->addQualifiers( $2 ); }
2301 | declaration_qualifier_list type_qualifier_list storage_class_list
2302 { $$ = $1->addQualifiers( $2 )->addQualifiers( $3 ); }
2303 ;
[51b73452]2304
2305storage_class_list:
[de62360d]2306 // A semantic check is necessary to ensure a storage class is appropriate for the kind of declaration and that
2307 // only one of each is specified, except for inline, which can appear with the others.
[4d51835]2308 //
[de62360d]2309 // ISO/IEC 9899:1999 Section 6.7.1(2) : At most, one storage-class specifier may be given in the declaration
2310 // specifiers in a declaration.
[4d51835]2311 storage_class
2312 | storage_class_list storage_class
2313 { $$ = $1->addQualifiers( $2 ); }
2314 ;
[51b73452]2315
2316storage_class:
[4d51835]2317 EXTERN
[36e6f10]2318 { $$ = DeclarationNode::newStorageClass( ast::Storage::Extern ); }
[4d51835]2319 | STATIC
[36e6f10]2320 { $$ = DeclarationNode::newStorageClass( ast::Storage::Static ); }
[4d51835]2321 | AUTO
[36e6f10]2322 { $$ = DeclarationNode::newStorageClass( ast::Storage::Auto ); }
[4d51835]2323 | REGISTER
[36e6f10]2324 { $$ = DeclarationNode::newStorageClass( ast::Storage::Register ); }
[ed9a1ae]2325 | THREADLOCALGCC // GCC
[36e6f10]2326 { $$ = DeclarationNode::newStorageClass( ast::Storage::ThreadLocalGcc ); }
[ed9a1ae]2327 | THREADLOCALC11 // C11
[36e6f10]2328 { $$ = DeclarationNode::newStorageClass( ast::Storage::ThreadLocalC11 ); }
[dd020c0]2329 // Put function specifiers here to simplify parsing rules, but separate them semantically.
[4d51835]2330 | INLINE // C99
[36e6f10]2331 { $$ = DeclarationNode::newFuncSpecifier( ast::Function::Inline ); }
[4d51835]2332 | FORTRAN // C99
[36e6f10]2333 { $$ = DeclarationNode::newFuncSpecifier( ast::Function::Fortran ); }
[68cd1ce]2334 | NORETURN // C11
[36e6f10]2335 { $$ = DeclarationNode::newFuncSpecifier( ast::Function::Noreturn ); }
[4d51835]2336 ;
[51b73452]2337
2338basic_type_name:
[6cef439]2339 basic_type_name_type
2340 { $$ = DeclarationNode::newFromTypeData( $1 ); }
2341 ;
2342
2343// Just an intermediate value for conversion.
2344basic_type_name_type:
[201aeb9]2345 VOID
[e048ece]2346 { $$ = build_basic_type( TypeData::Void ); }
[4d51835]2347 | BOOL // C99
[e048ece]2348 { $$ = build_basic_type( TypeData::Bool ); }
[201aeb9]2349 | CHAR
[e048ece]2350 { $$ = build_basic_type( TypeData::Char ); }
[201aeb9]2351 | INT
[e048ece]2352 { $$ = build_basic_type( TypeData::Int ); }
[201aeb9]2353 | INT128
[e048ece]2354 { $$ = build_basic_type( TypeData::Int128 ); }
[f1da02c]2355 | UINT128
[e048ece]2356 { $$ = addType( build_basic_type( TypeData::Int128 ), build_signedness( TypeData::Unsigned ) ); }
[201aeb9]2357 | FLOAT
[e048ece]2358 { $$ = build_basic_type( TypeData::Float ); }
[201aeb9]2359 | DOUBLE
[e048ece]2360 { $$ = build_basic_type( TypeData::Double ); }
[e15853c]2361 | uuFLOAT80
[e048ece]2362 { $$ = build_basic_type( TypeData::uuFloat80 ); }
[e15853c]2363 | uuFLOAT128
[e048ece]2364 { $$ = build_basic_type( TypeData::uuFloat128 ); }
[e15853c]2365 | uFLOAT16
[e048ece]2366 { $$ = build_basic_type( TypeData::uFloat16 ); }
[e15853c]2367 | uFLOAT32
[e048ece]2368 { $$ = build_basic_type( TypeData::uFloat32 ); }
[e15853c]2369 | uFLOAT32X
[e048ece]2370 { $$ = build_basic_type( TypeData::uFloat32x ); }
[e15853c]2371 | uFLOAT64
[e048ece]2372 { $$ = build_basic_type( TypeData::uFloat64 ); }
[e15853c]2373 | uFLOAT64X
[e048ece]2374 { $$ = build_basic_type( TypeData::uFloat64x ); }
[e15853c]2375 | uFLOAT128
[e048ece]2376 { $$ = build_basic_type( TypeData::uFloat128 ); }
[15f769c]2377 | DECIMAL32
2378 { SemanticError( yylloc, "_Decimal32 is currently unimplemented." ); $$ = nullptr; }
2379 | DECIMAL64
2380 { SemanticError( yylloc, "_Decimal64 is currently unimplemented." ); $$ = nullptr; }
2381 | DECIMAL128
2382 { SemanticError( yylloc, "_Decimal128 is currently unimplemented." ); $$ = nullptr; }
[4d51835]2383 | COMPLEX // C99
[e048ece]2384 { $$ = build_complex_type( TypeData::Complex ); }
[4d51835]2385 | IMAGINARY // C99
[e048ece]2386 { $$ = build_complex_type( TypeData::Imaginary ); }
[201aeb9]2387 | SIGNED
[e048ece]2388 { $$ = build_signedness( TypeData::Signed ); }
[201aeb9]2389 | UNSIGNED
[e048ece]2390 { $$ = build_signedness( TypeData::Unsigned ); }
[201aeb9]2391 | SHORT
[e048ece]2392 { $$ = build_length( TypeData::Short ); }
[201aeb9]2393 | LONG
[e048ece]2394 { $$ = build_length( TypeData::Long ); }
[59c7e3e]2395 | VA_LIST // GCC, __builtin_va_list
[e048ece]2396 { $$ = build_builtin_type( TypeData::Valist ); }
[f673c13c]2397 | AUTO_TYPE
[e048ece]2398 { $$ = build_builtin_type( TypeData::AutoType ); }
[1f652a7]2399 | vtable
2400 ;
2401
2402vtable_opt:
2403 // empty
2404 { $$ = nullptr; }
[9380add]2405 | vtable
[1f652a7]2406 ;
2407
2408vtable:
[8f6f3729]2409 VTABLE '(' type_name ')' default_opt
[6cef439]2410 { $$ = build_vtable_type( $3 ); }
[1f652a7]2411 ;
2412
2413default_opt:
2414 // empty
2415 { $$ = nullptr; }
2416 | DEFAULT
2417 { SemanticError( yylloc, "vtable default is currently unimplemented." ); $$ = nullptr; }
[4d51835]2418 ;
[51b73452]2419
2420basic_declaration_specifier:
[4d51835]2421 // A semantic check is necessary for conflicting storage classes.
2422 basic_type_specifier
2423 | declaration_qualifier_list basic_type_specifier
2424 { $$ = $2->addQualifiers( $1 ); }
2425 | basic_declaration_specifier storage_class // remaining OBSOLESCENT (see 2)
2426 { $$ = $1->addQualifiers( $2 ); }
2427 | basic_declaration_specifier storage_class type_qualifier_list
2428 { $$ = $1->addQualifiers( $2 )->addQualifiers( $3 ); }
2429 | basic_declaration_specifier storage_class basic_type_specifier
2430 { $$ = $3->addQualifiers( $2 )->addType( $1 ); }
2431 ;
[51b73452]2432
2433basic_type_specifier:
[84d58c5]2434 direct_type
[f38e7d7]2435 // Cannot have type modifiers, e.g., short, long, etc.
[84d58c5]2436 | type_qualifier_list_opt indirect_type type_qualifier_list_opt
[4d51835]2437 { $$ = $2->addQualifiers( $1 )->addQualifiers( $3 ); }
2438 ;
[51b73452]2439
[84d58c5]2440direct_type:
[4d51835]2441 basic_type_name
2442 | type_qualifier_list basic_type_name
2443 { $$ = $2->addQualifiers( $1 ); }
[84d58c5]2444 | direct_type type_qualifier
[4d51835]2445 { $$ = $1->addQualifiers( $2 ); }
[84d58c5]2446 | direct_type basic_type_name
[4d51835]2447 { $$ = $1->addType( $2 ); }
2448 ;
[51b73452]2449
[84d58c5]2450indirect_type:
[b6ad601]2451 TYPEOF '(' type ')' // GCC: typeof( x ) y;
[4d51835]2452 { $$ = $3; }
[b6ad601]2453 | TYPEOF '(' comma_expression ')' // GCC: typeof( a+b ) y;
[4d51835]2454 { $$ = DeclarationNode::newTypeof( $3 ); }
[b6ad601]2455 | BASETYPEOF '(' type ')' // CFA: basetypeof( x ) y;
[bb7422a]2456 { $$ = DeclarationNode::newTypeof( new ExpressionNode( new ast::TypeExpr( yylloc, maybeMoveBuildType( $3 ) ) ), true ); }
[b6ad601]2457 | BASETYPEOF '(' comma_expression ')' // CFA: basetypeof( a+b ) y;
2458 { $$ = DeclarationNode::newTypeof( $3, true ); }
[f38e7d7]2459 | ZERO_T // CFA
[e048ece]2460 { $$ = DeclarationNode::newFromTypeData( build_builtin_type( TypeData::Zero ) ); }
[f38e7d7]2461 | ONE_T // CFA
[e048ece]2462 { $$ = DeclarationNode::newFromTypeData( build_builtin_type( TypeData::One ) ); }
[4d51835]2463 ;
[51b73452]2464
[d0ffed1]2465sue_declaration_specifier: // struct, union, enum + storage class + type specifier
[4d51835]2466 sue_type_specifier
2467 | declaration_qualifier_list sue_type_specifier
2468 { $$ = $2->addQualifiers( $1 ); }
2469 | sue_declaration_specifier storage_class // remaining OBSOLESCENT (see 2)
2470 { $$ = $1->addQualifiers( $2 ); }
2471 | sue_declaration_specifier storage_class type_qualifier_list
2472 { $$ = $1->addQualifiers( $2 )->addQualifiers( $3 ); }
2473 ;
[51b73452]2474
[d0ffed1]2475sue_type_specifier: // struct, union, enum + type specifier
2476 elaborated_type
[fdca7c6]2477 | type_qualifier_list
2478 { if ( $1->type != nullptr && $1->type->forall ) forall = true; } // remember generic type
2479 elaborated_type
2480 { $$ = $3->addQualifiers( $1 ); }
[4d51835]2481 | sue_type_specifier type_qualifier
[284da8c]2482 {
2483 if ( $2->type != nullptr && $2->type->forall ) forall = true; // remember generic type
2484 $$ = $1->addQualifiers( $2 );
2485 }
[4d51835]2486 ;
[51b73452]2487
[d0ffed1]2488sue_declaration_specifier_nobody: // struct, union, enum - {...} + storage class + type specifier
2489 sue_type_specifier_nobody
2490 | declaration_qualifier_list sue_type_specifier_nobody
2491 { $$ = $2->addQualifiers( $1 ); }
2492 | sue_declaration_specifier_nobody storage_class // remaining OBSOLESCENT (see 2)
2493 { $$ = $1->addQualifiers( $2 ); }
2494 | sue_declaration_specifier_nobody storage_class type_qualifier_list
2495 { $$ = $1->addQualifiers( $2 )->addQualifiers( $3 ); }
2496 ;
2497
2498sue_type_specifier_nobody: // struct, union, enum - {...} + type specifier
2499 elaborated_type_nobody
2500 | type_qualifier_list elaborated_type_nobody
2501 { $$ = $2->addQualifiers( $1 ); }
2502 | sue_type_specifier_nobody type_qualifier
2503 { $$ = $1->addQualifiers( $2 ); }
2504 ;
2505
[84d58c5]2506type_declaration_specifier:
2507 type_type_specifier
2508 | declaration_qualifier_list type_type_specifier
[4d51835]2509 { $$ = $2->addQualifiers( $1 ); }
[84d58c5]2510 | type_declaration_specifier storage_class // remaining OBSOLESCENT (see 2)
[4d51835]2511 { $$ = $1->addQualifiers( $2 ); }
[84d58c5]2512 | type_declaration_specifier storage_class type_qualifier_list
[4d51835]2513 { $$ = $1->addQualifiers( $2 )->addQualifiers( $3 ); }
2514 ;
[b87a5ed]2515
[84d58c5]2516type_type_specifier: // typedef types
2517 type_name
[6cef439]2518 { $$ = DeclarationNode::newFromTypeData( $1 ); }
[84d58c5]2519 | type_qualifier_list type_name
[6cef439]2520 { $$ = DeclarationNode::newFromTypeData( $2 )->addQualifiers( $1 ); }
[84d58c5]2521 | type_type_specifier type_qualifier
2522 { $$ = $1->addQualifiers( $2 ); }
2523 ;
2524
2525type_name:
[4d51835]2526 TYPEDEFname
[6cef439]2527 { $$ = build_typedef( $1 ); }
[84d58c5]2528 | '.' TYPEDEFname
[6cef439]2529 { $$ = build_qualified_type( build_global_scope(), build_typedef( $2 ) ); }
[84d58c5]2530 | type_name '.' TYPEDEFname
[6cef439]2531 { $$ = build_qualified_type( $1, build_typedef( $3 ) ); }
[84d58c5]2532 | typegen_name
2533 | '.' typegen_name
[6cef439]2534 { $$ = build_qualified_type( build_global_scope(), $2 ); }
[84d58c5]2535 | type_name '.' typegen_name
[6cef439]2536 { $$ = build_qualified_type( $1, $3 ); }
[84d58c5]2537 ;
2538
2539typegen_name: // CFA
[65d6de4]2540 TYPEGENname
[6cef439]2541 { $$ = build_type_gen( $1, nullptr ); }
[65d6de4]2542 | TYPEGENname '(' ')'
[6cef439]2543 { $$ = build_type_gen( $1, nullptr ); }
[67cf18c]2544 | TYPEGENname '(' type_list ')'
[6cef439]2545 { $$ = build_type_gen( $1, $3 ); }
[4d51835]2546 ;
[51b73452]2547
[d0ffed1]2548elaborated_type: // struct, union, enum
[c0aa336]2549 aggregate_type
2550 | enum_type
[4d51835]2551 ;
[51b73452]2552
[d0ffed1]2553elaborated_type_nobody: // struct, union, enum - {...}
2554 aggregate_type_nobody
2555 | enum_type_nobody
2556 ;
2557
[7e13b11]2558// ************************** AGGREGATE *******************************
2559
[d0ffed1]2560aggregate_type: // struct, union
[fc20514]2561 aggregate_key attribute_list_opt
2562 { forall = false; } // reset
2563 '{' field_declaration_list_opt '}' type_parameters_opt
[777ed2b]2564 { $$ = DeclarationNode::newAggregate( $1, nullptr, $7, $5, true )->addQualifiers( $2 ); }
[73f04fd]2565 | aggregate_key attribute_list_opt identifier
[fdca7c6]2566 {
[71a422a]2567 typedefTable.makeTypedef( *$3, forall || typedefTable.getEnclForall() ? TYPEGENname : TYPEDEFname, "aggregate_type: 1" );
[fdca7c6]2568 forall = false; // reset
2569 }
[284da8c]2570 '{' field_declaration_list_opt '}' type_parameters_opt
[d8454b9]2571 {
2572 $$ = DeclarationNode::newAggregate( $1, $3, $8, $6, true )->addQualifiers( $2 );
2573 }
[f9c3100]2574 | aggregate_key attribute_list_opt TYPEDEFname // unqualified type name
[407bde5]2575 {
[71a422a]2576 typedefTable.makeTypedef( *$3, forall || typedefTable.getEnclForall() ? TYPEGENname : TYPEDEFname, "aggregate_type: 2" );
[407bde5]2577 forall = false; // reset
2578 }
[284da8c]2579 '{' field_declaration_list_opt '}' type_parameters_opt
[f9c3100]2580 {
[6cef439]2581 DeclarationNode::newFromTypeData( build_typedef( $3 ) );
[f9c3100]2582 $$ = DeclarationNode::newAggregate( $1, $3, $8, $6, true )->addQualifiers( $2 );
2583 }
2584 | aggregate_key attribute_list_opt TYPEGENname // unqualified type name
2585 {
[71a422a]2586 typedefTable.makeTypedef( *$3, forall || typedefTable.getEnclForall() ? TYPEGENname : TYPEDEFname, "aggregate_type: 3" );
[f9c3100]2587 forall = false; // reset
2588 }
2589 '{' field_declaration_list_opt '}' type_parameters_opt
2590 {
[6cef439]2591 DeclarationNode::newFromTypeData( build_type_gen( $3, nullptr ) );
[f9c3100]2592 $$ = DeclarationNode::newAggregate( $1, $3, $8, $6, true )->addQualifiers( $2 );
2593 }
[d0ffed1]2594 | aggregate_type_nobody
2595 ;
2596
[284da8c]2597type_parameters_opt:
2598 // empty
2599 { $$ = nullptr; } %prec '}'
2600 | '(' type_list ')'
2601 { $$ = $2; }
2602 ;
2603
[d0ffed1]2604aggregate_type_nobody: // struct, union - {...}
[73f04fd]2605 aggregate_key attribute_list_opt identifier
[84d58c5]2606 {
[71a422a]2607 typedefTable.makeTypedef( *$3, forall || typedefTable.getEnclForall() ? TYPEGENname : TYPEDEFname, "aggregate_type_nobody" );
[9997fee]2608 forall = false; // reset
[84d58c5]2609 $$ = DeclarationNode::newAggregate( $1, $3, nullptr, nullptr, false )->addQualifiers( $2 );
2610 }
[73f04fd]2611 | aggregate_key attribute_list_opt type_name
[65d6de4]2612 {
[fc20514]2613 forall = false; // reset
[65d6de4]2614 // Create new generic declaration with same name as previous forward declaration, where the IDENTIFIER is
2615 // switched to a TYPEGENname. Link any generic arguments from typegen_name to new generic declaration and
[446740a]2616 // delete newFromTypeGen.
[6cef439]2617 if ( $3->kind == TypeData::SymbolicInst && ! $3->symbolic.isTypedef ) {
2618 $$ = DeclarationNode::newFromTypeData( $3 )->addQualifiers( $2 );
[9fa61f5]2619 } else {
[6cef439]2620 $$ = DeclarationNode::newAggregate( $1, $3->symbolic.name, $3->symbolic.actuals, nullptr, false )->addQualifiers( $2 );
2621 $3->symbolic.name = nullptr; // copied to $$
2622 $3->symbolic.actuals = nullptr;
[9fa61f5]2623 delete $3;
2624 }
[65d6de4]2625 }
[4d51835]2626 ;
[51b73452]2627
2628aggregate_key:
[e307e12]2629 aggregate_data
2630 | aggregate_control
2631 ;
2632
2633aggregate_data:
[1f652a7]2634 STRUCT vtable_opt
[bb7422a]2635 { $$ = ast::AggregateDecl::Struct; }
[c0aa336]2636 | UNION
[bb7422a]2637 { $$ = ast::AggregateDecl::Union; }
[e307e12]2638 | EXCEPTION // CFA
[bb7422a]2639 { $$ = ast::AggregateDecl::Exception; }
[e307e12]2640 ;
2641
2642aggregate_control: // CFA
[cbbd8fd7]2643 MONITOR
[bb7422a]2644 { $$ = ast::AggregateDecl::Monitor; }
[cbbd8fd7]2645 | MUTEX STRUCT
[bb7422a]2646 { $$ = ast::AggregateDecl::Monitor; }
[cbbd8fd7]2647 | GENERATOR
[bb7422a]2648 { $$ = ast::AggregateDecl::Generator; }
[cbbd8fd7]2649 | MUTEX GENERATOR
[bb7422a]2650 {
2651 SemanticError( yylloc, "monitor generator is currently unimplemented." );
2652 $$ = ast::AggregateDecl::NoAggregate;
2653 }
[d3bc0ad]2654 | COROUTINE
[bb7422a]2655 { $$ = ast::AggregateDecl::Coroutine; }
[cbbd8fd7]2656 | MUTEX COROUTINE
[bb7422a]2657 {
2658 SemanticError( yylloc, "monitor coroutine is currently unimplemented." );
2659 $$ = ast::AggregateDecl::NoAggregate;
2660 }
[d3bc0ad]2661 | THREAD
[bb7422a]2662 { $$ = ast::AggregateDecl::Thread; }
[cbbd8fd7]2663 | MUTEX THREAD
[bb7422a]2664 {
2665 SemanticError( yylloc, "monitor thread is currently unimplemented." );
2666 $$ = ast::AggregateDecl::NoAggregate;
2667 }
[4d51835]2668 ;
[51b73452]2669
[7fdb94e1]2670field_declaration_list_opt:
[5d125e4]2671 // empty
[58dd019]2672 { $$ = nullptr; }
[7fdb94e1]2673 | field_declaration_list_opt field_declaration
[dc3fbe5]2674 { $$ = $1 ? $1->set_last( $2 ) : $2; }
[4d51835]2675 ;
[51b73452]2676
2677field_declaration:
[679e644]2678 type_specifier field_declaring_list_opt ';'
[d8454b9]2679 {
2680 // printf( "type_specifier1 %p %s\n", $$, $$->type->aggregate.name ? $$->type->aggregate.name->c_str() : "(nil)" );
2681 $$ = fieldDecl( $1, $2 );
2682 // printf( "type_specifier2 %p %s\n", $$, $$->type->aggregate.name ? $$->type->aggregate.name->c_str() : "(nil)" );
[9fd9d015]2683 // for ( Attribute * attr: reverseIterate( $$->attributes ) ) {
[d8454b9]2684 // printf( "\tattr %s\n", attr->name.c_str() );
2685 // } // for
2686 }
[0442f93f]2687 | type_specifier field_declaring_list_opt '}' // invalid syntax rule
[55266c7]2688 {
[253d0b4]2689 SemanticError( yylloc, "illegal syntax, expecting ';' at end of previous declaration." );
[55266c7]2690 $$ = nullptr;
2691 }
[679e644]2692 | EXTENSION type_specifier field_declaring_list_opt ';' // GCC
[f7e4db27]2693 { $$ = fieldDecl( $2, $3 ); distExt( $$ ); }
[466787a]2694 | STATIC type_specifier field_declaring_list_opt ';' // CFA
[9fd9d015]2695 { SemanticError( yylloc, "STATIC aggregate field qualifier currently unimplemented." ); $$ = nullptr; }
[e07caa2]2696 | INLINE type_specifier field_abstract_list_opt ';' // CFA
[679e644]2697 {
[dea36ee]2698 if ( ! $3 ) { // field declarator ?
2699 $3 = DeclarationNode::newName( nullptr );
2700 } // if
[679a260]2701 $3->inLine = true;
[679e644]2702 $$ = distAttr( $2, $3 ); // mark all fields in list
[e07caa2]2703 distInl( $3 );
[8f91c9ae]2704 }
[e307e12]2705 | INLINE aggregate_control ';' // CFA
[9fd9d015]2706 { SemanticError( yylloc, "INLINE aggregate control currently unimplemented." ); $$ = nullptr; }
[46fa473]2707 | typedef_declaration ';' // CFA
2708 | cfa_field_declaring_list ';' // CFA, new style field declaration
2709 | EXTENSION cfa_field_declaring_list ';' // GCC
2710 { distExt( $2 ); $$ = $2; } // mark all fields in list
[679e644]2711 | INLINE cfa_field_abstract_list ';' // CFA, new style field declaration
2712 { $$ = $2; } // mark all fields in list
[46fa473]2713 | cfa_typedef_declaration ';' // CFA
[b47b827]2714 | static_assert // C11
[4d51835]2715 ;
[b87a5ed]2716
[679e644]2717field_declaring_list_opt:
2718 // empty
2719 { $$ = nullptr; }
[12f1156]2720 | field_declarator
2721 | field_declaring_list_opt ',' attribute_list_opt field_declarator
[dc3fbe5]2722 { $$ = $1->set_last( $4->addQualifiers( $3 ) ); }
[4d51835]2723 ;
[51b73452]2724
[679e644]2725field_declarator:
[e07caa2]2726 bit_subrange_size // C special case, no field name
[4d51835]2727 { $$ = DeclarationNode::newBitfield( $1 ); }
2728 | variable_declarator bit_subrange_size_opt
[679e644]2729 // A semantic check is required to ensure bit_subrange only appears on integral types.
[4d51835]2730 { $$ = $1->addBitfield( $2 ); }
[c6b1105]2731 | variable_type_redeclarator bit_subrange_size_opt
[679e644]2732 // A semantic check is required to ensure bit_subrange only appears on integral types.
[4d51835]2733 { $$ = $1->addBitfield( $2 ); }
[1f771fc]2734 | function_type_redeclarator bit_subrange_size_opt
2735 // A semantic check is required to ensure bit_subrange only appears on integral types.
2736 { $$ = $1->addBitfield( $2 ); }
[679e644]2737 ;
2738
[e07caa2]2739field_abstract_list_opt:
2740 // empty
[dea36ee]2741 { $$ = nullptr; }
[e07caa2]2742 | field_abstract
2743 | field_abstract_list_opt ',' attribute_list_opt field_abstract
[dc3fbe5]2744 { $$ = $1->set_last( $4->addQualifiers( $3 ) ); }
[679e644]2745 ;
2746
[e07caa2]2747field_abstract:
[f7e4db27]2748 // no bit fields
[e07caa2]2749 variable_abstract_declarator
[679e644]2750 ;
2751
2752cfa_field_declaring_list: // CFA, new style field declaration
[f7e4db27]2753 // bit-fields are handled by C declarations
[033ff37]2754 cfa_abstract_declarator_tuple identifier_or_type_name
[679e644]2755 { $$ = $1->addName( $2 ); }
[033ff37]2756 | cfa_field_declaring_list ',' identifier_or_type_name
[dc3fbe5]2757 { $$ = $1->set_last( $1->cloneType( $3 ) ); }
[679e644]2758 ;
2759
2760cfa_field_abstract_list: // CFA, new style field declaration
[f7e4db27]2761 // bit-fields are handled by C declarations
[679e644]2762 cfa_abstract_declarator_tuple
2763 | cfa_field_abstract_list ','
[dc3fbe5]2764 { $$ = $1->set_last( $1->cloneType( 0 ) ); }
[4d51835]2765 ;
[51b73452]2766
2767bit_subrange_size_opt:
[4d51835]2768 // empty
[58dd019]2769 { $$ = nullptr; }
[4d51835]2770 | bit_subrange_size
2771 ;
[51b73452]2772
2773bit_subrange_size:
[c786e1d]2774 ':' assignment_expression
[4d51835]2775 { $$ = $2; }
2776 ;
[51b73452]2777
[7e13b11]2778// ************************** ENUMERATION *******************************
[647e2ea]2779
[9e7236f4]2780enum_type:
[30aab55]2781 // anonymous, no type name
2782 ENUM attribute_list_opt hide_opt '{' enumerator_list comma_opt '}'
2783 {
2784 if ( $3 == EnumHiding::Hide ) {
[253d0b4]2785 SemanticError( yylloc, "illegal syntax, hiding ('!') the enumerator names of an anonymous enumeration means the names are inaccessible." ); $$ = nullptr;
[30aab55]2786 } // if
2787 $$ = DeclarationNode::newEnum( nullptr, $5, true, false )->addQualifiers( $2 );
2788 }
[42422fb]2789 | ENUM enumerator_type attribute_list_opt hide_opt '{' enumerator_list comma_opt '}'
[30aab55]2790 {
[42422fb]2791 if ( $2 && ($2->storageClasses.val != 0 || $2->type->qualifiers.any()) ) {
[253d0b4]2792 SemanticError( yylloc, "illegal syntax, storage-class and CV qualifiers are not meaningful for enumeration constants, which are const." );
[55266c7]2793 }
[42422fb]2794 if ( $4 == EnumHiding::Hide ) {
[253d0b4]2795 SemanticError( yylloc, "illegal syntax, hiding ('!') the enumerator names of an anonymous enumeration means the names are inaccessible." ); $$ = nullptr;
[42422fb]2796 } // if
2797 $$ = DeclarationNode::newEnum( nullptr, $6, true, true, $2 )->addQualifiers( $3 );
[b0d9ff7]2798 }
[30aab55]2799
[42422fb]2800 // named type
[30aab55]2801 | ENUM attribute_list_opt identifier
2802 { typedefTable.makeTypedef( *$3, "enum_type 1" ); }
2803 hide_opt '{' enumerator_list comma_opt '}'
2804 { $$ = DeclarationNode::newEnum( $3, $7, true, false, nullptr, $5 )->addQualifiers( $2 ); }
2805 | ENUM attribute_list_opt typedef_name hide_opt '{' enumerator_list comma_opt '}' // unqualified type name
2806 { $$ = DeclarationNode::newEnum( $3->name, $6, true, false, nullptr, $4 )->addQualifiers( $2 ); }
[42422fb]2807 | ENUM enumerator_type attribute_list_opt identifier attribute_list_opt
[b0d9ff7]2808 {
[42422fb]2809 if ( $2 && ($2->storageClasses.any() || $2->type->qualifiers.val != 0) ) {
[253d0b4]2810 SemanticError( yylloc, "illegal syntax, storage-class and CV qualifiers are not meaningful for enumeration constants, which are const." );
[55266c7]2811 }
[42422fb]2812 typedefTable.makeTypedef( *$4, "enum_type 2" );
[8bea701]2813 }
[c7f12a4]2814 hide_opt '{' enumerator_list comma_opt '}'
[42422fb]2815 { $$ = DeclarationNode::newEnum( $4, $9, true, true, $2, $7 )->addQualifiers( $3 )->addQualifiers( $5 ); }
2816 | ENUM enumerator_type attribute_list_opt typedef_name attribute_list_opt hide_opt '{' enumerator_list comma_opt '}'
2817 { $$ = DeclarationNode::newEnum( $4->name, $8, true, true, $2, $6 )->addQualifiers( $3 )->addQualifiers( $5 ); }
[30aab55]2818
2819 // forward declaration
[d0ffed1]2820 | enum_type_nobody
2821 ;
2822
[42422fb]2823enumerator_type:
2824 '(' ')' // pure enumeration
2825 { $$ = nullptr; }
2826 | '(' cfa_abstract_parameter_declaration ')' // typed enumeration
2827 { $$ = $2; }
2828 ;
2829
[c7f12a4]2830hide_opt:
2831 // empty
[7cf8006]2832 { $$ = EnumHiding::Visible; }
[c7f12a4]2833 | '!'
[7cf8006]2834 { $$ = EnumHiding::Hide; }
[c7f12a4]2835 ;
2836
[d0ffed1]2837enum_type_nobody: // enum - {...}
[f9c3100]2838 ENUM attribute_list_opt identifier
[71a422a]2839 {
2840 typedefTable.makeTypedef( *$3, "enum_type_nobody 1" );
2841 $$ = DeclarationNode::newEnum( $3, nullptr, false, false )->addQualifiers( $2 );
2842 }
[0bd46fd]2843 | ENUM attribute_list_opt type_name
[71a422a]2844 {
[6cef439]2845 typedefTable.makeTypedef( *$3->symbolic.name, "enum_type_nobody 2" );
2846 $$ = DeclarationNode::newEnum( $3->symbolic.name, nullptr, false, false )->addQualifiers( $2 );
[71a422a]2847 }
[4d51835]2848 ;
[51b73452]2849
2850enumerator_list:
[7cf8006]2851 visible_hide_opt identifier_or_type_name enumerator_value_opt
[c7f12a4]2852 { $$ = DeclarationNode::newEnumValueGeneric( $2, $3 ); }
[f9c3100]2853 | INLINE type_name
[d9bad51]2854 {
2855 $$ = DeclarationNode::newEnumInLine( $2->symbolic.name );
2856 $2->symbolic.name = nullptr;
2857 delete $2;
2858 }
[7cf8006]2859 | enumerator_list ',' visible_hide_opt identifier_or_type_name enumerator_value_opt
[dc3fbe5]2860 { $$ = $1->set_last( DeclarationNode::newEnumValueGeneric( $4, $5 ) ); }
[85855b0]2861 | enumerator_list ',' INLINE type_name
2862 { $$ = $1->set_last( DeclarationNode::newEnumInLine( $4->symbolic.name ) ); }
[4d51835]2863 ;
[51b73452]2864
[7cf8006]2865visible_hide_opt:
[c7f12a4]2866 hide_opt
2867 | '^'
[7cf8006]2868 { $$ = EnumHiding::Visible; }
[c7f12a4]2869 ;
2870
[51b73452]2871enumerator_value_opt:
[4d51835]2872 // empty
[58dd019]2873 { $$ = nullptr; }
[7991c7d]2874 | '=' constant_expression { $$ = new InitializerNode( $2 ); }
2875 | '=' '{' initializer_list_opt comma_opt '}' { $$ = new InitializerNode( $3, true ); }
2876 // | simple_assignment_operator initializer
2877 // { $$ = $1 == OperKinds::Assign ? $2 : $2->set_maybeConstructed( false ); }
[4d51835]2878 ;
[51b73452]2879
[7e13b11]2880// ************************** FUNCTION PARAMETERS *******************************
[647e2ea]2881
2882parameter_list_ellipsis_opt:
2883 // empty
2884 { $$ = nullptr; }
2885 | ELLIPSIS
2886 { $$ = nullptr; }
2887 | parameter_list
2888 | parameter_list ',' ELLIPSIS
2889 { $$ = $1->addVarArgs(); }
2890 ;
2891
2892parameter_list: // abstract + real
2893 parameter_declaration
2894 | abstract_parameter_declaration
2895 | parameter_list ',' parameter_declaration
2896 { $$ = $1->set_last( $3 ); }
2897 | parameter_list ',' abstract_parameter_declaration
2898 { $$ = $1->set_last( $3 ); }
2899 ;
2900
2901cfa_parameter_list_ellipsis_opt: // CFA, abstract + real
[4d51835]2902 // empty
[e048ece]2903 { $$ = DeclarationNode::newFromTypeData( build_basic_type( TypeData::Void ) ); }
[2a8427c6]2904 | ELLIPSIS
[58dd019]2905 { $$ = nullptr; }
[c0aa336]2906 | cfa_parameter_list
[647e2ea]2907 | cfa_abstract_parameter_list
2908 | cfa_parameter_list ',' cfa_abstract_parameter_list
2909 { $$ = $1->set_last( $3 ); }
2910 | cfa_parameter_list ',' ELLIPSIS
[4d51835]2911 { $$ = $1->addVarArgs(); }
[647e2ea]2912 | cfa_abstract_parameter_list ',' ELLIPSIS
[4d51835]2913 { $$ = $1->addVarArgs(); }
2914 ;
[b87a5ed]2915
[c0aa336]2916cfa_parameter_list: // CFA
2917 // To obtain LR(1) between cfa_parameter_list and cfa_abstract_tuple, the last cfa_abstract_parameter_list is
2918 // factored out from cfa_parameter_list, flattening the rules to get lookahead to the ']'.
2919 cfa_parameter_declaration
[647e2ea]2920 | cfa_abstract_parameter_list ',' cfa_parameter_declaration
2921 { $$ = $1->set_last( $3 ); }
2922 | cfa_parameter_list ',' cfa_parameter_declaration
2923 { $$ = $1->set_last( $3 ); }
2924 | cfa_parameter_list ',' cfa_abstract_parameter_list ',' cfa_parameter_declaration
2925 { $$ = $1->set_last( $3 )->set_last( $5 ); }
[4d51835]2926 ;
[b87a5ed]2927
[c0aa336]2928cfa_abstract_parameter_list: // CFA, new & old style abstract
2929 cfa_abstract_parameter_declaration
[647e2ea]2930 | cfa_abstract_parameter_list ',' cfa_abstract_parameter_declaration
[dc3fbe5]2931 { $$ = $1->set_last( $3 ); }
[4d51835]2932 ;
[51b73452]2933
[de62360d]2934// Provides optional identifier names (abstract_declarator/variable_declarator), no initialization, different semantics
[2871210]2935// for typedef name by using type_parameter_redeclarator instead of typedef_redeclarator, and function prototypes.
[51b73452]2936
[647e2ea]2937parameter_declaration:
2938 // No SUE declaration in parameter list.
2939 declaration_specifier_nobody identifier_parameter_declarator default_initializer_opt
2940 { $$ = $2->addType( $1 )->addInitializer( $3 ? new InitializerNode( $3 ) : nullptr ); }
2941 | declaration_specifier_nobody type_parameter_redeclarator default_initializer_opt
2942 { $$ = $2->addType( $1 )->addInitializer( $3 ? new InitializerNode( $3 ) : nullptr ); }
2943 ;
2944
2945abstract_parameter_declaration:
2946 declaration_specifier_nobody default_initializer_opt
2947 { $$ = $1->addInitializer( $2 ? new InitializerNode( $2 ) : nullptr ); }
2948 | declaration_specifier_nobody abstract_parameter_declarator default_initializer_opt
2949 { $$ = $2->addType( $1 )->addInitializer( $3 ? new InitializerNode( $3 ) : nullptr ); }
2950 ;
2951
[c0aa336]2952cfa_parameter_declaration: // CFA, new & old style parameter declaration
[4d51835]2953 parameter_declaration
[5a51798]2954 | cfa_identifier_parameter_declarator_no_tuple identifier_or_type_name default_initializer_opt
[4d51835]2955 { $$ = $1->addName( $2 ); }
[5a51798]2956 | cfa_abstract_tuple identifier_or_type_name default_initializer_opt
[c0aa336]2957 // To obtain LR(1), these rules must be duplicated here (see cfa_abstract_declarator).
[4d51835]2958 { $$ = $1->addName( $2 ); }
[5a51798]2959 | type_qualifier_list cfa_abstract_tuple identifier_or_type_name default_initializer_opt
[4d51835]2960 { $$ = $2->addName( $3 )->addQualifiers( $1 ); }
[7e13b11]2961 | cfa_function_specifier // int f( "int fp()" );
[4d51835]2962 ;
[b87a5ed]2963
[c0aa336]2964cfa_abstract_parameter_declaration: // CFA, new & old style parameter declaration
[0ac8d07]2965 abstract_parameter_declaration
[c0aa336]2966 | cfa_identifier_parameter_declarator_no_tuple
2967 | cfa_abstract_tuple
2968 // To obtain LR(1), these rules must be duplicated here (see cfa_abstract_declarator).
2969 | type_qualifier_list cfa_abstract_tuple
[4d51835]2970 { $$ = $2->addQualifiers( $1 ); }
[7e13b11]2971 | cfa_abstract_function // int f( "int ()" );
[4d51835]2972 ;
[51b73452]2973
[c11e31c]2974// ISO/IEC 9899:1999 Section 6.9.1(6) : "An identifier declared as a typedef name shall not be redeclared as a
[de62360d]2975// parameter." Because the scope of the K&R-style parameter-list sees the typedef first, the following is based only on
2976// identifiers. The ANSI-style parameter-list can redefine a typedef name.
[51b73452]2977
[b87a5ed]2978identifier_list: // K&R-style parameter list => no types
[033ff37]2979 identifier
[4d51835]2980 { $$ = DeclarationNode::newName( $1 ); }
[033ff37]2981 | identifier_list ',' identifier
[dc3fbe5]2982 { $$ = $1->set_last( DeclarationNode::newName( $3 ) ); }
[4d51835]2983 ;
[51b73452]2984
[84d58c5]2985type_no_function: // sizeof, alignof, cast (constructor)
[c0aa336]2986 cfa_abstract_declarator_tuple // CFA
[9fa61f5]2987 | type_specifier // cannot be type_specifier_nobody, e.g., (struct S {}){} is a thing
[c0aa336]2988 | type_specifier abstract_declarator
[4d51835]2989 { $$ = $2->addType( $1 ); }
2990 ;
[b87a5ed]2991
[84d58c5]2992type: // typeof, assertion
2993 type_no_function
[c0aa336]2994 | cfa_abstract_function // CFA
[4d51835]2995 ;
[51b73452]2996
2997initializer_opt:
[4d51835]2998 // empty
[58dd019]2999 { $$ = nullptr; }
[f9c3100]3000 | simple_assignment_operator initializer { $$ = $1 == OperKinds::Assign ? $2 : $2->set_maybeConstructed( false ); }
3001 | '=' VOID { $$ = new InitializerNode( true ); }
[63b3279e]3002 | '{' initializer_list_opt comma_opt '}' { $$ = new InitializerNode( $2, true ); }
[4d51835]3003 ;
[51b73452]3004
3005initializer:
[de62360d]3006 assignment_expression { $$ = new InitializerNode( $1 ); }
[7fdb94e1]3007 | '{' initializer_list_opt comma_opt '}' { $$ = new InitializerNode( $2, true ); }
[4d51835]3008 ;
[51b73452]3009
[7fdb94e1]3010initializer_list_opt:
[097e2b0]3011 // empty
[58dd019]3012 { $$ = nullptr; }
[097e2b0]3013 | initializer
[4d51835]3014 | designation initializer { $$ = $2->set_designators( $1 ); }
[b93c544]3015 | initializer_list_opt ',' initializer { $$ = $1->set_last( $3 ); }
3016 | initializer_list_opt ',' designation initializer { $$ = $1->set_last( $4->set_designators( $3 ) ); }
[4d51835]3017 ;
[b87a5ed]3018
[de62360d]3019// There is an unreconcileable parsing problem between C99 and CFA with respect to designators. The problem is use of
3020// '=' to separator the designator from the initializer value, as in:
[c11e31c]3021//
[b87a5ed]3022// int x[10] = { [1] = 3 };
[c11e31c]3023//
[de62360d]3024// The string "[1] = 3" can be parsed as a designator assignment or a tuple assignment. To disambiguate this case, CFA
3025// changes the syntax from "=" to ":" as the separator between the designator and initializer. GCC does uses ":" for
3026// field selection. The optional use of the "=" in GCC, or in this case ":", cannot be supported either due to
3027// shift/reduce conflicts
[51b73452]3028
3029designation:
[4d51835]3030 designator_list ':' // C99, CFA uses ":" instead of "="
[e16eb460]3031 | identifier_at ':' // GCC, field name
[bb7422a]3032 { $$ = new ExpressionNode( build_varref( yylloc, $1 ) ); }
[4d51835]3033 ;
[51b73452]3034
[b87a5ed]3035designator_list: // C99
[4d51835]3036 designator
[2871210]3037 | designator_list designator
[b93c544]3038 { $$ = $1->set_last( $2 ); }
[d1625f8]3039 //| designator_list designator { $$ = new ExpressionNode( $1, $2 ); }
[4d51835]3040 ;
[51b73452]3041
3042designator:
[e16eb460]3043 '.' identifier_at // C99, field name
[bb7422a]3044 { $$ = new ExpressionNode( build_varref( yylloc, $2 ) ); }
[c0a33d2]3045 | '[' push assignment_expression pop ']' // C99, single array element
[de62360d]3046 // assignment_expression used instead of constant_expression because of shift/reduce conflicts with tuple.
[d1625f8]3047 { $$ = $3; }
[c0a33d2]3048 | '[' push subrange pop ']' // CFA, multiple array elements
3049 { $$ = $3; }
3050 | '[' push constant_expression ELLIPSIS constant_expression pop ']' // GCC, multiple array elements
[bb7422a]3051 { $$ = new ExpressionNode( new ast::RangeExpr( yylloc, maybeMoveBuild( $3 ), maybeMoveBuild( $5 ) ) ); }
[679e644]3052 | '.' '[' push field_name_list pop ']' // CFA, tuple field selector
[c0a33d2]3053 { $$ = $4; }
[4d51835]3054 ;
[51b73452]3055
[de62360d]3056// The CFA type system is based on parametric polymorphism, the ability to declare functions with type parameters,
3057// rather than an object-oriented type system. This required four groups of extensions:
[c11e31c]3058//
3059// Overloading: function, data, and operator identifiers may be overloaded.
3060//
[3ca7ef3]3061// Type declarations: "otype" is used to generate new types for declaring objects. Similarly, "dtype" is used for object
[de62360d]3062// and incomplete types, and "ftype" is used for function types. Type declarations with initializers provide
3063// definitions of new types. Type declarations with storage class "extern" provide opaque types.
[c11e31c]3064//
[de62360d]3065// Polymorphic functions: A forall clause declares a type parameter. The corresponding argument is inferred at the call
3066// site. A polymorphic function is not a template; it is a function, with an address and a type.
[c11e31c]3067//
3068// Specifications and Assertions: Specifications are collections of declarations parameterized by one or more
[de62360d]3069// types. They serve many of the purposes of abstract classes, and specification hierarchies resemble subclass
3070// hierarchies. Unlike classes, they can define relationships between types. Assertions declare that a type or
3071// types provide the operations declared by a specification. Assertions are normally used to declare requirements
3072// on type arguments of polymorphic functions.
[c11e31c]3073
[b87a5ed]3074type_parameter_list: // CFA
[67cf18c]3075 type_parameter
3076 | type_parameter_list ',' type_parameter
[dc3fbe5]3077 { $$ = $1->set_last( $3 ); }
[4d51835]3078 ;
[b87a5ed]3079
[84d58c5]3080type_initializer_opt: // CFA
3081 // empty
3082 { $$ = nullptr; }
3083 | '=' type
3084 { $$ = $2; }
3085 ;
3086
[b87a5ed]3087type_parameter: // CFA
[033ff37]3088 type_class identifier_or_type_name
[408ab79]3089 {
[71a422a]3090 typedefTable.addToScope( *$2, TYPEDEFname, "type_parameter 1" );
[bb7422a]3091 if ( $1 == ast::TypeDecl::Otype ) { SemanticError( yylloc, "otype keyword is deprecated, use T " ); }
3092 if ( $1 == ast::TypeDecl::Dtype ) { SemanticError( yylloc, "dtype keyword is deprecated, use T &" ); }
3093 if ( $1 == ast::TypeDecl::Ttype ) { SemanticError( yylloc, "ttype keyword is deprecated, use T ..." ); }
[fd54fef]3094 }
[5a51798]3095 type_initializer_opt assertion_list_opt
[67cf18c]3096 { $$ = DeclarationNode::newTypeParam( $1, $2 )->addTypeInitializer( $4 )->addAssertions( $5 ); }
[5a51798]3097 | identifier_or_type_name new_type_class
[71a422a]3098 { typedefTable.addToScope( *$1, TYPEDEFname, "type_parameter 2" ); }
[5a51798]3099 type_initializer_opt assertion_list_opt
3100 { $$ = DeclarationNode::newTypeParam( $2, $1 )->addTypeInitializer( $4 )->addAssertions( $5 ); }
3101 | '[' identifier_or_type_name ']'
[b66d14a]3102 {
[71a422a]3103 typedefTable.addToScope( *$2, TYPEDIMname, "type_parameter 3" );
[bb7422a]3104 $$ = DeclarationNode::newTypeParam( ast::TypeDecl::Dimension, $2 );
[b66d14a]3105 }
[5a51798]3106 // | type_specifier identifier_parameter_declarator
[9997fee]3107 | assertion_list
[bb7422a]3108 { $$ = DeclarationNode::newTypeParam( ast::TypeDecl::Dtype, new string( DeclarationNode::anonymous.newName() ) )->addAssertions( $1 ); }
[0522ebe]3109 | ENUM '(' identifier_or_type_name ')' identifier_or_type_name new_type_class type_initializer_opt assertion_list_opt
3110 {
3111 typedefTable.addToScope( *$3, TYPEDIMname, "type_parameter 4" );
3112 typedefTable.addToScope( *$5, TYPEDIMname, "type_parameter 5" );
3113 $$ = DeclarationNode::newTypeParam( $6, $5 )->addTypeInitializer( $7 )->addAssertions( $8 );
3114 }
[4d51835]3115 ;
[b87a5ed]3116
[5a51798]3117new_type_class: // CFA
3118 // empty
[bb7422a]3119 { $$ = ast::TypeDecl::Otype; }
[5a51798]3120 | '&'
[bb7422a]3121 { $$ = ast::TypeDecl::Dtype; }
[5a51798]3122 | '*'
[7e13b11]3123 { $$ = ast::TypeDecl::DStype; } // Dtype + sized
3124 // | '(' '*' ')' // Gregor made me do it
3125 // { $$ = ast::TypeDecl::Ftype; }
[5a51798]3126 | ELLIPSIS
[bb7422a]3127 { $$ = ast::TypeDecl::Ttype; }
[5a51798]3128 ;
3129
[b87a5ed]3130type_class: // CFA
[4040425]3131 OTYPE
[bb7422a]3132 { $$ = ast::TypeDecl::Otype; }
[4d51835]3133 | DTYPE
[bb7422a]3134 { $$ = ast::TypeDecl::Dtype; }
[8f60f0b]3135 | FTYPE
[bb7422a]3136 { $$ = ast::TypeDecl::Ftype; }
[8f60f0b]3137 | TTYPE
[bb7422a]3138 { $$ = ast::TypeDecl::Ttype; }
[4d51835]3139 ;
[b87a5ed]3140
3141assertion_list_opt: // CFA
[4d51835]3142 // empty
[58dd019]3143 { $$ = nullptr; }
[9997fee]3144 | assertion_list
3145 ;
3146
3147assertion_list: // CFA
3148 assertion
3149 | assertion_list assertion
[dc3fbe5]3150 { $$ = $1->set_last( $2 ); }
[4d51835]3151 ;
[b87a5ed]3152
3153assertion: // CFA
[033ff37]3154 '|' identifier_or_type_name '(' type_list ')'
[7fdb94e1]3155 { $$ = DeclarationNode::newTraitUse( $2, $4 ); }
[13e8427]3156 | '|' '{' push trait_declaration_list pop '}'
[4d51835]3157 { $$ = $4; }
[35718a9]3158 // | '|' '(' push type_parameter_list pop ')' '{' push trait_declaration_list pop '}' '(' type_list ')'
3159 // { SemanticError( yylloc, "Generic data-type assertion is currently unimplemented." ); $$ = nullptr; }
[4d51835]3160 ;
[b87a5ed]3161
[84d58c5]3162type_list: // CFA
3163 type
[bb7422a]3164 { $$ = new ExpressionNode( new ast::TypeExpr( yylloc, maybeMoveBuildType( $1 ) ) ); }
[4d51835]3165 | assignment_expression
[84d58c5]3166 | type_list ',' type
[b93c544]3167 { $$ = $1->set_last( new ExpressionNode( new ast::TypeExpr( yylloc, maybeMoveBuildType( $3 ) ) ) ); }
[84d58c5]3168 | type_list ',' assignment_expression
[b93c544]3169 { $$ = $1->set_last( $3 ); }
[4d51835]3170 ;
[b87a5ed]3171
3172type_declaring_list: // CFA
[4040425]3173 OTYPE type_declarator
[4d51835]3174 { $$ = $2; }
[4040425]3175 | storage_class_list OTYPE type_declarator
[4d51835]3176 { $$ = $3->addQualifiers( $1 ); }
3177 | type_declaring_list ',' type_declarator
[dc3fbe5]3178 { $$ = $1->set_last( $3->copySpecifiers( $1 ) ); }
[4d51835]3179 ;
[b87a5ed]3180
3181type_declarator: // CFA
[4d51835]3182 type_declarator_name assertion_list_opt
3183 { $$ = $1->addAssertions( $2 ); }
[84d58c5]3184 | type_declarator_name assertion_list_opt '=' type
[4d51835]3185 { $$ = $1->addAssertions( $2 )->addType( $4 ); }
3186 ;
[b87a5ed]3187
3188type_declarator_name: // CFA
[033ff37]3189 identifier_or_type_name
[4d51835]3190 {
[71a422a]3191 typedefTable.addToEnclosingScope( *$1, TYPEDEFname, "type_declarator_name 1" );
[a5f9444]3192 $$ = DeclarationNode::newTypeDecl( $1, nullptr );
[4d51835]3193 }
[033ff37]3194 | identifier_or_type_name '(' type_parameter_list ')'
[4d51835]3195 {
[71a422a]3196 typedefTable.addToEnclosingScope( *$1, TYPEGENname, "type_declarator_name 2" );
[35718a9]3197 $$ = DeclarationNode::newTypeDecl( $1, $3 );
[4d51835]3198 }
3199 ;
[b87a5ed]3200
[4040425]3201trait_specifier: // CFA
[033ff37]3202 TRAIT identifier_or_type_name '(' type_parameter_list ')' '{' '}'
[8a97248]3203 {
[3d937e2]3204 SemanticWarning( yylloc, Warning::DeprecTraitSyntax );
[8a97248]3205 $$ = DeclarationNode::newTrait( $2, $4, nullptr );
3206 }
3207 | forall TRAIT identifier_or_type_name '{' '}' // alternate
[7a24d76]3208 { $$ = DeclarationNode::newTrait( $3, $1, nullptr ); }
[033ff37]3209 | TRAIT identifier_or_type_name '(' type_parameter_list ')' '{' push trait_declaration_list pop '}'
[8a97248]3210 {
[3d937e2]3211 SemanticWarning( yylloc, Warning::DeprecTraitSyntax );
[8a97248]3212 $$ = DeclarationNode::newTrait( $2, $4, $8 );
3213 }
[7a24d76]3214 | forall TRAIT identifier_or_type_name '{' push trait_declaration_list pop '}' // alternate
3215 { $$ = DeclarationNode::newTrait( $3, $1, $6 ); }
[4d51835]3216 ;
[b87a5ed]3217
[84d58c5]3218trait_declaration_list: // CFA
[4040425]3219 trait_declaration
[13e8427]3220 | trait_declaration_list pop push trait_declaration
[dc3fbe5]3221 { $$ = $1->set_last( $4 ); }
[4d51835]3222 ;
[b87a5ed]3223
[84d58c5]3224trait_declaration: // CFA
[13e8427]3225 cfa_trait_declaring_list ';'
3226 | trait_declaring_list ';'
[4d51835]3227 ;
[b87a5ed]3228
[c0aa336]3229cfa_trait_declaring_list: // CFA
3230 cfa_variable_specifier
3231 | cfa_function_specifier
3232 | cfa_trait_declaring_list pop ',' push identifier_or_type_name
[dc3fbe5]3233 { $$ = $1->set_last( $1->cloneType( $5 ) ); }
[4d51835]3234 ;
[b87a5ed]3235
[4040425]3236trait_declaring_list: // CFA
[4d51835]3237 type_specifier declarator
[7fdb94e1]3238 { $$ = $2->addType( $1 ); }
[4040425]3239 | trait_declaring_list pop ',' push declarator
[dc3fbe5]3240 { $$ = $1->set_last( $1->cloneBaseType( $5 ) ); }
[4d51835]3241 ;
[51b73452]3242
[e1d66c84]3243// **************************** EXTERNAL DEFINITIONS *****************************
[51b73452]3244
3245translation_unit:
[3d56d15b]3246 // empty, input file
[4d51835]3247 | external_definition_list
[12f1156]3248 { parseTree = parseTree ? parseTree->set_last( $1 ) : $1; }
[4d51835]3249 ;
[51b73452]3250
3251external_definition_list:
[35718a9]3252 push external_definition pop
3253 { $$ = $2; }
[fc20514]3254 | external_definition_list push external_definition pop
[dc3fbe5]3255 { $$ = $1 ? $1->set_last( $3 ) : $3; }
[4d51835]3256 ;
[51b73452]3257
3258external_definition_list_opt:
[4d51835]3259 // empty
[58dd019]3260 { $$ = nullptr; }
[3d56d15b]3261 | external_definition_list
3262 ;
3263
3264up:
[fc20514]3265 { typedefTable.up( forall ); forall = false; }
[3d56d15b]3266 ;
3267
3268down:
3269 { typedefTable.down(); }
[4d51835]3270 ;
[51b73452]3271
3272external_definition:
[2d019af]3273 DIRECTIVE
[bb7422a]3274 { $$ = DeclarationNode::newDirectiveStmt( new StatementNode( build_directive( yylloc, $1 ) ) ); }
[2d019af]3275 | declaration
[1a73dbb]3276 {
3277 // Variable declarations of anonymous types requires creating a unique type-name across multiple translation
3278 // unit, which is a dubious task, especially because C uses name rather than structural typing; hence it is
3279 // disallowed at the moment.
[4eb3a7c5]3280 if ( $1->linkage == ast::Linkage::Cforall && ! $1->storageClasses.is_static &&
3281 $1->type && $1->type->kind == TypeData::AggregateInst ) {
[67467a3]3282 if ( $1->type->aggInst.aggregate->aggregate.anon ) {
3283 SemanticError( yylloc, "extern anonymous aggregate is currently unimplemented." ); $$ = nullptr;
[1a73dbb]3284 }
3285 }
3286 }
[996c8ed]3287 | IDENTIFIER IDENTIFIER
3288 { IdentifierBeforeIdentifier( *$1.str, *$2.str, " declaration" ); $$ = nullptr; }
[65ef0cd]3289 | IDENTIFIER type_qualifier // invalid syntax rule
[996c8ed]3290 { IdentifierBeforeType( *$1.str, "type qualifier" ); $$ = nullptr; }
[65ef0cd]3291 | IDENTIFIER storage_class // invalid syntax rule
[996c8ed]3292 { IdentifierBeforeType( *$1.str, "storage class" ); $$ = nullptr; }
[65ef0cd]3293 | IDENTIFIER basic_type_name // invalid syntax rule
[996c8ed]3294 { IdentifierBeforeType( *$1.str, "type" ); $$ = nullptr; }
[65ef0cd]3295 | IDENTIFIER TYPEDEFname // invalid syntax rule
[996c8ed]3296 { IdentifierBeforeType( *$1.str, "type" ); $$ = nullptr; }
[65ef0cd]3297 | IDENTIFIER TYPEGENname // invalid syntax rule
[996c8ed]3298 { IdentifierBeforeType( *$1.str, "type" ); $$ = nullptr; }
[4d51835]3299 | external_function_definition
[ecae5860]3300 | EXTENSION external_definition // GCC, multiple __extension__ allowed, meaning unknown
3301 {
3302 distExt( $2 ); // mark all fields in list
3303 $$ = $2;
3304 }
[e994912]3305 | ASM '(' string_literal ')' ';' // GCC, global assembler statement
[bb7422a]3306 { $$ = DeclarationNode::newAsmStmt( new StatementNode( build_asm( yylloc, false, $3, nullptr ) ) ); }
[aac37fa]3307 | EXTERN STRINGliteral
3308 {
3309 linkageStack.push( linkage ); // handle nested extern "C"/"Cforall"
[bb7422a]3310 linkage = ast::Linkage::update( yylloc, linkage, $2 );
[aac37fa]3311 }
[ae2f2ae]3312 up external_definition down
[aac37fa]3313 {
3314 linkage = linkageStack.top();
3315 linkageStack.pop();
3316 $$ = $5;
3317 }
[c0aa336]3318 | EXTERN STRINGliteral // C++-style linkage specifier
[4d51835]3319 {
[3b8e52c]3320 linkageStack.push( linkage ); // handle nested extern "C"/"Cforall"
[bb7422a]3321 linkage = ast::Linkage::update( yylloc, linkage, $2 );
[4d51835]3322 }
[3d56d15b]3323 '{' up external_definition_list_opt down '}'
[4d51835]3324 {
3325 linkage = linkageStack.top();
3326 linkageStack.pop();
[3d56d15b]3327 $$ = $6;
[8e9cbb2]3328 }
[7e13b11]3329 // global distribution
[9997fee]3330 | type_qualifier_list
3331 {
[55266c7]3332 if ( $1->type->qualifiers.any() ) {
[253d0b4]3333 SemanticError( yylloc, "illegal syntax, CV qualifiers cannot be distributed; only storage-class and forall qualifiers." );
[55266c7]3334 }
[fc20514]3335 if ( $1->type->forall ) forall = true; // remember generic type
[3d56d15b]3336 }
3337 '{' up external_definition_list_opt down '}' // CFA, namespace
3338 {
[4c3ee8d]3339 distQual( $5, $1 );
[9fd9d015]3340 forall = false;
[3d56d15b]3341 $$ = $5;
[9997fee]3342 }
3343 | declaration_qualifier_list
3344 {
[55266c7]3345 if ( $1->type && $1->type->qualifiers.any() ) {
[253d0b4]3346 SemanticError( yylloc, "illegal syntax, CV qualifiers cannot be distributed; only storage-class and forall qualifiers." );
[55266c7]3347 }
[fc20514]3348 if ( $1->type && $1->type->forall ) forall = true; // remember generic type
[3d56d15b]3349 }
3350 '{' up external_definition_list_opt down '}' // CFA, namespace
3351 {
[4c3ee8d]3352 distQual( $5, $1 );
[9fd9d015]3353 forall = false;
[3d56d15b]3354 $$ = $5;
[9997fee]3355 }
3356 | declaration_qualifier_list type_qualifier_list
3357 {
[55266c7]3358 if ( ($1->type && $1->type->qualifiers.any()) || ($2->type && $2->type->qualifiers.any()) ) {
[253d0b4]3359 SemanticError( yylloc, "illegal syntax, CV qualifiers cannot be distributed; only storage-class and forall qualifiers." );
[55266c7]3360 }
[b2ddaf3]3361 if ( ($1->type && $1->type->forall) || ($2->type && $2->type->forall) ) forall = true; // remember generic type
[9997fee]3362 }
[3d56d15b]3363 '{' up external_definition_list_opt down '}' // CFA, namespace
[9997fee]3364 {
[284da8c]3365 distQual( $6, $1->addQualifiers( $2 ) );
[9fd9d015]3366 forall = false;
[3d56d15b]3367 $$ = $6;
[9997fee]3368 }
[4d51835]3369 ;
3370
3371external_function_definition:
3372 function_definition
[de62360d]3373 // These rules are a concession to the "implicit int" type_specifier because there is a significant amount of
[c6b1105]3374 // legacy code with global functions missing the type-specifier for the return type, and assuming "int".
3375 // Parsing is possible because function_definition does not appear in the context of an expression (nested
3376 // functions preclude this concession, i.e., all nested function must have a return type). A function prototype
3377 // declaration must still have a type_specifier. OBSOLESCENT (see 1)
[4d51835]3378 | function_declarator compound_statement
[c0a33d2]3379 { $$ = $1->addFunctionBody( $2 ); }
[35718a9]3380 | KR_function_declarator KR_parameter_list_opt compound_statement
[c0a33d2]3381 { $$ = $1->addOldDeclList( $2 )->addFunctionBody( $3 ); }
[4d51835]3382 ;
[51b73452]3383
[8b47e50]3384with_clause_opt:
3385 // empty
[9997fee]3386 { $$ = nullptr; forall = false; }
[e78966e]3387 | WITH '(' type_list ')' attribute_list_opt // support scoped enumeration
[d8454b9]3388 {
3389 $$ = $3; forall = false;
3390 if ( $5 ) {
[253d0b4]3391 SemanticError( yylloc, "illegal syntax, attributes cannot be associated with function body. Move attribute(s) before \"with\" clause." );
[d8454b9]3392 $$ = nullptr;
3393 } // if
3394 }
[8b47e50]3395 ;
3396
[51b73452]3397function_definition:
[8b47e50]3398 cfa_function_declaration with_clause_opt compound_statement // CFA
[4d51835]3399 {
[481115f]3400 // Add the function body to the last identifier in the function definition list, i.e., foo3:
3401 // [const double] foo1(), foo2( int ), foo3( double ) { return 3.0; }
[5fcba14]3402 $1->get_last()->addFunctionBody( $3, $2 );
[481115f]3403 $$ = $1;
[4d51835]3404 }
[8b47e50]3405 | declaration_specifier function_declarator with_clause_opt compound_statement
[4d51835]3406 {
[c38ae92]3407 rebindForall( $1, $2 );
[7fdb94e1]3408 $$ = $2->addFunctionBody( $4, $3 )->addType( $1 );
3409 }
[1f771fc]3410 | declaration_specifier function_type_redeclarator with_clause_opt compound_statement
[7fdb94e1]3411 {
3412 rebindForall( $1, $2 );
[5fcba14]3413 $$ = $2->addFunctionBody( $4, $3 )->addType( $1 );
[4d51835]3414 }
[a16a7ec]3415 // handles default int return type, OBSOLESCENT (see 1)
[8b47e50]3416 | type_qualifier_list function_declarator with_clause_opt compound_statement
[c0a33d2]3417 { $$ = $2->addFunctionBody( $4, $3 )->addQualifiers( $1 ); }
[a16a7ec]3418 // handles default int return type, OBSOLESCENT (see 1)
[8b47e50]3419 | declaration_qualifier_list function_declarator with_clause_opt compound_statement
[c0a33d2]3420 { $$ = $2->addFunctionBody( $4, $3 )->addQualifiers( $1 ); }
[a16a7ec]3421 // handles default int return type, OBSOLESCENT (see 1)
[8b47e50]3422 | declaration_qualifier_list type_qualifier_list function_declarator with_clause_opt compound_statement
[c0a33d2]3423 { $$ = $3->addFunctionBody( $5, $4 )->addQualifiers( $2 )->addQualifiers( $1 ); }
[4d51835]3424
3425 // Old-style K&R function definition, OBSOLESCENT (see 4)
[35718a9]3426 | declaration_specifier KR_function_declarator KR_parameter_list_opt with_clause_opt compound_statement
[4d51835]3427 {
[c38ae92]3428 rebindForall( $1, $2 );
[5fcba14]3429 $$ = $2->addOldDeclList( $3 )->addFunctionBody( $5, $4 )->addType( $1 );
[4d51835]3430 }
[a16a7ec]3431 // handles default int return type, OBSOLESCENT (see 1)
[35718a9]3432 | type_qualifier_list KR_function_declarator KR_parameter_list_opt with_clause_opt compound_statement
[c0a33d2]3433 { $$ = $2->addOldDeclList( $3 )->addFunctionBody( $5, $4 )->addQualifiers( $1 ); }
[a16a7ec]3434 // handles default int return type, OBSOLESCENT (see 1)
[35718a9]3435 | declaration_qualifier_list KR_function_declarator KR_parameter_list_opt with_clause_opt compound_statement
[c0a33d2]3436 { $$ = $2->addOldDeclList( $3 )->addFunctionBody( $5, $4 )->addQualifiers( $1 ); }
[a16a7ec]3437 // handles default int return type, OBSOLESCENT (see 1)
[35718a9]3438 | declaration_qualifier_list type_qualifier_list KR_function_declarator KR_parameter_list_opt with_clause_opt compound_statement
[c0a33d2]3439 { $$ = $3->addOldDeclList( $4 )->addFunctionBody( $6, $5 )->addQualifiers( $2 )->addQualifiers( $1 ); }
[4d51835]3440 ;
[51b73452]3441
3442declarator:
[4d51835]3443 variable_declarator
[c6b1105]3444 | variable_type_redeclarator
[4d51835]3445 | function_declarator
[1f771fc]3446 | function_type_redeclarator
[4d51835]3447 ;
[51b73452]3448
3449subrange:
[4d51835]3450 constant_expression '~' constant_expression // CFA, integer subrange
[bb7422a]3451 { $$ = new ExpressionNode( new ast::RangeExpr( yylloc, maybeMoveBuild( $1 ), maybeMoveBuild( $3 ) ) ); }
[4d51835]3452 ;
[b87a5ed]3453
[7e13b11]3454// **************************** ASM *****************************
3455
[b87a5ed]3456asm_name_opt: // GCC
[4d51835]3457 // empty
[58dd019]3458 { $$ = nullptr; }
3459 | ASM '(' string_literal ')' attribute_list_opt
[c0aa336]3460 {
3461 DeclarationNode * name = new DeclarationNode();
[32d6fdc]3462 name->asmName = maybeMoveBuild( $3 );
[c0aa336]3463 $$ = name->addQualifiers( $5 );
3464 }
[4d51835]3465 ;
[b87a5ed]3466
[7e13b11]3467// **************************** ATTRIBUTE *****************************
3468
[b87a5ed]3469attribute_list_opt: // GCC
[4d51835]3470 // empty
[58dd019]3471 { $$ = nullptr; }
[4d51835]3472 | attribute_list
3473 ;
[b87a5ed]3474
3475attribute_list: // GCC
[4d51835]3476 attribute
3477 | attribute_list attribute
[1db21619]3478 { $$ = $2->addQualifiers( $1 ); }
[4d51835]3479 ;
[b87a5ed]3480
3481attribute: // GCC
[44a81853]3482 ATTRIBUTE '(' '(' attribute_name_list ')' ')'
3483 { $$ = $4; }
[647e2ea]3484 | ATTRIBUTE '(' attribute_name_list ')' // CFA
3485 { $$ = $3; }
3486 | ATTR '(' attribute_name_list ')' // CFA
3487 { $$ = $3; }
[4d51835]3488 ;
[b87a5ed]3489
[44a81853]3490attribute_name_list: // GCC
3491 attribute_name
3492 | attribute_name_list ',' attribute_name
[c0aa336]3493 { $$ = $3->addQualifiers( $1 ); }
[4d51835]3494 ;
[b87a5ed]3495
[44a81853]3496attribute_name: // GCC
[4d51835]3497 // empty
[44a81853]3498 { $$ = nullptr; }
3499 | attr_name
3500 { $$ = DeclarationNode::newAttribute( $1 ); }
[cbbd8fd7]3501 | attr_name '(' argument_expression_list_opt ')'
[44a81853]3502 { $$ = DeclarationNode::newAttribute( $1, $3 ); }
[4d51835]3503 ;
[b87a5ed]3504
[44a81853]3505attr_name: // GCC
[12f1156]3506 identifier_or_type_name
[114014c]3507 | FALLTHROUGH
3508 { $$ = Token{ new string( "fallthrough" ), { nullptr, -1 } }; }
[44a81853]3509 | CONST
[9ff56e7]3510 { $$ = Token{ new string( "__const__" ), { nullptr, -1 } }; }
[4d51835]3511 ;
[51b73452]3512
[c11e31c]3513// ============================================================================
[de62360d]3514// The following sections are a series of grammar patterns used to parse declarators. Multiple patterns are necessary
3515// because the type of an identifier in wrapped around the identifier in the same form as its usage in an expression, as
3516// in:
[c11e31c]3517//
[b87a5ed]3518// int (*f())[10] { ... };
3519// ... (*f())[3] += 1; // definition mimics usage
[c11e31c]3520//
[de62360d]3521// Because these patterns are highly recursive, changes at a lower level in the recursion require copying some or all of
3522// the pattern. Each of these patterns has some subtle variation to ensure correct syntax in a particular context.
[c11e31c]3523// ============================================================================
3524
3525// ----------------------------------------------------------------------------
[de62360d]3526// The set of valid declarators before a compound statement for defining a function is less than the set of declarators
3527// to define a variable or function prototype, e.g.:
[c11e31c]3528//
[b87a5ed]3529// valid declaration invalid definition
3530// ----------------- ------------------
[4d51835]3531// int f; int f {}
3532// int *f; int *f {}
[b87a5ed]3533// int f[10]; int f[10] {}
[4d51835]3534// int (*f)(int); int (*f)(int) {}
[c11e31c]3535//
[de62360d]3536// To preclude this syntactic anomaly requires separating the grammar rules for variable and function declarators, hence
3537// variable_declarator and function_declarator.
[c11e31c]3538// ----------------------------------------------------------------------------
3539
[de62360d]3540// This pattern parses a declaration of a variable that is not redefining a typedef name. The pattern precludes
3541// declaring an array of functions versus a pointer to an array of functions.
[51b73452]3542
[5e25953]3543paren_identifier:
[e16eb460]3544 identifier_at
[5e25953]3545 { $$ = DeclarationNode::newName( $1 ); }
3546 | '(' paren_identifier ')' // redundant parenthesis
3547 { $$ = $2; }
3548 ;
3549
[51b73452]3550variable_declarator:
[4d51835]3551 paren_identifier attribute_list_opt
[1db21619]3552 { $$ = $1->addQualifiers( $2 ); }
[4d51835]3553 | variable_ptr
3554 | variable_array attribute_list_opt
[1db21619]3555 { $$ = $1->addQualifiers( $2 ); }
[4d51835]3556 | variable_function attribute_list_opt
[1db21619]3557 { $$ = $1->addQualifiers( $2 ); }
[4d51835]3558 ;
[51b73452]3559
3560variable_ptr:
[dd51906]3561 ptrref_operator variable_declarator
[a5f9444]3562 { $$ = $2->addPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[dd51906]3563 | ptrref_operator type_qualifier_list variable_declarator
[ce8c12f]3564 { $$ = $3->addPointer( DeclarationNode::newPointer( $2, $1 ) ); }
[5e25953]3565 | '(' variable_ptr ')' attribute_list_opt // redundant parenthesis
3566 { $$ = $2->addQualifiers( $4 ); }
3567 | '(' attribute_list variable_ptr ')' attribute_list_opt // redundant parenthesis
3568 { $$ = $3->addQualifiers( $2 )->addQualifiers( $5 ); }
[4d51835]3569 ;
[51b73452]3570
3571variable_array:
[4d51835]3572 paren_identifier array_dimension
3573 { $$ = $1->addArray( $2 ); }
3574 | '(' variable_ptr ')' array_dimension
3575 { $$ = $2->addArray( $4 ); }
[5e25953]3576 | '(' attribute_list variable_ptr ')' array_dimension
3577 { $$ = $3->addQualifiers( $2 )->addArray( $5 ); }
[9fd9d015]3578 | '(' variable_array ')' multi_array_dimension // redundant parenthesis
[4d51835]3579 { $$ = $2->addArray( $4 ); }
[5e25953]3580 | '(' attribute_list variable_array ')' multi_array_dimension // redundant parenthesis
3581 { $$ = $3->addQualifiers( $2 )->addArray( $5 ); }
[4d51835]3582 | '(' variable_array ')' // redundant parenthesis
3583 { $$ = $2; }
[5e25953]3584 | '(' attribute_list variable_array ')' // redundant parenthesis
3585 { $$ = $3->addQualifiers( $2 ); }
[4d51835]3586 ;
[51b73452]3587
3588variable_function:
[647e2ea]3589 '(' variable_ptr ')' '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]3590 { $$ = $2->addParamList( $5 ); }
[647e2ea]3591 | '(' attribute_list variable_ptr ')' '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]3592 { $$ = $3->addQualifiers( $2 )->addParamList( $6 ); }
[4d51835]3593 | '(' variable_function ')' // redundant parenthesis
3594 { $$ = $2; }
[5e25953]3595 | '(' attribute_list variable_function ')' // redundant parenthesis
3596 { $$ = $3->addQualifiers( $2 ); }
[4d51835]3597 ;
[51b73452]3598
[c6b1105]3599// This pattern parses a function declarator that is not redefining a typedef name. For non-nested functions, there is
3600// no context where a function definition can redefine a typedef name, i.e., the typedef and function name cannot exist
3601// is the same scope. The pattern precludes returning arrays and functions versus pointers to arrays and functions.
[51b73452]3602
3603function_declarator:
[4d51835]3604 function_no_ptr attribute_list_opt
[1db21619]3605 { $$ = $1->addQualifiers( $2 ); }
[4d51835]3606 | function_ptr
3607 | function_array attribute_list_opt
[1db21619]3608 { $$ = $1->addQualifiers( $2 ); }
[4d51835]3609 ;
[51b73452]3610
3611function_no_ptr:
[647e2ea]3612 paren_identifier '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]3613 { $$ = $1->addParamList( $3 ); }
[647e2ea]3614 | '(' function_ptr ')' '(' parameter_list_ellipsis_opt ')'
[71a422a]3615 { $$ = $2->addParamList( $5 ); }
[647e2ea]3616 | '(' attribute_list function_ptr ')' '(' parameter_list_ellipsis_opt ')'
[71a422a]3617 { $$ = $3->addQualifiers( $2 )->addParamList( $6 ); }
[4d51835]3618 | '(' function_no_ptr ')' // redundant parenthesis
3619 { $$ = $2; }
[5e25953]3620 | '(' attribute_list function_no_ptr ')' // redundant parenthesis
3621 { $$ = $3->addQualifiers( $2 ); }
[4d51835]3622 ;
[51b73452]3623
3624function_ptr:
[dd51906]3625 ptrref_operator function_declarator
[a5f9444]3626 { $$ = $2->addPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[dd51906]3627 | ptrref_operator type_qualifier_list function_declarator
[ce8c12f]3628 { $$ = $3->addPointer( DeclarationNode::newPointer( $2, $1 ) ); }
[5e25953]3629 | '(' function_ptr ')' attribute_list_opt
3630 { $$ = $2->addQualifiers( $4 ); }
3631 | '(' attribute_list function_ptr ')' attribute_list_opt
3632 { $$ = $3->addQualifiers( $2 )->addQualifiers( $5 ); }
[4d51835]3633 ;
[51b73452]3634
3635function_array:
[4d51835]3636 '(' function_ptr ')' array_dimension
3637 { $$ = $2->addArray( $4 ); }
[5e25953]3638 | '(' attribute_list function_ptr ')' array_dimension
3639 { $$ = $3->addQualifiers( $2 )->addArray( $5 ); }
[4d51835]3640 | '(' function_array ')' multi_array_dimension // redundant parenthesis
3641 { $$ = $2->addArray( $4 ); }
[5e25953]3642 | '(' attribute_list function_array ')' multi_array_dimension // redundant parenthesis
3643 { $$ = $3->addQualifiers( $2 )->addArray( $5 ); }
[4d51835]3644 | '(' function_array ')' // redundant parenthesis
3645 { $$ = $2; }
[5e25953]3646 | '(' attribute_list function_array ')' // redundant parenthesis
3647 { $$ = $3->addQualifiers( $2 ); }
[4d51835]3648 ;
[51b73452]3649
[c0aa336]3650// This pattern parses an old-style K&R function declarator (OBSOLESCENT, see 4)
3651//
3652// f( a, b, c ) int a, *b, c[]; {}
3653//
3654// that is not redefining a typedef name (see function_declarator for additional comments). The pattern precludes
3655// returning arrays and functions versus pointers to arrays and functions.
[51b73452]3656
[c0aa336]3657KR_function_declarator:
3658 KR_function_no_ptr
3659 | KR_function_ptr
3660 | KR_function_array
[4d51835]3661 ;
[51b73452]3662
[c0aa336]3663KR_function_no_ptr:
[4d51835]3664 paren_identifier '(' identifier_list ')' // function_declarator handles empty parameter
3665 { $$ = $1->addIdList( $3 ); }
[647e2ea]3666 | '(' KR_function_ptr ')' '(' parameter_list_ellipsis_opt ')'
[71a422a]3667 { $$ = $2->addParamList( $5 ); }
[647e2ea]3668 | '(' attribute_list KR_function_ptr ')' '(' parameter_list_ellipsis_opt ')'
[71a422a]3669 { $$ = $3->addQualifiers( $2 )->addParamList( $6 ); }
[c0aa336]3670 | '(' KR_function_no_ptr ')' // redundant parenthesis
[4d51835]3671 { $$ = $2; }
[5e25953]3672 | '(' attribute_list KR_function_no_ptr ')' // redundant parenthesis
3673 { $$ = $3->addQualifiers( $2 ); }
[4d51835]3674 ;
[51b73452]3675
[c0aa336]3676KR_function_ptr:
3677 ptrref_operator KR_function_declarator
[a5f9444]3678 { $$ = $2->addPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[c0aa336]3679 | ptrref_operator type_qualifier_list KR_function_declarator
[ce8c12f]3680 { $$ = $3->addPointer( DeclarationNode::newPointer( $2, $1 ) ); }
[c0aa336]3681 | '(' KR_function_ptr ')'
[4d51835]3682 { $$ = $2; }
[5e25953]3683 | '(' attribute_list KR_function_ptr ')'
3684 { $$ = $3->addQualifiers( $2 ); }
[4d51835]3685 ;
[51b73452]3686
[c0aa336]3687KR_function_array:
3688 '(' KR_function_ptr ')' array_dimension
[4d51835]3689 { $$ = $2->addArray( $4 ); }
[5e25953]3690 | '(' attribute_list KR_function_ptr ')' array_dimension
3691 { $$ = $3->addQualifiers( $2 )->addArray( $5 ); }
[c0aa336]3692 | '(' KR_function_array ')' multi_array_dimension // redundant parenthesis
[4d51835]3693 { $$ = $2->addArray( $4 ); }
[5e25953]3694 | '(' attribute_list KR_function_array ')' multi_array_dimension // redundant parenthesis
3695 { $$ = $3->addQualifiers( $2 )->addArray( $5 ); }
[c0aa336]3696 | '(' KR_function_array ')' // redundant parenthesis
[4d51835]3697 { $$ = $2; }
[5e25953]3698 | '(' attribute_list KR_function_array ')' // redundant parenthesis
3699 { $$ = $3->addQualifiers( $2 ); }
[4d51835]3700 ;
[51b73452]3701
[1f771fc]3702// This pattern parses a declaration for a variable that redefines a type name, e.g.:
[c11e31c]3703//
[b87a5ed]3704// typedef int foo;
3705// {
3706// int foo; // redefine typedef name in new scope
3707// }
[51b73452]3708
[2871210]3709paren_type:
[f9c3100]3710 typedef_name
[c4f68dc]3711 {
[f9c3100]3712 // hide type name in enclosing scope by variable name
[71a422a]3713 typedefTable.addToEnclosingScope( *$1->name, IDENTIFIER, "paren_type" );
[c4f68dc]3714 }
[2871210]3715 | '(' paren_type ')'
[4d51835]3716 { $$ = $2; }
3717 ;
[51b73452]3718
[5e25953]3719variable_type_redeclarator:
3720 paren_type attribute_list_opt
3721 { $$ = $1->addQualifiers( $2 ); }
[1f771fc]3722 | variable_type_ptr
3723 | variable_type_array attribute_list_opt
[5e25953]3724 { $$ = $1->addQualifiers( $2 ); }
[1f771fc]3725 | variable_type_function attribute_list_opt
[5e25953]3726 { $$ = $1->addQualifiers( $2 ); }
3727 ;
3728
[1f771fc]3729variable_type_ptr:
[c6b1105]3730 ptrref_operator variable_type_redeclarator
[a5f9444]3731 { $$ = $2->addPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[c6b1105]3732 | ptrref_operator type_qualifier_list variable_type_redeclarator
[ce8c12f]3733 { $$ = $3->addPointer( DeclarationNode::newPointer( $2, $1 ) ); }
[1f771fc]3734 | '(' variable_type_ptr ')' attribute_list_opt // redundant parenthesis
[5e25953]3735 { $$ = $2->addQualifiers( $4 ); }
[1f771fc]3736 | '(' attribute_list variable_type_ptr ')' attribute_list_opt // redundant parenthesis
[5e25953]3737 { $$ = $3->addQualifiers( $2 )->addQualifiers( $5 ); }
[4d51835]3738 ;
[51b73452]3739
[1f771fc]3740variable_type_array:
[2871210]3741 paren_type array_dimension
[4d51835]3742 { $$ = $1->addArray( $2 ); }
[1f771fc]3743 | '(' variable_type_ptr ')' array_dimension
[4d51835]3744 { $$ = $2->addArray( $4 ); }
[1f771fc]3745 | '(' attribute_list variable_type_ptr ')' array_dimension
[5e25953]3746 { $$ = $3->addQualifiers( $2 )->addArray( $5 ); }
[1f771fc]3747 | '(' variable_type_array ')' multi_array_dimension // redundant parenthesis
[4d51835]3748 { $$ = $2->addArray( $4 ); }
[1f771fc]3749 | '(' attribute_list variable_type_array ')' multi_array_dimension // redundant parenthesis
[5e25953]3750 { $$ = $3->addQualifiers( $2 )->addArray( $5 ); }
[1f771fc]3751 | '(' variable_type_array ')' // redundant parenthesis
[4d51835]3752 { $$ = $2; }
[1f771fc]3753 | '(' attribute_list variable_type_array ')' // redundant parenthesis
[5e25953]3754 { $$ = $3->addQualifiers( $2 ); }
[4d51835]3755 ;
[51b73452]3756
[1f771fc]3757variable_type_function:
[647e2ea]3758 '(' variable_type_ptr ')' '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]3759 { $$ = $2->addParamList( $5 ); }
[647e2ea]3760 | '(' attribute_list variable_type_ptr ')' '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]3761 { $$ = $3->addQualifiers( $2 )->addParamList( $6 ); }
[1f771fc]3762 | '(' variable_type_function ')' // redundant parenthesis
3763 { $$ = $2; }
3764 | '(' attribute_list variable_type_function ')' // redundant parenthesis
3765 { $$ = $3->addQualifiers( $2 ); }
3766 ;
3767
3768// This pattern parses a declaration for a function prototype that redefines a type name. It precludes declaring an
3769// array of functions versus a pointer to an array of functions, and returning arrays and functions versus pointers to
3770// arrays and functions.
3771
3772function_type_redeclarator:
3773 function_type_no_ptr attribute_list_opt
3774 { $$ = $1->addQualifiers( $2 ); }
3775 | function_type_ptr
3776 | function_type_array attribute_list_opt
3777 { $$ = $1->addQualifiers( $2 ); }
3778 ;
3779
3780function_type_no_ptr:
[647e2ea]3781 paren_type '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]3782 { $$ = $1->addParamList( $3 ); }
[647e2ea]3783 | '(' function_type_ptr ')' '(' parameter_list_ellipsis_opt ')'
[71a422a]3784 { $$ = $2->addParamList( $5 ); }
[647e2ea]3785 | '(' attribute_list function_type_ptr ')' '(' parameter_list_ellipsis_opt ')'
[71a422a]3786 { $$ = $3->addQualifiers( $2 )->addParamList( $6 ); }
[1f771fc]3787 | '(' function_type_no_ptr ')' // redundant parenthesis
[4d51835]3788 { $$ = $2; }
[1f771fc]3789 | '(' attribute_list function_type_no_ptr ')' // redundant parenthesis
3790 { $$ = $3->addQualifiers( $2 ); }
3791 ;
3792
3793function_type_ptr:
3794 ptrref_operator function_type_redeclarator
3795 { $$ = $2->addPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
3796 | ptrref_operator type_qualifier_list function_type_redeclarator
3797 { $$ = $3->addPointer( DeclarationNode::newPointer( $2, $1 ) ); }
3798 | '(' function_type_ptr ')' attribute_list_opt
3799 { $$ = $2->addQualifiers( $4 ); }
3800 | '(' attribute_list function_type_ptr ')' attribute_list_opt
3801 { $$ = $3->addQualifiers( $2 )->addQualifiers( $5 ); }
3802 ;
3803
3804function_type_array:
3805 '(' function_type_ptr ')' array_dimension
3806 { $$ = $2->addArray( $4 ); }
3807 | '(' attribute_list function_type_ptr ')' array_dimension
3808 { $$ = $3->addQualifiers( $2 )->addArray( $5 ); }
3809 | '(' function_type_array ')' multi_array_dimension // redundant parenthesis
3810 { $$ = $2->addArray( $4 ); }
3811 | '(' attribute_list function_type_array ')' multi_array_dimension // redundant parenthesis
3812 { $$ = $3->addQualifiers( $2 )->addArray( $5 ); }
3813 | '(' function_type_array ')' // redundant parenthesis
[4d51835]3814 { $$ = $2; }
[1f771fc]3815 | '(' attribute_list function_type_array ')' // redundant parenthesis
[5e25953]3816 { $$ = $3->addQualifiers( $2 ); }
[4d51835]3817 ;
[51b73452]3818
[c0aa336]3819// This pattern parses a declaration for a parameter variable of a function prototype or actual that is not redefining a
3820// typedef name and allows the C99 array options, which can only appear in a parameter list. The pattern precludes
3821// declaring an array of functions versus a pointer to an array of functions, and returning arrays and functions versus
3822// pointers to arrays and functions.
[51b73452]3823
3824identifier_parameter_declarator:
[4d51835]3825 paren_identifier attribute_list_opt
[1db21619]3826 { $$ = $1->addQualifiers( $2 ); }
[b6b3c42]3827 | '&' MUTEX paren_identifier attribute_list_opt
[6cef439]3828 { $$ = $3->addPointer( DeclarationNode::newPointer( DeclarationNode::newFromTypeData( build_type_qualifier( ast::CV::Mutex ) ),
[647e2ea]3829 OperKinds::AddressOf ) )->addQualifiers( $4 ); }
[4d51835]3830 | identifier_parameter_ptr
3831 | identifier_parameter_array attribute_list_opt
[1db21619]3832 { $$ = $1->addQualifiers( $2 ); }
[4d51835]3833 | identifier_parameter_function attribute_list_opt
[1db21619]3834 { $$ = $1->addQualifiers( $2 ); }
[4d51835]3835 ;
[51b73452]3836
3837identifier_parameter_ptr:
[dd51906]3838 ptrref_operator identifier_parameter_declarator
[a5f9444]3839 { $$ = $2->addPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[dd51906]3840 | ptrref_operator type_qualifier_list identifier_parameter_declarator
[ce8c12f]3841 { $$ = $3->addPointer( DeclarationNode::newPointer( $2, $1 ) ); }
[5e25953]3842 | '(' identifier_parameter_ptr ')' attribute_list_opt // redundant parenthesis
[c0aa336]3843 { $$ = $2->addQualifiers( $4 ); }
[4d51835]3844 ;
[51b73452]3845
3846identifier_parameter_array:
[4d51835]3847 paren_identifier array_parameter_dimension
3848 { $$ = $1->addArray( $2 ); }
3849 | '(' identifier_parameter_ptr ')' array_dimension
3850 { $$ = $2->addArray( $4 ); }
3851 | '(' identifier_parameter_array ')' multi_array_dimension // redundant parenthesis
3852 { $$ = $2->addArray( $4 ); }
3853 | '(' identifier_parameter_array ')' // redundant parenthesis
3854 { $$ = $2; }
3855 ;
[51b73452]3856
3857identifier_parameter_function:
[647e2ea]3858 paren_identifier '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]3859 { $$ = $1->addParamList( $3 ); }
[647e2ea]3860 | '(' identifier_parameter_ptr ')' '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]3861 { $$ = $2->addParamList( $5 ); }
[4d51835]3862 | '(' identifier_parameter_function ')' // redundant parenthesis
3863 { $$ = $2; }
3864 ;
[b87a5ed]3865
[de62360d]3866// This pattern parses a declaration for a parameter variable or function prototype that is redefining a typedef name,
3867// e.g.:
[c11e31c]3868//
[b87a5ed]3869// typedef int foo;
[114014c]3870// forall( otype T ) struct foo;
[b87a5ed]3871// int f( int foo ); // redefine typedef name in new scope
[c11e31c]3872//
[c0aa336]3873// and allows the C99 array options, which can only appear in a parameter list.
[51b73452]3874
[2871210]3875type_parameter_redeclarator:
[f9c3100]3876 typedef_name attribute_list_opt
[1db21619]3877 { $$ = $1->addQualifiers( $2 ); }
[f9c3100]3878 | '&' MUTEX typedef_name attribute_list_opt
[6cef439]3879 { $$ = $3->addPointer( DeclarationNode::newPointer( DeclarationNode::newFromTypeData( build_type_qualifier( ast::CV::Mutex ) ),
[647e2ea]3880 OperKinds::AddressOf ) )->addQualifiers( $4 ); }
[2871210]3881 | type_parameter_ptr
3882 | type_parameter_array attribute_list_opt
[1db21619]3883 { $$ = $1->addQualifiers( $2 ); }
[2871210]3884 | type_parameter_function attribute_list_opt
[1db21619]3885 { $$ = $1->addQualifiers( $2 ); }
[4d51835]3886 ;
[51b73452]3887
[f9c3100]3888typedef_name:
[4d51835]3889 TYPEDEFname
[7fdb94e1]3890 { $$ = DeclarationNode::newName( $1 ); }
[2871210]3891 | TYPEGENname
[7fdb94e1]3892 { $$ = DeclarationNode::newName( $1 ); }
[4d51835]3893 ;
[51b73452]3894
[2871210]3895type_parameter_ptr:
[dd51906]3896 ptrref_operator type_parameter_redeclarator
[a5f9444]3897 { $$ = $2->addPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[dd51906]3898 | ptrref_operator type_qualifier_list type_parameter_redeclarator
[ce8c12f]3899 { $$ = $3->addPointer( DeclarationNode::newPointer( $2, $1 ) ); }
[5e25953]3900 | '(' type_parameter_ptr ')' attribute_list_opt // redundant parenthesis
[c0aa336]3901 { $$ = $2->addQualifiers( $4 ); }
[4d51835]3902 ;
[51b73452]3903
[2871210]3904type_parameter_array:
[f9c3100]3905 typedef_name array_parameter_dimension
[4d51835]3906 { $$ = $1->addArray( $2 ); }
[2871210]3907 | '(' type_parameter_ptr ')' array_parameter_dimension
[4d51835]3908 { $$ = $2->addArray( $4 ); }
3909 ;
[51b73452]3910
[2871210]3911type_parameter_function:
[7e13b11]3912 typedef_name '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]3913 { $$ = $1->addParamList( $3 ); }
[647e2ea]3914 | '(' type_parameter_ptr ')' '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]3915 { $$ = $2->addParamList( $5 ); }
[4d51835]3916 ;
[b87a5ed]3917
[de62360d]3918// This pattern parses a declaration of an abstract variable or function prototype, i.e., there is no identifier to
3919// which the type applies, e.g.:
[c11e31c]3920//
[b87a5ed]3921// sizeof( int );
[c0aa336]3922// sizeof( int * );
[b87a5ed]3923// sizeof( int [10] );
[c0aa336]3924// sizeof( int (*)() );
3925// sizeof( int () );
[c11e31c]3926//
[de62360d]3927// The pattern precludes declaring an array of functions versus a pointer to an array of functions, and returning arrays
3928// and functions versus pointers to arrays and functions.
[51b73452]3929
3930abstract_declarator:
[4d51835]3931 abstract_ptr
3932 | abstract_array attribute_list_opt
[1db21619]3933 { $$ = $1->addQualifiers( $2 ); }
[4d51835]3934 | abstract_function attribute_list_opt
[1db21619]3935 { $$ = $1->addQualifiers( $2 ); }
[4d51835]3936 ;
[51b73452]3937
3938abstract_ptr:
[dd51906]3939 ptrref_operator
[a5f9444]3940 { $$ = DeclarationNode::newPointer( nullptr, $1 ); }
[dd51906]3941 | ptrref_operator type_qualifier_list
[ce8c12f]3942 { $$ = DeclarationNode::newPointer( $2, $1 ); }
[dd51906]3943 | ptrref_operator abstract_declarator
[a5f9444]3944 { $$ = $2->addPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[dd51906]3945 | ptrref_operator type_qualifier_list abstract_declarator
[ce8c12f]3946 { $$ = $3->addPointer( DeclarationNode::newPointer( $2, $1 ) ); }
[c0aa336]3947 | '(' abstract_ptr ')' attribute_list_opt
3948 { $$ = $2->addQualifiers( $4 ); }
[4d51835]3949 ;
[51b73452]3950
3951abstract_array:
[4d51835]3952 array_dimension
3953 | '(' abstract_ptr ')' array_dimension
3954 { $$ = $2->addArray( $4 ); }
3955 | '(' abstract_array ')' multi_array_dimension // redundant parenthesis
3956 { $$ = $2->addArray( $4 ); }
3957 | '(' abstract_array ')' // redundant parenthesis
3958 { $$ = $2; }
3959 ;
[51b73452]3960
3961abstract_function:
[7e13b11]3962 '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]3963 { $$ = DeclarationNode::newFunction( nullptr, nullptr, $2, nullptr ); }
[647e2ea]3964 | '(' abstract_ptr ')' '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]3965 { $$ = $2->addParamList( $5 ); }
[4d51835]3966 | '(' abstract_function ')' // redundant parenthesis
3967 { $$ = $2; }
3968 ;
[51b73452]3969
3970array_dimension:
[4d51835]3971 // Only the first dimension can be empty.
[2871210]3972 '[' ']'
[a5f9444]3973 { $$ = DeclarationNode::newArray( nullptr, nullptr, false ); }
[2871210]3974 | '[' ']' multi_array_dimension
[a5f9444]3975 { $$ = DeclarationNode::newArray( nullptr, nullptr, false )->addArray( $3 ); }
[910e1d0]3976 // Cannot use constant_expression because of tuples => semantic check
[d41735a]3977 | '[' push assignment_expression pop ',' comma_expression ']' // CFA
[a5f9444]3978 { $$ = DeclarationNode::newArray( $3, nullptr, false )->addArray( DeclarationNode::newArray( $6, nullptr, false ) ); }
[6a99803]3979 // { SemanticError( yylloc, "New array dimension is currently unimplemented." ); $$ = nullptr; }
[647e2ea]3980
3981 // If needed, the following parses and does not use comma_expression, so the array structure can be built.
3982 // | '[' push assignment_expression pop ',' push array_dimension_list pop ']' // CFA
3983
[d41735a]3984 | '[' push array_type_list pop ']' // CFA
[0b0a285]3985 { $$ = DeclarationNode::newArray( $3, nullptr, false ); }
[4d51835]3986 | multi_array_dimension
3987 ;
[51b73452]3988
[647e2ea]3989// array_dimension_list:
3990// assignment_expression
3991// | array_dimension_list ',' assignment_expression
3992// ;
3993
[d41735a]3994array_type_list:
3995 basic_type_name
[bb7422a]3996 { $$ = new ExpressionNode( new ast::TypeExpr( yylloc, maybeMoveBuildType( $1 ) ) ); }
[d41735a]3997 | type_name
[bb7422a]3998 { $$ = new ExpressionNode( new ast::TypeExpr( yylloc, maybeMoveBuildType( $1 ) ) ); }
[d41735a]3999 | assignment_expression upupeq assignment_expression
4000 | array_type_list ',' basic_type_name
[b93c544]4001 { $$ = $1->set_last( new ExpressionNode( new ast::TypeExpr( yylloc, maybeMoveBuildType( $3 ) ) ) ); }
[bb7422a]4002 | array_type_list ',' type_name
[b93c544]4003 { $$ = $1->set_last( new ExpressionNode( new ast::TypeExpr( yylloc, maybeMoveBuildType( $3 ) ) ) ); }
[d41735a]4004 | array_type_list ',' assignment_expression upupeq assignment_expression
4005 ;
4006
4007upupeq:
4008 '~'
4009 { $$ = OperKinds::LThan; }
4010 | ErangeUpEq
4011 { $$ = OperKinds::LEThan; }
[9fd9d015]4012 ;
[d41735a]4013
[51b73452]4014multi_array_dimension:
[c0a33d2]4015 '[' push assignment_expression pop ']'
[a5f9444]4016 { $$ = DeclarationNode::newArray( $3, nullptr, false ); }
[c0a33d2]4017 | '[' push '*' pop ']' // C99
[4d51835]4018 { $$ = DeclarationNode::newVarArray( 0 ); }
[c0a33d2]4019 | multi_array_dimension '[' push assignment_expression pop ']'
[a5f9444]4020 { $$ = $1->addArray( DeclarationNode::newArray( $4, nullptr, false ) ); }
[c0a33d2]4021 | multi_array_dimension '[' push '*' pop ']' // C99
[4d51835]4022 { $$ = $1->addArray( DeclarationNode::newVarArray( 0 ) ); }
4023 ;
[51b73452]4024
[c11e31c]4025// This pattern parses a declaration of a parameter abstract variable or function prototype, i.e., there is no
4026// identifier to which the type applies, e.g.:
4027//
[c0aa336]4028// int f( int ); // not handled here
4029// int f( int * ); // abstract function-prototype parameter; no parameter name specified
4030// int f( int (*)() ); // abstract function-prototype parameter; no parameter name specified
[b87a5ed]4031// int f( int (int) ); // abstract function-prototype parameter; no parameter name specified
[c11e31c]4032//
[de62360d]4033// The pattern precludes declaring an array of functions versus a pointer to an array of functions, and returning arrays
[f678c53b]4034// and functions versus pointers to arrays and functions. In addition, the pattern handles the special meaning of
4035// parenthesis around a typedef name:
[c0aa336]4036//
4037// ISO/IEC 9899:1999 Section 6.7.5.3(11) : "In a parameter declaration, a single typedef name in
4038// parentheses is taken to be an abstract declarator that specifies a function with a single parameter,
4039// not as redundant parentheses around the identifier."
4040//
4041// For example:
4042//
4043// typedef float T;
4044// int f( int ( T [5] ) ); // see abstract_parameter_declarator
4045// int g( int ( T ( int ) ) ); // see abstract_parameter_declarator
4046// int f( int f1( T a[5] ) ); // see identifier_parameter_declarator
4047// int g( int g1( T g2( int p ) ) ); // see identifier_parameter_declarator
4048//
4049// In essence, a '(' immediately to the left of typedef name, T, is interpreted as starting a parameter type list, and
4050// not as redundant parentheses around a redeclaration of T. Finally, the pattern also precludes declaring an array of
4051// functions versus a pointer to an array of functions, and returning arrays and functions versus pointers to arrays and
4052// functions.
[51b73452]4053
[59c7e3e]4054abstract_parameter_declarator_opt:
4055 // empty
4056 { $$ = nullptr; }
4057 | abstract_parameter_declarator
4058 ;
4059
[51b73452]4060abstract_parameter_declarator:
[4d51835]4061 abstract_parameter_ptr
[b6b3c42]4062 | '&' MUTEX attribute_list_opt
[446740a]4063 { $$ = DeclarationNode::newPointer( DeclarationNode::newFromTypeData( build_type_qualifier( ast::CV::Mutex ) ),
4064 OperKinds::AddressOf )->addQualifiers( $3 ); }
[4d51835]4065 | abstract_parameter_array attribute_list_opt
[1db21619]4066 { $$ = $1->addQualifiers( $2 ); }
[4d51835]4067 | abstract_parameter_function attribute_list_opt
[1db21619]4068 { $$ = $1->addQualifiers( $2 ); }
[4d51835]4069 ;
[51b73452]4070
4071abstract_parameter_ptr:
[dd51906]4072 ptrref_operator
[ce8c12f]4073 { $$ = DeclarationNode::newPointer( nullptr, $1 ); }
[dd51906]4074 | ptrref_operator type_qualifier_list
[ce8c12f]4075 { $$ = DeclarationNode::newPointer( $2, $1 ); }
[dd51906]4076 | ptrref_operator abstract_parameter_declarator
[ce8c12f]4077 { $$ = $2->addPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[dd51906]4078 | ptrref_operator type_qualifier_list abstract_parameter_declarator
[ce8c12f]4079 { $$ = $3->addPointer( DeclarationNode::newPointer( $2, $1 ) ); }
[5e25953]4080 | '(' abstract_parameter_ptr ')' attribute_list_opt // redundant parenthesis
[c0aa336]4081 { $$ = $2->addQualifiers( $4 ); }
[4d51835]4082 ;
[51b73452]4083
4084abstract_parameter_array:
[4d51835]4085 array_parameter_dimension
4086 | '(' abstract_parameter_ptr ')' array_parameter_dimension
4087 { $$ = $2->addArray( $4 ); }
4088 | '(' abstract_parameter_array ')' multi_array_dimension // redundant parenthesis
4089 { $$ = $2->addArray( $4 ); }
4090 | '(' abstract_parameter_array ')' // redundant parenthesis
4091 { $$ = $2; }
4092 ;
[51b73452]4093
4094abstract_parameter_function:
[7e13b11]4095 '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]4096 { $$ = DeclarationNode::newFunction( nullptr, nullptr, $2, nullptr ); }
[647e2ea]4097 | '(' abstract_parameter_ptr ')' '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]4098 { $$ = $2->addParamList( $5 ); }
[4d51835]4099 | '(' abstract_parameter_function ')' // redundant parenthesis
4100 { $$ = $2; }
4101 ;
[51b73452]4102
4103array_parameter_dimension:
[4d51835]4104 // Only the first dimension can be empty or have qualifiers.
4105 array_parameter_1st_dimension
4106 | array_parameter_1st_dimension multi_array_dimension
4107 { $$ = $1->addArray( $2 ); }
4108 | multi_array_dimension
4109 ;
[51b73452]4110
[c11e31c]4111// The declaration of an array parameter has additional syntax over arrays in normal variable declarations:
4112//
[de62360d]4113// ISO/IEC 9899:1999 Section 6.7.5.2(1) : "The optional type qualifiers and the keyword static shall appear only in
4114// a declaration of a function parameter with an array type, and then only in the outermost array type derivation."
[51b73452]4115
4116array_parameter_1st_dimension:
[2871210]4117 '[' ']'
[a5f9444]4118 { $$ = DeclarationNode::newArray( nullptr, nullptr, false ); }
[13e8427]4119 // multi_array_dimension handles the '[' '*' ']' case
[c0a33d2]4120 | '[' push type_qualifier_list '*' pop ']' // remaining C99
4121 { $$ = DeclarationNode::newVarArray( $3 ); }
4122 | '[' push type_qualifier_list pop ']'
[a5f9444]4123 { $$ = DeclarationNode::newArray( nullptr, $3, false ); }
[13e8427]4124 // multi_array_dimension handles the '[' assignment_expression ']' case
[c0a33d2]4125 | '[' push type_qualifier_list assignment_expression pop ']'
4126 { $$ = DeclarationNode::newArray( $4, $3, false ); }
4127 | '[' push STATIC type_qualifier_list_opt assignment_expression pop ']'
4128 { $$ = DeclarationNode::newArray( $5, $4, true ); }
4129 | '[' push type_qualifier_list STATIC assignment_expression pop ']'
4130 { $$ = DeclarationNode::newArray( $5, $3, true ); }
[4d51835]4131 ;
[b87a5ed]4132
[c0aa336]4133// This pattern parses a declaration of an abstract variable, but does not allow "int ()" for a function pointer.
[c11e31c]4134//
[71a422a]4135// struct S {
4136// int;
4137// int *;
4138// int [10];
4139// int (*)();
4140// };
[51b73452]4141
4142variable_abstract_declarator:
[4d51835]4143 variable_abstract_ptr
4144 | variable_abstract_array attribute_list_opt
[1db21619]4145 { $$ = $1->addQualifiers( $2 ); }
[4d51835]4146 | variable_abstract_function attribute_list_opt
[1db21619]4147 { $$ = $1->addQualifiers( $2 ); }
[4d51835]4148 ;
[51b73452]4149
4150variable_abstract_ptr:
[dd51906]4151 ptrref_operator
[a5f9444]4152 { $$ = DeclarationNode::newPointer( nullptr, $1 ); }
[dd51906]4153 | ptrref_operator type_qualifier_list
[ce8c12f]4154 { $$ = DeclarationNode::newPointer( $2, $1 ); }
[dd51906]4155 | ptrref_operator variable_abstract_declarator
[a5f9444]4156 { $$ = $2->addPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[dd51906]4157 | ptrref_operator type_qualifier_list variable_abstract_declarator
[ce8c12f]4158 { $$ = $3->addPointer( DeclarationNode::newPointer( $2, $1 ) ); }
[5e25953]4159 | '(' variable_abstract_ptr ')' attribute_list_opt // redundant parenthesis
[c0aa336]4160 { $$ = $2->addQualifiers( $4 ); }
[4d51835]4161 ;
[51b73452]4162
4163variable_abstract_array:
[4d51835]4164 array_dimension
4165 | '(' variable_abstract_ptr ')' array_dimension
4166 { $$ = $2->addArray( $4 ); }
4167 | '(' variable_abstract_array ')' multi_array_dimension // redundant parenthesis
4168 { $$ = $2->addArray( $4 ); }
4169 | '(' variable_abstract_array ')' // redundant parenthesis
4170 { $$ = $2; }
4171 ;
[51b73452]4172
4173variable_abstract_function:
[647e2ea]4174 '(' variable_abstract_ptr ')' '(' parameter_list_ellipsis_opt ')' // empty parameter list OBSOLESCENT (see 3)
[71a422a]4175 { $$ = $2->addParamList( $5 ); }
[4d51835]4176 | '(' variable_abstract_function ')' // redundant parenthesis
4177 { $$ = $2; }
4178 ;
[b87a5ed]4179
[de62360d]4180// This pattern parses a new-style declaration for a parameter variable or function prototype that is either an
4181// identifier or typedef name and allows the C99 array options, which can only appear in a parameter list.
[b87a5ed]4182
[c0aa336]4183cfa_identifier_parameter_declarator_tuple: // CFA
4184 cfa_identifier_parameter_declarator_no_tuple
4185 | cfa_abstract_tuple
4186 | type_qualifier_list cfa_abstract_tuple
[4d51835]4187 { $$ = $2->addQualifiers( $1 ); }
4188 ;
[b87a5ed]4189
[c0aa336]4190cfa_identifier_parameter_declarator_no_tuple: // CFA
4191 cfa_identifier_parameter_ptr
4192 | cfa_identifier_parameter_array
[4d51835]4193 ;
[b87a5ed]4194
[c0aa336]4195cfa_identifier_parameter_ptr: // CFA
[d0ffed1]4196 // No SUE declaration in parameter list.
4197 ptrref_operator type_specifier_nobody
[a5f9444]4198 { $$ = $2->addNewPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[d0ffed1]4199 | type_qualifier_list ptrref_operator type_specifier_nobody
[ce8c12f]4200 { $$ = $3->addNewPointer( DeclarationNode::newPointer( $1, $2 ) ); }
[c0aa336]4201 | ptrref_operator cfa_abstract_function
[a5f9444]4202 { $$ = $2->addNewPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[c0aa336]4203 | type_qualifier_list ptrref_operator cfa_abstract_function
[ce8c12f]4204 { $$ = $3->addNewPointer( DeclarationNode::newPointer( $1, $2 ) ); }
[c0aa336]4205 | ptrref_operator cfa_identifier_parameter_declarator_tuple
[a5f9444]4206 { $$ = $2->addNewPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[c0aa336]4207 | type_qualifier_list ptrref_operator cfa_identifier_parameter_declarator_tuple
[ce8c12f]4208 { $$ = $3->addNewPointer( DeclarationNode::newPointer( $1, $2 ) ); }
[4d51835]4209 ;
[b87a5ed]4210
[c0aa336]4211cfa_identifier_parameter_array: // CFA
[de62360d]4212 // Only the first dimension can be empty or have qualifiers. Empty dimension must be factored out due to
4213 // shift/reduce conflict with new-style empty (void) function return type.
[d0ffed1]4214 '[' ']' type_specifier_nobody
[a5f9444]4215 { $$ = $3->addNewArray( DeclarationNode::newArray( nullptr, nullptr, false ) ); }
[d0ffed1]4216 | cfa_array_parameter_1st_dimension type_specifier_nobody
[4d51835]4217 { $$ = $2->addNewArray( $1 ); }
[d0ffed1]4218 | '[' ']' multi_array_dimension type_specifier_nobody
[a5f9444]4219 { $$ = $4->addNewArray( $3 )->addNewArray( DeclarationNode::newArray( nullptr, nullptr, false ) ); }
[d0ffed1]4220 | cfa_array_parameter_1st_dimension multi_array_dimension type_specifier_nobody
[4d51835]4221 { $$ = $3->addNewArray( $2 )->addNewArray( $1 ); }
[d0ffed1]4222 | multi_array_dimension type_specifier_nobody
[4d51835]4223 { $$ = $2->addNewArray( $1 ); }
[9059213]4224
[c0aa336]4225 | '[' ']' cfa_identifier_parameter_ptr
[a5f9444]4226 { $$ = $3->addNewArray( DeclarationNode::newArray( nullptr, nullptr, false ) ); }
[c0aa336]4227 | cfa_array_parameter_1st_dimension cfa_identifier_parameter_ptr
[4d51835]4228 { $$ = $2->addNewArray( $1 ); }
[c0aa336]4229 | '[' ']' multi_array_dimension cfa_identifier_parameter_ptr
[a5f9444]4230 { $$ = $4->addNewArray( $3 )->addNewArray( DeclarationNode::newArray( nullptr, nullptr, false ) ); }
[c0aa336]4231 | cfa_array_parameter_1st_dimension multi_array_dimension cfa_identifier_parameter_ptr
[4d51835]4232 { $$ = $3->addNewArray( $2 )->addNewArray( $1 ); }
[c0aa336]4233 | multi_array_dimension cfa_identifier_parameter_ptr
[4d51835]4234 { $$ = $2->addNewArray( $1 ); }
4235 ;
[51b73452]4236
[c0aa336]4237cfa_array_parameter_1st_dimension:
[c0a33d2]4238 '[' push type_qualifier_list '*' pop ']' // remaining C99
4239 { $$ = DeclarationNode::newVarArray( $3 ); }
4240 | '[' push type_qualifier_list assignment_expression pop ']'
4241 { $$ = DeclarationNode::newArray( $4, $3, false ); }
4242 | '[' push declaration_qualifier_list assignment_expression pop ']'
[4d51835]4243 // declaration_qualifier_list must be used because of shift/reduce conflict with
4244 // assignment_expression, so a semantic check is necessary to preclude them as a type_qualifier cannot
4245 // appear in this context.
[c0a33d2]4246 { $$ = DeclarationNode::newArray( $4, $3, true ); }
4247 | '[' push declaration_qualifier_list type_qualifier_list assignment_expression pop ']'
4248 { $$ = DeclarationNode::newArray( $5, $4->addQualifiers( $3 ), true ); }
[4d51835]4249 ;
[b87a5ed]4250
[de62360d]4251// This pattern parses a new-style declaration of an abstract variable or function prototype, i.e., there is no
4252// identifier to which the type applies, e.g.:
[c11e31c]4253//
[b87a5ed]4254// [int] f( int ); // abstract variable parameter; no parameter name specified
4255// [int] f( [int] (int) ); // abstract function-prototype parameter; no parameter name specified
[c11e31c]4256//
4257// These rules need LR(3):
4258//
[c0aa336]4259// cfa_abstract_tuple identifier_or_type_name
[647e2ea]4260// '[' cfa_parameter_list ']' identifier_or_type_name '(' cfa_parameter_list_ellipsis_opt ')'
[c11e31c]4261//
4262// since a function return type can be syntactically identical to a tuple type:
4263//
[b87a5ed]4264// [int, int] t;
4265// [int, int] f( int );
[c11e31c]4266//
[2871210]4267// Therefore, it is necessary to look at the token after identifier_or_type_name to know when to reduce
[c0aa336]4268// cfa_abstract_tuple. To make this LR(1), several rules have to be flattened (lengthened) to allow the necessary
4269// lookahead. To accomplish this, cfa_abstract_declarator has an entry point without tuple, and tuple declarations are
4270// duplicated when appearing with cfa_function_specifier.
[b87a5ed]4271
[c0aa336]4272cfa_abstract_declarator_tuple: // CFA
4273 cfa_abstract_tuple
4274 | type_qualifier_list cfa_abstract_tuple
[4d51835]4275 { $$ = $2->addQualifiers( $1 ); }
[c0aa336]4276 | cfa_abstract_declarator_no_tuple
[4d51835]4277 ;
[b87a5ed]4278
[c0aa336]4279cfa_abstract_declarator_no_tuple: // CFA
4280 cfa_abstract_ptr
4281 | cfa_abstract_array
[4d51835]4282 ;
[b87a5ed]4283
[c0aa336]4284cfa_abstract_ptr: // CFA
[dd51906]4285 ptrref_operator type_specifier
[a5f9444]4286 { $$ = $2->addNewPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[dd51906]4287 | type_qualifier_list ptrref_operator type_specifier
[ce8c12f]4288 { $$ = $3->addNewPointer( DeclarationNode::newPointer( $1, $2 ) ); }
[c0aa336]4289 | ptrref_operator cfa_abstract_function
[a5f9444]4290 { $$ = $2->addNewPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[c0aa336]4291 | type_qualifier_list ptrref_operator cfa_abstract_function
[ce8c12f]4292 { $$ = $3->addNewPointer( DeclarationNode::newPointer( $1, $2 ) ); }
[c0aa336]4293 | ptrref_operator cfa_abstract_declarator_tuple
[a5f9444]4294 { $$ = $2->addNewPointer( DeclarationNode::newPointer( nullptr, $1 ) ); }
[c0aa336]4295 | type_qualifier_list ptrref_operator cfa_abstract_declarator_tuple
[ce8c12f]4296 { $$ = $3->addNewPointer( DeclarationNode::newPointer( $1, $2 ) ); }
[4d51835]4297 ;
[b87a5ed]4298
[c0aa336]4299cfa_abstract_array: // CFA
[de62360d]4300 // Only the first dimension can be empty. Empty dimension must be factored out due to shift/reduce conflict with
4301 // empty (void) function return type.
[2871210]4302 '[' ']' type_specifier
[2298f728]4303 { $$ = $3->addNewArray( DeclarationNode::newArray( nullptr, nullptr, false ) ); }
[2871210]4304 | '[' ']' multi_array_dimension type_specifier
[2298f728]4305 { $$ = $4->addNewArray( $3 )->addNewArray( DeclarationNode::newArray( nullptr, nullptr, false ) ); }
[4d51835]4306 | multi_array_dimension type_specifier
4307 { $$ = $2->addNewArray( $1 ); }
[c0aa336]4308 | '[' ']' cfa_abstract_ptr
[2298f728]4309 { $$ = $3->addNewArray( DeclarationNode::newArray( nullptr, nullptr, false ) ); }
[c0aa336]4310 | '[' ']' multi_array_dimension cfa_abstract_ptr
[2298f728]4311 { $$ = $4->addNewArray( $3 )->addNewArray( DeclarationNode::newArray( nullptr, nullptr, false ) ); }
[c0aa336]4312 | multi_array_dimension cfa_abstract_ptr
[4d51835]4313 { $$ = $2->addNewArray( $1 ); }
4314 ;
[b87a5ed]4315
[c0aa336]4316cfa_abstract_tuple: // CFA
[c0a33d2]4317 '[' push cfa_abstract_parameter_list pop ']'
4318 { $$ = DeclarationNode::newTuple( $3 ); }
[35718a9]4319 | '[' push type_specifier_nobody ELLIPSIS pop ']'
[13e8427]4320 { SemanticError( yylloc, "Tuple array currently unimplemented." ); $$ = nullptr; }
[35718a9]4321 | '[' push type_specifier_nobody ELLIPSIS constant_expression pop ']'
[13e8427]4322 { SemanticError( yylloc, "Tuple array currently unimplemented." ); $$ = nullptr; }
[4d51835]4323 ;
[b87a5ed]4324
[c0aa336]4325cfa_abstract_function: // CFA
[647e2ea]4326 '[' ']' '(' cfa_parameter_list_ellipsis_opt ')'
4327 { $$ = DeclarationNode::newFunction( nullptr, DeclarationNode::newTuple( nullptr ), $4, nullptr ); }
4328 | cfa_abstract_tuple '(' push cfa_parameter_list_ellipsis_opt pop ')'
[c0a33d2]4329 { $$ = DeclarationNode::newFunction( nullptr, $1, $4, nullptr ); }
[647e2ea]4330 | cfa_function_return '(' push cfa_parameter_list_ellipsis_opt pop ')'
[c0a33d2]4331 { $$ = DeclarationNode::newFunction( nullptr, $1, $4, nullptr ); }
[4d51835]4332 ;
[b87a5ed]4333
[de62360d]4334// 1) ISO/IEC 9899:1999 Section 6.7.2(2) : "At least one type specifier shall be given in the declaration specifiers in
4335// each declaration, and in the specifier-qualifier list in each structure declaration and type name."
[c11e31c]4336//
[de62360d]4337// 2) ISO/IEC 9899:1999 Section 6.11.5(1) : "The placement of a storage-class specifier other than at the beginning of
4338// the declaration specifiers in a declaration is an obsolescent feature."
[c11e31c]4339//
4340// 3) ISO/IEC 9899:1999 Section 6.11.6(1) : "The use of function declarators with empty parentheses (not
4341// prototype-format parameter type declarators) is an obsolescent feature."
4342//
[de62360d]4343// 4) ISO/IEC 9899:1999 Section 6.11.7(1) : "The use of function definitions with separate parameter identifier and
4344// declaration lists (not prototype-format parameter type and identifier declarators) is an obsolescent feature.
[51b73452]4345
[e1d66c84]4346// ************************ MISCELLANEOUS ********************************
[51b73452]4347
[b87a5ed]4348comma_opt: // redundant comma
[4d51835]4349 // empty
4350 | ','
4351 ;
[51b73452]4352
[5a51798]4353default_initializer_opt:
[4d51835]4354 // empty
[58dd019]4355 { $$ = nullptr; }
[4d51835]4356 | '=' assignment_expression
4357 { $$ = $2; }
4358 ;
[51b73452]4359
4360%%
[a1c9ddd]4361
[c11e31c]4362// ----end of grammar----
[51b73452]4363
[c11e31c]4364// Local Variables: //
[b87a5ed]4365// mode: c++ //
[de62360d]4366// tab-width: 4 //
[7e13b11]4367// compile-command: "bison -Wcounterexamples parser.yy" //
[c11e31c]4368// End: //
Note: See TracBrowser for help on using the repository browser.