Changeset f1b1e4c


Ignore:
Timestamp:
Jun 1, 2016, 11:54:23 AM (9 years ago)
Author:
Rob Schluntz <rschlunt@…>
Branches:
ADT, aaron-thesis, arm-eh, ast-experimental, cleanup-dtors, ctor, deferred_resn, demangler, enum, forall-pointer-decay, gc_noraii, jacob/cs343-translation, jenkins-sandbox, master, memory, new-ast, new-ast-unique-expr, new-env, no_list, persistent-indexer, pthread-emulation, qualifiedEnum, resolv-new, with_gc
Children:
be945ac
Parents:
70f89d00
Message:

can construct global const objects, except with intrinsic constructors

Location:
src
Files:
19 edited

Legend:

Unmodified
Added
Removed
  • src/ArgTweak/FunctionFixer.cc

    r70f89d00 rf1b1e4c  
    55// file "LICENCE" distributed with Cforall.
    66//
    7 // FunctionFixer.cc -- 
     7// FunctionFixer.cc --
    88//
    99// Author           : Rodolfo G. Esteves
     
    4242        Expression *FunctionFixer::mutate( UntypedExpr *untypedExpr ) throw ( SemanticError ) {
    4343                assert( untypedExpr != 0 );
    44                 NameExpr *function;
    4544
    46                 if ( ( function = dynamic_cast< NameExpr *>(untypedExpr->get_function()) ) != 0 ) {
     45                if ( NameExpr * function = dynamic_cast< NameExpr *>(untypedExpr->get_function() ) ) {
    4746                        std::list < DeclarationWithType * > options;
    4847                        index->lookupId ( function->get_name(), options );
    4948                        for ( std::list < DeclarationWithType * >::iterator i = options.begin(); i != options.end(); i++ ) {
    50                                 FunctionType *f;
    51                                 if ( ( f = dynamic_cast< FunctionType * > ( (*i)->get_type() ) ) != 0 ) {
     49                                if ( FunctionType * f = dynamic_cast< FunctionType * > ( (*i)->get_type() ) )   {
    5250                                        std::list < DeclarationWithType * > &pars = f->get_parameters();
    53 
    5451                                        bool candidateExists ;
    55                                         for ( std::list < DeclarationWithType * >::iterator p = pars.begin(); p != pars.end(); p++ )
     52                                        for ( std::list < DeclarationWithType * >::iterator p = pars.begin(); p != pars.end(); p++ ) {
    5653                                                if ( ( candidateExists = align( f->get_parameters(), untypedExpr->get_args(), Matcher() ) ) ) break;
    57 
     54                                        }
    5855                                        if ( ! candidateExists ) throw SemanticError("Error in function call");
    5956                                } // if
  • src/InitTweak/FixGlobalInit.cc

    r70f89d00 rf1b1e4c  
    125125                std::list< Statement * > & destroyStatements = destroyFunction->get_statements()->get_kids();
    126126
    127                 // if ( objDecl->get_init() == NULL ) return;
    128127                if ( ! tryConstruct( objDecl ) ) return; // don't construct @= or designated objects
    129                 if ( objDecl->get_type()->get_isConst() ) return; // temporary: can't assign to a const variable
    130128                if ( objDecl->get_storageClass() == DeclarationNode::Extern ) return;
    131129                // C allows you to initialize objects with constant expressions
     
    146144                        init->get_args().push_back( new AddressExpr( new VariableExpr( objDecl ) ) );
    147145                        init->get_args().push_back( new VariableExpr( newObj ) );
    148                         initStatements.push_back( new ExprStmt( noLabels, init ) );
     146                        initStatements.push_back( new ImplicitCtorDtorStmt( new ExprStmt( noLabels, init ) ) );
    149147
    150148                        // add destructor calls to global destroy function
    151149                        UntypedExpr * destroy = new UntypedExpr( new NameExpr( "^?{}" ) );
    152150                        destroy->get_args().push_back( new AddressExpr( new VariableExpr( objDecl ) ) );
    153                         destroyStatements.push_front( new ExprStmt( noLabels, destroy ) );
     151                        destroyStatements.push_front( new ImplicitCtorDtorStmt( new ExprStmt( noLabels, destroy ) ) );
    154152                }
    155153        }
  • src/InitTweak/FixInit.cc

    r70f89d00 rf1b1e4c  
    132132                                return appExpr;
    133133                        } else if ( DeclarationWithType * funcDecl = dynamic_cast< DeclarationWithType * > ( function->get_var() ) ) {
    134                                 // FunctionType * ftype = funcDecl->get_functionType();
    135134                                FunctionType * ftype = dynamic_cast< FunctionType * >( GenPoly::getFunctionType( funcDecl->get_type() ) );
    136135                                assert( ftype );
  • src/InitTweak/GenInit.cc

    r70f89d00 rf1b1e4c  
    143143                if ( tryConstruct( objDecl ) ) {
    144144                        if ( inFunction ) {
    145                                 // remove qualifiers so that const objects can be initialized, and attach the
    146                                 // qualifiers to ConstructorInit so that they can be replaced after resolving
    147                                 Type * type = objDecl->get_type();
    148                                 Type::Qualifiers qualifiers = type->get_qualifiers();
    149                                 type->get_qualifiers() = Type::Qualifiers();
    150 
    151145                                if ( ArrayType * at = dynamic_cast< ArrayType * >( objDecl->get_type() ) ) {
    152146                                        // call into makeArrayFunction from validate.cc to generate calls to ctor/dtor for each element of array
     
    170164                                                assert( ctor.size() == 1 );
    171165                                                assert( dtor.size() == 1 );
    172 
    173                                                 objDecl->set_init( new ConstructorInit( ctor.front(), dtor.front(), objDecl->get_init(), objDecl, qualifiers ) );
     166                                                objDecl->set_init( new ConstructorInit( new ImplicitCtorDtorStmt( ctor.front() ), new ImplicitCtorDtorStmt( dtor.front() ), objDecl->get_init() ) );
    174167                                        } else {
    175168                                                // array came with an initializer list: initialize each element
     
    191184                                        ExprStmt * ctorStmt = new ExprStmt( noLabels, ctor );
    192185                                        ExprStmt * dtorStmt = new ExprStmt( noLabels, dtor );
    193                                         objDecl->set_init( new ConstructorInit( ctorStmt, dtorStmt, objDecl->get_init(), objDecl, qualifiers ) );
     186                                        objDecl->set_init( new ConstructorInit( new ImplicitCtorDtorStmt( ctorStmt ), new ImplicitCtorDtorStmt( dtorStmt ), objDecl->get_init() ) );
    194187                                }
    195188                        }
  • src/InitTweak/InitTweak.cc

    r70f89d00 rf1b1e4c  
    6060  }
    6161
    62   bool isInstrinsicSingleArgCallStmt( Statement * stmt ) {
    63     if ( stmt == NULL ) return false;
     62  Expression * getCtorDtorCall( Statement * stmt ) {
     63    if ( stmt == NULL ) return NULL;
    6464    if ( ExprStmt * exprStmt = dynamic_cast< ExprStmt * >( stmt ) ) {
    65       ApplicationExpr * appExpr = dynamic_cast< ApplicationExpr * >( exprStmt->get_expr() );
    66       assert( appExpr );
    67       VariableExpr * function = dynamic_cast< VariableExpr * >( appExpr->get_function() );
    68       assert( function );
    69       // check for Intrinsic only - don't want to remove all overridable ctor/dtors because autogenerated ctor/dtor
    70       // will call all member dtors, and some members may have a user defined dtor.
    71       FunctionType * funcType = GenPoly::getFunctionType( function->get_var()->get_type() );
    72       assert( funcType );
    73       return function->get_var()->get_linkage() == LinkageSpec::Intrinsic && funcType->get_parameters().size() == 1;
     65      return exprStmt->get_expr();
    7466    } else if ( CompoundStmt * compoundStmt = dynamic_cast< CompoundStmt * >( stmt ) ) {
    7567      // could also be a compound statement with a loop, in the case of an array
     
    7769      ForStmt * forStmt = dynamic_cast< ForStmt * >( compoundStmt->get_kids().back() );
    7870      assert( forStmt && forStmt->get_body() );
    79       return isInstrinsicSingleArgCallStmt( forStmt->get_body() );
     71      return getCtorDtorCall( forStmt->get_body() );
     72    } if ( ImplicitCtorDtorStmt * impCtorDtorStmt = dynamic_cast< ImplicitCtorDtorStmt * > ( stmt ) ) {
     73      return getCtorDtorCall( impCtorDtorStmt->get_callStmt() );
    8074    } else {
    8175      // should never get here
    8276      assert( false && "encountered unknown call statement" );
     77    }
     78  }
     79
     80  bool isInstrinsicSingleArgCallStmt( Statement * stmt ) {
     81    Expression * callExpr = getCtorDtorCall( stmt );
     82    if ( ! callExpr ) return false;
     83    ApplicationExpr * appExpr = dynamic_cast< ApplicationExpr * >( callExpr );
     84    assert( appExpr );
     85    VariableExpr * function = dynamic_cast< VariableExpr * >( appExpr->get_function() );
     86    assert( function );
     87    // check for Intrinsic only - don't want to remove all overridable ctor/dtors because autogenerated ctor/dtor
     88    // will call all member dtors, and some members may have a user defined dtor.
     89    FunctionType * funcType = GenPoly::getFunctionType( function->get_var()->get_type() );
     90    assert( funcType );
     91    return function->get_var()->get_linkage() == LinkageSpec::Intrinsic && funcType->get_parameters().size() == 1;
     92  }
     93
     94  namespace {
     95    template<typename CallExpr>
     96    Expression * callArg( CallExpr * callExpr, unsigned int pos ) {
     97      if ( pos >= callExpr->get_args().size() ) assert( false && "asking for argument that doesn't exist. Return NULL/throw exception?" );
     98      for ( Expression * arg : callExpr->get_args() ) {
     99        if ( pos == 0 ) return arg;
     100        pos--;
     101      }
     102      assert( false );
     103    }
     104  }
     105
     106  Expression * getCallArg( Expression * callExpr, unsigned int pos ) {
     107    if ( ApplicationExpr * appExpr = dynamic_cast< ApplicationExpr * >( callExpr ) ) {
     108      return callArg( appExpr, pos );
     109    } else if ( UntypedExpr * untypedExpr = dynamic_cast< UntypedExpr * >( callExpr ) ) {
     110      return callArg( untypedExpr, pos );
     111    } else {
     112      assert( false && "Unexpected expression type passed to getCallArg" );
    83113    }
    84114  }
  • src/InitTweak/InitTweak.h

    r70f89d00 rf1b1e4c  
    4040  bool isInstrinsicSingleArgCallStmt( Statement * expr );
    4141
     42  /// get the Ctor/Dtor call expression from a Statement that looks like a generated ctor/dtor call
     43  Expression * getCtorDtorCall( Statement * stmt );
     44
    4245  /// returns the name of the function being called
    43   std::string getFunctionName(Expression * expr);
     46  std::string getFunctionName( Expression * expr );
     47
     48  /// returns the argument to a call expression in position N indexed from 0
     49  Expression * getCallArg( Expression * callExpr, unsigned int pos );
    4450} // namespace
    4551
  • src/ResolvExpr/Resolver.cc

    r70f89d00 rf1b1e4c  
    5252                virtual void visit( BranchStmt *branchStmt );
    5353                virtual void visit( ReturnStmt *returnStmt );
     54                virtual void visit( ImplicitCtorDtorStmt * impCtorDtorStmt );
    5455
    5556                virtual void visit( SingleInit *singleInit );
     
    493494                        // no alternatives for the constructor initializer - fallback on C-style initializer
    494495                        // xxx - not sure if this makes a ton of sense - should maybe never be able to have this situation?
    495 
    496                         // reset type qualifiers
    497                         ctorInit->get_object()->get_type()->get_qualifiers() = ctorInit->get_qualifiers();
    498496                        fallbackInit( ctorInit );
    499497                        return;
    500498                }
    501                 // reset type qualifiers
    502                 ctorInit->get_object()->get_type()->get_qualifiers() = ctorInit->get_qualifiers();
    503499
    504500                // found a constructor - can get rid of C-style initializer
     
    518514                }
    519515        }
     516
     517        void Resolver::visit( ImplicitCtorDtorStmt * impCtorDtorStmt ) {
     518                // this code is fairly gross. If VariableExpr didn't have its own results list then this could be cleaned up a bit
     519                // by remembering the ObjectDecl in the ImplicitCtorDtorStmt and changing the ObjectDecl's type temporarily, but currently
     520                // VariableExprs have their own type list which is manipulated in AlternativeFinder (e.g. in inferRecursive).
     521
     522                // before resolving ctor/dtor, need to remove type qualifiers from the first argument (the object being constructed)
     523                Expression * callExpr = InitTweak::getCtorDtorCall( impCtorDtorStmt );
     524                assert( callExpr );
     525                Expression * constructee = InitTweak::getCallArg( callExpr, 0 );
     526                Type * type = 0;
     527                if ( UntypedExpr * plusExpr = dynamic_cast< UntypedExpr * >( constructee ) ) {
     528                        // constructee is <array>+<index>
     529                        // get Variable <array>, then get the base type of the VariableExpr - this is the type that needs to be fixed
     530                        Expression * arr = InitTweak::getCallArg( plusExpr, 0 );
     531                        assert( dynamic_cast< VariableExpr * >( arr ) );
     532                        assert( arr && arr->get_results().size() == 1 );
     533                        ArrayType * arrType = dynamic_cast< ArrayType * >( arr->get_results().front() );
     534                        assert( arrType );
     535                        type = arrType->get_base();
     536                } else {
     537                        // otherwise, constructing a plain object, which means the object's address is being taken.
     538                        // Need to get the type of the VariableExpr object, because the AddressExpr is rebuilt and uses the
     539                        // type of the VariableExpr to do so.
     540                        assert( constructee->get_results().size() == 1 );
     541                        AddressExpr * addrExpr = dynamic_cast< AddressExpr * > ( constructee );
     542                        assert( addrExpr );
     543                        VariableExpr * varExpr = dynamic_cast< VariableExpr * >( addrExpr->get_arg() );
     544                        assert( varExpr && varExpr->get_results().size() == 1 );
     545                        type = varExpr->get_results().front();
     546                }
     547                // remember qualifiers so they can be replaced
     548                Type::Qualifiers qualifiers = type->get_qualifiers();
     549
     550                // unfortunately, lvalue is considered a qualifier. For AddressExpr to resolve, its argument
     551                // must have an lvalue qualified type, so remove all qualifiers except lvalue. If we ever
     552                // remove lvalue as a qualifier, this can change to
     553                //   type->get_qualifiers() = Type::Qualifiers();
     554                type->get_qualifiers() -= Type::Qualifiers(true, true, true, false, true, true);
     555
     556                // finally, resolve the ctor/dtor
     557                impCtorDtorStmt->get_callStmt()->accept( *this );
     558
     559                // and reset type qualifiers after resolving
     560                type->get_qualifiers() = qualifiers;
     561        }
    520562} // namespace ResolvExpr
    521563
  • src/SymTab/Validate.cc

    r70f89d00 rf1b1e4c  
    291291
    292292        namespace {
    293                 template< typename DWTIterator >
    294                 void fixFunctionList( DWTIterator begin, DWTIterator end, FunctionType *func ) {
     293                template< typename DWTIterator, typename DWTList >
     294                void fixFunctionList( DWTIterator begin, DWTIterator end, FunctionType *func, DWTList & dwts ) {
    295295                        // the only case in which "void" is valid is where it is the only one in the list; then it should be removed
    296296                        // entirely other fix ups are handled by the FixFunction class
     
    298298                        FixFunction fixer;
    299299                        DWTIterator i = begin;
    300                         *i = (*i )->acceptMutator( fixer );
     300                        *i = (*i)->acceptMutator( fixer );
    301301                        if ( fixer.get_isVoid() ) {
    302302                                DWTIterator j = i;
    303303                                ++i;
    304                                 func->get_parameters().erase( j );
     304                                dwts.erase( j );
    305305                                if ( i != end ) {
    306306                                        throw SemanticError( "invalid type void in function type ", func );
     
    321321        void Pass1::visit( FunctionType *func ) {
    322322                // Fix up parameters and return types
    323                 fixFunctionList( func->get_parameters().begin(), func->get_parameters().end(), func );
    324                 fixFunctionList( func->get_returnVals().begin(), func->get_returnVals().end(), func );
     323                fixFunctionList( func->get_parameters().begin(), func->get_parameters().end(), func, func->get_parameters() );
     324                fixFunctionList( func->get_returnVals().begin(), func->get_returnVals().end(), func, func->get_returnVals() );
    325325                Visitor::visit( func );
    326326        }
  • src/SynTree/Initializer.cc

    r70f89d00 rf1b1e4c  
    8686
    8787
    88 ConstructorInit::ConstructorInit( Statement * ctor, Statement * dtor, Initializer * init, ObjectDecl * object, Type::Qualifiers qualifiers ) : Initializer( true ), ctor( ctor ), dtor( dtor ), init( init ), object( object ), qualifiers( qualifiers ) {}
    89 ConstructorInit::ConstructorInit( const ConstructorInit &other ) : Initializer( other ), ctor( maybeClone( other.ctor ) ), dtor( maybeClone( other.dtor ) ), init( maybeClone( other.init ) ), object( other.object ), qualifiers( other.qualifiers ) {
     88ConstructorInit::ConstructorInit( Statement * ctor, Statement * dtor, Initializer * init ) : Initializer( true ), ctor( ctor ), dtor( dtor ), init( init ) {}
     89ConstructorInit::ConstructorInit( const ConstructorInit &other ) : Initializer( other ), ctor( maybeClone( other.ctor ) ), dtor( maybeClone( other.dtor ) ), init( maybeClone( other.init ) ) {
    9090}
    9191
  • src/SynTree/Initializer.h

    r70f89d00 rf1b1e4c  
    109109class ConstructorInit : public Initializer {
    110110  public:
    111         ConstructorInit( Statement * ctor, Statement * dtor, Initializer * init, ObjectDecl * objectDecl, Type::Qualifiers qualifiers );
     111        ConstructorInit( Statement * ctor, Statement * dtor, Initializer * init );
    112112        ConstructorInit( const ConstructorInit &other );
    113113        virtual ~ConstructorInit();
     
    119119        void set_init( Initializer * newValue ) { init = newValue; }
    120120        Initializer * get_init() const { return init; }
    121         void set_object( ObjectDecl * newValue ) { object = newValue; }
    122         ObjectDecl * get_object() const { return object; }
    123         void set_qualifiers( Type::Qualifiers newValue ) { qualifiers = newValue; }
    124         Type::Qualifiers get_qualifiers() { return qualifiers; }
    125121
    126122        ConstructorInit *clone() const { return new ConstructorInit( *this ); }
     
    135131        // if an appropriate constructor definition is not found by the resolver
    136132        Initializer * init;
    137         // Non-owned pointer back to the object being constructed
    138         ObjectDecl * object;
    139         // to construct const objects, need to first remove type qualifiers, then resolve
    140         // then add qualifiers back onto object
    141         Type::Qualifiers qualifiers;
    142133};
    143134
  • src/SynTree/Mutator.cc

    r70f89d00 rf1b1e4c  
    182182}
    183183
     184Statement *Mutator::mutate( ImplicitCtorDtorStmt *impCtorDtorStmt ) {
     185        impCtorDtorStmt->set_callStmt( maybeMutate( impCtorDtorStmt->get_callStmt(), *this ) );
     186        return impCtorDtorStmt;
     187}
     188
    184189Expression *Mutator::mutate( ApplicationExpr *applicationExpr ) {
    185190        mutateAll( applicationExpr->get_results(), *this );
  • src/SynTree/Mutator.h

    r70f89d00 rf1b1e4c  
    5252        virtual NullStmt* mutate( NullStmt *nullStmt );
    5353        virtual Statement* mutate( DeclStmt *declStmt );
     54        virtual Statement* mutate( ImplicitCtorDtorStmt *impCtorDtorStmt );
    5455
    5556        virtual Expression* mutate( ApplicationExpr *applicationExpr );
  • src/SynTree/Statement.cc

    r70f89d00 rf1b1e4c  
    358358
    359359void CatchStmt::print( std::ostream &os, int indent ) const {
    360         os << string( indent, ' ' ) << "Catch Statement" << endl;
     360        os << "Catch Statement" << endl;
    361361
    362362        os << string( indent, ' ' ) << "... catching" << endl;
     
    383383
    384384void FinallyStmt::print( std::ostream &os, int indent ) const {
    385         os << string( indent, ' ' ) << "Finally Statement" << endl;
     385        os << "Finally Statement" << endl;
    386386        os << string( indent + 2, ' ' ) << "with block: " << endl;
    387387        block->print( os, indent + 4 );
     
    393393void NullStmt::print( std::ostream &os, int indent ) const {
    394394        os << "Null Statement" << endl ;
     395}
     396
     397ImplicitCtorDtorStmt::ImplicitCtorDtorStmt( Statement * callStmt ) : Statement( std::list<Label>() ), callStmt( callStmt ) {
     398        assert( callStmt );
     399}
     400
     401ImplicitCtorDtorStmt::ImplicitCtorDtorStmt( const ImplicitCtorDtorStmt & other ) : Statement( other ), callStmt( other.callStmt ) {
     402}
     403
     404ImplicitCtorDtorStmt::~ImplicitCtorDtorStmt() {
     405}
     406
     407void ImplicitCtorDtorStmt::print( std::ostream &os, int indent ) const {
     408        os << "Implicit Ctor Dtor Statement" << endl;
     409        os << string( indent + 2, ' ' ) << "with Ctor/Dtor: ";
     410        callStmt->print( os, indent + 2);
     411        os << endl;
    395412}
    396413
  • src/SynTree/Statement.h

    r70f89d00 rf1b1e4c  
    2121#include "Mutator.h"
    2222#include "Common/SemanticError.h"
     23#include "Type.h"
    2324
    2425class Statement {
     
    394395        virtual ~DeclStmt();
    395396
    396         Declaration *get_decl() { return decl; }
     397        Declaration *get_decl() const { return decl; }
    397398        void set_decl( Declaration *newValue ) { decl = newValue; }
    398399
     
    404405        Declaration *decl;
    405406};
     407
     408
     409/// represents an implicit application of a constructor or destructor. Qualifiers are replaced
     410/// immediately before and after the call so that qualified objects can be constructed
     411/// with the same functions as unqualified objects.
     412class ImplicitCtorDtorStmt : public Statement {
     413  public:
     414        ImplicitCtorDtorStmt( Statement * callStmt );
     415        ImplicitCtorDtorStmt( const ImplicitCtorDtorStmt & other );
     416        virtual ~ImplicitCtorDtorStmt();
     417
     418        Statement *get_callStmt() const { return callStmt; }
     419        void set_callStmt( Statement * newValue ) { callStmt = newValue; }
     420
     421        virtual ImplicitCtorDtorStmt *clone() const { return new ImplicitCtorDtorStmt( *this ); }
     422        virtual void accept( Visitor &v ) { v.visit( this ); }
     423        virtual Statement *acceptMutator( Mutator &m ) { return m.mutate( this ); }
     424        virtual void print( std::ostream &os, int indent = 0 ) const;
     425
     426  private:
     427        // Non-owned pointer to the constructor/destructor statement
     428        Statement * callStmt;
     429};
     430
    406431
    407432std::ostream & operator<<( std::ostream & out, Statement * statement );
  • src/SynTree/SynTree.h

    r70f89d00 rf1b1e4c  
    5656class DeclStmt;
    5757class NullStmt;
     58class ImplicitCtorDtorStmt;
    5859
    5960class Expression;
  • src/SynTree/Type.cc

    r70f89d00 rf1b1e4c  
    55// file "LICENCE" distributed with Cforall.
    66//
    7 // Type.cc -- 
     7// Type.cc --
    88//
    99// Author           : Richard C. Bilson
     
    5454}
    5555
     56void Type::Qualifiers::print( std::ostream &os, int indent ) const {
     57        if ( isConst ) {
     58                os << "const ";
     59        } // if
     60        if ( isVolatile ) {
     61                os << "volatile ";
     62        } // if
     63        if ( isRestrict ) {
     64                os << "restrict ";
     65        } // if
     66        if ( isLvalue ) {
     67                os << "lvalue ";
     68        } // if
     69        if ( isAtomic ) {
     70                os << "_Atomic ";
     71        } // if
     72        if ( isAttribute ) {
     73                os << "__attribute(( )) ";
     74        } // if
     75}
     76
    5677void Type::print( std::ostream &os, int indent ) const {
    5778        if ( ! forall.empty() ) {
     
    6081                os << std::string( indent+2, ' ' );
    6182        } // if
    62         if ( tq.isConst ) {
    63                 os << "const ";
    64         } // if
    65         if ( tq.isVolatile ) {
    66                 os << "volatile ";
    67         } // if
    68         if ( tq.isRestrict ) {
    69                 os << "restrict ";
    70         } // if
    71         if ( tq.isLvalue ) {
    72                 os << "lvalue ";
    73         } // if
    74         if ( tq.isAtomic ) {
    75                 os << "_Atomic ";
    76         } // if
    77         if ( tq.isAttribute ) {
    78                 os << "__attribute(( )) ";
    79         } // if
     83        tq.print( os, indent );
    8084}
    8185
  • src/SynTree/Type.h

    r70f89d00 rf1b1e4c  
    3636                bool operator<( const Qualifiers &other );
    3737                bool operator>( const Qualifiers &other );
     38                void print( std::ostream &os, int indent = 0 ) const;
    3839
    3940                bool isConst;
  • src/SynTree/Visitor.cc

    r70f89d00 rf1b1e4c  
    152152}
    153153
     154void Visitor::visit( ImplicitCtorDtorStmt *impCtorDtorStmt ) {
     155        maybeAccept( impCtorDtorStmt->get_callStmt(), *this );
     156}
     157
    154158void Visitor::visit( ApplicationExpr *applicationExpr ) {
    155159        acceptAll( applicationExpr->get_results(), *this );
  • src/SynTree/Visitor.h

    r70f89d00 rf1b1e4c  
    5252        virtual void visit( NullStmt *nullStmt );
    5353        virtual void visit( DeclStmt *declStmt );
     54        virtual void visit( ImplicitCtorDtorStmt *impCtorDtorStmt );
    5455
    5556        virtual void visit( ApplicationExpr *applicationExpr );
Note: See TracChangeset for help on using the changeset viewer.