Skip to content

Commit

Permalink
Generalize for trello. (#48)
Browse files Browse the repository at this point in the history
  • Loading branch information
jonthegeek committed Mar 29, 2024
1 parent a182c71 commit 116e8a9
Show file tree
Hide file tree
Showing 11 changed files with 67 additions and 25 deletions.
8 changes: 6 additions & 2 deletions R/generate_pkg-paths.R
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,7 @@ S7::method(as_bk_data, class_paths) <- function(x) {
endpoints$endpoint,
endpoints$operation
),
description = str_squish(endpoints$description),
description = .paths_fill_descriptions(endpoints$description),
params_df = endpoints$parameters
),
.paths_endpoint_to_list
Expand Down Expand Up @@ -205,13 +205,17 @@ S7::method(as_bk_data, class_paths) <- function(x) {
path$params_cookie <- .prep_param_args(path$params_cookie, security_args)
path$params_header <- .prep_param_args(path$params_header, security_args)
path$params_query <- .prep_param_args(path$params_query, security_args)
path$args <- .collapse_comma(map_chr(path$params, "name"))
path$args <- .params_to_args(path$params)
path$test_args <- path$args
return(path)
}
)
}

.params_to_args <- function(params) {
.collapse_comma(map_chr(params, "name")) %|"|% character()
}
.remove_security_args <- function(params, security_args) {
discard(
params,
Expand Down
4 changes: 2 additions & 2 deletions R/generate_pkg-security.R
Original file line number Diff line number Diff line change
Expand Up @@ -15,9 +15,9 @@
.generate_security_signature <- function(security_arg_names, api_abbr) {
env_vars <- toupper(glue("{api_abbr}_{security_arg_names}"))
return(
.collapse_comma_newline(c("", glue(
.collapse_comma_newline(glue(
"{security_arg_names} = Sys.getenv(\"{env_vars}\")"
)))
))
)
}

Expand Down
2 changes: 1 addition & 1 deletion inst/templates/010-call.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@
{{api_abbr}}_call_api <- function(path,
query = NULL,
body = NULL,
method = NULL{{{security_signature}}}) {
method = NULL{{#has_security}},{{{security_signature}}}{{/has_security}}) {
nectar::call_api(
base_url = "{{base_url}}",
path = path,
Expand Down
2 changes: 1 addition & 1 deletion inst/templates/paths.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@
#' @param {{name}} {{{description}}}{{/params}}
#' @return BKTODO: Return descriptions are not yet implemented in beekeeper
#' @export
{{api_abbr}}_{{operation_id}} <- function({{{args}}}{{{security_signature}}}) {
{{api_abbr}}_{{operation_id}} <- function({{{args}}}{{#has_security}}{{#args}},{{/args}}{{{security_signature}}}{{/has_security}}) {
{{api_abbr}}_call_api(
path = {{{path}}}{{#has_security}},
{{security_arg_list}}{{/has_security}}{{#params_query}},
Expand Down
12 changes: 11 additions & 1 deletion tests/testthat/_fixtures/000-create_fixtures.R
Original file line number Diff line number Diff line change
Expand Up @@ -52,8 +52,18 @@ apid_url <- "https://api.apis.guru/v2/specs/trello.com/1.0/openapi.yaml"
api_abbr <- "trello"
rapid_write_path <- test_path(glue::glue("_fixtures/{api_abbr}_rapid.rds"))
config_path <- test_path(glue::glue("_fixtures/{api_abbr}_beekeeper.yml"))
apid_url |>
trello_rapid <- apid_url |>
url() |>
rapid::as_rapid()
trello_rapid@paths <- rapid::as_paths({
trello_rapid@paths |>
tibble::as_tibble() |>
tidyr::unnest(operations) |>
dplyr::filter(tags == "board") |>
head(1) |>
tidyr::nest(.by = "endpoint", .key = "operations")
})
trello_rapid |>
use_beekeeper(
api_abbr = api_abbr,
config_file = config_path,
Expand Down
20 changes: 5 additions & 15 deletions tests/testthat/_fixtures/fec-paths-audit.R
Original file line number Diff line number Diff line change
Expand Up @@ -29,9 +29,7 @@
#' @param sort Provide a field to sort by. Use `-` for descending order. ex: `-case_no`
#' @return BKTODO: Return descriptions are not yet implemented in beekeeper
#' @export
fec_get_audit_case <- function(
audit_case_id, cycle, sub_category_id, sort_nulls_last, sort_hide_null, min_election_cycle, audit_id, q, per_page, max_election_cycle, candidate_id, committee_type, qq, page, committee_id, committee_designation, primary_category_id, sort_null_only, sort,
api_key = Sys.getenv("FEC_API_KEY")) {
fec_get_audit_case <- function(audit_case_id, cycle, sub_category_id, sort_nulls_last, sort_hide_null, min_election_cycle, audit_id, q, per_page, max_election_cycle, candidate_id, committee_type, qq, page, committee_id, committee_designation, primary_category_id, sort_null_only, sort, api_key = Sys.getenv("FEC_API_KEY")) {
fec_call_api(
path = "/audit-case/",
api_key = api_key,
Expand All @@ -54,9 +52,7 @@ fec_get_audit_case <- function(
#' @param sort Provide a field to sort by. Use `-` for descending order.
#' @return BKTODO: Return descriptions are not yet implemented in beekeeper
#' @export
fec_get_audit_category <- function(
sort_nulls_last, page, primary_category_name, sort_hide_null, primary_category_id, sort_null_only, per_page, sort,
api_key = Sys.getenv("FEC_API_KEY")) {
fec_get_audit_category <- function(sort_nulls_last, page, primary_category_name, sort_hide_null, primary_category_id, sort_null_only, per_page, sort, api_key = Sys.getenv("FEC_API_KEY")) {
fec_call_api(
path = "/audit-category/",
api_key = api_key,
Expand All @@ -79,9 +75,7 @@ fec_get_audit_category <- function(
#' @param sort Provide a field to sort by. Use `-` for descending order.
#' @return BKTODO: Return descriptions are not yet implemented in beekeeper
#' @export
fec_get_audit_primary_category <- function(
sort_nulls_last, page, primary_category_name, sort_hide_null, primary_category_id, sort_null_only, per_page, sort,
api_key = Sys.getenv("FEC_API_KEY")) {
fec_get_audit_primary_category <- function(sort_nulls_last, page, primary_category_name, sort_hide_null, primary_category_id, sort_null_only, per_page, sort, api_key = Sys.getenv("FEC_API_KEY")) {
fec_call_api(
path = "/audit-primary-category/",
api_key = api_key,
Expand All @@ -97,9 +91,7 @@ fec_get_audit_primary_category <- function(
#' @param q Name (candidate or committee) to search for
#' @return BKTODO: Return descriptions are not yet implemented in beekeeper
#' @export
fec_get_names_audit_candidates <- function(
q,
api_key = Sys.getenv("FEC_API_KEY")) {
fec_get_names_audit_candidates <- function(q, api_key = Sys.getenv("FEC_API_KEY")) {
fec_call_api(
path = "/names/audit_candidates/",
api_key = api_key,
Expand All @@ -115,9 +107,7 @@ fec_get_names_audit_candidates <- function(
#' @param q Name (candidate or committee) to search for
#' @return BKTODO: Return descriptions are not yet implemented in beekeeper
#' @export
fec_get_names_audit_committees <- function(
q,
api_key = Sys.getenv("FEC_API_KEY")) {
fec_get_names_audit_committees <- function(q, api_key = Sys.getenv("FEC_API_KEY")) {
fec_call_api(
path = "/names/audit_committees/",
api_key = api_key,
Expand Down
3 changes: 1 addition & 2 deletions tests/testthat/_fixtures/trello-010-call.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,7 @@
trello_call_api <- function(path,
query = NULL,
body = NULL,
method = NULL,
key = Sys.getenv("TRELLO_KEY"),
method = NULL, key = Sys.getenv("TRELLO_KEY"),
token = Sys.getenv("TRELLO_TOKEN")) {
nectar::call_api(
base_url = "https://trello.com/1",
Expand Down
20 changes: 20 additions & 0 deletions tests/testthat/_fixtures/trello-paths-board.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
# These functions were generated by the {beekeeper} package, based on the paths
# element from the source API description. You should carefully review these
# functions. Missing documentation is tagged with "BKTODO" to make it easier for
# you to search for issues.

#' addBoards()
#'
#' BKTODO: No description provided.
#'
#' @inheritParams trello_call_api
#' @return BKTODO: Return descriptions are not yet implemented in beekeeper
#' @export
trello_add_boards <- function(
key = Sys.getenv("TRELLO_KEY"),
token = Sys.getenv("TRELLO_TOKEN")) {
trello_call_api(
path = "/boards",
key = key, token = token
)
}
2 changes: 1 addition & 1 deletion tests/testthat/_fixtures/trello_beekeeper.yml
Original file line number Diff line number Diff line change
Expand Up @@ -2,4 +2,4 @@ api_title: Trello
api_abbr: trello
api_version: '1.0'
rapid_file: trello_rapid.rds
updated_on: 2024-03-27 19:14:39.671908
updated_on: 2024-03-29 21:06:50.517151
Binary file modified tests/testthat/_fixtures/trello_rapid.rds
Binary file not shown.
19 changes: 19 additions & 0 deletions tests/testthat/test-generate_pkg-paths.R
Original file line number Diff line number Diff line change
Expand Up @@ -74,3 +74,22 @@ test_that("generate_pkg() generates path functions for fec", {
generated_file_content <- readLines("R/paths-audit.R")
expect_identical(generated_file_content, expected_file_content)
})

test_that("generate_pkg() generates path functions for trello", {
# some tags failed before this, more complicated security
skip_on_cran()
config <- readLines(test_path("_fixtures", "trello_beekeeper.yml"))
trello_rapid <- readRDS(test_path("_fixtures", "trello_rapid.rds"))
expected_file_content <- readLines(
test_path("_fixtures", "trello-paths-board.R")
)

create_local_package()
writeLines(config, "_beekeeper.yml")
saveRDS(trello_rapid, "trello_rapid.rds")

generate_pkg(pkg_agent = "TESTPKG (https://example.com)")

generated_file_content <- readLines("R/paths-board.R")
expect_identical(generated_file_content, expected_file_content)
})

0 comments on commit 116e8a9

Please sign in to comment.