source: src/ResolvExpr/Resolver.cc@ f5212ca

Last change on this file since f5212ca was bc61563, checked in by Andrew Beach <ajbeach@…>, 19 months ago

Factored out a very complex condition into a helper function and documented it.

  • Property mode set to 100644
File size: 44.0 KB
RevLine 
[a32b204]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//
[71f4e4f]7// Resolver.cc --
[a32b204]8//
[d76c588]9// Author : Aaron B. Moss
[a32b204]10// Created On : Sun May 17 12:17:01 2015
[4c2fe47]11// Last Modified By : Peter A. Buhr
[ca9d65e]12// Last Modified On : Thu Dec 14 18:44:43 2023
13// Update Count : 251
[a32b204]14//
15
[e3e16bc]16#include <cassert> // for strict_dynamic_cast, assert
[ea6332d]17#include <memory> // for allocator, allocator_traits<...
18#include <tuple> // for get
[6d6e829]19#include <vector> // for vector
[ea6332d]20
[99d4584]21#include "Candidate.hpp"
22#include "CandidateFinder.hpp"
[d76c588]23#include "CurrentObject.h" // for CurrentObject
24#include "RenameVars.h" // for RenameVars, global_renamer
25#include "Resolver.h"
[16ba4a6f]26#include "ResolveTypeof.h"
[4a89b52]27#include "ResolveMode.hpp" // for ResolveMode
[d76c588]28#include "typeops.h" // for extractResultType
29#include "Unify.h" // for unify
[16ba4a6f]30#include "CompilationState.h"
[2a8f0c1]31#include "AST/Decl.hpp"
32#include "AST/Init.hpp"
[d76c588]33#include "AST/Pass.hpp"
[99d4584]34#include "AST/Print.hpp"
[d76c588]35#include "AST/SymbolTable.hpp"
[2773ab8]36#include "AST/Type.hpp"
[8f06277]37#include "Common/Eval.h" // for eval
[9feb34b]38#include "Common/Iterate.hpp" // for group_iterate
[ea6332d]39#include "Common/SemanticError.h" // for SemanticError
[57e0289]40#include "Common/Stats/ResolveTime.h" // for ResolveTime::start(), ResolveTime::stop()
[9feb34b]41#include "Common/ToString.hpp" // for toCString
[c6b4432]42#include "Common/UniqueName.h" // for UniqueName
[0a60c04]43#include "InitTweak/GenInit.h"
[ea6332d]44#include "InitTweak/InitTweak.h" // for isIntrinsicSingleArgCallStmt
[16ba4a6f]45#include "SymTab/Mangler.h" // for Mangler
[0a60c04]46#include "Tuples/Tuples.h"
[2bfc6b2]47#include "Validate/FindSpecialDecls.h" // for SizeType
[51b73452]48
[d9a0e76]49using namespace std;
[51b73452]50
[d9a0e76]51namespace ResolvExpr {
[99d4584]52
[14755e5]53namespace {
54 /// Finds deleted expressions in an expression tree
55 struct DeleteFinder final : public ast::WithShortCircuiting, public ast::WithVisitorRef<DeleteFinder> {
56 const ast::DeletedExpr * result = nullptr;
57
58 void previsit( const ast::DeletedExpr * expr ) {
59 if ( result ) { visit_children = false; }
60 else { result = expr; }
61 }
62
63 void previsit( const ast::Expr * expr ) {
64 if ( result ) { visit_children = false; }
65 if (expr->inferred.hasParams()) {
66 for (auto & imp : expr->inferred.inferParams() ) {
67 imp.second.expr->accept(*visitor);
[361bf01]68 }
[99d4584]69 }
[14755e5]70 }
71 };
[4894239]72
[14755e5]73 struct ResolveDesignators final : public ast::WithShortCircuiting {
74 ResolveContext& context;
75 bool result = false;
[4894239]76
[14755e5]77 ResolveDesignators( ResolveContext& _context ): context(_context) {};
[4894239]78
[14755e5]79 void previsit( const ast::Node * ) {
80 // short circuit if we already know there are designations
81 if ( result ) visit_children = false;
82 }
[4894239]83
[14755e5]84 void previsit( const ast::Designation * des ) {
85 if ( result ) visit_children = false;
86 else if ( ! des->designators.empty() ) {
87 if ( (des->designators.size() == 1) ) {
88 const ast::Expr * designator = des->designators.at(0);
89 if ( const ast::NameExpr * designatorName = dynamic_cast<const ast::NameExpr *>(designator) ) {
90 auto candidates = context.symtab.lookupId(designatorName->name);
91 for ( auto candidate : candidates ) {
92 if ( dynamic_cast<const ast::EnumInstType *>(candidate.id->get_type()) ) {
93 result = true;
94 break;
[4894239]95 }
[2345ab3]96 }
97 }
[4894239]98 }
[14755e5]99 visit_children = false;
[4894239]100 }
[14755e5]101 }
102 };
103} // anonymous namespace
[99d4584]104
[14755e5]105/// Check if this expression is or includes a deleted expression
106const ast::DeletedExpr * findDeletedExpr( const ast::Expr * expr ) {
107 return ast::Pass<DeleteFinder>::read( expr );
108}
[b7d92b96]109
[14755e5]110namespace {
111 /// always-accept candidate filter
112 bool anyCandidate( const Candidate & ) { return true; }
[99d4584]113
[14755e5]114 /// Calls the CandidateFinder and finds the single best candidate
115 CandidateRef findUnfinishedKindExpression(
116 const ast::Expr * untyped, const ResolveContext & context, const std::string & kind,
117 std::function<bool(const Candidate &)> pred = anyCandidate, ResolveMode mode = {}
118 ) {
119 if ( ! untyped ) return nullptr;
120
121 // xxx - this isn't thread-safe, but should work until we parallelize the resolver
122 static unsigned recursion_level = 0;
123
124 ++recursion_level;
125 ast::TypeEnvironment env;
126 CandidateFinder finder( context, env );
127 finder.allowVoid = true;
128 finder.find( untyped, recursion_level == 1 ? mode.atTopLevel() : mode );
129 --recursion_level;
130
131 // produce a filtered list of candidates
132 CandidateList candidates;
133 for ( auto & cand : finder.candidates ) {
134 if ( pred( *cand ) ) { candidates.emplace_back( cand ); }
135 }
[99d4584]136
[14755e5]137 // produce invalid error if no candidates
138 if ( candidates.empty() ) {
139 SemanticError( untyped,
140 toString( "No reasonable alternatives for ", kind, (kind != "" ? " " : ""),
141 "expression: ") );
142 }
[99d4584]143
[14755e5]144 // search for cheapest candidate
145 CandidateList winners;
146 bool seen_undeleted = false;
147 for ( CandidateRef & cand : candidates ) {
148 int c = winners.empty() ? -1 : cand->cost.compare( winners.front()->cost );
149
150 if ( c > 0 ) continue; // skip more expensive than winner
151
152 if ( c < 0 ) {
153 // reset on new cheapest
154 seen_undeleted = ! findDeletedExpr( cand->expr );
155 winners.clear();
156 } else /* if ( c == 0 ) */ {
157 if ( findDeletedExpr( cand->expr ) ) {
158 // skip deleted expression if already seen one equivalent-cost not
159 if ( seen_undeleted ) continue;
160 } else if ( ! seen_undeleted ) {
161 // replace list of equivalent-cost deleted expressions with one non-deleted
[99d4584]162 winners.clear();
[14755e5]163 seen_undeleted = true;
[99d4584]164 }
165 }
166
[14755e5]167 winners.emplace_back( std::move( cand ) );
168 }
[99d4584]169
[14755e5]170 // promote candidate.cvtCost to .cost
171 // promoteCvtCost( winners );
172
173 // produce ambiguous errors, if applicable
174 if ( winners.size() != 1 ) {
175 std::ostringstream stream;
176 stream << "Cannot choose between " << winners.size() << " alternatives for "
177 << kind << (kind != "" ? " " : "") << "expression\n";
178 ast::print( stream, untyped );
179 stream << " Alternatives are:\n";
180 print( stream, winners, 1 );
181 SemanticError( untyped->location, stream.str() );
182 }
[99d4584]183
[14755e5]184 // single selected choice
185 CandidateRef & choice = winners.front();
[99d4584]186
[14755e5]187 // fail on only expression deleted
188 if ( ! seen_undeleted ) {
189 SemanticError( untyped->location, choice->expr.get(), "Unique best alternative "
190 "includes deleted identifier in " );
[99d4584]191 }
192
[14755e5]193 return std::move( choice );
194 }
[99d4584]195
[14755e5]196 /// Strips extraneous casts out of an expression
197 struct StripCasts final {
198 const ast::Expr * postvisit( const ast::CastExpr * castExpr ) {
199 if (
200 castExpr->isGenerated == ast::GeneratedCast
201 && typesCompatible( castExpr->arg->result, castExpr->result )
202 ) {
203 // generated cast is the same type as its argument, remove it after keeping env
204 return ast::mutate_field(
205 castExpr->arg.get(), &ast::Expr::env, castExpr->env );
[99d4584]206 }
[14755e5]207 return castExpr;
208 }
[99d4584]209
[14755e5]210 static void strip( ast::ptr< ast::Expr > & expr ) {
211 ast::Pass< StripCasts > stripper;
212 expr = expr->accept( stripper );
[60aaa51d]213 }
[14755e5]214 };
[60aaa51d]215
[14755e5]216 /// Swaps argument into expression pointer, saving original environment
217 void swap_and_save_env( ast::ptr< ast::Expr > & expr, const ast::Expr * newExpr ) {
218 ast::ptr< ast::TypeSubstitution > env = expr->env;
219 expr.set_and_mutate( newExpr )->env = env;
220 }
221
222 /// Removes cast to type of argument (unlike StripCasts, also handles non-generated casts)
223 void removeExtraneousCast( ast::ptr<ast::Expr> & expr ) {
224 if ( const ast::CastExpr * castExpr = expr.as< ast::CastExpr >() ) {
225 if ( typesCompatible( castExpr->arg->result, castExpr->result ) ) {
226 // cast is to the same type as its argument, remove it
227 swap_and_save_env( expr, castExpr->arg );
[b7d92b96]228 }
229 }
[14755e5]230 }
[b7d92b96]231
[14755e5]232} // anonymous namespace
[6668a3e]233
[490fb92e]234/// Establish post-resolver invariants for expressions
[14755e5]235void finishExpr(
236 ast::ptr< ast::Expr > & expr, const ast::TypeEnvironment & env,
237 const ast::TypeSubstitution * oldenv = nullptr
238) {
239 // set up new type substitution for expression
240 ast::ptr< ast::TypeSubstitution > newenv =
241 oldenv ? oldenv : new ast::TypeSubstitution{};
242 env.writeToSubstitution( *newenv.get_and_mutate() );
243 expr.get_and_mutate()->env = std::move( newenv );
244 // remove unncecessary casts
245 StripCasts::strip( expr );
246}
247
248ast::ptr< ast::Expr > resolveInVoidContext(
249 const ast::Expr * expr, const ResolveContext & context,
250 ast::TypeEnvironment & env
251) {
252 assertf( expr, "expected a non-null expression" );
253
254 // set up and resolve expression cast to void
255 ast::ptr< ast::CastExpr > untyped = new ast::CastExpr{ expr };
256 CandidateRef choice = findUnfinishedKindExpression(
257 untyped, context, "", anyCandidate, ResolveMode::withAdjustment() );
258
259 // a cast expression has either 0 or 1 interpretations (by language rules);
260 // if 0, an exception has already been thrown, and this code will not run
261 const ast::CastExpr * castExpr = choice->expr.strict_as< ast::CastExpr >();
262 env = std::move( choice->env );
263
264 return castExpr->arg;
265}
266
267/// Resolve `untyped` to the expression whose candidate is the best match for a `void`
268/// context.
269ast::ptr< ast::Expr > findVoidExpression(
270 const ast::Expr * untyped, const ResolveContext & context
271) {
272 ast::TypeEnvironment env;
273 ast::ptr< ast::Expr > newExpr = resolveInVoidContext( untyped, context, env );
274 finishExpr( newExpr, env, untyped->env );
275 return newExpr;
276}
277
278namespace {
279 /// resolve `untyped` to the expression whose candidate satisfies `pred` with the
280 /// lowest cost, returning the resolved version
281 ast::ptr< ast::Expr > findKindExpression(
282 const ast::Expr * untyped, const ResolveContext & context,
283 std::function<bool(const Candidate &)> pred = anyCandidate,
284 const std::string & kind = "", ResolveMode mode = {}
[4b7cce6]285 ) {
[14755e5]286 if ( ! untyped ) return {};
287 CandidateRef choice =
288 findUnfinishedKindExpression( untyped, context, kind, pred, mode );
289 ResolvExpr::finishExpr( choice->expr, choice->env, untyped->env );
290 return std::move( choice->expr );
[4b7cce6]291 }
[b7d92b96]292
[14755e5]293 /// Resolve `untyped` to the single expression whose candidate is the best match
[16ba4a6f]294 ast::ptr< ast::Expr > findSingleExpression(
[14755e5]295 const ast::Expr * untyped, const ResolveContext & context
[16ba4a6f]296 ) {
[14755e5]297 Stats::ResolveTime::start( untyped );
298 auto res = findKindExpression( untyped, context );
299 Stats::ResolveTime::stop();
300 return res;
[16ba4a6f]301 }
[14755e5]302} // anonymous namespace
303
304ast::ptr< ast::Expr > findSingleExpression(
305 const ast::Expr * untyped, const ast::Type * type,
306 const ResolveContext & context
307) {
308 assert( untyped && type );
309 ast::ptr< ast::Expr > castExpr = new ast::CastExpr{ untyped, type };
310 ast::ptr< ast::Expr > newExpr = findSingleExpression( castExpr, context );
311 removeExtraneousCast( newExpr );
312 return newExpr;
313}
314
315namespace {
316 bool structOrUnion( const Candidate & i ) {
317 const ast::Type * t = i.expr->result->stripReferences();
318 return dynamic_cast< const ast::StructInstType * >( t ) || dynamic_cast< const ast::UnionInstType * >( t );
[99d4584]319 }
[14755e5]320 /// Predicate for "Candidate has integral type"
321 bool hasIntegralType( const Candidate & i ) {
322 const ast::Type * type = i.expr->result;
323
324 if ( auto bt = dynamic_cast< const ast::BasicType * >( type ) ) {
325 return bt->isInteger();
326 } else if (
327 dynamic_cast< const ast::EnumInstType * >( type )
328 || dynamic_cast< const ast::ZeroType * >( type )
329 || dynamic_cast< const ast::OneType * >( type )
330 ) {
331 return true;
332 } else return false;
[d76c588]333 }
334
[14755e5]335 /// Resolve `untyped` as an integral expression, returning the resolved version
336 ast::ptr< ast::Expr > findIntegralExpression(
337 const ast::Expr * untyped, const ResolveContext & context
[234b1cb]338 ) {
[14755e5]339 return findKindExpression( untyped, context, hasIntegralType, "condition" );
[234b1cb]340 }
341
[14755e5]342 /// check if a type is a character type
343 bool isCharType( const ast::Type * t ) {
344 if ( auto bt = dynamic_cast< const ast::BasicType * >( t ) ) {
345 return bt->kind == ast::BasicType::Char
346 || bt->kind == ast::BasicType::SignedChar
347 || bt->kind == ast::BasicType::UnsignedChar;
348 }
349 return false;
[17a0ede2]350 }
351
[14755e5]352 /// Advance a type itertor to the next mutex parameter
353 template<typename Iter>
354 inline bool nextMutex( Iter & it, const Iter & end ) {
355 while ( it != end && ! (*it)->is_mutex() ) { ++it; }
356 return it != end;
357 }
358}
359
360class Resolver final
361: public ast::WithSymbolTable, public ast::WithGuards,
362 public ast::WithVisitorRef<Resolver>, public ast::WithShortCircuiting,
363 public ast::WithStmtsToAdd<> {
364
365 ast::ptr< ast::Type > functionReturn = nullptr;
366 ast::CurrentObject currentObject;
367 // for work previously in GenInit
368 static InitTweak::ManagedTypes managedTypes;
369 ResolveContext context;
370
371 bool inEnumDecl = false;
372
373public:
374 static size_t traceId;
375 Resolver( const ast::TranslationGlobal & global ) :
376 ast::WithSymbolTable(ast::SymbolTable::ErrorDetection::ValidateOnAdd),
377 context{ symtab, global } {}
378 Resolver( const ResolveContext & context ) :
379 ast::WithSymbolTable{ context.symtab },
380 context{ symtab, context.global } {}
381
382 const ast::FunctionDecl * previsit( const ast::FunctionDecl * );
383 const ast::FunctionDecl * postvisit( const ast::FunctionDecl * );
384 const ast::ObjectDecl * previsit( const ast::ObjectDecl * );
385 void previsit( const ast::AggregateDecl * );
386 void previsit( const ast::StructDecl * );
387 void previsit( const ast::EnumDecl * );
388 const ast::StaticAssertDecl * previsit( const ast::StaticAssertDecl * );
389
390 const ast::ArrayType * previsit( const ast::ArrayType * );
391 const ast::PointerType * previsit( const ast::PointerType * );
392
393 const ast::ExprStmt * previsit( const ast::ExprStmt * );
394 const ast::AsmExpr * previsit( const ast::AsmExpr * );
395 const ast::AsmStmt * previsit( const ast::AsmStmt * );
396 const ast::IfStmt * previsit( const ast::IfStmt * );
397 const ast::WhileDoStmt * previsit( const ast::WhileDoStmt * );
398 const ast::ForStmt * previsit( const ast::ForStmt * );
399 const ast::SwitchStmt * previsit( const ast::SwitchStmt * );
400 const ast::CaseClause * previsit( const ast::CaseClause * );
401 const ast::BranchStmt * previsit( const ast::BranchStmt * );
402 const ast::ReturnStmt * previsit( const ast::ReturnStmt * );
403 const ast::ThrowStmt * previsit( const ast::ThrowStmt * );
404 const ast::CatchClause * previsit( const ast::CatchClause * );
405 const ast::CatchClause * postvisit( const ast::CatchClause * );
406 const ast::WaitForStmt * previsit( const ast::WaitForStmt * );
407 const ast::WithStmt * previsit( const ast::WithStmt * );
408
409 const ast::SingleInit * previsit( const ast::SingleInit * );
410 const ast::ListInit * previsit( const ast::ListInit * );
411 const ast::ConstructorInit * previsit( const ast::ConstructorInit * );
412
413 void resolveWithExprs(std::vector<ast::ptr<ast::Expr>> & exprs, std::list<ast::ptr<ast::Stmt>> & stmtsToAdd);
[bc61563]414 bool shouldGenCtorInit( const ast::ObjectDecl * ) const;
[14755e5]415
416 void beginScope() { managedTypes.beginScope(); }
417 void endScope() { managedTypes.endScope(); }
418 bool on_error(ast::ptr<ast::Decl> & decl);
419};
420// size_t Resolver::traceId = Stats::Heap::new_stacktrace_id("Resolver");
421
422InitTweak::ManagedTypes Resolver::managedTypes;
423
424void resolve( ast::TranslationUnit& translationUnit ) {
425 ast::Pass< Resolver >::run( translationUnit, translationUnit.global );
426}
427
428ast::ptr< ast::Init > resolveCtorInit(
429 const ast::ConstructorInit * ctorInit, const ResolveContext & context
430) {
431 assert( ctorInit );
432 ast::Pass< Resolver > resolver( context );
433 return ctorInit->accept( resolver );
434}
435
436const ast::Expr * resolveStmtExpr(
437 const ast::StmtExpr * stmtExpr, const ResolveContext & context
438) {
439 assert( stmtExpr );
440 ast::Pass< Resolver > resolver( context );
441 auto ret = mutate(stmtExpr->accept(resolver));
442 strict_dynamic_cast< ast::StmtExpr * >( ret )->computeResult();
443 return ret;
444}
445
446namespace {
447 const ast::Attribute * handleAttribute(const CodeLocation & loc, const ast::Attribute * attr, const ResolveContext & context) {
448 std::string name = attr->normalizedName();
449 if (name == "constructor" || name == "destructor") {
450 if (attr->params.size() == 1) {
451 auto arg = attr->params.front();
452 auto resolved = ResolvExpr::findSingleExpression( arg, new ast::BasicType( ast::BasicType::LongLongSignedInt ), context );
453 auto result = eval(arg);
454
455 auto mutAttr = mutate(attr);
456 mutAttr->params.front() = resolved;
457 if (! result.hasKnownValue) {
458 SemanticWarning(loc, Warning::GccAttributes,
459 toCString( name, " priorities must be integers from 0 to 65535 inclusive: ", arg ) );
460 }
461 else {
462 auto priority = result.knownValue;
463 if (priority < 101) {
[16ba4a6f]464 SemanticWarning(loc, Warning::GccAttributes,
[14755e5]465 toCString( name, " priorities from 0 to 100 are reserved for the implementation" ) );
466 } else if (priority < 201 && ! buildingLibrary()) {
467 SemanticWarning(loc, Warning::GccAttributes,
468 toCString( name, " priorities from 101 to 200 are reserved for the implementation" ) );
[16ba4a6f]469 }
470 }
[14755e5]471 return mutAttr;
472 } else if (attr->params.size() > 1) {
473 SemanticWarning(loc, Warning::GccAttributes, toCString( "too many arguments to ", name, " attribute" ) );
474 } else {
475 SemanticWarning(loc, Warning::GccAttributes, toCString( "too few arguments to ", name, " attribute" ) );
[16ba4a6f]476 }
477 }
[14755e5]478 return attr;
[16ba4a6f]479 }
[14755e5]480}
[16ba4a6f]481
[14755e5]482const ast::FunctionDecl * Resolver::previsit( const ast::FunctionDecl * functionDecl ) {
483 GuardValue( functionReturn );
[16ba4a6f]484
[14755e5]485 assert (functionDecl->unique());
486 if (!functionDecl->has_body() && !functionDecl->withExprs.empty()) {
487 SemanticError(functionDecl->location, functionDecl, "Function without body has with declarations");
488 }
[16ba4a6f]489
[14755e5]490 if (!functionDecl->isTypeFixed) {
491 auto mutDecl = mutate(functionDecl);
492 auto mutType = mutDecl->type.get_and_mutate();
[16ba4a6f]493
[14755e5]494 for (auto & attr: mutDecl->attributes) {
495 attr = handleAttribute(mutDecl->location, attr, context );
496 }
[16ba4a6f]497
[14755e5]498 // handle assertions
[16ba4a6f]499
[14755e5]500 symtab.enterScope();
501 mutType->forall.clear();
502 mutType->assertions.clear();
503 for (auto & typeParam : mutDecl->type_params) {
504 symtab.addType(typeParam);
505 mutType->forall.emplace_back(new ast::TypeInstType(typeParam));
506 }
507 for (auto & asst : mutDecl->assertions) {
508 asst = fixObjectType(asst.strict_as<ast::ObjectDecl>(), context);
509 symtab.addId(asst);
510 mutType->assertions.emplace_back(new ast::VariableExpr(functionDecl->location, asst));
511 }
[16ba4a6f]512
[14755e5]513 // temporarily adds params to symbol table.
514 // actual scoping rules for params and withexprs differ - see Pass::visit(FunctionDecl)
[16ba4a6f]515
[14755e5]516 std::vector<ast::ptr<ast::Type>> paramTypes;
517 std::vector<ast::ptr<ast::Type>> returnTypes;
[3e5dd913]518
[14755e5]519 for (auto & param : mutDecl->params) {
520 param = fixObjectType(param.strict_as<ast::ObjectDecl>(), context);
521 symtab.addId(param);
522 paramTypes.emplace_back(param->get_type());
523 }
524 for (auto & ret : mutDecl->returns) {
525 ret = fixObjectType(ret.strict_as<ast::ObjectDecl>(), context);
526 returnTypes.emplace_back(ret->get_type());
527 }
528 // since function type in decl is just a view of param types, need to update that as well
529 mutType->params = std::move(paramTypes);
530 mutType->returns = std::move(returnTypes);
[16ba4a6f]531
[14755e5]532 auto renamedType = strict_dynamic_cast<const ast::FunctionType *>(renameTyVars(mutType, RenameMode::GEN_EXPR_ID));
[16ba4a6f]533
[14755e5]534 std::list<ast::ptr<ast::Stmt>> newStmts;
535 resolveWithExprs (mutDecl->withExprs, newStmts);
[16ba4a6f]536
[14755e5]537 if (mutDecl->stmts) {
538 auto mutStmt = mutDecl->stmts.get_and_mutate();
539 mutStmt->kids.splice(mutStmt->kids.begin(), std::move(newStmts));
540 mutDecl->stmts = mutStmt;
[16ba4a6f]541 }
542
[14755e5]543 symtab.leaveScope();
[d76c588]544
[14755e5]545 mutDecl->type = renamedType;
546 mutDecl->mangleName = Mangle::mangle(mutDecl);
547 mutDecl->isTypeFixed = true;
548 functionDecl = mutDecl;
549 }
550 managedTypes.handleDWT(functionDecl);
551
552 functionReturn = extractResultType( functionDecl->type );
553 return functionDecl;
554}
555
556const ast::FunctionDecl * Resolver::postvisit( const ast::FunctionDecl * functionDecl ) {
557 // default value expressions have an environment which shouldn't be there and trips up
558 // later passes.
559 assert( functionDecl->unique() );
560 ast::FunctionType * mutType = mutate( functionDecl->type.get() );
561
562 for ( unsigned i = 0 ; i < mutType->params.size() ; ++i ) {
563 if ( const ast::ObjectDecl * obj = mutType->params[i].as< ast::ObjectDecl >() ) {
564 if ( const ast::SingleInit * init = obj->init.as< ast::SingleInit >() ) {
565 if ( init->value->env == nullptr ) continue;
566 // clone initializer minus the initializer environment
567 auto mutParam = mutate( mutType->params[i].strict_as< ast::ObjectDecl >() );
568 auto mutInit = mutate( mutParam->init.strict_as< ast::SingleInit >() );
569 auto mutValue = mutate( mutInit->value.get() );
570
571 mutValue->env = nullptr;
572 mutInit->value = mutValue;
573 mutParam->init = mutInit;
574 mutType->params[i] = mutParam;
575
576 assert( ! mutType->params[i].strict_as< ast::ObjectDecl >()->init.strict_as< ast::SingleInit >()->value->env);
[e068c8a]577 }
[2a8f0c1]578 }
[d76c588]579 }
[14755e5]580 mutate_field(functionDecl, &ast::FunctionDecl::type, mutType);
581 return functionDecl;
582}
583
[bc61563]584bool Resolver::shouldGenCtorInit( ast::ObjectDecl const * decl ) const {
585 // If we shouldn't try to construct it, then don't.
586 if ( !InitTweak::tryConstruct( decl ) ) return false;
587 // Otherwise, if it is a managed type, we may construct it.
588 if ( managedTypes.isManaged( decl ) ) return true;
589 // Skip construction if it is trivial at compile-time.
590 if ( InitTweak::isConstExpr( decl->init ) ) return false;
591 // Skip construction for local declarations.
592 return ( !isInFunction() || decl->storage.is_static );
593}
594
[14755e5]595const ast::ObjectDecl * Resolver::previsit( const ast::ObjectDecl * objectDecl ) {
596 // To handle initialization of routine pointers [e.g. int (*fp)(int) = foo()],
597 // class-variable `initContext` is changed multiple times because the LHS is analyzed
598 // twice. The second analysis changes `initContext` because a function type can contain
599 // object declarations in the return and parameter types. Therefore each value of
600 // `initContext` is retained so the type on the first analysis is preserved and used for
601 // selecting the RHS.
602 GuardValue( currentObject );
603
604 if ( inEnumDecl && dynamic_cast< const ast::EnumInstType * >( objectDecl->get_type() ) ) {
605 // enumerator initializers should not use the enum type to initialize, since the
606 // enum type is still incomplete at this point. Use `int` instead.
607
608 if ( auto enumBase = dynamic_cast< const ast::EnumInstType * >
609 ( objectDecl->get_type() )->base->base ) {
610 objectDecl = fixObjectType( objectDecl, context );
611 currentObject = ast::CurrentObject{
612 objectDecl->location,
613 enumBase
614 };
615 } else {
616 objectDecl = fixObjectType( objectDecl, context );
617 currentObject = ast::CurrentObject{
618 objectDecl->location, new ast::BasicType{ ast::BasicType::SignedInt } };
[b7d92b96]619 }
[14755e5]620 } else {
621 if ( !objectDecl->isTypeFixed ) {
622 auto newDecl = fixObjectType(objectDecl, context);
623 auto mutDecl = mutate(newDecl);
624
625 // generate CtorInit wrapper when necessary.
626 // in certain cases, fixObjectType is called before reaching
627 // this object in visitor pass, thus disabling CtorInit codegen.
628 // this happens on aggregate members and function parameters.
[bc61563]629 if ( shouldGenCtorInit( mutDecl ) ) {
[14755e5]630 // constructed objects cannot be designated
631 if ( InitTweak::isDesignated( mutDecl->init ) ) {
632 ast::Pass<ResolveDesignators> res( context );
633 maybe_accept( mutDecl->init.get(), res );
634 if ( !res.core.result ) {
635 SemanticError( mutDecl, "Cannot include designations in the initializer for a managed Object.\n"
636 "If this is really what you want, initialize with @=." );
[92355883]637 }
[16ba4a6f]638 }
[14755e5]639 // constructed objects should not have initializers nested too deeply
640 if ( ! InitTweak::checkInitDepth( mutDecl ) ) SemanticError( mutDecl, "Managed object's initializer is too deep " );
[16ba4a6f]641
[14755e5]642 mutDecl->init = InitTweak::genCtorInit( mutDecl->location, mutDecl );
[16ba4a6f]643 }
644
[14755e5]645 objectDecl = mutDecl;
[16ba4a6f]646 }
[14755e5]647 currentObject = ast::CurrentObject{ objectDecl->location, objectDecl->get_type() };
[16ba4a6f]648 }
649
[14755e5]650 return objectDecl;
651}
[d76c588]652
[14755e5]653void Resolver::previsit( const ast::AggregateDecl * _aggDecl ) {
654 auto aggDecl = mutate(_aggDecl);
655 assertf(aggDecl == _aggDecl, "type declarations must be unique");
[b7d92b96]656
[14755e5]657 for (auto & member: aggDecl->members) {
658 // nested type decls are hoisted already. no need to do anything
659 if (auto obj = member.as<ast::ObjectDecl>()) {
660 member = fixObjectType(obj, context);
[0f6a7752]661 }
[d76c588]662 }
[14755e5]663}
664
665void Resolver::previsit( const ast::StructDecl * structDecl ) {
666 previsit(static_cast<const ast::AggregateDecl *>(structDecl));
667 managedTypes.handleStruct(structDecl);
668}
669
670void Resolver::previsit( const ast::EnumDecl * ) {
671 // in case we decide to allow nested enums
672 GuardValue( inEnumDecl );
673 inEnumDecl = true;
674 // don't need to fix types for enum fields
675}
676
677const ast::StaticAssertDecl * Resolver::previsit(
678 const ast::StaticAssertDecl * assertDecl
679) {
680 return ast::mutate_field(
681 assertDecl, &ast::StaticAssertDecl::cond,
682 findIntegralExpression( assertDecl->cond, context ) );
683}
684
685template< typename PtrType >
686const PtrType * handlePtrType( const PtrType * type, const ResolveContext & context ) {
687 if ( type->dimension ) {
688 const ast::Type * sizeType = context.global.sizeType.get();
689 ast::ptr< ast::Expr > dimension = findSingleExpression( type->dimension, sizeType, context );
690 assertf(dimension->env->empty(), "array dimension expr has nonempty env");
691 dimension.get_and_mutate()->env = nullptr;
692 ast::mutate_field( type, &PtrType::dimension, dimension );
[d76c588]693 }
[14755e5]694 return type;
695}
696
697const ast::ArrayType * Resolver::previsit( const ast::ArrayType * at ) {
698 return handlePtrType( at, context );
699}
700
701const ast::PointerType * Resolver::previsit( const ast::PointerType * pt ) {
702 return handlePtrType( pt, context );
703}
704
705const ast::ExprStmt * Resolver::previsit( const ast::ExprStmt * exprStmt ) {
706 visit_children = false;
707 assertf( exprStmt->expr, "ExprStmt has null expression in resolver" );
708
709 return ast::mutate_field(
710 exprStmt, &ast::ExprStmt::expr, findVoidExpression( exprStmt->expr, context ) );
711}
712
713const ast::AsmExpr * Resolver::previsit( const ast::AsmExpr * asmExpr ) {
714 visit_children = false;
715
716 asmExpr = ast::mutate_field(
717 asmExpr, &ast::AsmExpr::operand, findVoidExpression( asmExpr->operand, context ) );
718
719 return asmExpr;
720}
721
722const ast::AsmStmt * Resolver::previsit( const ast::AsmStmt * asmStmt ) {
723 visitor->maybe_accept( asmStmt, &ast::AsmStmt::input );
724 visitor->maybe_accept( asmStmt, &ast::AsmStmt::output );
725 visit_children = false;
726 return asmStmt;
727}
728
729const ast::IfStmt * Resolver::previsit( const ast::IfStmt * ifStmt ) {
730 return ast::mutate_field(
731 ifStmt, &ast::IfStmt::cond, findIntegralExpression( ifStmt->cond, context ) );
732}
733
734const ast::WhileDoStmt * Resolver::previsit( const ast::WhileDoStmt * whileDoStmt ) {
735 return ast::mutate_field(
736 whileDoStmt, &ast::WhileDoStmt::cond, findIntegralExpression( whileDoStmt->cond, context ) );
737}
738
739const ast::ForStmt * Resolver::previsit( const ast::ForStmt * forStmt ) {
740 if ( forStmt->cond ) {
741 forStmt = ast::mutate_field(
742 forStmt, &ast::ForStmt::cond, findIntegralExpression( forStmt->cond, context ) );
[d76c588]743 }
744
[14755e5]745 if ( forStmt->inc ) {
746 forStmt = ast::mutate_field(
747 forStmt, &ast::ForStmt::inc, findVoidExpression( forStmt->inc, context ) );
[d76c588]748 }
749
[14755e5]750 return forStmt;
751}
752
753const ast::SwitchStmt * Resolver::previsit( const ast::SwitchStmt * switchStmt ) {
754 GuardValue( currentObject );
755 switchStmt = ast::mutate_field(
756 switchStmt, &ast::SwitchStmt::cond,
757 findIntegralExpression( switchStmt->cond, context ) );
758 currentObject = ast::CurrentObject{ switchStmt->location, switchStmt->cond->result };
759 return switchStmt;
760}
761
762const ast::CaseClause * Resolver::previsit( const ast::CaseClause * caseStmt ) {
763 if ( caseStmt->cond ) {
764 std::deque< ast::InitAlternative > initAlts = currentObject.getOptions();
765 assertf( initAlts.size() == 1, "SwitchStmt did not correctly resolve an integral "
766 "expression." );
767
768 ast::ptr< ast::Expr > untyped =
769 new ast::CastExpr{ caseStmt->location, caseStmt->cond, initAlts.front().type };
770 ast::ptr< ast::Expr > newExpr = findSingleExpression( untyped, context );
771
772 // case condition cannot have a cast in C, so it must be removed here, regardless of
773 // whether it would perform a conversion.
774 if ( const ast::CastExpr * castExpr = newExpr.as< ast::CastExpr >() ) {
775 swap_and_save_env( newExpr, castExpr->arg );
776 }
[ef5b828]777
[14755e5]778 caseStmt = ast::mutate_field( caseStmt, &ast::CaseClause::cond, newExpr );
[d76c588]779 }
[14755e5]780 return caseStmt;
781}
782
783const ast::BranchStmt * Resolver::previsit( const ast::BranchStmt * branchStmt ) {
784 visit_children = false;
785 // must resolve the argument of a computed goto
786 if ( branchStmt->kind == ast::BranchStmt::Goto && branchStmt->computedTarget ) {
787 // computed goto argument is void*
788 ast::ptr< ast::Type > target = new ast::PointerType{ new ast::VoidType{} };
789 branchStmt = ast::mutate_field(
790 branchStmt, &ast::BranchStmt::computedTarget,
791 findSingleExpression( branchStmt->computedTarget, target, context ) );
[d76c588]792 }
[14755e5]793 return branchStmt;
794}
795
796const ast::ReturnStmt * Resolver::previsit( const ast::ReturnStmt * returnStmt ) {
797 visit_children = false;
798 if ( returnStmt->expr ) {
799 returnStmt = ast::mutate_field(
800 returnStmt, &ast::ReturnStmt::expr,
801 findSingleExpression( returnStmt->expr, functionReturn, context ) );
[d76c588]802 }
[14755e5]803 return returnStmt;
804}
805
806const ast::ThrowStmt * Resolver::previsit( const ast::ThrowStmt * throwStmt ) {
807 visit_children = false;
808 if ( throwStmt->expr ) {
809 const ast::StructDecl * exceptionDecl =
810 symtab.lookupStruct( "__cfaehm_base_exception_t" );
811 assert( exceptionDecl );
812 ast::ptr< ast::Type > exceptType =
813 new ast::PointerType{ new ast::StructInstType{ exceptionDecl } };
814 throwStmt = ast::mutate_field(
815 throwStmt, &ast::ThrowStmt::expr,
816 findSingleExpression( throwStmt->expr, exceptType, context ) );
[d76c588]817 }
[14755e5]818 return throwStmt;
819}
820
821const ast::CatchClause * Resolver::previsit( const ast::CatchClause * catchClause ) {
822 // Until we are very sure this invarent (ifs that move between passes have then)
823 // holds, check it. This allows a check for when to decode the mangling.
824 if ( auto ifStmt = catchClause->body.as<ast::IfStmt>() ) {
825 assert( ifStmt->then );
[d76c588]826 }
[14755e5]827 // Encode the catchStmt so the condition can see the declaration.
828 if ( catchClause->cond ) {
829 ast::CatchClause * clause = mutate( catchClause );
830 clause->body = new ast::IfStmt( clause->location, clause->cond, nullptr, clause->body );
831 clause->cond = nullptr;
832 return clause;
[d76c588]833 }
[14755e5]834 return catchClause;
835}
836
837const ast::CatchClause * Resolver::postvisit( const ast::CatchClause * catchClause ) {
838 // Decode the catchStmt so everything is stored properly.
839 const ast::IfStmt * ifStmt = catchClause->body.as<ast::IfStmt>();
840 if ( nullptr != ifStmt && nullptr == ifStmt->then ) {
841 assert( ifStmt->cond );
842 assert( ifStmt->else_ );
843 ast::CatchClause * clause = ast::mutate( catchClause );
844 clause->cond = ifStmt->cond;
845 clause->body = ifStmt->else_;
846 // ifStmt should be implicately deleted here.
847 return clause;
[d76c588]848 }
[14755e5]849 return catchClause;
850}
[d76c588]851
[14755e5]852const ast::WaitForStmt * Resolver::previsit( const ast::WaitForStmt * stmt ) {
853 visit_children = false;
[d76c588]854
[14755e5]855 // Resolve all clauses first
856 for ( unsigned i = 0; i < stmt->clauses.size(); ++i ) {
857 const ast::WaitForClause & clause = *stmt->clauses[i];
[d76c588]858
[14755e5]859 ast::TypeEnvironment env;
860 CandidateFinder funcFinder( context, env );
[d76c588]861
[14755e5]862 // Find all candidates for a function in canonical form
863 funcFinder.find( clause.target, ResolveMode::withAdjustment() );
[b9fa85b]864
[14755e5]865 if ( funcFinder.candidates.empty() ) {
866 stringstream ss;
867 ss << "Use of undeclared indentifier '";
868 ss << clause.target.strict_as< ast::NameExpr >()->name;
869 ss << "' in call to waitfor";
870 SemanticError( stmt->location, ss.str() );
[2b59f55]871 }
[d76c588]872
[14755e5]873 if ( clause.target_args.empty() ) {
874 SemanticError( stmt->location,
875 "Waitfor clause must have at least one mutex parameter");
876 }
[2773ab8]877
[14755e5]878 // Find all alternatives for all arguments in canonical form
879 std::vector< CandidateFinder > argFinders =
880 funcFinder.findSubExprs( clause.target_args );
881
882 // List all combinations of arguments
883 std::vector< CandidateList > possibilities;
884 combos( argFinders.begin(), argFinders.end(), back_inserter( possibilities ) );
885
886 // For every possible function:
887 // * try matching the arguments to the parameters, not the other way around because
888 // more arguments than parameters
889 CandidateList funcCandidates;
890 std::vector< CandidateList > argsCandidates;
891 SemanticErrorException errors;
892 for ( CandidateRef & func : funcFinder.candidates ) {
893 try {
894 auto pointerType = dynamic_cast< const ast::PointerType * >(
895 func->expr->result->stripReferences() );
896 if ( ! pointerType ) {
897 SemanticError( stmt->location, func->expr->result.get(),
898 "candidate not viable: not a pointer type\n" );
899 }
[2773ab8]900
[14755e5]901 auto funcType = pointerType->base.as< ast::FunctionType >();
902 if ( ! funcType ) {
903 SemanticError( stmt->location, func->expr->result.get(),
904 "candidate not viable: not a function type\n" );
905 }
[2773ab8]906
[14755e5]907 {
908 auto param = funcType->params.begin();
909 auto paramEnd = funcType->params.end();
[2773ab8]910
[14755e5]911 if( ! nextMutex( param, paramEnd ) ) {
912 SemanticError( stmt->location, funcType,
913 "candidate function not viable: no mutex parameters\n");
914 }
915 }
[2773ab8]916
[14755e5]917 CandidateRef func2{ new Candidate{ *func } };
918 // strip reference from function
919 func2->expr = referenceToRvalueConversion( func->expr, func2->cost );
920
921 // Each argument must be matched with a parameter of the current candidate
922 for ( auto & argsList : possibilities ) {
923 try {
924 // Declare data structures needed for resolution
925 ast::OpenVarSet open;
926 ast::AssertionSet need, have;
927 ast::TypeEnvironment resultEnv{ func->env };
928 // Add all type variables as open so that those not used in the
929 // parameter list are still considered open
930 resultEnv.add( funcType->forall );
931
932 // load type variables from arguments into one shared space
933 for ( auto & arg : argsList ) {
934 resultEnv.simpleCombine( arg->env );
935 }
[2773ab8]936
[14755e5]937 // Make sure we don't widen any existing bindings
938 resultEnv.forbidWidening();
[2773ab8]939
[14755e5]940 // Find any unbound type variables
941 resultEnv.extractOpenVars( open );
[2773ab8]942
[14755e5]943 auto param = funcType->params.begin();
[2773ab8]944 auto paramEnd = funcType->params.end();
945
[14755e5]946 unsigned n_mutex_param = 0;
[2773ab8]947
[14755e5]948 // For every argument of its set, check if it matches one of the
949 // parameters. The order is important
950 for ( auto & arg : argsList ) {
951 // Ignore non-mutex arguments
952 if ( ! nextMutex( param, paramEnd ) ) {
953 // We ran out of parameters but still have arguments.
954 // This function doesn't match
955 SemanticError( stmt->location, funcType,
956 toString("candidate function not viable: too many mutex "
957 "arguments, expected ", n_mutex_param, "\n" ) );
[2773ab8]958 }
959
[14755e5]960 ++n_mutex_param;
961
962 // Check if the argument matches the parameter type in the current scope.
963 // ast::ptr< ast::Type > paramType = (*param)->get_type();
964
965 if (
966 ! unify(
967 arg->expr->result, *param, resultEnv, need, have, open )
968 ) {
969 // Type doesn't match
970 stringstream ss;
971 ss << "candidate function not viable: no known conversion "
972 "from '";
973 ast::print( ss, *param );
974 ss << "' to '";
975 ast::print( ss, arg->expr->result );
976 ss << "' with env '";
977 ast::print( ss, resultEnv );
978 ss << "'\n";
979 SemanticError( stmt->location, funcType, ss.str() );
980 }
[2773ab8]981
[14755e5]982 ++param;
983 }
[2773ab8]984
[14755e5]985 // All arguments match!
[2773ab8]986
[14755e5]987 // Check if parameters are missing
988 if ( nextMutex( param, paramEnd ) ) {
989 do {
[2773ab8]990 ++n_mutex_param;
991 ++param;
[14755e5]992 } while ( nextMutex( param, paramEnd ) );
[2773ab8]993
[14755e5]994 // We ran out of arguments but still have parameters left; this
995 // function doesn't match
996 SemanticError( stmt->location, funcType,
997 toString( "candidate function not viable: too few mutex "
998 "arguments, expected ", n_mutex_param, "\n" ) );
999 }
[2773ab8]1000
[14755e5]1001 // All parameters match!
[2773ab8]1002
[14755e5]1003 // Finish the expressions to tie in proper environments
1004 finishExpr( func2->expr, resultEnv );
1005 for ( CandidateRef & arg : argsList ) {
1006 finishExpr( arg->expr, resultEnv );
1007 }
[2773ab8]1008
[14755e5]1009 // This is a match, store it and save it for later
1010 funcCandidates.emplace_back( std::move( func2 ) );
1011 argsCandidates.emplace_back( std::move( argsList ) );
[2773ab8]1012
[14755e5]1013 } catch ( SemanticErrorException & e ) {
1014 errors.append( e );
[2773ab8]1015 }
1016 }
[14755e5]1017 } catch ( SemanticErrorException & e ) {
1018 errors.append( e );
[2773ab8]1019 }
[14755e5]1020 }
[2773ab8]1021
[14755e5]1022 // Make sure correct number of arguments
1023 if( funcCandidates.empty() ) {
1024 SemanticErrorException top( stmt->location,
1025 "No alternatives for function in call to waitfor" );
1026 top.append( errors );
1027 throw top;
1028 }
[2773ab8]1029
[14755e5]1030 if( argsCandidates.empty() ) {
1031 SemanticErrorException top( stmt->location,
1032 "No alternatives for arguments in call to waitfor" );
1033 top.append( errors );
1034 throw top;
1035 }
[2773ab8]1036
[14755e5]1037 if( funcCandidates.size() > 1 ) {
1038 SemanticErrorException top( stmt->location,
1039 "Ambiguous function in call to waitfor" );
1040 top.append( errors );
1041 throw top;
1042 }
1043 if( argsCandidates.size() > 1 ) {
1044 SemanticErrorException top( stmt->location,
1045 "Ambiguous arguments in call to waitfor" );
1046 top.append( errors );
1047 throw top;
[2773ab8]1048 }
[14755e5]1049 // TODO: need to use findDeletedExpr to ensure no deleted identifiers are used.
1050
1051 // build new clause
1052 auto clause2 = new ast::WaitForClause( clause.location );
1053
1054 clause2->target = funcCandidates.front()->expr;
1055
1056 clause2->target_args.reserve( clause.target_args.size() );
1057 const ast::StructDecl * decl_monitor = symtab.lookupStruct( "monitor$" );
1058 for ( auto arg : argsCandidates.front() ) {
1059 const auto & loc = stmt->location;
1060
1061 ast::Expr * init = new ast::CastExpr( loc,
1062 new ast::UntypedExpr( loc,
1063 new ast::NameExpr( loc, "get_monitor" ),
1064 { arg->expr }
1065 ),
1066 new ast::PointerType(
1067 new ast::StructInstType(
1068 decl_monitor
1069 )
1070 )
1071 );
[2773ab8]1072
[14755e5]1073 clause2->target_args.emplace_back( findSingleExpression( init, context ) );
[2773ab8]1074 }
1075
[14755e5]1076 // Resolve the conditions as if it were an IfStmt, statements normally
1077 clause2->when_cond = findSingleExpression( clause.when_cond, context );
1078 clause2->stmt = clause.stmt->accept( *visitor );
[2773ab8]1079
[14755e5]1080 // set results into stmt
1081 auto n = mutate( stmt );
1082 n->clauses[i] = clause2;
1083 stmt = n;
1084 }
[2773ab8]1085
[14755e5]1086 if ( stmt->timeout_stmt ) {
1087 // resolve the timeout as a size_t, the conditions like IfStmt, and stmts normally
1088 ast::ptr< ast::Type > target =
1089 new ast::BasicType{ ast::BasicType::LongLongUnsignedInt };
1090 auto timeout_time = findSingleExpression( stmt->timeout_time, target, context );
1091 auto timeout_cond = findSingleExpression( stmt->timeout_cond, context );
1092 auto timeout_stmt = stmt->timeout_stmt->accept( *visitor );
1093
1094 // set results into stmt
1095 auto n = mutate( stmt );
1096 n->timeout_time = std::move( timeout_time );
1097 n->timeout_cond = std::move( timeout_cond );
1098 n->timeout_stmt = std::move( timeout_stmt );
1099 stmt = n;
[d76c588]1100 }
1101
[14755e5]1102 if ( stmt->else_stmt ) {
1103 // resolve the condition like IfStmt, stmts normally
1104 auto else_cond = findSingleExpression( stmt->else_cond, context );
1105 auto else_stmt = stmt->else_stmt->accept( *visitor );
1106
1107 // set results into stmt
1108 auto n = mutate( stmt );
1109 n->else_cond = std::move( else_cond );
1110 n->else_stmt = std::move( else_stmt );
1111 stmt = n;
[16ba4a6f]1112 }
1113
[14755e5]1114 return stmt;
1115}
1116
1117const ast::WithStmt * Resolver::previsit( const ast::WithStmt * withStmt ) {
1118 auto mutStmt = mutate(withStmt);
1119 resolveWithExprs(mutStmt->exprs, stmtsToAddBefore);
1120 return mutStmt;
1121}
1122
1123void Resolver::resolveWithExprs(std::vector<ast::ptr<ast::Expr>> & exprs, std::list<ast::ptr<ast::Stmt>> & stmtsToAdd) {
1124 for (auto & expr : exprs) {
1125 // only struct- and union-typed expressions are viable candidates
1126 expr = findKindExpression( expr, context, structOrUnion, "with expression" );
1127
1128 // if with expression might be impure, create a temporary so that it is evaluated once
1129 if ( Tuples::maybeImpure( expr ) ) {
1130 static UniqueName tmpNamer( "_with_tmp_" );
1131 const CodeLocation loc = expr->location;
1132 auto tmp = new ast::ObjectDecl(loc, tmpNamer.newName(), expr->result, new ast::SingleInit(loc, expr ) );
1133 expr = new ast::VariableExpr( loc, tmp );
1134 stmtsToAdd.push_back( new ast::DeclStmt(loc, tmp ) );
1135 if ( InitTweak::isConstructable( tmp->type ) ) {
1136 // generate ctor/dtor and resolve them
1137 tmp->init = InitTweak::genCtorInit( loc, tmp );
[9e23b446]1138 }
[14755e5]1139 // since tmp is freshly created, this should modify tmp in-place
1140 tmp->accept( *visitor );
1141 } else if (expr->env && expr->env->empty()) {
1142 expr = ast::mutate_field(expr.get(), &ast::Expr::env, nullptr);
[16ba4a6f]1143 }
1144 }
[14755e5]1145}
1146
1147const ast::SingleInit * Resolver::previsit( const ast::SingleInit * singleInit ) {
1148 visit_children = false;
1149 // resolve initialization using the possibilities as determined by the `currentObject`
1150 // cursor.
1151 ast::ptr< ast::Expr > untyped = new ast::UntypedInitExpr{
1152 singleInit->location, singleInit->value, currentObject.getOptions() };
1153 ast::ptr<ast::Expr> newExpr = findSingleExpression( untyped, context );
1154 const ast::InitExpr * initExpr = newExpr.strict_as< ast::InitExpr >();
1155
1156 // move cursor to the object that is actually initialized
1157 currentObject.setNext( initExpr->designation );
1158
1159 // discard InitExpr wrapper and retain relevant pieces.
1160 // `initExpr` may have inferred params in the case where the expression specialized a
1161 // function pointer, and newExpr may already have inferParams of its own, so a simple
1162 // swap is not sufficient
1163 ast::Expr::InferUnion inferred = initExpr->inferred;
1164 swap_and_save_env( newExpr, initExpr->expr );
1165 newExpr.get_and_mutate()->inferred.splice( std::move(inferred) );
1166
1167 // get the actual object's type (may not exactly match what comes back from the resolver
1168 // due to conversions)
1169 const ast::Type * initContext = currentObject.getCurrentType();
1170
1171 removeExtraneousCast( newExpr );
1172
1173 // check if actual object's type is char[]
1174 if ( auto at = dynamic_cast< const ast::ArrayType * >( initContext ) ) {
1175 if ( isCharType( at->base ) ) {
1176 // check if the resolved type is char*
1177 if ( auto pt = newExpr->result.as< ast::PointerType >() ) {
1178 if ( isCharType( pt->base ) ) {
1179 // strip cast if we're initializing a char[] with a char*
1180 // e.g. char x[] = "hello"
1181 if ( auto ce = newExpr.as< ast::CastExpr >() ) {
1182 swap_and_save_env( newExpr, ce->arg );
[60aaa51d]1183 }
1184 }
1185 }
1186 }
[d76c588]1187 }
1188
[14755e5]1189 // move cursor to next object in preparation for next initializer
1190 currentObject.increment();
1191
1192 // set initializer expression to resolved expression
1193 return ast::mutate_field( singleInit, &ast::SingleInit::value, std::move(newExpr) );
1194}
1195
1196const ast::ListInit * Resolver::previsit( const ast::ListInit * listInit ) {
1197 // move cursor into brace-enclosed initializer-list
1198 currentObject.enterListInit( listInit->location );
1199
1200 assert( listInit->designations.size() == listInit->initializers.size() );
1201 for ( unsigned i = 0; i < listInit->designations.size(); ++i ) {
1202 // iterate designations and initializers in pairs, moving the cursor to the current
1203 // designated object and resolving the initializer against that object
1204 listInit = ast::mutate_field_index(
1205 listInit, &ast::ListInit::designations, i,
1206 currentObject.findNext( listInit->designations[i] ) );
1207 listInit = ast::mutate_field_index(
1208 listInit, &ast::ListInit::initializers, i,
1209 listInit->initializers[i]->accept( *visitor ) );
[d76c588]1210 }
1211
[14755e5]1212 // move cursor out of brace-enclosed initializer-list
1213 currentObject.exitListInit();
[2d11663]1214
[14755e5]1215 visit_children = false;
1216 return listInit;
1217}
[2d11663]1218
[14755e5]1219const ast::ConstructorInit * Resolver::previsit( const ast::ConstructorInit * ctorInit ) {
1220 visitor->maybe_accept( ctorInit, &ast::ConstructorInit::ctor );
1221 visitor->maybe_accept( ctorInit, &ast::ConstructorInit::dtor );
[2d11663]1222
[14755e5]1223 // found a constructor - can get rid of C-style initializer
1224 // xxx - Rob suggests this field is dead code
1225 ctorInit = ast::mutate_field( ctorInit, &ast::ConstructorInit::init, nullptr );
1226
1227 // intrinsic single-parameter constructors and destructors do nothing. Since this was
1228 // implicitly generated, there's no way for it to have side effects, so get rid of it to
1229 // clean up generated code
1230 if ( InitTweak::isIntrinsicSingleArgCallStmt( ctorInit->ctor ) ) {
1231 ctorInit = ast::mutate_field( ctorInit, &ast::ConstructorInit::ctor, nullptr );
1232 }
1233 if ( InitTweak::isIntrinsicSingleArgCallStmt( ctorInit->dtor ) ) {
1234 ctorInit = ast::mutate_field( ctorInit, &ast::ConstructorInit::dtor, nullptr );
[d76c588]1235 }
1236
[14755e5]1237 return ctorInit;
1238}
1239
1240// suppress error on autogen functions and mark invalid autogen as deleted.
1241bool Resolver::on_error(ast::ptr<ast::Decl> & decl) {
1242 if (auto functionDecl = decl.as<ast::FunctionDecl>()) {
1243 // xxx - can intrinsic gen ever fail?
1244 if (functionDecl->linkage == ast::Linkage::AutoGen) {
1245 auto mutDecl = mutate(functionDecl);
1246 mutDecl->isDeleted = true;
1247 mutDecl->stmts = nullptr;
1248 decl = mutDecl;
1249 return false;
[0dd9a5e]1250 }
1251 }
[14755e5]1252 return true;
1253}
[0dd9a5e]1254
[51b73452]1255} // namespace ResolvExpr
[a32b204]1256
1257// Local Variables: //
1258// tab-width: 4 //
1259// mode: c++ //
1260// compile-command: "make install" //
1261// End: //
Note: See TracBrowser for help on using the repository browser.