Skip to content

Commit

Permalink
Recover from closed sink/closed connection
Browse files Browse the repository at this point in the history
I'm not 100% convinced that silently restoring the sink + connection is the correct approach, but it doesn't happen very often and we aren't going to lose much output if we immediately re-open the sink + connection.

Fixes #104 (at least as much as it can be fixed)
  • Loading branch information
hadley committed Jun 23, 2024
1 parent 7c6bad8 commit 360eed6
Show file tree
Hide file tree
Showing 3 changed files with 106 additions and 20 deletions.
64 changes: 44 additions & 20 deletions R/watcher.R
Original file line number Diff line number Diff line change
Expand Up @@ -30,19 +30,7 @@ watchout <- function(handler = new_output_handler(),
devn <- length(dev.list())
dev <- dev.cur()

con <- file("", "w+b")
defer(frame = frame, {
if (!test_con(con, isOpen)) {
con_error('The connection has been closed')
}
sink()
close(con)
})
sink(con, split = debug)

# try() defaults to using stderr() so we need to explicitly override(#88)
old <- options(try.outFile = con)
defer(options(old), frame = frame)
sink_con <- local_persistent_sink_connection(debug, frame)

capture_plot <- function(incomplete = FALSE) {
# only record plots for our graphics device
Expand Down Expand Up @@ -71,7 +59,7 @@ watchout <- function(handler = new_output_handler(),
}

capture_output <- function() {
out <- read_con(con)
out <- sink_con()
if (!is.null(out)) {
push(out)
handler$text(out)
Expand Down Expand Up @@ -100,6 +88,36 @@ watchout <- function(handler = new_output_handler(),
)
}

# Persistent way to capture output ---------------------------------------------

local_persistent_sink_connection <- function(debug = FALSE,
frame = parent.frame()) {
con <- file("", "w+b")
defer(if (isValid(con)) close(con), frame)

# try() defaults to using stderr() so we need to explicitly override(#88)
old <- options(try.outFile = con)
defer(options(old), frame)

sink(con, split = debug)
sinkn <- sink.number()
defer(if (sink.number() >= sinkn) sink(), frame)

function() {
if (!isValid(con)) {
con <<- file("", "w+b")
options(try.outFile = con)
}

if (sink.number() < sinkn) {
sink(con)
sinkn <<- sink.number()
}

read_con(con)
}
}

read_con <- function(con, buffer = 32 * 1024) {
bytes <- raw()
repeat {
Expand All @@ -114,10 +132,16 @@ read_con <- function(con, buffer = 32 * 1024) {
}
}

test_con = function(con, test) {
tryCatch(test(con), error = function(e) con_error(e$message))
# isOpen doesn't work for two reasons:
# 1. It errors if con has been closed, rather than returning FALSE
# 2. If returns TRUE if con has been closed and a new connection opened
#
# So instead we retrieve the connection from its number and compare to the
# original connection. This works because connections have an undocumented
# external pointer.
isValid <- function(con) {
tryCatch(
identical(getConnection(con), con),
error = function(cnd) FALSE
)
}

con_error = function(x) stop(
x, '... Please make sure not to call closeAllConnections().', call. = FALSE
)
10 changes: 10 additions & 0 deletions tests/testthat/_snaps/watcher.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
# evaluate recovers from closed sink

Code
ev <- evaluate("sink()\n1")

# evaluate recovers from closed connection

Code
ev <- evaluate("closeAllConnections()\n1")

52 changes: 52 additions & 0 deletions tests/testthat/test-watcher.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,3 +7,55 @@ test_that("capture messages in try() (#88)", {
expect_output_types(ev, c("source", "text"))
expect_match(ev[[2]], "Obscure error")
})

test_that("code can use own sink", {
f <- function() {
con <- file("")
defer(close(con))

sink(con)
cat("One")
sink()
}
ev <- evaluate("f()\n1")
expect_output_types(ev, c("source", "source", "text"))
})

test_that("evaluate preserves externally created sinks", {
sink(withr::local_tempfile())
defer(sink())
n <- sink.number()

ev <- evaluate("1")
expect_output_types(ev, c("source", "text"))

expect_equal(sink.number(), n)
})

test_that("evaluate recovers from closed sink", {
expect_snapshot(ev <- evaluate("sink()\n1"))
expect_output_types(ev, c("source", "source", "text"))
})

test_that("unbalanced sink doesn't break evaluate", {
path <- withr::local_tempfile()
ev <- evaluate("sink(path)\n1\n1")
expect_output_types(ev, c("source", "source", "source"))
})

test_that("evaluate recovers from closed connection", {
expect_snapshot(ev <- evaluate("closeAllConnections()\n1"))
expect_output_types(ev, c("source", "source", "text"))
})

test_that("isValid() works correctly", {
con1 <- file("")
expect_true(isValid(con1))
close(con1)
expect_false(isValid(con1))

con2 <- file("")
expect_false(isValid(con1)) # isOpen would return TRUE here
expect_true(isValid(con2))
close(con2)
})

0 comments on commit 360eed6

Please sign in to comment.