source: src/Validate/Autogen.cpp@ 022bce0

Last change on this file since 022bce0 was 1761046, checked in by Andrew Beach <ajbeach@…>, 19 months ago

Note to self: Check the comments before you push.

  • Property mode set to 100644
File size: 29.4 KB
RevLine 
[a488783]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// Autogen.cpp -- Generate automatic routines for data types.
8//
9// Author : Andrew Beach
10// Created On : Thu Dec 2 13:44:00 2021
11// Last Modified By : Andrew Beach
[20737104]12// Last Modified On : Tue Sep 20 16:00:00 2022
13// Update Count : 2
[a488783]14//
15
16#include "Autogen.hpp"
17
18#include <algorithm> // for count_if
19#include <cassert> // for strict_dynamic_cast, assert, assertf
20#include <iterator> // for back_insert_iterator, back_inserter
21#include <list> // for list, _List_iterator, list<>::iter...
22#include <set> // for set, _Rb_tree_const_iterator
23#include <utility> // for pair
24#include <vector> // for vector
25
26#include "AST/Attribute.hpp"
[bccd70a]27#include "AST/Copy.hpp"
[20737104]28#include "AST/Create.hpp"
[a488783]29#include "AST/Decl.hpp"
30#include "AST/DeclReplacer.hpp"
31#include "AST/Expr.hpp"
[91715ce1]32#include "AST/Inspect.hpp"
[a488783]33#include "AST/Pass.hpp"
34#include "AST/Stmt.hpp"
35#include "AST/SymbolTable.hpp"
36#include "CodeGen/OperatorTable.h" // for isCtorDtor, isCtorDtorAssign
37#include "Common/ScopedMap.h" // for ScopedMap<>::const_iterator, Scope...
38#include "Common/utility.h" // for cloneAll, operator+
39#include "GenPoly/ScopedSet.h" // for ScopedSet, ScopedSet<>::iterator
40#include "InitTweak/GenInit.h" // for fixReturnStatements
[00a8e19]41#include "InitTweak/InitTweak.h" // for isAssignment, isCopyConstructor
[fb4dc28]42#include "SymTab/GenImplicitCall.hpp" // for genImplicitCall
[a488783]43#include "SymTab/Mangler.h" // for Mangler
44#include "CompilationState.h"
45
46namespace Validate {
47
48namespace {
49
50// --------------------------------------------------------------------------
[0bd3faf]51struct AutogenerateRoutines final :
[a488783]52 public ast::WithDeclsToAdd<>,
53 public ast::WithShortCircuiting {
54 void previsit( const ast::EnumDecl * enumDecl );
55 void previsit( const ast::StructDecl * structDecl );
56 void previsit( const ast::UnionDecl * structDecl );
57 void previsit( const ast::TypeDecl * typeDecl );
58 void previsit( const ast::TraitDecl * traitDecl );
59 void previsit( const ast::FunctionDecl * functionDecl );
60 void postvisit( const ast::FunctionDecl * functionDecl );
61
62private:
63 // Current level of nested functions.
64 unsigned int functionNesting = 0;
65};
66
67// --------------------------------------------------------------------------
68/// Class used to generate functions for a particular declaration.
69/// Note it isn't really stored, it is just a class for organization and to
70/// help pass around some of the common arguments.
71class FuncGenerator {
72public:
73 std::list<ast::ptr<ast::Decl>> forwards;
74 std::list<ast::ptr<ast::Decl>> definitions;
75
76 FuncGenerator( const ast::Type * type, unsigned int functionNesting ) :
77 type( type ), functionNesting( functionNesting )
78 {}
79
80 /// Generate functions (and forward decls.) and append them to the list.
81 void generateAndAppendFunctions( std::list<ast::ptr<ast::Decl>> & );
82
83 virtual bool shouldAutogen() const = 0;
84protected:
85 const ast::Type * type;
86 unsigned int functionNesting;
87 ast::Linkage::Spec proto_linkage = ast::Linkage::AutoGen;
88
89 // Internal helpers:
90 void genStandardFuncs();
91 void produceDecl( const ast::FunctionDecl * decl );
92 void produceForwardDecl( const ast::FunctionDecl * decl );
93
94 const CodeLocation& getLocation() const { return getDecl()->location; }
[8913de4]95 ast::FunctionDecl * genProto( std::string&& name,
[a488783]96 std::vector<ast::ptr<ast::DeclWithType>>&& params,
97 std::vector<ast::ptr<ast::DeclWithType>>&& returns ) const;
98
99 ast::ObjectDecl * dstParam() const;
100 ast::ObjectDecl * srcParam() const;
101 ast::FunctionDecl * genCtorProto() const;
102 ast::FunctionDecl * genCopyProto() const;
103 ast::FunctionDecl * genDtorProto() const;
104 ast::FunctionDecl * genAssignProto() const;
105 ast::FunctionDecl * genFieldCtorProto( unsigned int fields ) const;
106
107 // Internal Hooks:
108 virtual void genFuncBody( ast::FunctionDecl * decl ) = 0;
109 virtual void genFieldCtors() = 0;
110 virtual bool isConcurrentType() const { return false; }
111 virtual const ast::Decl * getDecl() const = 0;
112};
113
114class StructFuncGenerator final : public FuncGenerator {
115 const ast::StructDecl * decl;
116public:
117 StructFuncGenerator( const ast::StructDecl * decl,
118 const ast::StructInstType * type,
119 unsigned int functionNesting ) :
120 FuncGenerator( type, functionNesting ), decl( decl )
121 {}
122
123 // Built-ins do not use autogeneration.
[91715ce1]124 bool shouldAutogen() const final { return !decl->linkage.is_builtin && !structHasFlexibleArray(decl); }
[a488783]125private:
126 void genFuncBody( ast::FunctionDecl * decl ) final;
127 void genFieldCtors() final;
128 bool isConcurrentType() const final {
129 return decl->is_thread() || decl->is_monitor();
130 }
131 virtual const ast::Decl * getDecl() const final { return decl; }
132
133 /// Generates a single struct member operation.
134 /// (constructor call, destructor call, assignment call)
[4e2f1b2]135 const ast::Stmt * makeMemberOp(
[a488783]136 const CodeLocation& location,
137 const ast::ObjectDecl * dstParam, const ast::Expr * src,
138 const ast::ObjectDecl * field, ast::FunctionDecl * func,
139 SymTab::LoopDirection direction );
140
141 /// Generates the body of a struct function by iterating the struct members
142 /// (via parameters). Generates default constructor, copy constructor,
143 /// copy assignment, and destructor bodies. No field constructor bodies.
144 template<typename Iterator>
145 void makeFunctionBody( Iterator member, Iterator end,
146 ast::FunctionDecl * func, SymTab::LoopDirection direction );
147
148 /// Generate the body of a constructor which takes parameters that match
149 /// fields. (With arguments for one to all of the fields.)
150 template<typename Iterator>
151 void makeFieldCtorBody( Iterator member, Iterator end,
152 ast::FunctionDecl * func );
153};
154
155class UnionFuncGenerator final : public FuncGenerator {
156 const ast::UnionDecl * decl;
157public:
158 UnionFuncGenerator( const ast::UnionDecl * decl,
159 const ast::UnionInstType * type,
160 unsigned int functionNesting ) :
161 FuncGenerator( type, functionNesting ), decl( decl )
162 {}
163
164 // Built-ins do not use autogeneration.
165 bool shouldAutogen() const final { return !decl->linkage.is_builtin; }
166private:
167 void genFuncBody( ast::FunctionDecl * decl ) final;
168 void genFieldCtors() final;
169 const ast::Decl * getDecl() const final { return decl; }
170
171 /// Generate a single union assignment expression (using memcpy).
172 ast::ExprStmt * makeAssignOp( const CodeLocation& location,
173 const ast::ObjectDecl * dstParam, const ast::ObjectDecl * srcParam );
174};
175
176class EnumFuncGenerator final : public FuncGenerator {
177 const ast::EnumDecl * decl;
178public:
179 EnumFuncGenerator( const ast::EnumDecl * decl,
180 const ast::EnumInstType * type,
181 unsigned int functionNesting ) :
182 FuncGenerator( type, functionNesting ), decl( decl )
183 {
184 // TODO: These functions are somewhere between instrinsic and autogen,
[3322180]185 // could possibly use a new linkage type. For now we just make the
186 // basic ones intrinsic to code-gen them as C assignments.
[59c8dff]187 // const auto & real_type = decl->base;
188 // const auto & basic = real_type.as<ast::BasicType>();
189
190 // if(!real_type || (basic && basic->isInteger())) proto_linkage = ast::Linkage::Intrinsic;
191
192 // Turns other enumeration type into Intrinstic as well to temporarily fix the recursive
193 // construction bug
194 proto_linkage = ast::Linkage::Intrinsic;
[a488783]195 }
196
197 bool shouldAutogen() const final { return true; }
[c75b30a]198 void genAttrFuncForward();
[a488783]199private:
200 void genFuncBody( ast::FunctionDecl * decl ) final;
201 void genFieldCtors() final;
202 const ast::Decl * getDecl() const final { return decl; }
[c75b30a]203
204 ast::FunctionDecl * genPosProto() const;
205 ast::FunctionDecl * genLabelProto() const;
206 ast::FunctionDecl * genValueProto() const;
[a488783]207};
208
209class TypeFuncGenerator final : public FuncGenerator {
210 const ast::TypeDecl * decl;
211public:
212 TypeFuncGenerator( const ast::TypeDecl * decl,
213 ast::TypeInstType * type,
214 unsigned int functionNesting ) :
215 FuncGenerator( type, functionNesting ), decl( decl )
216 {}
217
218 bool shouldAutogen() const final { return true; }
219 void genFieldCtors() final;
220private:
221 void genFuncBody( ast::FunctionDecl * decl ) final;
222 const ast::Decl * getDecl() const final { return decl; }
223};
224
225// --------------------------------------------------------------------------
226const std::vector<ast::ptr<ast::TypeDecl>>& getGenericParams( const ast::Type * t ) {
227 if ( auto inst = dynamic_cast< const ast::StructInstType * >( t ) ) {
228 return inst->base->params;
229 } else if ( auto inst = dynamic_cast< const ast::UnionInstType * >( t ) ) {
230 return inst->base->params;
231 }
232 static std::vector<ast::ptr<ast::TypeDecl>> const empty;
233 return empty;
234}
235
236/// Changes the node inside a pointer so that it has the unused attribute.
237void addUnusedAttribute( ast::ptr<ast::DeclWithType> & declPtr ) {
238 ast::DeclWithType * decl = declPtr.get_and_mutate();
239 decl->attributes.push_back( new ast::Attribute( "unused" ) );
240}
241
242// --------------------------------------------------------------------------
[0bd3faf]243void AutogenerateRoutines::previsit( const ast::EnumDecl * enumDecl ) {
[a488783]244 if ( !enumDecl->body ) return;
245
246 ast::EnumInstType enumInst( enumDecl->name );
247 enumInst.base = enumDecl;
248 EnumFuncGenerator gen( enumDecl, &enumInst, functionNesting );
[c75b30a]249 if ( enumDecl->base ) {
250 gen.genAttrFuncForward();
251 }
[a488783]252 gen.generateAndAppendFunctions( declsToAddAfter );
253}
254
[0bd3faf]255void AutogenerateRoutines::previsit( const ast::StructDecl * structDecl ) {
[a488783]256 visit_children = false;
257 if ( !structDecl->body ) return;
258
259 ast::StructInstType structInst( structDecl->name );
260 structInst.base = structDecl;
261 for ( const ast::TypeDecl * typeDecl : structDecl->params ) {
262 structInst.params.push_back( new ast::TypeExpr(
263 typeDecl->location,
[b230091]264 new ast::TypeInstType( typeDecl )
[a488783]265 ) );
266 }
267 StructFuncGenerator gen( structDecl, &structInst, functionNesting );
268 gen.generateAndAppendFunctions( declsToAddAfter );
269}
270
[0bd3faf]271void AutogenerateRoutines::previsit( const ast::UnionDecl * unionDecl ) {
[a488783]272 visit_children = false;
273 if ( !unionDecl->body ) return;
274
275 ast::UnionInstType unionInst( unionDecl->name );
276 unionInst.base = unionDecl;
277 for ( const ast::TypeDecl * typeDecl : unionDecl->params ) {
278 unionInst.params.push_back( new ast::TypeExpr(
279 unionDecl->location,
[b230091]280 new ast::TypeInstType( typeDecl )
[a488783]281 ) );
282 }
283 UnionFuncGenerator gen( unionDecl, &unionInst, functionNesting );
284 gen.generateAndAppendFunctions( declsToAddAfter );
285}
286
287/// Generate ctor/dtors/assign for typedecls, e.g., otype T = int *;
[0bd3faf]288void AutogenerateRoutines::previsit( const ast::TypeDecl * typeDecl ) {
[a488783]289 if ( !typeDecl->base ) return;
290
291 ast::TypeInstType refType( typeDecl->name, typeDecl );
292 TypeFuncGenerator gen( typeDecl, &refType, functionNesting );
293 gen.generateAndAppendFunctions( declsToAddAfter );
294}
295
[0bd3faf]296void AutogenerateRoutines::previsit( const ast::TraitDecl * ) {
[a488783]297 // Ensure that we don't add assignment ops for types defined as part of the trait
298 visit_children = false;
299}
300
[0bd3faf]301void AutogenerateRoutines::previsit( const ast::FunctionDecl * ) {
[a488783]302 // Track whether we're currently in a function.
303 // Can ignore function type idiosyncrasies, because function type can never
304 // declare a new type.
305 functionNesting += 1;
306}
307
[0bd3faf]308void AutogenerateRoutines::postvisit( const ast::FunctionDecl * ) {
[a488783]309 functionNesting -= 1;
310}
311
312void FuncGenerator::generateAndAppendFunctions(
313 std::list<ast::ptr<ast::Decl>> & decls ) {
314 if ( !shouldAutogen() ) return;
315
316 // Generate the functions (they go into forwards and definitions).
317 genStandardFuncs();
318 genFieldCtors();
319
320 // Now export the lists contents.
321 decls.splice( decls.end(), forwards );
322 decls.splice( decls.end(), definitions );
323}
324
325void FuncGenerator::produceDecl( const ast::FunctionDecl * decl ) {
326 assert( nullptr != decl->stmts );
[b1e21da]327 assert( decl->type_params.size() == getGenericParams( type ).size() );
[a488783]328
329 definitions.push_back( decl );
330}
331
332/// Make a forward declaration of the decl and add it to forwards.
333void FuncGenerator::produceForwardDecl( const ast::FunctionDecl * decl ) {
334 if (0 != functionNesting) return;
[20737104]335 ast::FunctionDecl * fwd =
336 ( decl->stmts ) ? ast::asForward( decl ) : ast::deepCopy( decl ) ;
[a488783]337 fwd->fixUniqueId();
338 forwards.push_back( fwd );
339}
340
[8913de4]341void replaceAll( std::vector<ast::ptr<ast::DeclWithType>> & dwts,
342 const ast::DeclReplacer::TypeMap & map ) {
343 for ( auto & dwt : dwts ) {
344 dwt = strict_dynamic_cast<const ast::DeclWithType *>(
345 ast::DeclReplacer::replace( dwt, map ) );
346 }
347}
348
[a488783]349/// Generates a basic prototype function declaration.
[8913de4]350ast::FunctionDecl * FuncGenerator::genProto( std::string&& name,
[a488783]351 std::vector<ast::ptr<ast::DeclWithType>>&& params,
352 std::vector<ast::ptr<ast::DeclWithType>>&& returns ) const {
353
354 // Handle generic prameters and assertions, if any.
355 auto const & old_type_params = getGenericParams( type );
[8913de4]356 ast::DeclReplacer::TypeMap oldToNew;
[a488783]357 std::vector<ast::ptr<ast::TypeDecl>> type_params;
358 std::vector<ast::ptr<ast::DeclWithType>> assertions;
359 for ( auto & old_param : old_type_params ) {
360 ast::TypeDecl * decl = ast::deepCopy( old_param );
[8913de4]361 decl->init = nullptr;
362 splice( assertions, decl->assertions );
[b1e21da]363 oldToNew.emplace( old_param, decl );
[a488783]364 type_params.push_back( decl );
365 }
[8913de4]366 replaceAll( params, oldToNew );
367 replaceAll( returns, oldToNew );
368 replaceAll( assertions, oldToNew );
[a488783]369
370 ast::FunctionDecl * decl = new ast::FunctionDecl(
371 // Auto-generated routines use the type declaration's location.
372 getLocation(),
[8913de4]373 std::move( name ),
[a488783]374 std::move( type_params ),
[7edd5c1]375 std::move( assertions ),
[a488783]376 std::move( params ),
377 std::move( returns ),
378 // Only a prototype, no body.
379 nullptr,
380 // Use static storage if we are at the top level.
381 (0 < functionNesting) ? ast::Storage::Classes() : ast::Storage::Static,
382 proto_linkage,
383 std::vector<ast::ptr<ast::Attribute>>(),
384 // Auto-generated routines are inline to avoid conflicts.
385 ast::Function::Specs( ast::Function::Inline ) );
386 decl->fixUniqueId();
387 return decl;
388}
389
390ast::ObjectDecl * FuncGenerator::dstParam() const {
391 return new ast::ObjectDecl( getLocation(), "_dst",
[e8616b6]392 new ast::ReferenceType( ast::deepCopy( type ) ) );
[a488783]393}
394
395ast::ObjectDecl * FuncGenerator::srcParam() const {
396 return new ast::ObjectDecl( getLocation(), "_src",
[e8616b6]397 ast::deepCopy( type ) );
[a488783]398}
399
400/// Use the current type T to create `void ?{}(T & _dst)`.
401ast::FunctionDecl * FuncGenerator::genCtorProto() const {
402 return genProto( "?{}", { dstParam() }, {} );
403}
404
405/// Use the current type T to create `void ?{}(T & _dst, T _src)`.
406ast::FunctionDecl * FuncGenerator::genCopyProto() const {
407 return genProto( "?{}", { dstParam(), srcParam() }, {} );
408}
409
410/// Use the current type T to create `void ?{}(T & _dst)`.
411ast::FunctionDecl * FuncGenerator::genDtorProto() const {
412 // The destructor must be mutex on a concurrent type.
413 auto dst = dstParam();
414 if ( isConcurrentType() ) {
415 add_qualifiers( dst->type, ast::CV::Qualifiers( ast::CV::Mutex ) );
416 }
417 return genProto( "^?{}", { dst }, {} );
418}
419
420/// Use the current type T to create `T ?{}(T & _dst, T _src)`.
421ast::FunctionDecl * FuncGenerator::genAssignProto() const {
422 // Only the name is different, so just reuse the generation function.
423 auto retval = srcParam();
424 retval->name = "_ret";
425 return genProto( "?=?", { dstParam(), srcParam() }, { retval } );
426}
427
428// This one can return null if the last field is an unnamed bitfield.
429ast::FunctionDecl * FuncGenerator::genFieldCtorProto(
430 unsigned int fields ) const {
431 assert( 0 < fields );
432 auto aggr = strict_dynamic_cast<const ast::AggregateDecl *>( getDecl() );
433
434 std::vector<ast::ptr<ast::DeclWithType>> params = { dstParam() };
435 for ( unsigned int index = 0 ; index < fields ; ++index ) {
436 auto member = aggr->members[index].strict_as<ast::DeclWithType>();
[fb4dc28]437 if ( ast::isUnnamedBitfield(
[a488783]438 dynamic_cast<const ast::ObjectDecl *>( member ) ) ) {
439 if ( index == fields - 1 ) {
440 return nullptr;
441 }
442 continue;
443 }
444
445 auto * paramType = ast::deepCopy( member->get_type() );
[b262cb3]446 erase_if( paramType->attributes, []( ast::Attribute const * attr ){
447 return !attr->isValidOnFuncParam();
448 } );
[a488783]449 ast::ObjectDecl * param = new ast::ObjectDecl(
450 getLocation(), member->name, paramType );
451 for ( auto & attr : member->attributes ) {
452 if ( attr->isValidOnFuncParam() ) {
453 param->attributes.push_back( attr );
454 }
455 }
456 params.emplace_back( param );
457 }
458 return genProto( "?{}", std::move( params ), {} );
459}
460
461void appendReturnThis( ast::FunctionDecl * decl ) {
462 assert( 1 <= decl->params.size() );
463 assert( 1 == decl->returns.size() );
464 assert( decl->stmts );
465
466 const CodeLocation& location = (decl->stmts->kids.empty())
467 ? decl->stmts->location : decl->stmts->kids.back()->location;
468 const ast::DeclWithType * thisParam = decl->params.front();
469 decl->stmts.get_and_mutate()->push_back(
470 new ast::ReturnStmt( location,
471 new ast::VariableExpr( location, thisParam )
472 )
473 );
474}
475
476void FuncGenerator::genStandardFuncs() {
477 // The order here determines the order that these functions are generated.
478 // Assignment should come last since it uses copy constructor in return.
479 ast::FunctionDecl *(FuncGenerator::*standardProtos[4])() const = {
480 &FuncGenerator::genCtorProto, &FuncGenerator::genCopyProto,
481 &FuncGenerator::genDtorProto, &FuncGenerator::genAssignProto };
482 for ( auto & generator : standardProtos ) {
483 ast::FunctionDecl * decl = (this->*generator)();
484 produceForwardDecl( decl );
485 genFuncBody( decl );
486 if ( CodeGen::isAssignment( decl->name ) ) {
487 appendReturnThis( decl );
488 }
489 produceDecl( decl );
490 }
491}
492
493void StructFuncGenerator::genFieldCtors() {
494 // The field constructors are only generated if the default constructor
495 // and copy constructor are both generated, since the need both.
496 unsigned numCtors = std::count_if( definitions.begin(), definitions.end(),
497 [](const ast::Decl * decl){ return CodeGen::isConstructor( decl->name ); }
498 );
499 if ( 2 != numCtors ) return;
500
501 for ( unsigned int num = 1 ; num <= decl->members.size() ; ++num ) {
502 ast::FunctionDecl * ctor = genFieldCtorProto( num );
503 if ( nullptr == ctor ) {
504 continue;
505 }
506 produceForwardDecl( ctor );
507 makeFieldCtorBody( decl->members.begin(), decl->members.end(), ctor );
508 produceDecl( ctor );
509 }
510}
511
512void StructFuncGenerator::genFuncBody( ast::FunctionDecl * functionDecl ) {
513 // Generate appropriate calls to member constructors and assignment.
514 // Destructor needs to do everything in reverse,
515 // so pass "forward" based on whether the function is a destructor
516 if ( CodeGen::isDestructor( functionDecl->name ) ) {
517 makeFunctionBody( decl->members.rbegin(), decl->members.rend(),
518 functionDecl, SymTab::LoopBackward );
519 } else {
520 makeFunctionBody( decl->members.begin(), decl->members.end(),
521 functionDecl, SymTab::LoopForward );
522 }
523}
524
[4e2f1b2]525const ast::Stmt * StructFuncGenerator::makeMemberOp(
[a488783]526 const CodeLocation& location, const ast::ObjectDecl * dstParam,
527 const ast::Expr * src, const ast::ObjectDecl * field,
528 ast::FunctionDecl * func, SymTab::LoopDirection direction ) {
[0bd3faf]529 InitTweak::InitExpander srcParam( src );
[a488783]530 // Assign to destination.
[24d6572]531 ast::MemberExpr * dstSelect = new ast::MemberExpr(
[a488783]532 location,
533 field,
534 new ast::CastExpr(
535 location,
536 new ast::VariableExpr( location, dstParam ),
537 dstParam->type.strict_as<ast::ReferenceType>()->base
538 )
539 );
[4e2f1b2]540 const ast::Stmt * stmt = genImplicitCall(
[a488783]541 srcParam, dstSelect, location, func->name,
542 field, direction
543 );
[14c0f7b]544 // This could return the above directly, except the generated code is
545 // built using the structure's members and that means all the scoped
546 // names (the forall parameters) are incorrect. This corrects them.
547 if ( stmt && !decl->params.empty() ) {
548 ast::DeclReplacer::TypeMap oldToNew;
549 for ( auto pair : group_iterate( decl->params, func->type_params ) ) {
550 oldToNew.emplace( std::get<0>(pair), std::get<1>(pair) );
551 }
552 auto node = ast::DeclReplacer::replace( stmt, oldToNew );
553 stmt = strict_dynamic_cast<const ast::Stmt *>( node );
554 }
555 return stmt;
[a488783]556}
557
558template<typename Iterator>
559void StructFuncGenerator::makeFunctionBody( Iterator current, Iterator end,
560 ast::FunctionDecl * func, SymTab::LoopDirection direction ) {
561 // Trying to get the best code location. Should probably use a helper or
562 // just figure out what that would be given where this is called.
563 assert( nullptr == func->stmts );
564 const CodeLocation& location = func->location;
565
566 ast::CompoundStmt * stmts = new ast::CompoundStmt( location );
567
568 for ( ; current != end ; ++current ) {
569 const ast::ptr<ast::Decl> & member = *current;
570 auto field = member.as<ast::ObjectDecl>();
571 if ( nullptr == field ) {
572 continue;
573 }
574
575 // Don't assign to constant members (but do construct/destruct them).
576 if ( CodeGen::isAssignment( func->name ) ) {
577 // For array types we need to strip off the array layers.
578 const ast::Type * type = field->get_type();
579 while ( auto at = dynamic_cast<const ast::ArrayType *>( type ) ) {
580 type = at->base;
581 }
582 if ( type->is_const() ) {
583 continue;
584 }
585 }
586
587 assert( !func->params.empty() );
588 const ast::ObjectDecl * dstParam =
589 func->params.front().strict_as<ast::ObjectDecl>();
590 const ast::ObjectDecl * srcParam = nullptr;
591 if ( 2 == func->params.size() ) {
592 srcParam = func->params.back().strict_as<ast::ObjectDecl>();
593 }
594
[24d6572]595 ast::MemberExpr * srcSelect = (srcParam) ? new ast::MemberExpr(
[a488783]596 location, field, new ast::VariableExpr( location, srcParam )
597 ) : nullptr;
[4e2f1b2]598 const ast::Stmt * stmt =
[a488783]599 makeMemberOp( location, dstParam, srcSelect, field, func, direction );
600
601 if ( nullptr != stmt ) {
[4e2f1b2]602 stmts->kids.emplace_back( stmt );
[a488783]603 }
604 }
605
606 func->stmts = stmts;
607}
608
609template<typename Iterator>
610void StructFuncGenerator::makeFieldCtorBody( Iterator current, Iterator end,
611 ast::FunctionDecl * func ) {
612 const CodeLocation& location = func->location;
613 auto & params = func->params;
614 // Need at least the constructed parameter and one field parameter.
615 assert( 2 <= params.size() );
616
617 ast::CompoundStmt * stmts = new ast::CompoundStmt( location );
618
619 auto dstParam = params.front().strict_as<ast::ObjectDecl>();
620 // Skip over the 'this' parameter.
621 for ( auto param = params.begin() + 1 ; current != end ; ++current ) {
622 const ast::ptr<ast::Decl> & member = *current;
[4e2f1b2]623 const ast::Stmt * stmt = nullptr;
[a488783]624 auto field = member.as<ast::ObjectDecl>();
625 // Not sure why it could be null.
626 // Don't make a function for a parameter that is an unnamed bitfield.
[fb4dc28]627 if ( nullptr == field || ast::isUnnamedBitfield( field ) ) {
[a488783]628 continue;
629 // Matching Parameter: Initialize the field by copy.
630 } else if ( params.end() != param ) {
631 const ast::Expr *srcSelect = new ast::VariableExpr(
632 func->location, param->get() );
633 stmt = makeMemberOp( location, dstParam, srcSelect, field, func, SymTab::LoopForward );
634 ++param;
635 // No Matching Parameter: Initialize the field by default constructor.
636 } else {
637 stmt = makeMemberOp( location, dstParam, nullptr, field, func, SymTab::LoopForward );
638 }
639
640 if ( nullptr != stmt ) {
[4e2f1b2]641 stmts->kids.emplace_back( stmt );
[a488783]642 }
643 }
644 func->stmts = stmts;
645}
646
647void UnionFuncGenerator::genFieldCtors() {
648 // Field constructors are only generated if default and copy constructor
649 // are generated, since they need access to both
650 unsigned numCtors = std::count_if( definitions.begin(), definitions.end(),
651 []( const ast::Decl * d ){ return CodeGen::isConstructor( d->name ); }
652 );
653 if ( 2 != numCtors ) {
654 return;
655 }
656
657 // Create a constructor which takes the first member type as a
658 // parameter. For example for `union A { int x; char y; };` generate
659 // a function with signature `void ?{}(A *, int)`. This mimics C's
660 // behaviour which initializes the first member of the union.
661
662 // Still, there must be some members.
663 if ( !decl->members.empty() ) {
664 ast::FunctionDecl * ctor = genFieldCtorProto( 1 );
665 if ( nullptr == ctor ) {
666 return;
667 }
668 produceForwardDecl( ctor );
669 auto params = ctor->params;
670 auto dstParam = params.front().strict_as<ast::ObjectDecl>();
671 auto srcParam = params.back().strict_as<ast::ObjectDecl>();
672 ctor->stmts = new ast::CompoundStmt( getLocation(),
673 { makeAssignOp( getLocation(), dstParam, srcParam ) }
674 );
675 produceDecl( ctor );
676 }
677}
678
679void UnionFuncGenerator::genFuncBody( ast::FunctionDecl * functionDecl ) {
680 const CodeLocation& location = functionDecl->location;
681 auto & params = functionDecl->params;
682 if ( InitTweak::isCopyConstructor( functionDecl )
683 || InitTweak::isAssignment( functionDecl ) ) {
684 assert( 2 == params.size() );
685 auto dstParam = params.front().strict_as<ast::ObjectDecl>();
686 auto srcParam = params.back().strict_as<ast::ObjectDecl>();
687 functionDecl->stmts = new ast::CompoundStmt( location,
688 { makeAssignOp( location, dstParam, srcParam ) }
689 );
690 } else {
691 assert( 1 == params.size() );
692 // Default constructor and destructor is empty.
693 functionDecl->stmts = new ast::CompoundStmt( location );
694 // Add unused attribute to parameter to silence warnings.
695 addUnusedAttribute( params.front() );
696
697 // Just an extra step to make the forward and declaration match.
698 if ( forwards.empty() ) return;
699 ast::FunctionDecl * fwd = strict_dynamic_cast<ast::FunctionDecl *>(
700 forwards.back().get_and_mutate() );
701 addUnusedAttribute( fwd->params.front() );
702 }
703}
704
705ast::ExprStmt * UnionFuncGenerator::makeAssignOp( const CodeLocation& location,
706 const ast::ObjectDecl * dstParam, const ast::ObjectDecl * srcParam ) {
707 return new ast::ExprStmt( location, new ast::UntypedExpr(
708 location,
709 new ast::NameExpr( location, "__builtin_memcpy" ),
710 {
711 new ast::AddressExpr( location,
712 new ast::VariableExpr( location, dstParam ) ),
713 new ast::AddressExpr( location,
714 new ast::VariableExpr( location, srcParam ) ),
715 new ast::SizeofExpr( location, srcParam->type ),
716 } ) );
717}
718
719void EnumFuncGenerator::genFieldCtors() {
720 // Enumerations to not have field constructors.
721}
722
723void EnumFuncGenerator::genFuncBody( ast::FunctionDecl * functionDecl ) {
724 const CodeLocation& location = functionDecl->location;
725 auto & params = functionDecl->params;
726 if ( InitTweak::isCopyConstructor( functionDecl )
727 || InitTweak::isAssignment( functionDecl ) ) {
728 assert( 2 == params.size() );
729 auto dstParam = params.front().strict_as<ast::ObjectDecl>();
730 auto srcParam = params.back().strict_as<ast::ObjectDecl>();
731
732 /* This looks like a recursive call, but code-gen will turn it into
733 * a C-style assignment.
734 *
735 * This is still before function pointer type conversion,
736 * so this will have to do it manually.
737 *
738 * It will also reference the parent function declaration, creating
739 * a cycle for references. This also means that the ref-counts are
740 * now non-zero and the declaration will be deleted if it ever
741 * returns to zero.
742 */
743 auto callExpr = new ast::ApplicationExpr( location,
744 ast::VariableExpr::functionPointer( location, functionDecl ),
745 {
[496ffc17]746 new ast::VariableExpr( location, dstParam ),
747 new ast::VariableExpr( location, srcParam )
[a488783]748 }
749 );
[c75b30a]750
[a488783]751 functionDecl->stmts = new ast::CompoundStmt( location,
752 { new ast::ExprStmt( location, callExpr ) }
753 );
754 } else {
755 assert( 1 == params.size() );
756 // Default constructor and destructor is empty.
757 functionDecl->stmts = new ast::CompoundStmt( location );
758 // Just add unused attribute to parameter to silence warnings.
759 addUnusedAttribute( params.front() );
760
761 // Just an extra step to make the forward and declaration match.
762 if ( forwards.empty() ) return;
763 ast::FunctionDecl * fwd = strict_dynamic_cast<ast::FunctionDecl *>(
764 forwards.back().get_and_mutate() );
765 addUnusedAttribute( fwd->params.front() );
766 }
767}
768
[c75b30a]769ast::FunctionDecl * EnumFuncGenerator::genPosProto() const {
770 return genProto( "posE",
771 { new ast::ObjectDecl( getLocation(), "_i",
772 new ast::EnumInstType( decl ) )},
773 { new ast::ObjectDecl( getLocation(), "_ret",
774 new ast::BasicType{ ast::BasicType::UnsignedInt } )} );
775}
776
777ast::FunctionDecl * EnumFuncGenerator::genLabelProto() const {
778 return genProto( "labelE",
779 { new ast::ObjectDecl( getLocation(), "_i",
780 new ast::EnumInstType( decl ) ) },
781 { new ast::ObjectDecl( getLocation(), "_ret",
782 new ast::PointerType( new ast::BasicType{ ast::BasicType::Char } ) ) } );
783}
784
785ast::FunctionDecl * EnumFuncGenerator::genValueProto() const {
786 return genProto( "valueE",
787 { new ast::ObjectDecl( getLocation(), "_i", new ast::EnumInstType( decl ) )},
788 { new ast::ObjectDecl( getLocation(), "_ret", ast::deepCopy( decl->base ) ) } );
789}
790
791void EnumFuncGenerator::genAttrFuncForward() {
792 if ( decl->base ) {
793 ast::FunctionDecl *(EnumFuncGenerator::*attrProtos[3])() const = {
794 &EnumFuncGenerator::genPosProto, &EnumFuncGenerator::genLabelProto,
795 &EnumFuncGenerator::genValueProto };
796 for ( auto & generator : attrProtos ) {
797 produceForwardDecl( (this->*generator)() );
798 }
799 }
800}
801
[a488783]802void TypeFuncGenerator::genFieldCtors() {
803 // Opaque types do not have field constructors.
804}
805
806void TypeFuncGenerator::genFuncBody( ast::FunctionDecl * functionDecl ) {
807 const CodeLocation& location = functionDecl->location;
808 auto & params = functionDecl->type->params;
809 assertf( 1 == params.size() || 2 == params.size(),
810 "Incorrect number of parameters in autogenerated typedecl function: %zd",
811 params.size() );
812 auto dstParam = params.front().strict_as<ast::ObjectDecl>();
813 auto srcParam = (2 == params.size())
814 ? params.back().strict_as<ast::ObjectDecl>() : nullptr;
815 // Generate appropriate calls to member constructor and assignment.
816 ast::UntypedExpr * expr = new ast::UntypedExpr( location,
817 new ast::NameExpr( location, functionDecl->name )
818 );
819 expr->args.push_back( new ast::CastExpr( location,
820 new ast::VariableExpr( location, dstParam ),
821 new ast::ReferenceType( decl->base )
822 ) );
823 if ( srcParam ) {
824 expr->args.push_back( new ast::CastExpr( location,
825 new ast::VariableExpr( location, srcParam ),
826 decl->base
827 ) );
828 }
829 functionDecl->stmts = new ast::CompoundStmt( location,
830 { new ast::ExprStmt( location, expr ) }
831 );
832}
833
834} // namespace
835
836void autogenerateRoutines( ast::TranslationUnit & translationUnit ) {
[0bd3faf]837 ast::Pass<AutogenerateRoutines>::run( translationUnit );
[a488783]838}
839
840} // Validate
841
842// Local Variables: //
843// tab-width: 4 //
844// mode: c++ //
845// compile-command: "make install" //
846// End: //
Note: See TracBrowser for help on using the repository browser.