source: src/GenPoly/Box.cc@ 466787a

ADT ast-experimental
Last change on this file since 466787a was 331ee52c, checked in by Andrew Beach <ajbeach@…>, 3 years ago

Should silence a GCC 12 warning.

  • Property mode set to 100644
File size: 86.5 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 <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/typeops.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 FunctionType *originalFunction = funType->clone();
914 FunctionType *realFunction = funType->clone();
915 std::string mangleName = SymTab::Mangler::mangle( realFunction );
916
917 // only attempt to create an adapter or pass one as a parameter if we haven't already done so for this
918 // pre-substitution parameter function type.
919 // The second part of the insert result is "is the value new".
920 if ( adaptersDone.insert( mangleName ).second ) {
921
922 // apply substitution to type variables to figure out what the adapter's type should look like
923 assert( env );
924 env->apply( realFunction );
925 mangleName = SymTab::Mangler::mangle( realFunction );
926 mangleName += makePolyMonoSuffix( originalFunction, exprTyVars );
927
928 typedef ScopedMap< std::string, DeclarationWithType* >::iterator AdapterIter;
929 AdapterIter adapter = adapters.find( mangleName );
930 if ( adapter == adapters.end() ) {
931 // adapter has not been created yet in the current scope, so define it
932 FunctionDecl *newAdapter = makeAdapter( funType, realFunction, mangleName, exprTyVars );
933 std::pair< AdapterIter, bool > answer = adapters.insert( std::pair< std::string, DeclarationWithType *>( mangleName, newAdapter ) );
934 adapter = answer.first;
935 stmtsToAddBefore.push_back( new DeclStmt( newAdapter ) );
936 } // if
937 assert( adapter != adapters.end() );
938
939 // add the appropriate adapter as a parameter
940 appExpr->get_args().push_front( new VariableExpr( adapter->second ) );
941 } // if
942 } // for
943 } // passAdapters
944
945 Expression *makeIncrDecrExpr( ApplicationExpr *appExpr, Type *polyType, bool isIncr ) {
946 NameExpr *opExpr = new NameExpr( ( isIncr ) ? "?+=?" : "?-=?" );
947 UntypedExpr *addAssign = new UntypedExpr( opExpr );
948 if ( AddressExpr *address = dynamic_cast< AddressExpr *>( appExpr->get_args().front() ) ) {
949 addAssign->get_args().push_back( address->get_arg() );
950 } else {
951 addAssign->get_args().push_back( appExpr->get_args().front() );
952 } // if
953 addAssign->get_args().push_back( new NameExpr( sizeofName( mangleType( polyType ) ) ) );
954 addAssign->set_result( appExpr->get_result()->clone() );
955 if ( appExpr->get_env() ) {
956 addAssign->set_env( appExpr->get_env() );
957 appExpr->set_env( 0 );
958 } // if
959 appExpr->get_args().clear();
960 delete appExpr;
961 return addAssign;
962 }
963
964 Expression *CallAdapter::handleIntrinsics( ApplicationExpr *appExpr ) {
965 if ( VariableExpr *varExpr = dynamic_cast< VariableExpr *>( appExpr->function ) ) {
966 if ( varExpr->var->linkage == LinkageSpec::Intrinsic ) {
967 if ( varExpr->var->name == "?[?]" ) {
968 assert( appExpr->result );
969 assert( appExpr->get_args().size() == 2 );
970 Type *baseType1 = isPolyPtr( appExpr->args.front()->result, scopeTyVars, env );
971 Type *baseType2 = isPolyPtr( appExpr->args.back()->result, scopeTyVars, env );
972 assert( ! baseType1 || ! baseType2 ); // the arguments cannot both be polymorphic pointers
973 UntypedExpr *ret = 0;
974 if ( baseType1 || baseType2 ) { // one of the arguments is a polymorphic pointer
975 ret = new UntypedExpr( new NameExpr( "?+?" ) );
976 } // if
977 if ( baseType1 ) {
978 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
979 multiply->get_args().push_back( appExpr->get_args().back() );
980 multiply->get_args().push_back( new SizeofExpr( baseType1->clone() ) );
981 ret->get_args().push_back( appExpr->get_args().front() );
982 ret->get_args().push_back( multiply );
983 } else if ( baseType2 ) {
984 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
985 multiply->get_args().push_back( appExpr->get_args().front() );
986 multiply->get_args().push_back( new SizeofExpr( baseType2->clone() ) );
987 ret->get_args().push_back( multiply );
988 ret->get_args().push_back( appExpr->get_args().back() );
989 } // if
990 if ( baseType1 || baseType2 ) {
991 delete ret->get_result();
992 ret->set_result( appExpr->get_result()->clone() );
993 if ( appExpr->get_env() ) {
994 ret->set_env( appExpr->get_env() );
995 appExpr->set_env( 0 );
996 } // if
997 appExpr->get_args().clear();
998 delete appExpr;
999 return ret;
1000 } // if
1001 } else if ( varExpr->get_var()->get_name() == "*?" ) {
1002 assert( appExpr->result );
1003 assert( ! appExpr->get_args().empty() );
1004 if ( isPolyType( appExpr->get_result(), scopeTyVars, env ) ) {
1005 // remove dereference from polymorphic types since they are boxed.
1006 Expression *ret = appExpr->get_args().front();
1007 // fix expr type to remove pointer
1008 delete ret->get_result();
1009 ret->set_result( appExpr->get_result()->clone() );
1010 if ( appExpr->get_env() ) {
1011 ret->set_env( appExpr->get_env() );
1012 appExpr->set_env( 0 );
1013 } // if
1014 appExpr->get_args().clear();
1015 delete appExpr;
1016 return ret;
1017 } // if
1018 } else if ( varExpr->get_var()->get_name() == "?++" || varExpr->get_var()->get_name() == "?--" ) {
1019 assert( appExpr->result );
1020 assert( appExpr->get_args().size() == 1 );
1021 if ( Type *baseType = isPolyPtr( appExpr->get_result(), scopeTyVars, env ) ) {
1022 Type *tempType = appExpr->get_result()->clone();
1023 if ( env ) {
1024 env->apply( tempType );
1025 } // if
1026 ObjectDecl *newObj = makeTemporary( tempType );
1027 VariableExpr *tempExpr = new VariableExpr( newObj );
1028 UntypedExpr *assignExpr = new UntypedExpr( new NameExpr( "?=?" ) );
1029 assignExpr->get_args().push_back( tempExpr->clone() );
1030 if ( AddressExpr *address = dynamic_cast< AddressExpr *>( appExpr->get_args().front() ) ) {
1031 assignExpr->get_args().push_back( address->get_arg()->clone() );
1032 } else {
1033 assignExpr->get_args().push_back( appExpr->get_args().front()->clone() );
1034 } // if
1035 CommaExpr *firstComma = new CommaExpr( assignExpr, makeIncrDecrExpr( appExpr, baseType, varExpr->get_var()->get_name() == "?++" ) );
1036 return new CommaExpr( firstComma, tempExpr );
1037 } // if
1038 } else if ( varExpr->get_var()->get_name() == "++?" || varExpr->get_var()->get_name() == "--?" ) {
1039 assert( appExpr->result );
1040 assert( appExpr->get_args().size() == 1 );
1041 if ( Type *baseType = isPolyPtr( appExpr->get_result(), scopeTyVars, env ) ) {
1042 return makeIncrDecrExpr( appExpr, baseType, varExpr->get_var()->get_name() == "++?" );
1043 } // if
1044 } else if ( varExpr->get_var()->get_name() == "?+?" || varExpr->get_var()->get_name() == "?-?" ) {
1045 assert( appExpr->result );
1046 assert( appExpr->get_args().size() == 2 );
1047 Type *baseType1 = isPolyPtr( appExpr->get_args().front()->get_result(), scopeTyVars, env );
1048 Type *baseType2 = isPolyPtr( appExpr->get_args().back()->get_result(), scopeTyVars, env );
1049 if ( baseType1 && baseType2 ) {
1050 UntypedExpr *divide = new UntypedExpr( new NameExpr( "?/?" ) );
1051 divide->get_args().push_back( appExpr );
1052 divide->get_args().push_back( new SizeofExpr( baseType1->clone() ) );
1053 divide->set_result( appExpr->get_result()->clone() );
1054 if ( appExpr->get_env() ) {
1055 divide->set_env( appExpr->get_env() );
1056 appExpr->set_env( 0 );
1057 } // if
1058 return divide;
1059 } else if ( baseType1 ) {
1060 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1061 multiply->get_args().push_back( appExpr->get_args().back() );
1062 multiply->get_args().push_back( new SizeofExpr( baseType1->clone() ) );
1063 appExpr->get_args().back() = multiply;
1064 } else if ( baseType2 ) {
1065 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1066 multiply->get_args().push_back( appExpr->get_args().front() );
1067 multiply->get_args().push_back( new SizeofExpr( baseType2->clone() ) );
1068 appExpr->get_args().front() = multiply;
1069 } // if
1070 } else if ( varExpr->get_var()->get_name() == "?+=?" || varExpr->get_var()->get_name() == "?-=?" ) {
1071 assert( appExpr->result );
1072 assert( appExpr->get_args().size() == 2 );
1073 Type *baseType = isPolyPtr( appExpr->get_result(), scopeTyVars, env );
1074 if ( baseType ) {
1075 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1076 multiply->get_args().push_back( appExpr->get_args().back() );
1077 multiply->get_args().push_back( new SizeofExpr( baseType->clone() ) );
1078 appExpr->get_args().back() = multiply;
1079 } // if
1080 } // if
1081 return appExpr;
1082 } // if
1083 } // if
1084 return 0;
1085 }
1086
1087 Expression *CallAdapter::postmutate( ApplicationExpr *appExpr ) {
1088 // std::cerr << "mutate appExpr: " << InitTweak::getFunctionName( appExpr ) << std::endl;
1089 // for ( auto tyVar : scopeTyVars ) {
1090 // std::cerr << tyVar.first << " ";
1091 // }
1092 // std::cerr << "\n";
1093
1094 assert( appExpr->function->result );
1095 FunctionType * function = getFunctionType( appExpr->function->result );
1096 assertf( function, "ApplicationExpr has non-function type: %s", toString( appExpr->function->result ).c_str() );
1097
1098 if ( Expression *newExpr = handleIntrinsics( appExpr ) ) {
1099 return newExpr;
1100 } // if
1101
1102 Expression *ret = appExpr;
1103 // Save iterator to the first original parameter (works with lists).
1104 std::list< Expression *>::iterator paramBegin = appExpr->get_args().begin();
1105
1106 TyVarMap exprTyVars( TypeDecl::Data{} );
1107 makeTyVarMap( function, exprTyVars ); // xxx - should this take into account the variables already bound in scopeTyVars (i.e. remove them from exprTyVars?)
1108 ReferenceToType *dynRetType = isDynRet( function, exprTyVars );
1109
1110 // std::cerr << function << std::endl;
1111 // std::cerr << "scopeTyVars: ";
1112 // printTyVarMap( std::cerr, scopeTyVars );
1113 // std::cerr << "exprTyVars: ";
1114 // printTyVarMap( std::cerr, exprTyVars );
1115 // std::cerr << "env: " << *env << std::endl;
1116 // std::cerr << needsAdapter( function, scopeTyVars ) << ! needsAdapter( function, exprTyVars) << std::endl;
1117
1118 // 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
1119 // passTypeVars needs to know the program-text return type (i.e. the distinction between _conc_T30 and T3(int))
1120 // concRetType may not be a good name in one or both of these places. A more appropriate name change is welcome.
1121 if ( dynRetType ) {
1122 // std::cerr << "dynRetType: " << dynRetType << std::endl;
1123 Type *concRetType = appExpr->get_result()->isVoid() ? nullptr : appExpr->get_result();
1124 ret = addDynRetParam( appExpr, concRetType ); // xxx - used to use dynRetType instead of concRetType
1125 } else if ( needsAdapter( function, scopeTyVars ) && ! needsAdapter( function, exprTyVars) ) { // xxx - exprTyVars is used above...?
1126 // 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.
1127
1128 // std::cerr << "needs adapter: ";
1129 // printTyVarMap( std::cerr, scopeTyVars );
1130 // std::cerr << *env << std::endl;
1131 // change the application so it calls the adapter rather than the passed function
1132 ret = applyAdapter( appExpr, function );
1133 } // if
1134
1135 Type *concRetType = replaceWithConcrete( dynRetType, env );
1136 std::list< Expression *>::iterator arg =
1137 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)
1138 addInferredParams( appExpr, arg, function, exprTyVars );
1139
1140 // This needs to point at the original first argument.
1141 boxParams( appExpr, paramBegin, function, exprTyVars );
1142
1143 passAdapters( appExpr, function, exprTyVars );
1144
1145 return ret;
1146 }
1147
1148 bool isPolyDeref( UntypedExpr const * expr, TyVarMap const & scopeTyVars, TypeSubstitution const * env ) {
1149 if ( expr->result && isPolyType( expr->result, scopeTyVars, env ) ) {
1150 if ( auto name = dynamic_cast<NameExpr const *>( expr->function ) ) {
1151 if ( name->name == "*?" ) {
1152 return true;
1153 } // if
1154 } // if
1155 } // if
1156 return false;
1157 }
1158
1159 Expression * CallAdapter::postmutate( UntypedExpr *expr ) {
1160 if ( isPolyDeref( expr, scopeTyVars, env ) ) {
1161 Expression *ret = expr->args.front();
1162 expr->args.clear();
1163 delete expr;
1164 return ret;
1165 }
1166 return expr;
1167 }
1168
1169 void CallAdapter::premutate( AddressExpr * ) { visit_children = false; }
1170
1171 Expression * CallAdapter::postmutate( AddressExpr * addrExpr ) {
1172 assert( addrExpr->arg->result && ! addrExpr->arg->result->isVoid() );
1173
1174 bool needs = false;
1175 if ( UntypedExpr *expr = dynamic_cast< UntypedExpr *>( addrExpr->arg ) ) {
1176 if ( isPolyDeref( expr, scopeTyVars, env ) ) {
1177 if ( ApplicationExpr * appExpr = dynamic_cast< ApplicationExpr * >( expr->args.front() ) ) {
1178 assert( appExpr->function->result );
1179 FunctionType *function = getFunctionType( appExpr->function->result );
1180 assert( function );
1181 needs = needsAdapter( function, scopeTyVars );
1182 } // if
1183 } // if
1184 } // if
1185 // isPolyType check needs to happen before mutating addrExpr arg, so pull it forward
1186 // out of the if condition.
1187 addrExpr->arg = addrExpr->arg->acceptMutator( *visitor );
1188 // ... but must happen after mutate, since argument might change (e.g. intrinsic *?, ?[?]) - re-evaluate above comment
1189 bool polytype = isPolyType( addrExpr->arg->result, scopeTyVars, env );
1190 if ( polytype || needs ) {
1191 Expression *ret = addrExpr->arg;
1192 delete ret->result;
1193 ret->result = addrExpr->result->clone();
1194 addrExpr->arg = nullptr;
1195 delete addrExpr;
1196 return ret;
1197 } else {
1198 return addrExpr;
1199 } // if
1200 }
1201
1202 void CallAdapter::premutate( ReturnStmt *returnStmt ) {
1203 if ( retval && returnStmt->expr ) {
1204 assert( returnStmt->expr->result && ! returnStmt->expr->result->isVoid() );
1205 delete returnStmt->expr;
1206 returnStmt->expr = nullptr;
1207 } // if
1208 }
1209
1210 void CallAdapter::premutate( PointerType *pointerType ) {
1211 GuardScope( scopeTyVars );
1212 makeTyVarMap( pointerType, scopeTyVars );
1213 }
1214
1215 void CallAdapter::premutate( FunctionType *functionType ) {
1216 GuardScope( scopeTyVars );
1217 makeTyVarMap( functionType, scopeTyVars );
1218 }
1219
1220 void CallAdapter::beginScope() {
1221 adapters.beginScope();
1222 }
1223
1224 void CallAdapter::endScope() {
1225 adapters.endScope();
1226 }
1227
1228////////////////////////////////////////// DeclAdapter //////////////////////////////////////////
1229
1230 void DeclAdapter::addAdapters( FunctionType *functionType ) {
1231 std::list< FunctionType const *> functions;
1232 for ( DeclarationWithType * const arg : functionType->parameters ) {
1233 Type *orig = arg->get_type();
1234 findAndReplaceFunction( orig, functions, scopeTyVars, needsAdapter );
1235 arg->set_type( orig );
1236 }
1237 std::set< std::string > adaptersDone;
1238 for ( FunctionType const * const funType : functions ) {
1239 std::string mangleName = mangleAdapterName( funType, scopeTyVars );
1240 if ( adaptersDone.find( mangleName ) == adaptersDone.end() ) {
1241 std::string adapterName = makeAdapterName( mangleName );
1242 // adapter may not be used in body, pass along with unused attribute.
1243 functionType->parameters.push_front(
1244 new ObjectDecl( adapterName, Type::StorageClasses(), LinkageSpec::C, 0, new PointerType( Type::Qualifiers(), makeAdapterType( funType, scopeTyVars ) ), 0, { new Attribute( "unused" ) } ) );
1245 adaptersDone.insert( adaptersDone.begin(), mangleName );
1246 }
1247 }
1248 }
1249
1250 DeclarationWithType * DeclAdapter::postmutate( FunctionDecl *functionDecl ) {
1251 FunctionType * ftype = functionDecl->type;
1252 if ( ! ftype->returnVals.empty() && functionDecl->statements ) {
1253 // intrinsic functions won't be using the _retval so no need to generate it.
1254 if ( functionDecl->linkage != LinkageSpec::Intrinsic && !isPrefix( functionDecl->name, "_thunk" ) && ! isPrefix( functionDecl->name, "_adapter" ) ) { // xxx - remove check for prefix once thunks properly use ctor/dtors
1255 assert( ftype->returnVals.size() == 1 );
1256 DeclarationWithType * retval = ftype->returnVals.front();
1257 if ( retval->name == "" ) {
1258 retval->name = "_retval";
1259 }
1260 functionDecl->statements->kids.push_front( new DeclStmt( retval ) );
1261 DeclarationWithType * newRet = retval->clone(); // for ownership purposes
1262 ftype->returnVals.front() = newRet;
1263 }
1264 }
1265 // errors should have been caught by this point, remove initializers from parameters to allow correct codegen of default arguments
1266 for ( Declaration * param : functionDecl->type->parameters ) {
1267 if ( ObjectDecl * obj = dynamic_cast< ObjectDecl * >( param ) ) {
1268 delete obj->init;
1269 obj->init = nullptr;
1270 }
1271 }
1272 return functionDecl;
1273 }
1274
1275 void DeclAdapter::premutate( StructDecl * ) {
1276 // prevent tyVars from leaking into containing scope
1277 GuardScope( scopeTyVars );
1278 }
1279
1280 void DeclAdapter::premutate( UnionDecl * ) {
1281 // prevent tyVars from leaking into containing scope
1282 GuardScope( scopeTyVars );
1283 }
1284
1285 void DeclAdapter::premutate( TraitDecl * ) {
1286 // prevent tyVars from leaking into containing scope
1287 GuardScope( scopeTyVars );
1288 }
1289
1290 void DeclAdapter::premutate( TypeDecl *typeDecl ) {
1291 addToTyVarMap( typeDecl, scopeTyVars );
1292 }
1293
1294 void DeclAdapter::premutate( PointerType *pointerType ) {
1295 GuardScope( scopeTyVars );
1296 makeTyVarMap( pointerType, scopeTyVars );
1297 }
1298
1299 void DeclAdapter::premutate( FunctionType *funcType ) {
1300 GuardScope( scopeTyVars );
1301 makeTyVarMap( funcType, scopeTyVars );
1302
1303 // move polymorphic return type to parameter list
1304 if ( isDynRet( funcType ) ) {
1305 ObjectDecl *ret = strict_dynamic_cast< ObjectDecl* >( funcType->get_returnVals().front() );
1306 ret->set_type( new PointerType( Type::Qualifiers(), ret->get_type() ) );
1307 funcType->get_parameters().push_front( ret );
1308 funcType->get_returnVals().pop_front();
1309 ret->set_init( nullptr ); // xxx - memory leak?
1310 }
1311
1312 // add size/align and assertions for type parameters to parameter list
1313 std::list< DeclarationWithType *>::iterator last = funcType->get_parameters().begin();
1314 std::list< DeclarationWithType *> inferredParams;
1315 // size/align/offset parameters may not be used in body, pass along with unused attribute.
1316 ObjectDecl newObj( "", Type::StorageClasses(), LinkageSpec::C, 0, new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ), 0,
1317 { new Attribute( "unused" ) } );
1318 ObjectDecl newPtr( "", Type::StorageClasses(), LinkageSpec::C, 0,
1319 new PointerType( Type::Qualifiers(), new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ) ), 0 );
1320 for ( TypeDecl * const tyParam : funcType->get_forall() ) {
1321 ObjectDecl *sizeParm, *alignParm;
1322 // add all size and alignment parameters to parameter list
1323 if ( tyParam->isComplete() ) {
1324 TypeInstType parmType( Type::Qualifiers(), tyParam->get_name(), tyParam );
1325 std::string parmName = mangleType( &parmType );
1326
1327 sizeParm = newObj.clone();
1328 sizeParm->set_name( sizeofName( parmName ) );
1329 last = funcType->get_parameters().insert( last, sizeParm );
1330 ++last;
1331
1332 alignParm = newObj.clone();
1333 alignParm->set_name( alignofName( parmName ) );
1334 last = funcType->get_parameters().insert( last, alignParm );
1335 ++last;
1336 }
1337 // move all assertions into parameter list
1338 for ( DeclarationWithType * const assert : tyParam->get_assertions() ) {
1339 // assertion parameters may not be used in body, pass along with unused attribute.
1340 assert->get_attributes().push_back( new Attribute( "unused" ) );
1341 inferredParams.push_back( assert );
1342 }
1343 tyParam->get_assertions().clear();
1344 }
1345
1346 // add size/align for generic parameter types to parameter list
1347 std::set< std::string > seenTypes; // sizeofName for generic types we've seen
1348 for ( DeclarationWithType * const fnParam : funcType->get_parameters() ) {
1349 Type *polyType = isPolyType( fnParam->get_type(), scopeTyVars );
1350 if ( polyType && ! dynamic_cast< TypeInstType* >( polyType ) ) {
1351 std::string typeName = mangleType( polyType );
1352 if ( seenTypes.count( typeName ) ) continue;
1353
1354 ObjectDecl *sizeParm, *alignParm, *offsetParm;
1355 sizeParm = newObj.clone();
1356 sizeParm->set_name( sizeofName( typeName ) );
1357 last = funcType->get_parameters().insert( last, sizeParm );
1358 ++last;
1359
1360 alignParm = newObj.clone();
1361 alignParm->set_name( alignofName( typeName ) );
1362 last = funcType->get_parameters().insert( last, alignParm );
1363 ++last;
1364
1365 if ( StructInstType *polyBaseStruct = dynamic_cast< StructInstType* >( polyType ) ) {
1366 // NOTE zero-length arrays are illegal in C, so empty structs have no offset array
1367 if ( ! polyBaseStruct->get_baseStruct()->get_members().empty() ) {
1368 offsetParm = newPtr.clone();
1369 offsetParm->set_name( offsetofName( typeName ) );
1370 last = funcType->get_parameters().insert( last, offsetParm );
1371 ++last;
1372 }
1373 }
1374 seenTypes.insert( typeName );
1375 }
1376 }
1377
1378 // splice assertion parameters into parameter list
1379 funcType->get_parameters().splice( last, inferredParams );
1380 addAdapters( funcType );
1381 }
1382
1383////////////////////////////////////////// PolyGenericCalculator ////////////////////////////////
1384
1385 PolyGenericCalculator::PolyGenericCalculator()
1386 : knownLayouts(), knownOffsets(), bufNamer( "_buf" ) {}
1387
1388 void PolyGenericCalculator::beginTypeScope( Type *ty ) {
1389 GuardScope( scopeTyVars );
1390 makeTyVarMap( ty, scopeTyVars );
1391 }
1392
1393 void PolyGenericCalculator::beginGenericScope() {
1394 GuardScope( *this );
1395 // We expect the first function type see to be the type relating to this scope
1396 // but any further type is probably some unrelated function pointer
1397 // keep track of which is the first
1398 GuardValue( expect_func_type );
1399 expect_func_type = true;
1400 }
1401
1402 void PolyGenericCalculator::premutate( ObjectDecl *objectDecl ) {
1403 beginTypeScope( objectDecl->get_type() );
1404 }
1405
1406 void PolyGenericCalculator::premutate( FunctionDecl *functionDecl ) {
1407 beginGenericScope();
1408
1409 beginTypeScope( functionDecl->get_functionType() );
1410 }
1411
1412 void PolyGenericCalculator::premutate( TypedefDecl *typedefDecl ) {
1413 assert(false);
1414 beginTypeScope( typedefDecl->get_base() );
1415 }
1416
1417 void PolyGenericCalculator::premutate( TypeDecl * typeDecl ) {
1418 addToTyVarMap( typeDecl, scopeTyVars );
1419 }
1420
1421 Declaration * PolyGenericCalculator::postmutate( TypeDecl *typeDecl ) {
1422 if ( Type * base = typeDecl->base ) {
1423 // add size/align variables for opaque type declarations
1424 TypeInstType inst( Type::Qualifiers(), typeDecl->name, typeDecl );
1425 std::string typeName = mangleType( &inst );
1426 Type *layoutType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
1427
1428 ObjectDecl * sizeDecl = ObjectDecl::newObject( sizeofName( typeName ), layoutType, new SingleInit( new SizeofExpr( base->clone() ) ) );
1429 ObjectDecl * alignDecl = ObjectDecl::newObject( alignofName( typeName ), layoutType->clone(), new SingleInit( new AlignofExpr( base->clone() ) ) );
1430
1431 // ensure that the initializing sizeof/alignof exprs are properly mutated
1432 sizeDecl->acceptMutator( *visitor );
1433 alignDecl->acceptMutator( *visitor );
1434
1435 // can't use makeVar, because it inserts into stmtsToAdd and TypeDecls can occur at global scope
1436 declsToAddAfter.push_back( alignDecl );
1437 // replace with sizeDecl
1438 return sizeDecl;
1439 }
1440 return typeDecl;
1441 }
1442
1443 void PolyGenericCalculator::premutate( PointerType *pointerType ) {
1444 beginTypeScope( pointerType );
1445 }
1446
1447 void PolyGenericCalculator::premutate( FunctionType *funcType ) {
1448 beginTypeScope( funcType );
1449
1450 GuardValue( expect_func_type );
1451
1452 if(!expect_func_type) {
1453 // If this is the first function type we see
1454 // Then it's the type of the declaration and we care about it
1455 GuardScope( *this );
1456 }
1457
1458 // The other functions type we will see in this scope are probably functions parameters
1459 // they don't help us with the layout and offsets so don't mark them as known in this scope
1460 expect_func_type = false;
1461
1462 // make sure that any type information passed into the function is accounted for
1463 for ( DeclarationWithType * const fnParam : funcType->get_parameters() ) {
1464 // condition here duplicates that in DeclAdapter::mutate( FunctionType* )
1465 Type *polyType = isPolyType( fnParam->get_type(), scopeTyVars );
1466 if ( polyType && ! dynamic_cast< TypeInstType* >( polyType ) ) {
1467 knownLayouts.insert( mangleType( polyType ) );
1468 }
1469 }
1470 }
1471
1472 /// converts polymorphic type T into a suitable monomorphic representation, currently: __attribute__((aligned(8)) char[size_T]
1473 Type * polyToMonoType( Type const * declType ) {
1474 Type * charType = new BasicType( Type::Qualifiers(), BasicType::Kind::Char);
1475 Expression * size = new NameExpr( sizeofName( mangleType(declType) ) );
1476 Attribute * aligned = new Attribute( "aligned", std::list<Expression*>{ new ConstantExpr( Constant::from_int(8) ) } );
1477 return new ArrayType( Type::Qualifiers(), charType, size,
1478 true, false, std::list<Attribute *>{ aligned } );
1479 }
1480
1481 void PolyGenericCalculator::mutateMembers( AggregateDecl * aggrDecl ) {
1482 std::set< std::string > genericParams;
1483 for ( TypeDecl * td : aggrDecl->parameters ) {
1484 genericParams.insert( td->name );
1485 }
1486 for ( Declaration * decl : aggrDecl->members ) {
1487 if ( ObjectDecl * field = dynamic_cast< ObjectDecl * >( decl ) ) {
1488 Type * ty = replaceTypeInst( field->type, env );
1489 if ( TypeInstType *typeInst = dynamic_cast< TypeInstType* >( ty ) ) {
1490 // do not try to monomorphize generic parameters
1491 if ( scopeTyVars.find( typeInst->get_name() ) != scopeTyVars.end() && ! genericParams.count( typeInst->name ) ) {
1492 // polymorphic aggregate members should be converted into monomorphic members.
1493 // Using char[size_T] here respects the expected sizing rules of an aggregate type.
1494 Type * newType = polyToMonoType( field->type );
1495 delete field->type;
1496 field->type = newType;
1497 }
1498 }
1499 }
1500 }
1501 }
1502
1503 void PolyGenericCalculator::premutate( StructDecl * structDecl ) {
1504 mutateMembers( structDecl );
1505 }
1506
1507 void PolyGenericCalculator::premutate( UnionDecl * unionDecl ) {
1508 mutateMembers( unionDecl );
1509 }
1510
1511 void PolyGenericCalculator::premutate( DeclStmt *declStmt ) {
1512 if ( ObjectDecl *objectDecl = dynamic_cast< ObjectDecl *>( declStmt->get_decl() ) ) {
1513 if ( findGeneric( objectDecl->get_type() ) ) {
1514 // change initialization of a polymorphic value object to allocate via a VLA
1515 // (alloca was previously used, but can't be safely used in loops)
1516 ObjectDecl *newBuf = ObjectDecl::newObject( bufNamer.newName(), polyToMonoType( objectDecl->type ), nullptr );
1517 stmtsToAddBefore.push_back( new DeclStmt( newBuf ) );
1518
1519 // if the object has a cleanup attribute, the cleanup should be on the buffer, not the pointer
1520 auto matchAndMove = [newBuf](Attribute * attr){
1521 if(attr->name == "cleanup") {
1522 newBuf->attributes.push_back(attr);
1523 return true;
1524 }
1525 return false;
1526 };
1527
1528 objectDecl->attributes.remove_if(matchAndMove);
1529
1530 delete objectDecl->get_init();
1531 objectDecl->set_init( new SingleInit( new VariableExpr( newBuf ) ) );
1532 }
1533 }
1534 }
1535
1536 /// Finds the member in the base list that matches the given declaration; returns its index, or -1 if not present
1537 long findMember( DeclarationWithType *memberDecl, std::list< Declaration* > &baseDecls ) {
1538 for ( auto pair : enumerate( baseDecls ) ) {
1539 Declaration * decl = pair.val;
1540 size_t i = pair.idx;
1541 if ( memberDecl->get_name() != decl->get_name() )
1542 continue;
1543
1544 if ( memberDecl->get_name().empty() ) {
1545 // plan-9 field: match on unique_id
1546 if ( memberDecl->get_uniqueId() == decl->get_uniqueId() )
1547 return i;
1548 else
1549 continue;
1550 }
1551
1552 DeclarationWithType *declWithType = strict_dynamic_cast< DeclarationWithType* >( decl );
1553
1554 if ( memberDecl->get_mangleName().empty() || declWithType->get_mangleName().empty() ) {
1555 // tuple-element field: expect neither had mangled name; accept match on simple name (like field_2) only
1556 assert( memberDecl->get_mangleName().empty() && declWithType->get_mangleName().empty() );
1557 return i;
1558 }
1559
1560 // ordinary field: use full name to accommodate overloading
1561 if ( memberDecl->get_mangleName() == declWithType->get_mangleName() )
1562 return i;
1563 else
1564 continue;
1565 }
1566 return -1;
1567 }
1568
1569 /// Returns an index expression into the offset array for a type
1570 Expression *makeOffsetIndex( Type const *objectType, long i ) {
1571 ConstantExpr *fieldIndex = new ConstantExpr( Constant::from_ulong( i ) );
1572 UntypedExpr *fieldOffset = new UntypedExpr( new NameExpr( "?[?]" ) );
1573 fieldOffset->get_args().push_back( new NameExpr( offsetofName( mangleType( objectType ) ) ) );
1574 fieldOffset->get_args().push_back( fieldIndex );
1575 return fieldOffset;
1576 }
1577
1578 Expression *PolyGenericCalculator::postmutate( MemberExpr *memberExpr ) {
1579 // only mutate member expressions for polymorphic types
1580 int tyDepth;
1581 Type *objectType = hasPolyBase( memberExpr->aggregate->result, scopeTyVars, &tyDepth );
1582 if ( ! objectType ) return memberExpr;
1583 findGeneric( objectType ); // ensure layout for this type is available
1584
1585 // replace member expression with dynamically-computed layout expression
1586 Expression *newMemberExpr = nullptr;
1587 if ( StructInstType *structType = dynamic_cast< StructInstType* >( objectType ) ) {
1588 // look up offset index
1589 long i = findMember( memberExpr->member, structType->baseStruct->members );
1590 if ( i == -1 ) return memberExpr;
1591
1592 // replace member expression with pointer to base plus offset
1593 UntypedExpr *fieldLoc = new UntypedExpr( new NameExpr( "?+?" ) );
1594 Expression * aggr = memberExpr->aggregate->clone();
1595 delete aggr->env; // xxx - there's a problem with keeping the env for some reason, so for now just get rid of it
1596 aggr->env = nullptr;
1597 fieldLoc->get_args().push_back( aggr );
1598 fieldLoc->get_args().push_back( makeOffsetIndex( objectType, i ) );
1599 fieldLoc->set_result( memberExpr->result->clone() );
1600 newMemberExpr = fieldLoc;
1601 } else if ( dynamic_cast< UnionInstType* >( objectType ) ) {
1602 // union members are all at offset zero, so just use the aggregate expr
1603 Expression * aggr = memberExpr->aggregate->clone();
1604 delete aggr->env; // xxx - there's a problem with keeping the env for some reason, so for now just get rid of it
1605 aggr->env= nullptr;
1606 newMemberExpr = aggr;
1607 newMemberExpr->result = memberExpr->result->clone();
1608 } else return memberExpr;
1609 assert( newMemberExpr );
1610
1611 // 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.
1612 // forall(otype T) struct Box { T x; }
1613 // forall(otype T) f() {
1614 // Box(T *) b; b.x;
1615 // }
1616 // 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.
1617 Type *memberType = memberExpr->member->get_type()->clone();
1618 TypeSubstitution sub = objectType->genericSubstitution();
1619 sub.apply( memberType );
1620 if ( ! isPolyType( memberType, scopeTyVars ) ) {
1621 // 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
1622 CastExpr *ptrCastExpr = new CastExpr( newMemberExpr, new PointerType( Type::Qualifiers(), memberType->clone() ) );
1623 UntypedExpr *derefExpr = UntypedExpr::createDeref( ptrCastExpr );
1624 newMemberExpr = derefExpr;
1625 }
1626
1627 delete memberType;
1628 delete memberExpr;
1629 return newMemberExpr;
1630 }
1631
1632 void PolyGenericCalculator::premutate( AddressExpr * addrExpr ) {
1633 GuardValue( addrMember );
1634 // is the argument a MemberExpr before mutating?
1635 addrMember = dynamic_cast< MemberExpr * >( addrExpr->arg );
1636 }
1637
1638 Expression * PolyGenericCalculator::postmutate( AddressExpr * addrExpr ) {
1639 if ( addrMember && addrMember != addrExpr->arg ) {
1640 // arg was a MemberExpr and has been mutated
1641 if ( UntypedExpr * untyped = dynamic_cast< UntypedExpr * >( addrExpr->arg ) ) {
1642 if ( InitTweak::getFunctionName( untyped ) == "?+?" ) {
1643 // MemberExpr was converted to pointer+offset, and it is not valid C to take the address of an addition, so strip the address-of
1644 // TODO: should addrExpr->arg->result be changed to addrExpr->result?
1645 Expression * ret = addrExpr->arg;
1646 addrExpr->arg = nullptr;
1647 std::swap( addrExpr->env, ret->env );
1648 delete addrExpr;
1649 return ret;
1650 }
1651 }
1652 }
1653 return addrExpr;
1654 }
1655
1656 ObjectDecl *PolyGenericCalculator::makeVar( const std::string &name, Type *type, Initializer *init ) {
1657 ObjectDecl *newObj = new ObjectDecl( name, Type::StorageClasses(), LinkageSpec::C, nullptr, type, init );
1658 stmtsToAddBefore.push_back( new DeclStmt( newObj ) );
1659 return newObj;
1660 }
1661
1662 void PolyGenericCalculator::addOtypeParamsToLayoutCall( UntypedExpr *layoutCall, const std::list< Type* > &otypeParams ) {
1663 for ( Type * const param : otypeParams ) {
1664 if ( findGeneric( param ) ) {
1665 // push size/align vars for a generic parameter back
1666 std::string paramName = mangleType( param );
1667 layoutCall->get_args().push_back( new NameExpr( sizeofName( paramName ) ) );
1668 layoutCall->get_args().push_back( new NameExpr( alignofName( paramName ) ) );
1669 } else {
1670 layoutCall->get_args().push_back( new SizeofExpr( param->clone() ) );
1671 layoutCall->get_args().push_back( new AlignofExpr( param->clone() ) );
1672 }
1673 }
1674 }
1675
1676 /// returns true if any of the otype parameters have a dynamic layout and puts all otype parameters in the output list
1677 bool findGenericParams( std::list< TypeDecl* > const &baseParams, std::list< Expression* > const &typeParams, std::list< Type* > &out ) {
1678 bool hasDynamicLayout = false;
1679
1680 for ( auto paramPair : group_iterate( baseParams, typeParams ) ) {
1681 TypeDecl * baseParam = std::get<0>( paramPair );
1682 Expression * typeParam = std::get<1>( paramPair );
1683 // skip non-otype parameters
1684 if ( ! baseParam->isComplete() ) continue;
1685 TypeExpr *typeExpr = dynamic_cast< TypeExpr* >( typeParam );
1686 assert( typeExpr && "all otype parameters should be type expressions" );
1687
1688 Type *type = typeExpr->get_type();
1689 out.push_back( type );
1690 if ( isPolyType( type ) ) hasDynamicLayout = true;
1691 }
1692
1693 return hasDynamicLayout;
1694 }
1695
1696 bool PolyGenericCalculator::findGeneric( Type const *ty ) {
1697 ty = replaceTypeInst( ty, env );
1698
1699 if ( auto typeInst = dynamic_cast< TypeInstType const * >( ty ) ) {
1700 if ( scopeTyVars.find( typeInst->get_name() ) != scopeTyVars.end() ) {
1701 // NOTE assumes here that getting put in the scopeTyVars included having the layout variables set
1702 return true;
1703 }
1704 return false;
1705 } else if ( auto structTy = dynamic_cast< StructInstType const * >( ty ) ) {
1706 // check if this type already has a layout generated for it
1707 std::string typeName = mangleType( ty );
1708 if ( knownLayouts.find( typeName ) != knownLayouts.end() ) return true;
1709
1710 // check if any of the type parameters have dynamic layout; if none do, this type is (or will be) monomorphized
1711 std::list< Type* > otypeParams;
1712 if ( ! findGenericParams( *structTy->get_baseParameters(), structTy->parameters, otypeParams ) ) return false;
1713
1714 // insert local variables for layout and generate call to layout function
1715 knownLayouts.insert( typeName ); // done early so as not to interfere with the later addition of parameters to the layout call
1716 Type *layoutType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
1717
1718 int n_members = structTy->get_baseStruct()->get_members().size();
1719 if ( n_members == 0 ) {
1720 // all empty structs have the same layout - size 1, align 1
1721 makeVar( sizeofName( typeName ), layoutType, new SingleInit( new ConstantExpr( Constant::from_ulong( (unsigned long)1 ) ) ) );
1722 makeVar( alignofName( typeName ), layoutType->clone(), new SingleInit( new ConstantExpr( Constant::from_ulong( (unsigned long)1 ) ) ) );
1723 // NOTE zero-length arrays are forbidden in C, so empty structs have no offsetof array
1724 } else {
1725 ObjectDecl *sizeVar = makeVar( sizeofName( typeName ), layoutType );
1726 ObjectDecl *alignVar = makeVar( alignofName( typeName ), layoutType->clone() );
1727 ObjectDecl *offsetVar = makeVar( offsetofName( typeName ), new ArrayType( Type::Qualifiers(), layoutType->clone(), new ConstantExpr( Constant::from_int( n_members ) ), false, false ) );
1728
1729 // generate call to layout function
1730 UntypedExpr *layoutCall = new UntypedExpr( new NameExpr( layoutofName( structTy->get_baseStruct() ) ) );
1731 layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( sizeVar ) ) );
1732 layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( alignVar ) ) );
1733 layoutCall->get_args().push_back( new VariableExpr( offsetVar ) );
1734 addOtypeParamsToLayoutCall( layoutCall, otypeParams );
1735
1736 stmtsToAddBefore.push_back( new ExprStmt( layoutCall ) );
1737 }
1738
1739 // std::cout << "TRUE 2" << std::endl;
1740
1741 return true;
1742 } else if ( auto unionTy = dynamic_cast< UnionInstType const * >( ty ) ) {
1743 // check if this type already has a layout generated for it
1744 std::string typeName = mangleType( ty );
1745 if ( knownLayouts.find( typeName ) != knownLayouts.end() ) return true;
1746
1747 // check if any of the type parameters have dynamic layout; if none do, this type is (or will be) monomorphized
1748 std::list< Type* > otypeParams;
1749 if ( ! findGenericParams( *unionTy->get_baseParameters(), unionTy->parameters, otypeParams ) ) return false;
1750
1751 // insert local variables for layout and generate call to layout function
1752 knownLayouts.insert( typeName ); // done early so as not to interfere with the later addition of parameters to the layout call
1753 Type *layoutType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
1754
1755 ObjectDecl *sizeVar = makeVar( sizeofName( typeName ), layoutType );
1756 ObjectDecl *alignVar = makeVar( alignofName( typeName ), layoutType->clone() );
1757
1758 // generate call to layout function
1759 UntypedExpr *layoutCall = new UntypedExpr( new NameExpr( layoutofName( unionTy->get_baseUnion() ) ) );
1760 layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( sizeVar ) ) );
1761 layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( alignVar ) ) );
1762 addOtypeParamsToLayoutCall( layoutCall, otypeParams );
1763
1764 stmtsToAddBefore.push_back( new ExprStmt( layoutCall ) );
1765
1766 return true;
1767 }
1768
1769 return false;
1770 }
1771
1772 Expression * PolyGenericCalculator::genSizeof( Type* ty ) {
1773 if ( ArrayType * aty = dynamic_cast<ArrayType *>(ty) ) {
1774 // generate calculated size for possibly generic array
1775 Expression * sizeofBase = genSizeof( aty->get_base() );
1776 if ( ! sizeofBase ) return nullptr;
1777 Expression * dim = aty->get_dimension();
1778 aty->set_dimension( nullptr );
1779 return makeOp( "?*?", sizeofBase, dim );
1780 } else if ( findGeneric( ty ) ) {
1781 // generate calculated size for generic type
1782 return new NameExpr( sizeofName( mangleType( ty ) ) );
1783 } else return nullptr;
1784 }
1785
1786 Expression *PolyGenericCalculator::postmutate( SizeofExpr *sizeofExpr ) {
1787 Type *ty = sizeofExpr->get_isType() ?
1788 sizeofExpr->get_type() : sizeofExpr->get_expr()->get_result();
1789
1790 Expression * gen = genSizeof( ty );
1791 if ( gen ) {
1792 delete sizeofExpr;
1793 return gen;
1794 } else return sizeofExpr;
1795 }
1796
1797 Expression *PolyGenericCalculator::postmutate( AlignofExpr *alignofExpr ) {
1798 Type *ty = alignofExpr->get_isType() ? alignofExpr->get_type() : alignofExpr->get_expr()->get_result();
1799 if ( findGeneric( ty ) ) {
1800 Expression *ret = new NameExpr( alignofName( mangleType( ty ) ) );
1801 delete alignofExpr;
1802 return ret;
1803 }
1804 return alignofExpr;
1805 }
1806
1807 Expression *PolyGenericCalculator::postmutate( OffsetofExpr *offsetofExpr ) {
1808 // only mutate expressions for polymorphic structs/unions
1809 Type *ty = offsetofExpr->get_type();
1810 if ( ! findGeneric( ty ) ) return offsetofExpr;
1811
1812 if ( StructInstType *structType = dynamic_cast< StructInstType* >( ty ) ) {
1813 // replace offsetof expression by index into offset array
1814 long i = findMember( offsetofExpr->get_member(), structType->get_baseStruct()->get_members() );
1815 if ( i == -1 ) return offsetofExpr;
1816
1817 Expression *offsetInd = makeOffsetIndex( ty, i );
1818 delete offsetofExpr;
1819 return offsetInd;
1820 } else if ( dynamic_cast< UnionInstType* >( ty ) ) {
1821 // all union members are at offset zero
1822 delete offsetofExpr;
1823 return new ConstantExpr( Constant::from_ulong( 0 ) );
1824 } else return offsetofExpr;
1825 }
1826
1827 Expression *PolyGenericCalculator::postmutate( OffsetPackExpr *offsetPackExpr ) {
1828 StructInstType *ty = offsetPackExpr->get_type();
1829
1830 Expression *ret = 0;
1831 if ( findGeneric( ty ) ) {
1832 // pull offset back from generated type information
1833 ret = new NameExpr( offsetofName( mangleType( ty ) ) );
1834 } else {
1835 std::string offsetName = offsetofName( mangleType( ty ) );
1836 if ( knownOffsets.find( offsetName ) != knownOffsets.end() ) {
1837 // use the already-generated offsets for this type
1838 ret = new NameExpr( offsetName );
1839 } else {
1840 knownOffsets.insert( offsetName );
1841
1842 std::list< Declaration* > &baseMembers = ty->get_baseStruct()->get_members();
1843 Type *offsetType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
1844
1845 // build initializer list for offset array
1846 std::list< Initializer* > inits;
1847 for ( Declaration * const member : baseMembers ) {
1848 DeclarationWithType *memberDecl = dynamic_cast< DeclarationWithType* >( member );
1849 assertf( memberDecl, "Requesting offset of Non-DWT member: %s", toString( member ).c_str() );
1850 inits.push_back( new SingleInit( new OffsetofExpr( ty->clone(), memberDecl ) ) );
1851 }
1852
1853 // build the offset array and replace the pack with a reference to it
1854 ObjectDecl *offsetArray = makeVar( offsetName, new ArrayType( Type::Qualifiers(), offsetType, new ConstantExpr( Constant::from_ulong( baseMembers.size() ) ), false, false ),
1855 new ListInit( inits ) );
1856 ret = new VariableExpr( offsetArray );
1857 }
1858 }
1859
1860 delete offsetPackExpr;
1861 return ret;
1862 }
1863
1864 void PolyGenericCalculator::beginScope() {
1865 knownLayouts.beginScope();
1866 knownOffsets.beginScope();
1867 }
1868
1869 void PolyGenericCalculator::endScope() {
1870 knownLayouts.endScope();
1871 knownOffsets.endScope();
1872 }
1873
1874////////////////////////////////////////// Eraser ///////////////////////////////////////////////
1875
1876 void Eraser::premutate( ObjectDecl * objectDecl ) {
1877 ScrubTyVars::scrubAll( objectDecl );
1878 }
1879
1880 void Eraser::premutate( FunctionDecl * functionDecl ) {
1881 ScrubTyVars::scrubAll( functionDecl );
1882 }
1883
1884 void Eraser::premutate( TypedefDecl * typedefDecl ) {
1885 ScrubTyVars::scrubAll( typedefDecl );
1886 }
1887
1888 /// Strips the members from a generic aggregate
1889 static void stripGenericMembers( AggregateDecl * decl ) {
1890 if ( ! decl->parameters.empty() ) decl->members.clear();
1891 }
1892
1893 void Eraser::premutate( StructDecl * structDecl ) {
1894 stripGenericMembers( structDecl );
1895 }
1896
1897 void Eraser::premutate( UnionDecl * unionDecl ) {
1898 stripGenericMembers( unionDecl );
1899 }
1900 } // anonymous namespace
1901} // namespace GenPoly
1902
1903// Local Variables: //
1904// tab-width: 4 //
1905// mode: c++ //
1906// compile-command: "make install" //
1907// End: //
Note: See TracBrowser for help on using the repository browser.