source: src/AST/Convert.cpp @ bc899d6

ADTast-experimental
Last change on this file since bc899d6 was 5408b59, checked in by JiadaL <j82liang@…>, 22 months ago

Remove var in QualifiedNameExpr?

  • Property mode set to 100644
File size: 82.0 KB
Line 
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//
7// Convert.cpp -- Convert between the new and old syntax trees.
8//
9// Author           : Thierry Delisle
10// Created On       : Thu May 09 15::37::05 2019
11// Last Modified By : Andrew Beach
12// Last Modified On : Wed Apr 20 13:58:00 2022
13// Update Count     : 43
14//
15
16#include "Convert.hpp"
17
18#include <deque>
19#include <unordered_map>
20
21#include "AST/Attribute.hpp"
22#include "AST/Copy.hpp"
23#include "AST/Decl.hpp"
24#include "AST/Expr.hpp"
25#include "AST/Init.hpp"
26#include "AST/Stmt.hpp"
27#include "AST/TranslationUnit.hpp"
28#include "AST/TypeSubstitution.hpp"
29
30#include "SymTab/Autogen.h"
31#include "SynTree/Attribute.h"
32#include "SynTree/Declaration.h"
33#include "SynTree/TypeSubstitution.h"
34
35#include "Validate/FindSpecialDecls.h"
36
37//================================================================================================
38// Utilities
39template<template <class...> class C>
40struct to {
41        template<typename T>
42        static auto from( T && v ) -> C< typename T::value_type > {
43                C< typename T::value_type > l;
44                std::move(std::begin(v), std::end(v), std::back_inserter(l));
45                return l;
46        }
47};
48
49//================================================================================================
50namespace ast {
51// These are the shared local information used by ConverterNewToOld and
52// ConverterOldToNew to update the global information in the two versions.
53
54static ast::ptr<ast::Type> sizeType = nullptr;
55static const ast::FunctionDecl * dereferenceOperator = nullptr;
56static const ast::StructDecl   * dtorStruct = nullptr;
57static const ast::FunctionDecl * dtorStructDestroy = nullptr;
58
59}
60
61//================================================================================================
62class ConverterNewToOld : public ast::Visitor {
63        BaseSyntaxNode * node = nullptr;
64        using Cache = std::unordered_map< const ast::Node *, BaseSyntaxNode * >;
65        Cache cache;
66
67        // Statements can no longer be shared.
68        // however, since StmtExprResult is now implemented, need to still maintain
69        // readonly references.
70        Cache readonlyCache;
71
72        template<typename T>
73        struct Getter {
74                ConverterNewToOld & visitor;
75
76                template<typename U, enum ast::Node::ref_type R>
77                T * accept1( const ast::ptr_base<U, R> & ptr ) {
78                        if ( ! ptr ) return nullptr;
79                        ptr->accept( visitor );
80                        T * ret = strict_dynamic_cast< T * >( visitor.node );
81                        visitor.node = nullptr;
82                        return ret;
83                }
84
85                template<typename U>
86                std::list< T * > acceptL( const U & container ) {
87                        std::list< T * > ret;
88                        for ( auto ptr : container ) {
89                                ret.emplace_back( accept1( ptr ) );
90                        }
91                        return ret;
92                }
93        };
94
95        template<typename T>
96        Getter<T> get() {
97                return Getter<T>{ *this };
98        }
99
100        Label makeLabel(Statement * labelled, const ast::Label& label) {
101                // This probably will leak memory, but only until we get rid of the old tree.
102                if ( nullptr == labelled && label.location.isSet() ) {
103                        labelled = new NullStmt();
104                        labelled->location = label.location;
105                }
106                return Label(
107                        label.name,
108                        labelled,
109                        get<Attribute>().acceptL(label.attributes)
110                );
111        }
112
113        template<template <class...> class C>
114        std::list<Label> makeLabelL(Statement * labelled, const C<ast::Label>& labels) {
115                std::list<Label> ret;
116                for (auto label : labels) {
117                        ret.push_back( makeLabel(labelled, label) );
118                }
119                return ret;
120        }
121
122        /// get new qualifiers from old type
123        Type::Qualifiers cv( const ast::Type * ty ) { return { ty->qualifiers.val }; }
124
125        /// returns true and sets `node` if in cache
126        bool inCache( const ast::Node * node ) {
127                auto it = cache.find( node );
128                if ( it == cache.end() ) return false;
129                this->node = it->second;
130                return true;
131        }
132
133public:
134        Declaration * decl( const ast::Decl * declNode ) {
135                return get<Declaration>().accept1( ast::ptr<ast::Decl>( declNode ) );
136        }
137
138private:
139        void declPostamble( Declaration * decl, const ast::Decl * node ) {
140                decl->location = node->location;
141                // name comes from constructor
142                // linkage comes from constructor
143                decl->extension = node->extension;
144                decl->uniqueId = node->uniqueId;
145                // storageClasses comes from constructor
146                this->node = decl;
147        }
148
149        const ast::DeclWithType * declWithTypePostamble (
150                        DeclarationWithType * decl, const ast::DeclWithType * node ) {
151                cache.emplace( node, decl );
152                decl->mangleName = node->mangleName;
153                decl->scopeLevel = node->scopeLevel;
154                decl->asmName = get<Expression>().accept1( node->asmName );
155                // attributes comes from constructor
156                decl->isDeleted = node->isDeleted;
157                // fs comes from constructor
158                declPostamble( decl, node );
159                return nullptr;
160        }
161
162        const ast::DeclWithType * visit( const ast::ObjectDecl * node ) override final {       
163                if ( inCache( node ) ) {
164                        return nullptr;
165                }
166                auto bfwd = get<Expression>().accept1( node->bitfieldWidth );
167                auto type = get<Type>().accept1( node->type );
168                auto attr = get<Attribute>().acceptL( node->attributes );
169
170                // This field can be unset very early on (Pre-FixReturnTypes).
171                auto newType = (type) ? type->clone() : nullptr;
172
173                auto decl = new ObjectDecl(
174                        node->name,
175                        Type::StorageClasses( node->storage.val ),
176                        LinkageSpec::Spec( node->linkage.val ),
177                        bfwd,
178                        newType,
179                        nullptr, // prevent infinite loop
180                        attr,
181                        Type::FuncSpecifiers( node->funcSpec.val )
182                );
183
184                // handles the case where node->init references itself
185                // xxx - does it really happen?
186                declWithTypePostamble(decl, node);
187                auto init = get<Initializer>().accept1( node->init );
188                decl->init = init;
189
190                this->node = decl;
191                return nullptr;
192        }
193
194        const ast::DeclWithType * visit( const ast::FunctionDecl * node ) override final {
195                if ( inCache( node ) ) return nullptr;
196
197                // function decl contains real variables that the type must use.
198                // the structural change means function type in and out of decl
199                // must be handled **differently** on convert back to old.
200                auto ftype = new FunctionType(
201                        cv(node->type),
202                        (bool)node->type->isVarArgs
203                );
204                ftype->returnVals = get<DeclarationWithType>().acceptL(node->returns);
205                ftype->parameters = get<DeclarationWithType>().acceptL(node->params);
206
207                ftype->forall = get<TypeDecl>().acceptL( node->type_params );
208                if (!node->assertions.empty()) {
209                        assert(!ftype->forall.empty());
210                        // find somewhere to place assertions back, for convenience it is the last slot
211                        ftype->forall.back()->assertions = get<DeclarationWithType>().acceptL(node->assertions);
212                }
213
214                visitType(node->type, ftype);
215
216                auto decl = new FunctionDecl(
217                        node->name,
218                        Type::StorageClasses( node->storage.val ),
219                        LinkageSpec::Spec( node->linkage.val ),
220                        ftype,
221                        //get<FunctionType>().accept1( node->type ),
222                        {},
223                        get<Attribute>().acceptL( node->attributes ),
224                        Type::FuncSpecifiers( node->funcSpec.val )
225                );
226                cache.emplace( node, decl );
227                decl->statements = get<CompoundStmt>().accept1( node->stmts );
228                decl->withExprs = get<Expression>().acceptL( node->withExprs );
229                if ( ast::dereferenceOperator == node ) {
230                        Validate::dereferenceOperator = decl;
231                }
232                if ( ast::dtorStructDestroy == node ) {
233                        Validate::dtorStructDestroy = decl;
234                }
235                return declWithTypePostamble( decl, node );
236        }
237
238        const ast::Decl * namedTypePostamble( NamedTypeDecl * decl, const ast::NamedTypeDecl * node ) {
239                // base comes from constructor
240                decl->assertions = get<DeclarationWithType>().acceptL( node->assertions );
241                declPostamble( decl, node );
242                return nullptr;
243        }
244
245        const ast::Decl * visit( const ast::TypeDecl * node ) override final {
246                if ( inCache( node ) ) return nullptr;
247                auto decl = new TypeDecl(
248                        node->name,
249                        Type::StorageClasses( node->storage.val ),
250                        get<Type>().accept1( node->base ),
251                        (TypeDecl::Kind)(unsigned)node->kind,
252                        node->sized,
253                        get<Type>().accept1( node->init )
254                );
255                cache.emplace( node, decl );
256                return namedTypePostamble( decl, node );
257        }
258
259        const ast::Decl * visit( const ast::TypedefDecl * node ) override final {
260                auto decl = new TypedefDecl(
261                        node->name,
262                        node->location,
263                        Type::StorageClasses( node->storage.val ),
264            get<Type>().accept1( node->base ),
265                        LinkageSpec::Spec( node->linkage.val )
266                );
267                return namedTypePostamble( decl, node );
268        }
269
270        const ast::Decl * aggregatePostamble( AggregateDecl * decl, const ast::AggregateDecl * node ) {
271                cache.emplace( node, decl );
272                decl->members = get<Declaration>().acceptL( node->members );
273                decl->parameters = get<TypeDecl>().acceptL( node->params );
274                decl->body = node->body;
275                // attributes come from constructor
276                decl->parent = get<AggregateDecl>().accept1( node->parent );
277                declPostamble( decl, node );
278                return nullptr; // ??
279        }
280
281        const ast::Decl * visit( const ast::StructDecl * node ) override final {
282                if ( inCache( node ) ) return nullptr;
283                auto decl = new StructDecl(
284                        node->name,
285                        (AggregateDecl::Aggregate)node->kind,
286                        get<Attribute>().acceptL( node->attributes ),
287                        LinkageSpec::Spec( node->linkage.val )
288                );
289
290                if ( ast::dtorStruct == node ) {
291                        Validate::dtorStruct = decl;
292                }
293
294                return aggregatePostamble( decl, node );
295        }
296
297        const ast::Decl * visit( const ast::UnionDecl * node ) override final {
298                if ( inCache( node ) ) return nullptr;
299                auto decl = new UnionDecl(
300                        node->name,
301                        get<Attribute>().acceptL( node->attributes ),
302                        LinkageSpec::Spec( node->linkage.val )
303                );
304                return aggregatePostamble( decl, node );
305        }
306
307        const ast::Decl * visit( const ast::EnumDecl * node ) override final {
308                if ( inCache( node ) ) return nullptr;
309                auto decl = new EnumDecl(
310                        node->name,
311                        get<Attribute>().acceptL( node->attributes ),
312                        node->isTyped,
313                        LinkageSpec::Spec( node->linkage.val ),
314                        get<Type>().accept1(node->base)
315                );
316                return aggregatePostamble( decl, node );
317        }
318
319        const ast::Decl * visit( const ast::TraitDecl * node ) override final {
320                if ( inCache( node ) ) return nullptr;
321                auto decl = new TraitDecl(
322                        node->name,
323                        {},
324                        LinkageSpec::Spec( node->linkage.val )
325                );
326                return aggregatePostamble( decl, node );
327        }
328
329        const ast::AsmDecl * visit( const ast::AsmDecl * node ) override final {
330                auto decl = new AsmDecl( get<AsmStmt>().accept1( node->stmt ) );
331                declPostamble( decl, node );
332                return nullptr;
333        }
334
335        const ast::DirectiveDecl * visit( const ast::DirectiveDecl * node ) override final {
336                auto decl = new DirectiveDecl( get<DirectiveStmt>().accept1( node->stmt ) );
337                declPostamble( decl, node );
338                return nullptr;
339        }
340
341        const ast::StaticAssertDecl * visit( const ast::StaticAssertDecl * node ) override final {
342                auto decl = new StaticAssertDecl(
343                        get<Expression>().accept1( node->cond ),
344                        get<ConstantExpr>().accept1( node->msg )
345                );
346                declPostamble( decl, node );
347                return nullptr;
348        }
349
350        const ast::Stmt * stmtPostamble( Statement * stmt, const ast::Stmt * node ) {
351                // force statements in old tree to be unique.
352                // cache.emplace( node, stmt );
353                readonlyCache.emplace( node, stmt );
354                stmt->location = node->location;
355                stmt->labels = makeLabelL( stmt, node->labels );
356                this->node = stmt;
357                return nullptr;
358        }
359
360        void clausePostamble( Statement * stmt, const ast::StmtClause * node ) {
361                stmt->location = node->location;
362                this->node = stmt;
363        }
364
365        const ast::CompoundStmt * visit( const ast::CompoundStmt * node ) override final {
366                if ( inCache( node ) ) return nullptr;
367                auto stmt = new CompoundStmt( get<Statement>().acceptL( node->kids ) );
368                stmtPostamble( stmt, node );
369                return nullptr;
370        }
371
372        const ast::Stmt * visit( const ast::ExprStmt * node ) override final {
373                if ( inCache( node ) ) return nullptr;
374                auto stmt = new ExprStmt( nullptr );
375                stmt->expr = get<Expression>().accept1( node->expr );
376                return stmtPostamble( stmt, node );
377        }
378
379        const ast::Stmt * visit( const ast::AsmStmt * node ) override final {
380                if ( inCache( node ) ) return nullptr;
381                auto stmt = new AsmStmt(
382                        node->isVolatile,
383                        get<Expression>().accept1( node->instruction ),
384                        get<Expression>().acceptL( node->output ),
385                        get<Expression>().acceptL( node->input ),
386                        get<ConstantExpr>().acceptL( node->clobber ),
387                        makeLabelL( nullptr, node->gotoLabels ) // What are these labelling?
388                );
389                return stmtPostamble( stmt, node );
390        }
391
392        const ast::Stmt * visit( const ast::DirectiveStmt * node ) override final {
393                if ( inCache( node ) ) return nullptr;
394                auto stmt = new DirectiveStmt( node->directive );
395                return stmtPostamble( stmt, node );
396        }
397
398        const ast::Stmt * visit( const ast::IfStmt * node ) override final {
399                if ( inCache( node ) ) return nullptr;
400                auto stmt = new IfStmt(
401                        get<Expression>().accept1( node->cond ),
402                        get<Statement>().accept1( node->then ),
403                        get<Statement>().accept1( node->else_ ),
404                        get<Statement>().acceptL( node->inits )
405                );
406                return stmtPostamble( stmt, node );
407        }
408
409        const ast::Stmt * visit( const ast::SwitchStmt * node ) override final {
410                if ( inCache( node ) ) return nullptr;
411                auto stmt = new SwitchStmt(
412                        get<Expression>().accept1( node->cond ),
413                        get<Statement>().acceptL( node->cases )
414                );
415                return stmtPostamble( stmt, node );
416        }
417
418        const ast::CaseClause * visit( const ast::CaseClause * node ) override final {
419                if ( inCache( node ) ) return nullptr;
420                auto stmt = new CaseStmt(
421                        get<Expression>().accept1( node->cond ),
422                        get<Statement>().acceptL( node->stmts ),
423                        node->isDefault()
424                );
425                clausePostamble( stmt, node );
426                return nullptr;
427        }
428
429        const ast::Stmt * visit( const ast::WhileDoStmt * node ) override final {
430                if ( inCache( node ) ) return nullptr;
431                auto inits = get<Statement>().acceptL( node->inits );
432                auto stmt = new WhileDoStmt(
433                        get<Expression>().accept1( node->cond ),
434                        get<Statement>().accept1( node->body ),
435                        get<Statement>().accept1( node->else_ ),
436                        inits,
437                        node->isDoWhile
438                );
439                return stmtPostamble( stmt, node );
440        }
441
442        const ast::Stmt * visit( const ast::ForStmt * node ) override final {
443                if ( inCache( node ) ) return nullptr;
444                auto stmt = new ForStmt(
445                        get<Statement>().acceptL( node->inits ),
446                        get<Expression>().accept1( node->cond ),
447                        get<Expression>().accept1( node->inc ),
448                        get<Statement>().accept1( node->body ),
449                        get<Statement>().accept1( node->else_ )
450                );
451                return stmtPostamble( stmt, node );
452        }
453
454        const ast::Stmt * visit( const ast::BranchStmt * node ) override final {
455                if ( inCache( node ) ) return nullptr;
456                BranchStmt * stmt;
457                if (node->computedTarget) {
458                        stmt = new BranchStmt( get<Expression>().accept1( node->computedTarget ),
459                                BranchStmt::Goto );
460                } else {
461                        BranchStmt::Type type;
462                        switch (node->kind) {
463                        #define CASE(n) \
464                        case ast::BranchStmt::n: \
465                                type = BranchStmt::n; \
466                                break
467                        CASE(Goto);
468                        CASE(Break);
469                        CASE(Continue);
470                        CASE(FallThrough);
471                        CASE(FallThroughDefault);
472                        #undef CASE
473                        default:
474                                assertf(false, "Invalid ast::BranchStmt::Kind: %d\n", node->kind);
475                        }
476
477                        // The labels here are also weird.
478                        stmt = new BranchStmt( makeLabel( nullptr, node->originalTarget ), type );
479                        stmt->target = makeLabel( stmt, node->target );
480                }
481                return stmtPostamble( stmt, node );
482        }
483
484        const ast::Stmt * visit( const ast::ReturnStmt * node ) override final {
485                if ( inCache( node ) ) return nullptr;
486                auto stmt = new ReturnStmt( get<Expression>().accept1( node->expr ) );
487                return stmtPostamble( stmt, node );
488        }
489
490        const ast::Stmt * visit( const ast::ThrowStmt * node ) override final {
491                if ( inCache( node ) ) return nullptr;
492                ThrowStmt::Kind kind;
493                switch (node->kind) {
494                case ast::ExceptionKind::Terminate:
495                        kind = ThrowStmt::Terminate;
496                        break;
497                case ast::ExceptionKind::Resume:
498                        kind = ThrowStmt::Resume;
499                        break;
500                default:
501                        assertf(false, "Invalid ast::ThrowStmt::Kind: %d\n", node->kind);
502                }
503                auto stmt = new ThrowStmt(
504                        kind,
505                        get<Expression>().accept1( node->expr ),
506                        get<Expression>().accept1( node->target )
507                );
508                return stmtPostamble( stmt, node );
509        }
510
511        const ast::Stmt * visit( const ast::TryStmt * node ) override final {
512                if ( inCache( node ) ) return nullptr;
513                auto handlers = get<CatchStmt>().acceptL( node->handlers );
514                auto stmt = new TryStmt(
515                        get<CompoundStmt>().accept1( node->body ),
516                        handlers,
517                        get<FinallyStmt>().accept1( node->finally )
518                );
519                return stmtPostamble( stmt, node );
520        }
521
522        const ast::CatchClause * visit( const ast::CatchClause * node ) override final {
523                if ( inCache( node ) ) return nullptr;
524                CatchStmt::Kind kind;
525                switch (node->kind) {
526                case ast::ExceptionKind::Terminate:
527                        kind = CatchStmt::Terminate;
528                        break;
529                case ast::ExceptionKind::Resume:
530                        kind = CatchStmt::Resume;
531                        break;
532                default:
533                        assertf(false, "Invalid ast::ExceptionKind: %d\n", node->kind);
534                }
535                auto stmt = new CatchStmt(
536                        kind,
537                        get<Declaration>().accept1( node->decl ),
538                        get<Expression>().accept1( node->cond ),
539                        get<Statement>().accept1( node->body )
540                );
541                return clausePostamble( stmt, node ), nullptr;
542        }
543
544        const ast::FinallyClause * visit( const ast::FinallyClause * node ) override final {
545                if ( inCache( node ) ) return nullptr;
546                auto stmt = new FinallyStmt( get<CompoundStmt>().accept1( node->body ) );
547                return clausePostamble( stmt, node ), nullptr;
548        }
549
550        const ast::Stmt * visit(const ast::SuspendStmt * node ) override final {
551                if ( inCache( node ) ) return nullptr;
552                auto stmt = new SuspendStmt();
553                stmt->then   = get<CompoundStmt>().accept1( node->then   );
554                switch(node->type) {
555                        case ast::SuspendStmt::None     : stmt->type = SuspendStmt::None     ; break;
556                        case ast::SuspendStmt::Coroutine: stmt->type = SuspendStmt::Coroutine; break;
557                        case ast::SuspendStmt::Generator: stmt->type = SuspendStmt::Generator; break;
558                }
559                return stmtPostamble( stmt, node );
560        }
561
562        const ast::Stmt * visit( const ast::WaitForStmt * node ) override final {
563                if ( inCache( node ) ) return nullptr;
564                auto stmt = new WaitForStmt;
565                stmt->clauses.reserve( node->clauses.size() );
566                for ( auto clause : node->clauses ) {
567                        stmt->clauses.push_back({{
568                                        get<Expression>().accept1( clause->target_func ),
569                                        get<Expression>().acceptL( clause->target_args ),
570                                },
571                                get<Statement>().accept1( clause->stmt ),
572                                get<Expression>().accept1( clause->cond ),
573                        });
574                }
575                stmt->timeout = {
576                        get<Expression>().accept1( node->timeout_time ),
577                        get<Statement>().accept1( node->timeout_stmt ),
578                        get<Expression>().accept1( node->timeout_cond ),
579                };
580                stmt->orelse = {
581                        get<Statement>().accept1( node->else_stmt ),
582                        get<Expression>().accept1( node->else_cond ),
583                };
584                return stmtPostamble( stmt, node );
585        }
586
587        const ast::WaitForClause * visit( const ast::WaitForClause * node ) override final {
588                // There is no old-AST WaitForClause, so this should never be called.
589                assert( !node );
590                return nullptr;
591        }
592
593        const ast::Decl * visit( const ast::WithStmt * node ) override final {
594                if ( inCache( node ) ) return nullptr;
595                auto stmt = new WithStmt(
596                        get<Expression>().acceptL( node->exprs ),
597                        get<Statement>().accept1( node->stmt )
598                );
599                declPostamble( stmt, node );
600                return nullptr;
601        }
602
603        const ast::NullStmt * visit( const ast::NullStmt * node ) override final {
604                if ( inCache( node ) ) return nullptr;
605                auto stmt = new NullStmt();
606                stmtPostamble( stmt, node );
607                return nullptr;
608        }
609
610        const ast::Stmt * visit( const ast::DeclStmt * node ) override final {
611                if ( inCache( node ) ) return nullptr;
612                auto stmt = new DeclStmt( get<Declaration>().accept1( node->decl ) );
613                return stmtPostamble( stmt, node );
614        }
615
616        const ast::Stmt * visit( const ast::ImplicitCtorDtorStmt * node ) override final {
617                if ( inCache( node ) ) return nullptr;
618                auto stmt = new ImplicitCtorDtorStmt{
619                        get<Statement>().accept1( node->callStmt )
620                };
621                return stmtPostamble( stmt, node );
622        }
623
624        const ast::Stmt * visit( const ast::MutexStmt * node ) override final {
625                if ( inCache( node ) ) return nullptr;
626                 auto stmt = new MutexStmt(
627                        get<Statement>().accept1( node->stmt ),
628                        get<Expression>().acceptL( node->mutexObjs )
629                );
630                return stmtPostamble( stmt, node );
631        }
632
633        TypeSubstitution * convertTypeSubstitution(const ast::TypeSubstitution * src) {
634
635                if (!src) return nullptr;
636
637                TypeSubstitution *rslt = new TypeSubstitution();
638
639                for (decltype(src->begin()) src_i = src->begin(); src_i != src->end(); src_i++) {
640                        rslt->add( src_i->first.typeString(),
641                                   get<Type>().accept1(src_i->second) );
642                }
643
644                return rslt;
645        }
646
647        void convertInferUnion(std::map<UniqueId,ParamEntry> &tgtInferParams,
648                                                   std::vector<UniqueId>         &tgtResnSlots,
649                                                   const ast::Expr::InferUnion   &srcInferred ) {
650
651                assert( tgtInferParams.empty() );
652                assert( tgtResnSlots.empty() );
653
654                if ( srcInferred.data.inferParams ) {
655                        const ast::InferredParams &srcParams = srcInferred.inferParams();
656                        for (auto & srcParam : srcParams) {
657                                auto res = tgtInferParams.emplace(srcParam.first, ParamEntry(
658                                        srcParam.second.decl,
659                                        get<Declaration>().accept1(srcParam.second.declptr),
660                                        get<Type>().accept1(srcParam.second.actualType)->clone(),
661                                        get<Type>().accept1(srcParam.second.formalType)->clone(),
662                                        get<Expression>().accept1(srcParam.second.expr)->clone()
663                                ));
664                                assert(res.second);
665                        }
666                }
667                if ( srcInferred.data.resnSlots ) {
668                        const ast::ResnSlots &srcSlots = srcInferred.resnSlots();
669                        for (auto srcSlot : srcSlots) {
670                                tgtResnSlots.push_back(srcSlot);
671                        }
672                }
673        }
674
675        Expression * visitBaseExpr_skipResultType(const ast::Expr * src, Expression * tgt) {
676
677                tgt->location  = src->location;
678                tgt->env       = convertTypeSubstitution(src->env);
679                tgt->extension = src->extension;
680
681                convertInferUnion(tgt->inferParams, tgt->resnSlots, src->inferred);
682                return tgt;
683        }
684
685        Expression * visitBaseExpr(const ast::Expr * src, Expression * tgt) {
686
687                tgt->result = get<Type>().accept1(src->result);
688                // Unconditionally use a clone of the result type.
689                // We know this will leak some objects: much of the immediate conversion result.
690                // In some cases, using the conversion result directly gives unintended object sharing.
691                // A parameter (ObjectDecl, a child of a FunctionType) is shared by the weak-ref cache.
692                // But tgt->result must be fully owned privately by tgt.
693                // Applying these conservative copies here means
694                // - weak references point at the declaration's copy, not these expr.result copies (good)
695                // - we copy more objects than really needed (bad, tolerated)
696                if (tgt->result) {
697                        tgt->result = tgt->result->clone();
698                }
699                return visitBaseExpr_skipResultType(src, tgt);
700        }
701
702        const ast::Expr * visit( const ast::ApplicationExpr * node ) override final {
703                auto expr = visitBaseExpr( node,
704                        new ApplicationExpr(
705                                get<Expression>().accept1(node->func),
706                                get<Expression>().acceptL(node->args)
707                        )
708                );
709                this->node = expr;
710                return nullptr;
711        }
712
713        const ast::Expr * visit( const ast::UntypedExpr * node ) override final {
714                auto expr = visitBaseExpr( node,
715                        new UntypedExpr(
716                                get<Expression>().accept1(node->func),
717                                get<Expression>().acceptL(node->args)
718                        )
719                );
720                this->node = expr;
721                return nullptr;
722        }
723
724        const ast::Expr * visit( const ast::NameExpr * node ) override final {
725                auto expr = visitBaseExpr( node,
726                        new NameExpr(
727                                node->name
728                        )
729                );
730                this->node = expr;
731                return nullptr;
732        }
733
734        const ast::Expr * visit( const ast::QualifiedNameExpr * node ) override final {
735                auto temp = new QualifiedNameExpr(
736                                get<Declaration>().accept1(node->type_decl),
737                                node->name
738                );
739                auto expr = visitBaseExpr( node,
740                        temp
741                );
742                this->node = expr;
743                return nullptr;
744        }
745
746        const ast::Expr * visit( const ast::AddressExpr * node ) override final {
747                auto expr = visitBaseExpr( node,
748                        new AddressExpr(
749                                get<Expression>().accept1(node->arg)
750                        )
751                );
752                this->node = expr;
753                return nullptr;
754        }
755
756        const ast::Expr * visit( const ast::LabelAddressExpr * node ) override final {
757                auto expr = visitBaseExpr( node,
758                        new LabelAddressExpr(
759                                makeLabel(nullptr, node->arg)
760                        )
761                );
762                this->node = expr;
763                return nullptr;
764        }
765
766        const ast::Expr * visit( const ast::CastExpr * node ) override final {
767                auto expr = visitBaseExpr( node,
768                        new CastExpr(
769                                get<Expression>().accept1(node->arg),
770                                (node->isGenerated == ast::GeneratedCast)
771                        )
772                );
773                this->node = expr;
774                return nullptr;
775        }
776
777        const ast::Expr * visit( const ast::KeywordCastExpr * node ) override final {
778                AggregateDecl::Aggregate castTarget = (AggregateDecl::Aggregate)node->target;
779                assert( AggregateDecl::Generator <= castTarget && castTarget <= AggregateDecl::Thread );
780                auto expr = visitBaseExpr( node,
781                        new KeywordCastExpr(
782                                get<Expression>().accept1(node->arg),
783                                castTarget,
784                                {node->concrete_target.field, node->concrete_target.getter}
785                        )
786                );
787                this->node = expr;
788                return nullptr;
789        }
790
791        const ast::Expr * visit( const ast::VirtualCastExpr * node ) override final {
792                auto expr = visitBaseExpr_skipResultType( node,
793                        new VirtualCastExpr(
794                                get<Expression>().accept1(node->arg),
795                                get<Type>().accept1(node->result)
796                        )
797                );
798                this->node = expr;
799                return nullptr;
800        }
801
802        const ast::Expr * visit( const ast::UntypedMemberExpr * node ) override final {
803                auto expr = visitBaseExpr( node,
804                        new UntypedMemberExpr(
805                                get<Expression>().accept1(node->member),
806                                get<Expression>().accept1(node->aggregate)
807                        )
808                );
809                this->node = expr;
810                return nullptr;
811        }
812
813        const ast::Expr * visit( const ast::MemberExpr * node ) override final {
814                auto expr = visitBaseExpr( node,
815                        new MemberExpr(
816                                get<DeclarationWithType>().accept1(node->member),
817                                get<Expression>().accept1(node->aggregate)
818                        )
819                );
820                this->node = expr;
821                return nullptr;
822        }
823
824        const ast::Expr * visit( const ast::VariableExpr * node ) override final {
825                auto expr = new VariableExpr();
826                expr->var = get<DeclarationWithType>().accept1(node->var);
827                visitBaseExpr( node, expr );
828                this->node = expr;
829                return nullptr;
830        }
831
832        const ast::Expr * visit( const ast::ConstantExpr * node ) override final {
833                // Old world:   two types: rslt->constant.type, rslt->result
834                // New workd:   one public type: node->result, plus node->underlyer only to support roundtrip conversion
835                //              preserving underlyer because the correct type for string literals is complicated to construct,
836            //              and distinguishing a string from other literals using the type is hard to do accurately
837                // Both worlds: the outer, expression-level type can change during resolution
838                //              for a string, that's char[k] before-resolve and char * after
839                // Old world:   the inner Constant type stays what it was built with
840                //              for a string, that's char[k] always
841                // Both worlds: the "rep" field of a constant is the C source file fragment that compiles to the desired value
842        //              for a string, that includes outer quotes, backslashes, et al cases from the Literals test
843                ConstantExpr *rslt = new ConstantExpr(Constant(
844                        get<Type>().accept1(node->underlyer),
845                        node->rep,
846                        node->ival));
847                auto expr = visitBaseExpr( node, rslt );
848                this->node = expr;
849                return nullptr;
850        }
851
852        const ast::Expr * visit( const ast::SizeofExpr * node ) override final {
853                assert (node->expr || node->type);
854                assert (! (node->expr && node->type));
855                SizeofExpr *rslt;
856                if (node->expr) {
857                        rslt = new SizeofExpr(
858                                get<Expression>().accept1(node->expr)
859                        );
860                        assert (!rslt->isType);
861                }
862                else {
863                        assert(node->type);
864                        rslt = new SizeofExpr(
865                                get<Type>().accept1(node->type)
866                        );
867                        assert (rslt->isType);
868                }
869                auto expr = visitBaseExpr( node, rslt );
870                this->node = expr;
871                return nullptr;
872        }
873
874        const ast::Expr * visit( const ast::AlignofExpr * node ) override final {
875                assert (node->expr || node->type);
876                assert (! (node->expr && node->type));
877                AlignofExpr *rslt;
878                if (node->expr) {
879                        rslt = new AlignofExpr(
880                                get<Expression>().accept1(node->expr)
881                        );
882                        assert (!rslt->isType);
883                }
884                else {
885                        assert(node->type);
886                        rslt = new AlignofExpr(
887                                get<Type>().accept1(node->type)
888                        );
889                        assert (rslt->isType);
890                }
891                auto expr = visitBaseExpr( node, rslt );
892                this->node = expr;
893                return nullptr;
894        }
895
896        const ast::Expr * visit( const ast::UntypedOffsetofExpr * node ) override final {
897                auto expr = visitBaseExpr( node,
898                        new UntypedOffsetofExpr(
899                                get<Type>().accept1(node->type),
900                                node->member
901                        )
902                );
903                this->node = expr;
904                return nullptr;
905        }
906
907        const ast::Expr * visit( const ast::OffsetofExpr * node ) override final {
908                auto expr = visitBaseExpr( node,
909                        new OffsetofExpr(
910                                get<Type>().accept1(node->type),
911                                get<DeclarationWithType>().accept1(node->member)
912                        )
913                );
914                this->node = expr;
915                return nullptr;
916        }
917
918        const ast::Expr * visit( const ast::OffsetPackExpr * node ) override final {
919                auto expr = visitBaseExpr( node,
920                        new OffsetPackExpr(
921                                get<StructInstType>().accept1(node->type)
922                        )
923                );
924                this->node = expr;
925                return nullptr;
926        }
927
928        const ast::Expr * visit( const ast::LogicalExpr * node ) override final {
929                assert (node->isAnd == ast::LogicalFlag::AndExpr ||
930                                node->isAnd == ast::LogicalFlag::OrExpr );
931                auto expr = visitBaseExpr( node,
932                        new LogicalExpr(
933                                get<Expression>().accept1(node->arg1),
934                                get<Expression>().accept1(node->arg2),
935                                (node->isAnd == ast::LogicalFlag::AndExpr)
936                        )
937                );
938                this->node = expr;
939                return nullptr;
940        }
941
942        const ast::Expr * visit( const ast::ConditionalExpr * node ) override final {
943                auto expr = visitBaseExpr( node,
944                        new ConditionalExpr(
945                                get<Expression>().accept1(node->arg1),
946                                get<Expression>().accept1(node->arg2),
947                                get<Expression>().accept1(node->arg3)
948                        )
949                );
950                this->node = expr;
951                return nullptr;
952        }
953
954        const ast::Expr * visit( const ast::CommaExpr * node ) override final {
955                auto expr = visitBaseExpr( node,
956                        new CommaExpr(
957                                get<Expression>().accept1(node->arg1),
958                                get<Expression>().accept1(node->arg2)
959                        )
960                );
961                this->node = expr;
962                return nullptr;
963        }
964
965        const ast::Expr * visit( const ast::TypeExpr * node ) override final {
966                auto expr = visitBaseExpr( node,
967                        new TypeExpr(
968                                get<Type>().accept1(node->type)
969                        )
970                );
971                this->node = expr;
972                return nullptr;
973        }
974
975        const ast::Expr * visit( const ast::DimensionExpr * node ) override final {
976                auto expr = visitBaseExpr( node, new DimensionExpr( node->name ) );
977                this->node = expr;
978                return nullptr;
979        }
980
981        const ast::Expr * visit( const ast::AsmExpr * node ) override final {
982                auto expr = visitBaseExpr( node,
983                        new AsmExpr(
984                                new std::string(node->inout),
985                                get<Expression>().accept1(node->constraint),
986                                get<Expression>().accept1(node->operand)
987                        )
988                );
989                this->node = expr;
990                return nullptr;
991        }
992
993        const ast::Expr * visit( const ast::ImplicitCopyCtorExpr * node ) override final {
994                auto rslt = new ImplicitCopyCtorExpr(
995                        get<ApplicationExpr>().accept1(node->callExpr)
996                );
997
998                auto expr = visitBaseExpr( node, rslt );
999                this->node = expr;
1000                return nullptr;
1001        }
1002
1003        const ast::Expr * visit( const ast::ConstructorExpr * node ) override final {
1004                auto expr = visitBaseExpr( node,
1005                        new ConstructorExpr(
1006                                get<Expression>().accept1(node->callExpr)
1007                        )
1008                );
1009                this->node = expr;
1010                return nullptr;
1011        }
1012
1013        const ast::Expr * visit( const ast::CompoundLiteralExpr * node ) override final {
1014                auto expr = visitBaseExpr_skipResultType( node,
1015                        new CompoundLiteralExpr(
1016                                get<Type>().accept1(node->result),
1017                                get<Initializer>().accept1(node->init)
1018                        )
1019                );
1020                this->node = expr;
1021                return nullptr;
1022        }
1023
1024        const ast::Expr * visit( const ast::RangeExpr * node ) override final {
1025                auto expr = visitBaseExpr( node,
1026                        new RangeExpr(
1027                                get<Expression>().accept1(node->low),
1028                                get<Expression>().accept1(node->high)
1029                        )
1030                );
1031                this->node = expr;
1032                return nullptr;
1033        }
1034
1035        const ast::Expr * visit( const ast::UntypedTupleExpr * node ) override final {
1036                auto expr = visitBaseExpr( node,
1037                        new UntypedTupleExpr(
1038                                get<Expression>().acceptL(node->exprs)
1039                        )
1040                );
1041                this->node = expr;
1042                return nullptr;
1043        }
1044
1045        const ast::Expr * visit( const ast::TupleExpr * node ) override final {
1046                auto expr = visitBaseExpr( node,
1047                        new TupleExpr(
1048                                get<Expression>().acceptL(node->exprs)
1049                        )
1050                );
1051                this->node = expr;
1052                return nullptr;
1053        }
1054
1055        const ast::Expr * visit( const ast::TupleIndexExpr * node ) override final {
1056                auto expr = visitBaseExpr( node,
1057                        new TupleIndexExpr(
1058                                get<Expression>().accept1(node->tuple),
1059                                node->index
1060                        )
1061                );
1062                this->node = expr;
1063                return nullptr;
1064        }
1065
1066        const ast::Expr * visit( const ast::TupleAssignExpr * node ) override final {
1067                auto expr = visitBaseExpr( node,
1068                        new TupleAssignExpr(
1069                                get<StmtExpr>().accept1(node->stmtExpr)
1070                        )
1071                );
1072                this->node = expr;
1073                return nullptr;
1074        }
1075
1076        const ast::Expr * visit( const ast::StmtExpr * node ) override final {
1077                auto rslt = new StmtExpr(
1078                        get<CompoundStmt>().accept1(node->stmts)
1079                );
1080
1081                rslt->returnDecls = get<ObjectDecl>().acceptL(node->returnDecls);
1082                rslt->dtors       = get<Expression>().acceptL(node->dtors);
1083
1084                // is this even used after convert?
1085                //if (tmp->resultExpr) {
1086                //      // this MUST be found by children visit
1087                //      rslt->resultExpr  = strict_dynamic_cast<ExprStmt *>(readonlyCache.at(tmp->resultExpr));
1088                //}
1089
1090                auto expr = visitBaseExpr( node, rslt );
1091                this->node = expr;
1092                return nullptr;
1093        }
1094
1095        const ast::Expr * visit( const ast::UniqueExpr * node ) override final {
1096                auto rslt = new UniqueExpr(
1097                        get<Expression>().accept1(node->expr),
1098                        node->id
1099                );
1100
1101                rslt->object = get<ObjectDecl>  ().accept1(node->object);
1102                rslt->var    = get<VariableExpr>().accept1(node->var);
1103
1104                auto expr = visitBaseExpr( node, rslt );
1105                this->node = expr->clone();
1106                return nullptr;
1107        }
1108
1109        const ast::Expr * visit( const ast::UntypedInitExpr * node ) override final {
1110                std::list<InitAlternative> initAlts;
1111                for (auto ia : node->initAlts) {
1112                        initAlts.push_back(InitAlternative(
1113                                get<Type>       ().accept1(ia.type),
1114                                get<Designation>().accept1(ia.designation)
1115                        ));
1116                }
1117                auto expr = visitBaseExpr( node,
1118                        new UntypedInitExpr(
1119                                get<Expression>().accept1(node->expr),
1120                                initAlts
1121                        )
1122                );
1123                this->node = expr;
1124                return nullptr;
1125        }
1126
1127        const ast::Expr * visit( const ast::InitExpr * node ) override final {
1128                auto expr = visitBaseExpr( node,
1129                        new InitExpr(
1130                                get<Expression>().accept1(node->expr),
1131                                get<Designation>().accept1(node->designation)
1132                        )
1133                );
1134                this->node = expr;
1135                return nullptr;
1136        }
1137
1138        const ast::Expr * visit( const ast::DeletedExpr * node ) override final {
1139                auto expr = visitBaseExpr( node,
1140                        new DeletedExpr(
1141                                get<Expression>().accept1(node->expr),
1142                                inCache(node->deleteStmt) ?
1143                                        strict_dynamic_cast<Declaration*>(this->node) :
1144                                        get<Declaration>().accept1(node->deleteStmt)
1145                        )
1146                );
1147                this->node = expr;
1148                return nullptr;
1149        }
1150
1151        const ast::Expr * visit( const ast::DefaultArgExpr * node ) override final {
1152                auto expr = visitBaseExpr( node,
1153                        new DefaultArgExpr(
1154                                get<Expression>().accept1(node->expr)
1155                        )
1156                );
1157                this->node = expr;
1158                return nullptr;
1159        }
1160
1161        const ast::Expr * visit( const ast::GenericExpr * node ) override final {
1162                std::list<GenericExpr::Association> associations;
1163                for (auto association : node->associations) {
1164                        associations.push_back(GenericExpr::Association(
1165                                get<Type>      ().accept1(association.type),
1166                                get<Expression>().accept1(association.expr)
1167                        ));
1168                }
1169                auto expr = visitBaseExpr( node,
1170                        new GenericExpr(
1171                                get<Expression>().accept1(node->control),
1172                                associations
1173                        )
1174                );
1175                this->node = expr;
1176                return nullptr;
1177        }
1178
1179        const ast::Type * visitType( const ast::Type * node, Type * type ) {
1180                // Some types do this in their constructor so add a check.
1181                if ( !node->attributes.empty() && type->attributes.empty() ) {
1182                        type->attributes = get<Attribute>().acceptL( node->attributes );
1183                }
1184                this->node = type;
1185                return nullptr;
1186        }
1187
1188        const ast::Type * visit( const ast::VoidType * node ) override final {
1189                return visitType( node, new VoidType{ cv( node ) } );
1190        }
1191
1192        const ast::Type * visit( const ast::BasicType * node ) override final {
1193                auto type = new BasicType{ cv( node ), (BasicType::Kind)(unsigned)node->kind };
1194                // I believe this should always be a BasicType.
1195                if ( ast::sizeType == node ) {
1196                        Validate::SizeType = type;
1197                }
1198                return visitType( node, type );
1199        }
1200
1201        const ast::Type * visit( const ast::PointerType * node ) override final {
1202                return visitType( node, new PointerType{
1203                        cv( node ),
1204                        get<Type>().accept1( node->base ),
1205                        get<Expression>().accept1( node->dimension ),
1206                        (bool)node->isVarLen,
1207                        (bool)node->isStatic
1208                } );
1209        }
1210
1211        const ast::Type * visit( const ast::ArrayType * node ) override final {
1212                return visitType( node, new ArrayType{
1213                        cv( node ),
1214                        get<Type>().accept1( node->base ),
1215                        get<Expression>().accept1( node->dimension ),
1216                        (bool)node->isVarLen,
1217                        (bool)node->isStatic
1218                } );
1219        }
1220
1221        const ast::Type * visit( const ast::ReferenceType * node ) override final {
1222                return visitType( node, new ReferenceType{
1223                        cv( node ),
1224                        get<Type>().accept1( node->base )
1225                } );
1226        }
1227
1228        const ast::Type * visit( const ast::QualifiedType * node ) override final {
1229                return visitType( node, new QualifiedType{
1230                        cv( node ),
1231                        get<Type>().accept1( node->parent ),
1232                        get<Type>().accept1( node->child )
1233                } );
1234        }
1235
1236        const ast::Type * visit( const ast::FunctionType * node ) override final {
1237                static std::string dummy_paramvar_prefix = "__param_";
1238                static std::string dummy_returnvar_prefix = "__retval_";
1239
1240                auto ty = new FunctionType {
1241                        cv( node ),
1242                        (bool)node->isVarArgs
1243                };
1244                auto returns = get<Type>().acceptL(node->returns);
1245                auto params = get<Type>().acceptL(node->params);
1246
1247                int ret_index = 0;
1248                for (auto t: returns) {
1249                        // xxx - LinkageSpec shouldn't matter but needs to be something
1250                        ObjectDecl * dummy = new ObjectDecl(dummy_returnvar_prefix + std::to_string(ret_index++), {}, LinkageSpec::C, nullptr, t, nullptr);
1251                        ty->returnVals.push_back(dummy);
1252                }
1253                int param_index = 0;
1254                for (auto t: params) {
1255                        ObjectDecl * dummy = new ObjectDecl(dummy_paramvar_prefix + std::to_string(param_index++), {}, LinkageSpec::C, nullptr, t, nullptr);
1256                        ty->parameters.push_back(dummy);
1257                }
1258
1259                // ty->returnVals = get<DeclarationWithType>().acceptL( node->returns );
1260                // ty->parameters = get<DeclarationWithType>().acceptL( node->params );
1261
1262                auto types = get<TypeInstType>().acceptL( node->forall );
1263                for (auto t : types) {
1264                        auto newT = new TypeDecl(*t->baseType);
1265                        newT->name = t->name; // converted by typeString()
1266                        for (auto asst : newT->assertions) delete asst;
1267                        newT->assertions.clear();
1268                        ty->forall.push_back(newT);
1269                }
1270                auto assts = get<VariableExpr>().acceptL( node->assertions );
1271                if (!assts.empty()) {
1272                        assert(!types.empty());
1273                        for (auto asst : assts) {
1274                                auto newDecl = new ObjectDecl(*strict_dynamic_cast<ObjectDecl*>(asst->var));
1275                                delete newDecl->type;
1276                                newDecl->type = asst->result->clone();
1277                                newDecl->storageClasses.is_extern = true; // hack
1278                                ty->forall.back()->assertions.push_back(newDecl);
1279                        }
1280                }
1281
1282                return visitType( node, ty );
1283        }
1284
1285        const ast::Type * postvisit( const ast::BaseInstType * old, ReferenceToType * ty ) {
1286                ty->parameters = get<Expression>().acceptL( old->params );
1287                ty->hoistType = old->hoistType;
1288                return visitType( old, ty );
1289        }
1290
1291        const ast::Type * visit( const ast::StructInstType * node ) override final {
1292                StructInstType * ty;
1293                if ( node->base ) {
1294                        ty = new StructInstType{
1295                                cv( node ),
1296                                get<StructDecl>().accept1( node->base ),
1297                                get<Attribute>().acceptL( node->attributes )
1298                        };
1299                } else {
1300                        ty = new StructInstType{
1301                                cv( node ),
1302                                node->name,
1303                                get<Attribute>().acceptL( node->attributes )
1304                        };
1305                }
1306                return postvisit( node, ty );
1307        }
1308
1309        const ast::Type * visit( const ast::UnionInstType * node ) override final {
1310                UnionInstType * ty;
1311                if ( node->base ) {
1312                        ty = new UnionInstType{
1313                                cv( node ),
1314                                get<UnionDecl>().accept1( node->base ),
1315                                get<Attribute>().acceptL( node->attributes )
1316                        };
1317                } else {
1318                        ty = new UnionInstType{
1319                                cv( node ),
1320                                node->name,
1321                                get<Attribute>().acceptL( node->attributes )
1322                        };
1323                }
1324                return postvisit( node, ty );
1325        }
1326
1327        const ast::Type * visit( const ast::EnumInstType * node ) override final {
1328                EnumInstType * ty;
1329                if ( node->base ) {
1330                        ty = new EnumInstType{
1331                                cv( node ),
1332                                get<EnumDecl>().accept1( node->base ),
1333                                get<Attribute>().acceptL( node->attributes )
1334                        };
1335                } else {
1336                        ty = new EnumInstType{
1337                                cv( node ),
1338                                node->name,
1339                                get<Attribute>().acceptL( node->attributes )
1340                        };
1341                }
1342                return postvisit( node, ty );
1343        }
1344
1345        const ast::Type * visit( const ast::TraitInstType * node ) override final {
1346                TraitInstType * ty;
1347                if ( node->base ) {
1348                        ty = new TraitInstType{
1349                                cv( node ),
1350                                get<TraitDecl>().accept1( node->base ),
1351                                get<Attribute>().acceptL( node->attributes )
1352                        };
1353                } else {
1354                        ty = new TraitInstType{
1355                                cv( node ),
1356                                node->name,
1357                                get<Attribute>().acceptL( node->attributes )
1358                        };
1359                }
1360                return postvisit( node, ty );
1361        }
1362
1363        const ast::Type * visit( const ast::TypeInstType * node ) override final {
1364                TypeInstType * ty;
1365                if ( node->base ) {
1366                        ty = new TypeInstType{
1367                                cv( node ),
1368                                node->typeString(),
1369                                get<TypeDecl>().accept1( node->base ),
1370                                get<Attribute>().acceptL( node->attributes )
1371                        };
1372                } else {
1373                        ty = new TypeInstType{
1374                                cv( node ),
1375                                node->typeString(),
1376                                node->kind == ast::TypeDecl::Ftype,
1377                                get<Attribute>().acceptL( node->attributes )
1378                        };
1379                }
1380                return postvisit( node, ty );
1381        }
1382
1383        const ast::Type * visit( const ast::TupleType * node ) override final {
1384                return visitType( node, new TupleType{
1385                        cv( node ),
1386                        get<Type>().acceptL( node->types )
1387                        // members generated by TupleType c'tor
1388                } );
1389        }
1390
1391        const ast::Type * visit( const ast::TypeofType * node ) override final {
1392                return visitType( node, new TypeofType{
1393                        cv( node ),
1394                        get<Expression>().accept1( node->expr ),
1395                        (bool)node->kind
1396                } );
1397        }
1398
1399        const ast::Type * visit( const ast::VTableType * node ) override final {
1400                return visitType( node, new VTableType{
1401                        cv( node ),
1402                        get<Type>().accept1( node->base )
1403                } );
1404        }
1405
1406        const ast::Type * visit( const ast::VarArgsType * node ) override final {
1407                return visitType( node, new VarArgsType{ cv( node ) } );
1408        }
1409
1410        const ast::Type * visit( const ast::ZeroType * node ) override final {
1411                return visitType( node, new ZeroType{ cv( node ) } );
1412        }
1413
1414        const ast::Type * visit( const ast::OneType * node ) override final {
1415                return visitType( node, new OneType{ cv( node ) } );
1416        }
1417
1418        const ast::Type * visit( const ast::GlobalScopeType * node ) override final {
1419                return visitType( node, new GlobalScopeType{} );
1420        }
1421
1422        const ast::Designation * visit( const ast::Designation * node ) override final {
1423                auto designation = new Designation( get<Expression>().acceptL( node->designators ) );
1424                designation->location = node->location;
1425                this->node = designation;
1426                return nullptr;
1427        }
1428
1429        const ast::Init * visit( const ast::SingleInit * node ) override final {
1430                auto init = new SingleInit(
1431                        get<Expression>().accept1( node->value ),
1432                        ast::MaybeConstruct == node->maybeConstructed
1433                );
1434                init->location = node->location;
1435                this->node = init;
1436                return nullptr;
1437        }
1438
1439        const ast::Init * visit( const ast::ListInit * node ) override final {
1440                auto init = new ListInit(
1441                        get<Initializer>().acceptL( node->initializers ),
1442                        get<Designation>().acceptL( node->designations ),
1443                        ast::MaybeConstruct == node->maybeConstructed
1444                );
1445                init->location = node->location;
1446                this->node = init;
1447                return nullptr;
1448        }
1449
1450        const ast::Init * visit( const ast::ConstructorInit * node ) override final {
1451                auto init = new ConstructorInit(
1452                        get<Statement>().accept1( node->ctor ),
1453                        get<Statement>().accept1( node->dtor ),
1454                        get<Initializer>().accept1( node->init )
1455                );
1456                init->location = node->location;
1457                this->node = init;
1458                return nullptr;
1459        }
1460
1461        const ast::Attribute * visit( const ast::Attribute * node ) override final {
1462                auto attr = new Attribute(
1463                        node->name,
1464                        get<Expression>().acceptL(node->params)
1465                );
1466                this->node = attr;
1467                return nullptr;
1468        }
1469
1470        const ast::TypeSubstitution * visit( const ast::TypeSubstitution * node ) override final {
1471                // Handled by convertTypeSubstitution helper instead.
1472                // TypeSubstitution is not a node in the old model, so the conversion result wouldn't fit in this->node.
1473                assert( 0 );
1474                (void)node;
1475                return nullptr;
1476        }
1477};
1478
1479std::list< Declaration * > convert( const ast::TranslationUnit && translationUnit ) {
1480        // Copy values from the global store to the local static variables.
1481        ast::sizeType = translationUnit.global.sizeType;
1482        ast::dereferenceOperator = translationUnit.global.dereference;
1483        ast::dtorStruct = translationUnit.global.dtorStruct;
1484        ast::dtorStructDestroy = translationUnit.global.dtorDestroy;
1485
1486        ConverterNewToOld c;
1487        std::list< Declaration * > decls;
1488        for(auto d : translationUnit.decls) {
1489                decls.emplace_back( c.decl( d ) );
1490        }
1491        return decls;
1492}
1493
1494//================================================================================================
1495
1496class ConverterOldToNew : public Visitor {
1497public:
1498        ast::Decl * decl() {
1499                return strict_dynamic_cast< ast::Decl * >( node );
1500        }
1501       
1502        ConverterOldToNew() = default;
1503        ConverterOldToNew(const ConverterOldToNew &) = delete;
1504        ConverterOldToNew(ConverterOldToNew &&) = delete;
1505private:
1506        /// conversion output
1507        ast::Node * node = nullptr;
1508        /// cache of nodes that might be referenced by readonly<> for de-duplication
1509        /// in case that some nodes are dropped by conversion (due to possible structural change)
1510        /// use smart pointers in cache value to prevent accidental invalidation.
1511        /// at conversion stage, all created nodes are guaranteed to be unique, therefore
1512        /// const_casting out of smart pointers is permitted.
1513        std::unordered_map< const BaseSyntaxNode *, ast::readonly<ast::Node> > cache = {};
1514
1515        // Local Utilities:
1516
1517        template<typename NewT, typename OldT>
1518        NewT * getAccept1( OldT old ) {
1519                if ( ! old ) return nullptr;
1520                old->accept(*this);
1521                ast::Node * ret = node;
1522                node = nullptr;
1523                return strict_dynamic_cast< NewT * >( ret );
1524        }
1525
1526#       define GET_ACCEPT_1(child, type) \
1527                getAccept1< ast::type, decltype( old->child ) >( old->child )
1528
1529
1530        template<typename NewT, typename OldC>
1531        std::vector< ast::ptr<NewT> > getAcceptV( const OldC& old ) {
1532                std::vector< ast::ptr<NewT> > ret;
1533                ret.reserve( old.size() );
1534                for ( auto a : old ) {
1535                        a->accept( *this );
1536                        ret.emplace_back( strict_dynamic_cast< NewT * >(node) );
1537                        node = nullptr;
1538                }
1539                return ret;
1540        }
1541
1542#       define GET_ACCEPT_V(child, type) \
1543                getAcceptV< ast::type, decltype( old->child ) >( old->child )
1544
1545#       define GET_ACCEPT_E(child, type) \
1546                getAccept1< ast::type, decltype( old->base ) >( old->base )
1547
1548        template<typename NewT, typename OldC>
1549        std::deque< ast::ptr<NewT> > getAcceptD( const OldC& old ) {
1550                std::deque< ast::ptr<NewT> > ret;
1551                for ( auto a : old ) {
1552                        a->accept( *this );
1553                        ret.emplace_back( strict_dynamic_cast< NewT * >(node) );
1554                        node = nullptr;
1555                }
1556                return ret;
1557        }
1558
1559#       define GET_ACCEPT_D(child, type) \
1560                getAcceptD< ast::type, decltype( old->child ) >( old->child )
1561
1562        ast::Label make_label(const Label* old) {
1563                CodeLocation const & location =
1564                    ( old->labelled ) ? old->labelled->location : CodeLocation();
1565                return ast::Label(
1566                        location,
1567                        old->name,
1568                        GET_ACCEPT_V(attributes, Attribute)
1569                );
1570        }
1571
1572        template<template <class...> class C>
1573        C<ast::Label> make_labels(C<Label> olds) {
1574                C<ast::Label> ret;
1575                for (auto oldn : olds) {
1576                        ret.push_back( make_label( &oldn ) );
1577                }
1578                return ret;
1579        }
1580
1581#       define GET_LABELS_V(labels) \
1582                to<std::vector>::from( make_labels( std::move( labels ) ) )
1583
1584        static ast::CV::Qualifiers cv( const Type * ty ) { return { ty->tq.val }; }
1585
1586        /// returns true and sets `node` if in cache
1587        bool inCache( const BaseSyntaxNode * old ) {
1588                auto it = cache.find( old );
1589                if ( it == cache.end() ) return false;
1590                node = const_cast<ast::Node *>(it->second.get());
1591                return true;
1592        }
1593
1594        // Now all the visit functions:
1595
1596        virtual void visit( const ObjectDecl * old ) override final {
1597                if ( inCache( old ) ) {
1598                        return;
1599                }
1600                auto&& type = GET_ACCEPT_1(type, Type);
1601                auto&& init = GET_ACCEPT_1(init, Init);
1602                auto&& bfwd = GET_ACCEPT_1(bitfieldWidth, Expr);
1603                auto&& attr = GET_ACCEPT_V(attributes, Attribute);
1604
1605                auto decl = new ast::ObjectDecl(
1606                        old->location,
1607                        old->name,
1608                        type,
1609                        init,
1610                        { old->get_storageClasses().val },
1611                        { old->linkage.val },
1612                        bfwd,
1613                        std::move(attr),
1614                        { old->get_funcSpec().val }
1615                );
1616                decl->enumInLine = old->enumInLine;
1617                cache.emplace(old, decl);
1618                assert(cache.find( old ) != cache.end());
1619                decl->scopeLevel = old->scopeLevel;
1620                decl->mangleName = old->mangleName;
1621                decl->isDeleted  = old->isDeleted;
1622                decl->asmName    = GET_ACCEPT_1(asmName, Expr);
1623                decl->uniqueId   = old->uniqueId;
1624                decl->extension  = old->extension;
1625
1626                this->node = decl;
1627        }
1628
1629        virtual void visit( const FunctionDecl * old ) override final {
1630                if ( inCache( old ) ) return;
1631                auto paramVars = GET_ACCEPT_V(type->parameters, DeclWithType);
1632                auto returnVars = GET_ACCEPT_V(type->returnVals, DeclWithType);
1633                auto forall = GET_ACCEPT_V(type->forall, TypeDecl);
1634
1635                // function type is now derived from parameter decls instead of storing them
1636
1637                /*
1638                auto ftype = new ast::FunctionType((ast::ArgumentFlag)old->type->isVarArgs, cv(old->type));
1639                ftype->params.reserve(paramVars.size());
1640                ftype->returns.reserve(returnVars.size());
1641
1642                for (auto & v: paramVars) {
1643                        ftype->params.emplace_back(v->get_type());
1644                }
1645                for (auto & v: returnVars) {
1646                        ftype->returns.emplace_back(v->get_type());
1647                }
1648                ftype->forall = std::move(forall);
1649                */
1650
1651                // can function type have attributes? seems not to be the case.
1652                // visitType(old->type, ftype);
1653
1654                // collect assertions and put directly in FunctionDecl
1655                std::vector<ast::ptr<ast::DeclWithType>> assertions;
1656                for (auto & param: forall) {
1657                        for (auto & asst: param->assertions) {
1658                                assertf(asst->unique(), "newly converted decl must be unique");
1659                                assertions.emplace_back(asst);
1660                        }
1661                        auto mut = param.get_and_mutate();
1662                        assertf(mut == param, "newly converted decl must be unique");
1663                        mut->assertions.clear();
1664                }
1665
1666                auto decl = new ast::FunctionDecl{
1667                        old->location,
1668                        old->name,
1669                        // GET_ACCEPT_1(type, FunctionType),
1670                        std::move(forall),
1671                        std::move(assertions),
1672                        std::move(paramVars),
1673                        std::move(returnVars),
1674                        {},
1675                        { old->storageClasses.val },
1676                        { old->linkage.val },
1677                        GET_ACCEPT_V(attributes, Attribute),
1678                        { old->get_funcSpec().val },
1679                        old->type->isVarArgs
1680                };
1681
1682                // decl->type = ftype;
1683                cache.emplace( old, decl );
1684
1685                decl->withExprs = GET_ACCEPT_V(withExprs, Expr);
1686                decl->stmts = GET_ACCEPT_1(statements, CompoundStmt);
1687                decl->scopeLevel = old->scopeLevel;
1688                decl->mangleName = old->mangleName;
1689                decl->isDeleted  = old->isDeleted;
1690                decl->asmName    = GET_ACCEPT_1(asmName, Expr);
1691                decl->uniqueId   = old->uniqueId;
1692                decl->extension  = old->extension;
1693
1694                this->node = decl;
1695
1696                if ( Validate::dereferenceOperator == old ) {
1697                        ast::dereferenceOperator = decl;
1698                }
1699
1700                if ( Validate::dtorStructDestroy == old ) {
1701                        ast::dtorStructDestroy = decl;
1702                }
1703        }
1704
1705        virtual void visit( const StructDecl * old ) override final {
1706                if ( inCache( old ) ) return;
1707                auto decl = new ast::StructDecl(
1708                        old->location,
1709                        old->name,
1710                        (ast::AggregateDecl::Aggregate)old->kind,
1711                        GET_ACCEPT_V(attributes, Attribute),
1712                        { old->linkage.val }
1713                );
1714                cache.emplace( old, decl );
1715                decl->parent = GET_ACCEPT_1(parent, AggregateDecl);
1716                decl->body   = old->body;
1717                decl->params = GET_ACCEPT_V(parameters, TypeDecl);
1718                decl->members    = GET_ACCEPT_V(members, Decl);
1719                decl->extension  = old->extension;
1720                decl->uniqueId   = old->uniqueId;
1721                decl->storage    = { old->storageClasses.val };
1722
1723                this->node = decl;
1724
1725                if ( Validate::dtorStruct == old ) {
1726                        ast::dtorStruct = decl;
1727                }
1728        }
1729
1730        virtual void visit( const UnionDecl * old ) override final {
1731                if ( inCache( old ) ) return;
1732                auto decl = new ast::UnionDecl(
1733                        old->location,
1734                        old->name,
1735                        GET_ACCEPT_V(attributes, Attribute),
1736                        { old->linkage.val }
1737                );
1738                cache.emplace( old, decl );
1739                decl->parent = GET_ACCEPT_1(parent, AggregateDecl);
1740                decl->body   = old->body;
1741                decl->params = GET_ACCEPT_V(parameters, TypeDecl);
1742                decl->members    = GET_ACCEPT_V(members, Decl);
1743                decl->extension  = old->extension;
1744                decl->uniqueId   = old->uniqueId;
1745                decl->storage    = { old->storageClasses.val };
1746
1747                this->node = decl;
1748        }
1749
1750
1751        virtual void visit( const EnumDecl * old ) override final {
1752                if ( inCache( old ) ) return;
1753                auto decl = new ast::EnumDecl(
1754                        old->location,
1755                        old->name,
1756                        old->isTyped,
1757                        GET_ACCEPT_V(attributes, Attribute),
1758                        { old->linkage.val },
1759                        GET_ACCEPT_1(base, Type),
1760                        old->enumValues
1761                );
1762                cache.emplace( old, decl );
1763                decl->parent = GET_ACCEPT_1(parent, AggregateDecl);
1764                decl->body   = old->body;
1765                decl->params = GET_ACCEPT_V(parameters, TypeDecl);
1766                decl->members    = GET_ACCEPT_V(members, Decl);
1767                decl->extension  = old->extension;
1768                decl->uniqueId   = old->uniqueId;
1769                decl->storage    = { old->storageClasses.val };
1770                this->node = decl;
1771        }
1772
1773        virtual void visit( const TraitDecl * old ) override final {
1774                if ( inCache( old ) ) return;
1775                auto decl = new ast::TraitDecl(
1776                        old->location,
1777                        old->name,
1778                        GET_ACCEPT_V(attributes, Attribute),
1779                        { old->linkage.val }
1780                );
1781                cache.emplace( old, decl );
1782                decl->parent = GET_ACCEPT_1(parent, AggregateDecl);
1783                decl->body   = old->body;
1784                decl->params = GET_ACCEPT_V(parameters, TypeDecl);
1785                decl->members    = GET_ACCEPT_V(members, Decl);
1786                decl->extension  = old->extension;
1787                decl->uniqueId   = old->uniqueId;
1788                decl->storage    = { old->storageClasses.val };
1789
1790                this->node = decl;
1791        }
1792
1793        virtual void visit( const TypeDecl * old ) override final {
1794                if ( inCache( old ) ) return;
1795                auto decl = new ast::TypeDecl{
1796                        old->location,
1797                        old->name,
1798                        { old->storageClasses.val },
1799                        GET_ACCEPT_1(base, Type),
1800                        (ast::TypeDecl::Kind)(unsigned)old->kind,
1801                        old->sized,
1802                        GET_ACCEPT_1(init, Type)
1803                };
1804                cache.emplace( old, decl );
1805                decl->assertions = GET_ACCEPT_V(assertions, DeclWithType);
1806                decl->extension  = old->extension;
1807                decl->uniqueId   = old->uniqueId;
1808
1809                this->node = decl;
1810        }
1811
1812        virtual void visit( const TypedefDecl * old ) override final {
1813                auto decl = new ast::TypedefDecl(
1814                        old->location,
1815                        old->name,
1816                        { old->storageClasses.val },
1817                        GET_ACCEPT_1(base, Type),
1818                        { old->linkage.val }
1819                );
1820                decl->assertions = GET_ACCEPT_V(assertions, DeclWithType);
1821                decl->extension  = old->extension;
1822                decl->uniqueId   = old->uniqueId;
1823                decl->storage    = { old->storageClasses.val };
1824
1825                this->node = decl;
1826        }
1827
1828        virtual void visit( const AsmDecl * old ) override final {
1829                auto decl = new ast::AsmDecl{
1830                        old->location,
1831                        GET_ACCEPT_1(stmt, AsmStmt)
1832                };
1833                decl->extension  = old->extension;
1834                decl->uniqueId   = old->uniqueId;
1835                decl->storage    = { old->storageClasses.val };
1836
1837                this->node = decl;
1838        }
1839
1840        virtual void visit( const DirectiveDecl * old ) override final {
1841                auto decl = new ast::DirectiveDecl{
1842                        old->location,
1843                        GET_ACCEPT_1(stmt, DirectiveStmt)
1844                };
1845                decl->extension  = old->extension;
1846                decl->uniqueId   = old->uniqueId;
1847                decl->storage    = { old->storageClasses.val };
1848
1849                this->node = decl;
1850        }
1851
1852        virtual void visit( const StaticAssertDecl * old ) override final {
1853                auto decl = new ast::StaticAssertDecl{
1854                        old->location,
1855                        GET_ACCEPT_1(condition, Expr),
1856                        GET_ACCEPT_1(message, ConstantExpr)
1857                };
1858                decl->extension  = old->extension;
1859                decl->uniqueId   = old->uniqueId;
1860                decl->storage    = { old->storageClasses.val };
1861
1862                this->node = decl;
1863        }
1864
1865        virtual void visit( const CompoundStmt * old ) override final {
1866                if ( inCache( old ) ) return;
1867                auto stmt = new ast::CompoundStmt(
1868                        old->location,
1869                        to<std::list>::from( GET_ACCEPT_V(kids, Stmt) ),
1870                        GET_LABELS_V(old->labels)
1871                );
1872
1873                this->node = stmt;
1874                cache.emplace( old, this->node );
1875        }
1876
1877        virtual void visit( const ExprStmt * old ) override final {
1878                if ( inCache( old ) ) return;
1879                this->node = new ast::ExprStmt(
1880                        old->location,
1881                        GET_ACCEPT_1(expr, Expr),
1882                        GET_LABELS_V(old->labels)
1883                );
1884                cache.emplace( old, this->node );
1885        }
1886
1887        virtual void visit( const AsmStmt * old ) override final {
1888                if ( inCache( old ) ) return;
1889                this->node = new ast::AsmStmt(
1890                        old->location,
1891                        old->voltile,
1892                        GET_ACCEPT_1(instruction, Expr),
1893                        GET_ACCEPT_V(output, Expr),
1894                        GET_ACCEPT_V(input, Expr),
1895                        GET_ACCEPT_V(clobber, ConstantExpr),
1896                        GET_LABELS_V(old->gotolabels),
1897                        GET_LABELS_V(old->labels)
1898                );
1899                cache.emplace( old, this->node );
1900        }
1901
1902        virtual void visit( const DirectiveStmt * old ) override final {
1903                if ( inCache( old ) ) return;
1904                this->node = new ast::DirectiveStmt(
1905                        old->location,
1906                        old->directive,
1907                        GET_LABELS_V(old->labels)
1908                );
1909                cache.emplace( old, this->node );
1910        }
1911
1912        virtual void visit( const IfStmt * old ) override final {
1913                if ( inCache( old ) ) return;
1914                this->node = new ast::IfStmt(
1915                        old->location,
1916                        GET_ACCEPT_1(condition, Expr),
1917                        GET_ACCEPT_1(then, Stmt),
1918                        GET_ACCEPT_1(else_, Stmt),
1919                        GET_ACCEPT_V(initialization, Stmt),
1920                        GET_LABELS_V(old->labels)
1921                );
1922                cache.emplace( old, this->node );
1923        }
1924
1925        virtual void visit( const SwitchStmt * old ) override final {
1926                if ( inCache( old ) ) return;
1927                this->node = new ast::SwitchStmt(
1928                        old->location,
1929                        GET_ACCEPT_1(condition, Expr),
1930                        GET_ACCEPT_V(statements, CaseClause),
1931                        GET_LABELS_V(old->labels)
1932                );
1933                cache.emplace( old, this->node );
1934        }
1935
1936        virtual void visit( const CaseStmt * old ) override final {
1937                if ( inCache( old ) ) return;
1938                this->node = new ast::CaseClause(
1939                        old->location,
1940                        GET_ACCEPT_1(condition, Expr),
1941                        GET_ACCEPT_V(stmts, Stmt)
1942                );
1943                auto labels = GET_LABELS_V(old->labels);
1944                assertf(labels.empty(), "Labels found on CaseStmt.");
1945                cache.emplace( old, this->node );
1946        }
1947
1948        virtual void visit( const WhileDoStmt * old ) override final {
1949                if ( inCache( old ) ) return;
1950                this->node = new ast::WhileDoStmt(
1951                        old->location,
1952                        GET_ACCEPT_1(condition, Expr),
1953                        GET_ACCEPT_1(body, Stmt),
1954                        GET_ACCEPT_1(else_, Stmt),
1955                        GET_ACCEPT_V(initialization, Stmt),
1956                        old->isDoWhile,
1957                        GET_LABELS_V(old->labels)
1958                );
1959                cache.emplace( old, this->node );
1960        }
1961
1962        virtual void visit( const ForStmt * old ) override final {
1963                if ( inCache( old ) ) return;
1964                this->node = new ast::ForStmt(
1965                        old->location,
1966                        GET_ACCEPT_V(initialization, Stmt),
1967                        GET_ACCEPT_1(condition, Expr),
1968                        GET_ACCEPT_1(increment, Expr),
1969                        GET_ACCEPT_1(body, Stmt),
1970                        GET_ACCEPT_1(else_, Stmt),
1971                        GET_LABELS_V(old->labels)
1972                );
1973                cache.emplace( old, this->node );
1974        }
1975
1976        virtual void visit( const BranchStmt * old ) override final {
1977                if ( inCache( old ) ) return;
1978                if (old->computedTarget) {
1979                        this->node = new ast::BranchStmt(
1980                                old->location,
1981                                GET_ACCEPT_1(computedTarget, Expr),
1982                                GET_LABELS_V(old->labels)
1983                        );
1984                } else {
1985                        ast::BranchStmt::Kind kind;
1986                        switch (old->type) {
1987                        #define CASE(n) \
1988                        case BranchStmt::n: \
1989                                kind = ast::BranchStmt::n; \
1990                                break
1991                        CASE(Goto);
1992                        CASE(Break);
1993                        CASE(Continue);
1994                        CASE(FallThrough);
1995                        CASE(FallThroughDefault);
1996                        #undef CASE
1997                        default:
1998                                assertf(false, "Invalid BranchStmt::Type %d\n", old->type);
1999                        }
2000
2001                        auto stmt = new ast::BranchStmt(
2002                                old->location,
2003                                kind,
2004                                make_label(&old->originalTarget),
2005                                GET_LABELS_V(old->labels)
2006                        );
2007                        stmt->target = make_label(&old->target);
2008                        this->node = stmt;
2009                }
2010                cache.emplace( old, this->node );
2011        }
2012
2013        virtual void visit( const ReturnStmt * old ) override final {
2014                if ( inCache( old ) ) return;
2015                this->node = new ast::ReturnStmt(
2016                        old->location,
2017                        GET_ACCEPT_1(expr, Expr),
2018                        GET_LABELS_V(old->labels)
2019                );
2020                cache.emplace( old, this->node );
2021        }
2022
2023        virtual void visit( const ThrowStmt * old ) override final {
2024                if ( inCache( old ) ) return;
2025                ast::ExceptionKind kind;
2026                switch (old->kind) {
2027                case ThrowStmt::Terminate:
2028                        kind = ast::ExceptionKind::Terminate;
2029                        break;
2030                case ThrowStmt::Resume:
2031                        kind = ast::ExceptionKind::Resume;
2032                        break;
2033                default:
2034                        assertf(false, "Invalid ThrowStmt::Kind %d\n", old->kind);
2035                }
2036
2037                this->node = new ast::ThrowStmt(
2038                        old->location,
2039                        kind,
2040                        GET_ACCEPT_1(expr, Expr),
2041                        GET_ACCEPT_1(target, Expr),
2042                        GET_LABELS_V(old->labels)
2043                );
2044                cache.emplace( old, this->node );
2045        }
2046
2047        virtual void visit( const TryStmt * old ) override final {
2048                if ( inCache( old ) ) return;
2049                this->node = new ast::TryStmt(
2050                        old->location,
2051                        GET_ACCEPT_1(block, CompoundStmt),
2052                        GET_ACCEPT_V(handlers, CatchClause),
2053                        GET_ACCEPT_1(finallyBlock, FinallyClause),
2054                        GET_LABELS_V(old->labels)
2055                );
2056                cache.emplace( old, this->node );
2057        }
2058
2059        virtual void visit( const CatchStmt * old ) override final {
2060                if ( inCache( old ) ) return;
2061                ast::ExceptionKind kind;
2062                switch (old->kind) {
2063                case CatchStmt::Terminate:
2064                        kind = ast::ExceptionKind::Terminate;
2065                        break;
2066                case CatchStmt::Resume:
2067                        kind = ast::ExceptionKind::Resume;
2068                        break;
2069                default:
2070                        assertf(false, "Invalid CatchStmt::Kind %d\n", old->kind);
2071                }
2072
2073                this->node = new ast::CatchClause(
2074                        old->location,
2075                        kind,
2076                        GET_ACCEPT_1(decl, Decl),
2077                        GET_ACCEPT_1(cond, Expr),
2078                        GET_ACCEPT_1(body, Stmt)
2079                );
2080                auto labels = GET_LABELS_V(old->labels);
2081                assertf(labels.empty(), "Labels found on CatchStmt.");
2082                cache.emplace( old, this->node );
2083        }
2084
2085        virtual void visit( const FinallyStmt * old ) override final {
2086                if ( inCache( old ) ) return;
2087                this->node = new ast::FinallyClause(
2088                        old->location,
2089                        GET_ACCEPT_1(block, CompoundStmt)
2090                );
2091                auto labels = GET_LABELS_V(old->labels);
2092                assertf(labels.empty(), "Labels found on FinallyStmt.");
2093                cache.emplace( old, this->node );
2094        }
2095
2096        virtual void visit( const SuspendStmt * old ) override final {
2097                if ( inCache( old ) ) return;
2098                ast::SuspendStmt::Type type;
2099                switch (old->type) {
2100                        case SuspendStmt::Coroutine: type = ast::SuspendStmt::Coroutine; break;
2101                        case SuspendStmt::Generator: type = ast::SuspendStmt::Generator; break;
2102                        case SuspendStmt::None     : type = ast::SuspendStmt::None     ; break;
2103                        default: abort();
2104                }
2105                this->node = new ast::SuspendStmt(
2106                        old->location,
2107                        GET_ACCEPT_1(then  , CompoundStmt),
2108                        type,
2109                        GET_LABELS_V(old->labels)
2110                );
2111                cache.emplace( old, this->node );
2112        }
2113
2114        virtual void visit( const WaitForStmt * old ) override final {
2115                if ( inCache( old ) ) return;
2116                ast::WaitForStmt * stmt = new ast::WaitForStmt(
2117                        old->location,
2118                        GET_LABELS_V(old->labels)
2119                );
2120
2121                stmt->clauses.reserve( old->clauses.size() );
2122                for (size_t i = 0 ; i < old->clauses.size() ; ++i) {
2123                        auto clause = new ast::WaitForClause( old->location );
2124
2125                        clause->target_func = GET_ACCEPT_1(clauses[i].target.function, Expr);
2126                        clause->target_args = GET_ACCEPT_V(clauses[i].target.arguments, Expr);
2127                        clause->stmt = GET_ACCEPT_1(clauses[i].statement, Stmt);
2128                        clause->cond = GET_ACCEPT_1(clauses[i].condition, Expr);
2129
2130                        stmt->clauses.push_back( clause );
2131                }
2132                stmt->timeout_time = GET_ACCEPT_1(timeout.time, Expr);
2133                stmt->timeout_stmt = GET_ACCEPT_1(timeout.statement, Stmt);
2134                stmt->timeout_cond = GET_ACCEPT_1(timeout.condition, Expr);
2135                stmt->else_stmt = GET_ACCEPT_1(orelse.statement, Stmt);
2136                stmt->else_cond = GET_ACCEPT_1(orelse.condition, Expr);
2137
2138                this->node = stmt;
2139                cache.emplace( old, this->node );
2140        }
2141
2142        virtual void visit( const WithStmt * old ) override final {
2143                if ( inCache( old ) ) return;
2144                this->node = new ast::WithStmt(
2145                        old->location,
2146                        GET_ACCEPT_V(exprs, Expr),
2147                        GET_ACCEPT_1(stmt, Stmt)
2148                );
2149                cache.emplace( old, this->node );
2150        }
2151
2152        virtual void visit( const NullStmt * old ) override final {
2153                if ( inCache( old ) ) return;
2154                this->node = new ast::NullStmt(
2155                        old->location,
2156                        GET_LABELS_V(old->labels)
2157                );
2158                cache.emplace( old, this->node );
2159        }
2160
2161        virtual void visit( const DeclStmt * old ) override final {
2162                if ( inCache( old ) ) return;
2163                this->node = new ast::DeclStmt(
2164                        old->location,
2165                        GET_ACCEPT_1(decl, Decl),
2166                        GET_LABELS_V(old->labels)
2167                );
2168                cache.emplace( old, this->node );
2169        }
2170
2171        virtual void visit( const ImplicitCtorDtorStmt * old ) override final {
2172                if ( inCache( old ) ) return;
2173                auto stmt = new ast::ImplicitCtorDtorStmt(
2174                        old->location,
2175                        nullptr,
2176                        GET_LABELS_V(old->labels)
2177                );
2178                cache.emplace( old, stmt );
2179                stmt->callStmt = GET_ACCEPT_1(callStmt, Stmt);
2180                this->node = stmt;
2181        }
2182
2183        virtual void visit( const MutexStmt * old ) override final {
2184                if ( inCache( old ) ) return;
2185                this->node = new ast::MutexStmt(
2186                        old->location,
2187                        GET_ACCEPT_1(stmt, Stmt),
2188                        GET_ACCEPT_V(mutexObjs, Expr)
2189                );
2190                cache.emplace( old, this->node );
2191        }
2192
2193        // TypeSubstitution shouldn't exist yet in old.
2194        ast::TypeSubstitution * convertTypeSubstitution(const TypeSubstitution * old) {
2195               
2196                if (!old) return nullptr;
2197                if (old->empty()) return nullptr;
2198                assert(false);
2199
2200                /*
2201                ast::TypeSubstitution *rslt = new ast::TypeSubstitution();
2202
2203                for (decltype(old->begin()) old_i = old->begin(); old_i != old->end(); old_i++) {
2204                        rslt->add( old_i->first,
2205                                   getAccept1<ast::Type>(old_i->second) );
2206                }
2207
2208                return rslt;
2209                */
2210        }
2211
2212        void convertInferUnion(ast::Expr::InferUnion               &newInferred,
2213                                                   const std::map<UniqueId,ParamEntry> &oldInferParams,
2214                                                   const std::vector<UniqueId>         &oldResnSlots) {
2215
2216                assert( oldInferParams.empty() || oldResnSlots.empty() );
2217                // assert( newInferred.mode == ast::Expr::InferUnion::Empty );
2218
2219                if ( !oldInferParams.empty() ) {
2220                        ast::InferredParams &tgt = newInferred.inferParams();
2221                        for (auto & old : oldInferParams) {
2222                                tgt[old.first] = ast::ParamEntry(
2223                                        old.second.decl,
2224                                        getAccept1<ast::Decl>(old.second.declptr),
2225                                        getAccept1<ast::Type>(old.second.actualType),
2226                                        getAccept1<ast::Type>(old.second.formalType),
2227                                        getAccept1<ast::Expr>(old.second.expr)
2228                                );
2229                        }
2230                } else if ( !oldResnSlots.empty() ) {
2231                        ast::ResnSlots &tgt = newInferred.resnSlots();
2232                        for (auto old : oldResnSlots) {
2233                                tgt.push_back(old);
2234                        }
2235                }
2236        }
2237
2238        ast::Expr * visitBaseExpr_SkipResultType( const Expression * old, ast::Expr * nw) {
2239
2240                nw->env    = convertTypeSubstitution(old->env);
2241
2242                nw->extension = old->extension;
2243                convertInferUnion(nw->inferred, old->inferParams, old->resnSlots);
2244
2245                return nw;
2246        }
2247
2248        ast::Expr * visitBaseExpr( const Expression * old, ast::Expr * nw) {
2249
2250                nw->result = GET_ACCEPT_1(result, Type);
2251                return visitBaseExpr_SkipResultType(old, nw);;
2252        }
2253
2254        virtual void visit( const ApplicationExpr * old ) override final {
2255                this->node = visitBaseExpr( old,
2256                        new ast::ApplicationExpr(
2257                                old->location,
2258                                GET_ACCEPT_1(function, Expr),
2259                                GET_ACCEPT_V(args, Expr)
2260                        )
2261                );
2262        }
2263
2264        virtual void visit( const UntypedExpr * old ) override final {
2265                this->node = visitBaseExpr( old,
2266                        new ast::UntypedExpr(
2267                                old->location,
2268                                GET_ACCEPT_1(function, Expr),
2269                                GET_ACCEPT_V(args, Expr)
2270                        )
2271                );
2272        }
2273
2274        virtual void visit( const NameExpr * old ) override final {
2275                this->node = visitBaseExpr( old,
2276                        new ast::NameExpr(
2277                                old->location,
2278                                old->get_name()
2279                        )
2280                );
2281        }
2282
2283        virtual void visit( const QualifiedNameExpr * old ) override final {
2284                this->node = visitBaseExpr( old,
2285                        new ast::QualifiedNameExpr (
2286                                old->location,
2287                                GET_ACCEPT_1(type_decl, Decl),
2288                                old->name
2289                        )
2290                );
2291        }
2292
2293        virtual void visit( const CastExpr * old ) override final {
2294                this->node = visitBaseExpr( old,
2295                        new ast::CastExpr(
2296                                old->location,
2297                                GET_ACCEPT_1(arg, Expr),
2298                                old->isGenerated ? ast::GeneratedCast : ast::ExplicitCast
2299                        )
2300                );
2301        }
2302
2303        virtual void visit( const KeywordCastExpr * old ) override final {
2304                ast::AggregateDecl::Aggregate castTarget = (ast::AggregateDecl::Aggregate)old->target;
2305                assert( ast::AggregateDecl::Generator <= castTarget && castTarget <= ast::AggregateDecl::Thread );
2306                this->node = visitBaseExpr( old,
2307                        new ast::KeywordCastExpr(
2308                                old->location,
2309                                GET_ACCEPT_1(arg, Expr),
2310                                castTarget,
2311                                {old->concrete_target.field, old->concrete_target.getter}
2312                        )
2313                );
2314        }
2315
2316        virtual void visit( const VirtualCastExpr * old ) override final {
2317                this->node = visitBaseExpr_SkipResultType( old,
2318                        new ast::VirtualCastExpr(
2319                                old->location,
2320                                GET_ACCEPT_1(arg, Expr),
2321                                GET_ACCEPT_1(result, Type)
2322                        )
2323                );
2324        }
2325
2326        virtual void visit( const AddressExpr * old ) override final {
2327                this->node = visitBaseExpr( old,
2328                        new ast::AddressExpr(
2329                                old->location,
2330                                GET_ACCEPT_1(arg, Expr)
2331                        )
2332                );
2333        }
2334
2335        virtual void visit( const LabelAddressExpr * old ) override final {
2336                this->node = visitBaseExpr( old,
2337                        new ast::LabelAddressExpr(
2338                                old->location,
2339                                make_label(&old->arg)
2340                        )
2341                );
2342        }
2343
2344        virtual void visit( const UntypedMemberExpr * old ) override final {
2345                this->node = visitBaseExpr( old,
2346                        new ast::UntypedMemberExpr(
2347                                old->location,
2348                                GET_ACCEPT_1(member, Expr),
2349                                GET_ACCEPT_1(aggregate, Expr)
2350                        )
2351                );
2352        }
2353
2354        virtual void visit( const MemberExpr * old ) override final {
2355                this->node = visitBaseExpr( old,
2356                        new ast::MemberExpr(
2357                                old->location,
2358                                GET_ACCEPT_1(member, DeclWithType),
2359                                GET_ACCEPT_1(aggregate, Expr),
2360                                ast::MemberExpr::NoOpConstructionChosen
2361                        )
2362                );
2363        }
2364
2365        virtual void visit( const VariableExpr * old ) override final {
2366                auto expr = new ast::VariableExpr(
2367                        old->location
2368                );
2369
2370                expr->var = GET_ACCEPT_1(var, DeclWithType);
2371                visitBaseExpr( old, expr );
2372
2373                this->node = expr;
2374        }
2375
2376        virtual void visit( const ConstantExpr * old ) override final {
2377                ast::ConstantExpr *rslt = new ast::ConstantExpr(
2378                        old->location,
2379                        GET_ACCEPT_1(result, Type),
2380                        old->constant.rep,
2381                        old->constant.ival
2382                );
2383                rslt->underlyer = getAccept1< ast::Type, Type* >( old->constant.type );
2384                this->node = visitBaseExpr( old, rslt );
2385        }
2386
2387        virtual void visit( const SizeofExpr * old ) override final {
2388                assert (old->expr || old->type);
2389                assert (! (old->expr && old->type));
2390                ast::SizeofExpr *rslt;
2391                if (old->expr) {
2392                        assert(!old->isType);
2393                        rslt = new ast::SizeofExpr(
2394                                old->location,
2395                                GET_ACCEPT_1(expr, Expr)
2396                        );
2397                }
2398                if (old->type) {
2399                        assert(old->isType);
2400                        rslt = new ast::SizeofExpr(
2401                                old->location,
2402                                GET_ACCEPT_1(type, Type)
2403                        );
2404                }
2405                this->node = visitBaseExpr( old, rslt );
2406        }
2407
2408        virtual void visit( const AlignofExpr * old ) override final {
2409                assert (old->expr || old->type);
2410                assert (! (old->expr && old->type));
2411                ast::AlignofExpr *rslt;
2412                if (old->expr) {
2413                        assert(!old->isType);
2414                        rslt = new ast::AlignofExpr(
2415                                old->location,
2416                                GET_ACCEPT_1(expr, Expr)
2417                        );
2418                }
2419                if (old->type) {
2420                        assert(old->isType);
2421                        rslt = new ast::AlignofExpr(
2422                                old->location,
2423                                GET_ACCEPT_1(type, Type)
2424                        );
2425                }
2426                this->node = visitBaseExpr( old, rslt );
2427        }
2428
2429        virtual void visit( const UntypedOffsetofExpr * old ) override final {
2430                this->node = visitBaseExpr( old,
2431                        new ast::UntypedOffsetofExpr(
2432                                old->location,
2433                                GET_ACCEPT_1(type, Type),
2434                                old->member
2435                        )
2436                );
2437        }
2438
2439        virtual void visit( const OffsetofExpr * old ) override final {
2440                this->node = visitBaseExpr( old,
2441                        new ast::OffsetofExpr(
2442                                old->location,
2443                                GET_ACCEPT_1(type, Type),
2444                                GET_ACCEPT_1(member, DeclWithType)
2445                        )
2446                );
2447        }
2448
2449        virtual void visit( const OffsetPackExpr * old ) override final {
2450                this->node = visitBaseExpr( old,
2451                        new ast::OffsetPackExpr(
2452                                old->location,
2453                                GET_ACCEPT_1(type, StructInstType)
2454                        )
2455                );
2456        }
2457
2458        virtual void visit( const LogicalExpr * old ) override final {
2459                this->node = visitBaseExpr( old,
2460                        new ast::LogicalExpr(
2461                                old->location,
2462                                GET_ACCEPT_1(arg1, Expr),
2463                                GET_ACCEPT_1(arg2, Expr),
2464                                old->get_isAnd() ?
2465                                        ast::LogicalFlag::AndExpr :
2466                                        ast::LogicalFlag::OrExpr
2467                        )
2468                );
2469        }
2470
2471        virtual void visit( const ConditionalExpr * old ) override final {
2472                this->node = visitBaseExpr( old,
2473                        new ast::ConditionalExpr(
2474                                old->location,
2475                                GET_ACCEPT_1(arg1, Expr),
2476                                GET_ACCEPT_1(arg2, Expr),
2477                                GET_ACCEPT_1(arg3, Expr)
2478                        )
2479                );
2480        }
2481
2482        virtual void visit( const CommaExpr * old ) override final {
2483                this->node = visitBaseExpr( old,
2484                        new ast::CommaExpr(
2485                                old->location,
2486                                GET_ACCEPT_1(arg1, Expr),
2487                                GET_ACCEPT_1(arg2, Expr)
2488                        )
2489                );
2490        }
2491
2492        virtual void visit( const TypeExpr * old ) override final {
2493                this->node = visitBaseExpr( old,
2494                        new ast::TypeExpr(
2495                                old->location,
2496                                GET_ACCEPT_1(type, Type)
2497                        )
2498                );
2499        }
2500
2501        virtual void visit( const DimensionExpr * old ) override final {
2502                this->node = visitBaseExpr( old,
2503                        new ast::DimensionExpr( old->location, old->name )
2504                );
2505        }
2506
2507        virtual void visit( const AsmExpr * old ) override final {
2508                this->node = visitBaseExpr( old,
2509                        new ast::AsmExpr(
2510                                old->location,
2511                                old->inout,
2512                                GET_ACCEPT_1(constraint, Expr),
2513                                GET_ACCEPT_1(operand, Expr)
2514                        )
2515                );
2516        }
2517
2518        virtual void visit( const ImplicitCopyCtorExpr * old ) override final {
2519                auto rslt = new ast::ImplicitCopyCtorExpr(
2520                        old->location,
2521                        GET_ACCEPT_1(callExpr, ApplicationExpr)
2522                );
2523
2524                this->node = visitBaseExpr( old, rslt );
2525        }
2526
2527        virtual void visit( const ConstructorExpr * old ) override final {
2528                this->node = visitBaseExpr( old,
2529                        new ast::ConstructorExpr(
2530                                old->location,
2531                                GET_ACCEPT_1(callExpr, Expr)
2532                        )
2533                );
2534        }
2535
2536        virtual void visit( const CompoundLiteralExpr * old ) override final {
2537                this->node = visitBaseExpr_SkipResultType( old,
2538                        new ast::CompoundLiteralExpr(
2539                                old->location,
2540                                GET_ACCEPT_1(result, Type),
2541                                GET_ACCEPT_1(initializer, Init)
2542                        )
2543                );
2544        }
2545
2546        virtual void visit( const RangeExpr * old ) override final {
2547                this->node = visitBaseExpr( old,
2548                        new ast::RangeExpr(
2549                                old->location,
2550                                GET_ACCEPT_1(low, Expr),
2551                                GET_ACCEPT_1(high, Expr)
2552                        )
2553                );
2554        }
2555
2556        virtual void visit( const UntypedTupleExpr * old ) override final {
2557                this->node = visitBaseExpr( old,
2558                        new ast::UntypedTupleExpr(
2559                                old->location,
2560                                GET_ACCEPT_V(exprs, Expr)
2561                        )
2562                );
2563        }
2564
2565        virtual void visit( const TupleExpr * old ) override final {
2566                this->node = visitBaseExpr( old,
2567                        new ast::TupleExpr(
2568                                old->location,
2569                                GET_ACCEPT_V(exprs, Expr)
2570                        )
2571                );
2572        }
2573
2574        virtual void visit( const TupleIndexExpr * old ) override final {
2575                this->node = visitBaseExpr( old,
2576                        new ast::TupleIndexExpr(
2577                                old->location,
2578                                GET_ACCEPT_1(tuple, Expr),
2579                                old->index
2580                        )
2581                );
2582        }
2583
2584        virtual void visit( const TupleAssignExpr * old ) override final {
2585                this->node = visitBaseExpr_SkipResultType( old,
2586                        new ast::TupleAssignExpr(
2587                                old->location,
2588                                GET_ACCEPT_1(result, Type),
2589                                GET_ACCEPT_1(stmtExpr, StmtExpr)
2590                        )
2591                );
2592        }
2593
2594        virtual void visit( const StmtExpr * old ) override final {
2595                auto rslt = new ast::StmtExpr(
2596                        old->location,
2597                        GET_ACCEPT_1(statements, CompoundStmt)
2598                );
2599                rslt->returnDecls = GET_ACCEPT_V(returnDecls, ObjectDecl);
2600                rslt->dtors       = GET_ACCEPT_V(dtors      , Expr);
2601
2602                this->node = visitBaseExpr_SkipResultType( old, rslt );
2603        }
2604
2605        virtual void visit( const UniqueExpr * old ) override final {
2606                auto rslt = new ast::UniqueExpr(
2607                        old->location,
2608                        GET_ACCEPT_1(expr, Expr),
2609                        old->get_id()
2610                );
2611                rslt->object = GET_ACCEPT_1(object, ObjectDecl);
2612                rslt->var    = GET_ACCEPT_1(var   , VariableExpr);
2613
2614                this->node = visitBaseExpr( old, rslt );
2615        }
2616
2617        virtual void visit( const UntypedInitExpr * old ) override final {
2618                std::deque<ast::InitAlternative> initAlts;
2619                for (auto ia : old->initAlts) {
2620                        initAlts.push_back(ast::InitAlternative(
2621                                getAccept1< ast::Type, Type * >( ia.type ),
2622                                getAccept1< ast::Designation, Designation * >( ia.designation )
2623                        ));
2624                }
2625                this->node = visitBaseExpr( old,
2626                        new ast::UntypedInitExpr(
2627                                old->location,
2628                                GET_ACCEPT_1(expr, Expr),
2629                                std::move(initAlts)
2630                        )
2631                );
2632        }
2633
2634        virtual void visit( const InitExpr * old ) override final {
2635                this->node = visitBaseExpr( old,
2636                        new ast::InitExpr(
2637                                old->location,
2638                                GET_ACCEPT_1(expr, Expr),
2639                                GET_ACCEPT_1(designation, Designation)
2640                        )
2641                );
2642        }
2643
2644        virtual void visit( const DeletedExpr * old ) override final {
2645                this->node = visitBaseExpr( old,
2646                        new ast::DeletedExpr(
2647                                old->location,
2648                                GET_ACCEPT_1(expr, Expr),
2649                                inCache(old->deleteStmt) ?
2650                                        strict_dynamic_cast<ast::Decl*>(this->node) :
2651                                        GET_ACCEPT_1(deleteStmt, Decl)
2652                        )
2653                );
2654        }
2655
2656        virtual void visit( const DefaultArgExpr * old ) override final {
2657                this->node = visitBaseExpr( old,
2658                        new ast::DefaultArgExpr(
2659                                old->location,
2660                                GET_ACCEPT_1(expr, Expr)
2661                        )
2662                );
2663        }
2664
2665        virtual void visit( const GenericExpr * old ) override final {
2666                std::vector<ast::GenericExpr::Association> associations;
2667                for (auto association : old->associations) {
2668                        associations.push_back(ast::GenericExpr::Association(
2669                                getAccept1< ast::Type, Type * >( association.type ),
2670                                getAccept1< ast::Expr, Expression * >( association.expr )
2671                        ));
2672                }
2673                this->node = visitBaseExpr( old,
2674                        new ast::GenericExpr(
2675                                old->location,
2676                                GET_ACCEPT_1(control, Expr),
2677                                std::move(associations)
2678                        )
2679                );
2680        }
2681
2682        void visitType( const Type * old, ast::Type * type ) {
2683                // Some types do this in their constructor so add a check.
2684                if ( !old->attributes.empty() && type->attributes.empty() ) {
2685                        type->attributes = GET_ACCEPT_V(attributes, Attribute);
2686                }
2687                this->node = type;
2688        }
2689
2690        virtual void visit( const VoidType * old ) override final {
2691                visitType( old, new ast::VoidType{ cv( old ) } );
2692        }
2693
2694        virtual void visit( const BasicType * old ) override final {
2695                auto type = new ast::BasicType{ (ast::BasicType::Kind)(unsigned)old->kind, cv( old ) };
2696                // I believe this should always be a BasicType.
2697                if ( Validate::SizeType == old ) {
2698                        ast::sizeType = type;
2699                }
2700                visitType( old, type );
2701        }
2702
2703        virtual void visit( const PointerType * old ) override final {
2704                visitType( old, new ast::PointerType{
2705                        GET_ACCEPT_1( base, Type ),
2706                        GET_ACCEPT_1( dimension, Expr ),
2707                        (ast::LengthFlag)old->isVarLen,
2708                        (ast::DimensionFlag)old->isStatic,
2709                        cv( old )
2710                } );
2711        }
2712
2713        virtual void visit( const ArrayType * old ) override final {
2714                visitType( old, new ast::ArrayType{
2715                        GET_ACCEPT_1( base, Type ),
2716                        GET_ACCEPT_1( dimension, Expr ),
2717                        (ast::LengthFlag)old->isVarLen,
2718                        (ast::DimensionFlag)old->isStatic,
2719                        cv( old )
2720                } );
2721        }
2722
2723        virtual void visit( const ReferenceType * old ) override final {
2724                visitType( old, new ast::ReferenceType{
2725                        GET_ACCEPT_1( base, Type ),
2726                        cv( old )
2727                } );
2728        }
2729
2730        virtual void visit( const QualifiedType * old ) override final {
2731                visitType( old, new ast::QualifiedType{
2732                        GET_ACCEPT_1( parent, Type ),
2733                        GET_ACCEPT_1( child, Type ),
2734                        cv( old )
2735                } );
2736        }
2737
2738        virtual void visit( const FunctionType * old ) override final {
2739                auto ty = new ast::FunctionType {
2740                        (ast::ArgumentFlag)old->isVarArgs,
2741                        cv( old )
2742                };
2743                auto returnVars = GET_ACCEPT_V(returnVals, DeclWithType);
2744                auto paramVars = GET_ACCEPT_V(parameters, DeclWithType);
2745                // ty->returns = GET_ACCEPT_V( returnVals, DeclWithType );
2746                // ty->params = GET_ACCEPT_V( parameters, DeclWithType );
2747                for (auto & v: returnVars) {
2748                        ty->returns.emplace_back(v->get_type());
2749                }
2750                for (auto & v: paramVars) {
2751                        ty->params.emplace_back(v->get_type());
2752                }
2753                // xxx - when will this be non-null?
2754                // will have to create dangling (no-owner) decls to be pointed to
2755                auto foralls = GET_ACCEPT_V( forall, TypeDecl );
2756
2757                for (auto & param : foralls) {
2758                        ty->forall.emplace_back(new ast::TypeInstType(param));
2759                        for (auto asst : param->assertions) {
2760                                ty->assertions.emplace_back(
2761                                        new ast::VariableExpr(param->location, asst));
2762                        }
2763                }
2764                visitType( old, ty );
2765        }
2766
2767        void postvisit( const ReferenceToType * old, ast::BaseInstType * ty ) {
2768                ty->params = GET_ACCEPT_V( parameters, Expr );
2769                ty->hoistType = old->hoistType;
2770                visitType( old, ty );
2771        }
2772
2773        virtual void visit( const StructInstType * old ) override final {
2774                ast::StructInstType * ty;
2775                if ( old->baseStruct ) {
2776                        ty = new ast::StructInstType{
2777                                GET_ACCEPT_1( baseStruct, StructDecl ),
2778                                cv( old ),
2779                                GET_ACCEPT_V( attributes, Attribute )
2780                        };
2781                } else {
2782                        ty = new ast::StructInstType{
2783                                old->name,
2784                                cv( old ),
2785                                GET_ACCEPT_V( attributes, Attribute )
2786                        };
2787                }
2788                postvisit( old, ty );
2789        }
2790
2791        virtual void visit( const UnionInstType * old ) override final {
2792                ast::UnionInstType * ty;
2793                if ( old->baseUnion ) {
2794                        ty = new ast::UnionInstType{
2795                                GET_ACCEPT_1( baseUnion, UnionDecl ),
2796                                cv( old ),
2797                                GET_ACCEPT_V( attributes, Attribute )
2798                        };
2799                } else {
2800                        ty = new ast::UnionInstType{
2801                                old->name,
2802                                cv( old ),
2803                                GET_ACCEPT_V( attributes, Attribute )
2804                        };
2805                }
2806                postvisit( old, ty );
2807        }
2808
2809        virtual void visit( const EnumInstType * old ) override final {
2810                ast::EnumInstType * ty; 
2811                if ( old->baseEnum ) {
2812                        ty = new ast::EnumInstType{
2813                                GET_ACCEPT_1( baseEnum, EnumDecl ),
2814                                cv( old ),
2815                                GET_ACCEPT_V( attributes, Attribute )
2816                        };
2817                } else {
2818                        ty = new ast::EnumInstType{
2819                                old->name,
2820                                cv( old ),
2821                                GET_ACCEPT_V( attributes, Attribute )
2822                        };
2823                }
2824                postvisit( old, ty );
2825        }
2826
2827        virtual void visit( const TraitInstType * old ) override final {
2828                ast::TraitInstType * ty;
2829                if ( old->baseTrait ) {
2830                        ty = new ast::TraitInstType{
2831                                GET_ACCEPT_1( baseTrait, TraitDecl ),
2832                                cv( old ),
2833                                GET_ACCEPT_V( attributes, Attribute )
2834                        };
2835                } else {
2836                        ty = new ast::TraitInstType{
2837                                old->name,
2838                                cv( old ),
2839                                GET_ACCEPT_V( attributes, Attribute )
2840                        };
2841                }
2842                postvisit( old, ty );
2843        }
2844
2845        virtual void visit( const TypeInstType * old ) override final {
2846                ast::TypeInstType * ty;
2847                if ( old->baseType ) {
2848                        ty = new ast::TypeInstType{
2849                                old->name,
2850                                GET_ACCEPT_1( baseType, TypeDecl ),
2851                                cv( old ),
2852                                GET_ACCEPT_V( attributes, Attribute )
2853                        };
2854                } else {
2855                        ty = new ast::TypeInstType{
2856                                old->name,
2857                                old->isFtype ? ast::TypeDecl::Ftype : ast::TypeDecl::Dtype,
2858                                cv( old ),
2859                                GET_ACCEPT_V( attributes, Attribute )
2860                        };
2861                }
2862                postvisit( old, ty );
2863        }
2864
2865        virtual void visit( const TupleType * old ) override final {
2866                visitType( old, new ast::TupleType{
2867                        GET_ACCEPT_V( types, Type ),
2868                        // members generated by TupleType c'tor
2869                        cv( old )
2870                } );
2871        }
2872
2873        virtual void visit( const TypeofType * old ) override final {
2874                visitType( old, new ast::TypeofType{
2875                        GET_ACCEPT_1( expr, Expr ),
2876                        (ast::TypeofType::Kind)old->is_basetypeof,
2877                        cv( old )
2878                } );
2879        }
2880
2881        virtual void visit( const VTableType * old ) override final {
2882                visitType( old, new ast::VTableType{
2883                        GET_ACCEPT_1( base, Type ),
2884                        cv( old )
2885                } );
2886        }
2887
2888        virtual void visit( const AttrType * ) override final {
2889                assertf( false, "AttrType deprecated in new AST." );
2890        }
2891
2892        virtual void visit( const VarArgsType * old ) override final {
2893                visitType( old, new ast::VarArgsType{ cv( old ) } );
2894        }
2895
2896        virtual void visit( const ZeroType * old ) override final {
2897                visitType( old, new ast::ZeroType{ cv( old ) } );
2898        }
2899
2900        virtual void visit( const OneType * old ) override final {
2901                visitType( old, new ast::OneType{ cv( old ) } );
2902        }
2903
2904        virtual void visit( const GlobalScopeType * old ) override final {
2905                visitType( old, new ast::GlobalScopeType{} );
2906        }
2907
2908        virtual void visit( const Designation * old ) override final {
2909                this->node = new ast::Designation(
2910                        old->location,
2911                        GET_ACCEPT_D(designators, Expr)
2912                );
2913        }
2914
2915        virtual void visit( const SingleInit * old ) override final {
2916                this->node = new ast::SingleInit(
2917                        old->location,
2918                        GET_ACCEPT_1(value, Expr),
2919                        (old->get_maybeConstructed()) ? ast::MaybeConstruct : ast::NoConstruct
2920                );
2921        }
2922
2923        virtual void visit( const ListInit * old ) override final {
2924                this->node = new ast::ListInit(
2925                        old->location,
2926                        GET_ACCEPT_V(initializers, Init),
2927                        GET_ACCEPT_V(designations, Designation),
2928                        (old->get_maybeConstructed()) ? ast::MaybeConstruct : ast::NoConstruct
2929                );
2930        }
2931
2932        virtual void visit( const ConstructorInit * old ) override final {
2933                this->node = new ast::ConstructorInit(
2934                        old->location,
2935                        GET_ACCEPT_1(ctor, Stmt),
2936                        GET_ACCEPT_1(dtor, Stmt),
2937                        GET_ACCEPT_1(init, Init)
2938                );
2939        }
2940
2941        virtual void visit( const Constant * ) override final {
2942                // Handled in visit( ConstantEpxr * ).
2943                // In the new tree, Constant fields are inlined into containing ConstantExpression.
2944                assert( 0 );
2945        }
2946
2947        virtual void visit( const Attribute * old ) override final {
2948                this->node = new ast::Attribute(
2949                        old->name,
2950                        GET_ACCEPT_V( parameters, Expr )
2951                );
2952        }
2953};
2954
2955#undef GET_LABELS_V
2956#undef GET_ACCEPT_V
2957#undef GET_ACCEPT_1
2958
2959ast::TranslationUnit convert( const std::list< Declaration * > && translationUnit ) {
2960        ConverterOldToNew c;
2961        ast::TranslationUnit unit;
2962        if (Validate::SizeType) {
2963                // this should be a BasicType.
2964                auto old = strict_dynamic_cast<BasicType *>(Validate::SizeType);
2965                ast::sizeType = new ast::BasicType{ (ast::BasicType::Kind)(unsigned)old->kind };
2966        }
2967
2968        for(auto d : translationUnit) {
2969                d->accept( c );
2970                unit.decls.emplace_back( c.decl() );
2971        }
2972        deleteAll(translationUnit);
2973
2974        // Load the local static varables into the global store.
2975        unit.global.sizeType = ast::sizeType;
2976        unit.global.dereference = ast::dereferenceOperator;
2977        unit.global.dtorStruct = ast::dtorStruct;
2978        unit.global.dtorDestroy = ast::dtorStructDestroy;
2979
2980        return unit;
2981}
Note: See TracBrowser for help on using the repository browser.