Skip to content

Commit

Permalink
Merge pull request #1692 from rstudio/positron-variables-pane-methods
Browse files Browse the repository at this point in the history
Add Positron Variables Pane Methods
  • Loading branch information
t-kalinowski authored Nov 14, 2024
2 parents 5d509e1 + 85cfd0f commit 354a7bb
Show file tree
Hide file tree
Showing 4 changed files with 228 additions and 0 deletions.
3 changes: 3 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,9 @@
- Improved behavior when the conda binary used to create an environment
could not be resolved (contributed by @tl-hbk, #1654, #1659)

- Added Positron support for the Variables Pane and `repl_python()`
(#1692, #1641, #1648, #1658, #1681, #1687).

# reticulate 1.39.0

- Python background threads can now run in parallel with the R session (#1641).
Expand Down
92 changes: 92 additions & 0 deletions R/ark-variables-methods.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,92 @@

# Methods for Populating the Positron/Ark Variables Pane
# These methods primarily delegate to the implementation in the
# Positron python_ipykernel.inspectors python module.

#' @param x Object to get the display value for
#' @param width Maximum expected width. This is just a suggestion, the UI
#' can stil truncate the string to different widths.
ark_positron_variable_display_value.python.builtin.object <- function(x, ..., width = getOption("width")) {
.globals$get_positron_variable_inspector(x)$get_display_value(width)[[1L]]
}


#' @param x Object to get the display type for
#' @param include_length Boolean indicating whether to include object length.
ark_positron_variable_display_type.python.builtin.object <- function(x, ..., include_length = TRUE) {
i <- .globals$get_positron_variable_inspector(x)
out <- i$get_display_type()

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

out
}


#' @param x Object to get the variable kind for
ark_positron_variable_kind.python.builtin.object <- function(x, ...) {
i <- .globals$get_positron_variable_inspector(x)
i$get_kind()
}


#' @param x Check if `x` has children
ark_positron_variable_has_children.python.builtin.object <- function(x, ...) {
i <- .globals$get_positron_variable_inspector(x)
i$has_children()
}

ark_positron_variable_get_children.python.builtin.object <- function(x, ...) {
# Return an R list of children. The order of children should be
# stable between repeated calls on the same object. For example:
i <- .globals$get_positron_variable_inspector(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 <-
import("rpytools.ark_variables", convert = FALSE)$get_keys_and_children
}

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

children
}

#' @param index An integer > 1, representing the index position of the child in the
#' list returned by `ark_variable_get_children()`.
#' @param name The name of the child, corresponding to `names(ark_variable_get_children(x))[index]`.
#' This may be a string or `NULL`. If using the name, it is the method author's responsibility to ensure
#' the name is a valid, unique accessor. Additionally, if the original name from `ark_variable_get_children()`
#' was too long, `ark` may discard the name and supply `name = NULL` instead.
ark_positron_variable_get_child_at.python.builtin.object <- function(x, ..., name, index) {
# cat("name: ", name, "index: ", index, "\n", file = "~/debug.log", append = TRUE)
# This could be implemented as:
# ark_variable_get_children(x)[[index]]
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 <-
import("rpytools.ark_variables", convert = FALSE)$get_child
}

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
}
97 changes: 97 additions & 0 deletions R/zzz.R
Original file line number Diff line number Diff line change
Expand Up @@ -61,9 +61,106 @@
s3_register <- asNamespace("rlang")$s3_register
s3_register("pillar::type_sum", "python.builtin.object")

if (is_positron()) {

setHook("reticulate.onPyInit", function() {

disable <- nzchar(Sys.getenv("_RETICULATE_POSITRON_DISABLE_VARIABLE_INSPECTORS_"))
if (disable)
return()

# options("ark.testing" = TRUE)
inspectors <- tryCatch(import_positron_ipykernel_inspectors(), error = function(e) NULL)
if(is.null(inspectors)) {
# warning("positron_ipykernel.inspectors could not be found, variables pane support for Python objects will be limited")
return()
}

.globals$get_positron_variable_inspector <- inspectors$get_inspector

.ark.register_method <- get(".ark.register_method", envir = globalenv())

for (method_name in c(
"ark_positron_variable_display_value",
"ark_positron_variable_display_type",
"ark_positron_variable_has_children",
"ark_positron_variable_kind",
"ark_positron_variable_get_child_at",
"ark_positron_variable_get_children"
)) {
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)
}
}
}
})
}
}


