Skip to content

Commit

Permalink
feat: detect dependencies in R folder
Browse files Browse the repository at this point in the history
  • Loading branch information
ahasverus committed Oct 27, 2023
1 parent eb53dcb commit 1243ace
Show file tree
Hide file tree
Showing 2 changed files with 194 additions and 0 deletions.
1 change: 1 addition & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ Roxygen: list(markdown = TRUE)
RoxygenNote: 7.2.3
Imports:
rstudioapi,
stringr,
usethis,
utils
Suggests:
Expand Down
193 changes: 193 additions & 0 deletions R/utils-deps.R
Original file line number Diff line number Diff line change
Expand Up @@ -153,3 +153,196 @@ get_deps_in_namespace <- function() {

deps
}



#' **Extract and clean list of packages in the R folder**
#'
#' Detect dependencies in R functions written as `foo::bar()`, `library(foo)`,
#' `library("foo")`, `library('foo')`, `require(foo)`, `require("foo")`,
#' `require('foo')`.
#'
#' @return A named `list` of two `character` vectors:
#' - `depends`, packages called with `library(foo)` and `require(foo)`;
#' - `imports`, packages called with `foo:bar()`.
#'
#' If a package is called with `library(foo)` and `foo:bar()`, it will be added
#' only to `depends`.
#'
#' @noRd

get_deps_in_functions_r <- function() {

check_for_descr_file()

path <- path_proj()


## No R/ folder ----

if (!dir.exists(file.path(path, "R"))) {

ui_oops("No {ui_value('R/')} folder found")

return(NULL)
}


r_files <- list.files(path = file.path(path, "R"), pattern = "\\.R$",
full.names = TRUE, ignore.case = TRUE)


## No .R files in R/ ----

if (!length(r_files)) {

ui_oops("The {ui_value('R/')} folder is empty")

return(NULL)

}


## Read R files ----

content <- lapply(r_files, function(x) readLines(con = x, warn = FALSE))


## Remove comments ----

content <- remove_comment_lines(content)


## Remove messages ----

content <- remove_messages(content)


## Functions called as pkg::fun() ----

deps_imports <- get_colon_syntax_deps(content)


## Attached Packages (library & require) ----

deps_depends <- get_attached_deps(content)


## Remove duplicates ----

pos <- which(deps_imports %in% deps_depends)

if (length(pos) > 0) deps_imports <- deps_imports[-pos]


## Remove project name ----

pos <- which(deps_depends == basename(path))
if (length(pos) > 0) deps_depends <- deps_depends[-pos]

pos <- which(deps_imports == basename(path))
if (length(pos) > 0) deps_imports <- deps_imports[-pos]


## Clean objects ----

if (length(deps_depends) == 0) deps_depends <- NULL
if (length(deps_imports) == 0) deps_imports <- NULL

list(
"depends" = deps_depends,
"imports" = deps_imports
)
}



#' **Remove comment lines**
#'
#' Remove comment lines in .R files
#'
#' @noRd

remove_comment_lines <- function(x) {

lapply(x, function(x) {
comments <- grep("^\\s{0,}#", x)
if (length(comments)) x[-comments] else x })
}



#' **Remove messages**
#'
#' Remove messages in `stop()`, `messages()`, `cat()`, `print()`, etc.
#'
#' @noRd

remove_messages <- function(x) {

x <- lapply(x, function(x) gsub("\".{0,}\'.{0,}\'.{0,}\"", "", x))
x <- lapply(x, function(x) gsub("\'.{0,}\".{0,}\".{0,}\'", "", x))
x <- lapply(x, function(x) gsub("\".{0,}\\\".{0,}\\\".{0,}\"", "", x))
x <- lapply(x, function(x) gsub("\'.{0,}\\\'.{0,}\\\'.{0,}\'", "", x))

x
}



#' **Detect packages called with the double colon syntax**
#'
#' Detect packages called with the double colon syntax (i.e. `foo::bar()`).
#'
#' @noRd

get_colon_syntax_deps <- function(x) {

pattern <- paste0("[A-Z|a-z|0-9|\\.]{1,}\\s{0,}",
"::",
"\\s{0,}[A-Z|a-z|0-9|\\.|_]{1,}")

funs <- unlist(lapply(x, function(x) {
unlist(stringr::str_extract_all(x, pattern))
}))

funs <- gsub("\\s", "", funs)

deps <- strsplit(funs, "::")
deps <- lapply(deps, function(x) x[1])
deps <- sort(unique(unlist(deps)))

if (length(deps) == 0) deps <- NULL

deps
}



#' **Detect attached packages**
#'
#' Detect attached packages, i.e. called by `library()` and `require()`.
#'
#' @noRd

get_attached_deps <- function(x) {

pattern <- c(paste0("library\\s{0,}\\(\\s{0,}([A-Z|a-z|0-9|\\.]{1,}|",
"\"\\s{0,}[A-Z|a-z|0-9|\\.]{1,}\\s{0,}\"|",
"\'\\s{0,}[A-Z|a-z|0-9|\\.]{1,}\\s{0,}\')"),
paste0("require\\s{0,}\\(\\s{0,}([A-Z|a-z|0-9|\\.]{1,}|",
"\"\\s{0,}[A-Z|a-z|0-9|\\.]{1,}\\s{0,}\"|",
"\'\\s{0,}[A-Z|a-z|0-9|\\.]{1,}\\s{0,}\')"))
pattern <- paste0(pattern, collapse = "|")

deps <- unlist(lapply(x, function(x) {
unlist(stringr::str_extract_all(x, pattern))
}))

deps <- gsub("\\s", "", deps)
deps <- gsub("library\\(|require\\(|\"|\'", "", deps)

if (length(deps) == 0) deps <- NULL

deps
}

0 comments on commit 1243ace

Please sign in to comment.