Skip to content

Commit

Permalink
add rtoot fix #123 ref #121 #34
Browse files Browse the repository at this point in the history
  • Loading branch information
chainsawriot committed Dec 14, 2022
1 parent c868144 commit a4ce05c
Show file tree
Hide file tree
Showing 7 changed files with 853 additions and 4 deletions.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ export(get_timeline_public)
export(parse_stream)
export(post_toot)
export(post_user)
export(rtoot)
export(search_accounts)
export(stream_timeline_hashtag)
export(stream_timeline_list)
Expand Down
1 change: 1 addition & 0 deletions R/rtoot-package.R
Original file line number Diff line number Diff line change
Expand Up @@ -17,4 +17,5 @@
#' Get started by reading `vignette("rtoot")`. and browse all vignettes with `browseVignettes(package = "rtoot")`
#'
#' @keywords internal
#' @aliases rtoot-package
"_PACKAGE"
35 changes: 32 additions & 3 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -9,16 +9,45 @@ print.rtoot_bearer <- function(x,...){
invisible(x)
}

#' Query Mastodon API
#'
#' This is a minimalistic interface for querying the Mastodon API. This function is for advanced users who want to query
#' the Mastodon API for endpoints that the R functions are not yet implemented.
#' Please also note that the API responses will not be parsed as tibble. Refer to the official API documentation for endpoints and parameters.
#' @param endpoint character, a Mastodon API endpoint. Currently, only endpoints using GET are supported
#' @param ... Name-value pairs giving API parameters.
#' @param params list, API parameters to be submitted
#' @inheritParams get_timeline_public
#' @return a list
#' @export
#' @references https://docs.joinmastodon.org/methods/
#' @examples
#' \dontrun{
#' rtoot(endpoint = "api/v1/notifications")
#' rtoot(endpoint = "api/v1/notifications", limit = 8)
#' ## same
#' rtoot(endpoint = "api/v1/notifications", params = list(limit = 8))
#' rtoot(endpoint = "api/v1/followed_tags")
#' ## reimplement `get_timeline_public`
#' rtoot(endpoint = "api/v1/timelines/public", instance = "emacs.ch", local = TRUE, anonymous = TRUE)
#' }
rtoot <- function(endpoint, ..., params = list(), token = NULL, instance = NULL,
anonymous = FALSE) {
if (missing(endpoint)) {
stop("Please provide an `endpoint`", call. = FALSE)
}
params <- c(list(...), params)
make_get_request(token = token, path = endpoint, params = params, instance = instance, anonymous = anonymous)
}

## Endpoints under
## https://docs.joinmastodon.org/methods/statuses/
## https://docs.joinmastodon.org/methods/timelines/

make_get_request <- function(token, path, params = list(), instance = NULL, anonymous = FALSE, ...) {
if (is.null(instance) && anonymous) {
stop("provide either an instance or a token")
stop("provide either an instance or a token", call. = FALSE)
}

if (is.null(instance)) {
token <- check_token_rtoot(token)
url <- prepare_url(token$instance)
Expand All @@ -34,7 +63,7 @@ make_get_request <- function(token, path, params = list(), instance = NULL, anon

status_code <- httr::status_code(request_results)
if (!status_code %in% c(200)) {
stop(paste("something went wrong. Status code:", status_code))
stop(paste("something went wrong. Status code:", status_code), call. = FALSE)
}
output <- httr::content(request_results)
headers <- parse_header(httr::headers(request_results))
Expand Down
2 changes: 1 addition & 1 deletion man/rtoot-package.Rd

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

50 changes: 50 additions & 0 deletions man/rtoot.Rd

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

Loading

0 comments on commit a4ce05c

Please sign in to comment.