blob: f2d65a8fb551b10544741a2ef57d8a997c0c6119 [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 Kupietza824d502025-05-02 15:40:23 +020031KorAPConnection <- 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 +010032
Marc Kupietza824d502025-05-02 15:40:23 +020033generic_kor_app_id <- "99FbPHH7RrN36hbndF7b6f"
Marc Kupietz62b17892025-02-01 18:26:45 +010034
Marc Kupietza824d502025-05-02 15:40:23 +020035kustvakt_redirect_uri <- "http://localhost:1410/"
36kustvakt_auth_path <- "settings/oauth/authorize"
Marc Kupietz62b17892025-02-01 18:26:45 +010037
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 Kupietza824d502025-05-02 15:40:23 +0200106#' kcon <- KorAPConnection(verbose = TRUE, accessToken = "e739u6eOzkwADQPdVChxFg")
107#' kq <- corpusQuery(kcon, "Ameisenplage", metadataOnly = FALSE)
Marc Kupietz4862b862019-11-07 10:13:53 +0100108#' 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")) |
Marc Kupietza824d502025-05-02 15:40:23 +0200117 Sys.getenv("KORAP_URL") == "") {
Marc Kupietzb79fd442025-03-26 10:25:03 +0100118 "https://korap.ids-mannheim.de/"
Marc Kupietza824d502025-05-02 15:40:23 +0200119 } else {
120 Sys.getenv("KORAP_URL")
121 },
122 apiVersion = "v1.0",
Marc Kupietzb79fd442025-03-26 10:25:03 +0100123 apiUrl,
124 accessToken = getAccessToken(KorAPUrl),
125 oauthClient = NULL,
126 oauthScope = "search match_info",
127 authorizationSupported = TRUE,
128 userAgent = "R-KorAP-Client",
129 timeout = 240,
130 verbose = FALSE,
131 cache = TRUE) {
132 .Object <- callNextMethod()
133 m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
134 .Object@KorAPUrl <- regmatches(KorAPUrl, m)
Marc Kupietza824d502025-05-02 15:40:23 +0200135 if (!endsWith(.Object@KorAPUrl, "/")) {
Marc Kupietzb79fd442025-03-26 10:25:03 +0100136 .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
137 }
138 if (missing(apiUrl)) {
Marc Kupietza824d502025-05-02 15:40:23 +0200139 .Object@apiUrl <- paste0(.Object@KorAPUrl, "api/", apiVersion, "/")
140 } else {
141 .Object@apiUrl <- apiUrl
142 }
143 .Object@accessToken <- accessToken
144 .Object@oauthClient <- oauthClient
145 .Object@apiVersion <- apiVersion
146 .Object@userAgent <- userAgent
147 .Object@oauthScope <- oauthScope
148 .Object@authorizationSupported <- authorizationSupported
149 .Object@timeout <- timeout
150 .Object@verbose <- verbose
151 .Object@cache <- cache
152 .Object@welcome <- apiCall(.Object, .Object@apiUrl, json = FALSE, cache = FALSE, getHeaders = TRUE)
153 if (!is.null(.Object@welcome)) {
154 message(.Object@welcome[[2]])
155 resp <- httr2::request(.Object@KorAPUrl) |>
156 httr2::req_url_path_append(kustvakt_auth_path) |>
157 httr2::req_error(is_error = \(resp) FALSE) |>
158 httr2::req_perform()
159 .Object@authorizationSupported <- (httr2::resp_status(resp) == 200)
Marc Kupietz62b17892025-02-01 18:26:45 +0100160
Marc Kupietza824d502025-05-02 15:40:23 +0200161 .Object@indexRevision <- .Object@welcome[[1]][["x-index-revision"]]
162 } else {
163 if (grepl(.Object@KorAPUrl, .Object@apiUrl)) {
164 message("Could not connect to KorAP instance ", .Object@KorAPUrl)
165 } else {
166 message("Could not connect to KorAP API at ", .Object@apiUrl)
167 }
168 }
169 .Object
170})
Marc Kupietze95108e2019-09-18 13:23:58 +0200171
Marc Kupietza96537f2019-11-09 23:07:44 +0100172
Marc Kupietzb956b812019-11-25 17:53:13 +0100173accessTokenServiceName <- "RKorAPClientAccessToken"
Marc Kupietz4862b862019-11-07 10:13:53 +0100174
Marc Kupietza824d502025-05-02 15:40:23 +0200175setGeneric("persistAccessToken", function(kco, ...) standardGeneric("persistAccessToken"))
Marc Kupietz4862b862019-11-07 10:13:53 +0100176
Marc Kupietza4f51d72025-01-25 16:23:18 +0100177#' Persist current access token in keyring
178#'
179#' @param kco KorAPConnection object
180#' @param accessToken access token to be persisted. If not supplied, the current access token of the KorAPConnection object will be used.
181#' @return KorAPConnection object.
182#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100183#' @aliases persistAccessToken
Marc Kupietza4f51d72025-01-25 16:23:18 +0100184#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100185#' @import keyring
186#' @export
Marc Kupietza4f51d72025-01-25 16:23:18 +0100187#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100188#' @examples
189#' \dontrun{
Marc Kupietza824d502025-05-02 15:40:23 +0200190#' kco <- KorAPConnection(accessToken = "e739u6eOzkwADQPdVChxFg")
Marc Kupietzb956b812019-11-25 17:53:13 +0100191#' persistAccessToken(kco)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100192#'
Marc Kupietza824d502025-05-02 15:40:23 +0200193#' kco <- KorAPConnection() %>%
194#' auth(app_id = "<my application id>") %>%
195#' persistAccessToken()
Marc Kupietz4862b862019-11-07 10:13:53 +0100196#' }
197#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100198#' @seealso [clearAccessToken()], [auth()]
199#'
Marc Kupietza824d502025-05-02 15:40:23 +0200200setMethod("persistAccessToken", "KorAPConnection", function(kco, accessToken = kco@accessToken) {
201 if (!is.null(kco@oauthClient)) {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100202 warning("Short lived access tokens from a confidential application cannot be persisted.")
203 return(kco)
204 }
Marc Kupietza824d502025-05-02 15:40:23 +0200205 if (is.null(accessToken)) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100206 stop("It seems that you have not supplied any access token that could be persisted.", call. = FALSE)
Marc Kupietza824d502025-05-02 15:40:23 +0200207 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100208
Marc Kupietzb956b812019-11-25 17:53:13 +0100209 kco@accessToken <- accessToken
210 key_set_with_value(accessTokenServiceName, kco@KorAPUrl, accessToken)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100211 return(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100212})
213
Marc Kupietza824d502025-05-02 15:40:23 +0200214setGeneric("clearAccessToken", function(kco) standardGeneric("clearAccessToken"))
Marc Kupietz4862b862019-11-07 10:13:53 +0100215
Marc Kupietza4f51d72025-01-25 16:23:18 +0100216#' Clear access token from keyring and KorAPConnection object
217#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100218#' @aliases clearAccessToken
Marc Kupietz4862b862019-11-07 10:13:53 +0100219#' @import keyring
Marc Kupietza4f51d72025-01-25 16:23:18 +0100220#' @param kco KorAPConnection object
221#' @return KorAPConnection object with access token set to `NULL`.
Marc Kupietz4862b862019-11-07 10:13:53 +0100222#' @export
223#' @examples
Marc Kupietza4f51d72025-01-25 16:23:18 +0100224#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100225#' kco <- KorAPConnection()
Marc Kupietza4f51d72025-01-25 16:23:18 +0100226#' kco <- clearAccessToken(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100227#' }
228#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100229#' @seealso [persistAccessToken()]
230#'
Marc Kupietza824d502025-05-02 15:40:23 +0200231setMethod("clearAccessToken", "KorAPConnection", function(kco) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100232 key_delete(accessTokenServiceName, kco@KorAPUrl)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100233 kco@accessToken <- NULL
234 kco
Marc Kupietz4862b862019-11-07 10:13:53 +0100235})
236
Marc Kupietza4f51d72025-01-25 16:23:18 +0100237
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100238oauthRefresh <- function(req, client, scope, kco) {
Marc Kupietza824d502025-05-02 15:40:23 +0200239 httr2::req_oauth_auth_code(req, client,
240 scope = scope,
241 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
242 redirect_uri = kustvakt_redirect_uri,
243 cache_key = kco@KorAPUrl
244 )
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100245}
246
Marc Kupietza824d502025-05-02 15:40:23 +0200247setGeneric("auth", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) standardGeneric("auth"))
Marc Kupietza4f51d72025-01-25 16:23:18 +0100248
249#' Authorize RKorAPClient
250#'
251#' @aliases auth
252#'
253#' @description
254#' `r lifecycle::badge("experimental")`
255#'
256#' Authorize RKorAPClient to make KorAP queries and download results on behalf of the user.
257#'
258#' @param kco KorAPConnection object
259#' @param app_id OAuth2 application id. Defaults to the generic KorAP client application id.
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100260#' @param app_secret OAuth2 application secret. Used with confidential client applications. Defaults to `NULL`.
Marc Kupietza4f51d72025-01-25 16:23:18 +0100261#' @param scope OAuth2 scope. Defaults to "search match_info".
262#' @return KorAPConnection object with access token set in `@accessToken`.
263#'
264#' @importFrom httr2 oauth_client oauth_flow_auth_code
265#' @examples
266#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100267#' kco <- KorAPConnection(verbose = TRUE) %>% auth()
Marc Kupietza5501652025-01-28 20:25:42 +0100268#' df <- collocationAnalysis(kco, "focus([marmot/p=ADJA] {Ameisenplage})",
Marc Kupietza824d502025-05-02 15:40:23 +0200269#' leftContextSize = 1, rightContextSize = 0
270#' )
Marc Kupietza4f51d72025-01-25 16:23:18 +0100271#' }
272#'
273#' @seealso [persistAccessToken()], [clearAccessToken()]
274#'
275#' @export
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100276setMethod("auth", "KorAPConnection", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) {
Marc Kupietz62b17892025-02-01 18:26:45 +0100277 if (kco@authorizationSupported == FALSE) {
278 log_info(kco@verbose, "Authorization is not supported by this KorAP instance.")
279 return(kco)
280 }
Marc Kupietza824d502025-05-02 15:40:23 +0200281 if (kco@KorAPUrl != "https://korap.ids-mannheim.de/" & app_id == generic_kor_app_id) {
Marc Kupietza4f51d72025-01-25 16:23:18 +0100282 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))
283 return(kco)
284 }
285 if (is.null(kco@accessToken) || is.null(kco@welcome)) { # if access token is not set or invalid
Marc Kupietza824d502025-05-02 15:40:23 +0200286 client <- if (!is.null(kco@oauthClient)) {
287 kco@oauthClient
288 } else {
Marc Kupietza4f51d72025-01-25 16:23:18 +0100289 httr2::oauth_client(
Marc Kupietza824d502025-05-02 15:40:23 +0200290 id = app_id,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100291 secret = app_secret,
Marc Kupietza4f51d72025-01-25 16:23:18 +0100292 token_url = paste0(kco@apiUrl, "oauth2/token")
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100293 )
Marc Kupietza824d502025-05-02 15:40:23 +0200294 }
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100295 if (is.null(app_secret)) {
Marc Kupietza824d502025-05-02 15:40:23 +0200296 kco@accessToken <- (client |>
Marc Kupietza4f51d72025-01-25 16:23:18 +0100297 httr2::oauth_flow_auth_code(
298 scope = scope,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100299 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
Marc Kupietz62b17892025-02-01 18:26:45 +0100300 redirect_uri = kustvakt_redirect_uri
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100301 ))$access_token
302 log_info(kco@verbose, "Client authorized. New access token set.")
303 } else {
304 kco@oauthClient <- client
305 kco@oauthScope <- scope
306 req <- request(kco@apiUrl) |>
307 oauthRefresh(client, scope, kco) |>
308 req_perform()
309 log_info(kco@verbose, "Client authorized. Short lived access token will be refreshed automatically.")
310 }
Marc Kupietza4f51d72025-01-25 16:23:18 +0100311 } else {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100312 log_info(kco@verbose, "Access token already set.")
Marc Kupietza4f51d72025-01-25 16:23:18 +0100313 }
314 return(kco)
315})
316
317
318
Marc Kupietz4862b862019-11-07 10:13:53 +0100319#' @import keyring
Marc Kupietzb956b812019-11-25 17:53:13 +0100320getAccessToken <- function(KorAPUrl) {
Marc Kupietza824d502025-05-02 15:40:23 +0200321 keyList <- tryCatch(
322 withCallingHandlers(key_list(service = accessTokenServiceName),
323 warning = function(w) invokeRestart("muffleWarning"),
324 error = function(e) {
325 return(NULL)
326 }
327 ),
328 error = function(e) { }
329 )
330 if (KorAPUrl %in% keyList$username) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100331 key_get(accessTokenServiceName, KorAPUrl)
Marc Kupietza824d502025-05-02 15:40:23 +0200332 } else {
Marc Kupietzfd9e7492019-11-08 15:45:18 +0100333 NULL
Marc Kupietza824d502025-05-02 15:40:23 +0200334 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100335}
Marc Kupietz0a96b282019-10-01 11:05:31 +0200336
Marc Kupietz581a29b2021-09-04 20:51:04 +0200337
Marc Kupietz62b17892025-02-01 18:26:45 +0100338warnIfNotAuthorized <- function(kco) {
339 if (kco@authorizationSupported & is.null(kco@accessToken) & is.null(kco@oauthClient)) {
Marc Kupietz581a29b2021-09-04 20:51:04 +0200340 warning(
341 paste0(
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100342 "In order to receive KWICSs also from corpora with restricted licenses, you may need to\n",
343 "authorize your application with an access token or the auth() method.\n",
344 "To generate an access token, login to KorAP and navigate to KorAP's OAuth settings <",
Marc Kupietz581a29b2021-09-04 20:51:04 +0200345 kco@KorAPUrl,
346 "settings/oauth#page-top>"
347 )
348 )
349 }
350}
351
Marc Kupietz0a96b282019-10-01 11:05:31 +0200352KorAPCacheSubDir <- function() {
Marc Kupietza824d502025-05-02 15:40:23 +0200353 paste0(
354 "RKorAPClient_",
355 gsub(
356 "^([0-9]+\\.[0-9]+).*",
357 "\\1",
358 packageVersion("RKorAPClient"),
359 perl = TRUE
360 )
361 )
Marc Kupietz0a96b282019-10-01 11:05:31 +0200362}
363
Marc Kupietza824d502025-05-02 15:40:23 +0200364setGeneric("apiCall", function(kco, ...) standardGeneric("apiCall"))
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200365
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200366## quiets concerns of R CMD check re: the .'s that appear in pipelines
Marc Kupietzef1ef4a2025-02-19 12:12:40 +0100367utils::globalVariables(c("."))
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200368
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200369#' @aliases apiCall
370#' @rdname KorAPConnection-class
371#' @param kco KorAPConnection object
372#' @param url request url
Marc Kupietzf9129592025-01-26 19:17:54 +0100373#' @param json logical that determines if JSON result is expected
Marc Kupietzb49afa02020-06-04 15:50:29 +0200374#' @param getHeaders logical that determines if headers and content should be returned (as a list)
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200375#' @importFrom jsonlite fromJSON
Marc Kupietza4675722022-02-23 23:55:15 +0100376#' @importFrom curl has_internet
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100377#' @import httr2
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200378#' @export
Marc Kupietzf9129592025-01-26 19:17:54 +0100379setMethod("apiCall", "KorAPConnection", function(kco, url, json = TRUE, getHeaders = FALSE, cache = kco@cache, timeout = kco@timeout) {
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100380 result <- ""
Marc Kupietzf9129592025-01-26 19:17:54 +0100381
382 # Handle caching if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100383 if (cache) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100384 result <- R.cache::loadCache(dir = KorAPCacheSubDir(), key = list(url, kco@accessToken, kco@indexRevision))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100385 if (!is.null(result)) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100386 if (!is.null(result$meta)) result$meta$cached <- "local"
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100387 return(result)
Marc Kupietz0a96b282019-10-01 11:05:31 +0200388 }
389 }
Marc Kupietza4675722022-02-23 23:55:15 +0100390
Marc Kupietzf9129592025-01-26 19:17:54 +0100391 # Check for internet connection
Marc Kupietza4675722022-02-23 23:55:15 +0100392 if (!curl::has_internet()) {
393 message("No internet connection.")
394 return(invisible(NULL))
395 }
396
Marc Kupietzf9129592025-01-26 19:17:54 +0100397 # Create the request
398 req <- httr2::request(url) |>
399 httr2::req_user_agent(kco@userAgent) |>
400 httr2::req_timeout(timeout)
Marc Kupietza4675722022-02-23 23:55:15 +0100401
Marc Kupietz03402e72025-05-02 15:39:40 +0200402 if (!is.null(kco@oauthClient)) {
403 req <- req |> oauthRefresh(kco@oauthClient, scope = kco@oauthScope, kco)
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100404 } else if (!is.null(kco@accessToken)) {
405 req <- req |> httr2::req_auth_bearer_token(kco@accessToken)
Marc Kupietzf9129592025-01-26 19:17:54 +0100406 }
407
Marc Kupietzd36ee552025-05-02 20:42:50 +0200408 resp <- tryCatch(req |> httr2::req_perform(),
409 error = function(e) {
410 if (is.null(e$resp)) {
411 message(paste("Error: ", e$message, collapse = " "), if ("parent" %in% names(e)) paste0("\n", e$parent$message) else "")
412 return(invisible(NULL))
413 }
414 return(e$resp)
415 }
416 )
Marc Kupietz03402e72025-05-02 15:39:40 +0200417
418 if (is.null(resp)) {
Marc Kupietz03402e72025-05-02 15:39:40 +0200419 return(invisible(NULL))
420 }
Marc Kupietz62b17892025-02-01 18:26:45 +0100421
Marc Kupietzf9129592025-01-26 19:17:54 +0100422 if (resp |> httr2::resp_status() != 200) {
Marc Kupietzd36ee552025-05-02 20:42:50 +0200423 message("Error: Request failed with status ", resp |> httr2::resp_status(), ": ", resp |> httr2::resp_status_desc())
Marc Kupietz62b17892025-02-01 18:26:45 +0100424 if (resp |> httr2::resp_content_type() == "application/json") {
425 result <- tryCatch(
426 resp |> httr2::resp_body_json(),
427 error = function(e) {
428 message("Failed to parse json with error details: ", e$message)
429 return(NULL)
430 }
431 )
432 # Handle errors in the response (if any)
433 if (!is.null(result$errors)) {
434 errors <- result$errors
435 warning_msgs <- if (is.data.frame(errors)) {
436 apply(errors, 1, function(warning) paste(warning[1], ": ", warning[2]))
437 } else {
438 lapply(errors, function(error) paste(error, collapse = " "))
439 }
Marc Kupietz03402e72025-05-02 15:39:40 +0200440 message(paste("Warning: ", warning_msgs, collapse = "\n"))
Marc Kupietzf9129592025-01-26 19:17:54 +0100441 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100442 }
Marc Kupietza4675722022-02-23 23:55:15 +0100443 return(invisible(NULL))
444 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100445
446 # Process JSON response or raw text based on `json` parameter
447 if (json) {
448 content_type <- resp |> httr2::resp_content_type()
449 if (!content_type %in% c("application/json", "application/ld+json")) {
450 message("API did not return JSON")
Marc Kupietza4675722022-02-23 23:55:15 +0100451 return(invisible(NULL))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100452 }
Marc Kupietz04814f22023-04-16 17:13:27 +0200453
Marc Kupietzf9129592025-01-26 19:17:54 +0100454 result <- tryCatch(
455 resp |> httr2::resp_body_string() |> jsonlite::fromJSON(),
456 error = function(e) {
457 message("Failed to parse JSON: ", e$message)
458 return(NULL)
459 }
460 )
461
462 # Handle warnings in the response (if any)
463 if (!is.null(result$warnings)) {
464 warnings <- result$warnings
465 warning_msgs <- if (is.data.frame(warnings)) {
466 apply(warnings, 1, function(warning) paste(warning[1], ": ", warning[2]))
467 } else {
468 lapply(warnings, function(warning) paste(warning, collapse = " "))
469 }
Marc Kupietz03402e72025-05-02 15:39:40 +0200470 message(paste0("\nWarning: ", paste(warning_msgs, collapse = " ")))
471 if (cache & any(grepl("682", warning_msgs))) {
472 cache <- FALSE
Marc Kupietzd36ee552025-05-02 20:42:50 +0200473 log_info(kco@verbose, "Caching will be skipped because of warnings ")
Marc Kupietz03402e72025-05-02 15:39:40 +0200474 }
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100475 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100476 } else {
477 result <- resp |> httr2::resp_body_string()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200478 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100479
480 # Save to cache if enabled
Marc Kupietz03402e72025-05-02 15:39:40 +0200481 if (cache && resp |> httr2::resp_status() == 200) {
Marc Kupietzb49afa02020-06-04 15:50:29 +0200482 R.cache::saveCache(result, key = list(url, kco@accessToken, kco@indexRevision), dir = KorAPCacheSubDir(), compress = TRUE)
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100483 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100484
485 # Return headers and content as a list if `getHeaders` is TRUE
Marc Kupietzb49afa02020-06-04 15:50:29 +0200486 if (getHeaders) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100487 list(headers = resp |> httr2::resp_headers(), content = result)
Marc Kupietzb49afa02020-06-04 15:50:29 +0200488 } else {
489 result
490 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200491})
492
Marc Kupietza824d502025-05-02 15:40:23 +0200493setGeneric("clearCache", function(kco) standardGeneric("clearCache"))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200494
495#' @aliases clearCache
496#' @rdname KorAPConnection-class
497#' @export
Marc Kupietza824d502025-05-02 15:40:23 +0200498setMethod("clearCache", "KorAPConnection", function(kco) {
499 R.cache::clearCache(dir = KorAPCacheSubDir())
Marc Kupietz0a96b282019-10-01 11:05:31 +0200500})
501
Marc Kupietze95108e2019-09-18 13:23:58 +0200502#' @rdname KorAPConnection-class
503#' @param object KorAPConnection object
504#' @export
505setMethod("show", "KorAPConnection", function(object) {
506 cat("<KorAPConnection>", "\n")
507 cat("apiUrl: ", object@apiUrl, "\n")
508})
509
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200510##' Funtion KorAPConnection()
511##'
Marc Kupietz617266d2025-02-27 10:43:07 +0100512##' Wrappper function for KorAPConnection()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200513##'
514##' @rdname KorAPConnection-constructor
515##' @name KorAPConnection-constructor
516##' @export
Marc Kupietz617266d2025-02-27 10:43:07 +0100517## XKorAPConnection <- function(...) KorAPConnection(...)