source: src/GenPoly/Box.cc@ 382467f

ast-experimental
Last change on this file since 382467f was 9feb34b, checked in by Andrew Beach <ajbeach@…>, 3 years ago

Moved toString and toCString to a new header. Updated includes. cassert was somehow getting instances of toString before but that stopped working so I embedded the new smaller include.

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