diff --git a/DESCRIPTION b/DESCRIPTION index a8614611..9e8411ed 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -31,6 +31,7 @@ Imports: Suggests: covr, DBItest, + httr2, knitr, magrittr, rmarkdown, diff --git a/NEWS.md b/NEWS.md index 0fae612a..cf17bfaa 100644 --- a/NEWS.md +++ b/NEWS.md @@ -25,6 +25,10 @@ * SQL Server: Fix issue related to writing when using SIMBA drivers (#816). +* `snowflake()` and `databricks()` now accept a `session` argument for passing + viewer-based OAuth credentials from Shiny sessions on Posit Connect + (@atheriel, #853). + # odbc 1.5.0 ## Major changes diff --git a/R/driver-databricks.R b/R/driver-databricks.R index bc069706..eed3d898 100644 --- a/R/driver-databricks.R +++ b/R/driver-databricks.R @@ -31,6 +31,8 @@ NULL #' default name. #' @param uid,pwd Manually specify a username and password for authentication. #' Specifying these options will disable automated credential discovery. +#' @param session A Shiny session object, when using viewer-based credentials on +#' Posit Connect. #' @param ... Further arguments passed on to [`dbConnect()`]. #' #' @returns An `OdbcConnection` object with an active connection to a Databricks @@ -42,6 +44,16 @@ NULL #' odbc::databricks(), #' httpPath = "sql/protocolv1/o/4425955464597947/1026-023828-vn51jugj" #' ) +#' +#' # Use credentials from the viewer (when possible) in a Shiny app +#' # deployed to Posit Connect. +#' server <- function(input, output, session) { +#' conn <- DBI::dbConnect( +#' odbc::databricks(), +#' httpPath = "sql/protocolv1/o/4425955464597947/1026-023828-vn51jugj", +#' session = session +#' ) +#' } #' } #' @export databricks <- function() { @@ -64,6 +76,7 @@ setMethod("dbConnect", "DatabricksOdbcDriver", HTTPPath, uid = NULL, pwd = NULL, + session = NULL, ...) { call <- caller_env() # For backward compatibility with RStudio connection string @@ -74,6 +87,7 @@ setMethod("dbConnect", "DatabricksOdbcDriver", check_string(driver, allow_null = TRUE, call = call) check_string(uid, allow_null = TRUE, call = call) check_string(pwd, allow_null = TRUE, call = call) + check_shiny_session(session, allow_null = TRUE, call = call) args <- databricks_args( httpPath = if (missing(httpPath)) HTTPPath else httpPath, @@ -82,6 +96,7 @@ setMethod("dbConnect", "DatabricksOdbcDriver", driver = driver, uid = uid, pwd = pwd, + session = session, ... ) inject(dbConnect(odbc(), !!!args)) @@ -94,6 +109,7 @@ databricks_args <- function(httpPath, driver = NULL, uid = NULL, pwd = NULL, + session = NULL, ...) { host <- databricks_host(workspace) @@ -104,18 +120,21 @@ databricks_args <- function(httpPath, useNativeQuery = useNativeQuery ) - auth <- databricks_auth_args(host, uid = uid, pwd = pwd) + auth <- databricks_auth_args(host, uid = uid, pwd = pwd, session = session) all <- utils::modifyList(c(args, auth), list(...)) arg_names <- tolower(names(all)) if (!"authmech" %in% arg_names && !all(c("uid", "pwd") %in% arg_names)) { - abort( - c( - "x" = "Failed to detect ambient Databricks credentials.", - "i" = "Supply `uid` and `pwd` to authenticate manually." - ), - call = quote(DBI::dbConnect()) + msg <- c( + "Failed to detect ambient Databricks credentials.", + "i" = "Supply {.arg uid} and {.arg pwd} to authenticate manually." ) + if (running_on_connect()) { + msg <- c( + msg, "i" = "Or pass {.arg session} for viewer-based credentials." + ) + } + cli::cli_abort(msg, call = quote(DBI::dbConnect())) } all @@ -202,7 +221,16 @@ databricks_user_agent <- function() { user_agent } -databricks_auth_args <- function(host, uid = NULL, pwd = NULL) { +databricks_auth_args <- function(host, uid = NULL, pwd = NULL, session = NULL) { + # If a session is supplied, any viewer-based auth takes precedence. + if (!is.null(session)) { + check_installed("httr2", "for viewer-based authentication") + access_token <- connect_viewer_token(session, paste0("https://", host)) + if (!is.null(access_token)) { + return(list(authMech = 11, auth_flow = 0, auth_accesstoken = access_token)) + } + } + if (!is.null(uid) && !is.null(pwd)) { return(list(uid = uid, pwd = pwd, authMech = 3)) } else if (xor(is.null(uid), is.null(pwd))) { diff --git a/R/driver-snowflake.R b/R/driver-snowflake.R index fb5c98a7..98833f94 100644 --- a/R/driver-snowflake.R +++ b/R/driver-snowflake.R @@ -114,6 +114,8 @@ setMethod("odbcDataType", "Snowflake", #' default. #' @param uid,pwd Manually specify a username and password for authentication. #' Specifying these options will disable ambient credential discovery. +#' @param session A Shiny session object, when using viewer-based credentials on +#' Posit Connect. #' @param ... Further arguments passed on to [`dbConnect()`]. #' #' @returns An `OdbcConnection` object with an active connection to a Snowflake @@ -138,6 +140,12 @@ setMethod("odbcDataType", "Snowflake", #' uid = "me", #' pwd = rstudioapi::askForPassword() #' ) +#' +#' # Use credentials from the viewer (when possible) in a Shiny app +#' # deployed to Posit Connect. +#' server <- function(input, output, session) { +#' conn <- DBI::dbConnect(odbc::snowflake(), session = session) +#' } #' } #' @export snowflake <- function() { @@ -156,6 +164,7 @@ setMethod( schema = NULL, uid = NULL, pwd = NULL, + session = NULL, ...) { call <- caller_env() check_string(account, call = call) @@ -164,6 +173,7 @@ setMethod( check_string(database, allow_null = TRUE, call = call) check_string(uid, allow_null = TRUE, call = call) check_string(pwd, allow_null = TRUE, call = call) + check_shiny_session(session, allow_null = TRUE, call = call) args <- snowflake_args( account = account, driver = driver, @@ -172,6 +182,7 @@ setMethod( schema = schema, uid = uid, pwd = pwd, + session = session, ... ) inject(dbConnect(odbc(), !!!args)) @@ -202,13 +213,16 @@ snowflake_args <- function(account = Sys.getenv("SNOWFLAKE_ACCOUNT"), arg_names <- tolower(names(all)) if (!"authenticator" %in% arg_names && !all(c("uid", "pwd") %in% arg_names)) { - abort( - c( - "x" = "Failed to detect ambient Snowflake credentials.", - "i" = "Supply `uid` and `pwd` to authenticate manually." - ), - call = quote(DBI::dbConnect()) + msg <- c( + "Failed to detect ambient Snowflake credentials.", + "i" = "Supply {.arg uid} and {.arg pwd} to authenticate manually." ) + if (running_on_connect()) { + msg <- c( + msg, "i" = "Or pass {.arg session} for viewer-based credentials." + ) + } + cli::cli_abort(msg, call = quote(DBI::dbConnect())) } all @@ -270,7 +284,19 @@ snowflake_auth_args <- function(account, uid = NULL, pwd = NULL, authenticator = NULL, + session = NULL, ...) { + # If a session is supplied, any viewer-based auth takes precedence. + if (!is.null(session)) { + check_installed("httr2", "for viewer-based authentication") + access_token <- connect_viewer_token( + session, paste0("https://", account, ".snowflakecomputing.com") + ) + if (!is.null(access_token)) { + return(list(authenticator = "oauth", token = access_token)) + } + } + if (!is.null(uid) && # allow for uid without pwd for externalbrowser auth (#817) (!is.null(pwd) || identical(authenticator, "externalbrowser"))) { diff --git a/R/utils.R b/R/utils.R index e0d8796d..a2bc88b4 100644 --- a/R/utils.R +++ b/R/utils.R @@ -454,3 +454,79 @@ replace_or_append <- function(lines, pattern, replacement) { } lines } + +check_shiny_session <- function(x, + ..., + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (!missing(x)) { + if (inherits(x, "ShinySession")) { + return(invisible(NULL)) + } + if (allow_null && is_null(x)) { + return(invisible(NULL)) + } + } + + stop_input_type( + x, + "a Shiny session object", + ..., + allow_null = allow_null, + arg = arg, + call = call + ) +} + +# Request an OAuth access token for the given resource from Posit Connect. The +# OAuth token will belong to the user owning the given Shiny session. +connect_viewer_token <- function(session, resource) { + # Ensure we're running on Connect. + server_url <- Sys.getenv("CONNECT_SERVER") + api_key <- Sys.getenv("CONNECT_API_KEY") + if (!running_on_connect() || nchar(server_url) == 0 || nchar(api_key) == 0) { + cli::cli_inform(c( + "!" = "Ignoring {.arg sesssion} parameter.", + "i" = "Viewer-based credentials are only available when running on Connect." + )) + return(NULL) + } + + # Older versions or certain configurations of Connect might not supply a user + # session token. + token <- session$request$HTTP_POSIT_CONNECT_USER_SESSION_TOKEN + if (is.null(token)) { + cli::cli_abort( + "Viewer-based credentials are not supported by this version of Connect." + ) + } + + # See: https://docs.posit.co/connect/api/#post-/v1/oauth/integrations/credentials + req <- httr2::request(server_url) + req <- httr2::req_url_path_append( + req, "__api__/v1/oauth/integrations/credentials" + ) + req <- httr2::req_headers(req, + Authorization = paste("Key", api_key), .redact = "Authorization" + ) + req <- httr2::req_body_form( + req, + grant_type = "urn:ietf:params:oauth:grant-type:token-exchange", + subject_token_type = "urn:posit:connect:user-session-token", + subject_token = token, + resource = resource + ) + + # TODO: Do we need more precise error handling? + req <- httr2::req_error( + req, body = function(resp) httr2::resp_body_json(resp)$error + ) + + resp <- httr2::resp_body_json(httr2::req_perform(req)) + resp$access_token +} + +running_on_connect <- function() { + Sys.getenv("RSTUDIO_PRODUCT") == "CONNECT" +} diff --git a/man/databricks.Rd b/man/databricks.Rd index 5d385af2..1e2204ad 100644 --- a/man/databricks.Rd +++ b/man/databricks.Rd @@ -18,6 +18,7 @@ databricks() HTTPPath, uid = NULL, pwd = NULL, + session = NULL, ... ) } @@ -43,6 +44,9 @@ default name.} \item{uid, pwd}{Manually specify a username and password for authentication. Specifying these options will disable automated credential discovery.} +\item{session}{A Shiny session object, when using viewer-based credentials on +Posit Connect.} + \item{...}{Further arguments passed on to \code{\link[=dbConnect]{dbConnect()}}.} } \value{ @@ -66,5 +70,15 @@ DBI::dbConnect( odbc::databricks(), httpPath = "sql/protocolv1/o/4425955464597947/1026-023828-vn51jugj" ) + +# Use credentials from the viewer (when possible) in a Shiny app +# deployed to Posit Connect. +server <- function(input, output, session) { + conn <- DBI::dbConnect( + odbc::databricks(), + httpPath = "sql/protocolv1/o/4425955464597947/1026-023828-vn51jugj", + session = session + ) +} } } diff --git a/man/snowflake.Rd b/man/snowflake.Rd index 45b2713c..595636ae 100644 --- a/man/snowflake.Rd +++ b/man/snowflake.Rd @@ -16,6 +16,7 @@ snowflake() schema = NULL, uid = NULL, pwd = NULL, + session = NULL, ... ) } @@ -42,6 +43,9 @@ default.} \item{uid, pwd}{Manually specify a username and password for authentication. Specifying these options will disable ambient credential discovery.} +\item{session}{A Shiny session object, when using viewer-based credentials on +Posit Connect.} + \item{...}{Further arguments passed on to \code{\link[=dbConnect]{dbConnect()}}.} } \value{ @@ -74,5 +78,11 @@ DBI::dbConnect( uid = "me", pwd = rstudioapi::askForPassword() ) + +# Use credentials from the viewer (when possible) in a Shiny app +# deployed to Posit Connect. +server <- function(input, output, session) { + conn <- DBI::dbConnect(odbc::snowflake(), session = session) +} } } diff --git a/tests/testthat/_snaps/driver-databricks.md b/tests/testthat/_snaps/driver-databricks.md index ecffdba3..474945fc 100644 --- a/tests/testthat/_snaps/driver-databricks.md +++ b/tests/testthat/_snaps/driver-databricks.md @@ -22,7 +22,7 @@ . <- databricks_args1() Condition Error in `DBI::dbConnect()`: - ! x Failed to detect ambient Databricks credentials. + ! Failed to detect ambient Databricks credentials. i Supply `uid` and `pwd` to authenticate manually. # must supply both uid and pwd @@ -58,3 +58,22 @@ Error in `dbConnect()`: ! `httpPath` must be a single string or `NULL`, not the number 1. +# we mention viewer-based credentials have no effect locally + + Code + ignored <- databricks_args(workspace = "workspace", httpPath = "path", uid = "uid", + pwd = "pwd", session = list()) + Message + ! Ignoring `sesssion` parameter. + i Viewer-based credentials are only available when running on Connect. + +# we hint viewer-based credentials on Connect + + Code + databricks_args(workspace = "workspace", httpPath = "path") + Condition + Error in `DBI::dbConnect()`: + ! Failed to detect ambient Databricks credentials. + i Supply `uid` and `pwd` to authenticate manually. + i Or pass `session` for viewer-based credentials. + diff --git a/tests/testthat/_snaps/driver-snowflake.md b/tests/testthat/_snaps/driver-snowflake.md index 50822e5b..8b4f9a1b 100644 --- a/tests/testthat/_snaps/driver-snowflake.md +++ b/tests/testthat/_snaps/driver-snowflake.md @@ -23,9 +23,28 @@ snowflake_args(account = "testorg-test_account", driver = "driver") Condition Error in `DBI::dbConnect()`: - ! x Failed to detect ambient Snowflake credentials. + ! Failed to detect ambient Snowflake credentials. i Supply `uid` and `pwd` to authenticate manually. +# we mention viewer-based credentials have no effect locally + + Code + ignored <- snowflake_args(account = "testorg-test_account", driver = "driver", + uid = "uid", pwd = "pwd", session = list()) + Message + ! Ignoring `sesssion` parameter. + i Viewer-based credentials are only available when running on Connect. + +# we hint viewer-based credentials on Connect + + Code + snowflake_args(account = "testorg-test_account", driver = "driver") + Condition + Error in `DBI::dbConnect()`: + ! Failed to detect ambient Snowflake credentials. + i Supply `uid` and `pwd` to authenticate manually. + i Or pass `session` for viewer-based credentials. + # we error if we can't find the driver Code @@ -41,6 +60,6 @@ snowflake_args(account = "testorg-test_account", driver = "driver") Condition Error in `DBI::dbConnect()`: - ! x Failed to detect ambient Snowflake credentials. + ! Failed to detect ambient Snowflake credentials. i Supply `uid` and `pwd` to authenticate manually. diff --git a/tests/testthat/_snaps/utils.md b/tests/testthat/_snaps/utils.md index 51fe4c10..a36a506e 100644 --- a/tests/testthat/_snaps/utils.md +++ b/tests/testthat/_snaps/utils.md @@ -154,3 +154,19 @@ ! Detected needed changes to the driver configuration file at ., but the file was not writeable. i Please make the changes outlined at https://solutions.posit.co/connections/db/databases/databricks/#troubleshooting-apple-macos-users. +# viewer-based credentials are only available on Connect + + Code + token <- connect_viewer_token() + Message + ! Ignoring `sesssion` parameter. + i Viewer-based credentials are only available when running on Connect. + +# viewer-based credentials require a recent Connect version + + Code + token <- connect_viewer_token(session) + Condition + Error in `connect_viewer_token()`: + ! Viewer-based credentials are not supported by this version of Connect. + diff --git a/tests/testthat/test-driver-databricks.R b/tests/testthat/test-driver-databricks.R index 80d2b45b..bdd63cb2 100644 --- a/tests/testthat/test-driver-databricks.R +++ b/tests/testthat/test-driver-databricks.R @@ -152,3 +152,25 @@ test_that("Workbench-managed credentials are ignored for other hosts", { ) expect_equal(databricks_auth_args(host = "some-host"), NULL) }) + +test_that("we mention viewer-based credentials have no effect locally", { + expect_snapshot( + ignored <- databricks_args( + workspace = "workspace", + httpPath = "path", + uid = "uid", + pwd = "pwd", + session = list() + ) + ) +}) + +test_that("we hint viewer-based credentials on Connect", { + local_mocked_bindings( + running_on_connect = function() TRUE + ) + expect_snapshot( + databricks_args(workspace = "workspace", httpPath = "path"), + error = TRUE + ) +}) diff --git a/tests/testthat/test-driver-snowflake.R b/tests/testthat/test-driver-snowflake.R index 329e1a72..affd83a5 100644 --- a/tests/testthat/test-driver-snowflake.R +++ b/tests/testthat/test-driver-snowflake.R @@ -98,6 +98,31 @@ test_that("we error if we can't find ambient credentials", { ) }) +test_that("we mention viewer-based credentials have no effect locally", { + withr::local_envvar(SF_PARTNER = "") + expect_snapshot( + ignored <- snowflake_args( + account = "testorg-test_account", + driver = "driver", + uid = "uid", + pwd = "pwd", + session = list() + ) + ) +}) + +test_that("we hint viewer-based credentials on Connect", { + withr::local_envvar(SF_PARTNER = "") + local_mocked_bindings( + snowflake_auth_args = function(...) list(), + running_on_connect = function() TRUE + ) + expect_snapshot( + snowflake_args(account = "testorg-test_account", driver = "driver"), + error = TRUE + ) +}) + test_that("the default driver falls back to a known driver name", { local_mocked_bindings( snowflake_default_driver_paths = function() character(), diff --git a/tests/testthat/test-utils.R b/tests/testthat/test-utils.R index 87d1b696..0be643cd 100644 --- a/tests/testthat/test-utils.R +++ b/tests/testthat/test-utils.R @@ -265,3 +265,15 @@ test_that("configure_unixodbc_spark() writes reasonable entries", { ) ) }) + +test_that("viewer-based credentials are only available on Connect", { + expect_snapshot(token <- connect_viewer_token()) +}) + +test_that("viewer-based credentials require a recent Connect version", { + withr::local_envvar(CONNECT_SERVER = "localhost:3939", CONNECT_API_KEY = "x") + local_mocked_bindings(running_on_connect = function() TRUE) + # Mock a Shiny session object. + session <- list(request = list()) + expect_snapshot(token <- connect_viewer_token(session), error = TRUE) +})