source: src/AST/Pass.impl.hpp @ 13d33a75

ADTarm-ehast-experimentalenumforall-pointer-decayjacob/cs343-translationnew-astnew-ast-unique-exprpthread-emulationqualifiedEnum
Last change on this file since 13d33a75 was 7ff3e522, checked in by Andrew Beach <ajbeach@…>, 4 years ago

{pass_t Pass::pass; => core_t Pass::core;} To avoid confusion about which pass we are talking about.

  • Property mode set to 100644
File size: 56.3 KB
RevLine 
[04124c4]1//
2// Cforall Version 1.0.0 Copyright (C) 2019 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//
[e0016a5]7// ast::Pass.impl.hpp --
[04124c4]8//
9// Author           : Thierry Delisle
10// Created On       : Thu May 09 15::37::05 2019
11// Last Modified By :
12// Last Modified On :
13// Update Count     :
14//
15
[f47f887]16#pragma once
[04124c4]17// IWYU pragma: private, include "AST/Pass.hpp"
[f47f887]18
[6d51bd7]19#include <type_traits>
20#include <unordered_map>
21
[c671112]22#include "AST/TypeSubstitution.hpp"
23
[f47f887]24#define VISIT_START( node ) \
[04124c4]25        using namespace ast; \
[f47f887]26        /* back-up the visit children */ \
[7ff3e522]27        __attribute__((unused)) ast::__pass::visit_children_guard guard1( ast::__pass::visit_children(core, 0) ); \
[f47f887]28        /* setup the scope for passes that want to run code at exit */ \
[7ff3e522]29        __attribute__((unused)) ast::__pass::guard_value          guard2( ast::__pass::at_cleanup    (core, 0) ); \
[c15085d]30        /* begin tracing memory allocation if requested by this pass */ \
[7ff3e522]31        __pass::beginTrace( core, 0 ); \
[f47f887]32        /* call the implementation of the previsit of this pass */ \
[7ff3e522]33        __pass::previsit( core, node, 0 );
[f47f887]34
[6d51bd7]35#define VISIT( code... ) \
[f47f887]36        /* if this node should visit its children */ \
37        if ( __visit_children() ) { \
38                /* visit the children */ \
39                code \
40        }
41
42#define VISIT_END( type, node ) \
43        /* call the implementation of the postvisit of this pass */ \
[7ff3e522]44        auto __return = __pass::postvisit( core, node, 0 ); \
[f47f887]45        assertf(__return, "post visit should never return null"); \
[c15085d]46        /* end tracing memory allocation if requested by this pass */ \
[7ff3e522]47        __pass::endTrace( core, 0 ); \
[f47f887]48        return __return;
49
50#ifdef PEDANTIC_PASS_ASSERT
[6d51bd7]51#define __pedantic_pass_assert(...) assert (__VA_ARGS__)
52#define __pedantic_pass_assertf(...) assertf(__VA_ARGS__)
[f47f887]53#else
[6d51bd7]54#define __pedantic_pass_assert(...)
[f47f887]55#define __pedantic_pass_assertf(...)
56#endif
57
58namespace ast {
59        namespace __pass {
60                // Check if this is either a null pointer or a pointer to an empty container
61                template<typename T>
62                static inline bool empty( T * ptr ) {
63                        return !ptr || ptr->empty();
64                }
65
[6d51bd7]66                //------------------------------
67                template<typename it_t, template <class...> class container_t>
68                static inline void take_all( it_t it, container_t<ast::ptr<ast::Decl>> * decls, bool * mutated = nullptr ) {
[f47f887]69                        if(empty(decls)) return;
70
[6d51bd7]71                        std::transform(decls->begin(), decls->end(), it, [](const ast::Decl * decl) -> auto {
[8a5530c]72                                        return new DeclStmt( decl->location, decl );
[f47f887]73                                });
74                        decls->clear();
75                        if(mutated) *mutated = true;
76                }
77
[6d51bd7]78                template<typename it_t, template <class...> class container_t>
79                static inline void take_all( it_t it, container_t<ast::ptr<ast::Stmt>> * decls, bool * mutated = nullptr ) {
[f47f887]80                        if(empty(decls)) return;
81
82                        std::move(decls->begin(), decls->end(), it);
83                        decls->clear();
84                        if(mutated) *mutated = true;
85                }
86
[6d51bd7]87                //------------------------------
88                /// Check if should be skipped, different for pointers and containers
[f47f887]89                template<typename node_t>
[6d51bd7]90                bool skip( const ast::ptr<node_t> & val) {
91                        return !val;
[f47f887]92                }
93
[6d51bd7]94                template< template <class...> class container_t, typename node_t >
95                bool skip( const container_t<ast::ptr< node_t >> & val ) {
96                        return val.empty();
[f47f887]97                }
98
[6d51bd7]99                //------------------------------
100                /// Get the value to visit, different for pointers and containers
101                template<typename node_t>
102                auto get( const ast::ptr<node_t> & val, int ) -> decltype(val.get()) {
103                        return val.get();
104                }
[f47f887]105
[6d51bd7]106                template<typename node_t>
107                const node_t & get( const node_t & val, long) {
108                        return val;
109                }
[f47f887]110
[6d51bd7]111
112                //------------------------------
113                /// Check if value was mutated, different for pointers and containers
114                template<typename lhs_t, typename rhs_t>
115                bool differs( const lhs_t * old_val, const rhs_t * new_val ) {
116                        return old_val != new_val;
117                }
118
119                template< template <class...> class container_t, typename node_t >
120                bool differs( const container_t<ast::ptr< node_t >> &, const container_t<ast::ptr< node_t >> & new_val ) {
121                        return !new_val.empty();
[f47f887]122                }
123        }
124
[7ff3e522]125        template< typename core_t >
[f47f887]126        template< typename node_t >
[7ff3e522]127        auto ast::Pass< core_t >::call_accept( const node_t * node )
[8a5530c]128                -> typename std::enable_if<
129                                !std::is_base_of<ast::Expr, node_t>::value &&
130                                !std::is_base_of<ast::Stmt, node_t>::value
131                        , decltype( node->accept(*this) )
132                >::type
133        {
[f47f887]134                __pedantic_pass_assert( __visit_children() );
[e0e9a0b]135                __pedantic_pass_assert( node );
[f47f887]136
[6d51bd7]137                static_assert( !std::is_base_of<ast::Expr, node_t>::value, "ERROR");
138                static_assert( !std::is_base_of<ast::Stmt, node_t>::value, "ERROR");
139
[f47f887]140                return node->accept( *this );
141        }
142
[7ff3e522]143        template< typename core_t >
144        const ast::Expr * ast::Pass< core_t >::call_accept( const ast::Expr * expr ) {
[f47f887]145                __pedantic_pass_assert( __visit_children() );
146                __pedantic_pass_assert( expr );
147
[7ff3e522]148                const ast::TypeSubstitution ** env_ptr = __pass::env( core, 0);
[f47f887]149                if ( env_ptr && expr->env ) {
150                        *env_ptr = expr->env;
151                }
152
153                return expr->accept( *this );
154        }
155
[7ff3e522]156        template< typename core_t >
157        const ast::Stmt * ast::Pass< core_t >::call_accept( const ast::Stmt * stmt ) {
[f47f887]158                __pedantic_pass_assert( __visit_children() );
159                __pedantic_pass_assert( stmt );
160
161                // add a few useful symbols to the scope
162                using __pass::empty;
163
164                // get the stmts/decls that will need to be spliced in
[7ff3e522]165                auto stmts_before = __pass::stmtsToAddBefore( core, 0);
166                auto stmts_after  = __pass::stmtsToAddAfter ( core, 0);
167                auto decls_before = __pass::declsToAddBefore( core, 0);
168                auto decls_after  = __pass::declsToAddAfter ( core, 0);
[f47f887]169
170                // These may be modified by subnode but most be restored once we exit this statemnet.
[7ff3e522]171                ValueGuardPtr< const ast::TypeSubstitution * > __old_env         ( __pass::env( core, 0) );
[23f99e1]172                ValueGuardPtr< typename std::remove_pointer< decltype(stmts_before) >::type > __old_decls_before( stmts_before );
173                ValueGuardPtr< typename std::remove_pointer< decltype(stmts_after ) >::type > __old_decls_after ( stmts_after  );
174                ValueGuardPtr< typename std::remove_pointer< decltype(decls_before) >::type > __old_stmts_before( decls_before );
175                ValueGuardPtr< typename std::remove_pointer< decltype(decls_after ) >::type > __old_stmts_after ( decls_after  );
[f47f887]176
177                // Now is the time to actually visit the node
[6d51bd7]178                const ast::Stmt * nstmt = stmt->accept( *this );
[f47f887]179
180                // If the pass doesn't want to add anything then we are done
181                if( empty(stmts_before) && empty(stmts_after) && empty(decls_before) && empty(decls_after) ) {
182                        return nstmt;
183                }
184
185                // Make sure that it is either adding statements or declartions but not both
186                // this is because otherwise the order would be awkward to predict
187                assert(( empty( stmts_before ) && empty( stmts_after ))
188                    || ( empty( decls_before ) && empty( decls_after )) );
189
190                // Create a new Compound Statement to hold the new decls/stmts
[6d51bd7]191                ast::CompoundStmt * compound = new ast::CompoundStmt( stmt->location );
[f47f887]192
193                // Take all the declarations that go before
194                __pass::take_all( std::back_inserter( compound->kids ), decls_before );
195                __pass::take_all( std::back_inserter( compound->kids ), stmts_before );
196
197                // Insert the original declaration
[6d51bd7]198                compound->kids.emplace_back( nstmt );
[f47f887]199
200                // Insert all the declarations that go before
201                __pass::take_all( std::back_inserter( compound->kids ), decls_after );
202                __pass::take_all( std::back_inserter( compound->kids ), stmts_after );
203
204                return compound;
205        }
206
[7ff3e522]207        template< typename core_t >
[6d51bd7]208        template< template <class...> class container_t >
[7ff3e522]209        container_t< ptr<Stmt> > ast::Pass< core_t >::call_accept( const container_t< ptr<Stmt> > & statements ) {
[f47f887]210                __pedantic_pass_assert( __visit_children() );
211                if( statements.empty() ) return {};
212
213                // We are going to aggregate errors for all these statements
214                SemanticErrorException errors;
215
216                // add a few useful symbols to the scope
217                using __pass::empty;
218
219                // get the stmts/decls that will need to be spliced in
[7ff3e522]220                auto stmts_before = __pass::stmtsToAddBefore( core, 0);
221                auto stmts_after  = __pass::stmtsToAddAfter ( core, 0);
222                auto decls_before = __pass::declsToAddBefore( core, 0);
223                auto decls_after  = __pass::declsToAddAfter ( core, 0);
[f47f887]224
225                // These may be modified by subnode but most be restored once we exit this statemnet.
[23f99e1]226                ValueGuardPtr< typename std::remove_pointer< decltype(stmts_before) >::type > __old_decls_before( stmts_before );
227                ValueGuardPtr< typename std::remove_pointer< decltype(stmts_after ) >::type > __old_decls_after ( stmts_after  );
228                ValueGuardPtr< typename std::remove_pointer< decltype(decls_before) >::type > __old_stmts_before( decls_before );
229                ValueGuardPtr< typename std::remove_pointer< decltype(decls_after ) >::type > __old_stmts_after ( decls_after  );
[f47f887]230
231                // update pass statitistics
232                pass_visitor_stats.depth++;
233                pass_visitor_stats.max->push(pass_visitor_stats.depth);
234                pass_visitor_stats.avg->push(pass_visitor_stats.depth);
235
236                bool mutated = false;
[04124c4]237                container_t< ptr<Stmt> > new_kids;
238                for( const Stmt * stmt : statements ) {
[f47f887]239                        try {
240                                __pedantic_pass_assert( stmt );
[6d51bd7]241                                const ast::Stmt * new_stmt = stmt->accept( *this );
[f47f887]242                                assert( new_stmt );
243                                if(new_stmt != stmt ) mutated = true;
244
245                                // Make sure that it is either adding statements or declartions but not both
246                                // this is because otherwise the order would be awkward to predict
247                                assert(( empty( stmts_before ) && empty( stmts_after ))
248                                    || ( empty( decls_before ) && empty( decls_after )) );
249
250
251
252                                // Take all the statements which should have gone after, N/A for first iteration
253                                __pass::take_all( std::back_inserter( new_kids ), decls_before, &mutated );
254                                __pass::take_all( std::back_inserter( new_kids ), stmts_before, &mutated );
255
256                                // Now add the statement if there is one
257                                new_kids.emplace_back( new_stmt );
258
259                                // Take all the declarations that go before
260                                __pass::take_all( std::back_inserter( new_kids ), decls_after, &mutated );
261                                __pass::take_all( std::back_inserter( new_kids ), stmts_after, &mutated );
262                        }
263                        catch ( SemanticErrorException &e ) {
264                                errors.append( e );
265                        }
266                }
267                pass_visitor_stats.depth--;
268                if ( !errors.isEmpty() ) { throw errors; }
269
[6d51bd7]270                return mutated ? new_kids : container_t< ptr<Stmt> >();
[f47f887]271        }
272
[7ff3e522]273        template< typename core_t >
[6d51bd7]274        template< template <class...> class container_t, typename node_t >
[7ff3e522]275        container_t< ast::ptr<node_t> > ast::Pass< core_t >::call_accept( const container_t< ast::ptr<node_t> > & container ) {
[f47f887]276                __pedantic_pass_assert( __visit_children() );
277                if( container.empty() ) return {};
278                SemanticErrorException errors;
279
280                pass_visitor_stats.depth++;
281                pass_visitor_stats.max->push(pass_visitor_stats.depth);
282                pass_visitor_stats.avg->push(pass_visitor_stats.depth);
283
284                bool mutated = false;
285                container_t< ast::ptr<node_t> > new_kids;
286                for ( const node_t * node : container ) {
287                        try {
288                                __pedantic_pass_assert( node );
[6d51bd7]289                                const node_t * new_stmt = strict_dynamic_cast< const node_t * >( node->accept( *this ) );
290                                if(new_stmt != node ) mutated = true;
[f47f887]291
292                                new_kids.emplace_back( new_stmt );
293                        }
294                        catch( SemanticErrorException &e ) {
295                                errors.append( e );
296                        }
297                }
298                pass_visitor_stats.depth--;
299                if ( ! errors.isEmpty() ) { throw errors; }
300
[6d51bd7]301                return mutated ? new_kids : container_t< ast::ptr<node_t> >();
302        }
303
[7ff3e522]304        template< typename core_t >
[6d51bd7]305        template<typename node_t, typename parent_t, typename child_t>
[7ff3e522]306        void ast::Pass< core_t >::maybe_accept(
[6d51bd7]307                const node_t * & parent,
308                child_t parent_t::*child
309        ) {
[8a5530c]310                static_assert( std::is_base_of<parent_t, node_t>::value, "Error deducing member object" );
[6d51bd7]311
312                if(__pass::skip(parent->*child)) return;
313                const auto & old_val = __pass::get(parent->*child, 0);
314
315                static_assert( !std::is_same<const ast::Node * &, decltype(old_val)>::value, "ERROR");
316
317                auto new_val = call_accept( old_val );
318
319                static_assert( !std::is_same<const ast::Node *, decltype(new_val)>::value || std::is_same<int, decltype(old_val)>::value, "ERROR");
320
321                if( __pass::differs(old_val, new_val) ) {
322                        auto new_parent = mutate(parent);
323                        new_parent->*child = new_val;
324                        parent = new_parent;
325                }
[f47f887]326        }
[6d51bd7]327
[e0e9a0b]328
[7ff3e522]329        template< typename core_t >
[e0e9a0b]330        template< typename node_t >
[7ff3e522]331        void ast::Pass< core_t >::mutate_forall( const node_t *& node ) {
332                if ( auto subs = __pass::forall::subs( core, 0 ) ) {
[e0e9a0b]333                        // tracking TypeDecl substitution, full clone
334                        if ( node->forall.empty() ) return;
335
336                        node_t * mut = mutate( node );
337                        mut->forall = subs->clone( node->forall, *this );
338                        node = mut;
339                } else {
340                        // not tracking TypeDecl substitution, just mutate
341                        maybe_accept( node, &node_t::forall );
342                }
343        }
[f47f887]344}
345
346//------------------------------------------------------------------------------------------------------------------------------------------------------------------------
347//========================================================================================================================================================================
348//========================================================================================================================================================================
349//========================================================================================================================================================================
350//========================================================================================================================================================================
351//========================================================================================================================================================================
352//------------------------------------------------------------------------------------------------------------------------------------------------------------------------
353
[7ff3e522]354template< typename core_t >
355inline void ast::accept_all( std::list< ast::ptr<ast::Decl> > & decls, ast::Pass< core_t > & visitor ) {
[04124c4]356        // We are going to aggregate errors for all these statements
357        SemanticErrorException errors;
358
359        // add a few useful symbols to the scope
360        using __pass::empty;
361
362        // get the stmts/decls that will need to be spliced in
[7ff3e522]363        auto decls_before = __pass::declsToAddBefore( visitor.core, 0);
364        auto decls_after  = __pass::declsToAddAfter ( visitor.core, 0);
[04124c4]365
366        // update pass statitistics
367        pass_visitor_stats.depth++;
368        pass_visitor_stats.max->push(pass_visitor_stats.depth);
369        pass_visitor_stats.avg->push(pass_visitor_stats.depth);
370
371        for ( std::list< ast::ptr<ast::Decl> >::iterator i = decls.begin(); ; ++i ) {
372                // splice in new declarations after previous decl
373                if ( !empty( decls_after ) ) { decls.splice( i, *decls_after ); }
374
375                if ( i == decls.end() ) break;
376
377                try {
378                        // run visitor on declaration
379                        ast::ptr<ast::Decl> & node = *i;
380                        assert( node );
381                        node = node->accept( visitor );
382                }
383                catch( SemanticErrorException &e ) {
384                        errors.append( e );
385                }
386
387                // splice in new declarations before current decl
388                if ( !empty( decls_before ) ) { decls.splice( i, *decls_before ); }
389        }
390        pass_visitor_stats.depth--;
391        if ( !errors.isEmpty() ) { throw errors; }
392}
393
[f47f887]394// A NOTE ON THE ORDER OF TRAVERSAL
395//
396// Types and typedefs have their base types visited before they are added to the type table.  This is ok, since there is
397// no such thing as a recursive type or typedef.
398//
399//             typedef struct { T *x; } T; // never allowed
400//
401// for structs/unions, it is possible to have recursion, so the decl should be added as if it's incomplete to begin, the
402// members are traversed, and then the complete type should be added (assuming the type is completed by this particular
403// declaration).
404//
405//             struct T { struct T *x; }; // allowed
406//
407// It is important to add the complete type to the symbol table *after* the members/base has been traversed, since that
408// traversal may modify the definition of the type and these modifications should be visible when the symbol table is
409// queried later in this pass.
410
411//--------------------------------------------------------------------------
412// ObjectDecl
[7ff3e522]413template< typename core_t >
414const ast::DeclWithType * ast::Pass< core_t >::visit( const ast::ObjectDecl * node ) {
[f47f887]415        VISIT_START( node );
416
417        VISIT(
418                {
[0e42794]419                        guard_symtab guard { *this };
[23f99e1]420                        maybe_accept( node, &ObjectDecl::type );
[f47f887]421                }
[23f99e1]422                maybe_accept( node, &ObjectDecl::init          );
423                maybe_accept( node, &ObjectDecl::bitfieldWidth );
424                maybe_accept( node, &ObjectDecl::attributes    );
[f47f887]425        )
426
[7ff3e522]427        __pass::symtab::addId( core, 0, node );
[f47f887]428
[04124c4]429        VISIT_END( DeclWithType, node );
[f47f887]430}
431
[23f99e1]432//--------------------------------------------------------------------------
433// FunctionDecl
[7ff3e522]434template< typename core_t >
435const ast::DeclWithType * ast::Pass< core_t >::visit( const ast::FunctionDecl * node ) {
[23f99e1]436        VISIT_START( node );
437
[7ff3e522]438        __pass::symtab::addId( core, 0, node );
[23f99e1]439
440        VISIT(maybe_accept( node, &FunctionDecl::withExprs );)
441        {
442                // with clause introduces a level of scope (for the with expression members).
[0e42794]443                // with clause exprs are added to the symbol table before parameters so that parameters
[23f99e1]444                // shadow with exprs and not the other way around.
[0e42794]445                guard_symtab guard { *this };
[7ff3e522]446                __pass::symtab::addWith( core, 0, node->withExprs, node );
[23f99e1]447                {
[0e42794]448                        guard_symtab guard { *this };
[23f99e1]449                        // implicit add __func__ identifier as specified in the C manual 6.4.2.2
[9ea38de]450                        static ast::ptr< ast::ObjectDecl > func{ new ast::ObjectDecl{ 
451                                CodeLocation{}, "__func__",
452                                new ast::ArrayType{
453                                        new ast::BasicType{ ast::BasicType::Char, ast::CV::Const },
[8a5530c]454                                        nullptr, VariableLen, DynamicDim
[9ea38de]455                                }
456                        } };
[7ff3e522]457                        __pass::symtab::addId( core, 0, func );
[23f99e1]458                        VISIT(
459                                maybe_accept( node, &FunctionDecl::type );
460                                // function body needs to have the same scope as parameters - CompoundStmt will not enter
461                                // a new scope if inFunction is true
462                                ValueGuard< bool > oldInFunction( inFunction );
463                                inFunction = true;
[8a5530c]464                                maybe_accept( node, &FunctionDecl::stmts );
[23f99e1]465                                maybe_accept( node, &FunctionDecl::attributes );
466                        )
467                }
468        }
469
470        VISIT_END( DeclWithType, node );
471}
472
473//--------------------------------------------------------------------------
474// StructDecl
[7ff3e522]475template< typename core_t >
476const ast::Decl * ast::Pass< core_t >::visit( const ast::StructDecl * node ) {
[23f99e1]477        VISIT_START( node );
478
479        // make up a forward declaration and add it before processing the members
480        // needs to be on the heap because addStruct saves the pointer
[7ff3e522]481        __pass::symtab::addStructFwd( core, 0, node );
[23f99e1]482
483        VISIT({
[0e42794]484                guard_symtab guard { * this };
[87701b6]485                maybe_accept( node, &StructDecl::params  );
486                maybe_accept( node, &StructDecl::members );
[23f99e1]487        })
488
489        // this addition replaces the forward declaration
[7ff3e522]490        __pass::symtab::addStruct( core, 0, node );
[23f99e1]491
492        VISIT_END( Decl, node );
493}
494
495//--------------------------------------------------------------------------
496// UnionDecl
[7ff3e522]497template< typename core_t >
498const ast::Decl * ast::Pass< core_t >::visit( const ast::UnionDecl * node ) {
[23f99e1]499        VISIT_START( node );
500
501        // make up a forward declaration and add it before processing the members
[7ff3e522]502        __pass::symtab::addUnionFwd( core, 0, node );
[23f99e1]503
504        VISIT({
[0e42794]505                guard_symtab guard { * this };
[87701b6]506                maybe_accept( node, &UnionDecl::params  );
507                maybe_accept( node, &UnionDecl::members );
[23f99e1]508        })
509
[7ff3e522]510        __pass::symtab::addUnion( core, 0, node );
[23f99e1]511
512        VISIT_END( Decl, node );
513}
514
515//--------------------------------------------------------------------------
516// EnumDecl
[7ff3e522]517template< typename core_t >
518const ast::Decl * ast::Pass< core_t >::visit( const ast::EnumDecl * node ) {
[23f99e1]519        VISIT_START( node );
520
[7ff3e522]521        __pass::symtab::addEnum( core, 0, node );
[23f99e1]522
523        VISIT(
524                // unlike structs, traits, and unions, enums inject their members into the global scope
[87701b6]525                maybe_accept( node, &EnumDecl::params  );
526                maybe_accept( node, &EnumDecl::members );
[23f99e1]527        )
528
529        VISIT_END( Decl, node );
530}
531
532//--------------------------------------------------------------------------
533// TraitDecl
[7ff3e522]534template< typename core_t >
535const ast::Decl * ast::Pass< core_t >::visit( const ast::TraitDecl * node ) {
[23f99e1]536        VISIT_START( node );
537
538        VISIT({
[0e42794]539                guard_symtab guard { *this };
[87701b6]540                maybe_accept( node, &TraitDecl::params  );
541                maybe_accept( node, &TraitDecl::members );
[23f99e1]542        })
543
[7ff3e522]544        __pass::symtab::addTrait( core, 0, node );
[23f99e1]545
546        VISIT_END( Decl, node );
547}
548
549//--------------------------------------------------------------------------
550// TypeDecl
[7ff3e522]551template< typename core_t >
552const ast::Decl * ast::Pass< core_t >::visit( const ast::TypeDecl * node ) {
[23f99e1]553        VISIT_START( node );
554
555        VISIT({
[0e42794]556                guard_symtab guard { *this };
[87701b6]557                maybe_accept( node, &TypeDecl::params );
558                maybe_accept( node, &TypeDecl::base   );
[23f99e1]559        })
560
561        // see A NOTE ON THE ORDER OF TRAVERSAL, above
562        // note that assertions come after the type is added to the symtab, since they are not part of the type proper
563        // and may depend on the type itself
[7ff3e522]564        __pass::symtab::addType( core, 0, node );
[23f99e1]565
566        VISIT(
[8a5530c]567                maybe_accept( node, &TypeDecl::assertions );
[23f99e1]568
569                {
[0e42794]570                        guard_symtab guard { *this };
[23f99e1]571                        maybe_accept( node, &TypeDecl::init );
572                }
573        )
574
575        VISIT_END( Decl, node );
576}
577
578//--------------------------------------------------------------------------
579// TypedefDecl
[7ff3e522]580template< typename core_t >
581const ast::Decl * ast::Pass< core_t >::visit( const ast::TypedefDecl * node ) {
[23f99e1]582        VISIT_START( node );
583
584        VISIT({
[0e42794]585                guard_symtab guard { *this };
[87701b6]586                maybe_accept( node, &TypedefDecl::params );
587                maybe_accept( node, &TypedefDecl::base   );
[23f99e1]588        })
589
[7ff3e522]590        __pass::symtab::addType( core, 0, node );
[23f99e1]591
[17a0228a]592        VISIT( maybe_accept( node, &TypedefDecl::assertions ); )
[23f99e1]593
594        VISIT_END( Decl, node );
595}
596
597//--------------------------------------------------------------------------
598// AsmDecl
[7ff3e522]599template< typename core_t >
600const ast::AsmDecl * ast::Pass< core_t >::visit( const ast::AsmDecl * node ) {
[23f99e1]601        VISIT_START( node );
602
603        VISIT(
604                maybe_accept( node, &AsmDecl::stmt );
605        )
606
607        VISIT_END( AsmDecl, node );
608}
609
610//--------------------------------------------------------------------------
611// StaticAssertDecl
[7ff3e522]612template< typename core_t >
613const ast::StaticAssertDecl * ast::Pass< core_t >::visit( const ast::StaticAssertDecl * node ) {
[23f99e1]614        VISIT_START( node );
615
616        VISIT(
[112fe04]617                maybe_accept( node, &StaticAssertDecl::cond );
618                maybe_accept( node, &StaticAssertDecl::msg  );
[23f99e1]619        )
620
621        VISIT_END( StaticAssertDecl, node );
622}
623
624//--------------------------------------------------------------------------
625// CompoundStmt
[7ff3e522]626template< typename core_t >
627const ast::CompoundStmt * ast::Pass< core_t >::visit( const ast::CompoundStmt * node ) {
[23f99e1]628        VISIT_START( node );
629        VISIT({
630                // do not enter a new scope if inFunction is true - needs to check old state before the assignment
[9ea38de]631                auto guard1 = makeFuncGuard( [this, inFunctionCpy = this->inFunction]() {
[7ff3e522]632                        if ( ! inFunctionCpy ) __pass::symtab::enter(core, 0);
[9ea38de]633                }, [this, inFunctionCpy = this->inFunction]() {
[7ff3e522]634                        if ( ! inFunctionCpy ) __pass::symtab::leave(core, 0);
[23f99e1]635                });
636                ValueGuard< bool > guard2( inFunction );
637                guard_scope guard3 { *this };
638                inFunction = false;
639                maybe_accept( node, &CompoundStmt::kids );
640        })
641        VISIT_END( CompoundStmt, node );
642}
643
[8a5530c]644//--------------------------------------------------------------------------
645// ExprStmt
[7ff3e522]646template< typename core_t >
647const ast::Stmt * ast::Pass< core_t >::visit( const ast::ExprStmt * node ) {
[8a5530c]648        VISIT_START( node );
649
650        VISIT(
651                maybe_accept( node, &ExprStmt::expr );
652        )
653
654        VISIT_END( Stmt, node );
655}
656
657//--------------------------------------------------------------------------
658// AsmStmt
[7ff3e522]659template< typename core_t >
660const ast::Stmt * ast::Pass< core_t >::visit( const ast::AsmStmt * node ) {
[8a5530c]661        VISIT_START( node )
662
663        VISIT(
664                maybe_accept( node, &AsmStmt::instruction );
665                maybe_accept( node, &AsmStmt::output      );
666                maybe_accept( node, &AsmStmt::input       );
667                maybe_accept( node, &AsmStmt::clobber     );
668        )
669
670        VISIT_END( Stmt, node );
671}
672
673//--------------------------------------------------------------------------
674// DirectiveStmt
[7ff3e522]675template< typename core_t >
676const ast::Stmt * ast::Pass< core_t >::visit( const ast::DirectiveStmt * node ) {
[8a5530c]677        VISIT_START( node )
678
679        VISIT_END( Stmt, node );
680}
681
682//--------------------------------------------------------------------------
683// IfStmt
[7ff3e522]684template< typename core_t >
685const ast::Stmt * ast::Pass< core_t >::visit( const ast::IfStmt * node ) {
[8a5530c]686        VISIT_START( node );
[17a0228a]687
[8a5530c]688        VISIT({
689                // if statements introduce a level of scope (for the initialization)
[0e42794]690                guard_symtab guard { *this };
[8a5530c]691                maybe_accept( node, &IfStmt::inits    );
692                maybe_accept( node, &IfStmt::cond     );
693                maybe_accept( node, &IfStmt::thenPart );
694                maybe_accept( node, &IfStmt::elsePart );
695        })
[17a0228a]696
[8a5530c]697        VISIT_END( Stmt, node );
698}
699
700//--------------------------------------------------------------------------
701// WhileStmt
[7ff3e522]702template< typename core_t >
703const ast::Stmt * ast::Pass< core_t >::visit( const ast::WhileStmt * node ) {
[8a5530c]704        VISIT_START( node );
705
706        VISIT({
707                // while statements introduce a level of scope (for the initialization)
[0e42794]708                guard_symtab guard { *this };
[8a5530c]709                maybe_accept( node, &WhileStmt::inits );
710                maybe_accept( node, &WhileStmt::cond  );
711                maybe_accept( node, &WhileStmt::body  );
712        })
713
714        VISIT_END( Stmt, node );
715}
[23f99e1]716
[87701b6]717//--------------------------------------------------------------------------
718// ForStmt
[7ff3e522]719template< typename core_t >
720const ast::Stmt * ast::Pass< core_t >::visit( const ast::ForStmt * node ) {
[87701b6]721        VISIT_START( node );
722
723        VISIT({
724                // for statements introduce a level of scope (for the initialization)
[0e42794]725                guard_symtab guard { *this };
[87701b6]726                maybe_accept( node, &ForStmt::inits );
727                maybe_accept( node, &ForStmt::cond  );
728                maybe_accept( node, &ForStmt::inc   );
729                maybe_accept( node, &ForStmt::body  );
730        })
731
732        VISIT_END( Stmt, node );
733}
734
735//--------------------------------------------------------------------------
736// SwitchStmt
[7ff3e522]737template< typename core_t >
738const ast::Stmt * ast::Pass< core_t >::visit( const ast::SwitchStmt * node ) {
[87701b6]739        VISIT_START( node );
740
741        VISIT(
742                maybe_accept( node, &SwitchStmt::cond  );
743                maybe_accept( node, &SwitchStmt::stmts );
744        )
745
746        VISIT_END( Stmt, node );
747}
748
749//--------------------------------------------------------------------------
750// CaseStmt
[7ff3e522]751template< typename core_t >
752const ast::Stmt * ast::Pass< core_t >::visit( const ast::CaseStmt * node ) {
[87701b6]753        VISIT_START( node );
754
755        VISIT(
756                maybe_accept( node, &CaseStmt::cond  );
757                maybe_accept( node, &CaseStmt::stmts );
758        )
759
760        VISIT_END( Stmt, node );
761}
762
763//--------------------------------------------------------------------------
764// BranchStmt
[7ff3e522]765template< typename core_t >
766const ast::Stmt * ast::Pass< core_t >::visit( const ast::BranchStmt * node ) {
[87701b6]767        VISIT_START( node );
768        VISIT_END( Stmt, node );
769}
770
771//--------------------------------------------------------------------------
772// ReturnStmt
[7ff3e522]773template< typename core_t >
774const ast::Stmt * ast::Pass< core_t >::visit( const ast::ReturnStmt * node ) {
[87701b6]775        VISIT_START( node );
776
[e61207e7]777        VISIT(
778                maybe_accept( node, &ReturnStmt::expr );
779        )
[87701b6]780
781        VISIT_END( Stmt, node );
782}
783
784//--------------------------------------------------------------------------
785// ThrowStmt
[7ff3e522]786template< typename core_t >
787const ast::Stmt * ast::Pass< core_t >::visit( const ast::ThrowStmt * node ) {
[e61207e7]788        VISIT_START( node );
[87701b6]789
[e61207e7]790        VISIT(
791                maybe_accept( node, &ThrowStmt::expr   );
792                maybe_accept( node, &ThrowStmt::target );
793        )
794
795        VISIT_END( Stmt, node );
796}
797
798//--------------------------------------------------------------------------
799// TryStmt
[7ff3e522]800template< typename core_t >
801const ast::Stmt * ast::Pass< core_t >::visit( const ast::TryStmt * node ) {
[87701b6]802        VISIT_START( node );
803
[e61207e7]804        VISIT(
[acd80b4]805                maybe_accept( node, &TryStmt::body     );
806                maybe_accept( node, &TryStmt::handlers );
807                maybe_accept( node, &TryStmt::finally  );
[e61207e7]808        )
[87701b6]809
[e61207e7]810        VISIT_END( Stmt, node );
[87701b6]811}
812
[10a1225]813//--------------------------------------------------------------------------
814// CatchStmt
[7ff3e522]815template< typename core_t >
816const ast::Stmt * ast::Pass< core_t >::visit( const ast::CatchStmt * node ) {
[10a1225]817        VISIT_START( node );
818
819        VISIT({
820                // catch statements introduce a level of scope (for the caught exception)
[0e42794]821                guard_symtab guard { *this };
[10a1225]822                maybe_accept( node, &CatchStmt::decl );
823                maybe_accept( node, &CatchStmt::cond );
824                maybe_accept( node, &CatchStmt::body );
825        })
826
827        VISIT_END( Stmt, node );
828}
829
830//--------------------------------------------------------------------------
831// FinallyStmt
[7ff3e522]832template< typename core_t >
833const ast::Stmt * ast::Pass< core_t >::visit( const ast::FinallyStmt * node ) {
[10a1225]834        VISIT_START( node );
835
836        VISIT(
837                maybe_accept( node, &FinallyStmt::body );
838        )
839
840        VISIT_END( Stmt, node );
841}
842
[37cdd97]843//--------------------------------------------------------------------------
844// FinallyStmt
[7ff3e522]845template< typename core_t >
846const ast::Stmt * ast::Pass< core_t >::visit( const ast::SuspendStmt * node ) {
[37cdd97]847        VISIT_START( node );
848
849        VISIT(
850                maybe_accept( node, &SuspendStmt::then   );
851        )
852
853        VISIT_END( Stmt, node );
854}
855
[10a1225]856//--------------------------------------------------------------------------
857// WaitForStmt
[7ff3e522]858template< typename core_t >
859const ast::Stmt * ast::Pass< core_t >::visit( const ast::WaitForStmt * node ) {
[10a1225]860        VISIT_START( node );
861                // for( auto & clause : node->clauses ) {
862                //      maybeAccept_impl( clause.target.function, *this );
863                //      maybeAccept_impl( clause.target.arguments, *this );
864
865                //      maybeAccept_impl( clause.statement, *this );
866                //      maybeAccept_impl( clause.condition, *this );
867                // }
868
[e0016a5]869        VISIT({
870                std::vector<WaitForStmt::Clause> new_clauses;
871                new_clauses.reserve( node->clauses.size() );
872                bool mutated = false;
873                for( const auto & clause : node->clauses ) {
874
[b0abc8a0]875                        const Expr * func = clause.target.func ? clause.target.func->accept(*this) : nullptr;
[e0016a5]876                        if(func != clause.target.func) mutated = true;
877
878                        std::vector<ptr<Expr>> new_args;
879                        new_args.reserve(clause.target.args.size());
880                        for( const auto & arg : clause.target.args ) {
881                                auto a = arg->accept(*this);
882                                new_args.push_back( a );
883                                if( a != arg ) mutated = true;
884                        }
885
[b0abc8a0]886                        const Stmt * stmt = clause.stmt ? clause.stmt->accept(*this) : nullptr;
[e0016a5]887                        if(stmt != clause.stmt) mutated = true;
888
[b0abc8a0]889                        const Expr * cond = clause.cond ? clause.cond->accept(*this) : nullptr;
[e0016a5]890                        if(cond != clause.cond) mutated = true;
891
892                        new_clauses.push_back( WaitForStmt::Clause{ {func, std::move(new_args) }, stmt, cond } );
893                }
894
895                if(mutated) {
896                        auto n = mutate(node);
897                        n->clauses = std::move( new_clauses );
898                        node = n;
899                }
900        })
901
[10a1225]902        #define maybe_accept(field) \
903                if(node->field) { \
904                        auto nval = call_accept( node->field ); \
905                        if(nval != node->field ) { \
906                                auto nparent = mutate(node); \
907                                nparent->field = nval; \
908                                node = nparent; \
909                        } \
910                }
911
912        VISIT(
913                maybe_accept( timeout.time );
914                maybe_accept( timeout.stmt );
915                maybe_accept( timeout.cond );
916                maybe_accept( orElse.stmt  );
917                maybe_accept( orElse.cond  );
918        )
919
920        #undef maybe_accept
921
922        VISIT_END( Stmt, node );
923}
924
925//--------------------------------------------------------------------------
926// WithStmt
[7ff3e522]927template< typename core_t >
928const ast::Decl * ast::Pass< core_t >::visit( const ast::WithStmt * node ) {
[10a1225]929        VISIT_START( node );
930
931        VISIT(
932                maybe_accept( node, &WithStmt::exprs );
933                {
934                        // catch statements introduce a level of scope (for the caught exception)
[0e42794]935                        guard_symtab guard { *this };
[7ff3e522]936                        __pass::symtab::addWith( core, 0, node->exprs, node );
[10a1225]937                        maybe_accept( node, &WithStmt::stmt );
938                }
939        )
940        VISIT_END( Stmt, node );
941}
942
943//--------------------------------------------------------------------------
944// NullStmt
[7ff3e522]945template< typename core_t >
946const ast::NullStmt * ast::Pass< core_t >::visit( const ast::NullStmt * node ) {
[10a1225]947        VISIT_START( node );
948        VISIT_END( NullStmt, node );
949}
950
951//--------------------------------------------------------------------------
952// DeclStmt
[7ff3e522]953template< typename core_t >
954const ast::Stmt * ast::Pass< core_t >::visit( const ast::DeclStmt * node ) {
[10a1225]955        VISIT_START( node );
956
957        VISIT(
958                maybe_accept( node, &DeclStmt::decl );
959        )
960
961        VISIT_END( Stmt, node );
962}
963
964//--------------------------------------------------------------------------
965// ImplicitCtorDtorStmt
[7ff3e522]966template< typename core_t >
967const ast::Stmt * ast::Pass< core_t >::visit( const ast::ImplicitCtorDtorStmt * node ) {
[10a1225]968        VISIT_START( node );
969
970        // For now this isn't visited, it is unclear if this causes problem
971        // if all tests are known to pass, remove this code
[c570806]972        VISIT(
973                maybe_accept( node, &ImplicitCtorDtorStmt::callStmt );
974        )
[10a1225]975
976        VISIT_END( Stmt, node );
977}
978
[17a0228a]979//--------------------------------------------------------------------------
980// ApplicationExpr
[7ff3e522]981template< typename core_t >
982const ast::Expr * ast::Pass< core_t >::visit( const ast::ApplicationExpr * node ) {
[17a0228a]983        VISIT_START( node );
984
985        VISIT(
986                {
[0e42794]987                        guard_symtab guard { *this };
[17a0228a]988                        maybe_accept( node, &ApplicationExpr::result );
989                }
990                maybe_accept( node, &ApplicationExpr::func );
991                maybe_accept( node, &ApplicationExpr::args );
992        )
993
994        VISIT_END( Expr, node );
995}
996
997//--------------------------------------------------------------------------
998// UntypedExpr
[7ff3e522]999template< typename core_t >
1000const ast::Expr * ast::Pass< core_t >::visit( const ast::UntypedExpr * node ) {
[17a0228a]1001        VISIT_START( node );
1002
1003        VISIT(
1004                {
[0e42794]1005                        guard_symtab guard { *this };
[17a0228a]1006                        maybe_accept( node, &UntypedExpr::result );
1007                }
1008
1009                maybe_accept( node, &UntypedExpr::args );
1010        )
1011
1012        VISIT_END( Expr, node );
1013}
1014
1015//--------------------------------------------------------------------------
1016// NameExpr
[7ff3e522]1017template< typename core_t >
1018const ast::Expr * ast::Pass< core_t >::visit( const ast::NameExpr * node ) {
[17a0228a]1019        VISIT_START( node );
1020
1021        VISIT({
[0e42794]1022                guard_symtab guard { *this };
[17a0228a]1023                maybe_accept( node, &NameExpr::result );
1024        })
1025
1026        VISIT_END( Expr, node );
1027}
1028
1029//--------------------------------------------------------------------------
1030// CastExpr
[7ff3e522]1031template< typename core_t >
1032const ast::Expr * ast::Pass< core_t >::visit( const ast::CastExpr * node ) {
[17a0228a]1033        VISIT_START( node );
1034
1035        VISIT({
[0e42794]1036                        guard_symtab guard { *this };
[17a0228a]1037                        maybe_accept( node, &CastExpr::result );
1038                }
1039                maybe_accept( node, &CastExpr::arg );
1040        )
1041
1042        VISIT_END( Expr, node );
1043}
1044
1045//--------------------------------------------------------------------------
1046// KeywordCastExpr
[7ff3e522]1047template< typename core_t >
1048const ast::Expr * ast::Pass< core_t >::visit( const ast::KeywordCastExpr * node ) {
[17a0228a]1049        VISIT_START( node );
1050
1051        VISIT({
[0e42794]1052                        guard_symtab guard { *this };
[17a0228a]1053                        maybe_accept( node, &KeywordCastExpr::result );
1054                }
1055                maybe_accept( node, &KeywordCastExpr::arg );
1056        )
1057
1058        VISIT_END( Expr, node );
1059}
1060
1061//--------------------------------------------------------------------------
1062// VirtualCastExpr
[7ff3e522]1063template< typename core_t >
1064const ast::Expr * ast::Pass< core_t >::visit( const ast::VirtualCastExpr * node ) {
[17a0228a]1065        VISIT_START( node );
1066
1067        VISIT({
[0e42794]1068                        guard_symtab guard { *this };
[17a0228a]1069                        maybe_accept( node, &VirtualCastExpr::result );
1070                }
1071                maybe_accept( node, &VirtualCastExpr::arg );
1072        )
1073
1074        VISIT_END( Expr, node );
1075}
1076
1077//--------------------------------------------------------------------------
1078// AddressExpr
[7ff3e522]1079template< typename core_t >
1080const ast::Expr * ast::Pass< core_t >::visit( const ast::AddressExpr * node ) {
[17a0228a]1081        VISIT_START( node );
1082
1083        VISIT({
[0e42794]1084                        guard_symtab guard { *this };
[17a0228a]1085                        maybe_accept( node, &AddressExpr::result );
1086                }
1087                maybe_accept( node, &AddressExpr::arg );
1088        )
1089
1090        VISIT_END( Expr, node );
1091}
1092
1093//--------------------------------------------------------------------------
1094// LabelAddressExpr
[7ff3e522]1095template< typename core_t >
1096const ast::Expr * ast::Pass< core_t >::visit( const ast::LabelAddressExpr * node ) {
[17a0228a]1097        VISIT_START( node );
1098
1099        VISIT({
[0e42794]1100                guard_symtab guard { *this };
[17a0228a]1101                maybe_accept( node, &LabelAddressExpr::result );
1102        })
1103
1104        VISIT_END( Expr, node );
1105}
1106
1107//--------------------------------------------------------------------------
1108// UntypedMemberExpr
[7ff3e522]1109template< typename core_t >
1110const ast::Expr * ast::Pass< core_t >::visit( const ast::UntypedMemberExpr * node ) {
[17a0228a]1111        VISIT_START( node );
1112
1113        VISIT({
[0e42794]1114                        guard_symtab guard { *this };
[17a0228a]1115                        maybe_accept( node, &UntypedMemberExpr::result );
1116                }
1117                maybe_accept( node, &UntypedMemberExpr::aggregate );
1118                maybe_accept( node, &UntypedMemberExpr::member    );
1119        )
1120
1121        VISIT_END( Expr, node );
1122}
1123
1124//--------------------------------------------------------------------------
1125// MemberExpr
[7ff3e522]1126template< typename core_t >
1127const ast::Expr * ast::Pass< core_t >::visit( const ast::MemberExpr * node ) {
[17a0228a]1128        VISIT_START( node );
1129
1130        VISIT({
[0e42794]1131                        guard_symtab guard { *this };
[17a0228a]1132                        maybe_accept( node, &MemberExpr::result );
1133                }
1134                maybe_accept( node, &MemberExpr::aggregate );
1135        )
1136
1137        VISIT_END( Expr, node );
1138}
1139
1140//--------------------------------------------------------------------------
1141// VariableExpr
[7ff3e522]1142template< typename core_t >
1143const ast::Expr * ast::Pass< core_t >::visit( const ast::VariableExpr * node ) {
[17a0228a]1144        VISIT_START( node );
1145
1146        VISIT({
[0e42794]1147                guard_symtab guard { *this };
[17a0228a]1148                maybe_accept( node, &VariableExpr::result );
1149        })
1150
1151        VISIT_END( Expr, node );
1152}
1153
1154//--------------------------------------------------------------------------
1155// ConstantExpr
[7ff3e522]1156template< typename core_t >
1157const ast::Expr * ast::Pass< core_t >::visit( const ast::ConstantExpr * node ) {
[17a0228a]1158        VISIT_START( node );
1159
1160        VISIT({
[0e42794]1161                guard_symtab guard { *this };
[17a0228a]1162                maybe_accept( node, &ConstantExpr::result );
1163        })
1164
1165        VISIT_END( Expr, node );
1166}
1167
1168//--------------------------------------------------------------------------
1169// SizeofExpr
[7ff3e522]1170template< typename core_t >
1171const ast::Expr * ast::Pass< core_t >::visit( const ast::SizeofExpr * node ) {
[17a0228a]1172        VISIT_START( node );
1173
1174        VISIT({
[0e42794]1175                        guard_symtab guard { *this };
[17a0228a]1176                        maybe_accept( node, &SizeofExpr::result );
1177                }
1178                if ( node->type ) {
1179                        maybe_accept( node, &SizeofExpr::type );
1180                } else {
1181                        maybe_accept( node, &SizeofExpr::expr );
1182                }
1183        )
1184
1185        VISIT_END( Expr, node );
1186}
1187
1188//--------------------------------------------------------------------------
1189// AlignofExpr
[7ff3e522]1190template< typename core_t >
1191const ast::Expr * ast::Pass< core_t >::visit( const ast::AlignofExpr * node ) {
[17a0228a]1192        VISIT_START( node );
1193
1194        VISIT({
[0e42794]1195                        guard_symtab guard { *this };
[17a0228a]1196                        maybe_accept( node, &AlignofExpr::result );
1197                }
1198                if ( node->type ) {
1199                        maybe_accept( node, &AlignofExpr::type );
1200                } else {
1201                        maybe_accept( node, &AlignofExpr::expr );
1202                }
1203        )
1204
1205        VISIT_END( Expr, node );
1206}
1207
1208//--------------------------------------------------------------------------
1209// UntypedOffsetofExpr
[7ff3e522]1210template< typename core_t >
1211const ast::Expr * ast::Pass< core_t >::visit( const ast::UntypedOffsetofExpr * node ) {
[17a0228a]1212        VISIT_START( node );
1213
1214        VISIT({
[0e42794]1215                        guard_symtab guard { *this };
[17a0228a]1216                        maybe_accept( node, &UntypedOffsetofExpr::result );
1217                }
1218                maybe_accept( node, &UntypedOffsetofExpr::type   );
1219        )
1220
1221        VISIT_END( Expr, node );
1222}
1223
1224//--------------------------------------------------------------------------
1225// OffsetofExpr
[7ff3e522]1226template< typename core_t >
1227const ast::Expr * ast::Pass< core_t >::visit( const ast::OffsetofExpr * node ) {
[17a0228a]1228        VISIT_START( node );
1229
1230        VISIT({
[0e42794]1231                        guard_symtab guard { *this };
[17a0228a]1232                        maybe_accept( node, &OffsetofExpr::result );
1233                }
1234                maybe_accept( node, &OffsetofExpr::type   );
1235        )
1236
1237        VISIT_END( Expr, node );
1238}
1239
1240//--------------------------------------------------------------------------
1241// OffsetPackExpr
[7ff3e522]1242template< typename core_t >
1243const ast::Expr * ast::Pass< core_t >::visit( const ast::OffsetPackExpr * node ) {
[17a0228a]1244        VISIT_START( node );
1245
1246        VISIT({
[0e42794]1247                        guard_symtab guard { *this };
[17a0228a]1248                        maybe_accept( node, &OffsetPackExpr::result );
1249                }
1250                maybe_accept( node, &OffsetPackExpr::type   );
1251        )
1252
1253        VISIT_END( Expr, node );
1254}
1255
1256//--------------------------------------------------------------------------
1257// LogicalExpr
[7ff3e522]1258template< typename core_t >
1259const ast::Expr * ast::Pass< core_t >::visit( const ast::LogicalExpr * node ) {
[17a0228a]1260        VISIT_START( node );
1261
1262        VISIT({
[0e42794]1263                        guard_symtab guard { *this };
[17a0228a]1264                        maybe_accept( node, &LogicalExpr::result );
1265                }
1266                maybe_accept( node, &LogicalExpr::arg1 );
1267                maybe_accept( node, &LogicalExpr::arg2 );
1268        )
1269
1270        VISIT_END( Expr, node );
1271}
1272
1273//--------------------------------------------------------------------------
1274// ConditionalExpr
[7ff3e522]1275template< typename core_t >
1276const ast::Expr * ast::Pass< core_t >::visit( const ast::ConditionalExpr * node ) {
[17a0228a]1277        VISIT_START( node );
1278
1279        VISIT({
[0e42794]1280                        guard_symtab guard { *this };
[17a0228a]1281                        maybe_accept( node, &ConditionalExpr::result );
1282                }
1283                maybe_accept( node, &ConditionalExpr::arg1 );
1284                maybe_accept( node, &ConditionalExpr::arg2 );
1285                maybe_accept( node, &ConditionalExpr::arg3 );
1286        )
1287
1288        VISIT_END( Expr, node );
1289}
[10a1225]1290
[17a0228a]1291//--------------------------------------------------------------------------
1292// CommaExpr
[7ff3e522]1293template< typename core_t >
1294const ast::Expr * ast::Pass< core_t >::visit( const ast::CommaExpr * node ) {
[17a0228a]1295        VISIT_START( node );
1296
1297        VISIT({
[0e42794]1298                        guard_symtab guard { *this };
[17a0228a]1299                        maybe_accept( node, &CommaExpr::result );
1300                }
1301                maybe_accept( node, &CommaExpr::arg1 );
1302                maybe_accept( node, &CommaExpr::arg2 );
1303        )
1304
1305        VISIT_END( Expr, node );
1306}
1307
1308//--------------------------------------------------------------------------
1309// TypeExpr
[7ff3e522]1310template< typename core_t >
1311const ast::Expr * ast::Pass< core_t >::visit( const ast::TypeExpr * node ) {
[17a0228a]1312        VISIT_START( node );
1313
1314        VISIT({
[0e42794]1315                        guard_symtab guard { *this };
[17a0228a]1316                        maybe_accept( node, &TypeExpr::result );
1317                }
1318                maybe_accept( node, &TypeExpr::type );
1319        )
1320
1321        VISIT_END( Expr, node );
1322}
1323
1324//--------------------------------------------------------------------------
1325// AsmExpr
[7ff3e522]1326template< typename core_t >
1327const ast::Expr * ast::Pass< core_t >::visit( const ast::AsmExpr * node ) {
[17a0228a]1328        VISIT_START( node );
[10a1225]1329
[17a0228a]1330        VISIT({
[0e42794]1331                        guard_symtab guard { *this };
[17a0228a]1332                        maybe_accept( node, &AsmExpr::result );
1333                }
1334                maybe_accept( node, &AsmExpr::constraint );
1335                maybe_accept( node, &AsmExpr::operand    );
1336        )
[10a1225]1337
[17a0228a]1338        VISIT_END( Expr, node );
1339}
[10a1225]1340
[17a0228a]1341//--------------------------------------------------------------------------
1342// ImplicitCopyCtorExpr
[7ff3e522]1343template< typename core_t >
1344const ast::Expr * ast::Pass< core_t >::visit( const ast::ImplicitCopyCtorExpr * node ) {
[17a0228a]1345        VISIT_START( node );
1346
1347        VISIT({
[0e42794]1348                        guard_symtab guard { *this };
[17a0228a]1349                        maybe_accept( node, &ImplicitCopyCtorExpr::result );
1350                }
1351                maybe_accept( node, &ImplicitCopyCtorExpr::callExpr    );
1352        )
1353
1354        VISIT_END( Expr, node );
1355}
1356
1357//--------------------------------------------------------------------------
1358// ConstructorExpr
[7ff3e522]1359template< typename core_t >
1360const ast::Expr * ast::Pass< core_t >::visit( const ast::ConstructorExpr * node ) {
[17a0228a]1361        VISIT_START( node );
1362
1363        VISIT({
[0e42794]1364                        guard_symtab guard { *this };
[17a0228a]1365                        maybe_accept( node, &ConstructorExpr::result );
1366                }
1367                maybe_accept( node, &ConstructorExpr::callExpr );
1368        )
[10a1225]1369
[17a0228a]1370        VISIT_END( Expr, node );
1371}
1372
1373//--------------------------------------------------------------------------
1374// CompoundLiteralExpr
[7ff3e522]1375template< typename core_t >
1376const ast::Expr * ast::Pass< core_t >::visit( const ast::CompoundLiteralExpr * node ) {
[17a0228a]1377        VISIT_START( node );
1378
1379        VISIT({
[0e42794]1380                        guard_symtab guard { *this };
[17a0228a]1381                        maybe_accept( node, &CompoundLiteralExpr::result );
1382                }
1383                maybe_accept( node, &CompoundLiteralExpr::init );
1384        )
1385
1386        VISIT_END( Expr, node );
1387}
1388
1389//--------------------------------------------------------------------------
1390// RangeExpr
[7ff3e522]1391template< typename core_t >
1392const ast::Expr * ast::Pass< core_t >::visit( const ast::RangeExpr * node ) {
[17a0228a]1393        VISIT_START( node );
1394
1395        VISIT({
[0e42794]1396                        guard_symtab guard { *this };
[17a0228a]1397                        maybe_accept( node, &RangeExpr::result );
1398                }
1399                maybe_accept( node, &RangeExpr::low    );
1400                maybe_accept( node, &RangeExpr::high   );
1401        )
1402
1403        VISIT_END( Expr, node );
1404}
1405
1406//--------------------------------------------------------------------------
1407// UntypedTupleExpr
[7ff3e522]1408template< typename core_t >
1409const ast::Expr * ast::Pass< core_t >::visit( const ast::UntypedTupleExpr * node ) {
[17a0228a]1410        VISIT_START( node );
1411
1412        VISIT({
[0e42794]1413                        guard_symtab guard { *this };
[17a0228a]1414                        maybe_accept( node, &UntypedTupleExpr::result );
1415                }
1416                maybe_accept( node, &UntypedTupleExpr::exprs  );
1417        )
1418
1419        VISIT_END( Expr, node );
1420}
1421
1422//--------------------------------------------------------------------------
1423// TupleExpr
[7ff3e522]1424template< typename core_t >
1425const ast::Expr * ast::Pass< core_t >::visit( const ast::TupleExpr * node ) {
[17a0228a]1426        VISIT_START( node );
1427
1428        VISIT({
[0e42794]1429                        guard_symtab guard { *this };
[17a0228a]1430                        maybe_accept( node, &TupleExpr::result );
1431                }
1432                maybe_accept( node, &TupleExpr::exprs  );
1433        )
1434
1435        VISIT_END( Expr, node );
1436}
1437
1438//--------------------------------------------------------------------------
1439// TupleIndexExpr
[7ff3e522]1440template< typename core_t >
1441const ast::Expr * ast::Pass< core_t >::visit( const ast::TupleIndexExpr * node ) {
[17a0228a]1442        VISIT_START( node );
1443
1444        VISIT({
[0e42794]1445                        guard_symtab guard { *this };
[17a0228a]1446                        maybe_accept( node, &TupleIndexExpr::result );
1447                }
1448                maybe_accept( node, &TupleIndexExpr::tuple  );
1449        )
1450
1451        VISIT_END( Expr, node );
1452}
1453
1454//--------------------------------------------------------------------------
1455// TupleAssignExpr
[7ff3e522]1456template< typename core_t >
1457const ast::Expr * ast::Pass< core_t >::visit( const ast::TupleAssignExpr * node ) {
[17a0228a]1458        VISIT_START( node );
1459
1460        VISIT({
[0e42794]1461                        guard_symtab guard { *this };
[17a0228a]1462                        maybe_accept( node, &TupleAssignExpr::result );
1463                }
1464                maybe_accept( node, &TupleAssignExpr::stmtExpr );
1465        )
1466
1467        VISIT_END( Expr, node );
1468}
1469
1470//--------------------------------------------------------------------------
1471// StmtExpr
[7ff3e522]1472template< typename core_t >
1473const ast::Expr * ast::Pass< core_t >::visit( const ast::StmtExpr * node ) {
[17a0228a]1474        VISIT_START( node );
1475
1476        VISIT(// don't want statements from outer CompoundStmts to be added to this StmtExpr
1477                // get the stmts that will need to be spliced in
[7ff3e522]1478                auto stmts_before = __pass::stmtsToAddBefore( core, 0);
1479                auto stmts_after  = __pass::stmtsToAddAfter ( core, 0);
[17a0228a]1480
1481                // These may be modified by subnode but most be restored once we exit this statemnet.
[7ff3e522]1482                ValueGuardPtr< const ast::TypeSubstitution * > __old_env( __pass::env( core, 0) );
[17a0228a]1483                ValueGuardPtr< typename std::remove_pointer< decltype(stmts_before) >::type > __old_decls_before( stmts_before );
1484                ValueGuardPtr< typename std::remove_pointer< decltype(stmts_after ) >::type > __old_decls_after ( stmts_after  );
1485
1486                {
[0e42794]1487                        guard_symtab guard { *this };
[17a0228a]1488                        maybe_accept( node, &StmtExpr::result );
1489                }
1490                maybe_accept( node, &StmtExpr::stmts       );
1491                maybe_accept( node, &StmtExpr::returnDecls );
1492                maybe_accept( node, &StmtExpr::dtors       );
1493        )
1494
1495        VISIT_END( Expr, node );
1496}
1497
1498//--------------------------------------------------------------------------
1499// UniqueExpr
[7ff3e522]1500template< typename core_t >
1501const ast::Expr * ast::Pass< core_t >::visit( const ast::UniqueExpr * node ) {
[17a0228a]1502        VISIT_START( node );
1503
1504        VISIT({
[0e42794]1505                        guard_symtab guard { *this };
[17a0228a]1506                        maybe_accept( node, &UniqueExpr::result );
1507                }
1508                maybe_accept( node, &UniqueExpr::expr   );
1509        )
1510
1511        VISIT_END( Expr, node );
1512}
1513
1514//--------------------------------------------------------------------------
1515// UntypedInitExpr
[7ff3e522]1516template< typename core_t >
1517const ast::Expr * ast::Pass< core_t >::visit( const ast::UntypedInitExpr * node ) {
[17a0228a]1518        VISIT_START( node );
1519
1520        VISIT({
[0e42794]1521                        guard_symtab guard { *this };
[17a0228a]1522                        maybe_accept( node, &UntypedInitExpr::result );
1523                }
1524                maybe_accept( node, &UntypedInitExpr::expr   );
1525                // not currently visiting initAlts, but this doesn't matter since this node is only used in the resolver.
1526        )
1527
1528        VISIT_END( Expr, node );
1529}
1530
1531//--------------------------------------------------------------------------
1532// InitExpr
[7ff3e522]1533template< typename core_t >
1534const ast::Expr * ast::Pass< core_t >::visit( const ast::InitExpr * node ) {
[17a0228a]1535        VISIT_START( node );
1536
1537        VISIT({
[0e42794]1538                        guard_symtab guard { *this };
[17a0228a]1539                        maybe_accept( node, &InitExpr::result );
1540                }
1541                maybe_accept( node, &InitExpr::expr   );
1542                maybe_accept( node, &InitExpr::designation );
1543        )
1544
1545        VISIT_END( Expr, node );
1546}
1547
1548//--------------------------------------------------------------------------
1549// DeletedExpr
[7ff3e522]1550template< typename core_t >
1551const ast::Expr * ast::Pass< core_t >::visit( const ast::DeletedExpr * node ) {
[17a0228a]1552        VISIT_START( node );
1553
1554        VISIT({
[0e42794]1555                        guard_symtab guard { *this };
[17a0228a]1556                        maybe_accept( node, &DeletedExpr::result );
1557                }
1558                maybe_accept( node, &DeletedExpr::expr );
1559                // don't visit deleteStmt, because it is a pointer to somewhere else in the tree.
1560        )
1561
1562        VISIT_END( Expr, node );
1563}
1564
1565//--------------------------------------------------------------------------
1566// DefaultArgExpr
[7ff3e522]1567template< typename core_t >
1568const ast::Expr * ast::Pass< core_t >::visit( const ast::DefaultArgExpr * node ) {
[17a0228a]1569        VISIT_START( node );
1570
1571        VISIT({
[0e42794]1572                        guard_symtab guard { *this };
[17a0228a]1573                        maybe_accept( node, &DefaultArgExpr::result );
1574                }
1575                maybe_accept( node, &DefaultArgExpr::expr );
1576        )
1577
1578        VISIT_END( Expr, node );
1579}
1580
1581//--------------------------------------------------------------------------
1582// GenericExpr
[7ff3e522]1583template< typename core_t >
1584const ast::Expr * ast::Pass< core_t >::visit( const ast::GenericExpr * node ) {
[17a0228a]1585        VISIT_START( node );
1586
1587        VISIT({
[0e42794]1588                        guard_symtab guard { *this };
[17a0228a]1589                        maybe_accept( node, &GenericExpr::result );
1590                }
1591                maybe_accept( node, &GenericExpr::control );
1592
1593                std::vector<GenericExpr::Association> new_kids;
1594                new_kids.reserve(node->associations.size());
1595                bool mutated = false;
1596                for( const auto & assoc : node->associations ) {
[b0abc8a0]1597                        const Type * type = nullptr;
[17a0228a]1598                        if( assoc.type ) {
[0e42794]1599                                guard_symtab guard { *this };
[17a0228a]1600                                type = assoc.type->accept( *this );
1601                                if( type != assoc.type ) mutated = true;
1602                        }
[b0abc8a0]1603                        const Expr * expr = nullptr;
[17a0228a]1604                        if( assoc.expr ) {
1605                                expr = assoc.expr->accept( *this );
1606                                if( expr != assoc.expr ) mutated = true;
1607                        }
1608                        new_kids.emplace_back( type, expr );
1609                }
1610
1611                if(mutated) {
1612                        auto n = mutate(node);
1613                        n->associations = std::move( new_kids );
1614                        node = n;
1615                }
1616        )
1617
1618        VISIT_END( Expr, node );
1619}
[10a1225]1620
[e0016a5]1621//--------------------------------------------------------------------------
1622// VoidType
[7ff3e522]1623template< typename core_t >
1624const ast::Type * ast::Pass< core_t >::visit( const ast::VoidType * node ) {
[e0016a5]1625        VISIT_START( node );
[10a1225]1626
[e0016a5]1627        VISIT_END( Type, node );
1628}
[10a1225]1629
[e0016a5]1630//--------------------------------------------------------------------------
1631// BasicType
[7ff3e522]1632template< typename core_t >
1633const ast::Type * ast::Pass< core_t >::visit( const ast::BasicType * node ) {
[e0016a5]1634        VISIT_START( node );
1635
1636        VISIT_END( Type, node );
1637}
1638
1639//--------------------------------------------------------------------------
1640// PointerType
[7ff3e522]1641template< typename core_t >
1642const ast::Type * ast::Pass< core_t >::visit( const ast::PointerType * node ) {
[e0016a5]1643        VISIT_START( node );
1644
1645        VISIT(
1646                // xxx - should PointerType visit/mutate dimension?
1647                maybe_accept( node, &PointerType::base );
1648        )
1649
1650        VISIT_END( Type, node );
1651}
1652
1653//--------------------------------------------------------------------------
1654// ArrayType
[7ff3e522]1655template< typename core_t >
1656const ast::Type * ast::Pass< core_t >::visit( const ast::ArrayType * node ) {
[e0016a5]1657        VISIT_START( node );
1658
1659        VISIT(
1660                maybe_accept( node, &ArrayType::dimension );
1661                maybe_accept( node, &ArrayType::base );
1662        )
1663
1664        VISIT_END( Type, node );
1665}
1666
1667//--------------------------------------------------------------------------
1668// ReferenceType
[7ff3e522]1669template< typename core_t >
1670const ast::Type * ast::Pass< core_t >::visit( const ast::ReferenceType * node ) {
[e0016a5]1671        VISIT_START( node );
1672
1673        VISIT(
1674                maybe_accept( node, &ReferenceType::base );
1675        )
1676
1677        VISIT_END( Type, node );
1678}
1679
1680//--------------------------------------------------------------------------
1681// QualifiedType
[7ff3e522]1682template< typename core_t >
1683const ast::Type * ast::Pass< core_t >::visit( const ast::QualifiedType * node ) {
[e0016a5]1684        VISIT_START( node );
1685
1686        VISIT(
1687                maybe_accept( node, &QualifiedType::parent );
1688                maybe_accept( node, &QualifiedType::child );
1689        )
1690
1691        VISIT_END( Type, node );
1692}
1693
1694//--------------------------------------------------------------------------
1695// FunctionType
[7ff3e522]1696template< typename core_t >
1697const ast::Type * ast::Pass< core_t >::visit( const ast::FunctionType * node ) {
[e0016a5]1698        VISIT_START( node );
1699
[e0e9a0b]1700        VISIT({
1701                guard_forall_subs forall_guard { *this, node };
1702                mutate_forall( node );
[e0016a5]1703                maybe_accept( node, &FunctionType::returns );
1704                maybe_accept( node, &FunctionType::params  );
[e0e9a0b]1705        })
[e0016a5]1706
1707        VISIT_END( Type, node );
1708}
1709
1710//--------------------------------------------------------------------------
1711// StructInstType
[7ff3e522]1712template< typename core_t >
1713const ast::Type * ast::Pass< core_t >::visit( const ast::StructInstType * node ) {
[e0016a5]1714        VISIT_START( node );
1715
[7ff3e522]1716        __pass::symtab::addStruct( core, 0, node->name );
[e0016a5]1717
1718        VISIT({
[0e42794]1719                guard_symtab guard { *this };
[e0e9a0b]1720                guard_forall_subs forall_guard { *this, node };
1721                mutate_forall( node );
[e0016a5]1722                maybe_accept( node, &StructInstType::params );
1723        })
1724
1725        VISIT_END( Type, node );
1726}
1727
1728//--------------------------------------------------------------------------
1729// UnionInstType
[7ff3e522]1730template< typename core_t >
1731const ast::Type * ast::Pass< core_t >::visit( const ast::UnionInstType * node ) {
[e0016a5]1732        VISIT_START( node );
1733
[7ff3e522]1734        __pass::symtab::addUnion( core, 0, node->name );
[e0016a5]1735
[e0e9a0b]1736        VISIT({
[0e42794]1737                guard_symtab guard { *this };
[e0e9a0b]1738                guard_forall_subs forall_guard { *this, node };
1739                mutate_forall( node );
[e0016a5]1740                maybe_accept( node, &UnionInstType::params );
[e0e9a0b]1741        })
[e0016a5]1742
1743        VISIT_END( Type, node );
1744}
1745
1746//--------------------------------------------------------------------------
1747// EnumInstType
[7ff3e522]1748template< typename core_t >
1749const ast::Type * ast::Pass< core_t >::visit( const ast::EnumInstType * node ) {
[e0016a5]1750        VISIT_START( node );
1751
[e0e9a0b]1752        VISIT({
1753                guard_forall_subs forall_guard { *this, node };
1754                mutate_forall( node );
[e0016a5]1755                maybe_accept( node, &EnumInstType::params );
[e0e9a0b]1756        })
[e0016a5]1757
1758        VISIT_END( Type, node );
1759}
1760
1761//--------------------------------------------------------------------------
1762// TraitInstType
[7ff3e522]1763template< typename core_t >
1764const ast::Type * ast::Pass< core_t >::visit( const ast::TraitInstType * node ) {
[e0016a5]1765        VISIT_START( node );
1766
[e0e9a0b]1767        VISIT({
1768                guard_forall_subs forall_guard { *this, node };
1769                mutate_forall( node );
[e0016a5]1770                maybe_accept( node, &TraitInstType::params );
[e0e9a0b]1771        })
[e0016a5]1772
1773        VISIT_END( Type, node );
1774}
1775
1776//--------------------------------------------------------------------------
1777// TypeInstType
[7ff3e522]1778template< typename core_t >
1779const ast::Type * ast::Pass< core_t >::visit( const ast::TypeInstType * node ) {
[e0016a5]1780        VISIT_START( node );
1781
1782        VISIT(
[e0e9a0b]1783                {
1784                        guard_forall_subs forall_guard { *this, node };
1785                        mutate_forall( node );
1786                        maybe_accept( node, &TypeInstType::params );
1787                }
1788                // ensure that base re-bound if doing substitution
[7ff3e522]1789                __pass::forall::replace( core, 0, node );
[e0016a5]1790        )
1791
1792        VISIT_END( Type, node );
1793}
1794
1795//--------------------------------------------------------------------------
1796// TupleType
[7ff3e522]1797template< typename core_t >
1798const ast::Type * ast::Pass< core_t >::visit( const ast::TupleType * node ) {
[e0016a5]1799        VISIT_START( node );
1800
1801        VISIT(
1802                maybe_accept( node, &TupleType::types );
1803                maybe_accept( node, &TupleType::members );
1804        )
1805
1806        VISIT_END( Type, node );
1807}
1808
1809//--------------------------------------------------------------------------
1810// TypeofType
[7ff3e522]1811template< typename core_t >
1812const ast::Type * ast::Pass< core_t >::visit( const ast::TypeofType * node ) {
[e0016a5]1813        VISIT_START( node );
1814
1815        VISIT(
1816                maybe_accept( node, &TypeofType::expr );
1817        )
1818
1819        VISIT_END( Type, node );
1820}
1821
1822//--------------------------------------------------------------------------
1823// VarArgsType
[7ff3e522]1824template< typename core_t >
1825const ast::Type * ast::Pass< core_t >::visit( const ast::VarArgsType * node ) {
[e0016a5]1826        VISIT_START( node );
1827
1828        VISIT_END( Type, node );
1829}
1830
1831//--------------------------------------------------------------------------
1832// ZeroType
[7ff3e522]1833template< typename core_t >
1834const ast::Type * ast::Pass< core_t >::visit( const ast::ZeroType * node ) {
[e0016a5]1835        VISIT_START( node );
1836
1837        VISIT_END( Type, node );
1838}
1839
1840//--------------------------------------------------------------------------
1841// OneType
[7ff3e522]1842template< typename core_t >
1843const ast::Type * ast::Pass< core_t >::visit( const ast::OneType * node ) {
[e0016a5]1844        VISIT_START( node );
1845
1846        VISIT_END( Type, node );
1847}
1848
1849//--------------------------------------------------------------------------
1850// GlobalScopeType
[7ff3e522]1851template< typename core_t >
1852const ast::Type * ast::Pass< core_t >::visit( const ast::GlobalScopeType * node ) {
[e0016a5]1853        VISIT_START( node );
1854
1855        VISIT_END( Type, node );
1856}
1857
1858
1859//--------------------------------------------------------------------------
1860// Designation
[7ff3e522]1861template< typename core_t >
1862const ast::Designation * ast::Pass< core_t >::visit( const ast::Designation * node ) {
[e0016a5]1863        VISIT_START( node );
1864
1865        VISIT( maybe_accept( node, &Designation::designators ); )
1866
1867        VISIT_END( Designation, node );
1868}
[10a1225]1869
[6d51bd7]1870//--------------------------------------------------------------------------
1871// SingleInit
[7ff3e522]1872template< typename core_t >
1873const ast::Init * ast::Pass< core_t >::visit( const ast::SingleInit * node ) {
[6d51bd7]1874        VISIT_START( node );
1875
1876        VISIT(
1877                maybe_accept( node, &SingleInit::value );
1878        )
1879
1880        VISIT_END( Init, node );
1881}
1882
1883//--------------------------------------------------------------------------
1884// ListInit
[7ff3e522]1885template< typename core_t >
1886const ast::Init * ast::Pass< core_t >::visit( const ast::ListInit * node ) {
[6d51bd7]1887        VISIT_START( node );
1888
1889        VISIT(
1890                maybe_accept( node, &ListInit::designations );
1891                maybe_accept( node, &ListInit::initializers );
1892        )
1893
1894        VISIT_END( Init, node );
1895}
1896
1897//--------------------------------------------------------------------------
1898// ConstructorInit
[7ff3e522]1899template< typename core_t >
1900const ast::Init * ast::Pass< core_t >::visit( const ast::ConstructorInit * node ) {
[6d51bd7]1901        VISIT_START( node );
1902
1903        VISIT(
1904                maybe_accept( node, &ConstructorInit::ctor );
1905                maybe_accept( node, &ConstructorInit::dtor );
1906                maybe_accept( node, &ConstructorInit::init );
1907        )
1908
1909        VISIT_END( Init, node );
1910}
1911
[f47f887]1912//--------------------------------------------------------------------------
1913// Attribute
[7ff3e522]1914template< typename core_t >
1915const ast::Attribute * ast::Pass< core_t >::visit( const ast::Attribute * node  )  {
[6d51bd7]1916        VISIT_START( node );
[f47f887]1917
1918        VISIT(
[489bacf]1919                maybe_accept( node, &Attribute::params );
[f47f887]1920        )
1921
[8a5530c]1922        VISIT_END( Attribute, node );
[f47f887]1923}
1924
1925//--------------------------------------------------------------------------
1926// TypeSubstitution
[7ff3e522]1927template< typename core_t >
1928const ast::TypeSubstitution * ast::Pass< core_t >::visit( const ast::TypeSubstitution * node ) {
[6d51bd7]1929        VISIT_START( node );
[f47f887]1930
[6d51bd7]1931        VISIT(
1932                {
1933                        bool mutated = false;
1934                        std::unordered_map< std::string, ast::ptr< ast::Type > > new_map;
1935                        for ( const auto & p : node->typeEnv ) {
[0e42794]1936                                guard_symtab guard { *this };
[6d51bd7]1937                                auto new_node = p.second->accept( *this );
[417117e]1938                                if (new_node != p.second) mutated = true;
[6d51bd7]1939                                new_map.insert({ p.first, new_node });
1940                        }
1941                        if (mutated) {
1942                                auto new_node = mutate( node );
1943                                new_node->typeEnv.swap( new_map );
1944                                node = new_node;
1945                        }
1946                }
[f47f887]1947
[6d51bd7]1948                {
1949                        bool mutated = false;
1950                        std::unordered_map< std::string, ast::ptr< ast::Expr > > new_map;
1951                        for ( const auto & p : node->varEnv ) {
[0e42794]1952                                guard_symtab guard { *this };
[6d51bd7]1953                                auto new_node = p.second->accept( *this );
[417117e]1954                                if (new_node != p.second) mutated = true;
[6d51bd7]1955                                new_map.insert({ p.first, new_node });
1956                        }
1957                        if (mutated) {
1958                                auto new_node = mutate( node );
1959                                new_node->varEnv.swap( new_map );
1960                                node = new_node;
1961                        }
1962                }
1963        )
[f47f887]1964
[6d51bd7]1965        VISIT_END( TypeSubstitution, node );
[f47f887]1966}
1967
1968#undef VISIT_START
1969#undef VISIT
[112fe04]1970#undef VISIT_END
Note: See TracBrowser for help on using the repository browser.