source: src/GenPoly/Box.cc@ c0d00b6

ADT arm-eh ast-experimental cleanup-dtors enum forall-pointer-decay jacob/cs343-translation jenkins-sandbox new-ast new-ast-unique-expr pthread-emulation qualifiedEnum
Last change on this file since c0d00b6 was 8dceeb7, checked in by Rob Schluntz <rschlunt@…>, 8 years ago

Monomorphize polymorphic aggregate (but not generic) members [fixes #61]

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