source: src/Parser/parser.yy@ f5dbc8d

Last change on this file since f5dbc8d was b6f2e7ab, checked in by Andrew Beach <ajbeach@…>, 13 months ago

Removed SizeofExpr::expr and AlignofExpr::expr, expressions that would be stored there are wrapped in TypeofType and stored in the type field. Some special cases to hide the typeof in code generation were added. In addition, initializer length is calculated in more cases so that the full type of more arrays is known sooner. Other than that, most of the code changes were just stripping out the conditional code and checks no longer needed. Some tests had to be updated, because the typeof is not hidden in dumps and the resolver replaces known typeof expressions with the type. The extension case caused some concern but it appears that just hides warnings in the expression which no longer exists.

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