blob: e8a7e4969756db8b3bb25b91ce79b72a4409b9bd [file] [log] [blame]
Marc Kupietzfd9e7492019-11-08 15:45:18 +01001################################################################################
2# Use setClassUnion to define the unholy NULL-data union as a virtual class.
3################################################################################
4setClassUnion("characterOrNULL", c("character", "NULL"))
Marc Kupietza4675722022-02-23 23:55:15 +01005setClassUnion("listOrNULL", c("list", "NULL"))
Marc Kupietzfd9e7492019-11-08 15:45:18 +01006
Marc Kupietze95108e2019-09-18 13:23:58 +02007#' Class KorAPConnection
Marc Kupietz25aebc32019-09-16 18:40:50 +02008#'
Marc Kupietz67edcb52021-09-20 21:54:24 +02009#' `KorAPConnection` objects represent the connection to a KorAP server.
10#' New `KorAPConnection` objects can be created by `new("KorAPConnection")`.
Marc Kupietze95108e2019-09-18 13:23:58 +020011#'
Marc Kupietz0a96b282019-10-01 11:05:31 +020012#' @import R.cache
Marc Kupietze95108e2019-09-18 13:23:58 +020013#' @import utils
14#' @import methods
Marc Kupietza81343d2022-09-06 12:32:10 +020015#' @slot KorAPUrl URL of the web user interface of the KorAP server used in the connection.
16#' @slot apiVersion requested KorAP API version.
17#' @slot indexRevision indexRevision code as reported from API via `X-Index-Revision` HTTP header.
18#' @slot apiUrl full URL of API including version.
19#' @slot accessToken OAuth2 access token.
20#' @slot userAgent user agent string used for connection the API.
21#' @slot timeout tineout in seconds for API requests (this does not influence server internal timeouts)
22#' @slot verbose logical that decides whether operations will default to be verbose.
23#' @slot cache logical that decides if API calls are cached locally.
24#' @slot welcome list containing HTTP response received from KorAP server welcome function.
25
Marc Kupietze95108e2019-09-18 13:23:58 +020026#' @export
Marc Kupietza4675722022-02-23 23:55:15 +010027KorAPConnection <- setClass("KorAPConnection", slots=c(KorAPUrl="character", apiVersion="character", indexRevision="characterOrNULL", apiUrl="character", accessToken="characterOrNULL", userAgent="character", timeout="numeric", verbose="logical", cache="logical", welcome="listOrNULL"))
Marc Kupietze95108e2019-09-18 13:23:58 +020028
29#' @param .Object KorAPConnection object
Marc Kupietza81343d2022-09-06 12:32:10 +020030#' @param KorAPUrl URL of the web user interface of the KorAP server instance you want to access.
Marc Kupietze95108e2019-09-18 13:23:58 +020031#' @param apiVersion which version of KorAP's API you want to connect to.
32#' @param apiUrl URL of the KorAP web service.
Marc Kupietz132f0052023-04-16 14:23:05 +020033#' @param accessToken OAuth2 access token. For queries on corpus parts with restricted
34#' access (e.g. textual queries on IPR protected data), you need to authorize
35#' your application with an access token.
Marc Kupietza4f51d72025-01-25 16:23:18 +010036#' You can obtain an access token using the [auth()] method.
37#'
38#' More details are explained in the
Marc Kupietz132f0052023-04-16 14:23:05 +020039#' [authorization section](https://github.com/KorAP/RKorAPClient#authorization)
40#' of the RKorAPClient Readme on GitHub.
41#'
42#' To use authorization based on an access token
43#' in subsequent queries, initialize your KorAP connection with:
44#'
45#' ```
46#' kco <- new("KorAPConnection", accessToken="<access token>")
47#' ```
48#'
Marc Kupietz4862b862019-11-07 10:13:53 +010049#' In order to make the API
Marc Kupietz67edcb52021-09-20 21:54:24 +020050#' token persistent for the currently used `KorAPUrl` (you can have one
Marc Kupietz132f0052023-04-16 14:23:05 +020051#' token per KorAPUrl / KorAP server instance), use:
52#'
53#' ```
54#' persistAccessToken(kco)
55#' ```
56#'
57#' This will store it in your keyring using the
Marc Kupietz6a02e4c2025-01-09 21:22:30 +010058#' [keyring::keyring-package]. Subsequent new("KorAPConnection") calls will
Marc Kupietz4862b862019-11-07 10:13:53 +010059#' then automatically retrieve the token from your keying. To stop using a
Marc Kupietz67edcb52021-09-20 21:54:24 +020060#' persisted token, call `clearAccessToken(kco)`. Please note that for
Marc Kupietz4862b862019-11-07 10:13:53 +010061#' DeReKo, authorized queries will behave differently inside and outside the
62#' IDS, because of the special license situation. This concerns also cached
63#' results which do not take into account from where a request was issued. If
Marc Kupietz67edcb52021-09-20 21:54:24 +020064#' you experience problems or unexpected results, please try `kco <-
65#' new("KorAPConnection", cache=FALSE)` or use
66#' [clearCache()] to clear the cache completely.
Marc Kupietz132f0052023-04-16 14:23:05 +020067#'
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +020068#' @param userAgent user agent string.
Marc Kupietza81343d2022-09-06 12:32:10 +020069#' @param timeout tineout in seconds for API requests (this does not influence server internal timeouts).
70#' @param verbose logical that decides whether following operations will default to
Marc Kupietz4862b862019-11-07 10:13:53 +010071#' be verbose.
Marc Kupietza81343d2022-09-06 12:32:10 +020072#' @param cache logical that decides if API calls are cached locally. You can clear
Marc Kupietz67edcb52021-09-20 21:54:24 +020073#' the cache with [clearCache()].
74#' @return [KorAPConnection()] object that can be used e.g. with
75#' [corpusQuery()]
Marc Kupietze95108e2019-09-18 13:23:58 +020076#'
77#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +020078#' \dontrun{
79#'
Marc Kupietz5a519822019-09-20 21:43:52 +020080#' kcon <- new("KorAPConnection", verbose = TRUE)
Marc Kupietze95108e2019-09-18 13:23:58 +020081#' kq <- corpusQuery(kcon, "Ameisenplage")
Marc Kupietz5a519822019-09-20 21:43:52 +020082#' kq <- fetchAll(kq)
Marc Kupietz05b22772020-02-18 21:58:42 +010083#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +020084#'
Marc Kupietz4862b862019-11-07 10:13:53 +010085#' \dontrun{
Marc Kupietz6ae76052021-09-21 10:34:00 +020086#'
Marc Kupietzb956b812019-11-25 17:53:13 +010087#' kcon <- new("KorAPConnection", verbose = TRUE, accessToken="e739u6eOzkwADQPdVChxFg")
Marc Kupietz4862b862019-11-07 10:13:53 +010088#' kq <- corpusQuery(kcon, "Ameisenplage", metadataOnly=FALSE)
89#' kq <- fetchAll(kq)
90#' kq@collectedMatches$snippet
91#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +020092#'
Marc Kupietze95108e2019-09-18 13:23:58 +020093#' @rdname KorAPConnection-class
Marc Kupietz632cbd42019-09-06 16:04:51 +020094#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +020095setMethod("initialize", "KorAPConnection",
Marc Kupietz6a3185b2021-12-07 10:23:16 +010096 function(.Object, KorAPUrl = "https://korap.ids-mannheim.de/", apiVersion = 'v1.0', apiUrl, accessToken = getAccessToken(KorAPUrl), userAgent = "R-KorAP-Client", timeout=240, verbose = FALSE, cache = TRUE) {
Marc Kupietze95108e2019-09-18 13:23:58 +020097 .Object <- callNextMethod()
98 m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
99 .Object@KorAPUrl <- regmatches(KorAPUrl, m)
100 if (!endsWith(.Object@KorAPUrl, '/')) {
101 .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
102 }
103 if (missing(apiUrl)) {
104 .Object@apiUrl = paste0(.Object@KorAPUrl, 'api/', apiVersion, '/')
105 } else {
106 .Object@apiUrl = apiUrl
107 }
Marc Kupietzb956b812019-11-25 17:53:13 +0100108 .Object@accessToken = accessToken
Marc Kupietze95108e2019-09-18 13:23:58 +0200109 .Object@apiVersion = apiVersion
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200110 .Object@userAgent = userAgent
111 .Object@timeout = timeout
Marc Kupietz5a519822019-09-20 21:43:52 +0200112 .Object@verbose = verbose
Marc Kupietz0a96b282019-10-01 11:05:31 +0200113 .Object@cache = cache
Marc Kupietza4675722022-02-23 23:55:15 +0100114 .Object@welcome = apiCall(.Object, .Object@apiUrl, json = FALSE, cache = FALSE, getHeaders = TRUE)
115 if (!is.null(.Object@welcome)) {
116 message(.Object@welcome[[2]])
117 }
118 .Object@indexRevision <- .Object@welcome[[1]][["x-index-revision"]]
Marc Kupietze95108e2019-09-18 13:23:58 +0200119 .Object
120 })
121
Marc Kupietza96537f2019-11-09 23:07:44 +0100122
Marc Kupietzb956b812019-11-25 17:53:13 +0100123accessTokenServiceName <- "RKorAPClientAccessToken"
Marc Kupietz4862b862019-11-07 10:13:53 +0100124
Marc Kupietzb956b812019-11-25 17:53:13 +0100125setGeneric("persistAccessToken", function(kco, ...) standardGeneric("persistAccessToken") )
Marc Kupietz4862b862019-11-07 10:13:53 +0100126
Marc Kupietza4f51d72025-01-25 16:23:18 +0100127#' Persist current access token in keyring
128#'
129#' @param kco KorAPConnection object
130#' @param accessToken access token to be persisted. If not supplied, the current access token of the KorAPConnection object will be used.
131#' @return KorAPConnection object.
132#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100133#' @aliases persistAccessToken
Marc Kupietza4f51d72025-01-25 16:23:18 +0100134#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100135#' @import keyring
136#' @export
Marc Kupietza4f51d72025-01-25 16:23:18 +0100137#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100138#' @examples
139#' \dontrun{
Marc Kupietzb956b812019-11-25 17:53:13 +0100140#' kco <- new("KorAPConnection", accessToken="e739u6eOzkwADQPdVChxFg")
141#' persistAccessToken(kco)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100142#'
143#' kco <- new("KorAPConnection") %>% auth(app_id="<my application id>") %>% persistAccessToken()
Marc Kupietz4862b862019-11-07 10:13:53 +0100144#' }
145#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100146#' @seealso [clearAccessToken()], [auth()]
147#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100148setMethod("persistAccessToken", "KorAPConnection", function(kco, accessToken = kco@accessToken) {
149 if (is.null(accessToken))
150 stop("It seems that you have not supplied any access token that could be persisted.", call. = FALSE)
Marc Kupietz4862b862019-11-07 10:13:53 +0100151
Marc Kupietzb956b812019-11-25 17:53:13 +0100152 kco@accessToken <- accessToken
153 key_set_with_value(accessTokenServiceName, kco@KorAPUrl, accessToken)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100154 return(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100155})
156
Marc Kupietzb956b812019-11-25 17:53:13 +0100157setGeneric("clearAccessToken", function(kco) standardGeneric("clearAccessToken") )
Marc Kupietz4862b862019-11-07 10:13:53 +0100158
Marc Kupietza4f51d72025-01-25 16:23:18 +0100159#' Clear access token from keyring and KorAPConnection object
160#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100161#' @aliases clearAccessToken
Marc Kupietz4862b862019-11-07 10:13:53 +0100162#' @import keyring
Marc Kupietza4f51d72025-01-25 16:23:18 +0100163#' @param kco KorAPConnection object
164#' @return KorAPConnection object with access token set to `NULL`.
Marc Kupietz4862b862019-11-07 10:13:53 +0100165#' @export
166#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +0200167#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100168#' \dontrun{
Marc Kupietz4862b862019-11-07 10:13:53 +0100169#' kco <- new("KorAPConnection")
Marc Kupietza4f51d72025-01-25 16:23:18 +0100170#' kco <- clearAccessToken(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100171#' }
172#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100173#' @seealso [persistAccessToken()]
174#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100175setMethod("clearAccessToken", "KorAPConnection", function(kco) {
176 key_delete(accessTokenServiceName, kco@KorAPUrl)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100177 kco@accessToken <- NULL
178 kco
Marc Kupietz4862b862019-11-07 10:13:53 +0100179})
180
Marc Kupietza4f51d72025-01-25 16:23:18 +0100181generic_kor_app_id = "99FbPHH7RrN36hbndF7b6f"
182
183
184setGeneric("auth", function(kco, app_id = generic_kor_app_id, scope = "search match_info") standardGeneric("auth") )
185
186#' Authorize RKorAPClient
187#'
188#' @aliases auth
189#'
190#' @description
191#' `r lifecycle::badge("experimental")`
192#'
193#' Authorize RKorAPClient to make KorAP queries and download results on behalf of the user.
194#'
195#' @param kco KorAPConnection object
196#' @param app_id OAuth2 application id. Defaults to the generic KorAP client application id.
197#' @param scope OAuth2 scope. Defaults to "search match_info".
198#' @return KorAPConnection object with access token set in `@accessToken`.
199#'
200#' @importFrom httr2 oauth_client oauth_flow_auth_code
201#' @examples
202#' \dontrun{
203#' kco <- new("KorAPConnection", verbose = TRUE) %>% auth()
Marc Kupietza5501652025-01-28 20:25:42 +0100204#' df <- collocationAnalysis(kco, "focus([marmot/p=ADJA] {Ameisenplage})",
205#' leftContextSize=1, rightContextSize=0)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100206#' }
207#'
208#' @seealso [persistAccessToken()], [clearAccessToken()]
209#'
210#' @export
211setMethod("auth", "KorAPConnection", function(kco, app_id = generic_kor_app_id, scope = "search match_info") {
212 if ( kco@KorAPUrl != "https://korap.ids-mannheim.de/" & app_id == generic_kor_app_id) {
213 warning(paste("You can use the default app_id only for the IDS Mannheim KorAP main instance for querying DeReKo. Please provide your own app_id for accesing", kco@KorAPUrl))
214 return(kco)
215 }
216 if (is.null(kco@accessToken) || is.null(kco@welcome)) { # if access token is not set or invalid
217 kco@accessToken <- (
218 httr2::oauth_client(
219 id = app_id,
220 token_url = paste0(kco@apiUrl, "oauth2/token")
221 ) %>%
222 httr2::oauth_flow_auth_code(
223 scope = scope,
224 auth_url = paste0(kco@KorAPUrl, "settings/oauth/authorize"),
225 redirect_uri = "http://localhost:1410"
226 )
227 )$access_token
228 } else {
229 log_info(kco@verbose, "Client authorized. Access token already set.")
230 }
231 return(kco)
232})
233
234
235
Marc Kupietz4862b862019-11-07 10:13:53 +0100236#' @import keyring
Marc Kupietzb956b812019-11-25 17:53:13 +0100237getAccessToken <- function(KorAPUrl) {
Marc Kupietz59e449b2019-12-12 12:53:54 +0100238 keyList <- tryCatch(withCallingHandlers(key_list(service = accessTokenServiceName),
Marc Kupietzddce5562019-11-24 15:45:38 +0100239 warning = function(w) invokeRestart("muffleWarning"),
Marc Kupietz59e449b2019-12-12 12:53:54 +0100240 error = function(e) return(NULL)),
241 error = function(e) { })
Marc Kupietz01c24772021-07-14 18:27:36 +0200242 if (KorAPUrl %in% keyList$username)
Marc Kupietzb956b812019-11-25 17:53:13 +0100243 key_get(accessTokenServiceName, KorAPUrl)
Marc Kupietzfd9e7492019-11-08 15:45:18 +0100244 else
245 NULL
Marc Kupietz4862b862019-11-07 10:13:53 +0100246}
Marc Kupietz0a96b282019-10-01 11:05:31 +0200247
Marc Kupietz581a29b2021-09-04 20:51:04 +0200248
249warnIfNoAccessToken <- function(kco) {
250 if (is.null(kco@accessToken)) {
251 warning(
252 paste0(
253 "In order to receive KWICSs also from corpora with restricted licenses, you need an access token.\n",
254 "To generate an access token, login to KorAP and navigite to KorAP's OAuth settings <",
255 kco@KorAPUrl,
256 "settings/oauth#page-top>"
257 )
258 )
259 }
260}
261
Marc Kupietz0a96b282019-10-01 11:05:31 +0200262KorAPCacheSubDir <- function() {
Marc Kupietz70b2c722020-02-18 13:32:09 +0100263 paste0("RKorAPClient_",
264 gsub(
265 "^([0-9]+\\.[0-9]+).*",
266 "\\1",
267 packageVersion("RKorAPClient"),
268 perl = TRUE
269 ))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200270}
271
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200272setGeneric("apiCall", function(kco, ...) standardGeneric("apiCall") )
273
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200274## quiets concerns of R CMD check re: the .'s that appear in pipelines
275if(getRversion() >= "2.15.1") utils::globalVariables(c("."))
276
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200277#' @aliases apiCall
278#' @rdname KorAPConnection-class
279#' @param kco KorAPConnection object
280#' @param url request url
Marc Kupietzf9129592025-01-26 19:17:54 +0100281#' @param json logical that determines if JSON result is expected
Marc Kupietzb49afa02020-06-04 15:50:29 +0200282#' @param getHeaders logical that determines if headers and content should be returned (as a list)
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200283#' @importFrom jsonlite fromJSON
Marc Kupietza4675722022-02-23 23:55:15 +0100284#' @importFrom curl has_internet
Marc Kupietzf9129592025-01-26 19:17:54 +0100285#' @importFrom httr2 req_user_agent req_timeout req_headers req_perform resp_status resp_body_string resp_body_json resp_content_type
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200286#' @export
Marc Kupietzf9129592025-01-26 19:17:54 +0100287setMethod("apiCall", "KorAPConnection", function(kco, url, json = TRUE, getHeaders = FALSE, cache = kco@cache, timeout = kco@timeout) {
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100288 result <- ""
Marc Kupietzf9129592025-01-26 19:17:54 +0100289
290 # Handle caching if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100291 if (cache) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100292 result <- R.cache::loadCache(dir = KorAPCacheSubDir(), key = list(url, kco@accessToken, kco@indexRevision))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100293 if (!is.null(result)) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100294 if (!is.null(result$meta)) result$meta$cached <- "local"
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100295 return(result)
Marc Kupietz0a96b282019-10-01 11:05:31 +0200296 }
297 }
Marc Kupietza4675722022-02-23 23:55:15 +0100298
Marc Kupietzf9129592025-01-26 19:17:54 +0100299 # Check for internet connection
Marc Kupietza4675722022-02-23 23:55:15 +0100300 if (!curl::has_internet()) {
301 message("No internet connection.")
302 return(invisible(NULL))
303 }
304
Marc Kupietzf9129592025-01-26 19:17:54 +0100305 # Create the request
306 req <- httr2::request(url) |>
307 httr2::req_user_agent(kco@userAgent) |>
308 httr2::req_timeout(timeout)
Marc Kupietza4675722022-02-23 23:55:15 +0100309
Marc Kupietzf9129592025-01-26 19:17:54 +0100310 # Add authorization header if access token is available
311 if (!is.null(kco@accessToken)) {
312 req <- req |> httr2::req_headers(Authorization = paste("Bearer", kco@accessToken))
313 }
314
315 # Perform the request and handle errors
316 resp <- tryCatch(
317 req |> httr2::req_perform(),
318 error = function(e) {
319 message(if(kco@verbose) "\n" else "", "Request failed: ", paste(e$message, e$parent$message, sep = " "))
320 e$resp
321 }
322 )
323
324 if (is.null(resp)) return(invisible(NULL))
325
326 # Check response status
327 if (resp |> httr2::resp_status() != 200) {
328
329 message("API request failed with status: ", resp |> httr2::resp_status())
330
331 result <- tryCatch(
332 resp |> httr2::resp_body_json(),
333 error = function(e) {
334 message("Failed to parse json with error details: ", e$message)
335 return(NULL)
336 }
337 )
338 # Handle errors in the response (if any)
339 if (!is.null(result$errors)) {
340 errors <- result$errors
341 warning_msgs <- if (is.data.frame(errors)) {
342 apply(errors, 1, function(warning) paste(warning[1], ": ", warning[2]))
343 } else {
344 lapply(errors, function(error) paste(error, collapse = " "))
345 }
346 message(paste(warning_msgs, collapse = "\n"))
347 }
348
Marc Kupietza4675722022-02-23 23:55:15 +0100349 return(invisible(NULL))
350 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100351
352 # Process JSON response or raw text based on `json` parameter
353 if (json) {
354 content_type <- resp |> httr2::resp_content_type()
355 if (!content_type %in% c("application/json", "application/ld+json")) {
356 message("API did not return JSON")
Marc Kupietza4675722022-02-23 23:55:15 +0100357 return(invisible(NULL))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100358 }
Marc Kupietz04814f22023-04-16 17:13:27 +0200359
Marc Kupietzf9129592025-01-26 19:17:54 +0100360 result <- tryCatch(
361 resp |> httr2::resp_body_string() |> jsonlite::fromJSON(),
362 error = function(e) {
363 message("Failed to parse JSON: ", e$message)
364 return(NULL)
365 }
366 )
367
368 # Handle warnings in the response (if any)
369 if (!is.null(result$warnings)) {
370 warnings <- result$warnings
371 warning_msgs <- if (is.data.frame(warnings)) {
372 apply(warnings, 1, function(warning) paste(warning[1], ": ", warning[2]))
373 } else {
374 lapply(warnings, function(warning) paste(warning, collapse = " "))
375 }
376 message(paste(warning_msgs, collapse = "\n"))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100377 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100378 } else {
379 result <- resp |> httr2::resp_body_string()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200380 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100381
382 # Save to cache if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100383 if (cache) {
Marc Kupietzb49afa02020-06-04 15:50:29 +0200384 R.cache::saveCache(result, key = list(url, kco@accessToken, kco@indexRevision), dir = KorAPCacheSubDir(), compress = TRUE)
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100385 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100386
387 # Return headers and content as a list if `getHeaders` is TRUE
Marc Kupietzb49afa02020-06-04 15:50:29 +0200388 if (getHeaders) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100389 list(headers = resp |> httr2::resp_headers(), content = result)
Marc Kupietzb49afa02020-06-04 15:50:29 +0200390 } else {
391 result
392 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200393})
394
Marc Kupietz0a96b282019-10-01 11:05:31 +0200395setGeneric("clearCache", function(kco) standardGeneric("clearCache") )
396
397#' @aliases clearCache
398#' @rdname KorAPConnection-class
399#' @export
400setMethod("clearCache", "KorAPConnection", function(kco) {
401 R.cache::clearCache(dir=KorAPCacheSubDir())
402})
403
Marc Kupietze95108e2019-09-18 13:23:58 +0200404#' @rdname KorAPConnection-class
405#' @param object KorAPConnection object
406#' @export
407setMethod("show", "KorAPConnection", function(object) {
408 cat("<KorAPConnection>", "\n")
409 cat("apiUrl: ", object@apiUrl, "\n")
410})
411
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200412##' Funtion KorAPConnection()
413##'
414##' Wrappper function for new("KorAPConnection")
415##'
416##' @rdname KorAPConnection-constructor
417##' @name KorAPConnection-constructor
418##' @export
419## XKorAPConnection <- function(...) new("KorAPConnection", ...)