source: src/GenPoly/Box.cc@ b10c621c

ADT aaron-thesis arm-eh ast-experimental cleanup-dtors deferred_resn demangler enum forall-pointer-decay jacob/cs343-translation jenkins-sandbox new-ast new-ast-unique-expr new-env no_list persistent-indexer pthread-emulation qualifiedEnum resolv-new with_gc
Last change on this file since b10c621c was d29fa5f, checked in by Rob Schluntz <rschlunt@…>, 8 years ago

Remove has_result

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