source: src/GenPoly/Box.cc@ 70cd431

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

Cleaning old box pass for easier translation. Removing another out parameter.

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