source: src/GenPoly/Box.cc@ eada3cf

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

Minor cleanup in Box

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