Skip to content

Commit

Permalink
Ignore return values of generators (#57)
Browse files Browse the repository at this point in the history
  • Loading branch information
lionel- authored Nov 5, 2024
1 parent 1235934 commit 9dc9bc8
Show file tree
Hide file tree
Showing 10 changed files with 154 additions and 145 deletions.
4 changes: 4 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,10 @@
are now cleaned up when terminated early, either because of an
error or because of a `break` (#52).

* Implicit and explicit return values of generators are no longer
yielded. This is consistent with Javascript and Python and simplifies
certain idioms (#51).

* Generators and async functions assigned in namespaces no
longer produce R CMD check notes about visible bindings (#40).

Expand Down
12 changes: 8 additions & 4 deletions R/generator.R
Original file line number Diff line number Diff line change
Expand Up @@ -29,16 +29,18 @@
#' @export
#' @examples
#' # A generator statement creates a generator factory. The
#' # following generator yields two times and then returns `"c"`:
#' # following generator yields three times and then returns `"d"`.
#' # Only the yielded values are visible to the callers.
#' generate_abc <- generator(function() {
#' yield("a")
#' yield("b")
#' "c"
#' yield("c")
#' "d"
#' })
#'
#' # Or equivalently:
#' # Equivalently:
#' generate_abc <- generator(function() {
#' for (x in letters[1:3]) {
#' for (x in c("a", "b", "c")) {
#' yield(x)
#' }
#' })
Expand Down Expand Up @@ -103,13 +105,15 @@ generator <- function(fn) {
assert_lambda(substitute(fn))
generator0(fn)
}

#' @rdname generator
#' @param expr A yielding expression.
#' @export
gen <- function(expr) {
fn <- new_function(NULL, substitute(expr), caller_env())
generator0(fn)()
}

generator0 <- function(fn, type = "generator") {
state_machine <- NULL
fmls <- formals(fn)
Expand Down
6 changes: 3 additions & 3 deletions R/parser.R
Original file line number Diff line number Diff line change
Expand Up @@ -568,7 +568,7 @@ strip_explicit_return <- function(expr) {
}
return_call <- function(info) {
if (is_null(info$async_ops)) {
quote(return(last_value()))
quote(return(exhausted()))
} else {
quote(return(as_promise(last_value())))
}
Expand Down Expand Up @@ -996,8 +996,8 @@ try_catch_states <- function(preamble,
depth <- machine_depth(counter)
try_catch_depth <- depth + 1L

# Handlers can't be evaluated until runtime. We store them in a list
# dynamically.
# Handlers can't be evaluated until runtime. We store their expressions in a
# list. They are evaluated when the user enters the `tryCatch()` state.
handler_body <- expr({
!!!preamble %&&% list(user_call(preamble))
handlers[[!!try_catch_depth]] <- user(base::list(!!!handlers_exprs))
Expand Down
10 changes: 6 additions & 4 deletions man/generator.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 2 additions & 2 deletions tests/testthat/_snaps/generator.md
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@
state[[1L]] <- 3L
}, `3` = {
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -64,7 +64,7 @@
state[[1L]] <- 3L
}, `3` = {
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down
28 changes: 14 additions & 14 deletions tests/testthat/_snaps/parser-block.md
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@
state[[1L]] <- 3L
}, `3` = {
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -60,7 +60,7 @@
"after2"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -93,7 +93,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -141,7 +141,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -187,7 +187,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -222,7 +222,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -251,7 +251,7 @@
state[[1L]] <- 3L
}, `3` = {
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -291,7 +291,7 @@
state[[1L]] <- 5L
}, `5` = {
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -336,7 +336,7 @@
"after2"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -377,7 +377,7 @@
"after2"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -416,7 +416,7 @@
"after2"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -481,7 +481,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -520,7 +520,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -559,7 +559,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down
34 changes: 17 additions & 17 deletions tests/testthat/_snaps/parser-if.md
Original file line number Diff line number Diff line change
Expand Up @@ -83,7 +83,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -174,7 +174,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -271,7 +271,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -347,7 +347,7 @@
"if-after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
}, `4` = {
break
})
Expand All @@ -367,7 +367,7 @@
"foo"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
}, `2` = {
break
})
Expand Down Expand Up @@ -441,7 +441,7 @@
state[[3L]] <- 3L
}, `3` = {
exhausted <- TRUE
return(last_value())
return(exhausted())
}, `4` = {
break
})
Expand Down Expand Up @@ -476,7 +476,7 @@
"foo"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
}, `2` = {
break
})
Expand Down Expand Up @@ -589,7 +589,7 @@
"if-2-after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
}, `4` = {
break
})
Expand Down Expand Up @@ -624,7 +624,7 @@
FALSE
})
exhausted <- TRUE
return(last_value())
return(exhausted())
}, `2` = {
break
})
Expand Down Expand Up @@ -694,7 +694,7 @@
"if-after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
}, `4` = {
break
})
Expand Down Expand Up @@ -725,7 +725,7 @@
"else-after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
}, `4` = {
break
})
Expand Down Expand Up @@ -844,7 +844,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -932,7 +932,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -1026,7 +1026,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -1120,7 +1120,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -1209,7 +1209,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down Expand Up @@ -1430,7 +1430,7 @@
"after"
})
exhausted <- TRUE
return(last_value())
return(exhausted())
})
exhausted <- TRUE
invisible(exhausted())
Expand Down
Loading

0 comments on commit 9dc9bc8

Please sign in to comment.