source: src/Parser/parser.yy@ 924534e

Last change on this file since 924534e was dc3fbe5, checked in by Andrew Beach <ajbeach@…>, 2 years ago

Factored out the ParseNode's next field into a new child type. This is only type safe when used in the given one level curiously reoccurring template pattern, as it is now. This allowed most of the intermedate helpers to be removed.

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