source: src/GenPoly/Box.cc @ d63eeb0

ADTaaron-thesisarm-ehast-experimentalcleanup-dtorsctordeferred_resndemanglerenumforall-pointer-decaygc_noraiijacob/cs343-translationjenkins-sandboxmemorynew-astnew-ast-unique-exprnew-envno_listpersistent-indexerpthread-emulationqualifiedEnumresolv-newwith_gc
Last change on this file since d63eeb0 was d63eeb0, checked in by Rob Schluntz <rschlunt@…>, 8 years ago

Merge branch 'master' into ctor

Conflicts:

src/CodeGen/CodeGenerator.cc
src/GenPoly/Box.cc
src/Makefile.in
src/Parser/ParseNode.h
src/Parser/parser.cc
src/Parser/parser.yy
src/SymTab/Validate.cc
src/SynTree/Initializer.h
src/SynTree/ObjectDecl.cc
src/SynTree/Visitor.h
src/main.cc

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