blob: c810492621e631af9201be3e5d8f0bc162442c0e [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.
11#' New `KorAPConnection` objects can be created by `new("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 Kupietza81343d2022-09-06 12:32:10 +020023#' @slot userAgent user agent string used for connection the API.
24#' @slot timeout tineout in seconds for API requests (this does not influence server internal timeouts)
25#' @slot verbose logical that decides whether operations will default to be verbose.
26#' @slot cache logical that decides if API calls are cached locally.
27#' @slot welcome list containing HTTP response received from KorAP server welcome function.
28
Marc Kupietze95108e2019-09-18 13:23:58 +020029#' @export
Marc Kupietzf83d59a2025-02-01 14:48:30 +010030KorAPConnection <- setClass("KorAPConnection", slots=c(KorAPUrl="character", apiVersion="character", indexRevision="characterOrNULL", apiUrl="character", accessToken="characterOrNULL", oauthClient="ANY", oauthScope="characterOrNULL", userAgent="character", timeout="numeric", verbose="logical", cache="logical", welcome="listOrNULL"))
Marc Kupietze95108e2019-09-18 13:23:58 +020031
32#' @param .Object KorAPConnection object
Marc Kupietza81343d2022-09-06 12:32:10 +020033#' @param KorAPUrl URL of the web user interface of the KorAP server instance you want to access.
Marc Kupietze95108e2019-09-18 13:23:58 +020034#' @param apiVersion which version of KorAP's API you want to connect to.
35#' @param apiUrl URL of the KorAP web service.
Marc Kupietz132f0052023-04-16 14:23:05 +020036#' @param accessToken OAuth2 access token. For queries on corpus parts with restricted
37#' access (e.g. textual queries on IPR protected data), you need to authorize
38#' your application with an access token.
Marc Kupietza4f51d72025-01-25 16:23:18 +010039#' You can obtain an access token using the [auth()] method.
40#'
41#' More details are explained in the
Marc Kupietz132f0052023-04-16 14:23:05 +020042#' [authorization section](https://github.com/KorAP/RKorAPClient#authorization)
43#' of the RKorAPClient Readme on GitHub.
44#'
45#' To use authorization based on an access token
46#' in subsequent queries, initialize your KorAP connection with:
47#'
48#' ```
49#' kco <- new("KorAPConnection", accessToken="<access token>")
50#' ```
51#'
Marc Kupietz4862b862019-11-07 10:13:53 +010052#' In order to make the API
Marc Kupietz67edcb52021-09-20 21:54:24 +020053#' token persistent for the currently used `KorAPUrl` (you can have one
Marc Kupietz132f0052023-04-16 14:23:05 +020054#' token per KorAPUrl / KorAP server instance), use:
55#'
56#' ```
57#' persistAccessToken(kco)
58#' ```
59#'
60#' This will store it in your keyring using the
Marc Kupietz6a02e4c2025-01-09 21:22:30 +010061#' [keyring::keyring-package]. Subsequent new("KorAPConnection") calls will
Marc Kupietz4862b862019-11-07 10:13:53 +010062#' then automatically retrieve the token from your keying. To stop using a
Marc Kupietz67edcb52021-09-20 21:54:24 +020063#' persisted token, call `clearAccessToken(kco)`. Please note that for
Marc Kupietz4862b862019-11-07 10:13:53 +010064#' DeReKo, authorized queries will behave differently inside and outside the
65#' IDS, because of the special license situation. This concerns also cached
66#' results which do not take into account from where a request was issued. If
Marc Kupietz67edcb52021-09-20 21:54:24 +020067#' you experience problems or unexpected results, please try `kco <-
68#' new("KorAPConnection", cache=FALSE)` or use
69#' [clearCache()] to clear the cache completely.
Marc Kupietz132f0052023-04-16 14:23:05 +020070#'
Marc Kupietzf83d59a2025-02-01 14:48:30 +010071#' An alternative to using an access token is to use a browser-based oauth2 workflow
72#' to obtain an access token. This can be done with the [auth()] method.
73#'
74#' @param oauthClient OAuth2 client object.
75#' @param oauthScope OAuth2 scope.
76#' @param authorizationPossible logical that indicates if authorization is possible/necessary for the current KorAP instance. Automatically set during initialization.
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +020077#' @param userAgent user agent string.
Marc Kupietza81343d2022-09-06 12:32:10 +020078#' @param timeout tineout in seconds for API requests (this does not influence server internal timeouts).
79#' @param verbose logical that decides whether following operations will default to
Marc Kupietz4862b862019-11-07 10:13:53 +010080#' be verbose.
Marc Kupietza81343d2022-09-06 12:32:10 +020081#' @param cache logical that decides if API calls are cached locally. You can clear
Marc Kupietz67edcb52021-09-20 21:54:24 +020082#' the cache with [clearCache()].
83#' @return [KorAPConnection()] object that can be used e.g. with
84#' [corpusQuery()]
Marc Kupietze95108e2019-09-18 13:23:58 +020085#'
Marc Kupietzf83d59a2025-02-01 14:48:30 +010086#' @import httr2
Marc Kupietze95108e2019-09-18 13:23:58 +020087#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +020088#' \dontrun{
89#'
Marc Kupietz5a519822019-09-20 21:43:52 +020090#' kcon <- new("KorAPConnection", verbose = TRUE)
Marc Kupietze95108e2019-09-18 13:23:58 +020091#' kq <- corpusQuery(kcon, "Ameisenplage")
Marc Kupietz5a519822019-09-20 21:43:52 +020092#' kq <- fetchAll(kq)
Marc Kupietz05b22772020-02-18 21:58:42 +010093#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +020094#'
Marc Kupietz4862b862019-11-07 10:13:53 +010095#' \dontrun{
Marc Kupietz6ae76052021-09-21 10:34:00 +020096#'
Marc Kupietzb956b812019-11-25 17:53:13 +010097#' kcon <- new("KorAPConnection", verbose = TRUE, accessToken="e739u6eOzkwADQPdVChxFg")
Marc Kupietz4862b862019-11-07 10:13:53 +010098#' kq <- corpusQuery(kcon, "Ameisenplage", metadataOnly=FALSE)
99#' kq <- fetchAll(kq)
100#' kq@collectedMatches$snippet
101#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +0200102#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200103#' @rdname KorAPConnection-class
Marc Kupietz632cbd42019-09-06 16:04:51 +0200104#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +0200105setMethod("initialize", "KorAPConnection",
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100106 function(.Object, KorAPUrl = "https://korap.ids-mannheim.de/", apiVersion = 'v1.0', apiUrl, accessToken = getAccessToken(KorAPUrl), oauthClient = NULL, oauthScope = "search match_info", userAgent = "R-KorAP-Client", timeout=240, verbose = FALSE, cache = TRUE) {
Marc Kupietze95108e2019-09-18 13:23:58 +0200107 .Object <- callNextMethod()
108 m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
109 .Object@KorAPUrl <- regmatches(KorAPUrl, m)
110 if (!endsWith(.Object@KorAPUrl, '/')) {
111 .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
112 }
113 if (missing(apiUrl)) {
114 .Object@apiUrl = paste0(.Object@KorAPUrl, 'api/', apiVersion, '/')
115 } else {
116 .Object@apiUrl = apiUrl
117 }
Marc Kupietzb956b812019-11-25 17:53:13 +0100118 .Object@accessToken = accessToken
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100119 .Object@oauthClient = oauthClient
Marc Kupietze95108e2019-09-18 13:23:58 +0200120 .Object@apiVersion = apiVersion
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200121 .Object@userAgent = userAgent
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100122 .Object@oauthScope = oauthScope
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200123 .Object@timeout = timeout
Marc Kupietz5a519822019-09-20 21:43:52 +0200124 .Object@verbose = verbose
Marc Kupietz0a96b282019-10-01 11:05:31 +0200125 .Object@cache = cache
Marc Kupietza4675722022-02-23 23:55:15 +0100126 .Object@welcome = apiCall(.Object, .Object@apiUrl, json = FALSE, cache = FALSE, getHeaders = TRUE)
127 if (!is.null(.Object@welcome)) {
128 message(.Object@welcome[[2]])
129 }
130 .Object@indexRevision <- .Object@welcome[[1]][["x-index-revision"]]
Marc Kupietze95108e2019-09-18 13:23:58 +0200131 .Object
132 })
133
Marc Kupietza96537f2019-11-09 23:07:44 +0100134
Marc Kupietzb956b812019-11-25 17:53:13 +0100135accessTokenServiceName <- "RKorAPClientAccessToken"
Marc Kupietz4862b862019-11-07 10:13:53 +0100136
Marc Kupietzb956b812019-11-25 17:53:13 +0100137setGeneric("persistAccessToken", function(kco, ...) standardGeneric("persistAccessToken") )
Marc Kupietz4862b862019-11-07 10:13:53 +0100138
Marc Kupietza4f51d72025-01-25 16:23:18 +0100139#' Persist current access token in keyring
140#'
141#' @param kco KorAPConnection object
142#' @param accessToken access token to be persisted. If not supplied, the current access token of the KorAPConnection object will be used.
143#' @return KorAPConnection object.
144#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100145#' @aliases persistAccessToken
Marc Kupietza4f51d72025-01-25 16:23:18 +0100146#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100147#' @import keyring
148#' @export
Marc Kupietza4f51d72025-01-25 16:23:18 +0100149#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100150#' @examples
151#' \dontrun{
Marc Kupietzb956b812019-11-25 17:53:13 +0100152#' kco <- new("KorAPConnection", accessToken="e739u6eOzkwADQPdVChxFg")
153#' persistAccessToken(kco)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100154#'
155#' kco <- new("KorAPConnection") %>% auth(app_id="<my application id>") %>% persistAccessToken()
Marc Kupietz4862b862019-11-07 10:13:53 +0100156#' }
157#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100158#' @seealso [clearAccessToken()], [auth()]
159#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100160setMethod("persistAccessToken", "KorAPConnection", function(kco, accessToken = kco@accessToken) {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100161 if (! is.null(kco@oauthClient)) {
162 warning("Short lived access tokens from a confidential application cannot be persisted.")
163 return(kco)
164 }
Marc Kupietzb956b812019-11-25 17:53:13 +0100165 if (is.null(accessToken))
166 stop("It seems that you have not supplied any access token that could be persisted.", call. = FALSE)
Marc Kupietz4862b862019-11-07 10:13:53 +0100167
Marc Kupietzb956b812019-11-25 17:53:13 +0100168 kco@accessToken <- accessToken
169 key_set_with_value(accessTokenServiceName, kco@KorAPUrl, accessToken)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100170 return(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100171})
172
Marc Kupietzb956b812019-11-25 17:53:13 +0100173setGeneric("clearAccessToken", function(kco) standardGeneric("clearAccessToken") )
Marc Kupietz4862b862019-11-07 10:13:53 +0100174
Marc Kupietza4f51d72025-01-25 16:23:18 +0100175#' Clear access token from keyring and KorAPConnection object
176#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100177#' @aliases clearAccessToken
Marc Kupietz4862b862019-11-07 10:13:53 +0100178#' @import keyring
Marc Kupietza4f51d72025-01-25 16:23:18 +0100179#' @param kco KorAPConnection object
180#' @return KorAPConnection object with access token set to `NULL`.
Marc Kupietz4862b862019-11-07 10:13:53 +0100181#' @export
182#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +0200183#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100184#' \dontrun{
Marc Kupietz4862b862019-11-07 10:13:53 +0100185#' kco <- new("KorAPConnection")
Marc Kupietza4f51d72025-01-25 16:23:18 +0100186#' kco <- clearAccessToken(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100187#' }
188#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100189#' @seealso [persistAccessToken()]
190#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100191setMethod("clearAccessToken", "KorAPConnection", function(kco) {
192 key_delete(accessTokenServiceName, kco@KorAPUrl)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100193 kco@accessToken <- NULL
194 kco
Marc Kupietz4862b862019-11-07 10:13:53 +0100195})
196
Marc Kupietza4f51d72025-01-25 16:23:18 +0100197generic_kor_app_id = "99FbPHH7RrN36hbndF7b6f"
198
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100199kustvakt_redirekt_uri = "http://localhost:1410/"
200kustvakt_auth_path = "settings/oauth/authorize"
Marc Kupietza4f51d72025-01-25 16:23:18 +0100201
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100202oauthRefresh <- function(req, client, scope, kco) {
203 httr2::req_oauth_auth_code(req, client, scope = scope,
204 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
205 redirect_uri = kustvakt_redirekt_uri,
206 cache_key = kco@KorAPUrl)
207}
208
209setGeneric("auth", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) standardGeneric("auth") )
Marc Kupietza4f51d72025-01-25 16:23:18 +0100210
211#' Authorize RKorAPClient
212#'
213#' @aliases auth
214#'
215#' @description
216#' `r lifecycle::badge("experimental")`
217#'
218#' Authorize RKorAPClient to make KorAP queries and download results on behalf of the user.
219#'
220#' @param kco KorAPConnection object
221#' @param app_id OAuth2 application id. Defaults to the generic KorAP client application id.
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100222#' @param app_secret OAuth2 application secret. Used with confidential client applications. Defaults to `NULL`.
Marc Kupietza4f51d72025-01-25 16:23:18 +0100223#' @param scope OAuth2 scope. Defaults to "search match_info".
224#' @return KorAPConnection object with access token set in `@accessToken`.
225#'
226#' @importFrom httr2 oauth_client oauth_flow_auth_code
227#' @examples
228#' \dontrun{
229#' kco <- new("KorAPConnection", verbose = TRUE) %>% auth()
Marc Kupietza5501652025-01-28 20:25:42 +0100230#' df <- collocationAnalysis(kco, "focus([marmot/p=ADJA] {Ameisenplage})",
231#' leftContextSize=1, rightContextSize=0)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100232#' }
233#'
234#' @seealso [persistAccessToken()], [clearAccessToken()]
235#'
236#' @export
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100237setMethod("auth", "KorAPConnection", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) {
Marc Kupietza4f51d72025-01-25 16:23:18 +0100238 if ( kco@KorAPUrl != "https://korap.ids-mannheim.de/" & app_id == generic_kor_app_id) {
239 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))
240 return(kco)
241 }
242 if (is.null(kco@accessToken) || is.null(kco@welcome)) { # if access token is not set or invalid
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100243 client <- if (! is.null(kco@oauthClient)) kco@oauthClient else
Marc Kupietza4f51d72025-01-25 16:23:18 +0100244 httr2::oauth_client(
245 id = app_id,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100246 secret = app_secret,
Marc Kupietza4f51d72025-01-25 16:23:18 +0100247 token_url = paste0(kco@apiUrl, "oauth2/token")
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100248 )
249 if (is.null(app_secret)) {
250 kco@accessToken <- ( client |>
Marc Kupietza4f51d72025-01-25 16:23:18 +0100251 httr2::oauth_flow_auth_code(
252 scope = scope,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100253 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
254 redirect_uri = kustvakt_redirekt_uri
255 ))$access_token
256 log_info(kco@verbose, "Client authorized. New access token set.")
257 } else {
258 kco@oauthClient <- client
259 kco@oauthScope <- scope
260 req <- request(kco@apiUrl) |>
261 oauthRefresh(client, scope, kco) |>
262 req_perform()
263 log_info(kco@verbose, "Client authorized. Short lived access token will be refreshed automatically.")
264 }
Marc Kupietza4f51d72025-01-25 16:23:18 +0100265 } else {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100266 log_info(kco@verbose, "Access token already set.")
Marc Kupietza4f51d72025-01-25 16:23:18 +0100267 }
268 return(kco)
269})
270
271
272
Marc Kupietz4862b862019-11-07 10:13:53 +0100273#' @import keyring
Marc Kupietzb956b812019-11-25 17:53:13 +0100274getAccessToken <- function(KorAPUrl) {
Marc Kupietz59e449b2019-12-12 12:53:54 +0100275 keyList <- tryCatch(withCallingHandlers(key_list(service = accessTokenServiceName),
Marc Kupietzddce5562019-11-24 15:45:38 +0100276 warning = function(w) invokeRestart("muffleWarning"),
Marc Kupietz59e449b2019-12-12 12:53:54 +0100277 error = function(e) return(NULL)),
278 error = function(e) { })
Marc Kupietz01c24772021-07-14 18:27:36 +0200279 if (KorAPUrl %in% keyList$username)
Marc Kupietzb956b812019-11-25 17:53:13 +0100280 key_get(accessTokenServiceName, KorAPUrl)
Marc Kupietzfd9e7492019-11-08 15:45:18 +0100281 else
282 NULL
Marc Kupietz4862b862019-11-07 10:13:53 +0100283}
Marc Kupietz0a96b282019-10-01 11:05:31 +0200284
Marc Kupietz581a29b2021-09-04 20:51:04 +0200285
286warnIfNoAccessToken <- function(kco) {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100287 if (is.null(kco@accessToken) & is.null(kco@oauthClient)) {
Marc Kupietz581a29b2021-09-04 20:51:04 +0200288 warning(
289 paste0(
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100290 "In order to receive KWICSs also from corpora with restricted licenses, you may need to\n",
291 "authorize your application with an access token or the auth() method.\n",
292 "To generate an access token, login to KorAP and navigate to KorAP's OAuth settings <",
Marc Kupietz581a29b2021-09-04 20:51:04 +0200293 kco@KorAPUrl,
294 "settings/oauth#page-top>"
295 )
296 )
297 }
298}
299
Marc Kupietz0a96b282019-10-01 11:05:31 +0200300KorAPCacheSubDir <- function() {
Marc Kupietz70b2c722020-02-18 13:32:09 +0100301 paste0("RKorAPClient_",
302 gsub(
303 "^([0-9]+\\.[0-9]+).*",
304 "\\1",
305 packageVersion("RKorAPClient"),
306 perl = TRUE
307 ))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200308}
309
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200310setGeneric("apiCall", function(kco, ...) standardGeneric("apiCall") )
311
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200312## quiets concerns of R CMD check re: the .'s that appear in pipelines
313if(getRversion() >= "2.15.1") utils::globalVariables(c("."))
314
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200315#' @aliases apiCall
316#' @rdname KorAPConnection-class
317#' @param kco KorAPConnection object
318#' @param url request url
Marc Kupietzf9129592025-01-26 19:17:54 +0100319#' @param json logical that determines if JSON result is expected
Marc Kupietzb49afa02020-06-04 15:50:29 +0200320#' @param getHeaders logical that determines if headers and content should be returned (as a list)
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200321#' @importFrom jsonlite fromJSON
Marc Kupietza4675722022-02-23 23:55:15 +0100322#' @importFrom curl has_internet
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100323#' @import httr2
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200324#' @export
Marc Kupietzf9129592025-01-26 19:17:54 +0100325setMethod("apiCall", "KorAPConnection", function(kco, url, json = TRUE, getHeaders = FALSE, cache = kco@cache, timeout = kco@timeout) {
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100326 result <- ""
Marc Kupietzf9129592025-01-26 19:17:54 +0100327
328 # Handle caching if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100329 if (cache) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100330 result <- R.cache::loadCache(dir = KorAPCacheSubDir(), key = list(url, kco@accessToken, kco@indexRevision))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100331 if (!is.null(result)) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100332 if (!is.null(result$meta)) result$meta$cached <- "local"
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100333 return(result)
Marc Kupietz0a96b282019-10-01 11:05:31 +0200334 }
335 }
Marc Kupietza4675722022-02-23 23:55:15 +0100336
Marc Kupietzf9129592025-01-26 19:17:54 +0100337 # Check for internet connection
Marc Kupietza4675722022-02-23 23:55:15 +0100338 if (!curl::has_internet()) {
339 message("No internet connection.")
340 return(invisible(NULL))
341 }
342
Marc Kupietzf9129592025-01-26 19:17:54 +0100343 # Create the request
344 req <- httr2::request(url) |>
345 httr2::req_user_agent(kco@userAgent) |>
346 httr2::req_timeout(timeout)
Marc Kupietza4675722022-02-23 23:55:15 +0100347
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100348 if (! is.null(kco@oauthClient)) {
349 req <- req |> oauthRefresh(kco@oauthClient, scope = kco@oauthScope, kco)
350 } else if (!is.null(kco@accessToken)) {
351 req <- req |> httr2::req_auth_bearer_token(kco@accessToken)
Marc Kupietzf9129592025-01-26 19:17:54 +0100352 }
353
354 # Perform the request and handle errors
355 resp <- tryCatch(
356 req |> httr2::req_perform(),
357 error = function(e) {
358 message(if(kco@verbose) "\n" else "", "Request failed: ", paste(e$message, e$parent$message, sep = " "))
359 e$resp
360 }
361 )
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100362#
Marc Kupietzf9129592025-01-26 19:17:54 +0100363 if (is.null(resp)) return(invisible(NULL))
364
365 # Check response status
366 if (resp |> httr2::resp_status() != 200) {
367
368 message("API request failed with status: ", resp |> httr2::resp_status())
369
370 result <- tryCatch(
371 resp |> httr2::resp_body_json(),
372 error = function(e) {
373 message("Failed to parse json with error details: ", e$message)
374 return(NULL)
375 }
376 )
377 # Handle errors in the response (if any)
378 if (!is.null(result$errors)) {
379 errors <- result$errors
380 warning_msgs <- if (is.data.frame(errors)) {
381 apply(errors, 1, function(warning) paste(warning[1], ": ", warning[2]))
382 } else {
383 lapply(errors, function(error) paste(error, collapse = " "))
384 }
385 message(paste(warning_msgs, collapse = "\n"))
386 }
387
Marc Kupietza4675722022-02-23 23:55:15 +0100388 return(invisible(NULL))
389 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100390
391 # Process JSON response or raw text based on `json` parameter
392 if (json) {
393 content_type <- resp |> httr2::resp_content_type()
394 if (!content_type %in% c("application/json", "application/ld+json")) {
395 message("API did not return JSON")
Marc Kupietza4675722022-02-23 23:55:15 +0100396 return(invisible(NULL))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100397 }
Marc Kupietz04814f22023-04-16 17:13:27 +0200398
Marc Kupietzf9129592025-01-26 19:17:54 +0100399 result <- tryCatch(
400 resp |> httr2::resp_body_string() |> jsonlite::fromJSON(),
401 error = function(e) {
402 message("Failed to parse JSON: ", e$message)
403 return(NULL)
404 }
405 )
406
407 # Handle warnings in the response (if any)
408 if (!is.null(result$warnings)) {
409 warnings <- result$warnings
410 warning_msgs <- if (is.data.frame(warnings)) {
411 apply(warnings, 1, function(warning) paste(warning[1], ": ", warning[2]))
412 } else {
413 lapply(warnings, function(warning) paste(warning, collapse = " "))
414 }
415 message(paste(warning_msgs, collapse = "\n"))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100416 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100417 } else {
418 result <- resp |> httr2::resp_body_string()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200419 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100420
421 # Save to cache if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100422 if (cache) {
Marc Kupietzb49afa02020-06-04 15:50:29 +0200423 R.cache::saveCache(result, key = list(url, kco@accessToken, kco@indexRevision), dir = KorAPCacheSubDir(), compress = TRUE)
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100424 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100425
426 # Return headers and content as a list if `getHeaders` is TRUE
Marc Kupietzb49afa02020-06-04 15:50:29 +0200427 if (getHeaders) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100428 list(headers = resp |> httr2::resp_headers(), content = result)
Marc Kupietzb49afa02020-06-04 15:50:29 +0200429 } else {
430 result
431 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200432})
433
Marc Kupietz0a96b282019-10-01 11:05:31 +0200434setGeneric("clearCache", function(kco) standardGeneric("clearCache") )
435
436#' @aliases clearCache
437#' @rdname KorAPConnection-class
438#' @export
439setMethod("clearCache", "KorAPConnection", function(kco) {
440 R.cache::clearCache(dir=KorAPCacheSubDir())
441})
442
Marc Kupietze95108e2019-09-18 13:23:58 +0200443#' @rdname KorAPConnection-class
444#' @param object KorAPConnection object
445#' @export
446setMethod("show", "KorAPConnection", function(object) {
447 cat("<KorAPConnection>", "\n")
448 cat("apiUrl: ", object@apiUrl, "\n")
449})
450
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200451##' Funtion KorAPConnection()
452##'
453##' Wrappper function for new("KorAPConnection")
454##'
455##' @rdname KorAPConnection-constructor
456##' @name KorAPConnection-constructor
457##' @export
458## XKorAPConnection <- function(...) new("KorAPConnection", ...)