Skip to content

Commit

Permalink
Standardise audit functions; fixes #28 (#30)
Browse files Browse the repository at this point in the history
  • Loading branch information
csgillespie authored Oct 20, 2020
1 parent 48e9c33 commit d1bc1d5
Show file tree
Hide file tree
Showing 28 changed files with 213 additions and 163 deletions.
1 change: 1 addition & 0 deletions .Rbuildignore
Original file line number Diff line number Diff line change
Expand Up @@ -12,3 +12,4 @@
^CONTRIBUTORS\.md$
^docs/
^\.idea
^codecov\.yml$
5 changes: 5 additions & 0 deletions .travis.yml
Original file line number Diff line number Diff line change
Expand Up @@ -5,3 +5,8 @@ r:
- oldrel
- release
- devel

after_success: >
test $TRAVIS_PULL_REQUEST == "false" &&
test $TRAVIS_BRANCH == "master" &&
Rscript -e 'covr::codecov()'
3 changes: 2 additions & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,8 @@ Suggests:
httptest,
knitr,
rmarkdown,
testthat (>= 2.1.0)
testthat (>= 2.1.0),
covr
Encoding: UTF-8
LazyData: true
Roxygen: list(markdown = TRUE)
Expand Down
3 changes: 2 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
@@ -1,7 +1,8 @@
# Generated by roxygen2: do not edit by hand

export(audit)
export(audit_deps)
export(audit_pkgs)
export(audit_installed_r_pkgs)
export(audit_renv_lock)
export(audit_req_txt)
export(get_vulnerabilities)
Expand Down
2 changes: 1 addition & 1 deletion R/api_call.R
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ get_post_authenticate = function(verbose) {
}

