Skip to content

Commit 70d1c85

Browse files
t-kalinowskihadley
andauthored
Fix custom getters with class_call objects (RConsortium#470)
* print `topNamespaceName()` NULL value * protect call objects from evaluation when calling custom `getter` * add test for call `getter()` * fix custom `getter` on language objects. * allow subsetting `class_call` objects * add tests for custom `setter` on `class_call` objects * tidy; dry; rename helper * Update R/zzz.R Co-authored-by: Hadley Wickham <[email protected]> * Update R/zzz.R Co-authored-by: Hadley Wickham <[email protected]> * Use early return in `topNamespaceName()` for readability --------- Co-authored-by: Hadley Wickham <[email protected]>
1 parent 5e939fb commit 70d1c85

File tree

7 files changed

+165
-17
lines changed

7 files changed

+165
-17
lines changed

R/aaa.R

+5-2
Original file line numberDiff line numberDiff line change
@@ -25,8 +25,11 @@ new_function <- function(args = NULL,
2525

2626
topNamespaceName <- function(env = parent.frame()) {
2727
env <- topenv(env)
28-
if (isNamespace(env))
29-
getNamespaceName(env)
28+
if (!isNamespace(env)) {
29+
return()
30+
}
31+
32+
getNamespaceName(env)
3033
}
3134

3235
is_string <- function(x) {

R/zzz.R

+2-2
Original file line numberDiff line numberDiff line change
@@ -82,9 +82,9 @@ is_S7_type <- function(x) {
8282
}
8383

8484
check_subsettable <- function(x, allow_env = FALSE) {
85-
allowed_types <- c("list", if (allow_env) "environment")
85+
allowed_types <- c("list", "language", "pairlist", if (allow_env) "environment")
8686
if (!typeof(x) %in% allowed_types) {
87-
stop("S7 objects are not subsettable.", call. = FALSE)
87+
stop("S7 objects are not subsettable.")
8888
}
8989
invisible(TRUE)
9090
}

src/init.c

+4
Original file line numberDiff line numberDiff line change
@@ -36,6 +36,8 @@ SEXP sym_dot_should_validate;
3636
SEXP sym_dot_getting_prop;
3737
SEXP sym_dot_setting_prop;
3838

39+
SEXP fn_base_quote;
40+
3941
SEXP ns_S7;
4042

4143

@@ -58,5 +60,7 @@ void R_init_S7(DllInfo *dll)
5860
sym_dot_getting_prop = Rf_install(".getting_prop");
5961
sym_dot_setting_prop = Rf_install(".setting_prop");
6062

63+
fn_base_quote = Rf_eval(Rf_install("quote"), R_BaseEnv);
64+
6165
ns_S7 = Rf_findVarInFrame(R_NamespaceRegistry, Rf_install("S7"));
6266
}

src/prop.c

+69-9
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,8 @@ extern SEXP sym_dot_should_validate;
1818
extern SEXP sym_dot_getting_prop;
1919
extern SEXP sym_dot_setting_prop;
2020

21+
extern SEXP fn_base_quote;
22+
2123
static inline
2224
SEXP eval_here(SEXP lang) {
2325
PROTECT(lang);
@@ -26,6 +28,51 @@ SEXP eval_here(SEXP lang) {
2628
return ans;
2729
}
2830

31+
static inline
32+
SEXP do_call1(SEXP fn, SEXP arg) {
33+
SEXP call, answer;
34+
switch (TYPEOF(arg)) {
35+
case LANGSXP:
36+
case SYMSXP:
37+
arg = PROTECT(Rf_lang2(fn_base_quote, arg));
38+
call = PROTECT(Rf_lang2(fn, arg));
39+
answer = Rf_eval(call, ns_S7);
40+
UNPROTECT(2);
41+
return answer;
42+
default:
43+
call = PROTECT(Rf_lang2(fn, arg));
44+
answer = Rf_eval(call, ns_S7);
45+
UNPROTECT(1);
46+
return answer;
47+
}
48+
}
49+
50+
static inline SEXP do_call2(SEXP fn, SEXP arg1, SEXP arg2) {
51+
int n_protected = 0;
52+
// Protect the arguments from evaluation if they are SYMSXP or LANGSXP
53+
switch (TYPEOF(arg1)) {
54+
case LANGSXP:
55+
case SYMSXP:
56+
arg1 = PROTECT(Rf_lang2(fn_base_quote, arg1));
57+
++n_protected;
58+
}
59+
60+
switch (TYPEOF(arg2)) {
61+
case LANGSXP:
62+
case SYMSXP:
63+
arg2 = PROTECT(Rf_lang2(fn_base_quote, arg2));
64+
++n_protected;
65+
}
66+
67+
SEXP call = PROTECT(Rf_lang3(fn, arg1, arg2));
68+
++n_protected;
69+
70+
SEXP result = Rf_eval(call, ns_S7);
71+
72+
UNPROTECT(n_protected);
73+
return result;
74+
}
75+
2976
static __attribute__((noreturn))
3077
void signal_is_not_S7(SEXP object) {
3178
static SEXP check_is_S7 = NULL;
@@ -207,13 +254,25 @@ void obj_validate(SEXP object) {
207254
if (validate == NULL)
208255
validate = Rf_findVarInFrame(ns_S7, Rf_install("validate"));
209256

210-
eval_here(Rf_lang4(
211-
validate, object,
212-
/* recursive = */ Rf_ScalarLogical(TRUE),
213-
/* properties = */ Rf_ScalarLogical(FALSE)));
214-
}
215-
257+
switch (TYPEOF(object)) {
258+
case LANGSXP:
259+
case SYMSXP: {
260+
// Wrap the call or symbol in quote(), so it doesn't evaluate in Rf_eval()
261+
object = PROTECT(Rf_lang2(fn_base_quote, object));
262+
eval_here(Rf_lang4(validate, object,
263+
/* recursive = */ Rf_ScalarLogical(TRUE),
264+
/* properties = */ Rf_ScalarLogical(FALSE)));
265+
UNPROTECT(1); // object
266+
return;
267+
}
216268

269+
default:
270+
eval_here(Rf_lang4(
271+
validate, object,
272+
/* recursive = */ Rf_ScalarLogical(TRUE),
273+
/* properties = */ Rf_ScalarLogical(FALSE)));
274+
}
275+
}
217276

218277
static inline
219278
Rboolean getter_callable_no_recurse(SEXP getter, SEXP object, SEXP name_sym) {
@@ -248,9 +307,10 @@ SEXP prop_(SEXP object, SEXP name) {
248307
SEXP getter = extract_name(property, "getter");
249308
if (TYPEOF(getter) == CLOSXP &&
250309
getter_callable_no_recurse(getter, object, name_sym)) {
251-
SEXP value = PROTECT(eval_here(Rf_lang2(getter, object)));
310+
311+
SEXP value = PROTECT(do_call1(getter, object));
252312
getter_no_recurse_clear(object, name_sym);
253-
UNPROTECT(1);
313+
UNPROTECT(1); // value
254314
return value;
255315
}
256316

@@ -316,7 +376,7 @@ SEXP prop_set_(SEXP object, SEXP name, SEXP check_sexp, SEXP value) {
316376

317377
if (setter_callable_no_recurse(setter, object, name_sym, &should_validate_obj)) {
318378
// use setter()
319-
REPROTECT(object = eval_here(Rf_lang3(setter, object, value)), object_pi);
379+
REPROTECT(object = do_call2(setter, object, value), object_pi);
320380
setter_no_recurse_clear(object, name_sym);
321381
} else {
322382
// don't use setter()

tests/testthat/_snaps/zzz.md

+4-4
Original file line numberDiff line numberDiff line change
@@ -22,12 +22,12 @@
2222
x <- new_class("foo")()
2323
x[1]
2424
Condition
25-
Error:
25+
Error in `check_subsettable()`:
2626
! S7 objects are not subsettable.
2727
Code
2828
x[1] <- 1
2929
Condition
30-
Error:
30+
Error in `check_subsettable()`:
3131
! S7 objects are not subsettable.
3232

3333
# [[ gives more accurate error
@@ -36,11 +36,11 @@
3636
x <- new_class("foo")()
3737
x[[1]]
3838
Condition
39-
Error:
39+
Error in `check_subsettable()`:
4040
! S7 objects are not subsettable.
4141
Code
4242
x[[1]] <- 1
4343
Condition
44-
Error:
44+
Error in `check_subsettable()`:
4545
! S7 objects are not subsettable.
4646

tests/testthat/helper.R

+5
Original file line numberDiff line numberDiff line change
@@ -140,3 +140,8 @@ dbg <- function(..., .display = utils::str, .file = NULL) {
140140
}
141141

142142
`%error%` <- function(x, y) tryCatch(x, error = function(e) y)
143+
144+
drop_attributes <- function(x) {
145+
attributes(x) <- NULL
146+
x
147+
}

tests/testthat/test-property.R

+76
Original file line numberDiff line numberDiff line change
@@ -444,3 +444,79 @@ test_that("custom setters can call custom getters", {
444444
expect_equal(x@someprop, "FOOFOO")
445445

446446
})
447+
448+
449+
test_that("custom getters don't evaulate call objects", {
450+
QuotedCall := new_class(class_call, properties = list(
451+
name = new_property(getter = function(self) {
452+
stopifnot(is.call(self))
453+
as.character(self[[1]])
454+
}),
455+
args = new_property(getter = function(self) {
456+
stopifnot(is.call(self))
457+
as.list(self)[-1]
458+
})
459+
), constructor = function(x) {
460+
new_object(substitute(x))
461+
})
462+
463+
cl <- QuotedCall(stop("boom"))
464+
expect_equal(cl@name, "stop")
465+
expect_equal(cl@args, list("boom"))
466+
467+
})
468+
469+
470+
test_that("custom setters don't evaulate call objects", {
471+
472+
Call := new_class(class_call, properties = list(
473+
name = new_property(
474+
getter = function(self) {
475+
stopifnot(is.call(self))
476+
as.character(self[[1]])
477+
},
478+
setter = function(self, value) {
479+
stopifnot(is.call(self), is.name(value))
480+
self[[1]] <- value
481+
self
482+
}
483+
),
484+
args = new_property(
485+
getter = function(self) {
486+
stopifnot(is.call(self))
487+
as.list(self)[-1]
488+
},
489+
setter = function(self, value) {
490+
stopifnot(is.call(self), is.list(value) || is.pairlist(value))
491+
# self[seq(2, length.out = length(value))] <- value
492+
# names(self) <- c("", names(value))
493+
# self
494+
out <- as.call(c(self[[1]], value))
495+
attributes(out) <- attributes(self)
496+
out
497+
})
498+
), constructor = function(name, ...) {
499+
new_object(as.call(c(as.name(name), ...)))
500+
})
501+
502+
cl <- Call("stop", "boom")
503+
expect_identical(cl@name, "stop")
504+
expect_identical(cl@args, list("boom"))
505+
506+
abort <- stop
507+
cl@name <- quote(abort)
508+
expect_identical(cl@name, "abort")
509+
expect_identical(cl[[1]], quote(abort))
510+
511+
cl@args <- pairlist("boom2")
512+
expect_identical(cl[[2]], "boom2")
513+
expect_identical(cl@args, list("boom2"))
514+
expect_identical(drop_attributes(cl), quote(abort("boom2")))
515+
516+
cl@args <- alist(msg = "boom3", foo = bar, baz)
517+
expect_identical(cl@args, alist(msg = "boom3", foo = bar, baz))
518+
519+
expect_identical(drop_attributes(cl),
520+
quote(abort(msg = "boom3", foo = bar, baz)))
521+
522+
})

0 commit comments

Comments
 (0)