Changeset fc12f05 for src/GenPoly


Ignore:
Timestamp:
Nov 13, 2023, 3:43:43 AM (2 years ago)
Author:
JiadaL <j82liang@…>
Branches:
master
Children:
25f2798
Parents:
0030b508 (diff), 2174191 (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/GenPoly
Files:
4 deleted
9 edited

Legend:

Unmodified
Added
Removed
  • src/GenPoly/BoxNew.cpp

    r0030b508 rfc12f05  
    3939
    4040namespace {
    41 
    42 /// Common field of several sub-passes of box.
    43 struct BoxPass {
    44         TypeVarMap scopeTypeVars;
    45         BoxPass() : scopeTypeVars( ast::TypeData() ) {}
    46 };
    47 
    48 // TODO: Could this be a common helper somewhere?
    49 ast::FunctionType * makeFunctionType( ast::FunctionDecl const * decl ) {
    50         ast::FunctionType * type = new ast::FunctionType(
    51                 decl->type->isVarArgs, decl->type->qualifiers
    52         );
    53         for ( auto type_param : decl->type_params ) {
    54                 type->forall.emplace_back( new ast::TypeInstType( type_param ) );
    55         }
    56         for ( auto assertion : decl->assertions ) {
    57                 type->assertions.emplace_back( new ast::VariableExpr(
    58                         assertion->location, assertion ) );
    59         }
    60         for ( auto param : decl->params ) {
    61                 type->params.emplace_back( param->get_type() );
    62         }
    63         for ( auto retval : decl->returns ) {
    64                 type->returns.emplace_back( retval->get_type() );
    65         }
    66         return type;
    67 }
    6841
    6942// --------------------------------------------------------------------------
     
    359332/// * Adds appropriate type variables to the function calls.
    360333struct CallAdapter final :
    361                 public BoxPass,
    362334                public ast::WithConstTypeSubstitution,
    363335                public ast::WithGuards,
     
    376348        ast::Expr const * postvisit( ast::AddressExpr const * expr );
    377349        ast::ReturnStmt const * previsit( ast::ReturnStmt const * stmt );
    378         void previsit( ast::PointerType const * type );
    379         void previsit( ast::FunctionType const * type );
    380350
    381351        void beginScope();
     
    440410                CodeLocation const & location, ast::Type const * type );
    441411
    442         /// Set of adapter functions in the current scope.
     412        TypeVarMap scopeTypeVars;
    443413        ScopedMap< std::string, ast::DeclWithType const * > adapters;
    444414        std::map< ast::ApplicationExpr const *, ast::Expr const * > retVals;
     
    553523
    554524ast::FunctionDecl const * CallAdapter::previsit( ast::FunctionDecl const * decl ) {
     525        // Prevent type declaration information from leaking out.
     526        GuardScope( scopeTypeVars );
     527
    555528        if ( nullptr == decl->stmts ) {
    556                 // This may keep TypeDecls we don't ever want from sneaking in.
    557                 // Not visiting child nodes might just be faster.
    558                 GuardScope( scopeTypeVars );
    559529                return decl;
    560530        }
    561531
    562         GuardScope( scopeTypeVars );
    563532        GuardValue( retval );
    564533
     
    662631        ptrdiff_t initArgCount = mutExpr->args.size();
    663632
    664         TypeVarMap exprTypeVars = { ast::TypeData() };
     633        TypeVarMap exprTypeVars;
    665634        // TODO: Should this take into account the variables already bound in
    666635        // scopeTypeVars ([ex] remove them from exprTypeVars)?
     
    687656
    688657        assert( typeSubs );
    689         ast::Type const * concRetType = replaceWithConcrete( dynRetType, *typeSubs );
    690         // Used to use dynRetType instead of concRetType; this changed so that
    691         // the correct type parameters are passed for return types (it should be
    692         // the concrete type's parameters, not the formal type's).
    693658        ast::vector<ast::Expr>::iterator argIt =
    694659                passTypeVars( mutExpr, function );
     
    768733        }
    769734        return stmt;
    770 }
    771 
    772 void CallAdapter::previsit( ast::PointerType const * type ) {
    773         GuardScope( scopeTypeVars );
    774         makeTypeVarMap( type, scopeTypeVars );
    775 }
    776 
    777 void CallAdapter::previsit( ast::FunctionType const * type ) {
    778         GuardScope( scopeTypeVars );
    779         makeTypeVarMap( type, scopeTypeVars );
    780735}
    781736
     
    14271382
    14281383ast::FunctionDecl const * DeclAdapter::previsit( ast::FunctionDecl const * decl ) {
    1429         TypeVarMap localTypeVars = { ast::TypeData() };
     1384        TypeVarMap localTypeVars;
    14301385        makeTypeVarMap( decl, localTypeVars );
    14311386
     
    14581413                        layoutParams.emplace_back( alignParam );
    14591414                }
    1460                 // TODO: These should possibly all be gone.
    1461                 // More all assertions into parameter list.
    1462                 for ( ast::ptr<ast::DeclWithType> & assert : mutParam->assertions ) {
    1463                         // Assertion parameters may not be used in body,
    1464                         // pass along with unused attribute.
    1465                         assert.get_and_mutate()->attributes.push_back(
    1466                                 new ast::Attribute( "unused" ) );
    1467                         inferredParams.push_back( assert );
    1468                 }
    1469                 mutParam->assertions.clear();
     1415                // Assertions should be stored in the main list.
     1416                assert( mutParam->assertions.empty() );
    14701417                typeParam = mutParam;
    14711418        }
    1472         // TODO: New version of inner loop.
    14731419        for ( ast::ptr<ast::DeclWithType> & assert : mutDecl->assertions ) {
    14741420                // Assertion parameters may not be used in body,
     
    14851431        spliceBegin( mutDecl->params, layoutParams );
    14861432        addAdapters( mutDecl, localTypeVars );
     1433
     1434        // Now have to update the type to match the declaration.
     1435        ast::FunctionType * type = new ast::FunctionType(
     1436                mutDecl->type->isVarArgs, mutDecl->type->qualifiers );
     1437        for ( auto type_param : mutDecl->type_params ) {
     1438                type->forall.emplace_back( new ast::TypeInstType( type_param ) );
     1439        }
     1440        for ( auto param : mutDecl->params ) {
     1441                type->params.emplace_back( param->get_type() );
     1442        }
     1443        for ( auto retval : mutDecl->returns ) {
     1444                type->returns.emplace_back( retval->get_type() );
     1445        }
     1446        mutDecl->type = type;
    14871447
    14881448        return mutDecl;
     
    15181478                }
    15191479        }
    1520         // TODO: Can this be updated as we go along?
    1521         mutDecl->type = makeFunctionType( mutDecl );
    15221480        return mutDecl;
    15231481}
     
    15751533        assertf( it != adapters.end(), "Could not correct floating node." );
    15761534        return ast::mutate_field( expr, &ast::VariableExpr::var, it->second );
    1577 
    15781535}
    15791536
     
    15871544/// * Inserts dynamic calculation of polymorphic type layouts where needed.
    15881545struct PolyGenericCalculator final :
    1589                 public BoxPass,
    15901546                public ast::WithConstTypeSubstitution,
    15911547                public ast::WithDeclsToAdd<>,
     
    15951551        PolyGenericCalculator();
    15961552
    1597         void previsit( ast::ObjectDecl const * decl );
    15981553        void previsit( ast::FunctionDecl const * decl );
    15991554        void previsit( ast::TypedefDecl const * decl );
     
    16021557        ast::StructDecl const * previsit( ast::StructDecl const * decl );
    16031558        ast::UnionDecl const * previsit( ast::UnionDecl const * decl );
    1604         void previsit( ast::PointerType const * type );
    1605         void previsit( ast::FunctionType const * type );
    16061559        ast::DeclStmt const * previsit( ast::DeclStmt const * stmt );
    16071560        ast::Expr const * postvisit( ast::MemberExpr const * expr );
     
    16351588        /// C sizeof().
    16361589        ast::Expr const * genSizeof( CodeLocation const &, ast::Type const * );
    1637 
    16381590        /// Enters a new scope for type-variables,
    16391591        /// adding the type variables from the provided type.
    16401592        void beginTypeScope( ast::Type const * );
    1641         /// Enters a new scope for known layouts and offsets, and queues exit calls.
    1642         void beginGenericScope();
    1643 
     1593
     1594        /// The type variables and polymorphic parameters currently in scope.
     1595        TypeVarMap scopeTypeVars;
    16441596        /// Set of generic type layouts known in the current scope,
    16451597        /// indexed by sizeofName.
     
    16521604        /// If the argument of an AddressExpr is MemberExpr, it is stored here.
    16531605        ast::MemberExpr const * addrMember = nullptr;
    1654         /// Used to avoid recursing too deep in type declarations.
    1655         bool expect_func_type = false;
    16561606};
    16571607
     
    16751625}
    16761626
    1677 void PolyGenericCalculator::previsit( ast::ObjectDecl const * decl ) {
    1678         beginTypeScope( decl->type );
    1679 }
    1680 
    16811627void PolyGenericCalculator::previsit( ast::FunctionDecl const * decl ) {
    1682         beginGenericScope();
     1628        GuardScope( *this );
    16831629        beginTypeScope( decl->type );
    16841630}
     
    16961642                ast::TypeDecl const * decl ) {
    16971643        ast::Type const * base = decl->base;
    1698         if ( nullptr == base) return decl;
     1644        if ( nullptr == base ) return decl;
    16991645
    17001646        // Add size/align variables for opaque type declarations.
     
    17211667        alignDecl->accept( *visitor );
    17221668
    1723         // Can't use [makeVar], because it inserts into stmtsToAdd and TypeDecls
    1724         // can occur at global scope.
     1669        // A little trick to replace this with two declarations.
     1670        // Adding after makes sure that there is no conflict with adding stmts.
    17251671        declsToAddAfter.push_back( alignDecl );
    1726         // replace with sizeDecl.
    17271672        return sizeDecl;
    17281673}
     
    17421687}
    17431688
    1744 void PolyGenericCalculator::previsit( ast::PointerType const * type ) {
    1745         beginTypeScope( type );
    1746 }
    1747 
    1748 void PolyGenericCalculator::previsit( ast::FunctionType const * type ) {
    1749         beginTypeScope( type );
    1750 
    1751         GuardValue( expect_func_type );
    1752         GuardScope( *this );
    1753 
    1754         // The other functions type we will see in this scope are probably
    1755         // function parameters they don't help us with the layout and offsets so
    1756         // don't mark them as known in this scope.
    1757         expect_func_type = false;
    1758 }
    1759 
    1760 //void PolyGenericCalculator::previsit( ast::DeclStmt const * stmt ) {
    17611689ast::DeclStmt const * PolyGenericCalculator::previsit( ast::DeclStmt const * stmt ) {
    17621690        ast::ObjectDecl const * decl = stmt->decl.as<ast::ObjectDecl>();
     
    17661694
    17671695        // Change initialization of a polymorphic value object to allocate via a
    1768         // variable-length-array (alloca was previouly used, but it cannot be
    1769         // safely used in loops).
     1696        // variable-length-array (alloca cannot be safely used in loops).
    17701697        ast::ObjectDecl * newBuf = new ast::ObjectDecl( decl->location,
    17711698                bufNamer.newName(),
     
    22482175}
    22492176
    2250 void PolyGenericCalculator::beginGenericScope() {
    2251         GuardScope( *this );
    2252         // We expect the first function type see to be the type relating to this
    2253         // scope but any further type is probably some unrelated function pointer
    2254         // keep track of whrich is the first.
    2255         GuardValue( expect_func_type ) = true;
    2256 }
    2257 
    22582177// --------------------------------------------------------------------------
    2259 /// No common theme found.
     2178/// Removes unneeded or incorrect type information.
    22602179/// * Replaces initialization of polymorphic values with alloca.
    22612180/// * Replaces declaration of dtype/ftype with appropriate void expression.
     
    22632182/// * Strips fields from generic structure declarations.
    22642183struct Eraser final :
    2265                 public BoxPass,
    22662184                public ast::WithGuards {
    22672185        void guardTypeVarMap( ast::Type const * type ) {
     
    22782196        void previsit( ast::PointerType const * type );
    22792197        void previsit( ast::FunctionType const * type );
     2198public:
     2199        TypeVarMap scopeTypeVars;
    22802200};
    22812201
  • src/GenPoly/FindFunction.cc

    r0030b508 rfc12f05  
    2020#include "AST/Pass.hpp"                 // for Pass
    2121#include "AST/Type.hpp"
    22 #include "Common/PassVisitor.h"         // for PassVisitor
    2322#include "GenPoly/ErasableScopedMap.h"  // for ErasableScopedMap<>::iterator
    2423#include "GenPoly/GenPoly.h"            // for TyVarMap
    2524#include "ScrubTyVars.h"                // for ScrubTyVars
    26 #include "SynTree/Declaration.h"        // for DeclarationWithType, TypeDecl
    27 #include "SynTree/Mutator.h"            // for Mutator, mutateAll
    28 #include "SynTree/Type.h"               // for FunctionType, Type, Type::For...
    2925
    3026namespace GenPoly {
    31         class FindFunction : public WithGuards, public WithVisitorRef<FindFunction>, public WithShortCircuiting {
    32           public:
    33                 FindFunction( std::list< FunctionType const* > &functions, const TyVarMap &tyVars, bool replaceMode, FindFunctionPredicate predicate );
    34 
    35                 void premutate( FunctionType * functionType );
    36                 Type * postmutate( FunctionType * functionType );
    37                 void premutate( PointerType * pointerType );
    38           private:
    39                 void handleForall( const Type::ForallList &forall );
    40 
    41                 std::list< FunctionType const * > & functions;
    42                 TyVarMap tyVars;
    43                 bool replaceMode;
    44                 FindFunctionPredicate predicate;
    45         };
    46 
    47         void findFunction( Type *type, std::list< FunctionType const * > &functions, const TyVarMap &tyVars, FindFunctionPredicate predicate ) {
    48                 PassVisitor<FindFunction> finder( functions, tyVars, false, predicate );
    49                 type->acceptMutator( finder );
    50         }
    51 
    52         void findAndReplaceFunction( Type *&type, std::list< FunctionType const * > &functions, const TyVarMap &tyVars, FindFunctionPredicate predicate ) {
    53                 PassVisitor<FindFunction> finder( functions, tyVars, true, predicate );
    54                 type = type->acceptMutator( finder );
    55         }
    56 
    57         FindFunction::FindFunction( std::list< FunctionType const * > &functions, const TyVarMap &tyVars, bool replaceMode, FindFunctionPredicate predicate )
    58                 : functions( functions ), tyVars( tyVars ), replaceMode( replaceMode ), predicate( predicate ) {
    59         }
    60 
    61         void FindFunction::handleForall( const Type::ForallList &forall ) {
    62                 for ( const Declaration * td : forall ) {
    63                         TyVarMap::iterator var = tyVars.find( td->name );
    64                         if ( var != tyVars.end() ) {
    65                                 tyVars.erase( var->first );
    66                         } // if
    67                 } // for
    68         }
    69 
    70         void FindFunction::premutate( FunctionType * functionType ) {
    71                 visit_children = false;
    72                 GuardScope( tyVars );
    73                 handleForall( functionType->get_forall() );
    74                 mutateAll( functionType->get_returnVals(), *visitor );
    75         }
    76 
    77         Type * FindFunction::postmutate( FunctionType * functionType ) {
    78                 Type *ret = functionType;
    79                 if ( predicate( functionType, tyVars ) ) {
    80                         functions.push_back( functionType );
    81                         if ( replaceMode ) {
    82                                 // replace type parameters in function type with void*
    83                                 ret = ScrubTyVars::scrub( functionType->clone(), tyVars );
    84                         } // if
    85                 } // if
    86                 return ret;
    87         }
    88 
    89         void FindFunction::premutate( PointerType * pointerType ) {
    90                 GuardScope( tyVars );
    91                 handleForall( pointerType->get_forall() );
    92         }
    9327
    9428namespace {
     
    15488void FindFunctionCore::previsit( ast::PointerType const * /*type*/ ) {
    15589        GuardScope( typeVars );
    156         //handleForall( type->forall );
    15790}
    15891
     
    16497        ast::Pass<FindFunctionCore> pass( functions, typeVars, predicate, false );
    16598        type->accept( pass );
    166         //(void)type;
    167         //(void)functions;
    168         //(void)typeVars;
    169         //(void)predicate;
    17099}
    171100
     
    175104        ast::Pass<FindFunctionCore> pass( functions, typeVars, predicate, true );
    176105        return type->accept( pass );
    177         //(void)functions;
    178         //(void)typeVars;
    179         //(void)predicate;
    180         //return type;
    181106}
    182107
  • src/GenPoly/FindFunction.h

    r0030b508 rfc12f05  
    1616#pragma once
    1717
    18 #include <list>       // for list
    19 
    2018#include "GenPoly.h"  // for TyVarMap
    2119
    22 class FunctionType;
    23 class Type;
    24 
    2520namespace GenPoly {
    26         typedef bool (*FindFunctionPredicate)( FunctionType*, const TyVarMap& );
    27 
    28         /// recursively walk `type`, placing all functions that match `predicate` under `tyVars` into `functions`
    29         void findFunction( Type *type, std::list< FunctionType const * > &functions, const TyVarMap &tyVars, FindFunctionPredicate predicate );
    30         /// like `findFunction`, but also replaces the function type with void ()(void)
    31         void findAndReplaceFunction( Type *&type, std::list< FunctionType const * > &functions, const TyVarMap &tyVars, FindFunctionPredicate predicate );
    3221
    3322typedef bool (*FindFunctionPred)( const ast::FunctionType *, const TypeVarMap & );
  • src/GenPoly/GenPoly.cc

    r0030b508 rfc12f05  
    2929#include "GenPoly/ErasableScopedMap.h"  // for ErasableScopedMap<>::const_it...
    3030#include "ResolvExpr/typeops.h"         // for flatten
    31 #include "SynTree/Constant.h"           // for Constant
    32 #include "SynTree/Expression.h"         // for Expression, TypeExpr, Constan...
    33 #include "SynTree/Type.h"               // for Type, StructInstType, UnionIn...
    34 #include "SynTree/TypeSubstitution.h"   // for TypeSubstitution
    3531
    3632using namespace std;
     
    3935        namespace {
    4036                /// Checks a parameter list for polymorphic parameters; will substitute according to env if present
    41                 bool hasPolyParams( std::list< Expression* >& params, const TypeSubstitution *env ) {
    42                         for ( std::list< Expression* >::iterator param = params.begin(); param != params.end(); ++param ) {
    43                                 TypeExpr *paramType = dynamic_cast< TypeExpr* >( *param );
    44                                 assertf(paramType, "Aggregate parameters should be type expressions");
    45                                 if ( isPolyType( paramType->get_type(), env ) ) return true;
    46                         }
    47                         return false;
    48                 }
    49 
    5037                bool hasPolyParams( const std::vector<ast::ptr<ast::Expr>> & params, const ast::TypeSubstitution * env ) {
    5138                        for ( auto &param : params ) {
     
    5845
    5946                /// Checks a parameter list for polymorphic parameters from tyVars; will substitute according to env if present
    60                 bool hasPolyParams( std::list< Expression* >& params, const TyVarMap &tyVars, const TypeSubstitution *env ) {
    61                         for ( std::list< Expression* >::iterator param = params.begin(); param != params.end(); ++param ) {
    62                                 TypeExpr *paramType = dynamic_cast< TypeExpr* >( *param );
    63                                 assertf(paramType, "Aggregate parameters should be type expressions");
    64                                 if ( isPolyType( paramType->get_type(), tyVars, env ) ) return true;
    65                         }
    66                         return false;
    67                 }
    68 
    6947                bool hasPolyParams( const std::vector<ast::ptr<ast::Expr>> & params, const TypeVarMap & typeVars, const ast::TypeSubstitution * env ) {
    7048                        for ( auto & param : params ) {
     
    7755
    7856                /// Checks a parameter list for dynamic-layout parameters from tyVars; will substitute according to env if present
    79                 bool hasDynParams( std::list< Expression* >& params, const TyVarMap &tyVars, const TypeSubstitution *env ) {
    80                         for ( std::list< Expression* >::iterator param = params.begin(); param != params.end(); ++param ) {
    81                                 TypeExpr *paramType = dynamic_cast< TypeExpr* >( *param );
    82                                 assertf(paramType, "Aggregate parameters should be type expressions");
    83                                 if ( isDynType( paramType->get_type(), tyVars, env ) ) return true;
    84                         }
    85                         return false;
    86                 }
    87 
    8857                bool hasDynParams(
    8958                                const std::vector<ast::ptr<ast::Expr>> & params,
     
    9968                        return false;
    10069                }
    101 
    102                 /// Checks a parameter list for inclusion of polymorphic parameters; will substitute according to env if present
    103                 bool includesPolyParams( std::list< Expression* >& params, const TypeSubstitution *env ) {
    104                         for ( std::list< Expression* >::iterator param = params.begin(); param != params.end(); ++param ) {
    105                                 TypeExpr *paramType = dynamic_cast< TypeExpr* >( *param );
    106                                 assertf(paramType, "Aggregate parameters should be type expressions");
    107                                 if ( includesPolyType( paramType->get_type(), env ) ) return true;
    108                         }
    109                         return false;
    110                 }
    111 
    112                 /// Checks a parameter list for inclusion of polymorphic parameters from tyVars; will substitute according to env if present
    113                 bool includesPolyParams( std::list< Expression* >& params, const TyVarMap &tyVars, const TypeSubstitution *env ) {
    114                         for ( std::list< Expression* >::iterator param = params.begin(); param != params.end(); ++param ) {
    115                                 TypeExpr *paramType = dynamic_cast< TypeExpr* >( *param );
    116                                 assertf(paramType, "Aggregate parameters should be type expressions");
    117                                 if ( includesPolyType( paramType->get_type(), tyVars, env ) ) return true;
    118                         }
    119                         return false;
    120                 }
    121         }
    122 
    123         Type* replaceTypeInst( Type* type, const TypeSubstitution* env ) {
    124                 if ( ! env ) return type;
    125                 if ( TypeInstType *typeInst = dynamic_cast< TypeInstType* >( type ) ) {
    126                         Type *newType = env->lookup( typeInst->get_name() );
    127                         if ( newType ) return newType;
    128                 }
    129                 return type;
    130         }
    131 
    132         const Type* replaceTypeInst( const Type* type, const TypeSubstitution* env ) {
    133                 if ( ! env ) return type;
    134                 if ( auto typeInst = dynamic_cast< const TypeInstType* >( type ) ) {
    135                         Type *newType = env->lookup( typeInst->get_name() );
    136                         if ( newType ) return newType;
    137                 }
    138                 return type;
    13970        }
    14071
     
    14677                }
    14778                return type;
    148         }
    149 
    150         Type *isPolyType( Type *type, const TypeSubstitution *env ) {
    151                 type = replaceTypeInst( type, env );
    152 
    153                 if ( dynamic_cast< TypeInstType * >( type ) ) {
    154                         return type;
    155                 } else if ( ArrayType * arrayType = dynamic_cast< ArrayType * >( type ) ) {
    156                         return isPolyType( arrayType->base, env );
    157                 } else if ( StructInstType *structType = dynamic_cast< StructInstType* >( type ) ) {
    158                         if ( hasPolyParams( structType->get_parameters(), env ) ) return type;
    159                 } else if ( UnionInstType *unionType = dynamic_cast< UnionInstType* >( type ) ) {
    160                         if ( hasPolyParams( unionType->get_parameters(), env ) ) return type;
    161                 }
    162                 return 0;
    16379        }
    16480
     
    17894        }
    17995
    180         Type *isPolyType( Type *type, const TyVarMap &tyVars, const TypeSubstitution *env ) {
    181                 type = replaceTypeInst( type, env );
    182 
    183                 if ( TypeInstType *typeInst = dynamic_cast< TypeInstType * >( type ) ) {
    184                         if ( tyVars.contains( typeInst->get_name() ) ) {
    185                                 return type;
    186                         }
    187                 } else if ( ArrayType * arrayType = dynamic_cast< ArrayType * >( type ) ) {
    188                         return isPolyType( arrayType->base, tyVars, env );
    189                 } else if ( StructInstType *structType = dynamic_cast< StructInstType* >( type ) ) {
    190                         if ( hasPolyParams( structType->get_parameters(), tyVars, env ) ) return type;
    191                 } else if ( UnionInstType *unionType = dynamic_cast< UnionInstType* >( type ) ) {
    192                         if ( hasPolyParams( unionType->get_parameters(), tyVars, env ) ) return type;
    193                 }
    194                 return 0;
    195         }
    196 
    19796const ast::Type * isPolyType( const ast::Type * type,
    19897                const TypeVarMap & typeVars, const ast::TypeSubstitution * subst ) {
     
    211110}
    212111
    213         ReferenceToType *isDynType( Type *type, const TyVarMap &tyVars, const TypeSubstitution *env ) {
    214                 type = replaceTypeInst( type, env );
    215 
    216                 if ( TypeInstType *typeInst = dynamic_cast< TypeInstType * >( type ) ) {
    217                         auto var = tyVars.find( typeInst->get_name() );
    218                         if ( var != tyVars.end() && var->second.isComplete ) {
    219                                 return typeInst;
    220                         }
    221                 } else if ( StructInstType *structType = dynamic_cast< StructInstType* >( type ) ) {
    222                         if ( hasDynParams( structType->get_parameters(), tyVars, env ) ) return structType;
    223                 } else if ( UnionInstType *unionType = dynamic_cast< UnionInstType* >( type ) ) {
    224                         if ( hasDynParams( unionType->get_parameters(), tyVars, env ) ) return unionType;
    225                 }
    226                 return 0;
    227         }
    228 
    229112const ast::BaseInstType * isDynType(
    230113                const ast::Type * type, const TypeVarMap & typeVars,
     
    249132}
    250133
    251         ReferenceToType *isDynRet( FunctionType *function, const TyVarMap &forallTypes ) {
    252                 if ( function->get_returnVals().empty() ) return 0;
    253 
    254                 return (ReferenceToType*)isDynType( function->get_returnVals().front()->get_type(), forallTypes );
    255         }
    256 
    257134const ast::BaseInstType *isDynRet(
    258135                const ast::FunctionType * type, const TypeVarMap & typeVars ) {
     
    262139}
    263140
    264         ReferenceToType *isDynRet( FunctionType *function ) {
    265                 if ( function->get_returnVals().empty() ) return 0;
    266 
    267                 TyVarMap forallTypes( TypeDecl::Data{} );
    268                 makeTyVarMap( function, forallTypes );
    269                 return (ReferenceToType*)isDynType( function->get_returnVals().front()->get_type(), forallTypes );
    270         }
    271 
    272141const ast::BaseInstType *isDynRet( const ast::FunctionType * func ) {
    273142        if ( func->returns.empty() ) return nullptr;
    274143
    275         TypeVarMap forallTypes = { ast::TypeData() };
     144        TypeVarMap forallTypes;
    276145        makeTypeVarMap( func, forallTypes );
    277146        return isDynType( func->returns.front(), forallTypes );
    278147}
    279 
    280         bool needsAdapter( FunctionType *adaptee, const TyVarMap &tyVars ) {
    281 //              if ( ! adaptee->get_returnVals().empty() && isPolyType( adaptee->get_returnVals().front()->get_type(), tyVars ) ) {
    282 //                      return true;
    283 //              } // if
    284                 if ( isDynRet( adaptee, tyVars ) ) return true;
    285 
    286                 for ( std::list< DeclarationWithType* >::const_iterator innerArg = adaptee->get_parameters().begin(); innerArg != adaptee->get_parameters().end(); ++innerArg ) {
    287 //                      if ( isPolyType( (*innerArg)->get_type(), tyVars ) ) {
    288                         if ( isDynType( (*innerArg)->get_type(), tyVars ) ) {
    289                                 return true;
    290                         } // if
    291                 } // for
    292                 return false;
    293         }
    294148
    295149bool needsAdapter(
     
    304158        return false;
    305159}
    306 
    307         Type *isPolyPtr( Type *type, const TypeSubstitution *env ) {
    308                 type = replaceTypeInst( type, env );
    309 
    310                 if ( PointerType *ptr = dynamic_cast< PointerType *>( type ) ) {
    311                         return isPolyType( ptr->get_base(), env );
    312                 }
    313                 return 0;
    314         }
    315 
    316         Type *isPolyPtr( Type *type, const TyVarMap &tyVars, const TypeSubstitution *env ) {
    317                 type = replaceTypeInst( type, env );
    318 
    319                 if ( PointerType *ptr = dynamic_cast< PointerType *>( type ) ) {
    320                         return isPolyType( ptr->get_base(), tyVars, env );
    321                 }
    322                 return 0;
    323         }
    324160
    325161const ast::Type * isPolyPtr(
     
    333169        return nullptr;
    334170}
    335 
    336         Type * hasPolyBase( Type *type, int *levels, const TypeSubstitution *env ) {
    337                 int dummy;
    338                 if ( ! levels ) { levels = &dummy; }
    339                 *levels = 0;
    340 
    341                 while ( true ) {
    342                         type = replaceTypeInst( type, env );
    343 
    344                         if ( PointerType *ptr = dynamic_cast< PointerType *>( type ) ) {
    345                                 type = ptr->get_base();
    346                                 ++(*levels);
    347                         } else break;
    348                 }
    349 
    350                 return isPolyType( type, env );
    351         }
    352 
    353         Type * hasPolyBase( Type *type, const TyVarMap &tyVars, int *levels, const TypeSubstitution *env ) {
    354                 int dummy;
    355                 if ( ! levels ) { levels = &dummy; }
    356                 *levels = 0;
    357 
    358                 while ( true ) {
    359                         type = replaceTypeInst( type, env );
    360 
    361                         if ( PointerType *ptr = dynamic_cast< PointerType *>( type ) ) {
    362                                 type = ptr->get_base();
    363                                 ++(*levels);
    364                         } else break;
    365                 }
    366 
    367                 return isPolyType( type, tyVars, env );
    368         }
    369171
    370172ast::Type const * hasPolyBase(
     
    388190}
    389191
    390         bool includesPolyType( Type *type, const TypeSubstitution *env ) {
    391                 type = replaceTypeInst( type, env );
    392 
    393                 if ( dynamic_cast< TypeInstType * >( type ) ) {
    394                         return true;
    395                 } else if ( PointerType *pointerType = dynamic_cast< PointerType* >( type ) ) {
    396                         if ( includesPolyType( pointerType->get_base(), env ) ) return true;
    397                 } else if ( StructInstType *structType = dynamic_cast< StructInstType* >( type ) ) {
    398                         if ( includesPolyParams( structType->get_parameters(), env ) ) return true;
    399                 } else if ( UnionInstType *unionType = dynamic_cast< UnionInstType* >( type ) ) {
    400                         if ( includesPolyParams( unionType->get_parameters(), env ) ) return true;
    401                 }
    402                 return false;
    403         }
    404 
    405         bool includesPolyType( Type *type, const TyVarMap &tyVars, const TypeSubstitution *env ) {
    406                 type = replaceTypeInst( type, env );
    407 
    408                 if ( TypeInstType *typeInstType = dynamic_cast< TypeInstType * >( type ) ) {
    409                         if ( tyVars.contains( typeInstType->get_name() ) ) {
    410                                 return true;
    411                         }
    412                 } else if ( PointerType *pointerType = dynamic_cast< PointerType* >( type ) ) {
    413                         if ( includesPolyType( pointerType->get_base(), tyVars, env ) ) return true;
    414                 } else if ( StructInstType *structType = dynamic_cast< StructInstType* >( type ) ) {
    415                         if ( includesPolyParams( structType->get_parameters(), tyVars, env ) ) return true;
    416                 } else if ( UnionInstType *unionType = dynamic_cast< UnionInstType* >( type ) ) {
    417                         if ( includesPolyParams( unionType->get_parameters(), tyVars, env ) ) return true;
    418                 }
    419                 return false;
    420         }
    421 
    422         FunctionType * getFunctionType( Type *ty ) {
    423                 PointerType *ptrType;
    424                 if ( ( ptrType = dynamic_cast< PointerType* >( ty ) ) ) {
    425                         return dynamic_cast< FunctionType* >( ptrType->get_base() ); // pointer if FunctionType, NULL otherwise
    426                 } else {
    427                         return dynamic_cast< FunctionType* >( ty ); // pointer if FunctionType, NULL otherwise
    428                 }
    429         }
    430 
    431192        const ast::FunctionType * getFunctionType( const ast::Type * ty ) {
    432193                if ( auto pty = dynamic_cast< const ast::PointerType * >( ty ) ) {
     
    437198        }
    438199
    439         VariableExpr * getBaseVar( Expression *expr, int *levels ) {
    440                 int dummy;
    441                 if ( ! levels ) { levels = &dummy; }
    442                 *levels = 0;
    443 
    444                 while ( true ) {
    445                         if ( VariableExpr *varExpr = dynamic_cast< VariableExpr* >( expr ) ) {
    446                                 return varExpr;
    447                         } else if ( MemberExpr *memberExpr = dynamic_cast< MemberExpr* >( expr ) ) {
    448                                 expr = memberExpr->get_aggregate();
    449                         } else if ( AddressExpr *addressExpr = dynamic_cast< AddressExpr* >( expr ) ) {
    450                                 expr = addressExpr->get_arg();
    451                         } else if ( UntypedExpr *untypedExpr = dynamic_cast< UntypedExpr* >( expr ) ) {
    452                                 // look for compiler-inserted dereference operator
    453                                 NameExpr *fn = dynamic_cast< NameExpr* >( untypedExpr->get_function() );
    454                                 if ( ! fn || fn->get_name() != std::string("*?") ) return 0;
    455                                 expr = *untypedExpr->begin_args();
    456                         } else if ( CommaExpr *commaExpr = dynamic_cast< CommaExpr* >( expr ) ) {
    457                                 // copy constructors insert comma exprs, look at second argument which contains the variable
    458                                 expr = commaExpr->get_arg2();
    459                                 continue;
    460                         } else if ( ConditionalExpr * condExpr = dynamic_cast< ConditionalExpr * >( expr ) ) {
    461                                 int lvl1;
    462                                 int lvl2;
    463                                 VariableExpr * var1 = getBaseVar( condExpr->get_arg2(), &lvl1 );
    464                                 VariableExpr * var2 = getBaseVar( condExpr->get_arg3(), &lvl2 );
    465                                 if ( lvl1 == lvl2 && var1 && var2 && var1->get_var() == var2->get_var() ) {
    466                                         *levels = lvl1;
    467                                         return var1;
    468                                 }
    469                                 break;
    470                         } else break;
    471 
    472                         ++(*levels);
    473                 }
    474 
    475                 return 0;
    476         }
    477 
    478200        namespace {
    479201                /// Checks if is a pointer to D
     
    488210                inline D const * as( B const * p ) {
    489211                        return reinterpret_cast<D const *>( p );
    490                 }
    491 
    492                 /// Flattens a declaration list
    493                 template<typename Output>
    494                 void flattenList( list< DeclarationWithType* > src, Output out ) {
    495                         for ( DeclarationWithType* decl : src ) {
    496                                 ResolvExpr::flatten( decl->get_type(), out );
    497                         }
    498                 }
    499 
    500                 /// Flattens a list of types
    501                 template<typename Output>
    502                 void flattenList( list< Type* > src, Output out ) {
    503                         for ( Type* ty : src ) {
    504                                 ResolvExpr::flatten( ty, out );
    505                         }
    506212                }
    507213
     
    515221                }
    516222
    517                 /// Checks if two lists of parameters are equal up to polymorphic substitution.
    518                 bool paramListsPolyCompatible( const list< Expression* >& aparams, const list< Expression* >& bparams ) {
    519                         if ( aparams.size() != bparams.size() ) return false;
    520 
    521                         for ( list< Expression* >::const_iterator at = aparams.begin(), bt = bparams.begin();
    522                                         at != aparams.end(); ++at, ++bt ) {
    523                                 TypeExpr *aparam = dynamic_cast< TypeExpr* >(*at);
    524                                 assertf(aparam, "Aggregate parameters should be type expressions");
    525                                 TypeExpr *bparam = dynamic_cast< TypeExpr* >(*bt);
    526                                 assertf(bparam, "Aggregate parameters should be type expressions");
    527 
    528                                 // xxx - might need to let VoidType be a wildcard here too; could have some voids
    529                                 // stuffed in for dtype-statics.
    530                                 // if ( is<VoidType>( aparam->get_type() ) || is<VoidType>( bparam->get_type() ) ) continue;
    531                                 if ( ! typesPolyCompatible( aparam->get_type(), bparam->get_type() ) ) return false;
    532                         }
    533 
    534                         return true;
    535                 }
    536 
    537223                bool paramListsPolyCompatible(
    538224                                std::vector<ast::ptr<ast::Expr>> const & lparams,
     
    559245                        return true;
    560246                }
    561         }
    562 
    563         bool typesPolyCompatible( Type *a, Type *b ) {
    564                 type_index aid{ typeid(*a) };
    565                 // polymorphic types always match
    566                 if ( aid == type_index{typeid(TypeInstType)} ) return true;
    567 
    568                 type_index bid{ typeid(*b) };
    569                 // polymorphic types always match
    570                 if ( bid == type_index{typeid(TypeInstType)} ) return true;
    571 
    572                 // can't match otherwise if different types
    573                 if ( aid != bid ) return false;
    574 
    575                 // recurse through type structure (conditions borrowed from Unify.cc)
    576                 if ( aid == type_index{typeid(BasicType)} ) {
    577                         return as<BasicType>(a)->get_kind() == as<BasicType>(b)->get_kind();
    578                 } else if ( aid == type_index{typeid(PointerType)} ) {
    579                         PointerType *ap = as<PointerType>(a), *bp = as<PointerType>(b);
    580 
    581                         // void pointers should match any other pointer type
    582                         return is<VoidType>( ap->get_base() ) || is<VoidType>( bp->get_base() )
    583                                 || typesPolyCompatible( ap->get_base(), bp->get_base() );
    584                 } else if ( aid == type_index{typeid(ReferenceType)} ) {
    585                         ReferenceType *ap = as<ReferenceType>(a), *bp = as<ReferenceType>(b);
    586                         return is<VoidType>( ap->get_base() ) || is<VoidType>( bp->get_base() )
    587                                 || typesPolyCompatible( ap->get_base(), bp->get_base() );
    588                 } else if ( aid == type_index{typeid(ArrayType)} ) {
    589                         ArrayType *aa = as<ArrayType>(a), *ba = as<ArrayType>(b);
    590 
    591                         if ( aa->get_isVarLen() ) {
    592                                 if ( ! ba->get_isVarLen() ) return false;
    593                         } else {
    594                                 if ( ba->get_isVarLen() ) return false;
    595 
    596                                 ConstantExpr *ad = dynamic_cast<ConstantExpr*>( aa->get_dimension() );
    597                                 ConstantExpr *bd = dynamic_cast<ConstantExpr*>( ba->get_dimension() );
    598                                 if ( ad && bd
    599                                                 && ad->get_constant()->get_value() != bd->get_constant()->get_value() )
    600                                         return false;
    601                         }
    602 
    603                         return typesPolyCompatible( aa->get_base(), ba->get_base() );
    604                 } else if ( aid == type_index{typeid(FunctionType)} ) {
    605                         FunctionType *af = as<FunctionType>(a), *bf = as<FunctionType>(b);
    606 
    607                         vector<Type*> aparams, bparams;
    608                         flattenList( af->get_parameters(), back_inserter( aparams ) );
    609                         flattenList( bf->get_parameters(), back_inserter( bparams ) );
    610                         if ( aparams.size() != bparams.size() ) return false;
    611 
    612                         vector<Type*> areturns, breturns;
    613                         flattenList( af->get_returnVals(), back_inserter( areturns ) );
    614                         flattenList( bf->get_returnVals(), back_inserter( breturns ) );
    615                         if ( areturns.size() != breturns.size() ) return false;
    616 
    617                         for ( unsigned i = 0; i < aparams.size(); ++i ) {
    618                                 if ( ! typesPolyCompatible( aparams[i], bparams[i] ) ) return false;
    619                         }
    620                         for ( unsigned i = 0; i < areturns.size(); ++i ) {
    621                                 if ( ! typesPolyCompatible( areturns[i], breturns[i] ) ) return false;
    622                         }
    623                         return true;
    624                 } else if ( aid == type_index{typeid(StructInstType)} ) {
    625                         StructInstType *aa = as<StructInstType>(a), *ba = as<StructInstType>(b);
    626 
    627                         if ( aa->get_name() != ba->get_name() ) return false;
    628                         return paramListsPolyCompatible( aa->get_parameters(), ba->get_parameters() );
    629                 } else if ( aid == type_index{typeid(UnionInstType)} ) {
    630                         UnionInstType *aa = as<UnionInstType>(a), *ba = as<UnionInstType>(b);
    631 
    632                         if ( aa->get_name() != ba->get_name() ) return false;
    633                         return paramListsPolyCompatible( aa->get_parameters(), ba->get_parameters() );
    634                 } else if ( aid == type_index{typeid(EnumInstType)} ) {
    635                         return as<EnumInstType>(a)->get_name() == as<EnumInstType>(b)->get_name();
    636                 } else if ( aid == type_index{typeid(TraitInstType)} ) {
    637                         return as<TraitInstType>(a)->get_name() == as<TraitInstType>(b)->get_name();
    638                 } else if ( aid == type_index{typeid(TupleType)} ) {
    639                         TupleType *at = as<TupleType>(a), *bt = as<TupleType>(b);
    640 
    641                         vector<Type*> atypes, btypes;
    642                         flattenList( at->get_types(), back_inserter( atypes ) );
    643                         flattenList( bt->get_types(), back_inserter( btypes ) );
    644                         if ( atypes.size() != btypes.size() ) return false;
    645 
    646                         for ( unsigned i = 0; i < atypes.size(); ++i ) {
    647                                 if ( ! typesPolyCompatible( atypes[i], btypes[i] ) ) return false;
    648                         }
    649                         return true;
    650                 } else return true; // VoidType, VarArgsType, ZeroType & OneType just need the same type
    651247        }
    652248
     
    763359}
    764360
    765         bool needsBoxing( Type * param, Type * arg, const TyVarMap &exprTyVars, const TypeSubstitution * env ) {
    766                 // is parameter is not polymorphic, don't need to box
    767                 if ( ! isPolyType( param, exprTyVars ) ) return false;
    768                 Type * newType = arg->clone();
    769                 if ( env ) env->apply( newType );
    770                 std::unique_ptr<Type> manager( newType );
    771                 // if the argument's type is polymorphic, we don't need to box again!
    772                 return ! isPolyType( newType );
    773         }
    774 
    775361bool needsBoxing( const ast::Type * param, const ast::Type * arg,
    776362                const TypeVarMap & typeVars, const ast::TypeSubstitution * subst ) {
     
    786372        return !isPolyType( newType );
    787373}
    788 
    789         bool needsBoxing( Type * param, Type * arg, ApplicationExpr * appExpr, const TypeSubstitution * env ) {
    790                 FunctionType * function = getFunctionType( appExpr->function->result );
    791                 assertf( function, "ApplicationExpr has non-function type: %s", toString( appExpr->function->result ).c_str() );
    792                 TyVarMap exprTyVars( TypeDecl::Data{} );
    793                 makeTyVarMap( function, exprTyVars );
    794                 return needsBoxing( param, arg, exprTyVars, env );
    795         }
    796374
    797375bool needsBoxing(
     
    801379        const ast::FunctionType * function = getFunctionType( expr->func->result );
    802380        assertf( function, "ApplicationExpr has non-function type: %s", toString( expr->func->result ).c_str() );
    803         TypeVarMap exprTyVars = { ast::TypeData() };
     381        TypeVarMap exprTyVars;
    804382        makeTypeVarMap( function, exprTyVars );
    805383        return needsBoxing( param, arg, exprTyVars, subst );
    806384}
    807385
    808         void addToTyVarMap( TypeDecl * tyVar, TyVarMap &tyVarMap ) {
    809                 tyVarMap.insert( tyVar->name, TypeDecl::Data{ tyVar } );
    810         }
    811 
    812386void addToTypeVarMap( const ast::TypeDecl * decl, TypeVarMap & typeVars ) {
    813387        typeVars.insert( ast::TypeEnvKey( decl, 0, 0 ), ast::TypeData( decl ) );
     
    817391        typeVars.insert( ast::TypeEnvKey( *type ), ast::TypeData( type->base ) );
    818392}
    819 
    820         void makeTyVarMap( Type *type, TyVarMap &tyVarMap ) {
    821                 for ( Type::ForallList::const_iterator tyVar = type->get_forall().begin(); tyVar != type->get_forall().end(); ++tyVar ) {
    822                         assert( *tyVar );
    823                         addToTyVarMap( *tyVar, tyVarMap );
    824                 }
    825                 if ( PointerType *pointer = dynamic_cast< PointerType* >( type ) ) {
    826                         makeTyVarMap( pointer->get_base(), tyVarMap );
    827                 }
    828         }
    829393
    830394void makeTypeVarMap( const ast::Type * type, TypeVarMap & typeVars ) {
     
    846410}
    847411
    848         void printTyVarMap( std::ostream &os, const TyVarMap &tyVarMap ) {
    849                 for ( TyVarMap::const_iterator i = tyVarMap.begin(); i != tyVarMap.end(); ++i ) {
    850                         os << i->first << " (" << i->second << ") ";
    851                 } // for
    852                 os << std::endl;
    853         }
    854 
    855412} // namespace GenPoly
    856413
  • src/GenPoly/GenPoly.h

    r0030b508 rfc12f05  
    2323#include "AST/Fwd.hpp"            // for ApplicationExpr, BaseInstType, Func...
    2424#include "SymTab/Mangler.h"       // for Mangler
    25 #include "SynTree/Declaration.h"  // for TypeDecl::Data, AggregateDecl, Type...
    26 #include "SynTree/SynTree.h"      // for Visitor Nodes
    2725
    2826namespace ast {
     
    3230namespace GenPoly {
    3331
    34         typedef ErasableScopedMap< std::string, TypeDecl::Data > TyVarMap;
    35         using TypeVarMap = ErasableScopedMap< ast::TypeEnvKey, ast::TypeData >;
     32        struct TypeVarMap : public ErasableScopedMap<ast::TypeEnvKey, ast::TypeData> {
     33                TypeVarMap() : ErasableScopedMap( ast::TypeData() ) {}
     34        };
    3635
    3736        /// Replaces a TypeInstType by its referrent in the environment, if applicable
    38         Type* replaceTypeInst( Type* type, const TypeSubstitution* env );
    39         const Type* replaceTypeInst( const Type* type, const TypeSubstitution* env );
    4037        const ast::Type * replaceTypeInst( const ast::Type *, const ast::TypeSubstitution * );
    4138
    4239        /// returns polymorphic type if is polymorphic type, NULL otherwise; will look up substitution in env if provided
    43         Type *isPolyType( Type *type, const TypeSubstitution *env = 0 );
    4440        const ast::Type * isPolyType(const ast::Type * type, const ast::TypeSubstitution * env = nullptr);
    4541
    4642        /// returns polymorphic type if is polymorphic type in tyVars, NULL otherwise; will look up substitution in env if provided
    47         Type *isPolyType( Type *type, const TyVarMap &tyVars, const TypeSubstitution *env = 0 );
    4843        const ast::Type * isPolyType( const ast::Type * type, const TypeVarMap & typeVars, const ast::TypeSubstitution * subst = nullptr );
    4944
    5045        /// returns dynamic-layout type if is dynamic-layout type in tyVars, NULL otherwise; will look up substitution in env if provided
    51         ReferenceToType *isDynType( Type *type, const TyVarMap &tyVars, const TypeSubstitution *env = 0 );
    5246        const ast::BaseInstType *isDynType( const ast::Type * type, const TypeVarMap & typeVars, const ast::TypeSubstitution * subst = 0 );
    5347
    5448        /// true iff function has dynamic-layout return type under the given type variable map
    55         ReferenceToType *isDynRet( FunctionType *function, const TyVarMap &tyVars );
    5649        const ast::BaseInstType *isDynRet( const ast::FunctionType * type, const TypeVarMap & typeVars );
    5750
    5851        /// true iff function has dynamic-layout return type under the type variable map generated from its forall-parameters
    59         ReferenceToType *isDynRet( FunctionType *function );
    6052        const ast::BaseInstType *isDynRet( const ast::FunctionType * func );
    6153
    6254        /// A function needs an adapter if it returns a dynamic-layout value or if any of its parameters have dynamic-layout type
    63         bool needsAdapter( FunctionType *adaptee, const TyVarMap &tyVarr );
    6455        bool needsAdapter( ast::FunctionType const * adaptee, const TypeVarMap & typeVars );
    6556
    66         /// returns polymorphic type if is pointer to polymorphic type, NULL otherwise; will look up substitution in env if provided
    67         Type *isPolyPtr( Type *type, const TypeSubstitution *env = 0 );
    68 
    6957        /// returns polymorphic type if is pointer to polymorphic type in tyVars, NULL otherwise; will look up substitution in env if provided
    70         Type *isPolyPtr( Type *type, const TyVarMap &tyVars, const TypeSubstitution *env = 0 );
    7158        const ast::Type * isPolyPtr( const ast::Type * type, const TypeVarMap & typeVars, const ast::TypeSubstitution * env = 0 );
    72 
    73         /// if the base type (after dereferencing N >= 0 pointers) is a polymorphic type, returns the base type, NULL otherwise;
    74         /// N will be stored in levels, if provided, will look up substitution in env if provided
    75         Type *hasPolyBase( Type *type, int *levels = 0, const TypeSubstitution *env = 0 );
    7659
    7760        /// if the base type (after dereferencing N >= 0 pointers) is a polymorphic type in tyVars, returns the base type, NULL otherwise;
    7861        /// N will be stored in levels, if provided, will look up substitution in env if provided
    79         Type *hasPolyBase( Type *type, const TyVarMap &tyVars, int *levels = 0, const TypeSubstitution *env = 0 );
    8062        const ast::Type * hasPolyBase( const ast::Type * type, const TypeVarMap & typeVars, int * levels = 0, const ast::TypeSubstitution * env = 0 );
    8163
    82         /// true iff this type or some base of this type after dereferencing pointers is either polymorphic or a generic type with at least one
    83         /// polymorphic parameter; will look up substitution in env if provided.
    84         bool includesPolyType( Type *type, const TypeSubstitution *env = 0 );
    85 
    86         /// true iff this type or some base of this type after dereferencing pointers is either polymorphic in tyVars, or a generic type with
    87         /// at least one polymorphic parameter in tyVars; will look up substitution in env if provided.
    88         bool includesPolyType( Type *type, const TyVarMap &tyVars, const TypeSubstitution *env = 0 );
    89 
    9064        /// Returns a pointer to the base FunctionType if ty is the type of a function (or pointer to one), NULL otherwise
    91         FunctionType *getFunctionType( Type *ty );
    9265        const ast::FunctionType * getFunctionType( const ast::Type * ty );
    9366
    94         /// If expr (after dereferencing N >= 0 pointers) is a variable expression, returns the variable expression, NULL otherwise;
    95         /// N will be stored in levels, if provided
    96         VariableExpr *getBaseVar( Expression *expr, int *levels = 0 );
    97 
    9867        /// true iff types are structurally identical, where TypeInstType's match any type.
    99         bool typesPolyCompatible( Type *aty, Type *bty );
    10068        bool typesPolyCompatible( ast::Type const * lhs, ast::Type const * rhs );
    10169
    10270        /// true if arg requires boxing given exprTyVars
    103         bool needsBoxing( Type * param, Type * arg, const TyVarMap &exprTyVars, const TypeSubstitution * env );
    10471        bool needsBoxing( const ast::Type * param, const ast::Type * arg, const TypeVarMap & typeVars, const ast::TypeSubstitution * subst );
    10572
    10673        /// true if arg requires boxing in the call to appExpr
    107         bool needsBoxing( Type * param, Type * arg, ApplicationExpr * appExpr, const TypeSubstitution * env );
    10874        bool needsBoxing( const ast::Type * param, const ast::Type * arg, const ast::ApplicationExpr * expr, const ast::TypeSubstitution * subst );
    10975
    11076        /// Adds the type variable `tyVar` to `tyVarMap`
    111         void addToTyVarMap( TypeDecl * tyVar, TyVarMap &tyVarMap );
    11277        void addToTypeVarMap( const ast::TypeDecl * type, TypeVarMap & typeVars );
    11378        void addToTypeVarMap( const ast::TypeInstType * type, TypeVarMap & typeVars );
    11479
    11580        /// Adds the declarations in the forall list of type (and its pointed-to type if it's a pointer type) to `tyVarMap`
    116         void makeTyVarMap( Type *type, TyVarMap &tyVarMap );
    11781        void makeTypeVarMap( const ast::Type * type, TypeVarMap & typeVars );
    11882        void makeTypeVarMap( const ast::FunctionDecl * decl, TypeVarMap & typeVars );
    119 
    120         /// Prints type variable map
    121         void printTyVarMap( std::ostream &os, const TyVarMap &tyVarMap );
    122 
    123         /// Gets the mangled name of this type; alias for SymTab::Mangler::mangleType().
    124         inline std::string mangleType( const Type *ty ) { return SymTab::Mangler::mangleType( ty ); }
    12583
    12684        /// Gets the name of the sizeof parameter for the type, given its mangled name
     
    13492
    13593        /// Gets the name of the layout function for a given aggregate type, given its declaration
    136         inline std::string layoutofName( AggregateDecl *decl ) { return std::string( "_layoutof_" ) + decl->get_name(); }
    13794        inline std::string layoutofName( ast::AggregateDecl const * decl ) {
    13895                return std::string( "_layoutof_" ) + decl->name;
  • src/GenPoly/ScrubTyVars.cc

    r0030b508 rfc12f05  
    2121#include "ScrubTyVars.h"
    2222#include "SymTab/Mangler.h"             // for mangleType
    23 #include "SynTree/Declaration.h"        // for TypeDecl, TypeDecl::Data, Typ...
    24 #include "SynTree/Expression.h"         // for Expression (ptr only), NameExpr
    25 #include "SynTree/Mutator.h"            // for Mutator
    26 #include "SynTree/Type.h"               // for PointerType, TypeInstType, Type
    2723
    2824namespace GenPoly {
    29         Type * ScrubTyVars::postmutate( TypeInstType * typeInst ) {
    30                 if ( ! tyVars ) {
    31                         if ( typeInst->get_isFtype() ) {
    32                                 delete typeInst;
    33                                 return new PointerType( Type::Qualifiers(), new FunctionType( Type::Qualifiers(), true ) );
    34                         } else {
    35                                 PointerType * ret = new PointerType( Type::Qualifiers(), new VoidType( typeInst->get_qualifiers() ) );
    36                                 delete typeInst;
    37                                 return ret;
    38                         }
    39                 }
    40 
    41                 TyVarMap::const_iterator tyVar = tyVars->find( typeInst->name );
    42                 if ( tyVar != tyVars->end() ) {
    43                         switch ( tyVar->second.kind ) {
    44                           case TypeDecl::Dtype:
    45                           case TypeDecl::Ttype:
    46                                 {
    47                                         PointerType * ret = new PointerType( Type::Qualifiers(), new VoidType( typeInst->get_qualifiers() ) );
    48                                         delete typeInst;
    49                                         return ret;
    50                                 }
    51                           case TypeDecl::Ftype:
    52                                 delete typeInst;
    53                                 return new PointerType( Type::Qualifiers(), new FunctionType( Type::Qualifiers(), true ) );
    54                           default:
    55                                 assertf(false, "Unhandled tyvar kind: %d", tyVar->second.kind);
    56                         } // switch
    57                 } // if
    58                 return typeInst;
    59         }
    60 
    61         Type * ScrubTyVars::mutateAggregateType( Type * ty ) {
    62                 if ( shouldScrub( ty ) ) {
    63                         PointerType * ret = new PointerType( Type::Qualifiers(), new VoidType( ty->get_qualifiers() ) );
    64                         delete ty;
    65                         return ret;
    66                 }
    67                 return ty;
    68         }
    69 
    70         Type * ScrubTyVars::postmutate( StructInstType * structInst ) {
    71                 return mutateAggregateType( structInst );
    72         }
    73 
    74         Type * ScrubTyVars::postmutate( UnionInstType * unionInst ) {
    75                 return mutateAggregateType( unionInst );
    76         }
    77 
    78         void ScrubTyVars::primeBaseScrub( Type * type ) {
    79                 // need to determine whether type needs to be scrubbed to determine whether
    80                 // automatic recursion is necessary
    81                 if ( Type * t = shouldScrub( type ) ) {
    82                         visit_children = false;
    83                         GuardValue( dynType );
    84                         dynType = t;
    85                 }
    86         }
    87 
    88         Expression * ScrubTyVars::postmutate( SizeofExpr * szeof ) {
    89                 // sizeof( T ) => _sizeof_T parameter, which is the size of T
    90                 if ( dynType ) {
    91                         Expression *expr = new NameExpr( sizeofName( mangleType( dynType ) ) );
    92                         return expr;
    93                 } // if
    94                 return szeof;
    95         }
    96 
    97         Expression * ScrubTyVars::postmutate( AlignofExpr * algnof ) {
    98                 // alignof( T ) => _alignof_T parameter, which is the alignment of T
    99                 if ( dynType ) {
    100                         Expression *expr = new NameExpr( alignofName( mangleType( dynType ) ) );
    101                         return expr;
    102                 } // if
    103                 return algnof;
    104         }
    105 
    106         Type * ScrubTyVars::postmutate( PointerType * pointer ) {
    107                 if ( dynType ) {
    108                         Type * ret = dynType->acceptMutator( *visitor );
    109                         ret->get_qualifiers() |= pointer->get_qualifiers();
    110                         pointer->base = nullptr;
    111                         delete pointer;
    112                         return ret;
    113                 }
    114                 return pointer;
    115         }
    11625
    11726namespace {
  • src/GenPoly/ScrubTyVars.h

    r0030b508 rfc12f05  
    1919
    2020#include "AST/Fwd.hpp"        // for Node
    21 #include "Common/PassVisitor.h"
    2221#include "GenPoly.h"          // for TyVarMap, isPolyType, isDynType
    23 #include "SynTree/Mutator.h"  // for Mutator
    24 #include "SynTree/Type.h"     // for Type (ptr only), PointerType (ptr only)
    25 
    26 class AlignofExpr;
    27 class Expression;
    28 class SizeofExpr;
    2922
    3023namespace GenPoly {
    31         struct ScrubTyVars : public WithVisitorRef<ScrubTyVars>, public WithShortCircuiting, public WithGuards {
    32                 /// Whether to scrub all type variables from the provided map, dynamic type variables from the provided map, or all type variables
    33                 enum ScrubMode { FromMap, DynamicFromMap, All };
    34 
    35                 ScrubTyVars() : tyVars(nullptr), mode( All ) {}
    36 
    37                 ScrubTyVars( const TyVarMap &tyVars, ScrubMode mode = FromMap ): tyVars( &tyVars ), mode( mode ) {}
    38 
    39         public:
    40                 /// For all polymorphic types with type variables in `tyVars`, replaces generic types, dtypes, and ftypes with the appropriate void type,
    41                 /// and sizeof/alignof expressions with the proper variable
    42                 template< typename SynTreeClass >
    43                 static SynTreeClass *scrub( SynTreeClass *target, const TyVarMap &tyVars );
    44 
    45                 /// For all dynamic-layout types with type variables in `tyVars`, replaces generic types, dtypes, and ftypes with the appropriate void type,
    46                 /// and sizeof/alignof expressions with the proper variable
    47                 template< typename SynTreeClass >
    48                 static SynTreeClass *scrubDynamic( SynTreeClass *target, const TyVarMap &tyVars );
    49 
    50                 /// For all polymorphic types, replaces generic types, dtypes, and ftypes with the appropriate void type,
    51                 /// and sizeof/alignof expressions with the proper variable
    52                 template< typename SynTreeClass >
    53                 static SynTreeClass *scrubAll( SynTreeClass *target );
    54 
    55                 /// determine if children should be visited based on whether base type should be scrubbed.
    56                 void primeBaseScrub( Type * );
    57 
    58                 void premutate( TypeInstType * ) { visit_children = false; }
    59                 void premutate( StructInstType * ) { visit_children = false; }
    60                 void premutate( UnionInstType * ) { visit_children = false; }
    61                 void premutate( SizeofExpr * szeof ) { primeBaseScrub( szeof->type ); }
    62                 void premutate( AlignofExpr * algnof ) { primeBaseScrub( algnof->type ); }
    63                 void premutate( PointerType * pointer ) { primeBaseScrub( pointer->base ); }
    64 
    65                 Type * postmutate( TypeInstType * typeInst );
    66                 Type * postmutate( StructInstType * structInst );
    67                 Type * postmutate( UnionInstType * unionInst );
    68                 Expression * postmutate( SizeofExpr * szeof );
    69                 Expression * postmutate( AlignofExpr * algnof );
    70                 Type * postmutate( PointerType * pointer );
    71 
    72           private:
    73                 /// Returns the type if it should be scrubbed, NULL otherwise.
    74                 Type* shouldScrub( Type *ty ) {
    75                         switch ( mode ) {
    76                         case FromMap: return isPolyType( ty, *tyVars );
    77                         case DynamicFromMap: return isDynType( ty, *tyVars );
    78                         case All: return isPolyType( ty );
    79                         }
    80                         assert(false); return nullptr; // unreachable
    81                         // return dynamicOnly ? isDynType( ty, tyVars ) : isPolyType( ty, tyVars );
    82                 }
    83 
    84                 /// Mutates (possibly generic) aggregate types appropriately
    85                 Type* mutateAggregateType( Type *ty );
    86 
    87                 const TyVarMap *tyVars;  ///< Type variables to scrub
    88                 ScrubMode mode;          ///< which type variables to scrub? [FromMap]
    89 
    90                 Type * dynType = nullptr; ///< result of shouldScrub
    91         };
    92 
    93         template< typename SynTreeClass >
    94         SynTreeClass * ScrubTyVars::scrub( SynTreeClass *target, const TyVarMap &tyVars ) {
    95                 PassVisitor<ScrubTyVars> scrubber( tyVars );
    96                 return static_cast< SynTreeClass * >( target->acceptMutator( scrubber ) );
    97         }
    98 
    99         template< typename SynTreeClass >
    100         SynTreeClass * ScrubTyVars::scrubDynamic( SynTreeClass *target, const TyVarMap &tyVars ) {
    101                 PassVisitor<ScrubTyVars> scrubber( tyVars, ScrubTyVars::DynamicFromMap );
    102                 return static_cast< SynTreeClass * >( target->acceptMutator( scrubber ) );
    103         }
    104 
    105         template< typename SynTreeClass >
    106         SynTreeClass * ScrubTyVars::scrubAll( SynTreeClass *target ) {
    107                 PassVisitor<ScrubTyVars> scrubber;
    108                 return static_cast< SynTreeClass * >( target->acceptMutator( scrubber ) );
    109         }
    11024
    11125// ScrubMode and scrubTypeVarsBase are internal.
  • src/GenPoly/SpecializeNew.cpp

    r0030b508 rfc12f05  
    2323#include "GenPoly/GenPoly.h"             // for getFunctionType
    2424#include "ResolvExpr/FindOpenVars.h"     // for findOpenVars
    25 #include "ResolvExpr/TypeEnvironment.h"  // for FirstOpen, FirstClosed
    2625
    2726namespace GenPoly {
     
    8180}
    8281
    83 // The number of elements in a type if it is a flattened tuple.
    84 size_t flatTupleSize( const ast::Type * type ) {
    85         if ( auto tuple = dynamic_cast<const ast::TupleType *>( type ) ) {
    86                 size_t sum = 0;
    87                 for ( auto t : *tuple ) {
    88                         sum += flatTupleSize( t );
    89                 }
    90                 return sum;
    91         } else {
    92                 return 1;
    93         }
     82// The number of elements in a list, if all tuples had been flattened.
     83size_t flatTypeListSize( const std::vector<ast::ptr<ast::Type>> & types ) {
     84        size_t sum = 0;
     85        for ( const ast::ptr<ast::Type> & type : types ) {
     86                if ( const ast::TupleType * tuple = type.as<ast::TupleType>() ) {
     87                        sum += flatTypeListSize( tuple->types );
     88                } else {
     89                        sum += 1;
     90                }
     91        }
     92        return sum;
    9493}
    9594
    9695// Find the total number of components in a parameter list.
    9796size_t functionParameterSize( const ast::FunctionType * type ) {
    98         size_t sum = 0;
    99         for ( auto param : type->params ) {
    100                 sum += flatTupleSize( param );
    101         }
    102         return sum;
     97        return flatTypeListSize( type->params );
    10398}
    10499
  • src/GenPoly/module.mk

    r0030b508 rfc12f05  
    2323SRC += $(SRC_GENPOLY) \
    2424        GenPoly/BoxNew.cpp \
    25         GenPoly/Box.cc \
    2625        GenPoly/Box.h \
    2726        GenPoly/ErasableScopedMap.h \
     
    2928        GenPoly/FindFunction.h \
    3029        GenPoly/InstantiateGenericNew.cpp \
    31         GenPoly/InstantiateGeneric.cc \
    3230        GenPoly/InstantiateGeneric.h \
    3331        GenPoly/LvalueNew.cpp \
    34         GenPoly/Lvalue.cc \
    3532        GenPoly/ScopedSet.h \
    3633        GenPoly/ScrubTyVars.cc \
    3734        GenPoly/ScrubTyVars.h \
    38         GenPoly/Specialize.cc \
    3935        GenPoly/SpecializeNew.cpp \
    4036        GenPoly/Specialize.h
Note: See TracChangeset for help on using the changeset viewer.