no_purls_case = function(verbose) {
results = tibble::tibble(package = character(0), description = character(0),
results = tibble::tibble(oss_package = character(0), description = character(0),
reference = character(0), vulnerabilities = list(),
no_of_vulnerabilities = integer(0))
class(results) = c("oysteR_deps", class(results))
Expand Down
77 changes: 37 additions & 40 deletions R/audit_deps.R → R/audit.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,59 +12,56 @@
# See the License for the specific language governing permissions and
# limitations under the License."

#' Check Package Dependencies
#' Search for Package Vulnerabilities
#'
#' Collects R dependencies and checks them against OSS Index.
#' Returns a tibble of results.
#' Search the OSS Index for known package vulnerabilities in any of the supported ecosystems—
#' e.g. CRAN, PyPI, Conda, NPM, Maven, etc.
#' see https://ossindex.sonatype.org/ecosystems for full list.
#'
#' @details By default, packages listed in \code{installed.packages()} are scanned by sonatype.
#' However, you can pass your own data frame of packages. This data frame should have two columns,
#' \code{version} and \code{package}.
#' @param pkgs Default \code{NULL}. See details for further information.
#' @param pkg A vector of package names to search in the OSS Index.
#' @param version The specific package version to search for.
#' By default it will search all known versions. If not `*`, must be the same length as pkg.
#' @param type The package management environment. For R packages, set equal to "cran".
#' This defaults to \code{"cran"}. See https://ossindex.sonatype.org/ecosystems.
#' @param verbose Default \code{TRUE}.
#' @return A tibble/data.frame.
#'
#' @export
#' @examples
#' \donttest{
#' # Audit installed packages
#' # This calls installed.packages()
#' # pkgs = audit_deps()
#'
#' # Or pass your own packages
#' pkgs = data.frame(package = c("abind", "acepack"),
#' version = c("1.4-5", "1.4.1"))
#' audit_deps(pkgs)
#' pkg = c("abind", "acepack")
#' version = c("1.4-5", "1.4.1")
#' audit(pkg, version, type = "cran")
#' }
audit_deps = function(pkgs = NULL, verbose = TRUE) {
pkgs = get_pkgs(pkgs = pkgs, verbose = verbose)
purls = get_purls(pkgs = pkgs)
results = call_oss_index(purls, verbose = verbose)
audit = function(pkg, version, type, verbose = TRUE) {

if (is.null(pkg)) pkg = character(0)
if (is.null(version)) version = character(0)
# Create the purls. Checks will be inherited
purls = generate_purls(pkg, version, type)
results = call_oss_index(purls, verbose = verbose)
if (isTRUE(verbose)) {
audit_deps_verbose(results)
audit_verbose(results)
}
dplyr::bind_cols(pkgs, results)

audit = dplyr::bind_cols(tibble::tibble(package = pkg, version = version, type = type),
results)
return(audit)
}

#' Search for package vulnerabilities
#'
#' Search the OSS Index for known package vulnerabilities in any of the supported ecosystems—
#' e.g. CRAN, PyPI, Conda, NPM, Maven, etc.
#' see https://ossindex.sonatype.org/ecosystems for full list.
#' Check Package Dependencies
#'
#' @param pkg A vector of package names to search in the OSS Index.
#' @param version The specific package version to search for.
#' By default it will search all known versions. If not `*`, must be the same length as pkg.
#' @param type The package management environment.
#' This defaults to \code{"cran"}. See https://ossindex.sonatype.org/ecosystems.
#' Collects R dependencies by calling \code{installed.packages}
#' and checks them against OSS Index.
#' @param verbose Default \code{TRUE}.
#'
#' @return A tibble/data.frame.
#' @importFrom utils installed.packages
#' @export
audit_pkgs = function(pkg, version = "*", type = "cran", verbose = TRUE) {

# create the purls. Checks will be inherited
purls = gen_purls(pkg, version, type)
audit = call_oss_index(purls, verbose = verbose)
return(audit)
#' @examples
#' \donttest{
#' # Audit installed packages
#' # This calls installed.packages()
#' pkgs = audit_installed_r_pkgs()
#' }
audit_installed_r_pkgs = function(verbose = TRUE) {
pkgs = get_r_pkgs(verbose = verbose)
audit(pkg = pkgs$package, version = pkgs$version, type = "cran", verbose = verbose)
}
20 changes: 20 additions & 0 deletions R/deprecated.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
#' Check Package Dependencies
#'
#' Collects R dependencies and checks them against OSS Index.
#' Returns a tibble of results.
#'
#' This function is deprecated. See
#' @details By default, packages listed in \code{installed.packages()} are scanned by sonatype.
#' However, you can pass your own data frame of packages. This data frame should have two columns,
#' \code{version} and \code{package}.
#' @param pkgs Default \code{NULL}. See details for further information.
#' @param verbose Default \code{TRUE}.
#' @return A tibble/data.frame.
#' @export
audit_deps = function(pkgs = NULL, verbose = TRUE) {
.Deprecated("audit_install_pkgs")
if (is.null(pkgs))
audit_installed_r_pkgs(verbose = verbose)
else
audit(pkgs$package, version = pkgs$version, type = "cran", verbose = verbose)
}
27 changes: 18 additions & 9 deletions R/file_audits.R
Original file line number Diff line number Diff line change
@@ -1,9 +1,8 @@
#' Audit an renv.lock file.
#' Audit an renv.lock File
#'
#' This function searches the OSS index for vulnerabilities recorded for packages listed in
#' an `renv.lock` file.
#'
#' An `renv.lock` file is created by the `{renv}` package (https://rstudio.github.io/renv/)
#' An `renv.lock` file is created by the `{renv}` package
#' which is used for project level package management in R.
#'
#' @param dir The file path of an renv.lock file.
Expand All @@ -15,15 +14,24 @@
#' @importFrom purrr map_chr pluck
#' @importFrom rlang .data
#' @export
#' @examples
#' \donttest{
#' # Looks for renv.lock file in dir
#' audit_renv_lock(dir = ".")
#' }
audit_renv_lock = function(dir = ".", verbose = TRUE) {
renv_file = file.path(dir, "renv.lock")
renv_lock = jsonlite::read_json(renv_file)
renv_pkgs = purrr::map_chr(renv_lock$Packages, purrr::pluck, "Version")
pkgs = tibble::tibble(package = names(renv_pkgs), version = renv_pkgs)
audit_deps(pkgs, verbose = verbose)
if (!file.exists(renv_file)) {
cli::cli_alert_info("No renv.lock found")
renv_pkgs = NULL
} else {
renv_lock = jsonlite::read_json(renv_file)
renv_pkgs = purrr::map_chr(renv_lock$Packages, purrr::pluck, "Version")
}
audit(pkg = names(renv_pkgs), version = renv_pkgs, type = "cran", verbose = verbose)
}

#' Audit a requirements.txt file.
#' Audit a requirements.txt File
#'
#' This function searches the OSS index for vulnerabilities recorded for packages listed
#' in a requirements.txt file based on PyPi.
Expand All @@ -45,9 +53,10 @@ audit_req_txt = function(dir = ".", verbose = TRUE) {
audit = readLines(req_file) %>%
strsplit(">=|==|>") %>%
map_dfr(~tibble::tibble(package = .x[1], version = .x[2])) %>%
mutate(audit_pkgs(.data$package, .data$version, type = "pypi", verbose = verbose))
mutate(audit(pkg = .data$package, version = .data$version, type = "pypi", verbose = verbose))
return(audit)
}



# TO DO: environment.yml for Conda
4 changes: 2 additions & 2 deletions R/get_vulnerabilities.R
Original file line number Diff line number Diff line change
Expand Up @@ -29,8 +29,8 @@
#' # Or pass your own packages
#' pkgs = data.frame(package = c("abind", "acepack"),
#' version = c("1.4-5", "1.4.1"))
#' deps = audit_deps(pkgs)
#' get_vulnerabilities(deps)
#' #deps = audit_deps(pkgs)
#' #get_vulnerabilities(deps)
#' }
get_vulnerabilities = function(audit) {
if (sum(audit$no_of_vulnerabilities) == 0) {
Expand Down
2 changes: 1 addition & 1 deletion R/print.R
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@

globalVariables(c("no_of_pkgs", "no_of_vul", "no_of_vul_comps", "pkgs_in_sona"))
#' @import cli
audit_deps_verbose = function(results) {
audit_verbose = function(results) {
no_of_pkgs = nrow(results)
no_of_vul_comps = sum(results$no_of_vulnerabilities != 0)
no_of_vul = sum(results$no_of_vulnerabilities)
Expand Down
41 changes: 16 additions & 25 deletions R/utils.R
Original file line number Diff line number Diff line change
@@ -1,53 +1,44 @@
#' Function to generate purls
#'
#' Generates purls from a vector of package names, version, and type. `version` and `type`
#' must be the same length as `pkg` or else be of length one.
#' Generates purls from a vector of package names, version, and type. `version`
#' must be the same length as `pkg`.
#' `type` must of the same length or else be of length one.
#'
#' @keywords internal
gen_purls = function(pkg, version = "*", type = "cran") {

generate_purls = function(pkg, version, type) {
# Add in safety net
if ((is.null(pkg) && is.null(version)) ||
(length(pkg) == 0L && length(version) == 0L)) return(list())
# Institute checks for both version and type.
# type and version must be the same length as pkg or
# of length 1.
if ((length(type) > length(pkg)) && (length(type) != 1L)) {
stop("`type` must be length 1 or same length as `pkg`.", call. = FALSE)
if (length(pkg) != length(version)) {
stop("pkgs must be the same length as version.", call. = FALSE)
}
if ((length(version) > length(pkg)) && (length(version) != 1L)) {
stop("`version` must be length 1 or same length as `pkg`.", call. = FALSE)
if ((length(type) != 1L) && (length(pkg) != length(type))) {
stop("type must be 1 or the same length as pkgs", call. = FALSE)
}

# List format required for httr call
# The list translates to the body of the curl call
# Each purl must be it's own list element hence the use of as.list over list
purls = as.list(paste0("pkg:", type, "/", pkg, "@", version))
return(purls)
}


#' Get data frame of installed packages
#'
#' @importFrom tibble as_tibble tibble
#' @keywords internal
get_pkgs = function(pkgs = NULL, verbose = TRUE) {
if (!is.null(pkgs)) return(pkgs)

get_r_pkgs = function(verbose = TRUE) {
if (isTRUE(verbose)) {
cli::cli_alert_info("Calling {.pkg installed.packages()}, this may take time")
}
pkgs = tibble::as_tibble(installed.packages()[, c(1, 3:4)])

# ensuring all packages are included including base and recommended
pkgs = pkgs[, c("Package", "Version")]
pkgs = tibble::as_tibble(installed.packages()[, c(1, 3)])
# XXX: Remove line when audit_dep is removed
colnames(pkgs) = c("package", "version")
return(pkgs)
}

#' Create a list of purls based on installed packages
#'
#' @importFrom utils installed.packages
#' @keywords internal
get_purls = function(pkgs) {
if (nrow(pkgs) == 0) return(list())

# Extract Package and Version columns
purls = gen_purls(pkg = pkgs$package, version = pkgs$version, type = "cran")
return(purls)
}
2 changes: 1 addition & 1 deletion R/zzz.R
Original file line number Diff line number Diff line change
Expand Up @@ -14,5 +14,5 @@

.onAttach = function(...) { #nolint
if (!interactive()) return()
packageStartupMessage("See https://github.com/sonatype-nexus-community/oysteR/ for details.")
packageStartupMessage("See https://github.com/sonatype-nexus-community/oysteR/ for details.") # nocov
}
3 changes: 2 additions & 1 deletion README.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ editor_options:
[![CircleCI](https://circleci.com/gh/sonatype-nexus-community/oysteR.svg?style=shield)](https://circleci.com/gh/sonatype-nexus-community/oysteR)
[![Travis build status](https://travis-ci.org/sonatype-nexus-community/oysteR.svg?branch=master)](https://travis-ci.org/sonatype-nexus-community/oysteR)
[![Gitter](https://badges.gitter.im/sonatype-nexus-community/oysteR.svg)](https://gitter.im/sonatype-nexus-community/oysteR?utm_source=badge&utm_medium=badge&utm_campaign=pr-badge)
[![Codecov test coverage](https://codecov.io/gh/sonatype-nexus-community/oysteR/branch/master/graph/badge.svg)](https://codecov.io/gh/sonatype-nexus-community/oysteR?branch=master)

```{r, include = FALSE}
knitr::opts_chunk$set(
Expand All @@ -33,7 +34,7 @@ vulnerabilities

```{r, eval = FALSE}
library("oysteR")
audit = audit_deps()
audit = audit_installed_r_pkgs()
```
To extract the vulnerabilities into a nice data frame, use
```{r, eval = FALSE}
Expand Down
4 changes: 3 additions & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,8 @@ status](https://www.r-pkg.org/badges/version/oysteR)](https://CRAN.R-project.org
[![Travis build
status](https://travis-ci.org/sonatype-nexus-community/oysteR.svg?branch=master)](https://travis-ci.org/sonatype-nexus-community/oysteR)
[![Gitter](https://badges.gitter.im/sonatype-nexus-community/oysteR.svg)](https://gitter.im/sonatype-nexus-community/oysteR?utm_source=badge&utm_medium=badge&utm_campaign=pr-badge)
[![Codecov test
coverage](https://codecov.io/gh/sonatype-nexus-community/oysteR/branch/master/graph/badge.svg)](https://codecov.io/gh/sonatype-nexus-community/oysteR?branch=master)

Create purls from the filtered sands of your dependencies, powered by
[OSS Index](https://ossindex.sonatype.org/)
Expand All @@ -21,7 +23,7 @@ vulnerabilities

``` r
library("oysteR")
audit = audit_deps()
audit = audit_installed_r_pkgs()
```

To extract the vulnerabilities into a nice data frame, use
Expand Down
14 changes: 14 additions & 0 deletions codecov.yml
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
comment: false

coverage:
status:
project:
default:
target: auto
threshold: 1%
informational: true
patch:
default:
target: auto
threshold: 1%
informational: true
19 changes: 13 additions & 6 deletions man/audit_pkgs.Rd → man/audit.Rd

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

Loading

0 comments on commit d1bc1d5

Please sign in to comment.