blob: 1d567a8caecf98fcd5703253060ff6b299bdcf62 [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 Kupietz6dfeed92025-06-03 11:58:06 +020016#' @include logging.R
Marc Kupietza81343d2022-09-06 12:32:10 +020017#' @slot KorAPUrl URL of the web user interface of the KorAP server used in the connection.
18#' @slot apiVersion requested KorAP API version.
19#' @slot indexRevision indexRevision code as reported from API via `X-Index-Revision` HTTP header.
20#' @slot apiUrl full URL of API including version.
21#' @slot accessToken OAuth2 access token.
Marc Kupietzf83d59a2025-02-01 14:48:30 +010022#' @slot oauthClient OAuth2 client object.
23#' @slot oauthScope OAuth2 scope.
Marc Kupietz62b17892025-02-01 18:26:45 +010024#' @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 +020025#' @slot userAgent user agent string used for connection the API.
Marc Kupietz471d90a2025-02-01 18:26:12 +010026#' @slot timeout timeout in seconds for API requests (this does not influence server internal timeouts)
Marc Kupietza81343d2022-09-06 12:32:10 +020027#' @slot verbose logical that decides whether operations will default to be verbose.
28#' @slot cache logical that decides if API calls are cached locally.
29#' @slot welcome list containing HTTP response received from KorAP server welcome function.
30
Marc Kupietze95108e2019-09-18 13:23:58 +020031#' @export
Marc Kupietza824d502025-05-02 15:40:23 +020032KorAPConnection <- 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 +010033
Marc Kupietza824d502025-05-02 15:40:23 +020034generic_kor_app_id <- "99FbPHH7RrN36hbndF7b6f"
Marc Kupietz62b17892025-02-01 18:26:45 +010035
Marc Kupietza824d502025-05-02 15:40:23 +020036kustvakt_redirect_uri <- "http://localhost:1410/"
37kustvakt_auth_path <- "settings/oauth/authorize"
Marc Kupietz62b17892025-02-01 18:26:45 +010038
Marc Kupietze95108e2019-09-18 13:23:58 +020039
40#' @param .Object KorAPConnection object
Marc Kupietza81343d2022-09-06 12:32:10 +020041#' @param KorAPUrl URL of the web user interface of the KorAP server instance you want to access.
Marc Kupietzb79fd442025-03-26 10:25:03 +010042#' Defaults to the environment variable `KORAP_URL` if set and to the IDS Mannheim KorAP main instance
43#' to query DeReKo, otherwise.
Marc Kupietze95108e2019-09-18 13:23:58 +020044#' @param apiVersion which version of KorAP's API you want to connect to.
45#' @param apiUrl URL of the KorAP web service.
Marc Kupietz132f0052023-04-16 14:23:05 +020046#' @param accessToken OAuth2 access token. For queries on corpus parts with restricted
47#' access (e.g. textual queries on IPR protected data), you need to authorize
48#' your application with an access token.
Marc Kupietz62b17892025-02-01 18:26:45 +010049#' You can obtain an access token in the OAuth settings of your KorAP web interface.
Marc Kupietza4f51d72025-01-25 16:23:18 +010050#'
51#' More details are explained in the
Marc Kupietz132f0052023-04-16 14:23:05 +020052#' [authorization section](https://github.com/KorAP/RKorAPClient#authorization)
53#' of the RKorAPClient Readme on GitHub.
54#'
55#' To use authorization based on an access token
56#' in subsequent queries, initialize your KorAP connection with:
57#'
58#' ```
Marc Kupietz617266d2025-02-27 10:43:07 +010059#' kco <- KorAPConnection(accessToken="<access token>")
Marc Kupietz132f0052023-04-16 14:23:05 +020060#' ```
61#'
Marc Kupietz4862b862019-11-07 10:13:53 +010062#' In order to make the API
Marc Kupietz67edcb52021-09-20 21:54:24 +020063#' token persistent for the currently used `KorAPUrl` (you can have one
Marc Kupietz132f0052023-04-16 14:23:05 +020064#' token per KorAPUrl / KorAP server instance), use:
65#'
66#' ```
67#' persistAccessToken(kco)
68#' ```
69#'
70#' This will store it in your keyring using the
Marc Kupietz617266d2025-02-27 10:43:07 +010071#' [keyring::keyring-package]. Subsequent KorAPConnection() calls will
Marc Kupietz4862b862019-11-07 10:13:53 +010072#' then automatically retrieve the token from your keying. To stop using a
Marc Kupietz67edcb52021-09-20 21:54:24 +020073#' persisted token, call `clearAccessToken(kco)`. Please note that for
Marc Kupietz4862b862019-11-07 10:13:53 +010074#' DeReKo, authorized queries will behave differently inside and outside the
75#' IDS, because of the special license situation. This concerns also cached
76#' results which do not take into account from where a request was issued. If
Marc Kupietz67edcb52021-09-20 21:54:24 +020077#' you experience problems or unexpected results, please try `kco <-
Marc Kupietz617266d2025-02-27 10:43:07 +010078#' KorAPConnection(cache=FALSE)` or use
Marc Kupietz67edcb52021-09-20 21:54:24 +020079#' [clearCache()] to clear the cache completely.
Marc Kupietz132f0052023-04-16 14:23:05 +020080#'
Marc Kupietzf83d59a2025-02-01 14:48:30 +010081#' An alternative to using an access token is to use a browser-based oauth2 workflow
82#' to obtain an access token. This can be done with the [auth()] method.
83#'
84#' @param oauthClient OAuth2 client object.
85#' @param oauthScope OAuth2 scope.
Marc Kupietz62b17892025-02-01 18:26:45 +010086#' @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 +020087#' @param userAgent user agent string.
Marc Kupietza81343d2022-09-06 12:32:10 +020088#' @param timeout tineout in seconds for API requests (this does not influence server internal timeouts).
89#' @param verbose logical that decides whether following operations will default to
Marc Kupietz4862b862019-11-07 10:13:53 +010090#' be verbose.
Marc Kupietza81343d2022-09-06 12:32:10 +020091#' @param cache logical that decides if API calls are cached locally. You can clear
Marc Kupietz67edcb52021-09-20 21:54:24 +020092#' the cache with [clearCache()].
93#' @return [KorAPConnection()] object that can be used e.g. with
94#' [corpusQuery()]
Marc Kupietze95108e2019-09-18 13:23:58 +020095#'
Marc Kupietzf83d59a2025-02-01 14:48:30 +010096#' @import httr2
Marc Kupietze95108e2019-09-18 13:23:58 +020097#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +020098#' \dontrun{
99#'
Marc Kupietz617266d2025-02-27 10:43:07 +0100100#' kcon <- KorAPConnection(verbose = TRUE)
Marc Kupietze95108e2019-09-18 13:23:58 +0200101#' kq <- corpusQuery(kcon, "Ameisenplage")
Marc Kupietz5a519822019-09-20 21:43:52 +0200102#' kq <- fetchAll(kq)
Marc Kupietz05b22772020-02-18 21:58:42 +0100103#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +0200104#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100105#' \dontrun{
Marc Kupietz6ae76052021-09-21 10:34:00 +0200106#'
Marc Kupietza824d502025-05-02 15:40:23 +0200107#' kcon <- KorAPConnection(verbose = TRUE, accessToken = "e739u6eOzkwADQPdVChxFg")
108#' kq <- corpusQuery(kcon, "Ameisenplage", metadataOnly = FALSE)
Marc Kupietz4862b862019-11-07 10:13:53 +0100109#' kq <- fetchAll(kq)
110#' kq@collectedMatches$snippet
111#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +0200112#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200113#' @rdname KorAPConnection-class
Marc Kupietzb79fd442025-03-26 10:25:03 +0100114
Marc Kupietz632cbd42019-09-06 16:04:51 +0200115#' @export
Marc Kupietzb79fd442025-03-26 10:25:03 +0100116setMethod("initialize", "KorAPConnection", function(.Object,
117 KorAPUrl = if (is.null(Sys.getenv("KORAP_URL")) |
Marc Kupietza824d502025-05-02 15:40:23 +0200118 Sys.getenv("KORAP_URL") == "") {
Marc Kupietzb79fd442025-03-26 10:25:03 +0100119 "https://korap.ids-mannheim.de/"
Marc Kupietza824d502025-05-02 15:40:23 +0200120 } else {
121 Sys.getenv("KORAP_URL")
122 },
123 apiVersion = "v1.0",
Marc Kupietzb79fd442025-03-26 10:25:03 +0100124 apiUrl,
125 accessToken = getAccessToken(KorAPUrl),
126 oauthClient = NULL,
127 oauthScope = "search match_info",
128 authorizationSupported = TRUE,
129 userAgent = "R-KorAP-Client",
130 timeout = 240,
131 verbose = FALSE,
132 cache = TRUE) {
133 .Object <- callNextMethod()
134 m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
135 .Object@KorAPUrl <- regmatches(KorAPUrl, m)
Marc Kupietza824d502025-05-02 15:40:23 +0200136 if (!endsWith(.Object@KorAPUrl, "/")) {
Marc Kupietzb79fd442025-03-26 10:25:03 +0100137 .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
138 }
139 if (missing(apiUrl)) {
Marc Kupietza824d502025-05-02 15:40:23 +0200140 .Object@apiUrl <- paste0(.Object@KorAPUrl, "api/", apiVersion, "/")
141 } else {
142 .Object@apiUrl <- apiUrl
143 }
144 .Object@accessToken <- accessToken
145 .Object@oauthClient <- oauthClient
146 .Object@apiVersion <- apiVersion
147 .Object@userAgent <- userAgent
148 .Object@oauthScope <- oauthScope
149 .Object@authorizationSupported <- authorizationSupported
150 .Object@timeout <- timeout
151 .Object@verbose <- verbose
152 .Object@cache <- cache
153 .Object@welcome <- apiCall(.Object, .Object@apiUrl, json = FALSE, cache = FALSE, getHeaders = TRUE)
154 if (!is.null(.Object@welcome)) {
155 message(.Object@welcome[[2]])
156 resp <- httr2::request(.Object@KorAPUrl) |>
157 httr2::req_url_path_append(kustvakt_auth_path) |>
158 httr2::req_error(is_error = \(resp) FALSE) |>
159 httr2::req_perform()
160 .Object@authorizationSupported <- (httr2::resp_status(resp) == 200)
Marc Kupietz62b17892025-02-01 18:26:45 +0100161
Marc Kupietza824d502025-05-02 15:40:23 +0200162 .Object@indexRevision <- .Object@welcome[[1]][["x-index-revision"]]
163 } else {
164 if (grepl(.Object@KorAPUrl, .Object@apiUrl)) {
165 message("Could not connect to KorAP instance ", .Object@KorAPUrl)
166 } else {
167 message("Could not connect to KorAP API at ", .Object@apiUrl)
168 }
169 }
170 .Object
171})
Marc Kupietze95108e2019-09-18 13:23:58 +0200172
Marc Kupietza96537f2019-11-09 23:07:44 +0100173
Marc Kupietzb956b812019-11-25 17:53:13 +0100174accessTokenServiceName <- "RKorAPClientAccessToken"
Marc Kupietz4862b862019-11-07 10:13:53 +0100175
Marc Kupietza824d502025-05-02 15:40:23 +0200176setGeneric("persistAccessToken", function(kco, ...) standardGeneric("persistAccessToken"))
Marc Kupietz4862b862019-11-07 10:13:53 +0100177
Marc Kupietza4f51d72025-01-25 16:23:18 +0100178#' Persist current access token in keyring
179#'
180#' @param kco KorAPConnection object
181#' @param accessToken access token to be persisted. If not supplied, the current access token of the KorAPConnection object will be used.
182#' @return KorAPConnection object.
183#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100184#' @aliases persistAccessToken
Marc Kupietza4f51d72025-01-25 16:23:18 +0100185#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100186#' @import keyring
187#' @export
Marc Kupietza4f51d72025-01-25 16:23:18 +0100188#'
Marc Kupietz4862b862019-11-07 10:13:53 +0100189#' @examples
190#' \dontrun{
Marc Kupietza824d502025-05-02 15:40:23 +0200191#' kco <- KorAPConnection(accessToken = "e739u6eOzkwADQPdVChxFg")
Marc Kupietzb956b812019-11-25 17:53:13 +0100192#' persistAccessToken(kco)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100193#'
Marc Kupietza824d502025-05-02 15:40:23 +0200194#' kco <- KorAPConnection() %>%
195#' auth(app_id = "<my application id>") %>%
196#' persistAccessToken()
Marc Kupietz4862b862019-11-07 10:13:53 +0100197#' }
198#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100199#' @seealso [clearAccessToken()], [auth()]
200#'
Marc Kupietza824d502025-05-02 15:40:23 +0200201setMethod("persistAccessToken", "KorAPConnection", function(kco, accessToken = kco@accessToken) {
202 if (!is.null(kco@oauthClient)) {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100203 warning("Short lived access tokens from a confidential application cannot be persisted.")
204 return(kco)
205 }
Marc Kupietza824d502025-05-02 15:40:23 +0200206 if (is.null(accessToken)) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100207 stop("It seems that you have not supplied any access token that could be persisted.", call. = FALSE)
Marc Kupietza824d502025-05-02 15:40:23 +0200208 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100209
Marc Kupietzb956b812019-11-25 17:53:13 +0100210 kco@accessToken <- accessToken
211 key_set_with_value(accessTokenServiceName, kco@KorAPUrl, accessToken)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100212 return(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100213})
214
Marc Kupietza824d502025-05-02 15:40:23 +0200215setGeneric("clearAccessToken", function(kco) standardGeneric("clearAccessToken"))
Marc Kupietz4862b862019-11-07 10:13:53 +0100216
Marc Kupietza4f51d72025-01-25 16:23:18 +0100217#' Clear access token from keyring and KorAPConnection object
218#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100219#' @aliases clearAccessToken
Marc Kupietz4862b862019-11-07 10:13:53 +0100220#' @import keyring
Marc Kupietza4f51d72025-01-25 16:23:18 +0100221#' @param kco KorAPConnection object
222#' @return KorAPConnection object with access token set to `NULL`.
Marc Kupietz4862b862019-11-07 10:13:53 +0100223#' @export
224#' @examples
Marc Kupietza4f51d72025-01-25 16:23:18 +0100225#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100226#' kco <- KorAPConnection()
Marc Kupietza4f51d72025-01-25 16:23:18 +0100227#' kco <- clearAccessToken(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100228#' }
229#'
Marc Kupietza4f51d72025-01-25 16:23:18 +0100230#' @seealso [persistAccessToken()]
231#'
Marc Kupietza824d502025-05-02 15:40:23 +0200232setMethod("clearAccessToken", "KorAPConnection", function(kco) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100233 key_delete(accessTokenServiceName, kco@KorAPUrl)
Marc Kupietza4f51d72025-01-25 16:23:18 +0100234 kco@accessToken <- NULL
235 kco
Marc Kupietz4862b862019-11-07 10:13:53 +0100236})
237
Marc Kupietza4f51d72025-01-25 16:23:18 +0100238
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100239oauthRefresh <- function(req, client, scope, kco) {
Marc Kupietza824d502025-05-02 15:40:23 +0200240 httr2::req_oauth_auth_code(req, client,
241 scope = scope,
242 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
243 redirect_uri = kustvakt_redirect_uri,
244 cache_key = kco@KorAPUrl
245 )
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100246}
247
Marc Kupietza824d502025-05-02 15:40:23 +0200248setGeneric("auth", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) standardGeneric("auth"))
Marc Kupietza4f51d72025-01-25 16:23:18 +0100249
250#' Authorize RKorAPClient
251#'
252#' @aliases auth
253#'
254#' @description
255#' `r lifecycle::badge("experimental")`
256#'
257#' Authorize RKorAPClient to make KorAP queries and download results on behalf of the user.
258#'
259#' @param kco KorAPConnection object
260#' @param app_id OAuth2 application id. Defaults to the generic KorAP client application id.
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100261#' @param app_secret OAuth2 application secret. Used with confidential client applications. Defaults to `NULL`.
Marc Kupietza4f51d72025-01-25 16:23:18 +0100262#' @param scope OAuth2 scope. Defaults to "search match_info".
263#' @return KorAPConnection object with access token set in `@accessToken`.
264#'
265#' @importFrom httr2 oauth_client oauth_flow_auth_code
266#' @examples
267#' \dontrun{
Marc Kupietz617266d2025-02-27 10:43:07 +0100268#' kco <- KorAPConnection(verbose = TRUE) %>% auth()
Marc Kupietza5501652025-01-28 20:25:42 +0100269#' df <- collocationAnalysis(kco, "focus([marmot/p=ADJA] {Ameisenplage})",
Marc Kupietza824d502025-05-02 15:40:23 +0200270#' leftContextSize = 1, rightContextSize = 0
271#' )
Marc Kupietza4f51d72025-01-25 16:23:18 +0100272#' }
273#'
274#' @seealso [persistAccessToken()], [clearAccessToken()]
275#'
276#' @export
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100277setMethod("auth", "KorAPConnection", function(kco, app_id = generic_kor_app_id, app_secret = NULL, scope = kco@oauthScope) {
Marc Kupietz62b17892025-02-01 18:26:45 +0100278 if (kco@authorizationSupported == FALSE) {
279 log_info(kco@verbose, "Authorization is not supported by this KorAP instance.")
280 return(kco)
281 }
Marc Kupietza824d502025-05-02 15:40:23 +0200282 if (kco@KorAPUrl != "https://korap.ids-mannheim.de/" & app_id == generic_kor_app_id) {
Marc Kupietza4f51d72025-01-25 16:23:18 +0100283 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))
284 return(kco)
285 }
286 if (is.null(kco@accessToken) || is.null(kco@welcome)) { # if access token is not set or invalid
Marc Kupietza824d502025-05-02 15:40:23 +0200287 client <- if (!is.null(kco@oauthClient)) {
288 kco@oauthClient
289 } else {
Marc Kupietza4f51d72025-01-25 16:23:18 +0100290 httr2::oauth_client(
Marc Kupietza824d502025-05-02 15:40:23 +0200291 id = app_id,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100292 secret = app_secret,
Marc Kupietza4f51d72025-01-25 16:23:18 +0100293 token_url = paste0(kco@apiUrl, "oauth2/token")
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100294 )
Marc Kupietza824d502025-05-02 15:40:23 +0200295 }
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100296 if (is.null(app_secret)) {
Marc Kupietza824d502025-05-02 15:40:23 +0200297 kco@accessToken <- (client |>
Marc Kupietza4f51d72025-01-25 16:23:18 +0100298 httr2::oauth_flow_auth_code(
299 scope = scope,
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100300 auth_url = paste0(kco@KorAPUrl, kustvakt_auth_path),
Marc Kupietz62b17892025-02-01 18:26:45 +0100301 redirect_uri = kustvakt_redirect_uri
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100302 ))$access_token
303 log_info(kco@verbose, "Client authorized. New access token set.")
304 } else {
305 kco@oauthClient <- client
306 kco@oauthScope <- scope
307 req <- request(kco@apiUrl) |>
308 oauthRefresh(client, scope, kco) |>
309 req_perform()
310 log_info(kco@verbose, "Client authorized. Short lived access token will be refreshed automatically.")
311 }
Marc Kupietza4f51d72025-01-25 16:23:18 +0100312 } else {
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100313 log_info(kco@verbose, "Access token already set.")
Marc Kupietza4f51d72025-01-25 16:23:18 +0100314 }
315 return(kco)
316})
317
318
319
Marc Kupietz4862b862019-11-07 10:13:53 +0100320#' @import keyring
Marc Kupietzb956b812019-11-25 17:53:13 +0100321getAccessToken <- function(KorAPUrl) {
Marc Kupietza824d502025-05-02 15:40:23 +0200322 keyList <- tryCatch(
323 withCallingHandlers(key_list(service = accessTokenServiceName),
324 warning = function(w) invokeRestart("muffleWarning"),
325 error = function(e) {
326 return(NULL)
327 }
328 ),
329 error = function(e) { }
330 )
331 if (KorAPUrl %in% keyList$username) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100332 key_get(accessTokenServiceName, KorAPUrl)
Marc Kupietza824d502025-05-02 15:40:23 +0200333 } else {
Marc Kupietzfd9e7492019-11-08 15:45:18 +0100334 NULL
Marc Kupietza824d502025-05-02 15:40:23 +0200335 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100336}
Marc Kupietz0a96b282019-10-01 11:05:31 +0200337
Marc Kupietz581a29b2021-09-04 20:51:04 +0200338
Marc Kupietz62b17892025-02-01 18:26:45 +0100339warnIfNotAuthorized <- function(kco) {
340 if (kco@authorizationSupported & is.null(kco@accessToken) & is.null(kco@oauthClient)) {
Marc Kupietz581a29b2021-09-04 20:51:04 +0200341 warning(
342 paste0(
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100343 "In order to receive KWICSs also from corpora with restricted licenses, you may need to\n",
344 "authorize your application with an access token or the auth() method.\n",
345 "To generate an access token, login to KorAP and navigate to KorAP's OAuth settings <",
Marc Kupietz581a29b2021-09-04 20:51:04 +0200346 kco@KorAPUrl,
347 "settings/oauth#page-top>"
348 )
349 )
350 }
351}
352
Marc Kupietz0a96b282019-10-01 11:05:31 +0200353KorAPCacheSubDir <- function() {
Marc Kupietza824d502025-05-02 15:40:23 +0200354 paste0(
355 "RKorAPClient_",
356 gsub(
357 "^([0-9]+\\.[0-9]+).*",
358 "\\1",
359 packageVersion("RKorAPClient"),
360 perl = TRUE
361 )
362 )
Marc Kupietz0a96b282019-10-01 11:05:31 +0200363}
364
Marc Kupietza824d502025-05-02 15:40:23 +0200365setGeneric("apiCall", function(kco, ...) standardGeneric("apiCall"))
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200366
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200367## quiets concerns of R CMD check re: the .'s that appear in pipelines
Marc Kupietzef1ef4a2025-02-19 12:12:40 +0100368utils::globalVariables(c("."))
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200369
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200370#' @aliases apiCall
371#' @rdname KorAPConnection-class
372#' @param kco KorAPConnection object
373#' @param url request url
Marc Kupietzf9129592025-01-26 19:17:54 +0100374#' @param json logical that determines if JSON result is expected
Marc Kupietzb49afa02020-06-04 15:50:29 +0200375#' @param getHeaders logical that determines if headers and content should be returned (as a list)
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200376#' @importFrom jsonlite fromJSON
Marc Kupietza4675722022-02-23 23:55:15 +0100377#' @importFrom curl has_internet
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100378#' @import httr2
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200379#' @export
Marc Kupietzf9129592025-01-26 19:17:54 +0100380setMethod("apiCall", "KorAPConnection", function(kco, url, json = TRUE, getHeaders = FALSE, cache = kco@cache, timeout = kco@timeout) {
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100381 result <- ""
Marc Kupietzf9129592025-01-26 19:17:54 +0100382
383 # Handle caching if enabled
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100384 if (cache) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100385 result <- R.cache::loadCache(dir = KorAPCacheSubDir(), key = list(url, kco@accessToken, kco@indexRevision))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100386 if (!is.null(result)) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100387 if (!is.null(result$meta)) result$meta$cached <- "local"
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100388 return(result)
Marc Kupietz0a96b282019-10-01 11:05:31 +0200389 }
390 }
Marc Kupietza4675722022-02-23 23:55:15 +0100391
Marc Kupietzf9129592025-01-26 19:17:54 +0100392 # Check for internet connection
Marc Kupietza4675722022-02-23 23:55:15 +0100393 if (!curl::has_internet()) {
394 message("No internet connection.")
395 return(invisible(NULL))
396 }
397
Marc Kupietzf9129592025-01-26 19:17:54 +0100398 # Create the request
399 req <- httr2::request(url) |>
400 httr2::req_user_agent(kco@userAgent) |>
401 httr2::req_timeout(timeout)
Marc Kupietza4675722022-02-23 23:55:15 +0100402
Marc Kupietz03402e72025-05-02 15:39:40 +0200403 if (!is.null(kco@oauthClient)) {
404 req <- req |> oauthRefresh(kco@oauthClient, scope = kco@oauthScope, kco)
Marc Kupietzf83d59a2025-02-01 14:48:30 +0100405 } else if (!is.null(kco@accessToken)) {
406 req <- req |> httr2::req_auth_bearer_token(kco@accessToken)
Marc Kupietzf9129592025-01-26 19:17:54 +0100407 }
408
Marc Kupietzd36ee552025-05-02 20:42:50 +0200409 resp <- tryCatch(req |> httr2::req_perform(),
410 error = function(e) {
411 if (is.null(e$resp)) {
412 message(paste("Error: ", e$message, collapse = " "), if ("parent" %in% names(e)) paste0("\n", e$parent$message) else "")
413 return(invisible(NULL))
414 }
415 return(e$resp)
416 }
417 )
Marc Kupietz03402e72025-05-02 15:39:40 +0200418
419 if (is.null(resp)) {
Marc Kupietz03402e72025-05-02 15:39:40 +0200420 return(invisible(NULL))
421 }
Marc Kupietz62b17892025-02-01 18:26:45 +0100422
Marc Kupietzf9129592025-01-26 19:17:54 +0100423 if (resp |> httr2::resp_status() != 200) {
Marc Kupietzd36ee552025-05-02 20:42:50 +0200424 message("Error: Request failed with status ", resp |> httr2::resp_status(), ": ", resp |> httr2::resp_status_desc())
Marc Kupietz62b17892025-02-01 18:26:45 +0100425 if (resp |> httr2::resp_content_type() == "application/json") {
426 result <- tryCatch(
427 resp |> httr2::resp_body_json(),
428 error = function(e) {
429 message("Failed to parse json with error details: ", e$message)
430 return(NULL)
431 }
432 )
433 # Handle errors in the response (if any)
434 if (!is.null(result$errors)) {
435 errors <- result$errors
436 warning_msgs <- if (is.data.frame(errors)) {
437 apply(errors, 1, function(warning) paste(warning[1], ": ", warning[2]))
438 } else {
439 lapply(errors, function(error) paste(error, collapse = " "))
440 }
Marc Kupietz03402e72025-05-02 15:39:40 +0200441 message(paste("Warning: ", warning_msgs, collapse = "\n"))
Marc Kupietzf9129592025-01-26 19:17:54 +0100442 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100443 }
Marc Kupietza4675722022-02-23 23:55:15 +0100444 return(invisible(NULL))
445 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100446
447 # Process JSON response or raw text based on `json` parameter
448 if (json) {
449 content_type <- resp |> httr2::resp_content_type()
450 if (!content_type %in% c("application/json", "application/ld+json")) {
451 message("API did not return JSON")
Marc Kupietza4675722022-02-23 23:55:15 +0100452 return(invisible(NULL))
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100453 }
Marc Kupietz04814f22023-04-16 17:13:27 +0200454
Marc Kupietzf9129592025-01-26 19:17:54 +0100455 result <- tryCatch(
456 resp |> httr2::resp_body_string() |> jsonlite::fromJSON(),
457 error = function(e) {
458 message("Failed to parse JSON: ", e$message)
459 return(NULL)
460 }
461 )
462
463 # Handle warnings in the response (if any)
464 if (!is.null(result$warnings)) {
465 warnings <- result$warnings
466 warning_msgs <- if (is.data.frame(warnings)) {
467 apply(warnings, 1, function(warning) paste(warning[1], ": ", warning[2]))
468 } else {
469 lapply(warnings, function(warning) paste(warning, collapse = " "))
470 }
Marc Kupietz03402e72025-05-02 15:39:40 +0200471 message(paste0("\nWarning: ", paste(warning_msgs, collapse = " ")))
472 if (cache & any(grepl("682", warning_msgs))) {
473 cache <- FALSE
Marc Kupietzd36ee552025-05-02 20:42:50 +0200474 log_info(kco@verbose, "Caching will be skipped because of warnings ")
Marc Kupietz03402e72025-05-02 15:39:40 +0200475 }
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100476 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100477 } else {
478 result <- resp |> httr2::resp_body_string()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200479 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100480
481 # Save to cache if enabled
Marc Kupietz03402e72025-05-02 15:39:40 +0200482 if (cache && resp |> httr2::resp_status() == 200) {
Marc Kupietzb49afa02020-06-04 15:50:29 +0200483 R.cache::saveCache(result, key = list(url, kco@accessToken, kco@indexRevision), dir = KorAPCacheSubDir(), compress = TRUE)
Marc Kupietzb2b32a32020-03-24 13:56:50 +0100484 }
Marc Kupietzf9129592025-01-26 19:17:54 +0100485
486 # Return headers and content as a list if `getHeaders` is TRUE
Marc Kupietzb49afa02020-06-04 15:50:29 +0200487 if (getHeaders) {
Marc Kupietzf9129592025-01-26 19:17:54 +0100488 list(headers = resp |> httr2::resp_headers(), content = result)
Marc Kupietzb49afa02020-06-04 15:50:29 +0200489 } else {
490 result
491 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200492})
493
Marc Kupietza824d502025-05-02 15:40:23 +0200494setGeneric("clearCache", function(kco) standardGeneric("clearCache"))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200495
496#' @aliases clearCache
497#' @rdname KorAPConnection-class
498#' @export
Marc Kupietza824d502025-05-02 15:40:23 +0200499setMethod("clearCache", "KorAPConnection", function(kco) {
500 R.cache::clearCache(dir = KorAPCacheSubDir())
Marc Kupietz0a96b282019-10-01 11:05:31 +0200501})
502
Marc Kupietze95108e2019-09-18 13:23:58 +0200503#' @rdname KorAPConnection-class
504#' @param object KorAPConnection object
505#' @export
506setMethod("show", "KorAPConnection", function(object) {
507 cat("<KorAPConnection>", "\n")
508 cat("apiUrl: ", object@apiUrl, "\n")
509})
510
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200511##' Funtion KorAPConnection()
512##'
Marc Kupietz617266d2025-02-27 10:43:07 +0100513##' Wrappper function for KorAPConnection()
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200514##'
515##' @rdname KorAPConnection-constructor
516##' @name KorAPConnection-constructor
517##' @export
Marc Kupietz617266d2025-02-27 10:43:07 +0100518## XKorAPConnection <- function(...) KorAPConnection(...)