[R] How to test existence of an environment and how to remove it (from within functions)?
Marius Hofert
marius.hofert at uwaterloo.ca
Tue Aug 30 20:45:33 CEST 2016
Hi Duncan,
... I don't have to know (I thought). The idea was to set up the environment
only for a single object x. If it (= the environment (see MWE 2) *or* the object
(see MWE 1)) exists, it's the right one. But I agree that it's 'cleaner' to work
with a hash -- yet I first wanted to understand how to check whether the
environment exists and how to remove it (especially for the latter, I couldn't
find anything... most sources of information dealt with how to delete objects in
an environment, not an environment itself [caution: I just started to learn
about environments, there is a high chance that there's a misconception on my
end...:-) ]).
With memoise, it works as expected:
library(memoise)
## Auxiliary function
aux <- function(x) {
Sys.sleep(1)
x[,1:2]
}
## Main function
main <- function() {
aux. <- memoise(aux)
x <- matrix(rnorm(100*1000), ncol = 1000)
res <- replicate(5, aux.(x))
forget(aux.)
res
}
## Testing
set.seed(271)
system.time(res1 <- main()) # => ~ 1s
stopifnot(all.equal(res1[,,1], res1[,,2]),
all.equal(res1[,,2], res1[,,3]),
all.equal(res1[,,3], res1[,,4]),
all.equal(res1[,,4], res1[,,5]))
system.time(res2 <- main()) # => ~ 1s
stopifnot(all.equal(res2[,,1], res2[,,2]),
all.equal(res2[,,2], res2[,,3]),
all.equal(res2[,,3], res2[,,4]),
all.equal(res2[,,4], res2[,,5]))
The biggest takeaway here is to have main() set up another auxiliary function
(aux.()) which calls aux().
I looked at memoise and it is surprisingly short. I then tried to adapt the idea
directly (I try to learn things, not just use them), but it fails with "Error in
exists(hash, envir = cache, inherits = FALSE) (from #6) : use of NULL
environment is defunct". Not sure why this works from inside memoise...
library(digest)
## Auxiliary function
aux <- function(x) {
Sys.sleep(1)
x[,1:2]
}
## Main function
main <- function() {
## Wrap aux() in another helper function
aux. <- function(...) {
## Set up cache
cache <- NULL
cache_reset <- function() cache <<- new.env(TRUE, emptyenv())
## Define key
hash <- digest(list(...))
## Do the computation (if not done already)
if (exists(hash, envir = cache, inherits = FALSE)) {
get(hash, envir = cache, inherits = FALSE) # get result
} else {
res <- aux(...) # compute result
assign(hash, res, envir = cache) # cache result
res
}
}
## Call aux() via aux.()
x <- matrix(rnorm(100*1000), ncol = 1000)
res <- replicate(5, aux.(x))
## Reset cache
get("cache", environment(aux.))$reset()
## Return
res
}
## Testing
set.seed(271)
system.time(res1 <- main())
## => Error in exists(hash, envir = cache, inherits = FALSE) (from #6) :
## use of NULL environment is defunct
Thanks & cheers,
Marius
More information about the R-help
mailing list