--- title: R object browser functions --- # Helpers ## Get object Get an object from its full qualifying name (*fullname*). ```{r get object} ##' Get an object ##' ##' Get an object from its fullname ##' @title Get an object ##' @param fullname A string with the fullname of an object ##' @return The object get_object <- function(fullname) eval(parse(text = fullname)) ``` ## Get name Get the printing name of an object given its identifier. Identifiers come in **quoted** if the object is named, or as an **index** number. The printing name is unquoted or surrounded with double brackets if an index. ```{r get name} ##' Get an object name ##' ##' Return the printing name of an object as given to print_object ##' @title ##' @param identifier An object identifier string ##' @return The name of the object or its index in brackets get_name <- function(identifier) { if (substr(identifier, 1, 1) == "\"") substr(identifier, 2, nchar(identifier) - 1) else paste0("[[", identifier, "]]") } ``` ## Get fullname Get the fullname of an object given its identifier and fullname of the parent ```{r get fullname} ##' Get an object fullname ##' ##' Get the fullname of an object ##' by prepending its parent and indexing by name/position ##' @title Get fullname ##' @param identifier An object identifier string ##' @param parent A string with the name of the parent ##' @return The full object name get_fullname <- function(identifier, parent) { if (substr(parent, nchar(parent) - 1, nchar(parent)) == "::") # If part of a package fullname <- paste0(parent, gsub("\"", "`", identifier)) # replace quotes with backticks and prepend the package else fullname <- paste0(parent, "[[", identifier, "]]") # else index the parent by name/position with double brackets tryCatch(get_object(fullname), # If the object is not exported, use three colons error = function(e) fullname <<- gsub("::", ":::", fullname)) fullname } ``` ## Get type Get the type / class / mode of an object given its fullname. ```{r get type} ##' Get type of an object ##' ##' Get the type of an object ##' @title Get object type ##' @param fullname A string with the fullname of an object ##' @return The type of the object get_type <- function(fullname) class(get_object(fullname))[[1]] # Get the first class of the # object. This works for matrices, but # not for tibbles… ``` ## Get size Get the size of an object given its fullname. - environments, pkg, list : length - dataframe, matrix : ncol × nrow - function : args - default : length ```{r get size} ##' Get an object size ##' ##' Get the size of an object: ##' - list : length ##' - dataframe : nrow × length ##' - ##' @title ##' @param fullname A string with the fullname of an object ##' @param type The type of the object ##' @return The size of the object get_size <- function(fullname, type) { object <- get_object(fullname) switch(type, "environment" = length(objects(object)), "pkg" = length(objects(object)), "data.frame" = paste0(ncol(object), " × ", nrow(object)), "tbl_df" = paste0(ncol(object), " × ", nrow(object)), "matrix" = paste0(ncol(object), " × ", nrow(object)), "function" = length(formals(object)), length(object)) } ``` # Printers These functions return the line to print in the emacs buffer for different objects. ## Package Print a package: **package name**|pkg| **package name** ```{r print package} ##' Print a package ##' ##' Display the fullname of the package, ##' the type, and the name with the size. ##' @title Print a package ##' @param pkg The package to print ##' @return The line to print to the buffer print_package <- function(pkg) paste0(pkg, "|pkg| ", pkg) ``` ## searchlist Print a searchlist: **environment name**|env| **environment name** (*number of objects in the environment*) **Could be replaced by print_object** ```{r print searchlist} ##' Print an environment ##' ##' Display the fullname of the environment, ##' the type, and the name with the size. ##' @title Print an environment ##' @param env The environment to print ##' @return The line to print to the buffer print_searchlist <- function(env) paste0(env, "|environment| ", env, " (", length(objects(env)), ")") ``` ## Objects Print other objects: **object full qualifying nume**|*type*| **object name** (*number of objects in the container, dimensions for df and matrices, number of args in a function*) ```{r print object} ##' Print an object ##' ##' Display the fullname of an object, ##' the type, and the name with the size ##' ##' If the parent is "" then it is a base name, ##' else we construct the fullname by subsetting by name/position ##' Thus the caller needs to build the object name accordingly. ##' @title Print an object ##' @param identifier The identifier of the object to print ##' @param parent The parent object ##' @return The line to print to the buffer print_object <- function(identifier, parent = "") { full_name <- get_fullname(identifier, parent) type <- get_type(full_name) paste0(full_name, "|", type, "| ", get_name(identifier), " (", get_size(full_name, type), ")") } ``` # List objects List different objects and their contents. ## Packages ### List packages List all installed packages. ```{r list packages} ##' List packages ##' ##' List all the installed packages ##' @title List packages ##' @return A character vector of packages list_packages <- function() sapply(row.names(installed.packages()), print_package, USE.NAMES = F, simplify = T) ``` ### List package contents Print all the objects in a package. Parent is *package::* The names are quoted. The generic print_object function is used. Pourrait être remplacé par list_container_contents du même trait que pour list_searchlist_contents ```{r list package contents} ##' List package contents ##' ##' .. content for \details{} .. ##' @title List package contents ##' @param package Name of the package as a string ("dplyr") ##' @return char vector of contents of package list_package_contents <- function(package) { parent = paste0(package, "::") objects <- paste0("\"", objects(asNamespace(package)), "\"") mapply(print_object, objects, parent, USE.NAMES = F, SIMPLIFY = T) } ``` ## searchlist ### searchlist List all objects on the search list. print_searchlist could be replaced by print_object ```{r list searchlist} ##' List searchlist ##' ##' List environments as returned by `search()`, ##' but ommiting `ESSR` from ESS, and the `Autoloads`, ##' as they contain only hidden objects and have length=0 ##' @title List searchlist ##' @return A character vector of environments list_searchlist <- function() { sapply(setdiff(search(), c("ESSR", "Autoloads")), print_searchlist, USE.NAMES = F, simplify = T) } ``` ### List searchlist contents List the contents of the searchlist. Pourrait être remplacé par list_container_contents Si le parsing de "package:" est fait dans get_object et fix_names ? ```{r list searchlist contents} ##' List environment contents ##' ##' List environement contents. ##' Works with ".GlobalEnv", and "package:stats" ##' @title List environment contents ##' @name Name of the environment as character ##' @return A character vector of objects in the environment list_searchlist_contents <- function(env) { if (substring(env, 1, 8) == "package:") parent <- paste0(substring(env, 9), "::") else parent <- env objects <- paste0("\"", objects(env), "\"") mapply(print_object, objects, parent, USE.NAMES = F, SIMPLIFY = T) } ``` ## Containers ### Fix names Fix the names given by `ls` and create identifiers. If a name exists, surround it with quotes. If a name doesn't exist, replace it by its index. ```{r fix names} fix_names <- function(object) { indexes <- 1:length(object) names_out <- names(object) names_out[(names(object) == "") | is.na(names(object))] <- indexes[(names(object) == "") | is.na(names(object))] names_out[!(names(object) == "") | is.na(names(object))] <- paste0("\"", names_out[!(names(object) == "") | is.na(names(object))], "\"") names_out } ``` ### container ```{r list container contents} list_container_contents <- function(fullname) { mapply(print_object, fix_names(get_object(fullname)), fullname, USE.NAMES = F, SIMPLIFY = T) } ```