blob: 13a3b3916a5175043d3192003379cd1eec3e05d8 [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"))
5
Marc Kupietze95108e2019-09-18 13:23:58 +02006#' Class KorAPConnection
Marc Kupietz25aebc32019-09-16 18:40:50 +02007#'
Akron5e135462019-09-27 16:31:38 +02008#' \code{KorAPConnection} objects represent the connection to a KorAP server.
Marc Kupietz7715e9d2019-11-08 15:59:58 +01009#' New \code{KorAPConnection} objects can be created by \code{new("KorAPConnection")}.
Marc Kupietze95108e2019-09-18 13:23:58 +020010#'
Marc Kupietz0a96b282019-10-01 11:05:31 +020011#' @import R.cache
Marc Kupietze95108e2019-09-18 13:23:58 +020012#' @import utils
13#' @import methods
Marc Kupietze95108e2019-09-18 13:23:58 +020014#' @export
Marc Kupietzb956b812019-11-25 17:53:13 +010015KorAPConnection <- setClass("KorAPConnection", slots=c(KorAPUrl="character", apiVersion="character", apiUrl="character", accessToken="characterOrNULL", userAgent="character", timeout="numeric", verbose="logical", cache="logical"))
Marc Kupietze95108e2019-09-18 13:23:58 +020016
17#' @param .Object KorAPConnection object
18#' @param KorAPUrl the URL of the KorAP server instance you want to access.
19#' @param apiVersion which version of KorAP's API you want to connect to.
20#' @param apiUrl URL of the KorAP web service.
Marc Kupietzb956b812019-11-25 17:53:13 +010021#' @param accessToken OAuth2 access token. To use authorization based on an access token
Marc Kupietz4862b862019-11-07 10:13:53 +010022#' in subsequent queries, intialize your KorAP connection with
Marc Kupietzb956b812019-11-25 17:53:13 +010023#' \code{kco <- new("KorAPConnection", accessToken="<access token>")}.
Marc Kupietz4862b862019-11-07 10:13:53 +010024#' In order to make the API
25#' token persistent for the currently used \code{KorAPUrl} (you can have one
26#' token per KorAPUrl / KorAP server instance), use
Marc Kupietzb956b812019-11-25 17:53:13 +010027#' \code{persistAccessToken(kco)}. This will store it in your keyring using the
Marc Kupietz4862b862019-11-07 10:13:53 +010028#' \code{\link{keyring}} package. Subsequent new("KorAPConnection") calls will
29#' then automatically retrieve the token from your keying. To stop using a
Marc Kupietzb956b812019-11-25 17:53:13 +010030#' persisted token, call \code{clearAccessToken(kco)}. Please note that for
Marc Kupietz4862b862019-11-07 10:13:53 +010031#' DeReKo, authorized queries will behave differently inside and outside the
32#' IDS, because of the special license situation. This concerns also cached
33#' results which do not take into account from where a request was issued. If
34#' you experience problems or unexpected results, please try \code{kco <-
35#' new("KorAPConnection", cache=FALSE)} or use
36#' \code{\link{clearCache}} to clear the cache completely.
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +020037#' @param userAgent user agent string.
38#' @param timeout time out in seconds.
Marc Kupietz4862b862019-11-07 10:13:53 +010039#' @param verbose logical. Decides whether following operations will default to
40#' be verbose.
41#' @param cache logical. Decides if API calls are cached locally. You can clear
42#' the cache with \code{\link{clearCache}()}.
43#' @return \code{\link{KorAPConnection}} object that can be used e.g. with
44#' \code{\link{corpusQuery}}
Marc Kupietze95108e2019-09-18 13:23:58 +020045#'
46#' @examples
Marc Kupietz05b22772020-02-18 21:58:42 +010047#' \donttest{
Marc Kupietz5a519822019-09-20 21:43:52 +020048#' kcon <- new("KorAPConnection", verbose = TRUE)
Marc Kupietze95108e2019-09-18 13:23:58 +020049#' kq <- corpusQuery(kcon, "Ameisenplage")
Marc Kupietz5a519822019-09-20 21:43:52 +020050#' kq <- fetchAll(kq)
Marc Kupietz05b22772020-02-18 21:58:42 +010051#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +020052#'
Marc Kupietz4862b862019-11-07 10:13:53 +010053#' \dontrun{
Marc Kupietzb956b812019-11-25 17:53:13 +010054#' kcon <- new("KorAPConnection", verbose = TRUE, accessToken="e739u6eOzkwADQPdVChxFg")
Marc Kupietz4862b862019-11-07 10:13:53 +010055#' kq <- corpusQuery(kcon, "Ameisenplage", metadataOnly=FALSE)
56#' kq <- fetchAll(kq)
57#' kq@collectedMatches$snippet
58#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +020059#'
Marc Kupietze95108e2019-09-18 13:23:58 +020060#' @rdname KorAPConnection-class
Marc Kupietz632cbd42019-09-06 16:04:51 +020061#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +020062setMethod("initialize", "KorAPConnection",
Marc Kupietz8a82af72019-12-12 12:58:22 +010063 function(.Object, KorAPUrl = "https://korap.ids-mannheim.de/", apiVersion = 'v1.0', apiUrl, accessToken = getAccessToken(KorAPUrl), userAgent = "R-KorAP-Client", timeout=110, verbose = FALSE, cache = TRUE) {
Marc Kupietze95108e2019-09-18 13:23:58 +020064 .Object <- callNextMethod()
65 m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
66 .Object@KorAPUrl <- regmatches(KorAPUrl, m)
67 if (!endsWith(.Object@KorAPUrl, '/')) {
68 .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
69 }
70 if (missing(apiUrl)) {
71 .Object@apiUrl = paste0(.Object@KorAPUrl, 'api/', apiVersion, '/')
72 } else {
73 .Object@apiUrl = apiUrl
74 }
Marc Kupietzb956b812019-11-25 17:53:13 +010075 .Object@accessToken = accessToken
Marc Kupietze95108e2019-09-18 13:23:58 +020076 .Object@apiVersion = apiVersion
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +020077 .Object@userAgent = userAgent
78 .Object@timeout = timeout
Marc Kupietz5a519822019-09-20 21:43:52 +020079 .Object@verbose = verbose
Marc Kupietz0a96b282019-10-01 11:05:31 +020080 .Object@cache = cache
Marc Kupietze95108e2019-09-18 13:23:58 +020081 .Object
82 })
83
Marc Kupietza96537f2019-11-09 23:07:44 +010084
Marc Kupietzb956b812019-11-25 17:53:13 +010085accessTokenServiceName <- "RKorAPClientAccessToken"
Marc Kupietz4862b862019-11-07 10:13:53 +010086
Marc Kupietzb956b812019-11-25 17:53:13 +010087setGeneric("persistAccessToken", function(kco, ...) standardGeneric("persistAccessToken") )
Marc Kupietz4862b862019-11-07 10:13:53 +010088
Marc Kupietzb956b812019-11-25 17:53:13 +010089#' @aliases persistAccessToken
Marc Kupietz4862b862019-11-07 10:13:53 +010090#' @rdname KorAPConnection-class
91#' @import keyring
92#' @export
93#' @examples
94#' \dontrun{
Marc Kupietzb956b812019-11-25 17:53:13 +010095#' kco <- new("KorAPConnection", accessToken="e739u6eOzkwADQPdVChxFg")
96#' persistAccessToken(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +010097#' }
98#'
Marc Kupietzb956b812019-11-25 17:53:13 +010099setMethod("persistAccessToken", "KorAPConnection", function(kco, accessToken = kco@accessToken) {
100 if (is.null(accessToken))
101 stop("It seems that you have not supplied any access token that could be persisted.", call. = FALSE)
Marc Kupietz4862b862019-11-07 10:13:53 +0100102
Marc Kupietzb956b812019-11-25 17:53:13 +0100103 kco@accessToken <- accessToken
104 key_set_with_value(accessTokenServiceName, kco@KorAPUrl, accessToken)
Marc Kupietz4862b862019-11-07 10:13:53 +0100105})
106
Marc Kupietzb956b812019-11-25 17:53:13 +0100107setGeneric("clearAccessToken", function(kco) standardGeneric("clearAccessToken") )
Marc Kupietz4862b862019-11-07 10:13:53 +0100108
Marc Kupietzb956b812019-11-25 17:53:13 +0100109#' @aliases clearAccessToken
Marc Kupietz4862b862019-11-07 10:13:53 +0100110#' @rdname KorAPConnection-class
111#' @import keyring
112#' @export
113#' @examples
114#' \dontrun{
115#' kco <- new("KorAPConnection")
Marc Kupietzb956b812019-11-25 17:53:13 +0100116#' clearAccessToken(kco)
Marc Kupietz4862b862019-11-07 10:13:53 +0100117#' }
118#'
Marc Kupietzb956b812019-11-25 17:53:13 +0100119setMethod("clearAccessToken", "KorAPConnection", function(kco) {
120 key_delete(accessTokenServiceName, kco@KorAPUrl)
Marc Kupietz4862b862019-11-07 10:13:53 +0100121})
122
123#' @import keyring
Marc Kupietzb956b812019-11-25 17:53:13 +0100124getAccessToken <- function(KorAPUrl) {
Marc Kupietz59e449b2019-12-12 12:53:54 +0100125 keyList <- tryCatch(withCallingHandlers(key_list(service = accessTokenServiceName),
Marc Kupietzddce5562019-11-24 15:45:38 +0100126 warning = function(w) invokeRestart("muffleWarning"),
Marc Kupietz59e449b2019-12-12 12:53:54 +0100127 error = function(e) return(NULL)),
128 error = function(e) { })
Marc Kupietzb2870f22019-11-20 22:28:34 +0100129 if (KorAPUrl %in% keyList)
Marc Kupietzb956b812019-11-25 17:53:13 +0100130 key_get(accessTokenServiceName, KorAPUrl)
Marc Kupietzfd9e7492019-11-08 15:45:18 +0100131 else
132 NULL
Marc Kupietz4862b862019-11-07 10:13:53 +0100133}
Marc Kupietz0a96b282019-10-01 11:05:31 +0200134
135KorAPCacheSubDir <- function() {
Marc Kupietz70b2c722020-02-18 13:32:09 +0100136 paste0("RKorAPClient_",
137 gsub(
138 "^([0-9]+\\.[0-9]+).*",
139 "\\1",
140 packageVersion("RKorAPClient"),
141 perl = TRUE
142 ))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200143}
144
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200145setGeneric("apiCall", function(kco, ...) standardGeneric("apiCall") )
146
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200147## quiets concerns of R CMD check re: the .'s that appear in pipelines
148if(getRversion() >= "2.15.1") utils::globalVariables(c("."))
149
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200150#' @aliases apiCall
151#' @rdname KorAPConnection-class
152#' @param kco KorAPConnection object
153#' @param url request url
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200154#' @importFrom jsonlite fromJSON
155#' @export
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200156setMethod("apiCall", "KorAPConnection", function(kco, url) {
Marc Kupietz0a96b282019-10-01 11:05:31 +0200157 if (kco@cache) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100158 parsed <- R.cache::loadCache(dir=KorAPCacheSubDir(), key=list(url, kco@accessToken))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200159 if (!is.null(parsed)) {
Marc Kupietzcb1b3882020-02-18 13:32:45 +0100160 if (!is.null(parsed$meta))
Marc Kupietzf56e8452019-12-13 10:49:46 +0100161 parsed$meta$cached <- "local"
Marc Kupietz0a96b282019-10-01 11:05:31 +0200162 return(parsed)
163 }
164 }
Marc Kupietzb956b812019-11-25 17:53:13 +0100165 if (!is.null(kco@accessToken))
166 resp <- GET(url, user_agent(kco@userAgent), timeout(kco@timeout), add_headers(Authorization = paste("Bearer", kco@accessToken)))
Marc Kupietz4862b862019-11-07 10:13:53 +0100167 else
168 resp <- GET(url, user_agent(kco@userAgent), timeout(kco@timeout))
Marc Kupietz46a57672019-09-27 18:11:31 +0200169 if (!http_type(resp) %in% c("application/json", "application/ld+json")) {
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200170 stop("API did not return json", call. = FALSE)
171 }
Marc Kupietzb7d8c272020-01-31 18:51:50 +0100172 parsed <- jsonlite::fromJSON(content(resp, "text", encoding = "UTF-8"))
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200173 if (!is.null(parsed$warnings)) {
Marc Kupietza96537f2019-11-09 23:07:44 +0100174 message <- if (nrow(parsed$warnings) > 1)
175 sapply(parsed$warnings, function(warning) paste(sprintf("%s: %s", warning[1], warning[2]), sep="\n"))
176 else
177 sprintf("%s: %s", parsed$warnings[1], parsed$warnings[2])
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200178 warning(message, call. = FALSE)
179 }
180 if (status_code(resp) != 200) {
Marc Kupietzb7d8c272020-01-31 18:51:50 +0100181 if (kco@verbose) {
182 cat("\n")
183 }
184 message <- sprintf("%s KorAP API request failed", status_code(resp))
185 if (!is.null(parsed$errors)) {
186 message <- sprintf("%s - %s %s", message, parsed$errors[1], parsed$errors[2])
187 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200188 stop(message, call. = FALSE)
189 }
Marc Kupietz0a96b282019-10-01 11:05:31 +0200190 if (kco@cache) {
Marc Kupietzb956b812019-11-25 17:53:13 +0100191 R.cache::saveCache(parsed, key = list(url, kco@accessToken), dir = KorAPCacheSubDir(), compress = TRUE)
Marc Kupietz0a96b282019-10-01 11:05:31 +0200192 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200193 parsed
194})
195
Marc Kupietz0a96b282019-10-01 11:05:31 +0200196setGeneric("clearCache", function(kco) standardGeneric("clearCache") )
197
198#' @aliases clearCache
199#' @rdname KorAPConnection-class
200#' @export
201setMethod("clearCache", "KorAPConnection", function(kco) {
202 R.cache::clearCache(dir=KorAPCacheSubDir())
203})
204
Marc Kupietze95108e2019-09-18 13:23:58 +0200205#' @rdname KorAPConnection-class
206#' @param object KorAPConnection object
207#' @export
208setMethod("show", "KorAPConnection", function(object) {
209 cat("<KorAPConnection>", "\n")
210 cat("apiUrl: ", object@apiUrl, "\n")
211})
212
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200213##' Funtion KorAPConnection()
214##'
215##' Wrappper function for new("KorAPConnection")
216##'
217##' @rdname KorAPConnection-constructor
218##' @name KorAPConnection-constructor
219##' @export
220## XKorAPConnection <- function(...) new("KorAPConnection", ...)