blob: f1f433d9ba32f38254437fd6bb57f8620476b340 [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#'
35#' @details
36#' The KorAPConnection object contains various configuration slots for advanced users:
37#' KorAPUrl (server URL), apiVersion, accessToken (OAuth2 token),
38#' timeout (request timeout), verbose (logging), cache (local caching),
39#' and other technical parameters. Most users can ignore these implementation details.
40#'
41#' @family initialization functions
Marc Kupietz0a96b282019-10-01 11:05:31 +020042#' @import R.cache
Marc Kupietze95108e2019-09-18 13:23:58 +020043#' @import utils
44#' @import methods
Marc Kupietz6dfeed92025-06-03 11:58:06 +020045#' @include logging.R
Marc Kupietza81343d2022-09-06 12:32:10 +020046
Marc Kupietze95108e2019-09-18 13:23:58 +020047#' @export
Marc Kupietza824d502025-05-02 15:40:23 +020048KorAPConnection <- 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 +010049
Marc Kupietza824d502025-05-02 15:40:23 +020050generic_kor_app_id <- "99FbPHH7RrN36hbndF7b6f"
Marc Kupietz62b17892025-02-01 18:26:45 +010051
Marc Kupietza824d502025-05-02 15:40:23 +020052kustvakt_redirect_uri <- "http://localhost:1410/"
53kustvakt_auth_path <- "settings/oauth/authorize"
Marc Kupietz62b17892025-02-01 18:26:45 +010054
Marc Kupietze95108e2019-09-18 13:23:58 +020055
Marc Kupietza8c40f42025-06-24 15:49:52 +020056#' Initialize KorAPConnection object
57#' @keywords internal
Marc Kupietze95108e2019-09-18 13:23:58 +020058#' @param .Object KorAPConnection object
Marc Kupietza81343d2022-09-06 12:32:10 +020059#' @param KorAPUrl URL of the web user interface of the KorAP server instance you want to access.
Marc Kupietzb79fd442025-03-26 10:25:03 +010060#' Defaults to the environment variable `KORAP_URL` if set and to the IDS Mannheim KorAP main instance
61#' to query DeReKo, otherwise.
Marc Kupietze95108e2019-09-18 13:23:58 +020062#' @param apiVersion which version of KorAP's API you want to connect to.
63#' @param apiUrl URL of the KorAP web service.
Marc Kupietz132f0052023-04-16 14:23:05 +020064#' @param accessToken OAuth2 access token. For queries on corpus parts with restricted
65#' access (e.g. textual queries on IPR protected data), you need to authorize
66#' your application with an access token.
Marc Kupietz62b17892025-02-01 18:26:45 +010067#' You can obtain an access token in the OAuth settings of your KorAP web interface.
Marc Kupietza4f51d72025-01-25 16:23:18 +010068#'
69#' More details are explained in the
Marc Kupietz132f0052023-04-16 14:23:05 +020070#' [authorization section](https://github.com/KorAP/RKorAPClient#authorization)
71#' of the RKorAPClient Readme on GitHub.
72#'
73#' To use authorization based on an access token
74#' in subsequent queries, initialize your KorAP connection with:
75#'
76#' ```
Marc Kupietz617266d2025-02-27 10:43:07 +010077#' kco <- KorAPConnection(accessToken="<access token>")
Marc Kupietz132f0052023-04-16 14:23:05 +020078#' ```
79#'
Marc Kupietz4862b862019-11-07 10:13:53 +010080#' In order to make the API
Marc Kupietz67edcb52021-09-20 21:54:24 +020081#' token persistent for the currently used `KorAPUrl` (you can have one
Marc Kupietz132f0052023-04-16 14:23:05 +020082#' token per KorAPUrl / KorAP server instance), use:
83#'
84#' ```
85#' persistAccessToken(kco)
86#' ```
87#'
88#' This will store it in your keyring using the
Marc Kupietz617266d2025-02-27 10:43:07 +010089#' [keyring::keyring-package]. Subsequent KorAPConnection() calls will
Marc Kupietz4862b862019-11-07 10:13:53 +010090#' then automatically retrieve the token from your keying. To stop using a
Marc Kupietz67edcb52021-09-20 21:54:24 +020091#' persisted token, call `clearAccessToken(kco)`. Please note that for
Marc Kupietz4862b862019-11-07 10:13:53 +010092#' DeReKo, authorized queries will behave differently inside and outside the
93#' IDS, because of the special license situation. This concerns also cached
94#' results which do not take into account from where a request was issued. If
Marc Kupietz67edcb52021-09-20 21:54:24 +020095#' you experience problems or unexpected results, please try `kco <-
Marc Kupietz617266d2025-02-27 10:43:07 +010096#' KorAPConnection(cache=FALSE)` or use
Marc Kupietz67edcb52021-09-20 21:54:24 +020097#' [clearCache()] to clear the cache completely.
Marc Kupietz132f0052023-04-16 14:23:05 +020098#'
Marc Kupietzf83d59a2025-02-01 14:48:30 +010099#' An alternative to using an access token is to use a browser-based oauth2 workflow
100#' to obtain an access token. This can be done with the [auth()] method.
101#'
102#' @param oauthClient OAuth2 client object.
103#' @param oauthScope OAuth2 scope.
Marc Kupietz62b17892025-02-01 18:26:45 +0100104#' @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 +0200105#' @param userAgent user agent string.
Marc Kupietza81343d2022-09-06 12:32:10 +0200106#' @param timeout tineout in seconds for API requests (this does not influence server internal timeouts).
107#' @param verbose logical that decides whether following operations will default to
Marc Kupietz4862b862019-11-07 10:13:53 +0100108#' be verbose.
Marc Kupietza81343d2022-09-06 12:32:10 +0200109#' @param cache logical that decides if API calls are cached locally. You can clear
Marc Kupietz67edcb52021-09-20 21:54:24 +0200110#' the cache with [clearCache()].
111#' @return [KorAPConnection()] object that can be used e.g. with
112#' [corpusQuery()]
Marc Kupietze95108e2019-09-18 13:23:58 +0200113#'
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100114#' @import httr2
Marc Kupietze95108e2019-09-18 13:23:58 +0200115#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +0200116#' \dontrun{
117#'
Marc Kupietz617266d2025-02-27 10:43:07 +0100118#' kcon <- KorAPConnection(verbose = TRUE)
Marc Kupietze95108e2019-09-18 13:23:58 +0200119#' kq <- corpusQuery(kcon, "Ameisenplage")
Marc Kupietz5a519822019-09-20 21:43:52 +0200120#' kq <- fetchAll(kq)
Marc Kupietz05b22772020-02-18 21:58:42 +0100121#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +0200122#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100123#' \dontrun{
Marc Kupietz6ae76052021-09-21 10:34:00 +0200124#'
Marc Kupietza824d502025-05-02 15:40:23 +0200125#' kcon <- KorAPConnection(verbose = TRUE, accessToken = "e739u6eOzkwADQPdVChxFg")
126#' kq <- corpusQuery(kcon, "Ameisenplage", metadataOnly = FALSE)
Marc Kupietz4862b862019-11-07 10:13:53 +0100127#' kq <- fetchAll(kq)
128#' kq@collectedMatches$snippet
129#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +0200130#'
Marc Kupietzb79fd442025-03-26 10:25:03 +0100131
Marc Kupietz632cbd42019-09-06 16:04:51 +0200132#' @export
Marc Kupietzb79fd442025-03-26 10:25:03 +0100133setMethod("initialize", "KorAPConnection", function(.Object,
134 KorAPUrl = if (is.null(Sys.getenv("KORAP_URL")) |
Marc Kupietza824d502025-05-02 15:40:23 +0200135 Sys.getenv("KORAP_URL") == "") {
Marc Kupietzb79fd442025-03-26 10:25:03 +0100136 "https://korap.ids-mannheim.de/"
Marc Kupietza824d502025-05-02 15:40:23 +0200137 } else {
138 Sys.getenv("KORAP_URL")
139 },
140 apiVersion = "v1.0",
Marc Kupietzb79fd442025-03-26 10:25:03 +0100141 apiUrl,
142 accessToken = getAccessToken(KorAPUrl),
143 oauthClient = NULL,
144 oauthScope = "search match_info",
145 authorizationSupported = TRUE,
146 userAgent = "R-KorAP-Client",
147 timeout = 240,
148 verbose = FALSE,
149 cache = TRUE) {
150 .Object <- callNextMethod()
151 m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
152 .Object@KorAPUrl <- regmatches(KorAPUrl, m)
Marc Kupietza824d502025-05-02 15:40:23 +0200153 if (!endsWith(.Object@KorAPUrl, "/")) {
Marc Kupietzb79fd442025-03-26 10:25:03 +0100154 .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
155 }
156 if (missing(apiUrl)) {
Marc Kupietza824d502025-05-02 15:40:23 +0200157 .Object@apiUrl <- paste0(.Object@KorAPUrl, "api/", apiVersion, "/")
158 } else {
159 .Object@apiUrl <- apiUrl
160 }
161 .Object@accessToken <- accessToken
162 .Object@oauthClient <- oauthClient
163 .Object@apiVersion <- apiVersion
164 .Object@userAgent <- userAgent
165 .Object@oauthScope <- oauthScope
166 .Object@authorizationSupported <- authorizationSupported
167 .Object@timeout <- timeout
168 .Object@verbose <- verbose
169 .Object@cache <- cache
170 .Object@welcome <- apiCall(.Object, .Object@apiUrl, json = FALSE, cache = FALSE, getHeaders = TRUE)
171 if (!is.null(.Object@welcome)) {
172 message(.Object@welcome[[2]])
173 resp <- httr2::request(.Object@KorAPUrl) |>
174 httr2::req_url_path_append(kustvakt_auth_path) |>
175 httr2::req_error(is_error = \(resp) FALSE) |>
176 httr2::req_perform()
177 .Object@authorizationSupported <- (httr2::resp_status(resp) == 200)
Marc Kupietz62b17892025-02-01 18:26:45 +0100178
Marc Kupietza824d502025-05-02 15:40:23 +0200179 .Object@indexRevision <- .Object@welcome[[1]][["x-index-revision"]]
180 } else {
181 if (grepl(.Object@KorAPUrl, .Object@apiUrl)) {
182 message("Could not connect to KorAP instance ", .Object@KorAPUrl)
183 } else {
184 message("Could not connect to KorAP API at ", .Object@apiUrl)
185 }
186 }
187 .Object
188})
Marc Kupietze95108e2019-09-18 13:23:58 +0200189
Marc Kupietza96537f2019-11-09 23:07:44 +0100190
Marc Kupietzb956b812019-11-25 17:53:13 +0100191accessTokenServiceName <- "RKorAPClientAccessToken"
Marc Kupietz4862b862019-11-07 10:13:53 +0100192
Marc Kupietza824d502025-05-02 15:40:23 +0200193setGeneric("persistAccessToken", function(kco, ...) standardGeneric("persistAccessToken"))
Marc Kupietz4862b862019-11-07 10:13:53 +0100194
Marc Kupietza4f51d72025-01-25 16:23:18 +0100195#' Persist current access token in keyring
196#'
Marc Kupietza8c40f42025-06-24 15:49:52 +0200197#' @family initialization functions
Marc Kupietza4f51d72025-01-25 16:23:18 +0100198#' @param kco KorAPConnection object
199#' @param accessToken access token to be persisted. If not supplied, the current access token of the KorAPConnection object will be used.
200#' @return KorAPConnection object.
201#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100202#' @aliases persistAccessToken
Marc Kupietza4f51d72025-01-25 16:23:18 +0100203#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100204#' @import keyring
205#' @export
Marc Kupietza4f51d72025-01-25 16:23:18 +0100206#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100207#' @examples
208#' \dontrun{
Marc Kupietza824d502025-05-02 15:40:23 +0200209#' kco <- KorAPConnection(accessToken = "e739u6eOzkwADQPdVChxFg")
Marc Kupietzb956b812019-11-25 17:53:13 +0100210#' persistAccessToken(kco)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100211#'
Marc Kupietza824d502025-05-02 15:40:23 +0200212#' kco <- KorAPConnection() %>%
213#' auth(app_id = "<my application id>") %>%
214#' persistAccessToken()
Marc Kupietz4862b862019-11-07 10:13:53 +0100215#' }
216#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100217#' @seealso [clearAccessToken()], [auth()]
218#'
Marc Kupietza824d502025-05-02 15:40:23 +0200219setMethod("persistAccessToken", "KorAPConnection", function(kco, accessToken = kco@accessToken) {
220 if (!is.null(kco@oauthClient)) {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100221 warning("Short lived access tokens from a confidential application cannot be persisted.")
222 return(kco)
223 }
Marc Kupietza824d502025-05-02 15:40:23 +0200224 if (is.null(accessToken)) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100225 stop("It seems that you have not supplied any access token that could be persisted.", call. = FALSE)
Marc Kupietza824d502025-05-02 15:40:23 +0200226 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100227
Marc Kupietzb956b812019-11-25 17:53:13 +0100228 kco@accessToken <- accessToken
229 key_set_with_value(accessTokenServiceName, kco@KorAPUrl, accessToken)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100230 return(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100231})
232
Marc Kupietza824d502025-05-02 15:40:23 +0200233setGeneric("clearAccessToken", function(kco) standardGeneric("clearAccessToken"))
Marc Kupietz4862b862019-11-07 10:13:53 +0100234
Marc Kupietza4f51d72025-01-25 16:23:18 +0100235#' Clear access token from keyring and KorAPConnection object
236#'
Marc Kupietza8c40f42025-06-24 15:49:52 +0200237#' @family initialization functions
Marc Kupietzb956b812019-11-25 17:53:13 +0100238#' @aliases clearAccessToken
Marc Kupietz4862b862019-11-07 10:13:53 +0100239#' @import keyring
Marc Kupietza4f51d72025-01-25 16:23:18 +0100240#' @param kco KorAPConnection object
241#' @return KorAPConnection object with access token set to `NULL`.
Marc Kupietz4862b862019-11-07 10:13:53 +0100242#' @export
243#' @examples
Marc Kupietza4f51d72025-01-25 16:23:18 +0100244#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100245#' kco <- KorAPConnection()
Marc Kupietza4f51d72025-01-25 16:23:18 +0100246#' kco <- clearAccessToken(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100247#' }
248#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100249#' @seealso [persistAccessToken()]
250#'
Marc Kupietza824d502025-05-02 15:40:23 +0200251setMethod("clearAccessToken", "KorAPConnection", function(kco) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100252 key_delete(accessTokenServiceName, kco@KorAPUrl)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100253 kco@accessToken <- NULL
254 kco
Marc Kupietz4862b862019-11-07 10:13:53 +0100255})
256
Marc Kupietza4f51d72025-01-25 16:23:18 +0100257
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100258oauthRefresh <- function(req, client, scope, kco) {
Marc Kupietza824d502025-05-02 15:40:23 +0200259 httr2::req_oauth_auth_code(req, client,
260 scope = scope,
261 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
262 redirect_uri = kustvakt_redirect_uri,
263 cache_key = kco@KorAPUrl
264 )
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100265}
266
Marc Kupietza824d502025-05-02 15:40:23 +0200267setGeneric("auth", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) standardGeneric("auth"))
Marc Kupietza4f51d72025-01-25 16:23:18 +0100268
269#' Authorize RKorAPClient
270#'
Marc Kupietza8c40f42025-06-24 15:49:52 +0200271#' @family initialization functions
Marc Kupietza4f51d72025-01-25 16:23:18 +0100272#' @aliases auth
273#'
274#' @description
275#' `r lifecycle::badge("experimental")`
276#'
277#' Authorize RKorAPClient to make KorAP queries and download results on behalf of the user.
278#'
279#' @param kco KorAPConnection object
280#' @param app_id OAuth2 application id. Defaults to the generic KorAP client application id.
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100281#' @param app_secret OAuth2 application secret. Used with confidential client applications. Defaults to `NULL`.
Marc Kupietza4f51d72025-01-25 16:23:18 +0100282#' @param scope OAuth2 scope. Defaults to "search match_info".
283#' @return KorAPConnection object with access token set in `@accessToken`.
284#'
285#' @importFrom httr2 oauth_client oauth_flow_auth_code
286#' @examples
287#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100288#' kco <- KorAPConnection(verbose = TRUE) %>% auth()
Marc Kupietza5501652025-01-28 20:25:42 +0100289#' df <- collocationAnalysis(kco, "focus([marmot/p=ADJA] {Ameisenplage})",
Marc Kupietza824d502025-05-02 15:40:23 +0200290#' leftContextSize = 1, rightContextSize = 0
291#' )
Marc Kupietza4f51d72025-01-25 16:23:18 +0100292#' }
293#'
294#' @seealso [persistAccessToken()], [clearAccessToken()]
295#'
296#' @export
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100297setMethod("auth", "KorAPConnection", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) {
Marc Kupietz62b17892025-02-01 18:26:45 +0100298 if (kco@authorizationSupported == FALSE) {
299 log_info(kco@verbose, "Authorization is not supported by this KorAP instance.")
300 return(kco)
301 }
Marc Kupietza824d502025-05-02 15:40:23 +0200302 if (kco@KorAPUrl != "https://korap.ids-mannheim.de/" & app_id == generic_kor_app_id) {
Marc Kupietza4f51d72025-01-25 16:23:18 +0100303 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))
304 return(kco)
305 }
306 if (is.null(kco@accessToken) || is.null(kco@welcome)) { # if access token is not set or invalid
Marc Kupietza824d502025-05-02 15:40:23 +0200307 client <- if (!is.null(kco@oauthClient)) {
308 kco@oauthClient
309 } else {
Marc Kupietza4f51d72025-01-25 16:23:18 +0100310 httr2::oauth_client(
Marc Kupietza824d502025-05-02 15:40:23 +0200311 id = app_id,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100312 secret = app_secret,
Marc Kupietza4f51d72025-01-25 16:23:18 +0100313 token_url = paste0(kco@apiUrl, "oauth2/token")
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100314 )
Marc Kupietza824d502025-05-02 15:40:23 +0200315 }
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100316 if (is.null(app_secret)) {
Marc Kupietza824d502025-05-02 15:40:23 +0200317 kco@accessToken <- (client |>
Marc Kupietza4f51d72025-01-25 16:23:18 +0100318 httr2::oauth_flow_auth_code(
319 scope = scope,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100320 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
Marc Kupietz62b17892025-02-01 18:26:45 +0100321 redirect_uri = kustvakt_redirect_uri
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100322 ))$access_token
323 log_info(kco@verbose, "Client authorized. New access token set.")
324 } else {
325 kco@oauthClient <- client
326 kco@oauthScope <- scope
327 req <- request(kco@apiUrl) |>
328 oauthRefresh(client, scope, kco) |>
329 req_perform()
330 log_info(kco@verbose, "Client authorized. Short lived access token will be refreshed automatically.")
331 }
Marc Kupietza4f51d72025-01-25 16:23:18 +0100332 } else {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100333 log_info(kco@verbose, "Access token already set.")
Marc Kupietza4f51d72025-01-25 16:23:18 +0100334 }
335 return(kco)
336})
337
338
339
Marc Kupietz4862b862019-11-07 10:13:53 +0100340#' @import keyring
Marc Kupietzb956b812019-11-25 17:53:13 +0100341getAccessToken <- function(KorAPUrl) {
Marc Kupietza824d502025-05-02 15:40:23 +0200342 keyList <- tryCatch(
343 withCallingHandlers(key_list(service = accessTokenServiceName),
344 warning = function(w) invokeRestart("muffleWarning"),
345 error = function(e) {
346 return(NULL)
347 }
348 ),
349 error = function(e) { }
350 )
351 if (KorAPUrl %in% keyList$username) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100352 key_get(accessTokenServiceName, KorAPUrl)
Marc Kupietza824d502025-05-02 15:40:23 +0200353 } else {
Marc Kupietzfd9e7492019-11-08 15:45:18 +0100354 NULL
Marc Kupietza824d502025-05-02 15:40:23 +0200355 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100356}
Marc Kupietz0a96b282019-10-01 11:05:31 +0200357
Marc Kupietz581a29b2021-09-04 20:51:04 +0200358
Marc Kupietz62b17892025-02-01 18:26:45 +0100359warnIfNotAuthorized <- function(kco) {
360 if (kco@authorizationSupported & is.null(kco@accessToken) & is.null(kco@oauthClient)) {
Marc Kupietz581a29b2021-09-04 20:51:04 +0200361 warning(
362 paste0(
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100363 "In order to receive KWICSs also from corpora with restricted licenses, you may need to\n",
364 "authorize your application with an access token or the auth() method.\n",
365 "To generate an access token, login to KorAP and navigate to KorAP's OAuth settings <",
Marc Kupietz581a29b2021-09-04 20:51:04 +0200366 kco@KorAPUrl,
367 "settings/oauth#page-top>"
368 )
369 )
370 }
371}
372
Marc Kupietz0a96b282019-10-01 11:05:31 +0200373KorAPCacheSubDir <- function() {
Marc Kupietza824d502025-05-02 15:40:23 +0200374 paste0(
375 "RKorAPClient_",
376 gsub(
377 "^([0-9]+\\.[0-9]+).*",
378 "\\1",
379 packageVersion("RKorAPClient"),
380 perl = TRUE
381 )
382 )
Marc Kupietz0a96b282019-10-01 11:05:31 +0200383}
384
Marc Kupietza824d502025-05-02 15:40:23 +0200385setGeneric("apiCall", function(kco, ...) standardGeneric("apiCall"))
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200386
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200387## quiets concerns of R CMD check re: the .'s that appear in pipelines
Marc Kupietzef1ef4a2025-02-19 12:12:40 +0100388utils::globalVariables(c("."))
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200389
Marc Kupietza8c40f42025-06-24 15:49:52 +0200390#' Internal API call method
391#' @keywords internal
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200392#' @aliases apiCall
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200393#' @param kco KorAPConnection object
394#' @param url request url
Marc Kupietzf9129592025-01-26 19:17:54 +0100395#' @param json logical that determines if JSON result is expected
Marc Kupietzb49afa02020-06-04 15:50:29 +0200396#' @param getHeaders logical that determines if headers and content should be returned (as a list)
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200397#' @importFrom jsonlite fromJSON
Marc Kupietza4675722022-02-23 23:55:15 +0100398#' @importFrom curl has_internet
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100399#' @import httr2
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200400#' @export
Marc Kupietzf9129592025-01-26 19:17:54 +0100401setMethod("apiCall", "KorAPConnection", function(kco, url, json = TRUE, getHeaders = FALSE, cache = kco@cache, timeout = kco@timeout) {
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100402 result <- ""
Marc Kupietzf9129592025-01-26 19:17:54 +0100403
404 # Handle caching if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100405 if (cache) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100406 result <- R.cache::loadCache(dir = KorAPCacheSubDir(), key = list(url, kco@accessToken, kco@indexRevision))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100407 if (!is.null(result)) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100408 if (!is.null(result$meta)) result$meta$cached <- "local"
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100409 return(result)
Marc Kupietz0a96b282019-10-01 11:05:31 +0200410 }
411 }
Marc Kupietza4675722022-02-23 23:55:15 +0100412
Marc Kupietzf9129592025-01-26 19:17:54 +0100413 # Check for internet connection
Marc Kupietza4675722022-02-23 23:55:15 +0100414 if (!curl::has_internet()) {
415 message("No internet connection.")
416 return(invisible(NULL))
417 }
418
Marc Kupietzf9129592025-01-26 19:17:54 +0100419 # Create the request
420 req <- httr2::request(url) |>
421 httr2::req_user_agent(kco@userAgent) |>
422 httr2::req_timeout(timeout)
Marc Kupietza4675722022-02-23 23:55:15 +0100423
Marc Kupietz03402e72025-05-02 15:39:40 +0200424 if (!is.null(kco@oauthClient)) {
425 req <- req |> oauthRefresh(kco@oauthClient, scope = kco@oauthScope, kco)
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100426 } else if (!is.null(kco@accessToken)) {
427 req <- req |> httr2::req_auth_bearer_token(kco@accessToken)
Marc Kupietzf9129592025-01-26 19:17:54 +0100428 }
429
Marc Kupietzd36ee552025-05-02 20:42:50 +0200430 resp <- tryCatch(req |> httr2::req_perform(),
431 error = function(e) {
432 if (is.null(e$resp)) {
433 message(paste("Error: ", e$message, collapse = " "), if ("parent" %in% names(e)) paste0("\n", e$parent$message) else "")
434 return(invisible(NULL))
435 }
436 return(e$resp)
437 }
438 )
Marc Kupietz03402e72025-05-02 15:39:40 +0200439
440 if (is.null(resp)) {
Marc Kupietz03402e72025-05-02 15:39:40 +0200441 return(invisible(NULL))
442 }
Marc Kupietz62b17892025-02-01 18:26:45 +0100443
Marc Kupietzf9129592025-01-26 19:17:54 +0100444 if (resp |> httr2::resp_status() != 200) {
Marc Kupietzd36ee552025-05-02 20:42:50 +0200445 message("Error: Request failed with status ", resp |> httr2::resp_status(), ": ", resp |> httr2::resp_status_desc())
Marc Kupietz62b17892025-02-01 18:26:45 +0100446 if (resp |> httr2::resp_content_type() == "application/json") {
447 result <- tryCatch(
448 resp |> httr2::resp_body_json(),
449 error = function(e) {
450 message("Failed to parse json with error details: ", e$message)
451 return(NULL)
452 }
453 )
454 # Handle errors in the response (if any)
455 if (!is.null(result$errors)) {
456 errors <- result$errors
457 warning_msgs <- if (is.data.frame(errors)) {
458 apply(errors, 1, function(warning) paste(warning[1], ": ", warning[2]))
459 } else {
460 lapply(errors, function(error) paste(error, collapse = " "))
461 }
Marc Kupietz03402e72025-05-02 15:39:40 +0200462 message(paste("Warning: ", warning_msgs, collapse = "\n"))
Marc Kupietzf9129592025-01-26 19:17:54 +0100463 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100464 }
Marc Kupietza4675722022-02-23 23:55:15 +0100465 return(invisible(NULL))
466 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100467
468 # Process JSON response or raw text based on `json` parameter
469 if (json) {
470 content_type <- resp |> httr2::resp_content_type()
471 if (!content_type %in% c("application/json", "application/ld+json")) {
472 message("API did not return JSON")
Marc Kupietza4675722022-02-23 23:55:15 +0100473 return(invisible(NULL))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100474 }
Marc Kupietz04814f22023-04-16 17:13:27 +0200475
Marc Kupietzf9129592025-01-26 19:17:54 +0100476 result <- tryCatch(
477 resp |> httr2::resp_body_string() |> jsonlite::fromJSON(),
478 error = function(e) {
479 message("Failed to parse JSON: ", e$message)
480 return(NULL)
481 }
482 )
483
484 # Handle warnings in the response (if any)
485 if (!is.null(result$warnings)) {
486 warnings <- result$warnings
487 warning_msgs <- if (is.data.frame(warnings)) {
488 apply(warnings, 1, function(warning) paste(warning[1], ": ", warning[2]))
489 } else {
490 lapply(warnings, function(warning) paste(warning, collapse = " "))
491 }
Marc Kupietz03402e72025-05-02 15:39:40 +0200492 message(paste0("\nWarning: ", paste(warning_msgs, collapse = " ")))
493 if (cache & any(grepl("682", warning_msgs))) {
494 cache <- FALSE
Marc Kupietzd36ee552025-05-02 20:42:50 +0200495 log_info(kco@verbose, "Caching will be skipped because of warnings ")
Marc Kupietz03402e72025-05-02 15:39:40 +0200496 }
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100497 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100498 } else {
499 result <- resp |> httr2::resp_body_string()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200500 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100501
502 # Save to cache if enabled
Marc Kupietz03402e72025-05-02 15:39:40 +0200503 if (cache && resp |> httr2::resp_status() == 200) {
Marc Kupietzb49afa02020-06-04 15:50:29 +0200504 R.cache::saveCache(result, key = list(url, kco@accessToken, kco@indexRevision), dir = KorAPCacheSubDir(), compress = TRUE)
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100505 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100506
507 # Return headers and content as a list if `getHeaders` is TRUE
Marc Kupietzb49afa02020-06-04 15:50:29 +0200508 if (getHeaders) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100509 list(headers = resp |> httr2::resp_headers(), content = result)
Marc Kupietzb49afa02020-06-04 15:50:29 +0200510 } else {
511 result
512 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200513})
514
Marc Kupietza824d502025-05-02 15:40:23 +0200515setGeneric("clearCache", function(kco) standardGeneric("clearCache"))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200516
517#' @aliases clearCache
Marc Kupietz0a96b282019-10-01 11:05:31 +0200518#' @export
Marc Kupietza824d502025-05-02 15:40:23 +0200519setMethod("clearCache", "KorAPConnection", function(kco) {
520 R.cache::clearCache(dir = KorAPCacheSubDir())
Marc Kupietz0a96b282019-10-01 11:05:31 +0200521})
522
Marc Kupietza8c40f42025-06-24 15:49:52 +0200523#' Display KorAPConnection object
524#' @keywords internal
Marc Kupietze95108e2019-09-18 13:23:58 +0200525#' @param object KorAPConnection object
526#' @export
527setMethod("show", "KorAPConnection", function(object) {
528 cat("<KorAPConnection>", "\n")
529 cat("apiUrl: ", object@apiUrl, "\n")
530})
531
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200532##' Funtion KorAPConnection()
533##'
Marc Kupietz617266d2025-02-27 10:43:07 +0100534##' Wrappper function for KorAPConnection()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200535##'
536##' @rdname KorAPConnection-constructor
537##' @name KorAPConnection-constructor
538##' @export
Marc Kupietz617266d2025-02-27 10:43:07 +0100539## XKorAPConnection <- function(...) KorAPConnection(...)