source: src/GenPoly/Box.cc@ fdd0509

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 resolv-new with_gc
Last change on this file since fdd0509 was ba3706f, checked in by Rob Schluntz <rschlunt@…>, 8 years ago

Remove label lists from various Statement constructors

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