Skip to content

Commit

Permalink
Centralize some of the common test definitions.
Browse files Browse the repository at this point in the history
- Added some tests for correct deregistration.
- Added explicit tests for non-recursive listFiles.
  • Loading branch information
LTLA committed Nov 25, 2024
1 parent e223334 commit 1460d5f
Show file tree
Hide file tree
Showing 6 changed files with 72 additions and 52 deletions.
17 changes: 17 additions & 0 deletions tests/testthat/setup.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
basic_config <- function() {
# Starting up an example SewerRat service:
info <- SewerRat::startSewerRat()

# Mocking up a directory of stuff to query.
mydir <- tempfile()
dir.create(mydir)
write(file=file.path(mydir, "metadata.json"), '{ "first": "Aaron", "last": "Lun" }')

dir.create(file.path(mydir, "diet"))
write(file=file.path(mydir, "diet", "metadata.json"), '{ "meal": "lunch", "ingredients": "water" }')

# Registering it:
SewerRat::register(mydir, "metadata.json", url=info$url)

list(info=info, mydir=mydir)
}
21 changes: 21 additions & 0 deletions tests/testthat/test-listFiles.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,21 @@
# library(testthat); library(SewerRat); source("setup.R"); source("test-listFiles.R")

config <- basic_config()
info <- config$info
mydir <- config$mydir

test_that("listFiles works as expected", {
all <- listFiles(mydir, info$url)
expect_identical(sort(all), c("diet/metadata.json", "metadata.json"))

all <- listFiles(mydir, info$url, recursive=FALSE)
expect_identical(sort(all), c("diet/", "metadata.json"))

all <- listFiles(paste0(mydir, "/diet"), info$url)
expect_identical(sort(all), "metadata.json")

all <- listFiles(mydir, info$url, forceRemote=TRUE)
expect_identical(sort(all), c("diet/metadata.json", "metadata.json"))
})

deregister(mydir, url=info$url)
Original file line number Diff line number Diff line change
@@ -1,29 +1,8 @@
# Test the listing function.
# library(testthat); library(SewerRat); source("test-list.R")
# library(testthat); library(SewerRat); source("setup.R"); source("test-listRegisteredDirectories.R")

# Starting up an example SewerRat service:
info <- startSewerRat()

# Mocking up a directory of stuff to query.
mydir <- tempfile()
dir.create(mydir)
write(file=file.path(mydir, "metadata.json"), '{ "first": "Aaron", "last": "Lun" }')
dir.create(file.path(mydir, "diet"))
write(file=file.path(mydir, "diet", "metadata.json"),
'{ "meal": "lunch", "ingredients": "water" }')

# Registering it:
register(mydir, "metadata.json", url=info$url)

test_that("listing works as expected", {
expect_identical(sort(listFiles(mydir, url=info$url)), sort(c("diet/metadata.json", "metadata.json")))
expect_identical(sort(listFiles(paste0(mydir, "/diet"), url=info$url)), "metadata.json")
expect_identical(sort(listFiles(mydir, url=info$url, recursive=FALSE)), sort(c("diet/", "metadata.json")))

# Forcing remote access.
expect_identical(sort(listFiles(mydir, url=info$url, forceRemote=TRUE)), sort(c("diet/metadata.json", "metadata.json")))
expect_identical(sort(listFiles(mydir, url=info$url, forceRemote=TRUE, recursive=FALSE)), sort(c("diet/", "metadata.json")))
})
config <- basic_config()
info <- config$info
mydir <- config$mydir

test_that("listRegisteredDirectories works as expected", {
all <- listRegisteredDirectories(info$url)
Expand Down
29 changes: 12 additions & 17 deletions tests/testthat/test-query.R
Original file line number Diff line number Diff line change
@@ -1,25 +1,18 @@
# library(testthat); library(SewerRat); source("test-query.R")
# library(testthat); library(SewerRat); source("setup.R"); source("test-query.R")

# Starting up an example SewerRat service:
info <- startSewerRat()
config <- basic_config()
info <- config$info
mydir <- config$mydir

# Mocking up a directory of stuff to query.
mydir <- tempfile()
dir.create(mydir)
write(file=file.path(mydir, "metadata.json"), '{ "first": "Aaron", "last": "Lun" }')
dir.create(file.path(mydir, "diet"))
write(file=file.path(mydir, "diet", "metadata.json"),
'{ "meal": "lunch", "ingredients": "water" }')
test_that("basic queries work", {
q <- query("aaron", url=info$url)
expect_identical(length(q), 1L)

# Registering it:
register(mydir, "metadata.json", url=info$url)

test_that("query works as expected", {
q <- query("lun*", url=info$url)
expect_gte(length(q), 2L)
expect_identical(length(q), 2L)
})

test_that("query works with truncation", {
test_that("truncated queries work", {
expect_message(q <- query("lun*", url=info$url, number=0), "truncated")
expect_identical(length(q), 0L)

Expand All @@ -30,7 +23,7 @@ test_that("query works with truncation", {
expect_identical(length(q), 0L)
})

test_that("formatQueryResults works properly", {
test_that("formatting of query results works properly", {
q <- query("lun*", url=info$url)
res <- formatQueryResults(q)

Expand All @@ -39,3 +32,5 @@ test_that("formatQueryResults works properly", {
expect_equal(as.double(res$time), vapply(q, function(y) y$time, 0))
expect_identical(res$metadata[[1]], q[[1]]$metadata)
})

deregister(mydir, url=info$url)
14 changes: 14 additions & 0 deletions tests/testthat/test-register.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
# library(testthat); library(SewerRat); source("setup.R"); source("test-register.R")

config <- basic_config()
info <- config$info
mydir <- config$mydir

test_that("(de)registration works as expected", {
res <- query("aaron", url=info$url)
expect_identical(length(res), 1L)

deregister(mydir, url=info$url)
res <- query("aaron", url=info$url)
expect_identical(length(res), 0L)
})
14 changes: 4 additions & 10 deletions tests/testthat/test-retrieve.R
Original file line number Diff line number Diff line change
@@ -1,14 +1,8 @@
# Test the retrieval functions.
# library(testthat); library(SewerRat); source("test-retrieve.R")
# library(testthat); library(SewerRat); source("setup.R"); source("test-retrieve.R")

info <- startSewerRat()

mydir <- tempfile()
dir.create(mydir)
write(file=file.path(mydir, "metadata.json"), '{ "first": "Aaron", "last": "Lun" }')
dir.create(file.path(mydir, "diet"))
write(file=file.path(mydir, "diet", "metadata.json"), '{ "meal": "lunch", "ingredients": "water" }')
register(mydir, "metadata.json", url=info$url)
config <- basic_config()
info <- config$info
mydir <- config$mydir

test_that("retrieveFile works as expected", {
p <- retrieveFile(paste0(mydir, "/metadata.json"), url=info$url)
Expand Down

0 comments on commit 1460d5f

Please sign in to comment.