blob: 3627f2fa10c0775c9447d1a001a2b23fcf4fb23c [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 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 Kupietze95108e2019-09-18 13:23:58 +020041#' @param apiVersion which version of KorAP's API you want to connect to.
42#' @param apiUrl URL of the KorAP web service.
Marc Kupietz132f0052023-04-16 14:23:05 +020043#' @param accessToken OAuth2 access token. For queries on corpus parts with restricted
44#' access (e.g. textual queries on IPR protected data), you need to authorize
45#' your application with an access token.
Marc Kupietz62b17892025-02-01 18:26:45 +010046#' You can obtain an access token in the OAuth settings of your KorAP web interface.
Marc Kupietza4f51d72025-01-25 16:23:18 +010047#'
48#' More details are explained in the
Marc Kupietz132f0052023-04-16 14:23:05 +020049#' [authorization section](https://github.com/KorAP/RKorAPClient#authorization)
50#' of the RKorAPClient Readme on GitHub.
51#'
52#' To use authorization based on an access token
53#' in subsequent queries, initialize your KorAP connection with:
54#'
55#' ```
56#' kco <- new("KorAPConnection", accessToken="<access token>")
57#' ```
58#'
Marc Kupietz4862b862019-11-07 10:13:53 +010059#' In order to make the API
Marc Kupietz67edcb52021-09-20 21:54:24 +020060#' token persistent for the currently used `KorAPUrl` (you can have one
Marc Kupietz132f0052023-04-16 14:23:05 +020061#' token per KorAPUrl / KorAP server instance), use:
62#'
63#' ```
64#' persistAccessToken(kco)
65#' ```
66#'
67#' This will store it in your keyring using the
Marc Kupietz6a02e4c2025-01-09 21:22:30 +010068#' [keyring::keyring-package]. Subsequent new("KorAPConnection") calls will
Marc Kupietz4862b862019-11-07 10:13:53 +010069#' then automatically retrieve the token from your keying. To stop using a
Marc Kupietz67edcb52021-09-20 21:54:24 +020070#' persisted token, call `clearAccessToken(kco)`. Please note that for
Marc Kupietz4862b862019-11-07 10:13:53 +010071#' DeReKo, authorized queries will behave differently inside and outside the
72#' IDS, because of the special license situation. This concerns also cached
73#' results which do not take into account from where a request was issued. If
Marc Kupietz67edcb52021-09-20 21:54:24 +020074#' you experience problems or unexpected results, please try `kco <-
75#' new("KorAPConnection", cache=FALSE)` or use
76#' [clearCache()] to clear the cache completely.
Marc Kupietz132f0052023-04-16 14:23:05 +020077#'
Marc Kupietzf83d59a2025-02-01 14:48:30 +010078#' An alternative to using an access token is to use a browser-based oauth2 workflow
79#' to obtain an access token. This can be done with the [auth()] method.
80#'
81#' @param oauthClient OAuth2 client object.
82#' @param oauthScope OAuth2 scope.
Marc Kupietz62b17892025-02-01 18:26:45 +010083#' @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 +020084#' @param userAgent user agent string.
Marc Kupietza81343d2022-09-06 12:32:10 +020085#' @param timeout tineout in seconds for API requests (this does not influence server internal timeouts).
86#' @param verbose logical that decides whether following operations will default to
Marc Kupietz4862b862019-11-07 10:13:53 +010087#' be verbose.
Marc Kupietza81343d2022-09-06 12:32:10 +020088#' @param cache logical that decides if API calls are cached locally. You can clear
Marc Kupietz67edcb52021-09-20 21:54:24 +020089#' the cache with [clearCache()].
90#' @return [KorAPConnection()] object that can be used e.g. with
91#' [corpusQuery()]
Marc Kupietze95108e2019-09-18 13:23:58 +020092#'
Marc Kupietzf83d59a2025-02-01 14:48:30 +010093#' @import httr2
Marc Kupietze95108e2019-09-18 13:23:58 +020094#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +020095#' \dontrun{
96#'
Marc Kupietz5a519822019-09-20 21:43:52 +020097#' kcon <- new("KorAPConnection", verbose = TRUE)
Marc Kupietze95108e2019-09-18 13:23:58 +020098#' kq <- corpusQuery(kcon, "Ameisenplage")
Marc Kupietz5a519822019-09-20 21:43:52 +020099#' kq <- fetchAll(kq)
Marc Kupietz05b22772020-02-18 21:58:42 +0100100#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +0200101#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100102#' \dontrun{
Marc Kupietz6ae76052021-09-21 10:34:00 +0200103#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100104#' kcon <- new("KorAPConnection", verbose = TRUE, accessToken="e739u6eOzkwADQPdVChxFg")
Marc Kupietz4862b862019-11-07 10:13:53 +0100105#' kq <- corpusQuery(kcon, "Ameisenplage", metadataOnly=FALSE)
106#' kq <- fetchAll(kq)
107#' kq@collectedMatches$snippet
108#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +0200109#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200110#' @rdname KorAPConnection-class
Marc Kupietz632cbd42019-09-06 16:04:51 +0200111#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +0200112setMethod("initialize", "KorAPConnection",
Marc Kupietz62b17892025-02-01 18:26:45 +0100113 function(.Object, KorAPUrl = "https://korap.ids-mannheim.de/", apiVersion = 'v1.0', apiUrl, accessToken = getAccessToken(KorAPUrl), oauthClient = NULL, oauthScope = "search match_info", authorizationSupported = TRUE, userAgent = "R-KorAP-Client", timeout=240, verbose = FALSE, cache = TRUE) {
Marc Kupietze95108e2019-09-18 13:23:58 +0200114 .Object <- callNextMethod()
115 m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
116 .Object@KorAPUrl <- regmatches(KorAPUrl, m)
117 if (!endsWith(.Object@KorAPUrl, '/')) {
118 .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
119 }
120 if (missing(apiUrl)) {
121 .Object@apiUrl = paste0(.Object@KorAPUrl, 'api/', apiVersion, '/')
122 } else {
123 .Object@apiUrl = apiUrl
124 }
Marc Kupietzb956b812019-11-25 17:53:13 +0100125 .Object@accessToken = accessToken
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100126 .Object@oauthClient = oauthClient
Marc Kupietze95108e2019-09-18 13:23:58 +0200127 .Object@apiVersion = apiVersion
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200128 .Object@userAgent = userAgent
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100129 .Object@oauthScope = oauthScope
Marc Kupietz62b17892025-02-01 18:26:45 +0100130 .Object@authorizationSupported = authorizationSupported
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200131 .Object@timeout = timeout
Marc Kupietz5a519822019-09-20 21:43:52 +0200132 .Object@verbose = verbose
Marc Kupietz0a96b282019-10-01 11:05:31 +0200133 .Object@cache = cache
Marc Kupietza4675722022-02-23 23:55:15 +0100134 .Object@welcome = apiCall(.Object, .Object@apiUrl, json = FALSE, cache = FALSE, getHeaders = TRUE)
135 if (!is.null(.Object@welcome)) {
136 message(.Object@welcome[[2]])
Marc Kupietz62b17892025-02-01 18:26:45 +0100137 resp <- httr2::request(.Object@KorAPUrl) |>
138 httr2::req_url_path_append(kustvakt_auth_path) |>
139 httr2::req_error(is_error = \(resp) FALSE) |>
140 httr2::req_perform()
141 .Object@authorizationSupported = (httr2::resp_status(resp) == 200)
142
143 .Object@indexRevision <- .Object@welcome[[1]][["x-index-revision"]]
144 } else {
Marc Kupietz1b530472025-02-04 10:46:49 +0100145 if (grepl(.Object@KorAPUrl, .Object@apiUrl)) {
146 message("Could not connect to KorAP instance ", .Object@KorAPUrl)
147 } else {
148 message("Could not connect to KorAP API at ", .Object@apiUrl)
149 }
Marc Kupietza4675722022-02-23 23:55:15 +0100150 }
Marc Kupietze95108e2019-09-18 13:23:58 +0200151 .Object
152 })
153
Marc Kupietza96537f2019-11-09 23:07:44 +0100154
Marc Kupietzb956b812019-11-25 17:53:13 +0100155accessTokenServiceName <- "RKorAPClientAccessToken"
Marc Kupietz4862b862019-11-07 10:13:53 +0100156
Marc Kupietzb956b812019-11-25 17:53:13 +0100157setGeneric("persistAccessToken", function(kco, ...) standardGeneric("persistAccessToken") )
Marc Kupietz4862b862019-11-07 10:13:53 +0100158
Marc Kupietza4f51d72025-01-25 16:23:18 +0100159#' Persist current access token in keyring
160#'
161#' @param kco KorAPConnection object
162#' @param accessToken access token to be persisted. If not supplied, the current access token of the KorAPConnection object will be used.
163#' @return KorAPConnection object.
164#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100165#' @aliases persistAccessToken
Marc Kupietza4f51d72025-01-25 16:23:18 +0100166#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100167#' @import keyring
168#' @export
Marc Kupietza4f51d72025-01-25 16:23:18 +0100169#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100170#' @examples
171#' \dontrun{
Marc Kupietzb956b812019-11-25 17:53:13 +0100172#' kco <- new("KorAPConnection", accessToken="e739u6eOzkwADQPdVChxFg")
173#' persistAccessToken(kco)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100174#'
175#' kco <- new("KorAPConnection") %>% auth(app_id="<my application id>") %>% persistAccessToken()
Marc Kupietz4862b862019-11-07 10:13:53 +0100176#' }
177#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100178#' @seealso [clearAccessToken()], [auth()]
179#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100180setMethod("persistAccessToken", "KorAPConnection", function(kco, accessToken = kco@accessToken) {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100181 if (! is.null(kco@oauthClient)) {
182 warning("Short lived access tokens from a confidential application cannot be persisted.")
183 return(kco)
184 }
Marc Kupietzb956b812019-11-25 17:53:13 +0100185 if (is.null(accessToken))
186 stop("It seems that you have not supplied any access token that could be persisted.", call. = FALSE)
Marc Kupietz4862b862019-11-07 10:13:53 +0100187
Marc Kupietzb956b812019-11-25 17:53:13 +0100188 kco@accessToken <- accessToken
189 key_set_with_value(accessTokenServiceName, kco@KorAPUrl, accessToken)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100190 return(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100191})
192
Marc Kupietzb956b812019-11-25 17:53:13 +0100193setGeneric("clearAccessToken", function(kco) standardGeneric("clearAccessToken") )
Marc Kupietz4862b862019-11-07 10:13:53 +0100194
Marc Kupietza4f51d72025-01-25 16:23:18 +0100195#' Clear access token from keyring and KorAPConnection object
196#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100197#' @aliases clearAccessToken
Marc Kupietz4862b862019-11-07 10:13:53 +0100198#' @import keyring
Marc Kupietza4f51d72025-01-25 16:23:18 +0100199#' @param kco KorAPConnection object
200#' @return KorAPConnection object with access token set to `NULL`.
Marc Kupietz4862b862019-11-07 10:13:53 +0100201#' @export
202#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +0200203#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100204#' \dontrun{
Marc Kupietz4862b862019-11-07 10:13:53 +0100205#' kco <- new("KorAPConnection")
Marc Kupietza4f51d72025-01-25 16:23:18 +0100206#' kco <- clearAccessToken(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100207#' }
208#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100209#' @seealso [persistAccessToken()]
210#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100211setMethod("clearAccessToken", "KorAPConnection", function(kco) {
212 key_delete(accessTokenServiceName, kco@KorAPUrl)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100213 kco@accessToken <- NULL
214 kco
Marc Kupietz4862b862019-11-07 10:13:53 +0100215})
216
Marc Kupietza4f51d72025-01-25 16:23:18 +0100217
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100218oauthRefresh <- function(req, client, scope, kco) {
219 httr2::req_oauth_auth_code(req, client, scope = scope,
220 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
Marc Kupietz62b17892025-02-01 18:26:45 +0100221 redirect_uri = kustvakt_redirect_uri,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100222 cache_key = kco@KorAPUrl)
223}
224
225setGeneric("auth", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) standardGeneric("auth") )
Marc Kupietza4f51d72025-01-25 16:23:18 +0100226
227#' Authorize RKorAPClient
228#'
229#' @aliases auth
230#'
231#' @description
232#' `r lifecycle::badge("experimental")`
233#'
234#' Authorize RKorAPClient to make KorAP queries and download results on behalf of the user.
235#'
236#' @param kco KorAPConnection object
237#' @param app_id OAuth2 application id. Defaults to the generic KorAP client application id.
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100238#' @param app_secret OAuth2 application secret. Used with confidential client applications. Defaults to `NULL`.
Marc Kupietza4f51d72025-01-25 16:23:18 +0100239#' @param scope OAuth2 scope. Defaults to "search match_info".
240#' @return KorAPConnection object with access token set in `@accessToken`.
241#'
242#' @importFrom httr2 oauth_client oauth_flow_auth_code
243#' @examples
244#' \dontrun{
245#' kco <- new("KorAPConnection", verbose = TRUE) %>% auth()
Marc Kupietza5501652025-01-28 20:25:42 +0100246#' df <- collocationAnalysis(kco, "focus([marmot/p=ADJA] {Ameisenplage})",
247#' leftContextSize=1, rightContextSize=0)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100248#' }
249#'
250#' @seealso [persistAccessToken()], [clearAccessToken()]
251#'
252#' @export
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100253setMethod("auth", "KorAPConnection", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) {
Marc Kupietz62b17892025-02-01 18:26:45 +0100254 if (kco@authorizationSupported == FALSE) {
255 log_info(kco@verbose, "Authorization is not supported by this KorAP instance.")
256 return(kco)
257 }
Marc Kupietza4f51d72025-01-25 16:23:18 +0100258 if ( kco@KorAPUrl != "https://korap.ids-mannheim.de/" & app_id == generic_kor_app_id) {
259 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))
260 return(kco)
261 }
262 if (is.null(kco@accessToken) || is.null(kco@welcome)) { # if access token is not set or invalid
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100263 client <- if (! is.null(kco@oauthClient)) kco@oauthClient else
Marc Kupietza4f51d72025-01-25 16:23:18 +0100264 httr2::oauth_client(
265 id = app_id,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100266 secret = app_secret,
Marc Kupietza4f51d72025-01-25 16:23:18 +0100267 token_url = paste0(kco@apiUrl, "oauth2/token")
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100268 )
269 if (is.null(app_secret)) {
270 kco@accessToken <- ( client |>
Marc Kupietza4f51d72025-01-25 16:23:18 +0100271 httr2::oauth_flow_auth_code(
272 scope = scope,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100273 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
Marc Kupietz62b17892025-02-01 18:26:45 +0100274 redirect_uri = kustvakt_redirect_uri
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100275 ))$access_token
276 log_info(kco@verbose, "Client authorized. New access token set.")
277 } else {
278 kco@oauthClient <- client
279 kco@oauthScope <- scope
280 req <- request(kco@apiUrl) |>
281 oauthRefresh(client, scope, kco) |>
282 req_perform()
283 log_info(kco@verbose, "Client authorized. Short lived access token will be refreshed automatically.")
284 }
Marc Kupietza4f51d72025-01-25 16:23:18 +0100285 } else {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100286 log_info(kco@verbose, "Access token already set.")
Marc Kupietza4f51d72025-01-25 16:23:18 +0100287 }
288 return(kco)
289})
290
291
292
Marc Kupietz4862b862019-11-07 10:13:53 +0100293#' @import keyring
Marc Kupietzb956b812019-11-25 17:53:13 +0100294getAccessToken <- function(KorAPUrl) {
Marc Kupietz59e449b2019-12-12 12:53:54 +0100295 keyList <- tryCatch(withCallingHandlers(key_list(service = accessTokenServiceName),
Marc Kupietzddce5562019-11-24 15:45:38 +0100296 warning = function(w) invokeRestart("muffleWarning"),
Marc Kupietz59e449b2019-12-12 12:53:54 +0100297 error = function(e) return(NULL)),
298 error = function(e) { })
Marc Kupietz01c24772021-07-14 18:27:36 +0200299 if (KorAPUrl %in% keyList$username)
Marc Kupietzb956b812019-11-25 17:53:13 +0100300 key_get(accessTokenServiceName, KorAPUrl)
Marc Kupietzfd9e7492019-11-08 15:45:18 +0100301 else
302 NULL
Marc Kupietz4862b862019-11-07 10:13:53 +0100303}
Marc Kupietz0a96b282019-10-01 11:05:31 +0200304
Marc Kupietz581a29b2021-09-04 20:51:04 +0200305
Marc Kupietz62b17892025-02-01 18:26:45 +0100306warnIfNotAuthorized <- function(kco) {
307 if (kco@authorizationSupported & is.null(kco@accessToken) & is.null(kco@oauthClient)) {
Marc Kupietz581a29b2021-09-04 20:51:04 +0200308 warning(
309 paste0(
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100310 "In order to receive KWICSs also from corpora with restricted licenses, you may need to\n",
311 "authorize your application with an access token or the auth() method.\n",
312 "To generate an access token, login to KorAP and navigate to KorAP's OAuth settings <",
Marc Kupietz581a29b2021-09-04 20:51:04 +0200313 kco@KorAPUrl,
314 "settings/oauth#page-top>"
315 )
316 )
317 }
318}
319
Marc Kupietz0a96b282019-10-01 11:05:31 +0200320KorAPCacheSubDir <- function() {
Marc Kupietz70b2c722020-02-18 13:32:09 +0100321 paste0("RKorAPClient_",
322 gsub(
323 "^([0-9]+\\.[0-9]+).*",
324 "\\1",
325 packageVersion("RKorAPClient"),
326 perl = TRUE
327 ))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200328}
329
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200330setGeneric("apiCall", function(kco, ...) standardGeneric("apiCall") )
331
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200332## quiets concerns of R CMD check re: the .'s that appear in pipelines
333if(getRversion() >= "2.15.1") utils::globalVariables(c("."))
334
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200335#' @aliases apiCall
336#' @rdname KorAPConnection-class
337#' @param kco KorAPConnection object
338#' @param url request url
Marc Kupietzf9129592025-01-26 19:17:54 +0100339#' @param json logical that determines if JSON result is expected
Marc Kupietzb49afa02020-06-04 15:50:29 +0200340#' @param getHeaders logical that determines if headers and content should be returned (as a list)
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200341#' @importFrom jsonlite fromJSON
Marc Kupietza4675722022-02-23 23:55:15 +0100342#' @importFrom curl has_internet
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100343#' @import httr2
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200344#' @export
Marc Kupietzf9129592025-01-26 19:17:54 +0100345setMethod("apiCall", "KorAPConnection", function(kco, url, json = TRUE, getHeaders = FALSE, cache = kco@cache, timeout = kco@timeout) {
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100346 result <- ""
Marc Kupietzf9129592025-01-26 19:17:54 +0100347
348 # Handle caching if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100349 if (cache) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100350 result <- R.cache::loadCache(dir = KorAPCacheSubDir(), key = list(url, kco@accessToken, kco@indexRevision))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100351 if (!is.null(result)) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100352 if (!is.null(result$meta)) result$meta$cached <- "local"
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100353 return(result)
Marc Kupietz0a96b282019-10-01 11:05:31 +0200354 }
355 }
Marc Kupietza4675722022-02-23 23:55:15 +0100356
Marc Kupietzf9129592025-01-26 19:17:54 +0100357 # Check for internet connection
Marc Kupietza4675722022-02-23 23:55:15 +0100358 if (!curl::has_internet()) {
359 message("No internet connection.")
360 return(invisible(NULL))
361 }
362
Marc Kupietzf9129592025-01-26 19:17:54 +0100363 # Create the request
364 req <- httr2::request(url) |>
365 httr2::req_user_agent(kco@userAgent) |>
Marc Kupietz1b530472025-02-04 10:46:49 +0100366 httr2::req_error(is_error = \(resp) FALSE) |>
Marc Kupietzf9129592025-01-26 19:17:54 +0100367 httr2::req_timeout(timeout)
Marc Kupietza4675722022-02-23 23:55:15 +0100368
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100369 if (! is.null(kco@oauthClient)) {
370 req <- req |> oauthRefresh(kco@oauthClient, scope = kco@oauthScope, kco)
371 } else if (!is.null(kco@accessToken)) {
372 req <- req |> httr2::req_auth_bearer_token(kco@accessToken)
Marc Kupietzf9129592025-01-26 19:17:54 +0100373 }
374
Marc Kupietz1b530472025-02-04 10:46:49 +0100375 resp <- tryCatch(req |> httr2::req_perform(),
376 error = function(e) {
377 message(e$message, if("parent" %in% names(e)) paste0("\n", e$parent$message) else "")
378 return(NULL)
379 }
380 )
Marc Kupietzf9129592025-01-26 19:17:54 +0100381
Marc Kupietz1b530472025-02-04 10:46:49 +0100382 if (is.null(resp)) return(invisible(NULL))
Marc Kupietz62b17892025-02-01 18:26:45 +0100383
Marc Kupietzf9129592025-01-26 19:17:54 +0100384 if (resp |> httr2::resp_status() != 200) {
Marc Kupietz62b17892025-02-01 18:26:45 +0100385 message("Request failed with status ", resp |> httr2::resp_status(), ": ", resp |> httr2::resp_status_desc())
386 if (resp |> httr2::resp_content_type() == "application/json") {
387 result <- tryCatch(
388 resp |> httr2::resp_body_json(),
389 error = function(e) {
390 message("Failed to parse json with error details: ", e$message)
391 return(NULL)
392 }
393 )
394 # Handle errors in the response (if any)
395 if (!is.null(result$errors)) {
396 errors <- result$errors
397 warning_msgs <- if (is.data.frame(errors)) {
398 apply(errors, 1, function(warning) paste(warning[1], ": ", warning[2]))
399 } else {
400 lapply(errors, function(error) paste(error, collapse = " "))
401 }
402 message(paste(warning_msgs, collapse = "\n"))
Marc Kupietzf9129592025-01-26 19:17:54 +0100403 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100404 }
Marc Kupietza4675722022-02-23 23:55:15 +0100405 return(invisible(NULL))
406 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100407
408 # Process JSON response or raw text based on `json` parameter
409 if (json) {
410 content_type <- resp |> httr2::resp_content_type()
411 if (!content_type %in% c("application/json", "application/ld+json")) {
412 message("API did not return JSON")
Marc Kupietza4675722022-02-23 23:55:15 +0100413 return(invisible(NULL))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100414 }
Marc Kupietz04814f22023-04-16 17:13:27 +0200415
Marc Kupietzf9129592025-01-26 19:17:54 +0100416 result <- tryCatch(
417 resp |> httr2::resp_body_string() |> jsonlite::fromJSON(),
418 error = function(e) {
419 message("Failed to parse JSON: ", e$message)
420 return(NULL)
421 }
422 )
423
424 # Handle warnings in the response (if any)
425 if (!is.null(result$warnings)) {
426 warnings <- result$warnings
427 warning_msgs <- if (is.data.frame(warnings)) {
428 apply(warnings, 1, function(warning) paste(warning[1], ": ", warning[2]))
429 } else {
430 lapply(warnings, function(warning) paste(warning, collapse = " "))
431 }
432 message(paste(warning_msgs, collapse = "\n"))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100433 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100434 } else {
435 result <- resp |> httr2::resp_body_string()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200436 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100437
438 # Save to cache if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100439 if (cache) {
Marc Kupietzb49afa02020-06-04 15:50:29 +0200440 R.cache::saveCache(result, key = list(url, kco@accessToken, kco@indexRevision), dir = KorAPCacheSubDir(), compress = TRUE)
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100441 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100442
443 # Return headers and content as a list if `getHeaders` is TRUE
Marc Kupietzb49afa02020-06-04 15:50:29 +0200444 if (getHeaders) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100445 list(headers = resp |> httr2::resp_headers(), content = result)
Marc Kupietzb49afa02020-06-04 15:50:29 +0200446 } else {
447 result
448 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200449})
450
Marc Kupietz0a96b282019-10-01 11:05:31 +0200451setGeneric("clearCache", function(kco) standardGeneric("clearCache") )
452
453#' @aliases clearCache
454#' @rdname KorAPConnection-class
455#' @export
456setMethod("clearCache", "KorAPConnection", function(kco) {
457 R.cache::clearCache(dir=KorAPCacheSubDir())
458})
459
Marc Kupietze95108e2019-09-18 13:23:58 +0200460#' @rdname KorAPConnection-class
461#' @param object KorAPConnection object
462#' @export
463setMethod("show", "KorAPConnection", function(object) {
464 cat("<KorAPConnection>", "\n")
465 cat("apiUrl: ", object@apiUrl, "\n")
466})
467
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200468##' Funtion KorAPConnection()
469##'
470##' Wrappper function for new("KorAPConnection")
471##'
472##' @rdname KorAPConnection-constructor
473##' @name KorAPConnection-constructor
474##' @export
475## XKorAPConnection <- function(...) new("KorAPConnection", ...)