source: src/Validate/Autogen.cpp@ 00eaeb8

Last change on this file since 00eaeb8 was 00eaeb8, checked in by JiadaL <j82liang@…>, 21 months ago

Add prototype of succ function

  • Property mode set to 100644
File size: 32.4 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// 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
12// Last Modified On : Tue Sep 20 16:00:00 2022
13// Update Count : 2
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"
27#include "AST/Copy.hpp"
28#include "AST/Create.hpp"
29#include "AST/Decl.hpp"
30#include "AST/DeclReplacer.hpp"
31#include "AST/Expr.hpp"
32#include "AST/Inspect.hpp"
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
41#include "InitTweak/InitTweak.h" // for isAssignment, isCopyConstructor
42#include "SymTab/GenImplicitCall.hpp" // for genImplicitCall
43#include "SymTab/Mangler.h" // for Mangler
44#include "CompilationState.h"
45
46namespace Validate {
47
48namespace {
49
50// --------------------------------------------------------------------------
51struct AutogenerateRoutines final :
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; }
95 ast::FunctionDecl * genProto( std::string&& name,
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.
124 bool shouldAutogen() const final { return !decl->linkage.is_builtin && !structHasFlexibleArray(decl); }
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)
135 const ast::Stmt * makeMemberOp(
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,
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.
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;
195 }
196
197 bool shouldAutogen() const final { return true; }
198 void genAttrFuncForward();
199 void genPosFunctions();
200private:
201 void genFuncBody( ast::FunctionDecl * decl ) final;
202 void genFieldCtors() final;
203 const ast::Decl * getDecl() const final { return decl; }
204
205 ast::FunctionDecl * genPosProto() const;
206 ast::FunctionDecl * genLabelProto() const;
207 ast::FunctionDecl * genValueProto() const;
208 ast::FunctionDecl * genSuccProto() const;
209 ast::FunctionDecl * genPredProto() const;
210
211 ast::FunctionDecl * genSuccPosProto() const;
212 ast::FunctionDecl * genPredPosProto() const;
213
214 void genSuccFunc(ast::FunctionDecl *);
215};
216
217class TypeFuncGenerator final : public FuncGenerator {
218 const ast::TypeDecl * decl;
219public:
220 TypeFuncGenerator( const ast::TypeDecl * decl,
221 ast::TypeInstType * type,
222 unsigned int functionNesting ) :
223 FuncGenerator( type, functionNesting ), decl( decl )
224 {}
225
226 bool shouldAutogen() const final { return true; }
227 void genFieldCtors() final;
228private:
229 void genFuncBody( ast::FunctionDecl * decl ) final;
230 const ast::Decl * getDecl() const final { return decl; }
231};
232
233// --------------------------------------------------------------------------
234const std::vector<ast::ptr<ast::TypeDecl>>& getGenericParams( const ast::Type * t ) {
235 if ( auto inst = dynamic_cast< const ast::StructInstType * >( t ) ) {
236 return inst->base->params;
237 } else if ( auto inst = dynamic_cast< const ast::UnionInstType * >( t ) ) {
238 return inst->base->params;
239 }
240 static std::vector<ast::ptr<ast::TypeDecl>> const empty;
241 return empty;
242}
243
244/// Changes the node inside a pointer so that it has the unused attribute.
245void addUnusedAttribute( ast::ptr<ast::DeclWithType> & declPtr ) {
246 ast::DeclWithType * decl = declPtr.get_and_mutate();
247 decl->attributes.push_back( new ast::Attribute( "unused" ) );
248}
249
250// --------------------------------------------------------------------------
251void AutogenerateRoutines::previsit( const ast::EnumDecl * enumDecl ) {
252 if ( !enumDecl->body ) return;
253
254 ast::EnumInstType enumInst( enumDecl->name );
255 enumInst.base = enumDecl;
256 EnumFuncGenerator gen( enumDecl, &enumInst, functionNesting );
257 if ( enumDecl->base ) {
258 gen.genAttrFuncForward();
259 gen.genPosFunctions();
260 }
261 gen.generateAndAppendFunctions( declsToAddAfter );
262}
263
264void AutogenerateRoutines::previsit( const ast::StructDecl * structDecl ) {
265 visit_children = false;
266 if ( !structDecl->body ) return;
267
268 ast::StructInstType structInst( structDecl->name );
269 structInst.base = structDecl;
270 for ( const ast::TypeDecl * typeDecl : structDecl->params ) {
271 structInst.params.push_back( new ast::TypeExpr(
272 typeDecl->location,
273 new ast::TypeInstType( typeDecl )
274 ) );
275 }
276 StructFuncGenerator gen( structDecl, &structInst, functionNesting );
277 gen.generateAndAppendFunctions( declsToAddAfter );
278}
279
280void AutogenerateRoutines::previsit( const ast::UnionDecl * unionDecl ) {
281 visit_children = false;
282 if ( !unionDecl->body ) return;
283
284 ast::UnionInstType unionInst( unionDecl->name );
285 unionInst.base = unionDecl;
286 for ( const ast::TypeDecl * typeDecl : unionDecl->params ) {
287 unionInst.params.push_back( new ast::TypeExpr(
288 unionDecl->location,
289 new ast::TypeInstType( typeDecl )
290 ) );
291 }
292 UnionFuncGenerator gen( unionDecl, &unionInst, functionNesting );
293 gen.generateAndAppendFunctions( declsToAddAfter );
294}
295
296/// Generate ctor/dtors/assign for typedecls, e.g., otype T = int *;
297void AutogenerateRoutines::previsit( const ast::TypeDecl * typeDecl ) {
298 if ( !typeDecl->base ) return;
299
300 ast::TypeInstType refType( typeDecl->name, typeDecl );
301 TypeFuncGenerator gen( typeDecl, &refType, functionNesting );
302 gen.generateAndAppendFunctions( declsToAddAfter );
303}
304
305void AutogenerateRoutines::previsit( const ast::TraitDecl * ) {
306 // Ensure that we don't add assignment ops for types defined as part of the trait
307 visit_children = false;
308}
309
310void AutogenerateRoutines::previsit( const ast::FunctionDecl * ) {
311 // Track whether we're currently in a function.
312 // Can ignore function type idiosyncrasies, because function type can never
313 // declare a new type.
314 functionNesting += 1;
315}
316
317void AutogenerateRoutines::postvisit( const ast::FunctionDecl * ) {
318 functionNesting -= 1;
319}
320
321void FuncGenerator::generateAndAppendFunctions(
322 std::list<ast::ptr<ast::Decl>> & decls ) {
323 if ( !shouldAutogen() ) return;
324
325 // Generate the functions (they go into forwards and definitions).
326 genStandardFuncs();
327 genFieldCtors();
328
329 // Now export the lists contents.
330 decls.splice( decls.end(), forwards );
331 decls.splice( decls.end(), definitions );
332}
333
334void FuncGenerator::produceDecl( const ast::FunctionDecl * decl ) {
335 assert( nullptr != decl->stmts );
336 assert( decl->type_params.size() == getGenericParams( type ).size() );
337
338 definitions.push_back( decl );
339}
340
341/// Make a forward declaration of the decl and add it to forwards.
342void FuncGenerator::produceForwardDecl( const ast::FunctionDecl * decl ) {
343 if (0 != functionNesting) return;
344 ast::FunctionDecl * fwd =
345 ( decl->stmts ) ? ast::asForward( decl ) : ast::deepCopy( decl ) ;
346 fwd->fixUniqueId();
347 forwards.push_back( fwd );
348}
349
350void replaceAll( std::vector<ast::ptr<ast::DeclWithType>> & dwts,
351 const ast::DeclReplacer::TypeMap & map ) {
352 for ( auto & dwt : dwts ) {
353 dwt = strict_dynamic_cast<const ast::DeclWithType *>(
354 ast::DeclReplacer::replace( dwt, map ) );
355 }
356}
357
358/// Generates a basic prototype function declaration.
359ast::FunctionDecl * FuncGenerator::genProto( std::string&& name,
360 std::vector<ast::ptr<ast::DeclWithType>>&& params,
361 std::vector<ast::ptr<ast::DeclWithType>>&& returns ) const {
362
363 // Handle generic prameters and assertions, if any.
364 auto const & old_type_params = getGenericParams( type );
365 ast::DeclReplacer::TypeMap oldToNew;
366 std::vector<ast::ptr<ast::TypeDecl>> type_params;
367 std::vector<ast::ptr<ast::DeclWithType>> assertions;
368 for ( auto & old_param : old_type_params ) {
369 ast::TypeDecl * decl = ast::deepCopy( old_param );
370 decl->init = nullptr;
371 splice( assertions, decl->assertions );
372 oldToNew.emplace( old_param, decl );
373 type_params.push_back( decl );
374 }
375 replaceAll( params, oldToNew );
376 replaceAll( returns, oldToNew );
377 replaceAll( assertions, oldToNew );
378
379 ast::FunctionDecl * decl = new ast::FunctionDecl(
380 // Auto-generated routines use the type declaration's location.
381 getLocation(),
382 std::move( name ),
383 std::move( type_params ),
384 std::move( assertions ),
385 std::move( params ),
386 std::move( returns ),
387 // Only a prototype, no body.
388 nullptr,
389 // Use static storage if we are at the top level.
390 (0 < functionNesting) ? ast::Storage::Classes() : ast::Storage::Static,
391 proto_linkage,
392 std::vector<ast::ptr<ast::Attribute>>(),
393 // Auto-generated routines are inline to avoid conflicts.
394 ast::Function::Specs( ast::Function::Inline ) );
395 decl->fixUniqueId();
396 return decl;
397}
398
399ast::ObjectDecl * FuncGenerator::dstParam() const {
400 return new ast::ObjectDecl( getLocation(), "_dst",
401 new ast::ReferenceType( ast::deepCopy( type ) ) );
402}
403
404ast::ObjectDecl * FuncGenerator::srcParam() const {
405 return new ast::ObjectDecl( getLocation(), "_src",
406 ast::deepCopy( type ) );
407}
408
409/// Use the current type T to create `void ?{}(T & _dst)`.
410ast::FunctionDecl * FuncGenerator::genCtorProto() const {
411 return genProto( "?{}", { dstParam() }, {} );
412}
413
414/// Use the current type T to create `void ?{}(T & _dst, T _src)`.
415ast::FunctionDecl * FuncGenerator::genCopyProto() const {
416 return genProto( "?{}", { dstParam(), srcParam() }, {} );
417}
418
419/// Use the current type T to create `void ?{}(T & _dst)`.
420ast::FunctionDecl * FuncGenerator::genDtorProto() const {
421 // The destructor must be mutex on a concurrent type.
422 auto dst = dstParam();
423 if ( isConcurrentType() ) {
424 add_qualifiers( dst->type, ast::CV::Qualifiers( ast::CV::Mutex ) );
425 }
426 return genProto( "^?{}", { dst }, {} );
427}
428
429/// Use the current type T to create `T ?{}(T & _dst, T _src)`.
430ast::FunctionDecl * FuncGenerator::genAssignProto() const {
431 // Only the name is different, so just reuse the generation function.
432 auto retval = srcParam();
433 retval->name = "_ret";
434 return genProto( "?=?", { dstParam(), srcParam() }, { retval } );
435}
436
437// This one can return null if the last field is an unnamed bitfield.
438ast::FunctionDecl * FuncGenerator::genFieldCtorProto(
439 unsigned int fields ) const {
440 assert( 0 < fields );
441 auto aggr = strict_dynamic_cast<const ast::AggregateDecl *>( getDecl() );
442
443 std::vector<ast::ptr<ast::DeclWithType>> params = { dstParam() };
444 for ( unsigned int index = 0 ; index < fields ; ++index ) {
445 auto member = aggr->members[index].strict_as<ast::DeclWithType>();
446 if ( ast::isUnnamedBitfield(
447 dynamic_cast<const ast::ObjectDecl *>( member ) ) ) {
448 if ( index == fields - 1 ) {
449 return nullptr;
450 }
451 continue;
452 }
453
454 auto * paramType = ast::deepCopy( member->get_type() );
455 erase_if( paramType->attributes, []( ast::Attribute const * attr ){
456 return !attr->isValidOnFuncParam();
457 } );
458 ast::ObjectDecl * param = new ast::ObjectDecl(
459 getLocation(), member->name, paramType );
460 for ( auto & attr : member->attributes ) {
461 if ( attr->isValidOnFuncParam() ) {
462 param->attributes.push_back( attr );
463 }
464 }
465 params.emplace_back( param );
466 }
467 return genProto( "?{}", std::move( params ), {} );
468}
469
470void appendReturnThis( ast::FunctionDecl * decl ) {
471 assert( 1 <= decl->params.size() );
472 assert( 1 == decl->returns.size() );
473 assert( decl->stmts );
474
475 const CodeLocation& location = (decl->stmts->kids.empty())
476 ? decl->stmts->location : decl->stmts->kids.back()->location;
477 const ast::DeclWithType * thisParam = decl->params.front();
478 decl->stmts.get_and_mutate()->push_back(
479 new ast::ReturnStmt( location,
480 new ast::VariableExpr( location, thisParam )
481 )
482 );
483}
484
485void FuncGenerator::genStandardFuncs() {
486 // The order here determines the order that these functions are generated.
487 // Assignment should come last since it uses copy constructor in return.
488 ast::FunctionDecl *(FuncGenerator::*standardProtos[4])() const = {
489 &FuncGenerator::genCtorProto, &FuncGenerator::genCopyProto,
490 &FuncGenerator::genDtorProto, &FuncGenerator::genAssignProto };
491 for ( auto & generator : standardProtos ) {
492 ast::FunctionDecl * decl = (this->*generator)();
493 produceForwardDecl( decl );
494 genFuncBody( decl );
495 if ( CodeGen::isAssignment( decl->name ) ) {
496 appendReturnThis( decl );
497 }
498 produceDecl( decl );
499 }
500}
501
502void StructFuncGenerator::genFieldCtors() {
503 // The field constructors are only generated if the default constructor
504 // and copy constructor are both generated, since the need both.
505 unsigned numCtors = std::count_if( definitions.begin(), definitions.end(),
506 [](const ast::Decl * decl){ return CodeGen::isConstructor( decl->name ); }
507 );
508 if ( 2 != numCtors ) return;
509
510 for ( unsigned int num = 1 ; num <= decl->members.size() ; ++num ) {
511 ast::FunctionDecl * ctor = genFieldCtorProto( num );
512 if ( nullptr == ctor ) {
513 continue;
514 }
515 produceForwardDecl( ctor );
516 makeFieldCtorBody( decl->members.begin(), decl->members.end(), ctor );
517 produceDecl( ctor );
518 }
519}
520
521void StructFuncGenerator::genFuncBody( ast::FunctionDecl * functionDecl ) {
522 // Generate appropriate calls to member constructors and assignment.
523 // Destructor needs to do everything in reverse,
524 // so pass "forward" based on whether the function is a destructor
525 if ( CodeGen::isDestructor( functionDecl->name ) ) {
526 makeFunctionBody( decl->members.rbegin(), decl->members.rend(),
527 functionDecl, SymTab::LoopBackward );
528 } else {
529 makeFunctionBody( decl->members.begin(), decl->members.end(),
530 functionDecl, SymTab::LoopForward );
531 }
532}
533
534const ast::Stmt * StructFuncGenerator::makeMemberOp(
535 const CodeLocation& location, const ast::ObjectDecl * dstParam,
536 const ast::Expr * src, const ast::ObjectDecl * field,
537 ast::FunctionDecl * func, SymTab::LoopDirection direction ) {
538 InitTweak::InitExpander srcParam( src );
539 // Assign to destination.
540 ast::MemberExpr * dstSelect = new ast::MemberExpr(
541 location,
542 field,
543 new ast::CastExpr(
544 location,
545 new ast::VariableExpr( location, dstParam ),
546 dstParam->type.strict_as<ast::ReferenceType>()->base
547 )
548 );
549 const ast::Stmt * stmt = genImplicitCall(
550 srcParam, dstSelect, location, func->name,
551 field, direction
552 );
553 // This could return the above directly, except the generated code is
554 // built using the structure's members and that means all the scoped
555 // names (the forall parameters) are incorrect. This corrects them.
556 if ( stmt && !decl->params.empty() ) {
557 ast::DeclReplacer::TypeMap oldToNew;
558 for ( auto pair : group_iterate( decl->params, func->type_params ) ) {
559 oldToNew.emplace( std::get<0>(pair), std::get<1>(pair) );
560 }
561 auto node = ast::DeclReplacer::replace( stmt, oldToNew );
562 stmt = strict_dynamic_cast<const ast::Stmt *>( node );
563 }
564 return stmt;
565}
566
567template<typename Iterator>
568void StructFuncGenerator::makeFunctionBody( Iterator current, Iterator end,
569 ast::FunctionDecl * func, SymTab::LoopDirection direction ) {
570 // Trying to get the best code location. Should probably use a helper or
571 // just figure out what that would be given where this is called.
572 assert( nullptr == func->stmts );
573 const CodeLocation& location = func->location;
574
575 ast::CompoundStmt * stmts = new ast::CompoundStmt( location );
576
577 for ( ; current != end ; ++current ) {
578 const ast::ptr<ast::Decl> & member = *current;
579 auto field = member.as<ast::ObjectDecl>();
580 if ( nullptr == field ) {
581 continue;
582 }
583
584 // Don't assign to constant members (but do construct/destruct them).
585 if ( CodeGen::isAssignment( func->name ) ) {
586 // For array types we need to strip off the array layers.
587 const ast::Type * type = field->get_type();
588 while ( auto at = dynamic_cast<const ast::ArrayType *>( type ) ) {
589 type = at->base;
590 }
591 if ( type->is_const() ) {
592 continue;
593 }
594 }
595
596 assert( !func->params.empty() );
597 const ast::ObjectDecl * dstParam =
598 func->params.front().strict_as<ast::ObjectDecl>();
599 const ast::ObjectDecl * srcParam = nullptr;
600 if ( 2 == func->params.size() ) {
601 srcParam = func->params.back().strict_as<ast::ObjectDecl>();
602 }
603
604 ast::MemberExpr * srcSelect = (srcParam) ? new ast::MemberExpr(
605 location, field, new ast::VariableExpr( location, srcParam )
606 ) : nullptr;
607 const ast::Stmt * stmt =
608 makeMemberOp( location, dstParam, srcSelect, field, func, direction );
609
610 if ( nullptr != stmt ) {
611 stmts->kids.emplace_back( stmt );
612 }
613 }
614
615 func->stmts = stmts;
616}
617
618template<typename Iterator>
619void StructFuncGenerator::makeFieldCtorBody( Iterator current, Iterator end,
620 ast::FunctionDecl * func ) {
621 const CodeLocation& location = func->location;
622 auto & params = func->params;
623 // Need at least the constructed parameter and one field parameter.
624 assert( 2 <= params.size() );
625
626 ast::CompoundStmt * stmts = new ast::CompoundStmt( location );
627
628 auto dstParam = params.front().strict_as<ast::ObjectDecl>();
629 // Skip over the 'this' parameter.
630 for ( auto param = params.begin() + 1 ; current != end ; ++current ) {
631 const ast::ptr<ast::Decl> & member = *current;
632 const ast::Stmt * stmt = nullptr;
633 auto field = member.as<ast::ObjectDecl>();
634 // Not sure why it could be null.
635 // Don't make a function for a parameter that is an unnamed bitfield.
636 if ( nullptr == field || ast::isUnnamedBitfield( field ) ) {
637 continue;
638 // Matching Parameter: Initialize the field by copy.
639 } else if ( params.end() != param ) {
640 const ast::Expr *srcSelect = new ast::VariableExpr(
641 func->location, param->get() );
642 stmt = makeMemberOp( location, dstParam, srcSelect, field, func, SymTab::LoopForward );
643 ++param;
644 // No Matching Parameter: Initialize the field by default constructor.
645 } else {
646 stmt = makeMemberOp( location, dstParam, nullptr, field, func, SymTab::LoopForward );
647 }
648
649 if ( nullptr != stmt ) {
650 stmts->kids.emplace_back( stmt );
651 }
652 }
653 func->stmts = stmts;
654}
655
656void UnionFuncGenerator::genFieldCtors() {
657 // Field constructors are only generated if default and copy constructor
658 // are generated, since they need access to both
659 unsigned numCtors = std::count_if( definitions.begin(), definitions.end(),
660 []( const ast::Decl * d ){ return CodeGen::isConstructor( d->name ); }
661 );
662 if ( 2 != numCtors ) {
663 return;
664 }
665
666 // Create a constructor which takes the first member type as a
667 // parameter. For example for `union A { int x; char y; };` generate
668 // a function with signature `void ?{}(A *, int)`. This mimics C's
669 // behaviour which initializes the first member of the union.
670
671 // Still, there must be some members.
672 if ( !decl->members.empty() ) {
673 ast::FunctionDecl * ctor = genFieldCtorProto( 1 );
674 if ( nullptr == ctor ) {
675 return;
676 }
677 produceForwardDecl( ctor );
678 auto params = ctor->params;
679 auto dstParam = params.front().strict_as<ast::ObjectDecl>();
680 auto srcParam = params.back().strict_as<ast::ObjectDecl>();
681 ctor->stmts = new ast::CompoundStmt( getLocation(),
682 { makeAssignOp( getLocation(), dstParam, srcParam ) }
683 );
684 produceDecl( ctor );
685 }
686}
687
688void UnionFuncGenerator::genFuncBody( ast::FunctionDecl * functionDecl ) {
689 const CodeLocation& location = functionDecl->location;
690 auto & params = functionDecl->params;
691 if ( InitTweak::isCopyConstructor( functionDecl )
692 || InitTweak::isAssignment( functionDecl ) ) {
693 assert( 2 == params.size() );
694 auto dstParam = params.front().strict_as<ast::ObjectDecl>();
695 auto srcParam = params.back().strict_as<ast::ObjectDecl>();
696 functionDecl->stmts = new ast::CompoundStmt( location,
697 { makeAssignOp( location, dstParam, srcParam ) }
698 );
699 } else {
700 assert( 1 == params.size() );
701 // Default constructor and destructor is empty.
702 functionDecl->stmts = new ast::CompoundStmt( location );
703 // Add unused attribute to parameter to silence warnings.
704 addUnusedAttribute( params.front() );
705
706 // Just an extra step to make the forward and declaration match.
707 if ( forwards.empty() ) return;
708 ast::FunctionDecl * fwd = strict_dynamic_cast<ast::FunctionDecl *>(
709 forwards.back().get_and_mutate() );
710 addUnusedAttribute( fwd->params.front() );
711 }
712}
713
714ast::ExprStmt * UnionFuncGenerator::makeAssignOp( const CodeLocation& location,
715 const ast::ObjectDecl * dstParam, const ast::ObjectDecl * srcParam ) {
716 return new ast::ExprStmt( location, new ast::UntypedExpr(
717 location,
718 new ast::NameExpr( location, "__builtin_memcpy" ),
719 {
720 new ast::AddressExpr( location,
721 new ast::VariableExpr( location, dstParam ) ),
722 new ast::AddressExpr( location,
723 new ast::VariableExpr( location, srcParam ) ),
724 new ast::SizeofExpr( location, srcParam->type ),
725 } ) );
726}
727
728void EnumFuncGenerator::genFieldCtors() {
729 // Enumerations to not have field constructors.
730}
731
732void EnumFuncGenerator::genFuncBody( ast::FunctionDecl * functionDecl ) {
733 const CodeLocation& location = functionDecl->location;
734 auto & params = functionDecl->params;
735 if ( InitTweak::isCopyConstructor( functionDecl )
736 || InitTweak::isAssignment( functionDecl ) ) {
737 assert( 2 == params.size() );
738 auto dstParam = params.front().strict_as<ast::ObjectDecl>();
739 auto srcParam = params.back().strict_as<ast::ObjectDecl>();
740
741 /* This looks like a recursive call, but code-gen will turn it into
742 * a C-style assignment.
743 *
744 * This is still before function pointer type conversion,
745 * so this will have to do it manually.
746 *
747 * It will also reference the parent function declaration, creating
748 * a cycle for references. This also means that the ref-counts are
749 * now non-zero and the declaration will be deleted if it ever
750 * returns to zero.
751 */
752 auto callExpr = new ast::ApplicationExpr( location,
753 ast::VariableExpr::functionPointer( location, functionDecl ),
754 {
755 new ast::VariableExpr( location, dstParam ),
756 new ast::VariableExpr( location, srcParam )
757 }
758 );
759
760 functionDecl->stmts = new ast::CompoundStmt( location,
761 { new ast::ExprStmt( location, callExpr ) }
762 );
763 } else {
764 assert( 1 == params.size() );
765 // Default constructor and destructor is empty.
766 functionDecl->stmts = new ast::CompoundStmt( location );
767 // Just add unused attribute to parameter to silence warnings.
768 addUnusedAttribute( params.front() );
769
770 // Just an extra step to make the forward and declaration match.
771 if ( forwards.empty() ) return;
772 ast::FunctionDecl * fwd = strict_dynamic_cast<ast::FunctionDecl *>(
773 forwards.back().get_and_mutate() );
774 addUnusedAttribute( fwd->params.front() );
775 }
776}
777
778ast::FunctionDecl * EnumFuncGenerator::genPosProto() const {
779 return genProto( "posE",
780 { new ast::ObjectDecl( getLocation(), "_i",
781 new ast::EnumInstType( decl ) )},
782 { new ast::ObjectDecl( getLocation(), "_ret",
783 new ast::BasicType{ ast::BasicType::UnsignedInt } )} );
784}
785
786ast::FunctionDecl * EnumFuncGenerator::genLabelProto() const {
787 return genProto( "labelE",
788 { new ast::ObjectDecl( getLocation(), "_i",
789 new ast::EnumInstType( decl ) ) },
790 { new ast::ObjectDecl( getLocation(), "_ret",
791 new ast::PointerType( new ast::BasicType{ ast::BasicType::Char } ) ) } );
792}
793
794ast::FunctionDecl * EnumFuncGenerator::genValueProto() const {
795 return genProto( "valueE",
796 { new ast::ObjectDecl( getLocation(), "_i", new ast::EnumInstType( decl ) )},
797 { new ast::ObjectDecl( getLocation(), "_ret", ast::deepCopy( decl->base ) ) } );
798}
799
800ast::FunctionDecl * EnumFuncGenerator::genSuccProto() const {
801 return genProto( "succ",
802 { new ast::ObjectDecl( getLocation(), "_i", new ast::EnumInstType( decl ) )},
803 { new ast::ObjectDecl( getLocation(), "_ret", new ast::EnumInstType( decl ))} );
804}
805
806ast::FunctionDecl * EnumFuncGenerator::genPredProto() const {
807 return genProto( "pred",
808 { new ast::ObjectDecl( getLocation(), "_i", new ast::EnumInstType( decl ))},
809 { new ast::ObjectDecl( getLocation(), "_ret", new ast::EnumInstType( decl ))} );
810}
811
812ast::FunctionDecl * EnumFuncGenerator::genSuccPosProto() const {
813 return genProto( "succ",
814 { new ast::ObjectDecl( getLocation(), "_i",
815 new ast::EnumPosType( new ast::EnumInstType( decl ) ) )},
816 {
817 new ast::ObjectDecl( getLocation(), "_ret",
818 new ast::EnumPosType( new ast::EnumInstType( decl ) ) )
819 } );
820}
821
822ast::FunctionDecl * EnumFuncGenerator::genPredPosProto() const {
823 return genProto( "pred",
824 { new ast::ObjectDecl( getLocation(), "_i",
825 new ast::EnumPosType( new ast::EnumInstType( decl ) ) )},
826 {
827 new ast::ObjectDecl( getLocation(), "_ret",
828 new ast::EnumPosType( new ast::EnumInstType( decl ) ) )
829 } );
830}
831
832void EnumFuncGenerator::genSuccFunc(ast::FunctionDecl * succDecl) {
833 const CodeLocation& location = getLocation();
834
835 auto & params = succDecl->params;
836 assert( params.size() == 1 );
837 auto param = params.front().strict_as<ast::ObjectDecl>();
838
839 // auto & returns = succDecl->returns;
840 // assert( returns.size() == 1 );
841 // auto oldRet = returns.front().strict_as<ast::ObjectDecl>();
842
843 // auto param = new ast::ObjectDecl( getLocation(), "_i",
844 // new ast::EnumPosType( new ast::EnumInstType( decl ) ) );
845
846 auto newReturn = new ast::ObjectDecl( location, "_returns",
847 new ast::BasicType{ ast::BasicType::SignedInt} );
848
849
850 ast::UntypedExpr * addOneExpr = new ast::UntypedExpr( location,
851 new ast::NameExpr( location, "?+?" )
852 );
853 addOneExpr->args.push_back(
854 new ast::CastExpr( location,
855 new ast::VariableExpr( location, param ),
856 new ast::BasicType{ ast::BasicType::SignedInt }
857 )
858 );
859 addOneExpr->args.push_back(
860 ast::ConstantExpr::from_int( location, 1 )
861 );
862
863 ast::UntypedExpr * assignExpr = new ast::UntypedExpr( location,
864 new ast::NameExpr( location, "?=?" )
865 );
866 assignExpr->args.push_back(
867 new ast::VariableExpr( location, newReturn )
868 );
869 assignExpr->args.push_back(
870 addOneExpr
871 );
872
873 succDecl->stmts = new ast::CompoundStmt( location,
874 {
875 new ast::DeclStmt( location, newReturn ),
876 new ast::ExprStmt( location, assignExpr ),
877 new ast::ReturnStmt( location,
878 new ast::VariableExpr( location, newReturn ))
879 } );
880}
881
882void EnumFuncGenerator::genAttrFuncForward() {
883 if ( decl->base ) {
884 ast::FunctionDecl *(EnumFuncGenerator::*attrProtos[5])() const = {
885 &EnumFuncGenerator::genPosProto, &EnumFuncGenerator::genLabelProto,
886 &EnumFuncGenerator::genValueProto, &EnumFuncGenerator::genSuccProto,
887 &EnumFuncGenerator::genPredProto
888 };
889 for ( auto & generator : attrProtos ) {
890 produceForwardDecl( (this->*generator)() );
891 }
892 }
893}
894
895void EnumFuncGenerator::genPosFunctions() {
896 if ( decl->base ) {
897 ast::FunctionDecl * decl = genSuccPosProto();
898 produceForwardDecl( decl );
899 genSuccFunc (decl );
900 produceDecl( decl );
901 }
902
903}
904
905void TypeFuncGenerator::genFieldCtors() {
906 // Opaque types do not have field constructors.
907}
908
909void TypeFuncGenerator::genFuncBody( ast::FunctionDecl * functionDecl ) {
910 const CodeLocation& location = functionDecl->location;
911 auto & params = functionDecl->type->params;
912 assertf( 1 == params.size() || 2 == params.size(),
913 "Incorrect number of parameters in autogenerated typedecl function: %zd",
914 params.size() );
915 auto dstParam = params.front().strict_as<ast::ObjectDecl>();
916 auto srcParam = (2 == params.size())
917 ? params.back().strict_as<ast::ObjectDecl>() : nullptr;
918 // Generate appropriate calls to member constructor and assignment.
919 ast::UntypedExpr * expr = new ast::UntypedExpr( location,
920 new ast::NameExpr( location, functionDecl->name )
921 );
922 expr->args.push_back( new ast::CastExpr( location,
923 new ast::VariableExpr( location, dstParam ),
924 new ast::ReferenceType( decl->base )
925 ) );
926 if ( srcParam ) {
927 expr->args.push_back( new ast::CastExpr( location,
928 new ast::VariableExpr( location, srcParam ),
929 decl->base
930 ) );
931 }
932 functionDecl->stmts = new ast::CompoundStmt( location,
933 { new ast::ExprStmt( location, expr ) }
934 );
935}
936
937} // namespace
938
939void autogenerateRoutines( ast::TranslationUnit & translationUnit ) {
940 ast::Pass<AutogenerateRoutines>::run( translationUnit );
941}
942
943} // Validate
944
945// Local Variables: //
946// tab-width: 4 //
947// mode: c++ //
948// compile-command: "make install" //
949// End: //
Note: See TracBrowser for help on using the repository browser.