Skip to content

Commit

Permalink
Addressed comments
Browse files Browse the repository at this point in the history
  • Loading branch information
falaki committed Nov 14, 2019
1 parent 10925bf commit 6ad35c9
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 11 deletions.
13 changes: 7 additions & 6 deletions R/pkg/R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -543,14 +543,15 @@ processClosure <- function(node, oldEnv, defVars, checkedFuncs, newEnv) {
funcList <- mget(nodeChar, envir = checkedFuncs, inherits = F,
ifnotfound = list(list(NULL)))[[1]]
found <- sapply(funcList, function(func) {
ifelse(identical(func, obj), TRUE, FALSE)
ifelse(
identical(func, obj) &&
# Also check if the parent environment is identical to current parent
identical(parent.env(environment(func)), func.env),
TRUE, FALSE)
})
if (sum(found) > 0) {
# If function has been examined
if (identical(parent.env(environment(funcList[found][[1]])), func.env)) {
# If the parent environment is identical to current parent
break
}
# If function has been examined ignore
break
}
# Function has not been examined, record it and recursively clean its closure.
assign(nodeChar,
Expand Down
10 changes: 5 additions & 5 deletions R/pkg/tests/fulltests/test_utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -113,11 +113,11 @@ test_that("cleanClosure on R functions", {
# Test for combination for nested and sequenctial functions in a closure
f1 <- function(x) x + 1
f2 <- function(x) f1(x) + 2
user_func <- function(x) { f1(x); f2(x) }
c_user_func_env <- environment(cleanClosure(user_func))
expect_equal(length(c_user_func_env), 2)
inner_c_user_func_env <- environment(c_user_func_env$f2)
expect_equal(length(inner_c_user_func_env), 1)
userFunc <- function(x) { f1(x); f2(x) }
cUserFuncEnv <- environment(cleanClosure(userFunc))
expect_equal(length(cUserFuncEnv), 2)
innerCUserFuncEnv <- environment(cUserFuncEnv$f2)
expect_equal(length(innerCUserFuncEnv), 1)

# Test for function (and variable) definitions.
f <- function(x) {
Expand Down

0 comments on commit 6ad35c9

Please sign in to comment.