Skip to content

Commit

Permalink
Merge pull request #274 from zeehio/fix-253
Browse files Browse the repository at this point in the history
  • Loading branch information
wch authored Apr 20, 2023
2 parents e6b5eaf + 5782335 commit e97cca7
Show file tree
Hide file tree
Showing 4 changed files with 28 additions and 3 deletions.
4 changes: 2 additions & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -15,11 +15,11 @@ License: MIT + file LICENSE
URL: https://r6.r-lib.org, https://github.com/r-lib/R6/
BugReports: https://github.com/r-lib/R6/issues
Depends:
R (>= 3.0)
R (>= 3.2)
Suggests:
lobstr,
testthat (>= 3.0.0)
Config/Needs/website: tidyverse/tidytemplate, ggplot2, microbenchmark, scales
Config/testthat/edition: 3
Encoding: UTF-8
RoxygenNote: 7.2.1
RoxygenNote: 7.2.3
2 changes: 2 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@ R6 2.5.1.9000

* When a superclass is not cloneable, then subclasses cannot be cloneable (@IndrajeetPatil, #247).

* Fixed #253: Errors could occur when deep cloning if a member object was an environment with a class that had a `$` method. Deep cloning now uses `get0()` instead of `$`. R6 now requires R >= 3.2. (@zeehio, #274)

R6 2.5.1
========

Expand Down
4 changes: 3 additions & 1 deletion R/clone.R
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,9 @@ generator_funs$clone_method <- function(deep = FALSE) {
# fields that are R6 objects.
deep_clone <- function(name, value) {
# Check if it's an R6 object.
if (is.environment(value) && !is.null(value$`.__enclos_env__`)) {
is_r6_object <- is.environment(value) &&
!is.null(get0(".__enclos_env__", value, inherits = FALSE))
if (is_r6_object) {
return(value$clone(deep = TRUE))
}
value
Expand Down
21 changes: 21 additions & 0 deletions tests/testthat/test-clone.R
Original file line number Diff line number Diff line change
Expand Up @@ -1077,6 +1077,27 @@ test_that("Cloning inherited methods for non-portable classes", {
expect_identical(a$x, 3)
})

test_that("In deep_clone(), don't try to clone non-R6 objects", {

`$.test` <- function(x, value) {
stop("error")
}

AC <- R6Class("AC",
public = list(
x = NULL,
initialize = function() {
x <- new.env(parent = emptyenv())
class(x) <- "test"
self$x <- x
}
)
)

obj <- AC$new()
obj2 <- obj$clone(deep = TRUE)
expect_identical(obj$x, obj2$x)
})

test_that("Deep cloning", {
AC <- R6Class("AC", public = list(x = 1))
Expand Down

0 comments on commit e97cca7

Please sign in to comment.