# .onUnload <- function(libpath) {
# py_finalize() # called from reg.finalizer(.globals) instead.
# }


import_positron_ipykernel_inspectors <- function() {
if(!is_positron())
return (NULL)

tryCatch({
# https://github.com/posit-dev/positron/pull/5368
.ps.ui.executeCommand <- get(".ps.ui.executeCommand", globalenv())
ipykernel_path <- .ps.ui.executeCommand("positron.reticulate.getIPykernelPath")
inspectors <- import_from_path("positron_ipykernel.inspectors",
path = dirname(ipykernel_path))
return(inspectors)
},
error = function(e) NULL)


# hacky "usually work" fallbacks for finding the positron-python extension,
# until ark+positron are updated and can reliably provide the canonical path
# (i.e., until https://github.com/posit-dev/positron/pull/5368 is in the release build)

# Try inspecting `_` env var. Only works in some contexts.
x <- Sys.getenv("_")
# x ==
# on mac: "/Applications/Positron.app/Contents/Resources/app/extensions/positron-r/resources/ark/ark"
if (grepl("positron-r", x, ignore.case = TRUE)) {
inspectors_path <- list.files(
path = sub("positron-r.*$", "positron-python", x),
pattern = "^inspectors.py$",
recursive = TRUE, full.names = TRUE
)
# inspectors_path ==
# on mac: "/Applications/Positron.app/Contents/Resources/app/extensions/positron-python/python_files/positron/positron_ipykernel/inspectors.py"
if (length(inspectors_path) == 1) {
return(import_from_path("positron_ipykernel.inspectors",
path = dirname(dirname(inspectors_path))))

}
}

# vscode/positron-python will place itself on the PATH sometimes
PATH <- Sys.getenv("PATH")
PATH <- strsplit(PATH, .Platform$path.sep, fixed = TRUE)[[1L]]
PATH <- grep("positron-python", PATH, value = TRUE, ignore.case = TRUE)
# PATH ==
# on mac: "/Applications/Positron.app/Contents/Resources/app/extensions/positron-python/python_files/deactivate/zsh"
for (path in PATH) {
inspectors_path <- list.files(
path = sub("^(.*positron-python)(.*)$", "\\1", path),
pattern = "^inspectors.py$",
recursive = TRUE, full.names = TRUE
)
if (length(inspectors_path) == 1) {
return(import_from_path("positron_ipykernel.inspectors",
path = dirname(dirname(inspectors_path))))
}
}

NULL
}
36 changes: 36 additions & 0 deletions inst/python/rpytools/ark_variables.py
Original file line number Diff line number Diff line change
@@ -0,0 +1,36 @@
from itertools import islice

MAX_DISPLAY = 100


def get_keys_and_children(inspector):
# positron frontend only displays the first 100 items, then the count of the rest.
keys, values = [], []
keys_iterator = iter(inspector.get_children())
for key in islice(keys_iterator, MAX_DISPLAY):
keys.append(str(key))
values.append(inspector.get_child(key))

if len(keys) == MAX_DISPLAY:
# check if there are more children
n_children = inspector.get_length()
if n_children == 0:
# no len() method, finish iteratoring over keys_iterator to get the true size
for n_children, _ in enumerate(keys_iterator, MAX_DISPLAY + 1):
pass
n_remaining = n_children - MAX_DISPLAY
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 354a7bb

Please sign in to comment.