Changes in / [3de176d:c0d00b6]


Ignore:
Location:
src
Files:
14 edited

Legend:

Unmodified
Added
Removed
  • src/ControlStruct/ExceptTranslate.cc

    r3de176d rc0d00b6  
    315315                        {
    316316                                VarExprReplacer::DeclMap mapping;
    317                                 mapping[ handler_decl ] = local_except;
     317                                mapping[ handler_decl ] = new VariableExpr( local_except );
    318318                                VarExprReplacer mapper( mapping );
    319                                 handler->get_body()->accept( mapper );
     319                                handler->body->acceptMutator( mapper );
    320320                        }
    321321
    322                         block->push_back( handler->get_body() );
    323                         handler->set_body( nullptr );
     322                        block->push_back( handler->body );
     323                        handler->body = nullptr;
    324324
    325325                        std::list<Statement *> caseBody
  • src/InitTweak/FixInit.cc

    r3de176d rc0d00b6  
    5454#include "SynTree/Type.h"              // for Type, Type::StorageClasses
    5555#include "SynTree/TypeSubstitution.h"  // for TypeSubstitution, operator<<
     56#include "SynTree/VarExprReplacer.h"   // for VarExprReplacer
    5657#include "SynTree/Visitor.h"           // for acceptAll, maybeAccept
    5758
     
    158159                        using Parent::previsit;
    159160
    160                         void previsit( ObjectDecl * objDecl );
    161161                        void previsit( FunctionDecl * funcDecl );
    162162
    163                         void previsit( CompoundStmt * compoundStmt );
    164                         void postvisit( CompoundStmt * compoundStmt );
    165                         void previsit( ReturnStmt * returnStmt );
    166163                        void previsit( BranchStmt * stmt );
    167164                private:
     
    203200                        static void generate( std::list< Declaration * > & translationUnit );
    204201
     202                        void previsit( StructDecl * structDecl );
     203
    205204                        void previsit( FunctionDecl * funcDecl );
    206205                        void postvisit( FunctionDecl * funcDecl );
     
    220219                        bool isCtor = false; // true if current function is a constructor
    221220                        StructDecl * structDecl = nullptr;
     221
     222                        // special built-in functions necessary for this to work
     223                        StructDecl * dtorStruct = nullptr;
     224                        FunctionDecl * dtorStructDestroy = nullptr;
    222225                };
    223226
     
    644647                }
    645648
     649                DeclarationWithType * getDtorFunc( ObjectDecl * objDecl, Statement * input, std::list< Statement * > & stmtsToAdd ) {
     650                        // unwrap implicit statement wrapper
     651                        Statement * dtor = input;
     652                        if ( ImplicitCtorDtorStmt * implicit = dynamic_cast< ImplicitCtorDtorStmt * >( input ) ) {
     653                                // dtor = implicit->callStmt;
     654                                // implicit->callStmt = nullptr;
     655                        }
     656                        assert( dtor );
     657                        std::list< Expression * > matches;
     658                        collectCtorDtorCalls( dtor, matches );
     659
     660                        if ( dynamic_cast< ExprStmt * >( dtor ) ) {
     661                                // only one destructor call in the expression
     662                                if ( matches.size() == 1 ) {
     663                                        DeclarationWithType * func = getFunction( matches.front() );
     664                                        assertf( func, "getFunction failed to find function in %s", toString( matches.front() ).c_str() );
     665
     666                                        // cleanup argument must be a function, not an object (including function pointer)
     667                                        if ( FunctionDecl * dtorFunc = dynamic_cast< FunctionDecl * > ( func ) ) {
     668                                                if ( dtorFunc->type->forall.empty() ) {
     669                                                        // simple case where the destructor is a monomorphic function call - can simply
     670                                                        // use that function as the cleanup function.
     671                                                        delete dtor;
     672                                                        return func;
     673                                                }
     674                                        }
     675                                }
     676                        }
     677
     678                        // otherwise the cleanup is more complicated - need to build a single argument cleanup function that
     679                        // wraps the more complicated code.
     680                        static UniqueName dtorNamer( "__cleanup_dtor" );
     681                        FunctionDecl * dtorFunc = FunctionDecl::newFunction( dtorNamer.newName(), SymTab::genDefaultType( objDecl->type->stripReferences(), false ), new CompoundStmt( noLabels ) );
     682                        stmtsToAdd.push_back( new DeclStmt( noLabels, dtorFunc ) );
     683
     684                        // the original code contains uses of objDecl - replace them with the newly generated 'this' parameter.
     685                        ObjectDecl * thisParam = getParamThis( dtorFunc->type );
     686                        Expression * replacement = new VariableExpr( thisParam );
     687
     688                        Type * base = replacement->result->stripReferences();
     689                        if ( dynamic_cast< ArrayType * >( base ) || dynamic_cast< TupleType * > ( base ) ) {
     690                                // need to cast away reference for array types, since the destructor is generated without the reference type,
     691                                // and for tuple types since tuple indexing does not work directly on a reference
     692                                replacement = new CastExpr( replacement, base->clone() );
     693                        }
     694                        VarExprReplacer::replace( dtor, { std::make_pair( objDecl, replacement ) } );
     695                        dtorFunc->statements->push_back( dtor );
     696
     697                        return dtorFunc;
     698                }
     699
    646700                DeclarationWithType * FixInit::postmutate( ObjectDecl *objDecl ) {
    647701                        // since this removes the init field from objDecl, it must occur after children are mutated (i.e. postmutate)
     
    756810                                                        ctorInit->ctor = nullptr;
    757811                                                }
     812
     813                                                Statement * dtor = ctorInit->dtor;
     814                                                if ( dtor ) {
     815                                                        ImplicitCtorDtorStmt * implicit = strict_dynamic_cast< ImplicitCtorDtorStmt * >( dtor );
     816                                                        Statement * dtorStmt = implicit->callStmt;
     817
     818                                                        // don't need to call intrinsic dtor, because it does nothing, but
     819                                                        // non-intrinsic dtors must be called
     820                                                        if ( ! isIntrinsicSingleArgCallStmt( dtorStmt ) ) {
     821                                                                // set dtor location to the object's location for error messages
     822                                                                DeclarationWithType * dtorFunc = getDtorFunc( objDecl, dtorStmt, stmtsToAddBefore );
     823                                                                objDecl->attributes.push_back( new Attribute( "cleanup", { new VariableExpr( dtorFunc ) } ) );
     824                                                                ctorInit->dtor = nullptr;
     825                                                        } // if
     826                                                }
    758827                                        } // if
    759828                                } else if ( Initializer * init = ctorInit->init ) {
     
    798867
    799868
    800                 template<typename Iterator, typename OutputIterator>
    801                 void insertDtors( Iterator begin, Iterator end, OutputIterator out ) {
    802                         for ( Iterator it = begin ; it != end ; ++it ) {
    803                                 // extract destructor statement from the object decl and insert it into the output. Note that this is
    804                                 // only called on lists of non-static objects with implicit non-intrinsic dtors, so if the user manually
    805                                 // calls an intrinsic dtor then the call must (and will) still be generated since the argument may
    806                                 // contain side effects.
    807                                 ObjectDecl * objDecl = *it;
    808                                 ConstructorInit * ctorInit = dynamic_cast< ConstructorInit * >( objDecl->get_init() );
    809                                 assert( ctorInit && ctorInit->get_dtor() );
    810                                 *out++ = ctorInit->get_dtor()->clone();
    811                         } // for
    812                 }
    813 
    814                 void InsertDtors::previsit( ObjectDecl * objDecl ) {
    815                         // remember non-static destructed objects so that their destructors can be inserted later
    816                         if ( ! objDecl->get_storageClasses().is_static ) {
    817                                 if ( ConstructorInit * ctorInit = dynamic_cast< ConstructorInit * >( objDecl->get_init() ) ) {
    818                                         // a decision should have been made by the resolver, so ctor and init are not both non-NULL
    819                                         assert( ! ctorInit->get_ctor() || ! ctorInit->get_init() );
    820                                         Statement * dtor = ctorInit->get_dtor();
    821                                         // don't need to call intrinsic dtor, because it does nothing, but
    822                                         // non-intrinsic dtors must be called
    823                                         if ( dtor && ! isIntrinsicSingleArgCallStmt( dtor ) ) {
    824                                                 // set dtor location to the object's location for error messages
    825                                                 ctorInit->dtor->location = objDecl->location;
    826                                                 reverseDeclOrder.front().push_front( objDecl );
    827                                         } // if
    828                                 } // if
    829                         } // if
    830                 }
    831 
    832869                void InsertDtors::previsit( FunctionDecl * funcDecl ) {
    833870                        // each function needs to have its own set of labels
     
    842879                }
    843880
    844                 void InsertDtors::previsit( CompoundStmt * compoundStmt ) {
    845                         // visit statements - this will also populate reverseDeclOrder list.  don't want to dump all destructors
    846                         // when block is left, just the destructors associated with variables defined in this block, so push a new
    847                         // list to the top of the stack so that we can differentiate scopes
    848                         reverseDeclOrder.push_front( OrderedDecls() );
    849                         Parent::previsit( compoundStmt );
    850                 }
    851 
    852                 void InsertDtors::postvisit( CompoundStmt * compoundStmt ) {
    853                         // add destructors for the current scope that we're exiting, unless the last statement is a return, which
    854                         // causes unreachable code warnings
    855                         std::list< Statement * > & statements = compoundStmt->get_kids();
    856                         if ( ! statements.empty() && ! dynamic_cast< ReturnStmt * >( statements.back() ) ) {
    857                                 insertDtors( reverseDeclOrder.front().begin(), reverseDeclOrder.front().end(), back_inserter( statements ) );
    858                         }
    859                         reverseDeclOrder.pop_front();
    860                 }
    861 
    862                 void InsertDtors::previsit( ReturnStmt * ) {
    863                         // return exits all scopes, so dump destructors for all scopes
    864                         for ( OrderedDecls & od : reverseDeclOrder ) {
    865                                 insertDtors( od.begin(), od.end(), back_inserter( stmtsToAddBefore ) );
    866                         } // for
    867                 }
    868 
    869881                // Handle break/continue/goto in the same manner as C++.  Basic idea: any objects that are in scope at the
    870882                // BranchStmt but not at the labelled (target) statement must be destructed.  If there are any objects in scope
     
    894906                        if ( ! diff.empty() ) {
    895907                                throw SemanticError( std::string("jump to label '") + stmt->get_target().get_name() + "' crosses initialization of " + (*diff.begin())->get_name() + " ", stmt );
    896                         } // if
    897                         // S_G-S_L results in set of objects that must be destructed
    898                         diff.clear();
    899                         std::set_difference( curVars.begin(), curVars.end(), lvars.begin(), lvars.end(), std::inserter( diff, diff.end() ) );
    900                         DTOR_PRINT(
    901                                 std::cerr << "S_G-S_L = " << printSet( diff ) << std::endl;
    902                         )
    903                         if ( ! diff.empty() ) {
    904                                 // create an auxilliary set for fast lookup -- can't make diff a set, because diff ordering should be consistent for error messages.
    905                                 std::unordered_set<ObjectDecl *> needsDestructor( diff.begin(), diff.end() );
    906 
    907                                 // go through decl ordered list of objectdecl. for each element that occurs in diff, output destructor
    908                                 OrderedDecls ordered;
    909                                 for ( OrderedDecls & rdo : reverseDeclOrder ) {
    910                                         // add elements from reverseDeclOrder into ordered if they occur in diff - it is key that this happens in reverse declaration order.
    911                                         copy_if( rdo.begin(), rdo.end(), back_inserter( ordered ), [&]( ObjectDecl * objDecl ) { return needsDestructor.count( objDecl ); } );
    912                                 } // for
    913                                 insertDtors( ordered.begin(), ordered.end(), back_inserter( stmtsToAddBefore ) );
    914908                        } // if
    915909                }
     
    937931                }
    938932
     933                void GenStructMemberCalls::previsit( StructDecl * structDecl ) {
     934                        if ( ! dtorStruct && structDecl->name == "__Destructor" ) {
     935                                dtorStruct = structDecl;
     936                        }
     937                }
     938
    939939                void GenStructMemberCalls::previsit( FunctionDecl * funcDecl ) {
    940940                        GuardValue( function );
     
    949949                        unhandled.clear();
    950950                        usedUninit.clear();
     951
     952                        if ( ! dtorStructDestroy && funcDecl->name == "__destroy_Destructor" ) {
     953                                dtorStructDestroy = funcDecl;
     954                                return;
     955                        }
    951956
    952957                        function = funcDecl;
     
    960965                                if ( structType ) {
    961966                                        structDecl = structType->get_baseStruct();
     967                                        if ( structDecl == dtorStruct ) return;
    962968                                        for ( Declaration * member : structDecl->get_members() ) {
    963969                                                if ( ObjectDecl * field = dynamic_cast< ObjectDecl * >( member ) ) {
     
    10291035                                                        callStmt->acceptMutator( resolver );
    10301036                                                        if ( isCtor ) {
    1031                                                                 function->get_statements()->push_front( callStmt );
     1037                                                                function->statements->push_front( callStmt );
    10321038                                                        } else {
    10331039                                                                // destructor statements should be added at the end
    1034                                                                 function->get_statements()->push_back( callStmt );
     1040                                                                // function->get_statements()->push_back( callStmt );
     1041
     1042                                                                // Destructor _dtor0 = { &b.a1, (void (*)(void *)_destroy_A };
     1043                                                                std::list< Statement * > stmtsToAdd;
     1044
     1045                                                                static UniqueName memberDtorNamer = { "__memberDtor" };
     1046                                                                assertf( dtorStruct, "builtin __Destructor not found." );
     1047                                                                assertf( dtorStructDestroy, "builtin __destroy_Destructor not found." );
     1048
     1049                                                                Expression * thisExpr = new AddressExpr( new VariableExpr( thisParam ) );
     1050                                                                Expression * dtorExpr = new VariableExpr( getDtorFunc( thisParam, callStmt, stmtsToAdd ) );
     1051
     1052                                                                // cast destructor pointer to void (*)(void *), to silence GCC incompatible pointer warnings
     1053                                                                FunctionType * dtorFtype = new FunctionType( Type::Qualifiers(), false );
     1054                                                                dtorFtype->parameters.push_back( ObjectDecl::newObject( "", new PointerType( Type::Qualifiers(), new VoidType( Type::Qualifiers() ) ), nullptr ) );
     1055                                                                Type * dtorType = new PointerType( Type::Qualifiers(), dtorFtype );
     1056
     1057                                                                ObjectDecl * destructor = ObjectDecl::newObject( memberDtorNamer.newName(), new StructInstType( Type::Qualifiers(), dtorStruct ), new ListInit( { new SingleInit( thisExpr ), new SingleInit( new CastExpr( dtorExpr, dtorType ) ) } ) );
     1058                                                                function->statements->push_front( new DeclStmt( noLabels, destructor ) );
     1059                                                                destructor->attributes.push_back( new Attribute( "cleanup", { new VariableExpr( dtorStructDestroy ) } ) );
     1060
     1061                                                                function->statements->kids.splice( function->statements->kids.begin(), stmtsToAdd );
    10351062                                                        }
    10361063                                                } catch ( SemanticError & error ) {
  • src/InitTweak/InitTweak.cc

    r3de176d rc0d00b6  
    345345                std::list< Expression * > matches;
    346346                collectCtorDtorCalls( stmt, matches );
    347                 assert( matches.size() <= 1 );
     347                assertf( matches.size() <= 1, "%zd constructor/destructors found in %s", matches.size(), toString( stmt ).c_str() );
    348348                return matches.size() == 1 ? matches.front() : nullptr;
    349349        }
  • src/SymTab/Autogen.cc

    r3de176d rc0d00b6  
    4646        /// Data used to generate functions generically. Specifically, the name of the generated function and a function which generates the routine protoype
    4747        struct FuncData {
    48                 typedef FunctionType * (*TypeGen)( Type * );
     48                typedef FunctionType * (*TypeGen)( Type *, bool );
    4949                FuncData( const std::string & fname, const TypeGen & genType ) : fname( fname ), genType( genType ) {}
    5050                std::string fname;
     
    232232
    233233        /// given type T, generate type of default ctor/dtor, i.e. function type void (*) (T *)
    234         FunctionType * genDefaultType( Type * paramType ) {
    235                 const auto & typeParams = getGenericParams( paramType );
     234        FunctionType * genDefaultType( Type * paramType, bool maybePolymorphic ) {
    236235                FunctionType *ftype = new FunctionType( Type::Qualifiers(), false );
    237                 cloneAll( typeParams, ftype->forall );
     236                if ( maybePolymorphic ) {
     237                        // only copy in
     238                        const auto & typeParams = getGenericParams( paramType );
     239                        cloneAll( typeParams, ftype->forall );
     240                }
    238241                ObjectDecl *dstParam = new ObjectDecl( "_dst", Type::StorageClasses(), LinkageSpec::Cforall, nullptr, new ReferenceType( Type::Qualifiers(), paramType->clone() ), nullptr );
    239242                ftype->parameters.push_back( dstParam );
     
    242245
    243246        /// given type T, generate type of copy ctor, i.e. function type void (*) (T *, T)
    244         FunctionType * genCopyType( Type * paramType ) {
    245                 FunctionType *ftype = genDefaultType( paramType );
     247        FunctionType * genCopyType( Type * paramType, bool maybePolymorphic ) {
     248                FunctionType *ftype = genDefaultType( paramType, maybePolymorphic );
    246249                ObjectDecl *srcParam = new ObjectDecl( "_src", Type::StorageClasses(), LinkageSpec::Cforall, nullptr, paramType->clone(), nullptr );
    247250                ftype->parameters.push_back( srcParam );
     
    250253
    251254        /// given type T, generate type of assignment, i.e. function type T (*) (T *, T)
    252         FunctionType * genAssignType( Type * paramType ) {
    253                 FunctionType *ftype = genCopyType( paramType );
     255        FunctionType * genAssignType( Type * paramType, bool maybePolymorphic ) {
     256                FunctionType *ftype = genCopyType( paramType, maybePolymorphic );
    254257                ObjectDecl *returnVal = new ObjectDecl( "_ret", Type::StorageClasses(), LinkageSpec::Cforall, nullptr, paramType->clone(), nullptr );
    255258                ftype->returnVals.push_back( returnVal );
     
    309312                for ( const FuncData & d : data ) {
    310313                        // generate a function (?{}, ?=?, ^?{}) based on the current FuncData.
    311                         FunctionType * ftype = d.genType( type );
     314                        FunctionType * ftype = d.genType( type, true );
    312315
    313316                        // destructor for concurrent type must be mutex
  • src/SymTab/Autogen.h

    r3de176d rc0d00b6  
    4545        extern FunctionDecl * dereferenceOperator;
    4646
    47         // generate the type of an assignment function for paramType
    48         FunctionType * genAssignType( Type * paramType );
    49 
    50         // generate the type of a default constructor or destructor for paramType
    51         FunctionType * genDefaultType( Type * paramType );
    52 
    53         // generate the type of a copy constructor for paramType
    54         FunctionType * genCopyType( Type * paramType );
     47        /// generate the type of an assignment function for paramType.
     48        /// maybePolymorphic is true if the resulting FunctionType is allowed to be polymorphic
     49        FunctionType * genAssignType( Type * paramType, bool maybePolymorphic = true );
     50
     51        /// generate the type of a default constructor or destructor for paramType.
     52        /// maybePolymorphic is true if the resulting FunctionType is allowed to be polymorphic
     53        FunctionType * genDefaultType( Type * paramType, bool maybePolymorphic = true );
     54
     55        /// generate the type of a copy constructor for paramType.
     56        /// maybePolymorphic is true if the resulting FunctionType is allowed to be polymorphic
     57        FunctionType * genCopyType( Type * paramType, bool maybePolymorphic = true );
    5558
    5659        /// inserts into out a generated call expression to function fname with arguments dstParam and srcParam. Intended to be used with generated ?=?, ?{}, and ^?{} calls.
  • src/SynTree/CompoundStmt.cc

    r3de176d rc0d00b6  
    5959                                DeclarationWithType * origdwt = strict_dynamic_cast< DeclarationWithType * > ( origDeclStmt->get_decl() );
    6060                                assert( dwt->get_name() == origdwt->get_name() );
    61                                 declMap[ origdwt ] = dwt;
     61                                declMap[ origdwt ] = new VariableExpr( dwt );
    6262                        } else assert( ! dynamic_cast< DeclarationWithType * > ( origDeclStmt->get_decl() ) );
    6363                } else assert( ! dynamic_cast< DeclStmt * > ( s ) );
     
    6565        if ( ! declMap.empty() ) {
    6666                VarExprReplacer replacer( declMap );
    67                 accept( replacer );
     67                acceptMutator( replacer );
    6868        }
    6969}
  • src/SynTree/FunctionDecl.cc

    r3de176d rc0d00b6  
    4343        VarExprReplacer::DeclMap declMap;
    4444        for ( auto p : group_iterate( other.type->parameters, type->parameters ) ) {
    45                 declMap[ std::get<0>(p) ] = std::get<1>(p);
     45                declMap[ std::get<0>(p) ] = new VariableExpr( std::get<1>(p) );
    4646        }
    4747        for ( auto p : group_iterate( other.type->returnVals, type->returnVals ) ) {
    48                 declMap[ std::get<0>(p) ] = std::get<1>(p);
     48                declMap[ std::get<0>(p) ] = new VariableExpr( std::get<1>(p) );
    4949        }
    5050        if ( ! declMap.empty() ) {
    5151                VarExprReplacer replacer( declMap );
    52                 accept( replacer );
     52                acceptMutator( replacer );
    5353        }
    5454}
  • src/SynTree/Mutator.h

    r3de176d rc0d00b6  
    119119
    120120        virtual TypeSubstitution * mutate( TypeSubstitution * sub );
     121
    121122  private:
    122123        virtual Declaration * handleAggregateDecl(AggregateDecl * aggregateDecl );
  • src/SynTree/VarExprReplacer.cc

    r3de176d rc0d00b6  
    2222VarExprReplacer::VarExprReplacer( const DeclMap & declMap, bool debug ) : declMap( declMap ), debug( debug ) {}
    2323
    24 // replace variable with new node from decl map
    25 void VarExprReplacer::visit( VariableExpr * varExpr ) {
    26         // xxx - assertions and parameters aren't accounted for in this... (i.e. they aren't inserted into the map when it's made, only DeclStmts are)
    27         if ( declMap.count( varExpr->get_var() ) ) {
    28                 if ( debug ) {
    29                         std::cerr << "replacing variable reference: " << (void*)varExpr->get_var() << " " << varExpr->get_var() << " with " << (void*)declMap.at( varExpr->get_var() ) << " " << declMap.at( varExpr->get_var() ) << std::endl;
    30                 }
    31                 varExpr->set_var( declMap.at( varExpr->get_var() ) );
     24VarExprReplacer::~VarExprReplacer() {
     25        for ( auto p : declMap ) {
     26                delete p.second;
    3227        }
    3328}
     29
     30// replace variable with new node from decl map
     31Expression * VarExprReplacer::mutate( VariableExpr * varExpr ) {
     32        // xxx - assertions and parameters aren't accounted for in this... (i.e. they aren't inserted into the map when it's made, only DeclStmts are)
     33        if ( declMap.count( varExpr->var ) ) {
     34                Expression * expr = declMap.at( varExpr->var );
     35                if ( debug ) {
     36                        std::cerr << "replacing variable reference: " << (void*)varExpr->var << " " << varExpr->var << " with " << (void*)expr << " " << expr << std::endl;
     37                }
     38                delete varExpr;
     39                return expr->clone();
     40        }
     41        return varExpr;
     42}
  • src/SynTree/VarExprReplacer.h

    r3de176d rc0d00b6  
    2424
    2525/// Visitor that replaces the declarations that VariableExprs refer to, according to the supplied mapping
    26 class VarExprReplacer : public Visitor {
     26class VarExprReplacer : public Mutator {
    2727public:
    28         typedef std::map< DeclarationWithType *, DeclarationWithType * > DeclMap;
     28        typedef std::map< DeclarationWithType *, Expression * > DeclMap;
    2929private:
    3030        const DeclMap & declMap;
     
    3232public:
    3333        VarExprReplacer( const DeclMap & declMap, bool debug = false );
     34        ~VarExprReplacer();
    3435
    3536        // replace variable with new node from decl map
    36         virtual void visit( VariableExpr * varExpr );
     37        virtual Expression * mutate( VariableExpr * varExpr );
    3738
    38         static void replace( BaseSyntaxNode * node, const DeclMap & declMap, bool debug = false ) {
     39        template<typename Node>
     40        static void replace( Node *& node, const DeclMap & declMap, bool debug = false ) {
    3941                VarExprReplacer replacer( declMap, debug );
    40                 maybeAccept( node, replacer );
     42                node = maybeMutate( node, replacer );
    4143        }
    4244};
  • src/prelude/builtins.c

    r3de176d rc0d00b6  
    9696static inline unsigned int ?\=?( unsigned int & x, unsigned long int y ) { x = x \ y; return x; }
    9797
     98// type that wraps a pointer and a destructor-like function - used in generating implicit destructor calls for struct members in user-defined functions
     99forall(dtype T)
     100struct __Destructor {
     101  T * object;
     102  void (*dtor)(T *);
     103};
     104
     105// defined destructor in the case that non-generated code wants to use __Destructor
     106forall(dtype T)
     107static inline void ^?{}(__Destructor(T) & x) {
     108  x.dtor(x.object);
     109}
     110
     111// easy interface into __Destructor's destructor for easy codegen purposes
     112extern "C" {
     113  forall(dtype T)
     114  static inline void __destroy_Destructor(__Destructor(T) * dtor) {
     115    ^(*dtor){};
     116  }
     117}
     118
    98119// Local Variables: //
    99120// mode: c //
  • src/tests/.expect/memberCtors-ERR1.txt

    r3de176d rc0d00b6  
    1 memberCtors.c:71:1 error: in void ?{}(B &b), field a2 used before being constructed
     1memberCtors.c:78:1 error: in void ?{}(B &b), field a2 used before being constructed
  • src/tests/.expect/memberCtors.txt

    r3de176d rc0d00b6  
    9898end copy construct A
    9999End of main
     100begin destruct B
    100101constructing int
    101102constructing int
     
    146147destructing int: 0
    147148destructing int: 1000
    148 destructing int: 0
    149 destructing int: 0
    150 destructing int: 999
    151 destructing int: 0
    152 destructing int: 0
    153 destructing int: 0
    154 destructing int: 0
    155 destructing int: 0
    156 destructing int: 999
     149end destruct B
     150destructing int: 0
     151destructing int: 0
     152destructing int: 999
     153destructing int: 0
     154destructing int: 0
     155destructing int: 0
     156destructing int: 0
     157destructing int: 0
     158destructing int: 999
     159begin destruct B
    157160constructing int
    158161constructing int
     
    203206destructing int: 0
    204207destructing int: 1000
    205 destructing int: 0
    206 destructing int: 0
    207 destructing int: 999
    208 destructing int: 0
    209 destructing int: 0
    210 destructing int: 0
    211 destructing int: 0
    212 destructing int: 0
    213 destructing int: 999
     208end destruct B
     209destructing int: 0
     210destructing int: 0
     211destructing int: 999
     212destructing int: 0
     213destructing int: 0
     214destructing int: 0
     215destructing int: 0
     216destructing int: 0
     217destructing int: 999
  • src/tests/memberCtors.c

    r3de176d rc0d00b6  
    2222}
    2323
    24 void ?=?(WrappedInt & this, int x) {
     24/* WrappedInt */ void ?=?(WrappedInt & this, int x) {
    2525  printf("assigning int: %d %d\n", this.x, x);
    2626  this.x = x;
     27  // return this;
    2728}
     29
     30// WrappedInt ?=?(WrappedInt & this, WrappedInt other) {
     31//   printf("assigning int: %d %d\n", this.x, other.x);
     32//   this.x = other.x;
     33//   return this;
     34// }
    2835
    2936struct A {
     
    7986
    8087void ^?{}(B & b) {
     88  printf("begin destruct B\n");
    8189  b.a2 = (A) { 0 };
    8290  ^(b.a1){};
     91  printf("end destruct B\n");
    8392} // a2, a3 never destructed - will be automatically destructed
    8493
    8594int main() {
    8695  printf("Before declaration of b1\n");
    87   B b1;
     96  B b1;  // b1 = { { 1000, 0, 0 }, { 1001, 0, 0 }, { 0, 0, 0 } }
    8897  printf("Before declaration of b2\n");
    8998  B b2 = b1;
Note: See TracChangeset for help on using the changeset viewer.