We read every piece of feedback, and take your input very seriously.
To see all available qualifiers, see our documentation.
There was an error while loading. Please reload this page.
env_browse()
env_is_browsed()
1 parent 5634e96 commit 6f102ceCopy full SHA for 6f102ce
DESCRIPTION
@@ -44,7 +44,7 @@ Suggests:
44
Enhances:
45
winch
46
Encoding: UTF-8
47
-RoxygenNote: 7.3.1
+RoxygenNote: 7.3.2
48
Roxygen: list(markdown = TRUE)
49
URL: https://rlang.r-lib.org, https://github.com/r-lib/rlang
50
BugReports: https://github.com/r-lib/rlang/issues
NEWS.md
@@ -1,8 +1,11 @@
1
# rlang (development version)
2
3
+* `env_browse()` and `env_is_browsed()` are now defunct as they require an API
4
+ that is no longer available to packages (#1727).
5
+
6
* `env_unlock()` is now defunct because recent versions of R no long
- make it possible to unlock an environment. Make sure to use an up-to-date
- version of pkgload (>= 1.4.0) following this change.
7
+ make it possible to unlock an environment (#1705). Make sure to use an
8
+ up-to-date version of pkgload (>= 1.4.0) following this change.
9
10
11
# rlang 1.1.4
R/env.R
@@ -566,8 +566,8 @@ env_is_locked <- function(env) {
566
env_unlock <- function(env) {
567
msg <- "`env_unlock()` is defunct as of rlang 1.1.5"
568
569
- old_pkgload_running <-
570
- "pkgload" %in% loadedNamespaces() &&
+ old_pkgload_running <-
+ "pkgload" %in% loadedNamespaces() &&
571
some(sys.frames(), function(env) identical(topenv(env), ns_env("pkgload"))) &&
572
utils::packageVersion("pkgload") <= "1.3.4"
573
@@ -754,6 +754,8 @@ str.rlang_envs <- function(object, ...) {
754
#'
755
#' @description
756
757
+#' `r lifecycle::badge("defunct")`
758
+#'
759
#' * `env_browse(env)` is equivalent to evaluating `browser()` in
760
#' `env`. It persistently sets the environment for step-debugging.
761
#' Supply `value = FALSE` to disable browsing.
@@ -767,12 +769,12 @@ str.rlang_envs <- function(object, ...) {
767
769
#' `env_is_browsed()` (a logical), invisibly.
768
770
#' @export
771
env_browse <- function(env, value = TRUE) {
- invisible(.Call(ffi_env_browse, env, value))
772
+ abort("`env_browse()` is defunct as of rlang 1.2.0 because R no longer supports it")
773
}
774
#' @rdname env_browse
775
776
env_is_browsed <- function(env) {
- .Call(ffi_env_is_browsed, env)
777
+ abort("`env_is_browsed()` is defunct as of rlang 1.2.0 because R no longer supports it")
778
779
780
#' Is frame environment user facing?
man/env_browse.Rd
src/internal/exported.c
@@ -511,26 +511,6 @@ r_obj* ffi_env_bind_list(r_obj* env, r_obj* names, r_obj* data) {
511
return r_null;
512
513
514
-r_obj* ffi_env_browse(r_obj* env, r_obj* value) {
515
- if (r_typeof(env) != R_TYPE_environment) {
516
- r_abort("`env` must be an environment.");
517
- }
518
- if (!r_is_bool(value)) {
519
- r_abort("`value` must be a single logical value.");
520
521
-
522
- r_obj* old = r_lgl(RDEBUG(env));
523
- SET_RDEBUG(env, r_lgl_get(value, 0));
524
- return old;
525
-}
526
527
-r_obj* ffi_env_is_browsed(r_obj* env) {
528
529
530
531
- return r_lgl(RDEBUG(env));
532
533
534
r_obj* ffi_ns_registry_env(void) {
535
return R_NamespaceRegistry;
536
src/internal/init.c
@@ -74,7 +74,6 @@ static const R_CallMethodDef r_callables[] = {
74
{"ffi_env_bind", (DL_FUNC) &ffi_env_bind, 5},
75
{"ffi_env_bind_list", (DL_FUNC) &ffi_env_bind_list, 3},
76
{"ffi_env_binding_types", (DL_FUNC) &r_env_binding_types, 2},
77
- {"ffi_env_browse", (DL_FUNC) &ffi_env_browse, 2},
78
{"ffi_env_clone", (DL_FUNC) &r_env_clone, 2},
79
{"ffi_env_coalesce", (DL_FUNC) &ffi_env_coalesce, 2},
80
{"ffi_env_frame", (DL_FUNC) &ffi_env_frame, 1},
@@ -83,7 +82,6 @@ static const R_CallMethodDef r_callables[] = {
83
82
{"ffi_env_has", (DL_FUNC) &ffi_env_has, 3},
84
{"ffi_env_hash_table", (DL_FUNC) &ffi_env_hash_table, 1},
85
{"ffi_env_inherits", (DL_FUNC) &ffi_env_inherits, 2},
86
- {"ffi_env_is_browsed", (DL_FUNC) &ffi_env_is_browsed, 1},
87
{"ffi_env_poke", (DL_FUNC) &ffi_env_poke, 5},
88
{"ffi_env_poke_parent", (DL_FUNC) &ffi_env_poke_parent, 2},
89
{"ffi_env_unbind", (DL_FUNC) &ffi_env_unbind, 3},
tests/testthat/test-env.R
@@ -519,19 +519,6 @@ test_that("get_env() returns the base namespace for primitive functions (r-lib/d
expect_identical(get_env(is.null), ns_env("base"))
})
-test_that("can browse environments", {
- env <- env()
- expect_false(env_is_browsed(env))
- old <- env_browse(env)
- expect_false(old)
- expect_true(env_is_browsed(env))
- old <- env_browse(env, FALSE)
- expect_true(old)
-})
test_that("env_has() doesn't force active bindings (#1292)", {
e <- env()
537
env_bind_active(e, active = function() abort("forced"))
0 commit comments