source: src/GenPoly/Box.cc@ 1553a55

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

Cleaning old box pass for easier translation. Cleaned up more loops, particularly with the improved group_iterate.

  • Property mode set to 100644
File size: 86.8 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 const *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 /// 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< DeclarationWithType *> &paramList = functionType->parameters;
491 std::list< FunctionType const *> functions;
492 for ( TypeDecl * const tyVar : functionType->forall ) {
493 for ( DeclarationWithType * const assert : tyVar->assertions ) {
494 findFunction( assert->get_type(), functions, scopeTyVars, needsAdapter );
495 } // for
496 } // for
497 for ( DeclarationWithType * const arg : paramList ) {
498 findFunction( arg->get_type(), functions, scopeTyVars, needsAdapter );
499 } // for
500
501 for ( FunctionType const * const funType : functions ) {
502 std::string mangleName = mangleAdapterName( funType, scopeTyVars );
503 if ( adapters.find( mangleName ) == adapters.end() ) {
504 std::string adapterName = makeAdapterName( mangleName );
505 adapters.insert( std::pair< std::string, DeclarationWithType *>( mangleName, new ObjectDecl( adapterName, Type::StorageClasses(), LinkageSpec::C, nullptr, new PointerType( Type::Qualifiers(), makeAdapterType( funType, scopeTyVars ) ), nullptr ) ) );
506 } // if
507 } // for
508 // std::cerr << "end function: " << functionDecl->get_mangleName() << std::endl;
509 } // if
510 }
511
512 void Pass1::premutate( TypeDecl *typeDecl ) {
513 addToTyVarMap( typeDecl, scopeTyVars );
514 }
515
516 void Pass1::premutate( CommaExpr *commaExpr ) {
517 // Attempting to find application expressions that were mutated by the copy constructor passes
518 // to use an explicit return variable, so that the variable can be reused as a parameter to the
519 // call rather than creating a new temp variable. Previously this step was an optimization, but
520 // with the introduction of tuples and UniqueExprs, it is necessary to ensure that they use the same variable.
521 // Essentially, looking for pattern: (x=f(...), x)
522 // To compound the issue, the right side can be *x, etc. because of lvalue-returning functions
523 if ( UntypedExpr * assign = dynamic_cast< UntypedExpr * >( commaExpr->get_arg1() ) ) {
524 if ( CodeGen::isAssignment( InitTweak::getFunctionName( assign ) ) ) {
525 assert( assign->get_args().size() == 2 );
526 if ( ApplicationExpr * appExpr = dynamic_cast< ApplicationExpr * > ( assign->get_args().back() ) ) {
527 // first argument is assignable, so it must be an lvalue, so it should be legal to take its address.
528 retVals[appExpr] = assign->get_args().front();
529 }
530 }
531 }
532 }
533
534 void Pass1::passArgTypeVars( ApplicationExpr *appExpr, Type *parmType, Type *argBaseType, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars, std::set< std::string > &seenTypes ) {
535 Type *polyType = isPolyType( parmType, exprTyVars );
536 if ( polyType && ! dynamic_cast< TypeInstType* >( polyType ) ) {
537 std::string typeName = mangleType( polyType );
538 if ( seenTypes.count( typeName ) ) return;
539
540 arg = appExpr->get_args().insert( arg, new SizeofExpr( argBaseType->clone() ) );
541 arg++;
542 arg = appExpr->get_args().insert( arg, new AlignofExpr( argBaseType->clone() ) );
543 arg++;
544 if ( dynamic_cast< StructInstType* >( polyType ) ) {
545 if ( StructInstType *argBaseStructType = dynamic_cast< StructInstType* >( argBaseType ) ) {
546 // zero-length arrays are forbidden by C, so don't pass offset for empty struct
547 if ( ! argBaseStructType->get_baseStruct()->get_members().empty() ) {
548 arg = appExpr->get_args().insert( arg, new OffsetPackExpr( argBaseStructType->clone() ) );
549 arg++;
550 }
551 } else {
552 SemanticError( argBaseType, "Cannot pass non-struct type for generic struct: " );
553 }
554 }
555
556 seenTypes.insert( typeName );
557 }
558 }
559
560 std::list< Expression *>::iterator Pass1::passTypeVars( ApplicationExpr *appExpr, Type *polyRetType, const TyVarMap &exprTyVars ) {
561 assert( env );
562 std::list< Expression *>::iterator arg = appExpr->args.begin();
563 // pass size/align for type variables
564 for ( std::pair<std::string, TypeDecl::Data> const & tyParam : exprTyVars ) {
565 ResolvExpr::EqvClass eqvClass;
566 if ( tyParam.second.isComplete ) {
567 Type *concrete = env->lookup( tyParam.first );
568 // If there is an unbound type variable, it should have detected already.
569 assertf( concrete, "Unbound type variable: %s in: %s",
570 toCString( tyParam.first ), toCString( *env ) );
571
572 arg = appExpr->get_args().insert( arg, new SizeofExpr( concrete->clone() ) );
573 arg++;
574 arg = appExpr->get_args().insert( arg, new AlignofExpr( concrete->clone() ) );
575 arg++;
576 } // if
577 } // for
578
579 // add size/align for generic types to parameter list
580 if ( ! appExpr->get_function()->result ) return arg;
581 FunctionType *funcType = getFunctionType( appExpr->get_function()->get_result() );
582 assert( funcType );
583
584 // These iterators don't advance in unison.
585 std::list< DeclarationWithType* >::const_iterator fnParm = funcType->get_parameters().begin();
586 std::list< Expression* >::const_iterator fnArg = arg;
587 std::set< std::string > seenTypes; ///< names for generic types we've seen
588
589 // a polymorphic return type may need to be added to the argument list
590 if ( polyRetType ) {
591 Type *concRetType = replaceWithConcrete( polyRetType, env );
592 passArgTypeVars( appExpr, polyRetType, concRetType, arg, exprTyVars, seenTypes );
593 ++fnArg; // skip the return parameter in the argument list
594 }
595
596 // add type information args for presently unseen types in parameter list
597 for ( ; fnParm != funcType->get_parameters().end() && fnArg != appExpr->get_args().end(); ++fnParm, ++fnArg ) {
598 if ( ! (*fnArg)->get_result() ) continue;
599 Type * argType = (*fnArg)->get_result();
600 passArgTypeVars( appExpr, (*fnParm)->get_type(), argType, arg, exprTyVars, seenTypes );
601 }
602 return arg;
603 }
604
605 ObjectDecl *Pass1::makeTemporary( Type *type ) {
606 ObjectDecl *newObj = new ObjectDecl( tempNamer.newName(), Type::StorageClasses(), LinkageSpec::C, 0, type, 0 );
607 stmtsToAddBefore.push_back( new DeclStmt( newObj ) );
608 return newObj;
609 }
610
611 Expression *Pass1::addRetParam( ApplicationExpr *appExpr, Type *retType ) {
612 // Create temporary to hold return value of polymorphic function and produce that temporary as a result
613 // using a comma expression.
614 assert( retType );
615
616 Expression * paramExpr = nullptr;
617 // try to use existing return value parameter if it exists, otherwise create a new temporary
618 if ( retVals.count( appExpr ) ) {
619 paramExpr = retVals[appExpr]->clone();
620 } else {
621 ObjectDecl *newObj = makeTemporary( retType->clone() );
622 paramExpr = new VariableExpr( newObj );
623 }
624 Expression * retExpr = paramExpr->clone();
625
626 // If the type of the temporary is not polymorphic, box temporary by taking its address;
627 // otherwise the temporary is already boxed and can be used directly.
628 if ( ! isPolyType( paramExpr->get_result(), scopeTyVars, env ) ) {
629 paramExpr = new AddressExpr( paramExpr );
630 } // if
631 // Add argument to function call.
632 appExpr->args.push_front( paramExpr );
633 // Build a comma expression to call the function and emulate a normal return.
634 CommaExpr *commaExpr = new CommaExpr( appExpr, retExpr );
635 commaExpr->env = appExpr->env;
636 appExpr->env = nullptr;
637 return commaExpr;
638 }
639
640 /// Replaces all the type parameters of a generic type with their concrete equivalents under the current environment
641 void replaceParametersWithConcrete( std::list< Expression* >& params, TypeSubstitution const * env ) {
642 for ( Expression * const param : params ) {
643 TypeExpr *paramType = dynamic_cast< TypeExpr* >( param );
644 assertf(paramType, "Aggregate parameters should be type expressions");
645 paramType->set_type( replaceWithConcrete( paramType->get_type(), env, false ) );
646 }
647 }
648
649 // See forward definition.
650 Type *replaceWithConcrete( Type *type, TypeSubstitution const * env, bool doClone ) {
651 assert( env );
652 if ( TypeInstType *typeInst = dynamic_cast< TypeInstType * >( type ) ) {
653 Type *concrete = env->lookup( typeInst->get_name() );
654 if ( concrete == 0 ) {
655 return typeInst;
656 } // if
657 return concrete;
658 } else if ( StructInstType *structType = dynamic_cast< StructInstType* >( type ) ) {
659 if ( doClone ) {
660 structType = structType->clone();
661 }
662 replaceParametersWithConcrete( structType->get_parameters(), env );
663 return structType;
664 } else if ( UnionInstType *unionType = dynamic_cast< UnionInstType* >( type ) ) {
665 if ( doClone ) {
666 unionType = unionType->clone();
667 }
668 replaceParametersWithConcrete( unionType->get_parameters(), env );
669 return unionType;
670 }
671 return type;
672 }
673
674 Expression *Pass1::addDynRetParam( ApplicationExpr *appExpr, Type *dynType ) {
675 Type *concrete = replaceWithConcrete( dynType, env );
676 // add out-parameter for return value
677 return addRetParam( appExpr, concrete );
678 }
679
680 Expression *Pass1::applyAdapter( ApplicationExpr *appExpr, FunctionType *function ) {
681 Expression *ret = appExpr;
682// if ( ! function->get_returnVals().empty() && isPolyType( function->get_returnVals().front()->get_type(), tyVars ) ) {
683 if ( isDynRet( function, scopeTyVars ) ) {
684 ret = addRetParam( appExpr, function->returnVals.front()->get_type() );
685 } // if
686 std::string mangleName = mangleAdapterName( function, scopeTyVars );
687 std::string adapterName = makeAdapterName( mangleName );
688
689 // cast adaptee to void (*)(), since it may have any type inside a polymorphic function
690 Type * adapteeType = new PointerType( Type::Qualifiers(), new FunctionType( Type::Qualifiers(), true ) );
691 appExpr->get_args().push_front( new CastExpr( appExpr->function, adapteeType ) );
692 appExpr->set_function( new NameExpr( adapterName ) ); // xxx - result is never set on NameExpr
693
694 return ret;
695 }
696
697 // find instances of polymorphic type parameters
698 struct PolyFinder {
699 const TyVarMap * tyVars = nullptr;
700 bool found = false;
701
702 void previsit( TypeInstType * t ) {
703 if ( isPolyType( t, *tyVars ) ) {
704 found = true;
705 }
706 }
707 };
708
709 // true if there is an instance of a polymorphic type parameter in t
710 bool hasPolymorphism( Type * t, const TyVarMap &tyVars ) {
711 PassVisitor<PolyFinder> finder;
712 finder.pass.tyVars = &tyVars;
713 maybeAccept( t, finder );
714 return finder.pass.found;
715 }
716
717 /// cast parameters to polymorphic functions so that types are replaced with
718 /// void * if they are type parameters in the formal type.
719 /// this gets rid of warnings from gcc.
720 void addCast( Expression *&actual, Type *formal, const TyVarMap &tyVars ) {
721 // type contains polymorphism, but isn't exactly a polytype, in which case it
722 // has some real actual type (e.g. unsigned int) and casting to void * is wrong
723 if ( hasPolymorphism( formal, tyVars ) && ! isPolyType( formal, tyVars ) ) {
724 Type * newType = formal->clone();
725 newType = ScrubTyVars::scrub( newType, tyVars );
726 actual = new CastExpr( actual, newType );
727 } // if
728 }
729
730 void Pass1::boxParam( Expression *&arg, Type *param, const TyVarMap &exprTyVars ) {
731 assertf( arg->result, "arg does not have result: %s", toString( arg ).c_str() );
732 addCast( arg, param, exprTyVars );
733 if ( ! needsBoxing( param, arg->result, exprTyVars, env ) ) return;
734
735 if ( arg->get_lvalue() ) {
736 // argument expression may be CFA lvalue, but not C lvalue -- apply generalizedLvalue transformations.
737 // if ( VariableExpr * varExpr = dynamic_cast< VariableExpr * >( arg ) ) {
738 // if ( dynamic_cast<ArrayType *>( varExpr->var->get_type() ) ){
739 // // temporary hack - don't box arrays, because &arr is not the same as &arr[0]
740 // return;
741 // }
742 // }
743 arg = generalizedLvalue( new AddressExpr( arg ) );
744 if ( ! ResolvExpr::typesCompatible( param, arg->get_result(), SymTab::Indexer() ) ) {
745 // silence warnings by casting boxed parameters when the actual type does not match up with the formal type.
746 arg = new CastExpr( arg, param->clone() );
747 }
748 } else {
749 // use type computed in unification to declare boxed variables
750 Type * newType = param->clone();
751 if ( env ) env->apply( newType );
752 ObjectDecl *newObj = makeTemporary( newType );
753 // TODO: is this right??? (Why wouldn't it be?)
754 newObj->get_type()->get_qualifiers() = Type::Qualifiers();
755 // TODO: why doesn't this just use initialization syntax?
756 // (Possibly to ensure code is run at the right time.)
757 UntypedExpr *assign = new UntypedExpr( new NameExpr( "?=?" ) );
758 assign->get_args().push_back( new VariableExpr( newObj ) );
759 assign->get_args().push_back( arg );
760 stmtsToAddBefore.push_back( new ExprStmt( assign ) );
761 arg = new AddressExpr( new VariableExpr( newObj ) );
762 } // if
763 }
764
765 void Pass1::boxParams( ApplicationExpr *appExpr, std::list< Expression *>::iterator arg, FunctionType *function, const TyVarMap &exprTyVars ) {
766 for ( DeclarationWithType * param : function->parameters ) {
767 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() );
768 boxParam( *arg, param->get_type(), exprTyVars );
769 ++arg;
770 } // for
771 }
772
773 void Pass1::addInferredParams( ApplicationExpr *appExpr, std::list< Expression *>::iterator arg, FunctionType *functionType, const TyVarMap &tyVars ) {
774 std::list< Expression *>::iterator cur = arg;
775 for ( TypeDecl * const tyVar : functionType->forall ) {
776 for ( DeclarationWithType * const assert : tyVar->assertions ) {
777 InferredParams::const_iterator inferParam = appExpr->inferParams.find( assert->get_uniqueId() );
778 assertf( inferParam != appExpr->inferParams.end(), "addInferredParams missing inferred parameter: %s in: %s", toString( assert ).c_str(), toString( appExpr ).c_str() );
779 Expression *newExpr = inferParam->second.expr->clone();
780 boxParam( newExpr, assert->get_type(), tyVars );
781 appExpr->get_args().insert( cur, newExpr );
782 } // for
783 } // for
784 }
785
786 void makeRetParm( FunctionType *funcType ) {
787 DeclarationWithType *retParm = funcType->returnVals.front();
788
789 // make a new parameter that is a pointer to the type of the old return value
790 retParm->set_type( new PointerType( Type::Qualifiers(), retParm->get_type() ) );
791 funcType->get_parameters().push_front( retParm );
792
793 // we don't need the return value any more
794 funcType->get_returnVals().clear();
795 }
796
797 FunctionType *makeAdapterType( FunctionType const *adaptee, const TyVarMap &tyVars ) {
798 // actually make the adapter type
799 FunctionType *adapter = adaptee->clone();
800 if ( isDynRet( adapter, tyVars ) ) {
801 makeRetParm( adapter );
802 } // if
803 adapter->get_parameters().push_front( new ObjectDecl( "", Type::StorageClasses(), LinkageSpec::C, 0, new PointerType( Type::Qualifiers(), new FunctionType( Type::Qualifiers(), true ) ), 0 ) );
804 return adapter;
805 }
806
807 Expression *makeAdapterArg(
808 DeclarationWithType *param,
809 DeclarationWithType const *arg,
810 DeclarationWithType const *realParam,
811 const TyVarMap &tyVars ) {
812 assert( param );
813 assert( arg );
814 if ( isPolyType( realParam->get_type(), tyVars )
815 && ! isPolyType( arg->get_type() ) ) {
816 UntypedExpr *deref = new UntypedExpr( new NameExpr( "*?" ) );
817 deref->args.push_back( new CastExpr( new VariableExpr( param ), new PointerType( Type::Qualifiers(), arg->get_type()->clone() ) ) );
818 deref->result = arg->get_type()->clone();
819 return deref;
820 } // if
821 return new VariableExpr( param );
822 }
823
824 void addAdapterParams(
825 ApplicationExpr *adapteeApp,
826 std::list< DeclarationWithType *>::const_iterator arg,
827 std::list< DeclarationWithType *>::const_iterator param,
828 std::list< DeclarationWithType *>::const_iterator paramEnd,
829 std::list< DeclarationWithType *>::const_iterator realParam,
830 const TyVarMap &tyVars ) {
831 UniqueName paramNamer( "_p" );
832 for ( ; param != paramEnd; ++param, ++arg, ++realParam ) {
833 if ( (*param)->get_name() == "" ) {
834 (*param)->set_name( paramNamer.newName() );
835 (*param)->set_linkage( LinkageSpec::C );
836 } // if
837 adapteeApp->get_args().push_back( makeAdapterArg( *param, *arg, *realParam, tyVars ) );
838 } // for
839 }
840
841 FunctionDecl *Pass1::makeAdapter( FunctionType const *adaptee, FunctionType *realType, const std::string &mangleName, const TyVarMap &tyVars ) {
842 FunctionType *adapterType = makeAdapterType( adaptee, tyVars );
843 adapterType = ScrubTyVars::scrub( adapterType, tyVars );
844 DeclarationWithType *adapteeDecl = adapterType->get_parameters().front();
845 adapteeDecl->set_name( "_adaptee" );
846 // do not carry over attributes to real type parameters/return values
847 for ( DeclarationWithType * dwt : realType->parameters ) {
848 deleteAll( dwt->get_type()->attributes );
849 dwt->get_type()->attributes.clear();
850 }
851 for ( DeclarationWithType * dwt : realType->returnVals ) {
852 deleteAll( dwt->get_type()->attributes );
853 dwt->get_type()->attributes.clear();
854 }
855 ApplicationExpr *adapteeApp = new ApplicationExpr( new CastExpr( new VariableExpr( adapteeDecl ), new PointerType( Type::Qualifiers(), realType ) ) );
856 Statement *bodyStmt;
857
858 for ( auto tys : group_iterate( realType->forall, adapterType->forall, adaptee->forall ) ) {
859 TypeDecl * tyArg = std::get<0>( tys );
860 TypeDecl * tyParam = std::get<1>( tys );
861 TypeDecl * realTyParam = std::get<2>( tys );
862 for ( auto asserts : group_iterate( tyArg->assertions, tyParam->assertions, realTyParam->assertions ) ) {
863 DeclarationWithType * assertArg = std::get<0>( asserts );
864 DeclarationWithType * assertParam = std::get<1>( asserts );
865 DeclarationWithType * realAssertParam = std::get<2>( asserts );
866 adapteeApp->args.push_back( makeAdapterArg( assertParam, assertArg, realAssertParam, tyVars ) );
867 } // for
868 } // for
869
870 std::list< DeclarationWithType *>::const_iterator arg = realType->parameters.begin();
871 std::list< DeclarationWithType *>::const_iterator param = adapterType->parameters.begin();
872 std::list< DeclarationWithType *>::const_iterator realParam = adaptee->parameters.begin();
873 param++; // skip adaptee parameter in the adapter type
874 if ( realType->get_returnVals().empty() ) {
875 // void return
876 addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
877 bodyStmt = new ExprStmt( adapteeApp );
878 } else if ( isDynType( adaptee->returnVals.front()->get_type(), tyVars ) ) {
879 // return type T
880 if ( (*param)->get_name() == "" ) {
881 (*param)->set_name( "_ret" );
882 (*param)->set_linkage( LinkageSpec::C );
883 } // if
884 UntypedExpr *assign = new UntypedExpr( new NameExpr( "?=?" ) );
885 UntypedExpr *deref = UntypedExpr::createDeref( new CastExpr( new VariableExpr( *param++ ), new PointerType( Type::Qualifiers(), realType->get_returnVals().front()->get_type()->clone() ) ) );
886 assign->get_args().push_back( deref );
887 addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
888 assign->get_args().push_back( adapteeApp );
889 bodyStmt = new ExprStmt( assign );
890 } else {
891 // adapter for a function that returns a monomorphic value
892 addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
893 bodyStmt = new ReturnStmt( adapteeApp );
894 } // if
895 CompoundStmt *adapterBody = new CompoundStmt();
896 adapterBody->get_kids().push_back( bodyStmt );
897 std::string adapterName = makeAdapterName( mangleName );
898 return new FunctionDecl( adapterName, Type::StorageClasses(), LinkageSpec::C, adapterType, adapterBody );
899 }
900
901 void Pass1::passAdapters( ApplicationExpr * appExpr, FunctionType * functionType, const TyVarMap & exprTyVars ) {
902 // collect a list of function types passed as parameters or implicit parameters (assertions)
903 std::list<FunctionType const *> functions;
904 for ( TypeDecl * const tyVar : functionType->get_forall() ) {
905 for ( DeclarationWithType * const assert : tyVar->get_assertions() ) {
906 findFunction( assert->get_type(), functions, exprTyVars, needsAdapter );
907 } // for
908 } // for
909 for ( DeclarationWithType * const arg : functionType->get_parameters() ) {
910 findFunction( arg->get_type(), functions, exprTyVars, needsAdapter );
911 } // for
912
913 // parameter function types for which an appropriate adapter has been generated. we cannot use the types
914 // after applying substitutions, since two different parameter types may be unified to the same type
915 std::set< std::string > adaptersDone;
916
917 for ( FunctionType const * const funType : functions ) {
918 FunctionType *originalFunction = funType->clone();
919 FunctionType *realFunction = funType->clone();
920 std::string mangleName = SymTab::Mangler::mangle( realFunction );
921
922 // only attempt to create an adapter or pass one as a parameter if we haven't already done so for this
923 // pre-substitution parameter function type.
924 if ( adaptersDone.find( mangleName ) == adaptersDone.end() ) {
925 adaptersDone.insert( adaptersDone.begin(), mangleName );
926
927 // apply substitution to type variables to figure out what the adapter's type should look like
928 assert( env );
929 env->apply( realFunction );
930 mangleName = SymTab::Mangler::mangle( realFunction );
931 mangleName += makePolyMonoSuffix( originalFunction, exprTyVars );
932
933 typedef ScopedMap< std::string, DeclarationWithType* >::iterator AdapterIter;
934 AdapterIter adapter = adapters.find( mangleName );
935 if ( adapter == adapters.end() ) {
936 // adapter has not been created yet in the current scope, so define it
937 FunctionDecl *newAdapter = makeAdapter( funType, realFunction, mangleName, exprTyVars );
938 std::pair< AdapterIter, bool > answer = adapters.insert( std::pair< std::string, DeclarationWithType *>( mangleName, newAdapter ) );
939 adapter = answer.first;
940 stmtsToAddBefore.push_back( new DeclStmt( newAdapter ) );
941 } // if
942 assert( adapter != adapters.end() );
943
944 // add the appropriate adapter as a parameter
945 appExpr->get_args().push_front( new VariableExpr( adapter->second ) );
946 } // if
947 } // for
948 } // passAdapters
949
950 Expression *makeIncrDecrExpr( ApplicationExpr *appExpr, Type *polyType, bool isIncr ) {
951 NameExpr *opExpr = new NameExpr( ( isIncr ) ? "?+=?" : "?-=?" );
952 UntypedExpr *addAssign = new UntypedExpr( opExpr );
953 if ( AddressExpr *address = dynamic_cast< AddressExpr *>( appExpr->get_args().front() ) ) {
954 addAssign->get_args().push_back( address->get_arg() );
955 } else {
956 addAssign->get_args().push_back( appExpr->get_args().front() );
957 } // if
958 addAssign->get_args().push_back( new NameExpr( sizeofName( mangleType( polyType ) ) ) );
959 addAssign->set_result( appExpr->get_result()->clone() );
960 if ( appExpr->get_env() ) {
961 addAssign->set_env( appExpr->get_env() );
962 appExpr->set_env( 0 );
963 } // if
964 appExpr->get_args().clear();
965 delete appExpr;
966 return addAssign;
967 }
968
969 Expression *Pass1::handleIntrinsics( ApplicationExpr *appExpr ) {
970 if ( VariableExpr *varExpr = dynamic_cast< VariableExpr *>( appExpr->function ) ) {
971 if ( varExpr->var->linkage == LinkageSpec::Intrinsic ) {
972 if ( varExpr->var->name == "?[?]" ) {
973 assert( appExpr->result );
974 assert( appExpr->get_args().size() == 2 );
975 Type *baseType1 = isPolyPtr( appExpr->args.front()->result, scopeTyVars, env );
976 Type *baseType2 = isPolyPtr( appExpr->args.back()->result, scopeTyVars, env );
977 assert( ! baseType1 || ! baseType2 ); // the arguments cannot both be polymorphic pointers
978 UntypedExpr *ret = 0;
979 if ( baseType1 || baseType2 ) { // one of the arguments is a polymorphic pointer
980 ret = new UntypedExpr( new NameExpr( "?+?" ) );
981 } // if
982 if ( baseType1 ) {
983 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
984 multiply->get_args().push_back( appExpr->get_args().back() );
985 multiply->get_args().push_back( new SizeofExpr( baseType1->clone() ) );
986 ret->get_args().push_back( appExpr->get_args().front() );
987 ret->get_args().push_back( multiply );
988 } else if ( baseType2 ) {
989 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
990 multiply->get_args().push_back( appExpr->get_args().front() );
991 multiply->get_args().push_back( new SizeofExpr( baseType2->clone() ) );
992 ret->get_args().push_back( multiply );
993 ret->get_args().push_back( appExpr->get_args().back() );
994 } // if
995 if ( baseType1 || baseType2 ) {
996 delete ret->get_result();
997 ret->set_result( appExpr->get_result()->clone() );
998 if ( appExpr->get_env() ) {
999 ret->set_env( appExpr->get_env() );
1000 appExpr->set_env( 0 );
1001 } // if
1002 appExpr->get_args().clear();
1003 delete appExpr;
1004 return ret;
1005 } // if
1006 } else if ( varExpr->get_var()->get_name() == "*?" ) {
1007 assert( appExpr->result );
1008 assert( ! appExpr->get_args().empty() );
1009 if ( isPolyType( appExpr->get_result(), scopeTyVars, env ) ) {
1010 // remove dereference from polymorphic types since they are boxed.
1011 Expression *ret = appExpr->get_args().front();
1012 // fix expr type to remove pointer
1013 delete ret->get_result();
1014 ret->set_result( appExpr->get_result()->clone() );
1015 if ( appExpr->get_env() ) {
1016 ret->set_env( appExpr->get_env() );
1017 appExpr->set_env( 0 );
1018 } // if
1019 appExpr->get_args().clear();
1020 delete appExpr;
1021 return ret;
1022 } // if
1023 } else if ( varExpr->get_var()->get_name() == "?++" || varExpr->get_var()->get_name() == "?--" ) {
1024 assert( appExpr->result );
1025 assert( appExpr->get_args().size() == 1 );
1026 if ( Type *baseType = isPolyPtr( appExpr->get_result(), scopeTyVars, env ) ) {
1027 Type *tempType = appExpr->get_result()->clone();
1028 if ( env ) {
1029 env->apply( tempType );
1030 } // if
1031 ObjectDecl *newObj = makeTemporary( tempType );
1032 VariableExpr *tempExpr = new VariableExpr( newObj );
1033 UntypedExpr *assignExpr = new UntypedExpr( new NameExpr( "?=?" ) );
1034 assignExpr->get_args().push_back( tempExpr->clone() );
1035 if ( AddressExpr *address = dynamic_cast< AddressExpr *>( appExpr->get_args().front() ) ) {
1036 assignExpr->get_args().push_back( address->get_arg()->clone() );
1037 } else {
1038 assignExpr->get_args().push_back( appExpr->get_args().front()->clone() );
1039 } // if
1040 CommaExpr *firstComma = new CommaExpr( assignExpr, makeIncrDecrExpr( appExpr, baseType, varExpr->get_var()->get_name() == "?++" ) );
1041 return new CommaExpr( firstComma, tempExpr );
1042 } // if
1043 } else if ( varExpr->get_var()->get_name() == "++?" || varExpr->get_var()->get_name() == "--?" ) {
1044 assert( appExpr->result );
1045 assert( appExpr->get_args().size() == 1 );
1046 if ( Type *baseType = isPolyPtr( appExpr->get_result(), scopeTyVars, env ) ) {
1047 return makeIncrDecrExpr( appExpr, baseType, varExpr->get_var()->get_name() == "++?" );
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() == 2 );
1052 Type *baseType1 = isPolyPtr( appExpr->get_args().front()->get_result(), scopeTyVars, env );
1053 Type *baseType2 = isPolyPtr( appExpr->get_args().back()->get_result(), scopeTyVars, env );
1054 if ( baseType1 && baseType2 ) {
1055 UntypedExpr *divide = new UntypedExpr( new NameExpr( "?/?" ) );
1056 divide->get_args().push_back( appExpr );
1057 divide->get_args().push_back( new SizeofExpr( baseType1->clone() ) );
1058 divide->set_result( appExpr->get_result()->clone() );
1059 if ( appExpr->get_env() ) {
1060 divide->set_env( appExpr->get_env() );
1061 appExpr->set_env( 0 );
1062 } // if
1063 return divide;
1064 } else if ( baseType1 ) {
1065 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1066 multiply->get_args().push_back( appExpr->get_args().back() );
1067 multiply->get_args().push_back( new SizeofExpr( baseType1->clone() ) );
1068 appExpr->get_args().back() = multiply;
1069 } else if ( baseType2 ) {
1070 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1071 multiply->get_args().push_back( appExpr->get_args().front() );
1072 multiply->get_args().push_back( new SizeofExpr( baseType2->clone() ) );
1073 appExpr->get_args().front() = multiply;
1074 } // if
1075 } else if ( varExpr->get_var()->get_name() == "?+=?" || varExpr->get_var()->get_name() == "?-=?" ) {
1076 assert( appExpr->result );
1077 assert( appExpr->get_args().size() == 2 );
1078 Type *baseType = isPolyPtr( appExpr->get_result(), scopeTyVars, env );
1079 if ( baseType ) {
1080 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1081 multiply->get_args().push_back( appExpr->get_args().back() );
1082 multiply->get_args().push_back( new SizeofExpr( baseType->clone() ) );
1083 appExpr->get_args().back() = multiply;
1084 } // if
1085 } // if
1086 return appExpr;
1087 } // if
1088 } // if
1089 return 0;
1090 }
1091
1092 Expression *Pass1::postmutate( ApplicationExpr *appExpr ) {
1093 // std::cerr << "mutate appExpr: " << InitTweak::getFunctionName( appExpr ) << std::endl;
1094 // for ( auto tyVar : scopeTyVars ) {
1095 // std::cerr << tyVar.first << " ";
1096 // }
1097 // std::cerr << "\n";
1098
1099 assert( appExpr->function->result );
1100 FunctionType * function = getFunctionType( appExpr->function->result );
1101 assertf( function, "ApplicationExpr has non-function type: %s", toString( appExpr->function->result ).c_str() );
1102
1103 if ( Expression *newExpr = handleIntrinsics( appExpr ) ) {
1104 return newExpr;
1105 } // if
1106
1107 Expression *ret = appExpr;
1108 std::list< Expression *>::iterator paramBegin = appExpr->get_args().begin();
1109
1110 TyVarMap exprTyVars( TypeDecl::Data{} );
1111 makeTyVarMap( function, exprTyVars ); // xxx - should this take into account the variables already bound in scopeTyVars (i.e. remove them from exprTyVars?)
1112 ReferenceToType *dynRetType = isDynRet( function, exprTyVars );
1113
1114 // std::cerr << function << std::endl;
1115 // std::cerr << "scopeTyVars: ";
1116 // printTyVarMap( std::cerr, scopeTyVars );
1117 // std::cerr << "exprTyVars: ";
1118 // printTyVarMap( std::cerr, exprTyVars );
1119 // std::cerr << "env: " << *env << std::endl;
1120 // std::cerr << needsAdapter( function, scopeTyVars ) << ! needsAdapter( function, exprTyVars) << std::endl;
1121
1122 // 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
1123 // passTypeVars needs to know the program-text return type (i.e. the distinction between _conc_T30 and T3(int))
1124 // concRetType may not be a good name in one or both of these places. A more appropriate name change is welcome.
1125 if ( dynRetType ) {
1126 // std::cerr << "dynRetType: " << dynRetType << std::endl;
1127 Type *concRetType = appExpr->get_result()->isVoid() ? nullptr : appExpr->get_result();
1128 ret = addDynRetParam( appExpr, concRetType ); // xxx - used to use dynRetType instead of concRetType
1129 } else if ( needsAdapter( function, scopeTyVars ) && ! needsAdapter( function, exprTyVars) ) { // xxx - exprTyVars is used above...?
1130 // 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.
1131
1132 // std::cerr << "needs adapter: ";
1133 // printTyVarMap( std::cerr, scopeTyVars );
1134 // std::cerr << *env << std::endl;
1135 // change the application so it calls the adapter rather than the passed function
1136 ret = applyAdapter( appExpr, function );
1137 } // if
1138
1139 Type *concRetType = replaceWithConcrete( dynRetType, env );
1140 std::list< Expression *>::iterator arg =
1141 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)
1142 addInferredParams( appExpr, arg, function, exprTyVars );
1143
1144 // This needs to point at the original first argument.
1145 boxParams( appExpr, paramBegin, function, exprTyVars );
1146
1147 passAdapters( appExpr, function, exprTyVars );
1148
1149 return ret;
1150 }
1151
1152 bool isPolyDeref( UntypedExpr const * expr, TyVarMap const & scopeTyVars, TypeSubstitution const * env ) {
1153 if ( expr->result && isPolyType( expr->result, scopeTyVars, env ) ) {
1154 if ( auto name = dynamic_cast<NameExpr const *>( expr->function ) ) {
1155 if ( name->name == "*?" ) {
1156 return true;
1157 } // if
1158 } // if
1159 } // if
1160 return false;
1161 }
1162
1163 Expression * Pass1::postmutate( UntypedExpr *expr ) {
1164 if ( isPolyDeref( expr, scopeTyVars, env ) ) {
1165 Expression *ret = expr->args.front();
1166 expr->args.clear();
1167 delete expr;
1168 return ret;
1169 }
1170 return expr;
1171 }
1172
1173 void Pass1::premutate( AddressExpr * ) { visit_children = false; }
1174 Expression * Pass1::postmutate( AddressExpr * addrExpr ) {
1175 assert( addrExpr->arg->result && ! addrExpr->arg->result->isVoid() );
1176
1177 bool needs = false;
1178 if ( UntypedExpr *expr = dynamic_cast< UntypedExpr *>( addrExpr->arg ) ) {
1179 if ( isPolyDeref( expr, scopeTyVars, env ) ) {
1180 if ( ApplicationExpr * appExpr = dynamic_cast< ApplicationExpr * >( expr->args.front() ) ) {
1181 assert( appExpr->function->result );
1182 FunctionType *function = getFunctionType( appExpr->function->result );
1183 assert( function );
1184 needs = needsAdapter( function, scopeTyVars );
1185 } // if
1186 } // if
1187 } // if
1188 // isPolyType check needs to happen before mutating addrExpr arg, so pull it forward
1189 // out of the if condition.
1190 addrExpr->arg = addrExpr->arg->acceptMutator( *visitor );
1191 // ... but must happen after mutate, since argument might change (e.g. intrinsic *?, ?[?]) - re-evaluate above comment
1192 bool polytype = isPolyType( addrExpr->arg->result, scopeTyVars, env );
1193 if ( polytype || needs ) {
1194 Expression *ret = addrExpr->arg;
1195 delete ret->result;
1196 ret->result = addrExpr->result->clone();
1197 addrExpr->arg = nullptr;
1198 delete addrExpr;
1199 return ret;
1200 } else {
1201 return addrExpr;
1202 } // if
1203 }
1204
1205 void Pass1::premutate( ReturnStmt *returnStmt ) {
1206 if ( retval && returnStmt->expr ) {
1207 assert( returnStmt->expr->result && ! returnStmt->expr->result->isVoid() );
1208 delete returnStmt->expr;
1209 returnStmt->expr = nullptr;
1210 } // if
1211 }
1212
1213 void Pass1::premutate( PointerType *pointerType ) {
1214 GuardScope( scopeTyVars );
1215 makeTyVarMap( pointerType, scopeTyVars );
1216 }
1217
1218 void Pass1::premutate( FunctionType *functionType ) {
1219 GuardScope( scopeTyVars );
1220 makeTyVarMap( functionType, scopeTyVars );
1221 }
1222
1223 void Pass1::beginScope() {
1224 adapters.beginScope();
1225 }
1226
1227 void Pass1::endScope() {
1228 adapters.endScope();
1229 }
1230
1231////////////////////////////////////////// Pass2 ////////////////////////////////////////////////////
1232
1233 void Pass2::addAdapters( FunctionType *functionType ) {
1234 std::list< DeclarationWithType *> &paramList = functionType->parameters;
1235 std::list< FunctionType const *> functions;
1236 for ( DeclarationWithType * const arg : functionType->parameters ) {
1237 Type *orig = arg->get_type();
1238 findAndReplaceFunction( orig, functions, scopeTyVars, needsAdapter );
1239 arg->set_type( orig );
1240 }
1241 std::set< std::string > adaptersDone;
1242 for ( FunctionType const * const funType : functions ) {
1243 std::string mangleName = mangleAdapterName( funType, scopeTyVars );
1244 if ( adaptersDone.find( mangleName ) == adaptersDone.end() ) {
1245 std::string adapterName = makeAdapterName( mangleName );
1246 // adapter may not be used in body, pass along with unused attribute.
1247 paramList.push_front( new ObjectDecl( adapterName, Type::StorageClasses(), LinkageSpec::C, 0, new PointerType( Type::Qualifiers(), makeAdapterType( funType, scopeTyVars ) ), 0, { new Attribute( "unused" ) } ) );
1248 adaptersDone.insert( adaptersDone.begin(), mangleName );
1249 }
1250 }
1251// deleteAll( functions );
1252 }
1253
1254 DeclarationWithType * Pass2::postmutate( FunctionDecl *functionDecl ) {
1255 FunctionType * ftype = functionDecl->type;
1256 if ( ! ftype->returnVals.empty() && functionDecl->statements ) {
1257 // intrinsic functions won't be using the _retval so no need to generate it.
1258 if ( functionDecl->linkage != LinkageSpec::Intrinsic && !isPrefix( functionDecl->name, "_thunk" ) && ! isPrefix( functionDecl->name, "_adapter" ) ) { // xxx - remove check for prefix once thunks properly use ctor/dtors
1259 assert( ftype->returnVals.size() == 1 );
1260 DeclarationWithType * retval = ftype->returnVals.front();
1261 if ( retval->name == "" ) {
1262 retval->name = "_retval";
1263 }
1264 functionDecl->statements->kids.push_front( new DeclStmt( retval ) );
1265 DeclarationWithType * newRet = retval->clone(); // for ownership purposes
1266 ftype->returnVals.front() = newRet;
1267 }
1268 }
1269 // errors should have been caught by this point, remove initializers from parameters to allow correct codegen of default arguments
1270 for ( Declaration * param : functionDecl->type->parameters ) {
1271 if ( ObjectDecl * obj = dynamic_cast< ObjectDecl * >( param ) ) {
1272 delete obj->init;
1273 obj->init = nullptr;
1274 }
1275 }
1276 return functionDecl;
1277 }
1278
1279 void Pass2::premutate( StructDecl * ) {
1280 // prevent tyVars from leaking into containing scope
1281 GuardScope( scopeTyVars );
1282 }
1283
1284 void Pass2::premutate( UnionDecl * ) {
1285 // prevent tyVars from leaking into containing scope
1286 GuardScope( scopeTyVars );
1287 }
1288
1289 void Pass2::premutate( TraitDecl * ) {
1290 // prevent tyVars from leaking into containing scope
1291 GuardScope( scopeTyVars );
1292 }
1293
1294 void Pass2::premutate( TypeDecl *typeDecl ) {
1295 addToTyVarMap( typeDecl, scopeTyVars );
1296 }
1297
1298 void Pass2::premutate( PointerType *pointerType ) {
1299 GuardScope( scopeTyVars );
1300 makeTyVarMap( pointerType, scopeTyVars );
1301 }
1302
1303 void Pass2::premutate( FunctionType *funcType ) {
1304 GuardScope( scopeTyVars );
1305 makeTyVarMap( funcType, scopeTyVars );
1306
1307 // move polymorphic return type to parameter list
1308 if ( isDynRet( funcType ) ) {
1309 ObjectDecl *ret = strict_dynamic_cast< ObjectDecl* >( funcType->get_returnVals().front() );
1310 ret->set_type( new PointerType( Type::Qualifiers(), ret->get_type() ) );
1311 funcType->get_parameters().push_front( ret );
1312 funcType->get_returnVals().pop_front();
1313 ret->set_init( nullptr ); // xxx - memory leak?
1314 }
1315
1316 // add size/align and assertions for type parameters to parameter list
1317 std::list< DeclarationWithType *>::iterator last = funcType->get_parameters().begin();
1318 std::list< DeclarationWithType *> inferredParams;
1319 // size/align/offset parameters may not be used in body, pass along with unused attribute.
1320 ObjectDecl newObj( "", Type::StorageClasses(), LinkageSpec::C, 0, new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ), 0,
1321 { new Attribute( "unused" ) } );
1322 ObjectDecl newPtr( "", Type::StorageClasses(), LinkageSpec::C, 0,
1323 new PointerType( Type::Qualifiers(), new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ) ), 0 );
1324 for ( TypeDecl * const tyParam : funcType->get_forall() ) {
1325 ObjectDecl *sizeParm, *alignParm;
1326 // add all size and alignment parameters to parameter list
1327 if ( tyParam->isComplete() ) {
1328 TypeInstType parmType( Type::Qualifiers(), tyParam->get_name(), tyParam );
1329 std::string parmName = mangleType( &parmType );
1330
1331 sizeParm = newObj.clone();
1332 sizeParm->set_name( sizeofName( parmName ) );
1333 last = funcType->get_parameters().insert( last, sizeParm );
1334 ++last;
1335
1336 alignParm = newObj.clone();
1337 alignParm->set_name( alignofName( parmName ) );
1338 last = funcType->get_parameters().insert( last, alignParm );
1339 ++last;
1340 }
1341 // move all assertions into parameter list
1342 for ( DeclarationWithType * const assert : tyParam->get_assertions() ) {
1343 // assertion parameters may not be used in body, pass along with unused attribute.
1344 assert->get_attributes().push_back( new Attribute( "unused" ) );
1345 inferredParams.push_back( assert );
1346 }
1347 tyParam->get_assertions().clear();
1348 }
1349
1350 // add size/align for generic parameter types to parameter list
1351 std::set< std::string > seenTypes; // sizeofName for generic types we've seen
1352 for ( DeclarationWithType * const fnParam : funcType->get_parameters() ) {
1353 Type *polyType = isPolyType( fnParam->get_type(), scopeTyVars );
1354 if ( polyType && ! dynamic_cast< TypeInstType* >( polyType ) ) {
1355 std::string typeName = mangleType( polyType );
1356 if ( seenTypes.count( typeName ) ) continue;
1357
1358 ObjectDecl *sizeParm, *alignParm, *offsetParm;
1359 sizeParm = newObj.clone();
1360 sizeParm->set_name( sizeofName( typeName ) );
1361 last = funcType->get_parameters().insert( last, sizeParm );
1362 ++last;
1363
1364 alignParm = newObj.clone();
1365 alignParm->set_name( alignofName( typeName ) );
1366 last = funcType->get_parameters().insert( last, alignParm );
1367 ++last;
1368
1369 if ( StructInstType *polyBaseStruct = dynamic_cast< StructInstType* >( polyType ) ) {
1370 // NOTE zero-length arrays are illegal in C, so empty structs have no offset array
1371 if ( ! polyBaseStruct->get_baseStruct()->get_members().empty() ) {
1372 offsetParm = newPtr.clone();
1373 offsetParm->set_name( offsetofName( typeName ) );
1374 last = funcType->get_parameters().insert( last, offsetParm );
1375 ++last;
1376 }
1377 }
1378 seenTypes.insert( typeName );
1379 }
1380 }
1381
1382 // splice assertion parameters into parameter list
1383 funcType->get_parameters().splice( last, inferredParams );
1384 addAdapters( funcType );
1385 }
1386
1387////////////////////////////////////////// PolyGenericCalculator ////////////////////////////////////////////////////
1388
1389 PolyGenericCalculator::PolyGenericCalculator()
1390 : knownLayouts(), knownOffsets(), bufNamer( "_buf" ) {}
1391
1392 void PolyGenericCalculator::beginTypeScope( Type *ty ) {
1393 GuardScope( scopeTyVars );
1394 makeTyVarMap( ty, scopeTyVars );
1395 }
1396
1397 void PolyGenericCalculator::beginGenericScope() {
1398 GuardScope( *this );
1399 // We expect the first function type see to be the type relating to this scope
1400 // but any further type is probably some unrelated function pointer
1401 // keep track of which is the first
1402 GuardValue( expect_func_type );
1403 expect_func_type = true;
1404 }
1405
1406 void PolyGenericCalculator::premutate( ObjectDecl *objectDecl ) {
1407 beginTypeScope( objectDecl->get_type() );
1408 }
1409
1410 void PolyGenericCalculator::premutate( FunctionDecl *functionDecl ) {
1411 beginGenericScope();
1412
1413 beginTypeScope( functionDecl->get_functionType() );
1414 }
1415
1416 void PolyGenericCalculator::premutate( TypedefDecl *typedefDecl ) {
1417 assert(false);
1418 beginTypeScope( typedefDecl->get_base() );
1419 }
1420
1421 void PolyGenericCalculator::premutate( TypeDecl * typeDecl ) {
1422 addToTyVarMap( typeDecl, scopeTyVars );
1423 }
1424
1425 Declaration * PolyGenericCalculator::postmutate( TypeDecl *typeDecl ) {
1426 if ( Type * base = typeDecl->base ) {
1427 // add size/align variables for opaque type declarations
1428 TypeInstType inst( Type::Qualifiers(), typeDecl->name, typeDecl );
1429 std::string typeName = mangleType( &inst );
1430 Type *layoutType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
1431
1432 ObjectDecl * sizeDecl = ObjectDecl::newObject( sizeofName( typeName ), layoutType, new SingleInit( new SizeofExpr( base->clone() ) ) );
1433 ObjectDecl * alignDecl = ObjectDecl::newObject( alignofName( typeName ), layoutType->clone(), new SingleInit( new AlignofExpr( base->clone() ) ) );
1434
1435 // ensure that the initializing sizeof/alignof exprs are properly mutated
1436 sizeDecl->acceptMutator( *visitor );
1437 alignDecl->acceptMutator( *visitor );
1438
1439 // can't use makeVar, because it inserts into stmtsToAdd and TypeDecls can occur at global scope
1440 declsToAddAfter.push_back( alignDecl );
1441 // replace with sizeDecl
1442 return sizeDecl;
1443 }
1444 return typeDecl;
1445 }
1446
1447 void PolyGenericCalculator::premutate( PointerType *pointerType ) {
1448 beginTypeScope( pointerType );
1449 }
1450
1451 void PolyGenericCalculator::premutate( FunctionType *funcType ) {
1452 beginTypeScope( funcType );
1453
1454 GuardValue( expect_func_type );
1455
1456 if(!expect_func_type) {
1457 // If this is the first function type we see
1458 // Then it's the type of the declaration and we care about it
1459 GuardScope( *this );
1460 }
1461
1462 // The other functions type we will see in this scope are probably functions parameters
1463 // they don't help us with the layout and offsets so don't mark them as known in this scope
1464 expect_func_type = false;
1465
1466 // make sure that any type information passed into the function is accounted for
1467 for ( DeclarationWithType * const fnParam : funcType->get_parameters() ) {
1468 // condition here duplicates that in Pass2::mutate( FunctionType* )
1469 Type *polyType = isPolyType( fnParam->get_type(), scopeTyVars );
1470 if ( polyType && ! dynamic_cast< TypeInstType* >( polyType ) ) {
1471 knownLayouts.insert( mangleType( polyType ) );
1472 }
1473 }
1474 }
1475
1476 /// converts polymorphic type T into a suitable monomorphic representation, currently: __attribute__((aligned(8)) char[size_T]
1477 Type * polyToMonoType( Type const * declType ) {
1478 Type * charType = new BasicType( Type::Qualifiers(), BasicType::Kind::Char);
1479 Expression * size = new NameExpr( sizeofName( mangleType(declType) ) );
1480 Attribute * aligned = new Attribute( "aligned", std::list<Expression*>{ new ConstantExpr( Constant::from_int(8) ) } );
1481 return new ArrayType( Type::Qualifiers(), charType, size,
1482 true, false, std::list<Attribute *>{ aligned } );
1483 }
1484
1485 void PolyGenericCalculator::mutateMembers( AggregateDecl * aggrDecl ) {
1486 std::set< std::string > genericParams;
1487 for ( TypeDecl * td : aggrDecl->parameters ) {
1488 genericParams.insert( td->name );
1489 }
1490 for ( Declaration * decl : aggrDecl->members ) {
1491 if ( ObjectDecl * field = dynamic_cast< ObjectDecl * >( decl ) ) {
1492 Type * ty = replaceTypeInst( field->type, env );
1493 if ( TypeInstType *typeInst = dynamic_cast< TypeInstType* >( ty ) ) {
1494 // do not try to monomorphize generic parameters
1495 if ( scopeTyVars.find( typeInst->get_name() ) != scopeTyVars.end() && ! genericParams.count( typeInst->name ) ) {
1496 // polymorphic aggregate members should be converted into monomorphic members.
1497 // Using char[size_T] here respects the expected sizing rules of an aggregate type.
1498 Type * newType = polyToMonoType( field->type );
1499 delete field->type;
1500 field->type = newType;
1501 }
1502 }
1503 }
1504 }
1505 }
1506
1507 void PolyGenericCalculator::premutate( StructDecl * structDecl ) {
1508 mutateMembers( structDecl );
1509 }
1510
1511 void PolyGenericCalculator::premutate( UnionDecl * unionDecl ) {
1512 mutateMembers( unionDecl );
1513 }
1514
1515 void PolyGenericCalculator::premutate( DeclStmt *declStmt ) {
1516 if ( ObjectDecl *objectDecl = dynamic_cast< ObjectDecl *>( declStmt->get_decl() ) ) {
1517 if ( findGeneric( objectDecl->get_type() ) ) {
1518 // change initialization of a polymorphic value object to allocate via a VLA
1519 // (alloca was previously used, but can't be safely used in loops)
1520 ObjectDecl *newBuf = ObjectDecl::newObject( bufNamer.newName(), polyToMonoType( objectDecl->type ), nullptr );
1521 stmtsToAddBefore.push_back( new DeclStmt( newBuf ) );
1522
1523 // if the object has a cleanup attribute, the cleanup should be on the buffer, not the pointer
1524 auto matchAndMove = [newBuf](Attribute * attr){
1525 if(attr->name == "cleanup") {
1526 newBuf->attributes.push_back(attr);
1527 return true;
1528 }
1529 return false;
1530 };
1531
1532 objectDecl->attributes.remove_if(matchAndMove);
1533
1534 delete objectDecl->get_init();
1535 objectDecl->set_init( new SingleInit( new VariableExpr( newBuf ) ) );
1536 }
1537 }
1538 }
1539
1540 /// Finds the member in the base list that matches the given declaration; returns its index, or -1 if not present
1541 long findMember( DeclarationWithType *memberDecl, std::list< Declaration* > &baseDecls ) {
1542 for ( auto pair : enumerate( baseDecls ) ) {
1543 Declaration * decl = pair.val;
1544 size_t i = pair.idx;
1545 if ( memberDecl->get_name() != decl->get_name() )
1546 continue;
1547
1548 if ( memberDecl->get_name().empty() ) {
1549 // plan-9 field: match on unique_id
1550 if ( memberDecl->get_uniqueId() == decl->get_uniqueId() )
1551 return i;
1552 else
1553 continue;
1554 }
1555
1556 DeclarationWithType *declWithType = strict_dynamic_cast< DeclarationWithType* >( decl );
1557
1558 if ( memberDecl->get_mangleName().empty() || declWithType->get_mangleName().empty() ) {
1559 // tuple-element field: expect neither had mangled name; accept match on simple name (like field_2) only
1560 assert( memberDecl->get_mangleName().empty() && declWithType->get_mangleName().empty() );
1561 return i;
1562 }
1563
1564 // ordinary field: use full name to accommodate overloading
1565 if ( memberDecl->get_mangleName() == declWithType->get_mangleName() )
1566 return i;
1567 else
1568 continue;
1569 }
1570 return -1;
1571 }
1572
1573 /// Returns an index expression into the offset array for a type
1574 Expression *makeOffsetIndex( Type const *objectType, long i ) {
1575 ConstantExpr *fieldIndex = new ConstantExpr( Constant::from_ulong( i ) );
1576 UntypedExpr *fieldOffset = new UntypedExpr( new NameExpr( "?[?]" ) );
1577 fieldOffset->get_args().push_back( new NameExpr( offsetofName( mangleType( objectType ) ) ) );
1578 fieldOffset->get_args().push_back( fieldIndex );
1579 return fieldOffset;
1580 }
1581
1582 Expression *PolyGenericCalculator::postmutate( MemberExpr *memberExpr ) {
1583 // only mutate member expressions for polymorphic types
1584 int tyDepth;
1585 Type *objectType = hasPolyBase( memberExpr->aggregate->result, scopeTyVars, &tyDepth );
1586 if ( ! objectType ) return memberExpr;
1587 findGeneric( objectType ); // ensure layout for this type is available
1588
1589 // replace member expression with dynamically-computed layout expression
1590 Expression *newMemberExpr = nullptr;
1591 if ( StructInstType *structType = dynamic_cast< StructInstType* >( objectType ) ) {
1592 // look up offset index
1593 long i = findMember( memberExpr->member, structType->baseStruct->members );
1594 if ( i == -1 ) return memberExpr;
1595
1596 // replace member expression with pointer to base plus offset
1597 UntypedExpr *fieldLoc = new UntypedExpr( new NameExpr( "?+?" ) );
1598 Expression * aggr = memberExpr->aggregate->clone();
1599 delete aggr->env; // xxx - there's a problem with keeping the env for some reason, so for now just get rid of it
1600 aggr->env = nullptr;
1601 fieldLoc->get_args().push_back( aggr );
1602 fieldLoc->get_args().push_back( makeOffsetIndex( objectType, i ) );
1603 fieldLoc->set_result( memberExpr->result->clone() );
1604 newMemberExpr = fieldLoc;
1605 } else if ( dynamic_cast< UnionInstType* >( objectType ) ) {
1606 // union members are all at offset zero, so just use the aggregate expr
1607 Expression * aggr = memberExpr->aggregate->clone();
1608 delete aggr->env; // xxx - there's a problem with keeping the env for some reason, so for now just get rid of it
1609 aggr->env= nullptr;
1610 newMemberExpr = aggr;
1611 newMemberExpr->result = memberExpr->result->clone();
1612 } else return memberExpr;
1613 assert( newMemberExpr );
1614
1615 // 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.
1616 // forall(otype T) struct Box { T x; }
1617 // forall(otype T) f() {
1618 // Box(T *) b; b.x;
1619 // }
1620 // 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.
1621 Type *memberType = memberExpr->member->get_type()->clone();
1622 TypeSubstitution sub = objectType->genericSubstitution();
1623 sub.apply( memberType );
1624 if ( ! isPolyType( memberType, scopeTyVars ) ) {
1625 // 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
1626 CastExpr *ptrCastExpr = new CastExpr( newMemberExpr, new PointerType( Type::Qualifiers(), memberType->clone() ) );
1627 UntypedExpr *derefExpr = UntypedExpr::createDeref( ptrCastExpr );
1628 newMemberExpr = derefExpr;
1629 }
1630
1631 delete memberType;
1632 delete memberExpr;
1633 return newMemberExpr;
1634 }
1635
1636 void PolyGenericCalculator::premutate( AddressExpr * addrExpr ) {
1637 GuardValue( addrMember );
1638 // is the argument a MemberExpr before mutating?
1639 addrMember = dynamic_cast< MemberExpr * >( addrExpr->arg );
1640 }
1641
1642 Expression * PolyGenericCalculator::postmutate( AddressExpr * addrExpr ) {
1643 if ( addrMember && addrMember != addrExpr->arg ) {
1644 // arg was a MemberExpr and has been mutated
1645 if ( UntypedExpr * untyped = dynamic_cast< UntypedExpr * >( addrExpr->arg ) ) {
1646 if ( InitTweak::getFunctionName( untyped ) == "?+?" ) {
1647 // MemberExpr was converted to pointer+offset, and it is not valid C to take the address of an addition, so strip the address-of
1648 // TODO: should addrExpr->arg->result be changed to addrExpr->result?
1649 Expression * ret = addrExpr->arg;
1650 addrExpr->arg = nullptr;
1651 std::swap( addrExpr->env, ret->env );
1652 delete addrExpr;
1653 return ret;
1654 }
1655 }
1656 }
1657 return addrExpr;
1658 }
1659
1660 ObjectDecl *PolyGenericCalculator::makeVar( const std::string &name, Type *type, Initializer *init ) {
1661 ObjectDecl *newObj = new ObjectDecl( name, Type::StorageClasses(), LinkageSpec::C, nullptr, type, init );
1662 stmtsToAddBefore.push_back( new DeclStmt( newObj ) );
1663 return newObj;
1664 }
1665
1666 void PolyGenericCalculator::addOtypeParamsToLayoutCall( UntypedExpr *layoutCall, const std::list< Type* > &otypeParams ) {
1667 for ( Type * const param : otypeParams ) {
1668 if ( findGeneric( param ) ) {
1669 // push size/align vars for a generic parameter back
1670 std::string paramName = mangleType( param );
1671 layoutCall->get_args().push_back( new NameExpr( sizeofName( paramName ) ) );
1672 layoutCall->get_args().push_back( new NameExpr( alignofName( paramName ) ) );
1673 } else {
1674 layoutCall->get_args().push_back( new SizeofExpr( param->clone() ) );
1675 layoutCall->get_args().push_back( new AlignofExpr( param->clone() ) );
1676 }
1677 }
1678 }
1679
1680 /// returns true if any of the otype parameters have a dynamic layout and puts all otype parameters in the output list
1681 bool findGenericParams( std::list< TypeDecl* > const &baseParams, std::list< Expression* > const &typeParams, std::list< Type* > &out ) {
1682 bool hasDynamicLayout = false;
1683
1684 for ( auto paramPair : group_iterate( baseParams, typeParams ) ) {
1685 TypeDecl * baseParam = std::get<0>( paramPair );
1686 Expression * typeParam = std::get<1>( paramPair );
1687 // skip non-otype parameters
1688 if ( ! baseParam->isComplete() ) continue;
1689 TypeExpr *typeExpr = dynamic_cast< TypeExpr* >( typeParam );
1690 assert( typeExpr && "all otype parameters should be type expressions" );
1691
1692 Type *type = typeExpr->get_type();
1693 out.push_back( type );
1694 if ( isPolyType( type ) ) hasDynamicLayout = true;
1695 }
1696
1697 return hasDynamicLayout;
1698 }
1699
1700 bool PolyGenericCalculator::findGeneric( Type const *ty ) {
1701 ty = replaceTypeInst( ty, env );
1702
1703 if ( auto typeInst = dynamic_cast< TypeInstType const * >( ty ) ) {
1704 if ( scopeTyVars.find( typeInst->get_name() ) != scopeTyVars.end() ) {
1705 // NOTE assumes here that getting put in the scopeTyVars included having the layout variables set
1706 return true;
1707 }
1708 return false;
1709 } else if ( auto structTy = dynamic_cast< StructInstType const * >( ty ) ) {
1710 // check if this type already has a layout generated for it
1711 std::string typeName = mangleType( ty );
1712 if ( knownLayouts.find( typeName ) != knownLayouts.end() ) return true;
1713
1714 // check if any of the type parameters have dynamic layout; if none do, this type is (or will be) monomorphized
1715 std::list< Type* > otypeParams;
1716 if ( ! findGenericParams( *structTy->get_baseParameters(), structTy->parameters, otypeParams ) ) return false;
1717
1718 // insert local variables for layout and generate call to layout function
1719 knownLayouts.insert( typeName ); // done early so as not to interfere with the later addition of parameters to the layout call
1720 Type *layoutType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
1721
1722 int n_members = structTy->get_baseStruct()->get_members().size();
1723 if ( n_members == 0 ) {
1724 // all empty structs have the same layout - size 1, align 1
1725 makeVar( sizeofName( typeName ), layoutType, new SingleInit( new ConstantExpr( Constant::from_ulong( (unsigned long)1 ) ) ) );
1726 makeVar( alignofName( typeName ), layoutType->clone(), new SingleInit( new ConstantExpr( Constant::from_ulong( (unsigned long)1 ) ) ) );
1727 // NOTE zero-length arrays are forbidden in C, so empty structs have no offsetof array
1728 } else {
1729 ObjectDecl *sizeVar = makeVar( sizeofName( typeName ), layoutType );
1730 ObjectDecl *alignVar = makeVar( alignofName( typeName ), layoutType->clone() );
1731 ObjectDecl *offsetVar = makeVar( offsetofName( typeName ), new ArrayType( Type::Qualifiers(), layoutType->clone(), new ConstantExpr( Constant::from_int( n_members ) ), false, false ) );
1732
1733 // generate call to layout function
1734 UntypedExpr *layoutCall = new UntypedExpr( new NameExpr( layoutofName( structTy->get_baseStruct() ) ) );
1735 layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( sizeVar ) ) );
1736 layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( alignVar ) ) );
1737 layoutCall->get_args().push_back( new VariableExpr( offsetVar ) );
1738 addOtypeParamsToLayoutCall( layoutCall, otypeParams );
1739
1740 stmtsToAddBefore.push_back( new ExprStmt( layoutCall ) );
1741 }
1742
1743 // std::cout << "TRUE 2" << std::endl;
1744
1745 return true;
1746 } else if ( auto unionTy = dynamic_cast< UnionInstType const * >( ty ) ) {
1747 // check if this type already has a layout generated for it
1748 std::string typeName = mangleType( ty );
1749 if ( knownLayouts.find( typeName ) != knownLayouts.end() ) return true;
1750
1751 // check if any of the type parameters have dynamic layout; if none do, this type is (or will be) monomorphized
1752 std::list< Type* > otypeParams;
1753 if ( ! findGenericParams( *unionTy->get_baseParameters(), unionTy->parameters, otypeParams ) ) return false;
1754
1755 // insert local variables for layout and generate call to layout function
1756 knownLayouts.insert( typeName ); // done early so as not to interfere with the later addition of parameters to the layout call
1757 Type *layoutType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
1758
1759 ObjectDecl *sizeVar = makeVar( sizeofName( typeName ), layoutType );
1760 ObjectDecl *alignVar = makeVar( alignofName( typeName ), layoutType->clone() );
1761
1762 // generate call to layout function
1763 UntypedExpr *layoutCall = new UntypedExpr( new NameExpr( layoutofName( unionTy->get_baseUnion() ) ) );
1764 layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( sizeVar ) ) );
1765 layoutCall->get_args().push_back( new AddressExpr( new VariableExpr( alignVar ) ) );
1766 addOtypeParamsToLayoutCall( layoutCall, otypeParams );
1767
1768 stmtsToAddBefore.push_back( new ExprStmt( layoutCall ) );
1769
1770 return true;
1771 }
1772
1773 return false;
1774 }
1775
1776 Expression * PolyGenericCalculator::genSizeof( Type* ty ) {
1777 if ( ArrayType * aty = dynamic_cast<ArrayType *>(ty) ) {
1778 // generate calculated size for possibly generic array
1779 Expression * sizeofBase = genSizeof( aty->get_base() );
1780 if ( ! sizeofBase ) return nullptr;
1781 Expression * dim = aty->get_dimension();
1782 aty->set_dimension( nullptr );
1783 return makeOp( "?*?", sizeofBase, dim );
1784 } else if ( findGeneric( ty ) ) {
1785 // generate calculated size for generic type
1786 return new NameExpr( sizeofName( mangleType( ty ) ) );
1787 } else return nullptr;
1788 }
1789
1790 Expression *PolyGenericCalculator::postmutate( SizeofExpr *sizeofExpr ) {
1791 Type *ty = sizeofExpr->get_isType() ?
1792 sizeofExpr->get_type() : sizeofExpr->get_expr()->get_result();
1793
1794 Expression * gen = genSizeof( ty );
1795 if ( gen ) {
1796 delete sizeofExpr;
1797 return gen;
1798 } else return sizeofExpr;
1799 }
1800
1801 Expression *PolyGenericCalculator::postmutate( AlignofExpr *alignofExpr ) {
1802 Type *ty = alignofExpr->get_isType() ? alignofExpr->get_type() : alignofExpr->get_expr()->get_result();
1803 if ( findGeneric( ty ) ) {
1804 Expression *ret = new NameExpr( alignofName( mangleType( ty ) ) );
1805 delete alignofExpr;
1806 return ret;
1807 }
1808 return alignofExpr;
1809 }
1810
1811 Expression *PolyGenericCalculator::postmutate( OffsetofExpr *offsetofExpr ) {
1812 // only mutate expressions for polymorphic structs/unions
1813 Type *ty = offsetofExpr->get_type();
1814 if ( ! findGeneric( ty ) ) return offsetofExpr;
1815
1816 if ( StructInstType *structType = dynamic_cast< StructInstType* >( ty ) ) {
1817 // replace offsetof expression by index into offset array
1818 long i = findMember( offsetofExpr->get_member(), structType->get_baseStruct()->get_members() );
1819 if ( i == -1 ) return offsetofExpr;
1820
1821 Expression *offsetInd = makeOffsetIndex( ty, i );
1822 delete offsetofExpr;
1823 return offsetInd;
1824 } else if ( dynamic_cast< UnionInstType* >( ty ) ) {
1825 // all union members are at offset zero
1826 delete offsetofExpr;
1827 return new ConstantExpr( Constant::from_ulong( 0 ) );
1828 } else return offsetofExpr;
1829 }
1830
1831 Expression *PolyGenericCalculator::postmutate( OffsetPackExpr *offsetPackExpr ) {
1832 StructInstType *ty = offsetPackExpr->get_type();
1833
1834 Expression *ret = 0;
1835 if ( findGeneric( ty ) ) {
1836 // pull offset back from generated type information
1837 ret = new NameExpr( offsetofName( mangleType( ty ) ) );
1838 } else {
1839 std::string offsetName = offsetofName( mangleType( ty ) );
1840 if ( knownOffsets.find( offsetName ) != knownOffsets.end() ) {
1841 // use the already-generated offsets for this type
1842 ret = new NameExpr( offsetName );
1843 } else {
1844 knownOffsets.insert( offsetName );
1845
1846 std::list< Declaration* > &baseMembers = ty->get_baseStruct()->get_members();
1847 Type *offsetType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
1848
1849 // build initializer list for offset array
1850 std::list< Initializer* > inits;
1851 for ( Declaration * const member : baseMembers ) {
1852 DeclarationWithType *memberDecl = dynamic_cast< DeclarationWithType* >( member );
1853 assertf( memberDecl, "Requesting offset of Non-DWT member: %s", toString( member ).c_str() );
1854 inits.push_back( new SingleInit( new OffsetofExpr( ty->clone(), memberDecl ) ) );
1855 }
1856
1857 // build the offset array and replace the pack with a reference to it
1858 ObjectDecl *offsetArray = makeVar( offsetName, new ArrayType( Type::Qualifiers(), offsetType, new ConstantExpr( Constant::from_ulong( baseMembers.size() ) ), false, false ),
1859 new ListInit( inits ) );
1860 ret = new VariableExpr( offsetArray );
1861 }
1862 }
1863
1864 delete offsetPackExpr;
1865 return ret;
1866 }
1867
1868 void PolyGenericCalculator::beginScope() {
1869 knownLayouts.beginScope();
1870 knownOffsets.beginScope();
1871 }
1872
1873 void PolyGenericCalculator::endScope() {
1874 knownLayouts.endScope();
1875 knownOffsets.endScope();
1876 }
1877
1878////////////////////////////////////////// Pass3 ////////////////////////////////////////////////////
1879
1880 template< typename DeclClass >
1881 void Pass3::handleDecl( DeclClass * decl, Type * type ) {
1882 GuardScope( scopeTyVars );
1883 makeTyVarMap( type, scopeTyVars );
1884 ScrubTyVars::scrubAll( decl );
1885 }
1886
1887 void Pass3::premutate( ObjectDecl * objectDecl ) {
1888 handleDecl( objectDecl, objectDecl->type );
1889 }
1890
1891 void Pass3::premutate( FunctionDecl * functionDecl ) {
1892 handleDecl( functionDecl, functionDecl->type );
1893 }
1894
1895 void Pass3::premutate( TypedefDecl * typedefDecl ) {
1896 handleDecl( typedefDecl, typedefDecl->base );
1897 }
1898
1899 /// Strips the members from a generic aggregate
1900 void stripGenericMembers(AggregateDecl * decl) {
1901 if ( ! decl->parameters.empty() ) decl->members.clear();
1902 }
1903
1904 void Pass3::premutate( StructDecl * structDecl ) {
1905 stripGenericMembers( structDecl );
1906 }
1907
1908 void Pass3::premutate( UnionDecl * unionDecl ) {
1909 stripGenericMembers( unionDecl );
1910 }
1911
1912 void Pass3::premutate( TypeDecl * typeDecl ) {
1913 addToTyVarMap( typeDecl, scopeTyVars );
1914 }
1915
1916 void Pass3::premutate( PointerType * pointerType ) {
1917 GuardScope( scopeTyVars );
1918 makeTyVarMap( pointerType, scopeTyVars );
1919 }
1920
1921 void Pass3::premutate( FunctionType * functionType ) {
1922 GuardScope( scopeTyVars );
1923 makeTyVarMap( functionType, scopeTyVars );
1924 }
1925 } // anonymous namespace
1926} // namespace GenPoly
1927
1928// Local Variables: //
1929// tab-width: 4 //
1930// mode: c++ //
1931// compile-command: "make install" //
1932// End: //
1933
Note: See TracBrowser for help on using the repository browser.