Changeset d7dc824


Ignore:
Timestamp:
Jun 7, 2017, 4:53:42 PM (7 years ago)
Author:
Thierry Delisle <tdelisle@…>
Branches:
ADT, aaron-thesis, arm-eh, ast-experimental, cleanup-dtors, deferred_resn, demangler, enum, forall-pointer-decay, jacob/cs343-translation, jenkins-sandbox, master, new-ast, new-ast-unique-expr, new-env, no_list, persistent-indexer, pthread-emulation, qualifiedEnum, resolv-new, with_gc
Children:
c77fd8b, ec95d11
Parents:
af397ef8
Message:

Removed more warnings

Location:
src
Files:
26 edited

Legend:

Unmodified
Added
Removed
  • src/CodeGen/CodeGenerator.cc

    raf397ef8 rd7dc824  
    112112
    113113        CodeGenerator::CodeGenerator( std::ostream & os, bool pretty, bool genC, bool lineMarks ) : indent( *this), cur_indent( 0 ), insideFunction( false ), output( os ), printLabels( *this ), pretty( pretty ), genC( genC ), lineMarks( lineMarks ) {}
    114 
    115         CodeGenerator::CodeGenerator( std::ostream & os, std::string init, int indentation, bool infunp )
    116                         : indent( *this), cur_indent( indentation ), insideFunction( infunp ), output( os ), printLabels( *this ) {
    117                 //output << std::string( init );
    118         }
    119 
    120         CodeGenerator::CodeGenerator( std::ostream & os, char * init, int indentation, bool infunp )
    121                         : indent( *this ), cur_indent( indentation ), insideFunction( infunp ), output( os ), printLabels( *this ) {
    122                 //output << std::string( init );
    123         }
    124114
    125115        string CodeGenerator::mangleName( DeclarationWithType * decl ) {
  • src/Common/PassVisitor.h

    raf397ef8 rd7dc824  
    9090        virtual void visit( TupleExpr *tupleExpr ) override final;
    9191        virtual void visit( TupleIndexExpr *tupleExpr ) override final;
    92         virtual void visit( MemberTupleExpr *tupleExpr ) override final;
    9392        virtual void visit( TupleAssignExpr *assignExpr ) override final;
    9493        virtual void visit( StmtExpr * stmtExpr ) override final;
     
    176175        virtual Expression* mutate( TupleExpr *tupleExpr ) override final;
    177176        virtual Expression* mutate( TupleIndexExpr *tupleExpr ) override final;
    178         virtual Expression* mutate( MemberTupleExpr *tupleExpr ) override final;
    179177        virtual Expression* mutate( TupleAssignExpr *assignExpr ) override final;
    180178        virtual Expression* mutate( StmtExpr * stmtExpr ) override final;
  • src/Common/PassVisitor.impl.h

    raf397ef8 rd7dc824  
    617617
    618618template< typename pass_type >
    619 void PassVisitor< pass_type >::visit( MemberTupleExpr * node ) {
    620         VISIT_BODY( node );
    621 }
    622 
    623 template< typename pass_type >
    624619void PassVisitor< pass_type >::visit( TupleAssignExpr * node ) {
    625620        VISIT_BODY( node );
     
    999994
    1000995template< typename pass_type >
    1001 Expression * PassVisitor< pass_type >::mutate( MemberTupleExpr * node ) {
    1002         MUTATE_BODY( Expression, node );
    1003 }
    1004 
    1005 template< typename pass_type >
    1006996Expression * PassVisitor< pass_type >::mutate( TupleAssignExpr * node ) {
    1007997        MUTATE_BODY( Expression, node );
  • src/Common/PassVisitor.proto.h

    raf397ef8 rd7dc824  
    1818// Visit
    1919template<typename pass_type, typename node_type>
    20 static inline auto previsit_impl( pass_type& pass, node_type * node, __attribute__((unused)) int unused ) ->decltype( pass.previsit( node ), void() ) {
     20static inline auto previsit_impl( pass_type& pass, node_type * node, __attribute__((unused)) int unused ) -> decltype( pass.previsit( node ), void() ) {
    2121        pass.previsit( node );
    2222}
     
    2727
    2828template<typename pass_type, typename node_type>
    29 static inline auto postvisit_impl( pass_type& pass, node_type * node, __attribute__((unused)) int unused ) ->decltype( pass.postvisit( node ), void() ) {
     29static inline auto postvisit_impl( pass_type& pass, node_type * node, __attribute__((unused)) int unused ) -> decltype( pass.postvisit( node ), void() ) {
    3030        pass.postvisit( node );
    3131}
     
    3636// Mutate
    3737template<typename pass_type, typename node_type>
    38 static inline auto premutate_impl( pass_type& pass, node_type * node, __attribute__((unused)) int unused ) ->decltype( pass.premutate( node ), void() ) {
     38static inline auto premutate_impl( pass_type& pass, node_type * node, __attribute__((unused)) int unused ) -> decltype( pass.premutate( node ), void() ) {
    3939        return pass.premutate( node );
    4040}
     
    4545
    4646template<typename return_type, typename pass_type, typename node_type>
    47 static inline auto postmutate_impl( pass_type& pass, node_type * node, __attribute__((unused)) int unused ) ->decltype( pass.postmutate( node ) ) {
     47static inline auto postmutate_impl( pass_type& pass, node_type * node, __attribute__((unused)) int unused ) -> decltype( pass.postmutate( node ) ) {
    4848        return pass.postmutate( node );
    4949}
     
    5454// Begin/End scope
    5555template<typename pass_type>
    56 static inline auto begin_scope_impl( pass_type& pass, __attribute__((unused)) int unused ) ->decltype( pass.beginScope(), void() ) {
     56static inline auto begin_scope_impl( pass_type& pass, __attribute__((unused)) int unused ) -> decltype( pass.beginScope(), void() ) {
    5757        pass.beginScope();
    5858}
     
    6363
    6464template<typename pass_type>
    65 static inline auto end_scope_impl( pass_type& pass, __attribute__((unused)) int unused ) ->decltype( pass.endScope(), void() ) {
     65static inline auto end_scope_impl( pass_type& pass, __attribute__((unused)) int unused ) -> decltype( pass.endScope(), void() ) {
    6666        pass.endScope();
    6767}
     
    7373#define FIELD_PTR( type, name )                                                                                                        \
    7474template<typename pass_type>                                                                                                           \
    75 static inline auto name##_impl( pass_type& pass, __attribute__((unused)) int unused ) ->decltype( &pass.name ) { return &pass.name; }  \
     75static inline auto name##_impl( pass_type& pass, __attribute__((unused)) int unused ) -> decltype( &pass.name ) { return &pass.name; }  \
    7676                                                                                                                                       \
    7777template<typename pass_type>                                                                                                           \
  • src/GenPoly/Box.cc

    raf397ef8 rd7dc824  
    110110                        Type *replaceWithConcrete( ApplicationExpr *appExpr, Type *type, bool doClone = true );
    111111                        /// wraps a function application returning a polymorphic type with a new temporary for the out-parameter return value
    112                         Expression *addDynRetParam( ApplicationExpr *appExpr, FunctionType *function, Type *polyType, std::list< Expression *>::iterator &arg );
     112                        Expression *addDynRetParam( ApplicationExpr *appExpr, Type *polyType, std::list< Expression *>::iterator &arg );
    113113                        Expression *applyAdapter( ApplicationExpr *appExpr, FunctionType *function, std::list< Expression *>::iterator &arg, const TyVarMap &exprTyVars );
    114114                        void boxParam( Type *formal, Expression *&arg, const TyVarMap &exprTyVars );
     
    728728                }
    729729
    730                 Expression *Pass1::addDynRetParam( ApplicationExpr *appExpr, FunctionType *function, Type *dynType, std::list< Expression *>::iterator &arg ) {
     730                Expression *Pass1::addDynRetParam( ApplicationExpr *appExpr, Type *dynType, std::list< Expression *>::iterator &arg ) {
    731731                        assert( env );
    732732                        Type *concrete = replaceWithConcrete( appExpr, dynType );
     
    11481148                        if ( dynRetType ) {
    11491149                                Type *concRetType = appExpr->get_result()->isVoid() ? nullptr : appExpr->get_result();
    1150                                 ret = addDynRetParam( appExpr, function, concRetType, arg ); // xxx - used to use dynRetType instead of concRetType
     1150                                ret = addDynRetParam( appExpr, concRetType, arg ); // xxx - used to use dynRetType instead of concRetType
    11511151                        } else if ( needsAdapter( function, scopeTyVars ) && ! needsAdapter( function, exprTyVars) ) { // xxx - exprTyVars is used above...?
    11521152                                // xxx - the ! needsAdapter check may be incorrect. It seems there is some situation where an adapter is applied where it shouldn't be, and this fixes it for some cases. More investigation is needed.
  • src/GenPoly/Specialize.cc

    raf397ef8 rd7dc824  
    9393        }
    9494
    95         bool needsTupleSpecialization( Type *formalType, Type *actualType, TypeSubstitution *env ) {
     95        bool needsTupleSpecialization( Type *formalType, Type *actualType ) {
    9696                // Needs tuple specialization if the structure of the formal type and actual type do not match.
    9797                // This is the case if the formal type has ttype polymorphism, or if the structure  of tuple types
     
    112112
    113113        bool needsSpecialization( Type *formalType, Type *actualType, TypeSubstitution *env ) {
    114                 return needsPolySpecialization( formalType, actualType, env ) || needsTupleSpecialization( formalType, actualType, env );
     114                return needsPolySpecialization( formalType, actualType, env ) || needsTupleSpecialization( formalType, actualType );
    115115        }
    116116
  • src/InitTweak/FixInit.cc

    raf397ef8 rd7dc824  
    902902                }
    903903
    904                 void InsertDtors::visit( ReturnStmt * returnStmt ) {
     904                void InsertDtors::visit( __attribute((unused)) ReturnStmt * returnStmt ) {
    905905                        // return exits all scopes, so dump destructors for all scopes
    906906                        for ( OrderedDecls & od : reverseDeclOrder ) {
  • src/Parser/ExpressionNode.cc

    raf397ef8 rd7dc824  
    223223} // build_field_name_REALDECIMALconstant
    224224
    225 NameExpr * build_varref( const string *name, bool labelp ) {
     225NameExpr * build_varref( const string *name ) {
    226226        NameExpr *expr = new NameExpr( *name, nullptr );
    227227        delete name;
  • src/Parser/ParseNode.h

    raf397ef8 rd7dc824  
    166166Expression * build_field_name_REALDECIMALconstant( const std::string & str );
    167167
    168 NameExpr * build_varref( const std::string * name, bool labelp = false );
     168NameExpr * build_varref( const std::string * name );
    169169Expression * build_typevalue( DeclarationNode * decl );
    170170
  • src/Parser/parser.yy

    raf397ef8 rd7dc824  
    547547                { $$ = new ExpressionNode( build_attrtype( build_varref( $1 ), $3 ) ); }
    548548//      | ANDAND IDENTIFIER                                                                     // GCC, address of label
    549 //              { $$ = new ExpressionNode( new OperatorNode( OperKinds::LabelAddress ), new ExpressionNode( build_varref( $2, true ) ); }
     549//              { $$ = new ExpressionNode( new OperatorNode( OperKinds::LabelAddress ), new ExpressionNode( build_varref( $2 ) ); }
    550550        ;
    551551
  • src/ResolvExpr/AlternativeFinder.cc

    raf397ef8 rd7dc824  
    9797                /// Prunes a list of alternatives down to those that have the minimum conversion cost for a given return type; skips ambiguous interpretations
    9898                template< typename InputIterator, typename OutputIterator >
    99                 void pruneAlternatives( InputIterator begin, InputIterator end, OutputIterator out, const SymTab::Indexer &indexer ) {
     99                void pruneAlternatives( InputIterator begin, InputIterator end, OutputIterator out ) {
    100100                        // select the alternatives that have the minimum conversion cost for a particular set of result types
    101101                        std::map< std::string, PruneStruct > selected;
     
    183183                        )
    184184                        AltList::iterator oldBegin = alternatives.begin();
    185                         pruneAlternatives( alternatives.begin(), alternatives.end(), front_inserter( alternatives ), indexer );
     185                        pruneAlternatives( alternatives.begin(), alternatives.end(), front_inserter( alternatives ) );
    186186                        if ( alternatives.begin() == oldBegin ) {
    187187                                std::ostringstream stream;
  • src/ResolvExpr/CommonType.cc

    raf397ef8 rd7dc824  
    157157        void CommonType::visit( PointerType *pointerType ) {
    158158                if ( PointerType *otherPointer = dynamic_cast< PointerType* >( type2 ) ) {
    159                         if ( widenFirst && dynamic_cast< VoidType* >( otherPointer->get_base() ) && ! isFtype(pointerType->get_base(), indexer) ) {
     159                        if ( widenFirst && dynamic_cast< VoidType* >( otherPointer->get_base() ) && ! isFtype(pointerType->get_base()) ) {
    160160                                getCommonWithVoidPointer( otherPointer, pointerType );
    161                         } else if ( widenSecond && dynamic_cast< VoidType* >( pointerType->get_base() ) && ! isFtype(otherPointer->get_base(), indexer) ) {
     161                        } else if ( widenSecond && dynamic_cast< VoidType* >( pointerType->get_base() ) && ! isFtype(otherPointer->get_base()) ) {
    162162                                getCommonWithVoidPointer( pointerType, otherPointer );
    163163                        } else if ( ( pointerType->get_base()->get_qualifiers() >= otherPointer->get_base()->get_qualifiers() || widenFirst )
  • src/ResolvExpr/Unify.cc

    raf397ef8 rd7dc824  
    114114        }
    115115
    116         bool isFtype( Type *type, const SymTab::Indexer &indexer ) {
     116        bool isFtype( Type *type ) {
    117117                if ( dynamic_cast< FunctionType* >( type ) ) {
    118118                        return true;
     
    123123        }
    124124
    125         bool tyVarCompatible( const TypeDecl::Data & data, Type *type, const SymTab::Indexer &indexer ) {
     125        bool tyVarCompatible( const TypeDecl::Data & data, Type *type ) {
    126126                switch ( data.kind ) {
    127127                  case TypeDecl::Any:
     
    131131                        // type must also be complete
    132132                        // xxx - should this also check that type is not a tuple type and that it's not a ttype?
    133                         return ! isFtype( type, indexer ) && (! data.isComplete || type->isComplete() );
     133                        return ! isFtype( type ) && (! data.isComplete || type->isComplete() );
    134134                  case TypeDecl::Ftype:
    135                         return isFtype( type, indexer );
     135                        return isFtype( type );
    136136                  case TypeDecl::Ttype:
    137137                        // ttype unifies with any tuple type
     
    144144                OpenVarSet::const_iterator tyvar = openVars.find( typeInst->get_name() );
    145145                assert( tyvar != openVars.end() );
    146                 if ( ! tyVarCompatible( tyvar->second, other, indexer ) ) {
     146                if ( ! tyVarCompatible( tyvar->second, other ) ) {
    147147                        return false;
    148148                } // if
  • src/ResolvExpr/typeops.h

    raf397ef8 rd7dc824  
    118118
    119119        // in Unify.cc
    120         bool isFtype( Type *type, const SymTab::Indexer &indexer );
     120        bool isFtype( Type *type );
    121121        bool typesCompatible( Type *, Type *, const SymTab::Indexer &indexer, const TypeEnvironment &env );
    122122        bool typesCompatibleIgnoreQualifiers( Type *, Type *, const SymTab::Indexer &indexer, const TypeEnvironment &env );
  • src/SymTab/Autogen.cc

    raf397ef8 rd7dc824  
    262262        // E ?=?(E volatile*, int),
    263263        //   ?=?(E _Atomic volatile*, int);
    264         void makeEnumFunctions( EnumDecl *enumDecl, EnumInstType *refType, unsigned int functionNesting, std::list< Declaration * > &declsToAdd ) {
     264        void makeEnumFunctions( EnumInstType *refType, unsigned int functionNesting, std::list< Declaration * > &declsToAdd ) {
    265265
    266266                // T ?=?(E *, E);
     
    486486
    487487        /// generates the body of a union assignment/copy constructor/field constructor
    488         void makeUnionAssignBody( FunctionDecl * funcDecl, bool isDynamicLayout ) {
     488        void makeUnionAssignBody( FunctionDecl * funcDecl ) {
    489489                FunctionType * ftype = funcDecl->get_functionType();
    490490                assert( ftype->get_parameters().size() == 2 );
     
    506506                // Make function polymorphic in same parameters as generic union, if applicable
    507507                const std::list< TypeDecl* > & typeParams = aggregateDecl->get_parameters(); // List of type variables to be placed on the generated functions
    508                 bool isDynamicLayout = hasDynamicLayout( aggregateDecl );  // NOTE this flag is an incredibly ugly kludge; we should fix the assignment signature instead (ditto for struct)
    509 
     508               
    510509                // default ctor/dtor need only first parameter
    511510                // void ?{}(T *); void ^?{}(T *);
     
    533532                FunctionDecl *dtorDecl = genFunc( "^?{}", dtorType, functionNesting );
    534533
    535                 makeUnionAssignBody( assignDecl, isDynamicLayout );
     534                makeUnionAssignBody( assignDecl );
    536535
    537536                // body of assignment and copy ctor is the same
    538                 makeUnionAssignBody( copyCtorDecl, isDynamicLayout );
     537                makeUnionAssignBody( copyCtorDecl );
    539538
    540539                // create a constructor which takes the first member type as a parameter.
     
    551550                                FunctionDecl * ctor = genFunc( "?{}", memCtorType, functionNesting );
    552551
    553                                 makeUnionAssignBody( ctor, isDynamicLayout );
     552                                makeUnionAssignBody( ctor );
    554553                                memCtors.push_back( ctor );
    555554                                // only generate a ctor for the first field
     
    578577                        EnumInstType *enumInst = new EnumInstType( Type::Qualifiers(), enumDecl->get_name() );
    579578                        // enumInst->set_baseEnum( enumDecl );
    580                         makeEnumFunctions( enumDecl, enumInst, functionNesting, declsToAddAfter );
     579                        makeEnumFunctions( enumInst, functionNesting, declsToAddAfter );
    581580                }
    582581        }
  • src/SymTab/Indexer.cc

    raf397ef8 rd7dc824  
    518518                acceptNewScope( tupleExpr->get_result(), *this );
    519519                maybeAccept( tupleExpr->get_tuple(), *this );
    520         }
    521 
    522         void Indexer::visit( MemberTupleExpr *tupleExpr ) {
    523                 acceptNewScope( tupleExpr->get_result(), *this );
    524                 maybeAccept( tupleExpr->get_member(), *this );
    525                 maybeAccept( tupleExpr->get_aggregate(), *this );
    526520        }
    527521
  • src/SymTab/Indexer.h

    raf397ef8 rd7dc824  
    7474                virtual void visit( TupleExpr *tupleExpr );
    7575                virtual void visit( TupleIndexExpr *tupleExpr );
    76                 virtual void visit( MemberTupleExpr *tupleExpr );
    7776                virtual void visit( TupleAssignExpr *tupleExpr );
    7877                virtual void visit( StmtExpr * stmtExpr );
  • src/SynTree/Expression.h

    raf397ef8 rd7dc824  
    690690};
    691691
    692 /// MemberTupleExpr represents a tuple member selection operation on a struct type, e.g. s.[a, b, c] after processing by the expression analyzer
    693 class MemberTupleExpr : public Expression {
    694   public:
    695         MemberTupleExpr( Expression * member, Expression * aggregate, Expression * _aname = nullptr );
    696         MemberTupleExpr( const MemberTupleExpr & other );
    697         virtual ~MemberTupleExpr();
    698 
    699         Expression * get_member() const { return member; }
    700         Expression * get_aggregate() const { return aggregate; }
    701         MemberTupleExpr * set_member( Expression * newValue ) { member = newValue; return this; }
    702         MemberTupleExpr * set_aggregate( Expression * newValue ) { aggregate = newValue; return this; }
    703 
    704         virtual MemberTupleExpr * clone() const { return new MemberTupleExpr( * this ); }
    705         virtual void accept( Visitor & v ) { v.visit( this ); }
    706         virtual Expression * acceptMutator( Mutator & m ) { return m.mutate( this ); }
    707         virtual void print( std::ostream & os, int indent = 0 ) const;
    708   private:
    709         Expression * member;
    710         Expression * aggregate;
    711 };
    712 
    713692/// TupleAssignExpr represents a multiple assignment operation, where both sides of the assignment have tuple type, e.g. [a, b, c] = [d, e, f];, a mass assignment operation, where the left hand side has tuple type and the right hand side does not, e.g. [a, b, c] = 5.0;, or a tuple ctor/dtor expression
    714693class TupleAssignExpr : public Expression {
  • src/SynTree/Initializer.cc

    raf397ef8 rd7dc824  
    3333}
    3434
    35 void Initializer::print( std::ostream &os, int indent ) {}
     35// void Initializer::print( __attribute__((unused)) std::ostream &os, __attribute__((unused)) int indent ) {}
    3636
    3737SingleInit::SingleInit( Expression *v, const std::list< Expression *> &_designators, bool maybeConstructed ) : Initializer( maybeConstructed ), value ( v ), designators( _designators ) {
  • src/SynTree/Initializer.h

    raf397ef8 rd7dc824  
    5353        virtual void accept( Visitor &v ) = 0;
    5454        virtual Initializer *acceptMutator( Mutator &m ) = 0;
    55         virtual void print( std::ostream &os, int indent = 0 );
     55        virtual void print( std::ostream &os, int indent = 0 ) = 0;
    5656  private:
    5757        //      std::string name;
  • src/SynTree/Mutator.cc

    raf397ef8 rd7dc824  
    408408}
    409409
    410 Expression *Mutator::mutate( MemberTupleExpr *tupleExpr ) {
    411         tupleExpr->set_env( maybeMutate( tupleExpr->get_env(), *this ) );
    412         tupleExpr->set_result( maybeMutate( tupleExpr->get_result(), *this ) );
    413         tupleExpr->set_member( maybeMutate( tupleExpr->get_member(), *this ) );
    414         tupleExpr->set_aggregate( maybeMutate( tupleExpr->get_aggregate(), *this ) );
    415         return tupleExpr;
    416 }
    417 
    418410Expression *Mutator::mutate( TupleAssignExpr *assignExpr ) {
    419411        assignExpr->set_env( maybeMutate( assignExpr->get_env(), *this ) );
  • src/SynTree/Mutator.h

    raf397ef8 rd7dc824  
    8282        virtual Expression* mutate( TupleExpr *tupleExpr );
    8383        virtual Expression* mutate( TupleIndexExpr *tupleExpr );
    84         virtual Expression* mutate( MemberTupleExpr *tupleExpr );
    8584        virtual Expression* mutate( TupleAssignExpr *assignExpr );
    8685        virtual Expression* mutate( StmtExpr * stmtExpr );
  • src/SynTree/SynTree.h

    raf397ef8 rd7dc824  
    8989class TupleExpr;
    9090class TupleIndexExpr;
    91 class MemberTupleExpr;
    9291class TupleAssignExpr;
    9392class StmtExpr;
  • src/SynTree/TupleExpr.cc

    raf397ef8 rd7dc824  
    7878}
    7979
    80 MemberTupleExpr::MemberTupleExpr( Expression * member, Expression * aggregate, Expression * _aname ) : Expression( _aname ) {
    81         set_result( maybeClone( member->get_result() ) ); // xxx - ???
    82 }
    83 
    84 MemberTupleExpr::MemberTupleExpr( const MemberTupleExpr &other ) : Expression( other ), member( other.member->clone() ), aggregate( other.aggregate->clone() ) {
    85 }
    86 
    87 MemberTupleExpr::~MemberTupleExpr() {
    88         delete member;
    89         delete aggregate;
    90 }
    91 
    92 void MemberTupleExpr::print( std::ostream &os, int indent ) const {
    93         os << "Member Tuple Expression, with aggregate:" << std::endl;
    94         os << std::string( indent+2, ' ' );
    95         aggregate->print( os, indent+2 );
    96         os << std::string( indent+2, ' ' ) << "with member: " << std::endl;
    97         os << std::string( indent+2, ' ' );
    98         member->print( os, indent+2 );
    99         Expression::print( os, indent );
    100 }
    101 
    10280TupleAssignExpr::TupleAssignExpr( const std::list< Expression * > & assigns, const std::list< ObjectDecl * > & tempDecls, Expression * _aname ) : Expression( _aname ) {
    10381        // convert internally into a StmtExpr which contains the declarations and produces the tuple of the assignments
  • src/SynTree/Visitor.cc

    raf397ef8 rd7dc824  
    321321}
    322322
    323 void Visitor::visit( MemberTupleExpr *tupleExpr ) {
    324         maybeAccept( tupleExpr->get_result(), *this );
    325         maybeAccept( tupleExpr->get_member(), *this );
    326         maybeAccept( tupleExpr->get_aggregate(), *this );
    327 }
    328 
    329323void Visitor::visit( TupleAssignExpr *assignExpr ) {
    330324        maybeAccept( assignExpr->get_result(), *this );
  • src/SynTree/Visitor.h

    raf397ef8 rd7dc824  
    8585        virtual void visit( TupleExpr *tupleExpr );
    8686        virtual void visit( TupleIndexExpr *tupleExpr );
    87         virtual void visit( MemberTupleExpr *tupleExpr );
    8887        virtual void visit( TupleAssignExpr *assignExpr );
    8988        virtual void visit( StmtExpr * stmtExpr );
Note: See TracChangeset for help on using the changeset viewer.