blob: 5507ce7697a773d5ab1df58f06580a4cb4c2110e [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 Kupietze95108e2019-09-18 13:23:58 +02008#' Class KorAPConnection
Marc Kupietz25aebc32019-09-16 18:40:50 +02009#'
Marc Kupietz67edcb52021-09-20 21:54:24 +020010#' `KorAPConnection` objects represent the connection to a KorAP server.
Marc Kupietz617266d2025-02-27 10:43:07 +010011#' New `KorAPConnection` objects can be created by `KorAPConnection()`.
Marc Kupietze95108e2019-09-18 13:23:58 +020012#'
Marc Kupietz0a96b282019-10-01 11:05:31 +020013#' @import R.cache
Marc Kupietze95108e2019-09-18 13:23:58 +020014#' @import utils
15#' @import methods
Marc Kupietza81343d2022-09-06 12:32:10 +020016#' @slot KorAPUrl URL of the web user interface of the KorAP server used in the connection.
17#' @slot apiVersion requested KorAP API version.
18#' @slot indexRevision indexRevision code as reported from API via `X-Index-Revision` HTTP header.
19#' @slot apiUrl full URL of API including version.
20#' @slot accessToken OAuth2 access token.
Marc Kupietzf83d59a2025-02-01 14:48:30 +010021#' @slot oauthClient OAuth2 client object.
22#' @slot oauthScope OAuth2 scope.
Marc Kupietz62b17892025-02-01 18:26:45 +010023#' @slot authorizationSupported logical that indicates if authorization is supported/necessary for the current KorAP instance. Automatically set during initialization.
Marc Kupietza81343d2022-09-06 12:32:10 +020024#' @slot userAgent user agent string used for connection the API.
Marc Kupietz471d90a2025-02-01 18:26:12 +010025#' @slot timeout timeout in seconds for API requests (this does not influence server internal timeouts)
Marc Kupietza81343d2022-09-06 12:32:10 +020026#' @slot verbose logical that decides whether operations will default to be verbose.
27#' @slot cache logical that decides if API calls are cached locally.
28#' @slot welcome list containing HTTP response received from KorAP server welcome function.
29
Marc Kupietze95108e2019-09-18 13:23:58 +020030#' @export
Marc Kupietz62b17892025-02-01 18:26:45 +010031KorAPConnection <- 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"))
32
33generic_kor_app_id = "99FbPHH7RrN36hbndF7b6f"
34
35kustvakt_redirect_uri = "http://localhost:1410/"
36kustvakt_auth_path = "settings/oauth/authorize"
37
Marc Kupietze95108e2019-09-18 13:23:58 +020038
39#' @param .Object KorAPConnection object
Marc Kupietza81343d2022-09-06 12:32:10 +020040#' @param KorAPUrl URL of the web user interface of the KorAP server instance you want to access.
Marc Kupietzb79fd442025-03-26 10:25:03 +010041#' Defaults to the environment variable `KORAP_URL` if set and to the IDS Mannheim KorAP main instance
42#' to query DeReKo, otherwise.
Marc Kupietze95108e2019-09-18 13:23:58 +020043#' @param apiVersion which version of KorAP's API you want to connect to.
44#' @param apiUrl URL of the KorAP web service.
Marc Kupietz132f0052023-04-16 14:23:05 +020045#' @param accessToken OAuth2 access token. For queries on corpus parts with restricted
46#' access (e.g. textual queries on IPR protected data), you need to authorize
47#' your application with an access token.
Marc Kupietz62b17892025-02-01 18:26:45 +010048#' You can obtain an access token in the OAuth settings of your KorAP web interface.
Marc Kupietza4f51d72025-01-25 16:23:18 +010049#'
50#' More details are explained in the
Marc Kupietz132f0052023-04-16 14:23:05 +020051#' [authorization section](https://github.com/KorAP/RKorAPClient#authorization)
52#' of the RKorAPClient Readme on GitHub.
53#'
54#' To use authorization based on an access token
55#' in subsequent queries, initialize your KorAP connection with:
56#'
57#' ```
Marc Kupietz617266d2025-02-27 10:43:07 +010058#' kco <- KorAPConnection(accessToken="<access token>")
Marc Kupietz132f0052023-04-16 14:23:05 +020059#' ```
60#'
Marc Kupietz4862b862019-11-07 10:13:53 +010061#' In order to make the API
Marc Kupietz67edcb52021-09-20 21:54:24 +020062#' token persistent for the currently used `KorAPUrl` (you can have one
Marc Kupietz132f0052023-04-16 14:23:05 +020063#' token per KorAPUrl / KorAP server instance), use:
64#'
65#' ```
66#' persistAccessToken(kco)
67#' ```
68#'
69#' This will store it in your keyring using the
Marc Kupietz617266d2025-02-27 10:43:07 +010070#' [keyring::keyring-package]. Subsequent KorAPConnection() calls will
Marc Kupietz4862b862019-11-07 10:13:53 +010071#' then automatically retrieve the token from your keying. To stop using a
Marc Kupietz67edcb52021-09-20 21:54:24 +020072#' persisted token, call `clearAccessToken(kco)`. Please note that for
Marc Kupietz4862b862019-11-07 10:13:53 +010073#' DeReKo, authorized queries will behave differently inside and outside the
74#' IDS, because of the special license situation. This concerns also cached
75#' results which do not take into account from where a request was issued. If
Marc Kupietz67edcb52021-09-20 21:54:24 +020076#' you experience problems or unexpected results, please try `kco <-
Marc Kupietz617266d2025-02-27 10:43:07 +010077#' KorAPConnection(cache=FALSE)` or use
Marc Kupietz67edcb52021-09-20 21:54:24 +020078#' [clearCache()] to clear the cache completely.
Marc Kupietz132f0052023-04-16 14:23:05 +020079#'
Marc Kupietzf83d59a2025-02-01 14:48:30 +010080#' An alternative to using an access token is to use a browser-based oauth2 workflow
81#' to obtain an access token. This can be done with the [auth()] method.
82#'
83#' @param oauthClient OAuth2 client object.
84#' @param oauthScope OAuth2 scope.
Marc Kupietz62b17892025-02-01 18:26:45 +010085#' @param authorizationSupported logical that indicates if authorization is supported/necessary for the current KorAP instance. Automatically set during initialization.
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +020086#' @param userAgent user agent string.
Marc Kupietza81343d2022-09-06 12:32:10 +020087#' @param timeout tineout in seconds for API requests (this does not influence server internal timeouts).
88#' @param verbose logical that decides whether following operations will default to
Marc Kupietz4862b862019-11-07 10:13:53 +010089#' be verbose.
Marc Kupietza81343d2022-09-06 12:32:10 +020090#' @param cache logical that decides if API calls are cached locally. You can clear
Marc Kupietz67edcb52021-09-20 21:54:24 +020091#' the cache with [clearCache()].
92#' @return [KorAPConnection()] object that can be used e.g. with
93#' [corpusQuery()]
Marc Kupietze95108e2019-09-18 13:23:58 +020094#'
Marc Kupietzf83d59a2025-02-01 14:48:30 +010095#' @import httr2
Marc Kupietze95108e2019-09-18 13:23:58 +020096#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +020097#' \dontrun{
98#'
Marc Kupietz617266d2025-02-27 10:43:07 +010099#' kcon <- KorAPConnection(verbose = TRUE)
Marc Kupietze95108e2019-09-18 13:23:58 +0200100#' kq <- corpusQuery(kcon, "Ameisenplage")
Marc Kupietz5a519822019-09-20 21:43:52 +0200101#' kq <- fetchAll(kq)
Marc Kupietz05b22772020-02-18 21:58:42 +0100102#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +0200103#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100104#' \dontrun{
Marc Kupietz6ae76052021-09-21 10:34:00 +0200105#'
Marc Kupietz617266d2025-02-27 10:43:07 +0100106#' kcon <- KorAPConnection(verbose = TRUE, accessToken="e739u6eOzkwADQPdVChxFg")
Marc Kupietz4862b862019-11-07 10:13:53 +0100107#' kq <- corpusQuery(kcon, "Ameisenplage", metadataOnly=FALSE)
108#' kq <- fetchAll(kq)
109#' kq@collectedMatches$snippet
110#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +0200111#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200112#' @rdname KorAPConnection-class
Marc Kupietzb79fd442025-03-26 10:25:03 +0100113
Marc Kupietz632cbd42019-09-06 16:04:51 +0200114#' @export
Marc Kupietzb79fd442025-03-26 10:25:03 +0100115setMethod("initialize", "KorAPConnection", function(.Object,
116 KorAPUrl = if (is.null(Sys.getenv("KORAP_URL")) |
117 Sys.getenv("KORAP_URL") == "")
118 "https://korap.ids-mannheim.de/"
119 else
120 Sys.getenv("KORAP_URL"),
121 apiVersion = 'v1.0',
122 apiUrl,
123 accessToken = getAccessToken(KorAPUrl),
124 oauthClient = NULL,
125 oauthScope = "search match_info",
126 authorizationSupported = TRUE,
127 userAgent = "R-KorAP-Client",
128 timeout = 240,
129 verbose = FALSE,
130 cache = TRUE) {
131 .Object <- callNextMethod()
132 m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
133 .Object@KorAPUrl <- regmatches(KorAPUrl, m)
134 if (!endsWith(.Object@KorAPUrl, '/')) {
135 .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
136 }
137 if (missing(apiUrl)) {
Marc Kupietze95108e2019-09-18 13:23:58 +0200138 .Object@apiUrl = paste0(.Object@KorAPUrl, 'api/', apiVersion, '/')
139 } else {
140 .Object@apiUrl = apiUrl
141 }
Marc Kupietzb956b812019-11-25 17:53:13 +0100142 .Object@accessToken = accessToken
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100143 .Object@oauthClient = oauthClient
Marc Kupietze95108e2019-09-18 13:23:58 +0200144 .Object@apiVersion = apiVersion
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200145 .Object@userAgent = userAgent
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100146 .Object@oauthScope = oauthScope
Marc Kupietz62b17892025-02-01 18:26:45 +0100147 .Object@authorizationSupported = authorizationSupported
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200148 .Object@timeout = timeout
Marc Kupietz5a519822019-09-20 21:43:52 +0200149 .Object@verbose = verbose
Marc Kupietz0a96b282019-10-01 11:05:31 +0200150 .Object@cache = cache
Marc Kupietza4675722022-02-23 23:55:15 +0100151 .Object@welcome = apiCall(.Object, .Object@apiUrl, json = FALSE, cache = FALSE, getHeaders = TRUE)
152 if (!is.null(.Object@welcome)) {
153 message(.Object@welcome[[2]])
Marc Kupietz62b17892025-02-01 18:26:45 +0100154 resp <- httr2::request(.Object@KorAPUrl) |>
155 httr2::req_url_path_append(kustvakt_auth_path) |>
156 httr2::req_error(is_error = \(resp) FALSE) |>
157 httr2::req_perform()
158 .Object@authorizationSupported = (httr2::resp_status(resp) == 200)
159
160 .Object@indexRevision <- .Object@welcome[[1]][["x-index-revision"]]
161 } else {
Marc Kupietz1b530472025-02-04 10:46:49 +0100162 if (grepl(.Object@KorAPUrl, .Object@apiUrl)) {
163 message("Could not connect to KorAP instance ", .Object@KorAPUrl)
164 } else {
165 message("Could not connect to KorAP API at ", .Object@apiUrl)
166 }
Marc Kupietza4675722022-02-23 23:55:15 +0100167 }
Marc Kupietze95108e2019-09-18 13:23:58 +0200168 .Object
169 })
170
Marc Kupietza96537f2019-11-09 23:07:44 +0100171
Marc Kupietzb956b812019-11-25 17:53:13 +0100172accessTokenServiceName <- "RKorAPClientAccessToken"
Marc Kupietz4862b862019-11-07 10:13:53 +0100173
Marc Kupietzb956b812019-11-25 17:53:13 +0100174setGeneric("persistAccessToken", function(kco, ...) standardGeneric("persistAccessToken") )
Marc Kupietz4862b862019-11-07 10:13:53 +0100175
Marc Kupietza4f51d72025-01-25 16:23:18 +0100176#' Persist current access token in keyring
177#'
178#' @param kco KorAPConnection object
179#' @param accessToken access token to be persisted. If not supplied, the current access token of the KorAPConnection object will be used.
180#' @return KorAPConnection object.
181#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100182#' @aliases persistAccessToken
Marc Kupietza4f51d72025-01-25 16:23:18 +0100183#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100184#' @import keyring
185#' @export
Marc Kupietza4f51d72025-01-25 16:23:18 +0100186#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100187#' @examples
188#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100189#' kco <- KorAPConnection(accessToken="e739u6eOzkwADQPdVChxFg")
Marc Kupietzb956b812019-11-25 17:53:13 +0100190#' persistAccessToken(kco)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100191#'
Marc Kupietz617266d2025-02-27 10:43:07 +0100192#' kco <- KorAPConnection() %>% auth(app_id="<my application id>") %>% persistAccessToken()
Marc Kupietz4862b862019-11-07 10:13:53 +0100193#' }
194#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100195#' @seealso [clearAccessToken()], [auth()]
196#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100197setMethod("persistAccessToken", "KorAPConnection", function(kco, accessToken = kco@accessToken) {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100198 if (! is.null(kco@oauthClient)) {
199 warning("Short lived access tokens from a confidential application cannot be persisted.")
200 return(kco)
201 }
Marc Kupietzb956b812019-11-25 17:53:13 +0100202 if (is.null(accessToken))
203 stop("It seems that you have not supplied any access token that could be persisted.", call. = FALSE)
Marc Kupietz4862b862019-11-07 10:13:53 +0100204
Marc Kupietzb956b812019-11-25 17:53:13 +0100205 kco@accessToken <- accessToken
206 key_set_with_value(accessTokenServiceName, kco@KorAPUrl, accessToken)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100207 return(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100208})
209
Marc Kupietzb956b812019-11-25 17:53:13 +0100210setGeneric("clearAccessToken", function(kco) standardGeneric("clearAccessToken") )
Marc Kupietz4862b862019-11-07 10:13:53 +0100211
Marc Kupietza4f51d72025-01-25 16:23:18 +0100212#' Clear access token from keyring and KorAPConnection object
213#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100214#' @aliases clearAccessToken
Marc Kupietz4862b862019-11-07 10:13:53 +0100215#' @import keyring
Marc Kupietza4f51d72025-01-25 16:23:18 +0100216#' @param kco KorAPConnection object
217#' @return KorAPConnection object with access token set to `NULL`.
Marc Kupietz4862b862019-11-07 10:13:53 +0100218#' @export
219#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +0200220#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100221#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100222#' kco <- KorAPConnection()
Marc Kupietza4f51d72025-01-25 16:23:18 +0100223#' kco <- clearAccessToken(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100224#' }
225#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100226#' @seealso [persistAccessToken()]
227#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100228setMethod("clearAccessToken", "KorAPConnection", function(kco) {
229 key_delete(accessTokenServiceName, kco@KorAPUrl)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100230 kco@accessToken <- NULL
231 kco
Marc Kupietz4862b862019-11-07 10:13:53 +0100232})
233
Marc Kupietza4f51d72025-01-25 16:23:18 +0100234
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100235oauthRefresh <- function(req, client, scope, kco) {
236 httr2::req_oauth_auth_code(req, client, scope = scope,
237 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
Marc Kupietz62b17892025-02-01 18:26:45 +0100238 redirect_uri = kustvakt_redirect_uri,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100239 cache_key = kco@KorAPUrl)
240}
241
242setGeneric("auth", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) standardGeneric("auth") )
Marc Kupietza4f51d72025-01-25 16:23:18 +0100243
244#' Authorize RKorAPClient
245#'
246#' @aliases auth
247#'
248#' @description
249#' `r lifecycle::badge("experimental")`
250#'
251#' Authorize RKorAPClient to make KorAP queries and download results on behalf of the user.
252#'
253#' @param kco KorAPConnection object
254#' @param app_id OAuth2 application id. Defaults to the generic KorAP client application id.
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100255#' @param app_secret OAuth2 application secret. Used with confidential client applications. Defaults to `NULL`.
Marc Kupietza4f51d72025-01-25 16:23:18 +0100256#' @param scope OAuth2 scope. Defaults to "search match_info".
257#' @return KorAPConnection object with access token set in `@accessToken`.
258#'
259#' @importFrom httr2 oauth_client oauth_flow_auth_code
260#' @examples
261#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100262#' kco <- KorAPConnection(verbose = TRUE) %>% auth()
Marc Kupietza5501652025-01-28 20:25:42 +0100263#' df <- collocationAnalysis(kco, "focus([marmot/p=ADJA] {Ameisenplage})",
264#' leftContextSize=1, rightContextSize=0)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100265#' }
266#'
267#' @seealso [persistAccessToken()], [clearAccessToken()]
268#'
269#' @export
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100270setMethod("auth", "KorAPConnection", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) {
Marc Kupietz62b17892025-02-01 18:26:45 +0100271 if (kco@authorizationSupported == FALSE) {
272 log_info(kco@verbose, "Authorization is not supported by this KorAP instance.")
273 return(kco)
274 }
Marc Kupietza4f51d72025-01-25 16:23:18 +0100275 if ( kco@KorAPUrl != "https://korap.ids-mannheim.de/" & app_id == generic_kor_app_id) {
276 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))
277 return(kco)
278 }
279 if (is.null(kco@accessToken) || is.null(kco@welcome)) { # if access token is not set or invalid
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100280 client <- if (! is.null(kco@oauthClient)) kco@oauthClient else
Marc Kupietza4f51d72025-01-25 16:23:18 +0100281 httr2::oauth_client(
282 id = app_id,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100283 secret = app_secret,
Marc Kupietza4f51d72025-01-25 16:23:18 +0100284 token_url = paste0(kco@apiUrl, "oauth2/token")
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100285 )
286 if (is.null(app_secret)) {
287 kco@accessToken <- ( client |>
Marc Kupietza4f51d72025-01-25 16:23:18 +0100288 httr2::oauth_flow_auth_code(
289 scope = scope,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100290 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
Marc Kupietz62b17892025-02-01 18:26:45 +0100291 redirect_uri = kustvakt_redirect_uri
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100292 ))$access_token
293 log_info(kco@verbose, "Client authorized. New access token set.")
294 } else {
295 kco@oauthClient <- client
296 kco@oauthScope <- scope
297 req <- request(kco@apiUrl) |>
298 oauthRefresh(client, scope, kco) |>
299 req_perform()
300 log_info(kco@verbose, "Client authorized. Short lived access token will be refreshed automatically.")
301 }
Marc Kupietza4f51d72025-01-25 16:23:18 +0100302 } else {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100303 log_info(kco@verbose, "Access token already set.")
Marc Kupietza4f51d72025-01-25 16:23:18 +0100304 }
305 return(kco)
306})
307
308
309
Marc Kupietz4862b862019-11-07 10:13:53 +0100310#' @import keyring
Marc Kupietzb956b812019-11-25 17:53:13 +0100311getAccessToken <- function(KorAPUrl) {
Marc Kupietz59e449b2019-12-12 12:53:54 +0100312 keyList <- tryCatch(withCallingHandlers(key_list(service = accessTokenServiceName),
Marc Kupietzddce5562019-11-24 15:45:38 +0100313 warning = function(w) invokeRestart("muffleWarning"),
Marc Kupietz59e449b2019-12-12 12:53:54 +0100314 error = function(e) return(NULL)),
315 error = function(e) { })
Marc Kupietz01c24772021-07-14 18:27:36 +0200316 if (KorAPUrl %in% keyList$username)
Marc Kupietzb956b812019-11-25 17:53:13 +0100317 key_get(accessTokenServiceName, KorAPUrl)
Marc Kupietzfd9e7492019-11-08 15:45:18 +0100318 else
319 NULL
Marc Kupietz4862b862019-11-07 10:13:53 +0100320}
Marc Kupietz0a96b282019-10-01 11:05:31 +0200321
Marc Kupietz581a29b2021-09-04 20:51:04 +0200322
Marc Kupietz62b17892025-02-01 18:26:45 +0100323warnIfNotAuthorized <- function(kco) {
324 if (kco@authorizationSupported & is.null(kco@accessToken) & is.null(kco@oauthClient)) {
Marc Kupietz581a29b2021-09-04 20:51:04 +0200325 warning(
326 paste0(
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100327 "In order to receive KWICSs also from corpora with restricted licenses, you may need to\n",
328 "authorize your application with an access token or the auth() method.\n",
329 "To generate an access token, login to KorAP and navigate to KorAP's OAuth settings <",
Marc Kupietz581a29b2021-09-04 20:51:04 +0200330 kco@KorAPUrl,
331 "settings/oauth#page-top>"
332 )
333 )
334 }
335}
336
Marc Kupietz0a96b282019-10-01 11:05:31 +0200337KorAPCacheSubDir <- function() {
Marc Kupietz70b2c722020-02-18 13:32:09 +0100338 paste0("RKorAPClient_",
339 gsub(
340 "^([0-9]+\\.[0-9]+).*",
341 "\\1",
342 packageVersion("RKorAPClient"),
343 perl = TRUE
344 ))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200345}
346
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200347setGeneric("apiCall", function(kco, ...) standardGeneric("apiCall") )
348
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200349## quiets concerns of R CMD check re: the .'s that appear in pipelines
Marc Kupietzef1ef4a2025-02-19 12:12:40 +0100350utils::globalVariables(c("."))
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200351
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200352#' @aliases apiCall
353#' @rdname KorAPConnection-class
354#' @param kco KorAPConnection object
355#' @param url request url
Marc Kupietzf9129592025-01-26 19:17:54 +0100356#' @param json logical that determines if JSON result is expected
Marc Kupietzb49afa02020-06-04 15:50:29 +0200357#' @param getHeaders logical that determines if headers and content should be returned (as a list)
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200358#' @importFrom jsonlite fromJSON
Marc Kupietza4675722022-02-23 23:55:15 +0100359#' @importFrom curl has_internet
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100360#' @import httr2
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200361#' @export
Marc Kupietzf9129592025-01-26 19:17:54 +0100362setMethod("apiCall", "KorAPConnection", function(kco, url, json = TRUE, getHeaders = FALSE, cache = kco@cache, timeout = kco@timeout) {
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100363 result <- ""
Marc Kupietzf9129592025-01-26 19:17:54 +0100364
365 # Handle caching if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100366 if (cache) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100367 result <- R.cache::loadCache(dir = KorAPCacheSubDir(), key = list(url, kco@accessToken, kco@indexRevision))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100368 if (!is.null(result)) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100369 if (!is.null(result$meta)) result$meta$cached <- "local"
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100370 return(result)
Marc Kupietz0a96b282019-10-01 11:05:31 +0200371 }
372 }
Marc Kupietza4675722022-02-23 23:55:15 +0100373
Marc Kupietzf9129592025-01-26 19:17:54 +0100374 # Check for internet connection
Marc Kupietza4675722022-02-23 23:55:15 +0100375 if (!curl::has_internet()) {
376 message("No internet connection.")
377 return(invisible(NULL))
378 }
379
Marc Kupietzf9129592025-01-26 19:17:54 +0100380 # Create the request
381 req <- httr2::request(url) |>
382 httr2::req_user_agent(kco@userAgent) |>
Marc Kupietz1b530472025-02-04 10:46:49 +0100383 httr2::req_error(is_error = \(resp) FALSE) |>
Marc Kupietzf9129592025-01-26 19:17:54 +0100384 httr2::req_timeout(timeout)
Marc Kupietza4675722022-02-23 23:55:15 +0100385
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100386 if (! is.null(kco@oauthClient)) {
387 req <- req |> oauthRefresh(kco@oauthClient, scope = kco@oauthScope, kco)
388 } else if (!is.null(kco@accessToken)) {
389 req <- req |> httr2::req_auth_bearer_token(kco@accessToken)
Marc Kupietzf9129592025-01-26 19:17:54 +0100390 }
391
Marc Kupietz1b530472025-02-04 10:46:49 +0100392 resp <- tryCatch(req |> httr2::req_perform(),
393 error = function(e) {
394 message(e$message, if("parent" %in% names(e)) paste0("\n", e$parent$message) else "")
395 return(NULL)
396 }
397 )
Marc Kupietzf9129592025-01-26 19:17:54 +0100398
Marc Kupietz1b530472025-02-04 10:46:49 +0100399 if (is.null(resp)) return(invisible(NULL))
Marc Kupietz62b17892025-02-01 18:26:45 +0100400
Marc Kupietzf9129592025-01-26 19:17:54 +0100401 if (resp |> httr2::resp_status() != 200) {
Marc Kupietz62b17892025-02-01 18:26:45 +0100402 message("Request failed with status ", resp |> httr2::resp_status(), ": ", resp |> httr2::resp_status_desc())
403 if (resp |> httr2::resp_content_type() == "application/json") {
404 result <- tryCatch(
405 resp |> httr2::resp_body_json(),
406 error = function(e) {
407 message("Failed to parse json with error details: ", e$message)
408 return(NULL)
409 }
410 )
411 # Handle errors in the response (if any)
412 if (!is.null(result$errors)) {
413 errors <- result$errors
414 warning_msgs <- if (is.data.frame(errors)) {
415 apply(errors, 1, function(warning) paste(warning[1], ": ", warning[2]))
416 } else {
417 lapply(errors, function(error) paste(error, collapse = " "))
418 }
419 message(paste(warning_msgs, collapse = "\n"))
Marc Kupietzf9129592025-01-26 19:17:54 +0100420 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100421 }
Marc Kupietza4675722022-02-23 23:55:15 +0100422 return(invisible(NULL))
423 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100424
425 # Process JSON response or raw text based on `json` parameter
426 if (json) {
427 content_type <- resp |> httr2::resp_content_type()
428 if (!content_type %in% c("application/json", "application/ld+json")) {
429 message("API did not return JSON")
Marc Kupietza4675722022-02-23 23:55:15 +0100430 return(invisible(NULL))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100431 }
Marc Kupietz04814f22023-04-16 17:13:27 +0200432
Marc Kupietzf9129592025-01-26 19:17:54 +0100433 result <- tryCatch(
434 resp |> httr2::resp_body_string() |> jsonlite::fromJSON(),
435 error = function(e) {
436 message("Failed to parse JSON: ", e$message)
437 return(NULL)
438 }
439 )
440
441 # Handle warnings in the response (if any)
442 if (!is.null(result$warnings)) {
443 warnings <- result$warnings
444 warning_msgs <- if (is.data.frame(warnings)) {
445 apply(warnings, 1, function(warning) paste(warning[1], ": ", warning[2]))
446 } else {
447 lapply(warnings, function(warning) paste(warning, collapse = " "))
448 }
449 message(paste(warning_msgs, collapse = "\n"))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100450 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100451 } else {
452 result <- resp |> httr2::resp_body_string()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200453 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100454
455 # Save to cache if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100456 if (cache) {
Marc Kupietzb49afa02020-06-04 15:50:29 +0200457 R.cache::saveCache(result, key = list(url, kco@accessToken, kco@indexRevision), dir = KorAPCacheSubDir(), compress = TRUE)
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100458 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100459
460 # Return headers and content as a list if `getHeaders` is TRUE
Marc Kupietzb49afa02020-06-04 15:50:29 +0200461 if (getHeaders) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100462 list(headers = resp |> httr2::resp_headers(), content = result)
Marc Kupietzb49afa02020-06-04 15:50:29 +0200463 } else {
464 result
465 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200466})
467
Marc Kupietz0a96b282019-10-01 11:05:31 +0200468setGeneric("clearCache", function(kco) standardGeneric("clearCache") )
469
470#' @aliases clearCache
471#' @rdname KorAPConnection-class
472#' @export
473setMethod("clearCache", "KorAPConnection", function(kco) {
474 R.cache::clearCache(dir=KorAPCacheSubDir())
475})
476
Marc Kupietze95108e2019-09-18 13:23:58 +0200477#' @rdname KorAPConnection-class
478#' @param object KorAPConnection object
479#' @export
480setMethod("show", "KorAPConnection", function(object) {
481 cat("<KorAPConnection>", "\n")
482 cat("apiUrl: ", object@apiUrl, "\n")
483})
484
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200485##' Funtion KorAPConnection()
486##'
Marc Kupietz617266d2025-02-27 10:43:07 +0100487##' Wrappper function for KorAPConnection()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200488##'
489##' @rdname KorAPConnection-constructor
490##' @name KorAPConnection-constructor
491##' @export
Marc Kupietz617266d2025-02-27 10:43:07 +0100492## XKorAPConnection <- function(...) KorAPConnection(...)