source: src/GenPoly/Box.cc@ 3e5dd913

ADT arm-eh ast-experimental enum forall-pointer-decay jacob/cs343-translation new-ast-unique-expr pthread-emulation qualifiedEnum
Last change on this file since 3e5dd913 was 07de76b, checked in by Peter A. Buhr <pabuhr@…>, 6 years ago

remove file TypeVar.h* and put TypeVar::Kind into TypeDecl, move LinkageSpec.* from directory Parse to SynTree

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