source: src/Concurrency/KeywordsNew.cpp @ 884f3f67

ADTast-experimentalenumpthread-emulationqualifiedEnum
Last change on this file since 884f3f67 was 4f6dda0, checked in by Andrew Beach <ajbeach@…>, 2 years ago

Converted Implement Concurrent Keywords to the new AST. Includes updates to various helpers, including the virtual table and a lot of examine helpers.

  • Property mode set to 100644
File size: 42.4 KB
Line 
1//
2// Cforall Version 1.0.0 Copyright (C) 2016 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// KeywordsNew.cpp -- Implement concurrency constructs from their keywords.
8//
9// Author           : Andrew Beach
10// Created On       : Tue Nov 16  9:53:00 2021
11// Last Modified By : Andrew Beach
12// Last Modified On : Fri Mar 11 10:40:00 2022
13// Update Count     : 2
14//
15
16#include "Concurrency/Keywords.h"
17
18#include "AST/Copy.hpp"
19#include "AST/Decl.hpp"
20#include "AST/Expr.hpp"
21#include "AST/Pass.hpp"
22#include "AST/Stmt.hpp"
23#include "AST/DeclReplacer.hpp"
24#include "AST/TranslationUnit.hpp"
25#include "CodeGen/OperatorTable.h"
26#include "Common/Examine.h"
27#include "Common/utility.h"
28#include "ControlStruct/LabelGeneratorNew.hpp"
29#include "InitTweak/InitTweak.h"
30#include "Virtual/Tables.h"
31
32namespace Concurrency {
33
34namespace {
35
36// --------------------------------------------------------------------------
37// Loose Helper Functions:
38
39/// Detect threads constructed with the keyword thread.
40bool isThread( const ast::DeclWithType * decl ) {
41        auto baseType = decl->get_type()->stripDeclarator();
42        auto instType = dynamic_cast<const ast::StructInstType *>( baseType );
43        if ( nullptr == instType ) { return false; }
44        return instType->base->is_thread();
45}
46
47/// Get the virtual type id if given a type name.
48std::string typeIdType( std::string const & exception_name ) {
49        return exception_name.empty() ? std::string()
50                : Virtual::typeIdType( exception_name );
51}
52
53/// Get the vtable type name if given a type name.
54std::string vtableTypeName( std::string const & exception_name ) {
55        return exception_name.empty() ? std::string()
56                : Virtual::vtableTypeName( exception_name );
57}
58
59static ast::Type * mutate_under_references( ast::ptr<ast::Type>& type ) {
60        ast::Type * mutType = type.get_and_mutate();
61        for ( ast::ReferenceType * mutRef
62                ; (mutRef = dynamic_cast<ast::ReferenceType *>( mutType ))
63                ; mutType = mutRef->base.get_and_mutate() );
64        return mutType;
65}
66
67// Describe that it adds the generic parameters and the uses of the generic
68// parameters on the function and first "this" argument.
69ast::FunctionDecl * fixupGenerics(
70                const ast::FunctionDecl * func, const ast::StructDecl * decl ) {
71        const CodeLocation & location = decl->location;
72        // We have to update both the declaration
73        auto mutFunc = ast::mutate( func );
74        auto mutType = mutFunc->type.get_and_mutate();
75
76        if ( decl->params.empty() ) {
77                return mutFunc;
78        }
79
80        assert( 0 != mutFunc->params.size() );
81        assert( 0 != mutType->params.size() );
82
83        // Add the "forall" clause information.
84        for ( const ast::ptr<ast::TypeDecl> & typeParam : decl->params ) {
85                auto typeDecl = ast::deepCopy( typeParam );
86                mutFunc->type_params.push_back( typeDecl );
87                mutType->forall.push_back(
88                        new ast::TypeInstType( typeDecl->name, typeDecl ) );
89                for ( auto & assertion : typeDecl->assertions ) {
90                        mutFunc->assertions.push_back( assertion );
91                        mutType->assertions.emplace_back(
92                                new ast::VariableExpr( location, assertion ) );
93                }
94                typeDecl->assertions.clear();
95        }
96
97        // Even chain_mutate is not powerful enough for this:
98        ast::ptr<ast::Type>& paramType = strict_dynamic_cast<ast::ObjectDecl *>(
99                mutFunc->params[0].get_and_mutate() )->type;
100        auto paramTypeInst = strict_dynamic_cast<ast::StructInstType *>(
101                mutate_under_references( paramType ) );
102        auto typeParamInst = strict_dynamic_cast<ast::StructInstType *>(
103                mutate_under_references( mutType->params[0] ) );
104
105        for ( const ast::ptr<ast::TypeDecl> & typeDecl : mutFunc->type_params ) {
106                paramTypeInst->params.push_back(
107                        new ast::TypeExpr( location,
108                                new ast::TypeInstType( typeDecl->name, typeDecl ) ) );
109                typeParamInst->params.push_back(
110                        new ast::TypeExpr( location,
111                                new ast::TypeInstType( typeDecl->name, typeDecl ) ) );
112        }
113
114        return mutFunc;
115}
116
117// --------------------------------------------------------------------------
118struct ConcurrentSueKeyword : public ast::WithDeclsToAdd<> {
119        ConcurrentSueKeyword(
120                std::string&& type_name, std::string&& field_name,
121                std::string&& getter_name, std::string&& context_error,
122                std::string&& exception_name,
123                bool needs_main, ast::AggregateDecl::Aggregate cast_target
124        ) :
125                type_name( type_name ), field_name( field_name ),
126                getter_name( getter_name ), context_error( context_error ),
127                exception_name( exception_name ),
128                typeid_name( typeIdType( exception_name ) ),
129                vtable_name( vtableTypeName( exception_name ) ),
130                needs_main( needs_main ), cast_target( cast_target )
131        {}
132
133        virtual ~ConcurrentSueKeyword() {}
134
135        const ast::Decl * postvisit( const ast::StructDecl * decl );
136        const ast::DeclWithType * postvisit( const ast::FunctionDecl * decl );
137        const ast::Expr * postvisit( const ast::KeywordCastExpr * expr );
138
139        struct StructAndField {
140                const ast::StructDecl * decl;
141                const ast::ObjectDecl * field;
142        };
143
144        const ast::StructDecl * handleStruct( const ast::StructDecl * );
145        void handleMain( const ast::FunctionDecl *, const ast::StructInstType * );
146        void addTypeId( const ast::StructDecl * );
147        void addVtableForward( const ast::StructDecl * );
148        const ast::FunctionDecl * forwardDeclare( const ast::StructDecl * );
149        StructAndField addField( const ast::StructDecl * );
150        void addGetRoutines( const ast::ObjectDecl *, const ast::FunctionDecl * );
151        void addLockUnlockRoutines( const ast::StructDecl * );
152
153private:
154        const std::string type_name;
155        const std::string field_name;
156        const std::string getter_name;
157        const std::string context_error;
158        const std::string exception_name;
159        const std::string typeid_name;
160        const std::string vtable_name;
161        const bool needs_main;
162        const ast::AggregateDecl::Aggregate cast_target;
163
164        const ast::StructDecl   * type_decl = nullptr;
165        const ast::FunctionDecl * dtor_decl = nullptr;
166        const ast::StructDecl * except_decl = nullptr;
167        const ast::StructDecl * typeid_decl = nullptr;
168        const ast::StructDecl * vtable_decl = nullptr;
169};
170
171// Handles thread type declarations:
172//
173// thread Mythread {                         struct MyThread {
174//  int data;                                  int data;
175//  a_struct_t more_data;                      a_struct_t more_data;
176//                                =>             thread$ __thrd_d;
177// };                                        };
178//                                           static inline thread$ * get_thread( MyThread * this ) { return &this->__thrd_d; }
179//
180struct ThreadKeyword final : public ConcurrentSueKeyword {
181        ThreadKeyword() : ConcurrentSueKeyword(
182                "thread$",
183                "__thrd",
184                "get_thread",
185                "thread keyword requires threads to be in scope, add #include <thread.hfa>\n",
186                "ThreadCancelled",
187                true,
188                ast::AggregateDecl::Thread )
189        {}
190
191        virtual ~ThreadKeyword() {}
192};
193
194// Handles coroutine type declarations:
195//
196// coroutine MyCoroutine {                   struct MyCoroutine {
197//  int data;                                  int data;
198//  a_struct_t more_data;                      a_struct_t more_data;
199//                                =>             coroutine$ __cor_d;
200// };                                        };
201//                                           static inline coroutine$ * get_coroutine( MyCoroutine * this ) { return &this->__cor_d; }
202//
203struct CoroutineKeyword final : public ConcurrentSueKeyword {
204        CoroutineKeyword() : ConcurrentSueKeyword(
205                "coroutine$",
206                "__cor",
207                "get_coroutine",
208                "coroutine keyword requires coroutines to be in scope, add #include <coroutine.hfa>\n",
209                "CoroutineCancelled",
210                true,
211                ast::AggregateDecl::Coroutine )
212        {}
213
214        virtual ~CoroutineKeyword() {}
215};
216
217// Handles monitor type declarations:
218//
219// monitor MyMonitor {                       struct MyMonitor {
220//  int data;                                  int data;
221//  a_struct_t more_data;                      a_struct_t more_data;
222//                                =>             monitor$ __mon_d;
223// };                                        };
224//                                           static inline monitor$ * get_coroutine( MyMonitor * this ) {
225//                                               return &this->__cor_d;
226//                                           }
227//                                           void lock(MyMonitor & this) {
228//                                               lock(get_monitor(this));
229//                                           }
230//                                           void unlock(MyMonitor & this) {
231//                                               unlock(get_monitor(this));
232//                                           }
233//
234struct MonitorKeyword final : public ConcurrentSueKeyword {
235        MonitorKeyword() : ConcurrentSueKeyword(
236                "monitor$",
237                "__mon",
238                "get_monitor",
239                "monitor keyword requires monitors to be in scope, add #include <monitor.hfa>\n",
240                "",
241                false,
242                ast::AggregateDecl::Monitor )
243        {}
244
245        virtual ~MonitorKeyword() {}
246};
247
248// Handles generator type declarations:
249//
250// generator MyGenerator {                   struct MyGenerator {
251//  int data;                                  int data;
252//  a_struct_t more_data;                      a_struct_t more_data;
253//                                =>             int __generator_state;
254// };                                        };
255//
256struct GeneratorKeyword final : public ConcurrentSueKeyword {
257        GeneratorKeyword() : ConcurrentSueKeyword(
258                "generator$",
259                "__generator_state",
260                "get_generator",
261                "Unable to find builtin type generator$\n",
262                "",
263                true,
264                ast::AggregateDecl::Generator )
265        {}
266
267        virtual ~GeneratorKeyword() {}
268};
269
270const ast::Decl * ConcurrentSueKeyword::postvisit(
271                const ast::StructDecl * decl ) {
272        if ( !decl->body ) {
273                return decl;
274        } else if ( cast_target == decl->kind ) {
275                return handleStruct( decl );
276        } else if ( type_name == decl->name ) {
277                assert( !type_decl );
278                type_decl = decl;
279        } else if ( exception_name == decl->name ) {
280                assert( !except_decl );
281                except_decl = decl;
282        } else if ( typeid_name == decl->name ) {
283                assert( !typeid_decl );
284                typeid_decl = decl;
285        } else if ( vtable_name == decl->name ) {
286                assert( !vtable_decl );
287                vtable_decl = decl;
288        }
289        return decl;
290}
291
292// Try to get the full definition, but raise an error on conflicts.
293const ast::FunctionDecl * getDefinition(
294                const ast::FunctionDecl * old_decl,
295                const ast::FunctionDecl * new_decl ) {
296        if ( !new_decl->stmts ) {
297                return old_decl;
298        } else if ( !old_decl->stmts ) {
299                return new_decl;
300        } else {
301                assert( !old_decl->stmts || !new_decl->stmts );
302                return nullptr;
303        }
304}
305
306const ast::DeclWithType * ConcurrentSueKeyword::postvisit(
307                const ast::FunctionDecl * decl ) {
308        if ( type_decl && isDestructorFor( decl, type_decl ) ) {
309                // Check for forward declarations, try to get the full definition.
310                dtor_decl = (dtor_decl) ? getDefinition( dtor_decl, decl ) : decl;
311        } else if ( !vtable_name.empty() && decl->has_body() ) {
312                if (const ast::DeclWithType * param = isMainFor( decl, cast_target )) {
313                        if ( !vtable_decl ) {
314                                SemanticError( decl, context_error );
315                        }
316                        // Should be safe because of isMainFor.
317                        const ast::StructInstType * struct_type =
318                                static_cast<const ast::StructInstType *>(
319                                        static_cast<const ast::ReferenceType *>(
320                                                param->get_type() )->base.get() );
321
322                        handleMain( decl, struct_type );
323                }
324        }
325        return decl;
326}
327
328const ast::Expr * ConcurrentSueKeyword::postvisit(
329                const ast::KeywordCastExpr * expr ) {
330        if ( cast_target == expr->target ) {
331                // Convert `(thread &)ex` to `(thread$ &)*get_thread(ex)`, etc.
332                if ( !type_decl || !dtor_decl ) {
333                        SemanticError( expr, context_error );
334                }
335                assert( nullptr == expr->result );
336                auto cast = ast::mutate( expr );
337                cast->result = new ast::ReferenceType( new ast::StructInstType( type_decl ) );
338                cast->concrete_target.field  = field_name;
339                cast->concrete_target.getter = getter_name;
340                return cast;
341        }
342        return expr;
343}
344
345const ast::StructDecl * ConcurrentSueKeyword::handleStruct(
346                const ast::StructDecl * decl ) {
347        assert( decl->body );
348
349        if ( !type_decl || !dtor_decl ) {
350                SemanticError( decl, context_error );
351        }
352
353        if ( !exception_name.empty() ) {
354                if( !typeid_decl || !vtable_decl ) {
355                        SemanticError( decl, context_error );
356                }
357                addTypeId( decl );
358                addVtableForward( decl );
359        }
360
361        const ast::FunctionDecl * func = forwardDeclare( decl );
362        StructAndField addFieldRet = addField( decl );
363        decl = addFieldRet.decl;
364        const ast::ObjectDecl * field = addFieldRet.field;
365
366        addGetRoutines( field, func );
367        // Add routines to monitors for use by mutex stmt.
368        if ( ast::AggregateDecl::Monitor == cast_target ) {
369                addLockUnlockRoutines( decl );
370        }
371
372        return decl;
373}
374
375void ConcurrentSueKeyword::handleMain(
376                const ast::FunctionDecl * decl, const ast::StructInstType * type ) {
377        assert( vtable_decl );
378        assert( except_decl );
379
380        const CodeLocation & location = decl->location;
381
382        std::vector<ast::ptr<ast::Expr>> poly_args = {
383                new ast::TypeExpr( location, type ),
384        };
385        ast::ObjectDecl * vtable_object = Virtual::makeVtableInstance(
386                location,
387                "_default_vtable_object_declaration",
388                new ast::StructInstType( vtable_decl, copy( poly_args ) ),
389                type,
390                nullptr
391        );
392        declsToAddAfter.push_back( vtable_object );
393        declsToAddAfter.push_back(
394                new ast::ObjectDecl(
395                        location,
396                        Virtual::concurrentDefaultVTableName(),
397                        new ast::ReferenceType( vtable_object->type, ast::CV::Const ),
398                        new ast::SingleInit( location,
399                                new ast::VariableExpr( location, vtable_object ) ),
400                        ast::Storage::Classes(),
401                        ast::Linkage::Cforall
402                )
403        );
404        declsToAddAfter.push_back( Virtual::makeGetExceptionFunction(
405                location,
406                vtable_object,
407                new ast::StructInstType( except_decl, copy( poly_args ) )
408        ) );
409}
410
411void ConcurrentSueKeyword::addTypeId( const ast::StructDecl * decl ) {
412        assert( typeid_decl );
413        const CodeLocation & location = decl->location;
414
415        ast::StructInstType * typeid_type =
416                new ast::StructInstType( typeid_decl, ast::CV::Const );
417        typeid_type->params.push_back(
418                new ast::TypeExpr( location, new ast::StructInstType( decl ) ) );
419        declsToAddBefore.push_back(
420                Virtual::makeTypeIdInstance( location, typeid_type ) );
421        // If the typeid_type is going to be kept, the other reference will have
422        // been made by now, but we also get to avoid extra mutates.
423        ast::ptr<ast::StructInstType> typeid_cleanup = typeid_type;
424}
425
426void ConcurrentSueKeyword::addVtableForward( const ast::StructDecl * decl ) {
427        assert( vtable_decl );
428        const CodeLocation& location = decl->location;
429
430        std::vector<ast::ptr<ast::Expr>> poly_args = {
431                new ast::TypeExpr( location, new ast::StructInstType( decl ) ),
432        };
433        declsToAddBefore.push_back( Virtual::makeGetExceptionForward(
434                location,
435                new ast::StructInstType( vtable_decl, copy( poly_args ) ),
436                new ast::StructInstType( except_decl, copy( poly_args ) )
437        ) );
438        ast::ObjectDecl * vtable_object = Virtual::makeVtableForward(
439                location,
440                "_default_vtable_object_declaration",
441                new ast::StructInstType( vtable_decl, std::move( poly_args ) )
442        );
443        declsToAddBefore.push_back( vtable_object );
444        declsToAddBefore.push_back(
445                new ast::ObjectDecl(
446                        location,
447                        Virtual::concurrentDefaultVTableName(),
448                        new ast::ReferenceType( vtable_object->type, ast::CV::Const ),
449                        nullptr,
450                        ast::Storage::Extern,
451                        ast::Linkage::Cforall
452                )
453        );
454}
455
456const ast::FunctionDecl * ConcurrentSueKeyword::forwardDeclare(
457                const ast::StructDecl * decl ) {
458        const CodeLocation & location = decl->location;
459
460        ast::StructDecl * forward = ast::deepCopy( decl );
461        {
462                // If removing members makes ref-count go to zero, do not free.
463                ast::ptr<ast::StructDecl> forward_ptr = forward;
464                forward->body = false;
465                forward->members.clear();
466                forward_ptr.release();
467        }
468
469        ast::ObjectDecl * this_decl = new ast::ObjectDecl(
470                location,
471                "this",
472                new ast::ReferenceType( new ast::StructInstType( decl ) ),
473                nullptr,
474                ast::Storage::Classes(),
475                ast::Linkage::Cforall
476        );
477
478        ast::ObjectDecl * ret_decl = new ast::ObjectDecl(
479                location,
480                "ret",
481                new ast::PointerType( new ast::StructInstType( type_decl ) ),
482                nullptr,
483                ast::Storage::Classes(),
484                ast::Linkage::Cforall
485        );
486
487        ast::FunctionDecl * get_decl = new ast::FunctionDecl(
488                location,
489                getter_name,
490                {}, // forall
491                { this_decl }, // params
492                { ret_decl }, // returns
493                nullptr, // stmts
494                ast::Storage::Static,
495                ast::Linkage::Cforall,
496                { new ast::Attribute( "const" ) },
497                ast::Function::Inline
498        );
499        get_decl = fixupGenerics( get_decl, decl );
500
501        ast::FunctionDecl * main_decl = nullptr;
502        if ( needs_main ) {
503                // `this_decl` is copied here because the original was used above.
504                main_decl = new ast::FunctionDecl(
505                        location,
506                        "main",
507                        {},
508                        { ast::deepCopy( this_decl ) },
509                        {},
510                        nullptr,
511                        ast::Storage::Classes(),
512                        ast::Linkage::Cforall
513                );
514                main_decl = fixupGenerics( main_decl, decl );
515        }
516
517        declsToAddBefore.push_back( forward );
518        if ( needs_main ) declsToAddBefore.push_back( main_decl );
519        declsToAddBefore.push_back( get_decl );
520
521        return get_decl;
522}
523
524ConcurrentSueKeyword::StructAndField ConcurrentSueKeyword::addField(
525                const ast::StructDecl * decl ) {
526        const CodeLocation & location = decl->location;
527
528        ast::ObjectDecl * field = new ast::ObjectDecl(
529                location,
530                field_name,
531                new ast::StructInstType( type_decl ),
532                nullptr,
533                ast::Storage::Classes(),
534                ast::Linkage::Cforall
535        );
536
537        auto mutDecl = ast::mutate( decl );
538        mutDecl->members.push_back( field );
539
540        return {mutDecl, field};
541}
542
543void ConcurrentSueKeyword::addGetRoutines(
544                const ast::ObjectDecl * field, const ast::FunctionDecl * forward ) {
545        // Say it is generated at the "same" places as the forward declaration.
546        const CodeLocation & location = forward->location;
547
548        const ast::DeclWithType * param = forward->params.front();
549        ast::Stmt * stmt = new ast::ReturnStmt( location,
550                new ast::AddressExpr( location,
551                        new ast::MemberExpr( location,
552                                field,
553                                new ast::CastExpr( location,
554                                        new ast::VariableExpr( location, param ),
555                                        ast::deepCopy( param->get_type()->stripReferences() ),
556                                        ast::ExplicitCast
557                                )
558                        )
559                )
560        );
561
562        ast::FunctionDecl * decl = ast::deepCopy( forward );
563        decl->stmts = new ast::CompoundStmt( location, { stmt } );
564        declsToAddAfter.push_back( decl );
565}
566
567void ConcurrentSueKeyword::addLockUnlockRoutines(
568                const ast::StructDecl * decl ) {
569        // This should only be used on monitors.
570        assert( ast::AggregateDecl::Monitor == cast_target );
571
572        const CodeLocation & location = decl->location;
573
574        // The parameter for both routines.
575        ast::ObjectDecl * this_decl = new ast::ObjectDecl(
576                location,
577                "this",
578                new ast::ReferenceType( new ast::StructInstType( decl ) ),
579                nullptr,
580                ast::Storage::Classes(),
581                ast::Linkage::Cforall
582        );
583
584        ast::FunctionDecl * lock_decl = new ast::FunctionDecl(
585                location,
586                "lock",
587                { /* forall */ },
588                {
589                        // Copy the declaration of this.
590                        ast::deepCopy( this_decl ),
591                },
592                { /* returns */ },
593                nullptr,
594                ast::Storage::Static,
595                ast::Linkage::Cforall,
596                { /* attributes */ },
597                ast::Function::Inline
598        );
599        lock_decl = fixupGenerics( lock_decl, decl );
600
601        lock_decl->stmts = new ast::CompoundStmt( location, {
602                new ast::ExprStmt( location,
603                        new ast::UntypedExpr( location,
604                                new ast::NameExpr( location, "lock" ),
605                                {
606                                        new ast::UntypedExpr( location,
607                                                new ast::NameExpr( location, "get_monitor" ),
608                                                { new ast::VariableExpr( location,
609                                                        InitTweak::getParamThis( lock_decl ) ) }
610                                        )
611                                }
612                        )
613                )
614        } );
615
616        ast::FunctionDecl * unlock_decl = new ast::FunctionDecl(
617                location,
618                "unlock",
619                { /* forall */ },
620                {
621                        // Last use, consume the declaration of this.
622                        this_decl,
623                },
624                { /* returns */ },
625                nullptr,
626                ast::Storage::Static,
627                ast::Linkage::Cforall,
628                { /* attributes */ },
629                ast::Function::Inline
630        );
631        unlock_decl = fixupGenerics( unlock_decl, decl );
632
633        unlock_decl->stmts = new ast::CompoundStmt( location, {
634                new ast::ExprStmt( location,
635                        new ast::UntypedExpr( location,
636                                new ast::NameExpr( location, "unlock" ),
637                                {
638                                        new ast::UntypedExpr( location,
639                                                new ast::NameExpr( location, "get_monitor" ),
640                                                { new ast::VariableExpr( location,
641                                                        InitTweak::getParamThis( unlock_decl ) ) }
642                                        )
643                                }
644                        )
645                )
646        } );
647
648        declsToAddAfter.push_back( lock_decl );
649        declsToAddAfter.push_back( unlock_decl );
650}
651
652
653// --------------------------------------------------------------------------
654struct SuspendKeyword final :
655                public ast::WithStmtsToAdd<>, public ast::WithGuards {
656        SuspendKeyword() = default;
657        virtual ~SuspendKeyword() = default;
658
659        void previsit( const ast::FunctionDecl * );
660        const ast::DeclWithType * postvisit( const ast::FunctionDecl * );
661        const ast::Stmt * postvisit( const ast::SuspendStmt * );
662
663private:
664        bool is_real_suspend( const ast::FunctionDecl * );
665
666        const ast::Stmt * make_generator_suspend( const ast::SuspendStmt * );
667        const ast::Stmt * make_coroutine_suspend( const ast::SuspendStmt * );
668
669        struct LabelPair {
670                ast::Label obj;
671                int idx;
672        };
673
674        LabelPair make_label(const ast::Stmt * stmt ) {
675                labels.push_back( ControlStruct::newLabel( "generator", stmt ) );
676                return { labels.back(), int(labels.size()) };
677        }
678
679        const ast::DeclWithType * in_generator = nullptr;
680        const ast::FunctionDecl * decl_suspend = nullptr;
681        std::vector<ast::Label> labels;
682};
683
684void SuspendKeyword::previsit( const ast::FunctionDecl * decl ) {
685        GuardValue( in_generator ); in_generator = nullptr;
686
687        // If it is the real suspend, grab it if we don't have one already.
688        if ( is_real_suspend( decl ) ) {
689                decl_suspend = decl_suspend ? decl_suspend : decl;
690                return;
691        }
692
693        // Otherwise check if this is a generator main and, if so, handle it.
694        auto param = isMainFor( decl, ast::AggregateDecl::Generator );
695        if ( !param ) return;
696
697        if ( 0 != decl->returns.size() ) {
698                SemanticError( decl->location, "Generator main must return void" );
699        }
700
701        in_generator = param;
702        GuardValue( labels ); labels.clear();
703}
704
705const ast::DeclWithType * SuspendKeyword::postvisit(
706                const ast::FunctionDecl * decl ) {
707        // Only modify a full definition of a generator with states.
708        if ( !decl->stmts || !in_generator || labels.empty() ) return decl;
709
710        const CodeLocation & location = decl->location;
711
712        // Create a new function body:
713        // static void * __generator_labels[] = {&&s0, &&s1, ...};
714        // void * __generator_label = __generator_labels[GEN.__generator_state];
715        // goto * __generator_label;
716        // s0: ;
717        // OLD_BODY
718
719        // This is the null statement inserted right before the body.
720        ast::NullStmt * noop = new ast::NullStmt( location );
721        noop->labels.push_back( ControlStruct::newLabel( "generator", noop ) );
722        const ast::Label & first_label = noop->labels.back();
723
724        // Add each label to the init, starting with the first label.
725        std::vector<ast::ptr<ast::Init>> inits = {
726                new ast::SingleInit( location,
727                        new ast::LabelAddressExpr( location, copy( first_label ) ) ) };
728        // Then go through all the stored labels, and clear the store.
729        for ( auto && label : labels ) {
730                inits.push_back( new ast::SingleInit( label.location,
731                        new ast::LabelAddressExpr( label.location, std::move( label )
732                        ) ) );
733        }
734        labels.clear();
735        // Then construct the initializer itself.
736        auto init = new ast::ListInit( location, std::move( inits ) );
737
738        ast::ObjectDecl * generatorLabels = new ast::ObjectDecl(
739                location,
740                "__generator_labels",
741                new ast::ArrayType(
742                        new ast::PointerType( new ast::VoidType() ),
743                        nullptr,
744                        ast::FixedLen,
745                        ast::DynamicDim
746                ),
747                init,
748                ast::Storage::Classes(),
749                ast::Linkage::AutoGen
750        );
751
752        ast::ObjectDecl * generatorLabel = new ast::ObjectDecl(
753                location,
754                "__generator_label",
755                new ast::PointerType( new ast::VoidType() ),
756                new ast::SingleInit( location,
757                        new ast::UntypedExpr( location,
758                                new ast::NameExpr( location, "?[?]" ),
759                                {
760                                        // TODO: Could be a variable expr.
761                                        new ast::NameExpr( location, "__generator_labels" ),
762                                        new ast::UntypedMemberExpr( location,
763                                                new ast::NameExpr( location, "__generator_state" ),
764                                                new ast::VariableExpr( location, in_generator )
765                                        )
766                                }
767                        )
768                ),
769                ast::Storage::Classes(),
770                ast::Linkage::AutoGen
771        );
772
773        ast::BranchStmt * theGoTo = new ast::BranchStmt(
774                location, new ast::VariableExpr( location, generatorLabel )
775        );
776
777        // The noop goes here in order.
778
779        ast::CompoundStmt * body = new ast::CompoundStmt( location, {
780                { new ast::DeclStmt( location, generatorLabels ) },
781                { new ast::DeclStmt( location, generatorLabel ) },
782                { theGoTo },
783                { noop },
784                { decl->stmts },
785        } );
786
787        auto mutDecl = ast::mutate( decl );
788        mutDecl->stmts = body;
789        return mutDecl;
790}
791
792const ast::Stmt * SuspendKeyword::postvisit( const ast::SuspendStmt * stmt ) {
793        switch ( stmt->type ) {
794        case ast::SuspendStmt::None:
795                // Use the context to determain the implicit target.
796                if ( in_generator ) {
797                        return make_generator_suspend( stmt );
798                } else {
799                        return make_coroutine_suspend( stmt );
800                }
801        case ast::SuspendStmt::Coroutine:
802                return make_coroutine_suspend( stmt );
803        case ast::SuspendStmt::Generator:
804                // Generator suspends must be directly in a generator.
805                if ( !in_generator ) SemanticError( stmt->location, "'suspend generator' must be used inside main of generator type." );
806                return make_generator_suspend( stmt );
807        }
808        assert( false );
809        return stmt;
810}
811
812/// Find the real/official suspend declaration.
813bool SuspendKeyword::is_real_suspend( const ast::FunctionDecl * decl ) {
814        return ( !decl->linkage.is_mangled
815                && 0 == decl->params.size()
816                && 0 == decl->returns.size()
817                && "__cfactx_suspend" == decl->name );
818}
819
820const ast::Stmt * SuspendKeyword::make_generator_suspend(
821                const ast::SuspendStmt * stmt ) {
822        assert( in_generator );
823        // Target code is:
824        //   GEN.__generator_state = X;
825        //   THEN
826        //   return;
827        //   __gen_X:;
828
829        const CodeLocation & location = stmt->location;
830
831        LabelPair label = make_label( stmt );
832
833        // This is the context saving statement.
834        stmtsToAddBefore.push_back( new ast::ExprStmt( location,
835                new ast::UntypedExpr( location,
836                        new ast::NameExpr( location, "?=?" ),
837                        {
838                                new ast::UntypedMemberExpr( location,
839                                        new ast::NameExpr( location, "__generator_state" ),
840                                        new ast::VariableExpr( location, in_generator )
841                                ),
842                                ast::ConstantExpr::from_int( location, label.idx ),
843                        }
844                )
845        ) );
846
847        // The THEN component is conditional (return is not).
848        if ( stmt->then ) {
849                stmtsToAddBefore.push_back( stmt->then.get() );
850        }
851        stmtsToAddBefore.push_back( new ast::ReturnStmt( location, nullptr ) );
852
853        // The null statement replaces the old suspend statement.
854        return new ast::NullStmt( location, { label.obj } );
855}
856
857const ast::Stmt * SuspendKeyword::make_coroutine_suspend(
858                const ast::SuspendStmt * stmt ) {
859        // The only thing we need from the old statement is the location.
860        const CodeLocation & location = stmt->location;
861
862        if ( !decl_suspend ) {
863                SemanticError( location, "suspend keyword applied to coroutines requires coroutines to be in scope, add #include <coroutine.hfa>\n" );
864        }
865        if ( stmt->then ) {
866                SemanticError( location, "Compound statement following coroutines is not implemented." );
867        }
868
869        return new ast::ExprStmt( location,
870                new ast::UntypedExpr( location,
871                        ast::VariableExpr::functionPointer( location, decl_suspend ) )
872        );
873}
874
875// --------------------------------------------------------------------------
876struct MutexKeyword final {
877        const ast::FunctionDecl * postvisit( const ast::FunctionDecl * decl );
878        void postvisit( const ast::StructDecl * decl );
879        const ast::Stmt * postvisit( const ast::MutexStmt * stmt );
880
881        static std::vector<const ast::DeclWithType *> findMutexArgs(
882                        const ast::FunctionDecl * decl, bool & first );
883        static void validate( const ast::DeclWithType * decl );
884
885        ast::CompoundStmt * addDtorStatements( const ast::FunctionDecl* func, const ast::CompoundStmt *, const std::vector<const ast::DeclWithType *> &);
886        ast::CompoundStmt * addStatements( const ast::FunctionDecl* func, const ast::CompoundStmt *, const std::vector<const ast::DeclWithType *> &);
887        ast::CompoundStmt * addStatements( const ast::CompoundStmt * body, const std::vector<ast::ptr<ast::Expr>> & args );
888        ast::CompoundStmt * addThreadDtorStatements( const ast::FunctionDecl* func, const ast::CompoundStmt * body, const std::vector<const ast::DeclWithType *> & args );
889
890private:
891        const ast::StructDecl * monitor_decl = nullptr;
892        const ast::StructDecl * guard_decl = nullptr;
893        const ast::StructDecl * dtor_guard_decl = nullptr;
894        const ast::StructDecl * thread_guard_decl = nullptr;
895        const ast::StructDecl * lock_guard_decl = nullptr;
896
897        static ast::ptr<ast::Type> generic_func;
898};
899
900const ast::FunctionDecl * MutexKeyword::postvisit(
901                const ast::FunctionDecl * decl ) {
902        bool is_first_argument_mutex = false;
903        const std::vector<const ast::DeclWithType *> mutexArgs =
904                findMutexArgs( decl, is_first_argument_mutex );
905        bool const isDtor = CodeGen::isDestructor( decl->name );
906
907        // Does this function have any mutex arguments that connect to monitors?
908        if ( mutexArgs.empty() ) {
909                // If this is the destructor for a monitor it must be mutex.
910                if ( isDtor ) {
911                        // This reflects MutexKeyword::validate, but no error messages.
912                        const ast::Type * type = decl->type->params.front();
913
914                        // If it's a copy, it's not a mutex.
915                        const ast::ReferenceType * refType = dynamic_cast<const ast::ReferenceType *>( type );
916                        if ( nullptr == refType ) {
917                                return decl;
918                        }
919
920                        // If it is not pointing directly to a type, it's not a mutex.
921                        auto base = refType->base;
922                        if ( base.as<ast::ReferenceType>() ) return decl;
923                        if ( base.as<ast::PointerType>() ) return decl;
924
925                        // If it is not a struct, it's not a mutex.
926                        auto baseStruct = base.as<ast::StructInstType>();
927                        if ( nullptr == baseStruct ) return decl;
928
929                        // If it is a monitor, then it is a monitor.
930                        if( baseStruct->base->is_monitor() || baseStruct->base->is_thread() ) {
931                                SemanticError( decl, "destructors for structures declared as \"monitor\" must use mutex parameters\n" );
932                        }
933                }
934                return decl;
935        }
936
937        // Monitors can't be constructed with mutual exclusion.
938        if ( CodeGen::isConstructor( decl->name ) && is_first_argument_mutex ) {
939                SemanticError( decl, "constructors cannot have mutex parameters\n" );
940        }
941
942        // It makes no sense to have multiple mutex parameters for the destructor.
943        if ( isDtor && mutexArgs.size() != 1 ) {
944                SemanticError( decl, "destructors can only have 1 mutex argument\n" );
945        }
946
947        // Make sure all the mutex arguments are monitors.
948        for ( auto arg : mutexArgs ) {
949                validate( arg );
950        }
951
952        // Check to see if the body needs to be instrument the body.
953        const ast::CompoundStmt * body = decl->stmts;
954        if ( !body ) return decl;
955
956        // Check to if the required headers have been seen.
957        if ( !monitor_decl || !guard_decl || !dtor_guard_decl ) {
958                SemanticError( decl, "mutex keyword requires monitors to be in scope, add #include <monitor.hfa>\n" );
959        }
960
961        // Instrument the body.
962        ast::CompoundStmt * newBody = nullptr;
963        if ( isDtor && isThread( mutexArgs.front() ) ) {
964                if ( !thread_guard_decl ) {
965                        SemanticError( decl, "thread destructor requires threads to be in scope, add #include <thread.hfa>\n" );
966                }
967                newBody = addThreadDtorStatements( decl, body, mutexArgs );
968        } else if ( isDtor ) {
969                newBody = addDtorStatements( decl, body, mutexArgs );
970        } else {
971                newBody = addStatements( decl, body, mutexArgs );
972        }
973        assert( newBody );
974        return ast::mutate_field( decl, &ast::FunctionDecl::stmts, newBody );
975}
976
977void MutexKeyword::postvisit( const ast::StructDecl * decl ) {
978        if ( !decl->body ) {
979                return;
980        } else if ( decl->name == "monitor$" ) {
981                assert( !monitor_decl );
982                monitor_decl = decl;
983        } else if ( decl->name == "monitor_guard_t" ) {
984                assert( !guard_decl );
985                guard_decl = decl;
986        } else if ( decl->name == "monitor_dtor_guard_t" ) {
987                assert( !dtor_guard_decl );
988                dtor_guard_decl = decl;
989        } else if ( decl->name == "thread_dtor_guard_t" ) {
990                assert( !thread_guard_decl );
991                thread_guard_decl = decl;
992        } else if ( decl->name == "__mutex_stmt_lock_guard" ) {
993                assert( !lock_guard_decl );
994                lock_guard_decl = decl;
995        }
996}
997
998const ast::Stmt * MutexKeyword::postvisit( const ast::MutexStmt * stmt ) {
999        ast::CompoundStmt * body =
1000                        new ast::CompoundStmt( stmt->location, { stmt->stmt } );
1001        addStatements( body, stmt->mutexObjs );
1002        return body;
1003}
1004
1005std::vector<const ast::DeclWithType *> MutexKeyword::findMutexArgs(
1006                const ast::FunctionDecl * decl, bool & first ) {
1007        std::vector<const ast::DeclWithType *> mutexArgs;
1008
1009        bool once = true;
1010        for ( auto arg : decl->params ) {
1011                const ast::Type * type = arg->get_type();
1012                if ( type->is_mutex() ) {
1013                        if ( once ) first = true;
1014                        mutexArgs.push_back( arg.get() );
1015                }
1016                once = false;
1017        }
1018        return mutexArgs;
1019}
1020
1021void MutexKeyword::validate( const ast::DeclWithType * decl ) {
1022        const ast::Type * type = decl->get_type();
1023
1024        // If it's a copy, it's not a mutex.
1025        const ast::ReferenceType * refType = dynamic_cast<const ast::ReferenceType *>( type );
1026        if ( nullptr == refType ) {
1027                SemanticError( decl, "Mutex argument must be of reference type " );
1028        }
1029
1030        // If it is not pointing directly to a type, it's not a mutex.
1031        auto base = refType->base;
1032        if ( base.as<ast::ReferenceType>() || base.as<ast::PointerType>() ) {
1033                SemanticError( decl, "Mutex argument have exactly one level of indirection " );
1034        }
1035
1036        // If it is not a struct, it's not a mutex.
1037        auto baseStruct = base.as<ast::StructInstType>();
1038        if ( nullptr == baseStruct ) return;
1039
1040        // Make sure that only the outer reference is mutex.
1041        if( baseStruct->is_mutex() ) {
1042                SemanticError( decl, "mutex keyword may only appear once per argument " );
1043        }
1044}
1045
1046ast::CompoundStmt * MutexKeyword::addDtorStatements(
1047                const ast::FunctionDecl* func, const ast::CompoundStmt * body,
1048                const std::vector<const ast::DeclWithType *> & args ) {
1049        ast::Type * argType = ast::shallowCopy( args.front()->get_type() );
1050        argType->set_mutex( false );
1051
1052        ast::CompoundStmt * mutBody = ast::mutate( body );
1053
1054        // Generated code goes near the beginning of body:
1055        const CodeLocation & location = mutBody->location;
1056
1057        const ast::ObjectDecl * monitor = new ast::ObjectDecl(
1058                location,
1059                "__monitor",
1060                new ast::PointerType( new ast::StructInstType( monitor_decl ) ),
1061                new ast::SingleInit(
1062                        location,
1063                        new ast::UntypedExpr(
1064                                location,
1065                                new ast::NameExpr( location, "get_monitor" ),
1066                                { new ast::CastExpr(
1067                                        location,
1068                                        new ast::VariableExpr( location, args.front() ),
1069                                        argType, ast::ExplicitCast
1070                                ) }
1071                        )
1072                ),
1073                ast::Storage::Classes(),
1074                ast::Linkage::Cforall
1075        );
1076
1077        assert( generic_func );
1078
1079        // In reverse order:
1080        // monitor_dtor_guard_t __guard = { __monitor, func, false };
1081        mutBody->push_front(
1082                new ast::DeclStmt( location, new ast::ObjectDecl(
1083                        location,
1084                        "__guard",
1085                        new ast::StructInstType( dtor_guard_decl ),
1086                        new ast::ListInit(
1087                                location,
1088                                {
1089                                        new ast::SingleInit( location,
1090                                                new ast::AddressExpr( location,
1091                                                        new ast::VariableExpr( location, monitor ) ) ),
1092                                        new ast::SingleInit( location,
1093                                                new ast::CastExpr( location,
1094                                                        new ast::VariableExpr( location, func ),
1095                                                        generic_func,
1096                                                        ast::ExplicitCast ) ),
1097                                        new ast::SingleInit( location,
1098                                                ast::ConstantExpr::from_bool( location, false ) ),
1099                                },
1100                                {},
1101                                ast::MaybeConstruct
1102                        ),
1103                        ast::Storage::Classes(),
1104                        ast::Linkage::Cforall
1105                ))
1106        );
1107
1108        // monitor$ * __monitor = get_monitor(a);
1109        mutBody->push_front( new ast::DeclStmt( location, monitor ) );
1110
1111        return mutBody;
1112}
1113
1114ast::CompoundStmt * MutexKeyword::addStatements(
1115                const ast::FunctionDecl* func, const ast::CompoundStmt * body,
1116                const std::vector<const ast::DeclWithType * > & args ) {
1117        ast::CompoundStmt * mutBody = ast::mutate( body );
1118
1119        // Code is generated near the beginning of the compound statement.
1120        const CodeLocation & location = mutBody->location;
1121
1122        // Make pointer to the monitors.
1123        ast::ObjectDecl * monitors = new ast::ObjectDecl(
1124                location,
1125                "__monitors",
1126                new ast::ArrayType(
1127                        new ast::PointerType(
1128                                new ast::StructInstType( monitor_decl )
1129                        ),
1130                        ast::ConstantExpr::from_ulong( location, args.size() ),
1131                        ast::FixedLen,
1132                        ast::DynamicDim
1133                ),
1134                new ast::ListInit(
1135                        location,
1136                        map_range<std::vector<ast::ptr<ast::Init>>>(
1137                                args,
1138                                []( const ast::DeclWithType * decl ) {
1139                                        return new ast::SingleInit(
1140                                                decl->location,
1141                                                new ast::UntypedExpr(
1142                                                        decl->location,
1143                                                        new ast::NameExpr( decl->location, "get_monitor" ),
1144                                                        {
1145                                                                new ast::CastExpr(
1146                                                                        decl->location,
1147                                                                        new ast::VariableExpr( decl->location, decl ),
1148                                                                        decl->get_type(),
1149                                                                        ast::ExplicitCast
1150                                                                )
1151                                                        }
1152                                                )
1153                                        );
1154                                }
1155                        )
1156                ),
1157                ast::Storage::Classes(),
1158                ast::Linkage::Cforall
1159        );
1160
1161        assert( generic_func );
1162
1163        // In Reverse Order:
1164        mutBody->push_front(
1165                new ast::DeclStmt( location, new ast::ObjectDecl(
1166                        location,
1167                        "__guard",
1168                        new ast::StructInstType( guard_decl ),
1169                        new ast::ListInit(
1170                                location,
1171                                {
1172                                        new ast::SingleInit( location,
1173                                                new ast::VariableExpr( location, monitors ) ),
1174                                        new ast::SingleInit( location,
1175                                                ast::ConstantExpr::from_ulong( location, args.size() ) ),
1176                                        new ast::SingleInit( location, new ast::CastExpr(
1177                                                location,
1178                                                new ast::VariableExpr( location, func ),
1179                                                generic_func,
1180                                                ast::ExplicitCast
1181                                        ) ),
1182                                },
1183                                {},
1184                                ast::MaybeConstruct
1185                        ),
1186                        ast::Storage::Classes(),
1187                        ast::Linkage::Cforall
1188                ))
1189        );
1190
1191        // monitor$ * __monitors[] = { get_monitor(a), get_monitor(b) };
1192        mutBody->push_front( new ast::DeclStmt( location, monitors ) );
1193
1194        return mutBody;
1195}
1196
1197ast::CompoundStmt * MutexKeyword::addStatements(
1198                const ast::CompoundStmt * body,
1199                const std::vector<ast::ptr<ast::Expr>> & args ) {
1200        ast::CompoundStmt * mutBody = ast::mutate( body );
1201
1202        // Code is generated near the beginning of the compound statement.
1203        const CodeLocation & location = mutBody->location;
1204
1205        // Make pointer to the monitors.
1206        ast::ObjectDecl * monitors = new ast::ObjectDecl(
1207                location,
1208                "__monitors",
1209                new ast::ArrayType(
1210                        new ast::PointerType(
1211                                new ast::TypeofType(
1212                                        new ast::UntypedExpr(
1213                                                location,
1214                                                new ast::NameExpr( location, "__get_type" ),
1215                                                { args.front() }
1216                                        )
1217                                )
1218                        ),
1219                        ast::ConstantExpr::from_ulong( location, args.size() ),
1220                        ast::FixedLen,
1221                        ast::DynamicDim
1222                ),
1223                new ast::ListInit(
1224                        location,
1225                        map_range<std::vector<ast::ptr<ast::Init>>>(
1226                                args, [](const ast::Expr * expr) {
1227                                        return new ast::SingleInit(
1228                                                expr->location,
1229                                                new ast::UntypedExpr(
1230                                                        expr->location,
1231                                                        new ast::NameExpr( expr->location, "__get_ptr" ),
1232                                                        { expr }
1233                                                )
1234                                        );
1235                                }
1236                        )
1237                ),
1238                ast::Storage::Classes(),
1239                ast::Linkage::Cforall
1240        );
1241
1242        ast::StructInstType * lock_guard_struct =
1243                        new ast::StructInstType( lock_guard_decl );
1244        ast::TypeExpr * lock_type_expr = new ast::TypeExpr(
1245                location,
1246                new ast::TypeofType(
1247                        new ast::UntypedExpr(
1248                                location,
1249                                new ast::NameExpr( location, "__get_type" ),
1250                                { args.front() }
1251                        )
1252                )
1253        );
1254
1255        lock_guard_struct->params.push_back( lock_type_expr );
1256
1257        // In reverse order:
1258        // monitor_guard_t __guard = { __monitors, # };
1259        mutBody->push_front(
1260                new ast::DeclStmt(
1261                        location,
1262                        new ast::ObjectDecl(
1263                                location,
1264                                "__guard",
1265                                lock_guard_struct,
1266                                new ast::ListInit(
1267                                        location,
1268                                        {
1269                                                new ast::SingleInit(
1270                                                        location,
1271                                                        new ast::VariableExpr( location, monitors ) ),
1272                                                new ast::SingleInit(
1273                                                        location,
1274                                                        ast::ConstantExpr::from_ulong( location, args.size() ) ),
1275                                        },
1276                                        {},
1277                                        ast::MaybeConstruct
1278                                ),
1279                                ast::Storage::Classes(),
1280                                ast::Linkage::Cforall
1281                        )
1282                )
1283        );
1284
1285        // monitor$ * __monitors[] = { get_monitor(a), get_monitor(b) };
1286        mutBody->push_front( new ast::DeclStmt( location, monitors ) );
1287
1288        return mutBody;
1289}
1290
1291ast::CompoundStmt * MutexKeyword::addThreadDtorStatements(
1292                const ast::FunctionDecl*, const ast::CompoundStmt * body,
1293                const std::vector<const ast::DeclWithType * > & args ) {
1294        assert( args.size() == 1 );
1295        const ast::DeclWithType * arg = args.front();
1296        const ast::Type * argType = arg->get_type();
1297        assert( argType->is_mutex() );
1298
1299        ast::CompoundStmt * mutBody = ast::mutate( body );
1300
1301        // The code is generated near the front of the body.
1302        const CodeLocation & location = mutBody->location;
1303
1304        // thread_dtor_guard_t __guard = { this, intptr( 0 ) };
1305        mutBody->push_front( new ast::DeclStmt(
1306                location,
1307                new ast::ObjectDecl(
1308                        location,
1309                        "__guard",
1310                        new ast::StructInstType( thread_guard_decl ),
1311                        new ast::ListInit(
1312                                location,
1313                                {
1314                                        new ast::SingleInit( location,
1315                                                new ast::CastExpr( location,
1316                                                        new ast::VariableExpr( location, arg ), argType ) ),
1317                                        new ast::SingleInit(
1318                                                location,
1319                                                new ast::UntypedExpr(
1320                                                        location,
1321                                                        new ast::NameExpr( location, "intptr" ), {
1322                                                                ast::ConstantExpr::from_int( location, 0 ),
1323                                                        }
1324                                                ) ),
1325                                },
1326                                {},
1327                                ast::MaybeConstruct
1328                        ),
1329                        ast::Storage::Classes(),
1330                        ast::Linkage::Cforall
1331                )
1332        ));
1333
1334        return mutBody;
1335}
1336
1337ast::ptr<ast::Type> MutexKeyword::generic_func =
1338        new ast::FunctionType( ast::VariableArgs );
1339
1340// --------------------------------------------------------------------------
1341struct ThreadStarter final {
1342        void previsit( const ast::StructDecl * decl );
1343        const ast::FunctionDecl * postvisit( const ast::FunctionDecl * decl );
1344
1345private:
1346        bool thread_ctor_seen = false;
1347        const ast::StructDecl * thread_decl = nullptr;
1348};
1349
1350void ThreadStarter::previsit( const ast::StructDecl * decl ) {
1351        if ( decl->body && decl->name == "thread$" ) {
1352                assert( !thread_decl );
1353                thread_decl = decl;
1354        }
1355}
1356
1357const ast::FunctionDecl * ThreadStarter::postvisit( const ast::FunctionDecl * decl ) {
1358        if ( !CodeGen::isConstructor( decl->name ) ) return decl;
1359
1360        // Seach for the thread constructor.
1361        // (Are the "prefixes" of these to blocks the same?)
1362        const ast::Type * typeof_this = InitTweak::getTypeofThis( decl->type );
1363        auto ctored_type = dynamic_cast<const ast::StructInstType *>( typeof_this );
1364        if ( ctored_type && ctored_type->base == thread_decl ) {
1365                thread_ctor_seen = true;
1366        }
1367
1368        // Modify this declaration, the extra checks to see if we will are first.
1369        const ast::ptr<ast::DeclWithType> & param = decl->params.front();
1370        auto type = dynamic_cast<const ast::StructInstType *>(
1371                InitTweak::getPointerBase( param->get_type() ) );
1372        if ( nullptr == type ) return decl;
1373        if ( !type->base->is_thread() ) return decl;
1374        if ( !thread_decl || !thread_ctor_seen ) {
1375                SemanticError( type->base->location, "thread keyword requires threads to be in scope, add #include <thread.hfa>" );
1376        }
1377        const ast::CompoundStmt * stmt = decl->stmts;
1378        if ( nullptr == stmt ) return decl;
1379
1380        // Now do the actual modification:
1381        ast::CompoundStmt * mutStmt = ast::mutate( stmt );
1382        const CodeLocation & location = mutStmt->location;
1383        mutStmt->push_back(
1384                new ast::ExprStmt(
1385                        location,
1386                        new ast::UntypedExpr(
1387                                location,
1388                                new ast::NameExpr( location, "__thrd_start" ),
1389                                {
1390                                        new ast::VariableExpr( location, param ),
1391                                        new ast::NameExpr( location, "main" ),
1392                                }
1393                        )
1394                )
1395        );
1396
1397        return ast::mutate_field( decl, &ast::FunctionDecl::stmts, mutStmt );
1398}
1399
1400} // namespace
1401
1402// --------------------------------------------------------------------------
1403// Interface Functions:
1404
1405void implementKeywords( ast::TranslationUnit & translationUnit ) {
1406        ast::Pass<ThreadKeyword>::run( translationUnit );
1407        ast::Pass<CoroutineKeyword>::run( translationUnit );
1408        ast::Pass<MonitorKeyword>::run( translationUnit );
1409        ast::Pass<GeneratorKeyword>::run( translationUnit );
1410        ast::Pass<SuspendKeyword>::run( translationUnit );
1411}
1412
1413void implementMutex( ast::TranslationUnit & translationUnit ) {
1414        ast::Pass<MutexKeyword>::run( translationUnit );
1415}
1416
1417void implementThreadStarter( ast::TranslationUnit & translationUnit ) {
1418        ast::Pass<ThreadStarter>::run( translationUnit );
1419}
1420
1421}
1422
1423// Local Variables: //
1424// tab-width: 4 //
1425// mode: c++ //
1426// compile-command: "make install" //
1427// End: //
Note: See TracBrowser for help on using the repository browser.