Skip to content

Commit 5634e96

Browse files
committed
Remove sexp_named()
1 parent 64f74dd commit 5634e96

File tree

4 files changed

+0
-24
lines changed

4 files changed

+0
-24
lines changed

R/obj.R

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -34,11 +34,6 @@ sexp_address <- obj_address
3434
poke_type <- function(x, type) {
3535
invisible(.Call(ffi_poke_type, x, type))
3636
}
37-
sexp_named <- function(x) {
38-
# Don't use `substitute()` because dots might be forwarded
39-
arg <- match.call(expand.dots = FALSE)$x
40-
.Call(ffi_named, arg, parent.frame())
41-
}
4237

4338
mark_object <- function(x) {
4439
invisible(.Call(ffi_mark_object, x))

src/internal/encoding.c

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,6 @@ r_obj* obj_encode_utf8(r_obj* x) {
3232
default: break;
3333
}
3434

35-
// For performance, avoid `KEEP()` / `FREE()` when not needed
3635
r_obj* attrib = r_attrib(x);
3736
if (attrib != r_null) {
3837
KEEP(x);

src/internal/exported.c

Lines changed: 0 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -806,23 +806,6 @@ r_obj* ffi_promise_value(r_obj* x, r_obj* env) {
806806
}
807807
}
808808

809-
// Picks up symbols from parent environment to avoid bumping namedness
810-
// during promise resolution
811-
r_obj* ffi_named(r_obj* x, r_obj* env) {
812-
int n_kept = 0;
813-
814-
x = PROTECT(Rf_findVarInFrame3(env, x, FALSE));
815-
++n_kept;
816-
817-
if (TYPEOF(x) == PROMSXP) {
818-
x = PROTECT(Rf_eval(x, env));
819-
++n_kept;
820-
}
821-
822-
UNPROTECT(n_kept);
823-
return Rf_ScalarInteger(NAMED(x));
824-
}
825-
826809
r_obj* ffi_find_var(r_obj* env, r_obj* sym) {
827810
return Rf_findVar(sym, env);
828811
}

src/internal/init.c

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -142,7 +142,6 @@ static const R_CallMethodDef r_callables[] = {
142142
{"ffi_lof_unwrap", (DL_FUNC) &ffi_lof_unwrap, 1},
143143
{"ffi_mark_object", (DL_FUNC) &ffi_mark_object, 1},
144144
{"ffi_missing_arg", (DL_FUNC) &ffi_missing_arg, 0},
145-
{"ffi_named", (DL_FUNC) &ffi_named, 2},
146145
{"ffi_names2", (DL_FUNC) &ffi_names2, 2},
147146
{"ffi_names_as_unique", (DL_FUNC) &ffi_names_as_unique, 2},
148147
{"ffi_new_call", (DL_FUNC) &ffi_new_call_node, 2},

0 commit comments

Comments
 (0)