Ignore:
Timestamp:
Jun 12, 2023, 2:45:32 PM (2 years ago)
Author:
Fangren Yu <f37yu@…>
Branches:
ast-experimental, master
Children:
62d62db
Parents:
34b4268 (diff), 251ce80 (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' into ast-experimental

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/Parser/StatementNode.cc

    r34b4268 r24d6572  
    1010// Author           : Rodolfo G. Esteves
    1111// Created On       : Sat May 16 14:59:41 2015
    12 // Last Modified By : Peter A. Buhr
    13 // Last Modified On : Wed Feb  2 20:29:30 2022
    14 // Update Count     : 425
     12// Last Modified By : Andrew Beach
     13// Last Modified On : Tue Apr 11 10:16:00 2023
     14// Update Count     : 428
    1515//
    1616
     17#include "StatementNode.h"
     18
    1719#include <cassert>                 // for assert, strict_dynamic_cast, assertf
    18 #include <list>                    // for list
    1920#include <memory>                  // for unique_ptr
    2021#include <string>                  // for string
    2122
     23#include "AST/Label.hpp"           // for Label
     24#include "AST/Stmt.hpp"            // for Stmt, AsmStmt, BranchStmt, CaseCla...
    2225#include "Common/SemanticError.h"  // for SemanticError
    2326#include "Common/utility.h"        // for maybeMoveBuild, maybeBuild
    24 #include "ParseNode.h"             // for StatementNode, ExpressionNode, bui...
    25 #include "SynTree/Expression.h"    // for Expression, ConstantExpr
    26 #include "SynTree/Label.h"         // for Label, noLabels
    27 #include "SynTree/Declaration.h"
    28 #include "SynTree/Statement.h"     // for Statement, BranchStmt, CaseStmt
     27#include "DeclarationNode.h"       // for DeclarationNode
     28#include "ExpressionNode.h"        // for ExpressionNode
    2929#include "parserutility.h"         // for notZeroExpr
    3030
     
    3333using namespace std;
    3434
     35// Some helpers for cases that really want a single node but check for lists.
     36static const ast::Stmt * buildMoveSingle( StatementNode * node ) {
     37        std::vector<ast::ptr<ast::Stmt>> list;
     38        buildMoveList( node, list );
     39        assertf( list.size() == 1, "CFA Internal Error: Extra/Missing Nodes" );
     40        return list.front().release();
     41}
     42
     43static const ast::Stmt * buildMoveOptional( StatementNode * node ) {
     44        std::vector<ast::ptr<ast::Stmt>> list;
     45        buildMoveList( node, list );
     46        assertf( list.size() <= 1, "CFA Internal Error: Extra Nodes" );
     47        return list.empty() ? nullptr : list.front().release();
     48}
    3549
    3650StatementNode::StatementNode( DeclarationNode * decl ) {
     
    3852        DeclarationNode * agg = decl->extractAggregate();
    3953        if ( agg ) {
    40                 StatementNode * nextStmt = new StatementNode( new DeclStmt( maybeBuild< Declaration >( decl ) ) );
     54                StatementNode * nextStmt = new StatementNode(
     55                        new ast::DeclStmt( decl->location, maybeBuild( decl ) ) );
    4156                set_next( nextStmt );
    4257                if ( decl->get_next() ) {
     
    5166                agg = decl;
    5267        } // if
    53         stmt.reset( new DeclStmt( maybeMoveBuild< Declaration >(agg) ) );
     68        // Local copy to avoid accessing the pointer after it is moved from.
     69        CodeLocation declLocation = agg->location;
     70        stmt.reset( new ast::DeclStmt( declLocation, maybeMoveBuild( agg ) ) );
    5471} // StatementNode::StatementNode
    5572
    56 StatementNode * StatementNode::append_last_case( StatementNode * stmt ) {
    57         StatementNode * prev = this;
     73StatementNode * StatementNode::add_label(
     74                const CodeLocation & location,
     75                const std::string * name,
     76                DeclarationNode * attr ) {
     77        stmt->labels.emplace_back( location,
     78                *name,
     79                attr ? std::move( attr->attributes )
     80                        : std::vector<ast::ptr<ast::Attribute>>{} );
     81        delete attr;
     82        delete name;
     83        return this;
     84}
     85
     86ClauseNode * ClauseNode::append_last_case( StatementNode * stmt ) {
     87        ClauseNode * prev = this;
    5888        // find end of list and maintain previous pointer
    59         for ( StatementNode * curr = prev; curr != nullptr; curr = (StatementNode *)curr->get_next() ) {
    60                 StatementNode * node = strict_dynamic_cast< StatementNode * >(curr);
    61                 assert( dynamic_cast< CaseStmt * >(node->stmt.get()) );
     89        for ( ClauseNode * curr = prev; curr != nullptr; curr = (ClauseNode *)curr->get_next() ) {
     90                ClauseNode * node = strict_dynamic_cast< ClauseNode * >(curr);
     91                assert( dynamic_cast<ast::CaseClause *>( node->clause.get() ) );
    6292                prev = curr;
    6393        } // for
     94        ClauseNode * node = dynamic_cast< ClauseNode * >(prev);
    6495        // convert from StatementNode list to Statement list
    65         StatementNode * node = dynamic_cast< StatementNode * >(prev);
    66         list< Statement * > stmts;
     96        std::vector<ast::ptr<ast::Stmt>> stmts;
    6797        buildMoveList( stmt, stmts );
    6898        // splice any new Statements to end of current Statements
    69         CaseStmt * caseStmt = dynamic_cast< CaseStmt * >(node->stmt.get());
    70         caseStmt->get_statements().splice( caseStmt->get_statements().end(), stmts );
     99        auto caseStmt = strict_dynamic_cast<ast::CaseClause *>( node->clause.get() );
     100        for ( auto const & newStmt : stmts ) {
     101                caseStmt->stmts.emplace_back( newStmt );
     102        }
     103        stmts.clear();
    71104        return this;
    72 } // StatementNode::append_last_case
    73 
    74 Statement * build_expr( ExpressionNode * ctl ) {
    75         Expression * e = maybeMoveBuild< Expression >( ctl );
    76 
    77         if ( e ) return new ExprStmt( e );
    78         else return new NullStmt();
     105} // ClauseNode::append_last_case
     106
     107ast::Stmt * build_expr( CodeLocation const & location, ExpressionNode * ctl ) {
     108        if ( ast::Expr * e = maybeMoveBuild( ctl ) ) {
     109                return new ast::ExprStmt( location, e );
     110        } else {
     111                return new ast::NullStmt( location );
     112        }
    79113} // build_expr
    80114
    81 Expression * build_if_control( CondCtl * ctl, list< Statement * > & init ) {
    82         if ( ctl->init != 0 ) {
    83                 buildMoveList( ctl->init, init );
     115static ast::Expr * build_if_control( CondCtl * ctl,
     116                std::vector<ast::ptr<ast::Stmt>> & inits ) {
     117        assert( inits.empty() );
     118        if ( nullptr != ctl->init ) {
     119                buildMoveList( ctl->init, inits );
    84120        } // if
    85121
    86         Expression * cond = nullptr;
     122        ast::Expr * cond = nullptr;
    87123        if ( ctl->condition ) {
    88124                // compare the provided condition against 0
    89                 cond = notZeroExpr( maybeMoveBuild< Expression >(ctl->condition) );
     125                cond = notZeroExpr( maybeMoveBuild( ctl->condition ) );
    90126        } else {
    91                 for ( Statement * stmt : init ) {
     127                for ( ast::ptr<ast::Stmt> & stmt : inits ) {
    92128                        // build the && of all of the declared variables compared against 0
    93                         DeclStmt * declStmt = strict_dynamic_cast< DeclStmt * >( stmt );
    94                         DeclarationWithType * dwt = strict_dynamic_cast< DeclarationWithType * >( declStmt->decl );
    95                         Expression * nze = notZeroExpr( new VariableExpr( dwt ) );
    96                         cond = cond ? new LogicalExpr( cond, nze, true ) : nze;
     129                        auto declStmt = stmt.strict_as<ast::DeclStmt>();
     130                        auto dwt = declStmt->decl.strict_as<ast::DeclWithType>();
     131                        ast::Expr * nze = notZeroExpr( new ast::VariableExpr( dwt->location, dwt ) );
     132                        cond = cond ? new ast::LogicalExpr( dwt->location, cond, nze, ast::AndExpr ) : nze;
    97133                }
    98134        }
     
    101137} // build_if_control
    102138
    103 Statement * build_if( CondCtl * ctl, StatementNode * then, StatementNode * else_ ) {
    104         list< Statement * > astinit;                                            // maybe empty
    105         Expression * astcond = build_if_control( ctl, astinit ); // ctl deleted, cond/init set
    106 
    107         Statement * astthen, * astelse = nullptr;
    108         list< Statement * > aststmt;
    109         buildMoveList< Statement, StatementNode >( then, aststmt );
    110         assert( aststmt.size() == 1 );
    111         astthen = aststmt.front();
    112 
    113         if ( else_ ) {
    114                 list< Statement * > aststmt;
    115                 buildMoveList< Statement, StatementNode >( else_, aststmt );
    116                 assert( aststmt.size() == 1 );
    117                 astelse = aststmt.front();
    118         } // if
    119 
    120         return new IfStmt( astcond, astthen, astelse, astinit );
     139ast::Stmt * build_if( const CodeLocation & location, CondCtl * ctl, StatementNode * then, StatementNode * else_ ) {
     140        std::vector<ast::ptr<ast::Stmt>> astinit;                                               // maybe empty
     141        ast::Expr * astcond = build_if_control( ctl, astinit ); // ctl deleted, cond/init set
     142
     143        ast::Stmt const * astthen = buildMoveSingle( then );
     144        ast::Stmt const * astelse = buildMoveOptional( else_ );
     145
     146        return new ast::IfStmt( location, astcond, astthen, astelse,
     147                std::move( astinit )
     148        );
    121149} // build_if
    122150
    123 Statement * build_switch( bool isSwitch, ExpressionNode * ctl, StatementNode * stmt ) {
    124         list< Statement * > aststmt;
    125         buildMoveList< Statement, StatementNode >( stmt, aststmt );
    126         if ( ! isSwitch ) {                                                                     // choose statement
    127                 for ( Statement * stmt : aststmt ) {
    128                         CaseStmt * caseStmt = strict_dynamic_cast< CaseStmt * >( stmt );
    129                         if ( ! caseStmt->stmts.empty() ) {                      // code after "case" => end of case list
    130                                 CompoundStmt * block = strict_dynamic_cast< CompoundStmt * >( caseStmt->stmts.front() );
    131                                 block->kids.push_back( new BranchStmt( "", BranchStmt::Break ) );
     151ast::Stmt * build_switch( const CodeLocation & location, bool isSwitch, ExpressionNode * ctl, ClauseNode * stmt ) {
     152        std::vector<ast::ptr<ast::CaseClause>> aststmt;
     153        buildMoveList( stmt, aststmt );
     154        // If it is not a switch it is a choose statement.
     155        if ( ! isSwitch ) {
     156                for ( ast::ptr<ast::CaseClause> & stmt : aststmt ) {
     157                        // Code after "case" is the end of case list.
     158                        if ( !stmt->stmts.empty() ) {
     159                                auto mutStmt = ast::mutate( stmt.get() );
     160                                // I believe the stmts are actually always one block.
     161                                auto stmts = mutStmt->stmts.front().get_and_mutate();
     162                                auto block = strict_dynamic_cast<ast::CompoundStmt *>( stmts );
     163                                block->kids.push_back( new ast::BranchStmt( block->location,
     164                                        ast::BranchStmt::Break,
     165                                        ast::Label( block->location ) ) );
     166                                stmt = mutStmt;
    132167                        } // if
    133168                } // for
    134169        } // if
    135170        // aststmt.size() == 0 for switch (...) {}, i.e., no declaration or statements
    136         return new SwitchStmt( maybeMoveBuild< Expression >(ctl), aststmt );
     171        return new ast::SwitchStmt( location,
     172                maybeMoveBuild( ctl ), std::move( aststmt ) );
    137173} // build_switch
    138174
    139 Statement * build_case( ExpressionNode * ctl ) {
    140         return new CaseStmt( maybeMoveBuild< Expression >(ctl), {} ); // stmt starts empty and then added to
     175ast::CaseClause * build_case( const CodeLocation & location, ExpressionNode * ctl ) {
     176        // stmt starts empty and then added to
     177        auto expr = maybeMoveBuild( ctl );
     178        return new ast::CaseClause( location, expr, {} );
    141179} // build_case
    142180
    143 Statement * build_default() {
    144         return new CaseStmt( nullptr, {}, true );                       // stmt starts empty and then added to
     181ast::CaseClause * build_default( const CodeLocation & location ) {
     182        // stmt starts empty and then added to
     183        return new ast::CaseClause( location, nullptr, {} );
    145184} // build_default
    146185
    147 Statement * build_while( CondCtl * ctl, StatementNode * stmt, StatementNode * else_ ) {
    148         list< Statement * > astinit;                                            // maybe empty
    149         Expression * astcond = build_if_control( ctl, astinit ); // ctl deleted, cond/init set
    150 
    151         list< Statement * > aststmt;                                            // loop body, compound created if empty
    152         buildMoveList< Statement, StatementNode >( stmt, aststmt );
    153         assert( aststmt.size() == 1 );
    154 
    155         list< Statement * > astelse;                                            // else clause, maybe empty
    156         buildMoveList< Statement, StatementNode >( else_, astelse );
    157 
    158         return new WhileDoStmt( astcond, aststmt.front(), astelse.front(), astinit, false );
     186ast::Stmt * build_while( const CodeLocation & location, CondCtl * ctl, StatementNode * stmt, StatementNode * else_ ) {
     187        std::vector<ast::ptr<ast::Stmt>> astinit;                                               // maybe empty
     188        ast::Expr * astcond = build_if_control( ctl, astinit ); // ctl deleted, cond/init set
     189
     190        return new ast::WhileDoStmt( location,
     191                astcond,
     192                buildMoveSingle( stmt ),
     193                buildMoveOptional( else_ ),
     194                std::move( astinit ),
     195                ast::While
     196        );
    159197} // build_while
    160198
    161 Statement * build_do_while( ExpressionNode * ctl, StatementNode * stmt, StatementNode * else_ ) {
    162         list< Statement * > aststmt;                                            // loop body, compound created if empty
    163         buildMoveList< Statement, StatementNode >( stmt, aststmt );
    164         assert( aststmt.size() == 1 );                                          // compound created if empty
    165 
    166         list< Statement * > astelse;                                            // else clause, maybe empty
    167         buildMoveList< Statement, StatementNode >( else_, astelse );
    168 
     199ast::Stmt * build_do_while( const CodeLocation & location, ExpressionNode * ctl, StatementNode * stmt, StatementNode * else_ ) {
    169200        // do-while cannot have declarations in the contitional, so init is always empty
    170         return new WhileDoStmt( notZeroExpr( maybeMoveBuild< Expression >(ctl) ), aststmt.front(), astelse.front(), {}, true );
     201        return new ast::WhileDoStmt( location,
     202                notZeroExpr( maybeMoveBuild( ctl ) ),
     203                buildMoveSingle( stmt ),
     204                buildMoveOptional( else_ ),
     205                {},
     206                ast::DoWhile
     207        );
    171208} // build_do_while
    172209
    173 Statement * build_for( ForCtrl * forctl, StatementNode * stmt, StatementNode * else_ ) {
    174         list< Statement * > astinit;                                            // maybe empty
     210ast::Stmt * build_for( const CodeLocation & location, ForCtrl * forctl, StatementNode * stmt, StatementNode * else_ ) {
     211        std::vector<ast::ptr<ast::Stmt>> astinit;                                               // maybe empty
    175212        buildMoveList( forctl->init, astinit );
    176213
    177         Expression * astcond = nullptr;                                         // maybe empty
    178         astcond = notZeroExpr( maybeMoveBuild< Expression >(forctl->condition) );
    179 
    180         Expression * astincr = nullptr;                                         // maybe empty
    181         astincr = maybeMoveBuild< Expression >(forctl->change);
     214        ast::Expr * astcond = nullptr;                                          // maybe empty
     215        astcond = notZeroExpr( maybeMoveBuild( forctl->condition ) );
     216
     217        ast::Expr * astincr = nullptr;                                          // maybe empty
     218        astincr = maybeMoveBuild( forctl->change );
    182219        delete forctl;
    183220
    184         list< Statement * > aststmt;                                            // loop body, compound created if empty
    185         buildMoveList< Statement, StatementNode >( stmt, aststmt );
    186         assert( aststmt.size() == 1 );
    187 
    188         list< Statement * > astelse;                                            // else clause, maybe empty
    189         buildMoveList< Statement, StatementNode >( else_, astelse );
    190 
    191         return new ForStmt( astinit, astcond, astincr, aststmt.front(), astelse.front() );
     221        return new ast::ForStmt( location,
     222                std::move( astinit ),
     223                astcond,
     224                astincr,
     225                buildMoveSingle( stmt ),
     226                buildMoveOptional( else_ )
     227        );
    192228} // build_for
    193229
    194 Statement * build_branch( BranchStmt::Type kind ) {
    195         Statement * ret = new BranchStmt( "", kind );
    196         return ret;
     230ast::Stmt * build_branch( const CodeLocation & location, ast::BranchStmt::Kind kind ) {
     231        return new ast::BranchStmt( location,
     232                kind,
     233                ast::Label( location )
     234        );
    197235} // build_branch
    198236
    199 Statement * build_branch( string * identifier, BranchStmt::Type kind ) {
    200         Statement * ret = new BranchStmt( * identifier, kind );
     237ast::Stmt * build_branch( const CodeLocation & location, string * identifier, ast::BranchStmt::Kind kind ) {
     238        ast::Stmt * ret = new ast::BranchStmt( location,
     239                kind,
     240                ast::Label( location, *identifier )
     241        );
    201242        delete identifier;                                                                      // allocated by lexer
    202243        return ret;
    203244} // build_branch
    204245
    205 Statement * build_computedgoto( ExpressionNode * ctl ) {
    206         return new BranchStmt( maybeMoveBuild< Expression >(ctl), BranchStmt::Goto );
     246ast::Stmt * build_computedgoto( ExpressionNode * ctl ) {
     247        ast::Expr * expr = maybeMoveBuild( ctl );
     248        return new ast::BranchStmt( expr->location, expr );
    207249} // build_computedgoto
    208250
    209 Statement * build_return( ExpressionNode * ctl ) {
    210         list< Expression * > exps;
     251ast::Stmt * build_return( const CodeLocation & location, ExpressionNode * ctl ) {
     252        std::vector<ast::ptr<ast::Expr>> exps;
    211253        buildMoveList( ctl, exps );
    212         return new ReturnStmt( exps.size() > 0 ? exps.back() : nullptr );
     254        return new ast::ReturnStmt( location,
     255                exps.size() > 0 ? exps.back().release() : nullptr
     256        );
    213257} // build_return
    214258
    215 Statement * build_throw( ExpressionNode * ctl ) {
    216         list< Expression * > exps;
     259static ast::Stmt * build_throw_stmt(
     260                const CodeLocation & location,
     261                ExpressionNode * ctl,
     262                ast::ExceptionKind kind ) {
     263        std::vector<ast::ptr<ast::Expr>> exps;
    217264        buildMoveList( ctl, exps );
    218265        assertf( exps.size() < 2, "CFA internal error: leaking memory" );
    219         return new ThrowStmt( ThrowStmt::Terminate, !exps.empty() ? exps.back() : nullptr );
     266        return new ast::ThrowStmt( location,
     267                kind,
     268                !exps.empty() ? exps.back().release() : nullptr,
     269                (ast::Expr *)nullptr
     270        );
     271}
     272
     273ast::Stmt * build_throw( const CodeLocation & loc, ExpressionNode * ctl ) {
     274        return build_throw_stmt( loc, ctl, ast::Terminate );
    220275} // build_throw
    221276
    222 Statement * build_resume( ExpressionNode * ctl ) {
    223         list< Expression * > exps;
    224         buildMoveList( ctl, exps );
    225         assertf( exps.size() < 2, "CFA internal error: leaking memory" );
    226         return new ThrowStmt( ThrowStmt::Resume, !exps.empty() ? exps.back() : nullptr );
     277ast::Stmt * build_resume( const CodeLocation & loc, ExpressionNode * ctl ) {
     278        return build_throw_stmt( loc, ctl, ast::Resume );
    227279} // build_resume
    228280
    229 Statement * build_resume_at( ExpressionNode * ctl, ExpressionNode * target ) {
     281ast::Stmt * build_resume_at( ExpressionNode * ctl, ExpressionNode * target ) {
    230282        (void)ctl;
    231283        (void)target;
     
    233285} // build_resume_at
    234286
    235 Statement * build_try( StatementNode * try_, StatementNode * catch_, StatementNode * finally_ ) {
    236         list< CatchStmt * > aststmt;
    237         buildMoveList< CatchStmt, StatementNode >( catch_, aststmt );
    238         CompoundStmt * tryBlock = strict_dynamic_cast< CompoundStmt * >(maybeMoveBuild< Statement >(try_));
    239         FinallyStmt * finallyBlock = dynamic_cast< FinallyStmt * >(maybeMoveBuild< Statement >(finally_) );
    240         return new TryStmt( tryBlock, aststmt, finallyBlock );
     287ast::Stmt * build_try( const CodeLocation & location, StatementNode * try_, ClauseNode * catch_, ClauseNode * finally_ ) {
     288        std::vector<ast::ptr<ast::CatchClause>> aststmt;
     289        buildMoveList( catch_, aststmt );
     290        ast::CompoundStmt * tryBlock = strict_dynamic_cast<ast::CompoundStmt *>( maybeMoveBuild( try_ ) );
     291        ast::FinallyClause * finallyBlock = nullptr;
     292        if ( finally_ ) {
     293                finallyBlock = dynamic_cast<ast::FinallyClause *>( finally_->clause.release() );
     294        }
     295        return new ast::TryStmt( location,
     296                tryBlock,
     297                std::move( aststmt ),
     298                finallyBlock
     299        );
    241300} // build_try
    242301
    243 Statement * build_catch( CatchStmt::Kind kind, DeclarationNode * decl, ExpressionNode * cond, StatementNode * body ) {
    244         list< Statement * > aststmt;
    245         buildMoveList< Statement, StatementNode >( body, aststmt );
    246         assert( aststmt.size() == 1 );
    247         return new CatchStmt( kind, maybeMoveBuild< Declaration >(decl), maybeMoveBuild< Expression >(cond), aststmt.front() );
     302ast::CatchClause * build_catch( const CodeLocation & location, ast::ExceptionKind kind, DeclarationNode * decl, ExpressionNode * cond, StatementNode * body ) {
     303        return new ast::CatchClause( location,
     304                kind,
     305                maybeMoveBuild( decl ),
     306                maybeMoveBuild( cond ),
     307                buildMoveSingle( body )
     308        );
    248309} // build_catch
    249310
    250 Statement * build_finally( StatementNode * stmt ) {
    251         list< Statement * > aststmt;
    252         buildMoveList< Statement, StatementNode >( stmt, aststmt );
    253         assert( aststmt.size() == 1 );
    254         return new FinallyStmt( dynamic_cast< CompoundStmt * >( aststmt.front() ) );
     311ast::FinallyClause * build_finally( const CodeLocation & location, StatementNode * stmt ) {
     312        return new ast::FinallyClause( location,
     313                strict_dynamic_cast<const ast::CompoundStmt *>(
     314                        buildMoveSingle( stmt )
     315                )
     316        );
    255317} // build_finally
    256318
    257 SuspendStmt * build_suspend( StatementNode * then, SuspendStmt::Type type ) {
    258         auto node = new SuspendStmt();
    259 
    260         node->type = type;
    261 
    262         list< Statement * > stmts;
    263         buildMoveList< Statement, StatementNode >( then, stmts );
    264         if(!stmts.empty()) {
    265                 assert( stmts.size() == 1 );
    266                 node->then = dynamic_cast< CompoundStmt * >( stmts.front() );
    267         }
    268 
    269         return node;
    270 }
    271 
    272 WaitForStmt * build_waitfor( ExpressionNode * targetExpr, StatementNode * stmt, ExpressionNode * when ) {
    273         auto node = new WaitForStmt();
    274 
    275         WaitForStmt::Target target;
    276         target.function = maybeBuild<Expression>( targetExpr );
     319ast::SuspendStmt * build_suspend( const CodeLocation & location, StatementNode * then, ast::SuspendStmt::Kind kind ) {
     320        return new ast::SuspendStmt( location,
     321                strict_dynamic_cast<const ast::CompoundStmt *, nullptr>(
     322                        buildMoveOptional( then )
     323                ),
     324                kind
     325        );
     326} // build_suspend
     327
     328ast::WaitForStmt * build_waitfor( const CodeLocation & location, ast::WaitForStmt * existing, ExpressionNode * when, ExpressionNode * targetExpr, StatementNode * stmt ) {
     329        auto clause = new ast::WaitForClause( location );
     330        clause->target = maybeBuild( targetExpr );
     331        clause->stmt = maybeMoveBuild( stmt );
     332        clause->when_cond = notZeroExpr( maybeMoveBuild( when ) );
    277333
    278334        ExpressionNode * next = dynamic_cast<ExpressionNode *>( targetExpr->get_next() );
    279335        targetExpr->set_next( nullptr );
    280         buildMoveList< Expression >( next, target.arguments );
     336        buildMoveList( next, clause->target_args );
    281337
    282338        delete targetExpr;
    283339
    284         node->clauses.push_back( WaitForStmt::Clause{
    285                 target,
    286                 maybeMoveBuild<Statement >( stmt ),
    287                 notZeroExpr( maybeMoveBuild<Expression>( when ) )
    288         });
    289 
    290         return node;
     340        existing->clauses.insert( existing->clauses.begin(), clause );
     341
     342        return existing;
    291343} // build_waitfor
    292344
    293 WaitForStmt * build_waitfor( ExpressionNode * targetExpr, StatementNode * stmt, ExpressionNode * when, WaitForStmt * node ) {
    294         WaitForStmt::Target target;
    295         target.function = maybeBuild<Expression>( targetExpr );
    296 
    297         ExpressionNode * next = dynamic_cast<ExpressionNode *>( targetExpr->get_next() );
    298         targetExpr->set_next( nullptr );
    299         buildMoveList< Expression >( next, target.arguments );
    300 
    301         delete targetExpr;
    302 
    303         node->clauses.insert( node->clauses.begin(), WaitForStmt::Clause{
    304                 std::move( target ),
    305                 maybeMoveBuild<Statement >( stmt ),
    306                 notZeroExpr( maybeMoveBuild<Expression>( when ) )
    307         });
    308 
    309         return node;
    310 } // build_waitfor
    311 
    312 WaitForStmt * build_waitfor_timeout( ExpressionNode * timeout, StatementNode * stmt, ExpressionNode * when ) {
    313         auto node = new WaitForStmt();
    314 
    315         if( timeout ) {
    316                 node->timeout.time      = maybeMoveBuild<Expression>( timeout );
    317                 node->timeout.statement = maybeMoveBuild<Statement >( stmt    );
    318                 node->timeout.condition = notZeroExpr( maybeMoveBuild<Expression>( when ) );
    319         } else {
    320                 node->orelse.statement  = maybeMoveBuild<Statement >( stmt );
    321                 node->orelse.condition  = notZeroExpr( maybeMoveBuild<Expression>( when ) );
    322         } // if
    323 
    324         return node;
     345ast::WaitForStmt * build_waitfor_else( const CodeLocation & location, ast::WaitForStmt * existing, ExpressionNode * when, StatementNode * stmt ) {
     346        existing->else_stmt = maybeMoveBuild( stmt );
     347        existing->else_cond = notZeroExpr( maybeMoveBuild( when ) );
     348
     349        (void)location;
     350        return existing;
     351} // build_waitfor_else
     352
     353ast::WaitForStmt * build_waitfor_timeout( const CodeLocation & location, ast::WaitForStmt * existing, ExpressionNode * when, ExpressionNode * timeout, StatementNode * stmt ) {
     354        existing->timeout_time = maybeMoveBuild( timeout );
     355        existing->timeout_stmt = maybeMoveBuild( stmt );
     356        existing->timeout_cond = notZeroExpr( maybeMoveBuild( when ) );
     357
     358        (void)location;
     359        return existing;
    325360} // build_waitfor_timeout
    326361
    327 WaitForStmt * build_waitfor_timeout( ExpressionNode * timeout, StatementNode * stmt, ExpressionNode * when,  StatementNode * else_, ExpressionNode * else_when ) {
    328         auto node = new WaitForStmt();
    329 
    330         node->timeout.time      = maybeMoveBuild<Expression>( timeout );
    331         node->timeout.statement = maybeMoveBuild<Statement >( stmt    );
    332         node->timeout.condition = notZeroExpr( maybeMoveBuild<Expression>( when ) );
    333 
    334         node->orelse.statement  = maybeMoveBuild<Statement >( else_ );
    335         node->orelse.condition  = notZeroExpr( maybeMoveBuild<Expression>( else_when ) );
    336 
    337         return node;
    338 } // build_waitfor_timeout
    339 
    340 Statement * build_with( ExpressionNode * exprs, StatementNode * stmt ) {
    341         list< Expression * > e;
     362ast::WaitUntilStmt::ClauseNode * build_waituntil_clause( const CodeLocation & loc, ExpressionNode * when, ExpressionNode * targetExpr, StatementNode * stmt ) {
     363    ast::WhenClause * clause = new ast::WhenClause( loc );
     364    clause->when_cond = notZeroExpr( maybeMoveBuild( when ) );
     365    clause->stmt = maybeMoveBuild( stmt );
     366    clause->target = maybeMoveBuild( targetExpr );
     367    return new ast::WaitUntilStmt::ClauseNode( clause );
     368}
     369ast::WaitUntilStmt::ClauseNode * build_waituntil_else( const CodeLocation & loc, ExpressionNode * when, StatementNode * stmt ) {
     370    ast::WhenClause * clause = new ast::WhenClause( loc );
     371    clause->when_cond = notZeroExpr( maybeMoveBuild( when ) );
     372    clause->stmt = maybeMoveBuild( stmt );
     373    return new ast::WaitUntilStmt::ClauseNode( ast::WaitUntilStmt::ClauseNode::Op::ELSE, clause );
     374}
     375ast::WaitUntilStmt::ClauseNode * build_waituntil_timeout( const CodeLocation & loc, ExpressionNode * when, ExpressionNode * timeout, StatementNode * stmt ) {
     376    ast::WhenClause * clause = new ast::WhenClause( loc );
     377    clause->when_cond = notZeroExpr( maybeMoveBuild( when ) );
     378    clause->stmt = maybeMoveBuild( stmt );
     379    clause->target = maybeMoveBuild( timeout );
     380    return new ast::WaitUntilStmt::ClauseNode( ast::WaitUntilStmt::ClauseNode::Op::TIMEOUT, clause );
     381}
     382
     383ast::WaitUntilStmt * build_waituntil_stmt( const CodeLocation & loc, ast::WaitUntilStmt::ClauseNode * root ) {
     384    ast::WaitUntilStmt * retStmt = new ast::WaitUntilStmt( loc );
     385    retStmt->predicateTree = root;
     386   
     387    // iterative tree traversal
     388    std::vector<ast::WaitUntilStmt::ClauseNode *> nodeStack; // stack needed for iterative traversal
     389    ast::WaitUntilStmt::ClauseNode * currNode = nullptr;
     390    ast::WaitUntilStmt::ClauseNode * lastInternalNode = nullptr;
     391    ast::WaitUntilStmt::ClauseNode * cleanup = nullptr; // used to cleanup removed else/timeout
     392    nodeStack.push_back(root);
     393
     394    do {
     395        currNode = nodeStack.back();
     396        nodeStack.pop_back(); // remove node since it will be processed
     397
     398        switch (currNode->op) {
     399            case ast::WaitUntilStmt::ClauseNode::LEAF:
     400                retStmt->clauses.push_back(currNode->leaf);
     401                break;
     402            case ast::WaitUntilStmt::ClauseNode::ELSE:
     403                retStmt->else_stmt = currNode->leaf->stmt
     404                    ? ast::deepCopy( currNode->leaf->stmt )
     405                    : nullptr;
     406               
     407                retStmt->else_cond = currNode->leaf->when_cond
     408                    ? ast::deepCopy( currNode->leaf->when_cond )
     409                    : nullptr;
     410
     411                delete currNode->leaf;
     412                break;
     413            case ast::WaitUntilStmt::ClauseNode::TIMEOUT:
     414                retStmt->timeout_time = currNode->leaf->target
     415                    ? ast::deepCopy( currNode->leaf->target )
     416                    : nullptr;
     417                retStmt->timeout_stmt = currNode->leaf->stmt
     418                    ? ast::deepCopy( currNode->leaf->stmt )
     419                    : nullptr;
     420                retStmt->timeout_cond = currNode->leaf->when_cond
     421                    ? ast::deepCopy( currNode->leaf->when_cond )
     422                    : nullptr;
     423
     424                delete currNode->leaf;
     425                break;
     426            default:
     427                nodeStack.push_back( currNode->right ); // process right after left
     428                nodeStack.push_back( currNode->left );
     429
     430                // Cut else/timeout out of the tree
     431                if ( currNode->op == ast::WaitUntilStmt::ClauseNode::LEFT_OR ) {
     432                    if ( lastInternalNode )
     433                        lastInternalNode->right = currNode->left;
     434                    else    // if not set then root is LEFT_OR
     435                        retStmt->predicateTree = currNode->left;
     436   
     437                    currNode->left = nullptr;
     438                    cleanup = currNode;
     439                }
     440               
     441                lastInternalNode = currNode;
     442                break;
     443        }
     444    } while ( !nodeStack.empty() );
     445
     446    if ( cleanup ) delete cleanup;
     447
     448    return retStmt;
     449}
     450
     451ast::Stmt * build_with( const CodeLocation & location, ExpressionNode * exprs, StatementNode * stmt ) {
     452        std::vector<ast::ptr<ast::Expr>> e;
    342453        buildMoveList( exprs, e );
    343         Statement * s = maybeMoveBuild<Statement>( stmt );
    344         return new DeclStmt( new WithStmt( e, s ) );
     454        ast::Stmt * s = maybeMoveBuild( stmt );
     455        return new ast::DeclStmt( location, new ast::WithStmt( location, std::move( e ), s ) );
    345456} // build_with
    346457
    347 Statement * build_compound( StatementNode * first ) {
    348         CompoundStmt * cs = new CompoundStmt();
    349         buildMoveList( first, cs->get_kids() );
     458ast::Stmt * build_compound( const CodeLocation & location, StatementNode * first ) {
     459        auto cs = new ast::CompoundStmt( location );
     460        buildMoveList( first, cs->kids );
    350461        return cs;
    351462} // build_compound
     
    355466// statement and wrap it into a compound statement to insert additional code. Hence, all control structures have a
    356467// conical form for code generation.
    357 StatementNode * maybe_build_compound( StatementNode * first ) {
     468StatementNode * maybe_build_compound( const CodeLocation & location, StatementNode * first ) {
    358469        // Optimization: if the control-structure statement is a compound statement, do not wrap it.
    359470        // e.g., if (...) {...} do not wrap the existing compound statement.
    360         if ( ! dynamic_cast<CompoundStmt *>( first->stmt.get() ) ) { // unique_ptr
    361                 CompoundStmt * cs = new CompoundStmt();
    362                 buildMoveList( first, cs->get_kids() );
    363                 return new StatementNode( cs );
     471        if ( !dynamic_cast<ast::CompoundStmt *>( first->stmt.get() ) ) { // unique_ptr
     472                return new StatementNode( build_compound( location, first ) );
    364473        } // if
    365474        return first;
     
    367476
    368477// Question
    369 Statement * build_asm( bool voltile, Expression * instruction, ExpressionNode * output, ExpressionNode * input, ExpressionNode * clobber, LabelNode * gotolabels ) {
    370         list< Expression * > out, in;
    371         list< ConstantExpr * > clob;
     478ast::Stmt * build_asm( const CodeLocation & location, bool is_volatile, ExpressionNode * instruction, ExpressionNode * output, ExpressionNode * input, ExpressionNode * clobber, LabelNode * gotolabels ) {
     479        std::vector<ast::ptr<ast::Expr>> out, in;
     480        std::vector<ast::ptr<ast::ConstantExpr>> clob;
    372481
    373482        buildMoveList( output, out );
    374483        buildMoveList( input, in );
    375484        buildMoveList( clobber, clob );
    376         return new AsmStmt( voltile, instruction, out, in, clob, gotolabels ? gotolabels->labels : noLabels );
     485        return new ast::AsmStmt( location,
     486                is_volatile,
     487                maybeMoveBuild( instruction ),
     488                std::move( out ),
     489                std::move( in ),
     490                std::move( clob ),
     491                gotolabels ? gotolabels->labels : std::vector<ast::Label>()
     492        );
    377493} // build_asm
    378494
    379 Statement * build_directive( string * directive ) {
    380         return new DirectiveStmt( *directive );
     495ast::Stmt * build_directive( const CodeLocation & location, string * directive ) {
     496        auto stmt = new ast::DirectiveStmt( location, *directive );
     497        delete directive;
     498        return stmt;
    381499} // build_directive
    382500
    383 Statement * build_mutex( ExpressionNode * exprs, StatementNode * stmt ) {
    384         list< Expression * > expList;
     501ast::Stmt * build_mutex( const CodeLocation & location, ExpressionNode * exprs, StatementNode * stmt ) {
     502        std::vector<ast::ptr<ast::Expr>> expList;
    385503        buildMoveList( exprs, expList );
    386         Statement * body = maybeMoveBuild<Statement>( stmt );
    387         return new MutexStmt( body, expList );
     504        ast::Stmt * body = maybeMoveBuild( stmt );
     505        return new ast::MutexStmt( location, body, std::move( expList ) );
    388506} // build_mutex
    389507
Note: See TracChangeset for help on using the changeset viewer.