diff --git a/NAMESPACE b/NAMESPACE index 8436755..8345eff 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -2,6 +2,7 @@ export(api_key_security_scheme) export(as_api_key_security_scheme) +export(as_api_object) export(as_component_collection) export(as_contact) export(as_info) @@ -12,7 +13,6 @@ export(as_oauth2_security_scheme) export(as_oauth2_token_flow) export(as_origin) export(as_rapid) -export(as_rapid_class) export(as_scopes) export(as_security_requirements) export(as_security_scheme) @@ -21,6 +21,8 @@ export(as_security_scheme_details) export(as_server_variables) export(as_servers) export(as_string_replacements) +export(caller_arg) +export(caller_env) export(class_origin) export(component_collection) export(contact) @@ -48,6 +50,8 @@ importFrom(S7,class_missing) importFrom(S7,prop) importFrom(glue,glue) importFrom(rlang,"%||%") +importFrom(rlang,caller_arg) +importFrom(rlang,caller_env) importFrom(rlang,check_dots_empty) importFrom(stbl,stabilize_chr_scalar) importFrom(stbl,to_chr_scalar) diff --git a/R/absolute_paths.R b/R/absolute_paths.R index df72783..92b072b 100644 --- a/R/absolute_paths.R +++ b/R/absolute_paths.R @@ -13,7 +13,7 @@ NULL #' @return A `rapid` object as returned by [rapid()], with absolute server #' paths. #' @export -expand_servers <- S7::new_generic("expand_servers", dispatch_args = "x") +expand_servers <- S7::new_generic("expand_servers", "x") S7::method(expand_servers, rapid) <- function(x) { if (length(x@servers@url)) { @@ -37,8 +37,8 @@ S7::method(expand_servers, rapid) <- function(x) { } S7::method(expand_servers, class_any) <- function(x, - arg = rlang::caller_arg(x), - call = rlang::caller_env()) { + arg = caller_arg(x), + call = caller_env()) { cli::cli_abort( "{.arg {arg}} {.cls {class(x)}} must be a {.cls rapid}.", call = call diff --git a/R/as.R b/R/as.R index 523c944..64cdc41 100644 --- a/R/as.R +++ b/R/as.R @@ -1,6 +1,6 @@ -#' Convert to a rapid-style class +#' Convert to a rapid-style object #' -#' Convert a named list into a rapid-style class. +#' Convert a named list into an object with a rapid-style class. #' #' @inheritParams rlang::args_dots_empty #' @inheritParams rlang::args_error_context @@ -14,11 +14,34 @@ #' #' @return An object with the specified `target_class`. #' @export -as_rapid_class <- function(x, - target_class, - alternate_names = NULL, - arg = rlang::caller_arg(x), - call = rlang::caller_env()) { +as_api_object <- S7::new_generic( + "as_api_object", + "x", + function(x, + target_class, + ..., + alternate_names = NULL, + arg = caller_arg(x), + call = caller_env()) { + if (missing(x)) return(target_class()) + force(arg) + rlang::check_dots_empty(call = call) + if (S7::S7_inherits(x, target_class)) { + return(x) + } + S7::S7_dispatch() + } +) + +S7::method( + as_api_object, + class_list | class_character +) <- function(x, + target_class, + ..., + alternate_names = NULL, + arg = caller_arg(x), + call = caller_env()) { force(arg) x <- .validate_for_as_class( x, @@ -32,11 +55,37 @@ as_rapid_class <- function(x, }) } +S7::method( + as_api_object, + NULL | S7::new_S3_class("S7_missing") +) <- function(x, + target_class, + ..., + alternate_names = NULL, + arg = caller_arg(x), + call = caller_env()) { + target_class() +} + +S7::method(as_api_object, class_any) <- function(x, + target_class, + ..., + alternate_names = NULL, + arg = caller_arg(x), + call = caller_env()) { + target_class_nm <- class(target_class())[[1]] + cli::cli_abort( + "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls {target_class_nm}}.", + class = "rapid_error_unknown_coercion", + call = call + ) +} + .validate_for_as_class <- function(x, target_class, alternate_names = NULL, - x_arg = rlang::caller_arg(x), - call = rlang::caller_env()) { + x_arg = caller_arg(x), + call = caller_env()) { if (!length(x)) { return(NULL) } diff --git a/R/components-security_scheme-api_key.R b/R/components-security_scheme-api_key.R index 1671c6c..2a49f91 100644 --- a/R/components-security_scheme-api_key.R +++ b/R/components-security_scheme-api_key.R @@ -70,38 +70,16 @@ S7::method(length, api_key_security_scheme) <- function(x) { #' @return An `api_key_security_scheme` as returned by #' [api_key_security_scheme()]. #' @export -as_api_key_security_scheme <- S7::new_generic( - "as_api_key_security_scheme", - dispatch_args = "x" -) - -S7::method(as_api_key_security_scheme, api_key_security_scheme) <- function(x) { - x -} - -S7::method( - as_api_key_security_scheme, - class_list | class_character -) <- function(x) { - as_rapid_class( +as_api_key_security_scheme <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { + as_api_object( x, api_key_security_scheme, - alternate_names = c("in" = "location", "name" = "parameter_name") - ) -} - -S7::method( - as_api_key_security_scheme, - class_missing | NULL | S7::new_S3_class("S7_missing") -) <- function(x) { - api_key_security_scheme() -} - -S7::method( - as_api_key_security_scheme, - class_any -) <- function(x, ..., arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls api_key_security_scheme}." + ..., + alternate_names = c("in" = "location", "name" = "parameter_name"), + arg = arg, + call = call ) } diff --git a/R/components-security_scheme-oauth2-authorization_code_flow.R b/R/components-security_scheme-oauth2-authorization_code_flow.R index 6870c59..f431761 100644 --- a/R/components-security_scheme-oauth2-authorization_code_flow.R +++ b/R/components-security_scheme-oauth2-authorization_code_flow.R @@ -77,37 +77,9 @@ S7::method(length, oauth2_authorization_code_flow) <- function(x) { #' @return An `oauth2_authorization_code_flow` as returned by #' [oauth2_authorization_code_flow()]. #' @export -as_oauth2_authorization_code_flow <- S7::new_generic( - "as_oauth2_authorization_code_flow", - dispatch_args = "x" -) - -S7::method( - as_oauth2_authorization_code_flow, - oauth2_authorization_code_flow -) <- function(x) { - x -} - -S7::method( - as_oauth2_authorization_code_flow, - class_list | class_character -) <- function(x) { - as_rapid_class(x, oauth2_authorization_code_flow) -} - -S7::method( - as_oauth2_authorization_code_flow, - class_missing | NULL | S7::new_S3_class("S7_missing") -) <- function(x) { - oauth2_authorization_code_flow() -} - -S7::method( - as_oauth2_authorization_code_flow, - class_any -) <- function(x, ..., arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls oauth2_authorization_code_flow}." - ) +as_oauth2_authorization_code_flow <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { + as_api_object(x, oauth2_authorization_code_flow, ..., arg = arg, call = call) } diff --git a/R/components-security_scheme-oauth2-implicit_flow.R b/R/components-security_scheme-oauth2-implicit_flow.R index 6e989ad..dbedcc6 100644 --- a/R/components-security_scheme-oauth2-implicit_flow.R +++ b/R/components-security_scheme-oauth2-implicit_flow.R @@ -66,34 +66,9 @@ S7::method(length, oauth2_implicit_flow) <- function(x) { #' #' @return An `oauth2_implicit_flow` as returned by [oauth2_implicit_flow()]. #' @export -as_oauth2_implicit_flow <- S7::new_generic( - "as_oauth2_implicit_flow", - dispatch_args = "x" -) - -S7::method(as_oauth2_implicit_flow, oauth2_implicit_flow) <- function(x) { - x -} - -S7::method( - as_oauth2_implicit_flow, - class_list | class_character -) <- function(x) { - as_rapid_class(x, oauth2_implicit_flow) -} - -S7::method( - as_oauth2_implicit_flow, - class_missing | NULL | S7::new_S3_class("S7_missing") -) <- function(x) { - oauth2_implicit_flow() -} - -S7::method( - as_oauth2_implicit_flow, - class_any -) <- function(x, ..., arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls oauth2_implicit_flow}." - ) +as_oauth2_implicit_flow <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { + as_api_object(x, oauth2_implicit_flow, ..., arg = arg, call = call) } diff --git a/R/components-security_scheme-oauth2-scopes.R b/R/components-security_scheme-oauth2-scopes.R index b62151a..f2c3409 100644 --- a/R/components-security_scheme-oauth2-scopes.R +++ b/R/components-security_scheme-oauth2-scopes.R @@ -69,25 +69,19 @@ S7::method(length, scopes) <- function(x) { #' #' @return A `scopes` as returned by [scopes()]. #' @export -as_scopes <- S7::new_generic( - "as_scopes", - dispatch_args = "x" -) - -S7::method(as_scopes, scopes) <- function(x) { - x -} +as_scopes <- S7::new_generic("as_scopes", "x") S7::method( as_scopes, class_list | class_character -) <- function(x, ..., arg = rlang::caller_arg(x)) { +) <- function(x, ..., arg = caller_arg(x), call = caller_env()) { force(arg) x <- unlist(x) x <- stbl::stabilize_chr(x, x_arg = arg) if (!rlang::is_named2(x)) { cli::cli_abort( "{.arg {arg}} must be a named character vector.", + call = call ) } scopes( @@ -96,17 +90,9 @@ S7::method( ) } -S7::method( - as_scopes, - class_missing | NULL | S7::new_S3_class("S7_missing") -) <- function(x) { - scopes() -} - S7::method(as_scopes, class_any) <- function(x, ..., - arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls scopes}." - ) + arg = caller_arg(x), + call = caller_env()) { + as_api_object(x, scopes, ..., arg = arg, call = call) } diff --git a/R/components-security_scheme-oauth2-token_flow.R b/R/components-security_scheme-oauth2-token_flow.R index 9894f76..51a7c88 100644 --- a/R/components-security_scheme-oauth2-token_flow.R +++ b/R/components-security_scheme-oauth2-token_flow.R @@ -73,31 +73,9 @@ S7::method(length, oauth2_token_flow) <- function(x) { #' #' @return An `oauth2_token_flow` as returned by [oauth2_token_flow()]. #' @export -as_oauth2_token_flow <- S7::new_generic( - "as_oauth2_token_flow", - dispatch_args = "x" -) - -S7::method(as_oauth2_token_flow, oauth2_token_flow) <- function(x) { - x -} - -S7::method(as_oauth2_token_flow, class_list | class_character) <- function(x) { - as_rapid_class(x, oauth2_token_flow) -} - -S7::method( - as_oauth2_token_flow, - class_missing | NULL | S7::new_S3_class("S7_missing") -) <- function(x) { - oauth2_token_flow() -} - -S7::method( - as_oauth2_token_flow, - class_any -) <- function(x, ..., arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls oauth2_token_flow}." - ) +as_oauth2_token_flow <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { + as_api_object(x, oauth2_token_flow, ..., arg = arg, call = call) } diff --git a/R/components-security_scheme-oauth2.R b/R/components-security_scheme-oauth2.R index f2b9e97..a6c48ad 100644 --- a/R/components-security_scheme-oauth2.R +++ b/R/components-security_scheme-oauth2.R @@ -75,23 +75,21 @@ S7::method(length, oauth2_security_scheme) <- function(x) { #' @return An `oauth2_security_scheme` as returned by #' [oauth2_security_scheme()]. #' @export -as_oauth2_security_scheme <- S7::new_generic( - "as_oauth2_security_scheme", - dispatch_args = "x" -) - -S7::method(as_oauth2_security_scheme, oauth2_security_scheme) <- function(x) { - x -} +as_oauth2_security_scheme <- S7::new_generic("as_oauth2_security_scheme", "x") -S7::method(as_oauth2_security_scheme, class_list) <- function(x) { +S7::method( + as_oauth2_security_scheme, + class_list +) <- function(x, ..., arg = caller_arg(x), call = caller_env()) { + force(arg) if (!length(x) || !any(lengths(x))) { return(oauth2_security_scheme()) } if (!("flows" %in% names(x))) { cli::cli_abort( - "{.arg x} must contain a named flows object." + "{.arg {arg}} must contain a named flows object.", + call = call ) } names(x$flows) <- snakecase::to_snake_case(names(x$flows)) @@ -103,18 +101,9 @@ S7::method(as_oauth2_security_scheme, class_list) <- function(x) { ) } -S7::method( - as_oauth2_security_scheme, - class_missing | NULL | S7::new_S3_class("S7_missing") -) <- function(x) { - oauth2_security_scheme() -} - S7::method( as_oauth2_security_scheme, class_any -) <- function(x, ..., arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls oauth2_security_scheme}." - ) +) <- function(x, ..., arg = caller_arg(x), call = caller_env()) { + as_api_object(x, oauth2_security_scheme, ..., arg = arg, call = call) } diff --git a/R/components-security_scheme.R b/R/components-security_scheme.R index 4a34847..e51d3ca 100644 --- a/R/components-security_scheme.R +++ b/R/components-security_scheme.R @@ -68,34 +68,41 @@ security_scheme <- S7::new_class( #' type = "apiKey" #' ) #' ) -as_security_scheme <- S7::new_generic("as_security_scheme", dispatch_args = "x") +as_security_scheme <- S7::new_generic("as_security_scheme", "x") -S7::method(as_security_scheme, security_scheme) <- function(x) { +S7::method(as_security_scheme, security_scheme) <- function(x, ...) { x } -S7::method(as_security_scheme, class_list) <- function(x) { +S7::method(as_security_scheme, class_list) <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { if (!length(x) || !any(lengths(x))) { return(NULL) } type <- snakecase::to_snake_case(x$type) x$type <- NULL switch(type, - api_key = as_api_key_security_scheme(x), - # http = as_http_security_scheme(x), - # mutual_tls = as_mutual_tls_security_scheme(x), - oauth_2 = as_oauth2_security_scheme(x), - oauth2 = as_oauth2_security_scheme(x) # , - # open_id_connect = as_open_id_connect_security_scheme(x) + api_key = as_api_key_security_scheme(x, ..., arg = arg, call = call), + oauth_2 = as_oauth2_security_scheme(x, ..., arg = arg, call = call), + oauth2 = as_oauth2_security_scheme(x, ..., arg = arg, call = call) ) } -S7::method(as_security_scheme, class_missing | NULL) <- function(x) { +S7::method( + as_security_scheme, + class_missing | NULL +) <- function(x, ..., arg = caller_arg(x), call = caller_env()) { NULL } -S7::method(as_security_scheme, class_any) <- function(x) { +S7::method(as_security_scheme, class_any) <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { cli::cli_abort( - "Can't coerce {.arg x} {.cls {class(x)}} to {.cls security_scheme}." + "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls rapid::security_scheme}.", + call = call ) } diff --git a/R/components-security_scheme_collection.R b/R/components-security_scheme_collection.R index 18cc480..d1d00cf 100644 --- a/R/components-security_scheme_collection.R +++ b/R/components-security_scheme_collection.R @@ -143,17 +143,14 @@ S7::method(length, security_scheme_collection) <- function(x) { #' ) as_security_scheme_collection <- S7::new_generic( "as_security_scheme_collection", - dispatch_args = "x" + "x" ) S7::method( as_security_scheme_collection, - security_scheme_collection -) <- function(x) { - x -} - -S7::method(as_security_scheme_collection, class_list) <- function(x) { + class_list +) <- function(x, ..., arg = caller_arg(x), call = caller_env()) { + force(arg) # This is the first one where we're fundamentally rearranging things, so watch # out for new things to standardize (and then delete this comment)! if (!length(x) || !any(lengths(x))) { @@ -172,21 +169,15 @@ S7::method(as_security_scheme_collection, class_list) <- function(x) { ) ) } - cli::cli_abort(c("{.arg {x}} must have names.")) -} - -S7::method( - as_security_scheme_collection, - class_missing | NULL | S7::new_S3_class("S7_missing") -) <- function(x) { - security_scheme_collection() + cli::cli_abort( + c("{.arg {arg}} must have names."), + call = call + ) } S7::method( as_security_scheme_collection, class_any -) <- function(x, ..., arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls security_scheme_collection}." - ) +) <- function(x, ..., arg = caller_arg(x), call = caller_env()) { + as_api_object(x, security_scheme_collection, ..., arg = arg, call = call) } diff --git a/R/components-security_scheme_details.R b/R/components-security_scheme_details.R index 3d10ed5..b74657e 100644 --- a/R/components-security_scheme_details.R +++ b/R/components-security_scheme_details.R @@ -133,36 +133,28 @@ security_scheme_details <- S7::new_class( #' ) #' ) #' ) -as_security_scheme_details <- S7::new_generic( - "as_security_scheme_details", - dispatch_args = "x" -) - -S7::method(as_security_scheme_details, security_scheme_details) <- function(x) { - x -} +as_security_scheme_details <- S7::new_generic("as_security_scheme_details", "x") -S7::method(as_security_scheme_details, class_list) <- function(x) { +S7::method( + as_security_scheme_details, + class_list +) <- function(x, ..., arg = caller_arg(x), call = caller_env()) { if (!length(x) || !any(lengths(x))) { return(security_scheme_details()) } security_scheme_details( - purrr::map(unname(x), as_security_scheme) + purrr::map( + unname(x), + function(x) { + as_security_scheme(x, ..., arg = arg, call = call) + } + ) ) } -S7::method( - as_security_scheme_details, - class_missing | NULL | S7::new_S3_class("S7_missing") -) <- function(x) { - security_scheme_details() -} - S7::method( as_security_scheme_details, class_any -) <- function(x, ..., arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls security_scheme_details}." - ) +) <- function(x, ..., arg = caller_arg(x), call = caller_env()) { + as_api_object(x, security_scheme_details, ..., arg = arg, call = call) } diff --git a/R/components.R b/R/components.R index 0585e3c..09ba23b 100644 --- a/R/components.R +++ b/R/components.R @@ -110,28 +110,9 @@ S7::method(length, component_collection) <- function(x) { #' ) #' ) #' )) -as_component_collection <- S7::new_generic( - "as_component_collection", - dispatch_args = "x" -) - -S7::method(as_component_collection, component_collection) <- function(x) { - x -} - -S7::method(as_component_collection, class_list) <- function(x) { - as_rapid_class(x, component_collection) -} - -S7::method(as_component_collection, class_missing | NULL) <- function(x) { - component_collection() -} - -S7::method( - as_component_collection, - class_any -) <- function(x, ..., arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls component_collection}." - ) +as_component_collection <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { + as_api_object(x, component_collection, ..., arg = arg, call = call) } diff --git a/R/info-contact.R b/R/info-contact.R index 85137ba..573604d 100644 --- a/R/info-contact.R +++ b/R/info-contact.R @@ -59,27 +59,6 @@ S7::method(length, contact) <- function(x) { #' @examples #' as_contact() #' as_contact(list(name = "Jon Harmon", email = "jonthegeek@gmail.com")) -as_contact <- S7::new_generic("as_contact", dispatch_args = "x") - -S7::method(as_contact, contact) <- function(x) { - x -} - -S7::method(as_contact, class_list | class_character) <- function(x) { - as_rapid_class(x, contact) -} - -S7::method( - as_contact, - class_missing | NULL | S7::new_S3_class("S7_missing") -) <- function(x) { - contact() -} - -S7::method(as_contact, class_any) <- function(x, - ..., - arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls contact}." - ) +as_contact <- function(x, ..., arg = caller_arg(x), call = caller_env()) { + as_api_object(x, contact, ..., arg = arg, call = call) } diff --git a/R/info-license.R b/R/info-license.R index 1e9d942..593d0d6 100644 --- a/R/info-license.R +++ b/R/info-license.R @@ -81,27 +81,6 @@ S7::method(length, license) <- function(x) { #' @examples #' as_license() #' as_license(list(name = "Apache 2.0", identifier = "Apache-2.0")) -as_license <- S7::new_generic("as_license", dispatch_args = "x") - -S7::method(as_license, license) <- function(x) { - x -} - -S7::method(as_license, class_list | class_character) <- function(x) { - as_rapid_class(x, license) -} - -S7::method( - as_license, - class_missing | NULL | S7::new_S3_class("S7_missing") -) <- function(x) { - license() -} - -S7::method(as_license, class_any) <- function(x, - ..., - arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls license}." - ) +as_license <- function(x, ..., arg = caller_arg(x), call = caller_env()) { + as_api_object(x, license, ..., arg = arg, call = call) } diff --git a/R/info-origin.R b/R/info-origin.R index da94898..91a49c2 100644 --- a/R/info-origin.R +++ b/R/info-origin.R @@ -89,34 +89,33 @@ S7::method(length, class_origin) <- function(x) { #' ) #' ) #' ) -as_origin <- S7::new_generic("as_origin", dispatch_args = "x") +as_origin <- S7::new_generic("as_origin", "x", function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { + S7::S7_dispatch() +}) -S7::method(as_origin, class_origin) <- function(x) { - x +S7::method(as_origin, class_any) <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { + as_api_object(x, class_origin, ..., arg = arg, call = call) } -S7::method(as_origin, class_list | class_character) <- function(x) { +S7::method( + as_origin, + class_list | class_character +) <- function(x, ..., arg = caller_arg(x), call = caller_env()) { + force(arg) # Case 1: Passed in as a simple character vector, or that wrapped in a list. - if (length(x) == 1 && lengths(x) == 1 && is.character(unlist(x))) { + if (length(x) == 1 && is.character(unlist(x)) && lengths(x) == 1) { x <- list(url = unname(unlist(x))) } # Case 2: apis.guru provides a list of lists, but we currently only support # the case where that list has 1 entry. - if (length(x) == 1 && lengths(x) > 1) { + if (is.list(x) && length(x) == 1 && lengths(x) > 1) { x <- x[[1]] } - - as_rapid_class(x, class_origin) -} - -S7::method(as_origin, class_missing | NULL) <- function(x) { - class_origin() -} - -S7::method(as_origin, class_any) <- function(x, - ..., - arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls class_origin}." - ) + as_api_object(x, class_origin, ..., arg = arg, call = call) } diff --git a/R/info.R b/R/info.R index 4c2ed30..24df8b5 100644 --- a/R/info.R +++ b/R/info.R @@ -127,25 +127,13 @@ S7::method(length, info) <- function(x) { #' @examples #' as_info() #' as_info(list(title = "My Cool API", version = "1.0.0")) -as_info <- S7::new_generic("as_info", dispatch_args = "x") - -S7::method(as_info, info) <- function(x) { - x -} - -S7::method(as_info, class_list | class_character) <- function(x) { - as_rapid_class(x, info, alternate_names = c("x-origin" = "origin")) -} - -S7::method( - as_info, - class_missing | NULL | S7::new_S3_class("S7_missing") -) <- function(x) { - info() -} - -S7::method(as_info, class_any) <- function(x, ..., arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls info}." +as_info <- function(x, ..., arg = caller_arg(x), call = caller_env()) { + as_api_object( + x, + info, + ..., + alternate_names = c("x-origin" = "origin"), + arg = arg, + call = call ) } diff --git a/R/properties.R b/R/properties.R index 972b090..8184c05 100644 --- a/R/properties.R +++ b/R/properties.R @@ -1,3 +1,11 @@ +#' @importFrom rlang caller_arg +#' @export +rlang::caller_arg + +#' @importFrom rlang caller_env +#' @export +rlang::caller_env + # These should probably be defined in a separate package. character_scalar_property <- function(x_arg, ...) { @@ -5,7 +13,7 @@ character_scalar_property <- function(x_arg, ...) { name = x_arg, class = class_character, setter = function(self, value) { - call <- rlang::caller_env(3) + call <- caller_env(3) value <- value %||% character() value <- stbl::stabilize_chr_scalar( value, @@ -25,7 +33,7 @@ enum_property <- function(x_arg) { name = x_arg, class = class_list, setter = function(self, value) { - call <- rlang::caller_env(3) + call <- caller_env(3) if (!is.null(value) && !is.list(value)) { value <- list(value) } @@ -55,7 +63,7 @@ list_of_characters <- function(x_arg, ...) { name = x_arg, class = class_list, setter = function(self, value) { - call <- rlang::caller_env(3) + call <- caller_env(3) value <- as.list(value) value <- purrr::map( value, diff --git a/R/security_requirements.R b/R/security_requirements.R index b1fb1f0..064f9bd 100644 --- a/R/security_requirements.R +++ b/R/security_requirements.R @@ -89,19 +89,12 @@ S7::method(length, security_requirements) <- function(x) { #' list(internalApiKey = list()) #' ) #' ) -as_security_requirements <- S7::new_generic( - "as_security_requirements", - dispatch_args = "x" -) - -S7::method(as_security_requirements, security_requirements) <- function(x) { - x -} +as_security_requirements <- S7::new_generic("as_security_requirements", "x") S7::method( as_security_requirements, class_list -) <- function(x, ..., arg = rlang::caller_arg(x)) { +) <- function(x, ..., arg = caller_arg(x)) { force(arg) x <- .list_remove_wrappers(x) @@ -116,16 +109,9 @@ S7::method( ) } -S7::method(as_security_requirements, class_missing | NULL) <- function(x) { - security_requirements() -} - S7::method( as_security_requirements, class_any -) <- function(x, ..., arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls security_requirements}.", - class = "rapid_error_unknown_coercion" - ) +) <- function(x, ..., arg = caller_arg(x), call = caller_env()) { + as_api_object(x, security_requirements, ..., arg = arg, call = call) } diff --git a/R/servers-server_variables.R b/R/servers-server_variables.R index 5154749..c6e678b 100644 --- a/R/servers-server_variables.R +++ b/R/servers-server_variables.R @@ -76,14 +76,7 @@ server_variables <- S7::new_class( #' ) #' ) #' ) -as_server_variables <- S7::new_generic( - "as_server_variables", - dispatch_args = "x" -) - -S7::method(as_server_variables, server_variables) <- function(x) { - x -} +as_server_variables <- S7::new_generic("as_server_variables", "x") S7::method(as_server_variables, class_list) <- function(x) { if (!length(x) || !any(lengths(x))) { @@ -94,12 +87,9 @@ S7::method(as_server_variables, class_list) <- function(x) { ) } -S7::method(as_server_variables, class_missing | NULL) <- function(x) { - server_variables() -} - -S7::method(as_server_variables, class_any) <- function(x) { - cli::cli_abort( - "Can't coerce {.arg x} {.cls {class(x)}} to {.cls server_variables}." - ) +S7::method(as_server_variables, class_any) <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { + as_api_object(x, server_variables, ..., arg = arg, call = call) } diff --git a/R/servers-string_replacements.R b/R/servers-string_replacements.R index 535bdd8..d84bc46 100644 --- a/R/servers-string_replacements.R +++ b/R/servers-string_replacements.R @@ -108,14 +108,7 @@ S7::method(length, string_replacements) <- function(x) { #' ) #' ) #' ) -as_string_replacements <- S7::new_generic( - "as_string_replacements", - dispatch_args = "x" -) - -S7::method(as_string_replacements, string_replacements) <- function(x) { - x -} +as_string_replacements <- S7::new_generic("as_string_replacements", "x") S7::method(as_string_replacements, class_list) <- function(x) { nameless <- unname(x) @@ -127,12 +120,9 @@ S7::method(as_string_replacements, class_list) <- function(x) { ) } -S7::method(as_string_replacements, class_missing | NULL) <- function(x) { - string_replacements() -} - -S7::method(as_string_replacements, class_any) <- function(x) { - cli::cli_abort( - "Can't coerce {.arg x} {.cls {class(x)}} to {.cls string_replacements}." - ) +S7::method(as_string_replacements, class_any) <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { + as_api_object(x, string_replacements, ..., arg = arg, call = call) } diff --git a/R/servers.R b/R/servers.R index 786d1d7..5c14082 100644 --- a/R/servers.R +++ b/R/servers.R @@ -115,14 +115,9 @@ S7::method(length, servers) <- function(x) { #' ) #' ) #' ) -as_servers <- S7::new_generic("as_servers", dispatch_args = "x") +as_servers <- S7::new_generic("as_servers", "x") -S7::method(as_servers, servers) <- function(x) { - x -} - -S7::method(as_servers, class_list) <- function(x) { - call <- rlang::caller_env() +S7::method(as_servers, class_list) <- function(x, ..., call = caller_env()) { x <- purrr::map( x, function(x) { @@ -145,17 +140,9 @@ S7::method(as_servers, class_list) <- function(x) { ) } -S7::method( - as_servers, - class_missing | NULL | S7::new_S3_class("S7_missing") -) <- function(x) { - servers() -} - S7::method(as_servers, class_any) <- function(x, ..., - arg = rlang::caller_arg(x)) { - cli::cli_abort( - "Can't coerce {.arg {arg}} {.cls {class(x)}} to {.cls servers}." - ) + arg = caller_arg(x), + call = caller_env()) { + as_api_object(x, servers, ..., arg = arg, call = call) } diff --git a/R/validate_in.R b/R/validate_in.R index 204abe6..e6f540f 100644 --- a/R/validate_in.R +++ b/R/validate_in.R @@ -1,8 +1,5 @@ -validate_in_enums <- function(obj, - value_name, - enum_name) { +validate_in_enums <- function(obj, value_name, enum_name) { enums <- S7::prop(obj, enum_name) - if (length(enums)) { missing_msgs <- .check_all_in_enums(S7::prop(obj, value_name), enums) if (length(missing_msgs)) { diff --git a/R/validate_parallel.R b/R/validate_parallel.R index 00b339d..64d2dde 100644 --- a/R/validate_parallel.R +++ b/R/validate_parallel.R @@ -1,7 +1,4 @@ -validate_parallel <- function(obj, - key_name, - required = NULL, - optional = NULL) { +validate_parallel <- function(obj, key_name, required = NULL, optional = NULL) { validate_lengths( obj = obj, key_name = key_name, diff --git a/R/zz-rapid.R b/R/zz-rapid.R index f447847..dc9482e 100644 --- a/R/zz-rapid.R +++ b/R/zz-rapid.R @@ -114,16 +114,27 @@ S7::method(length, rapid) <- function(x) { #' #' @examples #' as_rapid() -as_rapid <- S7::new_generic("as_rapid", dispatch_args = "x") +as_rapid <- S7::new_generic("as_rapid", "x") -S7::method(as_rapid, rapid) <- function(x) { - x +S7::method(as_rapid, S7::new_S3_class("url")) <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { + url <- summary(x)$description + x <- yaml::read_yaml(x) + if (!length(x$info$`x-origin`)) { + x$info$`x-origin` <- list(url = url) + } + as_rapid(x, ..., arg = arg, call = call) } -S7::method(as_rapid, class_list) <- function(x) { +S7::method(as_rapid, class_any) <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { rlang::try_fetch( { - x <- as_rapid_class(x, rapid) + x <- as_api_object(x, rapid, ..., arg = arg, call = call) expand_servers(x) }, rapid_error_missing_names = function(cnd) { @@ -135,23 +146,3 @@ S7::method(as_rapid, class_list) <- function(x) { } ) } - -S7::method(as_rapid, S7::new_S3_class("url")) <- function(x) { - url <- summary(x)$description - x <- yaml::read_yaml(x) - if (!length(x$info$`x-origin`)) { - x$info$`x-origin` <- list(url = url) - } - - as_rapid(x) -} - -S7::method(as_rapid, class_missing | NULL) <- function(x) { - rapid() -} - -S7::method(as_rapid, class_any) <- function(x) { - cli::cli_abort( - "Can't coerce {.arg x} {.cls {class(x)}} to {.cls rapid}." - ) -} diff --git a/_pkgdown.yml b/_pkgdown.yml index 3b990c5..834992a 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -52,4 +52,4 @@ reference: - as_security_requirements - title: other contents: - - as_rapid_class + - as_api_object diff --git a/man/as_api_key_security_scheme.Rd b/man/as_api_key_security_scheme.Rd index 53ed45b..17fceed 100644 --- a/man/as_api_key_security_scheme.Rd +++ b/man/as_api_key_security_scheme.Rd @@ -4,7 +4,7 @@ \alias{as_api_key_security_scheme} \title{Coerce lists and character vectors to API key security schemes} \usage{ -as_api_key_security_scheme(x, ...) +as_api_key_security_scheme(x, ..., arg = caller_arg(x), call = caller_env()) } \arguments{ \item{x}{The object to coerce. Must be empty or be a list or character vector @@ -13,6 +13,15 @@ coerced to those names via \code{\link[snakecase:caseconverter]{snakecase::to_sn are ignored.} \item{...}{These dots are for future extensions and must be empty.} + +\item{arg}{An argument name as a string. This argument +will be mentioned in error messages as the input that is at the +origin of a problem.} + +\item{call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \value{ An \code{api_key_security_scheme} as returned by diff --git a/man/as_rapid_class.Rd b/man/as_api_object.Rd similarity index 80% rename from man/as_rapid_class.Rd rename to man/as_api_object.Rd index ff8711e..3e238c4 100644 --- a/man/as_rapid_class.Rd +++ b/man/as_api_object.Rd @@ -1,15 +1,16 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/as.R -\name{as_rapid_class} -\alias{as_rapid_class} -\title{Convert to a rapid-style class} +\name{as_api_object} +\alias{as_api_object} +\title{Convert to a rapid-style object} \usage{ -as_rapid_class( +as_api_object( x, target_class, + ..., alternate_names = NULL, - arg = rlang::caller_arg(x), - call = rlang::caller_env() + arg = caller_arg(x), + call = caller_env() ) } \arguments{ @@ -19,6 +20,8 @@ names via \code{\link[snakecase:caseconverter]{snakecase::to_snake_case()}}. Ext \item{target_class}{The S7 class to which the object should be converted.} +\item{...}{These dots are for future extensions and must be empty.} + \item{alternate_names}{Character vector (optional). An optional named character vector, where the names are the names as they might appear in \code{x}, and the values are the corresponding properties.} @@ -36,5 +39,5 @@ mentioned in error messages as the source of the error. See the An object with the specified \code{target_class}. } \description{ -Convert a named list into a rapid-style class. +Convert a named list into an object with a rapid-style class. } diff --git a/man/as_component_collection.Rd b/man/as_component_collection.Rd index 4e8f663..7cb423a 100644 --- a/man/as_component_collection.Rd +++ b/man/as_component_collection.Rd @@ -4,7 +4,7 @@ \alias{as_component_collection} \title{Coerce lists to component_collection objects} \usage{ -as_component_collection(x, ...) +as_component_collection(x, ..., arg = caller_arg(x), call = caller_env()) } \arguments{ \item{x}{The object to coerce. Must be empty or be a list containing a single @@ -13,6 +13,15 @@ list named "security_schemes", or a name that can be coerced to ignored.} \item{...}{These dots are for future extensions and must be empty.} + +\item{arg}{An argument name as a string. This argument +will be mentioned in error messages as the input that is at the +origin of a problem.} + +\item{call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \value{ A \code{component_collection} object as returned by diff --git a/man/as_contact.Rd b/man/as_contact.Rd index fcadbb8..7d1aec5 100644 --- a/man/as_contact.Rd +++ b/man/as_contact.Rd @@ -4,7 +4,7 @@ \alias{as_contact} \title{Coerce lists and character vectors to contacts} \usage{ -as_contact(x, ...) +as_contact(x, ..., arg = caller_arg(x), call = caller_env()) } \arguments{ \item{x}{The object to coerce. Must be empty or have names "name", "email", @@ -13,6 +13,15 @@ and/or "url", or names that can be coerced to those names via describe a single point of contact.} \item{...}{These dots are for future extensions and must be empty.} + +\item{arg}{An argument name as a string. This argument +will be mentioned in error messages as the input that is at the +origin of a problem.} + +\item{call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \value{ A \code{contact} as returned by \code{\link[=contact]{contact()}}. diff --git a/man/as_info.Rd b/man/as_info.Rd index 67ed47e..d3c9276 100644 --- a/man/as_info.Rd +++ b/man/as_info.Rd @@ -4,7 +4,7 @@ \alias{as_info} \title{Coerce lists and character vectors to info objects} \usage{ -as_info(x, ...) +as_info(x, ..., arg = caller_arg(x), call = caller_env()) } \arguments{ \item{x}{The object to coerce. Must be empty or have names "title", @@ -15,6 +15,15 @@ to "origin"), or names that can be coerced to those names via describe a single API.} \item{...}{These dots are for future extensions and must be empty.} + +\item{arg}{An argument name as a string. This argument +will be mentioned in error messages as the input that is at the +origin of a problem.} + +\item{call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \value{ An \code{info} object as returned by \code{\link[=info]{info()}}. diff --git a/man/as_license.Rd b/man/as_license.Rd index fa05451..baba2f1 100644 --- a/man/as_license.Rd +++ b/man/as_license.Rd @@ -4,7 +4,7 @@ \alias{as_license} \title{Coerce lists and character vectors to licenses} \usage{ -as_license(x, ...) +as_license(x, ..., arg = caller_arg(x), call = caller_env()) } \arguments{ \item{x}{The object to coerce. Must be empty or have names "name", @@ -13,6 +13,15 @@ as_license(x, ...) describe a single license.} \item{...}{These dots are for future extensions and must be empty.} + +\item{arg}{An argument name as a string. This argument +will be mentioned in error messages as the input that is at the +origin of a problem.} + +\item{call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \value{ A \code{license} as returned by \code{\link[=license]{license()}}. diff --git a/man/as_oauth2_authorization_code_flow.Rd b/man/as_oauth2_authorization_code_flow.Rd index d6923b6..b55d0bd 100644 --- a/man/as_oauth2_authorization_code_flow.Rd +++ b/man/as_oauth2_authorization_code_flow.Rd @@ -5,7 +5,12 @@ \alias{as_oauth2_authorization_code_flow} \title{Coerce lists and character vectors to OAuth2 authorization code flows} \usage{ -as_oauth2_authorization_code_flow(x, ...) +as_oauth2_authorization_code_flow( + x, + ..., + arg = caller_arg(x), + call = caller_env() +) } \arguments{ \item{x}{The object to coerce. Must be empty or be a list of named lists, @@ -14,6 +19,15 @@ each with names "refresh_url", "scopes", "authorization_url", and/or \code{\link[snakecase:caseconverter]{snakecase::to_snake_case()}}. Additional names are ignored.} \item{...}{These dots are for future extensions and must be empty.} + +\item{arg}{An argument name as a string. This argument +will be mentioned in error messages as the input that is at the +origin of a problem.} + +\item{call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \value{ An \code{oauth2_authorization_code_flow} as returned by diff --git a/man/as_oauth2_implicit_flow.Rd b/man/as_oauth2_implicit_flow.Rd index 2299ae3..c6136be 100644 --- a/man/as_oauth2_implicit_flow.Rd +++ b/man/as_oauth2_implicit_flow.Rd @@ -5,7 +5,7 @@ \alias{as_oauth2_implicit_flow} \title{Coerce lists and character vectors to OAuth2 implicit flows} \usage{ -as_oauth2_implicit_flow(x, ...) +as_oauth2_implicit_flow(x, ..., arg = caller_arg(x), call = caller_env()) } \arguments{ \item{x}{The object to coerce. Must be empty or be a list of named lists, @@ -14,6 +14,15 @@ names that can be coerced to those names via \code{\link[snakecase:caseconverter Additional names are ignored.} \item{...}{These dots are for future extensions and must be empty.} + +\item{arg}{An argument name as a string. This argument +will be mentioned in error messages as the input that is at the +origin of a problem.} + +\item{call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \value{ An \code{oauth2_implicit_flow} as returned by \code{\link[=oauth2_implicit_flow]{oauth2_implicit_flow()}}. diff --git a/man/as_oauth2_token_flow.Rd b/man/as_oauth2_token_flow.Rd index 798444d..5ccfcfa 100644 --- a/man/as_oauth2_token_flow.Rd +++ b/man/as_oauth2_token_flow.Rd @@ -4,7 +4,7 @@ \alias{as_oauth2_token_flow} \title{Coerce lists and character vectors to OAuth2 token flows} \usage{ -as_oauth2_token_flow(x, ...) +as_oauth2_token_flow(x, ..., arg = caller_arg(x), call = caller_env()) } \arguments{ \item{x}{The object to coerce. Must be empty or be a list of named lists, @@ -13,6 +13,15 @@ can be coerced to those names via \code{\link[snakecase:caseconverter]{snakecase names are ignored.} \item{...}{These dots are for future extensions and must be empty.} + +\item{arg}{An argument name as a string. This argument +will be mentioned in error messages as the input that is at the +origin of a problem.} + +\item{call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \value{ An \code{oauth2_token_flow} as returned by \code{\link[=oauth2_token_flow]{oauth2_token_flow()}}. diff --git a/man/as_origin.Rd b/man/as_origin.Rd index 7150093..ff53531 100644 --- a/man/as_origin.Rd +++ b/man/as_origin.Rd @@ -4,7 +4,7 @@ \alias{as_origin} \title{Coerce lists and character vectors to class_origin} \usage{ -as_origin(x, ...) +as_origin(x, ..., arg = caller_arg(x), call = caller_env()) } \arguments{ \item{x}{The object to coerce. Must be empty or have names "url", "format", @@ -13,6 +13,15 @@ and/or "version", or names that can be coerced to those names via describe a single origin for this API description.} \item{...}{These dots are for future extensions and must be empty.} + +\item{arg}{An argument name as a string. This argument +will be mentioned in error messages as the input that is at the +origin of a problem.} + +\item{call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \value{ A \code{class_origin} as returned by \code{\link[=class_origin]{class_origin()}}. diff --git a/man/reexports.Rd b/man/reexports.Rd new file mode 100644 index 0000000..1bea638 --- /dev/null +++ b/man/reexports.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/properties.R +\docType{import} +\name{reexports} +\alias{reexports} +\alias{caller_arg} +\alias{caller_env} +\title{Objects exported from other packages} +\keyword{internal} +\description{ +These objects are imported from other packages. Follow the links +below to see their documentation. + +\describe{ + \item{rlang}{\code{\link[rlang]{caller_arg}}, \code{\link[rlang:stack]{caller_env}}} +}} + diff --git a/tests/testthat/_snaps/components-security_scheme-api_key.md b/tests/testthat/_snaps/components-security_scheme-api_key.md index 24e7fa9..b44a5d9 100644 --- a/tests/testthat/_snaps/components-security_scheme-api_key.md +++ b/tests/testthat/_snaps/components-security_scheme-api_key.md @@ -24,7 +24,7 @@ as_api_key_security_scheme(list("Jon", "jonthegeek@gmail.com")) Condition Error: - ! `x` must have names "parameter_name", "location", "in", or "name". + ! `list("Jon", "jonthegeek@gmail.com")` must have names "parameter_name", "location", "in", or "name". * Any other names are ignored. # as_api_key_security_scheme() errors informatively for bad classes @@ -33,7 +33,7 @@ as_api_key_security_scheme(1:2) Condition Error: - ! Can't coerce `1:2` to . + ! Can't coerce `1:2` to . --- @@ -41,7 +41,7 @@ as_api_key_security_scheme(mean) Condition Error: - ! Can't coerce `mean` to . + ! Can't coerce `mean` to . --- @@ -49,5 +49,5 @@ as_api_key_security_scheme(TRUE) Condition Error: - ! Can't coerce `TRUE` to . + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/components-security_scheme-oauth2-authorization_code_flow.md b/tests/testthat/_snaps/components-security_scheme-oauth2-authorization_code_flow.md index cfd6c81..d11cd5f 100644 --- a/tests/testthat/_snaps/components-security_scheme-oauth2-authorization_code_flow.md +++ b/tests/testthat/_snaps/components-security_scheme-oauth2-authorization_code_flow.md @@ -103,7 +103,7 @@ Code oauth2_authorization_code_flow("a", "b", refresh_url = "c", scopes = "d") Condition - Error: + Error in `as_scopes()`: ! `scopes` must be a named character vector. # oauth2_authorization_code_flow() returns expected objects @@ -129,7 +129,7 @@ as_oauth2_authorization_code_flow("a") Condition Error: - ! `x` must have names "refresh_url", "scopes", "authorization_url", or "token_url". + ! `"a"` must have names "refresh_url", "scopes", "authorization_url", or "token_url". * Any other names are ignored. # as_oauth2_authorization_code_flow() errors for bad classes @@ -138,7 +138,7 @@ as_oauth2_authorization_code_flow(1:2) Condition Error: - ! Can't coerce `1:2` to . + ! Can't coerce `1:2` to . --- @@ -146,7 +146,7 @@ as_oauth2_authorization_code_flow(mean) Condition Error: - ! Can't coerce `mean` to . + ! Can't coerce `mean` to . --- @@ -154,5 +154,5 @@ as_oauth2_authorization_code_flow(TRUE) Condition Error: - ! Can't coerce `TRUE` to . + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/components-security_scheme-oauth2-implicit_flow.md b/tests/testthat/_snaps/components-security_scheme-oauth2-implicit_flow.md index 9e23de9..61f6638 100644 --- a/tests/testthat/_snaps/components-security_scheme-oauth2-implicit_flow.md +++ b/tests/testthat/_snaps/components-security_scheme-oauth2-implicit_flow.md @@ -74,7 +74,7 @@ Code oauth2_implicit_flow("a", refresh_url = "c", scopes = "d") Condition - Error: + Error in `as_scopes()`: ! `scopes` must be a named character vector. # oauth2_implicit_flow() returns expected objects @@ -98,7 +98,7 @@ as_oauth2_implicit_flow(list("Jon", "jonthegeek@gmail.com")) Condition Error: - ! `x` must have names "refresh_url", "scopes", or "authorization_url". + ! `list("Jon", "jonthegeek@gmail.com")` must have names "refresh_url", "scopes", or "authorization_url". * Any other names are ignored. # as_oauth2_implicit_flow() errors informatively for bad classes @@ -107,7 +107,7 @@ as_oauth2_implicit_flow(1:2) Condition Error: - ! Can't coerce `1:2` to . + ! Can't coerce `1:2` to . --- @@ -115,7 +115,7 @@ as_oauth2_implicit_flow(mean) Condition Error: - ! Can't coerce `mean` to . + ! Can't coerce `mean` to . --- @@ -123,5 +123,5 @@ as_oauth2_implicit_flow(TRUE) Condition Error: - ! Can't coerce `TRUE` to . + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/components-security_scheme-oauth2-scopes.md b/tests/testthat/_snaps/components-security_scheme-oauth2-scopes.md index 57116dc..b21f9fc 100644 --- a/tests/testthat/_snaps/components-security_scheme-oauth2-scopes.md +++ b/tests/testthat/_snaps/components-security_scheme-oauth2-scopes.md @@ -67,7 +67,7 @@ Code as_scopes("a") Condition - Error: + Error in `as_scopes()`: ! `"a"` must be a named character vector. # as_scopes() errors informatively for bad classes @@ -75,22 +75,22 @@ Code as_scopes(1:2) Condition - Error: - ! Can't coerce `1:2` to . + Error in `as_scopes()`: + ! Can't coerce `1:2` to . --- Code as_scopes(mean) Condition - Error: - ! Can't coerce `mean` to . + Error in `as_scopes()`: + ! Can't coerce `mean` to . --- Code as_scopes(TRUE) Condition - Error: - ! Can't coerce `TRUE` to . + Error in `as_scopes()`: + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/components-security_scheme-oauth2-token_flow.md b/tests/testthat/_snaps/components-security_scheme-oauth2-token_flow.md index 29243b1..ce1cc59 100644 --- a/tests/testthat/_snaps/components-security_scheme-oauth2-token_flow.md +++ b/tests/testthat/_snaps/components-security_scheme-oauth2-token_flow.md @@ -75,7 +75,7 @@ Code oauth2_token_flow("a", refresh_url = "c", scopes = "d") Condition - Error: + Error in `as_scopes()`: ! `scopes` must be a named character vector. # oauth2_token_flow() returns expected objects @@ -99,7 +99,7 @@ as_oauth2_token_flow(list("Jon", "jonthegeek@gmail.com")) Condition Error: - ! `x` must have names "refresh_url", "scopes", or "token_url". + ! `list("Jon", "jonthegeek@gmail.com")` must have names "refresh_url", "scopes", or "token_url". * Any other names are ignored. # as_oauth2_token_flow() errors informatively for bad classes @@ -108,7 +108,7 @@ as_oauth2_token_flow(1:2) Condition Error: - ! Can't coerce `1:2` to . + ! Can't coerce `1:2` to . --- @@ -116,7 +116,7 @@ as_oauth2_token_flow(mean) Condition Error: - ! Can't coerce `mean` to . + ! Can't coerce `mean` to . --- @@ -124,5 +124,5 @@ as_oauth2_token_flow(TRUE) Condition Error: - ! Can't coerce `TRUE` to . + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/components-security_scheme-oauth2.md b/tests/testthat/_snaps/components-security_scheme-oauth2.md index 5e578d2..13af8dd 100644 --- a/tests/testthat/_snaps/components-security_scheme-oauth2.md +++ b/tests/testthat/_snaps/components-security_scheme-oauth2.md @@ -14,32 +14,32 @@ Code oauth2_security_scheme(implicit_flow = oauth2_token_flow()) Condition - Error: - ! Can't coerce `implicit_flow` to . + Error in `oauth2_security_scheme()`: + ! Can't coerce `implicit_flow` to . --- Code oauth2_security_scheme(password_flow = oauth2_implicit_flow()) Condition - Error: - ! Can't coerce `password_flow` to . + Error in `oauth2_security_scheme()`: + ! Can't coerce `password_flow` to . --- Code oauth2_security_scheme(client_credentials_flow = oauth2_implicit_flow()) Condition - Error: - ! Can't coerce `client_credentials_flow` to . + Error in `oauth2_security_scheme()`: + ! Can't coerce `client_credentials_flow` to . --- Code oauth2_security_scheme(authorization_code_flow = oauth2_implicit_flow()) Condition - Error: - ! Can't coerce `authorization_code_flow` to . + Error in `oauth2_security_scheme()`: + ! Can't coerce `authorization_code_flow` to . # oauth2_security_scheme() works with valid objects @@ -80,30 +80,30 @@ Code as_oauth2_security_scheme(list("Jon", "jonthegeek@gmail.com")) Condition - Error: - ! `x` must contain a named flows object. + Error in `as_oauth2_security_scheme()`: + ! `list("Jon", "jonthegeek@gmail.com")` must contain a named flows object. # as_oauth2_security_scheme() errors for bad classes Code as_oauth2_security_scheme(1:2) Condition - Error: - ! Can't coerce `1:2` to . + Error in `as_oauth2_security_scheme()`: + ! Can't coerce `1:2` to . --- Code as_oauth2_security_scheme(mean) Condition - Error: - ! Can't coerce `mean` to . + Error in `as_oauth2_security_scheme()`: + ! Can't coerce `mean` to . --- Code as_oauth2_security_scheme(TRUE) Condition - Error: - ! Can't coerce `TRUE` to . + Error in `as_oauth2_security_scheme()`: + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/components-security_scheme.md b/tests/testthat/_snaps/components-security_scheme.md index a8bd164..770f5cd 100644 --- a/tests/testthat/_snaps/components-security_scheme.md +++ b/tests/testthat/_snaps/components-security_scheme.md @@ -3,22 +3,22 @@ Code as_security_scheme(1:2) Condition - Error: - ! Can't coerce `x` to . + Error in `as_security_scheme()`: + ! Can't coerce `1:2` to . --- Code as_security_scheme(mean) Condition - Error: - ! Can't coerce `x` to . + Error in `as_security_scheme()`: + ! Can't coerce `mean` to . --- Code as_security_scheme(TRUE) Condition - Error: - ! Can't coerce `x` to . + Error in `as_security_scheme()`: + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/components-security_scheme_collection.md b/tests/testthat/_snaps/components-security_scheme_collection.md index c8a19d9..2f58c7d 100644 --- a/tests/testthat/_snaps/components-security_scheme_collection.md +++ b/tests/testthat/_snaps/components-security_scheme_collection.md @@ -44,38 +44,39 @@ Code as_security_scheme_collection(as.list(letters)) Condition - Error: - ! `a`, `b`, `c`, `d`, `e`, `f`, `g`, `h`, `i`, `j`, `k`, `l`, `m`, `n`, `o`, `p`, `q`, `r`, ..., `y`, and `z` must have names. + Error in `as_security_scheme_collection()`: + ! `as.list(letters)` must have names. # as_security_scheme_collection() errors for bad classes Code as_security_scheme_collection(letters) Condition - Error: - ! Can't coerce `letters` to . + Error in `as_security_scheme_collection()`: + ! `letters` must have names "name", "details", or "description". + * Any other names are ignored. --- Code as_security_scheme_collection(1:2) Condition - Error: - ! Can't coerce `1:2` to . + Error in `as_security_scheme_collection()`: + ! Can't coerce `1:2` to . --- Code as_security_scheme_collection(mean) Condition - Error: - ! Can't coerce `mean` to . + Error in `as_security_scheme_collection()`: + ! Can't coerce `mean` to . --- Code as_security_scheme_collection(TRUE) Condition - Error: - ! Can't coerce `TRUE` to . + Error in `as_security_scheme_collection()`: + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/components-security_scheme_details.md b/tests/testthat/_snaps/components-security_scheme_details.md index 0109d88..66fa90d 100644 --- a/tests/testthat/_snaps/components-security_scheme_details.md +++ b/tests/testthat/_snaps/components-security_scheme_details.md @@ -133,22 +133,22 @@ Code as_security_scheme_details(1:2) Condition - Error: - ! Can't coerce `1:2` to . + Error in `as_security_scheme_details()`: + ! Can't coerce `1:2` to . --- Code as_security_scheme_details(mean) Condition - Error: - ! Can't coerce `mean` to . + Error in `as_security_scheme_details()`: + ! Can't coerce `mean` to . --- Code as_security_scheme_details(TRUE) Condition - Error: - ! Can't coerce `TRUE` to . + Error in `as_security_scheme_details()`: + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/components.md b/tests/testthat/_snaps/components.md index a60a56a..67de1d0 100644 --- a/tests/testthat/_snaps/components.md +++ b/tests/testthat/_snaps/components.md @@ -16,7 +16,7 @@ as_component_collection(as.list(letters)) Condition Error: - ! `x` must have names "security_schemes". + ! `as.list(letters)` must have names "security_schemes". * Any other names are ignored. --- @@ -25,7 +25,7 @@ as_component_collection(list("My Cool API")) Condition Error: - ! `x` must have names "security_schemes". + ! `list("My Cool API")` must have names "security_schemes". * Any other names are ignored. # as_component_collection() errors informatively for bad classes @@ -34,7 +34,7 @@ as_component_collection(1:2) Condition Error: - ! Can't coerce `1:2` to . + ! Can't coerce `1:2` to . --- @@ -42,7 +42,7 @@ as_component_collection(mean) Condition Error: - ! Can't coerce `mean` to . + ! Can't coerce `mean` to . --- @@ -50,5 +50,5 @@ as_component_collection(TRUE) Condition Error: - ! Can't coerce `TRUE` to . + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/info-contact.md b/tests/testthat/_snaps/info-contact.md index 4491cc1..7482fa2 100644 --- a/tests/testthat/_snaps/info-contact.md +++ b/tests/testthat/_snaps/info-contact.md @@ -70,7 +70,7 @@ as_contact(letters) Condition Error: - ! `x` must have names "name", "email", or "url". + ! `letters` must have names "name", "email", or "url". * Any other names are ignored. --- @@ -79,7 +79,7 @@ as_contact(list("Jon", "jonthegeek@gmail.com")) Condition Error: - ! `x` must have names "name", "email", or "url". + ! `list("Jon", "jonthegeek@gmail.com")` must have names "name", "email", or "url". * Any other names are ignored. --- @@ -88,7 +88,7 @@ as_contact(c("Jon", "jonthegeek@gmail.com")) Condition Error: - ! `x` must have names "name", "email", or "url". + ! `c("Jon", "jonthegeek@gmail.com")` must have names "name", "email", or "url". * Any other names are ignored. # as_contact() errors informatively for bad classes @@ -97,7 +97,7 @@ as_contact(1:2) Condition Error: - ! Can't coerce `1:2` to . + ! Can't coerce `1:2` to . --- @@ -105,7 +105,7 @@ as_contact(mean) Condition Error: - ! Can't coerce `mean` to . + ! Can't coerce `mean` to . --- @@ -113,5 +113,5 @@ as_contact(TRUE) Condition Error: - ! Can't coerce `TRUE` to . + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/info-license.md b/tests/testthat/_snaps/info-license.md index 35f5c37..dbd5788 100644 --- a/tests/testthat/_snaps/info-license.md +++ b/tests/testthat/_snaps/info-license.md @@ -117,7 +117,7 @@ as_license(letters) Condition Error: - ! `x` must have names "name", "identifier", or "url". + ! `letters` must have names "name", "identifier", or "url". * Any other names are ignored. # as_license() errors informatively for bad classes @@ -126,7 +126,7 @@ as_license(1:2) Condition Error: - ! Can't coerce `1:2` to . + ! Can't coerce `1:2` to . --- @@ -134,7 +134,7 @@ as_license(mean) Condition Error: - ! Can't coerce `mean` to . + ! Can't coerce `mean` to . --- @@ -142,5 +142,5 @@ as_license(TRUE) Condition Error: - ! Can't coerce `TRUE` to . + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/info.md b/tests/testthat/_snaps/info.md index 1c87750..2f1bc80 100644 --- a/tests/testthat/_snaps/info.md +++ b/tests/testthat/_snaps/info.md @@ -60,7 +60,7 @@ as_info(letters) Condition Error: - ! `x` must have names "title", "version", "contact", "description", "license", "summary", "terms_of_service", "origin", or "x_origin". + ! `letters` must have names "title", "version", "contact", "description", "license", "summary", "terms_of_service", "origin", or "x_origin". * Any other names are ignored. --- @@ -69,7 +69,7 @@ as_info(list("My Cool API")) Condition Error: - ! `x` must have names "title", "version", "contact", "description", "license", "summary", "terms_of_service", "origin", or "x_origin". + ! `list("My Cool API")` must have names "title", "version", "contact", "description", "license", "summary", "terms_of_service", "origin", or "x_origin". * Any other names are ignored. # as_info() errors informatively for bad classes @@ -78,7 +78,7 @@ as_info(1:2) Condition Error: - ! Can't coerce `1:2` to . + ! Can't coerce `1:2` to . --- @@ -86,7 +86,7 @@ as_info(mean) Condition Error: - ! Can't coerce `mean` to . + ! Can't coerce `mean` to . --- @@ -94,5 +94,5 @@ as_info(TRUE) Condition Error: - ! Can't coerce `TRUE` to . + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/security_requirements.md b/tests/testthat/_snaps/security_requirements.md index 77e3b10..4400867 100644 --- a/tests/testthat/_snaps/security_requirements.md +++ b/tests/testthat/_snaps/security_requirements.md @@ -24,22 +24,22 @@ Code as_security_requirements(x) Condition - Error: - ! Can't coerce `x` to . + Error in `as_security_requirements()`: + ! Can't coerce `x` to . --- Code as_security_requirements(x) Condition - Error: - ! Can't coerce `x` to . + Error in `as_security_requirements()`: + ! Can't coerce `x` to . --- Code as_security_requirements(x) Condition - Error: - ! Can't coerce `x` to . + Error in `as_security_requirements()`: + ! Can't coerce `x` to . diff --git a/tests/testthat/_snaps/servers-server_variables.md b/tests/testthat/_snaps/servers-server_variables.md index 2987c2d..12a8e6e 100644 --- a/tests/testthat/_snaps/servers-server_variables.md +++ b/tests/testthat/_snaps/servers-server_variables.md @@ -98,22 +98,22 @@ Code as_server_variables(1:2) Condition - Error: - ! Can't coerce `x` to . + Error in `as_server_variables()`: + ! Can't coerce `1:2` to . --- Code as_server_variables(mean) Condition - Error: - ! Can't coerce `x` to . + Error in `as_server_variables()`: + ! Can't coerce `mean` to . --- Code as_server_variables(TRUE) Condition - Error: - ! Can't coerce `x` to . + Error in `as_server_variables()`: + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/servers-string_replacements.md b/tests/testthat/_snaps/servers-string_replacements.md index a9435d9..c3d03b1 100644 --- a/tests/testthat/_snaps/servers-string_replacements.md +++ b/tests/testthat/_snaps/servers-string_replacements.md @@ -129,8 +129,9 @@ Code as_string_replacements(letters) Condition - Error: - ! Can't coerce `x` to . + Error in `as_string_replacements()`: + ! `letters` must have names "name", "default", "enum", or "description". + * Any other names are ignored. --- @@ -147,30 +148,31 @@ Code as_string_replacements(c("Jon", "jonthegeek@gmail.com")) Condition - Error: - ! Can't coerce `x` to . + Error in `as_string_replacements()`: + ! `c("Jon", "jonthegeek@gmail.com")` must have names "name", "default", "enum", or "description". + * Any other names are ignored. # as_string_replacements() errors informatively for bad classes Code as_string_replacements(1:2) Condition - Error: - ! Can't coerce `x` to . + Error in `as_string_replacements()`: + ! Can't coerce `1:2` to . --- Code as_string_replacements(mean) Condition - Error: - ! Can't coerce `x` to . + Error in `as_string_replacements()`: + ! Can't coerce `mean` to . --- Code as_string_replacements(TRUE) Condition - Error: - ! Can't coerce `x` to . + Error in `as_string_replacements()`: + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/servers.md b/tests/testthat/_snaps/servers.md index 90f22ef..288ad4c 100644 --- a/tests/testthat/_snaps/servers.md +++ b/tests/testthat/_snaps/servers.md @@ -25,22 +25,22 @@ Code as_servers(1:2) Condition - Error: - ! Can't coerce `1:2` to . + Error in `as_servers()`: + ! Can't coerce `1:2` to . --- Code as_servers(mean) Condition - Error: - ! Can't coerce `mean` to . + Error in `as_servers()`: + ! Can't coerce `mean` to . --- Code as_servers(TRUE) Condition - Error: - ! Can't coerce `TRUE` to . + Error in `as_servers()`: + ! Can't coerce `TRUE` to . diff --git a/tests/testthat/_snaps/zz-rapid.md b/tests/testthat/_snaps/zz-rapid.md index 74bc3f2..12984b5 100644 --- a/tests/testthat/_snaps/zz-rapid.md +++ b/tests/testthat/_snaps/zz-rapid.md @@ -3,8 +3,8 @@ Code rapid(info = mean) Condition - Error: - ! Can't coerce `info` to . + Error in `rapid()`: + ! Can't coerce `info` to . # rapid() requires info when anything is defined @@ -76,24 +76,24 @@ Code as_rapid(1:2) Condition - Error: - ! Can't coerce `x` to . + Error in `as_rapid()`: + ! Can't coerce `1:2` to . --- Code as_rapid(mean) Condition - Error: - ! Can't coerce `x` to . + Error in `as_rapid()`: + ! Can't coerce `mean` to . --- Code as_rapid(TRUE) Condition - Error: - ! Can't coerce `x` to . + Error in `as_rapid()`: + ! Can't coerce `TRUE` to . # as_rapid() errors informatively for unnamed input @@ -102,8 +102,8 @@ Condition Error: ! `x` must be comprised of properly formed, supported elements. - Caused by error: - ! `x` must have names "info", "servers", "components", or "security". + Caused by error in `as_rapid()`: + ! `list(letters)` must have names "info", "servers", "components", or "security". * Any other names are ignored. --- @@ -113,8 +113,8 @@ Condition Error: ! `x` must be comprised of properly formed, supported elements. - Caused by error: - ! `x` must have names "info", "servers", "components", or "security". + Caused by error in `as_rapid()`: + ! `list(list("https://example.com", "A cool server."))` must have names "info", "servers", "components", or "security". * Any other names are ignored. # as_rapid() works for urls