source: src/GenPoly/Box.cc @ 1194734

ADTaaron-thesisarm-ehast-experimentalcleanup-dtorsctordeferred_resndemanglerenumforall-pointer-decaygc_noraiijacob/cs343-translationjenkins-sandboxmemorynew-astnew-ast-unique-exprnew-envno_listpersistent-indexerpthread-emulationqualifiedEnumresolv-newstringwith_gc
Last change on this file since 1194734 was 1194734, checked in by Aaron Moss <a3moss@…>, 8 years ago

Continue to work on handling polymorphic generic returns

  • Property mode set to 100644
File size: 53.1 KB
Line 
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//
7// Box.cc --
8//
9// Author           : Richard C. Bilson
10// Created On       : Mon May 18 07:44:20 2015
11// Last Modified By : Rob Schluntz
12// Last Modified On : Fri Dec 18 14:53:08 2015
13// Update Count     : 217
14//
15
16#include <set>
17#include <stack>
18#include <string>
19#include <iterator>
20#include <algorithm>
21#include <cassert>
22
23#include "Box.h"
24#include "PolyMutator.h"
25#include "FindFunction.h"
26#include "ScopedMap.h"
27#include "ScrubTyVars.h"
28
29#include "Parser/ParseNode.h"
30
31#include "SynTree/Constant.h"
32#include "SynTree/Type.h"
33#include "SynTree/Expression.h"
34#include "SynTree/Initializer.h"
35#include "SynTree/Statement.h"
36#include "SynTree/Mutator.h"
37
38#include "ResolvExpr/TypeEnvironment.h"
39
40#include "SymTab/Mangler.h"
41
42#include "SemanticError.h"
43#include "UniqueName.h"
44#include "utility.h"
45
46#include <ext/functional> // temporary
47
48namespace GenPoly {
49        namespace {
50                const std::list<Label> noLabels;
51
52                FunctionType *makeAdapterType( FunctionType *adaptee, const TyVarMap &tyVars );
53
54                /// Replaces polymorphic return types with out-parameters, replaces calls to polymorphic functions with adapter calls as needed, and adds appropriate type variables to the function call
55                class Pass1 : public PolyMutator {
56                  public:
57                        Pass1();
58                        virtual Expression *mutate( ApplicationExpr *appExpr );
59                        virtual Expression *mutate( AddressExpr *addrExpr );
60                        virtual Expression *mutate( UntypedExpr *expr );
61                        virtual DeclarationWithType* mutate( FunctionDecl *functionDecl );
62                        virtual TypeDecl *mutate( TypeDecl *typeDecl );
63                        virtual Expression *mutate( CommaExpr *commaExpr );
64                        virtual Expression *mutate( ConditionalExpr *condExpr );
65                        virtual Statement * mutate( ReturnStmt *returnStmt );
66                        virtual Type *mutate( PointerType *pointerType );
67                        virtual Type * mutate( FunctionType *functionType );
68
69                        virtual void doBeginScope();
70                        virtual void doEndScope();
71                  private:
72                        void passTypeVars( ApplicationExpr *appExpr, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars );
73                        /// wraps a function application with a new temporary for the out-parameter return value
74                        Expression *addRetParam( ApplicationExpr *appExpr, FunctionType *function, Type *retType, std::list< Expression *>::iterator &arg );
75                        /// Replaces all the type parameters of a generic type with their concrete equivalents under the current environment
76                        void replaceParametersWithConcrete( ApplicationExpr *appExpr, std::list< Expression* >& params );
77                        /// Replaces a polymorphic type with its concrete equivalant under the current environment (returns itself if concrete).
78                        /// If `doClone` is set to false, will not clone interior types
79                        Type *replaceWithConcrete( ApplicationExpr *appExpr, Type *type, bool doClone = true );
80                        /// wraps a function application returning a polymorphic type with a new temporary for the out-parameter return value
81                        Expression *addPolyRetParam( ApplicationExpr *appExpr, FunctionType *function, ReferenceToType *polyType, std::list< Expression *>::iterator &arg );
82                        Expression *applyAdapter( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars );
83                        void boxParam( Type *formal, Expression *&arg, const TyVarMap &exprTyVars );
84                        void boxParams( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars );
85                        void addInferredParams( ApplicationExpr *appExpr, FunctionType *functionType, std::list< Expression *>::iterator &arg, const TyVarMap &tyVars );
86                        /// Stores assignment operators from assertion list in local map of assignment operations
87                        void findAssignOps( const std::list< TypeDecl *> &forall );
88                        void passAdapters( ApplicationExpr *appExpr, FunctionType *functionType, const TyVarMap &exprTyVars );
89                        FunctionDecl *makeAdapter( FunctionType *adaptee, FunctionType *realType, const std::string &mangleName, const TyVarMap &tyVars );
90                        Expression *handleIntrinsics( ApplicationExpr *appExpr );
91                        ObjectDecl *makeTemporary( Type *type );
92
93                        typedef std::map< std::string, DeclarationWithType *> AdapterMap;
94                        std::map< std::string, DeclarationWithType *> assignOps;
95                        ScopedMap< std::string, DeclarationWithType *> scopedAssignOps;
96                        std::stack< AdapterMap > adapters;
97                        DeclarationWithType *retval;
98                        bool useRetval;
99                        UniqueName tempNamer;
100                };
101
102                /// Moves polymorphic returns in function types to pointer-type parameters, adds type size and assertion parameters to parameter lists as well
103                class Pass2 : public PolyMutator {
104                  public:
105                        template< typename DeclClass >
106                        DeclClass *handleDecl( DeclClass *decl, Type *type );
107                        virtual DeclarationWithType *mutate( FunctionDecl *functionDecl );
108                        virtual ObjectDecl *mutate( ObjectDecl *objectDecl );
109                        virtual TypeDecl *mutate( TypeDecl *typeDecl );
110                        virtual TypedefDecl *mutate( TypedefDecl *typedefDecl );
111                        virtual Type *mutate( PointerType *pointerType );
112                        virtual Type *mutate( FunctionType *funcType );
113                  private:
114                        void addAdapters( FunctionType *functionType );
115
116                        std::map< UniqueId, std::string > adapterName;
117                };
118
119                /// Replaces initialization of polymorphic values with alloca, declaration of dtype/ftype with appropriate void expression, and sizeof expressions of polymorphic types with the proper variable
120                class Pass3 : public PolyMutator {
121                  public:
122                        template< typename DeclClass >
123                        DeclClass *handleDecl( DeclClass *decl, Type *type );
124                        virtual DeclarationWithType *mutate( FunctionDecl *functionDecl );
125                        virtual ObjectDecl *mutate( ObjectDecl *objectDecl );
126                        virtual TypedefDecl *mutate( TypedefDecl *objectDecl );
127                        virtual TypeDecl *mutate( TypeDecl *objectDecl );
128                        virtual Statement *mutate( DeclStmt *declStmt );
129                        virtual Type *mutate( PointerType *pointerType );
130                        virtual Type *mutate( FunctionType *funcType );
131                  private:
132                };
133
134        } // anonymous namespace
135
136        void printAllNotBuiltin( const std::list< Declaration *>& translationUnit, std::ostream &os ) {
137                for ( std::list< Declaration *>::const_iterator i = translationUnit.begin(); i != translationUnit.end(); ++i ) {
138                        if ( ! LinkageSpec::isBuiltin( (*i)->get_linkage() ) ) {
139                                (*i)->print( os );
140                                os << std::endl;
141                        } // if
142                } // for
143        }
144
145        void box( std::list< Declaration *>& translationUnit ) {
146                Pass1 pass1;
147                Pass2 pass2;
148                Pass3 pass3;
149                mutateAll( translationUnit, pass1 );
150                mutateAll( translationUnit, pass2 );
151                mutateAll( translationUnit, pass3 );
152        }
153
154        ////////////////////////////////////////// Pass1 ////////////////////////////////////////////////////
155
156        namespace {
157                std::string makePolyMonoSuffix( FunctionType * function, const TyVarMap &tyVars ) {
158                        std::stringstream name;
159
160                        // NOTE: this function previously used isPolyObj, which failed to produce
161                        // the correct thing in some situations. It's not clear to me why this wasn't working.
162
163                        // if the return type or a parameter type involved polymorphic types, then the adapter will need
164                        // to take those polymorphic types as pointers. Therefore, there can be two different functions
165                        // with the same mangled name, so we need to further mangle the names.
166                        for ( std::list< DeclarationWithType *>::iterator retval = function->get_returnVals().begin(); retval != function->get_returnVals().end(); ++retval ) {
167                                if ( isPolyType( (*retval)->get_type(), tyVars ) ) {
168                                        name << "P";
169                                } else {
170                                        name << "M";
171                                }
172                        }
173                        name << "_";
174                        std::list< DeclarationWithType *> &paramList = function->get_parameters();
175                        for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
176                                if ( isPolyType( (*arg)->get_type(), tyVars ) ) {
177                                        name << "P";
178                                } else {
179                                        name << "M";
180                                }
181                        } // for
182                        return name.str();
183                }
184
185                std::string mangleAdapterName( FunctionType * function, const TyVarMap &tyVars ) {
186                        return SymTab::Mangler::mangle( function ) + makePolyMonoSuffix( function, tyVars );
187                }
188
189                std::string makeAdapterName( const std::string &mangleName ) {
190                        return "_adapter" + mangleName;
191                }
192
193                Pass1::Pass1() : useRetval( false ), tempNamer( "_temp" ) {
194                        adapters.push(AdapterMap());
195                }
196
197                /// returns T if the given declaration is: (*?=?)(T *, T) for some T (return not checked, but maybe should be), NULL otherwise
198                ReferenceToType *isAssignment( DeclarationWithType *decl ) {
199                        if ( decl->get_name() == "?=?" ) {
200                                if ( FunctionType *funType = getFunctionType( decl->get_type() ) ) {
201                                        if ( funType->get_parameters().size() == 2 ) {
202                                                if ( PointerType *pointer = dynamic_cast< PointerType *>( funType->get_parameters().front()->get_type() ) ) {
203                                                        if ( ReferenceToType *refType = dynamic_cast< ReferenceToType *>( pointer->get_base() ) ) {
204                                                                if ( ReferenceToType *refType2 = dynamic_cast< ReferenceToType *>( funType->get_parameters().back()->get_type() ) ) {
205                                                                        if ( refType->get_name() == refType2->get_name() ) {
206                                                                                return refType;
207                                                                        } // if
208                                                                } // if
209                                                        } // if
210                                                } // if
211                                        } // if
212                                } // if
213                        } // if
214                        return 0;
215                }
216
217                void Pass1::findAssignOps( const std::list< TypeDecl *> &forall ) {
218                        // what if a nested function uses an assignment operator?
219                        // assignOps.clear();
220                        for ( std::list< TypeDecl *>::const_iterator i = forall.begin(); i != forall.end(); ++i ) {
221                                for ( std::list< DeclarationWithType *>::const_iterator assert = (*i)->get_assertions().begin(); assert != (*i)->get_assertions().end(); ++assert ) {
222                                        std::string typeName;
223                                        if ( TypeInstType *typeInst = dynamic_cast< TypeInstType* >( isAssignment( *assert ) ) ) {
224                                                assignOps[ typeInst->get_name() ] = *assert;
225                                        } // if
226                                } // for
227                        } // for
228                }
229
230                DeclarationWithType *Pass1::mutate( FunctionDecl *functionDecl ) {
231                        // if this is a polymorphic assignment function, put it in the map for this scope
232                        if ( ReferenceToType *refType = isAssignment( functionDecl ) ) {
233                                if ( ! dynamic_cast< TypeInstType* >( refType ) ) {
234                                        scopedAssignOps.insert( refType->get_name(), functionDecl );
235                                }
236                        }
237                       
238                        if ( functionDecl->get_statements() ) {         // empty routine body ?
239                                doBeginScope();
240                                TyVarMap oldtyVars = scopeTyVars;
241                                std::map< std::string, DeclarationWithType *> oldassignOps = assignOps;
242                                DeclarationWithType *oldRetval = retval;
243                                bool oldUseRetval = useRetval;
244
245                                // process polymorphic return value
246                                retval = 0;
247                                if ( isPolyRet( functionDecl->get_functionType() ) && functionDecl->get_linkage() == LinkageSpec::Cforall ) {
248                                        retval = functionDecl->get_functionType()->get_returnVals().front();
249
250                                        // give names to unnamed return values
251                                        if ( retval->get_name() == "" ) {
252                                                retval->set_name( "_retparm" );
253                                                retval->set_linkage( LinkageSpec::C );
254                                        } // if
255                                } // if
256
257                                FunctionType *functionType = functionDecl->get_functionType();
258                                makeTyVarMap( functionDecl->get_functionType(), scopeTyVars );
259                                findAssignOps( functionDecl->get_functionType()->get_forall() );
260
261                                std::list< DeclarationWithType *> &paramList = functionType->get_parameters();
262                                std::list< FunctionType *> functions;
263                                for ( std::list< TypeDecl *>::iterator tyVar = functionType->get_forall().begin(); tyVar != functionType->get_forall().end(); ++tyVar ) {
264                                        for ( std::list< DeclarationWithType *>::iterator assert = (*tyVar)->get_assertions().begin(); assert != (*tyVar)->get_assertions().end(); ++assert ) {
265                                                findFunction( (*assert)->get_type(), functions, scopeTyVars, needsAdapter );
266                                        } // for
267                                } // for
268                                for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
269                                        findFunction( (*arg)->get_type(), functions, scopeTyVars, needsAdapter );
270                                } // for
271                                AdapterMap & adapters = Pass1::adapters.top();
272                                for ( std::list< FunctionType *>::iterator funType = functions.begin(); funType != functions.end(); ++funType ) {
273                                        std::string mangleName = mangleAdapterName( *funType, scopeTyVars );
274                                        if ( adapters.find( mangleName ) == adapters.end() ) {
275                                                std::string adapterName = makeAdapterName( mangleName );
276                                                adapters.insert( std::pair< std::string, DeclarationWithType *>( mangleName, new ObjectDecl( adapterName, DeclarationNode::NoStorageClass, LinkageSpec::C, 0, new PointerType( Type::Qualifiers(), makeAdapterType( *funType, scopeTyVars ) ), 0 ) ) );
277                                        } // if
278                                } // for
279
280                                functionDecl->set_statements( functionDecl->get_statements()->acceptMutator( *this ) );
281
282                                scopeTyVars = oldtyVars;
283                                assignOps = oldassignOps;
284                                // std::cerr << "end FunctionDecl: ";
285                                // for ( TyVarMap::iterator i = scopeTyVars.begin(); i != scopeTyVars.end(); ++i ) {
286                                //      std::cerr << i->first << " ";
287                                // }
288                                // std::cerr << "\n";
289                                retval = oldRetval;
290                                useRetval = oldUseRetval;
291                                doEndScope();
292                        } // if
293                        return functionDecl;
294                }
295
296                TypeDecl *Pass1::mutate( TypeDecl *typeDecl ) {
297                        scopeTyVars[ typeDecl->get_name() ] = typeDecl->get_kind();
298                        return Mutator::mutate( typeDecl );
299                }
300
301                Expression *Pass1::mutate( CommaExpr *commaExpr ) {
302                        bool oldUseRetval = useRetval;
303                        useRetval = false;
304                        commaExpr->set_arg1( maybeMutate( commaExpr->get_arg1(), *this ) );
305                        useRetval = oldUseRetval;
306                        commaExpr->set_arg2( maybeMutate( commaExpr->get_arg2(), *this ) );
307                        return commaExpr;
308                }
309
310                Expression *Pass1::mutate( ConditionalExpr *condExpr ) {
311                        bool oldUseRetval = useRetval;
312                        useRetval = false;
313                        condExpr->set_arg1( maybeMutate( condExpr->get_arg1(), *this ) );
314                        useRetval = oldUseRetval;
315                        condExpr->set_arg2( maybeMutate( condExpr->get_arg2(), *this ) );
316                        condExpr->set_arg3( maybeMutate( condExpr->get_arg3(), *this ) );
317                        return condExpr;
318
319                }
320
321                void Pass1::passTypeVars( ApplicationExpr *appExpr, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars ) {
322                        // pass size/align for type variables
323                        for ( TyVarMap::const_iterator tyParm = exprTyVars.begin(); tyParm != exprTyVars.end(); ++tyParm ) {
324                                ResolvExpr::EqvClass eqvClass;
325                                assert( env );
326                                if ( tyParm->second == TypeDecl::Any ) {
327                                        Type *concrete = env->lookup( tyParm->first );
328                                        if ( concrete ) {
329                                                arg = appExpr->get_args().insert( arg, new SizeofExpr( concrete->clone() ) );
330                                                arg++;
331                                                arg = appExpr->get_args().insert( arg, new AlignofExpr( concrete->clone() ) );
332                                                arg++;
333                                        } else {
334                                                throw SemanticError( "unbound type variable in application ", appExpr );
335                                        } // if
336                                } // if
337                        } // for
338
339                        // add size/align for generic types to parameter list
340                        //assert( ! appExpr->get_function()->get_results().empty() );
341                        if ( appExpr->get_function()->get_results().empty() ) return;
342                        FunctionType *funcType = getFunctionType( appExpr->get_function()->get_results().front() );
343                        assert( funcType );
344
345                        std::list< DeclarationWithType* >::const_iterator fnParm = funcType->get_parameters().begin();
346                        std::list< Expression* >::const_iterator fnArg = arg;
347                        std::set< std::string > seenTypes; //< names for generic types we've seen
348                        for ( ; fnParm != funcType->get_parameters().end() && fnArg != appExpr->get_args().end(); ++fnParm, ++fnArg ) {
349                                Type *parmType = (*fnParm)->get_type();
350                                if ( ! dynamic_cast< TypeInstType* >( parmType ) && isPolyType( parmType, exprTyVars ) ) {
351                                        std::string sizeName = sizeofName( parmType );
352                                        if ( seenTypes.count( sizeName ) ) continue;
353
354                                        assert( ! (*fnArg)->get_results().empty() );
355                                        Type *argType = (*fnArg)->get_results().front();
356                                        arg = appExpr->get_args().insert( arg, new SizeofExpr( argType->clone() ) );
357                                        arg++;
358                                        arg = appExpr->get_args().insert( arg, new AlignofExpr( argType->clone() ) );
359                                        arg++;
360
361                                        seenTypes.insert( sizeName );
362                                }
363                        }
364                }
365
366                ObjectDecl *Pass1::makeTemporary( Type *type ) {
367                        ObjectDecl *newObj = new ObjectDecl( tempNamer.newName(), DeclarationNode::NoStorageClass, LinkageSpec::C, 0, type, 0 );
368                        stmtsToAdd.push_back( new DeclStmt( noLabels, newObj ) );
369                        return newObj;
370                }
371
372                Expression *Pass1::addRetParam( ApplicationExpr *appExpr, FunctionType *function, Type *retType, std::list< Expression *>::iterator &arg ) {
373                        // ***** Code Removal ***** After introducing a temporary variable for all return expressions, the following code appears superfluous.
374                        // if ( useRetval ) {
375                        //      assert( retval );
376                        //      arg = appExpr->get_args().insert( arg, new VariableExpr( retval ) );
377                        //      arg++;
378                        // } else {
379
380                        // Create temporary to hold return value of polymorphic function and produce that temporary as a result
381                        // using a comma expression.  Possibly change comma expression into statement expression "{}" for multiple
382                        // return values.
383                        ObjectDecl *newObj = makeTemporary( retType->clone() );
384                        Expression *paramExpr = new VariableExpr( newObj );
385                        // If the type of the temporary is not polymorphic, box temporary by taking its address; otherwise the
386                        // temporary is already boxed and can be used directly.
387                        if ( ! isPolyType( newObj->get_type(), scopeTyVars, env ) ) {
388                                paramExpr = new AddressExpr( paramExpr );
389                        } // if
390                        arg = appExpr->get_args().insert( arg, paramExpr ); // add argument to function call
391                        arg++;
392                        // Build a comma expression to call the function and emulate a normal return.
393                        CommaExpr *commaExpr = new CommaExpr( appExpr, new VariableExpr( newObj ) );
394                        commaExpr->set_env( appExpr->get_env() );
395                        appExpr->set_env( 0 );
396                        return commaExpr;
397                        // } // if
398                        // return appExpr;
399                }
400
401                void Pass1::replaceParametersWithConcrete( ApplicationExpr *appExpr, std::list< Expression* >& params ) {
402                        for ( std::list< Expression* >::iterator param = params.begin(); param != params.end(); ++param ) {
403                                TypeExpr *paramType = dynamic_cast< TypeExpr* >( *param );
404                                assert(paramType && "Aggregate parameters should be type expressions");
405                                paramType->set_type( replaceWithConcrete( appExpr, paramType->get_type(), false ) );
406                        }
407                }
408               
409                Type *Pass1::replaceWithConcrete( ApplicationExpr *appExpr, Type *type, bool doClone ) {
410                        if ( TypeInstType *typeInst = dynamic_cast< TypeInstType * >( type ) ) {
411                                Type *concrete = env->lookup( typeInst->get_name() );
412                                if ( concrete == 0 ) {
413                                        throw SemanticError( "Unbound type variable " + typeInst->get_name() + " in ", appExpr );
414                                } // if
415                                return concrete;
416                        } else if ( StructInstType *structType = dynamic_cast< StructInstType* >( type ) ) {
417                                if ( doClone ) {
418                                        structType = structType->clone();
419                                }
420                                replaceParametersWithConcrete( appExpr, structType->get_parameters() );
421                                return structType;
422                        } else if ( UnionInstType *unionType = dynamic_cast< UnionInstType* >( type ) ) {
423                                if ( doClone ) {
424                                        unionType = unionType->clone();
425                                }
426                                replaceParametersWithConcrete( appExpr, unionType->get_parameters() );
427                                return unionType;
428                        }
429                        return type;
430                }
431
432                Expression *Pass1::addPolyRetParam( ApplicationExpr *appExpr, FunctionType *function, ReferenceToType *polyType, std::list< Expression *>::iterator &arg ) {
433                        assert( env );
434                        Type *concrete = replaceWithConcrete( appExpr, polyType );
435                        return addRetParam( appExpr, function, concrete, arg );
436                }
437
438                Expression *Pass1::applyAdapter( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &tyVars ) {
439                        Expression *ret = appExpr;
440                        if ( ! function->get_returnVals().empty() && isPolyType( function->get_returnVals().front()->get_type(), tyVars ) ) {
441                                ret = addRetParam( appExpr, function, function->get_returnVals().front()->get_type(), arg );
442                        } // if
443                        std::string mangleName = mangleAdapterName( function, tyVars );
444                        std::string adapterName = makeAdapterName( mangleName );
445
446                        appExpr->get_args().push_front( appExpr->get_function() );
447                        appExpr->set_function( new NameExpr( adapterName ) );
448
449                        return ret;
450                }
451
452                void Pass1::boxParam( Type *param, Expression *&arg, const TyVarMap &exprTyVars ) {
453                        assert( ! arg->get_results().empty() );
454                        if ( isPolyType( param, exprTyVars ) ) {
455                                if ( dynamic_cast< TypeInstType *>( arg->get_results().front() ) ) {
456                                        // if the argument's type is a type parameter, we don't need to box again!
457                                        return;
458                                } else if ( arg->get_results().front()->get_isLvalue() ) {
459                                        // VariableExpr and MemberExpr are lvalues
460                                        arg = new AddressExpr( arg );
461                                } else {
462                                        ObjectDecl *newObj = new ObjectDecl( tempNamer.newName(), DeclarationNode::NoStorageClass, LinkageSpec::C, 0, arg->get_results().front()->clone(), 0 );
463                                        newObj->get_type()->get_qualifiers() = Type::Qualifiers(); // TODO: is this right???
464                                        stmtsToAdd.push_back( new DeclStmt( noLabels, newObj ) );
465                                        UntypedExpr *assign = new UntypedExpr( new NameExpr( "?=?" ) );
466                                        assign->get_args().push_back( new VariableExpr( newObj ) );
467                                        assign->get_args().push_back( arg );
468                                        stmtsToAdd.push_back( new ExprStmt( noLabels, assign ) );
469                                        arg = new AddressExpr( new VariableExpr( newObj ) );
470                                } // if
471                        } // if
472                }
473
474                void addCast( Expression *&actual, Type *formal, const TyVarMap &tyVars ) {
475                        Type *newType = formal->clone();
476                        std::list< FunctionType *> functions;
477                        // instead of functions needing adapters, this really ought to look for
478                        // any function mentioning a polymorphic type
479                        findAndReplaceFunction( newType, functions, tyVars, needsAdapter );
480                        if ( ! functions.empty() ) {
481                                actual = new CastExpr( actual, newType );
482                        } else {
483                                delete newType;
484                        } // if
485                }
486
487                void Pass1::boxParams( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars ) {
488                        for ( std::list< DeclarationWithType *>::const_iterator param = function->get_parameters().begin(); param != function->get_parameters().end(); ++param, ++arg ) {
489                                assert( arg != appExpr->get_args().end() );
490                                addCast( *arg, (*param)->get_type(), exprTyVars );
491                                boxParam( (*param)->get_type(), *arg, exprTyVars );
492                        } // for
493                }
494
495                void Pass1::addInferredParams( ApplicationExpr *appExpr, FunctionType *functionType, std::list< Expression *>::iterator &arg, const TyVarMap &tyVars ) {
496                        std::list< Expression *>::iterator cur = arg;
497                        for ( std::list< TypeDecl *>::iterator tyVar = functionType->get_forall().begin(); tyVar != functionType->get_forall().end(); ++tyVar ) {
498                                for ( std::list< DeclarationWithType *>::iterator assert = (*tyVar)->get_assertions().begin(); assert != (*tyVar)->get_assertions().end(); ++assert ) {
499                                        InferredParams::const_iterator inferParam = appExpr->get_inferParams().find( (*assert)->get_uniqueId() );
500                                        assert( inferParam != appExpr->get_inferParams().end() && "NOTE: Explicit casts of polymorphic functions to compatible monomorphic functions are currently unsupported" );
501                                        Expression *newExpr = inferParam->second.expr->clone();
502                                        addCast( newExpr, (*assert)->get_type(), tyVars );
503                                        boxParam( (*assert)->get_type(), newExpr, tyVars );
504                                        appExpr->get_args().insert( cur, newExpr );
505                                } // for
506                        } // for
507                }
508
509                void makeRetParm( FunctionType *funcType ) {
510                        DeclarationWithType *retParm = funcType->get_returnVals().front();
511
512                        // make a new parameter that is a pointer to the type of the old return value
513                        retParm->set_type( new PointerType( Type::Qualifiers(), retParm->get_type() ) );
514                        funcType->get_parameters().push_front( retParm );
515
516                        // we don't need the return value any more
517                        funcType->get_returnVals().clear();
518                }
519
520                FunctionType *makeAdapterType( FunctionType *adaptee, const TyVarMap &tyVars ) {
521                        // actually make the adapter type
522                        FunctionType *adapter = adaptee->clone();
523                        if ( ! adapter->get_returnVals().empty() && isPolyType( adapter->get_returnVals().front()->get_type(), tyVars ) ) {
524                                makeRetParm( adapter );
525                        } // if
526                        adapter->get_parameters().push_front( new ObjectDecl( "", DeclarationNode::NoStorageClass, LinkageSpec::C, 0, new PointerType( Type::Qualifiers(), new FunctionType( Type::Qualifiers(), true ) ), 0 ) );
527                        return adapter;
528                }
529
530                Expression *makeAdapterArg( DeclarationWithType *param, DeclarationWithType *arg, DeclarationWithType *realParam, const TyVarMap &tyVars ) {
531                        assert( param );
532                        assert( arg );
533                        if ( isPolyType( realParam->get_type(), tyVars ) ) {
534                                if ( dynamic_cast<TypeInstType *>(arg->get_type()) == NULL ) {
535                                        UntypedExpr *deref = new UntypedExpr( new NameExpr( "*?" ) );
536                                        deref->get_args().push_back( new CastExpr( new VariableExpr( param ), new PointerType( Type::Qualifiers(), arg->get_type()->clone() ) ) );
537                                        deref->get_results().push_back( arg->get_type()->clone() );
538                                        return deref;
539                                } // if
540                        } // if
541                        return new VariableExpr( param );
542                }
543
544                void addAdapterParams( ApplicationExpr *adapteeApp, std::list< DeclarationWithType *>::iterator arg, std::list< DeclarationWithType *>::iterator param, std::list< DeclarationWithType *>::iterator paramEnd, std::list< DeclarationWithType *>::iterator realParam, const TyVarMap &tyVars ) {
545                        UniqueName paramNamer( "_p" );
546                        for ( ; param != paramEnd; ++param, ++arg, ++realParam ) {
547                                if ( (*param)->get_name() == "" ) {
548                                        (*param)->set_name( paramNamer.newName() );
549                                        (*param)->set_linkage( LinkageSpec::C );
550                                } // if
551                                adapteeApp->get_args().push_back( makeAdapterArg( *param, *arg, *realParam, tyVars ) );
552                        } // for
553                }
554
555
556
557                FunctionDecl *Pass1::makeAdapter( FunctionType *adaptee, FunctionType *realType, const std::string &mangleName, const TyVarMap &tyVars ) {
558                        FunctionType *adapterType = makeAdapterType( adaptee, tyVars );
559                        adapterType = ScrubTyVars::scrub( adapterType, tyVars );
560                        DeclarationWithType *adapteeDecl = adapterType->get_parameters().front();
561                        adapteeDecl->set_name( "_adaptee" );
562                        ApplicationExpr *adapteeApp = new ApplicationExpr( new CastExpr( new VariableExpr( adapteeDecl ), new PointerType( Type::Qualifiers(), realType ) ) );
563                        Statement *bodyStmt;
564
565                        std::list< TypeDecl *>::iterator tyArg = realType->get_forall().begin();
566                        std::list< TypeDecl *>::iterator tyParam = adapterType->get_forall().begin();
567                        std::list< TypeDecl *>::iterator realTyParam = adaptee->get_forall().begin();
568                        for ( ; tyParam != adapterType->get_forall().end(); ++tyArg, ++tyParam, ++realTyParam ) {
569                                assert( tyArg != realType->get_forall().end() );
570                                std::list< DeclarationWithType *>::iterator assertArg = (*tyArg)->get_assertions().begin();
571                                std::list< DeclarationWithType *>::iterator assertParam = (*tyParam)->get_assertions().begin();
572                                std::list< DeclarationWithType *>::iterator realAssertParam = (*realTyParam)->get_assertions().begin();
573                                for ( ; assertParam != (*tyParam)->get_assertions().end(); ++assertArg, ++assertParam, ++realAssertParam ) {
574                                        assert( assertArg != (*tyArg)->get_assertions().end() );
575                                        adapteeApp->get_args().push_back( makeAdapterArg( *assertParam, *assertArg, *realAssertParam, tyVars ) );
576                                } // for
577                        } // for
578
579                        std::list< DeclarationWithType *>::iterator arg = realType->get_parameters().begin();
580                        std::list< DeclarationWithType *>::iterator param = adapterType->get_parameters().begin();
581                        std::list< DeclarationWithType *>::iterator realParam = adaptee->get_parameters().begin();
582                        param++;                // skip adaptee parameter
583                        if ( realType->get_returnVals().empty() ) {
584                                addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
585                                bodyStmt = new ExprStmt( noLabels, adapteeApp );
586                        } else if ( isPolyType( adaptee->get_returnVals().front()->get_type(), tyVars ) ) {
587                                if ( (*param)->get_name() == "" ) {
588                                        (*param)->set_name( "_ret" );
589                                        (*param)->set_linkage( LinkageSpec::C );
590                                } // if
591                                UntypedExpr *assign = new UntypedExpr( new NameExpr( "?=?" ) );
592                                UntypedExpr *deref = new UntypedExpr( new NameExpr( "*?" ) );
593                                deref->get_args().push_back( new CastExpr( new VariableExpr( *param++ ), new PointerType( Type::Qualifiers(), realType->get_returnVals().front()->get_type()->clone() ) ) );
594                                assign->get_args().push_back( deref );
595                                addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
596                                assign->get_args().push_back( adapteeApp );
597                                bodyStmt = new ExprStmt( noLabels, assign );
598                        } else {
599                                // adapter for a function that returns a monomorphic value
600                                addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
601                                bodyStmt = new ReturnStmt( noLabels, adapteeApp );
602                        } // if
603                        CompoundStmt *adapterBody = new CompoundStmt( noLabels );
604                        adapterBody->get_kids().push_back( bodyStmt );
605                        std::string adapterName = makeAdapterName( mangleName );
606                        return new FunctionDecl( adapterName, DeclarationNode::NoStorageClass, LinkageSpec::C, adapterType, adapterBody, false, false );
607                }
608
609                void Pass1::passAdapters( ApplicationExpr * appExpr, FunctionType * functionType, const TyVarMap & exprTyVars ) {
610                        // collect a list of function types passed as parameters or implicit parameters (assertions)
611                        std::list< DeclarationWithType *> &paramList = functionType->get_parameters();
612                        std::list< FunctionType *> functions;
613                        for ( std::list< TypeDecl *>::iterator tyVar = functionType->get_forall().begin(); tyVar != functionType->get_forall().end(); ++tyVar ) {
614                                for ( std::list< DeclarationWithType *>::iterator assert = (*tyVar)->get_assertions().begin(); assert != (*tyVar)->get_assertions().end(); ++assert ) {
615                                        findFunction( (*assert)->get_type(), functions, exprTyVars, needsAdapter );
616                                } // for
617                        } // for
618                        for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
619                                findFunction( (*arg)->get_type(), functions, exprTyVars, needsAdapter );
620                        } // for
621
622                        // parameter function types for which an appropriate adapter has been generated.  we cannot use the types
623                        // after applying substitutions, since two different parameter types may be unified to the same type
624                        std::set< std::string > adaptersDone;
625
626                        for ( std::list< FunctionType *>::iterator funType = functions.begin(); funType != functions.end(); ++funType ) {
627                                FunctionType *originalFunction = (*funType)->clone();
628                                FunctionType *realFunction = (*funType)->clone();
629                                std::string mangleName = SymTab::Mangler::mangle( realFunction );
630
631                                // only attempt to create an adapter or pass one as a parameter if we haven't already done so for this
632                                // pre-substitution parameter function type.
633                                if ( adaptersDone.find( mangleName ) == adaptersDone.end() ) {
634                                        adaptersDone.insert( adaptersDone.begin(), mangleName );
635
636                                        // apply substitution to type variables to figure out what the adapter's type should look like
637                                        assert( env );
638                                        env->apply( realFunction );
639                                        mangleName = SymTab::Mangler::mangle( realFunction );
640                                        mangleName += makePolyMonoSuffix( originalFunction, exprTyVars );
641
642                                        AdapterMap & adapters = Pass1::adapters.top();
643                                        AdapterMap::iterator adapter = adapters.find( mangleName );
644                                        if ( adapter == adapters.end() ) {
645                                                // adapter has not been created yet in the current scope, so define it
646                                                FunctionDecl *newAdapter = makeAdapter( *funType, realFunction, mangleName, exprTyVars );
647                                                adapter = adapters.insert( adapters.begin(), std::pair< std::string, DeclarationWithType *>( mangleName, newAdapter ) );
648                                                stmtsToAdd.push_back( new DeclStmt( noLabels, newAdapter ) );
649                                        } // if
650                                        assert( adapter != adapters.end() );
651
652                                        // add the appropriate adapter as a parameter
653                                        appExpr->get_args().push_front( new VariableExpr( adapter->second ) );
654                                } // if
655                        } // for
656                } // passAdapters
657
658                Expression *makeIncrDecrExpr( ApplicationExpr *appExpr, Type *polyType, bool isIncr ) {
659                        NameExpr *opExpr;
660                        if ( isIncr ) {
661                                opExpr = new NameExpr( "?+=?" );
662                        } else {
663                                opExpr = new NameExpr( "?-=?" );
664                        } // if
665                        UntypedExpr *addAssign = new UntypedExpr( opExpr );
666                        if ( AddressExpr *address = dynamic_cast< AddressExpr *>( appExpr->get_args().front() ) ) {
667                                addAssign->get_args().push_back( address->get_arg() );
668                        } else {
669                                addAssign->get_args().push_back( appExpr->get_args().front() );
670                        } // if
671                        addAssign->get_args().push_back( new NameExpr( sizeofName( polyType ) ) );
672                        addAssign->get_results().front() = appExpr->get_results().front()->clone();
673                        if ( appExpr->get_env() ) {
674                                addAssign->set_env( appExpr->get_env() );
675                                appExpr->set_env( 0 );
676                        } // if
677                        appExpr->get_args().clear();
678                        delete appExpr;
679                        return addAssign;
680                }
681
682                Expression *Pass1::handleIntrinsics( ApplicationExpr *appExpr ) {
683                        if ( VariableExpr *varExpr = dynamic_cast< VariableExpr *>( appExpr->get_function() ) ) {
684                                if ( varExpr->get_var()->get_linkage() == LinkageSpec::Intrinsic ) {
685                                        if ( varExpr->get_var()->get_name() == "?[?]" ) {
686                                                assert( ! appExpr->get_results().empty() );
687                                                assert( appExpr->get_args().size() == 2 );
688                                                Type *baseType1 = isPolyPtr( appExpr->get_args().front()->get_results().front(), scopeTyVars, env );
689                                                Type *baseType2 = isPolyPtr( appExpr->get_args().back()->get_results().front(), scopeTyVars, env );
690                                                assert( ! baseType1 || ! baseType2 ); // the arguments cannot both be polymorphic pointers
691                                                UntypedExpr *ret = 0;
692                                                if ( baseType1 || baseType2 ) { // one of the arguments is a polymorphic pointer
693                                                        ret = new UntypedExpr( new NameExpr( "?+?" ) );
694                                                } // if
695                                                if ( baseType1 ) {
696                                                        UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
697                                                        multiply->get_args().push_back( appExpr->get_args().back() );
698                                                        multiply->get_args().push_back( new NameExpr( sizeofName( baseType1 ) ) );
699                                                        ret->get_args().push_back( appExpr->get_args().front() );
700                                                        ret->get_args().push_back( multiply );
701                                                } else if ( baseType2 ) {
702                                                        UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
703                                                        multiply->get_args().push_back( appExpr->get_args().front() );
704                                                        multiply->get_args().push_back( new NameExpr( sizeofName( baseType2 ) ) );
705                                                        ret->get_args().push_back( multiply );
706                                                        ret->get_args().push_back( appExpr->get_args().back() );
707                                                } // if
708                                                if ( baseType1 || baseType2 ) {
709                                                        ret->get_results().push_front( appExpr->get_results().front()->clone() );
710                                                        if ( appExpr->get_env() ) {
711                                                                ret->set_env( appExpr->get_env() );
712                                                                appExpr->set_env( 0 );
713                                                        } // if
714                                                        appExpr->get_args().clear();
715                                                        delete appExpr;
716                                                        return ret;
717                                                } // if
718                                        } else if ( varExpr->get_var()->get_name() == "*?" ) {
719                                                assert( ! appExpr->get_results().empty() );
720                                                assert( ! appExpr->get_args().empty() );
721                                                if ( isPolyType( appExpr->get_results().front(), scopeTyVars, env ) ) {
722                                                        Expression *ret = appExpr->get_args().front();
723                                                        delete ret->get_results().front();
724                                                        ret->get_results().front() = appExpr->get_results().front()->clone();
725                                                        if ( appExpr->get_env() ) {
726                                                                ret->set_env( appExpr->get_env() );
727                                                                appExpr->set_env( 0 );
728                                                        } // if
729                                                        appExpr->get_args().clear();
730                                                        delete appExpr;
731                                                        return ret;
732                                                } // if
733                                        } else if ( varExpr->get_var()->get_name() == "?++" || varExpr->get_var()->get_name() == "?--" ) {
734                                                assert( ! appExpr->get_results().empty() );
735                                                assert( appExpr->get_args().size() == 1 );
736                                                if ( Type *baseType = isPolyPtr( appExpr->get_results().front(), scopeTyVars, env ) ) {
737                                                        Type *tempType = appExpr->get_results().front()->clone();
738                                                        if ( env ) {
739                                                                env->apply( tempType );
740                                                        } // if
741                                                        ObjectDecl *newObj = makeTemporary( tempType );
742                                                        VariableExpr *tempExpr = new VariableExpr( newObj );
743                                                        UntypedExpr *assignExpr = new UntypedExpr( new NameExpr( "?=?" ) );
744                                                        assignExpr->get_args().push_back( tempExpr->clone() );
745                                                        if ( AddressExpr *address = dynamic_cast< AddressExpr *>( appExpr->get_args().front() ) ) {
746                                                                assignExpr->get_args().push_back( address->get_arg()->clone() );
747                                                        } else {
748                                                                assignExpr->get_args().push_back( appExpr->get_args().front()->clone() );
749                                                        } // if
750                                                        CommaExpr *firstComma = new CommaExpr( assignExpr, makeIncrDecrExpr( appExpr, baseType, varExpr->get_var()->get_name() == "?++" ) );
751                                                        return new CommaExpr( firstComma, tempExpr );
752                                                } // if
753                                        } else if ( varExpr->get_var()->get_name() == "++?" || varExpr->get_var()->get_name() == "--?" ) {
754                                                assert( ! appExpr->get_results().empty() );
755                                                assert( appExpr->get_args().size() == 1 );
756                                                if ( Type *baseType = isPolyPtr( appExpr->get_results().front(), scopeTyVars, env ) ) {
757                                                        return makeIncrDecrExpr( appExpr, baseType, varExpr->get_var()->get_name() == "++?" );
758                                                } // if
759                                        } else if ( varExpr->get_var()->get_name() == "?+?" || varExpr->get_var()->get_name() == "?-?" ) {
760                                                assert( ! appExpr->get_results().empty() );
761                                                assert( appExpr->get_args().size() == 2 );
762                                                Type *baseType1 = isPolyPtr( appExpr->get_args().front()->get_results().front(), scopeTyVars, env );
763                                                Type *baseType2 = isPolyPtr( appExpr->get_args().back()->get_results().front(), scopeTyVars, env );
764                                                if ( baseType1 && baseType2 ) {
765                                                        UntypedExpr *divide = new UntypedExpr( new NameExpr( "?/?" ) );
766                                                        divide->get_args().push_back( appExpr );
767                                                        divide->get_args().push_back( new NameExpr( sizeofName( baseType1 ) ) );
768                                                        divide->get_results().push_front( appExpr->get_results().front()->clone() );
769                                                        if ( appExpr->get_env() ) {
770                                                                divide->set_env( appExpr->get_env() );
771                                                                appExpr->set_env( 0 );
772                                                        } // if
773                                                        return divide;
774                                                } else if ( baseType1 ) {
775                                                        UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
776                                                        multiply->get_args().push_back( appExpr->get_args().back() );
777                                                        multiply->get_args().push_back( new NameExpr( sizeofName( baseType1 ) ) );
778                                                        appExpr->get_args().back() = multiply;
779                                                } else if ( baseType2 ) {
780                                                        UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
781                                                        multiply->get_args().push_back( appExpr->get_args().front() );
782                                                        multiply->get_args().push_back( new NameExpr( sizeofName( baseType2 ) ) );
783                                                        appExpr->get_args().front() = multiply;
784                                                } // if
785                                        } else if ( varExpr->get_var()->get_name() == "?+=?" || varExpr->get_var()->get_name() == "?-=?" ) {
786                                                assert( ! appExpr->get_results().empty() );
787                                                assert( appExpr->get_args().size() == 2 );
788                                                Type *baseType = isPolyPtr( appExpr->get_results().front(), scopeTyVars, env );
789                                                if ( baseType ) {
790                                                        UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
791                                                        multiply->get_args().push_back( appExpr->get_args().back() );
792                                                        multiply->get_args().push_back( new NameExpr( sizeofName( baseType ) ) );
793                                                        appExpr->get_args().back() = multiply;
794                                                } // if
795                                        } // if
796                                        return appExpr;
797                                } // if
798                        } // if
799                        return 0;
800                }
801
802                Expression *Pass1::mutate( ApplicationExpr *appExpr ) {
803                        // std::cerr << "mutate appExpr: ";
804                        // for ( TyVarMap::iterator i = scopeTyVars.begin(); i != scopeTyVars.end(); ++i ) {
805                        //      std::cerr << i->first << " ";
806                        // }
807                        // std::cerr << "\n";
808                        bool oldUseRetval = useRetval;
809                        useRetval = false;
810                        appExpr->get_function()->acceptMutator( *this );
811                        mutateAll( appExpr->get_args(), *this );
812                        useRetval = oldUseRetval;
813
814                        assert( ! appExpr->get_function()->get_results().empty() );
815                        PointerType *pointer = dynamic_cast< PointerType *>( appExpr->get_function()->get_results().front() );
816                        assert( pointer );
817                        FunctionType *function = dynamic_cast< FunctionType *>( pointer->get_base() );
818                        assert( function );
819
820                        if ( Expression *newExpr = handleIntrinsics( appExpr ) ) {
821                                return newExpr;
822                        } // if
823
824                        Expression *ret = appExpr;
825
826                        std::list< Expression *>::iterator arg = appExpr->get_args().begin();
827                        std::list< Expression *>::iterator paramBegin = appExpr->get_args().begin();
828
829                        if ( ReferenceToType *polyType = isPolyRet( function ) ) {
830                                ret = addPolyRetParam( appExpr, function, polyType, arg );
831                        } else if ( needsAdapter( function, scopeTyVars ) ) {
832                                // std::cerr << "needs adapter: ";
833                                // for ( TyVarMap::iterator i = scopeTyVars.begin(); i != scopeTyVars.end(); ++i ) {
834                                //      std::cerr << i->first << " ";
835                                // }
836                                // std::cerr << "\n";
837                                // change the application so it calls the adapter rather than the passed function
838                                ret = applyAdapter( appExpr, function, arg, scopeTyVars );
839                        } // if
840                        arg = appExpr->get_args().begin();
841
842                        TyVarMap exprTyVars;
843                        makeTyVarMap( function, exprTyVars );
844
845                        passTypeVars( appExpr, arg, exprTyVars );
846                        addInferredParams( appExpr, function, arg, exprTyVars );
847
848                        arg = paramBegin;
849
850                        boxParams( appExpr, function, arg, exprTyVars );
851
852                        passAdapters( appExpr, function, exprTyVars );
853
854                        return ret;
855                }
856
857                Expression *Pass1::mutate( UntypedExpr *expr ) {
858                        if ( ! expr->get_results().empty() && isPolyType( expr->get_results().front(), scopeTyVars, env ) ) {
859                                if ( NameExpr *name = dynamic_cast< NameExpr *>( expr->get_function() ) ) {
860                                        if ( name->get_name() == "*?" ) {
861                                                Expression *ret = expr->get_args().front();
862                                                expr->get_args().clear();
863                                                delete expr;
864                                                return ret->acceptMutator( *this );
865                                        } // if
866                                } // if
867                        } // if
868                        return PolyMutator::mutate( expr );
869                }
870
871                Expression *Pass1::mutate( AddressExpr *addrExpr ) {
872                        assert( ! addrExpr->get_arg()->get_results().empty() );
873
874                        bool needs = false;
875                        if ( UntypedExpr *expr = dynamic_cast< UntypedExpr *>( addrExpr->get_arg() ) ) {
876                                if ( ! expr->get_results().empty() && isPolyType( expr->get_results().front(), scopeTyVars, env ) ) {
877                                        if ( NameExpr *name = dynamic_cast< NameExpr *>( expr->get_function() ) ) {
878                                                if ( name->get_name() == "*?" ) {
879                                                        if ( ApplicationExpr * appExpr = dynamic_cast< ApplicationExpr * >( expr->get_args().front() ) ) {
880                                                                assert( ! appExpr->get_function()->get_results().empty() );
881                                                                PointerType *pointer = dynamic_cast< PointerType *>( appExpr->get_function()->get_results().front() );
882                                                                assert( pointer );
883                                                                FunctionType *function = dynamic_cast< FunctionType *>( pointer->get_base() );
884                                                                assert( function );
885                                                                needs = needsAdapter( function, scopeTyVars );
886                                                        } // if
887                                                } // if
888                                        } // if
889                                } // if
890                        } // if
891                        addrExpr->set_arg( mutateExpression( addrExpr->get_arg() ) );
892                        if ( isPolyType( addrExpr->get_arg()->get_results().front(), scopeTyVars, env ) || needs ) {
893                                Expression *ret = addrExpr->get_arg();
894                                delete ret->get_results().front();
895                                ret->get_results().front() = addrExpr->get_results().front()->clone();
896                                addrExpr->set_arg( 0 );
897                                delete addrExpr;
898                                return ret;
899                        } else {
900                                return addrExpr;
901                        } // if
902                }
903
904                Statement * Pass1::mutate( ReturnStmt *returnStmt ) {
905                        if ( retval && returnStmt->get_expr() ) {
906                                assert( ! returnStmt->get_expr()->get_results().empty() );
907                                // ***** Code Removal ***** After introducing a temporary variable for all return expressions, the following code appears superfluous.
908                                // if ( returnStmt->get_expr()->get_results().front()->get_isLvalue() ) {
909                                // by this point, a cast expr on a polymorphic return value is redundant
910                                while ( CastExpr *castExpr = dynamic_cast< CastExpr *>( returnStmt->get_expr() ) ) {
911                                        returnStmt->set_expr( castExpr->get_arg() );
912                                        returnStmt->get_expr()->set_env( castExpr->get_env() );
913                                        castExpr->set_env( 0 );
914                                        castExpr->set_arg( 0 );
915                                        delete castExpr;
916                                } //while
917
918                                // find assignment operator for (polymorphic) return type
919                                DeclarationWithType *assignDecl = 0;
920                                if ( TypeInstType *typeInst = dynamic_cast< TypeInstType *>( retval->get_type() ) ) {
921                                        std::map< std::string, DeclarationWithType *>::const_iterator assignIter = assignOps.find( typeInst->get_name() );
922                                        if ( assignIter == assignOps.end() ) {
923                                                throw SemanticError( "Attempt to return dtype or ftype object in ", returnStmt->get_expr() );
924                                        } // if
925                                        assignDecl = assignIter->second;
926                                } else if ( ReferenceToType *refType = dynamic_cast< ReferenceToType *>( retval->get_type() ) ) {
927                                        ScopedMap< std::string, DeclarationWithType *>::const_iterator assignIter = scopedAssignOps.find( refType->get_name() );
928                                        if ( assignIter == scopedAssignOps.end() ) {
929                                                throw SemanticError( "Attempt to return dtype or ftype generic object in ", returnStmt->get_expr() );
930                                        }
931                                        assignDecl = new ObjectDecl( "", DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0,
932                                                                                                 new PointerType( Type::Qualifiers(), assignIter->second->get_type()->clone() ), 0 );
933                                }
934                                assert( assignDecl );
935
936                                // replace return statement with appropriate assignment to out parameter
937                                ApplicationExpr *assignExpr = new ApplicationExpr( new VariableExpr( assignDecl ) );
938                                Expression *retParm = new NameExpr( retval->get_name() );
939                                retParm->get_results().push_back( new PointerType( Type::Qualifiers(), retval->get_type()->clone() ) );
940                                assignExpr->get_args().push_back( retParm );
941                                assignExpr->get_args().push_back( returnStmt->get_expr() );
942                                stmtsToAdd.push_back( new ExprStmt( noLabels, mutateExpression( assignExpr ) ) );
943                                // } else {
944                                //      useRetval = true;
945                                //      stmtsToAdd.push_back( new ExprStmt( noLabels, mutateExpression( returnStmt->get_expr() ) ) );
946                                //      useRetval = false;
947                                // } // if
948                                returnStmt->set_expr( 0 );
949                        } else {
950                                returnStmt->set_expr( mutateExpression( returnStmt->get_expr() ) );
951                        } // if
952                        return returnStmt;
953                }
954
955                Type * Pass1::mutate( PointerType *pointerType ) {
956                        TyVarMap oldtyVars = scopeTyVars;
957                        makeTyVarMap( pointerType, scopeTyVars );
958
959                        Type *ret = Mutator::mutate( pointerType );
960
961                        scopeTyVars = oldtyVars;
962                        return ret;
963                }
964
965                Type * Pass1::mutate( FunctionType *functionType ) {
966                        TyVarMap oldtyVars = scopeTyVars;
967                        makeTyVarMap( functionType, scopeTyVars );
968
969                        Type *ret = Mutator::mutate( functionType );
970
971                        scopeTyVars = oldtyVars;
972                        return ret;
973                }
974
975                void Pass1::doBeginScope() {
976                        // push a copy of the current map
977                        adapters.push(adapters.top());
978                        scopedAssignOps.beginScope();
979                }
980
981                void Pass1::doEndScope() {
982                        adapters.pop();
983                        scopedAssignOps.endScope();
984                }
985
986////////////////////////////////////////// Pass2 ////////////////////////////////////////////////////
987
988                void Pass2::addAdapters( FunctionType *functionType ) {
989                        std::list< DeclarationWithType *> &paramList = functionType->get_parameters();
990                        std::list< FunctionType *> functions;
991                        for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
992                                Type *orig = (*arg)->get_type();
993                                findAndReplaceFunction( orig, functions, scopeTyVars, needsAdapter );
994                                (*arg)->set_type( orig );
995                        }
996                        std::set< std::string > adaptersDone;
997                        for ( std::list< FunctionType *>::iterator funType = functions.begin(); funType != functions.end(); ++funType ) {
998                                std::string mangleName = mangleAdapterName( *funType, scopeTyVars );
999                                if ( adaptersDone.find( mangleName ) == adaptersDone.end() ) {
1000                                        std::string adapterName = makeAdapterName( mangleName );
1001                                        paramList.push_front( new ObjectDecl( adapterName, DeclarationNode::NoStorageClass, LinkageSpec::C, 0, new PointerType( Type::Qualifiers(), makeAdapterType( *funType, scopeTyVars ) ), 0 ) );
1002                                        adaptersDone.insert( adaptersDone.begin(), mangleName );
1003                                }
1004                        }
1005//  deleteAll( functions );
1006                }
1007
1008                template< typename DeclClass >
1009                DeclClass * Pass2::handleDecl( DeclClass *decl, Type *type ) {
1010                        DeclClass *ret = static_cast< DeclClass *>( Mutator::mutate( decl ) );
1011
1012                        return ret;
1013                }
1014
1015                DeclarationWithType * Pass2::mutate( FunctionDecl *functionDecl ) {
1016                        return handleDecl( functionDecl, functionDecl->get_functionType() );
1017                }
1018
1019                ObjectDecl * Pass2::mutate( ObjectDecl *objectDecl ) {
1020                        return handleDecl( objectDecl, objectDecl->get_type() );
1021                }
1022
1023                TypeDecl * Pass2::mutate( TypeDecl *typeDecl ) {
1024                        scopeTyVars[ typeDecl->get_name() ] = typeDecl->get_kind();
1025                        if ( typeDecl->get_base() ) {
1026                                return handleDecl( typeDecl, typeDecl->get_base() );
1027                        } else {
1028                                return Mutator::mutate( typeDecl );
1029                        }
1030                }
1031
1032                TypedefDecl * Pass2::mutate( TypedefDecl *typedefDecl ) {
1033                        return handleDecl( typedefDecl, typedefDecl->get_base() );
1034                }
1035
1036                Type * Pass2::mutate( PointerType *pointerType ) {
1037                        TyVarMap oldtyVars = scopeTyVars;
1038                        makeTyVarMap( pointerType, scopeTyVars );
1039
1040                        Type *ret = Mutator::mutate( pointerType );
1041
1042                        scopeTyVars = oldtyVars;
1043                        return ret;
1044                }
1045
1046                Type *Pass2::mutate( FunctionType *funcType ) {
1047                        TyVarMap oldtyVars = scopeTyVars;
1048                        makeTyVarMap( funcType, scopeTyVars );
1049
1050                        // move polymorphic return type to parameter list
1051                        if ( isPolyRet( funcType ) ) {
1052                                DeclarationWithType *ret = funcType->get_returnVals().front();
1053                                ret->set_type( new PointerType( Type::Qualifiers(), ret->get_type() ) );
1054                                funcType->get_parameters().push_front( ret );
1055                                funcType->get_returnVals().pop_front();
1056                        }
1057
1058                        // add size/align and assertions for type parameters to parameter list
1059                        std::list< DeclarationWithType *>::iterator last = funcType->get_parameters().begin();
1060                        std::list< DeclarationWithType *> inferredParams;
1061                        ObjectDecl newObj( "", DeclarationNode::NoStorageClass, LinkageSpec::C, 0, new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ), 0 );
1062//   ObjectDecl *newFunPtr = new ObjectDecl( "", DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, new PointerType( Type::Qualifiers(), new FunctionType( Type::Qualifiers(), true ) ), 0 );
1063                        for ( std::list< TypeDecl *>::const_iterator tyParm = funcType->get_forall().begin(); tyParm != funcType->get_forall().end(); ++tyParm ) {
1064                                ObjectDecl *sizeParm, *alignParm;
1065                                // add all size and alignment parameters to parameter list
1066                                if ( (*tyParm)->get_kind() == TypeDecl::Any ) {
1067                                        TypeInstType parmType( Type::Qualifiers(), (*tyParm)->get_name(), *tyParm );
1068
1069                                        sizeParm = newObj.clone();
1070                                        sizeParm->set_name( sizeofName( &parmType ) );
1071                                        last = funcType->get_parameters().insert( last, sizeParm );
1072                                        ++last;
1073
1074                                        alignParm = newObj.clone();
1075                                        alignParm->set_name( alignofName( &parmType ) );
1076                                        last = funcType->get_parameters().insert( last, alignParm );
1077                                        ++last;
1078                                }
1079                                // move all assertions into parameter list
1080                                for ( std::list< DeclarationWithType *>::iterator assert = (*tyParm)->get_assertions().begin(); assert != (*tyParm)->get_assertions().end(); ++assert ) {
1081//      *assert = (*assert)->acceptMutator( *this );
1082                                        inferredParams.push_back( *assert );
1083                                }
1084                                (*tyParm)->get_assertions().clear();
1085                        }
1086
1087                        // add size/align for generic types to parameter list
1088                        std::set< std::string > seenTypes; // sizeofName for generic types we've seen
1089                        for ( std::list< DeclarationWithType* >::const_iterator fnParm = last; fnParm != funcType->get_parameters().end(); ++fnParm ) {
1090                                Type *parmType = (*fnParm)->get_type();
1091                                if ( ! dynamic_cast< TypeInstType* >( parmType ) && isPolyType( parmType, scopeTyVars ) ) {
1092                                        std::string sizeName = sizeofName( parmType );
1093                                        if ( seenTypes.count( sizeName ) ) continue;
1094
1095                                        ObjectDecl *sizeParm, *alignParm;
1096                                        sizeParm = newObj.clone();
1097                                        sizeParm->set_name( sizeName );
1098                                        last = funcType->get_parameters().insert( last, sizeParm );
1099                                        ++last;
1100
1101                                        alignParm = newObj.clone();
1102                                        alignParm->set_name( alignofName( parmType ) );
1103                                        last = funcType->get_parameters().insert( last, alignParm );
1104                                        ++last;
1105
1106                                        seenTypes.insert( sizeName );
1107                                }
1108                        }
1109
1110                        // splice assertion parameters into parameter list
1111                        funcType->get_parameters().splice( last, inferredParams );
1112                        addAdapters( funcType );
1113                        mutateAll( funcType->get_returnVals(), *this );
1114                        mutateAll( funcType->get_parameters(), *this );
1115
1116                        scopeTyVars = oldtyVars;
1117                        return funcType;
1118                }
1119
1120////////////////////////////////////////// Pass3 ////////////////////////////////////////////////////
1121
1122                template< typename DeclClass >
1123                DeclClass * Pass3::handleDecl( DeclClass *decl, Type *type ) {
1124                        TyVarMap oldtyVars = scopeTyVars;
1125                        makeTyVarMap( type, scopeTyVars );
1126
1127                        DeclClass *ret = static_cast< DeclClass *>( Mutator::mutate( decl ) );
1128                        ScrubTyVars::scrub( decl, scopeTyVars );
1129
1130                        scopeTyVars = oldtyVars;
1131                        return ret;
1132                }
1133
1134                ObjectDecl * Pass3::mutate( ObjectDecl *objectDecl ) {
1135                        return handleDecl( objectDecl, objectDecl->get_type() );
1136                }
1137
1138                DeclarationWithType * Pass3::mutate( FunctionDecl *functionDecl ) {
1139                        return handleDecl( functionDecl, functionDecl->get_functionType() );
1140                }
1141
1142                TypedefDecl * Pass3::mutate( TypedefDecl *typedefDecl ) {
1143                        return handleDecl( typedefDecl, typedefDecl->get_base() );
1144                }
1145
1146                TypeDecl * Pass3::mutate( TypeDecl *typeDecl ) {
1147//   Initializer *init = 0;
1148//   std::list< Expression *> designators;
1149//   scopeTyVars[ typeDecl->get_name() ] = typeDecl->get_kind();
1150//   if ( typeDecl->get_base() ) {
1151//     init = new SimpleInit( new SizeofExpr( handleDecl( typeDecl, typeDecl->get_base() ) ), designators );
1152//   }
1153//   return new ObjectDecl( typeDecl->get_name(), Declaration::Extern, LinkageSpec::C, 0, new BasicType( Type::Qualifiers(), BasicType::UnsignedInt ), init );
1154
1155                        scopeTyVars[ typeDecl->get_name() ] = typeDecl->get_kind();
1156                        return Mutator::mutate( typeDecl );
1157                }
1158
1159                Type * Pass3::mutate( PointerType *pointerType ) {
1160                        TyVarMap oldtyVars = scopeTyVars;
1161                        makeTyVarMap( pointerType, scopeTyVars );
1162
1163                        Type *ret = Mutator::mutate( pointerType );
1164
1165                        scopeTyVars = oldtyVars;
1166                        return ret;
1167                }
1168
1169                Type * Pass3::mutate( FunctionType *functionType ) {
1170                        TyVarMap oldtyVars = scopeTyVars;
1171                        makeTyVarMap( functionType, scopeTyVars );
1172
1173                        Type *ret = Mutator::mutate( functionType );
1174
1175                        scopeTyVars = oldtyVars;
1176                        return ret;
1177                }
1178
1179                Statement *Pass3::mutate( DeclStmt *declStmt ) {
1180                        if ( ObjectDecl *objectDecl = dynamic_cast< ObjectDecl *>( declStmt->get_decl() ) ) {
1181                                if ( isPolyType( objectDecl->get_type(), scopeTyVars ) ) {
1182                                        // change initialization of a polymorphic value object
1183                                        // to allocate storage with alloca
1184                                        Type *declType = objectDecl->get_type();
1185                                        UntypedExpr *alloc = new UntypedExpr( new NameExpr( "__builtin_alloca" ) );
1186                                        alloc->get_args().push_back( new NameExpr( sizeofName( declType ) ) );
1187
1188                                        delete objectDecl->get_init();
1189
1190                                        std::list<Expression*> designators;
1191                                        objectDecl->set_init( new SingleInit( alloc, designators ) );
1192                                }
1193                        }
1194                        return Mutator::mutate( declStmt );
1195                }
1196        } // anonymous namespace
1197} // namespace GenPoly
1198
1199// Local Variables: //
1200// tab-width: 4 //
1201// mode: c++ //
1202// compile-command: "make install" //
1203// End: //
Note: See TracBrowser for help on using the repository browser.