[Rd] Reference Classes copy(shallow=FALSE) unexpected behavior.

Hadley Wickham hadley at rice.edu
Wed May 11 15:37:42 CEST 2011


Hi Manuel,

The source code for copy is short and pretty readable, so I'd
encourage you to look at it:

> setRefClass("XXX")$copy
Class method definition for method copy()
function (shallow = FALSE)
{
    def <- .refClassDef
    value <- new(def)
    vEnv <- as.environment(value)
    selfEnv <- as.environment(.self)
    for (field in names(def at fieldClasses)) {
        if (shallow)
            assign(field, get(field, envir = selfEnv), envir = vEnv)
        else {
            current <- get(field, envir = selfEnv)
            if (is(current, "envRefClass"))
                current <- current$copy(FALSE)
            assign(field, current, envir = vEnv)
        }
    }
    value
}

The basic problem is that you have a list of reference class objects,
and currently copy does not recurse into lists.  I think this could be
fixed with

deep_copy <- function(x) {
  if (is(current, "envRefClass")) {
    x$copy()
  } else if (is.list(x))
    lapply(x, deep_copy)
  } else {
    x
  }
}

function (shallow = FALSE){
    def <- .refClassDef
    value <- new(def)
    vEnv <- as.environment(value)
    selfEnv <- as.environment(.self)
    for (field in names(def at fieldClasses)) {
        if (shallow)
            assign(field, get(field, envir = selfEnv), envir = vEnv)
        else {
            current <- get(field, envir = selfEnv)
            assign(field, deep_copy(current), envir = vEnv)
        }
    }
    value
}

Hadley

2011/5/11 Manuel Castejón Limas <manuel.castejon at unileon.es>:
> Dear Hadley,
>
> Thank you very much for your interest in the question proposed.
> The Con class is a Reference Class. P and k are from class listCon.
>
> I provide in the following lines a little more detail in order to be able
> to reproduce the case.
>
> #Class declaration
> gCon <- setRefClass("Con", fields=list(from="ANY",weight="numeric"))
> gListAMORE <- setRefClass("listAMORE", fields=list(.Data="list"))
> gListCon <- setRefClass("listCon", contains="listAMORE")
>
> # Let's create a few connections
> con1 <- gCon$new(from=1, weight=1.1)
> con2 <- gCon$new(from=2, weight=2.2)
> con3 <- gCon$new(from=3, weight=3.3)
>
> # And a list of connections
> lcon <-gListCon$new()
> lcon$.Data <- list(con1, con2, con3)
>
> # At this point, lcon contains:
> lcon$.Data
> [[1]]
> An object of class "Con"
> <environment: 0x9a1534>
>
> [[2]]
> An object of class "Con"
> <environment: 0xcd7ff0>
>
> [[3]]
> An object of class "Con"
> <environment: 0xdca724>
>
> # Let's copy lcon to k
> k <- lcon$copy(shallow=FALSE)
>
> # Now k is a new object but the cons are shared with lcon!
> k$.Data
> [[1]]
> An object of class "Con"
> <environment: 0x9a1534>
>
> [[2]]
> An object of class "Con"
> <environment: 0xcd7ff0>
>
> [[3]]
> An object of class "Con"
> <environment: 0xdca724>
>
>
> Best regards
>
> Manuel
>
>
>
> El 11/05/11 14:00, "Hadley Wickham" <hadley at rice.edu> escribió:
>
>>2011/5/10 Manuel Castejón Limas <manuel.castejon at unileon.es>:
>>> Dear all,
>>>
>>> I've just discovered the 'Reference Classes'.
>>> In a previous attempt ---a year ago--- to re-implement in a Object
>>>Oriented
>>> fashion the AMORE package using S4 classes I strongly felt the need of
>>>such
>>> capability. It's great to have the Reference Classes now available.
>>>Along
>>> with the discovery of the Rcpp package, this new programming paradigm
>>>has
>>> boosted my interest in rewriting that package.
>>>
>>> Nevertheless, I have found a surprising behavior in the
>>>$copy(shallow=FALSE)
>>> method. Let's have a look at the results which I believe are
>>> self-explanatories. The ".Data" field is a list which contains objects
>>>from
>>> the "Con" class  ---connections for what is worth---.
>>
>>What sort of class is the Con class? S4 or reference?
>>
>>Hadley
>>
>>
>>--
>>Assistant Professor / Dobelman Family Junior Chair
>>Department of Statistics / Rice University
>>http://had.co.nz/
>>
>
>
>
>



-- 
Assistant Professor / Dobelman Family Junior Chair
Department of Statistics / Rice University
http://had.co.nz/



More information about the R-devel mailing list