source: src/GenPoly/Box.cc@ dd46fd3

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

Cleaning old box pass for easier translation. I believe I have an explination for why the confusing loop works.

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