Skip to content

Commit

Permalink
implement ChildrenOverflow for >100 children
Browse files Browse the repository at this point in the history
  • Loading branch information
t-kalinowski committed Nov 13, 2024
1 parent e91bf80 commit d77cc68
Show file tree
Hide file tree
Showing 3 changed files with 65 additions and 22 deletions.
43 changes: 25 additions & 18 deletions R/ark-variables-methods.R
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ ark_positron_variable_display_type.python.builtin.object <- function(x, ..., inc
i <- .globals$get_positron_variable_inspector(x)
out <- i$get_display_type()

if(startsWith(class(x)[1], "python.builtin."))
if (startsWith(class(x)[1], "python.builtin.")) # display convert value?
out <- paste("python", out)

out
Expand All @@ -44,17 +44,15 @@ ark_positron_variable_get_children.python.builtin.object <- function(x, ...) {

get_keys_and_children <- .globals$ark_variable_get_keys_and_children
if (is.null(get_keys_and_children)) {
get_keys_and_children <- .globals$ark_variable_get_keys_and_children <- py_eval(
"lambda i: zip(*((str(key), i.get_child(key)) for key in i.get_children()))",
convert = FALSE
)
get_keys_and_children <- .globals$ark_variable_get_keys_and_children <-
import("rpytools.ark_variables", convert = FALSE)$get_keys_and_children
}

keys_and_children <- iterate(get_keys_and_children(i), simplify = FALSE)
out <- iterate(keys_and_children[[2L]], simplify = FALSE)
names(out) <- as.character(py_to_r(keys_and_children[[1L]]))
children <- iterate(keys_and_children[[2L]], simplify = FALSE)
names(children) <- as.character(py_to_r(keys_and_children[[1L]]))

out
children
}

#' @param index An integer > 1, representing the index position of the child in the
Expand All @@ -70,16 +68,25 @@ ark_positron_variable_get_child_at.python.builtin.object <- function(x, ..., nam
i <- .globals$get_positron_variable_inspector(x)
get_child <- .globals$ark_variable_get_child
if (is.null(get_child)) {
get_child <- .globals$ark_variable_get_child <- py_run_string(
local = TRUE, convert = FALSE, "
def new_get_child():
from itertools import islice
def get_child(inspector, index):
key = next(islice(inspector.get_children(), index-1, None))
return inspector.get_child(key)
return get_child
")$new_get_child()
get_child <- .globals$ark_variable_get_child <-
import("rpytools.ark_variables", convert = FALSE)$get_child
}

get_child(i, index)
}

get_child(i, index)

ark_positron_variable_display_type.rpytools.ark_variables.ChildrenOverflow <- function(x, ..., include_length = TRUE) {
""
}
ark_positron_variable_kind.rpytools.ark_variables.ChildrenOverflow <- function(x, ...) {
"empty" # other? collection? map? lazy?
}

ark_positron_variable_display_value.rpytools.ark_variables.ChildrenOverflow <- function(x, ..., width = getOption("width")) {
paste(py_to_r(x$n_remaining), "more values")
}

ark_positron_variable_has_children.rpytools.ark_variables.ChildrenOverflow <- function(x, ...) {
FALSE
}
11 changes: 7 additions & 4 deletions R/zzz.R
Original file line number Diff line number Diff line change
Expand Up @@ -84,10 +84,13 @@
"ark_positron_variable_get_child_at",
"ark_positron_variable_get_children"
)) {
method_sym <- as.name(paste0(method_name, ".python.builtin.object"))
.ark.register_method(
method_name, "python.builtin.object",
call(":::", quote(reticulate), method_sym))
for (class_name in c("python.builtin.object",
"rpytools.ark_variables.ChildrenOverflow")) {
method <- get0(paste0(method_name, ".", class_name))
if (!is.null(method)) {
.ark.register_method(method_name, class_name, method)
}
}
}
})
}
Expand Down
33 changes: 33 additions & 0 deletions inst/python/rpytools/ark_variables.py
Original file line number Diff line number Diff line change
@@ -0,0 +1,33 @@
from itertools import islice

MAX_DISPLAY = 100

def get_keys_and_children(inspector):
keys, values = [], []
keys_iterator = iter(inspector.get_children())
# positron frontend only displays the first 100 items, then the length of the rest.
try:
for _ in range(MAX_DISPLAY):
key = next(keys_iterator)
keys.append(str(key))
values.append(inspector.get_child(key))
except StopIteration:
return keys, values

n_remaining = 0
for n_remaining, _ in enumerate(keys_iterator, 1):
pass
if n_remaining > 0:
keys.append("[[...]]")
values.append(ChildrenOverflow(n_remaining))

return keys, values


def get_child(inspector, index):
key = next(islice(inspector.get_children(), index - 1, None))
return inspector.get_child(key)

class ChildrenOverflow:
def __init__(self, n_remaining):
self.n_remaining = n_remaining

0 comments on commit d77cc68

Please sign in to comment.