source: src/GenPoly/Box.cc@ 96fc67b

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 96fc67b was 4573e3c, checked in by Rob Schluntz <rschlunt@…>, 8 years ago

Fix pointer cast warning

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