source: src/GenPoly/Box.cc@ f38e7d7

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 new-env no_list persistent-indexer pthread-emulation qualifiedEnum with_gc
Last change on this file since f38e7d7 was 661214c, checked in by Rob Schluntz <rschlunt@…>, 8 years ago

Apply generic substitution to member type when transforming generic member expressions

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