source: src/GenPoly/Box.cc@ 038726d

ADT aaron-thesis arm-eh ast-experimental cleanup-dtors ctor deferred_resn demangler enum forall-pointer-decay gc_noraii jacob/cs343-translation jenkins-sandbox memory new-ast new-ast-unique-expr new-env no_list persistent-indexer pthread-emulation qualifiedEnum resolv-new string with_gc
Last change on this file since 038726d was 4e284ea6, checked in by Aaron Moss <a3moss@…>, 10 years ago

Move InstantiateGeneric into Box.cc to share impl details

  • Property mode set to 100644
File size: 93.9 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 Feb 5 16:45:07 2016
13// Update Count : 286
14//
15
16#include <algorithm>
17#include <iterator>
18#include <list>
19#include <map>
20#include <set>
21#include <stack>
22#include <string>
23#include <utility>
24#include <vector>
25#include <cassert>
26
27#include "Box.h"
28#include "DeclMutator.h"
29#include "PolyMutator.h"
30#include "FindFunction.h"
31#include "ScopedMap.h"
32#include "ScrubTyVars.h"
33
34#include "Parser/ParseNode.h"
35
36#include "SynTree/Constant.h"
37#include "SynTree/Declaration.h"
38#include "SynTree/Expression.h"
39#include "SynTree/Initializer.h"
40#include "SynTree/Mutator.h"
41#include "SynTree/Statement.h"
42#include "SynTree/Type.h"
43#include "SynTree/TypeSubstitution.h"
44
45#include "ResolvExpr/TypeEnvironment.h"
46#include "ResolvExpr/TypeMap.h"
47#include "ResolvExpr/typeops.h"
48
49#include "SymTab/Indexer.h"
50#include "SymTab/Mangler.h"
51
52#include "Common/SemanticError.h"
53#include "Common/UniqueName.h"
54#include "Common/utility.h"
55
56#include <ext/functional> // temporary
57
58namespace GenPoly {
59 namespace {
60 const std::list<Label> noLabels;
61
62 FunctionType *makeAdapterType( FunctionType *adaptee, const TyVarMap &tyVars );
63
64 /// Key for a unique concrete type; generic base type paired with type parameter list
65 struct ConcreteType {
66 ConcreteType() : base(NULL), params() {}
67
68 ConcreteType(AggregateDecl *_base, const std::list< Type* >& _params) : base(_base), params() { cloneAll(_params, params); }
69
70 ConcreteType(const ConcreteType& that) : base(that.base), params() { cloneAll(that.params, params); }
71
72 /// Extracts types from a list of TypeExpr*
73 ConcreteType(AggregateDecl *_base, const std::list< TypeExpr* >& _params) : base(_base), params() {
74 for ( std::list< TypeExpr* >::const_iterator param = _params.begin(); param != _params.end(); ++param ) {
75 params.push_back( (*param)->get_type()->clone() );
76 }
77 }
78
79 ConcreteType& operator= (const ConcreteType& that) {
80 deleteAll( params );
81 params.clear();
82
83 base = that.base;
84 cloneAll( that.params, params );
85
86 return *this;
87 }
88
89 ~ConcreteType() { deleteAll( params ); }
90
91 bool operator== (const ConcreteType& that) const {
92 if ( base != that.base ) return false;
93
94 SymTab::Indexer dummy;
95 if ( params.size() != that.params.size() ) return false;
96 for ( std::list< Type* >::const_iterator it = params.begin(), jt = that.params.begin(); it != params.end(); ++it, ++jt ) {
97 if ( ! ResolvExpr::typesCompatible( *it, *jt, dummy ) ) return false;
98 }
99 return true;
100 }
101
102 AggregateDecl *base; ///< Base generic type
103 std::list< Type* > params; ///< Instantiation parameters
104 };
105
106 /// Maps a concrete type to the some value, accounting for scope
107 template< typename Value >
108 class InstantiationMap {
109 /// Information about a specific instantiation of a generic type
110 struct Instantiation {
111 ConcreteType key; ///< Instantiation parameters for this type
112 Value *value; ///< Value for this instantiation
113
114 Instantiation() : key(), value(0) {}
115 Instantiation(const ConcreteType &_key, Value *_value) : key(_key), value(_value) {}
116 };
117 /// Map of generic types to instantiations of them
118 typedef std::map< AggregateDecl*, std::vector< Instantiation > > Scope;
119
120 std::vector< Scope > scopes; ///< list of scopes, from outermost to innermost
121
122 public:
123 /// Starts a new scope
124 void beginScope() {
125 Scope scope;
126 scopes.push_back(scope);
127 }
128
129 /// Ends a scope
130 void endScope() {
131 scopes.pop_back();
132 }
133
134 /// Default constructor initializes with one scope
135 InstantiationMap() { beginScope(); }
136
137// private:
138 /// Gets the value for the concrete instantiation of this type, assuming it has already been instantiated in the current scope.
139 /// Returns NULL on none such.
140 Value *lookup( AggregateDecl *generic, const std::list< TypeExpr* >& params ) {
141 ConcreteType key(generic, params);
142 // scan scopes from innermost out
143 for ( typename std::vector< Scope >::const_reverse_iterator scope = scopes.rbegin(); scope != scopes.rend(); ++scope ) {
144 // skip scope if no instantiations of this generic type
145 typename Scope::const_iterator insts = scope->find( generic );
146 if ( insts == scope->end() ) continue;
147 // look through instantiations for matches to concrete type
148 for ( typename std::vector< Instantiation >::const_iterator inst = insts->second.begin(); inst != insts->second.end(); ++inst ) {
149 if ( inst->key == key ) return inst->value;
150 }
151 }
152 // no matching instantiation found
153 return 0;
154 }
155 public:
156// StructDecl* lookup( StructInstType *inst, const std::list< TypeExpr* > &typeSubs ) { return (StructDecl*)lookup( inst->get_baseStruct(), typeSubs ); }
157// UnionDecl* lookup( UnionInstType *inst, const std::list< TypeExpr* > &typeSubs ) { return (UnionDecl*)lookup( inst->get_baseUnion(), typeSubs ); }
158
159// private:
160 /// Adds a value for a concrete type to the current scope
161 void insert( AggregateDecl *generic, const std::list< TypeExpr* > &params, Value *value ) {
162 ConcreteType key(generic, params);
163 scopes.back()[generic].push_back( Instantiation( key, value ) );
164 }
165// public:
166// void insert( StructInstType *inst, const std::list< TypeExpr* > &typeSubs, StructDecl *decl ) { insert( inst->get_baseStruct(), typeSubs, decl ); }
167// void insert( UnionInstType *inst, const std::list< TypeExpr* > &typeSubs, UnionDecl *decl ) { insert( inst->get_baseUnion(), typeSubs, decl ); }
168 };
169
170 /// Adds layout-generation functions to polymorphic types
171 class LayoutFunctionBuilder : public DeclMutator {
172 unsigned int functionNesting; // current level of nested functions
173 public:
174 LayoutFunctionBuilder() : functionNesting( 0 ) {}
175
176 virtual DeclarationWithType *mutate( FunctionDecl *functionDecl );
177 virtual Declaration *mutate( StructDecl *structDecl );
178 virtual Declaration *mutate( UnionDecl *unionDecl );
179 };
180
181 /// Replaces polymorphic return types with out-parameters, replaces calls to polymorphic functions with adapter calls as needed, and adds appropriate type variables to the function call
182 class Pass1 : public PolyMutator {
183 public:
184 Pass1();
185 virtual Expression *mutate( ApplicationExpr *appExpr );
186 virtual Expression *mutate( AddressExpr *addrExpr );
187 virtual Expression *mutate( UntypedExpr *expr );
188 virtual DeclarationWithType* mutate( FunctionDecl *functionDecl );
189 virtual TypeDecl *mutate( TypeDecl *typeDecl );
190 virtual Expression *mutate( CommaExpr *commaExpr );
191 virtual Expression *mutate( ConditionalExpr *condExpr );
192 virtual Statement * mutate( ReturnStmt *returnStmt );
193 virtual Type *mutate( PointerType *pointerType );
194 virtual Type * mutate( FunctionType *functionType );
195
196 virtual void doBeginScope();
197 virtual void doEndScope();
198 private:
199 /// Makes a new temporary array holding the offsets of the fields of `type`, and returns a new variable expression referencing it
200 Expression *makeOffsetArray( StructInstType *type );
201 /// Pass the extra type parameters from polymorphic generic arguments or return types into a function application
202 void passArgTypeVars( ApplicationExpr *appExpr, Type *parmType, Type *argBaseType, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars, std::set< std::string > &seenTypes );
203 /// passes extra type parameters into a polymorphic function application
204 void passTypeVars( ApplicationExpr *appExpr, ReferenceToType *polyRetType, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars );
205 /// wraps a function application with a new temporary for the out-parameter return value
206 Expression *addRetParam( ApplicationExpr *appExpr, FunctionType *function, Type *retType, std::list< Expression *>::iterator &arg );
207 /// Replaces all the type parameters of a generic type with their concrete equivalents under the current environment
208 void replaceParametersWithConcrete( ApplicationExpr *appExpr, std::list< Expression* >& params );
209 /// Replaces a polymorphic type with its concrete equivalant under the current environment (returns itself if concrete).
210 /// If `doClone` is set to false, will not clone interior types
211 Type *replaceWithConcrete( ApplicationExpr *appExpr, Type *type, bool doClone = true );
212 /// wraps a function application returning a polymorphic type with a new temporary for the out-parameter return value
213 Expression *addPolyRetParam( ApplicationExpr *appExpr, FunctionType *function, ReferenceToType *polyType, std::list< Expression *>::iterator &arg );
214 Expression *applyAdapter( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars );
215 void boxParam( Type *formal, Expression *&arg, const TyVarMap &exprTyVars );
216 void boxParams( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars );
217 void addInferredParams( ApplicationExpr *appExpr, FunctionType *functionType, std::list< Expression *>::iterator &arg, const TyVarMap &tyVars );
218 /// Stores assignment operators from assertion list in local map of assignment operations
219 void findAssignOps( const std::list< TypeDecl *> &forall );
220 void passAdapters( ApplicationExpr *appExpr, FunctionType *functionType, const TyVarMap &exprTyVars );
221 FunctionDecl *makeAdapter( FunctionType *adaptee, FunctionType *realType, const std::string &mangleName, const TyVarMap &tyVars );
222 /// Replaces intrinsic operator functions with their arithmetic desugaring
223 Expression *handleIntrinsics( ApplicationExpr *appExpr );
224 /// Inserts a new temporary variable into the current scope with an auto-generated name
225 ObjectDecl *makeTemporary( Type *type );
226
227 std::map< std::string, DeclarationWithType *> assignOps;
228 ResolvExpr::TypeMap< DeclarationWithType > scopedAssignOps;
229 ScopedMap< std::string, DeclarationWithType* > adapters;
230 DeclarationWithType *retval;
231 bool useRetval;
232 UniqueName tempNamer;
233 };
234
235 /// Moves polymorphic returns in function types to pointer-type parameters, adds type size and assertion parameters to parameter lists as well
236 class Pass2 : public PolyMutator {
237 public:
238 template< typename DeclClass >
239 DeclClass *handleDecl( DeclClass *decl, Type *type );
240 virtual DeclarationWithType *mutate( FunctionDecl *functionDecl );
241 virtual ObjectDecl *mutate( ObjectDecl *objectDecl );
242 virtual TypeDecl *mutate( TypeDecl *typeDecl );
243 virtual TypedefDecl *mutate( TypedefDecl *typedefDecl );
244 virtual Type *mutate( PointerType *pointerType );
245 virtual Type *mutate( FunctionType *funcType );
246 private:
247 void addAdapters( FunctionType *functionType );
248
249 std::map< UniqueId, std::string > adapterName;
250 };
251
252 /// Mutator pass that replaces concrete instantiations of generic types with actual struct declarations, scoped appropriately
253 class GenericInstantiator : public DeclMutator {
254 /// Map of (generic type, parameter list) pairs to concrete type instantiations
255 InstantiationMap< AggregateDecl > instantiations;
256 /// Namer for concrete types
257 UniqueName typeNamer;
258
259 public:
260 GenericInstantiator() : DeclMutator(), instantiations(), typeNamer("_conc_") {}
261
262 virtual Type* mutate( StructInstType *inst );
263 virtual Type* mutate( UnionInstType *inst );
264
265 // virtual Expression* mutate( MemberExpr *memberExpr );
266
267 virtual void doBeginScope();
268 virtual void doEndScope();
269 private:
270 /// Wrap instantiation lookup for structs
271 StructDecl* lookup( StructInstType *inst, const std::list< TypeExpr* > &typeSubs ) { return (StructDecl*)instantiations.lookup( inst->get_baseStruct(), typeSubs ); }
272 /// Wrap instantiation lookup for unions
273 UnionDecl* lookup( UnionInstType *inst, const std::list< TypeExpr* > &typeSubs ) { return (UnionDecl*)instantiations.lookup( inst->get_baseUnion(), typeSubs ); }
274 /// Wrap instantiation insertion for structs
275 void insert( StructInstType *inst, const std::list< TypeExpr* > &typeSubs, StructDecl *decl ) { instantiations.insert( inst->get_baseStruct(), typeSubs, decl ); }
276 /// Wrap instantiation insertion for unions
277 void insert( UnionInstType *inst, const std::list< TypeExpr* > &typeSubs, UnionDecl *decl ) { instantiations.insert( inst->get_baseUnion(), typeSubs, decl ); }
278 };
279
280 /// Replaces member expressions for polymorphic types with calculated add-field-offset-and-dereference;
281 /// also fixes offsetof expressions.
282 class MemberExprFixer : public PolyMutator {
283 public:
284 template< typename DeclClass >
285 DeclClass *handleDecl( DeclClass *decl, Type *type );
286 virtual DeclarationWithType *mutate( FunctionDecl *functionDecl );
287 virtual ObjectDecl *mutate( ObjectDecl *objectDecl );
288 virtual TypedefDecl *mutate( TypedefDecl *objectDecl );
289 virtual TypeDecl *mutate( TypeDecl *objectDecl );
290 virtual Statement *mutate( DeclStmt *declStmt );
291 virtual Type *mutate( PointerType *pointerType );
292 virtual Type *mutate( FunctionType *funcType );
293 virtual Expression *mutate( MemberExpr *memberExpr );
294 virtual Expression *mutate( OffsetofExpr *offsetofExpr );
295 };
296
297 /// Replaces initialization of polymorphic values with alloca, declaration of dtype/ftype with appropriate void expression, and sizeof expressions of polymorphic types with the proper variable
298 class Pass3 : public PolyMutator {
299 public:
300 template< typename DeclClass >
301 DeclClass *handleDecl( DeclClass *decl, Type *type );
302 virtual DeclarationWithType *mutate( FunctionDecl *functionDecl );
303 virtual ObjectDecl *mutate( ObjectDecl *objectDecl );
304 virtual TypedefDecl *mutate( TypedefDecl *objectDecl );
305 virtual TypeDecl *mutate( TypeDecl *objectDecl );
306 virtual Type *mutate( PointerType *pointerType );
307 virtual Type *mutate( FunctionType *funcType );
308 private:
309 };
310
311 } // anonymous namespace
312
313 /// version of mutateAll with special handling for translation unit so you can check the end of the prelude when debugging
314 template< typename MutatorType >
315 inline void mutateTranslationUnit( std::list< Declaration* > &translationUnit, MutatorType &mutator ) {
316 bool seenIntrinsic = false;
317 SemanticError errors;
318 for ( typename std::list< Declaration* >::iterator i = translationUnit.begin(); i != translationUnit.end(); ++i ) {
319 try {
320 if ( *i ) {
321 if ( (*i)->get_linkage() == LinkageSpec::Intrinsic ) {
322 seenIntrinsic = true;
323 } else if ( seenIntrinsic ) {
324 seenIntrinsic = false; // break on this line when debugging for end of prelude
325 }
326
327 *i = dynamic_cast< Declaration* >( (*i)->acceptMutator( mutator ) );
328 assert( *i );
329 } // if
330 } catch( SemanticError &e ) {
331 errors.append( e );
332 } // try
333 } // for
334 if ( ! errors.isEmpty() ) {
335 throw errors;
336 } // if
337 }
338
339 void box( std::list< Declaration *>& translationUnit ) {
340 LayoutFunctionBuilder layoutBuilder;
341 Pass1 pass1;
342 Pass2 pass2;
343 GenericInstantiator instantiator;
344 MemberExprFixer memberFixer;
345 Pass3 pass3;
346
347 layoutBuilder.mutateDeclarationList( translationUnit );
348 mutateTranslationUnit/*All*/( translationUnit, pass1 );
349 mutateTranslationUnit/*All*/( translationUnit, pass2 );
350// instantiateGeneric( translationUnit );
351 instantiator.mutateDeclarationList( translationUnit );
352 mutateTranslationUnit/*All*/( translationUnit, memberFixer );
353 mutateTranslationUnit/*All*/( translationUnit, pass3 );
354 }
355
356 ////////////////////////////////// LayoutFunctionBuilder ////////////////////////////////////////////
357
358 DeclarationWithType *LayoutFunctionBuilder::mutate( FunctionDecl *functionDecl ) {
359 functionDecl->set_functionType( maybeMutate( functionDecl->get_functionType(), *this ) );
360 mutateAll( functionDecl->get_oldDecls(), *this );
361 ++functionNesting;
362 functionDecl->set_statements( maybeMutate( functionDecl->get_statements(), *this ) );
363 --functionNesting;
364 return functionDecl;
365 }
366
367 /// Get a list of type declarations that will affect a layout function
368 std::list< TypeDecl* > takeOtypeOnly( std::list< TypeDecl* > &decls ) {
369 std::list< TypeDecl * > otypeDecls;
370
371 for ( std::list< TypeDecl* >::const_iterator decl = decls.begin(); decl != decls.end(); ++decl ) {
372 if ( (*decl)->get_kind() == TypeDecl::Any ) {
373 otypeDecls.push_back( *decl );
374 }
375 }
376
377 return otypeDecls;
378 }
379
380 /// Adds parameters for otype layout to a function type
381 void addOtypeParams( FunctionType *layoutFnType, std::list< TypeDecl* > &otypeParams ) {
382 BasicType sizeAlignType( Type::Qualifiers(), BasicType::LongUnsignedInt );
383
384 for ( std::list< TypeDecl* >::const_iterator param = otypeParams.begin(); param != otypeParams.end(); ++param ) {
385 TypeInstType paramType( Type::Qualifiers(), (*param)->get_name(), *param );
386 layoutFnType->get_parameters().push_back( new ObjectDecl( sizeofName( &paramType ), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignType.clone(), 0 ) );
387 layoutFnType->get_parameters().push_back( new ObjectDecl( alignofName( &paramType ), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignType.clone(), 0 ) );
388 }
389 }
390
391 /// Builds a layout function declaration
392 FunctionDecl *buildLayoutFunctionDecl( const std::string &typeName, unsigned int functionNesting, FunctionType *layoutFnType ) {
393 // Routines at global scope marked "static" to prevent multiple definitions is separate translation units
394 // because each unit generates copies of the default routines for each aggregate.
395 FunctionDecl *layoutDecl = new FunctionDecl(
396 "__layoutof_" + typeName, functionNesting > 0 ? DeclarationNode::NoStorageClass : DeclarationNode::Static, LinkageSpec::AutoGen, layoutFnType, new CompoundStmt( noLabels ), true, false );
397 layoutDecl->fixUniqueId();
398 return layoutDecl;
399 }
400
401 /// Makes a unary operation
402 Expression *makeOp( const std::string &name, Expression *arg ) {
403 UntypedExpr *expr = new UntypedExpr( new NameExpr( name ) );
404 expr->get_args().push_back( arg );
405 return expr;
406 }
407
408 /// Makes a binary operation
409 Expression *makeOp( const std::string &name, Expression *lhs, Expression *rhs ) {
410 UntypedExpr *expr = new UntypedExpr( new NameExpr( name ) );
411 expr->get_args().push_back( lhs );
412 expr->get_args().push_back( rhs );
413 return expr;
414 }
415
416 /// Returns the dereference of a local pointer variable
417 Expression *derefVar( ObjectDecl *var ) {
418 return makeOp( "*?", new VariableExpr( var ) );
419 }
420
421 /// makes an if-statement with a single-expression if-block and no then block
422 Statement *makeCond( Expression *cond, Expression *ifPart ) {
423 return new IfStmt( noLabels, cond, new ExprStmt( noLabels, ifPart ), 0 );
424 }
425
426 /// makes a statement that assigns rhs to lhs if lhs < rhs
427 Statement *makeAssignMax( Expression *lhs, Expression *rhs ) {
428 return makeCond( makeOp( "?<?", lhs, rhs ), makeOp( "?=?", lhs->clone(), rhs->clone() ) );
429 }
430
431 /// makes a statement that aligns lhs to rhs (rhs should be an integer power of two)
432 Statement *makeAlignTo( Expression *lhs, Expression *rhs ) {
433 // check that the lhs is zeroed out to the level of rhs
434 Expression *ifCond = makeOp( "?&?", lhs, makeOp( "?-?", rhs, new ConstantExpr( Constant( new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ), "1" ) ) ) );
435 // if not aligned, increment to alignment
436 Expression *ifExpr = makeOp( "?+=?", lhs->clone(), makeOp( "?-?", rhs->clone(), ifCond->clone() ) );
437 return makeCond( ifCond, ifExpr );
438 }
439
440 /// adds an expression to a compound statement
441 void addExpr( CompoundStmt *stmts, Expression *expr ) {
442 stmts->get_kids().push_back( new ExprStmt( noLabels, expr ) );
443 }
444
445 /// adds a statement to a compound statement
446 void addStmt( CompoundStmt *stmts, Statement *stmt ) {
447 stmts->get_kids().push_back( stmt );
448 }
449
450 Declaration *LayoutFunctionBuilder::mutate( StructDecl *structDecl ) {
451 // do not generate layout function for "empty" tag structs
452 if ( structDecl->get_members().empty() ) return structDecl;
453
454 // get parameters that can change layout, exiting early if none
455 std::list< TypeDecl* > otypeParams = takeOtypeOnly( structDecl->get_parameters() );
456 if ( otypeParams.empty() ) return structDecl;
457
458 // build layout function signature
459 FunctionType *layoutFnType = new FunctionType( Type::Qualifiers(), false );
460 BasicType *sizeAlignType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
461 PointerType *sizeAlignOutType = new PointerType( Type::Qualifiers(), sizeAlignType );
462
463 ObjectDecl *sizeParam = new ObjectDecl( "__sizeof_" + structDecl->get_name(), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignOutType, 0 );
464 layoutFnType->get_parameters().push_back( sizeParam );
465 ObjectDecl *alignParam = new ObjectDecl( "__alignof_" + structDecl->get_name(), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignOutType->clone(), 0 );
466 layoutFnType->get_parameters().push_back( alignParam );
467 ObjectDecl *offsetParam = new ObjectDecl( "__offsetof_" + structDecl->get_name(), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignOutType->clone(), 0 );
468 layoutFnType->get_parameters().push_back( offsetParam );
469 addOtypeParams( layoutFnType, otypeParams );
470
471 // build function decl
472 FunctionDecl *layoutDecl = buildLayoutFunctionDecl( structDecl->get_name(), functionNesting, layoutFnType );
473
474 // calculate struct layout in function body
475
476 // initialize size and alignment to 0 and 1 (will have at least one member to re-edit size
477 addExpr( layoutDecl->get_statements(), makeOp( "?=?", derefVar( sizeParam ), new ConstantExpr( Constant( sizeAlignType->clone(), "0" ) ) ) );
478 addExpr( layoutDecl->get_statements(), makeOp( "?=?", derefVar( alignParam ), new ConstantExpr( Constant( sizeAlignType->clone(), "1" ) ) ) );
479 unsigned long n_members = 0;
480 bool firstMember = true;
481 for ( std::list< Declaration* >::const_iterator member = structDecl->get_members().begin(); member != structDecl->get_members().end(); ++member ) {
482 DeclarationWithType *dwt = dynamic_cast< DeclarationWithType * >( *member );
483 assert( dwt );
484 Type *memberType = dwt->get_type();
485
486 if ( firstMember ) {
487 firstMember = false;
488 } else {
489 // make sure all members after the first (automatically aligned at 0) are properly padded for alignment
490 addStmt( layoutDecl->get_statements(), makeAlignTo( derefVar( sizeParam ), new AlignofExpr( memberType->clone() ) ) );
491 }
492
493 // place current size in the current offset index
494 addExpr( layoutDecl->get_statements(), makeOp( "?=?", makeOp( "?[?]", new VariableExpr( offsetParam ), new ConstantExpr( Constant::from( n_members ) ) ),
495 derefVar( sizeParam ) ) );
496 ++n_members;
497
498 // add member size to current size
499 addExpr( layoutDecl->get_statements(), makeOp( "?+=?", derefVar( sizeParam ), new SizeofExpr( memberType->clone() ) ) );
500
501 // take max of member alignment and global alignment
502 addStmt( layoutDecl->get_statements(), makeAssignMax( derefVar( alignParam ), new AlignofExpr( memberType->clone() ) ) );
503 }
504 // make sure the type is end-padded to a multiple of its alignment
505 addStmt( layoutDecl->get_statements(), makeAlignTo( derefVar( sizeParam ), derefVar( alignParam ) ) );
506
507 addDeclarationAfter( layoutDecl );
508 return structDecl;
509 }
510
511 Declaration *LayoutFunctionBuilder::mutate( UnionDecl *unionDecl ) {
512 // do not generate layout function for "empty" tag unions
513 if ( unionDecl->get_members().empty() ) return unionDecl;
514
515 // get parameters that can change layout, exiting early if none
516 std::list< TypeDecl* > otypeParams = takeOtypeOnly( unionDecl->get_parameters() );
517 if ( otypeParams.empty() ) return unionDecl;
518
519 // build layout function signature
520 FunctionType *layoutFnType = new FunctionType( Type::Qualifiers(), false );
521 BasicType *sizeAlignType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
522 PointerType *sizeAlignOutType = new PointerType( Type::Qualifiers(), sizeAlignType );
523
524 ObjectDecl *sizeParam = new ObjectDecl( "__sizeof_" + unionDecl->get_name(), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignOutType, 0 );
525 layoutFnType->get_parameters().push_back( sizeParam );
526 ObjectDecl *alignParam = new ObjectDecl( "__alignof_" + unionDecl->get_name(), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, sizeAlignOutType->clone(), 0 );
527 layoutFnType->get_parameters().push_back( alignParam );
528 addOtypeParams( layoutFnType, otypeParams );
529
530 // build function decl
531 FunctionDecl *layoutDecl = buildLayoutFunctionDecl( unionDecl->get_name(), functionNesting, layoutFnType );
532
533 // calculate union layout in function body
534 addExpr( layoutDecl->get_statements(), makeOp( "?=?", derefVar( sizeParam ), new ConstantExpr( Constant( sizeAlignType->clone(), "1" ) ) ) );
535 addExpr( layoutDecl->get_statements(), makeOp( "?=?", derefVar( alignParam ), new ConstantExpr( Constant( sizeAlignType->clone(), "1" ) ) ) );
536 for ( std::list< Declaration* >::const_iterator member = unionDecl->get_members().begin(); member != unionDecl->get_members().end(); ++member ) {
537 DeclarationWithType *dwt = dynamic_cast< DeclarationWithType * >( *member );
538 assert( dwt );
539 Type *memberType = dwt->get_type();
540
541 // take max member size and global size
542 addStmt( layoutDecl->get_statements(), makeAssignMax( derefVar( sizeParam ), new SizeofExpr( memberType->clone() ) ) );
543
544 // take max of member alignment and global alignment
545 addStmt( layoutDecl->get_statements(), makeAssignMax( derefVar( alignParam ), new AlignofExpr( memberType->clone() ) ) );
546 }
547 // make sure the type is end-padded to a multiple of its alignment
548 addStmt( layoutDecl->get_statements(), makeAlignTo( derefVar( sizeParam ), derefVar( alignParam ) ) );
549
550 addDeclarationAfter( layoutDecl );
551 return unionDecl;
552 }
553
554 ////////////////////////////////////////// Pass1 ////////////////////////////////////////////////////
555
556 namespace {
557 std::string makePolyMonoSuffix( FunctionType * function, const TyVarMap &tyVars ) {
558 std::stringstream name;
559
560 // NOTE: this function previously used isPolyObj, which failed to produce
561 // the correct thing in some situations. It's not clear to me why this wasn't working.
562
563 // if the return type or a parameter type involved polymorphic types, then the adapter will need
564 // to take those polymorphic types as pointers. Therefore, there can be two different functions
565 // with the same mangled name, so we need to further mangle the names.
566 for ( std::list< DeclarationWithType *>::iterator retval = function->get_returnVals().begin(); retval != function->get_returnVals().end(); ++retval ) {
567 if ( isPolyType( (*retval)->get_type(), tyVars ) ) {
568 name << "P";
569 } else {
570 name << "M";
571 }
572 }
573 name << "_";
574 std::list< DeclarationWithType *> &paramList = function->get_parameters();
575 for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
576 if ( isPolyType( (*arg)->get_type(), tyVars ) ) {
577 name << "P";
578 } else {
579 name << "M";
580 }
581 } // for
582 return name.str();
583 }
584
585 std::string mangleAdapterName( FunctionType * function, const TyVarMap &tyVars ) {
586 return SymTab::Mangler::mangle( function ) + makePolyMonoSuffix( function, tyVars );
587 }
588
589 std::string makeAdapterName( const std::string &mangleName ) {
590 return "_adapter" + mangleName;
591 }
592
593 Pass1::Pass1() : useRetval( false ), tempNamer( "_temp" ) {}
594
595 /// Returns T if the given declaration is (*?=?)(T *, T) for some TypeInstType T (return not checked, but maybe should be), NULL otherwise
596 TypeInstType *isTypeInstAssignment( DeclarationWithType *decl ) {
597 if ( decl->get_name() == "?=?" ) {
598 if ( FunctionType *funType = getFunctionType( decl->get_type() ) ) {
599 if ( funType->get_parameters().size() == 2 ) {
600 if ( PointerType *pointer = dynamic_cast< PointerType *>( funType->get_parameters().front()->get_type() ) ) {
601 if ( TypeInstType *refType = dynamic_cast< TypeInstType *>( pointer->get_base() ) ) {
602 if ( TypeInstType *refType2 = dynamic_cast< TypeInstType *>( funType->get_parameters().back()->get_type() ) ) {
603 if ( refType->get_name() == refType2->get_name() ) {
604 return refType;
605 } // if
606 } // if
607 } // if
608 } // if
609 } // if
610 } // if
611 } // if
612 return 0;
613 }
614
615 /// returns T if the given declaration is: (*?=?)(T *, T) for some type T (return not checked, but maybe should be), NULL otherwise
616 /// Only picks assignments where neither parameter is cv-qualified
617 Type *isAssignment( DeclarationWithType *decl ) {
618 if ( decl->get_name() == "?=?" ) {
619 if ( FunctionType *funType = getFunctionType( decl->get_type() ) ) {
620 if ( funType->get_parameters().size() == 2 ) {
621 Type::Qualifiers defaultQualifiers;
622 Type *paramType1 = funType->get_parameters().front()->get_type();
623 if ( paramType1->get_qualifiers() != defaultQualifiers ) return 0;
624 Type *paramType2 = funType->get_parameters().back()->get_type();
625 if ( paramType2->get_qualifiers() != defaultQualifiers ) return 0;
626
627 if ( PointerType *pointerType = dynamic_cast< PointerType* >( paramType1 ) ) {
628 Type *baseType1 = pointerType->get_base();
629 if ( baseType1->get_qualifiers() != defaultQualifiers ) return 0;
630 SymTab::Indexer dummy;
631 if ( ResolvExpr::typesCompatible( baseType1, paramType2, dummy ) ) {
632 return baseType1;
633 } // if
634 } // if
635 } // if
636 } // if
637 } // if
638 return 0;
639 }
640
641 void Pass1::findAssignOps( const std::list< TypeDecl *> &forall ) {
642 // what if a nested function uses an assignment operator?
643 // assignOps.clear();
644 for ( std::list< TypeDecl *>::const_iterator i = forall.begin(); i != forall.end(); ++i ) {
645 for ( std::list< DeclarationWithType *>::const_iterator assert = (*i)->get_assertions().begin(); assert != (*i)->get_assertions().end(); ++assert ) {
646 std::string typeName;
647 if ( TypeInstType *typeInst = isTypeInstAssignment( *assert ) ) {
648 assignOps[ typeInst->get_name() ] = *assert;
649 } // if
650 } // for
651 } // for
652 }
653
654 DeclarationWithType *Pass1::mutate( FunctionDecl *functionDecl ) {
655 // if this is a polymorphic assignment function, put it in the map for this scope
656 if ( Type *assignedType = isAssignment( functionDecl ) ) {
657 if ( ! dynamic_cast< TypeInstType* >( assignedType ) ) {
658 scopedAssignOps.insert( assignedType, functionDecl );
659 }
660 }
661
662 if ( functionDecl->get_statements() ) { // empty routine body ?
663 doBeginScope();
664 TyVarMap oldtyVars = scopeTyVars;
665 std::map< std::string, DeclarationWithType *> oldassignOps = assignOps;
666 DeclarationWithType *oldRetval = retval;
667 bool oldUseRetval = useRetval;
668
669 // process polymorphic return value
670 retval = 0;
671 if ( isPolyRet( functionDecl->get_functionType() ) && functionDecl->get_linkage() == LinkageSpec::Cforall ) {
672 retval = functionDecl->get_functionType()->get_returnVals().front();
673
674 // give names to unnamed return values
675 if ( retval->get_name() == "" ) {
676 retval->set_name( "_retparm" );
677 retval->set_linkage( LinkageSpec::C );
678 } // if
679 } // if
680
681 FunctionType *functionType = functionDecl->get_functionType();
682 makeTyVarMap( functionDecl->get_functionType(), scopeTyVars );
683 findAssignOps( functionDecl->get_functionType()->get_forall() );
684
685 std::list< DeclarationWithType *> &paramList = functionType->get_parameters();
686 std::list< FunctionType *> functions;
687 for ( std::list< TypeDecl *>::iterator tyVar = functionType->get_forall().begin(); tyVar != functionType->get_forall().end(); ++tyVar ) {
688 for ( std::list< DeclarationWithType *>::iterator assert = (*tyVar)->get_assertions().begin(); assert != (*tyVar)->get_assertions().end(); ++assert ) {
689 findFunction( (*assert)->get_type(), functions, scopeTyVars, needsAdapter );
690 } // for
691 } // for
692 for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
693 findFunction( (*arg)->get_type(), functions, scopeTyVars, needsAdapter );
694 } // for
695
696 for ( std::list< FunctionType *>::iterator funType = functions.begin(); funType != functions.end(); ++funType ) {
697 std::string mangleName = mangleAdapterName( *funType, scopeTyVars );
698 if ( adapters.find( mangleName ) == adapters.end() ) {
699 std::string adapterName = makeAdapterName( mangleName );
700 adapters.insert( std::pair< std::string, DeclarationWithType *>( mangleName, new ObjectDecl( adapterName, DeclarationNode::NoStorageClass, LinkageSpec::C, 0, new PointerType( Type::Qualifiers(), makeAdapterType( *funType, scopeTyVars ) ), 0 ) ) );
701 } // if
702 } // for
703
704 functionDecl->set_statements( functionDecl->get_statements()->acceptMutator( *this ) );
705
706 scopeTyVars = oldtyVars;
707 assignOps = oldassignOps;
708 // std::cerr << "end FunctionDecl: ";
709 // for ( TyVarMap::iterator i = scopeTyVars.begin(); i != scopeTyVars.end(); ++i ) {
710 // std::cerr << i->first << " ";
711 // }
712 // std::cerr << "\n";
713 retval = oldRetval;
714 useRetval = oldUseRetval;
715 doEndScope();
716 } // if
717 return functionDecl;
718 }
719
720 TypeDecl *Pass1::mutate( TypeDecl *typeDecl ) {
721 scopeTyVars[ typeDecl->get_name() ] = typeDecl->get_kind();
722 return Mutator::mutate( typeDecl );
723 }
724
725 Expression *Pass1::mutate( CommaExpr *commaExpr ) {
726 bool oldUseRetval = useRetval;
727 useRetval = false;
728 commaExpr->set_arg1( maybeMutate( commaExpr->get_arg1(), *this ) );
729 useRetval = oldUseRetval;
730 commaExpr->set_arg2( maybeMutate( commaExpr->get_arg2(), *this ) );
731 return commaExpr;
732 }
733
734 Expression *Pass1::mutate( ConditionalExpr *condExpr ) {
735 bool oldUseRetval = useRetval;
736 useRetval = false;
737 condExpr->set_arg1( maybeMutate( condExpr->get_arg1(), *this ) );
738 useRetval = oldUseRetval;
739 condExpr->set_arg2( maybeMutate( condExpr->get_arg2(), *this ) );
740 condExpr->set_arg3( maybeMutate( condExpr->get_arg3(), *this ) );
741 return condExpr;
742
743 }
744
745 Expression *Pass1::makeOffsetArray( StructInstType *ty ) {
746 std::list< Declaration* > &baseMembers = ty->get_baseStruct()->get_members();
747
748 // make a new temporary array
749 Type *offsetType = new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt );
750 std::stringstream lenGen;
751 lenGen << baseMembers.size();
752 ConstantExpr *lenExpr = new ConstantExpr( Constant( offsetType->clone(), lenGen.str() ) );
753 ObjectDecl *arrayTemp = makeTemporary( new ArrayType( Type::Qualifiers(), offsetType, lenExpr, false, false ) );
754
755 // build initializer list for temporary
756 std::list< Initializer* > inits;
757 for ( std::list< Declaration* >::const_iterator member = baseMembers.begin(); member != baseMembers.end(); ++member ) {
758 DeclarationWithType *memberDecl;
759 if ( DeclarationWithType *origMember = dynamic_cast< DeclarationWithType* >( *member ) ) {
760 memberDecl = origMember->clone();
761 } else {
762 memberDecl = new ObjectDecl( (*member)->get_name(), DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, offsetType->clone(), 0 );
763 }
764 inits.push_back( new SingleInit( new OffsetofExpr( ty->clone(), memberDecl ) ) );
765 }
766 arrayTemp->set_init( new ListInit( inits ) );
767
768 // return variable pointing to temporary
769 return new VariableExpr( arrayTemp );
770 }
771
772 void Pass1::passArgTypeVars( ApplicationExpr *appExpr, Type *parmType, Type *argBaseType, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars, std::set< std::string > &seenTypes ) {
773 Type *polyBase = hasPolyBase( parmType, exprTyVars );
774 if ( polyBase && ! dynamic_cast< TypeInstType* >( polyBase ) ) {
775 std::string sizeName = sizeofName( polyBase );
776 if ( seenTypes.count( sizeName ) ) return;
777
778 arg = appExpr->get_args().insert( arg, new SizeofExpr( argBaseType->clone() ) );
779 arg++;
780 arg = appExpr->get_args().insert( arg, new AlignofExpr( argBaseType->clone() ) );
781 arg++;
782 if ( dynamic_cast< StructInstType* >( polyBase ) ) {
783 if ( StructInstType *argBaseStructType = dynamic_cast< StructInstType* >( argBaseType ) ) {
784 arg = appExpr->get_args().insert( arg, makeOffsetArray( argBaseStructType ) );
785 arg++;
786 } else {
787 throw SemanticError( "Cannot pass non-struct type for generic struct" );
788 }
789 }
790
791 seenTypes.insert( sizeName );
792 }
793 }
794
795 void Pass1::passTypeVars( ApplicationExpr *appExpr, ReferenceToType *polyRetType, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars ) {
796 // pass size/align for type variables
797 for ( TyVarMap::const_iterator tyParm = exprTyVars.begin(); tyParm != exprTyVars.end(); ++tyParm ) {
798 ResolvExpr::EqvClass eqvClass;
799 assert( env );
800 if ( tyParm->second == TypeDecl::Any ) {
801 Type *concrete = env->lookup( tyParm->first );
802 if ( concrete ) {
803 arg = appExpr->get_args().insert( arg, new SizeofExpr( concrete->clone() ) );
804 arg++;
805 arg = appExpr->get_args().insert( arg, new AlignofExpr( concrete->clone() ) );
806 arg++;
807 } else {
808 throw SemanticError( "unbound type variable in application ", appExpr );
809 } // if
810 } // if
811 } // for
812
813 // add size/align for generic types to parameter list
814 if ( appExpr->get_function()->get_results().empty() ) return;
815 FunctionType *funcType = getFunctionType( appExpr->get_function()->get_results().front() );
816 assert( funcType );
817
818 std::list< DeclarationWithType* >::const_iterator fnParm = funcType->get_parameters().begin();
819 std::list< Expression* >::const_iterator fnArg = arg;
820 std::set< std::string > seenTypes; //< names for generic types we've seen
821
822 // a polymorphic return type may need to be added to the argument list
823 if ( polyRetType ) {
824 Type *concRetType = replaceWithConcrete( appExpr, polyRetType );
825 passArgTypeVars( appExpr, polyRetType, concRetType, arg, exprTyVars, seenTypes );
826 }
827
828 // add type information args for presently unseen types in parameter list
829 for ( ; fnParm != funcType->get_parameters().end() && fnArg != appExpr->get_args().end(); ++fnParm, ++fnArg ) {
830 VariableExpr *fnArgBase = getBaseVar( *fnArg );
831 if ( ! fnArgBase || fnArgBase->get_results().empty() ) continue;
832 passArgTypeVars( appExpr, (*fnParm)->get_type(), fnArgBase->get_results().front(), arg, exprTyVars, seenTypes );
833 }
834 }
835
836 ObjectDecl *Pass1::makeTemporary( Type *type ) {
837 ObjectDecl *newObj = new ObjectDecl( tempNamer.newName(), DeclarationNode::NoStorageClass, LinkageSpec::C, 0, type, 0 );
838 stmtsToAdd.push_back( new DeclStmt( noLabels, newObj ) );
839 return newObj;
840 }
841
842 Expression *Pass1::addRetParam( ApplicationExpr *appExpr, FunctionType *function, Type *retType, std::list< Expression *>::iterator &arg ) {
843 // ***** Code Removal ***** After introducing a temporary variable for all return expressions, the following code appears superfluous.
844 // if ( useRetval ) {
845 // assert( retval );
846 // arg = appExpr->get_args().insert( arg, new VariableExpr( retval ) );
847 // arg++;
848 // } else {
849
850 // Create temporary to hold return value of polymorphic function and produce that temporary as a result
851 // using a comma expression. Possibly change comma expression into statement expression "{}" for multiple
852 // return values.
853 ObjectDecl *newObj = makeTemporary( retType->clone() );
854 Expression *paramExpr = new VariableExpr( newObj );
855
856 // If the type of the temporary is not polymorphic, box temporary by taking its address;
857 // otherwise the temporary is already boxed and can be used directly.
858 if ( ! isPolyType( newObj->get_type(), scopeTyVars, env ) ) {
859 paramExpr = new AddressExpr( paramExpr );
860 } // if
861 arg = appExpr->get_args().insert( arg, paramExpr ); // add argument to function call
862 arg++;
863 // Build a comma expression to call the function and emulate a normal return.
864 CommaExpr *commaExpr = new CommaExpr( appExpr, new VariableExpr( newObj ) );
865 commaExpr->set_env( appExpr->get_env() );
866 appExpr->set_env( 0 );
867 return commaExpr;
868 // } // if
869 // return appExpr;
870 }
871
872 void Pass1::replaceParametersWithConcrete( ApplicationExpr *appExpr, std::list< Expression* >& params ) {
873 for ( std::list< Expression* >::iterator param = params.begin(); param != params.end(); ++param ) {
874 TypeExpr *paramType = dynamic_cast< TypeExpr* >( *param );
875 assert(paramType && "Aggregate parameters should be type expressions");
876 paramType->set_type( replaceWithConcrete( appExpr, paramType->get_type(), false ) );
877 }
878 }
879
880 Type *Pass1::replaceWithConcrete( ApplicationExpr *appExpr, Type *type, bool doClone ) {
881 if ( TypeInstType *typeInst = dynamic_cast< TypeInstType * >( type ) ) {
882 Type *concrete = env->lookup( typeInst->get_name() );
883 if ( concrete == 0 ) {
884 throw SemanticError( "Unbound type variable " + typeInst->get_name() + " in ", appExpr );
885 } // if
886 return concrete;
887 } else if ( StructInstType *structType = dynamic_cast< StructInstType* >( type ) ) {
888 if ( doClone ) {
889 structType = structType->clone();
890 }
891 replaceParametersWithConcrete( appExpr, structType->get_parameters() );
892 return structType;
893 } else if ( UnionInstType *unionType = dynamic_cast< UnionInstType* >( type ) ) {
894 if ( doClone ) {
895 unionType = unionType->clone();
896 }
897 replaceParametersWithConcrete( appExpr, unionType->get_parameters() );
898 return unionType;
899 }
900 return type;
901 }
902
903 Expression *Pass1::addPolyRetParam( ApplicationExpr *appExpr, FunctionType *function, ReferenceToType *polyType, std::list< Expression *>::iterator &arg ) {
904 assert( env );
905 Type *concrete = replaceWithConcrete( appExpr, polyType );
906 // add out-parameter for return value
907 return addRetParam( appExpr, function, concrete, arg );
908 }
909
910 Expression *Pass1::applyAdapter( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &tyVars ) {
911 Expression *ret = appExpr;
912 if ( ! function->get_returnVals().empty() && isPolyType( function->get_returnVals().front()->get_type(), tyVars ) ) {
913 ret = addRetParam( appExpr, function, function->get_returnVals().front()->get_type(), arg );
914 } // if
915 std::string mangleName = mangleAdapterName( function, tyVars );
916 std::string adapterName = makeAdapterName( mangleName );
917
918 // cast adaptee to void (*)(), since it may have any type inside a polymorphic function
919 Type * adapteeType = new PointerType( Type::Qualifiers(), new FunctionType( Type::Qualifiers(), true ) );
920 appExpr->get_args().push_front( new CastExpr( appExpr->get_function(), adapteeType ) );
921 appExpr->set_function( new NameExpr( adapterName ) );
922
923 return ret;
924 }
925
926 void Pass1::boxParam( Type *param, Expression *&arg, const TyVarMap &exprTyVars ) {
927 assert( ! arg->get_results().empty() );
928 if ( isPolyType( param, exprTyVars ) ) {
929 if ( isPolyType( arg->get_results().front() ) ) {
930 // if the argument's type is polymorphic, we don't need to box again!
931 return;
932 } else if ( arg->get_results().front()->get_isLvalue() ) {
933 // VariableExpr and MemberExpr are lvalues
934 arg = new AddressExpr( arg );
935 } else {
936 // use type computed in unification to declare boxed variables
937 Type * newType = param->clone();
938 if ( env ) env->apply( newType );
939 ObjectDecl *newObj = new ObjectDecl( tempNamer.newName(), DeclarationNode::NoStorageClass, LinkageSpec::C, 0, newType, 0 );
940 newObj->get_type()->get_qualifiers() = Type::Qualifiers(); // TODO: is this right???
941 stmtsToAdd.push_back( new DeclStmt( noLabels, newObj ) );
942 UntypedExpr *assign = new UntypedExpr( new NameExpr( "?=?" ) );
943 assign->get_args().push_back( new VariableExpr( newObj ) );
944 assign->get_args().push_back( arg );
945 stmtsToAdd.push_back( new ExprStmt( noLabels, assign ) );
946 arg = new AddressExpr( new VariableExpr( newObj ) );
947 } // if
948 } // if
949 }
950
951 /// cast parameters to polymorphic functions so that types are replaced with
952 /// void * if they are type parameters in the formal type.
953 /// this gets rid of warnings from gcc.
954 void addCast( Expression *&actual, Type *formal, const TyVarMap &tyVars ) {
955 Type * newType = formal->clone();
956 if ( getFunctionType( newType ) ) {
957 newType = ScrubTyVars::scrub( newType, tyVars );
958 actual = new CastExpr( actual, newType );
959 } // if
960 }
961
962 void Pass1::boxParams( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars ) {
963 for ( std::list< DeclarationWithType *>::const_iterator param = function->get_parameters().begin(); param != function->get_parameters().end(); ++param, ++arg ) {
964 assert( arg != appExpr->get_args().end() );
965 addCast( *arg, (*param)->get_type(), exprTyVars );
966 boxParam( (*param)->get_type(), *arg, exprTyVars );
967 } // for
968 }
969
970 void Pass1::addInferredParams( ApplicationExpr *appExpr, FunctionType *functionType, std::list< Expression *>::iterator &arg, const TyVarMap &tyVars ) {
971 std::list< Expression *>::iterator cur = arg;
972 for ( std::list< TypeDecl *>::iterator tyVar = functionType->get_forall().begin(); tyVar != functionType->get_forall().end(); ++tyVar ) {
973 for ( std::list< DeclarationWithType *>::iterator assert = (*tyVar)->get_assertions().begin(); assert != (*tyVar)->get_assertions().end(); ++assert ) {
974 InferredParams::const_iterator inferParam = appExpr->get_inferParams().find( (*assert)->get_uniqueId() );
975 assert( inferParam != appExpr->get_inferParams().end() && "NOTE: Explicit casts of polymorphic functions to compatible monomorphic functions are currently unsupported" );
976 Expression *newExpr = inferParam->second.expr->clone();
977 addCast( newExpr, (*assert)->get_type(), tyVars );
978 boxParam( (*assert)->get_type(), newExpr, tyVars );
979 appExpr->get_args().insert( cur, newExpr );
980 } // for
981 } // for
982 }
983
984 void makeRetParm( FunctionType *funcType ) {
985 DeclarationWithType *retParm = funcType->get_returnVals().front();
986
987 // make a new parameter that is a pointer to the type of the old return value
988 retParm->set_type( new PointerType( Type::Qualifiers(), retParm->get_type() ) );
989 funcType->get_parameters().push_front( retParm );
990
991 // we don't need the return value any more
992 funcType->get_returnVals().clear();
993 }
994
995 FunctionType *makeAdapterType( FunctionType *adaptee, const TyVarMap &tyVars ) {
996 // actually make the adapter type
997 FunctionType *adapter = adaptee->clone();
998 if ( ! adapter->get_returnVals().empty() && isPolyType( adapter->get_returnVals().front()->get_type(), tyVars ) ) {
999 makeRetParm( adapter );
1000 } // if
1001 adapter->get_parameters().push_front( new ObjectDecl( "", DeclarationNode::NoStorageClass, LinkageSpec::C, 0, new PointerType( Type::Qualifiers(), new FunctionType( Type::Qualifiers(), true ) ), 0 ) );
1002 return adapter;
1003 }
1004
1005 Expression *makeAdapterArg( DeclarationWithType *param, DeclarationWithType *arg, DeclarationWithType *realParam, const TyVarMap &tyVars ) {
1006 assert( param );
1007 assert( arg );
1008 if ( isPolyType( realParam->get_type(), tyVars ) ) {
1009 if ( ! isPolyType( arg->get_type() ) ) {
1010 UntypedExpr *deref = new UntypedExpr( new NameExpr( "*?" ) );
1011 deref->get_args().push_back( new CastExpr( new VariableExpr( param ), new PointerType( Type::Qualifiers(), arg->get_type()->clone() ) ) );
1012 deref->get_results().push_back( arg->get_type()->clone() );
1013 return deref;
1014 } // if
1015 } // if
1016 return new VariableExpr( param );
1017 }
1018
1019 void addAdapterParams( ApplicationExpr *adapteeApp, std::list< DeclarationWithType *>::iterator arg, std::list< DeclarationWithType *>::iterator param, std::list< DeclarationWithType *>::iterator paramEnd, std::list< DeclarationWithType *>::iterator realParam, const TyVarMap &tyVars ) {
1020 UniqueName paramNamer( "_p" );
1021 for ( ; param != paramEnd; ++param, ++arg, ++realParam ) {
1022 if ( (*param)->get_name() == "" ) {
1023 (*param)->set_name( paramNamer.newName() );
1024 (*param)->set_linkage( LinkageSpec::C );
1025 } // if
1026 adapteeApp->get_args().push_back( makeAdapterArg( *param, *arg, *realParam, tyVars ) );
1027 } // for
1028 }
1029
1030
1031
1032 FunctionDecl *Pass1::makeAdapter( FunctionType *adaptee, FunctionType *realType, const std::string &mangleName, const TyVarMap &tyVars ) {
1033 FunctionType *adapterType = makeAdapterType( adaptee, tyVars );
1034 adapterType = ScrubTyVars::scrub( adapterType, tyVars );
1035 DeclarationWithType *adapteeDecl = adapterType->get_parameters().front();
1036 adapteeDecl->set_name( "_adaptee" );
1037 ApplicationExpr *adapteeApp = new ApplicationExpr( new CastExpr( new VariableExpr( adapteeDecl ), new PointerType( Type::Qualifiers(), realType ) ) );
1038 Statement *bodyStmt;
1039
1040 std::list< TypeDecl *>::iterator tyArg = realType->get_forall().begin();
1041 std::list< TypeDecl *>::iterator tyParam = adapterType->get_forall().begin();
1042 std::list< TypeDecl *>::iterator realTyParam = adaptee->get_forall().begin();
1043 for ( ; tyParam != adapterType->get_forall().end(); ++tyArg, ++tyParam, ++realTyParam ) {
1044 assert( tyArg != realType->get_forall().end() );
1045 std::list< DeclarationWithType *>::iterator assertArg = (*tyArg)->get_assertions().begin();
1046 std::list< DeclarationWithType *>::iterator assertParam = (*tyParam)->get_assertions().begin();
1047 std::list< DeclarationWithType *>::iterator realAssertParam = (*realTyParam)->get_assertions().begin();
1048 for ( ; assertParam != (*tyParam)->get_assertions().end(); ++assertArg, ++assertParam, ++realAssertParam ) {
1049 assert( assertArg != (*tyArg)->get_assertions().end() );
1050 adapteeApp->get_args().push_back( makeAdapterArg( *assertParam, *assertArg, *realAssertParam, tyVars ) );
1051 } // for
1052 } // for
1053
1054 std::list< DeclarationWithType *>::iterator arg = realType->get_parameters().begin();
1055 std::list< DeclarationWithType *>::iterator param = adapterType->get_parameters().begin();
1056 std::list< DeclarationWithType *>::iterator realParam = adaptee->get_parameters().begin();
1057 param++; // skip adaptee parameter
1058 if ( realType->get_returnVals().empty() ) {
1059 addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
1060 bodyStmt = new ExprStmt( noLabels, adapteeApp );
1061 } else if ( isPolyType( adaptee->get_returnVals().front()->get_type(), tyVars ) ) {
1062 if ( (*param)->get_name() == "" ) {
1063 (*param)->set_name( "_ret" );
1064 (*param)->set_linkage( LinkageSpec::C );
1065 } // if
1066 UntypedExpr *assign = new UntypedExpr( new NameExpr( "?=?" ) );
1067 UntypedExpr *deref = new UntypedExpr( new NameExpr( "*?" ) );
1068 deref->get_args().push_back( new CastExpr( new VariableExpr( *param++ ), new PointerType( Type::Qualifiers(), realType->get_returnVals().front()->get_type()->clone() ) ) );
1069 assign->get_args().push_back( deref );
1070 addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
1071 assign->get_args().push_back( adapteeApp );
1072 bodyStmt = new ExprStmt( noLabels, assign );
1073 } else {
1074 // adapter for a function that returns a monomorphic value
1075 addAdapterParams( adapteeApp, arg, param, adapterType->get_parameters().end(), realParam, tyVars );
1076 bodyStmt = new ReturnStmt( noLabels, adapteeApp );
1077 } // if
1078 CompoundStmt *adapterBody = new CompoundStmt( noLabels );
1079 adapterBody->get_kids().push_back( bodyStmt );
1080 std::string adapterName = makeAdapterName( mangleName );
1081 return new FunctionDecl( adapterName, DeclarationNode::NoStorageClass, LinkageSpec::C, adapterType, adapterBody, false, false );
1082 }
1083
1084 void Pass1::passAdapters( ApplicationExpr * appExpr, FunctionType * functionType, const TyVarMap & exprTyVars ) {
1085 // collect a list of function types passed as parameters or implicit parameters (assertions)
1086 std::list< DeclarationWithType *> &paramList = functionType->get_parameters();
1087 std::list< FunctionType *> functions;
1088 for ( std::list< TypeDecl *>::iterator tyVar = functionType->get_forall().begin(); tyVar != functionType->get_forall().end(); ++tyVar ) {
1089 for ( std::list< DeclarationWithType *>::iterator assert = (*tyVar)->get_assertions().begin(); assert != (*tyVar)->get_assertions().end(); ++assert ) {
1090 findFunction( (*assert)->get_type(), functions, exprTyVars, needsAdapter );
1091 } // for
1092 } // for
1093 for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
1094 findFunction( (*arg)->get_type(), functions, exprTyVars, needsAdapter );
1095 } // for
1096
1097 // parameter function types for which an appropriate adapter has been generated. we cannot use the types
1098 // after applying substitutions, since two different parameter types may be unified to the same type
1099 std::set< std::string > adaptersDone;
1100
1101 for ( std::list< FunctionType *>::iterator funType = functions.begin(); funType != functions.end(); ++funType ) {
1102 FunctionType *originalFunction = (*funType)->clone();
1103 FunctionType *realFunction = (*funType)->clone();
1104 std::string mangleName = SymTab::Mangler::mangle( realFunction );
1105
1106 // only attempt to create an adapter or pass one as a parameter if we haven't already done so for this
1107 // pre-substitution parameter function type.
1108 if ( adaptersDone.find( mangleName ) == adaptersDone.end() ) {
1109 adaptersDone.insert( adaptersDone.begin(), mangleName );
1110
1111 // apply substitution to type variables to figure out what the adapter's type should look like
1112 assert( env );
1113 env->apply( realFunction );
1114 mangleName = SymTab::Mangler::mangle( realFunction );
1115 mangleName += makePolyMonoSuffix( originalFunction, exprTyVars );
1116
1117 typedef ScopedMap< std::string, DeclarationWithType* >::iterator AdapterIter;
1118 AdapterIter adapter = adapters.find( mangleName );
1119 if ( adapter == adapters.end() ) {
1120 // adapter has not been created yet in the current scope, so define it
1121 FunctionDecl *newAdapter = makeAdapter( *funType, realFunction, mangleName, exprTyVars );
1122 std::pair< AdapterIter, bool > answer = adapters.insert( std::pair< std::string, DeclarationWithType *>( mangleName, newAdapter ) );
1123 adapter = answer.first;
1124 stmtsToAdd.push_back( new DeclStmt( noLabels, newAdapter ) );
1125 } // if
1126 assert( adapter != adapters.end() );
1127
1128 // add the appropriate adapter as a parameter
1129 appExpr->get_args().push_front( new VariableExpr( adapter->second ) );
1130 } // if
1131 } // for
1132 } // passAdapters
1133
1134 Expression *makeIncrDecrExpr( ApplicationExpr *appExpr, Type *polyType, bool isIncr ) {
1135 NameExpr *opExpr;
1136 if ( isIncr ) {
1137 opExpr = new NameExpr( "?+=?" );
1138 } else {
1139 opExpr = new NameExpr( "?-=?" );
1140 } // if
1141 UntypedExpr *addAssign = new UntypedExpr( opExpr );
1142 if ( AddressExpr *address = dynamic_cast< AddressExpr *>( appExpr->get_args().front() ) ) {
1143 addAssign->get_args().push_back( address->get_arg() );
1144 } else {
1145 addAssign->get_args().push_back( appExpr->get_args().front() );
1146 } // if
1147 addAssign->get_args().push_back( new NameExpr( sizeofName( polyType ) ) );
1148 addAssign->get_results().front() = appExpr->get_results().front()->clone();
1149 if ( appExpr->get_env() ) {
1150 addAssign->set_env( appExpr->get_env() );
1151 appExpr->set_env( 0 );
1152 } // if
1153 appExpr->get_args().clear();
1154 delete appExpr;
1155 return addAssign;
1156 }
1157
1158 Expression *Pass1::handleIntrinsics( ApplicationExpr *appExpr ) {
1159 if ( VariableExpr *varExpr = dynamic_cast< VariableExpr *>( appExpr->get_function() ) ) {
1160 if ( varExpr->get_var()->get_linkage() == LinkageSpec::Intrinsic ) {
1161 if ( varExpr->get_var()->get_name() == "?[?]" ) {
1162 assert( ! appExpr->get_results().empty() );
1163 assert( appExpr->get_args().size() == 2 );
1164 Type *baseType1 = isPolyPtr( appExpr->get_args().front()->get_results().front(), scopeTyVars, env );
1165 Type *baseType2 = isPolyPtr( appExpr->get_args().back()->get_results().front(), scopeTyVars, env );
1166 assert( ! baseType1 || ! baseType2 ); // the arguments cannot both be polymorphic pointers
1167 UntypedExpr *ret = 0;
1168 if ( baseType1 || baseType2 ) { // one of the arguments is a polymorphic pointer
1169 ret = new UntypedExpr( new NameExpr( "?+?" ) );
1170 } // if
1171 if ( baseType1 ) {
1172 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1173 multiply->get_args().push_back( appExpr->get_args().back() );
1174 multiply->get_args().push_back( new NameExpr( sizeofName( baseType1 ) ) );
1175 ret->get_args().push_back( appExpr->get_args().front() );
1176 ret->get_args().push_back( multiply );
1177 } else if ( baseType2 ) {
1178 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1179 multiply->get_args().push_back( appExpr->get_args().front() );
1180 multiply->get_args().push_back( new NameExpr( sizeofName( baseType2 ) ) );
1181 ret->get_args().push_back( multiply );
1182 ret->get_args().push_back( appExpr->get_args().back() );
1183 } // if
1184 if ( baseType1 || baseType2 ) {
1185 ret->get_results().push_front( appExpr->get_results().front()->clone() );
1186 if ( appExpr->get_env() ) {
1187 ret->set_env( appExpr->get_env() );
1188 appExpr->set_env( 0 );
1189 } // if
1190 appExpr->get_args().clear();
1191 delete appExpr;
1192 return ret;
1193 } // if
1194 } else if ( varExpr->get_var()->get_name() == "*?" ) {
1195 assert( ! appExpr->get_results().empty() );
1196 assert( ! appExpr->get_args().empty() );
1197 if ( isPolyType( appExpr->get_results().front(), scopeTyVars, env ) ) {
1198 Expression *ret = appExpr->get_args().front();
1199 delete ret->get_results().front();
1200 ret->get_results().front() = appExpr->get_results().front()->clone();
1201 if ( appExpr->get_env() ) {
1202 ret->set_env( appExpr->get_env() );
1203 appExpr->set_env( 0 );
1204 } // if
1205 appExpr->get_args().clear();
1206 delete appExpr;
1207 return ret;
1208 } // if
1209 } else if ( varExpr->get_var()->get_name() == "?++" || varExpr->get_var()->get_name() == "?--" ) {
1210 assert( ! appExpr->get_results().empty() );
1211 assert( appExpr->get_args().size() == 1 );
1212 if ( Type *baseType = isPolyPtr( appExpr->get_results().front(), scopeTyVars, env ) ) {
1213 Type *tempType = appExpr->get_results().front()->clone();
1214 if ( env ) {
1215 env->apply( tempType );
1216 } // if
1217 ObjectDecl *newObj = makeTemporary( tempType );
1218 VariableExpr *tempExpr = new VariableExpr( newObj );
1219 UntypedExpr *assignExpr = new UntypedExpr( new NameExpr( "?=?" ) );
1220 assignExpr->get_args().push_back( tempExpr->clone() );
1221 if ( AddressExpr *address = dynamic_cast< AddressExpr *>( appExpr->get_args().front() ) ) {
1222 assignExpr->get_args().push_back( address->get_arg()->clone() );
1223 } else {
1224 assignExpr->get_args().push_back( appExpr->get_args().front()->clone() );
1225 } // if
1226 CommaExpr *firstComma = new CommaExpr( assignExpr, makeIncrDecrExpr( appExpr, baseType, varExpr->get_var()->get_name() == "?++" ) );
1227 return new CommaExpr( firstComma, tempExpr );
1228 } // if
1229 } else if ( varExpr->get_var()->get_name() == "++?" || varExpr->get_var()->get_name() == "--?" ) {
1230 assert( ! appExpr->get_results().empty() );
1231 assert( appExpr->get_args().size() == 1 );
1232 if ( Type *baseType = isPolyPtr( appExpr->get_results().front(), scopeTyVars, env ) ) {
1233 return makeIncrDecrExpr( appExpr, baseType, varExpr->get_var()->get_name() == "++?" );
1234 } // if
1235 } else if ( varExpr->get_var()->get_name() == "?+?" || varExpr->get_var()->get_name() == "?-?" ) {
1236 assert( ! appExpr->get_results().empty() );
1237 assert( appExpr->get_args().size() == 2 );
1238 Type *baseType1 = isPolyPtr( appExpr->get_args().front()->get_results().front(), scopeTyVars, env );
1239 Type *baseType2 = isPolyPtr( appExpr->get_args().back()->get_results().front(), scopeTyVars, env );
1240 if ( baseType1 && baseType2 ) {
1241 UntypedExpr *divide = new UntypedExpr( new NameExpr( "?/?" ) );
1242 divide->get_args().push_back( appExpr );
1243 divide->get_args().push_back( new NameExpr( sizeofName( baseType1 ) ) );
1244 divide->get_results().push_front( appExpr->get_results().front()->clone() );
1245 if ( appExpr->get_env() ) {
1246 divide->set_env( appExpr->get_env() );
1247 appExpr->set_env( 0 );
1248 } // if
1249 return divide;
1250 } else if ( baseType1 ) {
1251 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1252 multiply->get_args().push_back( appExpr->get_args().back() );
1253 multiply->get_args().push_back( new NameExpr( sizeofName( baseType1 ) ) );
1254 appExpr->get_args().back() = multiply;
1255 } else if ( baseType2 ) {
1256 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1257 multiply->get_args().push_back( appExpr->get_args().front() );
1258 multiply->get_args().push_back( new NameExpr( sizeofName( baseType2 ) ) );
1259 appExpr->get_args().front() = multiply;
1260 } // if
1261 } else if ( varExpr->get_var()->get_name() == "?+=?" || varExpr->get_var()->get_name() == "?-=?" ) {
1262 assert( ! appExpr->get_results().empty() );
1263 assert( appExpr->get_args().size() == 2 );
1264 Type *baseType = isPolyPtr( appExpr->get_results().front(), scopeTyVars, env );
1265 if ( baseType ) {
1266 UntypedExpr *multiply = new UntypedExpr( new NameExpr( "?*?" ) );
1267 multiply->get_args().push_back( appExpr->get_args().back() );
1268 multiply->get_args().push_back( new NameExpr( sizeofName( baseType ) ) );
1269 appExpr->get_args().back() = multiply;
1270 } // if
1271 } // if
1272 return appExpr;
1273 } // if
1274 } // if
1275 return 0;
1276 }
1277
1278 Expression *Pass1::mutate( ApplicationExpr *appExpr ) {
1279 // std::cerr << "mutate appExpr: ";
1280 // for ( TyVarMap::iterator i = scopeTyVars.begin(); i != scopeTyVars.end(); ++i ) {
1281 // std::cerr << i->first << " ";
1282 // }
1283 // std::cerr << "\n";
1284 bool oldUseRetval = useRetval;
1285 useRetval = false;
1286 appExpr->get_function()->acceptMutator( *this );
1287 mutateAll( appExpr->get_args(), *this );
1288 useRetval = oldUseRetval;
1289
1290 assert( ! appExpr->get_function()->get_results().empty() );
1291 PointerType *pointer = dynamic_cast< PointerType *>( appExpr->get_function()->get_results().front() );
1292 assert( pointer );
1293 FunctionType *function = dynamic_cast< FunctionType *>( pointer->get_base() );
1294 assert( function );
1295
1296 if ( Expression *newExpr = handleIntrinsics( appExpr ) ) {
1297 return newExpr;
1298 } // if
1299
1300 Expression *ret = appExpr;
1301
1302 std::list< Expression *>::iterator arg = appExpr->get_args().begin();
1303 std::list< Expression *>::iterator paramBegin = appExpr->get_args().begin();
1304
1305 TyVarMap exprTyVars;
1306 makeTyVarMap( function, exprTyVars );
1307 ReferenceToType *polyRetType = isPolyRet( function );
1308
1309 if ( polyRetType ) {
1310 ret = addPolyRetParam( appExpr, function, polyRetType, arg );
1311 } else if ( needsAdapter( function, scopeTyVars ) ) {
1312 // std::cerr << "needs adapter: ";
1313 // for ( TyVarMap::iterator i = scopeTyVars.begin(); i != scopeTyVars.end(); ++i ) {
1314 // std::cerr << i->first << " ";
1315 // }
1316 // std::cerr << "\n";
1317 // change the application so it calls the adapter rather than the passed function
1318 ret = applyAdapter( appExpr, function, arg, scopeTyVars );
1319 } // if
1320 arg = appExpr->get_args().begin();
1321
1322 passTypeVars( appExpr, polyRetType, arg, exprTyVars );
1323 addInferredParams( appExpr, function, arg, exprTyVars );
1324
1325 arg = paramBegin;
1326
1327 boxParams( appExpr, function, arg, exprTyVars );
1328
1329 passAdapters( appExpr, function, exprTyVars );
1330
1331 return ret;
1332 }
1333
1334 Expression *Pass1::mutate( UntypedExpr *expr ) {
1335 if ( ! expr->get_results().empty() && isPolyType( expr->get_results().front(), scopeTyVars, env ) ) {
1336 if ( NameExpr *name = dynamic_cast< NameExpr *>( expr->get_function() ) ) {
1337 if ( name->get_name() == "*?" ) {
1338 Expression *ret = expr->get_args().front();
1339 expr->get_args().clear();
1340 delete expr;
1341 return ret->acceptMutator( *this );
1342 } // if
1343 } // if
1344 } // if
1345 return PolyMutator::mutate( expr );
1346 }
1347
1348 Expression *Pass1::mutate( AddressExpr *addrExpr ) {
1349 assert( ! addrExpr->get_arg()->get_results().empty() );
1350
1351 bool needs = false;
1352 if ( UntypedExpr *expr = dynamic_cast< UntypedExpr *>( addrExpr->get_arg() ) ) {
1353 if ( ! expr->get_results().empty() && isPolyType( expr->get_results().front(), scopeTyVars, env ) ) {
1354 if ( NameExpr *name = dynamic_cast< NameExpr *>( expr->get_function() ) ) {
1355 if ( name->get_name() == "*?" ) {
1356 if ( ApplicationExpr * appExpr = dynamic_cast< ApplicationExpr * >( expr->get_args().front() ) ) {
1357 assert( ! appExpr->get_function()->get_results().empty() );
1358 PointerType *pointer = dynamic_cast< PointerType *>( appExpr->get_function()->get_results().front() );
1359 assert( pointer );
1360 FunctionType *function = dynamic_cast< FunctionType *>( pointer->get_base() );
1361 assert( function );
1362 needs = needsAdapter( function, scopeTyVars );
1363 } // if
1364 } // if
1365 } // if
1366 } // if
1367 } // if
1368 addrExpr->set_arg( mutateExpression( addrExpr->get_arg() ) );
1369 if ( isPolyType( addrExpr->get_arg()->get_results().front(), scopeTyVars, env ) || needs ) {
1370 Expression *ret = addrExpr->get_arg();
1371 delete ret->get_results().front();
1372 ret->get_results().front() = addrExpr->get_results().front()->clone();
1373 addrExpr->set_arg( 0 );
1374 delete addrExpr;
1375 return ret;
1376 } else {
1377 return addrExpr;
1378 } // if
1379 }
1380
1381 /// Wraps a function declaration in a new pointer-to-function variable expression
1382 VariableExpr *wrapFunctionDecl( DeclarationWithType *functionDecl ) {
1383 // line below cloned from FixFunction.cc
1384 ObjectDecl *functionObj = new ObjectDecl( functionDecl->get_name(), functionDecl->get_storageClass(), functionDecl->get_linkage(), 0,
1385 new PointerType( Type::Qualifiers(), functionDecl->get_type()->clone() ), 0 );
1386 functionObj->set_mangleName( functionDecl->get_mangleName() );
1387 return new VariableExpr( functionObj );
1388 }
1389
1390 Statement * Pass1::mutate( ReturnStmt *returnStmt ) {
1391 if ( retval && returnStmt->get_expr() ) {
1392 assert( ! returnStmt->get_expr()->get_results().empty() );
1393 // ***** Code Removal ***** After introducing a temporary variable for all return expressions, the following code appears superfluous.
1394 // if ( returnStmt->get_expr()->get_results().front()->get_isLvalue() ) {
1395 // by this point, a cast expr on a polymorphic return value is redundant
1396 while ( CastExpr *castExpr = dynamic_cast< CastExpr *>( returnStmt->get_expr() ) ) {
1397 returnStmt->set_expr( castExpr->get_arg() );
1398 returnStmt->get_expr()->set_env( castExpr->get_env() );
1399 castExpr->set_env( 0 );
1400 castExpr->set_arg( 0 );
1401 delete castExpr;
1402 } //while
1403
1404 // find assignment operator for (polymorphic) return type
1405 ApplicationExpr *assignExpr = 0;
1406 if ( TypeInstType *typeInst = dynamic_cast< TypeInstType *>( retval->get_type() ) ) {
1407 // find assignment operator for type variable
1408 std::map< std::string, DeclarationWithType *>::const_iterator assignIter = assignOps.find( typeInst->get_name() );
1409 if ( assignIter == assignOps.end() ) {
1410 throw SemanticError( "Attempt to return dtype or ftype object in ", returnStmt->get_expr() );
1411 } // if
1412 assignExpr = new ApplicationExpr( new VariableExpr( assignIter->second ) );
1413 } else if ( ReferenceToType *refType = dynamic_cast< ReferenceToType *>( retval->get_type() ) ) {
1414 // find assignment operator for generic type
1415 DeclarationWithType *functionDecl = scopedAssignOps.find( refType );
1416 if ( ! functionDecl ) {
1417 throw SemanticError( "Attempt to return dtype or ftype generic object in ", returnStmt->get_expr() );
1418 }
1419
1420 // wrap it up in an application expression
1421 assignExpr = new ApplicationExpr( wrapFunctionDecl( functionDecl ) );
1422 assignExpr->set_env( env->clone() );
1423
1424 // find each of its needed secondary assignment operators
1425 std::list< Expression* > &tyParams = refType->get_parameters();
1426 std::list< TypeDecl* > &forallParams = functionDecl->get_type()->get_forall();
1427 std::list< Expression* >::const_iterator tyIt = tyParams.begin();
1428 std::list< TypeDecl* >::const_iterator forallIt = forallParams.begin();
1429 for ( ; tyIt != tyParams.end() && forallIt != forallParams.end(); ++tyIt, ++forallIt ) {
1430 if ( (*forallIt)->get_kind() != TypeDecl::Any ) continue; // skip types with no assign op (ftype/dtype)
1431
1432 std::list< DeclarationWithType* > &asserts = (*forallIt)->get_assertions();
1433 assert( ! asserts.empty() && "Type param needs assignment operator assertion" );
1434 DeclarationWithType *actualDecl = asserts.front();
1435 TypeInstType *actualType = isTypeInstAssignment( actualDecl );
1436 assert( actualType && "First assertion of type with assertions should be assignment operator" );
1437 TypeExpr *formalTypeExpr = dynamic_cast< TypeExpr* >( *tyIt );
1438 assert( formalTypeExpr && "type parameters must be type expressions" );
1439 Type *formalType = formalTypeExpr->get_type();
1440 assignExpr->get_env()->add( actualType->get_name(), formalType );
1441
1442 DeclarationWithType *assertAssign = 0;
1443 if ( TypeInstType *formalTypeInstType = dynamic_cast< TypeInstType* >( formalType ) ) {
1444 std::map< std::string, DeclarationWithType *>::const_iterator assertAssignIt = assignOps.find( formalTypeInstType->get_name() );
1445 if ( assertAssignIt == assignOps.end() ) {
1446 throw SemanticError( "No assignment operation found for ", formalTypeInstType );
1447 }
1448 assertAssign = assertAssignIt->second;
1449 } else {
1450 assertAssign = scopedAssignOps.find( formalType );
1451 if ( ! assertAssign ) {
1452 throw SemanticError( "No assignment operation found for ", formalType );
1453 }
1454 }
1455
1456
1457 assignExpr->get_inferParams()[ actualDecl->get_uniqueId() ]
1458 = ParamEntry( assertAssign->get_uniqueId(), assertAssign->get_type()->clone(), actualDecl->get_type()->clone(), wrapFunctionDecl( assertAssign ) );
1459 }
1460 }
1461 assert( assignExpr );
1462
1463 // replace return statement with appropriate assignment to out parameter
1464 Expression *retParm = new NameExpr( retval->get_name() );
1465 retParm->get_results().push_back( new PointerType( Type::Qualifiers(), retval->get_type()->clone() ) );
1466 assignExpr->get_args().push_back( retParm );
1467 assignExpr->get_args().push_back( returnStmt->get_expr() );
1468 stmtsToAdd.push_back( new ExprStmt( noLabels, mutateExpression( assignExpr ) ) );
1469 // } else {
1470 // useRetval = true;
1471 // stmtsToAdd.push_back( new ExprStmt( noLabels, mutateExpression( returnStmt->get_expr() ) ) );
1472 // useRetval = false;
1473 // } // if
1474 returnStmt->set_expr( 0 );
1475 } else {
1476 returnStmt->set_expr( mutateExpression( returnStmt->get_expr() ) );
1477 } // if
1478 return returnStmt;
1479 }
1480
1481 Type * Pass1::mutate( PointerType *pointerType ) {
1482 TyVarMap oldtyVars = scopeTyVars;
1483 makeTyVarMap( pointerType, scopeTyVars );
1484
1485 Type *ret = Mutator::mutate( pointerType );
1486
1487 scopeTyVars = oldtyVars;
1488 return ret;
1489 }
1490
1491 Type * Pass1::mutate( FunctionType *functionType ) {
1492 TyVarMap oldtyVars = scopeTyVars;
1493 makeTyVarMap( functionType, scopeTyVars );
1494
1495 Type *ret = Mutator::mutate( functionType );
1496
1497 scopeTyVars = oldtyVars;
1498 return ret;
1499 }
1500
1501 void Pass1::doBeginScope() {
1502 adapters.beginScope();
1503 scopedAssignOps.beginScope();
1504 }
1505
1506 void Pass1::doEndScope() {
1507 adapters.endScope();
1508 scopedAssignOps.endScope();
1509 }
1510
1511////////////////////////////////////////// Pass2 ////////////////////////////////////////////////////
1512
1513 void Pass2::addAdapters( FunctionType *functionType ) {
1514 std::list< DeclarationWithType *> &paramList = functionType->get_parameters();
1515 std::list< FunctionType *> functions;
1516 for ( std::list< DeclarationWithType *>::iterator arg = paramList.begin(); arg != paramList.end(); ++arg ) {
1517 Type *orig = (*arg)->get_type();
1518 findAndReplaceFunction( orig, functions, scopeTyVars, needsAdapter );
1519 (*arg)->set_type( orig );
1520 }
1521 std::set< std::string > adaptersDone;
1522 for ( std::list< FunctionType *>::iterator funType = functions.begin(); funType != functions.end(); ++funType ) {
1523 std::string mangleName = mangleAdapterName( *funType, scopeTyVars );
1524 if ( adaptersDone.find( mangleName ) == adaptersDone.end() ) {
1525 std::string adapterName = makeAdapterName( mangleName );
1526 paramList.push_front( new ObjectDecl( adapterName, DeclarationNode::NoStorageClass, LinkageSpec::C, 0, new PointerType( Type::Qualifiers(), makeAdapterType( *funType, scopeTyVars ) ), 0 ) );
1527 adaptersDone.insert( adaptersDone.begin(), mangleName );
1528 }
1529 }
1530// deleteAll( functions );
1531 }
1532
1533 template< typename DeclClass >
1534 DeclClass * Pass2::handleDecl( DeclClass *decl, Type *type ) {
1535 DeclClass *ret = static_cast< DeclClass *>( Mutator::mutate( decl ) );
1536
1537 return ret;
1538 }
1539
1540 DeclarationWithType * Pass2::mutate( FunctionDecl *functionDecl ) {
1541 return handleDecl( functionDecl, functionDecl->get_functionType() );
1542 }
1543
1544 ObjectDecl * Pass2::mutate( ObjectDecl *objectDecl ) {
1545 return handleDecl( objectDecl, objectDecl->get_type() );
1546 }
1547
1548 TypeDecl * Pass2::mutate( TypeDecl *typeDecl ) {
1549 scopeTyVars[ typeDecl->get_name() ] = typeDecl->get_kind();
1550 if ( typeDecl->get_base() ) {
1551 return handleDecl( typeDecl, typeDecl->get_base() );
1552 } else {
1553 return Mutator::mutate( typeDecl );
1554 }
1555 }
1556
1557 TypedefDecl * Pass2::mutate( TypedefDecl *typedefDecl ) {
1558 return handleDecl( typedefDecl, typedefDecl->get_base() );
1559 }
1560
1561 Type * Pass2::mutate( PointerType *pointerType ) {
1562 TyVarMap oldtyVars = scopeTyVars;
1563 makeTyVarMap( pointerType, scopeTyVars );
1564
1565 Type *ret = Mutator::mutate( pointerType );
1566
1567 scopeTyVars = oldtyVars;
1568 return ret;
1569 }
1570
1571 Type *Pass2::mutate( FunctionType *funcType ) {
1572 TyVarMap oldtyVars = scopeTyVars;
1573 makeTyVarMap( funcType, scopeTyVars );
1574
1575 // move polymorphic return type to parameter list
1576 if ( isPolyRet( funcType ) ) {
1577 DeclarationWithType *ret = funcType->get_returnVals().front();
1578 ret->set_type( new PointerType( Type::Qualifiers(), ret->get_type() ) );
1579 funcType->get_parameters().push_front( ret );
1580 funcType->get_returnVals().pop_front();
1581 }
1582
1583 // add size/align and assertions for type parameters to parameter list
1584 std::list< DeclarationWithType *>::iterator last = funcType->get_parameters().begin();
1585 std::list< DeclarationWithType *> inferredParams;
1586 ObjectDecl newObj( "", DeclarationNode::NoStorageClass, LinkageSpec::C, 0, new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ), 0 );
1587 ObjectDecl newPtr( "", DeclarationNode::NoStorageClass, LinkageSpec::C, 0,
1588 new PointerType( Type::Qualifiers(), new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ) ), 0 );
1589// ObjectDecl *newFunPtr = new ObjectDecl( "", DeclarationNode::NoStorageClass, LinkageSpec::Cforall, 0, new PointerType( Type::Qualifiers(), new FunctionType( Type::Qualifiers(), true ) ), 0 );
1590 for ( std::list< TypeDecl *>::const_iterator tyParm = funcType->get_forall().begin(); tyParm != funcType->get_forall().end(); ++tyParm ) {
1591 ObjectDecl *sizeParm, *alignParm;
1592 // add all size and alignment parameters to parameter list
1593 if ( (*tyParm)->get_kind() == TypeDecl::Any ) {
1594 TypeInstType parmType( Type::Qualifiers(), (*tyParm)->get_name(), *tyParm );
1595
1596 sizeParm = newObj.clone();
1597 sizeParm->set_name( sizeofName( &parmType ) );
1598 last = funcType->get_parameters().insert( last, sizeParm );
1599 ++last;
1600
1601 alignParm = newObj.clone();
1602 alignParm->set_name( alignofName( &parmType ) );
1603 last = funcType->get_parameters().insert( last, alignParm );
1604 ++last;
1605 }
1606 // move all assertions into parameter list
1607 for ( std::list< DeclarationWithType *>::iterator assert = (*tyParm)->get_assertions().begin(); assert != (*tyParm)->get_assertions().end(); ++assert ) {
1608// *assert = (*assert)->acceptMutator( *this );
1609 inferredParams.push_back( *assert );
1610 }
1611 (*tyParm)->get_assertions().clear();
1612 }
1613
1614 // add size/align for generic parameter types to parameter list
1615 std::set< std::string > seenTypes; // sizeofName for generic types we've seen
1616 for ( std::list< DeclarationWithType* >::const_iterator fnParm = last; fnParm != funcType->get_parameters().end(); ++fnParm ) {
1617 Type *polyBase = hasPolyBase( (*fnParm)->get_type(), scopeTyVars );
1618 if ( polyBase && ! dynamic_cast< TypeInstType* >( polyBase ) ) {
1619 std::string sizeName = sizeofName( polyBase );
1620 if ( seenTypes.count( sizeName ) ) continue;
1621
1622 ObjectDecl *sizeParm, *alignParm, *offsetParm;
1623 sizeParm = newObj.clone();
1624 sizeParm->set_name( sizeName );
1625 last = funcType->get_parameters().insert( last, sizeParm );
1626 ++last;
1627
1628 alignParm = newObj.clone();
1629 alignParm->set_name( alignofName( polyBase ) );
1630 last = funcType->get_parameters().insert( last, alignParm );
1631 ++last;
1632
1633 if ( dynamic_cast< StructInstType* >( polyBase ) ) {
1634 offsetParm = newPtr.clone();
1635 offsetParm->set_name( offsetofName( polyBase ) );
1636 last = funcType->get_parameters().insert( last, offsetParm );
1637 ++last;
1638 }
1639
1640 seenTypes.insert( sizeName );
1641 }
1642 }
1643
1644 // splice assertion parameters into parameter list
1645 funcType->get_parameters().splice( last, inferredParams );
1646 addAdapters( funcType );
1647 mutateAll( funcType->get_returnVals(), *this );
1648 mutateAll( funcType->get_parameters(), *this );
1649
1650 scopeTyVars = oldtyVars;
1651 return funcType;
1652 }
1653
1654//////////////////////////////////////// GenericInstantiator //////////////////////////////////////////////////
1655
1656 /// Makes substitutions of params into baseParams; returns true if all parameters substituted for a concrete type
1657 bool makeSubstitutions( const std::list< TypeDecl* >& baseParams, const std::list< Expression* >& params, std::list< TypeExpr* >& out ) {
1658 bool allConcrete = true; // will finish the substitution list even if they're not all concrete
1659
1660 // substitute concrete types for given parameters, and incomplete types for placeholders
1661 std::list< TypeDecl* >::const_iterator baseParam = baseParams.begin();
1662 std::list< Expression* >::const_iterator param = params.begin();
1663 for ( ; baseParam != baseParams.end() && param != params.end(); ++baseParam, ++param ) {
1664 // switch ( (*baseParam)->get_kind() ) {
1665 // case TypeDecl::Any: { // any type is a valid substitution here; complete types can be used to instantiate generics
1666 TypeExpr *paramType = dynamic_cast< TypeExpr* >( *param );
1667 assert(paramType && "Aggregate parameters should be type expressions");
1668 out.push_back( paramType->clone() );
1669 // check that the substituted type isn't a type variable itself
1670 if ( dynamic_cast< TypeInstType* >( paramType->get_type() ) ) {
1671 allConcrete = false;
1672 }
1673 // break;
1674 // }
1675 // case TypeDecl::Dtype: // dtype can be consistently replaced with void [only pointers, which become void*]
1676 // out.push_back( new TypeExpr( new VoidType( Type::Qualifiers() ) ) );
1677 // break;
1678 // case TypeDecl::Ftype: // pointer-to-ftype can be consistently replaced with void (*)(void) [similar to dtype]
1679 // out.push_back( new TypeExpr( new FunctionType( Type::Qualifiers(), false ) ) );
1680 // break;
1681 // }
1682 }
1683
1684 // if any parameters left over, not done
1685 if ( baseParam != baseParams.end() ) return false;
1686 // // if not enough parameters given, substitute remaining incomplete types for placeholders
1687 // for ( ; baseParam != baseParams.end(); ++baseParam ) {
1688 // switch ( (*baseParam)->get_kind() ) {
1689 // case TypeDecl::Any: // no more substitutions here, fail early
1690 // return false;
1691 // case TypeDecl::Dtype: // dtype can be consistently replaced with void [only pointers, which become void*]
1692 // out.push_back( new TypeExpr( new VoidType( Type::Qualifiers() ) ) );
1693 // break;
1694 // case TypeDecl::Ftype: // pointer-to-ftype can be consistently replaced with void (*)(void) [similar to dtype]
1695 // out.push_back( new TypeExpr( new FunctionType( Type::Qualifiers(), false ) ) );
1696 // break;
1697 // }
1698 // }
1699
1700 return allConcrete;
1701 }
1702
1703 /// Substitutes types of members of in according to baseParams => typeSubs, appending the result to out
1704 void substituteMembers( const std::list< Declaration* >& in, const std::list< TypeDecl* >& baseParams, const std::list< TypeExpr* >& typeSubs,
1705 std::list< Declaration* >& out ) {
1706 // substitute types into new members
1707 TypeSubstitution subs( baseParams.begin(), baseParams.end(), typeSubs.begin() );
1708 for ( std::list< Declaration* >::const_iterator member = in.begin(); member != in.end(); ++member ) {
1709 Declaration *newMember = (*member)->clone();
1710 subs.apply(newMember);
1711 out.push_back( newMember );
1712 }
1713 }
1714
1715 Type* GenericInstantiator::mutate( StructInstType *inst ) {
1716 // mutate subtypes
1717 Type *mutated = Mutator::mutate( inst );
1718 inst = dynamic_cast< StructInstType* >( mutated );
1719 if ( ! inst ) return mutated;
1720
1721 // exit early if no need for further mutation
1722 if ( inst->get_parameters().empty() ) return inst;
1723 assert( inst->get_baseParameters() && "Base struct has parameters" );
1724
1725 // check if type can be concretely instantiated; put substitutions into typeSubs
1726 std::list< TypeExpr* > typeSubs;
1727 if ( ! makeSubstitutions( *inst->get_baseParameters(), inst->get_parameters(), typeSubs ) ) {
1728 deleteAll( typeSubs );
1729 return inst;
1730 }
1731
1732 // make concrete instantiation of generic type
1733 StructDecl *concDecl = lookup( inst, typeSubs );
1734 if ( ! concDecl ) {
1735 // set concDecl to new type, insert type declaration into statements to add
1736 concDecl = new StructDecl( typeNamer.newName( inst->get_name() ) );
1737 substituteMembers( inst->get_baseStruct()->get_members(), *inst->get_baseParameters(), typeSubs, concDecl->get_members() );
1738 DeclMutator::addDeclaration( concDecl );
1739 insert( inst, typeSubs, concDecl );
1740 }
1741 StructInstType *newInst = new StructInstType( inst->get_qualifiers(), concDecl->get_name() );
1742 newInst->set_baseStruct( concDecl );
1743
1744 deleteAll( typeSubs );
1745 delete inst;
1746 return newInst;
1747 }
1748
1749 Type* GenericInstantiator::mutate( UnionInstType *inst ) {
1750 // mutate subtypes
1751 Type *mutated = Mutator::mutate( inst );
1752 inst = dynamic_cast< UnionInstType* >( mutated );
1753 if ( ! inst ) return mutated;
1754
1755 // exit early if no need for further mutation
1756 if ( inst->get_parameters().empty() ) return inst;
1757 assert( inst->get_baseParameters() && "Base union has parameters" );
1758
1759 // check if type can be concretely instantiated; put substitutions into typeSubs
1760 std::list< TypeExpr* > typeSubs;
1761 if ( ! makeSubstitutions( *inst->get_baseParameters(), inst->get_parameters(), typeSubs ) ) {
1762 deleteAll( typeSubs );
1763 return inst;
1764 }
1765
1766 // make concrete instantiation of generic type
1767 UnionDecl *concDecl = lookup( inst, typeSubs );
1768 if ( ! concDecl ) {
1769 // set concDecl to new type, insert type declaration into statements to add
1770 concDecl = new UnionDecl( typeNamer.newName( inst->get_name() ) );
1771 substituteMembers( inst->get_baseUnion()->get_members(), *inst->get_baseParameters(), typeSubs, concDecl->get_members() );
1772 DeclMutator::addDeclaration( concDecl );
1773 insert( inst, typeSubs, concDecl );
1774 }
1775 UnionInstType *newInst = new UnionInstType( inst->get_qualifiers(), concDecl->get_name() );
1776 newInst->set_baseUnion( concDecl );
1777
1778 deleteAll( typeSubs );
1779 delete inst;
1780 return newInst;
1781 }
1782
1783 // /// Gets the base struct or union declaration for a member expression; NULL if not applicable
1784 // AggregateDecl* getMemberBaseDecl( MemberExpr *memberExpr ) {
1785 // // get variable for member aggregate
1786 // VariableExpr *varExpr = dynamic_cast< VariableExpr* >( memberExpr->get_aggregate() );
1787 // if ( ! varExpr ) return NULL;
1788 //
1789 // // get object for variable
1790 // ObjectDecl *objectDecl = dynamic_cast< ObjectDecl* >( varExpr->get_var() );
1791 // if ( ! objectDecl ) return NULL;
1792 //
1793 // // get base declaration from object type
1794 // Type *objectType = objectDecl->get_type();
1795 // StructInstType *structType = dynamic_cast< StructInstType* >( objectType );
1796 // if ( structType ) return structType->get_baseStruct();
1797 // UnionInstType *unionType = dynamic_cast< UnionInstType* >( objectType );
1798 // if ( unionType ) return unionType->get_baseUnion();
1799 //
1800 // return NULL;
1801 // }
1802 //
1803 // /// Finds the declaration with the given name, returning decls.end() if none such
1804 // std::list< Declaration* >::const_iterator findDeclNamed( const std::list< Declaration* > &decls, const std::string &name ) {
1805 // for( std::list< Declaration* >::const_iterator decl = decls.begin(); decl != decls.end(); ++decl ) {
1806 // if ( (*decl)->get_name() == name ) return decl;
1807 // }
1808 // return decls.end();
1809 // }
1810 //
1811 // Expression* Instantiate::mutate( MemberExpr *memberExpr ) {
1812 // // mutate, exiting early if no longer MemberExpr
1813 // Expression *expr = Mutator::mutate( memberExpr );
1814 // memberExpr = dynamic_cast< MemberExpr* >( expr );
1815 // if ( ! memberExpr ) return expr;
1816 //
1817 // // get declaration of member and base declaration of member, exiting early if not found
1818 // AggregateDecl *memberBase = getMemberBaseDecl( memberExpr );
1819 // if ( ! memberBase ) return memberExpr;
1820 // DeclarationWithType *memberDecl = memberExpr->get_member();
1821 // std::list< Declaration* >::const_iterator baseIt = findDeclNamed( memberBase->get_members(), memberDecl->get_name() );
1822 // if ( baseIt == memberBase->get_members().end() ) return memberExpr;
1823 // DeclarationWithType *baseDecl = dynamic_cast< DeclarationWithType* >( *baseIt );
1824 // if ( ! baseDecl ) return memberExpr;
1825 //
1826 // // check if stated type of the member is not the type of the member's declaration; if so, need a cast
1827 // // this *SHOULD* be safe, I don't think anything but the void-replacements I put in for dtypes would make it past the typechecker
1828 // SymTab::Indexer dummy;
1829 // if ( ResolvExpr::typesCompatible( memberDecl->get_type(), baseDecl->get_type(), dummy ) ) return memberExpr;
1830 // else return new CastExpr( memberExpr, memberDecl->get_type() );
1831 // }
1832
1833 void GenericInstantiator::doBeginScope() {
1834 DeclMutator::doBeginScope();
1835 instantiations.beginScope();
1836 }
1837
1838 void GenericInstantiator::doEndScope() {
1839 DeclMutator::doEndScope();
1840 instantiations.endScope();
1841 }
1842
1843////////////////////////////////////////// MemberExprFixer ////////////////////////////////////////////////////
1844
1845 template< typename DeclClass >
1846 DeclClass * MemberExprFixer::handleDecl( DeclClass *decl, Type *type ) {
1847 TyVarMap oldtyVars = scopeTyVars;
1848 makeTyVarMap( type, scopeTyVars );
1849
1850 DeclClass *ret = static_cast< DeclClass *>( Mutator::mutate( decl ) );
1851
1852 scopeTyVars = oldtyVars;
1853 return ret;
1854 }
1855
1856 ObjectDecl * MemberExprFixer::mutate( ObjectDecl *objectDecl ) {
1857 return handleDecl( objectDecl, objectDecl->get_type() );
1858 }
1859
1860 DeclarationWithType * MemberExprFixer::mutate( FunctionDecl *functionDecl ) {
1861 return handleDecl( functionDecl, functionDecl->get_functionType() );
1862 }
1863
1864 TypedefDecl * MemberExprFixer::mutate( TypedefDecl *typedefDecl ) {
1865 return handleDecl( typedefDecl, typedefDecl->get_base() );
1866 }
1867
1868 TypeDecl * MemberExprFixer::mutate( TypeDecl *typeDecl ) {
1869 scopeTyVars[ typeDecl->get_name() ] = typeDecl->get_kind();
1870 return Mutator::mutate( typeDecl );
1871 }
1872
1873 Type * MemberExprFixer::mutate( PointerType *pointerType ) {
1874 TyVarMap oldtyVars = scopeTyVars;
1875 makeTyVarMap( pointerType, scopeTyVars );
1876
1877 Type *ret = Mutator::mutate( pointerType );
1878
1879 scopeTyVars = oldtyVars;
1880 return ret;
1881 }
1882
1883 Type * MemberExprFixer::mutate( FunctionType *functionType ) {
1884 TyVarMap oldtyVars = scopeTyVars;
1885 makeTyVarMap( functionType, scopeTyVars );
1886
1887 Type *ret = Mutator::mutate( functionType );
1888
1889 scopeTyVars = oldtyVars;
1890 return ret;
1891 }
1892
1893 Statement *MemberExprFixer::mutate( DeclStmt *declStmt ) {
1894 if ( ObjectDecl *objectDecl = dynamic_cast< ObjectDecl *>( declStmt->get_decl() ) ) {
1895 if ( isPolyType( objectDecl->get_type(), scopeTyVars ) ) {
1896 // change initialization of a polymorphic value object
1897 // to allocate storage with alloca
1898 Type *declType = objectDecl->get_type();
1899 UntypedExpr *alloc = new UntypedExpr( new NameExpr( "__builtin_alloca" ) );
1900 alloc->get_args().push_back( new NameExpr( sizeofName( declType ) ) );
1901
1902 delete objectDecl->get_init();
1903
1904 std::list<Expression*> designators;
1905 objectDecl->set_init( new SingleInit( alloc, designators ) );
1906 }
1907 }
1908 return Mutator::mutate( declStmt );
1909 }
1910
1911 /// Finds the member in the base list that matches the given declaration; returns its index, or -1 if not present
1912 long findMember( DeclarationWithType *memberDecl, std::list< Declaration* > &baseDecls ) {
1913 long i = 0;
1914 for(std::list< Declaration* >::const_iterator decl = baseDecls.begin(); decl != baseDecls.end(); ++decl, ++i ) {
1915 if ( memberDecl->get_name() != (*decl)->get_name() ) continue;
1916
1917 if ( DeclarationWithType *declWithType = dynamic_cast< DeclarationWithType* >( *decl ) ) {
1918 if ( memberDecl->get_mangleName().empty() || declWithType->get_mangleName().empty()
1919 || memberDecl->get_mangleName() == declWithType->get_mangleName() ) return i;
1920 else continue;
1921 } else return i;
1922 }
1923 return -1;
1924 }
1925
1926 /// Returns an index expression into the offset array for a type
1927 Expression *makeOffsetIndex( Type *objectType, long i ) {
1928 std::stringstream offset_namer;
1929 offset_namer << i;
1930 ConstantExpr *fieldIndex = new ConstantExpr( Constant( new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ), offset_namer.str() ) );
1931 UntypedExpr *fieldOffset = new UntypedExpr( new NameExpr( "?[?]" ) );
1932 fieldOffset->get_args().push_back( new NameExpr( offsetofName( objectType ) ) );
1933 fieldOffset->get_args().push_back( fieldIndex );
1934 return fieldOffset;
1935 }
1936
1937 /// Returns an expression dereferenced n times
1938 Expression *makeDerefdVar( Expression *derefdVar, long n ) {
1939 for ( int i = 1; i < n; ++i ) {
1940 UntypedExpr *derefExpr = new UntypedExpr( new NameExpr( "*?" ) );
1941 derefExpr->get_args().push_back( derefdVar );
1942 derefdVar = derefExpr;
1943 }
1944 return derefdVar;
1945 }
1946
1947 Expression *MemberExprFixer::mutate( MemberExpr *memberExpr ) {
1948 // mutate, exiting early if no longer MemberExpr
1949 Expression *expr = Mutator::mutate( memberExpr );
1950 memberExpr = dynamic_cast< MemberExpr* >( expr );
1951 if ( ! memberExpr ) return expr;
1952
1953 // get declaration for base struct, exiting early if not found
1954 int varDepth;
1955 VariableExpr *varExpr = getBaseVar( memberExpr->get_aggregate(), &varDepth );
1956 if ( ! varExpr ) return memberExpr;
1957 ObjectDecl *objectDecl = dynamic_cast< ObjectDecl* >( varExpr->get_var() );
1958 if ( ! objectDecl ) return memberExpr;
1959
1960 // only mutate member expressions for polymorphic types
1961 int tyDepth;
1962 Type *objectType = hasPolyBase( objectDecl->get_type(), scopeTyVars, &tyDepth );
1963 if ( ! objectType ) return memberExpr;
1964
1965 Expression *newMemberExpr = 0;
1966 if ( StructInstType *structType = dynamic_cast< StructInstType* >( objectType ) ) {
1967 // look up offset index
1968 long i = findMember( memberExpr->get_member(), structType->get_baseStruct()->get_members() );
1969 if ( i == -1 ) return memberExpr;
1970
1971 // replace member expression with pointer to base plus offset
1972 UntypedExpr *fieldLoc = new UntypedExpr( new NameExpr( "?+?" ) );
1973 fieldLoc->get_args().push_back( makeDerefdVar( varExpr->clone(), varDepth ) );
1974 fieldLoc->get_args().push_back( makeOffsetIndex( objectType, i ) );
1975 newMemberExpr = fieldLoc;
1976 } else if ( dynamic_cast< UnionInstType* >( objectType ) ) {
1977 // union members are all at offset zero, so build appropriately-dereferenced variable
1978 newMemberExpr = makeDerefdVar( varExpr->clone(), varDepth );
1979 } else return memberExpr;
1980 assert( newMemberExpr );
1981
1982 Type *memberType = memberExpr->get_member()->get_type();
1983 if ( ! isPolyType( memberType, scopeTyVars ) ) {
1984 // 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
1985 CastExpr *ptrCastExpr = new CastExpr( newMemberExpr, new PointerType( Type::Qualifiers(), memberType->clone() ) );
1986 UntypedExpr *derefExpr = new UntypedExpr( new NameExpr( "*?" ) );
1987 derefExpr->get_args().push_back( ptrCastExpr );
1988 newMemberExpr = derefExpr;
1989 }
1990
1991 delete memberExpr;
1992 return newMemberExpr;
1993 }
1994
1995 Expression *MemberExprFixer::mutate( OffsetofExpr *offsetofExpr ) {
1996 // mutate, exiting early if no longer OffsetofExpr
1997 Expression *expr = Mutator::mutate( offsetofExpr );
1998 offsetofExpr = dynamic_cast< OffsetofExpr* >( expr );
1999 if ( ! offsetofExpr ) return expr;
2000
2001 // only mutate expressions for polymorphic structs/unions
2002 Type *ty = isPolyType( offsetofExpr->get_type(), scopeTyVars );
2003 if ( ! ty ) return offsetofExpr;
2004
2005 if ( StructInstType *structType = dynamic_cast< StructInstType* >( ty ) ) {
2006 // replace offsetof expression by index into offset array
2007 long i = findMember( offsetofExpr->get_member(), structType->get_baseStruct()->get_members() );
2008 if ( i == -1 ) return offsetofExpr;
2009
2010 Expression *offsetInd = makeOffsetIndex( ty, i );
2011 delete offsetofExpr;
2012 return offsetInd;
2013 } else if ( dynamic_cast< UnionInstType* >( ty ) ) {
2014 // all union members are at offset zero
2015 delete offsetofExpr;
2016 return new ConstantExpr( Constant( new BasicType( Type::Qualifiers(), BasicType::LongUnsignedInt ), std::string("0") ) );
2017 } else return offsetofExpr;
2018 }
2019
2020////////////////////////////////////////// Pass3 ////////////////////////////////////////////////////
2021
2022 template< typename DeclClass >
2023 DeclClass * Pass3::handleDecl( DeclClass *decl, Type *type ) {
2024 TyVarMap oldtyVars = scopeTyVars;
2025 makeTyVarMap( type, scopeTyVars );
2026
2027 DeclClass *ret = static_cast< DeclClass *>( Mutator::mutate( decl ) );
2028 ScrubTyVars::scrub( decl, scopeTyVars );
2029
2030 scopeTyVars = oldtyVars;
2031 return ret;
2032 }
2033
2034 ObjectDecl * Pass3::mutate( ObjectDecl *objectDecl ) {
2035 return handleDecl( objectDecl, objectDecl->get_type() );
2036 }
2037
2038 DeclarationWithType * Pass3::mutate( FunctionDecl *functionDecl ) {
2039 return handleDecl( functionDecl, functionDecl->get_functionType() );
2040 }
2041
2042 TypedefDecl * Pass3::mutate( TypedefDecl *typedefDecl ) {
2043 return handleDecl( typedefDecl, typedefDecl->get_base() );
2044 }
2045
2046 TypeDecl * Pass3::mutate( TypeDecl *typeDecl ) {
2047// Initializer *init = 0;
2048// std::list< Expression *> designators;
2049// scopeTyVars[ typeDecl->get_name() ] = typeDecl->get_kind();
2050// if ( typeDecl->get_base() ) {
2051// init = new SimpleInit( new SizeofExpr( handleDecl( typeDecl, typeDecl->get_base() ) ), designators );
2052// }
2053// return new ObjectDecl( typeDecl->get_name(), Declaration::Extern, LinkageSpec::C, 0, new BasicType( Type::Qualifiers(), BasicType::UnsignedInt ), init );
2054
2055 scopeTyVars[ typeDecl->get_name() ] = typeDecl->get_kind();
2056 return Mutator::mutate( typeDecl );
2057 }
2058
2059 Type * Pass3::mutate( PointerType *pointerType ) {
2060 TyVarMap oldtyVars = scopeTyVars;
2061 makeTyVarMap( pointerType, scopeTyVars );
2062
2063 Type *ret = Mutator::mutate( pointerType );
2064
2065 scopeTyVars = oldtyVars;
2066 return ret;
2067 }
2068
2069 Type * Pass3::mutate( FunctionType *functionType ) {
2070 TyVarMap oldtyVars = scopeTyVars;
2071 makeTyVarMap( functionType, scopeTyVars );
2072
2073 Type *ret = Mutator::mutate( functionType );
2074
2075 scopeTyVars = oldtyVars;
2076 return ret;
2077 }
2078 } // anonymous namespace
2079} // namespace GenPoly
2080
2081// Local Variables: //
2082// tab-width: 4 //
2083// mode: c++ //
2084// compile-command: "make install" //
2085// End: //
Note: See TracBrowser for help on using the repository browser.