From 58e84ac477e8700c87e91458b3f437b5dd16b877 Mon Sep 17 00:00:00 2001 From: Barret Schloerke Date: Thu, 6 Aug 2020 13:21:15 -0400 Subject: [PATCH] Add `plumb_api()` and `available_apis()` (#631) Co-authored-by: Barret Schloerke Co-authored-by: Carson Sievert --- .Rbuildignore | 2 +- .github/workflows/docker.yaml | 1 + DESCRIPTION | 4 +- Dockerfile | 12 +- NAMESPACE | 6 +- NEWS.md | 10 +- R/digital-ocean.R | 4 +- R/includes.R | 8 +- R/openapi-spec.R | 2 +- R/plumb-block.R | 2 +- R/plumb.R | 260 ++++++++++++++++++ R/plumber.R | 106 ++----- R/session-cookie.R | 4 +- inst/examples/03-github/Dockerfile | 5 - inst/examples/06-sessions/Dockerfile | 6 - inst/examples/07-mailgun/Dockerfile | 5 - inst/examples/12-entrypoint/entrypoint.R | 5 - inst/hosted-new.R | 10 +- .../{examples => plumber}/01-append/plumber.R | 0 .../02-filters/plumber.R | 0 .../03-github/.gitignore | 0 inst/plumber/03-github/Dockerfile | 5 + .../{examples => plumber}/03-github/plumber.R | 0 .../04-mean-sum/plumber.R | 0 .../{examples => plumber}/05-static/README.md | 0 .../05-static/files/a.html | 0 .../05-static/files/b.txt | 0 .../{examples => plumber}/05-static/plumber.R | 0 inst/plumber/06-sessions/Dockerfile | 5 + .../06-sessions/plumber.R | 2 +- .../06-sessions/static/iframe-secure.html | 0 .../06-sessions/static/iframe.html | 0 .../06-sessions/static/js-cookie.js | 0 inst/plumber/07-mailgun/Dockerfile | 5 + .../07-mailgun/plumber.R | 0 .../08-identity/plumber.R | 0 .../09-content-type/plumber.R | 0 .../10-welcome/plumber.R | 0 .../11-car-inventory/inventory.csv | 0 .../11-car-inventory/plumber.R | 0 inst/plumber/12-entrypoint/entrypoint.R | 10 + .../12-entrypoint/myplumberapi.R | 0 .../plumber/12-entrypoint/using_plumber_tag.R | 23 ++ .../13-promises/plumber.R | 0 .../{examples => plumber}/14-future/plumber.R | 0 .../14-future/test-future.R | 4 +- .../15-openapi-spec/entrypoint.R | 7 +- .../16-attachment/plumber.R | 0 man-roxygen/param_pr.R | 2 +- man/include_file.Rd | 5 +- man/plumb.Rd | 27 ++ man/plumb_api.Rd | 34 +++ man/plumber.Rd | 26 +- man/pr_cookie.Rd | 2 +- man/pr_filter.Rd | 2 +- man/pr_handle.Rd | 2 +- man/pr_hook.Rd | 2 +- man/pr_run.Rd | 2 +- man/pr_set_404.Rd | 2 +- man/pr_set_api_spec.Rd | 2 +- man/pr_set_debug.Rd | 2 +- man/pr_set_error.Rd | 2 +- man/pr_set_parsers.Rd | 2 +- man/pr_set_serializer.Rd | 2 +- man/pr_set_ui.Rd | 2 +- man/pr_set_ui_callback.Rd | 2 +- man/sessionCookie.Rd | 4 +- package.json | 2 +- pkgdown/_pkgdown.yml | 2 + scripts/manual_testing.R | 2 +- tests/testthat/helper-for-each-plumber-api.R | 25 ++ tests/testthat/test-openapi.R | 37 +-- tests/testthat/test-plumb_api.R | 80 ++++++ tests/testthat/test-zzz-include.R | 4 +- vignettes/hosting.Rmd | 4 +- 75 files changed, 579 insertions(+), 214 deletions(-) create mode 100644 R/plumb.R delete mode 100644 inst/examples/03-github/Dockerfile delete mode 100644 inst/examples/06-sessions/Dockerfile delete mode 100644 inst/examples/07-mailgun/Dockerfile delete mode 100644 inst/examples/12-entrypoint/entrypoint.R rename inst/{examples => plumber}/01-append/plumber.R (100%) rename inst/{examples => plumber}/02-filters/plumber.R (100%) rename inst/{examples => plumber}/03-github/.gitignore (100%) create mode 100644 inst/plumber/03-github/Dockerfile rename inst/{examples => plumber}/03-github/plumber.R (100%) rename inst/{examples => plumber}/04-mean-sum/plumber.R (100%) rename inst/{examples => plumber}/05-static/README.md (100%) rename inst/{examples => plumber}/05-static/files/a.html (100%) rename inst/{examples => plumber}/05-static/files/b.txt (100%) rename inst/{examples => plumber}/05-static/plumber.R (100%) create mode 100644 inst/plumber/06-sessions/Dockerfile rename inst/{examples => plumber}/06-sessions/plumber.R (96%) rename inst/{examples => plumber}/06-sessions/static/iframe-secure.html (100%) rename inst/{examples => plumber}/06-sessions/static/iframe.html (100%) rename inst/{examples => plumber}/06-sessions/static/js-cookie.js (100%) create mode 100644 inst/plumber/07-mailgun/Dockerfile rename inst/{examples => plumber}/07-mailgun/plumber.R (100%) rename inst/{examples => plumber}/08-identity/plumber.R (100%) rename inst/{examples => plumber}/09-content-type/plumber.R (100%) rename inst/{examples => plumber}/10-welcome/plumber.R (100%) rename inst/{examples => plumber}/11-car-inventory/inventory.csv (100%) rename inst/{examples => plumber}/11-car-inventory/plumber.R (100%) create mode 100644 inst/plumber/12-entrypoint/entrypoint.R rename inst/{examples => plumber}/12-entrypoint/myplumberapi.R (100%) create mode 100644 inst/plumber/12-entrypoint/using_plumber_tag.R rename inst/{examples => plumber}/13-promises/plumber.R (100%) rename inst/{examples => plumber}/14-future/plumber.R (100%) rename inst/{examples => plumber}/14-future/test-future.R (94%) rename inst/{examples => plumber}/15-openapi-spec/entrypoint.R (87%) rename inst/{examples => plumber}/16-attachment/plumber.R (100%) create mode 100644 man/plumb.Rd create mode 100644 man/plumb_api.Rd create mode 100644 tests/testthat/helper-for-each-plumber-api.R create mode 100644 tests/testthat/test-plumb_api.R diff --git a/.Rbuildignore b/.Rbuildignore index 059ef3b01..6c937b0df 100644 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -4,7 +4,7 @@ ^\.travis\.yml$ ^Dockerfile ^inst/analog-keys.R -^inst/examples/03-github/github-key.txt +^inst/plumber/03-github/github-key.txt ^\.httr-oauth ^docs ^scripts diff --git a/.github/workflows/docker.yaml b/.github/workflows/docker.yaml index e7f2abcd7..1abdbe031 100644 --- a/.github/workflows/docker.yaml +++ b/.github/workflows/docker.yaml @@ -25,6 +25,7 @@ jobs: # always overwrite the latest version with the CRAN version tags: "v0.4.6,latest" ref: "v0.4.6" + extra_build_args: ",ENTRYPOINT_FILE='/usr/local/lib/R/site-library/plumber/examples/04-mean-sum/plumber.R'" - name: GitHub # 'next' tag signifies the _next_ release diff --git a/DESCRIPTION b/DESCRIPTION index cc95a5a75..ed134ba31 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -42,7 +42,8 @@ Suggests: later, readr, yaml, - feather + feather, + future Remotes: rstudio/swagger RoxygenNote: 7.1.1 @@ -65,6 +66,7 @@ Collate: 'paths.R' 'plumb-block.R' 'plumb-globals.R' + 'plumb.R' 'plumber-options.R' 'plumber-response.R' 'shared-secret-filter.R' diff --git a/Dockerfile b/Dockerfile index 9e0c3183c..a3b8b38c6 100644 --- a/Dockerfile +++ b/Dockerfile @@ -4,8 +4,6 @@ ARG R_VERSION=latest FROM rocker/r-ver:${R_VERSION} LABEL maintainer="barret@rstudio.com" -ARG PLUMBER_REF=master - # BEGIN rstudio/plumber layers RUN apt-get update -qq && apt-get install -y --no-install-recommends \ git-core \ @@ -21,13 +19,17 @@ RUN install2.r remotes ## https://stackoverflow.com/a/55621942/591574 #ADD https://github.com/rstudio/plumber/commits/ _docker_cache +ARG PLUMBER_REF=master RUN Rscript -e "remotes::install_github('rstudio/plumber@${PLUMBER_REF}')" EXPOSE 8000 - ENTRYPOINT ["R", "-e", "pr <- plumber::plumb(rev(commandArgs())[1]); pr$run(host='0.0.0.0', port=8000, swagger=TRUE)"] -CMD ["/usr/local/lib/R/site-library/plumber/examples/04-mean-sum/plumber.R"] +# Copy installed example to default file at ~/plumber.R +ARG ENTRYPOINT_FILE=/usr/local/lib/R/site-library/plumber/plumber/04-mean-sum/plumber.R +RUN cp ${ENTRYPOINT_FILE} ~/plumber.R + +CMD ["~/plumber.R"] # EOF rstudio/plumber layers @@ -43,7 +45,7 @@ CMD ["/usr/local/lib/R/site-library/plumber/examples/04-mean-sum/plumber.R"] # firefox http://localhost:8000/__swagger__/ & # to run with your own api - mount your plumber.R file into the container like so: -# docker run -it -p 8000:8000 --rm -v ~/R/x86_64-pc-linux-gnu-library/4.0/plumber/examples/10-welcome/plumber.R:/api/plumber.R:ro --name myapi rstudio/plumber:latest /api/plumber.R +# docker run -it -p 8000:8000 --rm -v ~/R/x86_64-pc-linux-gnu-library/4.0/plumber/plumber/10-welcome/plumber.R:/api/plumber.R:ro --name myapi rstudio/plumber:latest /api/plumber.R # then browse with # curl http://localhost:8000/ diff --git a/NAMESPACE b/NAMESPACE index da06eec71..17001967b 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1,10 +1,13 @@ # Generated by roxygen2: do not edit by hand +S3method(format,plumber_available_apis) +S3method(print,plumber_available_apis) export("%>%") export(PlumberEndpoint) export(PlumberStatic) export(addSerializer) export(as_attachment) +export(available_apis) export(do_configure_https) export(do_deploy_api) export(do_forward) @@ -31,6 +34,7 @@ export(parser_text) export(parser_tsv) export(parser_yaml) export(plumb) +export(plumb_api) export(plumber) export(pr) export(pr_cookie) @@ -84,11 +88,11 @@ export(serializer_unboxed_json) export(serializer_yaml) export(sessionCookie) import(R6) -import(crayon) import(promises) import(stringi) importFrom(jsonlite,parse_json) importFrom(jsonlite,toJSON) importFrom(magrittr,"%>%") importFrom(stats,runif) +importFrom(utils,installed.packages) importFrom(webutils,parse_multipart) diff --git a/NEWS.md b/NEWS.md index 30c9da362..8e85422a3 100644 --- a/NEWS.md +++ b/NEWS.md @@ -20,6 +20,8 @@ plumber 1.0.0 ### Breaking changes +* When `plumb()`ing a file (or `plumber$new(file)`), the working directory is set to the file's directory before parsing the file. When running the Plumber API, the working directory will be set to file's directory before running.(#631) + * Plumber's OpenAPI Specification is now defined using [OpenAPI 3](https://github.com/OAI/OpenAPI-Specification/blob/master/versions/3.0.3.md), upgrading from Swagger Specification. (#365) @@ -51,7 +53,7 @@ both UIs integration are available from https://github.com/meztez/rapidoc/ and h * Added support for promises in endpoints, filters, and hooks. (#248) -* Add support for `#' @plumber` tag to gain programmatic access to the `plumber` router via `function(pr) {....}`. (@meztez and @blairj09, #568) +* Added support for `#' @plumber` tag to gain programmatic access to the `plumber` router via `function(pr) {....}`. (@meztez and @blairj09, #568) * Added OpenAPI support for array parameters using syntax `name:[type]` and new type `list` (synonym df, data.frame). (@meztez, #532) @@ -62,11 +64,15 @@ both UIs integration are available from https://github.com/meztez/rapidoc/ and h * Documentation is presented using pkgdown (#570) -* Tidy API for easier programmatic usage (@blairj09, #590) +* Added a Tidy API for easier programmatic usage (@blairj09, #590) + +* Added `plumb_api()` for standardizing where to locate (`inst/plumber`) and how to run (`plumb_api(package, name)`) plumber apis inside an R package. To view the available Plumber APIs, call `available_apis()`. (#631) ### Minor new features and improvements +* When calling `include_file()`, the `content_type` is automatically inferred from the file extension if `content_type` is not provided. (#631) + * Added `serializer_feather()` and `parser_feather()` (#626) * When `plumb()`ing a file, arguments supplied to parsers and serializers may be values defined earlier in the file. (@meztez, #620) diff --git a/R/digital-ocean.R b/R/digital-ocean.R index 577b6f7dd..c19bbc752 100644 --- a/R/digital-ocean.R +++ b/R/digital-ocean.R @@ -79,7 +79,7 @@ do_provision <- function(droplet, unstable=FALSE, example=TRUE, ...){ install_firewall(droplet) if (example){ - do_deploy_api(droplet, "hello", system.file("examples", "10-welcome", package="plumber"), port=8000, forward=TRUE) + do_deploy_api(droplet, "hello", system.file("plumber", "10-welcome", package="plumber"), port=8000, forward=TRUE) } invisible(droplet) @@ -121,7 +121,7 @@ droplet_capture <- function(droplet, command){ install_api <- function(droplet){ analogsea::droplet_ssh(droplet, "mkdir -p /var/plumber") - example_plumber_file <- system.file("examples", "10-welcome", "plumber.R", package="plumber") + example_plumber_file <- system.file("plumber", "10-welcome", "plumber.R", package="plumber") if (nchar(example_plumber_file) < 1) { stop("Could not find example 10-welcome plumber file", call. = FALSE) } diff --git a/R/includes.R b/R/includes.R index ddc4fcf00..ad9dc03db 100644 --- a/R/includes.R +++ b/R/includes.R @@ -17,16 +17,16 @@ requireRmd <- function(fun_name){ #' @param file The path to the file to return #' @param res The response object into which we'll write #' @param content_type If provided, the given value will be sent as the -#' \code{Content-Type} header in the response. +#' `Content-Type` header in the response. Defaults to the contentType of the file extension. +#' To disable the `Content-Type` header, set `content_type = NULL`. #' @export -include_file <- function(file, res, content_type){ +include_file <- function(file, res, content_type = getContentType(tools::file_ext(file))){ # TODO stream this directly to the request w/o loading in memory - # TODO set content type automatically lines <- paste(readLines(file), collapse="\n") res$serializer <- "null" res$body <- c(res$body, lines) - if (!missing(content_type)){ + if (!is.null(content_type)) { res$setHeader("Content-Type", content_type) } diff --git a/R/openapi-spec.R b/R/openapi-spec.R index 9dafedd28..5a78e8d60 100644 --- a/R/openapi-spec.R +++ b/R/openapi-spec.R @@ -1,6 +1,6 @@ -#' Convert the endpoints as they exist on the router to a list which can +#' Convert the endpoints as they exist on the Plumber object to a list which can #' be converted into a OpenAPI Specification for these endpoints #' @noRd endpointSpecification <- function(routerEndpointEntry, path = routerEndpointEntry$path) { diff --git a/R/plumb-block.R b/R/plumb-block.R index c827cb293..178caf9be 100644 --- a/R/plumb-block.R +++ b/R/plumb-block.R @@ -259,7 +259,7 @@ evaluateBlock <- function(srcref, file, expr, envir, addEndpoint, addFilter, pr) block <- plumbBlock(lineNum, file, envir) if (sum(!is.null(block$filter), !is.null(block$paths), !is.null(block$assets), !is.null(block$routerModifier)) > 1){ - stopOnLine(lineNum, file[lineNum], "A single function can only be a filter, an API endpoint, an asset or a router modifier (@filter AND @get, @post, @assets, @plumber, etc.)") + stopOnLine(lineNum, file[lineNum], "A single function can only be a filter, an API endpoint, an asset or a Plumber object modifier (@filter AND @get, @post, @assets, @plumber, etc.)") } # ALL if statements possibilities must eventually call eval(expr, envir) diff --git a/R/plumb.R b/R/plumb.R new file mode 100644 index 000000000..5a9c2c664 --- /dev/null +++ b/R/plumb.R @@ -0,0 +1,260 @@ +#' Process a Plumber API +#' +#' @details API routers are the core request handler in plumber. A router is responsible for +#' taking an incoming request, submitting it through the appropriate filters and +#' eventually to a corresponding endpoint, if one is found. +#' +#' See \url{http://www.rplumber.io/articles/programmatic-usage.html} for additional +#' details on the methods available on this object. +#' @param file The file to parse as the plumber router definition. +#' @param dir The directory containing the `plumber.R` file to parse as the +#' plumber router definition. Alternatively, if an `entrypoint.R` file is +#' found, it will take precedence and be responsible for returning a runnable +#' router. +#' @export +plumb <- function(file = NULL, dir = ".") { + + if (!is.null(file) && !identical(dir, ".")) { + # both were explicitly set. + # assume it is a file in that dir and continue like normal + file <- file.path( + # removing trailing slash in dir + normalize_dir_path(dir), + file + ) + } + + if (is.null(file)) { + if (identical(dir, "")) { + # dir and file are both empty. Error + stop("You must specify either a file or directory parameter") + } + + dir <- normalize_dir_path(dir) + + # if the entrypoint file exists... + entrypoint <- list.files(dir, "^entrypoint\\.r$", ignore.case = TRUE) + if (length(entrypoint) >= 1) { + if (length(entrypoint) > 1) { + entrypoint <- entrypoint[1] + warning("Found multiple files named 'entrypoint.R'. Using: '", entrypoint, "'") + } + + # set working directory to dir before sourcing + old_wd <- setwd(dir) + on.exit(setwd(old_wd), add = TRUE) + + # Expect that entrypoint will provide us with the router + # Do not 'poison' the global env. Using a local environment that points to global env. + # sourceUTF8 returns the (visible) value object. No need to call source()$value() + pr <- sourceUTF8(entrypoint, new.env(parent = globalenv())) + + if (!inherits(pr, "plumber")){ + stop("'", entrypoint, "' must return a runnable Plumber router.") + } + + # return plumber object + return(pr) + } + + # Find plumber.R in the directory case-insensitive + file <- list.files(dir, "^plumber\\.r$", ignore.case = TRUE, full.names = TRUE) + if (length(file) == 0) { + stop("No plumber.R file found in the specified directory: ", dir) + } + if (length(file) > 1) { + file <- file[1] + warning("Found multiple files named 'plumber.R' in directory: '", dir, "'.\nUsing: '", file, "'") + } + # continue as if a file has been provided... + } + + if (!file.exists(file)) { + # Couldn't find the Plumber file nor an entrypoint + stop("File does not exist: ", file) + } + + # Plumber file found + plumber$new(file) +} + + + + +#' Process a Package's Plumber API +#' +#' So that packages can ship multiple plumber routers, users should store their Plumber APIs +#' in the `inst` subfolder `plumber` (`./inst/plumber/API_1/plumber.R`). +#' +#' To view all available Plumber APIs across all packages, please call `available_apis()`. +#' A `package` value may be provided to only display a particular package's Plumber APIs. +#' +#' @param package Package to inspect +#' @param name Name of the package folder to [plumb()]. +#' @describeIn plumb_api [plumb()]s a package's Plumber API. Returns a [`plumber`] router object +#' @return A [`plumber`] object. If either `package` or `name` is null, the appropriate [available_apis()] will be returned. +#' @export +plumb_api <- function(package = NULL, name = NULL) { + + if (is.null(package)) { + return(available_apis(package = NULL)) + } + if (is.null(name)) { + return(available_apis(package = package)) + } + + stopifnot(length(package) == 1) + stopifnot(length(name) == 1) + stopifnot(is.character(package)) + stopifnot(is.character(name)) + + apis <- available_apis(package = package) + apis_sub <- (apis$package == package) & (apis$name == name) + if (sum(apis_sub) == 0) { + stop("Could not find Plumber API for package '", package, "' with name '", name, "'") + } + + plumb( + dir = system.file( + file.path("plumber", name), + package = package + ) + ) +} + + +#' @describeIn plumb_api Displays all available package Plumber APIs. Returns a `data.frame` of `package` and `name` information. +#' @export +available_apis <- function(package = NULL) { + info <- + if (is.null(package)) { + all_available_apis() + } else { + available_apis_for_package(package) + } + if (!is.null(info$error)) { + stop(info$error, call. = FALSE) + } + apis <- info$apis + return(apis) +} + + +#' @return will return a list of `error` and `apis`. +#' `apis` is a \code{data.frame} containing +#' "package": name of package; string +#' "name": API directory. (can be passed in as `plumb_api(PKG, NAME)`; string +#' @noRd +available_apis_for_package <- function(package) { + + an_error <- function(...) { + list( + apis = NULL, + error = paste0(...) + ) + } + + if (!nzchar(system.file(package = package))) { + return(an_error( + "No package found with name: \"", package, "\"" + )) + } + + apis_dir <- system.file("plumber", package = package) + if (!nzchar(apis_dir)) { + return(an_error( + "No Plumber APIs found for package: \"", package, "\"" + )) + } + + api_folders <- list.dirs(apis_dir, full.names = TRUE, recursive = FALSE) + names(api_folders) <- basename(api_folders) + + api_info <- lapply(api_folders, function(api_dir) { + api_files <- dir(api_dir) + if (!any(c("plumber.r", "entrypoint.r") %in% tolower(api_files))) { + # could not find any plumber files. Quitting + return(NULL) + } + + # did find a plumb file. Can return the dir + data.frame( + package = package, + name = basename(api_dir), + stringsAsFactors = FALSE, + row.names = FALSE + ) + }) + + has_no_api <- vapply(api_info, is.null, logical(1)) + if (all(has_no_api)) { + return(an_error( + "No Plumber APIs found for package: \"", package, "\"" + )) + } + + api_info <- api_info[!has_no_api] + + apis <- do.call(rbind, api_info) + class(apis) <- c("plumber_available_apis", class(apis)) + rownames(apis) <- NULL + + list( + apis = apis, + error = NULL + ) +} + +#' @return will return a list of `error` and `apis` which is a \code{data.frame} containing "package", and "name" +#' +#' @importFrom utils installed.packages +#' @noRd +all_available_apis <- function() { + ret <- list() + all_pkgs <- installed.packages()[,"Package"] + + for (pkg in all_pkgs) { + info <- available_apis_for_package(pkg) + if (!is.null(info$apis)) { + ret[[length(ret) + 1]] <- info$apis + } + } + + # do not check for size 0, as plumber contains apis. + + apis <- do.call(rbind, ret) + + list( + apis = apis, # will maintain class + error = NULL + ) +} + + +#' @export +format.plumber_available_apis <- function(x, ...) { + apis <- x + split_apis <- split(apis, apis$package) + + pkg_apis <- vapply( + split_apis, + function(apis_sub) { + paste0( + "* ", apis_sub$package[1], "\n", + paste0(" - ", apis$name, collapse = "\n") + ) + }, + character(1) + ) + + paste0( + "Available Plumber APIs:\n", + paste0(pkg_apis, collapse = "\n") + ) +} + + +#' @export +print.plumber_available_apis <- function(x, ...) { + cat(format(x, ...), "\n", sep = "") +} diff --git a/R/plumber.R b/R/plumber.R index bbb0c8735..2248086bc 100644 --- a/R/plumber.R +++ b/R/plumber.R @@ -11,85 +11,7 @@ enumerateVerbs <- function(v) { toupper(v) } -#' Plumber Router -#' @details Routers are the core request handler in plumber. A router is responsible for -#' taking an incoming request, submitting it through the appropriate filters and -#' eventually to a corresponding endpoint, if one is found. -#' -#' See \url{http://www.rplumber.io/articles/programmatic-usage.html} for additional -#' details on the methods available on this object. -#' @rdname plumber -#' @param file The file to parse as the plumber router definition. -#' @param dir The directory containing the `plumber.R` file to parse as the -#' plumber router definition. Alternatively, if an `entrypoint.R` file is -#' found, it will take precedence and be responsible for returning a runnable -#' router. -#' @export -plumb <- function(file = NULL, dir = ".") { - - if (!is.null(file) && !identical(dir, ".")) { - # both were explicitly set. - # assume it is a file in that dir and continue like normal - file <- file.path( - # removing trailing slash in dir - normalize_dir_path(dir), - file - ) - } - - if (is.null(file)) { - if (identical(dir, "")) { - # dir and file are both empty. Error - stop("You must specify either a file or directory parameter") - } - - dir <- normalize_dir_path(dir) - - # if the entrypoint file exists... - entrypoint <- list.files(dir, "^entrypoint\\.r$", ignore.case = TRUE) - if (length(entrypoint) >= 1) { - if (length(entrypoint) > 1) { - entrypoint <- entrypoint[1] - warning("Found multiple files named 'entrypoint.R'. Using: '", entrypoint, "'") - } - - # set working directory to dir before sourcing - old <- setwd(dir) - on.exit(setwd(old), add = TRUE) - - # Expect that entrypoint will provide us with the router - # Do not 'poison' the global env. Using a local environment - # sourceUTF8 returns the (visible) value object. No need to call source()$value() - pr <- sourceUTF8(entrypoint, environment()) - if (!inherits(pr, "plumber")){ - stop("'", entrypoint, "' must return a runnable Plumber router.") - } - - # return plumber object - return(pr) - } - - # Find plumber.R in the directory case-insensitive - file <- list.files(dir, "^plumber\\.r$", ignore.case = TRUE, full.names = TRUE) - if (length(file) == 0) { - stop("No plumber.R file found in the specified directory: ", dir) - } - if (length(file) > 1) { - file <- file[1] - warning("Found multiple files named 'plumber.R' in directory: '", dir, "'.\nUsing: '", file, "'") - } - # continue as if a file has been provided... - } - - if (!file.exists(file)) { - # Couldn't find the Plumber file nor an entrypoint - stop("File does not exist: ", file) - } - - # Plumber file found - plumber$new(file) -} #' @include parse-query.R @@ -100,7 +22,8 @@ defaultPlumberFilters <- list( queryString = queryStringFilter, postBody = postBodyFilter, cookieParser = cookieFilter, - sharedSecret = sharedSecretFilter) + sharedSecret = sharedSecretFilter +) #' @keywords internal #' @title hookable @@ -181,8 +104,14 @@ hookable <- R6Class( ) +#' Package Plumber Router +# ' @details Routers are the core request handler in plumber. A router is responsible for +# ' taking an incoming request, submitting it through the appropriate filters and +# ' eventually to a corresponding endpoint, if one is found. +# ' +# ' See \url{http://www.rplumber.io/articles/programmatic-usage.html} for additional +# ' details on the methods available on this object. #' @export -#' @import crayon plumber <- R6Class( "plumber", inherit = hookable, @@ -236,7 +165,14 @@ plumber <- R6Class( private$filts <- c(private$filts, fil) } - if (!is.null(file)){ + if (!is.null(file)) { + # plumb() the file in the working directory + # The directory is also set when running the plumber object + private$filename <- file + old_wd <- setwd(dirname(file)) + on.exit({setwd(old_wd)}, add = TRUE) + file <- basename(file) + private$lines <- readUTF8(file) private$parsed <- parseUTF8(file) private$disable_run <- TRUE @@ -326,10 +262,9 @@ plumber <- R6Class( options("plumber.debug" = private$debug) # Set and restore the wd to make it appear that the proc is running local to the file's definition. - if (!is.null(private$filename)){ - cwd <- getwd() - on.exit({ setwd(cwd) }, add = TRUE) - setwd(dirname(private$filename)) + if (!is.null(private$filename)) { + old_wd <- setwd(dirname(private$file)) + on.exit({setwd(old_wd)}, add = TRUE) } if (isTRUE(private$ui_info$enabled)) { @@ -1178,6 +1113,7 @@ plumber <- R6Class( mnts = list(), envir = NULL, # The environment in which all API execution will be conducted + filename = NULL, # The file which was plumbed lines = NULL, # The lines constituting the API parsed = NULL, # The parsed representation of the API globalSettings = list(info=list()), # Global settings for this API. Primarily used for OpenAPI Specification. diff --git a/R/session-cookie.R b/R/session-cookie.R index dbe3ef3b0..d6bf75951 100644 --- a/R/session-cookie.R +++ b/R/session-cookie.R @@ -56,7 +56,7 @@ #' #' #' # Load a plumber API -#' pr <- plumb(system.file(file.path("examples", "01-append", "plumber.R"), package = "plumber")) +#' pr <- plumb_api("plumber", "01-append") #' #' # Add cookie support and retrieve secret key using `keyring` #' pr$registerHooks( @@ -78,7 +78,7 @@ #' #' #' # Load a plumber API -#' pr <- plumb(system.file(file.path("examples", "01-append", "plumber.R"), package = "plumber")) +#' pr <- plumb_api("plumber", "01-append") #' #' # Add cookie support and retrieve secret key from file #' pr$registerHooks( diff --git a/inst/examples/03-github/Dockerfile b/inst/examples/03-github/Dockerfile deleted file mode 100644 index 1a4f92a0b..000000000 --- a/inst/examples/03-github/Dockerfile +++ /dev/null @@ -1,5 +0,0 @@ -FROM rstudio/plumber:next - -COPY github-key.txt /github-key - -CMD ["/usr/local/lib/R/site-library/plumber/examples/03-github/plumber.R"] diff --git a/inst/examples/06-sessions/Dockerfile b/inst/examples/06-sessions/Dockerfile deleted file mode 100644 index e8a2531b4..000000000 --- a/inst/examples/06-sessions/Dockerfile +++ /dev/null @@ -1,6 +0,0 @@ -FROM rstudio/plumber:next - -ENTRYPOINT R \ - -e "pr <- plumber::plumb(system.file('examples/06-sessions/plumber.R', package = 'plumber'))" \ - -e "pr\$registerHooks(plumber::sessionCookie('pleasechangeme', 'cookieName'))" \ - -e "pr\$run(host='0.0.0.0', port=8000)" diff --git a/inst/examples/07-mailgun/Dockerfile b/inst/examples/07-mailgun/Dockerfile deleted file mode 100644 index aeb50e12a..000000000 --- a/inst/examples/07-mailgun/Dockerfile +++ /dev/null @@ -1,5 +0,0 @@ -FROM rstudio/plumber:next - -RUN R -e "install.packages('htmltools')" - -CMD ["/usr/local/lib/R/site-library/plumber/examples/07-mailgun/plumber.R"] diff --git a/inst/examples/12-entrypoint/entrypoint.R b/inst/examples/12-entrypoint/entrypoint.R deleted file mode 100644 index 198714b75..000000000 --- a/inst/examples/12-entrypoint/entrypoint.R +++ /dev/null @@ -1,5 +0,0 @@ - -pr <- plumb("myplumberapi.R") -pr$registerHook("preroute", sessionCookie("secret", "cookieName")) - -pr diff --git a/inst/hosted-new.R b/inst/hosted-new.R index b32308e3f..7cb13a36c 100644 --- a/inst/hosted-new.R +++ b/inst/hosted-new.R @@ -7,21 +7,21 @@ install_package_secure <- function(droplet, pkg){ drop <- plumber::do_provision(unstable=TRUE, example=FALSE, name="hostedplumber") -do_deploy_api(drop, "append", "./inst/examples/01-append/", 8001) -do_deploy_api(drop, "filters", "./inst/examples/02-filters/", 8002) +do_deploy_api(drop, "append", "./inst/plumber/01-append/", 8001) +do_deploy_api(drop, "filters", "./inst/plumber/02-filters/", 8002) # GitHub install_package_secure(drop, "digest") # remotes is the other dependency, but by unstable=TRUE on do_provision we already have that -do_deploy_api(drop, "github", "./inst/examples/03-github/", 8003) +do_deploy_api(drop, "github", "./inst/plumber/03-github/", 8003) # Sessions -do_deploy_api(drop, "sessions", "./inst/examples/06-sessions/", 8006, +do_deploy_api(drop, "sessions", "./inst/plumber/06-sessions/", 8006, preflight="pr$registerHooks(plumber::sessionCookie('secret', 'cookieName', path='/'));") # Mailgun install_package_secure(drop, "htmltools") -do_deploy_api(drop, "mailgun", "./inst/examples/07-mailgun/", 8007) +do_deploy_api(drop, "mailgun", "./inst/plumber/07-mailgun/", 8007) # MANUAL: configure DNS, then # do_configure_https(drop, "plumber.tres.tl"... ) diff --git a/inst/examples/01-append/plumber.R b/inst/plumber/01-append/plumber.R similarity index 100% rename from inst/examples/01-append/plumber.R rename to inst/plumber/01-append/plumber.R diff --git a/inst/examples/02-filters/plumber.R b/inst/plumber/02-filters/plumber.R similarity index 100% rename from inst/examples/02-filters/plumber.R rename to inst/plumber/02-filters/plumber.R diff --git a/inst/examples/03-github/.gitignore b/inst/plumber/03-github/.gitignore similarity index 100% rename from inst/examples/03-github/.gitignore rename to inst/plumber/03-github/.gitignore diff --git a/inst/plumber/03-github/Dockerfile b/inst/plumber/03-github/Dockerfile new file mode 100644 index 000000000..6c24dcbfb --- /dev/null +++ b/inst/plumber/03-github/Dockerfile @@ -0,0 +1,5 @@ +FROM rstudio/plumber:next + +COPY github-key.txt /github-key + +CMD ["/usr/local/lib/R/site-library/plumber/plumber/03-github/plumber.R"] diff --git a/inst/examples/03-github/plumber.R b/inst/plumber/03-github/plumber.R similarity index 100% rename from inst/examples/03-github/plumber.R rename to inst/plumber/03-github/plumber.R diff --git a/inst/examples/04-mean-sum/plumber.R b/inst/plumber/04-mean-sum/plumber.R similarity index 100% rename from inst/examples/04-mean-sum/plumber.R rename to inst/plumber/04-mean-sum/plumber.R diff --git a/inst/examples/05-static/README.md b/inst/plumber/05-static/README.md similarity index 100% rename from inst/examples/05-static/README.md rename to inst/plumber/05-static/README.md diff --git a/inst/examples/05-static/files/a.html b/inst/plumber/05-static/files/a.html similarity index 100% rename from inst/examples/05-static/files/a.html rename to inst/plumber/05-static/files/a.html diff --git a/inst/examples/05-static/files/b.txt b/inst/plumber/05-static/files/b.txt similarity index 100% rename from inst/examples/05-static/files/b.txt rename to inst/plumber/05-static/files/b.txt diff --git a/inst/examples/05-static/plumber.R b/inst/plumber/05-static/plumber.R similarity index 100% rename from inst/examples/05-static/plumber.R rename to inst/plumber/05-static/plumber.R diff --git a/inst/plumber/06-sessions/Dockerfile b/inst/plumber/06-sessions/Dockerfile new file mode 100644 index 000000000..62b3274f4 --- /dev/null +++ b/inst/plumber/06-sessions/Dockerfile @@ -0,0 +1,5 @@ +FROM rstudio/plumber:next + +ENTRYPOINT R \ + -e "library(plumber)" \ + -e "plumb_api('plumber', '06-sessions') %>% pr_cookie('pleasechangeme', 'cookieName') %>% pr_run(host='0.0.0.0', port=8000)" diff --git a/inst/examples/06-sessions/plumber.R b/inst/plumber/06-sessions/plumber.R similarity index 96% rename from inst/examples/06-sessions/plumber.R rename to inst/plumber/06-sessions/plumber.R index efdee4c40..21146b45f 100644 --- a/inst/examples/06-sessions/plumber.R +++ b/inst/plumber/06-sessions/plumber.R @@ -10,7 +10,7 @@ function(req, res) { return(paste0("This is visit #", count)) } -#* Example using req$session. Requires adding "sessionCookie()" support to your router in order +#* Example using req$session. Requires adding "sessionCookie()" support to your API in order #* to work: #* `pr <- plumb("file.R"); pr$registerHooks(sessionCookie("secret", "cookieName")); pr$run()` #* @get /sessionCounter diff --git a/inst/examples/06-sessions/static/iframe-secure.html b/inst/plumber/06-sessions/static/iframe-secure.html similarity index 100% rename from inst/examples/06-sessions/static/iframe-secure.html rename to inst/plumber/06-sessions/static/iframe-secure.html diff --git a/inst/examples/06-sessions/static/iframe.html b/inst/plumber/06-sessions/static/iframe.html similarity index 100% rename from inst/examples/06-sessions/static/iframe.html rename to inst/plumber/06-sessions/static/iframe.html diff --git a/inst/examples/06-sessions/static/js-cookie.js b/inst/plumber/06-sessions/static/js-cookie.js similarity index 100% rename from inst/examples/06-sessions/static/js-cookie.js rename to inst/plumber/06-sessions/static/js-cookie.js diff --git a/inst/plumber/07-mailgun/Dockerfile b/inst/plumber/07-mailgun/Dockerfile new file mode 100644 index 000000000..6326076ec --- /dev/null +++ b/inst/plumber/07-mailgun/Dockerfile @@ -0,0 +1,5 @@ +FROM rstudio/plumber:next + +RUN R -e "install.packages('htmltools')" + +CMD ["/usr/local/lib/R/site-library/plumber/plumber/07-mailgun/plumber.R"] diff --git a/inst/examples/07-mailgun/plumber.R b/inst/plumber/07-mailgun/plumber.R similarity index 100% rename from inst/examples/07-mailgun/plumber.R rename to inst/plumber/07-mailgun/plumber.R diff --git a/inst/examples/08-identity/plumber.R b/inst/plumber/08-identity/plumber.R similarity index 100% rename from inst/examples/08-identity/plumber.R rename to inst/plumber/08-identity/plumber.R diff --git a/inst/examples/09-content-type/plumber.R b/inst/plumber/09-content-type/plumber.R similarity index 100% rename from inst/examples/09-content-type/plumber.R rename to inst/plumber/09-content-type/plumber.R diff --git a/inst/examples/10-welcome/plumber.R b/inst/plumber/10-welcome/plumber.R similarity index 100% rename from inst/examples/10-welcome/plumber.R rename to inst/plumber/10-welcome/plumber.R diff --git a/inst/examples/11-car-inventory/inventory.csv b/inst/plumber/11-car-inventory/inventory.csv similarity index 100% rename from inst/examples/11-car-inventory/inventory.csv rename to inst/plumber/11-car-inventory/inventory.csv diff --git a/inst/examples/11-car-inventory/plumber.R b/inst/plumber/11-car-inventory/plumber.R similarity index 100% rename from inst/examples/11-car-inventory/plumber.R rename to inst/plumber/11-car-inventory/plumber.R diff --git a/inst/plumber/12-entrypoint/entrypoint.R b/inst/plumber/12-entrypoint/entrypoint.R new file mode 100644 index 000000000..e53166cf2 --- /dev/null +++ b/inst/plumber/12-entrypoint/entrypoint.R @@ -0,0 +1,10 @@ + +library(plumber) +pr <- pr("myplumberapi.R") %>% + pr_cookie( + key = "pleasechangeme", + name = "cookieName" + ) + +# MUST return a Plumber object when using `entrypoint.R` +pr diff --git a/inst/examples/12-entrypoint/myplumberapi.R b/inst/plumber/12-entrypoint/myplumberapi.R similarity index 100% rename from inst/examples/12-entrypoint/myplumberapi.R rename to inst/plumber/12-entrypoint/myplumberapi.R diff --git a/inst/plumber/12-entrypoint/using_plumber_tag.R b/inst/plumber/12-entrypoint/using_plumber_tag.R new file mode 100644 index 000000000..cf8e5e117 --- /dev/null +++ b/inst/plumber/12-entrypoint/using_plumber_tag.R @@ -0,0 +1,23 @@ +## plumber::plumb("using_plumber_tag.R") + +library(plumber) + +#* @get /counter +function(req){ + count <- 0 + if (!is.null(req$session$counter)){ + count <- as.numeric(req$session$counter) + } + req$session$counter <- count + 1 + return(paste0("This is visit #", count)) +} + + +#' @plumber +function(pr) { + pr %>% + pr_cookie( + key = "pleasechangeme", + name = "cookieName" + ) +} diff --git a/inst/examples/13-promises/plumber.R b/inst/plumber/13-promises/plumber.R similarity index 100% rename from inst/examples/13-promises/plumber.R rename to inst/plumber/13-promises/plumber.R diff --git a/inst/examples/14-future/plumber.R b/inst/plumber/14-future/plumber.R similarity index 100% rename from inst/examples/14-future/plumber.R rename to inst/plumber/14-future/plumber.R diff --git a/inst/examples/14-future/test-future.R b/inst/plumber/14-future/test-future.R similarity index 94% rename from inst/examples/14-future/test-future.R rename to inst/plumber/14-future/test-future.R index 81e161e33..83d7998a0 100644 --- a/inst/examples/14-future/test-future.R +++ b/inst/plumber/14-future/test-future.R @@ -1,6 +1,6 @@ # Instructions: -# 1. `plumb` API - `plumb(system.file("examples/14-future/plumber.R", package = "plumber"))$run(port = 1234)` -# 2. In separate R session, source the test file - `source(system.file("examples/14-future/test-future.R", package = "plumber"))` +# 1. `plumb` API - `plumb_api("plumber", "14-future")$run(port = 1234)` +# 2. In separate R session, source the test file - `source(system.file("plumber/14-future/test-future.R", package = "plumber"))` local(withAutoprint({ # print when sourced diff --git a/inst/examples/15-openapi-spec/entrypoint.R b/inst/plumber/15-openapi-spec/entrypoint.R similarity index 87% rename from inst/examples/15-openapi-spec/entrypoint.R rename to inst/plumber/15-openapi-spec/entrypoint.R index ba3263b07..5a380e117 100644 --- a/inst/examples/15-openapi-spec/entrypoint.R +++ b/inst/plumber/15-openapi-spec/entrypoint.R @@ -15,10 +15,15 @@ openapi_func <- function(spec) { spec } -handler <- function(num) { sum(as.integer(num)) } +handler <- function(num) { + sum(as.integer(num)) +} pr$handle("GET", "/sum", handler, serializer = serializer_json()) pr$set_api_spec(api = openapi_func) pr$get_api_spec() + +# return Plumber object +pr diff --git a/inst/examples/16-attachment/plumber.R b/inst/plumber/16-attachment/plumber.R similarity index 100% rename from inst/examples/16-attachment/plumber.R rename to inst/plumber/16-attachment/plumber.R diff --git a/man-roxygen/param_pr.R b/man-roxygen/param_pr.R index d295c1690..fafe9a033 100644 --- a/man-roxygen/param_pr.R +++ b/man-roxygen/param_pr.R @@ -1 +1 @@ -#' @param pr A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function. +#' @param pr A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function. diff --git a/man/include_file.Rd b/man/include_file.Rd index e01176260..c644010ee 100644 --- a/man/include_file.Rd +++ b/man/include_file.Rd @@ -7,7 +7,7 @@ \alias{include_rmd} \title{Send File Contents as Response} \usage{ -include_file(file, res, content_type) +include_file(file, res, content_type = getContentType(tools::file_ext(file))) include_html(file, res) @@ -21,7 +21,8 @@ include_rmd(file, res, format = NULL) \item{res}{The response object into which we'll write} \item{content_type}{If provided, the given value will be sent as the -\code{Content-Type} header in the response.} +\code{Content-Type} header in the response. Defaults to the contentType of the file extension. +To disable the \code{Content-Type} header, set \code{content_type = NULL}.} \item{format}{Passed as the \code{output_format} to \code{rmarkdown::render}} } diff --git a/man/plumb.Rd b/man/plumb.Rd new file mode 100644 index 000000000..ca69b3102 --- /dev/null +++ b/man/plumb.Rd @@ -0,0 +1,27 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/plumb.R +\name{plumb} +\alias{plumb} +\title{Process a Plumber API} +\usage{ +plumb(file = NULL, dir = ".") +} +\arguments{ +\item{file}{The file to parse as the plumber router definition.} + +\item{dir}{The directory containing the \code{plumber.R} file to parse as the +plumber router definition. Alternatively, if an \code{entrypoint.R} file is +found, it will take precedence and be responsible for returning a runnable +router.} +} +\description{ +Process a Plumber API +} +\details{ +API routers are the core request handler in plumber. A router is responsible for +taking an incoming request, submitting it through the appropriate filters and +eventually to a corresponding endpoint, if one is found. + +See \url{http://www.rplumber.io/articles/programmatic-usage.html} for additional +details on the methods available on this object. +} diff --git a/man/plumb_api.Rd b/man/plumb_api.Rd new file mode 100644 index 000000000..59a73a55a --- /dev/null +++ b/man/plumb_api.Rd @@ -0,0 +1,34 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/plumb.R +\name{plumb_api} +\alias{plumb_api} +\alias{available_apis} +\title{Process a Package's Plumber API} +\usage{ +plumb_api(package = NULL, name = NULL) + +available_apis(package = NULL) +} +\arguments{ +\item{package}{Package to inspect} + +\item{name}{Name of the package folder to \code{\link[=plumb]{plumb()}}.} +} +\value{ +A \code{\link{plumber}} object. If either \code{package} or \code{name} is null, the appropriate \code{\link[=available_apis]{available_apis()}} will be returned. +} +\description{ +So that packages can ship multiple plumber routers, users should store their Plumber APIs +in the \code{inst} subfolder \code{plumber} (\code{./inst/plumber/API_1/plumber.R}). +} +\details{ +To view all available Plumber APIs across all packages, please call \code{available_apis()}. +A \code{package} value may be provided to only display a particular package's Plumber APIs. +} +\section{Functions}{ +\itemize{ +\item \code{plumb_api}: \code{\link[=plumb]{plumb()}}s a package's Plumber API. Returns a \code{\link{plumber}} router object + +\item \code{available_apis}: Displays all available package Plumber APIs. Returns a \code{data.frame} of \code{package} and \code{name} information. +}} + diff --git a/man/plumber.Rd b/man/plumber.Rd index 6b7a05060..c5e9fe33b 100644 --- a/man/plumber.Rd +++ b/man/plumber.Rd @@ -1,30 +1,12 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/plumber.R -\name{plumb} -\alias{plumb} +\name{plumber} \alias{plumber} -\title{Plumber Router} -\usage{ -plumb(file = NULL, dir = ".") -} -\arguments{ -\item{file}{The file to parse as the plumber router definition.} - -\item{dir}{The directory containing the \code{plumber.R} file to parse as the -plumber router definition. Alternatively, if an \code{entrypoint.R} file is -found, it will take precedence and be responsible for returning a runnable -router.} -} +\title{Package Plumber Router} \description{ -Plumber Router -} -\details{ -Routers are the core request handler in plumber. A router is responsible for -taking an incoming request, submitting it through the appropriate filters and -eventually to a corresponding endpoint, if one is found. +Package Plumber Router -See \url{http://www.rplumber.io/articles/programmatic-usage.html} for additional -details on the methods available on this object. +Package Plumber Router } \examples{ diff --git a/man/pr_cookie.Rd b/man/pr_cookie.Rd index 60cfa7974..a2ae0bfbe 100644 --- a/man/pr_cookie.Rd +++ b/man/pr_cookie.Rd @@ -14,7 +14,7 @@ pr_cookie( ) } \arguments{ -\item{pr}{A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function.} +\item{pr}{A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function.} \item{key}{The secret key to use. This must be consistent across all R sessions where you want to save/restore encrypted cookies. It should be produced using diff --git a/man/pr_filter.Rd b/man/pr_filter.Rd index 1577efed7..1e1931d1a 100644 --- a/man/pr_filter.Rd +++ b/man/pr_filter.Rd @@ -7,7 +7,7 @@ pr_filter(pr, name, expr, serializer) } \arguments{ -\item{pr}{A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function.} +\item{pr}{A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function.} \item{name}{A character string. Name of filter} diff --git a/man/pr_handle.Rd b/man/pr_handle.Rd index b6b894e97..342256402 100644 --- a/man/pr_handle.Rd +++ b/man/pr_handle.Rd @@ -22,7 +22,7 @@ pr_delete(pr, path, handler, preempt, serializer, endpoint, ...) pr_head(pr, path, handler, preempt, serializer, endpoint, ...) } \arguments{ -\item{pr}{A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function.} +\item{pr}{A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function.} \item{methods}{Character vector of HTTP methods} diff --git a/man/pr_hook.Rd b/man/pr_hook.Rd index 7cb883b06..ec77f2b23 100644 --- a/man/pr_hook.Rd +++ b/man/pr_hook.Rd @@ -10,7 +10,7 @@ pr_hook(pr, stage, handler) pr_hooks(pr, handlers) } \arguments{ -\item{pr}{A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function.} +\item{pr}{A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function.} \item{stage}{A character string. Point in the lifecycle of a request.} diff --git a/man/pr_run.Rd b/man/pr_run.Rd index fce531bd9..5346731e6 100644 --- a/man/pr_run.Rd +++ b/man/pr_run.Rd @@ -7,7 +7,7 @@ pr_run(pr, host = "127.0.0.1", port = getOption("plumber.port", NULL)) } \arguments{ -\item{pr}{A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function.} +\item{pr}{A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function.} \item{host}{A string that is a valid IPv4 or IPv6 address that is owned by this server, which the application will listen on. "0.0.0.0" represents diff --git a/man/pr_set_404.Rd b/man/pr_set_404.Rd index ab8035e2d..1d16ae242 100644 --- a/man/pr_set_404.Rd +++ b/man/pr_set_404.Rd @@ -7,7 +7,7 @@ pr_set_404(pr, fun) } \arguments{ -\item{pr}{A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function.} +\item{pr}{A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function.} \item{fun}{A handler function} } diff --git a/man/pr_set_api_spec.Rd b/man/pr_set_api_spec.Rd index c889dc2d3..d5ef2ad1c 100644 --- a/man/pr_set_api_spec.Rd +++ b/man/pr_set_api_spec.Rd @@ -7,7 +7,7 @@ pr_set_api_spec(pr, api) } \arguments{ -\item{pr}{A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function.} +\item{pr}{A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function.} \item{api}{This can be \itemize{ diff --git a/man/pr_set_debug.Rd b/man/pr_set_debug.Rd index f3d6a6cd1..cfeb9b3d5 100644 --- a/man/pr_set_debug.Rd +++ b/man/pr_set_debug.Rd @@ -7,7 +7,7 @@ pr_set_debug(pr, debug = interactive()) } \arguments{ -\item{pr}{A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function.} +\item{pr}{A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function.} \item{debug}{\code{TRUE} provides more insight into your API errors.} } diff --git a/man/pr_set_error.Rd b/man/pr_set_error.Rd index 29391c79f..9453165e8 100644 --- a/man/pr_set_error.Rd +++ b/man/pr_set_error.Rd @@ -8,7 +8,7 @@ error} pr_set_error(pr, fun) } \arguments{ -\item{pr}{A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function.} +\item{pr}{A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function.} \item{fun}{An error handler function. This should accept \code{req}, \code{res}, and the error value} } diff --git a/man/pr_set_parsers.Rd b/man/pr_set_parsers.Rd index 03e881c7d..a62935d06 100644 --- a/man/pr_set_parsers.Rd +++ b/man/pr_set_parsers.Rd @@ -7,7 +7,7 @@ pr_set_parsers(pr, parsers) } \arguments{ -\item{pr}{A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function.} +\item{pr}{A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function.} \item{parsers}{Can be one of: \itemize{ diff --git a/man/pr_set_serializer.Rd b/man/pr_set_serializer.Rd index 8c1fb540c..dac6b3dc8 100644 --- a/man/pr_set_serializer.Rd +++ b/man/pr_set_serializer.Rd @@ -7,7 +7,7 @@ pr_set_serializer(pr, serializer) } \arguments{ -\item{pr}{A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function.} +\item{pr}{A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function.} \item{serializer}{A serializer function} } diff --git a/man/pr_set_ui.Rd b/man/pr_set_ui.Rd index de578da97..2e9f2cadd 100644 --- a/man/pr_set_ui.Rd +++ b/man/pr_set_ui.Rd @@ -7,7 +7,7 @@ pr_set_ui(pr, ui = getOption("plumber.ui", TRUE), ...) } \arguments{ -\item{pr}{A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function.} +\item{pr}{A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function.} \item{ui}{a character value or a logical value. If using \code{\link[=options_plumber]{options_plumber()}}, the value must be set before initializing your Plumber router.} diff --git a/man/pr_set_ui_callback.Rd b/man/pr_set_ui_callback.Rd index e19ad7aed..dfa774086 100644 --- a/man/pr_set_ui_callback.Rd +++ b/man/pr_set_ui_callback.Rd @@ -10,7 +10,7 @@ pr_set_ui_callback( ) } \arguments{ -\item{pr}{A Plumber router. Note: The supplied Plumber router will also be updated in place as well as returned by the function.} +\item{pr}{A Plumber API. Note: The supplied Plumber API object will also be updated in place as well as returned by the function.} \item{callback}{a callback function for taking action on UI url.} } diff --git a/man/sessionCookie.Rd b/man/sessionCookie.Rd index f70b2e51c..c42dcf187 100644 --- a/man/sessionCookie.Rd +++ b/man/sessionCookie.Rd @@ -70,7 +70,7 @@ keyring::key_set_with_value("plumber_api", plumber::randomCookieKey()) # Load a plumber API -pr <- plumb(system.file(file.path("examples", "01-append", "plumber.R"), package = "plumber")) +pr <- plumb_api("plumber", "01-append") # Add cookie support and retrieve secret key using `keyring` pr$registerHooks( @@ -92,7 +92,7 @@ Sys.chmod(pswd_file, mode = "0600") # Load a plumber API -pr <- plumb(system.file(file.path("examples", "01-append", "plumber.R"), package = "plumber")) +pr <- plumb_api("plumber", "01-append") # Add cookie support and retrieve secret key from file pr$registerHooks( diff --git a/package.json b/package.json index 0382fec38..ac3c314d4 100644 --- a/package.json +++ b/package.json @@ -1,5 +1,5 @@ { "dependencies": { - "swagger-cli": "^2.2.0" + "swagger-cli": "^4.0.4" } } diff --git a/pkgdown/_pkgdown.yml b/pkgdown/_pkgdown.yml index b01621cb5..a6c5e6be6 100644 --- a/pkgdown/_pkgdown.yml +++ b/pkgdown/_pkgdown.yml @@ -43,6 +43,8 @@ reference: - title: Router contents: - 'plumb' + - 'plumb_api' + - 'plumber' - 'pr' - 'pr_run' - 'options_plumber' diff --git a/scripts/manual_testing.R b/scripts/manual_testing.R index b91c235e8..2c42cea46 100644 --- a/scripts/manual_testing.R +++ b/scripts/manual_testing.R @@ -33,7 +33,7 @@ test_that("custom OpenAPI Specification update function works", { test_that("host doesn't change for messages, but does for RStudio IDE", { - pr <- plumb(system.file("examples/01-append/plumber.R", package = "plumber")) + pr <- plumb_api("plumber", "01-append") pr$run( "0.0.0.0", port = 1234 diff --git a/tests/testthat/helper-for-each-plumber-api.R b/tests/testthat/helper-for-each-plumber-api.R new file mode 100644 index 000000000..9e5afdb28 --- /dev/null +++ b/tests/testthat/helper-for-each-plumber-api.R @@ -0,0 +1,25 @@ +for_each_plumber_api <- function(fn) { + lapply( + available_apis("plumber")$name, + function(name) { + if (name == "14-future") { + if (!require("future", character.only = TRUE, quietly = TRUE)) { + return() + } + } + + pr <- + if (name == "12-entrypoint") { + expect_warning({ + plumb_api("plumber", name) + }, "Legacy cookie secret") + } else { + plumb_api("plumber", name) + } + expect_true(inherits(pr, "plumber"), paste0("plumb_api(\"", package, "\", \"", name, "\")")) + + + fn(pr) + } + ) +} diff --git a/tests/testthat/test-openapi.R b/tests/testthat/test-openapi.R index 42e715bfd..f06e5a45d 100644 --- a/tests/testthat/test-openapi.R +++ b/tests/testthat/test-openapi.R @@ -248,10 +248,8 @@ test_that("parametersSpecification works", { test_that("api kitchen sink", { skip_on_cran() - skip_on_travis() - skip_on_appveyor() skip_on_bioc() - skip_on_os(setdiff(c("windows", "mac", "linux", "solaris"), "mac")) + skip_on_os(setdiff(c("windows", "mac", "linux", "solaris"), c("mac", "linux"))) ## install brew - https://brew.sh/ # /usr/bin/ruby -e "$(curl -fsSL https://raw.githubusercontent.com/Homebrew/install/master/install)" @@ -259,20 +257,12 @@ test_that("api kitchen sink", { # brew install yarn ## install yarn # yarn add swagger-ui + + # yarn install swagger_cli_path <- "../../node_modules/.bin/swagger-cli" skip_if_not(file.exists(swagger_cli_path)) swagger_cli_path <- normalizePath(swagger_cli_path) - with_dir <- function(dir, x) { - old_wd <- getwd() - on.exit({ - setwd(old_wd) - }) - setwd(folder) - - force(x) - } - validate_spec <- function(pr) { spec <- jsonlite::toJSON(pr$get_api_spec(), auto_unbox = TRUE) tmpfile <- tempfile(fileext = ".json") @@ -297,26 +287,7 @@ test_that("api kitchen sink", { expect_equal(sub(tmpfile, "", output, fixed = TRUE), " is valid") } - - folders <- dir(system.file("examples/", package = "plumber"), full.names = TRUE) - for (folder in folders) { - with_dir(folder, { - if (file.exists("entrypoint.R")) { - if (basename(folder) == "12-entrypoint") { - # this file has a bad secret on purpose, - # don't show the warning - expect_warning({ - pr <- sourceUTF8("entrypoint.R") - }, "Legacy cookie secret") - } else { - pr <- sourceUTF8("entrypoint.R") - } - } else { - pr <- plumb(dir = ".") - } - validate_spec(pr) - }) - } + for_each_plumber_api(validate_spec) # TODO test more situations diff --git a/tests/testthat/test-plumb_api.R b/tests/testthat/test-plumb_api.R new file mode 100644 index 000000000..45330eb02 --- /dev/null +++ b/tests/testthat/test-plumb_api.R @@ -0,0 +1,80 @@ +context("plumb() package APIs") + + +expect_apis <- function(apis) { + expect_s3_class(apis, "plumber_available_apis") + expect_s3_class(apis, "data.frame") + expect_true(all(c("package", "name") %in% names(apis))) +} +test_that("available_apis() works with no package", { + skip_on_cran() + + apis <- available_apis() + expect_apis(apis) +}) +test_that("available_apis() works with a package", { + apis <- available_apis("plumber") + expect_apis(apis) +}) +test_that("available_apis() print method works", { + apis_output <- capture.output({ + available_apis("plumber") + }) + + expected_apis_output <- c( + "Available Plumber APIs:", + "* plumber", + " - 01-append", + " - 02-filters", + " - 03-github", + " - 04-mean-sum", + " - 05-static", + " - 06-sessions", + " - 07-mailgun", + " - 08-identity", + " - 09-content-type", + " - 10-welcome", + " - 11-car-inventory", + " - 12-entrypoint", + " - 13-promises", + " - 14-future", + " - 15-openapi-spec", + " - 16-attachment" + ) + + expect_equal( + apis_output, + expected_apis_output + ) +}) + +test_that("missing args are handled", { + expect_equal(plumb_api("plumber", NULL), available_apis("plumber")) + + skip_on_cran() + all_apis <- available_apis() + expect_equal(plumb_api(NULL, "01-append"), all_apis) + expect_equal(plumb_api(NULL, NULL), all_apis) +}) + +test_that("errors are thrown", { + + + expect_error(plumb_api(c("plumber", "plumber"), "01-append")) + expect_error(plumb_api("plumber", c("01-append", "01-append"))) + + expect_error(plumb_api(TRUE, "01-append")) + expect_error(plumb_api("plumber", TRUE)) + + expect_error(plumb_api("plumber", "not an api")) + + expect_error(available_apis("not a package"), "No package found with name") + expect_error(available_apis("crayon"), "No Plumber APIs found for package") +}) + + +context("plumb() plumber APIs") +test_that("all example plumber apis plumb", { + # plumb each api and validate they return a plumber object + for_each_plumber_api(identity) +}) diff --git a/tests/testthat/test-zzz-include.R b/tests/testthat/test-zzz-include.R index d363bb4aa..4eaf38690 100644 --- a/tests/testthat/test-zzz-include.R +++ b/tests/testthat/test-zzz-include.R @@ -6,12 +6,12 @@ test_that("Includes work", { # When running, we setwd to the file's dir. Simulate that here. cwd <- getwd() on.exit( { setwd(cwd) } ) - setwd("files") + setwd(test_path("files")) res <- PlumberResponse$new() val <- r$route(make_req("GET", "/"), res) expect_equal(val$body, "test.txt content") - expect_equal(val$headers$`Content-Type`, NULL) + expect_equal(val$headers$`Content-Type`, "text/plain") res <- PlumberResponse$new() val <- r$route(make_req("GET", "/html"), res) diff --git a/vignettes/hosting.Rmd b/vignettes/hosting.Rmd index 8bea7dfc1..596d250cd 100644 --- a/vignettes/hosting.Rmd +++ b/vignettes/hosting.Rmd @@ -75,14 +75,14 @@ which is the same as: ```bash docker run --rm -p 8000:8000 rstudio/plumber \ - /usr/local/lib/R/site-library/plumber/examples/04-mean-sum/plumber.R + /usr/local/lib/R/site-library/plumber/plumber/04-mean-sum/plumber.R ``` - `docker run` tells Docker to run a new container - `--rm` tells Docker to clean-up after the container when it's done - `-p 8000:8000` says to map port 8000 from the plumber container (which is where we'll run the server) to port 8000 of your local machine - `rstudio/plumber` is the name of the image we want to run - - `/usr/local/lib/R/site-library/plumber/examples/03-mean-sum/plumber.R` is the path **inside of the Docker container** to the Plumber file you want to host. You'll note that you do not need plumber installed on your host machine for this to work, nor does the path `/usr/local/...` need to exist on your host machine. This references the path inside of the docker container where the R file you want to `plumb()` can be found. This `mean-sum` path is the default path that the image uses if you don't specify one yourself. + - `/usr/local/lib/R/site-library/plumber/plumber/03-mean-sum/plumber.R` is the path **inside of the Docker container** to the Plumber file you want to host. You'll note that you do not need plumber installed on your host machine for this to work, nor does the path `/usr/local/...` need to exist on your host machine. This references the path inside of the docker container where the R file you want to `plumb()` can be found. This `mean-sum` path is the default path that the image uses if you don't specify one yourself. This will ask Plumber to `plumb` and `run` the file you specified on port 8000 of that new container. Because you used the `-p` argument, port 8000 of your local machine will be forwarded into your container. You can test this by running this on the machine where Docker is running: `curl localhost:8000/mean`, or if you know the IP address of the machine where Docker is running, you could visit it in a web browser. The `/mean` path is one that's defined in the plumber file we just specified -- you should get an single number in an array back (`[-0.1993]`).