source: src/GenPoly/Box.cc@ e3bf4cf

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

Cleaning old box pass for easier translation. Used isInFunction() to simplify LayoutFunctionBuilder.

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