Skip to content

Commit

Permalink
Initial stab at having a general R project scanner
Browse files Browse the repository at this point in the history
Some redundancies already seen here may warrant adding a class or function factories to assist.
  • Loading branch information
al-obrien committed Nov 15, 2023
1 parent 94f55e4 commit 3fb5599
Show file tree
Hide file tree
Showing 7 changed files with 168 additions and 59 deletions.
3 changes: 2 additions & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,8 @@ Imports:
httr2 (>= 1.0.0),
jsonlite,
memoise,
purrr
purrr,
utils
Depends:
R (>= 2.10)
URL: https://al-obrien.github.io/rosv/, https://github.com/al-obrien/rosv
Expand Down
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -16,5 +16,6 @@ export(normalize_pypi_pkg)
export(osv_query)
export(osv_query_1)
export(osv_querybatch)
export(osv_scan)
export(osv_vulns)
importFrom(memoise,memoise)
2 changes: 1 addition & 1 deletion R/query_1.R
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@
#'
#' @seealso \href{https://ossf.github.io/osv-schema/#affectedpackage-field}{Ecosystem list}
#'
#' @examples
#' @examplesIf interactive()
#' osv_query_1(commit = '6879efc2c1596d11a6a6ad296f80063b558d5e0f')
#'
#' @export
Expand Down
138 changes: 138 additions & 0 deletions R/scans.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,138 @@
#' Parse renv LOCK file
#'
#' Parse the LOCK file containing R packages and versions at the provided location.
#'
#' @param dir Directory of project with LOCK file.
#' @param file_name Name of LOCK file (default: 'renv.lock').
#' @param as.data.frame Boolean value, determine if parsed content is in a data.frame format
#'
#' @returns Package and version information as a list of data.frame.
#'
#' @noRd
parse_renv_lock <- function(dir = '.', file_name = 'renv.lock', as.data.frame = TRUE) {

lock_location <- file.path(dir, file_name)
stopifnot(file.exists(lock_location))

lock_n_load <- jsonlite::fromJSON(lock_location)[['Packages']]

if(as.data.frame) {
purrr::list_rbind(purrr::map(lock_n_load,
function(x) {
data.frame(name = purrr::pluck(x, 'Package'),
version = purrr::pluck(x, 'Version'),
ecosystem = 'CRAN')
})
)
} else {
purrr::map(lock_n_load,
function(x) {
c(name = purrr::pluck(x, 'Package'),
version = purrr::pluck(x, 'Version'),
ecosystem = 'CRAN')
})
}
}

#' Parse R installed libraries
#'
#' Parse and return installed libraries discovered at the library paths.
#'
#' @details
#' Default path will be from results of \code{.libPaths()}.
#'
#'
#' @param ... Parameters for \code{\link[utils]{installed.packages()}}.
#'
#' @returns Package and version information as a data.frame.
#'
#' @noRd
parse_r_libpath <- function(...) {
rlibs <- utils::installed.packages(...)[,c('Package', 'Version')]
rlibs <- as.data.frame(rlibs, row.names = FALSE)
colnames(rlibs) <- c('name', 'version')
rlibs <- cbind(rlibs, ecosystem = 'CRAN')
rlibs
}


#' Scan renv LOCK file for vulnerabilities
#'
#' Parse and scan the renv LOCK file at specified location for vulnerabilities in the OSV database.
#'
#' @inheritParams parse_renv_lock
#'
#' @returns A data.frame specifying which packages are vulnerable or not.
#'
#' @noRd
osv_scan_renv <- function(dir = '.', as.data.frame = TRUE) {
pkg_data <- parse_renv_lock(dir = dir, as.data.frame = as.data.frame)
pkg_data$is_vul <- is_pkg_vulnerable(name = pkg_data$name, ecosystem = pkg_data$ecosystem, version = pkg_data$version)
pkg_data
}


