source: src/GenPoly/Box.cc@ fa2e183

ADT ast-experimental
Last change on this file since fa2e183 was 8c91088, checked in by Andrew Beach <ajbeach@…>, 3 years ago

Slight improvement to documentation in Box.cc.

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