source: src/GenPoly/Box.cc@ 58b6d1b

ADT aaron-thesis arm-eh ast-experimental cleanup-dtors deferred_resn demangler enum forall-pointer-decay jacob/cs343-translation jenkins-sandbox new-ast new-ast-unique-expr no_list persistent-indexer pthread-emulation qualifiedEnum
Last change on this file since 58b6d1b was e16294d, checked in by Aaron Moss <a3moss@…>, 8 years ago

Fix sizeof expressions for generic types

  • Property mode set to 100644
File size: 88.6 KB
RevLine 
[51587aa]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//
[ae63a18]7// Box.cc --
[51587aa]8//
9// Author : Richard C. Bilson
10// Created On : Mon May 18 07:44:20 2015
[ca35c51]11// Last Modified By : Peter A. Buhr
[d56e5bc]12// Last Modified On : Wed Jun 21 15:49:59 2017
13// Update Count : 346
[51587aa]14//
[51b73452]15
[08fc48f]16#include <algorithm> // for mismatch
[e3e16bc]17#include <cassert> // for assert, strict_dynamic_cast
[08fc48f]18#include <iostream> // for operator<<, stringstream
19#include <list> // for list, list<>::iterator, _Lis...
20#include <map> // for _Rb_tree_const_iterator, map
21#include <memory> // for auto_ptr
22#include <set> // for set
23#include <string> // for string, allocator, basic_string
24#include <utility> // for pair
[51b73452]25
26#include "Box.h"
27
[bff227f]28#include "CodeGen/OperatorTable.h"
[a0c7dc36]29#include "Common/PassVisitor.h" // for PassVisitor
[08fc48f]30#include "Common/ScopedMap.h" // for ScopedMap, ScopedMap<>::iter...
31#include "Common/SemanticError.h" // for SemanticError
32#include "Common/UniqueName.h" // for UniqueName
33#include "Common/utility.h" // for toString
34#include "FindFunction.h" // for findFunction, findAndReplace...
35#include "GenPoly/ErasableScopedMap.h" // for ErasableScopedMap<>::const_i...
36#include "GenPoly/GenPoly.h" // for TyVarMap, isPolyType, mangle...
37#include "InitTweak/InitTweak.h" // for getFunctionName, isAssignment
38#include "Lvalue.h" // for generalizedLvalue
39#include "Parser/LinkageSpec.h" // for C, Spec, Cforall, Intrinsic
40#include "ResolvExpr/TypeEnvironment.h" // for EqvClass
41#include "ResolvExpr/typeops.h" // for typesCompatible
42#include "ScopedSet.h" // for ScopedSet, ScopedSet<>::iter...
43#include "ScrubTyVars.h" // for ScrubTyVars
44#include "SymTab/Indexer.h" // for Indexer
45#include "SymTab/Mangler.h" // for Mangler
46#include "SynTree/Attribute.h" // for Attribute
47#include "SynTree/Constant.h" // for Constant
48#include "SynTree/Declaration.h" // for DeclarationWithType, ObjectDecl
49#include "SynTree/Expression.h" // for ApplicationExpr, UntypedExpr
50#include "SynTree/Initializer.h" // for SingleInit, Initializer, Lis...
[ba3706f]51#include "SynTree/Label.h" // for Label
[08fc48f]52#include "SynTree/Mutator.h" // for maybeMutate, Mutator, mutateAll
53#include "SynTree/Statement.h" // for ExprStmt, DeclStmt, ReturnStmt
54#include "SynTree/SynTree.h" // for UniqueId
55#include "SynTree/Type.h" // for Type, FunctionType, PointerType
56#include "SynTree/TypeSubstitution.h" // for TypeSubstitution, operator<<
[51b73452]57
58namespace GenPoly {
[01aeade]59 namespace {
[e56cfdb0]60 FunctionType *makeAdapterType( FunctionType *adaptee, const TyVarMap &tyVars );
61
[fc72845d]62 class BoxPass {
63 protected:
64 BoxPass() : scopeTyVars( TypeDecl::Data{} ) {}
65 TyVarMap scopeTyVars;
66 };
67
[9d7b3ea]68 /// Adds layout-generation functions to polymorphic types
[b4bfa0a]69 class LayoutFunctionBuilder final : public WithDeclsToAdd, public WithVisitorRef<LayoutFunctionBuilder>, public WithShortCircuiting {
70 unsigned int functionNesting = 0; // current level of nested functions
[9d7b3ea]71 public:
[b4bfa0a]72 void previsit( FunctionDecl *functionDecl );
73 void previsit( StructDecl *structDecl );
74 void previsit( UnionDecl *unionDecl );
[9d7b3ea]75 };
[70a06f6]76
[f8b961b]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
[201182a]78 class Pass1 final : public BoxPass, public WithTypeSubstitution, public WithStmtsToAdd, public WithGuards, public WithVisitorRef<Pass1>, public WithShortCircuiting {
[01aeade]79 public:
80 Pass1();
[62e5546]81
[201182a]82 void premutate( FunctionDecl * functionDecl );
83 void premutate( TypeDecl * typeDecl );
84 void premutate( CommaExpr * commaExpr );
85 Expression * postmutate( ApplicationExpr * appExpr );
86 Expression * postmutate( UntypedExpr *expr );
87 void premutate( AddressExpr * addrExpr );
88 Expression * postmutate( AddressExpr * addrExpr );
89 void premutate( ReturnStmt * returnStmt );
90 void premutate( PointerType * pointerType );
91 void premutate( FunctionType * functionType );
[62e5546]92
[201182a]93 void beginScope();
94 void endScope();
[01aeade]95 private:
[5c52b06]96 /// Pass the extra type parameters from polymorphic generic arguments or return types into a function application
97 void passArgTypeVars( ApplicationExpr *appExpr, Type *parmType, Type *argBaseType, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars, std::set< std::string > &seenTypes );
[05d47278]98 /// passes extra type parameters into a polymorphic function application
[d9fa60a]99 void passTypeVars( ApplicationExpr *appExpr, Type *polyRetType, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars );
[48ca586]100 /// wraps a function application with a new temporary for the out-parameter return value
[7e003011]101 Expression *addRetParam( ApplicationExpr *appExpr, Type *retType, std::list< Expression *>::iterator &arg );
[48ca586]102 /// Replaces all the type parameters of a generic type with their concrete equivalents under the current environment
103 void replaceParametersWithConcrete( ApplicationExpr *appExpr, std::list< Expression* >& params );
104 /// Replaces a polymorphic type with its concrete equivalant under the current environment (returns itself if concrete).
105 /// If `doClone` is set to false, will not clone interior types
106 Type *replaceWithConcrete( ApplicationExpr *appExpr, Type *type, bool doClone = true );
107 /// wraps a function application returning a polymorphic type with a new temporary for the out-parameter return value
[d7dc824]108 Expression *addDynRetParam( ApplicationExpr *appExpr, Type *polyType, std::list< Expression *>::iterator &arg );
[01aeade]109 Expression *applyAdapter( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars );
110 void boxParam( Type *formal, Expression *&arg, const TyVarMap &exprTyVars );
111 void boxParams( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars );
112 void addInferredParams( ApplicationExpr *appExpr, FunctionType *functionType, std::list< Expression *>::iterator &arg, const TyVarMap &tyVars );
[1194734]113 /// Stores assignment operators from assertion list in local map of assignment operations
[01aeade]114 void passAdapters( ApplicationExpr *appExpr, FunctionType *functionType, const TyVarMap &exprTyVars );
115 FunctionDecl *makeAdapter( FunctionType *adaptee, FunctionType *realType, const std::string &mangleName, const TyVarMap &tyVars );
[05d47278]116 /// Replaces intrinsic operator functions with their arithmetic desugaring
[01aeade]117 Expression *handleIntrinsics( ApplicationExpr *appExpr );
[05d47278]118 /// Inserts a new temporary variable into the current scope with an auto-generated name
[01aeade]119 ObjectDecl *makeTemporary( Type *type );
[c29d9ce]120
[89173242]121 ScopedMap< std::string, DeclarationWithType* > adapters; ///< Set of adapter functions in the current scope
[70a06f6]122
[cce9429]123 std::map< ApplicationExpr *, Expression * > retVals;
124
[01aeade]125 DeclarationWithType *retval;
126 UniqueName tempNamer;
127 };
128
[89173242]129 /// * Moves polymorphic returns in function types to pointer-type parameters
130 /// * adds type size and assertion parameters to parameter lists
[a31b384]131 struct Pass2 final : public BoxPass, public WithGuards {
132 void handleAggDecl();
133
134 DeclarationWithType * postmutate( FunctionDecl *functionDecl );
135 void premutate( StructDecl *structDecl );
136 void premutate( UnionDecl *unionDecl );
137 void premutate( TraitDecl *unionDecl );
138 void premutate( TypeDecl *typeDecl );
139 void premutate( PointerType *pointerType );
140 void premutate( FunctionType *funcType );
[70a06f6]141
[01aeade]142 private:
143 void addAdapters( FunctionType *functionType );
[ae63a18]144
[01aeade]145 std::map< UniqueId, std::string > adapterName;
146 };
147
[8a34677]148 /// Replaces member and size/align/offsetof expressions on polymorphic generic types with calculated expressions.
149 /// * Replaces member expressions for polymorphic types with calculated add-field-offset-and-dereference
150 /// * Calculates polymorphic offsetof expressions from offset array
151 /// * Inserts dynamic calculation of polymorphic type layouts where needed
[201182a]152 class PolyGenericCalculator final : public BoxPass, public WithGuards, public WithVisitorRef<PolyGenericCalculator>, public WithStmtsToAdd, public WithDeclsToAdd, public WithTypeSubstitution {
[8a34677]153 public:
[a0ad7dc]154 PolyGenericCalculator();
155
[a0c7dc36]156 void premutate( ObjectDecl *objectDecl );
157 void premutate( FunctionDecl *functionDecl );
158 void premutate( TypedefDecl *objectDecl );
159 void premutate( TypeDecl *objectDecl );
160 Declaration * postmutate( TypeDecl *TraitDecl );
161 void premutate( PointerType *pointerType );
162 void premutate( FunctionType *funcType );
163 void premutate( DeclStmt *declStmt );
164 Expression *postmutate( MemberExpr *memberExpr );
[02c816fc]165 void premutate( AddressExpr *addrExpr );
166 Expression *postmutate( AddressExpr *addrExpr );
[a0c7dc36]167 Expression *postmutate( SizeofExpr *sizeofExpr );
168 Expression *postmutate( AlignofExpr *alignofExpr );
169 Expression *postmutate( OffsetofExpr *offsetofExpr );
170 Expression *postmutate( OffsetPackExpr *offsetPackExpr );
[8dceeb7]171 void premutate( StructDecl * );
172 void premutate( UnionDecl * );
[a0c7dc36]173
174 void beginScope();
175 void endScope();
[8a34677]176
177 private:
178 /// Makes a new variable in the current scope with the given name, type & optional initializer
179 ObjectDecl *makeVar( const std::string &name, Type *type, Initializer *init = 0 );
180 /// returns true if the type has a dynamic layout; such a layout will be stored in appropriately-named local variables when the function returns
181 bool findGeneric( Type *ty );
182 /// adds type parameters to the layout call; will generate the appropriate parameters if needed
183 void addOtypeParamsToLayoutCall( UntypedExpr *layoutCall, const std::list< Type* > &otypeParams );
[8dceeb7]184 /// change the type of generic aggregate members to char[]
185 void mutateMembers( AggregateDecl * aggrDecl );
[e16294d]186 /// returns the calculated sizeof expression for ty, or nullptr for use C sizeof()
187 Expression* genSizeof( Type* ty );
[aa19ccf]188
189 /// Enters a new scope for type-variables, adding the type variables from ty
190 void beginTypeScope( Type *ty );
191 /// Exits the type-variable scope
192 void endTypeScope();
[a0c7dc36]193 /// Enters a new scope for knowLayouts and knownOffsets and queues exit calls
194 void beginGenericScope();
[70a06f6]195
[8a34677]196 ScopedSet< std::string > knownLayouts; ///< Set of generic type layouts known in the current scope, indexed by sizeofName
197 ScopedSet< std::string > knownOffsets; ///< Set of non-generic types for which the offset array exists in the current scope, indexed by offsetofName
[a0ad7dc]198 UniqueName bufNamer; ///< Namer for VLA buffers
[02c816fc]199 Expression * addrMember = nullptr; ///< AddressExpr argument is MemberExpr?
[05d47278]200 };
[b4cd03b7]201
[fea3faa]202 /// Replaces initialization of polymorphic values with alloca, declaration of dtype/ftype with appropriate void expression, sizeof expressions of polymorphic types with the proper variable, and strips fields from generic struct declarations.
[fc72845d]203 struct Pass3 final : public BoxPass, public WithGuards {
[01aeade]204 template< typename DeclClass >
[fc72845d]205 void handleDecl( DeclClass * decl, Type * type );
206
207 void premutate( ObjectDecl * objectDecl );
208 void premutate( FunctionDecl * functionDecl );
209 void premutate( TypedefDecl * typedefDecl );
210 void premutate( StructDecl * structDecl );
211 void premutate( UnionDecl * unionDecl );
212 void premutate( TypeDecl * typeDecl );
213 void premutate( PointerType * pointerType );
214 void premutate( FunctionType * funcType );
[01aeade]215 };
216 } // anonymous namespace
217
[05d47278]218 /// version of mutateAll with special handling for translation unit so you can check the end of the prelude when debugging
219 template< typename MutatorType >
220 inline void mutateTranslationUnit( std::list< Declaration* > &translationUnit, MutatorType &mutator ) {
221 bool seenIntrinsic = false;
[a16764a6]222 SemanticErrorException errors;
[05d47278]223 for ( typename std::list< Declaration* >::iterator i = translationUnit.begin(); i != translationUnit.end(); ++i ) {
224 try {
225 if ( *i ) {
226 if ( (*i)->get_linkage() == LinkageSpec::Intrinsic ) {
227 seenIntrinsic = true;
228 } else if ( seenIntrinsic ) {
229 seenIntrinsic = false; // break on this line when debugging for end of prelude
230 }
[b4cd03b7]231
[05d47278]232 *i = dynamic_cast< Declaration* >( (*i)->acceptMutator( mutator ) );
233 assert( *i );
234 } // if
[a16764a6]235 } catch( SemanticErrorException &e ) {
[05d47278]236 errors.append( e );
237 } // try
238 } // for
239 if ( ! errors.isEmpty() ) {
240 throw errors;
241 } // if
242 }
243
[01aeade]244 void box( std::list< Declaration *>& translationUnit ) {
[b4bfa0a]245 PassVisitor<LayoutFunctionBuilder> layoutBuilder;
[201182a]246 PassVisitor<Pass1> pass1;
[a31b384]247 PassVisitor<Pass2> pass2;
[a0c7dc36]248 PassVisitor<PolyGenericCalculator> polyCalculator;
[fc72845d]249 PassVisitor<Pass3> pass3;
[70a06f6]250
[b4bfa0a]251 acceptAll( translationUnit, layoutBuilder );
[201182a]252 mutateAll( translationUnit, pass1 );
[a31b384]253 mutateAll( translationUnit, pass2 );
[a0c7dc36]254 mutateAll( translationUnit, polyCalculator );
[fc72845d]255 mutateAll( translationUnit, pass3 );
[6c3744e]256 }
257
[9d7b3ea]258 ////////////////////////////////// LayoutFunctionBuilder ////////////////////////////////////////////
259
[b4bfa0a]260 void LayoutFunctionBuilder::previsit( FunctionDecl *functionDecl ) {
261 visit_children = false;
262 maybeAccept( functionDecl->get_functionType(), *visitor );
[9d7b3ea]263 ++functionNesting;
[b4bfa0a]264 maybeAccept( functionDecl->get_statements(), *visitor );
[9d7b3ea]265 --functionNesting;
266 }
[70a06f6]267
[9d7b3ea]268 /// Get a list of type declarations that will affect a layout function
269 std::list< TypeDecl* > takeOtypeOnly( std::list< TypeDecl* > &decls ) {
270 std::list< TypeDecl * > otypeDecls;
271
272 for ( std::list< TypeDecl* >::const_iterator decl = decls.begin(); decl != decls.end(); ++decl ) {
[2c57025]273 if ( (*decl)->isComplete() ) {
[9d7b3ea]274 otypeDecls.push_back( *decl );
275 }
276 }
[70a06f6]277
[9d7b3ea]278 return otypeDecls;
279 }
280
281 /// Adds parameters for otype layout to a function type
282 void addOtypeParams( FunctionType *layoutFnType, std::list< TypeDecl* > &otypeParams ) {
283 BasicType sizeAlignType( Type::Qualifiers(), BasicType::LongUnsignedInt );
[70a06f6]284
[9d7b3ea]285 for ( std::list< TypeDecl* >::const_iterator param = otypeParams.begin(); param != otypeParams.end(); ++param ) {
[2e60a1a]286 TypeInstType paramType( Type::Qualifiers(), (*param)->get_name(), *param );
[adc6781]287 std::string paramName = mangleType( &paramType );
[68fe077a]288 layoutFnType->get_parameters().push_back( new ObjectDecl( sizeofName( paramName ), Type::StorageClasses(), LinkageSpec::Cforall, 0, sizeAlignType.clone(), 0 ) );
289 layoutFnType->get_parameters().push_back( new ObjectDecl( alignofName( paramName ), Type::StorageClasses(), LinkageSpec::Cforall, 0, sizeAlignType.clone(), 0 ) );
[9d7b3ea]290 }
291 }
292
293 /// Builds a layout function declaration
[adc6781]294 FunctionDecl *buildLayoutFunctionDecl( AggregateDecl *typeDecl, unsigned int functionNesting, FunctionType *layoutFnType ) {
[9d7b3ea]295 // Routines at global scope marked "static" to prevent multiple definitions is separate translation units
296 // because each unit generates copies of the default routines for each aggregate.
[a7c90d4]297 FunctionDecl *layoutDecl = new FunctionDecl( layoutofName( typeDecl ),
[68fe077a]298 functionNesting > 0 ? Type::StorageClasses() : Type::StorageClasses( Type::Static ),
[ba3706f]299 LinkageSpec::AutoGen, layoutFnType, new CompoundStmt(),
[ddfd945]300 std::list< Attribute * >(), Type::FuncSpecifiers( Type::Inline ) );
[9d7b3ea]301 layoutDecl->fixUniqueId();
302 return layoutDecl;
303 }
304
305 /// Makes a unary operation
306 Expression *makeOp( const std::string &name, Expression *arg ) {
307 UntypedExpr *expr = new UntypedExpr( new NameExpr( name ) );
[0690350]308 expr->args.push_back( arg );
[9d7b3ea]309 return expr;
310 }
311
312 /// Makes a binary operation
313 Expression *makeOp( const std::string &name, Expression *lhs, Expression *rhs ) {
314 UntypedExpr *expr = new UntypedExpr( new NameExpr( name ) );
[0690350]315 expr->args.push_back( lhs );
316 expr->args.push_back( rhs );
[9d7b3ea]317 return expr;
318 }
319
320 /// Returns the dereference of a local pointer variable
321 Expression *derefVar( ObjectDecl *var ) {
[0690350]322 return UntypedExpr::createDeref( new VariableExpr( var ) );
[9d7b3ea]323 }
324
325 /// makes an if-statement with a single-expression if-block and no then block
326 Statement *makeCond( Expression *cond, Expression *ifPart ) {
[ba3706f]327 return new IfStmt( cond, new ExprStmt( ifPart ), 0 );
[9d7b3ea]328 }
329
330 /// makes a statement that assigns rhs to lhs if lhs < rhs
331 Statement *makeAssignMax( Expression *lhs, Expression *rhs ) {
332 return makeCond( makeOp( "?<?", lhs, rhs ), makeOp( "?=?", lhs->clone(), rhs->clone() ) );
333 }
334
335 /// makes a statement that aligns lhs to rhs (rhs should be an integer power of two)
336 Statement *makeAlignTo( Expression *lhs, Expression *rhs ) {
337 // check that the lhs is zeroed out to the level of rhs
[d56e5bc]338 Expression *ifCond = makeOp( "?&?", lhs, makeOp( "?-?", rhs, new ConstantExpr( Constant::from_ulong( 1 ) ) ) );
[9d7b3ea]339 // if not aligned, increment to alignment
340 Expression *ifExpr = makeOp( "?+=?", lhs->clone(), makeOp( "?-?", rhs->clone(), ifCond->clone() ) );
341 return makeCond( ifCond, ifExpr );
342 }
[70a06f6]343
[9d7b3ea]344 /// adds an expression to a compound statement
345 void addExpr( CompoundStmt *stmts, Expression *expr ) {
[ba3706f]346 stmts->get_kids().push_back( new ExprStmt( expr ) );
[9d7b3ea]347 }
348
349 /// adds a statement to a compound statement
350 void addStmt( CompoundStmt *stmts, Statement *stmt ) {
351 stmts->get_kids().push_back( stmt );
352 }
[70a06f6]353
[b4bfa0a]354 void LayoutFunctionBuilder::previsit( StructDecl *structDecl ) {
[9d7b3ea]355 // do not generate layout function for "empty" tag structs
[b4bfa0a]356 visit_children = false;
357 if ( structDecl->get_members().empty() ) return;
[9d7b3ea]358
359 // get parameters that can change layout, exiting early if none
360 std::list< TypeDecl* > otypeParams = takeOtypeOnly( structDecl->get_parameters() );
[b4bfa0a]361 if ( otypeParams.empty() ) return;
[9d7b3ea]362
363 // build layout function signature
364 FunctionType *layoutFnType = new FunctionType( Type::Qualifiers(), false );
365 BasicType *sizeAlignType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
366 PointerType *sizeAlignOutType = new PointerType( Type::Qualifiers(), sizeAlignType );
[70a06f6]367
[68fe077a]368 ObjectDecl *sizeParam = new ObjectDecl( sizeofName( structDecl->get_name() ), Type::StorageClasses(), LinkageSpec::Cforall, 0, sizeAlignOutType, 0 );
[9d7b3ea]369 layoutFnType->get_parameters().push_back( sizeParam );
[68fe077a]370 ObjectDecl *alignParam = new ObjectDecl( alignofName( structDecl->get_name() ), Type::StorageClasses(), LinkageSpec::Cforall, 0, sizeAlignOutType->clone(), 0 );
[9d7b3ea]371 layoutFnType->get_parameters().push_back( alignParam );
[68fe077a]372 ObjectDecl *offsetParam = new ObjectDecl( offsetofName( structDecl->get_name() ), Type::StorageClasses(), LinkageSpec::Cforall, 0, sizeAlignOutType->clone(), 0 );
[9d7b3ea]373 layoutFnType->get_parameters().push_back( offsetParam );
374 addOtypeParams( layoutFnType, otypeParams );
375
376 // build function decl
[adc6781]377 FunctionDecl *layoutDecl = buildLayoutFunctionDecl( structDecl, functionNesting, layoutFnType );
[9d7b3ea]378
379 // calculate struct layout in function body
380
[5a3ac84]381 // initialize size and alignment to 0 and 1 (will have at least one member to re-edit size)
[d56e5bc]382 addExpr( layoutDecl->get_statements(), makeOp( "?=?", derefVar( sizeParam ), new ConstantExpr( Constant::from_ulong( 0 ) ) ) );
383 addExpr( layoutDecl->get_statements(), makeOp( "?=?", derefVar( alignParam ), new ConstantExpr( Constant::from_ulong( 1 ) ) ) );
[9d7b3ea]384 unsigned long n_members = 0;
385 bool firstMember = true;
[e16294d]386 for ( Declaration* member : structDecl->get_members() ) {
387 DeclarationWithType *dwt = dynamic_cast< DeclarationWithType * >( member );
[9d7b3ea]388 assert( dwt );
[bd91e2a]389 Type *memberType = dwt->get_type();
[9d7b3ea]390
391 if ( firstMember ) {
392 firstMember = false;
393 } else {
394 // make sure all members after the first (automatically aligned at 0) are properly padded for alignment
[bd91e2a]395 addStmt( layoutDecl->get_statements(), makeAlignTo( derefVar( sizeParam ), new AlignofExpr( memberType->clone() ) ) );
[9d7b3ea]396 }
[70a06f6]397
[9d7b3ea]398 // place current size in the current offset index
[cb4c607]399 addExpr( layoutDecl->get_statements(), makeOp( "?=?", makeOp( "?[?]", new VariableExpr( offsetParam ), new ConstantExpr( Constant::from_ulong( n_members ) ) ),
[9d7b3ea]400 derefVar( sizeParam ) ) );
401 ++n_members;
402
403 // add member size to current size
[bd91e2a]404 addExpr( layoutDecl->get_statements(), makeOp( "?+=?", derefVar( sizeParam ), new SizeofExpr( memberType->clone() ) ) );
[70a06f6]405
[9d7b3ea]406 // take max of member alignment and global alignment
[bd91e2a]407 addStmt( layoutDecl->get_statements(), makeAssignMax( derefVar( alignParam ), new AlignofExpr( memberType->clone() ) ) );
[9d7b3ea]408 }
409 // make sure the type is end-padded to a multiple of its alignment
410 addStmt( layoutDecl->get_statements(), makeAlignTo( derefVar( sizeParam ), derefVar( alignParam ) ) );
411
[b4bfa0a]412 declsToAddAfter.push_back( layoutDecl );
[9d7b3ea]413 }
[70a06f6]414
[b4bfa0a]415 void LayoutFunctionBuilder::previsit( UnionDecl *unionDecl ) {
[9d7b3ea]416 // do not generate layout function for "empty" tag unions
[b4bfa0a]417 visit_children = false;
418 if ( unionDecl->get_members().empty() ) return;
[70a06f6]419
[9d7b3ea]420 // get parameters that can change layout, exiting early if none
421 std::list< TypeDecl* > otypeParams = takeOtypeOnly( unionDecl->get_parameters() );
[b4bfa0a]422 if ( otypeParams.empty() ) return;
[9d7b3ea]423
424 // build layout function signature
425 FunctionType *layoutFnType = new FunctionType( Type::Qualifiers(), false );
426 BasicType *sizeAlignType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
427 PointerType *sizeAlignOutType = new PointerType( Type::Qualifiers(), sizeAlignType );
[70a06f6]428
[68fe077a]429 ObjectDecl *sizeParam = new ObjectDecl( sizeofName( unionDecl->get_name() ), Type::StorageClasses(), LinkageSpec::Cforall, 0, sizeAlignOutType, 0 );
[9d7b3ea]430 layoutFnType->get_parameters().push_back( sizeParam );
[68fe077a]431 ObjectDecl *alignParam = new ObjectDecl( alignofName( unionDecl->get_name() ), Type::StorageClasses(), LinkageSpec::Cforall, 0, sizeAlignOutType->clone(), 0 );
[9d7b3ea]432 layoutFnType->get_parameters().push_back( alignParam );
433 addOtypeParams( layoutFnType, otypeParams );
434
435 // build function decl
[adc6781]436 FunctionDecl *layoutDecl = buildLayoutFunctionDecl( unionDecl, functionNesting, layoutFnType );
[9d7b3ea]437
438 // calculate union layout in function body
[d56e5bc]439 addExpr( layoutDecl->get_statements(), makeOp( "?=?", derefVar( sizeParam ), new ConstantExpr( Constant::from_ulong( 1 ) ) ) );
440 addExpr( layoutDecl->get_statements(), makeOp( "?=?", derefVar( alignParam ), new ConstantExpr( Constant::from_ulong( 1 ) ) ) );
[9d7b3ea]441 for ( std::list< Declaration* >::const_iterator member = unionDecl->get_members().begin(); member != unionDecl->get_members().end(); ++member ) {
442 DeclarationWithType *dwt = dynamic_cast< DeclarationWithType * >( *member );
443 assert( dwt );
[bd91e2a]444 Type *memberType = dwt->get_type();
[70a06f6]445
[9d7b3ea]446 // take max member size and global size
[bd91e2a]447 addStmt( layoutDecl->get_statements(), makeAssignMax( derefVar( sizeParam ), new SizeofExpr( memberType->clone() ) ) );
[70a06f6]448
[9d7b3ea]449 // take max of member alignment and global alignment
[bd91e2a]450 addStmt( layoutDecl->get_statements(), makeAssignMax( derefVar( alignParam ), new AlignofExpr( memberType->clone() ) ) );
[9d7b3ea]451 }
452 // make sure the type is end-padded to a multiple of its alignment
453 addStmt( layoutDecl->get_statements(), makeAlignTo( derefVar( sizeParam ), derefVar( alignParam ) ) );
454
[b4bfa0a]455 declsToAddAfter.push_back( layoutDecl );
[9d7b3ea]456 }
[70a06f6]457
[01aeade]458 ////////////////////////////////////////// Pass1 ////////////////////////////////////////////////////
459
460 namespace {
[bdf1954]461 std::string makePolyMonoSuffix( FunctionType * function, const TyVarMap &tyVars ) {
462 std::stringstream name;
463
[ed1065c]464 // NOTE: this function previously used isPolyObj, which failed to produce
465 // the correct thing in some situations. It's not clear to me why this wasn't working.
466
[ae63a18]467 // if the return type or a parameter type involved polymorphic types, then the adapter will need
468 // to take those polymorphic types as pointers. Therefore, there can be two different functions
[bdf1954]469 // with the same mangled name, so we need to further mangle the names.
[ed1065c]470 for ( std::list< DeclarationWithType *>::iterator retval = function->get_returnVals().begin(); retval != function->get_returnVals().end(); ++retval ) {
[ffad73a]471 if ( isPolyType( (*retval)->get_type(), tyVars ) ) {
[ed1065c]472 name << "P";
473 } else {
474 name << "M";
475 }
[bdf1954]476 }
477 name << "_";
478 std::list< DeclarationWithType *> &paramList = function->get_parameters();
479 for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
[ffad73a]480 if ( isPolyType( (*arg)->get_type(), tyVars ) ) {
[bdf1954]481 name << "P";
482 } else {
[ae63a18]483 name << "M";
[bdf1954]484 }
485 } // for
486 return name.str();
487 }
488
489 std::string mangleAdapterName( FunctionType * function, const TyVarMap &tyVars ) {
490 return SymTab::Mangler::mangle( function ) + makePolyMonoSuffix( function, tyVars );
491 }
492
[01aeade]493 std::string makeAdapterName( const std::string &mangleName ) {
494 return "_adapter" + mangleName;
495 }
[6c3744e]496
[cce9429]497 Pass1::Pass1() : tempNamer( "_temp" ) {}
[01aeade]498
[201182a]499 void Pass1::premutate( FunctionDecl *functionDecl ) {
[e56cfdb0]500 if ( functionDecl->get_statements() ) { // empty routine body ?
[2a7b3ca]501 // std::cerr << "mutating function: " << functionDecl->get_mangleName() << std::endl;
[201182a]502 GuardScope( scopeTyVars );
503 GuardValue( retval );
[e56cfdb0]504
505 // process polymorphic return value
[cce9429]506 retval = nullptr;
[201182a]507 FunctionType *functionType = functionDecl->type;
508 if ( isDynRet( functionType ) && functionDecl->linkage != LinkageSpec::C ) {
509 retval = functionType->returnVals.front();
[ae63a18]510
[01aeade]511 // give names to unnamed return values
[201182a]512 if ( retval->name == "" ) {
513 retval->name = "_retparm";
514 retval->linkage = LinkageSpec::C;
[01aeade]515 } // if
516 } // if
[ae63a18]517
[201182a]518 makeTyVarMap( functionType, scopeTyVars );
[e56cfdb0]519
[201182a]520 std::list< DeclarationWithType *> &paramList = functionType->parameters;
[e56cfdb0]521 std::list< FunctionType *> functions;
[201182a]522 for ( Type::ForallList::iterator tyVar = functionType->forall.begin(); tyVar != functionType->forall.end(); ++tyVar ) {
523 for ( std::list< DeclarationWithType *>::iterator assert = (*tyVar)->assertions.begin(); assert != (*tyVar)->assertions.end(); ++assert ) {
[e56cfdb0]524 findFunction( (*assert)->get_type(), functions, scopeTyVars, needsAdapter );
525 } // for
526 } // for
527 for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
528 findFunction( (*arg)->get_type(), functions, scopeTyVars, needsAdapter );
529 } // for
[b4cd03b7]530
[e56cfdb0]531 for ( std::list< FunctionType *>::iterator funType = functions.begin(); funType != functions.end(); ++funType ) {
[bdf1954]532 std::string mangleName = mangleAdapterName( *funType, scopeTyVars );
[e56cfdb0]533 if ( adapters.find( mangleName ) == adapters.end() ) {
534 std::string adapterName = makeAdapterName( mangleName );
[68fe077a]535 adapters.insert( std::pair< std::string, DeclarationWithType *>( mangleName, new ObjectDecl( adapterName, Type::StorageClasses(), LinkageSpec::C, nullptr, new PointerType( Type::Qualifiers(), makeAdapterType( *funType, scopeTyVars ) ), nullptr ) ) );
[e56cfdb0]536 } // if
537 } // for
[2a7b3ca]538 // std::cerr << "end function: " << functionDecl->get_mangleName() << std::endl;
[01aeade]539 } // if
540 }
[6c3744e]541
[201182a]542 void Pass1::premutate( TypeDecl *typeDecl ) {
[2c57025]543 addToTyVarMap( typeDecl, scopeTyVars );
[01aeade]544 }
[6c3744e]545
[201182a]546 void Pass1::premutate( CommaExpr *commaExpr ) {
[cce9429]547 // Attempting to find application expressions that were mutated by the copy constructor passes
548 // to use an explicit return variable, so that the variable can be reused as a parameter to the
549 // call rather than creating a new temp variable. Previously this step was an optimization, but
550 // with the introduction of tuples and UniqueExprs, it is necessary to ensure that they use the same variable.
551 // Essentially, looking for pattern: (x=f(...), x)
552 // To compound the issue, the right side can be *x, etc. because of lvalue-returning functions
553 if ( UntypedExpr * assign = dynamic_cast< UntypedExpr * >( commaExpr->get_arg1() ) ) {
[bff227f]554 if ( CodeGen::isAssignment( InitTweak::getFunctionName( assign ) ) ) {
[cce9429]555 assert( assign->get_args().size() == 2 );
556 if ( ApplicationExpr * appExpr = dynamic_cast< ApplicationExpr * > ( assign->get_args().back() ) ) {
557 // first argument is assignable, so it must be an lvalue, so it should be legal to take its address.
558 retVals[appExpr] = assign->get_args().front();
559 }
560 }
561 }
[01aeade]562 }
[6c3744e]563
[5c52b06]564 void Pass1::passArgTypeVars( ApplicationExpr *appExpr, Type *parmType, Type *argBaseType, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars, std::set< std::string > &seenTypes ) {
[4b8f918]565 Type *polyType = isPolyType( parmType, exprTyVars );
566 if ( polyType && ! dynamic_cast< TypeInstType* >( polyType ) ) {
567 std::string typeName = mangleType( polyType );
[adc6781]568 if ( seenTypes.count( typeName ) ) return;
[5c52b06]569
570 arg = appExpr->get_args().insert( arg, new SizeofExpr( argBaseType->clone() ) );
571 arg++;
572 arg = appExpr->get_args().insert( arg, new AlignofExpr( argBaseType->clone() ) );
573 arg++;
[4b8f918]574 if ( dynamic_cast< StructInstType* >( polyType ) ) {
[5c52b06]575 if ( StructInstType *argBaseStructType = dynamic_cast< StructInstType* >( argBaseType ) ) {
[89173242]576 // zero-length arrays are forbidden by C, so don't pass offset for empty struct
577 if ( ! argBaseStructType->get_baseStruct()->get_members().empty() ) {
[d75038c]578 arg = appExpr->get_args().insert( arg, new OffsetPackExpr( argBaseStructType->clone() ) );
[89173242]579 arg++;
580 }
[5c52b06]581 } else {
[a16764a6]582 SemanticError( argBaseType, "Cannot pass non-struct type for generic struct: " );
[5c52b06]583 }
584 }
585
[adc6781]586 seenTypes.insert( typeName );
[5c52b06]587 }
588 }
589
[d9fa60a]590 void Pass1::passTypeVars( ApplicationExpr *appExpr, Type *polyRetType, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars ) {
[7754cde]591 // pass size/align for type variables
[01aeade]592 for ( TyVarMap::const_iterator tyParm = exprTyVars.begin(); tyParm != exprTyVars.end(); ++tyParm ) {
593 ResolvExpr::EqvClass eqvClass;
594 assert( env );
[2c57025]595 if ( tyParm->second.isComplete ) {
[01aeade]596 Type *concrete = env->lookup( tyParm->first );
597 if ( concrete ) {
598 arg = appExpr->get_args().insert( arg, new SizeofExpr( concrete->clone() ) );
599 arg++;
[db0b3ce]600 arg = appExpr->get_args().insert( arg, new AlignofExpr( concrete->clone() ) );
601 arg++;
[01aeade]602 } else {
[ea5daeb]603 // xxx - should this be an assertion?
[a16764a6]604 SemanticError( appExpr, toString( *env, "\nunbound type variable: ", tyParm->first, " in application " ) );
[01aeade]605 } // if
606 } // if
607 } // for
[7754cde]608
609 // add size/align for generic types to parameter list
[d29fa5f]610 if ( ! appExpr->get_function()->result ) return;
[906e24d]611 FunctionType *funcType = getFunctionType( appExpr->get_function()->get_result() );
[7754cde]612 assert( funcType );
[ae63a18]613
[7754cde]614 std::list< DeclarationWithType* >::const_iterator fnParm = funcType->get_parameters().begin();
615 std::list< Expression* >::const_iterator fnArg = arg;
[ea5daeb]616 std::set< std::string > seenTypes; ///< names for generic types we've seen
[7754cde]617
[5c52b06]618 // a polymorphic return type may need to be added to the argument list
619 if ( polyRetType ) {
620 Type *concRetType = replaceWithConcrete( appExpr, polyRetType );
621 passArgTypeVars( appExpr, polyRetType, concRetType, arg, exprTyVars, seenTypes );
[5802a4f]622 ++fnArg; // skip the return parameter in the argument list
[5c52b06]623 }
[70a06f6]624
[5c52b06]625 // add type information args for presently unseen types in parameter list
626 for ( ; fnParm != funcType->get_parameters().end() && fnArg != appExpr->get_args().end(); ++fnParm, ++fnArg ) {
[5802a4f]627 if ( ! (*fnArg)->get_result() ) continue;
628 Type * argType = (*fnArg)->get_result();
629 passArgTypeVars( appExpr, (*fnParm)->get_type(), argType, arg, exprTyVars, seenTypes );
[7754cde]630 }
[01aeade]631 }
[6c3744e]632
[01aeade]633 ObjectDecl *Pass1::makeTemporary( Type *type ) {
[68fe077a]634 ObjectDecl *newObj = new ObjectDecl( tempNamer.newName(), Type::StorageClasses(), LinkageSpec::C, 0, type, 0 );
[ba3706f]635 stmtsToAddBefore.push_back( new DeclStmt( newObj ) );
[01aeade]636 return newObj;
637 }
[6c3744e]638
[7e003011]639 Expression *Pass1::addRetParam( ApplicationExpr *appExpr, Type *retType, std::list< Expression *>::iterator &arg ) {
[cf16f94]640 // Create temporary to hold return value of polymorphic function and produce that temporary as a result
[cce9429]641 // using a comma expression.
[d9fa60a]642 assert( retType );
[cce9429]643
644 Expression * paramExpr = nullptr;
645 // try to use existing return value parameter if it exists, otherwise create a new temporary
646 if ( retVals.count( appExpr ) ) {
647 paramExpr = retVals[appExpr]->clone();
648 } else {
649 ObjectDecl *newObj = makeTemporary( retType->clone() );
650 paramExpr = new VariableExpr( newObj );
651 }
652 Expression * retExpr = paramExpr->clone();
[5c52b06]653
654 // If the type of the temporary is not polymorphic, box temporary by taking its address;
655 // otherwise the temporary is already boxed and can be used directly.
[cce9429]656 if ( ! isPolyType( paramExpr->get_result(), scopeTyVars, env ) ) {
[cf16f94]657 paramExpr = new AddressExpr( paramExpr );
[01aeade]658 } // if
[cf16f94]659 arg = appExpr->get_args().insert( arg, paramExpr ); // add argument to function call
660 arg++;
661 // Build a comma expression to call the function and emulate a normal return.
[cce9429]662 CommaExpr *commaExpr = new CommaExpr( appExpr, retExpr );
[cf16f94]663 commaExpr->set_env( appExpr->get_env() );
664 appExpr->set_env( 0 );
665 return commaExpr;
[01aeade]666 }
[6c3744e]667
[48ca586]668 void Pass1::replaceParametersWithConcrete( ApplicationExpr *appExpr, std::list< Expression* >& params ) {
669 for ( std::list< Expression* >::iterator param = params.begin(); param != params.end(); ++param ) {
670 TypeExpr *paramType = dynamic_cast< TypeExpr* >( *param );
[8bf784a]671 assertf(paramType, "Aggregate parameters should be type expressions");
[48ca586]672 paramType->set_type( replaceWithConcrete( appExpr, paramType->get_type(), false ) );
673 }
674 }
[b4cd03b7]675
[48ca586]676 Type *Pass1::replaceWithConcrete( ApplicationExpr *appExpr, Type *type, bool doClone ) {
677 if ( TypeInstType *typeInst = dynamic_cast< TypeInstType * >( type ) ) {
678 Type *concrete = env->lookup( typeInst->get_name() );
679 if ( concrete == 0 ) {
[7b2c0a99]680 return typeInst;
[48ca586]681 } // if
682 return concrete;
683 } else if ( StructInstType *structType = dynamic_cast< StructInstType* >( type ) ) {
684 if ( doClone ) {
685 structType = structType->clone();
686 }
687 replaceParametersWithConcrete( appExpr, structType->get_parameters() );
688 return structType;
689 } else if ( UnionInstType *unionType = dynamic_cast< UnionInstType* >( type ) ) {
690 if ( doClone ) {
691 unionType = unionType->clone();
692 }
693 replaceParametersWithConcrete( appExpr, unionType->get_parameters() );
694 return unionType;
695 }
696 return type;
697 }
698
[d7dc824]699 Expression *Pass1::addDynRetParam( ApplicationExpr *appExpr, Type *dynType, std::list< Expression *>::iterator &arg ) {
[01aeade]700 assert( env );
[3bb195cb]701 Type *concrete = replaceWithConcrete( appExpr, dynType );
[70a06f6]702 // add out-parameter for return value
[7e003011]703 return addRetParam( appExpr, concrete, arg );
[01aeade]704 }
[6c3744e]705
[01aeade]706 Expression *Pass1::applyAdapter( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &tyVars ) {
707 Expression *ret = appExpr;
[3bb195cb]708// if ( ! function->get_returnVals().empty() && isPolyType( function->get_returnVals().front()->get_type(), tyVars ) ) {
709 if ( isDynRet( function, tyVars ) ) {
[7e003011]710 ret = addRetParam( appExpr, function->get_returnVals().front()->get_type(), arg );
[01aeade]711 } // if
[bdf1954]712 std::string mangleName = mangleAdapterName( function, tyVars );
[01aeade]713 std::string adapterName = makeAdapterName( mangleName );
[b1a6d6b]714
[b4cd03b7]715 // cast adaptee to void (*)(), since it may have any type inside a polymorphic function
716 Type * adapteeType = new PointerType( Type::Qualifiers(), new FunctionType( Type::Qualifiers(), true ) );
717 appExpr->get_args().push_front( new CastExpr( appExpr->get_function(), adapteeType ) );
[906e24d]718 appExpr->set_function( new NameExpr( adapterName ) ); // xxx - result is never set on NameExpr
[ae63a18]719
[01aeade]720 return ret;
721 }
[6c3744e]722
[01aeade]723 void Pass1::boxParam( Type *param, Expression *&arg, const TyVarMap &exprTyVars ) {
[d29fa5f]724 assertf( arg->result, "arg does not have result: %s", toString( arg ).c_str() );
[ae1b9ea]725 if ( ! needsBoxing( param, arg->result, exprTyVars, env ) ) return;
726
727 if ( arg->result->get_lvalue() ) {
728 // argument expression may be CFA lvalue, but not C lvalue -- apply generalizedLvalue transformations.
729 // if ( VariableExpr * varExpr = dynamic_cast< VariableExpr * >( arg ) ) {
730 // if ( dynamic_cast<ArrayType *>( varExpr->var->get_type() ) ){
731 // // temporary hack - don't box arrays, because &arr is not the same as &arr[0]
732 // return;
733 // }
734 // }
735 arg = generalizedLvalue( new AddressExpr( arg ) );
736 if ( ! ResolvExpr::typesCompatible( param, arg->get_result(), SymTab::Indexer() ) ) {
737 // silence warnings by casting boxed parameters when the actual type does not match up with the formal type.
738 arg = new CastExpr( arg, param->clone() );
739 }
740 } else {
741 // use type computed in unification to declare boxed variables
742 Type * newType = param->clone();
[acd7c5dd]743 if ( env ) env->apply( newType );
[4573e3c]744 ObjectDecl *newObj = ObjectDecl::newObject( tempNamer.newName(), newType, nullptr );
[ae1b9ea]745 newObj->get_type()->get_qualifiers() = Type::Qualifiers(); // TODO: is this right???
[ba3706f]746 stmtsToAddBefore.push_back( new DeclStmt( newObj ) );
[ae1b9ea]747 UntypedExpr *assign = new UntypedExpr( new NameExpr( "?=?" ) ); // TODO: why doesn't this just use initialization syntax?
748 assign->get_args().push_back( new VariableExpr( newObj ) );
749 assign->get_args().push_back( arg );
[ba3706f]750 stmtsToAddBefore.push_back( new ExprStmt( assign ) );
[ae1b9ea]751 arg = new AddressExpr( new VariableExpr( newObj ) );
[01aeade]752 } // if
753 }
[6c3744e]754
[4573e3c]755 // find instances of polymorphic type parameters
756 struct PolyFinder {
757 const TyVarMap * tyVars = nullptr;
758 bool found = false;
759
760 void previsit( TypeInstType * t ) {
761 if ( isPolyType( t, *tyVars ) ) {
762 found = true;
763 }
764 }
765 };
766
767 // true if there is an instance of a polymorphic type parameter in t
768 bool hasPolymorphism( Type * t, const TyVarMap &tyVars ) {
769 PassVisitor<PolyFinder> finder;
770 finder.pass.tyVars = &tyVars;
771 maybeAccept( t, finder );
772 return finder.pass.found;
773 }
774
[b4cd03b7]775 /// cast parameters to polymorphic functions so that types are replaced with
776 /// void * if they are type parameters in the formal type.
777 /// this gets rid of warnings from gcc.
[01aeade]778 void addCast( Expression *&actual, Type *formal, const TyVarMap &tyVars ) {
[4573e3c]779 // type contains polymorphism, but isn't exactly a polytype, in which case it
780 // has some real actual type (e.g. unsigned int) and casting to void * is wrong
781 if ( hasPolymorphism( formal, tyVars ) && ! isPolyType( formal, tyVars ) ) {
[ea5daeb]782 Type * newType = formal->clone();
[b4cd03b7]783 newType = ScrubTyVars::scrub( newType, tyVars );
[01aeade]784 actual = new CastExpr( actual, newType );
785 } // if
786 }
[6c3744e]787
[01aeade]788 void Pass1::boxParams( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars ) {
[4573e3c]789 for ( std::list< DeclarationWithType *>::const_iterator param = function->get_parameters().begin(); param != function->parameters.end(); ++param, ++arg ) {
790 assertf( arg != appExpr->args.end(), "boxParams: missing argument for param %s to %s in %s", toString( *param ).c_str(), toString( function ).c_str(), toString( appExpr ).c_str() );
[01aeade]791 addCast( *arg, (*param)->get_type(), exprTyVars );
792 boxParam( (*param)->get_type(), *arg, exprTyVars );
793 } // for
794 }
[6c3744e]795
[01aeade]796 void Pass1::addInferredParams( ApplicationExpr *appExpr, FunctionType *functionType, std::list< Expression *>::iterator &arg, const TyVarMap &tyVars ) {
797 std::list< Expression *>::iterator cur = arg;
[8c49c0e]798 for ( Type::ForallList::iterator tyVar = functionType->get_forall().begin(); tyVar != functionType->get_forall().end(); ++tyVar ) {
[4573e3c]799 for ( std::list< DeclarationWithType *>::iterator assert = (*tyVar)->assertions.begin(); assert != (*tyVar)->assertions.end(); ++assert ) {
[01aeade]800 InferredParams::const_iterator inferParam = appExpr->get_inferParams().find( (*assert)->get_uniqueId() );
[4573e3c]801 assertf( inferParam != appExpr->get_inferParams().end(), "addInferredParams missing inferred parameter: %s in: %s", toString( *assert ).c_str(), toString( appExpr ).c_str() );
[01aeade]802 Expression *newExpr = inferParam->second.expr->clone();
803 addCast( newExpr, (*assert)->get_type(), tyVars );
804 boxParam( (*assert)->get_type(), newExpr, tyVars );
805 appExpr->get_args().insert( cur, newExpr );
806 } // for
807 } // for
808 }
[6c3744e]809
[01aeade]810 void makeRetParm( FunctionType *funcType ) {
[4573e3c]811 DeclarationWithType *retParm = funcType->returnVals.front();
[6c3744e]812
[01aeade]813 // make a new parameter that is a pointer to the type of the old return value
814 retParm->set_type( new PointerType( Type::Qualifiers(), retParm->get_type() ) );
815 funcType->get_parameters().push_front( retParm );
[6c3744e]816
[01aeade]817 // we don't need the return value any more
818 funcType->get_returnVals().clear();
819 }
[6c3744e]820
[01aeade]821 FunctionType *makeAdapterType( FunctionType *adaptee, const TyVarMap &tyVars ) {
822 // actually make the adapter type
823 FunctionType *adapter = adaptee->clone();
[3bb195cb]824 if ( isDynRet( adapter, tyVars ) ) {
[01aeade]825 makeRetParm( adapter );
826 } // if
[68fe077a]827 adapter->get_parameters().push_front( new ObjectDecl( "", Type::StorageClasses(), LinkageSpec::C, 0, new PointerType( Type::Qualifiers(), new FunctionType( Type::Qualifiers(), true ) ), 0 ) );
[01aeade]828 return adapter;
829 }
[6c3744e]830
[01aeade]831 Expression *makeAdapterArg( DeclarationWithType *param, DeclarationWithType *arg, DeclarationWithType *realParam, const TyVarMap &tyVars ) {
832 assert( param );
833 assert( arg );
[ffad73a]834 if ( isPolyType( realParam->get_type(), tyVars ) ) {
[30aeb27]835 if ( ! isPolyType( arg->get_type() ) ) {
[e56cfdb0]836 UntypedExpr *deref = new UntypedExpr( new NameExpr( "*?" ) );
[0690350]837 deref->args.push_back( new CastExpr( new VariableExpr( param ), new PointerType( Type::Qualifiers(), arg->get_type()->clone() ) ) );
838 deref->result = arg->get_type()->clone();
[1a4bef3]839 deref->result->set_lvalue( true );
[e56cfdb0]840 return deref;
841 } // if
[01aeade]842 } // if
843 return new VariableExpr( param );
844 }
[6c3744e]845
[01aeade]846 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 ) {
847 UniqueName paramNamer( "_p" );
848 for ( ; param != paramEnd; ++param, ++arg, ++realParam ) {
849 if ( (*param)->get_name() == "" ) {
850 (*param)->set_name( paramNamer.newName() );
851 (*param)->set_linkage( LinkageSpec::C );
852 } // if
853 adapteeApp->get_args().push_back( makeAdapterArg( *param, *arg, *realParam, tyVars ) );
854 } // for
855 }
[6c3744e]856
[01aeade]857 FunctionDecl *Pass1::makeAdapter( FunctionType *adaptee, FunctionType *realType, const std::string &mangleName, const TyVarMap &tyVars ) {
858 FunctionType *adapterType = makeAdapterType( adaptee, tyVars );
859 adapterType = ScrubTyVars::scrub( adapterType, tyVars );
860 DeclarationWithType *adapteeDecl = adapterType->get_parameters().front();
861 adapteeDecl->set_name( "_adaptee" );
[1f370451]862 // do not carry over attributes to real type parameters/return values
863 for ( DeclarationWithType * dwt : realType->parameters ) {
864 deleteAll( dwt->get_type()->attributes );
865 dwt->get_type()->attributes.clear();
866 }
867 for ( DeclarationWithType * dwt : realType->returnVals ) {
868 deleteAll( dwt->get_type()->attributes );
869 dwt->get_type()->attributes.clear();
870 }
[01aeade]871 ApplicationExpr *adapteeApp = new ApplicationExpr( new CastExpr( new VariableExpr( adapteeDecl ), new PointerType( Type::Qualifiers(), realType ) ) );
872 Statement *bodyStmt;
[ae63a18]873
[8c49c0e]874 Type::ForallList::iterator tyArg = realType->get_forall().begin();
875 Type::ForallList::iterator tyParam = adapterType->get_forall().begin();
876 Type::ForallList::iterator realTyParam = adaptee->get_forall().begin();
[01aeade]877 for ( ; tyParam != adapterType->get_forall().end(); ++tyArg, ++tyParam, ++realTyParam ) {
878 assert( tyArg != realType->get_forall().end() );
879 std::list< DeclarationWithType *>::iterator assertArg = (*tyArg)->get_assertions().begin();
880 std::list< DeclarationWithType *>::iterator assertParam = (*tyParam)->get_assertions().begin();
881 std::list< DeclarationWithType *>::iterator realAssertParam = (*realTyParam)->get_assertions().begin();
882 for ( ; assertParam != (*tyParam)->get_assertions().end(); ++assertArg, ++assertParam, ++realAssertParam ) {
883 assert( assertArg != (*tyArg)->get_assertions().end() );
884 adapteeApp->get_args().push_back( makeAdapterArg( *assertParam, *assertArg, *realAssertParam, tyVars ) );
885 } // for
886 } // for
[ae63a18]887
[01aeade]888 std::list< DeclarationWithType *>::iterator arg = realType->get_parameters().begin();
889 std::list< DeclarationWithType *>::iterator param = adapterType->get_parameters().begin();
890 std::list< DeclarationWithType *>::iterator realParam = adaptee->get_parameters().begin();
[cc3528f]891 param++; // skip adaptee parameter in the adapter type
[01aeade]892 if ( realType->get_returnVals().empty() ) {
[cc3528f]893 // void return
[01aeade]894 addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
[ba3706f]895 bodyStmt = new ExprStmt( adapteeApp );
[3bb195cb]896 } else if ( isDynType( adaptee->get_returnVals().front()->get_type(), tyVars ) ) {
[cc3528f]897 // return type T
[01aeade]898 if ( (*param)->get_name() == "" ) {
899 (*param)->set_name( "_ret" );
900 (*param)->set_linkage( LinkageSpec::C );
901 } // if
902 UntypedExpr *assign = new UntypedExpr( new NameExpr( "?=?" ) );
[c10ee66]903 UntypedExpr *deref = UntypedExpr::createDeref( new CastExpr( new VariableExpr( *param++ ), new PointerType( Type::Qualifiers(), realType->get_returnVals().front()->get_type()->clone() ) ) );
[01aeade]904 assign->get_args().push_back( deref );
905 addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
906 assign->get_args().push_back( adapteeApp );
[ba3706f]907 bodyStmt = new ExprStmt( assign );
[01aeade]908 } else {
909 // adapter for a function that returns a monomorphic value
910 addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
[ba3706f]911 bodyStmt = new ReturnStmt( adapteeApp );
[01aeade]912 } // if
[ba3706f]913 CompoundStmt *adapterBody = new CompoundStmt();
[01aeade]914 adapterBody->get_kids().push_back( bodyStmt );
915 std::string adapterName = makeAdapterName( mangleName );
[68fe077a]916 return new FunctionDecl( adapterName, Type::StorageClasses(), LinkageSpec::C, adapterType, adapterBody );
[01aeade]917 }
[6c3744e]918
[c29d9ce]919 void Pass1::passAdapters( ApplicationExpr * appExpr, FunctionType * functionType, const TyVarMap & exprTyVars ) {
[e497c1d]920 // collect a list of function types passed as parameters or implicit parameters (assertions)
[01aeade]921 std::list< DeclarationWithType *> &paramList = functionType->get_parameters();
922 std::list< FunctionType *> functions;
[8c49c0e]923 for ( Type::ForallList::iterator tyVar = functionType->get_forall().begin(); tyVar != functionType->get_forall().end(); ++tyVar ) {
[01aeade]924 for ( std::list< DeclarationWithType *>::iterator assert = (*tyVar)->get_assertions().begin(); assert != (*tyVar)->get_assertions().end(); ++assert ) {
925 findFunction( (*assert)->get_type(), functions, exprTyVars, needsAdapter );
926 } // for
927 } // for
928 for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
929 findFunction( (*arg)->get_type(), functions, exprTyVars, needsAdapter );
930 } // for
[e497c1d]931
[e56cfdb0]932 // parameter function types for which an appropriate adapter has been generated. we cannot use the types
933 // after applying substitutions, since two different parameter types may be unified to the same type
[01aeade]934 std::set< std::string > adaptersDone;
[e497c1d]935
[01aeade]936 for ( std::list< FunctionType *>::iterator funType = functions.begin(); funType != functions.end(); ++funType ) {
[c29d9ce]937 FunctionType *originalFunction = (*funType)->clone();
[01aeade]938 FunctionType *realFunction = (*funType)->clone();
939 std::string mangleName = SymTab::Mangler::mangle( realFunction );
[e497c1d]940
[e56cfdb0]941 // only attempt to create an adapter or pass one as a parameter if we haven't already done so for this
942 // pre-substitution parameter function type.
[01aeade]943 if ( adaptersDone.find( mangleName ) == adaptersDone.end() ) {
[e497c1d]944 adaptersDone.insert( adaptersDone.begin(), mangleName );
[ae63a18]945
[e56cfdb0]946 // apply substitution to type variables to figure out what the adapter's type should look like
[e497c1d]947 assert( env );
948 env->apply( realFunction );
[ae63a18]949 mangleName = SymTab::Mangler::mangle( realFunction );
[bdf1954]950 mangleName += makePolyMonoSuffix( originalFunction, exprTyVars );
[e497c1d]951
[6635c74]952 typedef ScopedMap< std::string, DeclarationWithType* >::iterator AdapterIter;
953 AdapterIter adapter = adapters.find( mangleName );
[e56cfdb0]954 if ( adapter == adapters.end() ) {
955 // adapter has not been created yet in the current scope, so define it
956 FunctionDecl *newAdapter = makeAdapter( *funType, realFunction, mangleName, exprTyVars );
[6635c74]957 std::pair< AdapterIter, bool > answer = adapters.insert( std::pair< std::string, DeclarationWithType *>( mangleName, newAdapter ) );
958 adapter = answer.first;
[ba3706f]959 stmtsToAddBefore.push_back( new DeclStmt( newAdapter ) );
[c29d9ce]960 } // if
[e56cfdb0]961 assert( adapter != adapters.end() );
962
963 // add the appropriate adapter as a parameter
964 appExpr->get_args().push_front( new VariableExpr( adapter->second ) );
[01aeade]965 } // if
966 } // for
[e56cfdb0]967 } // passAdapters
[6c3744e]968
[78dd0da]969 Expression *makeIncrDecrExpr( ApplicationExpr *appExpr, Type *polyType, bool isIncr ) {
[01aeade]970 NameExpr *opExpr;
971 if ( isIncr ) {
972 opExpr = new NameExpr( "?+=?" );
973 } else {
974 opExpr = new NameExpr( "?-=?" );
[6c3744e]975 } // if
[01aeade]976 UntypedExpr *addAssign = new UntypedExpr( opExpr );
977 if ( AddressExpr *address = dynamic_cast< AddressExpr *>( appExpr->get_args().front() ) ) {
978 addAssign->get_args().push_back( address->get_arg() );
979 } else {
980 addAssign->get_args().push_back( appExpr->get_args().front() );
[6c3744e]981 } // if
[adc6781]982 addAssign->get_args().push_back( new NameExpr( sizeofName( mangleType( polyType ) ) ) );
[906e24d]983 addAssign->set_result( appExpr->get_result()->clone() );
[01aeade]984 if ( appExpr->get_env() ) {
985 addAssign->set_env( appExpr->get_env() );
[6c3744e]986 appExpr->set_env( 0 );
987 } // if
[01aeade]988 appExpr->get_args().clear();
989 delete appExpr;
990 return addAssign;
991 }
992
993 Expression *Pass1::handleIntrinsics( ApplicationExpr *appExpr ) {
[20cba76]994 if ( VariableExpr *varExpr = dynamic_cast< VariableExpr *>( appExpr->function ) ) {
995 if ( varExpr->var->linkage == LinkageSpec::Intrinsic ) {
996 if ( varExpr->var->name == "?[?]" ) {
[d29fa5f]997 assert( appExpr->result );
[01aeade]998 assert( appExpr->get_args().size() == 2 );
[20cba76]999 Type *baseType1 = isPolyPtr( appExpr->args.front()->result, scopeTyVars, env );
1000 Type *baseType2 = isPolyPtr( appExpr->args.back()->result, scopeTyVars, env );
[ae63a18]1001 assert( ! baseType1 || ! baseType2 ); // the arguments cannot both be polymorphic pointers
[01aeade]1002 UntypedExpr *ret = 0;
[ae63a18]1003 if ( baseType1 || baseType2 ) { // one of the arguments is a polymorphic pointer
[01aeade]1004 ret = new UntypedExpr( new NameExpr( "?+?" ) );
1005 } // if
[ffad73a]1006 if ( baseType1 ) {
[01aeade]1007 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1008 multiply->get_args().push_back( appExpr->get_args().back() );
[adc6781]1009 multiply->get_args().push_back( new SizeofExpr( baseType1->clone() ) );
[01aeade]1010 ret->get_args().push_back( appExpr->get_args().front() );
1011 ret->get_args().push_back( multiply );
[ffad73a]1012 } else if ( baseType2 ) {
[01aeade]1013 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1014 multiply->get_args().push_back( appExpr->get_args().front() );
[adc6781]1015 multiply->get_args().push_back( new SizeofExpr( baseType2->clone() ) );
[01aeade]1016 ret->get_args().push_back( multiply );
1017 ret->get_args().push_back( appExpr->get_args().back() );
1018 } // if
[ffad73a]1019 if ( baseType1 || baseType2 ) {
[83794e1]1020 delete ret->get_result();
1021 ret->set_result( appExpr->get_result()->clone() );
[01aeade]1022 if ( appExpr->get_env() ) {
1023 ret->set_env( appExpr->get_env() );
1024 appExpr->set_env( 0 );
1025 } // if
1026 appExpr->get_args().clear();
1027 delete appExpr;
1028 return ret;
1029 } // if
1030 } else if ( varExpr->get_var()->get_name() == "*?" ) {
[d29fa5f]1031 assert( appExpr->result );
[01aeade]1032 assert( ! appExpr->get_args().empty() );
[83794e1]1033 if ( isPolyType( appExpr->get_result(), scopeTyVars, env ) ) {
[0a81c3f]1034 // remove dereference from polymorphic types since they are boxed.
[01aeade]1035 Expression *ret = appExpr->get_args().front();
[83794e1]1036 // fix expr type to remove pointer
[906e24d]1037 delete ret->get_result();
[83794e1]1038 ret->set_result( appExpr->get_result()->clone() );
[01aeade]1039 if ( appExpr->get_env() ) {
1040 ret->set_env( appExpr->get_env() );
1041 appExpr->set_env( 0 );
1042 } // if
1043 appExpr->get_args().clear();
1044 delete appExpr;
1045 return ret;
1046 } // if
1047 } else if ( varExpr->get_var()->get_name() == "?++" || varExpr->get_var()->get_name() == "?--" ) {
[d29fa5f]1048 assert( appExpr->result );
[01aeade]1049 assert( appExpr->get_args().size() == 1 );
[906e24d]1050 if ( Type *baseType = isPolyPtr( appExpr->get_result(), scopeTyVars, env ) ) {
1051 Type *tempType = appExpr->get_result()->clone();
[01aeade]1052 if ( env ) {
1053 env->apply( tempType );
1054 } // if
1055 ObjectDecl *newObj = makeTemporary( tempType );
1056 VariableExpr *tempExpr = new VariableExpr( newObj );
1057 UntypedExpr *assignExpr = new UntypedExpr( new NameExpr( "?=?" ) );
1058 assignExpr->get_args().push_back( tempExpr->clone() );
1059 if ( AddressExpr *address = dynamic_cast< AddressExpr *>( appExpr->get_args().front() ) ) {
1060 assignExpr->get_args().push_back( address->get_arg()->clone() );
1061 } else {
1062 assignExpr->get_args().push_back( appExpr->get_args().front()->clone() );
1063 } // if
[ffad73a]1064 CommaExpr *firstComma = new CommaExpr( assignExpr, makeIncrDecrExpr( appExpr, baseType, varExpr->get_var()->get_name() == "?++" ) );
[01aeade]1065 return new CommaExpr( firstComma, tempExpr );
1066 } // if
1067 } else if ( varExpr->get_var()->get_name() == "++?" || varExpr->get_var()->get_name() == "--?" ) {
[d29fa5f]1068 assert( appExpr->result );
[01aeade]1069 assert( appExpr->get_args().size() == 1 );
[906e24d]1070 if ( Type *baseType = isPolyPtr( appExpr->get_result(), scopeTyVars, env ) ) {
[ffad73a]1071 return makeIncrDecrExpr( appExpr, baseType, varExpr->get_var()->get_name() == "++?" );
[01aeade]1072 } // if
1073 } else if ( varExpr->get_var()->get_name() == "?+?" || varExpr->get_var()->get_name() == "?-?" ) {
[d29fa5f]1074 assert( appExpr->result );
[01aeade]1075 assert( appExpr->get_args().size() == 2 );
[906e24d]1076 Type *baseType1 = isPolyPtr( appExpr->get_args().front()->get_result(), scopeTyVars, env );
1077 Type *baseType2 = isPolyPtr( appExpr->get_args().back()->get_result(), scopeTyVars, env );
[ffad73a]1078 if ( baseType1 && baseType2 ) {
[01aeade]1079 UntypedExpr *divide = new UntypedExpr( new NameExpr( "?/?" ) );
1080 divide->get_args().push_back( appExpr );
[adc6781]1081 divide->get_args().push_back( new SizeofExpr( baseType1->clone() ) );
[906e24d]1082 divide->set_result( appExpr->get_result()->clone() );
[01aeade]1083 if ( appExpr->get_env() ) {
1084 divide->set_env( appExpr->get_env() );
1085 appExpr->set_env( 0 );
1086 } // if
1087 return divide;
[ffad73a]1088 } else if ( baseType1 ) {
[01aeade]1089 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1090 multiply->get_args().push_back( appExpr->get_args().back() );
[adc6781]1091 multiply->get_args().push_back( new SizeofExpr( baseType1->clone() ) );
[01aeade]1092 appExpr->get_args().back() = multiply;
[ffad73a]1093 } else if ( baseType2 ) {
[01aeade]1094 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1095 multiply->get_args().push_back( appExpr->get_args().front() );
[adc6781]1096 multiply->get_args().push_back( new SizeofExpr( baseType2->clone() ) );
[01aeade]1097 appExpr->get_args().front() = multiply;
1098 } // if
1099 } else if ( varExpr->get_var()->get_name() == "?+=?" || varExpr->get_var()->get_name() == "?-=?" ) {
[d29fa5f]1100 assert( appExpr->result );
[01aeade]1101 assert( appExpr->get_args().size() == 2 );
[906e24d]1102 Type *baseType = isPolyPtr( appExpr->get_result(), scopeTyVars, env );
[ffad73a]1103 if ( baseType ) {
[01aeade]1104 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1105 multiply->get_args().push_back( appExpr->get_args().back() );
[adc6781]1106 multiply->get_args().push_back( new SizeofExpr( baseType->clone() ) );
[01aeade]1107 appExpr->get_args().back() = multiply;
1108 } // if
1109 } // if
1110 return appExpr;
1111 } // if
[6c3744e]1112 } // if
[01aeade]1113 return 0;
1114 }
[6c3744e]1115
[201182a]1116 Expression *Pass1::postmutate( ApplicationExpr *appExpr ) {
[2a7b3ca]1117 // std::cerr << "mutate appExpr: " << InitTweak::getFunctionName( appExpr ) << std::endl;
[e56cfdb0]1118 // for ( TyVarMap::iterator i = scopeTyVars.begin(); i != scopeTyVars.end(); ++i ) {
1119 // std::cerr << i->first << " ";
1120 // }
1121 // std::cerr << "\n";
[ae63a18]1122
[201182a]1123 assert( appExpr->function->result );
1124 FunctionType * function = getFunctionType( appExpr->function->result );
1125 assertf( function, "ApplicationExpr has non-function type: %s", toString( appExpr->function->result ).c_str() );
[ae63a18]1126
[01aeade]1127 if ( Expression *newExpr = handleIntrinsics( appExpr ) ) {
1128 return newExpr;
1129 } // if
[ae63a18]1130
[01aeade]1131 Expression *ret = appExpr;
[ae63a18]1132
[01aeade]1133 std::list< Expression *>::iterator arg = appExpr->get_args().begin();
1134 std::list< Expression *>::iterator paramBegin = appExpr->get_args().begin();
[ae63a18]1135
[2c57025]1136 TyVarMap exprTyVars( TypeDecl::Data{} );
[5802a4f]1137 makeTyVarMap( function, exprTyVars ); // xxx - should this take into account the variables already bound in scopeTyVars (i.e. remove them from exprTyVars?)
[3bb195cb]1138 ReferenceToType *dynRetType = isDynRet( function, exprTyVars );
[5c52b06]1139
[2a7b3ca]1140 // std::cerr << function << std::endl;
1141 // std::cerr << "scopeTyVars: ";
1142 // printTyVarMap( std::cerr, scopeTyVars );
1143 // std::cerr << "exprTyVars: ";
1144 // printTyVarMap( std::cerr, exprTyVars );
1145 // std::cerr << "env: " << *env << std::endl;
1146 // std::cerr << needsAdapter( function, scopeTyVars ) << ! needsAdapter( function, exprTyVars) << std::endl;
1147
[b940dc71]1148 // NOTE: addDynRetParam needs to know the actual (generated) return type so it can make a temp variable, so pass the result type from the appExpr
1149 // passTypeVars needs to know the program-text return type (i.e. the distinction between _conc_T30 and T3(int))
1150 // concRetType may not be a good name in one or both of these places. A more appropriate name change is welcome.
[3bb195cb]1151 if ( dynRetType ) {
[2a7b3ca]1152 // std::cerr << "dynRetType: " << dynRetType << std::endl;
[b940dc71]1153 Type *concRetType = appExpr->get_result()->isVoid() ? nullptr : appExpr->get_result();
[d7dc824]1154 ret = addDynRetParam( appExpr, concRetType, arg ); // xxx - used to use dynRetType instead of concRetType
[5802a4f]1155 } else if ( needsAdapter( function, scopeTyVars ) && ! needsAdapter( function, exprTyVars) ) { // xxx - exprTyVars is used above...?
1156 // xxx - the ! needsAdapter check may be incorrect. It seems there is some situation where an adapter is applied where it shouldn't be, and this fixes it for some cases. More investigation is needed.
1157
[e56cfdb0]1158 // std::cerr << "needs adapter: ";
[2e3a379]1159 // printTyVarMap( std::cerr, scopeTyVars );
1160 // std::cerr << *env << std::endl;
[01aeade]1161 // change the application so it calls the adapter rather than the passed function
1162 ret = applyAdapter( appExpr, function, arg, scopeTyVars );
1163 } // if
1164 arg = appExpr->get_args().begin();
[ae63a18]1165
[b940dc71]1166 Type *concRetType = replaceWithConcrete( appExpr, dynRetType );
[5802a4f]1167 passTypeVars( appExpr, concRetType, arg, exprTyVars ); // xxx - used to use dynRetType instead of concRetType; this changed so that the correct type paramaters are passed for return types (it should be the concrete type's parameters, not the formal type's)
[01aeade]1168 addInferredParams( appExpr, function, arg, exprTyVars );
[51b73452]1169
[01aeade]1170 arg = paramBegin;
[ae63a18]1171
[01aeade]1172 boxParams( appExpr, function, arg, exprTyVars );
1173 passAdapters( appExpr, function, exprTyVars );
[6c3744e]1174
[01aeade]1175 return ret;
1176 }
[6c3744e]1177
[201182a]1178 Expression * Pass1::postmutate( UntypedExpr *expr ) {
1179 if ( expr->result && isPolyType( expr->result, scopeTyVars, env ) ) {
1180 if ( NameExpr *name = dynamic_cast< NameExpr *>( expr->function ) ) {
[2097cd4]1181 if ( name->name == "*?" ) {
[201182a]1182 Expression *ret = expr->args.front();
1183 expr->args.clear();
[01aeade]1184 delete expr;
[201182a]1185 return ret;
[01aeade]1186 } // if
1187 } // if
1188 } // if
[201182a]1189 return expr;
[01aeade]1190 }
[6c3744e]1191
[201182a]1192 void Pass1::premutate( AddressExpr * ) { visit_children = false; }
1193 Expression * Pass1::postmutate( AddressExpr * addrExpr ) {
[2097cd4]1194 assert( addrExpr->arg->result && ! addrExpr->arg->result->isVoid() );
[cf16f94]1195
1196 bool needs = false;
[2097cd4]1197 if ( UntypedExpr *expr = dynamic_cast< UntypedExpr *>( addrExpr->arg ) ) {
1198 if ( expr->result && isPolyType( expr->result, scopeTyVars, env ) ) {
1199 if ( NameExpr *name = dynamic_cast< NameExpr *>( expr->function ) ) {
1200 if ( name->name == "*?" ) {
1201 if ( ApplicationExpr * appExpr = dynamic_cast< ApplicationExpr * >( expr->args.front() ) ) {
1202 assert( appExpr->function->result );
1203 FunctionType *function = getFunctionType( appExpr->function->result );
[83794e1]1204 assert( function );
[cf16f94]1205 needs = needsAdapter( function, scopeTyVars );
1206 } // if
1207 } // if
1208 } // if
1209 } // if
1210 } // if
[fea7ca7]1211 // isPolyType check needs to happen before mutating addrExpr arg, so pull it forward
1212 // out of the if condition.
[2097cd4]1213 addrExpr->arg = addrExpr->arg->acceptMutator( *visitor );
[d335627]1214 // ... but must happen after mutate, since argument might change (e.g. intrinsic *?, ?[?]) - re-evaluate above comment
[2097cd4]1215 bool polytype = isPolyType( addrExpr->arg->result, scopeTyVars, env );
[fea7ca7]1216 if ( polytype || needs ) {
[2097cd4]1217 Expression *ret = addrExpr->arg;
1218 delete ret->result;
1219 ret->result = addrExpr->result->clone();
1220 addrExpr->arg = nullptr;
[01aeade]1221 delete addrExpr;
1222 return ret;
1223 } else {
1224 return addrExpr;
1225 } // if
1226 }
[6c3744e]1227
[201182a]1228 void Pass1::premutate( ReturnStmt *returnStmt ) {
1229 if ( retval && returnStmt->expr ) {
1230 assert( returnStmt->expr->result && ! returnStmt->expr->result->isVoid() );
1231 delete returnStmt->expr;
1232 returnStmt->expr = nullptr;
[01aeade]1233 } // if
1234 }
[6c3744e]1235
[201182a]1236 void Pass1::premutate( PointerType *pointerType ) {
1237 GuardScope( scopeTyVars );
[01aeade]1238 makeTyVarMap( pointerType, scopeTyVars );
1239 }
[6c3744e]1240
[201182a]1241 void Pass1::premutate( FunctionType *functionType ) {
1242 GuardScope( scopeTyVars );
[01aeade]1243 makeTyVarMap( functionType, scopeTyVars );
1244 }
[51b73452]1245
[201182a]1246 void Pass1::beginScope() {
[6635c74]1247 adapters.beginScope();
[01aeade]1248 }
[b1a6d6b]1249
[201182a]1250 void Pass1::endScope() {
[6635c74]1251 adapters.endScope();
[01aeade]1252 }
[51b73452]1253
1254////////////////////////////////////////// Pass2 ////////////////////////////////////////////////////
1255
[01aeade]1256 void Pass2::addAdapters( FunctionType *functionType ) {
[2097cd4]1257 std::list< DeclarationWithType *> &paramList = functionType->parameters;
[01aeade]1258 std::list< FunctionType *> functions;
1259 for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
1260 Type *orig = (*arg)->get_type();
1261 findAndReplaceFunction( orig, functions, scopeTyVars, needsAdapter );
1262 (*arg)->set_type( orig );
1263 }
1264 std::set< std::string > adaptersDone;
1265 for ( std::list< FunctionType *>::iterator funType = functions.begin(); funType != functions.end(); ++funType ) {
[bdf1954]1266 std::string mangleName = mangleAdapterName( *funType, scopeTyVars );
[01aeade]1267 if ( adaptersDone.find( mangleName ) == adaptersDone.end() ) {
1268 std::string adapterName = makeAdapterName( mangleName );
[83794e1]1269 // adapter may not be used in body, pass along with unused attribute.
1270 paramList.push_front( new ObjectDecl( adapterName, Type::StorageClasses(), LinkageSpec::C, 0, new PointerType( Type::Qualifiers(), makeAdapterType( *funType, scopeTyVars ) ), 0, { new Attribute( "unused" ) } ) );
[01aeade]1271 adaptersDone.insert( adaptersDone.begin(), mangleName );
1272 }
1273 }
[5f6c42c]1274// deleteAll( functions );
[01aeade]1275 }
[6c3744e]1276
[a31b384]1277 DeclarationWithType * Pass2::postmutate( FunctionDecl *functionDecl ) {
[2097cd4]1278 FunctionType * ftype = functionDecl->type;
1279 if ( ! ftype->returnVals.empty() && functionDecl->statements ) {
1280 if ( ! isPrefix( functionDecl->name, "_thunk" ) && ! isPrefix( functionDecl->name, "_adapter" ) ) { // xxx - remove check for prefix once thunks properly use ctor/dtors
1281 assert( ftype->returnVals.size() == 1 );
1282 DeclarationWithType * retval = ftype->returnVals.front();
1283 if ( retval->name == "" ) {
1284 retval->name = "_retval";
[cce9429]1285 }
[2097cd4]1286 functionDecl->statements->kids.push_front( new DeclStmt( retval ) );
[cce9429]1287 DeclarationWithType * newRet = retval->clone(); // for ownership purposes
[2097cd4]1288 ftype->returnVals.front() = newRet;
[cce9429]1289 }
1290 }
[064cb18]1291 // errors should have been caught by this point, remove initializers from parameters to allow correct codegen of default arguments
[2097cd4]1292 for ( Declaration * param : functionDecl->type->parameters ) {
[064cb18]1293 if ( ObjectDecl * obj = dynamic_cast< ObjectDecl * >( param ) ) {
[2097cd4]1294 delete obj->init;
1295 obj->init = nullptr;
[064cb18]1296 }
1297 }
[cce9429]1298 return functionDecl;
[01aeade]1299 }
[6c3744e]1300
[a31b384]1301 void Pass2::premutate( StructDecl * ) {
[dd0c97b]1302 // prevent tyVars from leaking into containing scope
[a31b384]1303 GuardScope( scopeTyVars );
[dd0c97b]1304 }
1305
[a31b384]1306 void Pass2::premutate( UnionDecl * ) {
1307 // prevent tyVars from leaking into containing scope
1308 GuardScope( scopeTyVars );
[dd0c97b]1309 }
1310
[a31b384]1311 void Pass2::premutate( TraitDecl * ) {
1312 // prevent tyVars from leaking into containing scope
1313 GuardScope( scopeTyVars );
[9b18044]1314 }
1315
[a31b384]1316 void Pass2::premutate( TypeDecl *typeDecl ) {
[2c57025]1317 addToTyVarMap( typeDecl, scopeTyVars );
[01aeade]1318 }
[6c3744e]1319
[a31b384]1320 void Pass2::premutate( PointerType *pointerType ) {
1321 GuardScope( scopeTyVars );
[01aeade]1322 makeTyVarMap( pointerType, scopeTyVars );
1323 }
[6c3744e]1324
[a31b384]1325 void Pass2::premutate( FunctionType *funcType ) {
1326 GuardScope( scopeTyVars );
[01aeade]1327 makeTyVarMap( funcType, scopeTyVars );
[7754cde]1328
1329 // move polymorphic return type to parameter list
[3bb195cb]1330 if ( isDynRet( funcType ) ) {
[e3e16bc]1331 ObjectDecl *ret = strict_dynamic_cast< ObjectDecl* >( funcType->get_returnVals().front() );
[01aeade]1332 ret->set_type( new PointerType( Type::Qualifiers(), ret->get_type() ) );
1333 funcType->get_parameters().push_front( ret );
1334 funcType->get_returnVals().pop_front();
[d9fa60a]1335 ret->set_init( nullptr ); // xxx - memory leak?
[01aeade]1336 }
[7754cde]1337
1338 // add size/align and assertions for type parameters to parameter list
[01aeade]1339 std::list< DeclarationWithType *>::iterator last = funcType->get_parameters().begin();
1340 std::list< DeclarationWithType *> inferredParams;
[83794e1]1341 // size/align/offset parameters may not be used in body, pass along with unused attribute.
1342 ObjectDecl newObj( "", Type::StorageClasses(), LinkageSpec::C, 0, new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ), 0,
1343 { new Attribute( "unused" ) } );
[68fe077a]1344 ObjectDecl newPtr( "", Type::StorageClasses(), LinkageSpec::C, 0,
[05d47278]1345 new PointerType( Type::Qualifiers(), new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ) ), 0 );
[8c49c0e]1346 for ( Type::ForallList::const_iterator tyParm = funcType->get_forall().begin(); tyParm != funcType->get_forall().end(); ++tyParm ) {
[db0b3ce]1347 ObjectDecl *sizeParm, *alignParm;
1348 // add all size and alignment parameters to parameter list
[2c57025]1349 if ( (*tyParm)->isComplete() ) {
[78dd0da]1350 TypeInstType parmType( Type::Qualifiers(), (*tyParm)->get_name(), *tyParm );
[adc6781]1351 std::string parmName = mangleType( &parmType );
[ae63a18]1352
[78dd0da]1353 sizeParm = newObj.clone();
[adc6781]1354 sizeParm->set_name( sizeofName( parmName ) );
[db0b3ce]1355 last = funcType->get_parameters().insert( last, sizeParm );
1356 ++last;
[78dd0da]1357
1358 alignParm = newObj.clone();
[adc6781]1359 alignParm->set_name( alignofName( parmName ) );
[db0b3ce]1360 last = funcType->get_parameters().insert( last, alignParm );
[01aeade]1361 ++last;
1362 }
[e56cfdb0]1363 // move all assertions into parameter list
[01aeade]1364 for ( std::list< DeclarationWithType *>::iterator assert = (*tyParm)->get_assertions().begin(); assert != (*tyParm)->get_assertions().end(); ++assert ) {
[83794e1]1365 // assertion parameters may not be used in body, pass along with unused attribute.
1366 (*assert)->get_attributes().push_back( new Attribute( "unused" ) );
[01aeade]1367 inferredParams.push_back( *assert );
1368 }
1369 (*tyParm)->get_assertions().clear();
1370 }
[7754cde]1371
[5c52b06]1372 // add size/align for generic parameter types to parameter list
[b18b0b5]1373 std::set< std::string > seenTypes; // sizeofName for generic types we've seen
[7754cde]1374 for ( std::list< DeclarationWithType* >::const_iterator fnParm = last; fnParm != funcType->get_parameters().end(); ++fnParm ) {
[4b8f918]1375 Type *polyType = isPolyType( (*fnParm)->get_type(), scopeTyVars );
1376 if ( polyType && ! dynamic_cast< TypeInstType* >( polyType ) ) {
1377 std::string typeName = mangleType( polyType );
[adc6781]1378 if ( seenTypes.count( typeName ) ) continue;
[ae63a18]1379
[05d47278]1380 ObjectDecl *sizeParm, *alignParm, *offsetParm;
[7754cde]1381 sizeParm = newObj.clone();
[adc6781]1382 sizeParm->set_name( sizeofName( typeName ) );
[7754cde]1383 last = funcType->get_parameters().insert( last, sizeParm );
1384 ++last;
1385
1386 alignParm = newObj.clone();
[adc6781]1387 alignParm->set_name( alignofName( typeName ) );
[7754cde]1388 last = funcType->get_parameters().insert( last, alignParm );
1389 ++last;
1390
[4b8f918]1391 if ( StructInstType *polyBaseStruct = dynamic_cast< StructInstType* >( polyType ) ) {
[89173242]1392 // NOTE zero-length arrays are illegal in C, so empty structs have no offset array
1393 if ( ! polyBaseStruct->get_baseStruct()->get_members().empty() ) {
1394 offsetParm = newPtr.clone();
[adc6781]1395 offsetParm->set_name( offsetofName( typeName ) );
[89173242]1396 last = funcType->get_parameters().insert( last, offsetParm );
1397 ++last;
1398 }
[05d47278]1399 }
[adc6781]1400 seenTypes.insert( typeName );
[7754cde]1401 }
1402 }
1403
1404 // splice assertion parameters into parameter list
[01aeade]1405 funcType->get_parameters().splice( last, inferredParams );
1406 addAdapters( funcType );
1407 }
[51b73452]1408
[4b8f918]1409////////////////////////////////////////// PolyGenericCalculator ////////////////////////////////////////////////////
[51b73452]1410
[a0ad7dc]1411 PolyGenericCalculator::PolyGenericCalculator()
[201182a]1412 : knownLayouts(), knownOffsets(), bufNamer( "_buf" ) {}
[a0ad7dc]1413
[aa19ccf]1414 void PolyGenericCalculator::beginTypeScope( Type *ty ) {
[a0c7dc36]1415 GuardScope( scopeTyVars );
[aa19ccf]1416 makeTyVarMap( ty, scopeTyVars );
1417 }
1418
[a0c7dc36]1419 void PolyGenericCalculator::beginGenericScope() {
1420 GuardScope( *this );
[01aeade]1421 }
[6c3744e]1422
[a0c7dc36]1423 void PolyGenericCalculator::premutate( ObjectDecl *objectDecl ) {
1424 beginTypeScope( objectDecl->get_type() );
[01aeade]1425 }
[6c3744e]1426
[a0c7dc36]1427 void PolyGenericCalculator::premutate( FunctionDecl *functionDecl ) {
1428 beginGenericScope();
[1ba88a0]1429
[a0c7dc36]1430 beginTypeScope( functionDecl->get_functionType() );
[01aeade]1431 }
[6c3744e]1432
[a0c7dc36]1433 void PolyGenericCalculator::premutate( TypedefDecl *typedefDecl ) {
[8dceeb7]1434 assert(false);
[a0c7dc36]1435 beginTypeScope( typedefDecl->get_base() );
[01aeade]1436 }
[6c3744e]1437
[a0c7dc36]1438 void PolyGenericCalculator::premutate( TypeDecl * typeDecl ) {
[2c57025]1439 addToTyVarMap( typeDecl, scopeTyVars );
[01aeade]1440 }
[51b73452]1441
[a0c7dc36]1442 Declaration * PolyGenericCalculator::postmutate( TypeDecl *typeDecl ) {
1443 if ( Type * base = typeDecl->base ) {
1444 // add size/align variables for opaque type declarations
1445 TypeInstType inst( Type::Qualifiers(), typeDecl->name, typeDecl );
1446 std::string typeName = mangleType( &inst );
1447 Type *layoutType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
[ae63a18]1448
[a0c7dc36]1449 ObjectDecl * sizeDecl = ObjectDecl::newObject( sizeofName( typeName ), layoutType, new SingleInit( new SizeofExpr( base->clone() ) ) );
1450 ObjectDecl * alignDecl = ObjectDecl::newObject( alignofName( typeName ), layoutType->clone(), new SingleInit( new AlignofExpr( base->clone() ) ) );
[ae63a18]1451
[a0c7dc36]1452 // ensure that the initializing sizeof/alignof exprs are properly mutated
1453 sizeDecl->acceptMutator( *visitor );
1454 alignDecl->acceptMutator( *visitor );
1455
1456 // can't use makeVar, because it inserts into stmtsToAdd and TypeDecls can occur at global scope
1457 declsToAddAfter.push_back( alignDecl );
1458 // replace with sizeDecl
1459 return sizeDecl;
1460 }
1461 return typeDecl;
1462 }
1463
1464 void PolyGenericCalculator::premutate( PointerType *pointerType ) {
1465 beginTypeScope( pointerType );
[01aeade]1466 }
[6c3744e]1467
[a0c7dc36]1468 void PolyGenericCalculator::premutate( FunctionType *funcType ) {
[aa19ccf]1469 beginTypeScope( funcType );
[ae63a18]1470
[8a34677]1471 // make sure that any type information passed into the function is accounted for
1472 for ( std::list< DeclarationWithType* >::const_iterator fnParm = funcType->get_parameters().begin(); fnParm != funcType->get_parameters().end(); ++fnParm ) {
1473 // condition here duplicates that in Pass2::mutate( FunctionType* )
[4b8f918]1474 Type *polyType = isPolyType( (*fnParm)->get_type(), scopeTyVars );
1475 if ( polyType && ! dynamic_cast< TypeInstType* >( polyType ) ) {
1476 knownLayouts.insert( mangleType( polyType ) );
[8a34677]1477 }
1478 }
[6c3744e]1479 }
[51b73452]1480
[8dceeb7]1481 /// converts polymorphic type T into a suitable monomorphic representation, currently: __attribute__((aligned(8)) char[size_T]
1482 Type * polyToMonoType( Type * declType ) {
1483 Type * charType = new BasicType( Type::Qualifiers(), BasicType::Kind::Char);
1484 Expression * size = new NameExpr( sizeofName( mangleType(declType) ) );
1485 Attribute * aligned = new Attribute( "aligned", std::list<Expression*>{ new ConstantExpr( Constant::from_int(8) ) } );
1486 return new ArrayType( Type::Qualifiers(), charType, size,
1487 true, false, std::list<Attribute *>{ aligned } );
1488 }
1489
1490 void PolyGenericCalculator::mutateMembers( AggregateDecl * aggrDecl ) {
1491 std::set< std::string > genericParams;
1492 for ( TypeDecl * td : aggrDecl->parameters ) {
1493 genericParams.insert( td->name );
1494 }
1495 for ( Declaration * decl : aggrDecl->members ) {
1496 if ( ObjectDecl * field = dynamic_cast< ObjectDecl * >( decl ) ) {
1497 Type * ty = replaceTypeInst( field->type, env );
1498 if ( TypeInstType *typeInst = dynamic_cast< TypeInstType* >( ty ) ) {
1499 // do not try to monomorphize generic parameters
1500 if ( scopeTyVars.find( typeInst->get_name() ) != scopeTyVars.end() && ! genericParams.count( typeInst->name ) ) {
1501 // polymorphic aggregate members should be converted into monomorphic members.
1502 // Using char[size_T] here respects the expected sizing rules of an aggregate type.
1503 Type * newType = polyToMonoType( field->type );
1504 delete field->type;
1505 field->type = newType;
1506 }
1507 }
1508 }
1509 }
1510 }
1511
1512 void PolyGenericCalculator::premutate( StructDecl * structDecl ) {
1513 mutateMembers( structDecl );
1514 }
1515
1516 void PolyGenericCalculator::premutate( UnionDecl * unionDecl ) {
1517 mutateMembers( unionDecl );
1518 }
1519
[a0c7dc36]1520 void PolyGenericCalculator::premutate( DeclStmt *declStmt ) {
[01aeade]1521 if ( ObjectDecl *objectDecl = dynamic_cast< ObjectDecl *>( declStmt->get_decl() ) ) {
[8a34677]1522 if ( findGeneric( objectDecl->get_type() ) ) {
[a0ad7dc]1523 // change initialization of a polymorphic value object to allocate via a VLA
1524 // (alloca was previously used, but can't be safely used in loops)
[8dceeb7]1525 ObjectDecl *newBuf = ObjectDecl::newObject( bufNamer.newName(), polyToMonoType( objectDecl->type ), nullptr );
[ba3706f]1526 stmtsToAddBefore.push_back( new DeclStmt( newBuf ) );
[e01559c]1527
1528 delete objectDecl->get_init();
[cccc534]1529 objectDecl->set_init( new SingleInit( new VariableExpr( newBuf ) ) );
[01aeade]1530 }
1531 }
1532 }
[05d47278]1533
[2a4b088]1534 /// Finds the member in the base list that matches the given declaration; returns its index, or -1 if not present
1535 long findMember( DeclarationWithType *memberDecl, std::list< Declaration* > &baseDecls ) {
1536 long i = 0;
1537 for(std::list< Declaration* >::const_iterator decl = baseDecls.begin(); decl != baseDecls.end(); ++decl, ++i ) {
1538 if ( memberDecl->get_name() != (*decl)->get_name() ) continue;
1539
1540 if ( DeclarationWithType *declWithType = dynamic_cast< DeclarationWithType* >( *decl ) ) {
[bed4d37c]1541 if ( memberDecl->get_mangleName().empty() || declWithType->get_mangleName().empty()
1542 || memberDecl->get_mangleName() == declWithType->get_mangleName() ) return i;
[2a4b088]1543 else continue;
1544 } else return i;
1545 }
1546 return -1;
1547 }
1548
1549 /// Returns an index expression into the offset array for a type
1550 Expression *makeOffsetIndex( Type *objectType, long i ) {
[d56e5bc]1551 ConstantExpr *fieldIndex = new ConstantExpr( Constant::from_ulong( i ) );
[2a4b088]1552 UntypedExpr *fieldOffset = new UntypedExpr( new NameExpr( "?[?]" ) );
[adc6781]1553 fieldOffset->get_args().push_back( new NameExpr( offsetofName( mangleType( objectType ) ) ) );
[2a4b088]1554 fieldOffset->get_args().push_back( fieldIndex );
1555 return fieldOffset;
1556 }
1557
[a0c7dc36]1558 Expression *PolyGenericCalculator::postmutate( MemberExpr *memberExpr ) {
[05d47278]1559 // only mutate member expressions for polymorphic types
[8488c715]1560 int tyDepth;
[20cba76]1561 Type *objectType = hasPolyBase( memberExpr->aggregate->result, scopeTyVars, &tyDepth );
[05d47278]1562 if ( ! objectType ) return memberExpr;
[8a34677]1563 findGeneric( objectType ); // ensure layout for this type is available
[05d47278]1564
[ea5daeb]1565 // replace member expression with dynamically-computed layout expression
[20cba76]1566 Expression *newMemberExpr = nullptr;
[05d47278]1567 if ( StructInstType *structType = dynamic_cast< StructInstType* >( objectType ) ) {
[2a4b088]1568 // look up offset index
[20cba76]1569 long i = findMember( memberExpr->member, structType->baseStruct->members );
[2a4b088]1570 if ( i == -1 ) return memberExpr;
[05d47278]1571
[2a4b088]1572 // replace member expression with pointer to base plus offset
1573 UntypedExpr *fieldLoc = new UntypedExpr( new NameExpr( "?+?" ) );
[20cba76]1574 Expression * aggr = memberExpr->aggregate->clone();
1575 delete aggr->env; // xxx - there's a problem with keeping the env for some reason, so for now just get rid of it
1576 aggr->env = nullptr;
[5802a4f]1577 fieldLoc->get_args().push_back( aggr );
[2a4b088]1578 fieldLoc->get_args().push_back( makeOffsetIndex( objectType, i ) );
[20cba76]1579 fieldLoc->set_result( memberExpr->result->clone() );
[4318107]1580 newMemberExpr = fieldLoc;
[98735ef]1581 } else if ( dynamic_cast< UnionInstType* >( objectType ) ) {
[c10ee66]1582 // union members are all at offset zero, so just use the aggregate expr
[20cba76]1583 Expression * aggr = memberExpr->aggregate->clone();
1584 delete aggr->env; // xxx - there's a problem with keeping the env for some reason, so for now just get rid of it
1585 aggr->env= nullptr;
[c10ee66]1586 newMemberExpr = aggr;
[20cba76]1587 newMemberExpr->result = memberExpr->result->clone();
[2a4b088]1588 } else return memberExpr;
[4318107]1589 assert( newMemberExpr );
1590
[661214c]1591 // Must apply the generic substitution to the member type to handle cases where the member is a generic parameter substituted by a known concrete type, e.g.
1592 // forall(otype T) struct Box { T x; }
1593 // forall(otype T) f() {
1594 // Box(T *) b; b.x;
1595 // }
1596 // TODO: memberExpr->result should be exactly memberExpr->member->get_type() after substitution, so it doesn't seem like it should be necessary to apply the substitution manually. For some reason this is not currently the case. This requires more investigation.
1597 Type *memberType = memberExpr->member->get_type()->clone();
1598 TypeSubstitution sub = objectType->genericSubstitution();
1599 sub.apply( memberType );
[4067aa8]1600 if ( ! isPolyType( memberType, scopeTyVars ) ) {
1601 // 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
1602 CastExpr *ptrCastExpr = new CastExpr( newMemberExpr, new PointerType( Type::Qualifiers(), memberType->clone() ) );
[c10ee66]1603 UntypedExpr *derefExpr = UntypedExpr::createDeref( ptrCastExpr );
[4318107]1604 newMemberExpr = derefExpr;
1605 }
1606
[661214c]1607 delete memberType;
[4318107]1608 delete memberExpr;
1609 return newMemberExpr;
[2a4b088]1610 }
[05d47278]1611
[02c816fc]1612 void PolyGenericCalculator::premutate( AddressExpr * addrExpr ) {
1613 GuardValue( addrMember );
1614 // is the argument a MemberExpr before mutating?
1615 addrMember = dynamic_cast< MemberExpr * >( addrExpr->arg );
1616 }
1617
1618 Expression * PolyGenericCalculator::postmutate( AddressExpr * addrExpr ) {
1619 if ( addrMember && addrMember != addrExpr->arg ) {
1620 // arg was a MemberExpr and has been mutated
1621 if ( UntypedExpr * untyped = dynamic_cast< UntypedExpr * >( addrExpr->arg ) ) {
1622 if ( InitTweak::getFunctionName( untyped ) == "?+?" ) {
1623 // MemberExpr was converted to pointer+offset, and it is not valid C to take the address of an addition, so strip the address-of
1624 // TODO: should addrExpr->arg->result be changed to addrExpr->result?
1625 Expression * ret = addrExpr->arg;
1626 addrExpr->arg = nullptr;
1627 std::swap( addrExpr->env, ret->env );
1628 delete addrExpr;
1629 return ret;
1630 }
1631 }
1632 }
1633 return addrExpr;
1634 }
1635
[8a34677]1636 ObjectDecl *PolyGenericCalculator::makeVar( const std::string &name, Type *type, Initializer *init ) {
[20cba76]1637 ObjectDecl *newObj = new ObjectDecl( name, Type::StorageClasses(), LinkageSpec::C, nullptr, type, init );
[ba3706f]1638 stmtsToAddBefore.push_back( new DeclStmt( newObj ) );
[8a34677]1639 return newObj;
1640 }
1641
1642 void PolyGenericCalculator::addOtypeParamsToLayoutCall( UntypedExpr *layoutCall, const std::list< Type* > &otypeParams ) {
1643 for ( std::list< Type* >::const_iterator param = otypeParams.begin(); param != otypeParams.end(); ++param ) {
1644 if ( findGeneric( *param ) ) {
1645 // push size/align vars for a generic parameter back
[adc6781]1646 std::string paramName = mangleType( *param );
1647 layoutCall->get_args().push_back( new NameExpr( sizeofName( paramName ) ) );
1648 layoutCall->get_args().push_back( new NameExpr( alignofName( paramName ) ) );
[8a34677]1649 } else {
1650 layoutCall->get_args().push_back( new SizeofExpr( (*param)->clone() ) );
1651 layoutCall->get_args().push_back( new AlignofExpr( (*param)->clone() ) );
1652 }
1653 }
1654 }
1655
1656 /// returns true if any of the otype parameters have a dynamic layout and puts all otype parameters in the output list
1657 bool findGenericParams( std::list< TypeDecl* > &baseParams, std::list< Expression* > &typeParams, std::list< Type* > &out ) {
1658 bool hasDynamicLayout = false;
1659
1660 std::list< TypeDecl* >::const_iterator baseParam = baseParams.begin();
1661 std::list< Expression* >::const_iterator typeParam = typeParams.begin();
1662 for ( ; baseParam != baseParams.end() && typeParam != typeParams.end(); ++baseParam, ++typeParam ) {
1663 // skip non-otype parameters
[2c57025]1664 if ( ! (*baseParam)->isComplete() ) continue;
[8a34677]1665 TypeExpr *typeExpr = dynamic_cast< TypeExpr* >( *typeParam );
1666 assert( typeExpr && "all otype parameters should be type expressions" );
1667
1668 Type *type = typeExpr->get_type();
1669 out.push_back( type );
1670 if ( isPolyType( type ) ) hasDynamicLayout = true;
1671 }
1672 assert( baseParam == baseParams.end() && typeParam == typeParams.end() );
1673
1674 return hasDynamicLayout;
1675 }
1676
1677 bool PolyGenericCalculator::findGeneric( Type *ty ) {
[c2ad3c9]1678 ty = replaceTypeInst( ty, env );
[9799ec8]1679
[8a34677]1680 if ( TypeInstType *typeInst = dynamic_cast< TypeInstType* >( ty ) ) {
1681 if ( scopeTyVars.find( typeInst->get_name() ) != scopeTyVars.end() ) {
1682 // NOTE assumes here that getting put in the scopeTyVars included having the layout variables set
1683 return true;
1684 }
1685 return false;
1686 } else if ( StructInstType *structTy = dynamic_cast< StructInstType* >( ty ) ) {
1687 // check if this type already has a layout generated for it
[adc6781]1688 std::string typeName = mangleType( ty );
1689 if ( knownLayouts.find( typeName ) != knownLayouts.end() ) return true;
[8a34677]1690
1691 // check if any of the type parameters have dynamic layout; if none do, this type is (or will be) monomorphized
1692 std::list< Type* > otypeParams;
1693 if ( ! findGenericParams( *structTy->get_baseParameters(), structTy->get_parameters(), otypeParams ) ) return false;
1694
1695 // insert local variables for layout and generate call to layout function
[adc6781]1696 knownLayouts.insert( typeName ); // done early so as not to interfere with the later addition of parameters to the layout call
[8a34677]1697 Type *layoutType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
1698
1699 int n_members = structTy->get_baseStruct()->get_members().size();
1700 if ( n_members == 0 ) {
1701 // all empty structs have the same layout - size 1, align 1
[cc3528f]1702 makeVar( sizeofName( typeName ), layoutType, new SingleInit( new ConstantExpr( Constant::from_ulong( (unsigned long)1 ) ) ) );
1703 makeVar( alignofName( typeName ), layoutType->clone(), new SingleInit( new ConstantExpr( Constant::from_ulong( (unsigned long)1 ) ) ) );
[8a34677]1704 // NOTE zero-length arrays are forbidden in C, so empty structs have no offsetof array
1705 } else {
[adc6781]1706 ObjectDecl *sizeVar = makeVar( sizeofName( typeName ), layoutType );
1707 ObjectDecl *alignVar = makeVar( alignofName( typeName ), layoutType->clone() );
[cb4c607]1708 ObjectDecl *offsetVar = makeVar( offsetofName( typeName ), new ArrayType( Type::Qualifiers(), layoutType->clone(), new ConstantExpr( Constant::from_int( n_members ) ), false, false ) );
[8a34677]1709
1710 // generate call to layout function
[adc6781]1711 UntypedExpr *layoutCall = new UntypedExpr( new NameExpr( layoutofName( structTy->get_baseStruct() ) ) );
[8a34677]1712 layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( sizeVar ) ) );
1713 layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( alignVar ) ) );
1714 layoutCall->get_args().push_back( new VariableExpr( offsetVar ) );
1715 addOtypeParamsToLayoutCall( layoutCall, otypeParams );
1716
[ba3706f]1717 stmtsToAddBefore.push_back( new ExprStmt( layoutCall ) );
[8a34677]1718 }
1719
1720 return true;
1721 } else if ( UnionInstType *unionTy = dynamic_cast< UnionInstType* >( ty ) ) {
1722 // check if this type already has a layout generated for it
[adc6781]1723 std::string typeName = mangleType( ty );
1724 if ( knownLayouts.find( typeName ) != knownLayouts.end() ) return true;
[8a34677]1725
1726 // check if any of the type parameters have dynamic layout; if none do, this type is (or will be) monomorphized
1727 std::list< Type* > otypeParams;
1728 if ( ! findGenericParams( *unionTy->get_baseParameters(), unionTy->get_parameters(), otypeParams ) ) return false;
1729
1730 // insert local variables for layout and generate call to layout function
[adc6781]1731 knownLayouts.insert( typeName ); // done early so as not to interfere with the later addition of parameters to the layout call
[8a34677]1732 Type *layoutType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
1733
[adc6781]1734 ObjectDecl *sizeVar = makeVar( sizeofName( typeName ), layoutType );
1735 ObjectDecl *alignVar = makeVar( alignofName( typeName ), layoutType->clone() );
[8a34677]1736
1737 // generate call to layout function
[adc6781]1738 UntypedExpr *layoutCall = new UntypedExpr( new NameExpr( layoutofName( unionTy->get_baseUnion() ) ) );
[8a34677]1739 layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( sizeVar ) ) );
1740 layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( alignVar ) ) );
1741 addOtypeParamsToLayoutCall( layoutCall, otypeParams );
1742
[ba3706f]1743 stmtsToAddBefore.push_back( new ExprStmt( layoutCall ) );
[8a34677]1744
1745 return true;
1746 }
1747
1748 return false;
1749 }
1750
[e16294d]1751 Expression * PolyGenericCalculator::genSizeof( Type* ty ) {
1752 if ( ArrayType * aty = dynamic_cast<ArrayType *>(ty) ) {
1753 // generate calculated size for possibly generic array
1754 Expression * sizeofBase = genSizeof( aty->get_base() );
1755 if ( ! sizeofBase ) return nullptr;
1756 Expression * dim = aty->get_dimension();
1757 aty->set_dimension( nullptr );
1758 return makeOp( "?*?", sizeofBase, dim );
1759 } else if ( findGeneric( ty ) ) {
1760 // generate calculated size for generic type
1761 return new NameExpr( sizeofName( mangleType( ty ) ) );
1762 } else return nullptr;
1763 }
1764
[a0c7dc36]1765 Expression *PolyGenericCalculator::postmutate( SizeofExpr *sizeofExpr ) {
[e16294d]1766 Type *ty = sizeofExpr->get_isType() ?
1767 sizeofExpr->get_type() : sizeofExpr->get_expr()->get_result();
1768
1769 Expression * gen = genSizeof( ty );
1770 if ( gen ) {
[8a34677]1771 delete sizeofExpr;
[e16294d]1772 return gen;
1773 } else return sizeofExpr;
[8a34677]1774 }
1775
[a0c7dc36]1776 Expression *PolyGenericCalculator::postmutate( AlignofExpr *alignofExpr ) {
[2edd80ae]1777 Type *ty = alignofExpr->get_isType() ? alignofExpr->get_type() : alignofExpr->get_expr()->get_result();
[8a34677]1778 if ( findGeneric( ty ) ) {
[adc6781]1779 Expression *ret = new NameExpr( alignofName( mangleType( ty ) ) );
[8a34677]1780 delete alignofExpr;
1781 return ret;
1782 }
1783 return alignofExpr;
1784 }
1785
[a0c7dc36]1786 Expression *PolyGenericCalculator::postmutate( OffsetofExpr *offsetofExpr ) {
[2a4b088]1787 // only mutate expressions for polymorphic structs/unions
[8a34677]1788 Type *ty = offsetofExpr->get_type();
1789 if ( ! findGeneric( ty ) ) return offsetofExpr;
[2a4b088]1790
1791 if ( StructInstType *structType = dynamic_cast< StructInstType* >( ty ) ) {
1792 // replace offsetof expression by index into offset array
1793 long i = findMember( offsetofExpr->get_member(), structType->get_baseStruct()->get_members() );
1794 if ( i == -1 ) return offsetofExpr;
1795
1796 Expression *offsetInd = makeOffsetIndex( ty, i );
1797 delete offsetofExpr;
1798 return offsetInd;
[5c52b06]1799 } else if ( dynamic_cast< UnionInstType* >( ty ) ) {
[2a4b088]1800 // all union members are at offset zero
1801 delete offsetofExpr;
[d56e5bc]1802 return new ConstantExpr( Constant::from_ulong( 0 ) );
[2a4b088]1803 } else return offsetofExpr;
[05d47278]1804 }
1805
[a0c7dc36]1806 Expression *PolyGenericCalculator::postmutate( OffsetPackExpr *offsetPackExpr ) {
[8a34677]1807 StructInstType *ty = offsetPackExpr->get_type();
1808
1809 Expression *ret = 0;
1810 if ( findGeneric( ty ) ) {
1811 // pull offset back from generated type information
[adc6781]1812 ret = new NameExpr( offsetofName( mangleType( ty ) ) );
[8a34677]1813 } else {
[adc6781]1814 std::string offsetName = offsetofName( mangleType( ty ) );
[8a34677]1815 if ( knownOffsets.find( offsetName ) != knownOffsets.end() ) {
1816 // use the already-generated offsets for this type
1817 ret = new NameExpr( offsetName );
1818 } else {
1819 knownOffsets.insert( offsetName );
1820
1821 std::list< Declaration* > &baseMembers = ty->get_baseStruct()->get_members();
1822 Type *offsetType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
1823
1824 // build initializer list for offset array
1825 std::list< Initializer* > inits;
1826 for ( std::list< Declaration* >::const_iterator member = baseMembers.begin(); member != baseMembers.end(); ++member ) {
[2164637]1827 if ( DeclarationWithType *memberDecl = dynamic_cast< DeclarationWithType* >( *member ) ) {
1828 inits.push_back( new SingleInit( new OffsetofExpr( ty->clone(), memberDecl ) ) );
[8a34677]1829 } else {
[2164637]1830 assertf( false, "Requesting offset of Non-DWT member: %s", toString( *member ).c_str() );
[8a34677]1831 }
1832 }
1833
1834 // build the offset array and replace the pack with a reference to it
[cb4c607]1835 ObjectDecl *offsetArray = makeVar( offsetName, new ArrayType( Type::Qualifiers(), offsetType, new ConstantExpr( Constant::from_ulong( baseMembers.size() ) ), false, false ),
[8a34677]1836 new ListInit( inits ) );
1837 ret = new VariableExpr( offsetArray );
1838 }
1839 }
1840
1841 delete offsetPackExpr;
1842 return ret;
1843 }
1844
[a0c7dc36]1845 void PolyGenericCalculator::beginScope() {
[8a34677]1846 knownLayouts.beginScope();
1847 knownOffsets.beginScope();
1848 }
1849
[a0c7dc36]1850 void PolyGenericCalculator::endScope() {
[8a34677]1851 knownLayouts.endScope();
[adc6781]1852 knownOffsets.endScope();
[8a34677]1853 }
1854
[05d47278]1855////////////////////////////////////////// Pass3 ////////////////////////////////////////////////////
1856
1857 template< typename DeclClass >
[fc72845d]1858 void Pass3::handleDecl( DeclClass * decl, Type * type ) {
1859 GuardScope( scopeTyVars );
[05d47278]1860 makeTyVarMap( type, scopeTyVars );
[5a3ac84]1861 ScrubTyVars::scrubAll( decl );
[05d47278]1862 }
1863
[fc72845d]1864 void Pass3::premutate( ObjectDecl * objectDecl ) {
1865 handleDecl( objectDecl, objectDecl->type );
[05d47278]1866 }
1867
[fc72845d]1868 void Pass3::premutate( FunctionDecl * functionDecl ) {
1869 handleDecl( functionDecl, functionDecl->type );
[05d47278]1870 }
1871
[fc72845d]1872 void Pass3::premutate( TypedefDecl * typedefDecl ) {
1873 handleDecl( typedefDecl, typedefDecl->base );
[05d47278]1874 }
1875
[fea3faa]1876 /// Strips the members from a generic aggregate
[fc72845d]1877 void stripGenericMembers(AggregateDecl * decl) {
1878 if ( ! decl->parameters.empty() ) decl->members.clear();
[fea3faa]1879 }
1880
[fc72845d]1881 void Pass3::premutate( StructDecl * structDecl ) {
[fea3faa]1882 stripGenericMembers( structDecl );
1883 }
[acd7c5dd]1884
[fc72845d]1885 void Pass3::premutate( UnionDecl * unionDecl ) {
[fea3faa]1886 stripGenericMembers( unionDecl );
1887 }
1888
[fc72845d]1889 void Pass3::premutate( TypeDecl * typeDecl ) {
[2c57025]1890 addToTyVarMap( typeDecl, scopeTyVars );
[05d47278]1891 }
1892
[fc72845d]1893 void Pass3::premutate( PointerType * pointerType ) {
1894 GuardScope( scopeTyVars );
[05d47278]1895 makeTyVarMap( pointerType, scopeTyVars );
1896 }
1897
[fc72845d]1898 void Pass3::premutate( FunctionType * functionType ) {
1899 GuardScope( scopeTyVars );
[05d47278]1900 makeTyVarMap( functionType, scopeTyVars );
1901 }
[01aeade]1902 } // anonymous namespace
[51b73452]1903} // namespace GenPoly
[01aeade]1904
[51587aa]1905// Local Variables: //
1906// tab-width: 4 //
1907// mode: c++ //
1908// compile-command: "make install" //
1909// End: //
Note: See TracBrowser for help on using the repository browser.