source: src/GenPoly/Box.cc@ df9e412

ADT ast-experimental
Last change on this file since df9e412 was 49db841, checked in by Andrew Beach <ajbeach@…>, 3 years ago

Cleaning old box pass for easier translation. Renamed the numbered sub-passes.

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