Reputation: 83
Let's say I define an S4 class 'foo'
with two slots 'a'
and 'b'
, and define an object x
of class 'foo'
,
setClass(Class = 'foo', slots = c(
a = 'numeric',
b = 'character'
))
x <- new('foo', a = rnorm(1e3L), b = rep('A', times = 1e3L))
format(object.size(x), units = 'auto') # "16.5 Kb"
Then I want to remove slot 'a'
from the definition of 'foo'
setClass(Class = 'foo', slots = c(
b = 'character'
))
slotNames(x) # slot 'a' automatically removed!! wow!!!
I see that R automatically take cares my object x
and have the slot 'a'
removed. Nice! But wait, the size of object x
is not reduced.
format(object.size(x), units = 'auto') # still "16.5 Kb"
format(object.size(new(Class = 'foo', x)), units = 'auto') # still "16.5 Kb"
Right.. Somehow 'a'
is still there but I just cannot do anything to it
head(x@a) # `'a'` is still there
rm(x@a) # error
x@a <- NULL # error
So question: how can I really remove slot 'a'
from x
and have its size reduced (which is my primary concern)?
My deepest gratitude to all answers!
The following solution is inspired by dww
trimS4slot <- function(x) {
nm0 <- names(attributes(x))
nm1 <- names(getClassDef(class(x))@slots) # ?methods::.slotNames
if (any(id <- is.na(match(nm0, table = c(nm1, 'class'))))) attributes(x)[nm0[id]] <- NULL # ?base::setdiff
return(x)
}
format(object.size(y1 <- trimS4slot(x)), units = 'auto') # "8.5 Kb"
The following solution is inspired by Robert Hijmans
setClass('foo1', contains = 'foo')
format(object.size(y2 <- as(x, 'foo1')), units = 'auto') # "8.5 Kb"
method::as
probably does some comprehensive checks, so it's quite slow though
library(microbenchmark)
microbenchmark(trimS4slot(x), as(x, 'foo1')) # ?methods::as 10 times slower
Upvotes: 6
Views: 1307
Reputation: 31452
Slots are stored as attributes. We have a couple of options for converting a slot to NULL
.
Option 1: You can use the check=FALSE
argument in slot<-
to assign a slot as NULL without triggering an error.
slot(x, 'a', check=FALSE) <- NULL
setClass(Class = 'foo', slots = c(b = 'character'))
format(object.size(x), units = 'auto')
# [1] "8.7 Kb"
However, the attribute is not completely removed (it still exists with a value of \001NULL\001
). This happens because of a line in the C function R_do_slot_assign
, which has: if(isNull(value)) value = pseudo_NULL;
where pseudo_NULL is "an object that is ...used to represent slots that are NULL (which an attribute can not be)".
One should also take notice of the advice in ?slot
that "User's should not set check=FALSE
in normal use, since the resulting object can be invalid." It should not cause any issues in this instance, since the slot is being removed immediately after. Nonetheless it is good to be cautious about using the check=False flag unless you are sure you understand what you are doing.
Option 2: A more complete removal can be achieved by directly removing the attribute after removing the slot from the class definition:
setClass(Class = 'foo', slots = c(
b = 'character'
))
attr(x, 'a') <- NULL
format(object.size(x), units = 'auto')
# [1] "8.7 Kb"
But, is removing slots even a good idea?
Removing slots is something of a hack that could cause errors later, e.g. if a method is called that assumes the existence of the slot. You might get away with doing this for a specific use case on your own machine. But releasing this into the wild as production code would not be a good idea. In that case, the approach in @RobertHijmans' answer would be the way to go.
Upvotes: 3
Reputation: 47091
What @dww suggests is nifty, and answers your question. But isn't the point of a class that you are guaranteed that its members (the slots) will always be there? If you don't care about that you can use the anything goes S3
classes instead? With S4
, I would suggest a more formal approach like this:
setClass(Class = 'bar', slots = c(b = 'character'))
setClass(Class = 'foo', contains='bar', slots = c(a = 'numeric'))
x <- new('foo', a = rnorm(1e3L), b = rep('A', times = 1e3L))
format(object.size(x), units = 'auto')
#[1] "16.5 Kb"
x <- as(x, "bar")
format(object.size(x), units = 'auto')
#[1] "8.5 Kb"
And if this is just about size, why not just do
x <- new('foo', a = rnorm(1e3L), b = rep('A', times = 1e3L))
x@b <- ""
format(object.size(x), units = 'auto')
#[1] "8.7 Kb"
To me this is clearly the best solution because of its simplicity.
Upvotes: 2