source: src/ResolvExpr/AlternativeFinder.cc @ 95642c9

ADTaaron-thesisarm-ehast-experimentalcleanup-dtorsdeferred_resndemanglerenumforall-pointer-decayjacob/cs343-translationjenkins-sandboxnew-astnew-ast-unique-exprnew-envno_listpersistent-indexerpthread-emulationqualifiedEnumwith_gc
Last change on this file since 95642c9 was 95642c9, checked in by Rob Schluntz <rschlunt@…>, 6 years ago

Minor cleanup

  • Property mode set to 100644
File size: 73.8 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//
[6ed1d4b]7// AlternativeFinder.cc --
[a32b204]8//
9// Author           : Richard C. Bilson
10// Created On       : Sat May 16 23:52:08 2015
[b128d3e]11// Last Modified By : Peter A. Buhr
[93401f8]12// Last Modified On : Sat Feb 17 11:19:39 2018
13// Update Count     : 33
[a32b204]14//
15
[ea6332d]16#include <algorithm>               // for copy
[e3e16bc]17#include <cassert>                 // for strict_dynamic_cast, assert, assertf
[403b388]18#include <cstddef>                 // for size_t
[ea6332d]19#include <iostream>                // for operator<<, cerr, ostream, endl
20#include <iterator>                // for back_insert_iterator, back_inserter
21#include <list>                    // for _List_iterator, list, _List_const_...
22#include <map>                     // for _Rb_tree_iterator, map, _Rb_tree_c...
[403b388]23#include <memory>                  // for allocator_traits<>::value_type, unique_ptr
[ea6332d]24#include <utility>                 // for pair
[aeb75b1]25#include <vector>                  // for vector
[51b7345]26
[ea6332d]27#include "Alternative.h"           // for AltList, Alternative
[51b7345]28#include "AlternativeFinder.h"
[ea6332d]29#include "Common/SemanticError.h"  // for SemanticError
30#include "Common/utility.h"        // for deleteAll, printAll, CodeLocation
31#include "Cost.h"                  // for Cost, Cost::zero, operator<<, Cost...
[a8b27c6]32#include "ExplodedActual.h"        // for ExplodedActual
[ea6332d]33#include "InitTweak/InitTweak.h"   // for getFunctionName
34#include "RenameVars.h"            // for RenameVars, global_renamer
35#include "ResolveTypeof.h"         // for resolveTypeof
36#include "Resolver.h"              // for resolveStmtExpr
37#include "SymTab/Indexer.h"        // for Indexer
38#include "SymTab/Mangler.h"        // for Mangler
39#include "SymTab/Validate.h"       // for validateType
40#include "SynTree/Constant.h"      // for Constant
41#include "SynTree/Declaration.h"   // for DeclarationWithType, TypeDecl, Dec...
42#include "SynTree/Expression.h"    // for Expression, CastExpr, NameExpr
43#include "SynTree/Initializer.h"   // for SingleInit, operator<<, Designation
44#include "SynTree/SynTree.h"       // for UniqueId
45#include "SynTree/Type.h"          // for Type, FunctionType, PointerType
46#include "Tuples/Explode.h"        // for explode
47#include "Tuples/Tuples.h"         // for isTtype, handleTupleAssignment
48#include "Unify.h"                 // for unify
49#include "typeops.h"               // for adjustExprType, polyCost, castCost
[51b7345]50
[b87a5ed]51extern bool resolvep;
[6ed1d4b]52#define PRINT( text ) if ( resolvep ) { text }
[51b7345]53//#define DEBUG_COST
54
[403b388]55using std::move;
56
57/// copies any copyable type
58template<typename T>
59T copy(const T& x) { return x; }
60
[51b7345]61namespace ResolvExpr {
[13deae88]62        struct AlternativeFinder::Finder : public WithShortCircuiting {
63                Finder( AlternativeFinder & altFinder ) : altFinder( altFinder ), indexer( altFinder.indexer ), alternatives( altFinder.alternatives ), env( altFinder.env ), targetType( altFinder.targetType )  {}
64
65                void previsit( BaseSyntaxNode * ) { visit_children = false; }
66
67                void postvisit( ApplicationExpr * applicationExpr );
68                void postvisit( UntypedExpr * untypedExpr );
69                void postvisit( AddressExpr * addressExpr );
70                void postvisit( LabelAddressExpr * labelExpr );
71                void postvisit( CastExpr * castExpr );
72                void postvisit( VirtualCastExpr * castExpr );
73                void postvisit( UntypedMemberExpr * memberExpr );
74                void postvisit( MemberExpr * memberExpr );
75                void postvisit( NameExpr * variableExpr );
76                void postvisit( VariableExpr * variableExpr );
77                void postvisit( ConstantExpr * constantExpr );
78                void postvisit( SizeofExpr * sizeofExpr );
79                void postvisit( AlignofExpr * alignofExpr );
80                void postvisit( UntypedOffsetofExpr * offsetofExpr );
81                void postvisit( OffsetofExpr * offsetofExpr );
82                void postvisit( OffsetPackExpr * offsetPackExpr );
83                void postvisit( AttrExpr * attrExpr );
84                void postvisit( LogicalExpr * logicalExpr );
85                void postvisit( ConditionalExpr * conditionalExpr );
86                void postvisit( CommaExpr * commaExpr );
87                void postvisit( ImplicitCopyCtorExpr  * impCpCtorExpr );
88                void postvisit( ConstructorExpr  * ctorExpr );
89                void postvisit( RangeExpr  * rangeExpr );
90                void postvisit( UntypedTupleExpr * tupleExpr );
91                void postvisit( TupleExpr * tupleExpr );
92                void postvisit( TupleIndexExpr * tupleExpr );
93                void postvisit( TupleAssignExpr * tupleExpr );
94                void postvisit( UniqueExpr * unqExpr );
95                void postvisit( StmtExpr * stmtExpr );
96                void postvisit( UntypedInitExpr * initExpr );
[c71b256]97                void postvisit( InitExpr * initExpr );
98                void postvisit( DeletedExpr * delExpr );
[13deae88]99
100                /// Adds alternatives for anonymous members
101                void addAnonConversions( const Alternative & alt );
102                /// Adds alternatives for member expressions, given the aggregate, conversion cost for that aggregate, and name of the member
103                template< typename StructOrUnionType > void addAggMembers( StructOrUnionType *aggInst, Expression *expr, const Cost &newCost, const TypeEnvironment & env, Expression * member );
104                /// Adds alternatives for member expressions where the left side has tuple type
105                void addTupleMembers( TupleType * tupleType, Expression *expr, const Cost &newCost, const TypeEnvironment & env, Expression * member );
106                /// Adds alternatives for offsetof expressions, given the base type and name of the member
107                template< typename StructOrUnionType > void addOffsetof( StructOrUnionType *aggInst, const std::string &name );
108                /// Takes a final result and checks if its assertions can be satisfied
109                template<typename OutputIterator>
110                void validateFunctionAlternative( const Alternative &func, ArgPack& result, const std::vector<ArgPack>& results, OutputIterator out );
111                /// Finds matching alternatives for a function, given a set of arguments
112                template<typename OutputIterator>
113                void makeFunctionAlternatives( const Alternative &func, FunctionType *funcType, const ExplodedArgs& args, OutputIterator out );
114                /// Checks if assertion parameters match for a new alternative
115                template< typename OutputIterator >
116                void inferParameters( const AssertionSet &need, AssertionSet &have, const Alternative &newAlt, OpenVarSet &openVars, OutputIterator out );
117        private:
118                AlternativeFinder & altFinder;
119                const SymTab::Indexer &indexer;
120                AltList & alternatives;
121                const TypeEnvironment &env;
122                Type *& targetType;
123        };
124
[908cc83]125        Cost sumCost( const AltList &in ) {
[89be1c68]126                Cost total = Cost::zero;
[908cc83]127                for ( AltList::const_iterator i = in.begin(); i != in.end(); ++i ) {
128                        total += i->cost;
129                }
130                return total;
131        }
132
[1e8bbac9]133        void printAlts( const AltList &list, std::ostream &os, unsigned int indentAmt ) {
134                Indenter indent = { Indenter::tabsize, indentAmt };
135                for ( AltList::const_iterator i = list.begin(); i != list.end(); ++i ) {
136                        i->print( os, indent );
137                        os << std::endl;
[a32b204]138                }
[1e8bbac9]139        }
[d9a0e76]140
[1e8bbac9]141        namespace {
[a32b204]142                void makeExprList( const AltList &in, std::list< Expression* > &out ) {
143                        for ( AltList::const_iterator i = in.begin(); i != in.end(); ++i ) {
144                                out.push_back( i->expr->clone() );
145                        }
146                }
[d9a0e76]147
[a32b204]148                struct PruneStruct {
149                        bool isAmbiguous;
150                        AltList::iterator candidate;
151                        PruneStruct() {}
152                        PruneStruct( AltList::iterator candidate ): isAmbiguous( false ), candidate( candidate ) {}
153                };
154
[0f19d763]155                /// Prunes a list of alternatives down to those that have the minimum conversion cost for a given return type; skips ambiguous interpretations
[a32b204]156                template< typename InputIterator, typename OutputIterator >
[d7dc824]157                void pruneAlternatives( InputIterator begin, InputIterator end, OutputIterator out ) {
[a32b204]158                        // select the alternatives that have the minimum conversion cost for a particular set of result types
159                        std::map< std::string, PruneStruct > selected;
160                        for ( AltList::iterator candidate = begin; candidate != end; ++candidate ) {
161                                PruneStruct current( candidate );
162                                std::string mangleName;
[906e24d]163                                {
164                                        Type * newType = candidate->expr->get_result()->clone();
[a32b204]165                                        candidate->env.apply( newType );
[906e24d]166                                        mangleName = SymTab::Mangler::mangle( newType );
[a32b204]167                                        delete newType;
168                                }
169                                std::map< std::string, PruneStruct >::iterator mapPlace = selected.find( mangleName );
170                                if ( mapPlace != selected.end() ) {
171                                        if ( candidate->cost < mapPlace->second.candidate->cost ) {
172                                                PRINT(
[6ed1d4b]173                                                        std::cerr << "cost " << candidate->cost << " beats " << mapPlace->second.candidate->cost << std::endl;
[7c64920]174                                                )
[0f19d763]175                                                selected[ mangleName ] = current;
[a32b204]176                                        } else if ( candidate->cost == mapPlace->second.candidate->cost ) {
177                                                PRINT(
[6ed1d4b]178                                                        std::cerr << "marking ambiguous" << std::endl;
[7c64920]179                                                )
[0f19d763]180                                                mapPlace->second.isAmbiguous = true;
[b0837e4]181                                        } else {
182                                                PRINT(
183                                                        std::cerr << "cost " << candidate->cost << " loses to " << mapPlace->second.candidate->cost << std::endl;
184                                                )
[a32b204]185                                        }
186                                } else {
187                                        selected[ mangleName ] = current;
188                                }
189                        }
[d9a0e76]190
[0f19d763]191                        // accept the alternatives that were unambiguous
192                        for ( std::map< std::string, PruneStruct >::iterator target = selected.begin(); target != selected.end(); ++target ) {
193                                if ( ! target->second.isAmbiguous ) {
194                                        Alternative &alt = *target->second.candidate;
[906e24d]195                                        alt.env.applyFree( alt.expr->get_result() );
[0f19d763]196                                        *out++ = alt;
[a32b204]197                                }
[0f19d763]198                        }
[d9a0e76]199                }
[a32b204]200
201                void renameTypes( Expression *expr ) {
[ad51cc2]202                        renameTyVars( expr->result );
[e76acbe]203                }
[1dcd9554]204        } // namespace
[b1bead1]205
[a181494]206        void referenceToRvalueConversion( Expression *& expr, Cost & cost ) {
[1dcd9554]207                if ( dynamic_cast< ReferenceType * >( expr->get_result() ) ) {
208                        // cast away reference from expr
209                        expr = new CastExpr( expr, expr->get_result()->stripReferences()->clone() );
[a181494]210                        cost.incReference();
[b1bead1]211                }
[1dcd9554]212        }
[d9a0e76]213
[a32b204]214        template< typename InputIterator, typename OutputIterator >
215        void AlternativeFinder::findSubExprs( InputIterator begin, InputIterator end, OutputIterator out ) {
216                while ( begin != end ) {
217                        AlternativeFinder finder( indexer, env );
218                        finder.findWithAdjustment( *begin );
219                        // XXX  either this
220                        //Designators::fixDesignations( finder, (*begin++)->get_argName() );
221                        // or XXX this
222                        begin++;
223                        PRINT(
[6ed1d4b]224                                std::cerr << "findSubExprs" << std::endl;
225                                printAlts( finder.alternatives, std::cerr );
[7c64920]226                        )
[0f19d763]227                        *out++ = finder;
[a32b204]228                }
[d9a0e76]229        }
230
[a32b204]231        AlternativeFinder::AlternativeFinder( const SymTab::Indexer &indexer, const TypeEnvironment &env )
232                : indexer( indexer ), env( env ) {
[d9a0e76]233        }
[51b7345]234
[4e66a18]235        void AlternativeFinder::find( Expression *expr, bool adjust, bool prune, bool failFast ) {
[13deae88]236                PassVisitor<Finder> finder( *this );
237                expr->accept( finder );
[4e66a18]238                if ( failFast && alternatives.empty() ) {
[83882e9]239                        PRINT(
240                                std::cerr << "No reasonable alternatives for expression " << expr << std::endl;
241                        )
[a16764a6]242                        SemanticError( expr, "No reasonable alternatives for expression " );
[a32b204]243                }
[b6fe7e6]244                if ( prune ) {
[b0837e4]245                        auto oldsize = alternatives.size();
[b6fe7e6]246                        PRINT(
247                                std::cerr << "alternatives before prune:" << std::endl;
248                                printAlts( alternatives, std::cerr );
249                        )
[bd4f2e9]250                        AltList pruned;
251                        pruneAlternatives( alternatives.begin(), alternatives.end(), back_inserter( pruned ) );
252                        if ( failFast && pruned.empty() ) {
[b6fe7e6]253                                std::ostringstream stream;
254                                AltList winners;
255                                findMinCost( alternatives.begin(), alternatives.end(), back_inserter( winners ) );
[50377a4]256                                stream << "Cannot choose between " << winners.size() << " alternatives for expression\n";
[5a824c2]257                                expr->print( stream );
[93401f8]258                                stream << " Alternatives are:\n";
[50377a4]259                                printAlts( winners, stream, 1 );
[a16764a6]260                                SemanticError( expr->location, stream.str() );
[b6fe7e6]261                        }
[bd4f2e9]262                        alternatives = move(pruned);
[b0837e4]263                        PRINT(
264                                std::cerr << "there are " << oldsize << " alternatives before elimination" << std::endl;
265                        )
[b6fe7e6]266                        PRINT(
267                                std::cerr << "there are " << alternatives.size() << " alternatives after elimination" << std::endl;
268                        )
[a32b204]269                }
[954ef5b]270                // adjust types after pruning so that types substituted by pruneAlternatives are correctly adjusted
271                for ( AltList::iterator i = alternatives.begin(); i != alternatives.end(); ++i ) {
272                        if ( adjust ) {
273                                adjustExprType( i->expr->get_result(), i->env, indexer );
274                        }
275                }
[8e9cbb2]276
[64ac636]277                // Central location to handle gcc extension keyword, etc. for all expression types.
[8e9cbb2]278                for ( Alternative &iter: alternatives ) {
279                        iter.expr->set_extension( expr->get_extension() );
[64ac636]280                        iter.expr->location = expr->location;
[8e9cbb2]281                } // for
[0f19d763]282        }
[d9a0e76]283
[4e66a18]284        void AlternativeFinder::findWithAdjustment( Expression *expr ) {
285                find( expr, true );
286        }
287
288        void AlternativeFinder::findWithoutPrune( Expression * expr ) {
289                find( expr, true, false );
290        }
291
292        void AlternativeFinder::maybeFind( Expression * expr ) {
293                find( expr, true, true, false );
[d9a0e76]294        }
[a32b204]295
[13deae88]296        void AlternativeFinder::Finder::addAnonConversions( const Alternative & alt ) {
[4b0f997]297                // adds anonymous member interpretations whenever an aggregate value type is seen.
[d1685588]298                // it's okay for the aggregate expression to have reference type -- cast it to the base type to treat the aggregate as the referenced value
299                std::unique_ptr<Expression> aggrExpr( alt.expr->clone() );
300                alt.env.apply( aggrExpr->get_result() );
301                Type * aggrType = aggrExpr->get_result();
302                if ( dynamic_cast< ReferenceType * >( aggrType ) ) {
303                        aggrType = aggrType->stripReferences();
304                        aggrExpr.reset( new CastExpr( aggrExpr.release(), aggrType->clone() ) );
305                }
306
307                if ( StructInstType *structInst = dynamic_cast< StructInstType* >( aggrExpr->get_result() ) ) {
[4b0f997]308                        NameExpr nameExpr( "" );
[d1685588]309                        addAggMembers( structInst, aggrExpr.get(), alt.cost+Cost::safe, alt.env, &nameExpr );
310                } else if ( UnionInstType *unionInst = dynamic_cast< UnionInstType* >( aggrExpr->get_result() ) ) {
[4b0f997]311                        NameExpr nameExpr( "" );
[d1685588]312                        addAggMembers( unionInst, aggrExpr.get(), alt.cost+Cost::safe, alt.env, &nameExpr );
[4b0f997]313                } // if
314        }
[77971f6]315
[a32b204]316        template< typename StructOrUnionType >
[13deae88]317        void AlternativeFinder::Finder::addAggMembers( StructOrUnionType *aggInst, Expression *expr, const Cost &newCost, const TypeEnvironment & env, Expression * member ) {
[bf32bb8]318                // by this point, member must be a name expr
[c93bc28]319                NameExpr * nameExpr = dynamic_cast< NameExpr * >( member );
320                if ( ! nameExpr ) return;
[bf32bb8]321                const std::string & name = nameExpr->get_name();
322                std::list< Declaration* > members;
323                aggInst->lookup( name, members );
[4b0f997]324
[bf32bb8]325                for ( std::list< Declaration* >::const_iterator i = members.begin(); i != members.end(); ++i ) {
326                        if ( DeclarationWithType *dwt = dynamic_cast< DeclarationWithType* >( *i ) ) {
[d9fa60a]327                                alternatives.push_back( Alternative( new MemberExpr( dwt, expr->clone() ), env, newCost ) );
[bf32bb8]328                                renameTypes( alternatives.back().expr );
[4b0f997]329                                addAnonConversions( alternatives.back() ); // add anonymous member interpretations whenever an aggregate value type is seen as a member expression.
[bf32bb8]330                        } else {
331                                assert( false );
[a32b204]332                        }
333                }
[d9a0e76]334        }
[a32b204]335
[13deae88]336        void AlternativeFinder::Finder::addTupleMembers( TupleType * tupleType, Expression *expr, const Cost &newCost, const TypeEnvironment & env, Expression * member ) {
[848ce71]337                if ( ConstantExpr * constantExpr = dynamic_cast< ConstantExpr * >( member ) ) {
338                        // get the value of the constant expression as an int, must be between 0 and the length of the tuple type to have meaning
339                        // xxx - this should be improved by memoizing the value of constant exprs
340                        // during parsing and reusing that information here.
341                        std::stringstream ss( constantExpr->get_constant()->get_value() );
[c93bc28]342                        int val = 0;
[848ce71]343                        std::string tmp;
344                        if ( ss >> val && ! (ss >> tmp) ) {
345                                if ( val >= 0 && (unsigned int)val < tupleType->size() ) {
346                                        alternatives.push_back( Alternative( new TupleIndexExpr( expr->clone(), val ), env, newCost ) );
347                                } // if
348                        } // if
[141b786]349                } else if ( NameExpr * nameExpr = dynamic_cast< NameExpr * >( member ) ) {
350                        // xxx - temporary hack until 0/1 are int constants
351                        if ( nameExpr->get_name() == "0" || nameExpr->get_name() == "1" ) {
352                                std::stringstream ss( nameExpr->get_name() );
353                                int val;
354                                ss >> val;
355                                alternatives.push_back( Alternative( new TupleIndexExpr( expr->clone(), val ), env, newCost ) );
356                        }
[848ce71]357                } // if
358        }
359
[13deae88]360        void AlternativeFinder::Finder::postvisit( ApplicationExpr *applicationExpr ) {
[a32b204]361                alternatives.push_back( Alternative( applicationExpr->clone(), env, Cost::zero ) );
[d9a0e76]362        }
363
[ddf8a29]364        Cost computeConversionCost( Type * actualType, Type * formalType, const SymTab::Indexer &indexer, const TypeEnvironment & env ) {
365                PRINT(
366                        std::cerr << std::endl << "converting ";
367                        actualType->print( std::cerr, 8 );
368                        std::cerr << std::endl << " to ";
369                        formalType->print( std::cerr, 8 );
370                        std::cerr << std::endl << "environment is: ";
371                        env.print( std::cerr, 8 );
372                        std::cerr << std::endl;
373                )
374                Cost convCost = conversionCost( actualType, formalType, indexer, env );
375                PRINT(
[d06c808]376                        std::cerr << std::endl << "cost is " << convCost << std::endl;
[ddf8a29]377                )
378                if ( convCost == Cost::infinity ) {
379                        return convCost;
380                }
381                convCost.incPoly( polyCost( formalType, env, indexer ) + polyCost( actualType, env, indexer ) );
[d06c808]382                PRINT(
383                        std::cerr << "cost with polycost is " << convCost << std::endl;
384                )
[ddf8a29]385                return convCost;
386        }
387
388        Cost computeExpressionConversionCost( Expression *& actualExpr, Type * formalType, const SymTab::Indexer &indexer, const TypeEnvironment & env ) {
389                Cost convCost = computeConversionCost( actualExpr->result, formalType, indexer, env );
390
[bb666f64]391                // if there is a non-zero conversion cost, ignoring poly cost, then the expression requires conversion.
392                // ignore poly cost for now, since this requires resolution of the cast to infer parameters and this
393                // does not currently work for the reason stated below.
[ddf8a29]394                Cost tmpCost = convCost;
395                tmpCost.incPoly( -tmpCost.get_polyCost() );
396                if ( tmpCost != Cost::zero ) {
397                        Type *newType = formalType->clone();
398                        env.apply( newType );
399                        actualExpr = new CastExpr( actualExpr, newType );
400                        // xxx - SHOULD be able to resolve this cast, but at the moment pointers are not castable to zero_t, but are implicitly convertible. This is clearly
401                        // inconsistent, once this is fixed it should be possible to resolve the cast.
402                        // xxx - this isn't working, it appears because type1 (the formal type) is seen as widenable, but it shouldn't be, because this makes the conversion from DT* to DT* since commontype(zero_t, DT*) is DT*, rather than just nothing.
403
404                        // AlternativeFinder finder( indexer, env );
405                        // finder.findWithAdjustment( actualExpr );
406                        // assertf( finder.get_alternatives().size() > 0, "Somehow castable expression failed to find alternatives." );
407                        // assertf( finder.get_alternatives().size() == 1, "Somehow got multiple alternatives for known cast expression." );
408                        // Alternative & alt = finder.get_alternatives().front();
409                        // delete actualExpr;
410                        // actualExpr = alt.expr->clone();
411                }
412                return convCost;
413        }
414
415        Cost computeApplicationConversionCost( Alternative &alt, const SymTab::Indexer &indexer ) {
[e3e16bc]416                ApplicationExpr *appExpr = strict_dynamic_cast< ApplicationExpr* >( alt.expr );
417                PointerType *pointer = strict_dynamic_cast< PointerType* >( appExpr->get_function()->get_result() );
418                FunctionType *function = strict_dynamic_cast< FunctionType* >( pointer->get_base() );
[a32b204]419
[89be1c68]420                Cost convCost = Cost::zero;
[a32b204]421                std::list< DeclarationWithType* >& formals = function->get_parameters();
422                std::list< DeclarationWithType* >::iterator formal = formals.begin();
423                std::list< Expression* >& actuals = appExpr->get_args();
[0362d42]424
[a32b204]425                for ( std::list< Expression* >::iterator actualExpr = actuals.begin(); actualExpr != actuals.end(); ++actualExpr ) {
[53e3b4a]426                        Type * actualType = (*actualExpr)->get_result();
[a32b204]427                        PRINT(
[6ed1d4b]428                                std::cerr << "actual expression:" << std::endl;
429                                (*actualExpr)->print( std::cerr, 8 );
430                                std::cerr << "--- results are" << std::endl;
[53e3b4a]431                                actualType->print( std::cerr, 8 );
[7c64920]432                        )
[53e3b4a]433                        if ( formal == formals.end() ) {
434                                if ( function->get_isVarArgs() ) {
[89be1c68]435                                        convCost.incUnsafe();
[d06c808]436                                        PRINT( std::cerr << "end of formals with varargs function: inc unsafe: " << convCost << std::endl; ; )
[b1bead1]437                                        // convert reference-typed expressions to value-typed expressions
[a181494]438                                        referenceToRvalueConversion( *actualExpr, convCost );
[53e3b4a]439                                        continue;
440                                } else {
441                                        return Cost::infinity;
[7c64920]442                                }
[53e3b4a]443                        }
444                        Type * formalType = (*formal)->get_type();
[ddf8a29]445                        convCost += computeExpressionConversionCost( *actualExpr, formalType, indexer, alt.env );
[53e3b4a]446                        ++formal; // can't be in for-loop update because of the continue
[d9a0e76]447                }
[a32b204]448                if ( formal != formals.end() ) {
449                        return Cost::infinity;
[d9a0e76]450                }
451
[a32b204]452                for ( InferredParams::const_iterator assert = appExpr->get_inferParams().begin(); assert != appExpr->get_inferParams().end(); ++assert ) {
[ddf8a29]453                        convCost += computeConversionCost( assert->second.actualType, assert->second.formalType, indexer, alt.env );
[a32b204]454                }
[d9a0e76]455
[a32b204]456                return convCost;
457        }
[d9a0e76]458
[8c84ebd]459        /// Adds type variables to the open variable set and marks their assertions
[a32b204]460        void makeUnifiableVars( Type *type, OpenVarSet &unifiableVars, AssertionSet &needAssertions ) {
[43bd69d]461                for ( Type::ForallList::const_iterator tyvar = type->forall.begin(); tyvar != type->forall.end(); ++tyvar ) {
[2c57025]462                        unifiableVars[ (*tyvar)->get_name() ] = TypeDecl::Data{ *tyvar };
[43bd69d]463                        for ( std::list< DeclarationWithType* >::iterator assert = (*tyvar)->assertions.begin(); assert != (*tyvar)->assertions.end(); ++assert ) {
[6c3a988f]464                                needAssertions[ *assert ].isUsed = true;
[a32b204]465                        }
[d9a0e76]466///     needAssertions.insert( needAssertions.end(), (*tyvar)->get_assertions().begin(), (*tyvar)->get_assertions().end() );
467                }
468        }
[a32b204]469
[89b686a]470        // /// Map of declaration uniqueIds (intended to be the assertions in an AssertionSet) to their parents and the number of times they've been included
471        //typedef std::unordered_map< UniqueId, std::unordered_map< UniqueId, unsigned > > AssertionParentSet;
[79970ed]472
[a1d7679]473        static const int recursionLimit = /*10*/ 4;  ///< Limit to depth of recursion satisfaction
[89b686a]474        //static const unsigned recursionParentLimit = 1;  ///< Limit to the number of times an assertion can recursively use itself
[51b7345]475
[a32b204]476        void addToIndexer( AssertionSet &assertSet, SymTab::Indexer &indexer ) {
477                for ( AssertionSet::iterator i = assertSet.begin(); i != assertSet.end(); ++i ) {
[6c3a988f]478                        if ( i->second.isUsed ) {
[33a25f9]479                                indexer.addId( i->first );
[a32b204]480                        }
481                }
[d9a0e76]482        }
[79970ed]483
[a32b204]484        template< typename ForwardIterator, typename OutputIterator >
[79970ed]485        void inferRecursive( ForwardIterator begin, ForwardIterator end, const Alternative &newAlt, OpenVarSet &openVars, const SymTab::Indexer &decls, const AssertionSet &newNeed, /*const AssertionParentSet &needParents,*/
[ebf5689]486                                                 int level, const SymTab::Indexer &indexer, OutputIterator out ) {
[a32b204]487                if ( begin == end ) {
488                        if ( newNeed.empty() ) {
[6c3a988f]489                                PRINT(
490                                        std::cerr << "all assertions satisfied, output alternative: ";
491                                        newAlt.print( std::cerr );
492                                        std::cerr << std::endl;
493                                );
[a32b204]494                                *out++ = newAlt;
495                                return;
496                        } else if ( level >= recursionLimit ) {
[a16764a6]497                                SemanticError( newAlt.expr->location, "Too many recursive assertions" );
[a32b204]498                        } else {
499                                AssertionSet newerNeed;
500                                PRINT(
501                                        std::cerr << "recursing with new set:" << std::endl;
502                                        printAssertionSet( newNeed, std::cerr, 8 );
[7c64920]503                                )
[89b686a]504                                inferRecursive( newNeed.begin(), newNeed.end(), newAlt, openVars, decls, newerNeed, /*needParents,*/ level+1, indexer, out );
[a32b204]505                                return;
506                        }
507                }
508
509                ForwardIterator cur = begin++;
[6c3a988f]510                if ( ! cur->second.isUsed ) {
[89b686a]511                        inferRecursive( begin, end, newAlt, openVars, decls, newNeed, /*needParents,*/ level, indexer, out );
[7933351]512                        return; // xxx - should this continue? previously this wasn't here, and it looks like it should be
[a32b204]513                }
514                DeclarationWithType *curDecl = cur->first;
[7933351]515
[d9a0e76]516                PRINT(
[a32b204]517                        std::cerr << "inferRecursive: assertion is ";
518                        curDecl->print( std::cerr );
519                        std::cerr << std::endl;
[7c64920]520                )
[a40d503]521                std::list< SymTab::Indexer::IdData > candidates;
[a32b204]522                decls.lookupId( curDecl->get_name(), candidates );
[6ed1d4b]523///   if ( candidates.empty() ) { std::cerr << "no candidates!" << std::endl; }
[a40d503]524                for ( const auto & data : candidates ) {
525                        DeclarationWithType * candidate = data.id;
[a32b204]526                        PRINT(
[6ed1d4b]527                                std::cerr << "inferRecursive: candidate is ";
[a40d503]528                                candidate->print( std::cerr );
[6ed1d4b]529                                std::cerr << std::endl;
[7c64920]530                        )
[79970ed]531
[0f19d763]532                        AssertionSet newHave, newerNeed( newNeed );
[a32b204]533                        TypeEnvironment newEnv( newAlt.env );
534                        OpenVarSet newOpenVars( openVars );
[a40d503]535                        Type *adjType = candidate->get_type()->clone();
[a32b204]536                        adjustExprType( adjType, newEnv, indexer );
[ad51cc2]537                        renameTyVars( adjType );
[a32b204]538                        PRINT(
539                                std::cerr << "unifying ";
540                                curDecl->get_type()->print( std::cerr );
541                                std::cerr << " with ";
542                                adjType->print( std::cerr );
543                                std::cerr << std::endl;
[7c64920]544                        )
[0f19d763]545                        if ( unify( curDecl->get_type(), adjType, newEnv, newerNeed, newHave, newOpenVars, indexer ) ) {
546                                PRINT(
547                                        std::cerr << "success!" << std::endl;
[a32b204]548                                )
[0f19d763]549                                SymTab::Indexer newDecls( decls );
550                                addToIndexer( newHave, newDecls );
551                                Alternative newerAlt( newAlt );
552                                newerAlt.env = newEnv;
[a40d503]553                                assertf( candidate->get_uniqueId(), "Assertion candidate does not have a unique ID: %s", toString( candidate ).c_str() );
[6c3a988f]554
555                                // everything with an empty idChain was pulled in by the current assertion.
556                                // add current assertion's idChain + current assertion's ID so that the correct inferParameters can be found.
557                                for ( auto & a : newerNeed ) {
558                                        if ( a.second.idChain.empty() ) {
559                                                a.second.idChain = cur->second.idChain;
560                                                a.second.idChain.push_back( curDecl->get_uniqueId() );
561                                        }
562                                }
563
[89b686a]564                                //AssertionParentSet newNeedParents( needParents );
[22cad76]565                                // skip repeatingly-self-recursive assertion satisfaction
[89b686a]566                                // DOESN'T WORK: grandchild nodes conflict with their cousins
567                                //if ( newNeedParents[ curDecl->get_uniqueId() ][ candDecl->get_uniqueId() ]++ > recursionParentLimit ) continue;
[a181494]568
[54043f4]569                                Expression *varExpr = data.combine( newerAlt.cvtCost );
[906e24d]570                                delete varExpr->get_result();
571                                varExpr->set_result( adjType->clone() );
[0f19d763]572                                PRINT(
[6ed1d4b]573                                        std::cerr << "satisfying assertion " << curDecl->get_uniqueId() << " ";
574                                        curDecl->print( std::cerr );
[a40d503]575                                        std::cerr << " with declaration " << candidate->get_uniqueId() << " ";
576                                        candidate->print( std::cerr );
[6ed1d4b]577                                        std::cerr << std::endl;
[7c64920]578                                )
[6c3a988f]579                                // follow the current assertion's ID chain to find the correct set of inferred parameters to add the candidate to (i.e. the set of inferred parameters belonging to the entity which requested the assertion parameter).
[df626eb]580                                InferredParams * inferParameters = &newerAlt.expr->get_inferParams();
[6c3a988f]581                                for ( UniqueId id : cur->second.idChain ) {
582                                        inferParameters = (*inferParameters)[ id ].inferParams.get();
583                                }
[0f19d763]584                                // XXX: this is a memory leak, but adjType can't be deleted because it might contain assertions
[a40d503]585                                (*inferParameters)[ curDecl->get_uniqueId() ] = ParamEntry( candidate->get_uniqueId(), adjType->clone(), curDecl->get_type()->clone(), varExpr );
[89b686a]586                                inferRecursive( begin, end, newerAlt, newOpenVars, newDecls, newerNeed, /*newNeedParents,*/ level, indexer, out );
[0f19d763]587                        } else {
588                                delete adjType;
589                        }
[a32b204]590                }
[d9a0e76]591        }
592
[a32b204]593        template< typename OutputIterator >
[13deae88]594        void AlternativeFinder::Finder::inferParameters( const AssertionSet &need, AssertionSet &have, const Alternative &newAlt, OpenVarSet &openVars, OutputIterator out ) {
[d9a0e76]595//      PRINT(
[6ed1d4b]596//          std::cerr << "inferParameters: assertions needed are" << std::endl;
597//          printAll( need, std::cerr, 8 );
[d9a0e76]598//          )
[a32b204]599                SymTab::Indexer decls( indexer );
[e4d829b]600                // PRINT(
601                //      std::cerr << "============= original indexer" << std::endl;
602                //      indexer.print( std::cerr );
603                //      std::cerr << "============= new indexer" << std::endl;
604                //      decls.print( std::cerr );
605                // )
[0f19d763]606                addToIndexer( have, decls );
[a32b204]607                AssertionSet newNeed;
[89b686a]608                //AssertionParentSet needParents;
[74b007ba]609                PRINT(
610                        std::cerr << "env is: " << std::endl;
611                        newAlt.env.print( std::cerr, 0 );
612                        std::cerr << std::endl;
613                )
614
[89b686a]615                inferRecursive( need.begin(), need.end(), newAlt, openVars, decls, newNeed, /*needParents,*/ 0, indexer, out );
[d9a0e76]616//      PRINT(
[6ed1d4b]617//          std::cerr << "declaration 14 is ";
[d9a0e76]618//          Declaration::declFromId
619//          *out++ = newAlt;
620//          )
621        }
622
[aeb75b1]623        /// Gets a default value from an initializer, nullptr if not present
624        ConstantExpr* getDefaultValue( Initializer* init ) {
625                if ( SingleInit* si = dynamic_cast<SingleInit*>( init ) ) {
626                        if ( CastExpr* ce = dynamic_cast<CastExpr*>( si->get_value() ) ) {
627                                return dynamic_cast<ConstantExpr*>( ce->get_arg() );
628                        }
629                }
630                return nullptr;
631        }
632
633        /// State to iteratively build a match of parameter expressions to arguments
634        struct ArgPack {
[452747a]635                std::size_t parent;                ///< Index of parent pack
[403b388]636                std::unique_ptr<Expression> expr;  ///< The argument stored here
637                Cost cost;                         ///< The cost of this argument
638                TypeEnvironment env;               ///< Environment for this pack
639                AssertionSet need;                 ///< Assertions outstanding for this pack
640                AssertionSet have;                 ///< Assertions found for this pack
641                OpenVarSet openVars;               ///< Open variables for this pack
642                unsigned nextArg;                  ///< Index of next argument in arguments list
643                unsigned tupleStart;               ///< Number of tuples that start at this index
[a8b27c6]644                unsigned nextExpl;                 ///< Index of next exploded element
645                unsigned explAlt;                  ///< Index of alternative for nextExpl > 0
[403b388]646
647                ArgPack()
[ad51cc2]648                        : parent(0), expr(), cost(Cost::zero), env(), need(), have(), openVars(), nextArg(0),
[a8b27c6]649                          tupleStart(0), nextExpl(0), explAlt(0) {}
[aeb75b1]650
[11094d9]651                ArgPack(const TypeEnvironment& env, const AssertionSet& need, const AssertionSet& have,
[aeb75b1]652                                const OpenVarSet& openVars)
[452747a]653                        : parent(0), expr(), cost(Cost::zero), env(env), need(need), have(have),
[a8b27c6]654                          openVars(openVars), nextArg(0), tupleStart(0), nextExpl(0), explAlt(0) {}
[11094d9]655
[452747a]656                ArgPack(std::size_t parent, Expression* expr, TypeEnvironment&& env, AssertionSet&& need,
657                                AssertionSet&& have, OpenVarSet&& openVars, unsigned nextArg,
[178e4ec]658                                unsigned tupleStart = 0, Cost cost = Cost::zero, unsigned nextExpl = 0,
[a8b27c6]659                                unsigned explAlt = 0 )
[452747a]660                        : parent(parent), expr(expr->clone()), cost(cost), env(move(env)), need(move(need)),
[403b388]661                          have(move(have)), openVars(move(openVars)), nextArg(nextArg), tupleStart(tupleStart),
[a8b27c6]662                          nextExpl(nextExpl), explAlt(explAlt) {}
[452747a]663
664                ArgPack(const ArgPack& o, TypeEnvironment&& env, AssertionSet&& need, AssertionSet&& have,
[73a5cadb]665                                OpenVarSet&& openVars, unsigned nextArg, Cost added )
[452747a]666                        : parent(o.parent), expr(o.expr ? o.expr->clone() : nullptr), cost(o.cost + added),
667                          env(move(env)), need(move(need)), have(move(have)), openVars(move(openVars)),
[a8b27c6]668                          nextArg(nextArg), tupleStart(o.tupleStart), nextExpl(0), explAlt(0) {}
[73a5cadb]669
[a8b27c6]670                /// true iff this pack is in the middle of an exploded argument
671                bool hasExpl() const { return nextExpl > 0; }
[aeb75b1]672
[a8b27c6]673                /// Gets the list of exploded alternatives for this pack
674                const ExplodedActual& getExpl( const ExplodedArgs& args ) const {
675                        return args[nextArg-1][explAlt];
676                }
[aeb75b1]677
678                /// Ends a tuple expression, consolidating the appropriate actuals
[403b388]679                void endTuple( const std::vector<ArgPack>& packs ) {
680                        // add all expressions in tuple to list, summing cost
[aeb75b1]681                        std::list<Expression*> exprs;
[403b388]682                        const ArgPack* pack = this;
683                        if ( expr ) { exprs.push_front( expr.release() ); }
684                        while ( pack->tupleStart == 0 ) {
685                                pack = &packs[pack->parent];
686                                exprs.push_front( pack->expr->clone() );
687                                cost += pack->cost;
[aeb75b1]688                        }
[403b388]689                        // reset pack to appropriate tuple
690                        expr.reset( new TupleExpr( exprs ) );
691                        tupleStart = pack->tupleStart - 1;
692                        parent = pack->parent;
[aeb75b1]693                }
[4b6ef70]694        };
[aeb75b1]695
696        /// Instantiates an argument to match a formal, returns false if no results left
[11094d9]697        bool instantiateArgument( Type* formalType, Initializer* initializer,
[178e4ec]698                        const ExplodedArgs& args, std::vector<ArgPack>& results, std::size_t& genStart,
[a8b27c6]699                        const SymTab::Indexer& indexer, unsigned nTuples = 0 ) {
[aeb75b1]700                if ( TupleType* tupleType = dynamic_cast<TupleType*>( formalType ) ) {
701                        // formalType is a TupleType - group actuals into a TupleExpr
[403b388]702                        ++nTuples;
[aeb75b1]703                        for ( Type* type : *tupleType ) {
704                                // xxx - dropping initializer changes behaviour from previous, but seems correct
[452747a]705                                if ( ! instantiateArgument(
706                                                type, nullptr, args, results, genStart, indexer, nTuples ) )
[aeb75b1]707                                        return false;
[403b388]708                                nTuples = 0;
709                        }
710                        // re-consititute tuples for final generation
711                        for ( auto i = genStart; i < results.size(); ++i ) {
712                                results[i].endTuple( results );
[aeb75b1]713                        }
714                        return true;
715                } else if ( TypeInstType* ttype = Tuples::isTtype( formalType ) ) {
716                        // formalType is a ttype, consumes all remaining arguments
717                        // xxx - mixing default arguments with variadic??
[403b388]718
719                        // completed tuples; will be spliced to end of results to finish
720                        std::vector<ArgPack> finalResults{};
721
[aeb75b1]722                        // iterate until all results completed
[403b388]723                        std::size_t genEnd;
724                        ++nTuples;
725                        do {
726                                genEnd = results.size();
727
[aeb75b1]728                                // add another argument to results
[403b388]729                                for ( std::size_t i = genStart; i < genEnd; ++i ) {
[a8b27c6]730                                        auto nextArg = results[i].nextArg;
[452747a]731
[62194cb]732                                        // use next element of exploded tuple if present
[a8b27c6]733                                        if ( results[i].hasExpl() ) {
734                                                const ExplodedActual& expl = results[i].getExpl( args );
[403b388]735
[a8b27c6]736                                                unsigned nextExpl = results[i].nextExpl + 1;
[62194cb]737                                                if ( nextExpl == expl.exprs.size() ) {
[a8b27c6]738                                                        nextExpl = 0;
739                                                }
[403b388]740
741                                                results.emplace_back(
[178e4ec]742                                                        i, expl.exprs[results[i].nextExpl].get(), copy(results[i].env),
743                                                        copy(results[i].need), copy(results[i].have),
744                                                        copy(results[i].openVars), nextArg, nTuples, Cost::zero, nextExpl,
[62194cb]745                                                        results[i].explAlt );
[452747a]746
[403b388]747                                                continue;
748                                        }
[452747a]749
[aeb75b1]750                                        // finish result when out of arguments
[a8b27c6]751                                        if ( nextArg >= args.size() ) {
[452747a]752                                                ArgPack newResult{
753                                                        results[i].env, results[i].need, results[i].have,
[403b388]754                                                        results[i].openVars };
[a8b27c6]755                                                newResult.nextArg = nextArg;
[403b388]756                                                Type* argType;
757
[7faab5e]758                                                if ( nTuples > 0 || ! results[i].expr ) {
[ad51cc2]759                                                        // first iteration or no expression to clone,
[7faab5e]760                                                        // push empty tuple expression
[403b388]761                                                        newResult.parent = i;
762                                                        std::list<Expression*> emptyList;
763                                                        newResult.expr.reset( new TupleExpr( emptyList ) );
764                                                        argType = newResult.expr->get_result();
[aeb75b1]765                                                } else {
[403b388]766                                                        // clone result to collect tuple
767                                                        newResult.parent = results[i].parent;
768                                                        newResult.cost = results[i].cost;
769                                                        newResult.tupleStart = results[i].tupleStart;
770                                                        newResult.expr.reset( results[i].expr->clone() );
771                                                        argType = newResult.expr->get_result();
772
773                                                        if ( results[i].tupleStart > 0 && Tuples::isTtype( argType ) ) {
[452747a]774                                                                // the case where a ttype value is passed directly is special,
[403b388]775                                                                // e.g. for argument forwarding purposes
[452747a]776                                                                // xxx - what if passing multiple arguments, last of which is
[403b388]777                                                                //       ttype?
[452747a]778                                                                // xxx - what would happen if unify was changed so that unifying
779                                                                //       tuple
780                                                                // types flattened both before unifying lists? then pass in
[403b388]781                                                                // TupleType (ttype) below.
782                                                                --newResult.tupleStart;
783                                                        } else {
784                                                                // collapse leftover arguments into tuple
785                                                                newResult.endTuple( results );
786                                                                argType = newResult.expr->get_result();
787                                                        }
[aeb75b1]788                                                }
[403b388]789
[aeb75b1]790                                                // check unification for ttype before adding to final
[452747a]791                                                if ( unify( ttype, argType, newResult.env, newResult.need, newResult.have,
[403b388]792                                                                newResult.openVars, indexer ) ) {
793                                                        finalResults.push_back( move(newResult) );
[aeb75b1]794                                                }
[452747a]795
[aeb75b1]796                                                continue;
797                                        }
798
799                                        // add each possible next argument
[a8b27c6]800                                        for ( std::size_t j = 0; j < args[nextArg].size(); ++j ) {
801                                                const ExplodedActual& expl = args[nextArg][j];
[178e4ec]802
[403b388]803                                                // fresh copies of parent parameters for this iteration
804                                                TypeEnvironment env = results[i].env;
805                                                OpenVarSet openVars = results[i].openVars;
806
[a8b27c6]807                                                env.addActual( expl.env, openVars );
[11094d9]808
[a8b27c6]809                                                // skip empty tuple arguments by (near-)cloning parent into next gen
[62194cb]810                                                if ( expl.exprs.empty() ) {
[73a5cadb]811                                                        results.emplace_back(
[452747a]812                                                                results[i], move(env), copy(results[i].need),
[a8b27c6]813                                                                copy(results[i].have), move(openVars), nextArg + 1, expl.cost );
[452747a]814
[403b388]815                                                        continue;
[4b6ef70]816                                                }
[11094d9]817
[403b388]818                                                // add new result
819                                                results.emplace_back(
[178e4ec]820                                                        i, expl.exprs.front().get(), move(env), copy(results[i].need),
821                                                        copy(results[i].have), move(openVars), nextArg + 1,
[62194cb]822                                                        nTuples, expl.cost, expl.exprs.size() == 1 ? 0 : 1, j );
[aeb75b1]823                                        }
824                                }
825
826                                // reset for next round
[403b388]827                                genStart = genEnd;
828                                nTuples = 0;
829                        } while ( genEnd != results.size() );
830
831                        // splice final results onto results
832                        for ( std::size_t i = 0; i < finalResults.size(); ++i ) {
833                                results.push_back( move(finalResults[i]) );
[aeb75b1]834                        }
[403b388]835                        return ! finalResults.empty();
[aeb75b1]836                }
[11094d9]837
[aeb75b1]838                // iterate each current subresult
[403b388]839                std::size_t genEnd = results.size();
840                for ( std::size_t i = genStart; i < genEnd; ++i ) {
[a8b27c6]841                        auto nextArg = results[i].nextArg;
842
[403b388]843                        // use remainder of exploded tuple if present
[a8b27c6]844                        if ( results[i].hasExpl() ) {
845                                const ExplodedActual& expl = results[i].getExpl( args );
[62194cb]846                                Expression* expr = expl.exprs[results[i].nextExpl].get();
[452747a]847
[403b388]848                                TypeEnvironment env = results[i].env;
849                                AssertionSet need = results[i].need, have = results[i].have;
850                                OpenVarSet openVars = results[i].openVars;
[4b6ef70]851
[62194cb]852                                Type* actualType = expr->get_result();
[4b6ef70]853
854                                PRINT(
855                                        std::cerr << "formal type is ";
856                                        formalType->print( std::cerr );
857                                        std::cerr << std::endl << "actual type is ";
858                                        actualType->print( std::cerr );
859                                        std::cerr << std::endl;
860                                )
[11094d9]861
[403b388]862                                if ( unify( formalType, actualType, env, need, have, openVars, indexer ) ) {
[a8b27c6]863                                        unsigned nextExpl = results[i].nextExpl + 1;
[62194cb]864                                        if ( nextExpl == expl.exprs.size() ) {
[a8b27c6]865                                                nextExpl = 0;
866                                        }
[178e4ec]867
[452747a]868                                        results.emplace_back(
[178e4ec]869                                                i, expr, move(env), move(need), move(have), move(openVars), nextArg,
[62194cb]870                                                nTuples, Cost::zero, nextExpl, results[i].explAlt );
[4b6ef70]871                                }
872
873                                continue;
[403b388]874                        }
[452747a]875
[403b388]876                        // use default initializers if out of arguments
[a8b27c6]877                        if ( nextArg >= args.size() ) {
[aeb75b1]878                                if ( ConstantExpr* cnstExpr = getDefaultValue( initializer ) ) {
879                                        if ( Constant* cnst = dynamic_cast<Constant*>( cnstExpr->get_constant() ) ) {
[403b388]880                                                TypeEnvironment env = results[i].env;
881                                                AssertionSet need = results[i].need, have = results[i].have;
882                                                OpenVarSet openVars = results[i].openVars;
883
[452747a]884                                                if ( unify( formalType, cnst->get_type(), env, need, have, openVars,
[403b388]885                                                                indexer ) ) {
886                                                        results.emplace_back(
[452747a]887                                                                i, cnstExpr, move(env), move(need), move(have),
[a8b27c6]888                                                                move(openVars), nextArg, nTuples );
[aeb75b1]889                                                }
890                                        }
891                                }
[403b388]892
[aeb75b1]893                                continue;
894                        }
895
896                        // Check each possible next argument
[a8b27c6]897                        for ( std::size_t j = 0; j < args[nextArg].size(); ++j ) {
898                                const ExplodedActual& expl = args[nextArg][j];
899
[403b388]900                                // fresh copies of parent parameters for this iteration
901                                TypeEnvironment env = results[i].env;
902                                AssertionSet need = results[i].need, have = results[i].have;
903                                OpenVarSet openVars = results[i].openVars;
904
[a8b27c6]905                                env.addActual( expl.env, openVars );
[4b6ef70]906
[a8b27c6]907                                // skip empty tuple arguments by (near-)cloning parent into next gen
[62194cb]908                                if ( expl.exprs.empty() ) {
[73a5cadb]909                                        results.emplace_back(
[178e4ec]910                                                results[i], move(env), move(need), move(have), move(openVars),
[a8b27c6]911                                                nextArg + 1, expl.cost );
[73a5cadb]912
[4b6ef70]913                                        continue;
914                                }
[aeb75b1]915
[4b6ef70]916                                // consider only first exploded actual
[62194cb]917                                Expression* expr = expl.exprs.front().get();
918                                Type* actualType = expr->get_result()->clone();
[a585396]919
[4b6ef70]920                                PRINT(
921                                        std::cerr << "formal type is ";
922                                        formalType->print( std::cerr );
923                                        std::cerr << std::endl << "actual type is ";
924                                        actualType->print( std::cerr );
925                                        std::cerr << std::endl;
926                                )
[aeb75b1]927
[4b6ef70]928                                // attempt to unify types
[403b388]929                                if ( unify( formalType, actualType, env, need, have, openVars, indexer ) ) {
930                                        // add new result
931                                        results.emplace_back(
[178e4ec]932                                                i, expr, move(env), move(need), move(have), move(openVars), nextArg + 1,
[62194cb]933                                                nTuples, expl.cost, expl.exprs.size() == 1 ? 0 : 1, j );
[4b6ef70]934                                }
[aeb75b1]935                        }
936                }
937
938                // reset for next parameter
[403b388]939                genStart = genEnd;
[11094d9]940
[403b388]941                return genEnd != results.size();
942        }
943
944        template<typename OutputIterator>
[13deae88]945        void AlternativeFinder::Finder::validateFunctionAlternative( const Alternative &func, ArgPack& result,
[403b388]946                        const std::vector<ArgPack>& results, OutputIterator out ) {
947                ApplicationExpr *appExpr = new ApplicationExpr( func.expr->clone() );
948                // sum cost and accumulate actuals
949                std::list<Expression*>& args = appExpr->get_args();
[8a62d04]950                Cost cost = func.cost;
[403b388]951                const ArgPack* pack = &result;
952                while ( pack->expr ) {
953                        args.push_front( pack->expr->clone() );
954                        cost += pack->cost;
955                        pack = &results[pack->parent];
956                }
957                // build and validate new alternative
958                Alternative newAlt( appExpr, result.env, cost );
959                PRINT(
960                        std::cerr << "instantiate function success: " << appExpr << std::endl;
961                        std::cerr << "need assertions:" << std::endl;
962                        printAssertionSet( result.need, std::cerr, 8 );
963                )
964                inferParameters( result.need, result.have, newAlt, result.openVars, out );
[11094d9]965        }
[aeb75b1]966
967        template<typename OutputIterator>
[13deae88]968        void AlternativeFinder::Finder::makeFunctionAlternatives( const Alternative &func,
[a8b27c6]969                        FunctionType *funcType, const ExplodedArgs &args, OutputIterator out ) {
[aeb75b1]970                OpenVarSet funcOpenVars;
971                AssertionSet funcNeed, funcHave;
[3f7e12cb]972                TypeEnvironment funcEnv( func.env );
[aeb75b1]973                makeUnifiableVars( funcType, funcOpenVars, funcNeed );
[11094d9]974                // add all type variables as open variables now so that those not used in the parameter
[aeb75b1]975                // list are still considered open.
976                funcEnv.add( funcType->get_forall() );
[11094d9]977
[53e3b4a]978                if ( targetType && ! targetType->isVoid() && ! funcType->get_returnVals().empty() ) {
[ea83e00a]979                        // attempt to narrow based on expected target type
980                        Type * returnType = funcType->get_returnVals().front()->get_type();
[11094d9]981                        if ( ! unify( returnType, targetType, funcEnv, funcNeed, funcHave, funcOpenVars,
[aeb75b1]982                                        indexer ) ) {
983                                // unification failed, don't pursue this function alternative
[ea83e00a]984                                return;
985                        }
986                }
987
[aeb75b1]988                // iteratively build matches, one parameter at a time
[403b388]989                std::vector<ArgPack> results;
990                results.push_back( ArgPack{ funcEnv, funcNeed, funcHave, funcOpenVars } );
991                std::size_t genStart = 0;
992
[aeb75b1]993                for ( DeclarationWithType* formal : funcType->get_parameters() ) {
994                        ObjectDecl* obj = strict_dynamic_cast< ObjectDecl* >( formal );
[11094d9]995                        if ( ! instantiateArgument(
[403b388]996                                        obj->get_type(), obj->get_init(), args, results, genStart, indexer ) )
[aeb75b1]997                                return;
998                }
999
1000                if ( funcType->get_isVarArgs() ) {
[403b388]1001                        // append any unused arguments to vararg pack
1002                        std::size_t genEnd;
1003                        do {
1004                                genEnd = results.size();
1005
1006                                // iterate results
1007                                for ( std::size_t i = genStart; i < genEnd; ++i ) {
[a8b27c6]1008                                        auto nextArg = results[i].nextArg;
[452747a]1009
[403b388]1010                                        // use remainder of exploded tuple if present
[a8b27c6]1011                                        if ( results[i].hasExpl() ) {
1012                                                const ExplodedActual& expl = results[i].getExpl( args );
[403b388]1013
[a8b27c6]1014                                                unsigned nextExpl = results[i].nextExpl + 1;
[62194cb]1015                                                if ( nextExpl == expl.exprs.size() ) {
[a8b27c6]1016                                                        nextExpl = 0;
1017                                                }
[403b388]1018
1019                                                results.emplace_back(
[178e4ec]1020                                                        i, expl.exprs[results[i].nextExpl].get(), copy(results[i].env),
1021                                                        copy(results[i].need), copy(results[i].have),
1022                                                        copy(results[i].openVars), nextArg, 0, Cost::zero, nextExpl,
[62194cb]1023                                                        results[i].explAlt );
[452747a]1024
[403b388]1025                                                continue;
1026                                        }
1027
1028                                        // finish result when out of arguments
[a8b27c6]1029                                        if ( nextArg >= args.size() ) {
[403b388]1030                                                validateFunctionAlternative( func, results[i], results, out );
[fae6f21]1031
[aeb75b1]1032                                                continue;
1033                                        }
1034
1035                                        // add each possible next argument
[a8b27c6]1036                                        for ( std::size_t j = 0; j < args[nextArg].size(); ++j ) {
1037                                                const ExplodedActual& expl = args[nextArg][j];
1038
[403b388]1039                                                // fresh copies of parent parameters for this iteration
1040                                                TypeEnvironment env = results[i].env;
1041                                                OpenVarSet openVars = results[i].openVars;
1042
[a8b27c6]1043                                                env.addActual( expl.env, openVars );
[d551d0a]1044
[a8b27c6]1045                                                // skip empty tuple arguments by (near-)cloning parent into next gen
[62194cb]1046                                                if ( expl.exprs.empty() ) {
[452747a]1047                                                        results.emplace_back(
1048                                                                results[i], move(env), copy(results[i].need),
[a8b27c6]1049                                                                copy(results[i].have), move(openVars), nextArg + 1, expl.cost );
[178e4ec]1050
[403b388]1051                                                        continue;
1052                                                }
[d551d0a]1053
[403b388]1054                                                // add new result
1055                                                results.emplace_back(
[178e4ec]1056                                                        i, expl.exprs.front().get(), move(env), copy(results[i].need),
1057                                                        copy(results[i].have), move(openVars), nextArg + 1, 0,
[62194cb]1058                                                        expl.cost, expl.exprs.size() == 1 ? 0 : 1, j );
[aeb75b1]1059                                        }
1060                                }
1061
[403b388]1062                                genStart = genEnd;
1063                        } while ( genEnd != results.size() );
[aeb75b1]1064                } else {
1065                        // filter out results that don't use all the arguments
[403b388]1066                        for ( std::size_t i = genStart; i < results.size(); ++i ) {
1067                                ArgPack& result = results[i];
[a8b27c6]1068                                if ( ! result.hasExpl() && result.nextArg >= args.size() ) {
[403b388]1069                                        validateFunctionAlternative( func, result, results, out );
[aeb75b1]1070                                }
1071                        }
1072                }
[d9a0e76]1073        }
1074
[13deae88]1075        void AlternativeFinder::Finder::postvisit( UntypedExpr *untypedExpr ) {
[6ccfb7f]1076                AlternativeFinder funcFinder( indexer, env );
[a32b204]1077                funcFinder.findWithAdjustment( untypedExpr->get_function() );
[6ccfb7f]1078                // if there are no function alternatives, then proceeding is a waste of time.
1079                if ( funcFinder.alternatives.empty() ) return;
1080
[aeb75b1]1081                std::vector< AlternativeFinder > argAlternatives;
[13deae88]1082                altFinder.findSubExprs( untypedExpr->begin_args(), untypedExpr->end_args(),
[aeb75b1]1083                        back_inserter( argAlternatives ) );
[d9a0e76]1084
[5af62f1]1085                // take care of possible tuple assignments
1086                // if not tuple assignment, assignment is taken care of as a normal function call
[13deae88]1087                Tuples::handleTupleAssignment( altFinder, untypedExpr, argAlternatives );
[c43c171]1088
[6ccfb7f]1089                // find function operators
[4e66a18]1090                static NameExpr *opExpr = new NameExpr( "?()" );
[6ccfb7f]1091                AlternativeFinder funcOpFinder( indexer, env );
[4e66a18]1092                // it's ok if there aren't any defined function ops
1093                funcOpFinder.maybeFind( opExpr);
[6ccfb7f]1094                PRINT(
1095                        std::cerr << "known function ops:" << std::endl;
[50377a4]1096                        printAlts( funcOpFinder.alternatives, std::cerr, 1 );
[6ccfb7f]1097                )
1098
[a8b27c6]1099                // pre-explode arguments
1100                ExplodedArgs argExpansions;
1101                argExpansions.reserve( argAlternatives.size() );
1102
1103                for ( const AlternativeFinder& arg : argAlternatives ) {
1104                        argExpansions.emplace_back();
1105                        auto& argE = argExpansions.back();
1106                        argE.reserve( arg.alternatives.size() );
[178e4ec]1107
[a8b27c6]1108                        for ( const Alternative& actual : arg ) {
1109                                argE.emplace_back( actual, indexer );
1110                        }
1111                }
1112
[a32b204]1113                AltList candidates;
[a16764a6]1114                SemanticErrorException errors;
[b1bead1]1115                for ( AltList::iterator func = funcFinder.alternatives.begin(); func != funcFinder.alternatives.end(); ++func ) {
[91b8a17]1116                        try {
1117                                PRINT(
1118                                        std::cerr << "working on alternative: " << std::endl;
1119                                        func->print( std::cerr, 8 );
1120                                )
1121                                // check if the type is pointer to function
[b1bead1]1122                                if ( PointerType *pointer = dynamic_cast< PointerType* >( func->expr->get_result()->stripReferences() ) ) {
[91b8a17]1123                                        if ( FunctionType *function = dynamic_cast< FunctionType* >( pointer->get_base() ) ) {
[326338ae]1124                                                Alternative newFunc( *func );
[a181494]1125                                                referenceToRvalueConversion( newFunc.expr, newFunc.cost );
[a8b27c6]1126                                                makeFunctionAlternatives( newFunc, function, argExpansions,
[aeb75b1]1127                                                        std::back_inserter( candidates ) );
[b1bead1]1128                                        }
1129                                } else if ( TypeInstType *typeInst = dynamic_cast< TypeInstType* >( func->expr->get_result()->stripReferences() ) ) { // handle ftype (e.g. *? on function pointer)
1130                                        EqvClass eqvClass;
1131                                        if ( func->env.lookup( typeInst->get_name(), eqvClass ) && eqvClass.type ) {
1132                                                if ( FunctionType *function = dynamic_cast< FunctionType* >( eqvClass.type ) ) {
[326338ae]1133                                                        Alternative newFunc( *func );
[a181494]1134                                                        referenceToRvalueConversion( newFunc.expr, newFunc.cost );
[a8b27c6]1135                                                        makeFunctionAlternatives( newFunc, function, argExpansions,
[aeb75b1]1136                                                                std::back_inserter( candidates ) );
[a32b204]1137                                                } // if
1138                                        } // if
[11094d9]1139                                }
[a16764a6]1140                        } catch ( SemanticErrorException &e ) {
[91b8a17]1141                                errors.append( e );
1142                        }
[a32b204]1143                } // for
1144
[aeb75b1]1145                // try each function operator ?() with each function alternative
1146                if ( ! funcOpFinder.alternatives.empty() ) {
[a8b27c6]1147                        // add exploded function alternatives to front of argument list
1148                        std::vector<ExplodedActual> funcE;
1149                        funcE.reserve( funcFinder.alternatives.size() );
1150                        for ( const Alternative& actual : funcFinder ) {
1151                                funcE.emplace_back( actual, indexer );
1152                        }
1153                        argExpansions.insert( argExpansions.begin(), move(funcE) );
[aeb75b1]1154
1155                        for ( AltList::iterator funcOp = funcOpFinder.alternatives.begin();
1156                                        funcOp != funcOpFinder.alternatives.end(); ++funcOp ) {
1157                                try {
1158                                        // check if type is a pointer to function
[11094d9]1159                                        if ( PointerType* pointer = dynamic_cast<PointerType*>(
[aeb75b1]1160                                                        funcOp->expr->get_result()->stripReferences() ) ) {
[11094d9]1161                                                if ( FunctionType* function =
[aeb75b1]1162                                                                dynamic_cast<FunctionType*>( pointer->get_base() ) ) {
1163                                                        Alternative newFunc( *funcOp );
[a181494]1164                                                        referenceToRvalueConversion( newFunc.expr, newFunc.cost );
[a8b27c6]1165                                                        makeFunctionAlternatives( newFunc, function, argExpansions,
[aeb75b1]1166                                                                std::back_inserter( candidates ) );
1167                                                }
1168                                        }
[a16764a6]1169                                } catch ( SemanticErrorException &e ) {
[aeb75b1]1170                                        errors.append( e );
1171                                }
1172                        }
1173                }
1174
[91b8a17]1175                // Implement SFINAE; resolution errors are only errors if there aren't any non-erroneous resolutions
1176                if ( candidates.empty() && ! errors.isEmpty() ) { throw errors; }
1177
[4b0f997]1178                // compute conversionsion costs
[bd4f2e9]1179                for ( Alternative& withFunc : candidates ) {
1180                        Cost cvtCost = computeApplicationConversionCost( withFunc, indexer );
[a32b204]1181
1182                        PRINT(
[bd4f2e9]1183                                ApplicationExpr *appExpr = strict_dynamic_cast< ApplicationExpr* >( withFunc.expr );
[e3e16bc]1184                                PointerType *pointer = strict_dynamic_cast< PointerType* >( appExpr->get_function()->get_result() );
1185                                FunctionType *function = strict_dynamic_cast< FunctionType* >( pointer->get_base() );
[a61ad31]1186                                std::cerr << "Case +++++++++++++ " << appExpr->get_function() << std::endl;
[6ed1d4b]1187                                std::cerr << "formals are:" << std::endl;
1188                                printAll( function->get_parameters(), std::cerr, 8 );
1189                                std::cerr << "actuals are:" << std::endl;
1190                                printAll( appExpr->get_args(), std::cerr, 8 );
1191                                std::cerr << "bindings are:" << std::endl;
[bd4f2e9]1192                                withFunc.env.print( std::cerr, 8 );
[6ed1d4b]1193                                std::cerr << "cost of conversion is:" << cvtCost << std::endl;
[7c64920]1194                        )
1195                        if ( cvtCost != Cost::infinity ) {
[bd4f2e9]1196                                withFunc.cvtCost = cvtCost;
1197                                alternatives.push_back( withFunc );
[7c64920]1198                        } // if
[a32b204]1199                } // for
[4b0f997]1200
[bd4f2e9]1201                candidates = move(alternatives);
[a32b204]1202
[11094d9]1203                // use a new list so that alternatives are not examined by addAnonConversions twice.
1204                AltList winners;
1205                findMinCost( candidates.begin(), candidates.end(), std::back_inserter( winners ) );
[ea83e00a]1206
[452747a]1207                // function may return struct or union value, in which case we need to add alternatives
1208                // for implicitconversions to each of the anonymous members, must happen after findMinCost
[bd4f2e9]1209                // since anon conversions are never the cheapest expression
[11094d9]1210                for ( const Alternative & alt : winners ) {
[ca946a4]1211                        addAnonConversions( alt );
1212                }
[bd4f2e9]1213                spliceBegin( alternatives, winners );
[ca946a4]1214
[ea83e00a]1215                if ( alternatives.empty() && targetType && ! targetType->isVoid() ) {
1216                        // xxx - this is a temporary hack. If resolution is unsuccessful with a target type, try again without a
1217                        // target type, since it will sometimes succeed when it wouldn't easily with target type binding. For example,
1218                        //   forall( otype T ) lvalue T ?[?]( T *, ptrdiff_t );
1219                        //   const char * x = "hello world";
1220                        //   unsigned char ch = x[0];
1221                        // Fails with simple return type binding. First, T is bound to unsigned char, then (x: const char *) is unified
1222                        // with unsigned char *, which fails because pointer base types must be unified exactly. The new resolver should
1223                        // fix this issue in a more robust way.
1224                        targetType = nullptr;
[13deae88]1225                        postvisit( untypedExpr );
[ea83e00a]1226                }
[a32b204]1227        }
1228
1229        bool isLvalue( Expression *expr ) {
[906e24d]1230                // xxx - recurse into tuples?
[d29fa5f]1231                return expr->result && ( expr->get_result()->get_lvalue() || dynamic_cast< ReferenceType * >( expr->get_result() ) );
[a32b204]1232        }
1233
[13deae88]1234        void AlternativeFinder::Finder::postvisit( AddressExpr *addressExpr ) {
[a32b204]1235                AlternativeFinder finder( indexer, env );
1236                finder.find( addressExpr->get_arg() );
[bd4f2e9]1237                for ( Alternative& alt : finder.alternatives ) {
1238                        if ( isLvalue( alt.expr ) ) {
[452747a]1239                                alternatives.push_back(
[bd4f2e9]1240                                        Alternative{ new AddressExpr( alt.expr->clone() ), alt.env, alt.cost } );
[a32b204]1241                        } // if
1242                } // for
1243        }
1244
[13deae88]1245        void AlternativeFinder::Finder::postvisit( LabelAddressExpr * expr ) {
[bd4f2e9]1246                alternatives.push_back( Alternative{ expr->clone(), env, Cost::zero } );
[5809461]1247        }
1248
[c0bf94e]1249        Expression * restructureCast( Expression * argExpr, Type * toType, bool isGenerated ) {
[e6cee92]1250                if ( argExpr->get_result()->size() > 1 && ! toType->isVoid() && ! dynamic_cast<ReferenceType *>( toType ) ) {
1251                        // Argument expression is a tuple and the target type is not void and not a reference type.
1252                        // Cast each member of the tuple to its corresponding target type, producing the tuple of those
1253                        // cast expressions. If there are more components of the tuple than components in the target type,
1254                        // then excess components do not come out in the result expression (but UniqueExprs ensure that
1255                        // side effects will still be done).
[5ccb10d]1256                        if ( Tuples::maybeImpureIgnoreUnique( argExpr ) ) {
[62423350]1257                                // expressions which may contain side effects require a single unique instance of the expression.
1258                                argExpr = new UniqueExpr( argExpr );
1259                        }
1260                        std::list< Expression * > componentExprs;
1261                        for ( unsigned int i = 0; i < toType->size(); i++ ) {
1262                                // cast each component
1263                                TupleIndexExpr * idx = new TupleIndexExpr( argExpr->clone(), i );
[c0bf94e]1264                                componentExprs.push_back( restructureCast( idx, toType->getComponent( i ), isGenerated ) );
[62423350]1265                        }
1266                        delete argExpr;
1267                        assert( componentExprs.size() > 0 );
1268                        // produce the tuple of casts
1269                        return new TupleExpr( componentExprs );
1270                } else {
1271                        // handle normally
[c0bf94e]1272                        CastExpr * ret = new CastExpr( argExpr, toType->clone() );
1273                        ret->isGenerated = isGenerated;
1274                        return ret;
[62423350]1275                }
1276        }
1277
[13deae88]1278        void AlternativeFinder::Finder::postvisit( CastExpr *castExpr ) {
[906e24d]1279                Type *& toType = castExpr->get_result();
[7933351]1280                assert( toType );
[906e24d]1281                toType = resolveTypeof( toType, indexer );
1282                SymTab::validateType( toType, &indexer );
1283                adjustExprType( toType, env, indexer );
[a32b204]1284
1285                AlternativeFinder finder( indexer, env );
[7933351]1286                finder.targetType = toType;
[95642c9]1287                finder.findWithAdjustment( castExpr->arg );
[a32b204]1288
1289                AltList candidates;
[452747a]1290                for ( Alternative & alt : finder.alternatives ) {
[a32b204]1291                        AssertionSet needAssertions, haveAssertions;
1292                        OpenVarSet openVars;
1293
1294                        // It's possible that a cast can throw away some values in a multiply-valued expression.  (An example is a
1295                        // cast-to-void, which casts from one value to zero.)  Figure out the prefix of the subexpression results
1296                        // that are cast directly.  The candidate is invalid if it has fewer results than there are types to cast
1297                        // to.
[95642c9]1298                        int discardedValues = alt.expr->result->size() - castExpr->result->size();
[a32b204]1299                        if ( discardedValues < 0 ) continue;
[7933351]1300                        // xxx - may need to go into tuple types and extract relevant types and use unifyList. Note that currently, this does not
1301                        // allow casting a tuple to an atomic type (e.g. (int)([1, 2, 3]))
[adcdd2f]1302                        // unification run for side-effects
[95642c9]1303                        unify( castExpr->result, alt.expr->result, alt.env, needAssertions,
[bd4f2e9]1304                                haveAssertions, openVars, indexer );
[95642c9]1305                        Cost thisCost = castCost( alt.expr->result, castExpr->result, indexer,
[bd4f2e9]1306                                alt.env );
[7e4c4f4]1307                        PRINT(
1308                                std::cerr << "working on cast with result: " << castExpr->result << std::endl;
[452747a]1309                                std::cerr << "and expr type: " << alt.expr->result << std::endl;
1310                                std::cerr << "env: " << alt.env << std::endl;
[7e4c4f4]1311                        )
[a32b204]1312                        if ( thisCost != Cost::infinity ) {
[7e4c4f4]1313                                PRINT(
1314                                        std::cerr << "has finite cost." << std::endl;
1315                                )
[a32b204]1316                                // count one safe conversion for each value that is thrown away
[89be1c68]1317                                thisCost.incSafe( discardedValues );
[c0bf94e]1318                                Alternative newAlt( restructureCast( alt.expr->clone(), toType, castExpr->isGenerated ), alt.env,
[bd4f2e9]1319                                        alt.cost, thisCost );
[452747a]1320                                inferParameters( needAssertions, haveAssertions, newAlt, openVars,
[bd4f2e9]1321                                        back_inserter( candidates ) );
[a32b204]1322                        } // if
1323                } // for
1324
1325                // findMinCost selects the alternatives with the lowest "cost" members, but has the side effect of copying the
1326                // cvtCost member to the cost member (since the old cost is now irrelevant).  Thus, calling findMinCost twice
1327                // selects first based on argument cost, then on conversion cost.
1328                AltList minArgCost;
1329                findMinCost( candidates.begin(), candidates.end(), std::back_inserter( minArgCost ) );
1330                findMinCost( minArgCost.begin(), minArgCost.end(), std::back_inserter( alternatives ) );
1331        }
1332
[13deae88]1333        void AlternativeFinder::Finder::postvisit( VirtualCastExpr * castExpr ) {
[a5f0529]1334                assertf( castExpr->get_result(), "Implicate virtual cast targets not yet supported." );
1335                AlternativeFinder finder( indexer, env );
1336                // don't prune here, since it's guaranteed all alternatives will have the same type
[4e66a18]1337                finder.findWithoutPrune( castExpr->get_arg() );
[a5f0529]1338                for ( Alternative & alt : finder.alternatives ) {
1339                        alternatives.push_back( Alternative(
1340                                new VirtualCastExpr( alt.expr->clone(), castExpr->get_result()->clone() ),
1341                                alt.env, alt.cost ) );
1342                }
1343        }
1344
[13deae88]1345        void AlternativeFinder::Finder::postvisit( UntypedMemberExpr *memberExpr ) {
[a32b204]1346                AlternativeFinder funcFinder( indexer, env );
1347                funcFinder.findWithAdjustment( memberExpr->get_aggregate() );
1348                for ( AltList::const_iterator agg = funcFinder.alternatives.begin(); agg != funcFinder.alternatives.end(); ++agg ) {
[a61ad31]1349                        // it's okay for the aggregate expression to have reference type -- cast it to the base type to treat the aggregate as the referenced value
[a181494]1350                        Cost cost = agg->cost;
1351                        Expression * aggrExpr = agg->expr->clone();
1352                        referenceToRvalueConversion( aggrExpr, cost );
1353                        std::unique_ptr<Expression> guard( aggrExpr );
1354
[a61ad31]1355                        // find member of the given type
1356                        if ( StructInstType *structInst = dynamic_cast< StructInstType* >( aggrExpr->get_result() ) ) {
[a181494]1357                                addAggMembers( structInst, aggrExpr, cost, agg->env, memberExpr->get_member() );
[a61ad31]1358                        } else if ( UnionInstType *unionInst = dynamic_cast< UnionInstType* >( aggrExpr->get_result() ) ) {
[a181494]1359                                addAggMembers( unionInst, aggrExpr, cost, agg->env, memberExpr->get_member() );
[a61ad31]1360                        } else if ( TupleType * tupleType = dynamic_cast< TupleType * >( aggrExpr->get_result() ) ) {
[a181494]1361                                addTupleMembers( tupleType, aggrExpr, cost, agg->env, memberExpr->get_member() );
[a32b204]1362                        } // if
1363                } // for
1364        }
1365
[13deae88]1366        void AlternativeFinder::Finder::postvisit( MemberExpr *memberExpr ) {
[a32b204]1367                alternatives.push_back( Alternative( memberExpr->clone(), env, Cost::zero ) );
1368        }
1369
[13deae88]1370        void AlternativeFinder::Finder::postvisit( NameExpr *nameExpr ) {
[a40d503]1371                std::list< SymTab::Indexer::IdData > declList;
[490ff5c3]1372                indexer.lookupId( nameExpr->name, declList );
1373                PRINT( std::cerr << "nameExpr is " << nameExpr->name << std::endl; )
[a40d503]1374                for ( auto & data : declList ) {
[a181494]1375                        Cost cost = Cost::zero;
1376                        Expression * newExpr = data.combine( cost );
[54043f4]1377                        alternatives.push_back( Alternative( newExpr, env, Cost::zero, cost ) );
[0f19d763]1378                        PRINT(
1379                                std::cerr << "decl is ";
[a40d503]1380                                data.id->print( std::cerr );
[0f19d763]1381                                std::cerr << std::endl;
1382                                std::cerr << "newExpr is ";
[a40d503]1383                                newExpr->print( std::cerr );
[0f19d763]1384                                std::cerr << std::endl;
[7c64920]1385                        )
[0f19d763]1386                        renameTypes( alternatives.back().expr );
[4b0f997]1387                        addAnonConversions( alternatives.back() ); // add anonymous member interpretations whenever an aggregate value type is seen as a name expression.
[0f19d763]1388                } // for
[a32b204]1389        }
1390
[13deae88]1391        void AlternativeFinder::Finder::postvisit( VariableExpr *variableExpr ) {
[85517ddb]1392                // not sufficient to clone here, because variable's type may have changed
1393                // since the VariableExpr was originally created.
[490ff5c3]1394                alternatives.push_back( Alternative( new VariableExpr( variableExpr->var ), env, Cost::zero ) );
[a32b204]1395        }
1396
[13deae88]1397        void AlternativeFinder::Finder::postvisit( ConstantExpr *constantExpr ) {
[a32b204]1398                alternatives.push_back( Alternative( constantExpr->clone(), env, Cost::zero ) );
1399        }
1400
[13deae88]1401        void AlternativeFinder::Finder::postvisit( SizeofExpr *sizeofExpr ) {
[a32b204]1402                if ( sizeofExpr->get_isType() ) {
[322b97e]1403                        Type * newType = sizeofExpr->get_type()->clone();
1404                        alternatives.push_back( Alternative( new SizeofExpr( resolveTypeof( newType, indexer ) ), env, Cost::zero ) );
[a32b204]1405                } else {
1406                        // find all alternatives for the argument to sizeof
1407                        AlternativeFinder finder( indexer, env );
1408                        finder.find( sizeofExpr->get_expr() );
1409                        // find the lowest cost alternative among the alternatives, otherwise ambiguous
1410                        AltList winners;
1411                        findMinCost( finder.alternatives.begin(), finder.alternatives.end(), back_inserter( winners ) );
1412                        if ( winners.size() != 1 ) {
[a16764a6]1413                                SemanticError( sizeofExpr->get_expr(), "Ambiguous expression in sizeof operand: " );
[a32b204]1414                        } // if
1415                        // return the lowest cost alternative for the argument
1416                        Alternative &choice = winners.front();
[a181494]1417                        referenceToRvalueConversion( choice.expr, choice.cost );
[a32b204]1418                        alternatives.push_back( Alternative( new SizeofExpr( choice.expr->clone() ), choice.env, Cost::zero ) );
[47534159]1419                } // if
1420        }
1421
[13deae88]1422        void AlternativeFinder::Finder::postvisit( AlignofExpr *alignofExpr ) {
[47534159]1423                if ( alignofExpr->get_isType() ) {
[322b97e]1424                        Type * newType = alignofExpr->get_type()->clone();
1425                        alternatives.push_back( Alternative( new AlignofExpr( resolveTypeof( newType, indexer ) ), env, Cost::zero ) );
[47534159]1426                } else {
1427                        // find all alternatives for the argument to sizeof
1428                        AlternativeFinder finder( indexer, env );
1429                        finder.find( alignofExpr->get_expr() );
1430                        // find the lowest cost alternative among the alternatives, otherwise ambiguous
1431                        AltList winners;
1432                        findMinCost( finder.alternatives.begin(), finder.alternatives.end(), back_inserter( winners ) );
1433                        if ( winners.size() != 1 ) {
[a16764a6]1434                                SemanticError( alignofExpr->get_expr(), "Ambiguous expression in alignof operand: " );
[47534159]1435                        } // if
1436                        // return the lowest cost alternative for the argument
1437                        Alternative &choice = winners.front();
[a181494]1438                        referenceToRvalueConversion( choice.expr, choice.cost );
[47534159]1439                        alternatives.push_back( Alternative( new AlignofExpr( choice.expr->clone() ), choice.env, Cost::zero ) );
[a32b204]1440                } // if
1441        }
1442
[2a4b088]1443        template< typename StructOrUnionType >
[13deae88]1444        void AlternativeFinder::Finder::addOffsetof( StructOrUnionType *aggInst, const std::string &name ) {
[2a4b088]1445                std::list< Declaration* > members;
1446                aggInst->lookup( name, members );
1447                for ( std::list< Declaration* >::const_iterator i = members.begin(); i != members.end(); ++i ) {
1448                        if ( DeclarationWithType *dwt = dynamic_cast< DeclarationWithType* >( *i ) ) {
[79970ed]1449                                alternatives.push_back( Alternative( new OffsetofExpr( aggInst->clone(), dwt ), env, Cost::zero ) );
[2a4b088]1450                                renameTypes( alternatives.back().expr );
1451                        } else {
1452                                assert( false );
1453                        }
1454                }
1455        }
[6ed1d4b]1456
[13deae88]1457        void AlternativeFinder::Finder::postvisit( UntypedOffsetofExpr *offsetofExpr ) {
[2a4b088]1458                AlternativeFinder funcFinder( indexer, env );
[85517ddb]1459                // xxx - resolveTypeof?
[2a4b088]1460                if ( StructInstType *structInst = dynamic_cast< StructInstType* >( offsetofExpr->get_type() ) ) {
[490ff5c3]1461                        addOffsetof( structInst, offsetofExpr->member );
[2a4b088]1462                } else if ( UnionInstType *unionInst = dynamic_cast< UnionInstType* >( offsetofExpr->get_type() ) ) {
[490ff5c3]1463                        addOffsetof( unionInst, offsetofExpr->member );
[2a4b088]1464                }
1465        }
[6ed1d4b]1466
[13deae88]1467        void AlternativeFinder::Finder::postvisit( OffsetofExpr *offsetofExpr ) {
[25a054f]1468                alternatives.push_back( Alternative( offsetofExpr->clone(), env, Cost::zero ) );
[afc1045]1469        }
1470
[13deae88]1471        void AlternativeFinder::Finder::postvisit( OffsetPackExpr *offsetPackExpr ) {
[afc1045]1472                alternatives.push_back( Alternative( offsetPackExpr->clone(), env, Cost::zero ) );
[25a054f]1473        }
1474
[a40d503]1475        namespace {
1476                void resolveAttr( SymTab::Indexer::IdData data, FunctionType *function, Type *argType, const TypeEnvironment &env, AlternativeFinder & finder ) {
1477                        // assume no polymorphism
1478                        // assume no implicit conversions
1479                        assert( function->get_parameters().size() == 1 );
1480                        PRINT(
1481                                std::cerr << "resolvAttr: funcDecl is ";
1482                                data.id->print( std::cerr );
1483                                std::cerr << " argType is ";
1484                                argType->print( std::cerr );
1485                                std::cerr << std::endl;
1486                        )
1487                        const SymTab::Indexer & indexer = finder.get_indexer();
1488                        AltList & alternatives = finder.get_alternatives();
1489                        if ( typesCompatibleIgnoreQualifiers( argType, function->get_parameters().front()->get_type(), indexer, env ) ) {
[a181494]1490                                Cost cost = Cost::zero;
1491                                Expression * newExpr = data.combine( cost );
[54043f4]1492                                alternatives.push_back( Alternative( new AttrExpr( newExpr, argType->clone() ), env, Cost::zero, cost ) );
[a40d503]1493                                for ( DeclarationWithType * retVal : function->returnVals ) {
1494                                        alternatives.back().expr->result = retVal->get_type()->clone();
1495                                } // for
1496                        } // if
1497                }
[a32b204]1498        }
1499
[13deae88]1500        void AlternativeFinder::Finder::postvisit( AttrExpr *attrExpr ) {
[a32b204]1501                // assume no 'pointer-to-attribute'
1502                NameExpr *nameExpr = dynamic_cast< NameExpr* >( attrExpr->get_attr() );
1503                assert( nameExpr );
[a40d503]1504                std::list< SymTab::Indexer::IdData > attrList;
[a32b204]1505                indexer.lookupId( nameExpr->get_name(), attrList );
1506                if ( attrExpr->get_isType() || attrExpr->get_expr() ) {
[a40d503]1507                        for ( auto & data : attrList ) {
1508                                DeclarationWithType * id = data.id;
[a32b204]1509                                // check if the type is function
[a40d503]1510                                if ( FunctionType *function = dynamic_cast< FunctionType* >( id->get_type() ) ) {
[a32b204]1511                                        // assume exactly one parameter
1512                                        if ( function->get_parameters().size() == 1 ) {
1513                                                if ( attrExpr->get_isType() ) {
[13deae88]1514                                                        resolveAttr( data, function, attrExpr->get_type(), env, altFinder);
[a32b204]1515                                                } else {
1516                                                        AlternativeFinder finder( indexer, env );
1517                                                        finder.find( attrExpr->get_expr() );
1518                                                        for ( AltList::iterator choice = finder.alternatives.begin(); choice != finder.alternatives.end(); ++choice ) {
[906e24d]1519                                                                if ( choice->expr->get_result()->size() == 1 ) {
[13deae88]1520                                                                        resolveAttr(data, function, choice->expr->get_result(), choice->env, altFinder );
[a32b204]1521                                                                } // fi
1522                                                        } // for
1523                                                } // if
1524                                        } // if
1525                                } // if
1526                        } // for
1527                } else {
[a40d503]1528                        for ( auto & data : attrList ) {
[a181494]1529                                Cost cost = Cost::zero;
1530                                Expression * newExpr = data.combine( cost );
[54043f4]1531                                alternatives.push_back( Alternative( newExpr, env, Cost::zero, cost ) );
[a32b204]1532                                renameTypes( alternatives.back().expr );
1533                        } // for
1534                } // if
1535        }
1536
[13deae88]1537        void AlternativeFinder::Finder::postvisit( LogicalExpr *logicalExpr ) {
[a32b204]1538                AlternativeFinder firstFinder( indexer, env );
1539                firstFinder.findWithAdjustment( logicalExpr->get_arg1() );
[fee651f]1540                if ( firstFinder.alternatives.empty() ) return;
1541                AlternativeFinder secondFinder( indexer, env );
1542                secondFinder.findWithAdjustment( logicalExpr->get_arg2() );
1543                if ( secondFinder.alternatives.empty() ) return;
[490ff5c3]1544                for ( const Alternative & first : firstFinder.alternatives ) {
1545                        for ( const Alternative & second : secondFinder.alternatives ) {
[fee651f]1546                                TypeEnvironment compositeEnv;
[490ff5c3]1547                                compositeEnv.simpleCombine( first.env );
1548                                compositeEnv.simpleCombine( second.env );
[fee651f]1549
[490ff5c3]1550                                LogicalExpr *newExpr = new LogicalExpr( first.expr->clone(), second.expr->clone(), logicalExpr->get_isAnd() );
1551                                alternatives.push_back( Alternative( newExpr, compositeEnv, first.cost + second.cost ) );
[d9a0e76]1552                        }
1553                }
1554        }
[51b7345]1555
[13deae88]1556        void AlternativeFinder::Finder::postvisit( ConditionalExpr *conditionalExpr ) {
[32b8144]1557                // find alternatives for condition
[a32b204]1558                AlternativeFinder firstFinder( indexer, env );
[624b722d]1559                firstFinder.findWithAdjustment( conditionalExpr->arg1 );
[ebcb7ba]1560                if ( firstFinder.alternatives.empty() ) return;
1561                // find alternatives for true expression
1562                AlternativeFinder secondFinder( indexer, env );
[624b722d]1563                secondFinder.findWithAdjustment( conditionalExpr->arg2 );
[ebcb7ba]1564                if ( secondFinder.alternatives.empty() ) return;
1565                // find alterantives for false expression
1566                AlternativeFinder thirdFinder( indexer, env );
[624b722d]1567                thirdFinder.findWithAdjustment( conditionalExpr->arg3 );
[ebcb7ba]1568                if ( thirdFinder.alternatives.empty() ) return;
[624b722d]1569                for ( const Alternative & first : firstFinder.alternatives ) {
1570                        for ( const Alternative & second : secondFinder.alternatives ) {
1571                                for ( const Alternative & third : thirdFinder.alternatives ) {
[ebcb7ba]1572                                        TypeEnvironment compositeEnv;
[624b722d]1573                                        compositeEnv.simpleCombine( first.env );
1574                                        compositeEnv.simpleCombine( second.env );
1575                                        compositeEnv.simpleCombine( third.env );
[ebcb7ba]1576
[32b8144]1577                                        // unify true and false types, then infer parameters to produce new alternatives
[a32b204]1578                                        OpenVarSet openVars;
1579                                        AssertionSet needAssertions, haveAssertions;
[624b722d]1580                                        Alternative newAlt( 0, compositeEnv, first.cost + second.cost + third.cost );
[668e971a]1581                                        Type* commonType = nullptr;
[624b722d]1582                                        if ( unify( second.expr->result, third.expr->result, newAlt.env, needAssertions, haveAssertions, openVars, indexer, commonType ) ) {
1583                                                ConditionalExpr *newExpr = new ConditionalExpr( first.expr->clone(), second.expr->clone(), third.expr->clone() );
1584                                                newExpr->result = commonType ? commonType : second.expr->result->clone();
[ddf8a29]1585                                                // convert both options to the conditional result type
1586                                                newAlt.cost += computeExpressionConversionCost( newExpr->arg2, newExpr->result, indexer, newAlt.env );
1587                                                newAlt.cost += computeExpressionConversionCost( newExpr->arg3, newExpr->result, indexer, newAlt.env );
[a32b204]1588                                                newAlt.expr = newExpr;
1589                                                inferParameters( needAssertions, haveAssertions, newAlt, openVars, back_inserter( alternatives ) );
1590                                        } // if
1591                                } // for
1592                        } // for
1593                } // for
1594        }
1595
[13deae88]1596        void AlternativeFinder::Finder::postvisit( CommaExpr *commaExpr ) {
[a32b204]1597                TypeEnvironment newEnv( env );
1598                Expression *newFirstArg = resolveInVoidContext( commaExpr->get_arg1(), indexer, newEnv );
1599                AlternativeFinder secondFinder( indexer, newEnv );
1600                secondFinder.findWithAdjustment( commaExpr->get_arg2() );
[490ff5c3]1601                for ( const Alternative & alt : secondFinder.alternatives ) {
1602                        alternatives.push_back( Alternative( new CommaExpr( newFirstArg->clone(), alt.expr->clone() ), alt.env, alt.cost ) );
[a32b204]1603                } // for
1604                delete newFirstArg;
1605        }
1606
[13deae88]1607        void AlternativeFinder::Finder::postvisit( RangeExpr * rangeExpr ) {
[32b8144]1608                // resolve low and high, accept alternatives whose low and high types unify
1609                AlternativeFinder firstFinder( indexer, env );
[490ff5c3]1610                firstFinder.findWithAdjustment( rangeExpr->low );
[fee651f]1611                if ( firstFinder.alternatives.empty() ) return;
1612                AlternativeFinder secondFinder( indexer, env );
[490ff5c3]1613                secondFinder.findWithAdjustment( rangeExpr->high );
[fee651f]1614                if ( secondFinder.alternatives.empty() ) return;
[490ff5c3]1615                for ( const Alternative & first : firstFinder.alternatives ) {
1616                        for ( const Alternative & second : secondFinder.alternatives ) {
[fee651f]1617                                TypeEnvironment compositeEnv;
[490ff5c3]1618                                compositeEnv.simpleCombine( first.env );
1619                                compositeEnv.simpleCombine( second.env );
[32b8144]1620                                OpenVarSet openVars;
1621                                AssertionSet needAssertions, haveAssertions;
[490ff5c3]1622                                Alternative newAlt( 0, compositeEnv, first.cost + second.cost );
[32b8144]1623                                Type* commonType = nullptr;
[490ff5c3]1624                                if ( unify( first.expr->result, second.expr->result, newAlt.env, needAssertions, haveAssertions, openVars, indexer, commonType ) ) {
1625                                        RangeExpr * newExpr = new RangeExpr( first.expr->clone(), second.expr->clone() );
1626                                        newExpr->result = commonType ? commonType : first.expr->result->clone();
[32b8144]1627                                        newAlt.expr = newExpr;
1628                                        inferParameters( needAssertions, haveAssertions, newAlt, openVars, back_inserter( alternatives ) );
1629                                } // if
1630                        } // for
1631                } // for
1632        }
1633
[13deae88]1634        void AlternativeFinder::Finder::postvisit( UntypedTupleExpr *tupleExpr ) {
[bd4f2e9]1635                std::vector< AlternativeFinder > subExprAlternatives;
[13deae88]1636                altFinder.findSubExprs( tupleExpr->get_exprs().begin(), tupleExpr->get_exprs().end(),
[bd4f2e9]1637                        back_inserter( subExprAlternatives ) );
1638                std::vector< AltList > possibilities;
[452747a]1639                combos( subExprAlternatives.begin(), subExprAlternatives.end(),
[bd4f2e9]1640                        back_inserter( possibilities ) );
1641                for ( const AltList& alts : possibilities ) {
[907eccb]1642                        std::list< Expression * > exprs;
[bd4f2e9]1643                        makeExprList( alts, exprs );
[a32b204]1644
1645                        TypeEnvironment compositeEnv;
[bd4f2e9]1646                        simpleCombineEnvironments( alts.begin(), alts.end(), compositeEnv );
[452747a]1647                        alternatives.push_back(
[bd4f2e9]1648                                Alternative{ new TupleExpr( exprs ), compositeEnv, sumCost( alts ) } );
[a32b204]1649                } // for
[d9a0e76]1650        }
[dc2e7e0]1651
[13deae88]1652        void AlternativeFinder::Finder::postvisit( TupleExpr *tupleExpr ) {
[907eccb]1653                alternatives.push_back( Alternative( tupleExpr->clone(), env, Cost::zero ) );
1654        }
1655
[13deae88]1656        void AlternativeFinder::Finder::postvisit( ImplicitCopyCtorExpr * impCpCtorExpr ) {
[dc2e7e0]1657                alternatives.push_back( Alternative( impCpCtorExpr->clone(), env, Cost::zero ) );
1658        }
[b6fe7e6]1659
[13deae88]1660        void AlternativeFinder::Finder::postvisit( ConstructorExpr * ctorExpr ) {
[b6fe7e6]1661                AlternativeFinder finder( indexer, env );
1662                // don't prune here, since it's guaranteed all alternatives will have the same type
1663                // (giving the alternatives different types is half of the point of ConstructorExpr nodes)
[4e66a18]1664                finder.findWithoutPrune( ctorExpr->get_callExpr() );
[b6fe7e6]1665                for ( Alternative & alt : finder.alternatives ) {
1666                        alternatives.push_back( Alternative( new ConstructorExpr( alt.expr->clone() ), alt.env, alt.cost ) );
1667                }
1668        }
[8f7cea1]1669
[13deae88]1670        void AlternativeFinder::Finder::postvisit( TupleIndexExpr *tupleExpr ) {
[8f7cea1]1671                alternatives.push_back( Alternative( tupleExpr->clone(), env, Cost::zero ) );
1672        }
[aa8f9df]1673
[13deae88]1674        void AlternativeFinder::Finder::postvisit( TupleAssignExpr *tupleAssignExpr ) {
[aa8f9df]1675                alternatives.push_back( Alternative( tupleAssignExpr->clone(), env, Cost::zero ) );
1676        }
[bf32bb8]1677
[13deae88]1678        void AlternativeFinder::Finder::postvisit( UniqueExpr *unqExpr ) {
[bf32bb8]1679                AlternativeFinder finder( indexer, env );
1680                finder.findWithAdjustment( unqExpr->get_expr() );
1681                for ( Alternative & alt : finder.alternatives ) {
[141b786]1682                        // ensure that the id is passed on to the UniqueExpr alternative so that the expressions are "linked"
[77971f6]1683                        UniqueExpr * newUnqExpr = new UniqueExpr( alt.expr->clone(), unqExpr->get_id() );
[141b786]1684                        alternatives.push_back( Alternative( newUnqExpr, alt.env, alt.cost ) );
[bf32bb8]1685                }
1686        }
1687
[13deae88]1688        void AlternativeFinder::Finder::postvisit( StmtExpr *stmtExpr ) {
[722617d]1689                StmtExpr * newStmtExpr = stmtExpr->clone();
1690                ResolvExpr::resolveStmtExpr( newStmtExpr, indexer );
1691                // xxx - this env is almost certainly wrong, and needs to somehow contain the combined environments from all of the statements in the stmtExpr...
1692                alternatives.push_back( Alternative( newStmtExpr, env, Cost::zero ) );
1693        }
1694
[13deae88]1695        void AlternativeFinder::Finder::postvisit( UntypedInitExpr *initExpr ) {
[62423350]1696                // handle each option like a cast
[e4d829b]1697                AltList candidates;
[13deae88]1698                PRINT(
1699                        std::cerr << "untyped init expr: " << initExpr << std::endl;
1700                )
[e4d829b]1701                // O(N^2) checks of d-types with e-types
[62423350]1702                for ( InitAlternative & initAlt : initExpr->get_initAlts() ) {
[228099e]1703                        Type * toType = resolveTypeof( initAlt.type->clone(), indexer );
[62423350]1704                        SymTab::validateType( toType, &indexer );
1705                        adjustExprType( toType, env, indexer );
1706                        // Ideally the call to findWithAdjustment could be moved out of the loop, but unfortunately it currently has to occur inside or else
1707                        // polymorphic return types are not properly bound to the initialization type, since return type variables are only open for the duration of resolving
1708                        // the UntypedExpr. This is only actually an issue in initialization contexts that allow more than one possible initialization type, but it is still suboptimal.
1709                        AlternativeFinder finder( indexer, env );
1710                        finder.targetType = toType;
1711                        finder.findWithAdjustment( initExpr->get_expr() );
1712                        for ( Alternative & alt : finder.get_alternatives() ) {
1713                                TypeEnvironment newEnv( alt.env );
[e4d829b]1714                                AssertionSet needAssertions, haveAssertions;
[62423350]1715                                OpenVarSet openVars;  // find things in env that don't have a "representative type" and claim those are open vars?
[13deae88]1716                                PRINT(
1717                                        std::cerr << "  @ " << toType << " " << initAlt.designation << std::endl;
1718                                 )
[e4d829b]1719                                // It's possible that a cast can throw away some values in a multiply-valued expression.  (An example is a
1720                                // cast-to-void, which casts from one value to zero.)  Figure out the prefix of the subexpression results
1721                                // that are cast directly.  The candidate is invalid if it has fewer results than there are types to cast
1722                                // to.
[62423350]1723                                int discardedValues = alt.expr->get_result()->size() - toType->size();
[e4d829b]1724                                if ( discardedValues < 0 ) continue;
1725                                // xxx - may need to go into tuple types and extract relevant types and use unifyList. Note that currently, this does not
1726                                // allow casting a tuple to an atomic type (e.g. (int)([1, 2, 3]))
1727                                // unification run for side-effects
[95642c9]1728                                unify( toType, alt.expr->result, newEnv, needAssertions, haveAssertions, openVars, indexer ); // xxx - do some inspecting on this line... why isn't result bound to initAlt.type??
[e4d829b]1729
[62423350]1730                                Cost thisCost = castCost( alt.expr->get_result(), toType, indexer, newEnv );
[e4d829b]1731                                if ( thisCost != Cost::infinity ) {
1732                                        // count one safe conversion for each value that is thrown away
[89be1c68]1733                                        thisCost.incSafe( discardedValues );
[c0bf94e]1734                                        Alternative newAlt( new InitExpr( restructureCast( alt.expr->clone(), toType, true ), initAlt.designation->clone() ), newEnv, alt.cost, thisCost );
[bb666f64]1735                                        inferParameters( needAssertions, haveAssertions, newAlt, openVars, back_inserter( candidates ) );
[e4d829b]1736                                }
1737                        }
1738                }
1739
1740                // findMinCost selects the alternatives with the lowest "cost" members, but has the side effect of copying the
1741                // cvtCost member to the cost member (since the old cost is now irrelevant).  Thus, calling findMinCost twice
1742                // selects first based on argument cost, then on conversion cost.
1743                AltList minArgCost;
1744                findMinCost( candidates.begin(), candidates.end(), std::back_inserter( minArgCost ) );
1745                findMinCost( minArgCost.begin(), minArgCost.end(), std::back_inserter( alternatives ) );
1746        }
[c71b256]1747
1748        void AlternativeFinder::Finder::postvisit( InitExpr * ) {
1749                assertf( false, "AlternativeFinder should never see a resolved InitExpr." );
1750        }
1751
1752        void AlternativeFinder::Finder::postvisit( DeletedExpr * ) {
1753                assertf( false, "AlternativeFinder should never see a DeletedExpr." );
1754        }
[51b7345]1755} // namespace ResolvExpr
[a32b204]1756
1757// Local Variables: //
1758// tab-width: 4 //
1759// mode: c++ //
1760// compile-command: "make install" //
1761// End: //
Note: See TracBrowser for help on using the repository browser.