Skip to content

Commit 64f74dd

Browse files
authored
Merge pull request #1720 from r-lib/feature/defunct-env-unlock
Deprecate `env_unlock()`
2 parents 81a6c97 + 38b770d commit 64f74dd

File tree

7 files changed

+33
-25
lines changed

7 files changed

+33
-25
lines changed

NEWS.md

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,10 @@
11
# rlang (development version)
22

3+
* `env_unlock()` is now defunct because recent versions of R no long
4+
make it possible to unlock an environment. Make sure to use an up-to-date
5+
version of pkgload (>= 1.4.0) following this change.
6+
7+
38
# rlang 1.1.4
49

510
* Added missing C level `r_dyn_raw_push_back()` and `r_dyn_chr_push_back()`

R/env.R

Lines changed: 22 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -554,16 +554,35 @@ env_is_locked <- function(env) {
554554

555555
#' Unlock an environment
556556
#'
557-
#' This function should only be used in development tools or
558-
#' interactively.
557+
#' `r lifecycle::badge("defunct")`. This function is now defunct
558+
#' because recent versions of R no longer make it possible to
559+
#' unlock an environment.
559560
#'
560561
#' @inheritParams env_lock
561562
#' @return Whether the environment has been unlocked.
562563
#'
563564
#' @keywords internal
564565
#' @export
565566
env_unlock <- function(env) {
566-
invisible(.Call(ffi_env_unlock, env))
567+
msg <- "`env_unlock()` is defunct as of rlang 1.1.5"
568+
569+
old_pkgload_running <-
570+
"pkgload" %in% loadedNamespaces() &&
571+
some(sys.frames(), function(env) identical(topenv(env), ns_env("pkgload"))) &&
572+
utils::packageVersion("pkgload") <= "1.3.4"
573+
574+
if (old_pkgload_running) {
575+
ver <- utils::packageVersion("pkgload")
576+
msg <- c(
577+
msg,
578+
"i" = sprintf(
579+
"This error is likely caused by an outdated version of pkgload. You are running pkgload %s and you need at least 1.4.0",
580+
ver
581+
)
582+
)
583+
}
584+
585+
abort(msg)
567586
}
568587

569588

R/rlang-package.R

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -18,3 +18,6 @@ compiled_by_gcc <- function() {
1818
#' @rawNamespace export(ffi_standalone_is_bool_1.0.7)
1919
#' @rawNamespace export(ffi_standalone_check_number_1.0.7)
2020
NULL
21+
22+
# Enable pkgload to hotpatch `::` in detached namespaces
23+
on_load(`::` <- base::`::`)

man/env_unlock.Rd

Lines changed: 3 additions & 2 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

src/internal/env.c

Lines changed: 0 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,16 +1,5 @@
11
#include <rlang.h>
22

3-
#define FRAME_LOCK_MASK (1 << 14)
4-
#define FRAME_IS_LOCKED(e) (ENVFLAGS(e) & FRAME_LOCK_MASK)
5-
#define UNLOCK_FRAME(e) SET_ENVFLAGS(e, ENVFLAGS(e) & (~FRAME_LOCK_MASK))
6-
7-
// Should only be used in development tools
8-
r_obj* ffi_env_unlock(r_obj* env) {
9-
UNLOCK_FRAME(env);
10-
return FRAME_IS_LOCKED(env) == 0 ? r_true : r_false;
11-
}
12-
13-
143
void r_env_unbind_anywhere(r_obj* env, r_obj* sym) {
154
while (env != r_envs.empty) {
165
if (r_env_has(env, sym)) {

src/internal/init.c

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -87,7 +87,6 @@ static const R_CallMethodDef r_callables[] = {
8787
{"ffi_env_poke", (DL_FUNC) &ffi_env_poke, 5},
8888
{"ffi_env_poke_parent", (DL_FUNC) &ffi_env_poke_parent, 2},
8989
{"ffi_env_unbind", (DL_FUNC) &ffi_env_unbind, 3},
90-
{"ffi_env_unlock", (DL_FUNC) &ffi_env_unlock, 1},
9190
{"ffi_eval_top", (DL_FUNC) &ffi_eval_top, 2},
9291
{"ffi_exprs_interp", (DL_FUNC) &ffi_exprs_interp, 6},
9392
{"ffi_f_lhs", (DL_FUNC) &r_f_lhs, 1},

tests/testthat/test-env.R

Lines changed: 0 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -236,14 +236,6 @@ test_that("can lock environments", {
236236
expect_true(env_lock(env))
237237
})
238238

239-
test_that("can unlock environments", {
240-
env <- env()
241-
env_lock(env)
242-
expect_true(env_unlock(env))
243-
expect_false(env_is_locked(env))
244-
expect_no_error(env_bind(env, a = 1))
245-
})
246-
247239
test_that("env_print() has flexible input", {
248240
# because it's primarily used interactively
249241
f <- function() 1

0 commit comments

Comments
 (0)