Skip to content

Commit 942d7d9

Browse files
committed
Fix srcref handling with new evaluate
Closes #49
1 parent 5ba5881 commit 942d7d9

File tree

4 files changed

+111
-6
lines changed

4 files changed

+111
-6
lines changed

R/parser.R

+1-1
Original file line numberDiff line numberDiff line change
@@ -324,7 +324,7 @@ block_states <- function(block, counter, continue, last, return, info) {
324324
curr_refs <<- nested_refs
325325
} else {
326326
node_poke_cdr(prev_node, nested_node)
327-
node_poke_cdr(prev_refs, nested_refs)
327+
prev_refs %&&% node_poke_cdr(prev_refs, nested_refs)
328328
}
329329

330330
node <<- nested_node

tests/testthat/_snaps/parser-block.md

+110
Original file line numberDiff line numberDiff line change
@@ -297,6 +297,51 @@
297297
invisible(exhausted())
298298
}
299299

300+
# `{` blocks - nested
301+
302+
Code
303+
generator_body(function() {
304+
"before1"
305+
"before2"
306+
{
307+
"before-inner"
308+
yield(1L)
309+
"after-inner"
310+
}
311+
"after1"
312+
"after2"
313+
})
314+
Output
315+
{
316+
if (exhausted) {
317+
return(invisible(exhausted()))
318+
}
319+
repeat switch(state[[1L]], `1` = {
320+
user({
321+
"before1"
322+
"before2"
323+
"before-inner"
324+
1L
325+
})
326+
state[[1L]] <- 2L
327+
suspend()
328+
return(last_value())
329+
}, `2` = {
330+
.last_value <- if (missing(arg)) NULL else arg
331+
state[[1L]] <- 3L
332+
}, `3` = {
333+
user({
334+
"after-inner"
335+
"after1"
336+
"after2"
337+
})
338+
exhausted <- TRUE
339+
return(last_value())
340+
})
341+
exhausted <- TRUE
342+
invisible(exhausted())
343+
}
344+
300345
# `{` blocks - nested and no past before pause
301346

302347
Code
@@ -377,6 +422,71 @@
377422
invisible(exhausted())
378423
}
379424

425+
# `{` blocks - complex nesting
426+
427+
Code
428+
generator_body(function() {
429+
"before"
430+
{
431+
"before-inner"
432+
yield(1L)
433+
{
434+
yield(2L)
435+
yield(3L)
436+
}
437+
"after-inner"
438+
}
439+
"after"
440+
})
441+
Output
442+
{
443+
if (exhausted) {
444+
return(invisible(exhausted()))
445+
}
446+
repeat switch(state[[1L]], `1` = {
447+
user({
448+
"before"
449+
"before-inner"
450+
1L
451+
})
452+
state[[1L]] <- 2L
453+
suspend()
454+
return(last_value())
455+
}, `2` = {
456+
.last_value <- if (missing(arg)) NULL else arg
457+
state[[1L]] <- 3L
458+
}, `3` = {
459+
user({
460+
2L
461+
})
462+
state[[1L]] <- 4L
463+
suspend()
464+
return(last_value())
465+
}, `4` = {
466+
.last_value <- if (missing(arg)) NULL else arg
467+
state[[1L]] <- 5L
468+
}, `5` = {
469+
user({
470+
3L
471+
})
472+
state[[1L]] <- 6L
473+
suspend()
474+
return(last_value())
475+
}, `6` = {
476+
.last_value <- if (missing(arg)) NULL else arg
477+
state[[1L]] <- 7L
478+
}, `7` = {
479+
user({
480+
"after-inner"
481+
"after"
482+
})
483+
exhausted <- TRUE
484+
return(last_value())
485+
})
486+
exhausted <- TRUE
487+
invisible(exhausted())
488+
}
489+
380490
# `{` blocks - simple nesting with various continuation states
381491

382492
Code

tests/testthat/test-parser-block.R

-4
Original file line numberDiff line numberDiff line change
@@ -60,8 +60,6 @@ test_that("`{` blocks - no return value", {
6060
})
6161

6262
test_that("`{` blocks - nested", {
63-
skip()
64-
6563
expect_snapshot0(generator_body(function() {
6664
"before1"
6765
"before2"
@@ -99,8 +97,6 @@ test_that("`{` blocks - nested and goto after pause", {
9997
})
10098

10199
test_that("`{` blocks - complex nesting", {
102-
skip()
103-
104100
expect_snapshot0(generator_body(function() {
105101
"before"
106102
{

tests/testthat/test-parser-if.R

-1
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,6 @@ test_that("`else` blocks - one pause", {
2727
})
2828

2929
test_that("`if` blocks - inner block", {
30-
skip()
3130
expect_snapshot0(generator_body(function() {
3231
"before"
3332
if (TRUE) {

0 commit comments

Comments
 (0)