[R-pkg-devel] cannot change value of locked binding for '*tmp*'

Jens Oehlschlägel Jen@@Oehl@chl@egel @ending from trueclu@ter@com
Sun Jun 3 20:29:23 CEST 2018


Hello R language experts,

I get an error I don't understand in an assigment function
of the form

deref(z[i]) <- v

Error in deref(z[1:5]) <- -deref(z[1:5]) :
   cannot change value of locked binding for '*tmp*'

*after* the assignment did what it should. I can workaround
using a standard function achieving the desired side-effects

refset(z[i], value=v)

Any explanation or idea how to make the standard notation working?

Context and replication code follows below.

Best

Jens


# I am trying to modernize package 'ref'
# which stems from the time of S+ and early R.
# Old package 'ref' (version 0.99) allows passing arguments by reference
# but has lost the ability to change parts of a vector
# without copying the complete vector since R version 1.8.

# I think we can restore performance if
# a new reference is not longer "an object name plus an environment"
# but is "an expression such as 'z' or 'z[i]' plus an environment"
# such that the ref-functions just become convenience wrappers to
# 'eval', 'substitute' and friends
ref <- function(expr, envir = parent.frame()){
   ret <- list(expr=substitute(expr), envir=envir)
   class(ret) <- "ref"
   ret
}

# get data at referenced expression
deref <- refget <- function(x, ...){
   # ensure that $ does the usual job once we define $.ref
   oldClass(x) <- NULL
   eval(x$expr, envir=x$envir)
}

# modify data at referenced expression
"deref<-" <- refset <- function(x, value){
   oldClass(x) <- NULL
   newexpr <- substitute(a <- b, list(a=x$expr, b=value))
   eval(newexpr, envir=x$envir)
   newexpr
}

# subscript referenced expression (without evaluating it)
"[.ref" <- function(x, ...){
   cl <- oldClass(x)
   oldClass(x) <- NULL
   newexpr <- sys.call()
   newexpr[[1]] <- call("[")[[1]]
   newexpr[[2]] <- x$expr
   x$expr <- newexpr
   oldClass(x) <- cl
   x
}

# some example data
n <- 1e1
x <- 1:n
# create a reference to it
z <- ref(x)

# using refget(z[i]) and refset(z[i], v)
# efficiently assignes to a referenced subset as desired
v <- refget(z[1:5])
refset(z[1:5], -v)
# so my code works
x[1:10]

# but doing it R-style
# with deref(z[i]) and deref(z[i]) <- v
# gives this error:
# Error in deref(z[1:5]) <- -deref(z[1:5]) :
#   cannot change value of locked binding for '*tmp*'
v <- deref(z[1:5])
deref(z[1:5]) <- -v
# anyhow the referenced vector has been changed !?
x[1:10]



More information about the R-package-devel mailing list