Skip to content

Commit

Permalink
Replace usage of the deprecated with_mock() with with_mocked_bindings()
Browse files Browse the repository at this point in the history
  • Loading branch information
jarodmeng committed Jan 12, 2025
1 parent 26713bc commit d5aaba6
Show file tree
Hide file tree
Showing 20 changed files with 584 additions and 564 deletions.
3 changes: 3 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,8 @@
# RPresto 1.4.7.9000

* Replaced deprecated `with_mock()` usage in unit testing with
`with_mocked_bindings()`. (#292)

# RPresto 1.4.7

* Fixed Trino support quirks (#254) and expanded unit tests to Trino
Expand Down
19 changes: 16 additions & 3 deletions R/PrestoQuery.R
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,19 @@ wait <- function() {
return(content)
}

# Wrapper of httr::POST() and httr::GET() so that we can mock the POST
# and GET responses within RPresto in unit tests
# See https://testthat.r-lib.org/reference/local_mocked_bindings.html#namespaced-calls
httr_POST <- function(...) {
httr::POST(...)
}
httr_GET <- function(...) {
httr::GET(...)
}
httr_handle_reset <- function(...) {
httr::handle_reset(...)
}

#' Class to encapsulate a Presto query
#'
#' This reference class (so that the object can be passed by reference and
Expand Down Expand Up @@ -207,7 +220,7 @@ PrestoQuery <- setRefClass("PrestoQuery",
headers <- .request_headers(.conn)
while (status == 503L || (retries > 0 && status >= 400L)) {
wait()
post.response <- httr::POST(
post.response <- httr_POST(
url,
body = enc2utf8(.statement),
config = headers
Expand All @@ -224,7 +237,7 @@ PrestoQuery <- setRefClass("PrestoQuery",
headers <- .request_headers(.conn)
get.response <- tryCatch(
{
response <- httr::GET(.next.uri, config = headers)
response <- httr_GET(.next.uri, config = headers)
if (httr::status_code(response) >= 400L) {
# stop_for_status also fails for 300 <= status < 400
# so we need the if condition
Expand All @@ -244,7 +257,7 @@ PrestoQuery <- setRefClass("PrestoQuery",
'", retrying [', 4 - num.retry, "/3]\n"
)
wait()
httr::handle_reset(.next.uri)
httr_handle_reset(.next.uri)
return(get(num.retry - 1))
}
)
Expand Down
6 changes: 5 additions & 1 deletion R/dbClearResult.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,10 @@
#' @include PrestoResult.R
NULL

httr_DELETE <- function(...) {
httr::DELETE(...)
}

#' @rdname PrestoResult-class
#' @importMethodsFrom DBI dbClearResult
#' @export
Expand All @@ -32,7 +36,7 @@ setMethod(
res@connection@host, ":", res@connection@port,
"/v1/query/", res@query$id()
)
delete.result <- httr::DELETE(delete.uri, config = headers)
delete.result <- httr_DELETE(delete.uri, config = headers)
s <- httr::status_code(delete.result)
if (s >= 200 && s < 300) {
res@query$state("__KILLED")
Expand Down
44 changes: 22 additions & 22 deletions tests/testthat/helper-mock_connection.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,16 +5,7 @@
# LICENSE file in the root directory of this source tree.

setup_mock_connection <- function() {
with_mock(
`httr::POST` = mock_httr_replies(
mock_httr_response(
"http://localhost:8000/v1/statement",
status_code = 200,
state = "FINISHED",
request_body = "SELECT current_timezone() AS tz",
data = data.frame(tz = Sys.timezone(), stringsAsFactors = FALSE)
)
),
with_mocked_bindings(
{
mock.conn <- dbConnect(
RPresto::Presto(),
Expand All @@ -27,24 +18,24 @@ setup_mock_connection <- function() {
user = Sys.getenv("USER")
)
return(mock.conn)
}
)
}

setup_mock_dplyr_connection <- function() {
if (!requireNamespace("dplyr", quietly = TRUE)) {
skip("Skipping dplyr tests because we can't load dplyr")
}
with_mock(
`httr::POST` = mock_httr_replies(
},
httr_POST = mock_httr_replies(
mock_httr_response(
"http://localhost:8000/v1/statement",
status_code = 200,
state = "FINISHED",
request_body = "SELECT current_timezone() AS tz",
data = data.frame(tz = Sys.timezone(), stringsAsFactors = FALSE)
)
),
)
)
}

setup_mock_dplyr_connection <- function() {
if (!requireNamespace("dplyr", quietly = TRUE)) {
skip("Skipping dplyr tests because we can't load dplyr")
}
with_mocked_bindings(
{
db <- src_presto(
schema = "test",
Expand All @@ -58,6 +49,15 @@ setup_mock_dplyr_connection <- function() {
)

return(list(db = db, iris_table_name = "iris_table"))
}
},
httr_POST = mock_httr_replies(
mock_httr_response(
"http://localhost:8000/v1/statement",
status_code = 200,
state = "FINISHED",
request_body = "SELECT current_timezone() AS tz",
data = data.frame(tz = Sys.timezone(), stringsAsFactors = FALSE)
)
)
)
}
24 changes: 12 additions & 12 deletions tests/testthat/test-PrestoQuery.R
Original file line number Diff line number Diff line change
Expand Up @@ -25,14 +25,7 @@ test_that("PrestoQuery methods work correctly", {
),
class = "response"
)
with_mock(
`httr::POST` = mock_httr_replies(
list(
url = "http://localhost:8000/v1/statement",
response = post.response,
request_body = "SELECT 1"
)
),
with_mocked_bindings(
{
query <- PrestoQuery(conn, "SELECT 1")
res <- query$execute()
Expand All @@ -49,7 +42,14 @@ test_that("PrestoQuery methods work correctly", {
expect_false(query$postDataFetched(FALSE))
query$state("__TEST")
expect_equal(query$state(), "__TEST")
}
},
httr_POST = mock_httr_replies(
list(
url = "http://localhost:8000/v1/statement",
response = post.response,
request_body = "SELECT 1"
)
)
)
})

Expand All @@ -62,8 +62,7 @@ test_that("PrestoQuery methods work correctly with POST data", {
data = data.frame(x = 1),
request_body = "SELECT 1"
)
with_mock(
`httr::POST` = mock_httr_replies(mock_response),
with_mocked_bindings(
{
query <- PrestoQuery(conn, "SELECT 1")
res <- query$execute()
Expand All @@ -78,6 +77,7 @@ test_that("PrestoQuery methods work correctly with POST data", {
expect_true(query$postDataFetched(TRUE))
expect_true(query$postDataFetched())
expect_true(query$hasCompleted())
}
},
httr_POST = mock_httr_replies(mock_response)
)
})
30 changes: 15 additions & 15 deletions tests/testthat/test-dbClearResult.R
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,19 @@ test_that("dbClearResult works with live database", {

test_that("dbClearResult works with mock", {
conn <- setup_mock_connection()
with_mock(
`httr::POST` = mock_httr_replies(
with_mocked_bindings(
{
result <- dbSendQuery(conn, "SELECT 1")
expect_true(dbClearResult(result), label = "regular query")
expect_true(dbClearResult(result), label = "idempotency")

result <- dbSendQuery(conn, "SELECT 2")
expect_false(dbClearResult(result), label = "DELETE fails")

result <- dbSendQuery(conn, "SELECT 3")
expect_true(dbClearResult(result), label = "complete query")
},
httr_POST = mock_httr_replies(
mock_httr_response(
url = "http://localhost:8000/v1/statement",
status_code = 200,
Expand All @@ -40,7 +51,7 @@ test_that("dbClearResult works with mock", {
query_id = "query_3"
)
),
`httr::DELETE` = mock_httr_replies(
httr_DELETE = mock_httr_replies(
mock_httr_response(
url = "http://localhost:8000/v1/query/query_1",
status_code = 200,
Expand All @@ -51,17 +62,6 @@ test_that("dbClearResult works with mock", {
status_code = 500,
state = ""
)
),
{
result <- dbSendQuery(conn, "SELECT 1")
expect_true(dbClearResult(result), label = "regular query")
expect_true(dbClearResult(result), label = "idempotency")

result <- dbSendQuery(conn, "SELECT 2")
expect_false(dbClearResult(result), label = "DELETE fails")

result <- dbSendQuery(conn, "SELECT 3")
expect_true(dbClearResult(result), label = "complete query")
}
)
)
})
22 changes: 11 additions & 11 deletions tests/testthat/test-dbConnect.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,16 +7,7 @@
context("dbConnect")

test_that("dbConnect constructs PrestoConnection correctly", {
with_mock(
`httr::POST` = mock_httr_replies(
mock_httr_response(
"http://localhost:8000/v1/statement",
status_code = 200,
state = "FINISHED",
request_body = "SELECT current_timezone() AS tz",
data = data.frame(tz = Sys.timezone(), stringsAsFactors = FALSE)
)
),
with_mocked_bindings(
{
expect_error(dbConnect(RPresto::Presto()), label = "not enough arguments")

Expand Down Expand Up @@ -141,6 +132,15 @@ test_that("dbConnect constructs PrestoConnection correctly", {
),
"should be one of"
)
}
},
httr_POST = mock_httr_replies(
mock_httr_response(
"http://localhost:8000/v1/statement",
status_code = 200,
state = "FINISHED",
request_body = "SELECT current_timezone() AS tz",
data = data.frame(tz = Sys.timezone(), stringsAsFactors = FALSE)
)
)
)
})
Loading

0 comments on commit d5aaba6

Please sign in to comment.