source: src/GenPoly/Box.cc@ 0c11d3c

ADT ast-experimental pthread-emulation
Last change on this file since 0c11d3c was 18070ee, checked in by Thierry Delisle <tdelisle@…>, 3 years ago

Change box pass to scope better when polymorphic functions get assertions functions passed as parameter.
fixes 214

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