source: src/GenPoly/Box.cc @ 1aa4b71

ADTaaron-thesisarm-ehast-experimentalcleanup-dtorsdeferred_resndemanglerenumforall-pointer-decayjacob/cs343-translationjenkins-sandboxnew-astnew-ast-unique-exprnew-envno_listpersistent-indexerpthread-emulationqualifiedEnumresolv-newwith_gc
Last change on this file since 1aa4b71 was cce9429, checked in by Rob Schluntz <rschlunt@…>, 7 years ago

fix function return type in Validate and add single return decl, construct the return decl, fix polymorphic functions to use the return decl

  • Property mode set to 100644
File size: 99.0 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 : Peter A. Buhr
12// Last Modified On : Wed Jun 29 21:43:03 2016
13// Update Count     : 296
14//
15
16#include <algorithm>
17#include <iterator>
18#include <list>
19#include <map>
20#include <set>
21#include <stack>
22#include <string>
23#include <utility>
24#include <vector>
25#include <cassert>
26
27#include "Box.h"
28#include "DeclMutator.h"
29#include "PolyMutator.h"
30#include "FindFunction.h"
31#include "ScopedSet.h"
32#include "ScrubTyVars.h"
33
34#include "Parser/ParseNode.h"
35
36#include "SynTree/Constant.h"
37#include "SynTree/Declaration.h"
38#include "SynTree/Expression.h"
39#include "SynTree/Initializer.h"
40#include "SynTree/Mutator.h"
41#include "SynTree/Statement.h"
42#include "SynTree/Type.h"
43#include "SynTree/TypeSubstitution.h"
44
45#include "ResolvExpr/TypeEnvironment.h"
46#include "ResolvExpr/TypeMap.h"
47#include "ResolvExpr/typeops.h"
48
49#include "SymTab/Indexer.h"
50#include "SymTab/Mangler.h"
51
52#include "Common/ScopedMap.h"
53#include "Common/SemanticError.h"
54#include "Common/UniqueName.h"
55#include "Common/utility.h"
56
57#include <ext/functional> // temporary
58
59namespace GenPoly {
60        namespace {
61                const std::list<Label> noLabels;
62
63                FunctionType *makeAdapterType( FunctionType *adaptee, const TyVarMap &tyVars );
64
65                /// Adds layout-generation functions to polymorphic types
66                class LayoutFunctionBuilder final : public DeclMutator {
67                        unsigned int functionNesting;  // current level of nested functions
68                public:
69                        LayoutFunctionBuilder() : functionNesting( 0 ) {}
70
71                        using DeclMutator::mutate;
72                        virtual DeclarationWithType *mutate( FunctionDecl *functionDecl ) override;
73                        virtual Declaration *mutate( StructDecl *structDecl ) override;
74                        virtual Declaration *mutate( UnionDecl *unionDecl ) override;
75                };
76
77                /// 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
78                class Pass1 final : public PolyMutator {
79                  public:
80                        Pass1();
81
82                        using PolyMutator::mutate;
83                        virtual Expression *mutate( ApplicationExpr *appExpr ) override;
84                        virtual Expression *mutate( AddressExpr *addrExpr ) override;
85                        virtual Expression *mutate( UntypedExpr *expr ) override;
86                        virtual DeclarationWithType* mutate( FunctionDecl *functionDecl ) override;
87                        virtual TypeDecl *mutate( TypeDecl *typeDecl ) override;
88                        virtual Expression *mutate( CommaExpr *commaExpr ) override;
89                        virtual Expression *mutate( ConditionalExpr *condExpr ) override;
90                        virtual Statement * mutate( ReturnStmt *returnStmt ) override;
91                        virtual Type *mutate( PointerType *pointerType ) override;
92                        virtual Type * mutate( FunctionType *functionType ) override;
93
94                        virtual void doBeginScope() override;
95                        virtual void doEndScope() override;
96                  private:
97                        /// Pass the extra type parameters from polymorphic generic arguments or return types into a function application
98                        void passArgTypeVars( ApplicationExpr *appExpr, Type *parmType, Type *argBaseType, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars, std::set< std::string > &seenTypes );
99                        /// passes extra type parameters into a polymorphic function application
100                        void passTypeVars( ApplicationExpr *appExpr, Type *polyRetType, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars );
101                        /// wraps a function application with a new temporary for the out-parameter return value
102                        Expression *addRetParam( ApplicationExpr *appExpr, FunctionType *function, Type *retType, std::list< Expression *>::iterator &arg );
103                        /// Replaces all the type parameters of a generic type with their concrete equivalents under the current environment
104                        void replaceParametersWithConcrete( ApplicationExpr *appExpr, std::list< Expression* >& params );
105                        /// Replaces a polymorphic type with its concrete equivalant under the current environment (returns itself if concrete).
106                        /// If `doClone` is set to false, will not clone interior types
107                        Type *replaceWithConcrete( ApplicationExpr *appExpr, Type *type, bool doClone = true );
108                        /// wraps a function application returning a polymorphic type with a new temporary for the out-parameter return value
109                        Expression *addDynRetParam( ApplicationExpr *appExpr, FunctionType *function, Type *polyType, std::list< Expression *>::iterator &arg );
110                        Expression *applyAdapter( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars );
111                        void boxParam( Type *formal, Expression *&arg, const TyVarMap &exprTyVars );
112                        void boxParams( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars );
113                        void addInferredParams( ApplicationExpr *appExpr, FunctionType *functionType, std::list< Expression *>::iterator &arg, const TyVarMap &tyVars );
114                        /// Stores assignment operators from assertion list in local map of assignment operations
115                        void findTypeOps( const Type::ForallList &forall );
116                        void passAdapters( ApplicationExpr *appExpr, FunctionType *functionType, const TyVarMap &exprTyVars );
117                        FunctionDecl *makeAdapter( FunctionType *adaptee, FunctionType *realType, const std::string &mangleName, const TyVarMap &tyVars );
118                        /// Replaces intrinsic operator functions with their arithmetic desugaring
119                        Expression *handleIntrinsics( ApplicationExpr *appExpr );
120                        /// Inserts a new temporary variable into the current scope with an auto-generated name
121                        ObjectDecl *makeTemporary( Type *type );
122
123                        ScopedMap< std::string, DeclarationWithType* > assignOps;    ///< Currently known type variable assignment operators
124                        ScopedMap< std::string, DeclarationWithType* > ctorOps;      ///< Currently known type variable constructors
125                        ScopedMap< std::string, DeclarationWithType* > copyOps;      ///< Currently known type variable copy constructors
126                        ScopedMap< std::string, DeclarationWithType* > dtorOps;      ///< Currently known type variable destructors
127                        ResolvExpr::TypeMap< DeclarationWithType > scopedAssignOps;  ///< Currently known assignment operators
128                        ResolvExpr::TypeMap< DeclarationWithType > scopedCtorOps;    ///< Currently known assignment operators
129                        ResolvExpr::TypeMap< DeclarationWithType > scopedCopyOps;    ///< Currently known assignment operators
130                        ResolvExpr::TypeMap< DeclarationWithType > scopedDtorOps;    ///< Currently known assignment operators
131                        ScopedMap< std::string, DeclarationWithType* > adapters;     ///< Set of adapter functions in the current scope
132
133                        std::map< ApplicationExpr *, Expression * > retVals;
134
135                        DeclarationWithType *retval;
136                        UniqueName tempNamer;
137                };
138
139                /// * Moves polymorphic returns in function types to pointer-type parameters
140                /// * adds type size and assertion parameters to parameter lists
141                class Pass2 final : public PolyMutator {
142                  public:
143                        template< typename DeclClass >
144                        DeclClass *handleDecl( DeclClass *decl, Type *type );
145
146                        using PolyMutator::mutate;
147                        virtual DeclarationWithType *mutate( FunctionDecl *functionDecl ) override;
148                        virtual ObjectDecl *mutate( ObjectDecl *objectDecl ) override;
149                        virtual TypeDecl *mutate( TypeDecl *typeDecl ) override;
150                        virtual TypedefDecl *mutate( TypedefDecl *typedefDecl ) override;
151                        virtual Type *mutate( PointerType *pointerType ) override;
152                        virtual Type *mutate( FunctionType *funcType ) override;
153
154                  private:
155                        void addAdapters( FunctionType *functionType );
156
157                        std::map< UniqueId, std::string > adapterName;
158                };
159
160                /// Replaces member and size/align/offsetof expressions on polymorphic generic types with calculated expressions.
161                /// * Replaces member expressions for polymorphic types with calculated add-field-offset-and-dereference
162                /// * Calculates polymorphic offsetof expressions from offset array
163                /// * Inserts dynamic calculation of polymorphic type layouts where needed
164                class PolyGenericCalculator final : public PolyMutator {
165                public:
166                        typedef PolyMutator Parent;
167                        using Parent::mutate;
168
169                        template< typename DeclClass >
170                        DeclClass *handleDecl( DeclClass *decl, Type *type );
171                        virtual DeclarationWithType *mutate( FunctionDecl *functionDecl ) override;
172                        virtual ObjectDecl *mutate( ObjectDecl *objectDecl ) override;
173                        virtual TypedefDecl *mutate( TypedefDecl *objectDecl ) override;
174                        virtual TypeDecl *mutate( TypeDecl *objectDecl ) override;
175                        virtual Statement *mutate( DeclStmt *declStmt ) override;
176                        virtual Type *mutate( PointerType *pointerType ) override;
177                        virtual Type *mutate( FunctionType *funcType ) override;
178                        virtual Expression *mutate( MemberExpr *memberExpr ) override;
179                        virtual Expression *mutate( SizeofExpr *sizeofExpr ) override;
180                        virtual Expression *mutate( AlignofExpr *alignofExpr ) override;
181                        virtual Expression *mutate( OffsetofExpr *offsetofExpr ) override;
182                        virtual Expression *mutate( OffsetPackExpr *offsetPackExpr ) override;
183
184                        virtual void doBeginScope() override;
185                        virtual void doEndScope() override;
186
187                private:
188                        /// Makes a new variable in the current scope with the given name, type & optional initializer
189                        ObjectDecl *makeVar( const std::string &name, Type *type, Initializer *init = 0 );
190                        /// returns true if the type has a dynamic layout; such a layout will be stored in appropriately-named local variables when the function returns
191                        bool findGeneric( Type *ty );
192                        /// adds type parameters to the layout call; will generate the appropriate parameters if needed
193                        void addOtypeParamsToLayoutCall( UntypedExpr *layoutCall, const std::list< Type* > &otypeParams );
194
195                        /// Enters a new scope for type-variables, adding the type variables from ty
196                        void beginTypeScope( Type *ty );
197                        /// Exits the type-variable scope
198                        void endTypeScope();
199
200                        ScopedSet< std::string > knownLayouts;          ///< Set of generic type layouts known in the current scope, indexed by sizeofName
201                        ScopedSet< std::string > knownOffsets;          ///< Set of non-generic types for which the offset array exists in the current scope, indexed by offsetofName
202                };
203
204                /// 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
205                class Pass3 final : public PolyMutator {
206                  public:
207                        template< typename DeclClass >
208                        DeclClass *handleDecl( DeclClass *decl, Type *type );
209
210                        using PolyMutator::mutate;
211                        virtual DeclarationWithType *mutate( FunctionDecl *functionDecl ) override;
212                        virtual ObjectDecl *mutate( ObjectDecl *objectDecl ) override;
213                        virtual TypedefDecl *mutate( TypedefDecl *objectDecl ) override;
214                        virtual TypeDecl *mutate( TypeDecl *objectDecl ) override;
215                        virtual Type *mutate( PointerType *pointerType ) override;
216                        virtual Type *mutate( FunctionType *funcType ) override;
217                  private:
218                };
219
220        } // anonymous namespace
221
222        /// version of mutateAll with special handling for translation unit so you can check the end of the prelude when debugging
223        template< typename MutatorType >
224        inline void mutateTranslationUnit( std::list< Declaration* > &translationUnit, MutatorType &mutator ) {
225                bool seenIntrinsic = false;
226                SemanticError errors;
227                for ( typename std::list< Declaration* >::iterator i = translationUnit.begin(); i != translationUnit.end(); ++i ) {
228                        try {
229                                if ( *i ) {
230                                        if ( (*i)->get_linkage() == LinkageSpec::Intrinsic ) {
231                                                seenIntrinsic = true;
232                                        } else if ( seenIntrinsic ) {
233                                                seenIntrinsic = false; // break on this line when debugging for end of prelude
234                                        }
235
236                                        *i = dynamic_cast< Declaration* >( (*i)->acceptMutator( mutator ) );
237                                        assert( *i );
238                                } // if
239                        } catch( SemanticError &e ) {
240                                errors.append( e );
241                        } // try
242                } // for
243                if ( ! errors.isEmpty() ) {
244                        throw errors;
245                } // if
246        }
247
248        void box( std::list< Declaration *>& translationUnit ) {
249                LayoutFunctionBuilder layoutBuilder;
250                Pass1 pass1;
251                Pass2 pass2;
252                PolyGenericCalculator polyCalculator;
253                Pass3 pass3;
254
255                layoutBuilder.mutateDeclarationList( translationUnit );
256                mutateTranslationUnit/*All*/( translationUnit, pass1 );
257                mutateTranslationUnit/*All*/( translationUnit, pass2 );
258                mutateTranslationUnit/*All*/( translationUnit, polyCalculator );
259                mutateTranslationUnit/*All*/( translationUnit, pass3 );
260        }
261
262        ////////////////////////////////// LayoutFunctionBuilder ////////////////////////////////////////////
263
264        DeclarationWithType *LayoutFunctionBuilder::mutate( FunctionDecl *functionDecl ) {
265                functionDecl->set_functionType( maybeMutate( functionDecl->get_functionType(), *this ) );
266                mutateAll( functionDecl->get_oldDecls(), *this );
267                ++functionNesting;
268                functionDecl->set_statements( maybeMutate( functionDecl->get_statements(), *this ) );
269                --functionNesting;
270                return functionDecl;
271        }
272
273        /// Get a list of type declarations that will affect a layout function
274        std::list< TypeDecl* > takeOtypeOnly( std::list< TypeDecl* > &decls ) {
275                std::list< TypeDecl * > otypeDecls;
276
277                for ( std::list< TypeDecl* >::const_iterator decl = decls.begin(); decl != decls.end(); ++decl ) {
278                        if ( (*decl)->isComplete() ) {
279                                otypeDecls.push_back( *decl );
280                        }
281                }
282
283                return otypeDecls;
284        }
285
286        /// Adds parameters for otype layout to a function type
287        void addOtypeParams( FunctionType *layoutFnType, std::list< TypeDecl* > &otypeParams ) {
288                BasicType sizeAlignType( Type::Qualifiers(), BasicType::LongUnsignedInt );
289
290                for ( std::list< TypeDecl* >::const_iterator param = otypeParams.begin(); param != otypeParams.end(); ++param ) {
291                        TypeInstType paramType( Type::Qualifiers(), (*param)->get_name(), *param );
292                        std::string paramName = mangleType( &paramType );
293                        layoutFnType->get_parameters().push_back( new ObjectDecl( sizeofName( paramName ), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignType.clone(), 0 ) );
294                        layoutFnType->get_parameters().push_back( new ObjectDecl( alignofName( paramName ), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignType.clone(), 0 ) );
295                }
296        }
297
298        /// Builds a layout function declaration
299        FunctionDecl *buildLayoutFunctionDecl( AggregateDecl *typeDecl, unsigned int functionNesting, FunctionType *layoutFnType ) {
300                // Routines at global scope marked "static" to prevent multiple definitions is separate translation units
301                // because each unit generates copies of the default routines for each aggregate.
302                FunctionDecl *layoutDecl = new FunctionDecl(
303                        layoutofName( typeDecl ), functionNesting > 0 ? DeclarationNode::NoStorageClass : DeclarationNode::Static, LinkageSpec::AutoGen, layoutFnType, new CompoundStmt( noLabels ), true, false );
304                layoutDecl->fixUniqueId();
305                return layoutDecl;
306        }
307
308        /// Makes a unary operation
309        Expression *makeOp( const std::string &name, Expression *arg ) {
310                UntypedExpr *expr = new UntypedExpr( new NameExpr( name ) );
311                expr->get_args().push_back( arg );
312                return expr;
313        }
314
315        /// Makes a binary operation
316        Expression *makeOp( const std::string &name, Expression *lhs, Expression *rhs ) {
317                UntypedExpr *expr = new UntypedExpr( new NameExpr( name ) );
318                expr->get_args().push_back( lhs );
319                expr->get_args().push_back( rhs );
320                return expr;
321        }
322
323        /// Returns the dereference of a local pointer variable
324        Expression *derefVar( ObjectDecl *var ) {
325                return makeOp( "*?", new VariableExpr( var ) );
326        }
327
328        /// makes an if-statement with a single-expression if-block and no then block
329        Statement *makeCond( Expression *cond, Expression *ifPart ) {
330                return new IfStmt( noLabels, cond, new ExprStmt( noLabels, ifPart ), 0 );
331        }
332
333        /// makes a statement that assigns rhs to lhs if lhs < rhs
334        Statement *makeAssignMax( Expression *lhs, Expression *rhs ) {
335                return makeCond( makeOp( "?<?", lhs, rhs ), makeOp( "?=?", lhs->clone(), rhs->clone() ) );
336        }
337
338        /// makes a statement that aligns lhs to rhs (rhs should be an integer power of two)
339        Statement *makeAlignTo( Expression *lhs, Expression *rhs ) {
340                // check that the lhs is zeroed out to the level of rhs
341                Expression *ifCond = makeOp( "?&?", lhs, makeOp( "?-?", rhs, new ConstantExpr( Constant( new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ), "1" ) ) ) );
342                // if not aligned, increment to alignment
343                Expression *ifExpr = makeOp( "?+=?", lhs->clone(), makeOp( "?-?", rhs->clone(), ifCond->clone() ) );
344                return makeCond( ifCond, ifExpr );
345        }
346
347        /// adds an expression to a compound statement
348        void addExpr( CompoundStmt *stmts, Expression *expr ) {
349                stmts->get_kids().push_back( new ExprStmt( noLabels, expr ) );
350        }
351
352        /// adds a statement to a compound statement
353        void addStmt( CompoundStmt *stmts, Statement *stmt ) {
354                stmts->get_kids().push_back( stmt );
355        }
356
357        Declaration *LayoutFunctionBuilder::mutate( StructDecl *structDecl ) {
358                // do not generate layout function for "empty" tag structs
359                if ( structDecl->get_members().empty() ) return structDecl;
360
361                // get parameters that can change layout, exiting early if none
362                std::list< TypeDecl* > otypeParams = takeOtypeOnly( structDecl->get_parameters() );
363                if ( otypeParams.empty() ) return structDecl;
364
365                // build layout function signature
366                FunctionType *layoutFnType = new FunctionType( Type::Qualifiers(), false );
367                BasicType *sizeAlignType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
368                PointerType *sizeAlignOutType = new PointerType( Type::Qualifiers(), sizeAlignType );
369
370                ObjectDecl *sizeParam = new ObjectDecl( sizeofName( structDecl->get_name() ), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignOutType, 0 );
371                layoutFnType->get_parameters().push_back( sizeParam );
372                ObjectDecl *alignParam = new ObjectDecl( alignofName( structDecl->get_name() ), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignOutType->clone(), 0 );
373                layoutFnType->get_parameters().push_back( alignParam );
374                ObjectDecl *offsetParam = new ObjectDecl( offsetofName( structDecl->get_name() ), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignOutType->clone(), 0 );
375                layoutFnType->get_parameters().push_back( offsetParam );
376                addOtypeParams( layoutFnType, otypeParams );
377
378                // build function decl
379                FunctionDecl *layoutDecl = buildLayoutFunctionDecl( structDecl, functionNesting, layoutFnType );
380
381                // calculate struct layout in function body
382
383                // initialize size and alignment to 0 and 1 (will have at least one member to re-edit size
384                addExpr( layoutDecl->get_statements(), makeOp( "?=?", derefVar( sizeParam ), new ConstantExpr( Constant( sizeAlignType->clone(), "0" ) ) ) );
385                addExpr( layoutDecl->get_statements(), makeOp( "?=?", derefVar( alignParam ), new ConstantExpr( Constant( sizeAlignType->clone(), "1" ) ) ) );
386                unsigned long n_members = 0;
387                bool firstMember = true;
388                for ( std::list< Declaration* >::const_iterator member = structDecl->get_members().begin(); member != structDecl->get_members().end(); ++member ) {
389                        DeclarationWithType *dwt = dynamic_cast< DeclarationWithType * >( *member );
390                        assert( dwt );
391                        Type *memberType = dwt->get_type();
392
393                        if ( firstMember ) {
394                                firstMember = false;
395                        } else {
396                                // make sure all members after the first (automatically aligned at 0) are properly padded for alignment
397                                addStmt( layoutDecl->get_statements(), makeAlignTo( derefVar( sizeParam ), new AlignofExpr( memberType->clone() ) ) );
398                        }
399
400                        // place current size in the current offset index
401                        addExpr( layoutDecl->get_statements(), makeOp( "?=?", makeOp( "?[?]", new VariableExpr( offsetParam ), new ConstantExpr( Constant::from_ulong( n_members ) ) ),
402                                                                              derefVar( sizeParam ) ) );
403                        ++n_members;
404
405                        // add member size to current size
406                        addExpr( layoutDecl->get_statements(), makeOp( "?+=?", derefVar( sizeParam ), new SizeofExpr( memberType->clone() ) ) );
407
408                        // take max of member alignment and global alignment
409                        addStmt( layoutDecl->get_statements(), makeAssignMax( derefVar( alignParam ), new AlignofExpr( memberType->clone() ) ) );
410                }
411                // make sure the type is end-padded to a multiple of its alignment
412                addStmt( layoutDecl->get_statements(), makeAlignTo( derefVar( sizeParam ), derefVar( alignParam ) ) );
413
414                addDeclarationAfter( layoutDecl );
415                return structDecl;
416        }
417
418        Declaration *LayoutFunctionBuilder::mutate( UnionDecl *unionDecl ) {
419                // do not generate layout function for "empty" tag unions
420                if ( unionDecl->get_members().empty() ) return unionDecl;
421
422                // get parameters that can change layout, exiting early if none
423                std::list< TypeDecl* > otypeParams = takeOtypeOnly( unionDecl->get_parameters() );
424                if ( otypeParams.empty() ) return unionDecl;
425
426                // build layout function signature
427                FunctionType *layoutFnType = new FunctionType( Type::Qualifiers(), false );
428                BasicType *sizeAlignType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
429                PointerType *sizeAlignOutType = new PointerType( Type::Qualifiers(), sizeAlignType );
430
431                ObjectDecl *sizeParam = new ObjectDecl( sizeofName( unionDecl->get_name() ), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignOutType, 0 );
432                layoutFnType->get_parameters().push_back( sizeParam );
433                ObjectDecl *alignParam = new ObjectDecl( alignofName( unionDecl->get_name() ), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignOutType->clone(), 0 );
434                layoutFnType->get_parameters().push_back( alignParam );
435                addOtypeParams( layoutFnType, otypeParams );
436
437                // build function decl
438                FunctionDecl *layoutDecl = buildLayoutFunctionDecl( unionDecl, functionNesting, layoutFnType );
439
440                // calculate union layout in function body
441                addExpr( layoutDecl->get_statements(), makeOp( "?=?", derefVar( sizeParam ), new ConstantExpr( Constant( sizeAlignType->clone(), "1" ) ) ) );
442                addExpr( layoutDecl->get_statements(), makeOp( "?=?", derefVar( alignParam ), new ConstantExpr( Constant( sizeAlignType->clone(), "1" ) ) ) );
443                for ( std::list< Declaration* >::const_iterator member = unionDecl->get_members().begin(); member != unionDecl->get_members().end(); ++member ) {
444                        DeclarationWithType *dwt = dynamic_cast< DeclarationWithType * >( *member );
445                        assert( dwt );
446                        Type *memberType = dwt->get_type();
447
448                        // take max member size and global size
449                        addStmt( layoutDecl->get_statements(), makeAssignMax( derefVar( sizeParam ), new SizeofExpr( memberType->clone() ) ) );
450
451                        // take max of member alignment and global alignment
452                        addStmt( layoutDecl->get_statements(), makeAssignMax( derefVar( alignParam ), new AlignofExpr( memberType->clone() ) ) );
453                }
454                // make sure the type is end-padded to a multiple of its alignment
455                addStmt( layoutDecl->get_statements(), makeAlignTo( derefVar( sizeParam ), derefVar( alignParam ) ) );
456
457                addDeclarationAfter( layoutDecl );
458                return unionDecl;
459        }
460
461        ////////////////////////////////////////// Pass1 ////////////////////////////////////////////////////
462
463        namespace {
464                std::string makePolyMonoSuffix( FunctionType * function, const TyVarMap &tyVars ) {
465                        std::stringstream name;
466
467                        // NOTE: this function previously used isPolyObj, which failed to produce
468                        // the correct thing in some situations. It's not clear to me why this wasn't working.
469
470                        // if the return type or a parameter type involved polymorphic types, then the adapter will need
471                        // to take those polymorphic types as pointers. Therefore, there can be two different functions
472                        // with the same mangled name, so we need to further mangle the names.
473                        for ( std::list< DeclarationWithType *>::iterator retval = function->get_returnVals().begin(); retval != function->get_returnVals().end(); ++retval ) {
474                                if ( isPolyType( (*retval)->get_type(), tyVars ) ) {
475                                        name << "P";
476                                } else {
477                                        name << "M";
478                                }
479                        }
480                        name << "_";
481                        std::list< DeclarationWithType *> &paramList = function->get_parameters();
482                        for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
483                                if ( isPolyType( (*arg)->get_type(), tyVars ) ) {
484                                        name << "P";
485                                } else {
486                                        name << "M";
487                                }
488                        } // for
489                        return name.str();
490                }
491
492                std::string mangleAdapterName( FunctionType * function, const TyVarMap &tyVars ) {
493                        return SymTab::Mangler::mangle( function ) + makePolyMonoSuffix( function, tyVars );
494                }
495
496                std::string makeAdapterName( const std::string &mangleName ) {
497                        return "_adapter" + mangleName;
498                }
499
500                Pass1::Pass1() : tempNamer( "_temp" ) {}
501
502                /// Returns T if the given declaration is a function with parameter (T*) for some TypeInstType T, NULL otherwise
503                TypeInstType *isTypeInstPtrFn( DeclarationWithType *decl ) {
504                        if ( FunctionType *funType = getFunctionType( decl->get_type() ) ) {
505                                if ( funType->get_parameters().size() == 1 ) {
506                                        if ( PointerType *pointer = dynamic_cast< PointerType *>( funType->get_parameters().front()->get_type() ) ) {
507                                                if ( TypeInstType *refType = dynamic_cast< TypeInstType *>( pointer->get_base() ) ) {
508                                                        return refType;
509                                                } // if
510                                        } // if
511                                } // if
512                        } // if
513                        return 0;
514                }
515
516                /// Returns T if the given declaration is a function with parameters (T*, T) for some TypeInstType T, NULL otherwise
517                TypeInstType *isTypeInstPtrValFn( DeclarationWithType *decl ) {
518                        if ( FunctionType *funType = getFunctionType( decl->get_type() ) ) {
519                                if ( funType->get_parameters().size() == 2 ) {
520                                        if ( PointerType *pointer = dynamic_cast< PointerType *>( funType->get_parameters().front()->get_type() ) ) {
521                                                if ( TypeInstType *refType = dynamic_cast< TypeInstType *>( pointer->get_base() ) ) {
522                                                        if ( TypeInstType *refType2 = dynamic_cast< TypeInstType *>( funType->get_parameters().back()->get_type() ) ) {
523                                                                if ( refType->get_name() == refType2->get_name() ) {
524                                                                        return refType;
525                                                                } // if
526                                                        } // if
527                                                } // if
528                                        } // if
529                                } // if
530                        } // if
531                        return 0;
532                }
533
534                /// Returns T if the given declaration is (*?=?)(T *, T) for some TypeInstType T (return not checked, but maybe should be), NULL otherwise
535                TypeInstType *isTypeInstAssignment( DeclarationWithType *decl ) {
536                        return decl->get_name() == "?=?" ? isTypeInstPtrValFn( decl ) : 0;
537                }
538
539                /// Returns T if the given declaration is (*?{})(T *) for some TypeInstType T (return not checked, but maybe should be), NULL otherwise
540                TypeInstType *isTypeInstCtor( DeclarationWithType *decl ) {
541                        return decl->get_name() == "?{}" ? isTypeInstPtrFn( decl ) : 0;
542                }
543
544                /// Returns T if the given declaration is (*?{})(T *, T) for some TypeInstType T (return not checked, but maybe should be), NULL otherwise
545                TypeInstType *isTypeInstCopy( DeclarationWithType *decl ) {
546                        return decl->get_name() == "?{}" ? isTypeInstPtrValFn( decl ) : 0;
547                }
548
549                /// Returns T if the given declaration is (*^?{})(T *) for some TypeInstType T (return not checked, but maybe should be), NULL otherwise
550                TypeInstType *isTypeInstDtor( DeclarationWithType *decl ) {
551                        return decl->get_name() == "^?{}" ? isTypeInstPtrFn( decl ) : 0;
552                }
553
554                /// Returns T if the given declaration is a function with parameters (T*, T) for some type T, where neither parameter is cv-qualified,
555                /// NULL otherwise
556                Type *isNoCvPtrFn( DeclarationWithType *decl ) {
557                        if ( FunctionType *funType = getFunctionType( decl->get_type() ) ) {
558                                if ( funType->get_parameters().size() == 1 ) {
559                                        Type::Qualifiers defaultQualifiers;
560                                        Type *paramType = funType->get_parameters().front()->get_type();
561                                        if ( paramType->get_qualifiers() != defaultQualifiers ) return 0;
562
563                                        if ( PointerType *pointerType = dynamic_cast< PointerType* >( paramType ) ) {
564                                                Type *baseType = pointerType->get_base();
565                                                if ( baseType->get_qualifiers() == defaultQualifiers ) {
566                                                        return baseType;
567                                                } // if
568                                        } // if
569                                } // if
570                        } // if
571                        return 0;
572                }
573
574                /// Returns T if the given declaration is a function with parameters (T*, T) for some type T, where neither parameter is cv-qualified,
575                /// NULL otherwise
576                Type *isNoCvPtrValFn( DeclarationWithType *decl ) {
577                        if ( FunctionType *funType = getFunctionType( decl->get_type() ) ) {
578                                if ( funType->get_parameters().size() == 2 ) {
579                                        Type::Qualifiers defaultQualifiers;
580                                        Type *paramType1 = funType->get_parameters().front()->get_type();
581                                        if ( paramType1->get_qualifiers() != defaultQualifiers ) return 0;
582                                        Type *paramType2 = funType->get_parameters().back()->get_type();
583                                        if ( paramType2->get_qualifiers() != defaultQualifiers ) return 0;
584
585                                        if ( PointerType *pointerType = dynamic_cast< PointerType* >( paramType1 ) ) {
586                                                Type *baseType1 = pointerType->get_base();
587                                                if ( baseType1->get_qualifiers() != defaultQualifiers ) return 0;
588                                                SymTab::Indexer dummy;
589                                                if ( ResolvExpr::typesCompatible( baseType1, paramType2, dummy ) ) {
590                                                        return baseType1;
591                                                } // if
592                                        } // if
593                                } // if
594                        } // if
595                        return 0;
596                }
597
598                /// returns T if the given declaration is: (*?=?)(T *, T) for some type T (return not checked, but maybe should be), NULL otherwise
599                /// Only picks assignments where neither parameter is cv-qualified
600                Type *isAssignment( DeclarationWithType *decl ) {
601                        return decl->get_name() == "?=?" ? isNoCvPtrValFn( decl ) : 0;
602                }
603
604                /// returns T if the given declaration is: (*?{})(T *) for some type T, NULL otherwise
605                /// Only picks ctors where the parameter is not cv-qualified
606                Type *isCtor( DeclarationWithType *decl ) {
607                        return decl->get_name() == "?{}" ? isNoCvPtrFn( decl ) : 0;
608                }
609
610                /// returns T if the given declaration is: (*?{})(T *, T) for some type T (return not checked, but maybe should be), NULL otherwise
611                /// Only picks copy constructors where neither parameter is cv-qualified
612                Type *isCopy( DeclarationWithType *decl ) {
613                        return decl->get_name() == "?{}" ? isNoCvPtrValFn( decl ) : 0;
614                }
615
616                /// returns T if the given declaration is: (*?{})(T *) for some type T, NULL otherwise
617                /// Only picks ctors where the parameter is not cv-qualified
618                Type *isDtor( DeclarationWithType *decl ) {
619                        return decl->get_name() == "^?{}" ? isNoCvPtrFn( decl ) : 0;
620                }
621
622                void Pass1::findTypeOps( const Type::ForallList &forall ) {
623                        // what if a nested function uses an assignment operator?
624                        // assignOps.clear();
625                        for ( Type::ForallList::const_iterator i = forall.begin(); i != forall.end(); ++i ) {
626                                for ( std::list< DeclarationWithType *>::const_iterator assert = (*i)->get_assertions().begin(); assert != (*i)->get_assertions().end(); ++assert ) {
627                                        std::string typeName;
628                                        if ( TypeInstType *typeInst = isTypeInstAssignment( *assert ) ) {
629                                                assignOps[ typeInst->get_name() ] = *assert;
630                                        } else if ( TypeInstType *typeInst = isTypeInstCtor( *assert ) ) {
631                                                ctorOps[ typeInst->get_name() ] = *assert;
632                                        } else if ( TypeInstType *typeInst = isTypeInstCopy( *assert ) ) {
633                                                copyOps[ typeInst->get_name() ] = *assert;
634                                        } else if ( TypeInstType *typeInst = isTypeInstDtor( *assert ) ) {
635                                                dtorOps[ typeInst->get_name() ] = *assert;
636                                        } // if
637                                } // for
638                        } // for
639                }
640
641                DeclarationWithType *Pass1::mutate( FunctionDecl *functionDecl ) {
642                        // if this is a assignment function, put it in the map for this scope
643                        if ( Type *paramType = isAssignment( functionDecl ) ) {
644                                if ( ! dynamic_cast< TypeInstType* >( paramType ) ) {
645                                        scopedAssignOps.insert( paramType, functionDecl );
646                                }
647                        } else if ( Type *paramType = isCtor( functionDecl ) ) {
648                                if ( ! dynamic_cast< TypeInstType* >( paramType ) ) {
649                                        scopedCtorOps.insert( paramType, functionDecl );
650                                }
651                        } else if ( Type *paramType = isCopy( functionDecl ) ) {
652                                if ( ! dynamic_cast< TypeInstType* >( paramType ) ) {
653                                        scopedCopyOps.insert( paramType, functionDecl );
654                                }
655                        } else if ( Type *paramType = isDtor( functionDecl ) ) {
656                                if ( ! dynamic_cast< TypeInstType* >( paramType ) ) {
657                                        scopedDtorOps.insert( paramType, functionDecl );
658                                }
659                        }
660
661                        if ( functionDecl->get_statements() ) {         // empty routine body ?
662                                doBeginScope();
663                                scopeTyVars.beginScope();
664                                assignOps.beginScope();
665                                ctorOps.beginScope();
666                                copyOps.beginScope();
667                                dtorOps.beginScope();
668
669                                DeclarationWithType *oldRetval = retval;
670
671                                // process polymorphic return value
672                                retval = nullptr;
673                                if ( isDynRet( functionDecl->get_functionType() ) && functionDecl->get_linkage() != LinkageSpec::C ) {
674                                        retval = functionDecl->get_functionType()->get_returnVals().front();
675
676                                        // give names to unnamed return values
677                                        if ( retval->get_name() == "" ) {
678                                                retval->set_name( "_retparm" );
679                                                retval->set_linkage( LinkageSpec::C );
680                                        } // if
681                                } // if
682
683                                FunctionType *functionType = functionDecl->get_functionType();
684                                makeTyVarMap( functionDecl->get_functionType(), scopeTyVars );
685                                findTypeOps( functionDecl->get_functionType()->get_forall() );
686
687                                std::list< DeclarationWithType *> &paramList = functionType->get_parameters();
688                                std::list< FunctionType *> functions;
689                                for ( Type::ForallList::iterator tyVar = functionType->get_forall().begin(); tyVar != functionType->get_forall().end(); ++tyVar ) {
690                                        for ( std::list< DeclarationWithType *>::iterator assert = (*tyVar)->get_assertions().begin(); assert != (*tyVar)->get_assertions().end(); ++assert ) {
691                                                findFunction( (*assert)->get_type(), functions, scopeTyVars, needsAdapter );
692                                        } // for
693                                } // for
694                                for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
695                                        findFunction( (*arg)->get_type(), functions, scopeTyVars, needsAdapter );
696                                } // for
697
698                                for ( std::list< FunctionType *>::iterator funType = functions.begin(); funType != functions.end(); ++funType ) {
699                                        std::string mangleName = mangleAdapterName( *funType, scopeTyVars );
700                                        if ( adapters.find( mangleName ) == adapters.end() ) {
701                                                std::string adapterName = makeAdapterName( mangleName );
702                                                adapters.insert( std::pair< std::string, DeclarationWithType *>( mangleName, new ObjectDecl( adapterName, DeclarationNode::NoStorageClass, LinkageSpec::C, nullptr, new PointerType( Type::Qualifiers(), makeAdapterType( *funType, scopeTyVars ) ), nullptr ) ) );
703                                        } // if
704                                } // for
705
706                                functionDecl->set_statements( functionDecl->get_statements()->acceptMutator( *this ) );
707
708                                scopeTyVars.endScope();
709                                assignOps.endScope();
710                                ctorOps.endScope();
711                                copyOps.endScope();
712                                dtorOps.endScope();
713                                retval = oldRetval;
714                                doEndScope();
715                        } // if
716                        return functionDecl;
717                }
718
719                TypeDecl *Pass1::mutate( TypeDecl *typeDecl ) {
720                        addToTyVarMap( typeDecl, scopeTyVars );
721                        return Mutator::mutate( typeDecl );
722                }
723
724                Expression *Pass1::mutate( CommaExpr *commaExpr ) {
725                        // Attempting to find application expressions that were mutated by the copy constructor passes
726                        // to use an explicit return variable, so that the variable can be reused as a parameter to the
727                        // call rather than creating a new temp variable. Previously this step was an optimization, but
728                        // with the introduction of tuples and UniqueExprs, it is necessary to ensure that they use the same variable.
729                        // Essentially, looking for pattern: (x=f(...), x)
730                        // To compound the issue, the right side can be *x, etc. because of lvalue-returning functions
731                        if ( UntypedExpr * assign = dynamic_cast< UntypedExpr * >( commaExpr->get_arg1() ) ) {
732                                if ( InitTweak::isAssignment( InitTweak::getFunctionName( assign ) ) ) {
733                                        assert( assign->get_args().size() == 2 );
734                                        if ( ApplicationExpr * appExpr = dynamic_cast< ApplicationExpr * > ( assign->get_args().back() ) ) {
735                                                // first argument is assignable, so it must be an lvalue, so it should be legal to take its address.
736                                                retVals[appExpr] = assign->get_args().front();
737                                        }
738                                }
739                        }
740
741                        commaExpr->set_arg1( maybeMutate( commaExpr->get_arg1(), *this ) );
742                        commaExpr->set_arg2( maybeMutate( commaExpr->get_arg2(), *this ) );
743                        return commaExpr;
744                }
745
746                Expression *Pass1::mutate( ConditionalExpr *condExpr ) {
747                        condExpr->set_arg1( maybeMutate( condExpr->get_arg1(), *this ) );
748                        condExpr->set_arg2( maybeMutate( condExpr->get_arg2(), *this ) );
749                        condExpr->set_arg3( maybeMutate( condExpr->get_arg3(), *this ) );
750                        return condExpr;
751
752                }
753
754                void Pass1::passArgTypeVars( ApplicationExpr *appExpr, Type *parmType, Type *argBaseType, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars, std::set< std::string > &seenTypes ) {
755                        Type *polyType = isPolyType( parmType, exprTyVars );
756                        if ( polyType && ! dynamic_cast< TypeInstType* >( polyType ) ) {
757                                std::string typeName = mangleType( polyType );
758                                if ( seenTypes.count( typeName ) ) return;
759
760                                arg = appExpr->get_args().insert( arg, new SizeofExpr( argBaseType->clone() ) );
761                                arg++;
762                                arg = appExpr->get_args().insert( arg, new AlignofExpr( argBaseType->clone() ) );
763                                arg++;
764                                if ( dynamic_cast< StructInstType* >( polyType ) ) {
765                                        if ( StructInstType *argBaseStructType = dynamic_cast< StructInstType* >( argBaseType ) ) {
766                                                // zero-length arrays are forbidden by C, so don't pass offset for empty struct
767                                                if ( ! argBaseStructType->get_baseStruct()->get_members().empty() ) {
768                                                        arg = appExpr->get_args().insert( arg, new OffsetPackExpr( argBaseStructType->clone() ) );
769                                                        arg++;
770                                                }
771                                        } else {
772                                                throw SemanticError( "Cannot pass non-struct type for generic struct" );
773                                        }
774                                }
775
776                                seenTypes.insert( typeName );
777                        }
778                }
779
780                void Pass1::passTypeVars( ApplicationExpr *appExpr, Type *polyRetType, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars ) {
781                        // pass size/align for type variables
782                        for ( TyVarMap::const_iterator tyParm = exprTyVars.begin(); tyParm != exprTyVars.end(); ++tyParm ) {
783                                ResolvExpr::EqvClass eqvClass;
784                                assert( env );
785                                if ( tyParm->second.isComplete ) {
786                                        Type *concrete = env->lookup( tyParm->first );
787                                        if ( concrete ) {
788                                                arg = appExpr->get_args().insert( arg, new SizeofExpr( concrete->clone() ) );
789                                                arg++;
790                                                arg = appExpr->get_args().insert( arg, new AlignofExpr( concrete->clone() ) );
791                                                arg++;
792                                        } else {
793                                                // xxx - should this be an assertion?
794                                                std::string x = env ? toString( *env ) : "missing env";
795                                                throw SemanticError( x + "\n" + "unbound type variable: " + tyParm->first + " in application ", appExpr );
796                                        } // if
797                                } // if
798                        } // for
799
800                        // add size/align for generic types to parameter list
801                        if ( ! appExpr->get_function()->has_result() ) return;
802                        FunctionType *funcType = getFunctionType( appExpr->get_function()->get_result() );
803                        assert( funcType );
804
805                        std::list< DeclarationWithType* >::const_iterator fnParm = funcType->get_parameters().begin();
806                        std::list< Expression* >::const_iterator fnArg = arg;
807                        std::set< std::string > seenTypes; ///< names for generic types we've seen
808
809                        // a polymorphic return type may need to be added to the argument list
810                        if ( polyRetType ) {
811                                Type *concRetType = replaceWithConcrete( appExpr, polyRetType );
812                                passArgTypeVars( appExpr, polyRetType, concRetType, arg, exprTyVars, seenTypes );
813                        }
814
815                        // add type information args for presently unseen types in parameter list
816                        for ( ; fnParm != funcType->get_parameters().end() && fnArg != appExpr->get_args().end(); ++fnParm, ++fnArg ) {
817                                VariableExpr *fnArgBase = getBaseVar( *fnArg );
818                                if ( ! fnArgBase ) continue; // xxx - previously had check for non-empty fnArgBase results
819                                passArgTypeVars( appExpr, (*fnParm)->get_type(), fnArgBase->get_result(), arg, exprTyVars, seenTypes );
820                        }
821                }
822
823                ObjectDecl *Pass1::makeTemporary( Type *type ) {
824                        ObjectDecl *newObj = new ObjectDecl( tempNamer.newName(), DeclarationNode::NoStorageClass, LinkageSpec::C, 0, type, 0 );
825                        stmtsToAdd.push_back( new DeclStmt( noLabels, newObj ) );
826                        return newObj;
827                }
828
829                Expression *Pass1::addRetParam( ApplicationExpr *appExpr, FunctionType *function, Type *retType, std::list< Expression *>::iterator &arg ) {
830                        // Create temporary to hold return value of polymorphic function and produce that temporary as a result
831                        // using a comma expression.
832                        assert( retType );
833
834                        Expression * paramExpr = nullptr;
835                        // try to use existing return value parameter if it exists, otherwise create a new temporary
836                        if ( retVals.count( appExpr ) ) {
837                                paramExpr = retVals[appExpr]->clone();
838                        } else {
839                                ObjectDecl *newObj = makeTemporary( retType->clone() );
840                                paramExpr = new VariableExpr( newObj );
841                        }
842                        Expression * retExpr = paramExpr->clone();
843
844                        // If the type of the temporary is not polymorphic, box temporary by taking its address;
845                        // otherwise the temporary is already boxed and can be used directly.
846                        if ( ! isPolyType( paramExpr->get_result(), scopeTyVars, env ) ) {
847                                paramExpr = new AddressExpr( paramExpr );
848                        } // if
849                        arg = appExpr->get_args().insert( arg, paramExpr ); // add argument to function call
850                        arg++;
851                        // Build a comma expression to call the function and emulate a normal return.
852                        CommaExpr *commaExpr = new CommaExpr( appExpr, retExpr );
853                        commaExpr->set_env( appExpr->get_env() );
854                        appExpr->set_env( 0 );
855                        return commaExpr;
856                }
857
858                void Pass1::replaceParametersWithConcrete( ApplicationExpr *appExpr, std::list< Expression* >& params ) {
859                        for ( std::list< Expression* >::iterator param = params.begin(); param != params.end(); ++param ) {
860                                TypeExpr *paramType = dynamic_cast< TypeExpr* >( *param );
861                                assert(paramType && "Aggregate parameters should be type expressions");
862                                paramType->set_type( replaceWithConcrete( appExpr, paramType->get_type(), false ) );
863                        }
864                }
865
866                Type *Pass1::replaceWithConcrete( ApplicationExpr *appExpr, Type *type, bool doClone ) {
867                        if ( TypeInstType *typeInst = dynamic_cast< TypeInstType * >( type ) ) {
868                                Type *concrete = env->lookup( typeInst->get_name() );
869                                if ( concrete == 0 ) {
870                                        // xxx - should this be an assertion?
871                                        std::string x = env ? toString( *env ) : "missing env";
872                                        throw SemanticError( x + "\n" + "Unbound type variable " + typeInst->get_name() + " in ", appExpr );
873                                } // if
874                                return concrete;
875                        } else if ( StructInstType *structType = dynamic_cast< StructInstType* >( type ) ) {
876                                if ( doClone ) {
877                                        structType = structType->clone();
878                                }
879                                replaceParametersWithConcrete( appExpr, structType->get_parameters() );
880                                return structType;
881                        } else if ( UnionInstType *unionType = dynamic_cast< UnionInstType* >( type ) ) {
882                                if ( doClone ) {
883                                        unionType = unionType->clone();
884                                }
885                                replaceParametersWithConcrete( appExpr, unionType->get_parameters() );
886                                return unionType;
887                        }
888                        return type;
889                }
890
891                Expression *Pass1::addDynRetParam( ApplicationExpr *appExpr, FunctionType *function, Type *dynType, std::list< Expression *>::iterator &arg ) {
892                        assert( env );
893                        Type *concrete = replaceWithConcrete( appExpr, dynType );
894                        // add out-parameter for return value
895                        return addRetParam( appExpr, function, concrete, arg );
896                }
897
898                Expression *Pass1::applyAdapter( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &tyVars ) {
899                        Expression *ret = appExpr;
900//                      if ( ! function->get_returnVals().empty() && isPolyType( function->get_returnVals().front()->get_type(), tyVars ) ) {
901                        if ( isDynRet( function, tyVars ) ) {
902                                ret = addRetParam( appExpr, function, function->get_returnVals().front()->get_type(), arg );
903                        } // if
904                        std::string mangleName = mangleAdapterName( function, tyVars );
905                        std::string adapterName = makeAdapterName( mangleName );
906
907                        // cast adaptee to void (*)(), since it may have any type inside a polymorphic function
908                        Type * adapteeType = new PointerType( Type::Qualifiers(), new FunctionType( Type::Qualifiers(), true ) );
909                        appExpr->get_args().push_front( new CastExpr( appExpr->get_function(), adapteeType ) );
910                        appExpr->set_function( new NameExpr( adapterName ) ); // xxx - result is never set on NameExpr
911
912                        return ret;
913                }
914
915                void Pass1::boxParam( Type *param, Expression *&arg, const TyVarMap &exprTyVars ) {
916                        assert( arg->has_result() );
917                        if ( isPolyType( param, exprTyVars ) ) {
918                                if ( isPolyType( arg->get_result() ) ) {
919                                        // if the argument's type is polymorphic, we don't need to box again!
920                                        return;
921                                } else if ( arg->get_result()->get_isLvalue() ) {
922                                        // VariableExpr and MemberExpr are lvalues; need to check this isn't coming from the second arg of a comma expression though (not an lvalue)
923                                        // xxx - need to test that this code is still reachable
924                                        if ( CommaExpr *commaArg = dynamic_cast< CommaExpr* >( arg ) ) {
925                                                commaArg->set_arg2( new AddressExpr( commaArg->get_arg2() ) );
926                                        } else {
927                                                arg = new AddressExpr( arg );
928                                        }
929                                } else {
930                                        // use type computed in unification to declare boxed variables
931                                        Type * newType = param->clone();
932                                        if ( env ) env->apply( newType );
933                                        ObjectDecl *newObj = new ObjectDecl( tempNamer.newName(), DeclarationNode::NoStorageClass, LinkageSpec::C, 0, newType, 0 );
934                                        newObj->get_type()->get_qualifiers() = Type::Qualifiers(); // TODO: is this right???
935                                        stmtsToAdd.push_back( new DeclStmt( noLabels, newObj ) );
936                                        UntypedExpr *assign = new UntypedExpr( new NameExpr( "?=?" ) );
937                                        assign->get_args().push_back( new VariableExpr( newObj ) );
938                                        assign->get_args().push_back( arg );
939                                        stmtsToAdd.push_back( new ExprStmt( noLabels, assign ) );
940                                        arg = new AddressExpr( new VariableExpr( newObj ) );
941                                } // if
942                        } // if
943                }
944
945                /// cast parameters to polymorphic functions so that types are replaced with
946                /// void * if they are type parameters in the formal type.
947                /// this gets rid of warnings from gcc.
948                void addCast( Expression *&actual, Type *formal, const TyVarMap &tyVars ) {
949                        if ( getFunctionType( formal ) ) {
950                                Type * newType = formal->clone();
951                                newType = ScrubTyVars::scrub( newType, tyVars );
952                                actual = new CastExpr( actual, newType );
953                        } // if
954                }
955
956                void Pass1::boxParams( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars ) {
957                        for ( std::list< DeclarationWithType *>::const_iterator param = function->get_parameters().begin(); param != function->get_parameters().end(); ++param, ++arg ) {
958                                assert( arg != appExpr->get_args().end() );
959                                addCast( *arg, (*param)->get_type(), exprTyVars );
960                                boxParam( (*param)->get_type(), *arg, exprTyVars );
961                        } // for
962                }
963
964                void Pass1::addInferredParams( ApplicationExpr *appExpr, FunctionType *functionType, std::list< Expression *>::iterator &arg, const TyVarMap &tyVars ) {
965                        std::list< Expression *>::iterator cur = arg;
966                        for ( Type::ForallList::iterator tyVar = functionType->get_forall().begin(); tyVar != functionType->get_forall().end(); ++tyVar ) {
967                                for ( std::list< DeclarationWithType *>::iterator assert = (*tyVar)->get_assertions().begin(); assert != (*tyVar)->get_assertions().end(); ++assert ) {
968                                        InferredParams::const_iterator inferParam = appExpr->get_inferParams().find( (*assert)->get_uniqueId() );
969                                        assert( inferParam != appExpr->get_inferParams().end() && "NOTE: Explicit casts of polymorphic functions to compatible monomorphic functions are currently unsupported" );
970                                        Expression *newExpr = inferParam->second.expr->clone();
971                                        addCast( newExpr, (*assert)->get_type(), tyVars );
972                                        boxParam( (*assert)->get_type(), newExpr, tyVars );
973                                        appExpr->get_args().insert( cur, newExpr );
974                                } // for
975                        } // for
976                }
977
978                void makeRetParm( FunctionType *funcType ) {
979                        DeclarationWithType *retParm = funcType->get_returnVals().front();
980
981                        // make a new parameter that is a pointer to the type of the old return value
982                        retParm->set_type( new PointerType( Type::Qualifiers(), retParm->get_type() ) );
983                        funcType->get_parameters().push_front( retParm );
984
985                        // we don't need the return value any more
986                        funcType->get_returnVals().clear();
987                }
988
989                FunctionType *makeAdapterType( FunctionType *adaptee, const TyVarMap &tyVars ) {
990                        // actually make the adapter type
991                        FunctionType *adapter = adaptee->clone();
992//                      if ( ! adapter->get_returnVals().empty() && isPolyType( adapter->get_returnVals().front()->get_type(), tyVars ) ) {
993                        if ( isDynRet( adapter, tyVars ) ) {
994                                makeRetParm( adapter );
995                        } // if
996                        adapter->get_parameters().push_front( new ObjectDecl( "", DeclarationNode::NoStorageClass, LinkageSpec::C, 0, new PointerType( Type::Qualifiers(), new FunctionType( Type::Qualifiers(), true ) ), 0 ) );
997                        return adapter;
998                }
999
1000                Expression *makeAdapterArg( DeclarationWithType *param, DeclarationWithType *arg, DeclarationWithType *realParam, const TyVarMap &tyVars ) {
1001                        assert( param );
1002                        assert( arg );
1003                        if ( isPolyType( realParam->get_type(), tyVars ) ) {
1004                                if ( ! isPolyType( arg->get_type() ) ) {
1005                                        UntypedExpr *deref = new UntypedExpr( new NameExpr( "*?" ) );
1006                                        deref->get_args().push_back( new CastExpr( new VariableExpr( param ), new PointerType( Type::Qualifiers(), arg->get_type()->clone() ) ) );
1007                                        deref->set_result( arg->get_type()->clone() );
1008                                        return deref;
1009                                } // if
1010                        } // if
1011                        return new VariableExpr( param );
1012                }
1013
1014                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 ) {
1015                        UniqueName paramNamer( "_p" );
1016                        for ( ; param != paramEnd; ++param, ++arg, ++realParam ) {
1017                                if ( (*param)->get_name() == "" ) {
1018                                        (*param)->set_name( paramNamer.newName() );
1019                                        (*param)->set_linkage( LinkageSpec::C );
1020                                } // if
1021                                adapteeApp->get_args().push_back( makeAdapterArg( *param, *arg, *realParam, tyVars ) );
1022                        } // for
1023                }
1024
1025                FunctionDecl *Pass1::makeAdapter( FunctionType *adaptee, FunctionType *realType, const std::string &mangleName, const TyVarMap &tyVars ) {
1026                        FunctionType *adapterType = makeAdapterType( adaptee, tyVars );
1027                        adapterType = ScrubTyVars::scrub( adapterType, tyVars );
1028                        DeclarationWithType *adapteeDecl = adapterType->get_parameters().front();
1029                        adapteeDecl->set_name( "_adaptee" );
1030                        ApplicationExpr *adapteeApp = new ApplicationExpr( new CastExpr( new VariableExpr( adapteeDecl ), new PointerType( Type::Qualifiers(), realType ) ) );
1031                        Statement *bodyStmt;
1032
1033                        Type::ForallList::iterator tyArg = realType->get_forall().begin();
1034                        Type::ForallList::iterator tyParam = adapterType->get_forall().begin();
1035                        Type::ForallList::iterator realTyParam = adaptee->get_forall().begin();
1036                        for ( ; tyParam != adapterType->get_forall().end(); ++tyArg, ++tyParam, ++realTyParam ) {
1037                                assert( tyArg != realType->get_forall().end() );
1038                                std::list< DeclarationWithType *>::iterator assertArg = (*tyArg)->get_assertions().begin();
1039                                std::list< DeclarationWithType *>::iterator assertParam = (*tyParam)->get_assertions().begin();
1040                                std::list< DeclarationWithType *>::iterator realAssertParam = (*realTyParam)->get_assertions().begin();
1041                                for ( ; assertParam != (*tyParam)->get_assertions().end(); ++assertArg, ++assertParam, ++realAssertParam ) {
1042                                        assert( assertArg != (*tyArg)->get_assertions().end() );
1043                                        adapteeApp->get_args().push_back( makeAdapterArg( *assertParam, *assertArg, *realAssertParam, tyVars ) );
1044                                } // for
1045                        } // for
1046
1047                        std::list< DeclarationWithType *>::iterator arg = realType->get_parameters().begin();
1048                        std::list< DeclarationWithType *>::iterator param = adapterType->get_parameters().begin();
1049                        std::list< DeclarationWithType *>::iterator realParam = adaptee->get_parameters().begin();
1050                        param++;                // skip adaptee parameter in the adapter type
1051                        if ( realType->get_returnVals().empty() ) {
1052                                // void return
1053                                addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
1054                                bodyStmt = new ExprStmt( noLabels, adapteeApp );
1055//                      } else if ( isPolyType( adaptee->get_returnVals().front()->get_type(), tyVars ) ) {
1056                        } else if ( isDynType( adaptee->get_returnVals().front()->get_type(), tyVars ) ) {
1057                                // return type T
1058                                if ( (*param)->get_name() == "" ) {
1059                                        (*param)->set_name( "_ret" );
1060                                        (*param)->set_linkage( LinkageSpec::C );
1061                                } // if
1062                                UntypedExpr *assign = new UntypedExpr( new NameExpr( "?=?" ) );
1063                                UntypedExpr *deref = new UntypedExpr( new NameExpr( "*?" ) );
1064                                deref->get_args().push_back( new CastExpr( new VariableExpr( *param++ ), new PointerType( Type::Qualifiers(), realType->get_returnVals().front()->get_type()->clone() ) ) );
1065                                assign->get_args().push_back( deref );
1066                                addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
1067                                assign->get_args().push_back( adapteeApp );
1068                                bodyStmt = new ExprStmt( noLabels, assign );
1069                        } else {
1070                                // adapter for a function that returns a monomorphic value
1071                                addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
1072                                bodyStmt = new ReturnStmt( noLabels, adapteeApp );
1073                        } // if
1074                        CompoundStmt *adapterBody = new CompoundStmt( noLabels );
1075                        adapterBody->get_kids().push_back( bodyStmt );
1076                        std::string adapterName = makeAdapterName( mangleName );
1077                        return new FunctionDecl( adapterName, DeclarationNode::NoStorageClass, LinkageSpec::C, adapterType, adapterBody, false, false );
1078                }
1079
1080                void Pass1::passAdapters( ApplicationExpr * appExpr, FunctionType * functionType, const TyVarMap & exprTyVars ) {
1081                        // collect a list of function types passed as parameters or implicit parameters (assertions)
1082                        std::list< DeclarationWithType *> &paramList = functionType->get_parameters();
1083                        std::list< FunctionType *> functions;
1084                        for ( Type::ForallList::iterator tyVar = functionType->get_forall().begin(); tyVar != functionType->get_forall().end(); ++tyVar ) {
1085                                for ( std::list< DeclarationWithType *>::iterator assert = (*tyVar)->get_assertions().begin(); assert != (*tyVar)->get_assertions().end(); ++assert ) {
1086                                        findFunction( (*assert)->get_type(), functions, exprTyVars, needsAdapter );
1087                                } // for
1088                        } // for
1089                        for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
1090                                findFunction( (*arg)->get_type(), functions, exprTyVars, needsAdapter );
1091                        } // for
1092
1093                        // parameter function types for which an appropriate adapter has been generated.  we cannot use the types
1094                        // after applying substitutions, since two different parameter types may be unified to the same type
1095                        std::set< std::string > adaptersDone;
1096
1097                        for ( std::list< FunctionType *>::iterator funType = functions.begin(); funType != functions.end(); ++funType ) {
1098                                FunctionType *originalFunction = (*funType)->clone();
1099                                FunctionType *realFunction = (*funType)->clone();
1100                                std::string mangleName = SymTab::Mangler::mangle( realFunction );
1101
1102                                // only attempt to create an adapter or pass one as a parameter if we haven't already done so for this
1103                                // pre-substitution parameter function type.
1104                                if ( adaptersDone.find( mangleName ) == adaptersDone.end() ) {
1105                                        adaptersDone.insert( adaptersDone.begin(), mangleName );
1106
1107                                        // apply substitution to type variables to figure out what the adapter's type should look like
1108                                        assert( env );
1109                                        env->apply( realFunction );
1110                                        mangleName = SymTab::Mangler::mangle( realFunction );
1111                                        mangleName += makePolyMonoSuffix( originalFunction, exprTyVars );
1112
1113                                        typedef ScopedMap< std::string, DeclarationWithType* >::iterator AdapterIter;
1114                                        AdapterIter adapter = adapters.find( mangleName );
1115                                        if ( adapter == adapters.end() ) {
1116                                                // adapter has not been created yet in the current scope, so define it
1117                                                FunctionDecl *newAdapter = makeAdapter( *funType, realFunction, mangleName, exprTyVars );
1118                                                std::pair< AdapterIter, bool > answer = adapters.insert( std::pair< std::string, DeclarationWithType *>( mangleName, newAdapter ) );
1119                                                adapter = answer.first;
1120                                                stmtsToAdd.push_back( new DeclStmt( noLabels, newAdapter ) );
1121                                        } // if
1122                                        assert( adapter != adapters.end() );
1123
1124                                        // add the appropriate adapter as a parameter
1125                                        appExpr->get_args().push_front( new VariableExpr( adapter->second ) );
1126                                } // if
1127                        } // for
1128                } // passAdapters
1129
1130                Expression *makeIncrDecrExpr( ApplicationExpr *appExpr, Type *polyType, bool isIncr ) {
1131                        NameExpr *opExpr;
1132                        if ( isIncr ) {
1133                                opExpr = new NameExpr( "?+=?" );
1134                        } else {
1135                                opExpr = new NameExpr( "?-=?" );
1136                        } // if
1137                        UntypedExpr *addAssign = new UntypedExpr( opExpr );
1138                        if ( AddressExpr *address = dynamic_cast< AddressExpr *>( appExpr->get_args().front() ) ) {
1139                                addAssign->get_args().push_back( address->get_arg() );
1140                        } else {
1141                                addAssign->get_args().push_back( appExpr->get_args().front() );
1142                        } // if
1143                        addAssign->get_args().push_back( new NameExpr( sizeofName( mangleType( polyType ) ) ) );
1144                        addAssign->set_result( appExpr->get_result()->clone() );
1145                        if ( appExpr->get_env() ) {
1146                                addAssign->set_env( appExpr->get_env() );
1147                                appExpr->set_env( 0 );
1148                        } // if
1149                        appExpr->get_args().clear();
1150                        delete appExpr;
1151                        return addAssign;
1152                }
1153
1154                Expression *Pass1::handleIntrinsics( ApplicationExpr *appExpr ) {
1155                        if ( VariableExpr *varExpr = dynamic_cast< VariableExpr *>( appExpr->get_function() ) ) {
1156                                if ( varExpr->get_var()->get_linkage() == LinkageSpec::Intrinsic ) {
1157                                        if ( varExpr->get_var()->get_name() == "?[?]" ) {
1158                                                assert( appExpr->has_result() );
1159                                                assert( appExpr->get_args().size() == 2 );
1160                                                Type *baseType1 = isPolyPtr( appExpr->get_args().front()->get_result(), scopeTyVars, env );
1161                                                Type *baseType2 = isPolyPtr( appExpr->get_args().back()->get_result(), scopeTyVars, env );
1162                                                assert( ! baseType1 || ! baseType2 ); // the arguments cannot both be polymorphic pointers
1163                                                UntypedExpr *ret = 0;
1164                                                if ( baseType1 || baseType2 ) { // one of the arguments is a polymorphic pointer
1165                                                        ret = new UntypedExpr( new NameExpr( "?+?" ) );
1166                                                } // if
1167                                                if ( baseType1 ) {
1168                                                        UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1169                                                        multiply->get_args().push_back( appExpr->get_args().back() );
1170                                                        multiply->get_args().push_back( new SizeofExpr( baseType1->clone() ) );
1171                                                        ret->get_args().push_back( appExpr->get_args().front() );
1172                                                        ret->get_args().push_back( multiply );
1173                                                } else if ( baseType2 ) {
1174                                                        UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1175                                                        multiply->get_args().push_back( appExpr->get_args().front() );
1176                                                        multiply->get_args().push_back( new SizeofExpr( baseType2->clone() ) );
1177                                                        ret->get_args().push_back( multiply );
1178                                                        ret->get_args().push_back( appExpr->get_args().back() );
1179                                                } // if
1180                                                if ( baseType1 || baseType2 ) {
1181                                                        ret->set_result( appExpr->get_result()->clone() );
1182                                                        if ( appExpr->get_env() ) {
1183                                                                ret->set_env( appExpr->get_env() );
1184                                                                appExpr->set_env( 0 );
1185                                                        } // if
1186                                                        appExpr->get_args().clear();
1187                                                        delete appExpr;
1188                                                        return ret;
1189                                                } // if
1190                                        } else if ( varExpr->get_var()->get_name() == "*?" ) {
1191                                                assert( appExpr->has_result() );
1192                                                assert( ! appExpr->get_args().empty() );
1193                                                if ( isPolyType( appExpr->get_result(), scopeTyVars, env ) ) {
1194                                                        Expression *ret = appExpr->get_args().front();
1195                                                        delete ret->get_result();
1196                                                        ret->set_result( appExpr->get_result()->clone() );
1197                                                        if ( appExpr->get_env() ) {
1198                                                                ret->set_env( appExpr->get_env() );
1199                                                                appExpr->set_env( 0 );
1200                                                        } // if
1201                                                        appExpr->get_args().clear();
1202                                                        delete appExpr;
1203                                                        return ret;
1204                                                } // if
1205                                        } else if ( varExpr->get_var()->get_name() == "?++" || varExpr->get_var()->get_name() == "?--" ) {
1206                                                assert( appExpr->has_result() );
1207                                                assert( appExpr->get_args().size() == 1 );
1208                                                if ( Type *baseType = isPolyPtr( appExpr->get_result(), scopeTyVars, env ) ) {
1209                                                        Type *tempType = appExpr->get_result()->clone();
1210                                                        if ( env ) {
1211                                                                env->apply( tempType );
1212                                                        } // if
1213                                                        ObjectDecl *newObj = makeTemporary( tempType );
1214                                                        VariableExpr *tempExpr = new VariableExpr( newObj );
1215                                                        UntypedExpr *assignExpr = new UntypedExpr( new NameExpr( "?=?" ) );
1216                                                        assignExpr->get_args().push_back( tempExpr->clone() );
1217                                                        if ( AddressExpr *address = dynamic_cast< AddressExpr *>( appExpr->get_args().front() ) ) {
1218                                                                assignExpr->get_args().push_back( address->get_arg()->clone() );
1219                                                        } else {
1220                                                                assignExpr->get_args().push_back( appExpr->get_args().front()->clone() );
1221                                                        } // if
1222                                                        CommaExpr *firstComma = new CommaExpr( assignExpr, makeIncrDecrExpr( appExpr, baseType, varExpr->get_var()->get_name() == "?++" ) );
1223                                                        return new CommaExpr( firstComma, tempExpr );
1224                                                } // if
1225                                        } else if ( varExpr->get_var()->get_name() == "++?" || varExpr->get_var()->get_name() == "--?" ) {
1226                                                assert( appExpr->has_result() );
1227                                                assert( appExpr->get_args().size() == 1 );
1228                                                if ( Type *baseType = isPolyPtr( appExpr->get_result(), scopeTyVars, env ) ) {
1229                                                        return makeIncrDecrExpr( appExpr, baseType, varExpr->get_var()->get_name() == "++?" );
1230                                                } // if
1231                                        } else if ( varExpr->get_var()->get_name() == "?+?" || varExpr->get_var()->get_name() == "?-?" ) {
1232                                                assert( appExpr->has_result() );
1233                                                assert( appExpr->get_args().size() == 2 );
1234                                                Type *baseType1 = isPolyPtr( appExpr->get_args().front()->get_result(), scopeTyVars, env );
1235                                                Type *baseType2 = isPolyPtr( appExpr->get_args().back()->get_result(), scopeTyVars, env );
1236                                                if ( baseType1 && baseType2 ) {
1237                                                        UntypedExpr *divide = new UntypedExpr( new NameExpr( "?/?" ) );
1238                                                        divide->get_args().push_back( appExpr );
1239                                                        divide->get_args().push_back( new SizeofExpr( baseType1->clone() ) );
1240                                                        divide->set_result( appExpr->get_result()->clone() );
1241                                                        if ( appExpr->get_env() ) {
1242                                                                divide->set_env( appExpr->get_env() );
1243                                                                appExpr->set_env( 0 );
1244                                                        } // if
1245                                                        return divide;
1246                                                } else if ( baseType1 ) {
1247                                                        UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1248                                                        multiply->get_args().push_back( appExpr->get_args().back() );
1249                                                        multiply->get_args().push_back( new SizeofExpr( baseType1->clone() ) );
1250                                                        appExpr->get_args().back() = multiply;
1251                                                } else if ( baseType2 ) {
1252                                                        UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1253                                                        multiply->get_args().push_back( appExpr->get_args().front() );
1254                                                        multiply->get_args().push_back( new SizeofExpr( baseType2->clone() ) );
1255                                                        appExpr->get_args().front() = multiply;
1256                                                } // if
1257                                        } else if ( varExpr->get_var()->get_name() == "?+=?" || varExpr->get_var()->get_name() == "?-=?" ) {
1258                                                assert( appExpr->has_result() );
1259                                                assert( appExpr->get_args().size() == 2 );
1260                                                Type *baseType = isPolyPtr( appExpr->get_result(), scopeTyVars, env );
1261                                                if ( baseType ) {
1262                                                        UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1263                                                        multiply->get_args().push_back( appExpr->get_args().back() );
1264                                                        multiply->get_args().push_back( new SizeofExpr( baseType->clone() ) );
1265                                                        appExpr->get_args().back() = multiply;
1266                                                } // if
1267                                        } // if
1268                                        return appExpr;
1269                                } // if
1270                        } // if
1271                        return 0;
1272                }
1273
1274                Expression *Pass1::mutate( ApplicationExpr *appExpr ) {
1275                        // std::cerr << "mutate appExpr: ";
1276                        // for ( TyVarMap::iterator i = scopeTyVars.begin(); i != scopeTyVars.end(); ++i ) {
1277                        //      std::cerr << i->first << " ";
1278                        // }
1279                        // std::cerr << "\n";
1280                        appExpr->get_function()->acceptMutator( *this );
1281                        mutateAll( appExpr->get_args(), *this );
1282
1283                        assert( appExpr->get_function()->has_result() );
1284                        PointerType *pointer = safe_dynamic_cast< PointerType *>( appExpr->get_function()->get_result() );
1285                        FunctionType *function = safe_dynamic_cast< FunctionType *>( pointer->get_base() );
1286
1287                        if ( Expression *newExpr = handleIntrinsics( appExpr ) ) {
1288                                return newExpr;
1289                        } // if
1290
1291                        Expression *ret = appExpr;
1292
1293                        std::list< Expression *>::iterator arg = appExpr->get_args().begin();
1294                        std::list< Expression *>::iterator paramBegin = appExpr->get_args().begin();
1295
1296                        TyVarMap exprTyVars( TypeDecl::Data{} );
1297                        makeTyVarMap( function, exprTyVars );
1298                        ReferenceToType *dynRetType = isDynRet( function, exprTyVars );
1299                        Type *concRetType = appExpr->get_result();// ?: dynRetType; // xxx - is concRetType a good name?
1300
1301                        if ( dynRetType ) {
1302                                ret = addDynRetParam( appExpr, function, concRetType, arg ); // xxx - used to use dynRetType instead of concRetType
1303                        } else if ( needsAdapter( function, scopeTyVars ) ) {
1304                                // std::cerr << "needs adapter: ";
1305                                // printTyVarMap( std::cerr, scopeTyVars );
1306                                // std::cerr << *env << std::endl;
1307                                // change the application so it calls the adapter rather than the passed function
1308                                ret = applyAdapter( appExpr, function, arg, scopeTyVars );
1309                        } // if
1310                        arg = appExpr->get_args().begin();
1311
1312                        passTypeVars( appExpr, concRetType, arg, exprTyVars ); // xxx - used to use dynRetType instead of concRetType
1313                        addInferredParams( appExpr, function, arg, exprTyVars );
1314
1315                        arg = paramBegin;
1316
1317                        boxParams( appExpr, function, arg, exprTyVars );
1318                        passAdapters( appExpr, function, exprTyVars );
1319
1320                        return ret;
1321                }
1322
1323                Expression *Pass1::mutate( UntypedExpr *expr ) {
1324                        if ( expr->has_result() && isPolyType( expr->get_result(), scopeTyVars, env ) ) {
1325                                if ( NameExpr *name = dynamic_cast< NameExpr *>( expr->get_function() ) ) {
1326                                        if ( name->get_name() == "*?" ) {
1327                                                Expression *ret = expr->get_args().front();
1328                                                expr->get_args().clear();
1329                                                delete expr;
1330                                                return ret->acceptMutator( *this );
1331                                        } // if
1332                                } // if
1333                        } // if
1334                        return PolyMutator::mutate( expr );
1335                }
1336
1337                Expression *Pass1::mutate( AddressExpr *addrExpr ) {
1338                        assert( addrExpr->get_arg()->has_result() && ! addrExpr->get_arg()->get_result()->isVoid() );
1339
1340                        bool needs = false;
1341                        if ( UntypedExpr *expr = dynamic_cast< UntypedExpr *>( addrExpr->get_arg() ) ) {
1342                                if ( expr->has_result() && isPolyType( expr->get_result(), scopeTyVars, env ) ) {
1343                                        if ( NameExpr *name = dynamic_cast< NameExpr *>( expr->get_function() ) ) {
1344                                                if ( name->get_name() == "*?" ) {
1345                                                        if ( ApplicationExpr * appExpr = dynamic_cast< ApplicationExpr * >( expr->get_args().front() ) ) {
1346                                                                assert( appExpr->get_function()->has_result() );
1347                                                                PointerType *pointer = safe_dynamic_cast< PointerType *>( appExpr->get_function()->get_result() );
1348                                                                FunctionType *function = safe_dynamic_cast< FunctionType *>( pointer->get_base() );
1349                                                                needs = needsAdapter( function, scopeTyVars );
1350                                                        } // if
1351                                                } // if
1352                                        } // if
1353                                } // if
1354                        } // if
1355                        // isPolyType check needs to happen before mutating addrExpr arg, so pull it forward
1356                        // out of the if condition.
1357                        bool polytype = isPolyType( addrExpr->get_arg()->get_result(), scopeTyVars, env );
1358                        addrExpr->set_arg( mutateExpression( addrExpr->get_arg() ) );
1359                        if ( polytype || needs ) {
1360                                Expression *ret = addrExpr->get_arg();
1361                                delete ret->get_result();
1362                                ret->set_result( addrExpr->get_result()->clone() );
1363                                addrExpr->set_arg( 0 );
1364                                delete addrExpr;
1365                                return ret;
1366                        } else {
1367                                return addrExpr;
1368                        } // if
1369                }
1370
1371                /// Wraps a function declaration in a new pointer-to-function variable expression
1372                VariableExpr *wrapFunctionDecl( DeclarationWithType *functionDecl ) {
1373                        // line below cloned from FixFunction.cc
1374                        // xxx - functionObj is never added to a list of declarations...
1375                        // alternatively, this function could return a new VariableExpr( functionDecl ) and change the result type of the new expression
1376                        ObjectDecl *functionObj = new ObjectDecl( functionDecl->get_name(), functionDecl->get_storageClass(), functionDecl->get_linkage(), 0,
1377                                                                  new PointerType( Type::Qualifiers(), functionDecl->get_type()->clone() ), 0 );
1378                        functionObj->set_mangleName( functionDecl->get_mangleName() );
1379                        functionObj->set_scopeLevel( functionDecl->get_scopeLevel() );
1380                        return new VariableExpr( functionObj );
1381                }
1382
1383                /// Finds the operation declaration for a given type in one of the two maps
1384                DeclarationWithType* findOpForType( Type *formalType, const ScopedMap< std::string, DeclarationWithType* >& ops, ResolvExpr::TypeMap< DeclarationWithType >& scopedOps ) {
1385                        if ( TypeInstType *formalTypeInstType = dynamic_cast< TypeInstType* >( formalType ) ) {
1386                                ScopedMap< std::string, DeclarationWithType *>::const_iterator opIt = ops.find( formalTypeInstType->get_name() );
1387                                return opIt == ops.end() ? 0 : opIt->second;
1388                        } else {
1389                                return scopedOps.find( formalType );
1390                        }
1391                }
1392
1393                /// Adds an assertion parameter to the application expression for the actual assertion declaration valued with the assert op
1394                void addAssertionFor( ApplicationExpr *appExpr, DeclarationWithType *actualDecl, DeclarationWithType *assertOp ) {
1395                        appExpr->get_inferParams()[ actualDecl->get_uniqueId() ]
1396                                        = ParamEntry( assertOp->get_uniqueId(), assertOp->get_type()->clone(), actualDecl->get_type()->clone(), wrapFunctionDecl( assertOp ) );
1397                }
1398
1399                Statement * Pass1::mutate( ReturnStmt *returnStmt ) {
1400                        if ( retval && returnStmt->get_expr() ) {
1401                                assert( returnStmt->get_expr()->has_result() && ! returnStmt->get_expr()->get_result()->isVoid() );
1402                                // ***** Code Removal ***** After introducing a temporary variable for all return expressions, the following code appears superfluous.
1403                                // if ( returnStmt->get_expr()->get_results().front()->get_isLvalue() ) {
1404                                // by this point, a cast expr on a polymorphic return value is redundant
1405                                while ( CastExpr *castExpr = dynamic_cast< CastExpr *>( returnStmt->get_expr() ) ) {
1406                                        returnStmt->set_expr( castExpr->get_arg() );
1407                                        returnStmt->get_expr()->set_env( castExpr->get_env() );
1408                                        castExpr->set_env( 0 );
1409                                        castExpr->set_arg( 0 );
1410                                        delete castExpr;
1411                                } //while
1412
1413                                // find assignment operator for (polymorphic) return type
1414                                ApplicationExpr *assignExpr = 0;
1415                                if ( TypeInstType *typeInst = dynamic_cast< TypeInstType *>( retval->get_type() ) ) {
1416                                        // find assignment operator for type variable
1417                                        ScopedMap< std::string, DeclarationWithType *>::const_iterator assignIter = assignOps.find( typeInst->get_name() );
1418                                        if ( assignIter == assignOps.end() ) {
1419                                                throw SemanticError( "Attempt to return dtype or ftype object in ", returnStmt->get_expr() );
1420                                        } // if
1421                                        assignExpr = new ApplicationExpr( new VariableExpr( assignIter->second ) );
1422                                } else if ( ReferenceToType *refType = dynamic_cast< ReferenceToType *>( retval->get_type() ) ) {
1423                                        // find assignment operator for generic type
1424                                        DeclarationWithType *functionDecl = scopedAssignOps.find( refType );
1425                                        if ( ! functionDecl ) {
1426                                                throw SemanticError( "Attempt to return dtype or ftype generic object in ", returnStmt->get_expr() );
1427                                        }
1428
1429                                        // wrap it up in an application expression
1430                                        assignExpr = new ApplicationExpr( wrapFunctionDecl( functionDecl ) );
1431                                        assignExpr->set_env( env->clone() );
1432
1433                                        // find each of its needed secondary assignment operators
1434                                        std::list< Expression* > &tyParams = refType->get_parameters();
1435                                        Type::ForallList &forallParams = functionDecl->get_type()->get_forall();
1436                                        std::list< Expression* >::const_iterator tyIt = tyParams.begin();
1437                                        Type::ForallList::const_iterator forallIt = forallParams.begin();
1438                                        for ( ; tyIt != tyParams.end() && forallIt != forallParams.end(); ++tyIt, ++forallIt ) {
1439                                                // Add appropriate mapping to assignment expression environment
1440                                                TypeExpr *formalTypeExpr = dynamic_cast< TypeExpr* >( *tyIt );
1441                                                assert( formalTypeExpr && "type parameters must be type expressions" );
1442                                                Type *formalType = formalTypeExpr->get_type();
1443                                                assignExpr->get_env()->add( (*forallIt)->get_name(), formalType );
1444
1445                                                // skip non-otype parameters (ftype/dtype)
1446                                                // xxx - should this check whether the type is complete instead?
1447                                                if ( (*forallIt)->get_kind() != TypeDecl::Any ) continue;
1448
1449                                                // find otype operators for formal type
1450                                                DeclarationWithType *assertAssign = findOpForType( formalType, assignOps, scopedAssignOps );
1451                                                if ( ! assertAssign ) throw SemanticError( "No assignment operation found for ", formalType );
1452
1453                                                DeclarationWithType *assertCtor = findOpForType( formalType, ctorOps, scopedCtorOps );
1454                                                if ( ! assertCtor ) throw SemanticError( "No default constructor found for ", formalType );
1455
1456                                                DeclarationWithType *assertCopy = findOpForType( formalType, copyOps, scopedCopyOps );
1457                                                if ( ! assertCopy ) throw SemanticError( "No copy constructor found for ", formalType );
1458
1459                                                DeclarationWithType *assertDtor = findOpForType( formalType, dtorOps, scopedDtorOps );
1460                                                if ( ! assertDtor ) throw SemanticError( "No destructor found for ", formalType );
1461
1462                                                // add inferred parameters for otype operators to assignment expression
1463                                                // NOTE: Code here assumes that first four assertions are assign op, ctor, copy ctor, dtor, in that order
1464                                                std::list< DeclarationWithType* > &asserts = (*forallIt)->get_assertions();
1465                                                assert( asserts.size() >= 4 && "Type param needs otype operator assertions" );
1466
1467                                                std::list< DeclarationWithType* >::iterator actualIt = asserts.begin();
1468                                                addAssertionFor( assignExpr, *actualIt, assertAssign );
1469                                                ++actualIt;
1470                                                addAssertionFor( assignExpr, *actualIt, assertCtor );
1471                                                ++actualIt;
1472                                                addAssertionFor( assignExpr, *actualIt, assertCopy );
1473                                                ++actualIt;
1474                                                addAssertionFor( assignExpr, *actualIt, assertDtor );
1475
1476                                        }
1477                                }
1478                                assert( assignExpr );
1479
1480                                // replace return statement with appropriate assignment to out parameter
1481                                Expression *retParm = new NameExpr( retval->get_name() );
1482                                retParm->set_result( new PointerType( Type::Qualifiers(), retval->get_type()->clone() ) );
1483                                assignExpr->get_args().push_back( retParm );
1484                                assignExpr->get_args().push_back( returnStmt->get_expr() );
1485                                stmtsToAdd.push_back( new ExprStmt( noLabels, mutateExpression( assignExpr ) ) );
1486                                // } else {
1487                                //      useRetval = true;
1488                                //      stmtsToAdd.push_back( new ExprStmt( noLabels, mutateExpression( returnStmt->get_expr() ) ) );
1489                                //      useRetval = false;
1490                                // } // if
1491                                returnStmt->set_expr( 0 );
1492                        } else {
1493                                returnStmt->set_expr( mutateExpression( returnStmt->get_expr() ) );
1494                        } // if
1495                        return returnStmt;
1496                }
1497
1498                Type * Pass1::mutate( PointerType *pointerType ) {
1499                        scopeTyVars.beginScope();
1500                        makeTyVarMap( pointerType, scopeTyVars );
1501
1502                        Type *ret = Mutator::mutate( pointerType );
1503
1504                        scopeTyVars.endScope();
1505                        return ret;
1506                }
1507
1508                Type * Pass1::mutate( FunctionType *functionType ) {
1509                        scopeTyVars.beginScope();
1510                        makeTyVarMap( functionType, scopeTyVars );
1511
1512                        Type *ret = Mutator::mutate( functionType );
1513
1514                        scopeTyVars.endScope();
1515                        return ret;
1516                }
1517
1518                void Pass1::doBeginScope() {
1519                        adapters.beginScope();
1520                        scopedAssignOps.beginScope();
1521                        scopedCtorOps.beginScope();
1522                        scopedCopyOps.beginScope();
1523                        scopedDtorOps.beginScope();
1524                }
1525
1526                void Pass1::doEndScope() {
1527                        adapters.endScope();
1528                        scopedAssignOps.endScope();
1529                        scopedCtorOps.endScope();
1530                        scopedCopyOps.endScope();
1531                        scopedDtorOps.endScope();
1532                }
1533
1534////////////////////////////////////////// Pass2 ////////////////////////////////////////////////////
1535
1536                void Pass2::addAdapters( FunctionType *functionType ) {
1537                        std::list< DeclarationWithType *> &paramList = functionType->get_parameters();
1538                        std::list< FunctionType *> functions;
1539                        for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
1540                                Type *orig = (*arg)->get_type();
1541                                findAndReplaceFunction( orig, functions, scopeTyVars, needsAdapter );
1542                                (*arg)->set_type( orig );
1543                        }
1544                        std::set< std::string > adaptersDone;
1545                        for ( std::list< FunctionType *>::iterator funType = functions.begin(); funType != functions.end(); ++funType ) {
1546                                std::string mangleName = mangleAdapterName( *funType, scopeTyVars );
1547                                if ( adaptersDone.find( mangleName ) == adaptersDone.end() ) {
1548                                        std::string adapterName = makeAdapterName( mangleName );
1549                                        paramList.push_front( new ObjectDecl( adapterName, DeclarationNode::NoStorageClass, LinkageSpec::C, 0, new PointerType( Type::Qualifiers(), makeAdapterType( *funType, scopeTyVars ) ), 0 ) );
1550                                        adaptersDone.insert( adaptersDone.begin(), mangleName );
1551                                }
1552                        }
1553//  deleteAll( functions );
1554                }
1555
1556                template< typename DeclClass >
1557                DeclClass * Pass2::handleDecl( DeclClass *decl, Type *type ) {
1558                        DeclClass *ret = static_cast< DeclClass *>( Mutator::mutate( decl ) );
1559
1560                        return ret;
1561                }
1562
1563                /// determines if `pref` is a prefix of `str`
1564                bool isPrefix( const std::string & str, const std::string & pref ) {
1565                        if ( pref.size() > str.size() ) return false;
1566                        auto its = std::mismatch( pref.begin(), pref.end(), str.begin() );
1567                        return its.first == pref.end();
1568                }
1569
1570                DeclarationWithType * Pass2::mutate( FunctionDecl *functionDecl ) {
1571                        if ( ! LinkageSpec::isBuiltin( functionDecl->get_linkage() ) ) {
1572                                // std::cerr << "mutating function: " << functionDecl->get_name() << std::endl;
1573                        }
1574                        functionDecl = safe_dynamic_cast< FunctionDecl * > ( handleDecl( functionDecl, functionDecl->get_functionType() ) );
1575                        FunctionType * ftype = functionDecl->get_functionType();
1576                        if ( ! ftype->get_returnVals().empty() && functionDecl->get_statements() ) {
1577                                if ( functionDecl->get_name() != "?=?" && ! isPrefix( functionDecl->get_name(), "_thunk" ) ) { // xxx - remove check for ?=? once reference types are in; remove check for prefix once thunks properly use ctor/dtors
1578                                        assert( ftype->get_returnVals().size() == 1 );
1579                                        DeclarationWithType * retval = ftype->get_returnVals().front();
1580                                        if ( retval->get_name() == "" ) {
1581                                                retval->set_name( "_retval" );
1582                                        }
1583                                        functionDecl->get_statements()->get_kids().push_front( new DeclStmt( noLabels, retval ) );
1584                                        DeclarationWithType * newRet = retval->clone(); // for ownership purposes
1585                                        ftype->get_returnVals().front() = newRet;
1586                                }
1587                        }
1588                        return functionDecl;
1589                }
1590
1591                ObjectDecl * Pass2::mutate( ObjectDecl *objectDecl ) {
1592                        return handleDecl( objectDecl, objectDecl->get_type() );
1593                }
1594
1595                TypeDecl * Pass2::mutate( TypeDecl *typeDecl ) {
1596                        addToTyVarMap( typeDecl, scopeTyVars );
1597                        if ( typeDecl->get_base() ) {
1598                                return handleDecl( typeDecl, typeDecl->get_base() );
1599                        } else {
1600                                return Mutator::mutate( typeDecl );
1601                        }
1602                }
1603
1604                TypedefDecl * Pass2::mutate( TypedefDecl *typedefDecl ) {
1605                        return handleDecl( typedefDecl, typedefDecl->get_base() );
1606                }
1607
1608                Type * Pass2::mutate( PointerType *pointerType ) {
1609                        scopeTyVars.beginScope();
1610                        makeTyVarMap( pointerType, scopeTyVars );
1611
1612                        Type *ret = Mutator::mutate( pointerType );
1613
1614                        scopeTyVars.endScope();
1615                        return ret;
1616                }
1617
1618                Type *Pass2::mutate( FunctionType *funcType ) {
1619                        scopeTyVars.beginScope();
1620                        makeTyVarMap( funcType, scopeTyVars );
1621
1622                        // move polymorphic return type to parameter list
1623                        if ( isDynRet( funcType ) ) {
1624                                ObjectDecl *ret = safe_dynamic_cast< ObjectDecl* >( funcType->get_returnVals().front() );
1625                                ret->set_type( new PointerType( Type::Qualifiers(), ret->get_type() ) );
1626                                funcType->get_parameters().push_front( ret );
1627                                funcType->get_returnVals().pop_front();
1628                                ret->set_init( nullptr ); // xxx - memory leak?
1629                        }
1630
1631                        // add size/align and assertions for type parameters to parameter list
1632                        std::list< DeclarationWithType *>::iterator last = funcType->get_parameters().begin();
1633                        std::list< DeclarationWithType *> inferredParams;
1634                        ObjectDecl newObj( "", DeclarationNode::NoStorageClass, LinkageSpec::C, 0, new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ), 0 );
1635                        ObjectDecl newPtr( "", DeclarationNode::NoStorageClass, LinkageSpec::C, 0,
1636                                           new PointerType( Type::Qualifiers(), new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ) ), 0 );
1637                        for ( Type::ForallList::const_iterator tyParm = funcType->get_forall().begin(); tyParm != funcType->get_forall().end(); ++tyParm ) {
1638                                ObjectDecl *sizeParm, *alignParm;
1639                                // add all size and alignment parameters to parameter list
1640                                if ( (*tyParm)->isComplete() ) {
1641                                        TypeInstType parmType( Type::Qualifiers(), (*tyParm)->get_name(), *tyParm );
1642                                        std::string parmName = mangleType( &parmType );
1643
1644                                        sizeParm = newObj.clone();
1645                                        sizeParm->set_name( sizeofName( parmName ) );
1646                                        last = funcType->get_parameters().insert( last, sizeParm );
1647                                        ++last;
1648
1649                                        alignParm = newObj.clone();
1650                                        alignParm->set_name( alignofName( parmName ) );
1651                                        last = funcType->get_parameters().insert( last, alignParm );
1652                                        ++last;
1653                                }
1654                                // move all assertions into parameter list
1655                                for ( std::list< DeclarationWithType *>::iterator assert = (*tyParm)->get_assertions().begin(); assert != (*tyParm)->get_assertions().end(); ++assert ) {
1656//      *assert = (*assert)->acceptMutator( *this );
1657                                        inferredParams.push_back( *assert );
1658                                }
1659                                (*tyParm)->get_assertions().clear();
1660                        }
1661
1662                        // add size/align for generic parameter types to parameter list
1663                        std::set< std::string > seenTypes; // sizeofName for generic types we've seen
1664                        for ( std::list< DeclarationWithType* >::const_iterator fnParm = last; fnParm != funcType->get_parameters().end(); ++fnParm ) {
1665                                Type *polyType = isPolyType( (*fnParm)->get_type(), scopeTyVars );
1666                                if ( polyType && ! dynamic_cast< TypeInstType* >( polyType ) ) {
1667                                        std::string typeName = mangleType( polyType );
1668                                        if ( seenTypes.count( typeName ) ) continue;
1669
1670                                        ObjectDecl *sizeParm, *alignParm, *offsetParm;
1671                                        sizeParm = newObj.clone();
1672                                        sizeParm->set_name( sizeofName( typeName ) );
1673                                        last = funcType->get_parameters().insert( last, sizeParm );
1674                                        ++last;
1675
1676                                        alignParm = newObj.clone();
1677                                        alignParm->set_name( alignofName( typeName ) );
1678                                        last = funcType->get_parameters().insert( last, alignParm );
1679                                        ++last;
1680
1681                                        if ( StructInstType *polyBaseStruct = dynamic_cast< StructInstType* >( polyType ) ) {
1682                                                // NOTE zero-length arrays are illegal in C, so empty structs have no offset array
1683                                                if ( ! polyBaseStruct->get_baseStruct()->get_members().empty() ) {
1684                                                        offsetParm = newPtr.clone();
1685                                                        offsetParm->set_name( offsetofName( typeName ) );
1686                                                        last = funcType->get_parameters().insert( last, offsetParm );
1687                                                        ++last;
1688                                                }
1689                                        }
1690
1691                                        seenTypes.insert( typeName );
1692                                }
1693                        }
1694
1695                        // splice assertion parameters into parameter list
1696                        funcType->get_parameters().splice( last, inferredParams );
1697                        addAdapters( funcType );
1698                        mutateAll( funcType->get_returnVals(), *this );
1699                        mutateAll( funcType->get_parameters(), *this );
1700
1701                        scopeTyVars.endScope();
1702                        return funcType;
1703                }
1704
1705////////////////////////////////////////// PolyGenericCalculator ////////////////////////////////////////////////////
1706
1707                void PolyGenericCalculator::beginTypeScope( Type *ty ) {
1708                        scopeTyVars.beginScope();
1709                        makeTyVarMap( ty, scopeTyVars );
1710                }
1711
1712                void PolyGenericCalculator::endTypeScope() {
1713                        scopeTyVars.endScope();
1714                }
1715
1716                template< typename DeclClass >
1717                DeclClass * PolyGenericCalculator::handleDecl( DeclClass *decl, Type *type ) {
1718                        beginTypeScope( type );
1719                        // knownLayouts.beginScope();
1720                        // knownOffsets.beginScope();
1721
1722                        DeclClass *ret = static_cast< DeclClass *>( Parent::mutate( decl ) );
1723
1724                        // knownOffsets.endScope();
1725                        // knownLayouts.endScope();
1726                        endTypeScope();
1727                        return ret;
1728                }
1729
1730                ObjectDecl * PolyGenericCalculator::mutate( ObjectDecl *objectDecl ) {
1731                        return handleDecl( objectDecl, objectDecl->get_type() );
1732                }
1733
1734                DeclarationWithType * PolyGenericCalculator::mutate( FunctionDecl *functionDecl ) {
1735                        knownLayouts.beginScope();
1736                        knownOffsets.beginScope();
1737
1738                        DeclarationWithType * decl = handleDecl( functionDecl, functionDecl->get_functionType() );
1739                        knownOffsets.endScope();
1740                        knownLayouts.endScope();
1741                        return decl;
1742                }
1743
1744                TypedefDecl * PolyGenericCalculator::mutate( TypedefDecl *typedefDecl ) {
1745                        return handleDecl( typedefDecl, typedefDecl->get_base() );
1746                }
1747
1748                TypeDecl * PolyGenericCalculator::mutate( TypeDecl *typeDecl ) {
1749                        addToTyVarMap( typeDecl, scopeTyVars );
1750                        return Parent::mutate( typeDecl );
1751                }
1752
1753                Type * PolyGenericCalculator::mutate( PointerType *pointerType ) {
1754                        beginTypeScope( pointerType );
1755
1756                        Type *ret = Parent::mutate( pointerType );
1757
1758                        endTypeScope();
1759                        return ret;
1760                }
1761
1762                Type * PolyGenericCalculator::mutate( FunctionType *funcType ) {
1763                        beginTypeScope( funcType );
1764
1765                        // make sure that any type information passed into the function is accounted for
1766                        for ( std::list< DeclarationWithType* >::const_iterator fnParm = funcType->get_parameters().begin(); fnParm != funcType->get_parameters().end(); ++fnParm ) {
1767                                // condition here duplicates that in Pass2::mutate( FunctionType* )
1768                                Type *polyType = isPolyType( (*fnParm)->get_type(), scopeTyVars );
1769                                if ( polyType && ! dynamic_cast< TypeInstType* >( polyType ) ) {
1770                                        knownLayouts.insert( mangleType( polyType ) );
1771                                }
1772                        }
1773
1774                        Type *ret = Parent::mutate( funcType );
1775
1776                        endTypeScope();
1777                        return ret;
1778                }
1779
1780                Statement *PolyGenericCalculator::mutate( DeclStmt *declStmt ) {
1781                        if ( ObjectDecl *objectDecl = dynamic_cast< ObjectDecl *>( declStmt->get_decl() ) ) {
1782                                if ( findGeneric( objectDecl->get_type() ) ) {
1783                                        // change initialization of a polymorphic value object
1784                                        // to allocate storage with alloca
1785                                        Type *declType = objectDecl->get_type();
1786                                        UntypedExpr *alloc = new UntypedExpr( new NameExpr( "__builtin_alloca" ) );
1787                                        alloc->get_args().push_back( new NameExpr( sizeofName( mangleType( declType ) ) ) );
1788
1789                                        delete objectDecl->get_init();
1790
1791                                        std::list<Expression*> designators;
1792                                        objectDecl->set_init( new SingleInit( alloc, designators, false ) ); // not constructed
1793                                }
1794                        }
1795                        return Parent::mutate( declStmt );
1796                }
1797
1798                /// Finds the member in the base list that matches the given declaration; returns its index, or -1 if not present
1799                long findMember( DeclarationWithType *memberDecl, std::list< Declaration* > &baseDecls ) {
1800                        long i = 0;
1801                        for(std::list< Declaration* >::const_iterator decl = baseDecls.begin(); decl != baseDecls.end(); ++decl, ++i ) {
1802                                if ( memberDecl->get_name() != (*decl)->get_name() ) continue;
1803
1804                                if ( DeclarationWithType *declWithType = dynamic_cast< DeclarationWithType* >( *decl ) ) {
1805                                        if ( memberDecl->get_mangleName().empty() || declWithType->get_mangleName().empty()
1806                                             || memberDecl->get_mangleName() == declWithType->get_mangleName() ) return i;
1807                                        else continue;
1808                                } else return i;
1809                        }
1810                        return -1;
1811                }
1812
1813                /// Returns an index expression into the offset array for a type
1814                Expression *makeOffsetIndex( Type *objectType, long i ) {
1815                        std::stringstream offset_namer;
1816                        offset_namer << i;
1817                        ConstantExpr *fieldIndex = new ConstantExpr( Constant( new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ), offset_namer.str() ) );
1818                        UntypedExpr *fieldOffset = new UntypedExpr( new NameExpr( "?[?]" ) );
1819                        fieldOffset->get_args().push_back( new NameExpr( offsetofName( mangleType( objectType ) ) ) );
1820                        fieldOffset->get_args().push_back( fieldIndex );
1821                        return fieldOffset;
1822                }
1823
1824                /// Returns an expression dereferenced n times
1825                Expression *makeDerefdVar( Expression *derefdVar, long n ) {
1826                        for ( int i = 1; i < n; ++i ) {
1827                                UntypedExpr *derefExpr = new UntypedExpr( new NameExpr( "*?" ) );
1828                                derefExpr->get_args().push_back( derefdVar );
1829                                // xxx - should set results on derefExpr
1830                                derefdVar = derefExpr;
1831                        }
1832                        return derefdVar;
1833                }
1834
1835                Expression *PolyGenericCalculator::mutate( MemberExpr *memberExpr ) {
1836                        // mutate, exiting early if no longer MemberExpr
1837                        Expression *expr = Parent::mutate( memberExpr );
1838                        memberExpr = dynamic_cast< MemberExpr* >( expr );
1839                        if ( ! memberExpr ) return expr;
1840
1841                        // get declaration for base struct, exiting early if not found
1842                        int varDepth;
1843                        VariableExpr *varExpr = getBaseVar( memberExpr->get_aggregate(), &varDepth );
1844                        if ( ! varExpr ) return memberExpr;
1845                        ObjectDecl *objectDecl = dynamic_cast< ObjectDecl* >( varExpr->get_var() );
1846                        if ( ! objectDecl ) return memberExpr;
1847
1848                        // only mutate member expressions for polymorphic types
1849                        int tyDepth;
1850                        Type *objectType = hasPolyBase( objectDecl->get_type(), scopeTyVars, &tyDepth );
1851                        if ( ! objectType ) return memberExpr;
1852                        findGeneric( objectType ); // ensure layout for this type is available
1853
1854                        // replace member expression with dynamically-computed layout expression
1855                        Expression *newMemberExpr = 0;
1856                        if ( StructInstType *structType = dynamic_cast< StructInstType* >( objectType ) ) {
1857                                // look up offset index
1858                                long i = findMember( memberExpr->get_member(), structType->get_baseStruct()->get_members() );
1859                                if ( i == -1 ) return memberExpr;
1860
1861                                // replace member expression with pointer to base plus offset
1862                                UntypedExpr *fieldLoc = new UntypedExpr( new NameExpr( "?+?" ) );
1863                                fieldLoc->get_args().push_back( makeDerefdVar( varExpr->clone(), varDepth ) );
1864                                fieldLoc->get_args().push_back( makeOffsetIndex( objectType, i ) );
1865                                newMemberExpr = fieldLoc;
1866                        } else if ( dynamic_cast< UnionInstType* >( objectType ) ) {
1867                                // union members are all at offset zero, so build appropriately-dereferenced variable
1868                                newMemberExpr = makeDerefdVar( varExpr->clone(), varDepth );
1869                        } else return memberExpr;
1870                        assert( newMemberExpr );
1871
1872                        Type *memberType = memberExpr->get_member()->get_type();
1873                        if ( ! isPolyType( memberType, scopeTyVars ) ) {
1874                                // Not all members of a polymorphic type are themselves of polymorphic type; in this case the member expression should be wrapped and dereferenced to form an lvalue
1875                                CastExpr *ptrCastExpr = new CastExpr( newMemberExpr, new PointerType( Type::Qualifiers(), memberType->clone() ) );
1876                                UntypedExpr *derefExpr = new UntypedExpr( new NameExpr( "*?" ) );
1877                                derefExpr->get_args().push_back( ptrCastExpr );
1878                                newMemberExpr = derefExpr;
1879                        }
1880
1881                        delete memberExpr;
1882                        return newMemberExpr;
1883                }
1884
1885                ObjectDecl *PolyGenericCalculator::makeVar( const std::string &name, Type *type, Initializer *init ) {
1886                        ObjectDecl *newObj = new ObjectDecl( name, DeclarationNode::NoStorageClass, LinkageSpec::C, 0, type, init );
1887                        stmtsToAdd.push_back( new DeclStmt( noLabels, newObj ) );
1888                        return newObj;
1889                }
1890
1891                void PolyGenericCalculator::addOtypeParamsToLayoutCall( UntypedExpr *layoutCall, const std::list< Type* > &otypeParams ) {
1892                        for ( std::list< Type* >::const_iterator param = otypeParams.begin(); param != otypeParams.end(); ++param ) {
1893                                if ( findGeneric( *param ) ) {
1894                                        // push size/align vars for a generic parameter back
1895                                        std::string paramName = mangleType( *param );
1896                                        layoutCall->get_args().push_back( new NameExpr( sizeofName( paramName ) ) );
1897                                        layoutCall->get_args().push_back( new NameExpr( alignofName( paramName ) ) );
1898                                } else {
1899                                        layoutCall->get_args().push_back( new SizeofExpr( (*param)->clone() ) );
1900                                        layoutCall->get_args().push_back( new AlignofExpr( (*param)->clone() ) );
1901                                }
1902                        }
1903                }
1904
1905                /// returns true if any of the otype parameters have a dynamic layout and puts all otype parameters in the output list
1906                bool findGenericParams( std::list< TypeDecl* > &baseParams, std::list< Expression* > &typeParams, std::list< Type* > &out ) {
1907                        bool hasDynamicLayout = false;
1908
1909                        std::list< TypeDecl* >::const_iterator baseParam = baseParams.begin();
1910                        std::list< Expression* >::const_iterator typeParam = typeParams.begin();
1911                        for ( ; baseParam != baseParams.end() && typeParam != typeParams.end(); ++baseParam, ++typeParam ) {
1912                                // skip non-otype parameters
1913                                if ( ! (*baseParam)->isComplete() ) continue;
1914                                TypeExpr *typeExpr = dynamic_cast< TypeExpr* >( *typeParam );
1915                                assert( typeExpr && "all otype parameters should be type expressions" );
1916
1917                                Type *type = typeExpr->get_type();
1918                                out.push_back( type );
1919                                if ( isPolyType( type ) ) hasDynamicLayout = true;
1920                        }
1921                        assert( baseParam == baseParams.end() && typeParam == typeParams.end() );
1922
1923                        return hasDynamicLayout;
1924                }
1925
1926                bool PolyGenericCalculator::findGeneric( Type *ty ) {
1927                        ty = replaceTypeInst( ty, env );
1928
1929                        if ( TypeInstType *typeInst = dynamic_cast< TypeInstType* >( ty ) ) {
1930                                if ( scopeTyVars.find( typeInst->get_name() ) != scopeTyVars.end() ) {
1931                                        // NOTE assumes here that getting put in the scopeTyVars included having the layout variables set
1932                                        return true;
1933                                }
1934                                return false;
1935                        } else if ( StructInstType *structTy = dynamic_cast< StructInstType* >( ty ) ) {
1936                                // check if this type already has a layout generated for it
1937                                std::string typeName = mangleType( ty );
1938                                if ( knownLayouts.find( typeName ) != knownLayouts.end() ) return true;
1939
1940                                // check if any of the type parameters have dynamic layout; if none do, this type is (or will be) monomorphized
1941                                std::list< Type* > otypeParams;
1942                                if ( ! findGenericParams( *structTy->get_baseParameters(), structTy->get_parameters(), otypeParams ) ) return false;
1943
1944                                // insert local variables for layout and generate call to layout function
1945                                knownLayouts.insert( typeName );  // done early so as not to interfere with the later addition of parameters to the layout call
1946                                Type *layoutType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
1947
1948                                int n_members = structTy->get_baseStruct()->get_members().size();
1949                                if ( n_members == 0 ) {
1950                                        // all empty structs have the same layout - size 1, align 1
1951                                        makeVar( sizeofName( typeName ), layoutType, new SingleInit( new ConstantExpr( Constant::from_ulong( (unsigned long)1 ) ) ) );
1952                                        makeVar( alignofName( typeName ), layoutType->clone(), new SingleInit( new ConstantExpr( Constant::from_ulong( (unsigned long)1 ) ) ) );
1953                                        // NOTE zero-length arrays are forbidden in C, so empty structs have no offsetof array
1954                                } else {
1955                                        ObjectDecl *sizeVar = makeVar( sizeofName( typeName ), layoutType );
1956                                        ObjectDecl *alignVar = makeVar( alignofName( typeName ), layoutType->clone() );
1957                                        ObjectDecl *offsetVar = makeVar( offsetofName( typeName ), new ArrayType( Type::Qualifiers(), layoutType->clone(), new ConstantExpr( Constant::from_int( n_members ) ), false, false ) );
1958
1959                                        // generate call to layout function
1960                                        UntypedExpr *layoutCall = new UntypedExpr( new NameExpr( layoutofName( structTy->get_baseStruct() ) ) );
1961                                        layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( sizeVar ) ) );
1962                                        layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( alignVar ) ) );
1963                                        layoutCall->get_args().push_back( new VariableExpr( offsetVar ) );
1964                                        addOtypeParamsToLayoutCall( layoutCall, otypeParams );
1965
1966                                        stmtsToAdd.push_back( new ExprStmt( noLabels, layoutCall ) );
1967                                }
1968
1969                                return true;
1970                        } else if ( UnionInstType *unionTy = dynamic_cast< UnionInstType* >( ty ) ) {
1971                                // check if this type already has a layout generated for it
1972                                std::string typeName = mangleType( ty );
1973                                if ( knownLayouts.find( typeName ) != knownLayouts.end() ) return true;
1974
1975                                // check if any of the type parameters have dynamic layout; if none do, this type is (or will be) monomorphized
1976                                std::list< Type* > otypeParams;
1977                                if ( ! findGenericParams( *unionTy->get_baseParameters(), unionTy->get_parameters(), otypeParams ) ) return false;
1978
1979                                // insert local variables for layout and generate call to layout function
1980                                knownLayouts.insert( typeName );  // done early so as not to interfere with the later addition of parameters to the layout call
1981                                Type *layoutType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
1982
1983                                ObjectDecl *sizeVar = makeVar( sizeofName( typeName ), layoutType );
1984                                ObjectDecl *alignVar = makeVar( alignofName( typeName ), layoutType->clone() );
1985
1986                                // generate call to layout function
1987                                UntypedExpr *layoutCall = new UntypedExpr( new NameExpr( layoutofName( unionTy->get_baseUnion() ) ) );
1988                                layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( sizeVar ) ) );
1989                                layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( alignVar ) ) );
1990                                addOtypeParamsToLayoutCall( layoutCall, otypeParams );
1991
1992                                stmtsToAdd.push_back( new ExprStmt( noLabels, layoutCall ) );
1993
1994                                return true;
1995                        }
1996
1997                        return false;
1998                }
1999
2000                Expression *PolyGenericCalculator::mutate( SizeofExpr *sizeofExpr ) {
2001                        Type *ty = sizeofExpr->get_type();
2002                        if ( findGeneric( ty ) ) {
2003                                Expression *ret = new NameExpr( sizeofName( mangleType( ty ) ) );
2004                                delete sizeofExpr;
2005                                return ret;
2006                        }
2007                        return sizeofExpr;
2008                }
2009
2010                Expression *PolyGenericCalculator::mutate( AlignofExpr *alignofExpr ) {
2011                        Type *ty = alignofExpr->get_type();
2012                        if ( findGeneric( ty ) ) {
2013                                Expression *ret = new NameExpr( alignofName( mangleType( ty ) ) );
2014                                delete alignofExpr;
2015                                return ret;
2016                        }
2017                        return alignofExpr;
2018                }
2019
2020                Expression *PolyGenericCalculator::mutate( OffsetofExpr *offsetofExpr ) {
2021                        // mutate, exiting early if no longer OffsetofExpr
2022                        Expression *expr = Parent::mutate( offsetofExpr );
2023                        offsetofExpr = dynamic_cast< OffsetofExpr* >( expr );
2024                        if ( ! offsetofExpr ) return expr;
2025
2026                        // only mutate expressions for polymorphic structs/unions
2027                        Type *ty = offsetofExpr->get_type();
2028                        if ( ! findGeneric( ty ) ) return offsetofExpr;
2029
2030                        if ( StructInstType *structType = dynamic_cast< StructInstType* >( ty ) ) {
2031                                // replace offsetof expression by index into offset array
2032                                long i = findMember( offsetofExpr->get_member(), structType->get_baseStruct()->get_members() );
2033                                if ( i == -1 ) return offsetofExpr;
2034
2035                                Expression *offsetInd = makeOffsetIndex( ty, i );
2036                                delete offsetofExpr;
2037                                return offsetInd;
2038                        } else if ( dynamic_cast< UnionInstType* >( ty ) ) {
2039                                // all union members are at offset zero
2040                                delete offsetofExpr;
2041                                return new ConstantExpr( Constant( new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ), "0" ) );
2042                        } else return offsetofExpr;
2043                }
2044
2045                Expression *PolyGenericCalculator::mutate( OffsetPackExpr *offsetPackExpr ) {
2046                        StructInstType *ty = offsetPackExpr->get_type();
2047
2048                        Expression *ret = 0;
2049                        if ( findGeneric( ty ) ) {
2050                                // pull offset back from generated type information
2051                                ret = new NameExpr( offsetofName( mangleType( ty ) ) );
2052                        } else {
2053                                std::string offsetName = offsetofName( mangleType( ty ) );
2054                                if ( knownOffsets.find( offsetName ) != knownOffsets.end() ) {
2055                                        // use the already-generated offsets for this type
2056                                        ret = new NameExpr( offsetName );
2057                                } else {
2058                                        knownOffsets.insert( offsetName );
2059
2060                                        std::list< Declaration* > &baseMembers = ty->get_baseStruct()->get_members();
2061                                        Type *offsetType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
2062
2063                                        // build initializer list for offset array
2064                                        std::list< Initializer* > inits;
2065                                        for ( std::list< Declaration* >::const_iterator member = baseMembers.begin(); member != baseMembers.end(); ++member ) {
2066                                                DeclarationWithType *memberDecl;
2067                                                if ( DeclarationWithType *origMember = dynamic_cast< DeclarationWithType* >( *member ) ) {
2068                                                        memberDecl = origMember->clone();
2069                                                } else {
2070                                                        memberDecl = new ObjectDecl( (*member)->get_name(), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, offsetType->clone(), 0 );
2071                                                }
2072                                                inits.push_back( new SingleInit( new OffsetofExpr( ty->clone(), memberDecl ) ) );
2073                                        }
2074
2075                                        // build the offset array and replace the pack with a reference to it
2076                                        ObjectDecl *offsetArray = makeVar( offsetName, new ArrayType( Type::Qualifiers(), offsetType, new ConstantExpr( Constant::from_ulong( baseMembers.size() ) ), false, false ),
2077                                                        new ListInit( inits ) );
2078                                        ret = new VariableExpr( offsetArray );
2079                                }
2080                        }
2081
2082                        delete offsetPackExpr;
2083                        return ret;
2084                }
2085
2086                void PolyGenericCalculator::doBeginScope() {
2087                        knownLayouts.beginScope();
2088                        knownOffsets.beginScope();
2089                }
2090
2091                void PolyGenericCalculator::doEndScope() {
2092                        knownLayouts.endScope();
2093                        knownOffsets.endScope();
2094                }
2095
2096////////////////////////////////////////// Pass3 ////////////////////////////////////////////////////
2097
2098                template< typename DeclClass >
2099                DeclClass * Pass3::handleDecl( DeclClass *decl, Type *type ) {
2100                        scopeTyVars.beginScope();
2101                        makeTyVarMap( type, scopeTyVars );
2102
2103                        DeclClass *ret = static_cast< DeclClass *>( Mutator::mutate( decl ) );
2104                        ScrubTyVars::scrub( decl, scopeTyVars );
2105
2106                        scopeTyVars.endScope();
2107                        return ret;
2108                }
2109
2110                ObjectDecl * Pass3::mutate( ObjectDecl *objectDecl ) {
2111                        return handleDecl( objectDecl, objectDecl->get_type() );
2112                }
2113
2114                DeclarationWithType * Pass3::mutate( FunctionDecl *functionDecl ) {
2115                        return handleDecl( functionDecl, functionDecl->get_functionType() );
2116                }
2117
2118                TypedefDecl * Pass3::mutate( TypedefDecl *typedefDecl ) {
2119                        return handleDecl( typedefDecl, typedefDecl->get_base() );
2120                }
2121
2122                TypeDecl * Pass3::mutate( TypeDecl *typeDecl ) {
2123//   Initializer *init = 0;
2124//   std::list< Expression *> designators;
2125//   addToTyVarMap( typeDecl, scopeTyVars );
2126//   if ( typeDecl->get_base() ) {
2127//     init = new SimpleInit( new SizeofExpr( handleDecl( typeDecl, typeDecl->get_base() ) ), designators );
2128//   }
2129//   return new ObjectDecl( typeDecl->get_name(), Declaration::Extern, LinkageSpec::C, 0, new BasicType( Type::Qualifiers(), BasicType::UnsignedInt ), init );
2130
2131                        addToTyVarMap( typeDecl, scopeTyVars );
2132                        return Mutator::mutate( typeDecl );
2133                }
2134
2135                Type * Pass3::mutate( PointerType *pointerType ) {
2136                        scopeTyVars.beginScope();
2137                        makeTyVarMap( pointerType, scopeTyVars );
2138
2139                        Type *ret = Mutator::mutate( pointerType );
2140
2141                        scopeTyVars.endScope();
2142                        return ret;
2143                }
2144
2145                Type * Pass3::mutate( FunctionType *functionType ) {
2146                        scopeTyVars.beginScope();
2147                        makeTyVarMap( functionType, scopeTyVars );
2148
2149                        Type *ret = Mutator::mutate( functionType );
2150
2151                        scopeTyVars.endScope();
2152                        return ret;
2153                }
2154        } // anonymous namespace
2155} // namespace GenPoly
2156
2157// Local Variables: //
2158// tab-width: 4 //
2159// mode: c++ //
2160// compile-command: "make install" //
2161// End: //
Note: See TracBrowser for help on using the repository browser.