Skip to content

Commit

Permalink
Fix srcref handling with new evaluate
Browse files Browse the repository at this point in the history
Closes #49
  • Loading branch information
lionel- committed Oct 30, 2024
1 parent 5ba5881 commit 942d7d9
Show file tree
Hide file tree
Showing 4 changed files with 111 additions and 6 deletions.
2 changes: 1 addition & 1 deletion R/parser.R
Original file line number Diff line number Diff line change
Expand Up @@ -324,7 +324,7 @@ block_states <- function(block, counter, continue, last, return, info) {
curr_refs <<- nested_refs
} else {
node_poke_cdr(prev_node, nested_node)
node_poke_cdr(prev_refs, nested_refs)
prev_refs %&&% node_poke_cdr(prev_refs, nested_refs)
}

node <<- nested_node
Expand Down
110 changes: 110 additions & 0 deletions tests/testthat/_snaps/parser-block.md
Original file line number Diff line number Diff line change
Expand Up @@ -297,6 +297,51 @@
invisible(exhausted())
}

# `{` blocks - nested

Code
generator_body(function() {
"before1"
"before2"
{
"before-inner"
yield(1L)
"after-inner"
}
"after1"
"after2"
})
Output
{
if (exhausted) {
return(invisible(exhausted()))
}
repeat switch(state[[1L]], `1` = {
user({
"before1"
"before2"
"before-inner"
1L
})
state[[1L]] <- 2L
suspend()
return(last_value())
}, `2` = {
.last_value <- if (missing(arg)) NULL else arg
state[[1L]] <- 3L
}, `3` = {
user({
"after-inner"
"after1"
"after2"
})
exhausted <- TRUE
return(last_value())
})
exhausted <- TRUE
invisible(exhausted())
}

# `{` blocks - nested and no past before pause

Code
Expand Down Expand Up @@ -377,6 +422,71 @@
invisible(exhausted())
}

# `{` blocks - complex nesting

Code
generator_body(function() {
"before"
{
"before-inner"
yield(1L)
{
yield(2L)
yield(3L)
}
"after-inner"
}
"after"
})
Output
{
if (exhausted) {
return(invisible(exhausted()))
}
repeat switch(state[[1L]], `1` = {
user({
"before"
"before-inner"
1L
})
state[[1L]] <- 2L
suspend()
return(last_value())
}, `2` = {
.last_value <- if (missing(arg)) NULL else arg
state[[1L]] <- 3L
}, `3` = {
user({
2L
})
state[[1L]] <- 4L
suspend()
return(last_value())
}, `4` = {
.last_value <- if (missing(arg)) NULL else arg
state[[1L]] <- 5L
}, `5` = {
user({
3L
})
state[[1L]] <- 6L
suspend()
return(last_value())
}, `6` = {
.last_value <- if (missing(arg)) NULL else arg
state[[1L]] <- 7L
}, `7` = {
user({
"after-inner"
"after"
})
exhausted <- TRUE
return(last_value())
})
exhausted <- TRUE
invisible(exhausted())
}

# `{` blocks - simple nesting with various continuation states

Code
Expand Down
4 changes: 0 additions & 4 deletions tests/testthat/test-parser-block.R
Original file line number Diff line number Diff line change
Expand Up @@ -60,8 +60,6 @@ test_that("`{` blocks - no return value", {
})

test_that("`{` blocks - nested", {
skip()

expect_snapshot0(generator_body(function() {
"before1"
"before2"
Expand Down Expand Up @@ -99,8 +97,6 @@ test_that("`{` blocks - nested and goto after pause", {
})

test_that("`{` blocks - complex nesting", {
skip()

expect_snapshot0(generator_body(function() {
"before"
{
Expand Down
1 change: 0 additions & 1 deletion tests/testthat/test-parser-if.R
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,6 @@ test_that("`else` blocks - one pause", {
})

test_that("`if` blocks - inner block", {
skip()
expect_snapshot0(generator_body(function() {
"before"
if (TRUE) {
Expand Down

0 comments on commit 942d7d9

Please sign in to comment.