source: src/GenPoly/Box.cc@ 834b892

ADT aaron-thesis arm-eh ast-experimental cleanup-dtors deferred_resn demangler enum forall-pointer-decay jacob/cs343-translation jenkins-sandbox new-ast new-ast-unique-expr new-env no_list persistent-indexer pthread-emulation qualifiedEnum resolv-new with_gc
Last change on this file since 834b892 was 20cba76, checked in by Rob Schluntz <rschlunt@…>, 8 years ago

Minor code cleanup

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