source: src/Parser/parser.yy@ 83fd57d

Last change on this file since 83fd57d was c6b4432, checked in by Andrew Beach <ajbeach@…>, 2 years ago

Remove BaseSyntaxNode and clean-up.

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