blob: f7b6af87bfe508cb2571374f3bb7b03427169ad9 [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
Marc Kupietz39da9dc2025-09-10 13:54:40 +020085#' be verbose. Defaults to FALSE. If not explicitly provided, this can be overridden
86#' via environment variable `KORAP_VERBOSE` (accepted true-ish values: 1, true, yes, on)
87#' or R option `rkorap.verbose` (logical).
Marc Kupietzf9914bb2025-06-25 09:57:55 +020088#' @param cache logical that decides if API calls are cached locally. You can clear
89#' the cache with [clearCache()]. Defaults to TRUE.
90#'
91#' @return [KorAPConnection()] object that can be used e.g. with [corpusQuery()]
92#'
Marc Kupietza8c40f42025-06-24 15:49:52 +020093#' @details
94#' The KorAPConnection object contains various configuration slots for advanced users:
95#' KorAPUrl (server URL), apiVersion, accessToken (OAuth2 token),
96#' timeout (request timeout), verbose (logging), cache (local caching),
97#' and other technical parameters. Most users can ignore these implementation details.
98#'
99#' @family initialization functions
Marc Kupietz0a96b282019-10-01 11:05:31 +0200100#' @import R.cache
Marc Kupietze95108e2019-09-18 13:23:58 +0200101#' @import utils
102#' @import methods
Marc Kupietz6dfeed92025-06-03 11:58:06 +0200103#' @include logging.R
Marc Kupietza81343d2022-09-06 12:32:10 +0200104
Marc Kupietze95108e2019-09-18 13:23:58 +0200105#' @export
Marc Kupietza824d502025-05-02 15:40:23 +0200106KorAPConnection <- 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 +0100107
Marc Kupietza824d502025-05-02 15:40:23 +0200108generic_kor_app_id <- "99FbPHH7RrN36hbndF7b6f"
Marc Kupietz62b17892025-02-01 18:26:45 +0100109
Marc Kupietza824d502025-05-02 15:40:23 +0200110kustvakt_redirect_uri <- "http://localhost:1410/"
111kustvakt_auth_path <- "settings/oauth/authorize"
Marc Kupietz62b17892025-02-01 18:26:45 +0100112
Marc Kupietze95108e2019-09-18 13:23:58 +0200113
Marc Kupietza8c40f42025-06-24 15:49:52 +0200114#' Initialize KorAPConnection object
115#' @keywords internal
Marc Kupietz632cbd42019-09-06 16:04:51 +0200116#' @export
Marc Kupietz36117de2025-06-25 12:46:10 +0200117#'
Marc Kupietzb79fd442025-03-26 10:25:03 +0100118setMethod("initialize", "KorAPConnection", function(.Object,
119 KorAPUrl = if (is.null(Sys.getenv("KORAP_URL")) |
Marc Kupietza824d502025-05-02 15:40:23 +0200120 Sys.getenv("KORAP_URL") == "") {
Marc Kupietzb79fd442025-03-26 10:25:03 +0100121 "https://korap.ids-mannheim.de/"
Marc Kupietza824d502025-05-02 15:40:23 +0200122 } else {
123 Sys.getenv("KORAP_URL")
124 },
125 apiVersion = "v1.0",
Marc Kupietzb79fd442025-03-26 10:25:03 +0100126 apiUrl,
127 accessToken = getAccessToken(KorAPUrl),
128 oauthClient = NULL,
129 oauthScope = "search match_info",
130 authorizationSupported = TRUE,
131 userAgent = "R-KorAP-Client",
132 timeout = 240,
133 verbose = FALSE,
134 cache = TRUE) {
135 .Object <- callNextMethod()
136 m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
137 .Object@KorAPUrl <- regmatches(KorAPUrl, m)
Marc Kupietza824d502025-05-02 15:40:23 +0200138 if (!endsWith(.Object@KorAPUrl, "/")) {
Marc Kupietzb79fd442025-03-26 10:25:03 +0100139 .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
140 }
141 if (missing(apiUrl)) {
Marc Kupietza824d502025-05-02 15:40:23 +0200142 .Object@apiUrl <- paste0(.Object@KorAPUrl, "api/", apiVersion, "/")
143 } else {
144 .Object@apiUrl <- apiUrl
145 }
146 .Object@accessToken <- accessToken
147 .Object@oauthClient <- oauthClient
148 .Object@apiVersion <- apiVersion
149 .Object@userAgent <- userAgent
150 .Object@oauthScope <- oauthScope
151 .Object@authorizationSupported <- authorizationSupported
152 .Object@timeout <- timeout
Marc Kupietz39da9dc2025-09-10 13:54:40 +0200153 # Allow environment/option override only if user did not pass `verbose`
154 if (missing(verbose)) {
155 ev <- Sys.getenv("KORAP_VERBOSE", unset = "")
156 if (nzchar(ev)) {
157 verbose <- tolower(ev) %in% c("1", "true", "t", "yes", "y", "on")
158 } else {
159 opt <- getOption("rkorap.verbose", NULL)
160 if (!is.null(opt)) verbose <- isTRUE(opt)
161 }
162 }
Marc Kupietza824d502025-05-02 15:40:23 +0200163 .Object@verbose <- verbose
164 .Object@cache <- cache
165 .Object@welcome <- apiCall(.Object, .Object@apiUrl, json = FALSE, cache = FALSE, getHeaders = TRUE)
166 if (!is.null(.Object@welcome)) {
167 message(.Object@welcome[[2]])
168 resp <- httr2::request(.Object@KorAPUrl) |>
169 httr2::req_url_path_append(kustvakt_auth_path) |>
170 httr2::req_error(is_error = \(resp) FALSE) |>
171 httr2::req_perform()
172 .Object@authorizationSupported <- (httr2::resp_status(resp) == 200)
Marc Kupietz62b17892025-02-01 18:26:45 +0100173
Marc Kupietza824d502025-05-02 15:40:23 +0200174 .Object@indexRevision <- .Object@welcome[[1]][["x-index-revision"]]
175 } else {
176 if (grepl(.Object@KorAPUrl, .Object@apiUrl)) {
177 message("Could not connect to KorAP instance ", .Object@KorAPUrl)
178 } else {
179 message("Could not connect to KorAP API at ", .Object@apiUrl)
180 }
181 }
182 .Object
183})
Marc Kupietze95108e2019-09-18 13:23:58 +0200184
Marc Kupietza96537f2019-11-09 23:07:44 +0100185
Marc Kupietzb956b812019-11-25 17:53:13 +0100186accessTokenServiceName <- "RKorAPClientAccessToken"
Marc Kupietz4862b862019-11-07 10:13:53 +0100187
Marc Kupietza824d502025-05-02 15:40:23 +0200188setGeneric("persistAccessToken", function(kco, ...) standardGeneric("persistAccessToken"))
Marc Kupietz4862b862019-11-07 10:13:53 +0100189
Marc Kupietza4f51d72025-01-25 16:23:18 +0100190#' Persist current access token in keyring
191#'
Marc Kupietza8c40f42025-06-24 15:49:52 +0200192#' @family initialization functions
Marc Kupietza4f51d72025-01-25 16:23:18 +0100193#' @param kco KorAPConnection object
194#' @param accessToken access token to be persisted. If not supplied, the current access token of the KorAPConnection object will be used.
195#' @return KorAPConnection object.
196#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100197#' @aliases persistAccessToken
Marc Kupietza4f51d72025-01-25 16:23:18 +0100198#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100199#' @import keyring
200#' @export
Marc Kupietza4f51d72025-01-25 16:23:18 +0100201#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100202#' @examples
203#' \dontrun{
Marc Kupietza824d502025-05-02 15:40:23 +0200204#' kco <- KorAPConnection(accessToken = "e739u6eOzkwADQPdVChxFg")
Marc Kupietzb956b812019-11-25 17:53:13 +0100205#' persistAccessToken(kco)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100206#'
Marc Kupietza824d502025-05-02 15:40:23 +0200207#' kco <- KorAPConnection() %>%
208#' auth(app_id = "<my application id>") %>%
209#' persistAccessToken()
Marc Kupietz4862b862019-11-07 10:13:53 +0100210#' }
211#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100212#' @seealso [clearAccessToken()], [auth()]
213#'
Marc Kupietza824d502025-05-02 15:40:23 +0200214setMethod("persistAccessToken", "KorAPConnection", function(kco, accessToken = kco@accessToken) {
215 if (!is.null(kco@oauthClient)) {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100216 warning("Short lived access tokens from a confidential application cannot be persisted.")
217 return(kco)
218 }
Marc Kupietza824d502025-05-02 15:40:23 +0200219 if (is.null(accessToken)) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100220 stop("It seems that you have not supplied any access token that could be persisted.", call. = FALSE)
Marc Kupietza824d502025-05-02 15:40:23 +0200221 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100222
Marc Kupietzb956b812019-11-25 17:53:13 +0100223 kco@accessToken <- accessToken
224 key_set_with_value(accessTokenServiceName, kco@KorAPUrl, accessToken)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100225 return(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100226})
227
Marc Kupietza824d502025-05-02 15:40:23 +0200228setGeneric("clearAccessToken", function(kco) standardGeneric("clearAccessToken"))
Marc Kupietz4862b862019-11-07 10:13:53 +0100229
Marc Kupietza4f51d72025-01-25 16:23:18 +0100230#' Clear access token from keyring and KorAPConnection object
231#'
Marc Kupietza8c40f42025-06-24 15:49:52 +0200232#' @family initialization functions
Marc Kupietzb956b812019-11-25 17:53:13 +0100233#' @aliases clearAccessToken
Marc Kupietz4862b862019-11-07 10:13:53 +0100234#' @import keyring
Marc Kupietza4f51d72025-01-25 16:23:18 +0100235#' @param kco KorAPConnection object
236#' @return KorAPConnection object with access token set to `NULL`.
Marc Kupietz4862b862019-11-07 10:13:53 +0100237#' @export
238#' @examples
Marc Kupietza4f51d72025-01-25 16:23:18 +0100239#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100240#' kco <- KorAPConnection()
Marc Kupietza4f51d72025-01-25 16:23:18 +0100241#' kco <- clearAccessToken(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100242#' }
243#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100244#' @seealso [persistAccessToken()]
245#'
Marc Kupietza824d502025-05-02 15:40:23 +0200246setMethod("clearAccessToken", "KorAPConnection", function(kco) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100247 key_delete(accessTokenServiceName, kco@KorAPUrl)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100248 kco@accessToken <- NULL
249 kco
Marc Kupietz4862b862019-11-07 10:13:53 +0100250})
251
Marc Kupietza4f51d72025-01-25 16:23:18 +0100252
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100253oauthRefresh <- function(req, client, scope, kco) {
Marc Kupietza824d502025-05-02 15:40:23 +0200254 httr2::req_oauth_auth_code(req, client,
255 scope = scope,
256 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
257 redirect_uri = kustvakt_redirect_uri,
258 cache_key = kco@KorAPUrl
259 )
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100260}
261
Marc Kupietza824d502025-05-02 15:40:23 +0200262setGeneric("auth", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) standardGeneric("auth"))
Marc Kupietza4f51d72025-01-25 16:23:18 +0100263
264#' Authorize RKorAPClient
265#'
Marc Kupietza8c40f42025-06-24 15:49:52 +0200266#' @family initialization functions
Marc Kupietza4f51d72025-01-25 16:23:18 +0100267#' @aliases auth
268#'
269#' @description
Marc Kupietza4f51d72025-01-25 16:23:18 +0100270#'
271#' Authorize RKorAPClient to make KorAP queries and download results on behalf of the user.
272#'
273#' @param kco KorAPConnection object
274#' @param app_id OAuth2 application id. Defaults to the generic KorAP client application id.
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100275#' @param app_secret OAuth2 application secret. Used with confidential client applications. Defaults to `NULL`.
Marc Kupietza4f51d72025-01-25 16:23:18 +0100276#' @param scope OAuth2 scope. Defaults to "search match_info".
277#' @return KorAPConnection object with access token set in `@accessToken`.
278#'
279#' @importFrom httr2 oauth_client oauth_flow_auth_code
280#' @examples
281#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100282#' kco <- KorAPConnection(verbose = TRUE) %>% auth()
Marc Kupietza5501652025-01-28 20:25:42 +0100283#' df <- collocationAnalysis(kco, "focus([marmot/p=ADJA] {Ameisenplage})",
Marc Kupietza824d502025-05-02 15:40:23 +0200284#' leftContextSize = 1, rightContextSize = 0
285#' )
Marc Kupietza4f51d72025-01-25 16:23:18 +0100286#' }
287#'
288#' @seealso [persistAccessToken()], [clearAccessToken()]
289#'
290#' @export
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100291setMethod("auth", "KorAPConnection", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) {
Marc Kupietz62b17892025-02-01 18:26:45 +0100292 if (kco@authorizationSupported == FALSE) {
293 log_info(kco@verbose, "Authorization is not supported by this KorAP instance.")
294 return(kco)
295 }
Marc Kupietza824d502025-05-02 15:40:23 +0200296 if (kco@KorAPUrl != "https://korap.ids-mannheim.de/" & app_id == generic_kor_app_id) {
Marc Kupietza4f51d72025-01-25 16:23:18 +0100297 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))
298 return(kco)
299 }
300 if (is.null(kco@accessToken) || is.null(kco@welcome)) { # if access token is not set or invalid
Marc Kupietza824d502025-05-02 15:40:23 +0200301 client <- if (!is.null(kco@oauthClient)) {
302 kco@oauthClient
303 } else {
Marc Kupietza4f51d72025-01-25 16:23:18 +0100304 httr2::oauth_client(
Marc Kupietza824d502025-05-02 15:40:23 +0200305 id = app_id,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100306 secret = app_secret,
Marc Kupietza4f51d72025-01-25 16:23:18 +0100307 token_url = paste0(kco@apiUrl, "oauth2/token")
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100308 )
Marc Kupietza824d502025-05-02 15:40:23 +0200309 }
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100310 if (is.null(app_secret)) {
Marc Kupietza824d502025-05-02 15:40:23 +0200311 kco@accessToken <- (client |>
Marc Kupietza4f51d72025-01-25 16:23:18 +0100312 httr2::oauth_flow_auth_code(
313 scope = scope,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100314 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
Marc Kupietz62b17892025-02-01 18:26:45 +0100315 redirect_uri = kustvakt_redirect_uri
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100316 ))$access_token
317 log_info(kco@verbose, "Client authorized. New access token set.")
318 } else {
319 kco@oauthClient <- client
320 kco@oauthScope <- scope
321 req <- request(kco@apiUrl) |>
322 oauthRefresh(client, scope, kco) |>
323 req_perform()
324 log_info(kco@verbose, "Client authorized. Short lived access token will be refreshed automatically.")
325 }
Marc Kupietza4f51d72025-01-25 16:23:18 +0100326 } else {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100327 log_info(kco@verbose, "Access token already set.")
Marc Kupietza4f51d72025-01-25 16:23:18 +0100328 }
329 return(kco)
330})
331
332
333
Marc Kupietz4862b862019-11-07 10:13:53 +0100334#' @import keyring
Marc Kupietzb956b812019-11-25 17:53:13 +0100335getAccessToken <- function(KorAPUrl) {
Marc Kupietza824d502025-05-02 15:40:23 +0200336 keyList <- tryCatch(
337 withCallingHandlers(key_list(service = accessTokenServiceName),
338 warning = function(w) invokeRestart("muffleWarning"),
339 error = function(e) {
340 return(NULL)
341 }
342 ),
343 error = function(e) { }
344 )
345 if (KorAPUrl %in% keyList$username) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100346 key_get(accessTokenServiceName, KorAPUrl)
Marc Kupietza824d502025-05-02 15:40:23 +0200347 } else {
Marc Kupietzfd9e7492019-11-08 15:45:18 +0100348 NULL
Marc Kupietza824d502025-05-02 15:40:23 +0200349 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100350}
Marc Kupietz0a96b282019-10-01 11:05:31 +0200351
Marc Kupietz581a29b2021-09-04 20:51:04 +0200352
Marc Kupietz62b17892025-02-01 18:26:45 +0100353warnIfNotAuthorized <- function(kco) {
354 if (kco@authorizationSupported & is.null(kco@accessToken) & is.null(kco@oauthClient)) {
Marc Kupietz581a29b2021-09-04 20:51:04 +0200355 warning(
356 paste0(
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100357 "In order to receive KWICSs also from corpora with restricted licenses, you may need to\n",
358 "authorize your application with an access token or the auth() method.\n",
359 "To generate an access token, login to KorAP and navigate to KorAP's OAuth settings <",
Marc Kupietz581a29b2021-09-04 20:51:04 +0200360 kco@KorAPUrl,
361 "settings/oauth#page-top>"
362 )
363 )
364 }
365}
366
Marc Kupietz0a96b282019-10-01 11:05:31 +0200367KorAPCacheSubDir <- function() {
Marc Kupietza824d502025-05-02 15:40:23 +0200368 paste0(
369 "RKorAPClient_",
370 gsub(
371 "^([0-9]+\\.[0-9]+).*",
372 "\\1",
373 packageVersion("RKorAPClient"),
374 perl = TRUE
375 )
376 )
Marc Kupietz0a96b282019-10-01 11:05:31 +0200377}
378
Marc Kupietza824d502025-05-02 15:40:23 +0200379setGeneric("apiCall", function(kco, ...) standardGeneric("apiCall"))
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200380
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200381## quiets concerns of R CMD check re: the .'s that appear in pipelines
Marc Kupietzef1ef4a2025-02-19 12:12:40 +0100382utils::globalVariables(c("."))
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200383
Marc Kupietza8c40f42025-06-24 15:49:52 +0200384#' Internal API call method
385#' @keywords internal
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200386#' @aliases apiCall
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200387#' @param kco KorAPConnection object
388#' @param url request url
Marc Kupietzf9129592025-01-26 19:17:54 +0100389#' @param json logical that determines if JSON result is expected
Marc Kupietzb49afa02020-06-04 15:50:29 +0200390#' @param getHeaders logical that determines if headers and content should be returned (as a list)
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200391#' @importFrom jsonlite fromJSON
Marc Kupietza4675722022-02-23 23:55:15 +0100392#' @importFrom curl has_internet
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100393#' @import httr2
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200394#' @export
Marc Kupietzf9129592025-01-26 19:17:54 +0100395setMethod("apiCall", "KorAPConnection", function(kco, url, json = TRUE, getHeaders = FALSE, cache = kco@cache, timeout = kco@timeout) {
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100396 result <- ""
Marc Kupietzf9129592025-01-26 19:17:54 +0100397
398 # Handle caching if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100399 if (cache) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100400 result <- R.cache::loadCache(dir = KorAPCacheSubDir(), key = list(url, kco@accessToken, kco@indexRevision))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100401 if (!is.null(result)) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100402 if (!is.null(result$meta)) result$meta$cached <- "local"
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100403 return(result)
Marc Kupietz0a96b282019-10-01 11:05:31 +0200404 }
405 }
Marc Kupietza4675722022-02-23 23:55:15 +0100406
Marc Kupietzf9129592025-01-26 19:17:54 +0100407 # Check for internet connection
Marc Kupietza4675722022-02-23 23:55:15 +0100408 if (!curl::has_internet()) {
409 message("No internet connection.")
410 return(invisible(NULL))
411 }
412
Marc Kupietzf9129592025-01-26 19:17:54 +0100413 # Create the request
414 req <- httr2::request(url) |>
415 httr2::req_user_agent(kco@userAgent) |>
416 httr2::req_timeout(timeout)
Marc Kupietza4675722022-02-23 23:55:15 +0100417
Marc Kupietz03402e72025-05-02 15:39:40 +0200418 if (!is.null(kco@oauthClient)) {
419 req <- req |> oauthRefresh(kco@oauthClient, scope = kco@oauthScope, kco)
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100420 } else if (!is.null(kco@accessToken)) {
421 req <- req |> httr2::req_auth_bearer_token(kco@accessToken)
Marc Kupietzf9129592025-01-26 19:17:54 +0100422 }
423
Marc Kupietzd36ee552025-05-02 20:42:50 +0200424 resp <- tryCatch(req |> httr2::req_perform(),
425 error = function(e) {
426 if (is.null(e$resp)) {
427 message(paste("Error: ", e$message, collapse = " "), if ("parent" %in% names(e)) paste0("\n", e$parent$message) else "")
428 return(invisible(NULL))
429 }
430 return(e$resp)
431 }
432 )
Marc Kupietz03402e72025-05-02 15:39:40 +0200433
434 if (is.null(resp)) {
Marc Kupietz03402e72025-05-02 15:39:40 +0200435 return(invisible(NULL))
436 }
Marc Kupietz62b17892025-02-01 18:26:45 +0100437
Marc Kupietzf9129592025-01-26 19:17:54 +0100438 if (resp |> httr2::resp_status() != 200) {
Marc Kupietzd36ee552025-05-02 20:42:50 +0200439 message("Error: Request failed with status ", resp |> httr2::resp_status(), ": ", resp |> httr2::resp_status_desc())
Marc Kupietz62b17892025-02-01 18:26:45 +0100440 if (resp |> httr2::resp_content_type() == "application/json") {
441 result <- tryCatch(
442 resp |> httr2::resp_body_json(),
443 error = function(e) {
444 message("Failed to parse json with error details: ", e$message)
445 return(NULL)
446 }
447 )
448 # Handle errors in the response (if any)
449 if (!is.null(result$errors)) {
450 errors <- result$errors
451 warning_msgs <- if (is.data.frame(errors)) {
452 apply(errors, 1, function(warning) paste(warning[1], ": ", warning[2]))
453 } else {
454 lapply(errors, function(error) paste(error, collapse = " "))
455 }
Marc Kupietz03402e72025-05-02 15:39:40 +0200456 message(paste("Warning: ", warning_msgs, collapse = "\n"))
Marc Kupietzf9129592025-01-26 19:17:54 +0100457 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100458 }
Marc Kupietza4675722022-02-23 23:55:15 +0100459 return(invisible(NULL))
460 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100461
462 # Process JSON response or raw text based on `json` parameter
463 if (json) {
464 content_type <- resp |> httr2::resp_content_type()
465 if (!content_type %in% c("application/json", "application/ld+json")) {
466 message("API did not return JSON")
Marc Kupietza4675722022-02-23 23:55:15 +0100467 return(invisible(NULL))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100468 }
Marc Kupietz04814f22023-04-16 17:13:27 +0200469
Marc Kupietzf9129592025-01-26 19:17:54 +0100470 result <- tryCatch(
471 resp |> httr2::resp_body_string() |> jsonlite::fromJSON(),
472 error = function(e) {
473 message("Failed to parse JSON: ", e$message)
474 return(NULL)
475 }
476 )
477
478 # Handle warnings in the response (if any)
479 if (!is.null(result$warnings)) {
480 warnings <- result$warnings
481 warning_msgs <- if (is.data.frame(warnings)) {
482 apply(warnings, 1, function(warning) paste(warning[1], ": ", warning[2]))
483 } else {
484 lapply(warnings, function(warning) paste(warning, collapse = " "))
485 }
Marc Kupietz03402e72025-05-02 15:39:40 +0200486 message(paste0("\nWarning: ", paste(warning_msgs, collapse = " ")))
487 if (cache & any(grepl("682", warning_msgs))) {
488 cache <- FALSE
Marc Kupietzd36ee552025-05-02 20:42:50 +0200489 log_info(kco@verbose, "Caching will be skipped because of warnings ")
Marc Kupietz03402e72025-05-02 15:39:40 +0200490 }
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100491 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100492 } else {
493 result <- resp |> httr2::resp_body_string()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200494 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100495
496 # Save to cache if enabled
Marc Kupietz03402e72025-05-02 15:39:40 +0200497 if (cache && resp |> httr2::resp_status() == 200) {
Marc Kupietzb49afa02020-06-04 15:50:29 +0200498 R.cache::saveCache(result, key = list(url, kco@accessToken, kco@indexRevision), dir = KorAPCacheSubDir(), compress = TRUE)
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100499 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100500
501 # Return headers and content as a list if `getHeaders` is TRUE
Marc Kupietzb49afa02020-06-04 15:50:29 +0200502 if (getHeaders) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100503 list(headers = resp |> httr2::resp_headers(), content = result)
Marc Kupietzb49afa02020-06-04 15:50:29 +0200504 } else {
505 result
506 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200507})
508
Marc Kupietza824d502025-05-02 15:40:23 +0200509setGeneric("clearCache", function(kco) standardGeneric("clearCache"))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200510
Marc Kupietzdc880ac2025-06-24 20:34:43 +0200511#' Clear local cache
512#'
513#' Clears the local cache of API responses for the current RKorAPClient version.
514#' Useful when you want to force fresh data retrieval or free up disk space.
515#'
516#' @family connection-initialization
517#' @param kco KorAPConnection object
518#' @return Invisible NULL (function called for side effects)
519#' @examples
520#' \dontrun{
521#' kco <- KorAPConnection()
522#' clearCache(kco)
523#' }
Marc Kupietzf9914bb2025-06-25 09:57:55 +0200524#'
Marc Kupietz0a96b282019-10-01 11:05:31 +0200525#' @aliases clearCache
Marc Kupietz0a96b282019-10-01 11:05:31 +0200526#' @export
Marc Kupietza824d502025-05-02 15:40:23 +0200527setMethod("clearCache", "KorAPConnection", function(kco) {
528 R.cache::clearCache(dir = KorAPCacheSubDir())
Marc Kupietz0a96b282019-10-01 11:05:31 +0200529})
530
Marc Kupietza8c40f42025-06-24 15:49:52 +0200531#' Display KorAPConnection object
532#' @keywords internal
Marc Kupietze95108e2019-09-18 13:23:58 +0200533#' @param object KorAPConnection object
534#' @export
535setMethod("show", "KorAPConnection", function(object) {
536 cat("<KorAPConnection>", "\n")
537 cat("apiUrl: ", object@apiUrl, "\n")
538})
539
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200540##' Funtion KorAPConnection()
541##'
Marc Kupietz617266d2025-02-27 10:43:07 +0100542##' Wrappper function for KorAPConnection()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200543##'
544##' @rdname KorAPConnection-constructor
545##' @name KorAPConnection-constructor
546##' @export
Marc Kupietz617266d2025-02-27 10:43:07 +0100547## XKorAPConnection <- function(...) KorAPConnection(...)