blob: fe6b9f178fb5d3ce1ddecd5c6151ec8f3840cf2c [file] [log] [blame]
Marc Kupietzfd9e7492019-11-08 15:45:18 +01001################################################################################
2# Use setClassUnion to define the unholy NULL-data union as a virtual class.
3################################################################################
4setClassUnion("characterOrNULL", c("character", "NULL"))
Marc Kupietza4675722022-02-23 23:55:15 +01005setClassUnion("listOrNULL", c("list", "NULL"))
Marc Kupietzf83d59a2025-02-01 14:48:30 +01006# setOldClass("httr2_oauth_client")
Marc Kupietzfd9e7492019-11-08 15:45:18 +01007
Marc Kupietza8c40f42025-06-24 15:49:52 +02008#' Connect to KorAP Server
Marc Kupietz25aebc32019-09-16 18:40:50 +02009#'
Marc Kupietza8c40f42025-06-24 15:49:52 +020010#' `KorAPConnection()` creates a connection to a KorAP server for corpus queries.
11#' This is your starting point for all corpus analysis tasks.
Marc Kupietze95108e2019-09-18 13:23:58 +020012#'
Marc Kupietza8c40f42025-06-24 15:49:52 +020013#' Use `KorAPConnection()` to connect, then `corpusQuery()` to search, and
14#' `fetchAll()` to retrieve results. For authorized access to restricted corpora,
15#' use `auth()` or provide an `accessToken`.
16#'
17#' @section Basic Workflow:
18#' ```r
19#' # Connect to KorAP
20#' kcon <- KorAPConnection()
21#'
22#' # Search for a term
23#' query <- corpusQuery(kcon, "Ameisenplage")
24#'
25#' # Get all results
26#' results <- fetchAll(query)
27#' ```
28#'
29#' @section Authorization:
30#' For access to restricted corpora, authorize your connection:
31#' ```r
32#' kcon <- KorAPConnection() |> auth()
33#' ```
34#'
Marc Kupietzf9914bb2025-06-25 09:57:55 +020035#' @param KorAPUrl URL of the web user interface of the KorAP server instance you want to access.
36#' Defaults to the environment variable `KORAP_URL` if set and to the IDS Mannheim KorAP main instance
37#' to query DeReKo, otherwise.
38#' @param apiVersion which version of KorAP's API you want to connect to. Defaults to "v1.0".
39#' @param apiUrl URL of the KorAP web service. If not provided, it will be constructed from KorAPUrl and apiVersion.
40#' @param accessToken OAuth2 access token. For queries on corpus parts with restricted
41#' access (e.g. textual queries on IPR protected data), you need to authorize
42#' your application with an access token.
43#' You can obtain an access token in the OAuth settings of your KorAP web interface.
44#'
45#' More details are explained in the
46#' [authorization section](https://github.com/KorAP/RKorAPClient#authorization)
47#' of the RKorAPClient Readme on GitHub.
48#'
49#' To use authorization based on an access token
50#' in subsequent queries, initialize your KorAP connection with:
51#'
52#' ```
53#' kco <- KorAPConnection(accessToken="<access token>")
54#' ```
55#'
56#' In order to make the API
57#' token persistent for the currently used `KorAPUrl` (you can have one
58#' token per KorAPUrl / KorAP server instance), use:
59#'
60#' ```
61#' persistAccessToken(kco)
62#' ```
63#'
64#' This will store it in your keyring using the
65#' [keyring::keyring-package]. Subsequent KorAPConnection() calls will
66#' then automatically retrieve the token from your keying. To stop using a
67#' persisted token, call `clearAccessToken(kco)`. Please note that for
68#' DeReKo, authorized queries will behave differently inside and outside the
69#' IDS, because of the special license situation. This concerns also cached
70#' results which do not take into account from where a request was issued. If
71#' you experience problems or unexpected results, please try `kco <-
72#' KorAPConnection(cache=FALSE)` or use
73#' [clearCache()] to clear the cache completely.
74#'
75#' An alternative to using an access token is to use a browser-based oauth2 workflow
76#' to obtain an access token. This can be done with the [auth()] method.
77#' @param oauthClient OAuth2 client object (advanced users only).
78#' @param oauthScope OAuth2 scope. Defaults to "search match_info".
79#' @param authorizationSupported logical that indicates if authorization is supported/necessary for the current KorAP instance. Automatically set during initialization.
80#' @param userAgent user agent string. Defaults to "R-KorAP-Client".
81#' @param timeout timeout in seconds for API requests (this does not influence server internal timeouts). Defaults to 240 seconds.
82#' @param verbose logical that decides whether following operations will default to
83#' be verbose. Defaults to FALSE.
84#' @param cache logical that decides if API calls are cached locally. You can clear
85#' the cache with [clearCache()]. Defaults to TRUE.
86#'
87#' @return [KorAPConnection()] object that can be used e.g. with [corpusQuery()]
88#'
Marc Kupietza8c40f42025-06-24 15:49:52 +020089#' @details
90#' The KorAPConnection object contains various configuration slots for advanced users:
91#' KorAPUrl (server URL), apiVersion, accessToken (OAuth2 token),
92#' timeout (request timeout), verbose (logging), cache (local caching),
93#' and other technical parameters. Most users can ignore these implementation details.
94#'
95#' @family initialization functions
Marc Kupietz0a96b282019-10-01 11:05:31 +020096#' @import R.cache
Marc Kupietze95108e2019-09-18 13:23:58 +020097#' @import utils
98#' @import methods
Marc Kupietz6dfeed92025-06-03 11:58:06 +020099#' @include logging.R
Marc Kupietza81343d2022-09-06 12:32:10 +0200100
Marc Kupietze95108e2019-09-18 13:23:58 +0200101#' @export
Marc Kupietza824d502025-05-02 15:40:23 +0200102KorAPConnection <- 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 +0100103
Marc Kupietza824d502025-05-02 15:40:23 +0200104generic_kor_app_id <- "99FbPHH7RrN36hbndF7b6f"
Marc Kupietz62b17892025-02-01 18:26:45 +0100105
Marc Kupietza824d502025-05-02 15:40:23 +0200106kustvakt_redirect_uri <- "http://localhost:1410/"
107kustvakt_auth_path <- "settings/oauth/authorize"
Marc Kupietz62b17892025-02-01 18:26:45 +0100108
Marc Kupietze95108e2019-09-18 13:23:58 +0200109
Marc Kupietza8c40f42025-06-24 15:49:52 +0200110#' Initialize KorAPConnection object
111#' @keywords internal
Marc Kupietze95108e2019-09-18 13:23:58 +0200112#' @param .Object KorAPConnection object
Marc Kupietza81343d2022-09-06 12:32:10 +0200113#' @param KorAPUrl URL of the web user interface of the KorAP server instance you want to access.
Marc Kupietzb79fd442025-03-26 10:25:03 +0100114#' Defaults to the environment variable `KORAP_URL` if set and to the IDS Mannheim KorAP main instance
Marc Kupietzf9914bb2025-06-25 09:57:55 +0200115#' (<https://korap.ids-mannheim.de/>) to query DeReKo, otherwise.
116#' In order to access the KorAP instance at the DNB to query the contemporary fiction corpus DeLiKo@@DNB,
117#' for example, set `KorAPUrl` to `https://korap.dnb.de/`.
Marc Kupietze95108e2019-09-18 13:23:58 +0200118#' @param apiVersion which version of KorAP's API you want to connect to.
119#' @param apiUrl URL of the KorAP web service.
Marc Kupietz132f0052023-04-16 14:23:05 +0200120#' @param accessToken OAuth2 access token. For queries on corpus parts with restricted
121#' access (e.g. textual queries on IPR protected data), you need to authorize
122#' your application with an access token.
Marc Kupietz62b17892025-02-01 18:26:45 +0100123#' You can obtain an access token in the OAuth settings of your KorAP web interface.
Marc Kupietza4f51d72025-01-25 16:23:18 +0100124#'
125#' More details are explained in the
Marc Kupietz132f0052023-04-16 14:23:05 +0200126#' [authorization section](https://github.com/KorAP/RKorAPClient#authorization)
127#' of the RKorAPClient Readme on GitHub.
128#'
129#' To use authorization based on an access token
130#' in subsequent queries, initialize your KorAP connection with:
131#'
132#' ```
Marc Kupietz617266d2025-02-27 10:43:07 +0100133#' kco <- KorAPConnection(accessToken="<access token>")
Marc Kupietz132f0052023-04-16 14:23:05 +0200134#' ```
135#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100136#' In order to make the API
Marc Kupietz67edcb52021-09-20 21:54:24 +0200137#' token persistent for the currently used `KorAPUrl` (you can have one
Marc Kupietz132f0052023-04-16 14:23:05 +0200138#' token per KorAPUrl / KorAP server instance), use:
139#'
140#' ```
141#' persistAccessToken(kco)
142#' ```
143#'
144#' This will store it in your keyring using the
Marc Kupietz617266d2025-02-27 10:43:07 +0100145#' [keyring::keyring-package]. Subsequent KorAPConnection() calls will
Marc Kupietz4862b862019-11-07 10:13:53 +0100146#' then automatically retrieve the token from your keying. To stop using a
Marc Kupietz67edcb52021-09-20 21:54:24 +0200147#' persisted token, call `clearAccessToken(kco)`. Please note that for
Marc Kupietz4862b862019-11-07 10:13:53 +0100148#' DeReKo, authorized queries will behave differently inside and outside the
149#' IDS, because of the special license situation. This concerns also cached
150#' results which do not take into account from where a request was issued. If
Marc Kupietz67edcb52021-09-20 21:54:24 +0200151#' you experience problems or unexpected results, please try `kco <-
Marc Kupietz617266d2025-02-27 10:43:07 +0100152#' KorAPConnection(cache=FALSE)` or use
Marc Kupietz67edcb52021-09-20 21:54:24 +0200153#' [clearCache()] to clear the cache completely.
Marc Kupietz132f0052023-04-16 14:23:05 +0200154#'
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100155#' An alternative to using an access token is to use a browser-based oauth2 workflow
156#' to obtain an access token. This can be done with the [auth()] method.
157#'
158#' @param oauthClient OAuth2 client object.
159#' @param oauthScope OAuth2 scope.
Marc Kupietz62b17892025-02-01 18:26:45 +0100160#' @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 +0200161#' @param userAgent user agent string.
Marc Kupietza81343d2022-09-06 12:32:10 +0200162#' @param timeout tineout in seconds for API requests (this does not influence server internal timeouts).
163#' @param verbose logical that decides whether following operations will default to
Marc Kupietz4862b862019-11-07 10:13:53 +0100164#' be verbose.
Marc Kupietza81343d2022-09-06 12:32:10 +0200165#' @param cache logical that decides if API calls are cached locally. You can clear
Marc Kupietz67edcb52021-09-20 21:54:24 +0200166#' the cache with [clearCache()].
167#' @return [KorAPConnection()] object that can be used e.g. with
168#' [corpusQuery()]
Marc Kupietze95108e2019-09-18 13:23:58 +0200169#'
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100170#' @import httr2
Marc Kupietze95108e2019-09-18 13:23:58 +0200171#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +0200172#' \dontrun{
173#'
Marc Kupietz617266d2025-02-27 10:43:07 +0100174#' kcon <- KorAPConnection(verbose = TRUE)
Marc Kupietze95108e2019-09-18 13:23:58 +0200175#' kq <- corpusQuery(kcon, "Ameisenplage")
Marc Kupietz5a519822019-09-20 21:43:52 +0200176#' kq <- fetchAll(kq)
Marc Kupietz05b22772020-02-18 21:58:42 +0100177#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +0200178#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100179#' \dontrun{
Marc Kupietz6ae76052021-09-21 10:34:00 +0200180#'
Marc Kupietza824d502025-05-02 15:40:23 +0200181#' kcon <- KorAPConnection(verbose = TRUE, accessToken = "e739u6eOzkwADQPdVChxFg")
182#' kq <- corpusQuery(kcon, "Ameisenplage", metadataOnly = FALSE)
Marc Kupietz4862b862019-11-07 10:13:53 +0100183#' kq <- fetchAll(kq)
184#' kq@collectedMatches$snippet
185#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +0200186#'
Marc Kupietzb79fd442025-03-26 10:25:03 +0100187
Marc Kupietz632cbd42019-09-06 16:04:51 +0200188#' @export
Marc Kupietzb79fd442025-03-26 10:25:03 +0100189setMethod("initialize", "KorAPConnection", function(.Object,
190 KorAPUrl = if (is.null(Sys.getenv("KORAP_URL")) |
Marc Kupietza824d502025-05-02 15:40:23 +0200191 Sys.getenv("KORAP_URL") == "") {
Marc Kupietzb79fd442025-03-26 10:25:03 +0100192 "https://korap.ids-mannheim.de/"
Marc Kupietza824d502025-05-02 15:40:23 +0200193 } else {
194 Sys.getenv("KORAP_URL")
195 },
196 apiVersion = "v1.0",
Marc Kupietzb79fd442025-03-26 10:25:03 +0100197 apiUrl,
198 accessToken = getAccessToken(KorAPUrl),
199 oauthClient = NULL,
200 oauthScope = "search match_info",
201 authorizationSupported = TRUE,
202 userAgent = "R-KorAP-Client",
203 timeout = 240,
204 verbose = FALSE,
205 cache = TRUE) {
206 .Object <- callNextMethod()
207 m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
208 .Object@KorAPUrl <- regmatches(KorAPUrl, m)
Marc Kupietza824d502025-05-02 15:40:23 +0200209 if (!endsWith(.Object@KorAPUrl, "/")) {
Marc Kupietzb79fd442025-03-26 10:25:03 +0100210 .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
211 }
212 if (missing(apiUrl)) {
Marc Kupietza824d502025-05-02 15:40:23 +0200213 .Object@apiUrl <- paste0(.Object@KorAPUrl, "api/", apiVersion, "/")
214 } else {
215 .Object@apiUrl <- apiUrl
216 }
217 .Object@accessToken <- accessToken
218 .Object@oauthClient <- oauthClient
219 .Object@apiVersion <- apiVersion
220 .Object@userAgent <- userAgent
221 .Object@oauthScope <- oauthScope
222 .Object@authorizationSupported <- authorizationSupported
223 .Object@timeout <- timeout
224 .Object@verbose <- verbose
225 .Object@cache <- cache
226 .Object@welcome <- apiCall(.Object, .Object@apiUrl, json = FALSE, cache = FALSE, getHeaders = TRUE)
227 if (!is.null(.Object@welcome)) {
228 message(.Object@welcome[[2]])
229 resp <- httr2::request(.Object@KorAPUrl) |>
230 httr2::req_url_path_append(kustvakt_auth_path) |>
231 httr2::req_error(is_error = \(resp) FALSE) |>
232 httr2::req_perform()
233 .Object@authorizationSupported <- (httr2::resp_status(resp) == 200)
Marc Kupietz62b17892025-02-01 18:26:45 +0100234
Marc Kupietza824d502025-05-02 15:40:23 +0200235 .Object@indexRevision <- .Object@welcome[[1]][["x-index-revision"]]
236 } else {
237 if (grepl(.Object@KorAPUrl, .Object@apiUrl)) {
238 message("Could not connect to KorAP instance ", .Object@KorAPUrl)
239 } else {
240 message("Could not connect to KorAP API at ", .Object@apiUrl)
241 }
242 }
243 .Object
244})
Marc Kupietze95108e2019-09-18 13:23:58 +0200245
Marc Kupietza96537f2019-11-09 23:07:44 +0100246
Marc Kupietzb956b812019-11-25 17:53:13 +0100247accessTokenServiceName <- "RKorAPClientAccessToken"
Marc Kupietz4862b862019-11-07 10:13:53 +0100248
Marc Kupietza824d502025-05-02 15:40:23 +0200249setGeneric("persistAccessToken", function(kco, ...) standardGeneric("persistAccessToken"))
Marc Kupietz4862b862019-11-07 10:13:53 +0100250
Marc Kupietza4f51d72025-01-25 16:23:18 +0100251#' Persist current access token in keyring
252#'
Marc Kupietza8c40f42025-06-24 15:49:52 +0200253#' @family initialization functions
Marc Kupietza4f51d72025-01-25 16:23:18 +0100254#' @param kco KorAPConnection object
255#' @param accessToken access token to be persisted. If not supplied, the current access token of the KorAPConnection object will be used.
256#' @return KorAPConnection object.
257#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100258#' @aliases persistAccessToken
Marc Kupietza4f51d72025-01-25 16:23:18 +0100259#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100260#' @import keyring
261#' @export
Marc Kupietza4f51d72025-01-25 16:23:18 +0100262#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100263#' @examples
264#' \dontrun{
Marc Kupietza824d502025-05-02 15:40:23 +0200265#' kco <- KorAPConnection(accessToken = "e739u6eOzkwADQPdVChxFg")
Marc Kupietzb956b812019-11-25 17:53:13 +0100266#' persistAccessToken(kco)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100267#'
Marc Kupietza824d502025-05-02 15:40:23 +0200268#' kco <- KorAPConnection() %>%
269#' auth(app_id = "<my application id>") %>%
270#' persistAccessToken()
Marc Kupietz4862b862019-11-07 10:13:53 +0100271#' }
272#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100273#' @seealso [clearAccessToken()], [auth()]
274#'
Marc Kupietza824d502025-05-02 15:40:23 +0200275setMethod("persistAccessToken", "KorAPConnection", function(kco, accessToken = kco@accessToken) {
276 if (!is.null(kco@oauthClient)) {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100277 warning("Short lived access tokens from a confidential application cannot be persisted.")
278 return(kco)
279 }
Marc Kupietza824d502025-05-02 15:40:23 +0200280 if (is.null(accessToken)) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100281 stop("It seems that you have not supplied any access token that could be persisted.", call. = FALSE)
Marc Kupietza824d502025-05-02 15:40:23 +0200282 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100283
Marc Kupietzb956b812019-11-25 17:53:13 +0100284 kco@accessToken <- accessToken
285 key_set_with_value(accessTokenServiceName, kco@KorAPUrl, accessToken)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100286 return(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100287})
288
Marc Kupietza824d502025-05-02 15:40:23 +0200289setGeneric("clearAccessToken", function(kco) standardGeneric("clearAccessToken"))
Marc Kupietz4862b862019-11-07 10:13:53 +0100290
Marc Kupietza4f51d72025-01-25 16:23:18 +0100291#' Clear access token from keyring and KorAPConnection object
292#'
Marc Kupietza8c40f42025-06-24 15:49:52 +0200293#' @family initialization functions
Marc Kupietzb956b812019-11-25 17:53:13 +0100294#' @aliases clearAccessToken
Marc Kupietz4862b862019-11-07 10:13:53 +0100295#' @import keyring
Marc Kupietza4f51d72025-01-25 16:23:18 +0100296#' @param kco KorAPConnection object
297#' @return KorAPConnection object with access token set to `NULL`.
Marc Kupietz4862b862019-11-07 10:13:53 +0100298#' @export
299#' @examples
Marc Kupietza4f51d72025-01-25 16:23:18 +0100300#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100301#' kco <- KorAPConnection()
Marc Kupietza4f51d72025-01-25 16:23:18 +0100302#' kco <- clearAccessToken(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100303#' }
304#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100305#' @seealso [persistAccessToken()]
306#'
Marc Kupietza824d502025-05-02 15:40:23 +0200307setMethod("clearAccessToken", "KorAPConnection", function(kco) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100308 key_delete(accessTokenServiceName, kco@KorAPUrl)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100309 kco@accessToken <- NULL
310 kco
Marc Kupietz4862b862019-11-07 10:13:53 +0100311})
312
Marc Kupietza4f51d72025-01-25 16:23:18 +0100313
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100314oauthRefresh <- function(req, client, scope, kco) {
Marc Kupietza824d502025-05-02 15:40:23 +0200315 httr2::req_oauth_auth_code(req, client,
316 scope = scope,
317 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
318 redirect_uri = kustvakt_redirect_uri,
319 cache_key = kco@KorAPUrl
320 )
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100321}
322
Marc Kupietza824d502025-05-02 15:40:23 +0200323setGeneric("auth", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) standardGeneric("auth"))
Marc Kupietza4f51d72025-01-25 16:23:18 +0100324
325#' Authorize RKorAPClient
326#'
Marc Kupietza8c40f42025-06-24 15:49:52 +0200327#' @family initialization functions
Marc Kupietza4f51d72025-01-25 16:23:18 +0100328#' @aliases auth
329#'
330#' @description
331#' `r lifecycle::badge("experimental")`
332#'
333#' Authorize RKorAPClient to make KorAP queries and download results on behalf of the user.
334#'
335#' @param kco KorAPConnection object
336#' @param app_id OAuth2 application id. Defaults to the generic KorAP client application id.
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100337#' @param app_secret OAuth2 application secret. Used with confidential client applications. Defaults to `NULL`.
Marc Kupietza4f51d72025-01-25 16:23:18 +0100338#' @param scope OAuth2 scope. Defaults to "search match_info".
339#' @return KorAPConnection object with access token set in `@accessToken`.
340#'
341#' @importFrom httr2 oauth_client oauth_flow_auth_code
342#' @examples
343#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100344#' kco <- KorAPConnection(verbose = TRUE) %>% auth()
Marc Kupietza5501652025-01-28 20:25:42 +0100345#' df <- collocationAnalysis(kco, "focus([marmot/p=ADJA] {Ameisenplage})",
Marc Kupietza824d502025-05-02 15:40:23 +0200346#' leftContextSize = 1, rightContextSize = 0
347#' )
Marc Kupietza4f51d72025-01-25 16:23:18 +0100348#' }
349#'
350#' @seealso [persistAccessToken()], [clearAccessToken()]
351#'
352#' @export
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100353setMethod("auth", "KorAPConnection", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) {
Marc Kupietz62b17892025-02-01 18:26:45 +0100354 if (kco@authorizationSupported == FALSE) {
355 log_info(kco@verbose, "Authorization is not supported by this KorAP instance.")
356 return(kco)
357 }
Marc Kupietza824d502025-05-02 15:40:23 +0200358 if (kco@KorAPUrl != "https://korap.ids-mannheim.de/" & app_id == generic_kor_app_id) {
Marc Kupietza4f51d72025-01-25 16:23:18 +0100359 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))
360 return(kco)
361 }
362 if (is.null(kco@accessToken) || is.null(kco@welcome)) { # if access token is not set or invalid
Marc Kupietza824d502025-05-02 15:40:23 +0200363 client <- if (!is.null(kco@oauthClient)) {
364 kco@oauthClient
365 } else {
Marc Kupietza4f51d72025-01-25 16:23:18 +0100366 httr2::oauth_client(
Marc Kupietza824d502025-05-02 15:40:23 +0200367 id = app_id,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100368 secret = app_secret,
Marc Kupietza4f51d72025-01-25 16:23:18 +0100369 token_url = paste0(kco@apiUrl, "oauth2/token")
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100370 )
Marc Kupietza824d502025-05-02 15:40:23 +0200371 }
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100372 if (is.null(app_secret)) {
Marc Kupietza824d502025-05-02 15:40:23 +0200373 kco@accessToken <- (client |>
Marc Kupietza4f51d72025-01-25 16:23:18 +0100374 httr2::oauth_flow_auth_code(
375 scope = scope,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100376 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
Marc Kupietz62b17892025-02-01 18:26:45 +0100377 redirect_uri = kustvakt_redirect_uri
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100378 ))$access_token
379 log_info(kco@verbose, "Client authorized. New access token set.")
380 } else {
381 kco@oauthClient <- client
382 kco@oauthScope <- scope
383 req <- request(kco@apiUrl) |>
384 oauthRefresh(client, scope, kco) |>
385 req_perform()
386 log_info(kco@verbose, "Client authorized. Short lived access token will be refreshed automatically.")
387 }
Marc Kupietza4f51d72025-01-25 16:23:18 +0100388 } else {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100389 log_info(kco@verbose, "Access token already set.")
Marc Kupietza4f51d72025-01-25 16:23:18 +0100390 }
391 return(kco)
392})
393
394
395
Marc Kupietz4862b862019-11-07 10:13:53 +0100396#' @import keyring
Marc Kupietzb956b812019-11-25 17:53:13 +0100397getAccessToken <- function(KorAPUrl) {
Marc Kupietza824d502025-05-02 15:40:23 +0200398 keyList <- tryCatch(
399 withCallingHandlers(key_list(service = accessTokenServiceName),
400 warning = function(w) invokeRestart("muffleWarning"),
401 error = function(e) {
402 return(NULL)
403 }
404 ),
405 error = function(e) { }
406 )
407 if (KorAPUrl %in% keyList$username) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100408 key_get(accessTokenServiceName, KorAPUrl)
Marc Kupietza824d502025-05-02 15:40:23 +0200409 } else {
Marc Kupietzfd9e7492019-11-08 15:45:18 +0100410 NULL
Marc Kupietza824d502025-05-02 15:40:23 +0200411 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100412}
Marc Kupietz0a96b282019-10-01 11:05:31 +0200413
Marc Kupietz581a29b2021-09-04 20:51:04 +0200414
Marc Kupietz62b17892025-02-01 18:26:45 +0100415warnIfNotAuthorized <- function(kco) {
416 if (kco@authorizationSupported & is.null(kco@accessToken) & is.null(kco@oauthClient)) {
Marc Kupietz581a29b2021-09-04 20:51:04 +0200417 warning(
418 paste0(
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100419 "In order to receive KWICSs also from corpora with restricted licenses, you may need to\n",
420 "authorize your application with an access token or the auth() method.\n",
421 "To generate an access token, login to KorAP and navigate to KorAP's OAuth settings <",
Marc Kupietz581a29b2021-09-04 20:51:04 +0200422 kco@KorAPUrl,
423 "settings/oauth#page-top>"
424 )
425 )
426 }
427}
428
Marc Kupietz0a96b282019-10-01 11:05:31 +0200429KorAPCacheSubDir <- function() {
Marc Kupietza824d502025-05-02 15:40:23 +0200430 paste0(
431 "RKorAPClient_",
432 gsub(
433 "^([0-9]+\\.[0-9]+).*",
434 "\\1",
435 packageVersion("RKorAPClient"),
436 perl = TRUE
437 )
438 )
Marc Kupietz0a96b282019-10-01 11:05:31 +0200439}
440
Marc Kupietza824d502025-05-02 15:40:23 +0200441setGeneric("apiCall", function(kco, ...) standardGeneric("apiCall"))
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200442
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200443## quiets concerns of R CMD check re: the .'s that appear in pipelines
Marc Kupietzef1ef4a2025-02-19 12:12:40 +0100444utils::globalVariables(c("."))
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200445
Marc Kupietza8c40f42025-06-24 15:49:52 +0200446#' Internal API call method
447#' @keywords internal
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200448#' @aliases apiCall
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200449#' @param kco KorAPConnection object
450#' @param url request url
Marc Kupietzf9129592025-01-26 19:17:54 +0100451#' @param json logical that determines if JSON result is expected
Marc Kupietzb49afa02020-06-04 15:50:29 +0200452#' @param getHeaders logical that determines if headers and content should be returned (as a list)
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200453#' @importFrom jsonlite fromJSON
Marc Kupietza4675722022-02-23 23:55:15 +0100454#' @importFrom curl has_internet
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100455#' @import httr2
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200456#' @export
Marc Kupietzf9129592025-01-26 19:17:54 +0100457setMethod("apiCall", "KorAPConnection", function(kco, url, json = TRUE, getHeaders = FALSE, cache = kco@cache, timeout = kco@timeout) {
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100458 result <- ""
Marc Kupietzf9129592025-01-26 19:17:54 +0100459
460 # Handle caching if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100461 if (cache) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100462 result <- R.cache::loadCache(dir = KorAPCacheSubDir(), key = list(url, kco@accessToken, kco@indexRevision))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100463 if (!is.null(result)) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100464 if (!is.null(result$meta)) result$meta$cached <- "local"
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100465 return(result)
Marc Kupietz0a96b282019-10-01 11:05:31 +0200466 }
467 }
Marc Kupietza4675722022-02-23 23:55:15 +0100468
Marc Kupietzf9129592025-01-26 19:17:54 +0100469 # Check for internet connection
Marc Kupietza4675722022-02-23 23:55:15 +0100470 if (!curl::has_internet()) {
471 message("No internet connection.")
472 return(invisible(NULL))
473 }
474
Marc Kupietzf9129592025-01-26 19:17:54 +0100475 # Create the request
476 req <- httr2::request(url) |>
477 httr2::req_user_agent(kco@userAgent) |>
478 httr2::req_timeout(timeout)
Marc Kupietza4675722022-02-23 23:55:15 +0100479
Marc Kupietz03402e72025-05-02 15:39:40 +0200480 if (!is.null(kco@oauthClient)) {
481 req <- req |> oauthRefresh(kco@oauthClient, scope = kco@oauthScope, kco)
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100482 } else if (!is.null(kco@accessToken)) {
483 req <- req |> httr2::req_auth_bearer_token(kco@accessToken)
Marc Kupietzf9129592025-01-26 19:17:54 +0100484 }
485
Marc Kupietzd36ee552025-05-02 20:42:50 +0200486 resp <- tryCatch(req |> httr2::req_perform(),
487 error = function(e) {
488 if (is.null(e$resp)) {
489 message(paste("Error: ", e$message, collapse = " "), if ("parent" %in% names(e)) paste0("\n", e$parent$message) else "")
490 return(invisible(NULL))
491 }
492 return(e$resp)
493 }
494 )
Marc Kupietz03402e72025-05-02 15:39:40 +0200495
496 if (is.null(resp)) {
Marc Kupietz03402e72025-05-02 15:39:40 +0200497 return(invisible(NULL))
498 }
Marc Kupietz62b17892025-02-01 18:26:45 +0100499
Marc Kupietzf9129592025-01-26 19:17:54 +0100500 if (resp |> httr2::resp_status() != 200) {
Marc Kupietzd36ee552025-05-02 20:42:50 +0200501 message("Error: Request failed with status ", resp |> httr2::resp_status(), ": ", resp |> httr2::resp_status_desc())
Marc Kupietz62b17892025-02-01 18:26:45 +0100502 if (resp |> httr2::resp_content_type() == "application/json") {
503 result <- tryCatch(
504 resp |> httr2::resp_body_json(),
505 error = function(e) {
506 message("Failed to parse json with error details: ", e$message)
507 return(NULL)
508 }
509 )
510 # Handle errors in the response (if any)
511 if (!is.null(result$errors)) {
512 errors <- result$errors
513 warning_msgs <- if (is.data.frame(errors)) {
514 apply(errors, 1, function(warning) paste(warning[1], ": ", warning[2]))
515 } else {
516 lapply(errors, function(error) paste(error, collapse = " "))
517 }
Marc Kupietz03402e72025-05-02 15:39:40 +0200518 message(paste("Warning: ", warning_msgs, collapse = "\n"))
Marc Kupietzf9129592025-01-26 19:17:54 +0100519 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100520 }
Marc Kupietza4675722022-02-23 23:55:15 +0100521 return(invisible(NULL))
522 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100523
524 # Process JSON response or raw text based on `json` parameter
525 if (json) {
526 content_type <- resp |> httr2::resp_content_type()
527 if (!content_type %in% c("application/json", "application/ld+json")) {
528 message("API did not return JSON")
Marc Kupietza4675722022-02-23 23:55:15 +0100529 return(invisible(NULL))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100530 }
Marc Kupietz04814f22023-04-16 17:13:27 +0200531
Marc Kupietzf9129592025-01-26 19:17:54 +0100532 result <- tryCatch(
533 resp |> httr2::resp_body_string() |> jsonlite::fromJSON(),
534 error = function(e) {
535 message("Failed to parse JSON: ", e$message)
536 return(NULL)
537 }
538 )
539
540 # Handle warnings in the response (if any)
541 if (!is.null(result$warnings)) {
542 warnings <- result$warnings
543 warning_msgs <- if (is.data.frame(warnings)) {
544 apply(warnings, 1, function(warning) paste(warning[1], ": ", warning[2]))
545 } else {
546 lapply(warnings, function(warning) paste(warning, collapse = " "))
547 }
Marc Kupietz03402e72025-05-02 15:39:40 +0200548 message(paste0("\nWarning: ", paste(warning_msgs, collapse = " ")))
549 if (cache & any(grepl("682", warning_msgs))) {
550 cache <- FALSE
Marc Kupietzd36ee552025-05-02 20:42:50 +0200551 log_info(kco@verbose, "Caching will be skipped because of warnings ")
Marc Kupietz03402e72025-05-02 15:39:40 +0200552 }
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100553 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100554 } else {
555 result <- resp |> httr2::resp_body_string()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200556 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100557
558 # Save to cache if enabled
Marc Kupietz03402e72025-05-02 15:39:40 +0200559 if (cache && resp |> httr2::resp_status() == 200) {
Marc Kupietzb49afa02020-06-04 15:50:29 +0200560 R.cache::saveCache(result, key = list(url, kco@accessToken, kco@indexRevision), dir = KorAPCacheSubDir(), compress = TRUE)
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100561 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100562
563 # Return headers and content as a list if `getHeaders` is TRUE
Marc Kupietzb49afa02020-06-04 15:50:29 +0200564 if (getHeaders) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100565 list(headers = resp |> httr2::resp_headers(), content = result)
Marc Kupietzb49afa02020-06-04 15:50:29 +0200566 } else {
567 result
568 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200569})
570
Marc Kupietza824d502025-05-02 15:40:23 +0200571setGeneric("clearCache", function(kco) standardGeneric("clearCache"))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200572
Marc Kupietzdc880ac2025-06-24 20:34:43 +0200573#' Clear local cache
574#'
575#' Clears the local cache of API responses for the current RKorAPClient version.
576#' Useful when you want to force fresh data retrieval or free up disk space.
577#'
578#' @family connection-initialization
579#' @param kco KorAPConnection object
580#' @return Invisible NULL (function called for side effects)
581#' @examples
582#' \dontrun{
583#' kco <- KorAPConnection()
584#' clearCache(kco)
585#' }
Marc Kupietzf9914bb2025-06-25 09:57:55 +0200586#'
Marc Kupietz0a96b282019-10-01 11:05:31 +0200587#' @aliases clearCache
Marc Kupietz0a96b282019-10-01 11:05:31 +0200588#' @export
Marc Kupietza824d502025-05-02 15:40:23 +0200589setMethod("clearCache", "KorAPConnection", function(kco) {
590 R.cache::clearCache(dir = KorAPCacheSubDir())
Marc Kupietz0a96b282019-10-01 11:05:31 +0200591})
592
Marc Kupietza8c40f42025-06-24 15:49:52 +0200593#' Display KorAPConnection object
594#' @keywords internal
Marc Kupietze95108e2019-09-18 13:23:58 +0200595#' @param object KorAPConnection object
596#' @export
597setMethod("show", "KorAPConnection", function(object) {
598 cat("<KorAPConnection>", "\n")
599 cat("apiUrl: ", object@apiUrl, "\n")
600})
601
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200602##' Funtion KorAPConnection()
603##'
Marc Kupietz617266d2025-02-27 10:43:07 +0100604##' Wrappper function for KorAPConnection()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200605##'
606##' @rdname KorAPConnection-constructor
607##' @name KorAPConnection-constructor
608##' @export
Marc Kupietz617266d2025-02-27 10:43:07 +0100609## XKorAPConnection <- function(...) KorAPConnection(...)