blob: 834d1e3c03911a5a40ed3ff2e1f4e4647316637e [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 Kupietzf83d59a2025-02-01 14:48:30 +01006# setOldClass("httr2_oauth_client")
Marc Kupietzfd9e7492019-11-08 15:45:18 +01007
Marc Kupietza8c40f42025-06-24 15:49:52 +02008#' Connect to KorAP Server
Marc Kupietz25aebc32019-09-16 18:40:50 +02009#'
Marc Kupietza8c40f42025-06-24 15:49:52 +020010#' `KorAPConnection()` creates a connection to a KorAP server for corpus queries.
11#' This is your starting point for all corpus analysis tasks.
Marc Kupietze95108e2019-09-18 13:23:58 +020012#'
Marc Kupietza8c40f42025-06-24 15:49:52 +020013#' Use `KorAPConnection()` to connect, then `corpusQuery()` to search, and
14#' `fetchAll()` to retrieve results. For authorized access to restricted corpora,
15#' use `auth()` or provide an `accessToken`.
16#'
17#' @section Basic Workflow:
18#' ```r
19#' # Connect to KorAP
20#' kcon <- KorAPConnection()
21#'
22#' # Search for a term
23#' query <- corpusQuery(kcon, "Ameisenplage")
24#'
25#' # Get all results
26#' results <- fetchAll(query)
27#' ```
28#'
29#' @section Authorization:
30#' For access to restricted corpora, authorize your connection:
31#' ```r
32#' kcon <- KorAPConnection() |> auth()
33#' ```
34#'
Marc Kupietzf9914bb2025-06-25 09:57:55 +020035#' @param KorAPUrl URL of the web user interface of the KorAP server instance you want to access.
36#' Defaults to the environment variable `KORAP_URL` if set and to the IDS Mannheim KorAP main instance
Marc Kupietz36117de2025-06-25 12:46:10 +020037#' to query DeReKo, otherwise. In order to access the KorAP instance at the German
38#' National Library (DNB) to query the contemporary fiction corpus DeLiKo@@DNB,
39#' for example, set `KorAPUrl` to <https://korap.dnb.de/>.
Marc Kupietzf9914bb2025-06-25 09:57:55 +020040#' @param apiVersion which version of KorAP's API you want to connect to. Defaults to "v1.0".
41#' @param apiUrl URL of the KorAP web service. If not provided, it will be constructed from KorAPUrl and apiVersion.
42#' @param accessToken OAuth2 access token. For queries on corpus parts with restricted
43#' access (e.g. textual queries on IPR protected data), you need to authorize
44#' your application with an access token.
45#' You can obtain an access token in the OAuth settings of your KorAP web interface.
46#'
47#' More details are explained in the
48#' [authorization section](https://github.com/KorAP/RKorAPClient#authorization)
49#' of the RKorAPClient Readme on GitHub.
50#'
51#' To use authorization based on an access token
52#' in subsequent queries, initialize your KorAP connection with:
53#'
54#' ```
55#' kco <- KorAPConnection(accessToken="<access token>")
56#' ```
57#'
58#' In order to make the API
59#' token persistent for the currently used `KorAPUrl` (you can have one
60#' token per KorAPUrl / KorAP server instance), use:
61#'
62#' ```
63#' persistAccessToken(kco)
64#' ```
65#'
66#' This will store it in your keyring using the
67#' [keyring::keyring-package]. Subsequent KorAPConnection() calls will
68#' then automatically retrieve the token from your keying. To stop using a
69#' persisted token, call `clearAccessToken(kco)`. Please note that for
70#' DeReKo, authorized queries will behave differently inside and outside the
71#' IDS, because of the special license situation. This concerns also cached
72#' results which do not take into account from where a request was issued. If
73#' you experience problems or unexpected results, please try `kco <-
74#' KorAPConnection(cache=FALSE)` or use
75#' [clearCache()] to clear the cache completely.
76#'
77#' An alternative to using an access token is to use a browser-based oauth2 workflow
78#' to obtain an access token. This can be done with the [auth()] method.
Marc Kupietz36117de2025-06-25 12:46:10 +020079#' @param oauthClient OAuth2 client object.
Marc Kupietzf9914bb2025-06-25 09:57:55 +020080#' @param oauthScope OAuth2 scope. Defaults to "search match_info".
81#' @param authorizationSupported logical that indicates if authorization is supported/necessary for the current KorAP instance. Automatically set during initialization.
82#' @param userAgent user agent string. Defaults to "R-KorAP-Client".
83#' @param timeout timeout in seconds for API requests (this does not influence server internal timeouts). Defaults to 240 seconds.
84#' @param verbose logical that decides whether following operations will default to
85#' be verbose. Defaults to FALSE.
86#' @param cache logical that decides if API calls are cached locally. You can clear
87#' the cache with [clearCache()]. Defaults to TRUE.
88#'
89#' @return [KorAPConnection()] object that can be used e.g. with [corpusQuery()]
90#'
Marc Kupietza8c40f42025-06-24 15:49:52 +020091#' @details
92#' The KorAPConnection object contains various configuration slots for advanced users:
93#' KorAPUrl (server URL), apiVersion, accessToken (OAuth2 token),
94#' timeout (request timeout), verbose (logging), cache (local caching),
95#' and other technical parameters. Most users can ignore these implementation details.
96#'
97#' @family initialization functions
Marc Kupietz0a96b282019-10-01 11:05:31 +020098#' @import R.cache
Marc Kupietze95108e2019-09-18 13:23:58 +020099#' @import utils
100#' @import methods
Marc Kupietz6dfeed92025-06-03 11:58:06 +0200101#' @include logging.R
Marc Kupietza81343d2022-09-06 12:32:10 +0200102
Marc Kupietze95108e2019-09-18 13:23:58 +0200103#' @export
Marc Kupietza824d502025-05-02 15:40:23 +0200104KorAPConnection <- setClass("KorAPConnection", slots = c(KorAPUrl = "character", apiVersion = "character", indexRevision = "characterOrNULL", apiUrl = "character", accessToken = "characterOrNULL", oauthClient = "ANY", oauthScope = "characterOrNULL", authorizationSupported = "logical", userAgent = "character", timeout = "numeric", verbose = "logical", cache = "logical", welcome = "listOrNULL"))
Marc Kupietz62b17892025-02-01 18:26:45 +0100105
Marc Kupietza824d502025-05-02 15:40:23 +0200106generic_kor_app_id <- "99FbPHH7RrN36hbndF7b6f"
Marc Kupietz62b17892025-02-01 18:26:45 +0100107
Marc Kupietza824d502025-05-02 15:40:23 +0200108kustvakt_redirect_uri <- "http://localhost:1410/"
109kustvakt_auth_path <- "settings/oauth/authorize"
Marc Kupietz62b17892025-02-01 18:26:45 +0100110
Marc Kupietze95108e2019-09-18 13:23:58 +0200111
Marc Kupietza8c40f42025-06-24 15:49:52 +0200112#' Initialize KorAPConnection object
113#' @keywords internal
Marc Kupietz632cbd42019-09-06 16:04:51 +0200114#' @export
Marc Kupietz36117de2025-06-25 12:46:10 +0200115#'
Marc Kupietzb79fd442025-03-26 10:25:03 +0100116setMethod("initialize", "KorAPConnection", function(.Object,
117 KorAPUrl = if (is.null(Sys.getenv("KORAP_URL")) |
Marc Kupietza824d502025-05-02 15:40:23 +0200118 Sys.getenv("KORAP_URL") == "") {
Marc Kupietzb79fd442025-03-26 10:25:03 +0100119 "https://korap.ids-mannheim.de/"
Marc Kupietza824d502025-05-02 15:40:23 +0200120 } else {
121 Sys.getenv("KORAP_URL")
122 },
123 apiVersion = "v1.0",
Marc Kupietzb79fd442025-03-26 10:25:03 +0100124 apiUrl,
125 accessToken = getAccessToken(KorAPUrl),
126 oauthClient = NULL,
127 oauthScope = "search match_info",
128 authorizationSupported = TRUE,
129 userAgent = "R-KorAP-Client",
130 timeout = 240,
131 verbose = FALSE,
132 cache = TRUE) {
133 .Object <- callNextMethod()
134 m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
135 .Object@KorAPUrl <- regmatches(KorAPUrl, m)
Marc Kupietza824d502025-05-02 15:40:23 +0200136 if (!endsWith(.Object@KorAPUrl, "/")) {
Marc Kupietzb79fd442025-03-26 10:25:03 +0100137 .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
138 }
139 if (missing(apiUrl)) {
Marc Kupietza824d502025-05-02 15:40:23 +0200140 .Object@apiUrl <- paste0(.Object@KorAPUrl, "api/", apiVersion, "/")
141 } else {
142 .Object@apiUrl <- apiUrl
143 }
144 .Object@accessToken <- accessToken
145 .Object@oauthClient <- oauthClient
146 .Object@apiVersion <- apiVersion
147 .Object@userAgent <- userAgent
148 .Object@oauthScope <- oauthScope
149 .Object@authorizationSupported <- authorizationSupported
150 .Object@timeout <- timeout
151 .Object@verbose <- verbose
152 .Object@cache <- cache
153 .Object@welcome <- apiCall(.Object, .Object@apiUrl, json = FALSE, cache = FALSE, getHeaders = TRUE)
154 if (!is.null(.Object@welcome)) {
155 message(.Object@welcome[[2]])
156 resp <- httr2::request(.Object@KorAPUrl) |>
157 httr2::req_url_path_append(kustvakt_auth_path) |>
158 httr2::req_error(is_error = \(resp) FALSE) |>
159 httr2::req_perform()
160 .Object@authorizationSupported <- (httr2::resp_status(resp) == 200)
Marc Kupietz62b17892025-02-01 18:26:45 +0100161
Marc Kupietza824d502025-05-02 15:40:23 +0200162 .Object@indexRevision <- .Object@welcome[[1]][["x-index-revision"]]
163 } else {
164 if (grepl(.Object@KorAPUrl, .Object@apiUrl)) {
165 message("Could not connect to KorAP instance ", .Object@KorAPUrl)
166 } else {
167 message("Could not connect to KorAP API at ", .Object@apiUrl)
168 }
169 }
170 .Object
171})
Marc Kupietze95108e2019-09-18 13:23:58 +0200172
Marc Kupietza96537f2019-11-09 23:07:44 +0100173
Marc Kupietzb956b812019-11-25 17:53:13 +0100174accessTokenServiceName <- "RKorAPClientAccessToken"
Marc Kupietz4862b862019-11-07 10:13:53 +0100175
Marc Kupietza824d502025-05-02 15:40:23 +0200176setGeneric("persistAccessToken", function(kco, ...) standardGeneric("persistAccessToken"))
Marc Kupietz4862b862019-11-07 10:13:53 +0100177
Marc Kupietza4f51d72025-01-25 16:23:18 +0100178#' Persist current access token in keyring
179#'
Marc Kupietza8c40f42025-06-24 15:49:52 +0200180#' @family initialization functions
Marc Kupietza4f51d72025-01-25 16:23:18 +0100181#' @param kco KorAPConnection object
182#' @param accessToken access token to be persisted. If not supplied, the current access token of the KorAPConnection object will be used.
183#' @return KorAPConnection object.
184#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100185#' @aliases persistAccessToken
Marc Kupietza4f51d72025-01-25 16:23:18 +0100186#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100187#' @import keyring
188#' @export
Marc Kupietza4f51d72025-01-25 16:23:18 +0100189#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100190#' @examples
191#' \dontrun{
Marc Kupietza824d502025-05-02 15:40:23 +0200192#' kco <- KorAPConnection(accessToken = "e739u6eOzkwADQPdVChxFg")
Marc Kupietzb956b812019-11-25 17:53:13 +0100193#' persistAccessToken(kco)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100194#'
Marc Kupietza824d502025-05-02 15:40:23 +0200195#' kco <- KorAPConnection() %>%
196#' auth(app_id = "<my application id>") %>%
197#' persistAccessToken()
Marc Kupietz4862b862019-11-07 10:13:53 +0100198#' }
199#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100200#' @seealso [clearAccessToken()], [auth()]
201#'
Marc Kupietza824d502025-05-02 15:40:23 +0200202setMethod("persistAccessToken", "KorAPConnection", function(kco, accessToken = kco@accessToken) {
203 if (!is.null(kco@oauthClient)) {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100204 warning("Short lived access tokens from a confidential application cannot be persisted.")
205 return(kco)
206 }
Marc Kupietza824d502025-05-02 15:40:23 +0200207 if (is.null(accessToken)) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100208 stop("It seems that you have not supplied any access token that could be persisted.", call. = FALSE)
Marc Kupietza824d502025-05-02 15:40:23 +0200209 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100210
Marc Kupietzb956b812019-11-25 17:53:13 +0100211 kco@accessToken <- accessToken
212 key_set_with_value(accessTokenServiceName, kco@KorAPUrl, accessToken)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100213 return(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100214})
215
Marc Kupietza824d502025-05-02 15:40:23 +0200216setGeneric("clearAccessToken", function(kco) standardGeneric("clearAccessToken"))
Marc Kupietz4862b862019-11-07 10:13:53 +0100217
Marc Kupietza4f51d72025-01-25 16:23:18 +0100218#' Clear access token from keyring and KorAPConnection object
219#'
Marc Kupietza8c40f42025-06-24 15:49:52 +0200220#' @family initialization functions
Marc Kupietzb956b812019-11-25 17:53:13 +0100221#' @aliases clearAccessToken
Marc Kupietz4862b862019-11-07 10:13:53 +0100222#' @import keyring
Marc Kupietza4f51d72025-01-25 16:23:18 +0100223#' @param kco KorAPConnection object
224#' @return KorAPConnection object with access token set to `NULL`.
Marc Kupietz4862b862019-11-07 10:13:53 +0100225#' @export
226#' @examples
Marc Kupietza4f51d72025-01-25 16:23:18 +0100227#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100228#' kco <- KorAPConnection()
Marc Kupietza4f51d72025-01-25 16:23:18 +0100229#' kco <- clearAccessToken(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100230#' }
231#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100232#' @seealso [persistAccessToken()]
233#'
Marc Kupietza824d502025-05-02 15:40:23 +0200234setMethod("clearAccessToken", "KorAPConnection", function(kco) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100235 key_delete(accessTokenServiceName, kco@KorAPUrl)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100236 kco@accessToken <- NULL
237 kco
Marc Kupietz4862b862019-11-07 10:13:53 +0100238})
239
Marc Kupietza4f51d72025-01-25 16:23:18 +0100240
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100241oauthRefresh <- function(req, client, scope, kco) {
Marc Kupietza824d502025-05-02 15:40:23 +0200242 httr2::req_oauth_auth_code(req, client,
243 scope = scope,
244 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
245 redirect_uri = kustvakt_redirect_uri,
246 cache_key = kco@KorAPUrl
247 )
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100248}
249
Marc Kupietza824d502025-05-02 15:40:23 +0200250setGeneric("auth", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) standardGeneric("auth"))
Marc Kupietza4f51d72025-01-25 16:23:18 +0100251
252#' Authorize RKorAPClient
253#'
Marc Kupietza8c40f42025-06-24 15:49:52 +0200254#' @family initialization functions
Marc Kupietza4f51d72025-01-25 16:23:18 +0100255#' @aliases auth
256#'
257#' @description
258#' `r lifecycle::badge("experimental")`
259#'
260#' Authorize RKorAPClient to make KorAP queries and download results on behalf of the user.
261#'
262#' @param kco KorAPConnection object
263#' @param app_id OAuth2 application id. Defaults to the generic KorAP client application id.
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100264#' @param app_secret OAuth2 application secret. Used with confidential client applications. Defaults to `NULL`.
Marc Kupietza4f51d72025-01-25 16:23:18 +0100265#' @param scope OAuth2 scope. Defaults to "search match_info".
266#' @return KorAPConnection object with access token set in `@accessToken`.
267#'
268#' @importFrom httr2 oauth_client oauth_flow_auth_code
269#' @examples
270#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100271#' kco <- KorAPConnection(verbose = TRUE) %>% auth()
Marc Kupietza5501652025-01-28 20:25:42 +0100272#' df <- collocationAnalysis(kco, "focus([marmot/p=ADJA] {Ameisenplage})",
Marc Kupietza824d502025-05-02 15:40:23 +0200273#' leftContextSize = 1, rightContextSize = 0
274#' )
Marc Kupietza4f51d72025-01-25 16:23:18 +0100275#' }
276#'
277#' @seealso [persistAccessToken()], [clearAccessToken()]
278#'
279#' @export
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100280setMethod("auth", "KorAPConnection", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) {
Marc Kupietz62b17892025-02-01 18:26:45 +0100281 if (kco@authorizationSupported == FALSE) {
282 log_info(kco@verbose, "Authorization is not supported by this KorAP instance.")
283 return(kco)
284 }
Marc Kupietza824d502025-05-02 15:40:23 +0200285 if (kco@KorAPUrl != "https://korap.ids-mannheim.de/" & app_id == generic_kor_app_id) {
Marc Kupietza4f51d72025-01-25 16:23:18 +0100286 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))
287 return(kco)
288 }
289 if (is.null(kco@accessToken) || is.null(kco@welcome)) { # if access token is not set or invalid
Marc Kupietza824d502025-05-02 15:40:23 +0200290 client <- if (!is.null(kco@oauthClient)) {
291 kco@oauthClient
292 } else {
Marc Kupietza4f51d72025-01-25 16:23:18 +0100293 httr2::oauth_client(
Marc Kupietza824d502025-05-02 15:40:23 +0200294 id = app_id,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100295 secret = app_secret,
Marc Kupietza4f51d72025-01-25 16:23:18 +0100296 token_url = paste0(kco@apiUrl, "oauth2/token")
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100297 )
Marc Kupietza824d502025-05-02 15:40:23 +0200298 }
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100299 if (is.null(app_secret)) {
Marc Kupietza824d502025-05-02 15:40:23 +0200300 kco@accessToken <- (client |>
Marc Kupietza4f51d72025-01-25 16:23:18 +0100301 httr2::oauth_flow_auth_code(
302 scope = scope,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100303 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
Marc Kupietz62b17892025-02-01 18:26:45 +0100304 redirect_uri = kustvakt_redirect_uri
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100305 ))$access_token
306 log_info(kco@verbose, "Client authorized. New access token set.")
307 } else {
308 kco@oauthClient <- client
309 kco@oauthScope <- scope
310 req <- request(kco@apiUrl) |>
311 oauthRefresh(client, scope, kco) |>
312 req_perform()
313 log_info(kco@verbose, "Client authorized. Short lived access token will be refreshed automatically.")
314 }
Marc Kupietza4f51d72025-01-25 16:23:18 +0100315 } else {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100316 log_info(kco@verbose, "Access token already set.")
Marc Kupietza4f51d72025-01-25 16:23:18 +0100317 }
318 return(kco)
319})
320
321
322
Marc Kupietz4862b862019-11-07 10:13:53 +0100323#' @import keyring
Marc Kupietzb956b812019-11-25 17:53:13 +0100324getAccessToken <- function(KorAPUrl) {
Marc Kupietza824d502025-05-02 15:40:23 +0200325 keyList <- tryCatch(
326 withCallingHandlers(key_list(service = accessTokenServiceName),
327 warning = function(w) invokeRestart("muffleWarning"),
328 error = function(e) {
329 return(NULL)
330 }
331 ),
332 error = function(e) { }
333 )
334 if (KorAPUrl %in% keyList$username) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100335 key_get(accessTokenServiceName, KorAPUrl)
Marc Kupietza824d502025-05-02 15:40:23 +0200336 } else {
Marc Kupietzfd9e7492019-11-08 15:45:18 +0100337 NULL
Marc Kupietza824d502025-05-02 15:40:23 +0200338 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100339}
Marc Kupietz0a96b282019-10-01 11:05:31 +0200340
Marc Kupietz581a29b2021-09-04 20:51:04 +0200341
Marc Kupietz62b17892025-02-01 18:26:45 +0100342warnIfNotAuthorized <- function(kco) {
343 if (kco@authorizationSupported & is.null(kco@accessToken) & is.null(kco@oauthClient)) {
Marc Kupietz581a29b2021-09-04 20:51:04 +0200344 warning(
345 paste0(
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100346 "In order to receive KWICSs also from corpora with restricted licenses, you may need to\n",
347 "authorize your application with an access token or the auth() method.\n",
348 "To generate an access token, login to KorAP and navigate to KorAP's OAuth settings <",
Marc Kupietz581a29b2021-09-04 20:51:04 +0200349 kco@KorAPUrl,
350 "settings/oauth#page-top>"
351 )
352 )
353 }
354}
355
Marc Kupietz0a96b282019-10-01 11:05:31 +0200356KorAPCacheSubDir <- function() {
Marc Kupietza824d502025-05-02 15:40:23 +0200357 paste0(
358 "RKorAPClient_",
359 gsub(
360 "^([0-9]+\\.[0-9]+).*",
361 "\\1",
362 packageVersion("RKorAPClient"),
363 perl = TRUE
364 )
365 )
Marc Kupietz0a96b282019-10-01 11:05:31 +0200366}
367
Marc Kupietza824d502025-05-02 15:40:23 +0200368setGeneric("apiCall", function(kco, ...) standardGeneric("apiCall"))
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200369
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200370## quiets concerns of R CMD check re: the .'s that appear in pipelines
Marc Kupietzef1ef4a2025-02-19 12:12:40 +0100371utils::globalVariables(c("."))
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200372
Marc Kupietza8c40f42025-06-24 15:49:52 +0200373#' Internal API call method
374#' @keywords internal
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200375#' @aliases apiCall
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200376#' @param kco KorAPConnection object
377#' @param url request url
Marc Kupietzf9129592025-01-26 19:17:54 +0100378#' @param json logical that determines if JSON result is expected
Marc Kupietzb49afa02020-06-04 15:50:29 +0200379#' @param getHeaders logical that determines if headers and content should be returned (as a list)
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200380#' @importFrom jsonlite fromJSON
Marc Kupietza4675722022-02-23 23:55:15 +0100381#' @importFrom curl has_internet
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100382#' @import httr2
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200383#' @export
Marc Kupietzf9129592025-01-26 19:17:54 +0100384setMethod("apiCall", "KorAPConnection", function(kco, url, json = TRUE, getHeaders = FALSE, cache = kco@cache, timeout = kco@timeout) {
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100385 result <- ""
Marc Kupietzf9129592025-01-26 19:17:54 +0100386
387 # Handle caching if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100388 if (cache) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100389 result <- R.cache::loadCache(dir = KorAPCacheSubDir(), key = list(url, kco@accessToken, kco@indexRevision))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100390 if (!is.null(result)) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100391 if (!is.null(result$meta)) result$meta$cached <- "local"
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100392 return(result)
Marc Kupietz0a96b282019-10-01 11:05:31 +0200393 }
394 }
Marc Kupietza4675722022-02-23 23:55:15 +0100395
Marc Kupietzf9129592025-01-26 19:17:54 +0100396 # Check for internet connection
Marc Kupietza4675722022-02-23 23:55:15 +0100397 if (!curl::has_internet()) {
398 message("No internet connection.")
399 return(invisible(NULL))
400 }
401
Marc Kupietzf9129592025-01-26 19:17:54 +0100402 # Create the request
403 req <- httr2::request(url) |>
404 httr2::req_user_agent(kco@userAgent) |>
405 httr2::req_timeout(timeout)
Marc Kupietza4675722022-02-23 23:55:15 +0100406
Marc Kupietz03402e72025-05-02 15:39:40 +0200407 if (!is.null(kco@oauthClient)) {
408 req <- req |> oauthRefresh(kco@oauthClient, scope = kco@oauthScope, kco)
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100409 } else if (!is.null(kco@accessToken)) {
410 req <- req |> httr2::req_auth_bearer_token(kco@accessToken)
Marc Kupietzf9129592025-01-26 19:17:54 +0100411 }
412
Marc Kupietzd36ee552025-05-02 20:42:50 +0200413 resp <- tryCatch(req |> httr2::req_perform(),
414 error = function(e) {
415 if (is.null(e$resp)) {
416 message(paste("Error: ", e$message, collapse = " "), if ("parent" %in% names(e)) paste0("\n", e$parent$message) else "")
417 return(invisible(NULL))
418 }
419 return(e$resp)
420 }
421 )
Marc Kupietz03402e72025-05-02 15:39:40 +0200422
423 if (is.null(resp)) {
Marc Kupietz03402e72025-05-02 15:39:40 +0200424 return(invisible(NULL))
425 }
Marc Kupietz62b17892025-02-01 18:26:45 +0100426
Marc Kupietzf9129592025-01-26 19:17:54 +0100427 if (resp |> httr2::resp_status() != 200) {
Marc Kupietzd36ee552025-05-02 20:42:50 +0200428 message("Error: Request failed with status ", resp |> httr2::resp_status(), ": ", resp |> httr2::resp_status_desc())
Marc Kupietz62b17892025-02-01 18:26:45 +0100429 if (resp |> httr2::resp_content_type() == "application/json") {
430 result <- tryCatch(
431 resp |> httr2::resp_body_json(),
432 error = function(e) {
433 message("Failed to parse json with error details: ", e$message)
434 return(NULL)
435 }
436 )
437 # Handle errors in the response (if any)
438 if (!is.null(result$errors)) {
439 errors <- result$errors
440 warning_msgs <- if (is.data.frame(errors)) {
441 apply(errors, 1, function(warning) paste(warning[1], ": ", warning[2]))
442 } else {
443 lapply(errors, function(error) paste(error, collapse = " "))
444 }
Marc Kupietz03402e72025-05-02 15:39:40 +0200445 message(paste("Warning: ", warning_msgs, collapse = "\n"))
Marc Kupietzf9129592025-01-26 19:17:54 +0100446 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100447 }
Marc Kupietza4675722022-02-23 23:55:15 +0100448 return(invisible(NULL))
449 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100450
451 # Process JSON response or raw text based on `json` parameter
452 if (json) {
453 content_type <- resp |> httr2::resp_content_type()
454 if (!content_type %in% c("application/json", "application/ld+json")) {
455 message("API did not return JSON")
Marc Kupietza4675722022-02-23 23:55:15 +0100456 return(invisible(NULL))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100457 }
Marc Kupietz04814f22023-04-16 17:13:27 +0200458
Marc Kupietzf9129592025-01-26 19:17:54 +0100459 result <- tryCatch(
460 resp |> httr2::resp_body_string() |> jsonlite::fromJSON(),
461 error = function(e) {
462 message("Failed to parse JSON: ", e$message)
463 return(NULL)
464 }
465 )
466
467 # Handle warnings in the response (if any)
468 if (!is.null(result$warnings)) {
469 warnings <- result$warnings
470 warning_msgs <- if (is.data.frame(warnings)) {
471 apply(warnings, 1, function(warning) paste(warning[1], ": ", warning[2]))
472 } else {
473 lapply(warnings, function(warning) paste(warning, collapse = " "))
474 }
Marc Kupietz03402e72025-05-02 15:39:40 +0200475 message(paste0("\nWarning: ", paste(warning_msgs, collapse = " ")))
476 if (cache & any(grepl("682", warning_msgs))) {
477 cache <- FALSE
Marc Kupietzd36ee552025-05-02 20:42:50 +0200478 log_info(kco@verbose, "Caching will be skipped because of warnings ")
Marc Kupietz03402e72025-05-02 15:39:40 +0200479 }
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100480 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100481 } else {
482 result <- resp |> httr2::resp_body_string()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200483 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100484
485 # Save to cache if enabled
Marc Kupietz03402e72025-05-02 15:39:40 +0200486 if (cache && resp |> httr2::resp_status() == 200) {
Marc Kupietzb49afa02020-06-04 15:50:29 +0200487 R.cache::saveCache(result, key = list(url, kco@accessToken, kco@indexRevision), dir = KorAPCacheSubDir(), compress = TRUE)
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100488 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100489
490 # Return headers and content as a list if `getHeaders` is TRUE
Marc Kupietzb49afa02020-06-04 15:50:29 +0200491 if (getHeaders) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100492 list(headers = resp |> httr2::resp_headers(), content = result)
Marc Kupietzb49afa02020-06-04 15:50:29 +0200493 } else {
494 result
495 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200496})
497
Marc Kupietza824d502025-05-02 15:40:23 +0200498setGeneric("clearCache", function(kco) standardGeneric("clearCache"))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200499
Marc Kupietzdc880ac2025-06-24 20:34:43 +0200500#' Clear local cache
501#'
502#' Clears the local cache of API responses for the current RKorAPClient version.
503#' Useful when you want to force fresh data retrieval or free up disk space.
504#'
505#' @family connection-initialization
506#' @param kco KorAPConnection object
507#' @return Invisible NULL (function called for side effects)
508#' @examples
509#' \dontrun{
510#' kco <- KorAPConnection()
511#' clearCache(kco)
512#' }
Marc Kupietzf9914bb2025-06-25 09:57:55 +0200513#'
Marc Kupietz0a96b282019-10-01 11:05:31 +0200514#' @aliases clearCache
Marc Kupietz0a96b282019-10-01 11:05:31 +0200515#' @export
Marc Kupietza824d502025-05-02 15:40:23 +0200516setMethod("clearCache", "KorAPConnection", function(kco) {
517 R.cache::clearCache(dir = KorAPCacheSubDir())
Marc Kupietz0a96b282019-10-01 11:05:31 +0200518})
519
Marc Kupietza8c40f42025-06-24 15:49:52 +0200520#' Display KorAPConnection object
521#' @keywords internal
Marc Kupietze95108e2019-09-18 13:23:58 +0200522#' @param object KorAPConnection object
523#' @export
524setMethod("show", "KorAPConnection", function(object) {
525 cat("<KorAPConnection>", "\n")
526 cat("apiUrl: ", object@apiUrl, "\n")
527})
528
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200529##' Funtion KorAPConnection()
530##'
Marc Kupietz617266d2025-02-27 10:43:07 +0100531##' Wrappper function for KorAPConnection()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200532##'
533##' @rdname KorAPConnection-constructor
534##' @name KorAPConnection-constructor
535##' @export
Marc Kupietz617266d2025-02-27 10:43:07 +0100536## XKorAPConnection <- function(...) KorAPConnection(...)