#' Scan installed R libraries for vulnerabilities
#'
#' Parse and scan installed R libraries for vulnerabilities in the OSV database.
#'
#' @inheritParams parse_r_libpath
#'
#' @returns A data.frame specifying which packages are vulnerable or not.
#'
#' @noRd
osv_scan_r_libpath <- function(...) {
pkg_data <- parse_r_libpath(...)
pkg_data$is_vul <- is_pkg_vulnerable(name = pkg_data$name, ecosystem = pkg_data$ecosystem, version = pkg_data$version)
pkg_data
}


#' Scan an R project for vulnerabilities
#'
#' Parse and scan LOCK files and installed packages for package vulnerabilities in the OSV database.
#'
#' @param dir Project location.
#' @param sort_by_vul Boolean value, to determine if vulnerable packages should be listed at top.
#'
#' @returns A data.frame specifying which packages are vulnerable or not.
#'
#' @noRd
osv_scan_r_project <- function(dir = '.', sort_by_vul = TRUE) {

# Attempt each and bind
lock_pkgs <- tryCatch(parse_renv_lock(dir = dir),
error = function(e) {warning(e); return(NULL)})

pkg_data <- unique(rbind(parse_r_libpath(), lock_pkgs))

pkg_data$is_vul <- is_pkg_vulnerable(name = pkg_data$name, ecosystem = pkg_data$ecosystem, version = pkg_data$version)

if(sort_by_vul) {
pkg_data[order(pkg_data$is_vul, pkg_data$name, pkg_data$version, decreasing = TRUE),]
} else{
pkg_data[order(pkg_data$name, pkg_data$version),]
}
}


#' Use OSV database to scan for vulnerabilities
#'
#' Scan project based upon specified mode to determine if any vulnerable packages are detected.
#'
#' @param mode The kind of scan to perform.
#' @param ... Parameters passed to specific underlying functions for mode selected.
#'
#' @returns A data.frame specifying which packages are vulnerable or not.
#'
#' @examplesIf interactive()
#' osv_scan('r_libpath')
#'
#' @export
osv_scan <- function(mode, ...) {
switch(mode,
r_project = osv_scan_r_libpath(...),
renv = osv_scan_renv(...),
r_libpath = osv_scan_r_project(...))
}

56 changes: 0 additions & 56 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -279,59 +279,3 @@ filter_affected <- function(data, name = NULL, ecosystem = NULL, version = NULL)

}

#' Parse renv LOCK file
#'
#' Parse the LOCK file containing R packages and versions at the provided location.
#'
#' @param loc Location of the renv LOCK file.
#' @param as.data.frame Boolean value, determine if parsed content is in a data.frame format
#'
#' @returns Package and version information as a list of data.frame.
#'
#' @noRd
parse_renv_lock <- function(loc = NULL, as.data.frame = TRUE) {

if(is.null(loc)) loc <- 'renv.lock'
stopifnot(file.exists(loc))

lock_n_load <- jsonlite::fromJSON(loc)[['Packages']]

if(as.data.frame) {
purrr::list_rbind(purrr::map(lock_n_load,
function(x) {
data.frame(name = pluck(x, 'Package'),
version = pluck(x, 'Version'),
ecosystem = 'CRAN')
})
)
} else {
purrr::map(lock_n_load,
function(x) {
c(name = purrr::pluck(x, 'Package'),
version = purrr::pluck(x, 'Version'),
ecosystem = 'CRAN')
})
}
}

#' Parse R installed libraries
#'
#' Parse and return installed libraries discovered at the library paths.
#'
#' @details
#' Default path will be from results of \code{.libPaths()}.
#'
#'
#' @param ... Parameters for \code{\link[utils]{installed.packages()}}.
#'
#' @returns Package and version information as a data.frame.
#'
#' @noRd
parse_r_libpath <- function(...) {
rlibs <- installed.packages(...)[,c('Package', 'Version')]
rlibs <- as.data.frame(rlibs, row.names = FALSE)
colnames(rlibs) <- c('name', 'version')
rlibs <- cbind(rlibs, ecosystem = 'CRAN')
rlibs
}

3 changes: 2 additions & 1 deletion man/osv_query_1.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

24 changes: 24 additions & 0 deletions man/osv_scan.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit 3fb5599

Please sign in to comment.