source: src/GenPoly/Box.cc@ 79a6b17

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

Header Clean-up: Clearing out typeops, moving things to Unify because that header already exist.

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