Changeset c532847


Ignore:
Timestamp:
Oct 24, 2020, 9:42:38 AM (3 years ago)
Author:
Peter A. Buhr <pabuhr@…>
Branches:
ADT, arm-eh, ast-experimental, enum, forall-pointer-decay, jacob/cs343-translation, master, new-ast-unique-expr, pthread-emulation, qualifiedEnum
Children:
a3f36dc
Parents:
76d73fc (diff), e7d6968 (diff)
Note: this is a merge changeset, the changes displayed below correspond to the merge itself.
Use the (diff) links above to see all the changes relative to each parent.
Message:

Merge branch 'master' of plg.uwaterloo.ca:software/cfa/cfa-cc

Location:
src
Files:
1 added
30 edited

Legend:

Unmodified
Added
Removed
  • src/AST/Convert.cpp

    r76d73fc rc532847  
    4747
    4848//================================================================================================
    49 namespace {
     49namespace ast {
    5050
    5151// This is to preserve the FindSpecialDecls hack. It does not (and perhaps should not)
    5252// allow us to use the same stratagy in the new ast.
     53// xxx - since convert back pass works, this concern seems to be unnecessary.
     54
     55// these need to be accessed in new FixInit now
    5356ast::Type * sizeType = nullptr;
    5457ast::FunctionDecl * dereferenceOperator = nullptr;
     
    6366        using Cache = std::unordered_map< const ast::Node *, BaseSyntaxNode * >;
    6467        Cache cache;
     68
     69        // Statements can no longer be shared.
     70        // however, since StmtExprResult is now implemented, need to still maintain
     71        // readonly references.
     72        Cache readonlyCache;
    6573
    6674        template<typename T>
     
    154162        }
    155163
    156         const ast::DeclWithType * visit( const ast::ObjectDecl * node ) override final {
    157                 auto&& bfwd = get<Expression>().accept1( node->bitfieldWidth );
    158                 auto&& type = get<Type>().accept1( node->type );
    159                 auto&& init = get<Initializer>().accept1( node->init );
    160                 auto&& attr = get<Attribute>().acceptL( node->attributes );
     164        const ast::DeclWithType * visit( const ast::ObjectDecl * node ) override final {       
    161165                if ( inCache( node ) ) {
    162166                        return nullptr;
    163167                }
     168                auto bfwd = get<Expression>().accept1( node->bitfieldWidth );
     169                auto type = get<Type>().accept1( node->type );
     170                auto attr = get<Attribute>().acceptL( node->attributes );
     171
    164172                auto decl = new ObjectDecl(
    165173                        node->name,
     
    168176                        bfwd,
    169177                        type->clone(),
    170                         init,
     178                        nullptr, // prevent infinite loop
    171179                        attr,
    172180                        Type::FuncSpecifiers( node->funcSpec.val )
    173181                );
    174                 return declWithTypePostamble( decl, node );
     182
     183                // handles the case where node->init references itself
     184                // xxx - does it really happen?
     185                declWithTypePostamble(decl, node);
     186                auto init = get<Initializer>().accept1( node->init );
     187                decl->init = init;
     188               
     189                this->node = decl;
     190                return nullptr;
    175191        }
    176192
     
    205221                decl->statements = get<CompoundStmt>().accept1( node->stmts );
    206222                decl->withExprs = get<Expression>().acceptL( node->withExprs );
    207                 if ( dereferenceOperator == node ) {
     223                if ( ast::dereferenceOperator == node ) {
    208224                        Validate::dereferenceOperator = decl;
    209225                }
    210                 if ( dtorStructDestroy == node ) {
     226                if ( ast::dtorStructDestroy == node ) {
    211227                        Validate::dtorStructDestroy = decl;
    212228                }
     
    267283                );
    268284
    269                 if ( dtorStruct == node ) {
     285                if ( ast::dtorStruct == node ) {
    270286                        Validate::dtorStruct = decl;
    271287                }
     
    320336
    321337        const ast::Stmt * stmtPostamble( Statement * stmt, const ast::Stmt * node ) {
    322                 cache.emplace( node, stmt );
     338                // force statements in old tree to be unique.
     339                // cache.emplace( node, stmt );
     340                readonlyCache.emplace( node, stmt );
    323341                stmt->location = node->location;
    324342                stmt->labels = makeLabelL( stmt, node->labels );
     
    337355                if ( inCache( node ) ) return nullptr;
    338356                auto stmt = new ExprStmt( nullptr );
    339                 cache.emplace( node, stmt );
    340357                stmt->expr = get<Expression>().accept1( node->expr );
    341358                return stmtPostamble( stmt, node );
     
    10111028                auto stmts = node->stmts;
    10121029                // disable sharing between multiple StmtExprs explicitly.
    1013                 if (inCache(stmts)) {
    1014                         stmts = ast::deepCopy(stmts.get());
    1015                 }
     1030                // this should no longer be true.
     1031
    10161032                auto rslt = new StmtExpr(
    10171033                        get<CompoundStmt>().accept1(stmts)
     
    10201036                rslt->returnDecls = get<ObjectDecl>().acceptL(node->returnDecls);
    10211037                rslt->dtors       = get<Expression>().acceptL(node->dtors);
     1038                if (node->resultExpr) {
     1039                        // this MUST be found by children visit
     1040                        rslt->resultExpr  = strict_dynamic_cast<ExprStmt *>(readonlyCache.at(node->resultExpr));
     1041                }
    10221042
    10231043                auto expr = visitBaseExpr( node, rslt );
     
    10361056
    10371057                auto expr = visitBaseExpr( node, rslt );
    1038                 this->node = expr;
     1058                this->node = expr->clone();
    10391059                return nullptr;
    10401060        }
     
    11261146                auto type = new BasicType{ cv( node ), (BasicType::Kind)(unsigned)node->kind };
    11271147                // I believe this should always be a BasicType.
    1128                 if ( sizeType == node ) {
     1148                if ( ast::sizeType == node ) {
    11291149                        Validate::SizeType = type;
    11301150                }
     
    15291549
    15301550                // function type is now derived from parameter decls instead of storing them
     1551
     1552                /*
    15311553                auto ftype = new ast::FunctionType((ast::ArgumentFlag)old->type->isVarArgs, cv(old->type));
    15321554                ftype->params.reserve(paramVars.size());
     
    15401562                }
    15411563                ftype->forall = std::move(forall);
    1542                 visitType(old->type, ftype);
     1564                */
     1565
     1566                // can function type have attributes? seems not to be the case.
     1567                // visitType(old->type, ftype);
    15431568
    15441569                auto decl = new ast::FunctionDecl{
     
    15461571                        old->name,
    15471572                        // GET_ACCEPT_1(type, FunctionType),
     1573                        std::move(forall),
    15481574                        std::move(paramVars),
    15491575                        std::move(returnVars),
     
    15521578                        { old->linkage.val },
    15531579                        GET_ACCEPT_V(attributes, Attribute),
    1554                         { old->get_funcSpec().val }
     1580                        { old->get_funcSpec().val },
     1581                        old->type->isVarArgs
    15551582                };
    15561583
    1557                 decl->type = ftype;
     1584                // decl->type = ftype;
    15581585                cache.emplace( old, decl );
    15591586
     
    15701597
    15711598                if ( Validate::dereferenceOperator == old ) {
    1572                         dereferenceOperator = decl;
     1599                        ast::dereferenceOperator = decl;
    15731600                }
    15741601
    15751602                if ( Validate::dtorStructDestroy == old ) {
    1576                         dtorStructDestroy = decl;
     1603                        ast::dtorStructDestroy = decl;
    15771604                }
    15781605        }
     
    15991626
    16001627                if ( Validate::dtorStruct == old ) {
    1601                         dtorStruct = decl;
     1628                        ast::dtorStruct = decl;
    16021629                }
    16031630        }
     
    25312558                // I believe this should always be a BasicType.
    25322559                if ( Validate::SizeType == old ) {
    2533                         sizeType = type;
     2560                        ast::sizeType = type;
    25342561                }
    25352562                visitType( old, type );
  • src/AST/Decl.cpp

    r76d73fc rc532847  
    4848
    4949// --- FunctionDecl
     50
     51FunctionDecl::FunctionDecl( const CodeLocation & loc, const std::string & name,
     52                std::vector<ptr<TypeDecl>>&& forall,
     53                std::vector<ptr<DeclWithType>>&& params, std::vector<ptr<DeclWithType>>&& returns,
     54                CompoundStmt * stmts, Storage::Classes storage, Linkage::Spec linkage,
     55                std::vector<ptr<Attribute>>&& attrs, Function::Specs fs, bool isVarArgs)
     56        : DeclWithType( loc, name, storage, linkage, std::move(attrs), fs ), params(std::move(params)), returns(std::move(returns)),
     57          stmts( stmts ) {
     58                  FunctionType * ftype = new FunctionType(static_cast<ArgumentFlag>(isVarArgs));
     59                  for (auto & param : this->params) {
     60                          ftype->params.emplace_back(param->get_type());
     61                  }
     62                  for (auto & ret : this->returns) {
     63                          ftype->returns.emplace_back(ret->get_type());
     64                  }
     65                  ftype->forall = std::move(forall);
     66                  this->type = ftype;
     67          }
     68
    5069
    5170const Type * FunctionDecl::get_type() const { return type.get(); }
  • src/AST/Decl.hpp

    r76d73fc rc532847  
    131131        std::vector< ptr<Expr> > withExprs;
    132132
    133         FunctionDecl( const CodeLocation & loc, const std::string & name,
     133        FunctionDecl( const CodeLocation & loc, const std::string & name, std::vector<ptr<TypeDecl>>&& forall,
    134134                std::vector<ptr<DeclWithType>>&& params, std::vector<ptr<DeclWithType>>&& returns,
    135135                CompoundStmt * stmts, Storage::Classes storage = {}, Linkage::Spec linkage = Linkage::C,
    136                 std::vector<ptr<Attribute>>&& attrs = {}, Function::Specs fs = {})
    137         : DeclWithType( loc, name, storage, linkage, std::move(attrs), fs ), params(std::move(params)), returns(std::move(returns)),
    138           stmts( stmts ) {}
     136                std::vector<ptr<Attribute>>&& attrs = {}, Function::Specs fs = {}, bool isVarArgs = false);
     137        // : DeclWithType( loc, name, storage, linkage, std::move(attrs), fs ), params(std::move(params)), returns(std::move(returns)),
     138        //  stmts( stmts ) {}
    139139
    140140        const Type * get_type() const override;
  • src/AST/DeclReplacer.cpp

    r76d73fc rc532847  
    3838                        const ast::TypeInstType * previsit( const ast::TypeInstType * );
    3939                };
     40
     41                struct VarExprReplacer {
     42                private:
     43                        const ExprMap & exprMap;
     44                       
     45                public:
     46                        VarExprReplacer(const ExprMap & exprMap): exprMap (exprMap) {}
     47
     48                        const Expr * postvisit (const VariableExpr *);
     49                };
    4050        }
    4151
     
    5464                DeclMap declMap;
    5565                return replace( node, declMap, typeMap, debug );
     66        }
     67
     68        const ast::Node * replace( const ast::Node * node, const ExprMap & exprMap) {
     69                Pass<VarExprReplacer> replacer = {exprMap};
     70                return node->accept( replacer );
    5671        }
    5772
     
    88103                        return ninst;
    89104                }
     105
     106                const Expr * VarExprReplacer::postvisit( const VariableExpr * expr ) {
     107                        if (!exprMap.count(expr->var)) return expr;
     108
     109                        return exprMap.at(expr->var);
     110                }
     111
    90112        }
    91113}
  • src/AST/DeclReplacer.hpp

    r76d73fc rc532847  
    2323        class DeclWithType;
    2424        class TypeDecl;
     25        class Expr;
    2526
    2627        namespace DeclReplacer {
    2728                using DeclMap = std::unordered_map< const DeclWithType *, const DeclWithType * >;
    2829                using TypeMap = std::unordered_map< const TypeDecl *, const TypeDecl * >;
     30                using ExprMap = std::unordered_map< const DeclWithType *, const Expr * >;
    2931
    3032                const Node * replace( const Node * node, const DeclMap & declMap, bool debug = false );
    3133                const Node * replace( const Node * node, const TypeMap & typeMap, bool debug = false );
    3234                const Node * replace( const Node * node, const DeclMap & declMap, const TypeMap & typeMap, bool debug = false );
     35                const Node * replace( const Node * node, const ExprMap & exprMap);
    3336        }
    3437}
  • src/AST/Expr.cpp

    r76d73fc rc532847  
    6767// --- UntypedExpr
    6868
    69 UntypedExpr * UntypedExpr::createDeref( const CodeLocation & loc, Expr * arg ) {
     69UntypedExpr * UntypedExpr::createDeref( const CodeLocation & loc, const Expr * arg ) {
    7070        assert( arg );
    7171
     
    9292}
    9393
    94 UntypedExpr * UntypedExpr::createAssign( const CodeLocation & loc, Expr * lhs, Expr * rhs ) {
     94UntypedExpr * UntypedExpr::createAssign( const CodeLocation & loc, const Expr * lhs, const Expr * rhs ) {
    9595        assert( lhs && rhs );
    9696
  • src/AST/Expr.hpp

    r76d73fc rc532847  
    226226
    227227        /// Creates a new dereference expression
    228         static UntypedExpr * createDeref( const CodeLocation & loc, Expr * arg );
     228        static UntypedExpr * createDeref( const CodeLocation & loc, const Expr * arg );
    229229        /// Creates a new assignment expression
    230         static UntypedExpr * createAssign( const CodeLocation & loc, Expr * lhs, Expr * rhs );
     230        static UntypedExpr * createAssign( const CodeLocation & loc, const Expr * lhs, const Expr * rhs );
    231231
    232232        const Expr * accept( Visitor & v ) const override { return v.visit( this ); }
     
    422422                const CodeLocation & loc, const Type * ty, const std::string & r,
    423423                        std::optional<unsigned long long> i )
    424         : Expr( loc, ty ), rep( r ), ival( i ) {}
     424        : Expr( loc, ty ), rep( r ), ival( i ), underlyer(ty) {}
    425425
    426426        /// Gets the integer value of this constant, if one is appropriate to its type.
     
    617617
    618618        ImplicitCopyCtorExpr( const CodeLocation& loc, const ApplicationExpr * call )
    619         : Expr( loc, call->result ) { assert( call ); }
     619        : Expr( loc, call->result ), callExpr(call) { assert( call ); assert(call->result); }
    620620
    621621        const Expr * accept( Visitor & v ) const override { return v.visit( this ); }
     
    742742        std::vector<ptr<Expr>> dtors;              ///< destructor(s) for return variable(s)
    743743
     744        readonly<ExprStmt> resultExpr;
     745
    744746        StmtExpr( const CodeLocation & loc, const CompoundStmt * ss );
    745747
  • src/AST/Fwd.hpp

    r76d73fc rc532847  
    137137typedef unsigned int UniqueId;
    138138
     139extern Type * sizeType;
     140extern FunctionDecl * dereferenceOperator;
     141extern StructDecl   * dtorStruct;
     142extern FunctionDecl * dtorStructDestroy;
     143
    139144}
  • src/AST/Node.hpp

    r76d73fc rc532847  
    4949
    5050        bool unique() const { return strong_count == 1; }
     51        bool isManaged() const {return strong_count > 0; }
    5152
    5253private:
  • src/AST/Pass.hpp

    r76d73fc rc532847  
    236236        const ast::Expr * call_accept( const ast::Expr * );
    237237
     238        // requests WithStmtsToAdd directly add to this statement, as if it is a compound.
     239
     240        const ast::Stmt * call_accept_as_compound(const ast::Stmt *);
     241
    238242        template< typename node_t >
    239243        auto call_accept( const node_t * node ) -> typename std::enable_if<
     
    257261        template<typename node_t, typename parent_t, typename child_t>
    258262        void maybe_accept(const node_t * &, child_t parent_t::* child);
     263
     264        template<typename node_t, typename parent_t, typename child_t>
     265        void maybe_accept_as_compound(const node_t * &, child_t parent_t::* child);
    259266
    260267private:
  • src/AST/Pass.impl.hpp

    r76d73fc rc532847  
    167167                __pedantic_pass_assert( stmt );
    168168
     169                return stmt->accept( *this );
     170        }
     171
     172        template< typename core_t >
     173        const ast::Stmt * ast::Pass< core_t >::call_accept_as_compound( const ast::Stmt * stmt ) {
     174                __pedantic_pass_assert( __visit_children() );
     175                __pedantic_pass_assert( stmt );
     176
    169177                // add a few useful symbols to the scope
    170178                using __pass::empty;
     
    324332
    325333                auto new_val = call_accept( old_val );
     334
     335                static_assert( !std::is_same<const ast::Node *, decltype(new_val)>::value || std::is_same<int, decltype(old_val)>::value, "ERROR");
     336
     337                if( __pass::differs(old_val, new_val) ) {
     338                        auto new_parent = __pass::mutate<core_t>(parent);
     339                        new_parent->*child = new_val;
     340                        parent = new_parent;
     341                }
     342        }
     343
     344        template< typename core_t >
     345        template<typename node_t, typename parent_t, typename child_t>
     346        void ast::Pass< core_t >::maybe_accept_as_compound(
     347                const node_t * & parent,
     348                child_t parent_t::*child
     349        ) {
     350                static_assert( std::is_base_of<parent_t, node_t>::value, "Error deducing member object" );
     351
     352                if(__pass::skip(parent->*child)) return;
     353                const auto & old_val = __pass::get(parent->*child, 0);
     354
     355                static_assert( !std::is_same<const ast::Node * &, decltype(old_val)>::value, "ERROR");
     356
     357                auto new_val = call_accept_as_compound( old_val );
    326358
    327359                static_assert( !std::is_same<const ast::Node *, decltype(new_val)>::value || std::is_same<int, decltype(old_val)>::value, "ERROR");
     
    703735                maybe_accept( node, &IfStmt::inits    );
    704736                maybe_accept( node, &IfStmt::cond     );
    705                 maybe_accept( node, &IfStmt::thenPart );
    706                 maybe_accept( node, &IfStmt::elsePart );
     737                maybe_accept_as_compound( node, &IfStmt::thenPart );
     738                maybe_accept_as_compound( node, &IfStmt::elsePart );
    707739        })
    708740
     
    721753                maybe_accept( node, &WhileStmt::inits );
    722754                maybe_accept( node, &WhileStmt::cond  );
    723                 maybe_accept( node, &WhileStmt::body  );
     755                maybe_accept_as_compound( node, &WhileStmt::body  );
    724756        })
    725757
     
    736768                // for statements introduce a level of scope (for the initialization)
    737769                guard_symtab guard { *this };
     770                // xxx - old ast does not create WithStmtsToAdd scope for loop inits. should revisit this later.
    738771                maybe_accept( node, &ForStmt::inits );
    739772                maybe_accept( node, &ForStmt::cond  );
    740773                maybe_accept( node, &ForStmt::inc   );
    741                 maybe_accept( node, &ForStmt::body  );
     774                maybe_accept_as_compound( node, &ForStmt::body  );
    742775        })
    743776
     
    834867                maybe_accept( node, &CatchStmt::decl );
    835868                maybe_accept( node, &CatchStmt::cond );
    836                 maybe_accept( node, &CatchStmt::body );
     869                maybe_accept_as_compound( node, &CatchStmt::body );
    837870        })
    838871
  • src/AST/SymbolTable.cpp

    r76d73fc rc532847  
    335335}
    336336
    337 /*
    338 void SymbolTable::addFunctionType( const FunctionType * ftype ) {
    339         addTypes( ftype->forall );
    340         addIds( ftype->returns );
    341         addIds( ftype->params );
    342 }
    343 */
     337
     338void SymbolTable::addFunction( const FunctionDecl * func ) {
     339        addTypes( func->type->forall );
     340        addIds( func->returns );
     341        addIds( func->params );
     342}
     343
    344344
    345345void SymbolTable::lazyInitScope() {
  • src/AST/SymbolTable.hpp

    r76d73fc rc532847  
    145145
    146146        /// convenience function for adding all of the declarations in a function type to the indexer
    147         // void addFunctionType( const FunctionType * ftype );
     147        void addFunction( const FunctionDecl * );
    148148
    149149private:
  • src/Common/utility.h

    r76d73fc rc532847  
    360360        reverse_iterate_t( T & ref ) : ref(ref) {}
    361361
    362         typedef typename T::reverse_iterator iterator;
    363         iterator begin() { return ref.rbegin(); }
    364         iterator end() { return ref.rend(); }
     362        // this does NOT work on const T!!!
     363        // typedef typename T::reverse_iterator iterator;
     364        auto begin() { return ref.rbegin(); }
     365        auto end() { return ref.rend(); }
    365366};
    366367
  • src/GenPoly/GenPoly.cc

    r76d73fc rc532847  
    4646                }
    4747
     48                bool hasPolyParams( const std::vector<ast::ptr<ast::Expr>> & params, const ast::TypeSubstitution * env) {
     49                        for (auto &param : params) {
     50                                auto paramType = param.strict_as<ast::TypeExpr>();
     51                                if (isPolyType(paramType->type, env)) return true;
     52                        }
     53                        return false;
     54                }
     55
    4856                /// Checks a parameter list for polymorphic parameters from tyVars; will substitute according to env if present
    4957                bool hasPolyParams( std::list< Expression* >& params, const TyVarMap &tyVars, const TypeSubstitution *env ) {
     
    5664                }
    5765
     66                bool hasPolyParams( const std::vector<ast::ptr<ast::Expr>> & params, const TyVarMap & tyVars, const ast::TypeSubstitution * env) {
     67                        for (auto &param : params) {
     68                                auto paramType = param.strict_as<ast::TypeExpr>();
     69                                if (isPolyType(paramType->type, tyVars, env)) return true;
     70                        }
     71                        return false;
     72                }
     73
    5874                /// Checks a parameter list for dynamic-layout parameters from tyVars; will substitute according to env if present
    5975                bool hasDynParams( std::list< Expression* >& params, const TyVarMap &tyVars, const TypeSubstitution *env ) {
     
    92108                        Type *newType = env->lookup( typeInst->get_name() );
    93109                        if ( newType ) return newType;
     110                }
     111                return type;
     112        }
     113
     114        const ast::Type * replaceTypeInst(const ast::Type * type, const ast::TypeSubstitution * env) {
     115                if (!env) return type;
     116                if (auto typeInst = dynamic_cast<const ast::TypeInstType*> (type)) {
     117                        auto newType = env->lookup(typeInst->name);
     118                        if (newType) return newType;
    94119                }
    95120                return type;
     
    111136        }
    112137
     138        const ast::Type * isPolyType(const ast::Type * type, const ast::TypeSubstitution * env) {
     139                type = replaceTypeInst( type, env );
     140
     141                if ( dynamic_cast< const ast::TypeInstType * >( type ) ) {
     142                        return type;
     143                } else if ( auto arrayType = dynamic_cast< const ast::ArrayType * >( type ) ) {
     144                        return isPolyType( arrayType->base, env );
     145                } else if ( auto structType = dynamic_cast< const ast::StructInstType* >( type ) ) {
     146                        if ( hasPolyParams( structType->params, env ) ) return type;
     147                } else if ( auto unionType = dynamic_cast< const ast::UnionInstType* >( type ) ) {
     148                        if ( hasPolyParams( unionType->params, env ) ) return type;
     149                }
     150                return 0;
     151        }
     152
    113153        Type *isPolyType( Type *type, const TyVarMap &tyVars, const TypeSubstitution *env ) {
    114154                type = replaceTypeInst( type, env );
     
    126166                }
    127167                return 0;
     168        }
     169
     170        const ast::Type * isPolyType(const ast::Type * type, const TyVarMap & tyVars, const ast::TypeSubstitution * env) {
     171                type = replaceTypeInst( type, env );
     172
     173                if ( auto typeInst = dynamic_cast< const ast::TypeInstType * >( type ) ) {
     174                        return tyVars.find(typeInst->name) != tyVars.end() ? type : nullptr;
     175                } else if ( auto arrayType = dynamic_cast< const ast::ArrayType * >( type ) ) {
     176                        return isPolyType( arrayType->base, env );
     177                } else if ( auto structType = dynamic_cast< const ast::StructInstType* >( type ) ) {
     178                        if ( hasPolyParams( structType->params, env ) ) return type;
     179                } else if ( auto unionType = dynamic_cast< const ast::UnionInstType* >( type ) ) {
     180                        if ( hasPolyParams( unionType->params, env ) ) return type;
     181                }
     182                return nullptr;
    128183        }
    129184
     
    449504        }
    450505
     506        namespace {
     507                // temporary hack to avoid re-implementing anything related to TyVarMap
     508                // does this work? these two structs have identical definitions.
     509                inline TypeDecl::Data convData(const ast::TypeDecl::Data & data) {
     510                        return *reinterpret_cast<const TypeDecl::Data *>(&data);
     511                }
     512        }
     513
    451514        bool needsBoxing( Type * param, Type * arg, const TyVarMap &exprTyVars, const TypeSubstitution * env ) {
    452515                // is parameter is not polymorphic, don't need to box
     
    459522        }
    460523
     524        bool needsBoxing( const ast::Type * param, const ast::Type * arg, const TyVarMap &exprTyVars, const ast::TypeSubstitution * env) {
     525                // is parameter is not polymorphic, don't need to box
     526                if ( ! isPolyType( param, exprTyVars ) ) return false;
     527                ast::ptr<ast::Type> newType = arg;
     528                if ( env ) env->apply( newType );
     529                // if the argument's type is polymorphic, we don't need to box again!
     530                return ! isPolyType( newType );
     531        }
     532
    461533        bool needsBoxing( Type * param, Type * arg, ApplicationExpr * appExpr, const TypeSubstitution * env ) {
    462534                FunctionType * function = getFunctionType( appExpr->function->result );
     
    467539        }
    468540
     541        bool needsBoxing( const ast::Type * param, const ast::Type * arg, const ast::ApplicationExpr * appExpr, const ast::TypeSubstitution * env) {
     542                const ast::FunctionType * function = getFunctionType(appExpr->func->result);
     543                assertf( function, "ApplicationExpr has non-function type: %s", toString( appExpr->func->result ).c_str() );
     544                TyVarMap exprTyVars(TypeDecl::Data{});
     545                makeTyVarMap(function, exprTyVars);
     546                return needsBoxing(param, arg, exprTyVars, env);
     547
     548        }
     549
    469550        void addToTyVarMap( TypeDecl * tyVar, TyVarMap &tyVarMap ) {
    470551                tyVarMap.insert( tyVar->name, TypeDecl::Data{ tyVar } );
     552        }
     553
     554        void addToTyVarMap( const ast::TypeDecl * tyVar, TyVarMap & tyVarMap) {
     555                tyVarMap.insert(tyVar->name, convData(ast::TypeDecl::Data{tyVar}));
    471556        }
    472557
     
    478563                if ( PointerType *pointer = dynamic_cast< PointerType* >( type ) ) {
    479564                        makeTyVarMap( pointer->get_base(), tyVarMap );
     565                }
     566        }
     567
     568        void makeTyVarMap(const ast::Type * type, TyVarMap & tyVarMap) {
     569                if (auto ptype = dynamic_cast<const ast::ParameterizedType *>(type)) {
     570                        for (auto & tyVar : ptype->forall) {
     571                                assert (tyVar);
     572                                addToTyVarMap(tyVar, tyVarMap);
     573                        }
     574                }
     575                if (auto pointer = dynamic_cast<const ast::PointerType *>(type)) {
     576                        makeTyVarMap(pointer->base, tyVarMap);
    480577                }
    481578        }
  • src/GenPoly/GenPoly.h

    r76d73fc rc532847  
    2626
    2727namespace GenPoly {
     28
    2829        typedef ErasableScopedMap< std::string, TypeDecl::Data > TyVarMap;
    29 
    3030        /// Replaces a TypeInstType by its referrent in the environment, if applicable
    3131        Type* replaceTypeInst( Type* type, const TypeSubstitution* env );
     
    3333        /// returns polymorphic type if is polymorphic type, NULL otherwise; will look up substitution in env if provided
    3434        Type *isPolyType( Type *type, const TypeSubstitution *env = 0 );
     35        const ast::Type * isPolyType(const ast::Type * type, const ast::TypeSubstitution * env = nullptr);
    3536
    3637        /// returns polymorphic type if is polymorphic type in tyVars, NULL otherwise; will look up substitution in env if provided
    3738        Type *isPolyType( Type *type, const TyVarMap &tyVars, const TypeSubstitution *env = 0 );
     39        const ast::Type * isPolyType(const ast::Type * type, const TyVarMap & tyVars, const ast::TypeSubstitution * env = nullptr);
    3840
    3941        /// returns dynamic-layout type if is dynamic-layout type in tyVars, NULL otherwise; will look up substitution in env if provided
     
    8486        /// true if arg requires boxing given exprTyVars
    8587        bool needsBoxing( Type * param, Type * arg, const TyVarMap &exprTyVars, const TypeSubstitution * env );
     88        bool needsBoxing( const ast::Type * param, const ast::Type * arg, const TyVarMap &exprTyVars, const ast::TypeSubstitution * env);
    8689
    8790        /// true if arg requires boxing in the call to appExpr
    8891        bool needsBoxing( Type * param, Type * arg, ApplicationExpr * appExpr, const TypeSubstitution * env );
     92        bool needsBoxing( const ast::Type * param, const ast::Type * arg, const ast::ApplicationExpr * appExpr, const ast::TypeSubstitution * env);
    8993
    9094        /// Adds the type variable `tyVar` to `tyVarMap`
     
    9397        /// Adds the declarations in the forall list of type (and its pointed-to type if it's a pointer type) to `tyVarMap`
    9498        void makeTyVarMap( Type *type, TyVarMap &tyVarMap );
     99        void makeTyVarMap(const ast::Type * type, TyVarMap & tyVarMap);
    95100
    96101        /// Prints type variable map
  • src/InitTweak/FixGlobalInit.cc

    r76d73fc rc532847  
    3434#include "SynTree/Visitor.h"       // for acceptAll, Visitor
    3535
     36#include "AST/Expr.hpp"
     37#include "AST/Node.hpp"
     38#include "AST/Pass.hpp"
     39
    3640namespace InitTweak {
    3741        class GlobalFixer : public WithShortCircuiting {
     
    5054                FunctionDecl * initFunction;
    5155                FunctionDecl * destroyFunction;
     56        };
     57
     58        class GlobalFixer_new : public ast::WithShortCircuiting {
     59        public:
     60                void previsit (const ast::ObjectDecl *);
     61                void previsit (const ast::FunctionDecl *) { visit_children = false; }
     62                void previsit (const ast::StructDecl *) { visit_children = false; }
     63                void previsit (const ast::UnionDecl *) { visit_children = false; }
     64                void previsit (const ast::EnumDecl *) { visit_children = false; }
     65                void previsit (const ast::TraitDecl *) { visit_children = false; }
     66                void previsit (const ast::TypeDecl *) { visit_children = false; }
     67
     68                std::list< ast::ptr<ast::Stmt> > initStmts;
     69                std::list< ast::ptr<ast::Stmt> > destroyStmts;
    5270        };
    5371
     
    91109        }
    92110
     111        void fixGlobalInit(std::list<ast::ptr<ast::Decl>> & translationUnit, bool inLibrary) {
     112                ast::Pass<GlobalFixer_new> fixer;
     113                accept_all(translationUnit, fixer);
     114
     115                if ( !fixer.core.initStmts.empty() ) {
     116                        std::vector<ast::ptr<ast::Expr>> ctorParams;
     117                        if (inLibrary) ctorParams.emplace_back(ast::ConstantExpr::from_int({}, 200));
     118                        auto initFunction = new ast::FunctionDecl({}, "__global_init__", {}, {}, {}, new ast::CompoundStmt({}, std::move(fixer.core.initStmts)),
     119                                ast::Storage::Static, ast::Linkage::C, {new ast::Attribute("constructor", std::move(ctorParams))});
     120
     121                        translationUnit.emplace_back( initFunction );
     122                } // if
     123
     124                if ( !fixer.core.destroyStmts.empty() ) {
     125                        std::vector<ast::ptr<ast::Expr>> dtorParams;
     126                        if (inLibrary) dtorParams.emplace_back(ast::ConstantExpr::from_int({}, 200));
     127                        auto destroyFunction = new ast::FunctionDecl({}, "__global_destroy__", {}, {}, {}, new ast::CompoundStmt({}, std::move(fixer.core.destroyStmts)),
     128                                ast::Storage::Static, ast::Linkage::C, {new ast::Attribute("destructor", std::move(dtorParams))});
     129
     130                        translationUnit.emplace_back(destroyFunction);
     131                } // if
     132        }
     133
    93134        void GlobalFixer::previsit( ObjectDecl *objDecl ) {
    94135                std::list< Statement * > & initStatements = initFunction->get_statements()->get_kids();
     
    127168        }
    128169
     170        void GlobalFixer_new::previsit(const ast::ObjectDecl * objDecl) {
     171                auto mutDecl = mutate(objDecl);
     172                assertf(mutDecl == objDecl, "Global object decl must be unique");
     173                if ( auto ctorInit = objDecl->init.as<ast::ConstructorInit>() ) {
     174                        // a decision should have been made by the resolver, so ctor and init are not both non-NULL
     175                        assert( ! ctorInit->ctor || ! ctorInit->init );
     176
     177                        const ast::Stmt * dtor = ctorInit->dtor;
     178                        if ( dtor && ! isIntrinsicSingleArgCallStmt( dtor ) ) {
     179                                // don't need to call intrinsic dtor, because it does nothing, but
     180                                // non-intrinsic dtors must be called
     181                                destroyStmts.push_front( dtor );
     182                                // ctorInit->dtor = nullptr;
     183                        } // if
     184                        if ( const ast::Stmt * ctor = ctorInit->ctor ) {
     185                                initStmts.push_back( ctor );
     186                                mutDecl->init = nullptr;
     187                                // ctorInit->ctor = nullptr;
     188                        } else if ( const ast::Init * init = ctorInit->init ) {
     189                                mutDecl->init = init;
     190                                // ctorInit->init = nullptr;
     191                        } else {
     192                                // no constructor and no initializer, which is okay
     193                                mutDecl->init = nullptr;
     194                        } // if
     195                        // delete ctorInit;
     196                } // if
     197        }
     198
    129199        // only modify global variables
    130200        void GlobalFixer::previsit( FunctionDecl * ) { visit_children = false; }
  • src/InitTweak/FixGlobalInit.h

    r76d73fc rc532847  
    1919#include <string>  // for string
    2020
     21#include <AST/Fwd.hpp>
     22
     23
    2124class Declaration;
    2225
     
    2629        /// function is for library code.
    2730        void fixGlobalInit( std::list< Declaration * > & translationUnit, bool inLibrary );
     31        void fixGlobalInit( std::list< ast::ptr<ast::Decl> > & translationUnit, bool inLibrary );
    2832} // namespace
    2933
  • src/InitTweak/FixInit.cc

    r76d73fc rc532847  
    219219                };
    220220
    221                 struct SplitExpressions : public WithShortCircuiting, public WithTypeSubstitution, public WithStmtsToAdd {
     221                struct SplitExpressions : public WithShortCircuiting, /*public WithTypeSubstitution, */public WithStmtsToAdd {
    222222                        /// add CompoundStmts around top-level expressions so that temporaries are destroyed in the correct places.
    223223                        static void split( std::list< Declaration * > &translationUnit );
  • src/InitTweak/FixInit.h

    r76d73fc rc532847  
    1919#include <string>  // for string
    2020
     21#include <AST/Fwd.hpp>
     22
    2123class Declaration;
    2224
     
    2426        /// replace constructor initializers with expression statements and unwrap basic C-style initializers
    2527        void fix( std::list< Declaration * > & translationUnit, bool inLibrary );
     28
     29        void fix( std::list<ast::ptr<ast::Decl>> & translationUnit, bool inLibrary);
    2630} // namespace
    2731
  • src/InitTweak/GenInit.cc

    r76d73fc rc532847  
    283283                assert( stmts.size() <= 1 );
    284284                return stmts.size() == 1 ? strict_dynamic_cast< ImplicitCtorDtorStmt * >( stmts.front() ) : nullptr;
     285
     286        }
     287
     288        ast::ptr<ast::Stmt> genCtorDtor (const CodeLocation & loc, const std::string & fname, const ast::ObjectDecl * objDecl, const ast::Expr * arg) {
     289                assertf(objDecl, "genCtorDtor passed null objDecl");
     290                InitExpander_new srcParam(arg);
     291                return SymTab::genImplicitCall(srcParam, new ast::VariableExpr(loc, objDecl), loc, fname, objDecl);
    285292        }
    286293
  • src/InitTweak/GenInit.h

    r76d73fc rc532847  
    3333        /// generates a single ctor/dtor statement using objDecl as the 'this' parameter and arg as the optional argument
    3434        ImplicitCtorDtorStmt * genCtorDtor( const std::string & fname, ObjectDecl * objDecl, Expression * arg = nullptr );
     35        ast::ptr<ast::Stmt> genCtorDtor (const CodeLocation & loc, const std::string & fname, const ast::ObjectDecl * objDecl, const ast::Expr * arg = nullptr);
    3536
    3637        /// creates an appropriate ConstructorInit node which contains a constructor, destructor, and C-initializer
  • src/InitTweak/InitTweak.cc

    r76d73fc rc532847  
    498498        }
    499499
     500        const ast::ObjectDecl * getParamThis(const ast::FunctionDecl * func) {
     501                assertf( func, "getParamThis: nullptr ftype" );
     502                auto & params = func->params;
     503                assertf( ! params.empty(), "getParamThis: ftype with 0 parameters: %s", toString( func ).c_str());
     504                return params.front().strict_as<ast::ObjectDecl>();
     505        }
     506
    500507        bool tryConstruct( DeclarationWithType * dwt ) {
    501508                ObjectDecl * objDecl = dynamic_cast< ObjectDecl * >( dwt );
     
    511518        }
    512519
     520        bool tryConstruct( const ast::DeclWithType * dwt ) {
     521                auto objDecl = dynamic_cast< const ast::ObjectDecl * >( dwt );
     522                if ( ! objDecl ) return false;
     523                return (objDecl->init == nullptr ||
     524                                ( objDecl->init != nullptr && objDecl->init->maybeConstructed ))
     525                        && ! objDecl->storage.is_extern
     526                        && isConstructable( objDecl->type );
     527        }
     528
     529        bool isConstructable( const ast::Type * type ) {
     530                return ! dynamic_cast< const ast::VarArgsType * >( type ) && ! dynamic_cast< const ast::ReferenceType * >( type )
     531                && ! dynamic_cast< const ast::FunctionType * >( type ) && ! Tuples::isTtype( type );
     532        }
     533
    513534        struct CallFinder_old {
    514535                CallFinder_old( const std::list< std::string > & names ) : names( names ) {}
     
    536557
    537558        struct CallFinder_new final {
    538                 std::vector< ast::ptr< ast::Expr > > matches;
     559                std::vector< const ast::Expr * > matches;
    539560                const std::vector< std::string > names;
    540561
     
    558579        }
    559580
    560         std::vector< ast::ptr< ast::Expr > > collectCtorDtorCalls( const ast::Stmt * stmt ) {
     581        std::vector< const ast::Expr * > collectCtorDtorCalls( const ast::Stmt * stmt ) {
    561582                ast::Pass< CallFinder_new > finder{ std::vector< std::string >{ "?{}", "^?{}" } };
    562583                maybe_accept( stmt, finder );
     
    696717                template <typename Predicate>
    697718                bool allofCtorDtor( const ast::Stmt * stmt, const Predicate & pred ) {
    698                         std::vector< ast::ptr< ast::Expr > > callExprs = collectCtorDtorCalls( stmt );
     719                        std::vector< const ast::Expr * > callExprs = collectCtorDtorCalls( stmt );
    699720                        return std::all_of( callExprs.begin(), callExprs.end(), pred );
    700721                }
     
    939960        }
    940961
     962        // looks like some other such codegen uses UntypedExpr and does not create fake function. should revisit afterwards
     963        // following passes may accidentally resolve this expression if returned as untyped...
     964        ast::Expr * createBitwiseAssignment (const ast::Expr * dst, const ast::Expr * src) {
     965                static ast::ptr<ast::FunctionDecl> assign = nullptr;
     966                if (!assign) {
     967                        auto td = new ast::TypeDecl({}, "T", {}, nullptr, ast::TypeDecl::Dtype, true);
     968                        assign = new ast::FunctionDecl({}, "?=?", {},
     969                        { new ast::ObjectDecl({}, "_dst", new ast::ReferenceType(new ast::TypeInstType("T", td))),
     970                          new ast::ObjectDecl({}, "_src", new ast::TypeInstType("T", td))},
     971                        { new ast::ObjectDecl({}, "_ret", new ast::TypeInstType("T", td))}, nullptr, {}, ast::Linkage::Intrinsic);
     972                }
     973                if (dst->result.as<ast::ReferenceType>()) {
     974                        for (int depth = dst->result->referenceDepth(); depth > 0; depth--) {
     975                                dst = new ast::AddressExpr(dst);
     976                        }
     977                }
     978                else {
     979                        dst = new ast::CastExpr(dst, new ast::ReferenceType(dst->result, {}));
     980                }
     981                if (src->result.as<ast::ReferenceType>()) {
     982                        for (int depth = src->result->referenceDepth(); depth > 0; depth--) {
     983                                src = new ast::AddressExpr(src);
     984                        }
     985                }
     986                return new ast::ApplicationExpr(dst->location, ast::VariableExpr::functionPointer(dst->location, assign), {dst, src});
     987        }
     988
    941989        struct ConstExprChecker : public WithShortCircuiting {
    942990                // most expressions are not const expr
  • src/InitTweak/InitTweak.h

    r76d73fc rc532847  
    3838        /// returns the first parameter of a constructor/destructor/assignment function
    3939        ObjectDecl * getParamThis( FunctionType * ftype );
     40        const ast::ObjectDecl * getParamThis(const ast::FunctionDecl * func);
    4041
    4142        /// generate a bitwise assignment operation.
    4243        ApplicationExpr * createBitwiseAssignment( Expression * dst, Expression * src );
     44
     45        ast::Expr * createBitwiseAssignment( const ast::Expr * dst, const ast::Expr * src);
    4346
    4447        /// transform Initializer into an argument list that can be passed to a call expression
     
    4851        /// True if the resolver should try to construct dwt
    4952        bool tryConstruct( DeclarationWithType * dwt );
     53        bool tryConstruct( const ast::DeclWithType * dwt );
    5054
    5155        /// True if the type can have a user-defined constructor
    5256        bool isConstructable( Type * t );
     57        bool isConstructable( const ast::Type * t );
    5358
    5459        /// True if the Initializer contains designations
     
    7984        /// get all Ctor/Dtor call expressions from a Statement
    8085        void collectCtorDtorCalls( Statement * stmt, std::list< Expression * > & matches );
    81         std::vector< ast::ptr< ast::Expr > > collectCtorDtorCalls( const ast::Stmt * stmt );
     86        std::vector< const ast::Expr * > collectCtorDtorCalls( const ast::Stmt * stmt );
    8287
    8388        /// get the Ctor/Dtor call expression from a Statement that looks like a generated ctor/dtor call
  • src/InitTweak/module.mk

    r76d73fc rc532847  
    2323        InitTweak/GenInit.h \
    2424        InitTweak/InitTweak.cc \
    25         InitTweak/InitTweak.h
     25        InitTweak/InitTweak.h \
     26        InitTweak/FixInitNew.cpp
    2627
    2728SRCDEMANGLE += \
  • src/ResolvExpr/Resolver.cc

    r76d73fc rc532847  
    11051105                }
    11061106
    1107                 /// Establish post-resolver invariants for expressions
     1107               
     1108        } // anonymous namespace
     1109/// Establish post-resolver invariants for expressions
    11081110                void finishExpr(
    11091111                        ast::ptr< ast::Expr > & expr, const ast::TypeEnvironment & env,
     
    11181120                        StripCasts_new::strip( expr );
    11191121                }
    1120         } // anonymous namespace
    1121 
    11221122
    11231123        ast::ptr< ast::Expr > resolveInVoidContext(
     
    11391139        }
    11401140
    1141         namespace {
    1142                 /// Resolve `untyped` to the expression whose candidate is the best match for a `void`
     1141        /// Resolve `untyped` to the expression whose candidate is the best match for a `void`
    11431142                /// context.
    11441143                ast::ptr< ast::Expr > findVoidExpression(
     
    11511150                        return newExpr;
    11521151                }
     1152
     1153        namespace {
     1154               
    11531155
    11541156                /// resolve `untyped` to the expression whose candidate satisfies `pred` with the
     
    11621164                        CandidateRef choice =
    11631165                                findUnfinishedKindExpression( untyped, symtab, kind, pred, mode );
    1164                         finishExpr( choice->expr, choice->env, untyped->env );
     1166                        ResolvExpr::finishExpr( choice->expr, choice->env, untyped->env );
    11651167                        return std::move( choice->expr );
    11661168                }
  • src/ResolvExpr/Resolver.h

    r76d73fc rc532847  
    6666        ast::ptr< ast::Expr > findSingleExpression(
    6767                const ast::Expr * untyped, const ast::Type * type, const ast::SymbolTable & symtab );
     68        ast::ptr< ast::Expr > findVoidExpression(
     69                const ast::Expr * untyped, const ast::SymbolTable & symtab);
    6870        /// Resolves a constructor init expression
    6971        ast::ptr< ast::Init > resolveCtorInit(
  • src/SymTab/Autogen.cc

    r76d73fc rc532847  
    233233        }
    234234
     235        // shallow copy the pointer list for return
     236        std::vector<ast::ptr<ast::TypeDecl>> getGenericParams (const ast::Type * t) {
     237                if (auto structInst = dynamic_cast<const ast::StructInstType*>(t)) {
     238                        return structInst->base->params;
     239                }
     240                if (auto unionInst = dynamic_cast<const ast::UnionInstType*>(t)) {
     241                        return unionInst->base->params;
     242                }
     243                return {};
     244        }
     245
    235246        /// given type T, generate type of default ctor/dtor, i.e. function type void (*) (T *)
    236247        FunctionType * genDefaultType( Type * paramType, bool maybePolymorphic ) {
     
    244255                ftype->parameters.push_back( dstParam );
    245256                return ftype;
     257        }
     258
     259        ///
     260        ast::FunctionDecl * genDefaultFunc(const CodeLocation loc, const std::string fname, const ast::Type * paramType, bool maybePolymorphic) {
     261                std::vector<ast::ptr<ast::TypeDecl>> typeParams;
     262                if (maybePolymorphic) typeParams = getGenericParams(paramType);
     263                auto dstParam = new ast::ObjectDecl(loc, "_dst", new ast::ReferenceType(paramType), nullptr, {}, ast::Linkage::Cforall);
     264                return new ast::FunctionDecl(loc, fname, std::move(typeParams), {dstParam}, {}, new ast::CompoundStmt(loc));
    246265        }
    247266
  • src/SymTab/Autogen.h

    r76d73fc rc532847  
    5555        /// maybePolymorphic is true if the resulting FunctionType is allowed to be polymorphic
    5656        FunctionType * genDefaultType( Type * paramType, bool maybePolymorphic = true );
     57
     58        ast::FunctionDecl * genDefaultFunc(const CodeLocation loc, const std::string fname, const ast::Type * paramType, bool maybePolymorphic = true);
    5759
    5860        /// generate the type of a copy constructor for paramType.
  • src/main.cc

    r76d73fc rc532847  
    343343                        auto transUnit = convert( move( translationUnit ) );
    344344                        PASS( "Resolve", ResolvExpr::resolve( transUnit ) );
     345                        if ( exprp ) {
     346                                translationUnit = convert( move( transUnit ) );
     347                                dump( translationUnit );
     348                                return EXIT_SUCCESS;
     349                        } // if
     350
     351                        PASS( "Fix Init", InitTweak::fix(transUnit, buildingLibrary()));
    345352                        translationUnit = convert( move( transUnit ) );
    346353                } else {
    347354                        PASS( "Resolve", ResolvExpr::resolve( translationUnit ) );
     355                        if ( exprp ) {
     356                                dump( translationUnit );
     357                                return EXIT_SUCCESS;
     358                        }
     359
     360                        PASS( "Fix Init", InitTweak::fix( translationUnit, buildingLibrary() ) );
    348361                }
    349362
    350                 if ( exprp ) {
    351                         dump( translationUnit );
    352                         return EXIT_SUCCESS;
    353                 } // if
    354 
    355363                // fix ObjectDecl - replaces ConstructorInit nodes
    356                 PASS( "Fix Init", InitTweak::fix( translationUnit, buildingLibrary() ) );
    357364                if ( ctorinitp ) {
    358365                        dump ( translationUnit );
Note: See TracChangeset for help on using the changeset viewer.