source: src/GenPoly/Box.cc@ e220391

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 e220391 was ae1b9ea, checked in by Rob Schluntz <rschlunt@…>, 8 years ago

Always copy construct arguments that require boxing

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