Skip to content

Commit

Permalink
test external classes with actual packages
Browse files Browse the repository at this point in the history
  • Loading branch information
t-kalinowski committed Nov 4, 2024
1 parent dfe6eec commit 0b21f03
Show file tree
Hide file tree
Showing 9 changed files with 99 additions and 21 deletions.
11 changes: 11 additions & 0 deletions R/class-spec.R
Original file line number Diff line number Diff line change
Expand Up @@ -100,6 +100,17 @@ class_construct_expr <- function(.x, envir = NULL, package = NULL) {
} else {
# namespace the pkgname::classname() call
cl <- as.call(list(quote(`::`), as.name(f@package), as.name(f@name)))

# check the call evaluates to f.
# This will error if package is not installed or object is not exported.
f2 <- eval(cl, baseenv())
if (!identical(f, f2)) {
msg <- sprintf(
"`%s::%s` is not identical to the class with the same @package and @name properties",
f@package, f@name
)
stop(msg, call. = FALSE)
}
return(as.call(list(cl)))
}
}
Expand Down
8 changes: 0 additions & 8 deletions tests/testthat/_snaps/constructor.md
Original file line number Diff line number Diff line change
Expand Up @@ -79,11 +79,3 @@
new_object(foo(...), y = y)
<environment: 0x0>

# package exported classes are not inlined in constructor formals

Code
args(Bar)
Output
function (foo = pkgname::Foo())
NULL

38 changes: 38 additions & 0 deletions tests/testthat/_snaps/external-generic.md
Original file line number Diff line number Diff line change
Expand Up @@ -5,3 +5,41 @@
Output
<S7_external_generic> foo::bar(x)

# new_method works with both hard and soft dependencies

Code
args(Foo)
Output
function (bar = t0::AnS7Class())
NULL
Code
args(t2::AnS7Class2)
Output
function (bar = t0::AnS7Class())
NULL
Code
args(t2:::AnInternalClass)
Output
function (foo = t0::AnS7Class(), bar = AnS7Class2())
NULL

---

Code
new_class("Foo", properties = list(bar = new_class("MadeUpClass", package = "t0")))
Condition
Error:
! 'MadeUpClass' is not an exported object from 'namespace:t0'
Code
new_class("Foo", properties = list(bar = new_class("MadeUpClass", package = "MadeUpPackage")))
Condition
Error in `loadNamespace()`:
! there is no package called 'MadeUpPackage'
Code
modified_class <- t0::AnS7Class
attr(modified_class, "xyz") <- "abc"
new_class("Foo", properties = list(bar = modified_class))
Condition
Error:
! `t0::AnS7Class` is not identical to the class with the same @package and @name properties

1 change: 1 addition & 0 deletions tests/testthat/t0/NAMESPACE
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
# Generated by roxygen2: do not edit by hand

export(AnS7Class)
export(an_s3_generic)
export(an_s7_generic)
3 changes: 3 additions & 0 deletions tests/testthat/t0/R/t0.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,3 +3,6 @@ an_s7_generic <- S7::new_generic("an_s7_generic", "x")

#' @export
an_s3_generic <- function(x) UseMethod("an_s3_generic")

#' @export
AnS7Class <- S7::new_class("AnS7Class")
2 changes: 2 additions & 0 deletions tests/testthat/t2/NAMESPACE
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
# Generated by roxygen2: do not edit by hand

export(AnS7Class2)
export(an_s7_class)
importFrom(t0,AnS7Class)
importFrom(t0,an_s3_generic)
importFrom(t0,an_s7_generic)
11 changes: 11 additions & 0 deletions tests/testthat/t2/R/t2.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,13 +10,24 @@ S7::method(an_s7_generic, an_s7_class) <- function(x) "foo"
S7::method(an_s3_generic, an_s7_class) <- function(x) "foo"


#' @importFrom t0 AnS7Class
#' @export
AnS7Class2 <- S7::new_class("AnS7Class2", properties = list(bar = AnS7Class))

AnInternalClass <- S7::new_class("AnInternalClass", properties = list(
foo = AnS7Class,
bar = AnS7Class2
))


another_s7_generic <- S7::new_external_generic("t1", "another_s7_generic", "x")
S7::method(another_s7_generic, S7::class_character) <- function(x) "foo"
S7::method(another_s7_generic, an_s7_class) <- function(x) "foo"

another_s3_generic <- S7::new_external_generic("t1", "another_s3_generic", "x")
S7::method(another_s3_generic, an_s7_class) <- function(x) "foo"


.onLoad <- function(libname, pkgname) {
S7::methods_register()
}
13 changes: 0 additions & 13 deletions tests/testthat/test-constructor.R
Original file line number Diff line number Diff line change
Expand Up @@ -191,16 +191,3 @@ test_that("Dynamic settable properties are included in constructor", {
expect_equal(foo@dynamic_settable, 1)

})

test_that("package exported classes are not inlined in constructor formals", {
# https://github.com/RConsortium/S7/issues/477
Foo := new_class(package = "pkgname")
Bar := new_class(properties = list(foo = Foo))

expect_identical(
formals(Bar)$foo,
quote(pkgname::Foo())
)

expect_snapshot(args(Bar))
})
33 changes: 33 additions & 0 deletions tests/testthat/test-external-generic.R
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,39 @@ test_that("new_method works with both hard and soft dependencies", {
expect_equal(an_s3_generic(t2::an_s7_class()), "foo")
expect_equal(an_s7_generic("x"), "foo")

# test that new_class() will construct a property default as a namespaced call
# to t0::AnS7Class() (and not inline the full class object).
# As these tests grow, consider splitting this into a separate context like:
# test_that("package exported classes are not inlined in constructor formals", {...})
Foo <- new_class("Foo", properties = list(bar = t0::AnS7Class))
expect_identical(formals(Foo) , as.pairlist(alist(bar = t0::AnS7Class())))
expect_identical(formals(t2::AnS7Class2), as.pairlist(alist(bar = t0::AnS7Class())))
expect_identical(formals(t2:::AnInternalClass), as.pairlist(alist(
foo = t0::AnS7Class(), bar = AnS7Class2()
)))

expect_snapshot({
args(Foo)
args(t2::AnS7Class2)
args(t2:::AnInternalClass)
})

# test we emit informative error messages if a new_class() call with an
# external class dependency is malformed.
# https://github.com/RConsortium/S7/issues/477
expect_snapshot(error = TRUE, {
new_class("Foo", properties = list(
bar = new_class("MadeUpClass", package = "t0")
))
new_class("Foo", properties = list(
bar = new_class("MadeUpClass", package = "MadeUpPackage")
))

modified_class <- t0::AnS7Class
attr(modified_class, "xyz") <- "abc"
new_class("Foo", properties = list(bar = modified_class))
})

# Now install the soft dependency
quick_install(test_path("t1"), tmp_lib)

Expand Down

0 comments on commit 0b21f03

Please sign in to comment.