blob: 98a088f3289daff1911519b5be0315d76994dc2d [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 Kupietzfd9e7492019-11-08 15:45:18 +010015KorAPConnection <- setClass("KorAPConnection", slots=c(KorAPUrl="character", apiVersion="character", apiUrl="character", apiToken="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 Kupietz4862b862019-11-07 10:13:53 +010021#' @param apiToken OAuth2 API token. To use authorization based on an API token
22#' in subsequent queries, intialize your KorAP connection with
23#' \code{kco <- new("KorAPConnection", apiToken="<API Token>")}.
24#' 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
27#' \code{persistApiToken(kco)}. This will store it in your keyring using the
28#' \code{\link{keyring}} package. Subsequent new("KorAPConnection") calls will
29#' then automatically retrieve the token from your keying. To stop using a
30#' persisted token, call \code{clearApiToken(kco)}. Please note that for
31#' 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 Kupietz5a519822019-09-20 21:43:52 +020047#' kcon <- new("KorAPConnection", verbose = TRUE)
Marc Kupietze95108e2019-09-18 13:23:58 +020048#' kq <- corpusQuery(kcon, "Ameisenplage")
Marc Kupietz5a519822019-09-20 21:43:52 +020049#' kq <- fetchAll(kq)
Marc Kupietz7915dc42019-09-12 17:44:58 +020050#'
Marc Kupietz4862b862019-11-07 10:13:53 +010051#' \dontrun{
52#' kcon <- new("KorAPConnection", verbose = TRUE, apiToken="e739u6eOzkwADQPdVChxFg")
53#' kq <- corpusQuery(kcon, "Ameisenplage", metadataOnly=FALSE)
54#' kq <- fetchAll(kq)
55#' kq@collectedMatches$snippet
56#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +020057#'
Marc Kupietze95108e2019-09-18 13:23:58 +020058#' @rdname KorAPConnection-class
Marc Kupietz632cbd42019-09-06 16:04:51 +020059#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +020060setMethod("initialize", "KorAPConnection",
Marc Kupietz4862b862019-11-07 10:13:53 +010061 function(.Object, KorAPUrl = "https://korap.ids-mannheim.de/", apiVersion = 'v1.0', apiUrl, apiToken = getApiToken(KorAPUrl), userAgent = "R-KorAP-Client", timeout=10, verbose = FALSE, cache = TRUE) {
Marc Kupietze95108e2019-09-18 13:23:58 +020062 .Object <- callNextMethod()
63 m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
64 .Object@KorAPUrl <- regmatches(KorAPUrl, m)
65 if (!endsWith(.Object@KorAPUrl, '/')) {
66 .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
67 }
68 if (missing(apiUrl)) {
69 .Object@apiUrl = paste0(.Object@KorAPUrl, 'api/', apiVersion, '/')
70 } else {
71 .Object@apiUrl = apiUrl
72 }
Marc Kupietz4862b862019-11-07 10:13:53 +010073 .Object@apiToken = apiToken
Marc Kupietze95108e2019-09-18 13:23:58 +020074 .Object@apiVersion = apiVersion
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +020075 .Object@userAgent = userAgent
76 .Object@timeout = timeout
Marc Kupietz5a519822019-09-20 21:43:52 +020077 .Object@verbose = verbose
Marc Kupietz0a96b282019-10-01 11:05:31 +020078 .Object@cache = cache
Marc Kupietze95108e2019-09-18 13:23:58 +020079 .Object
80 })
81
Marc Kupietza96537f2019-11-09 23:07:44 +010082
Marc Kupietz4862b862019-11-07 10:13:53 +010083apiTokenServiceName <- "RKorAPClientAPIToken"
84
Marc Kupietz409bf742019-11-20 18:39:51 +010085setGeneric("persistApiToken", function(kco, ...) standardGeneric("persistApiToken") )
Marc Kupietz4862b862019-11-07 10:13:53 +010086
87#' @aliases persistApiToken
88#' @rdname KorAPConnection-class
89#' @import keyring
90#' @export
91#' @examples
92#' \dontrun{
93#' kco <- new("KorAPConnection", apiToken="e739u6eOzkwADQPdVChxFg")
94#' persistApiToken(kco)
95#' }
96#'
97setMethod("persistApiToken", "KorAPConnection", function(kco, apiToken = kco@apiToken) {
98 if (is.null(apiToken))
99 stop("It seems that you have not supplied any API token that could be persisted.", call. = FALSE)
100
101 kco@apiToken <- apiToken
102 key_set_with_value(apiTokenServiceName, kco@KorAPUrl, apiToken)
103})
104
105setGeneric("clearApiToken", function(kco) standardGeneric("clearApiToken") )
106
107#' @aliases clearApiToken
108#' @rdname KorAPConnection-class
109#' @import keyring
110#' @export
111#' @examples
112#' \dontrun{
113#' kco <- new("KorAPConnection")
114#' clearApiToken(kco)
115#' }
116#'
117setMethod("clearApiToken", "KorAPConnection", function(kco) {
Marc Kupietz1057b6e2019-11-08 16:01:12 +0100118 key_delete(apiTokenServiceName, kco@KorAPUrl)
Marc Kupietz4862b862019-11-07 10:13:53 +0100119})
120
121#' @import keyring
122getApiToken <- function(KorAPUrl) {
Marc Kupietzddce5562019-11-24 15:45:38 +0100123 keyList <- withCallingHandlers(key_list(service = apiTokenServiceName),
124 warning = function(w) invokeRestart("muffleWarning"),
125 error = function(e) return(NULL))
Marc Kupietzb2870f22019-11-20 22:28:34 +0100126 if (KorAPUrl %in% keyList)
127 key_get(apiTokenServiceName, KorAPUrl)
Marc Kupietzfd9e7492019-11-08 15:45:18 +0100128 else
129 NULL
Marc Kupietz4862b862019-11-07 10:13:53 +0100130}
Marc Kupietz0a96b282019-10-01 11:05:31 +0200131
132KorAPCacheSubDir <- function() {
133 paste0("RKorAPClient_", packageVersion("RKorAPClient"))
134}
135
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200136setGeneric("apiCall", function(kco, ...) standardGeneric("apiCall") )
137
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200138## quiets concerns of R CMD check re: the .'s that appear in pipelines
139if(getRversion() >= "2.15.1") utils::globalVariables(c("."))
140
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200141#' @aliases apiCall
142#' @rdname KorAPConnection-class
143#' @param kco KorAPConnection object
144#' @param url request url
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200145#' @importFrom jsonlite fromJSON
146#' @export
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200147setMethod("apiCall", "KorAPConnection", function(kco, url) {
Marc Kupietz0a96b282019-10-01 11:05:31 +0200148 if (kco@cache) {
Marc Kupietz4862b862019-11-07 10:13:53 +0100149 parsed <- R.cache::loadCache(dir=KorAPCacheSubDir(), key=list(url, kco@apiToken))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200150 if (!is.null(parsed)) {
151 return(parsed)
152 }
153 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100154 if (!is.null(kco@apiToken))
155 resp <- GET(url, user_agent(kco@userAgent), timeout(kco@timeout), add_headers(Authorization = paste("Bearer", kco@apiToken)))
156 else
157 resp <- GET(url, user_agent(kco@userAgent), timeout(kco@timeout))
Marc Kupietz46a57672019-09-27 18:11:31 +0200158 if (!http_type(resp) %in% c("application/json", "application/ld+json")) {
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200159 stop("API did not return json", call. = FALSE)
160 }
161 parsed <- jsonlite::fromJSON(content(resp, "text"))
162 if (!is.null(parsed$warnings)) {
Marc Kupietza96537f2019-11-09 23:07:44 +0100163 message <- if (nrow(parsed$warnings) > 1)
164 sapply(parsed$warnings, function(warning) paste(sprintf("%s: %s", warning[1], warning[2]), sep="\n"))
165 else
166 sprintf("%s: %s", parsed$warnings[1], parsed$warnings[2])
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200167 warning(message, call. = FALSE)
168 }
169 if (status_code(resp) != 200) {
Marc Kupietza96537f2019-11-09 23:07:44 +0100170 message <- if (!is.null(parsed$errors))
171 sapply(parsed$errors, function(error) paste0(sprintf("\n%s: KorAP API request failed: %s", error[1], error[2])))
172 else
173 message <- sprintf("%s: KorAP API request failed.", status_code(resp))
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200174 stop(message, call. = FALSE)
175 }
Marc Kupietz0a96b282019-10-01 11:05:31 +0200176 if (kco@cache) {
Marc Kupietz4862b862019-11-07 10:13:53 +0100177 R.cache::saveCache(parsed, key = list(url, kco@apiToken), dir = KorAPCacheSubDir(), compress = TRUE)
Marc Kupietz0a96b282019-10-01 11:05:31 +0200178 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200179 parsed
180})
181
Marc Kupietz0a96b282019-10-01 11:05:31 +0200182setGeneric("clearCache", function(kco) standardGeneric("clearCache") )
183
184#' @aliases clearCache
185#' @rdname KorAPConnection-class
186#' @export
187setMethod("clearCache", "KorAPConnection", function(kco) {
188 R.cache::clearCache(dir=KorAPCacheSubDir())
189})
190
Marc Kupietze95108e2019-09-18 13:23:58 +0200191#' @rdname KorAPConnection-class
192#' @param object KorAPConnection object
193#' @export
194setMethod("show", "KorAPConnection", function(object) {
195 cat("<KorAPConnection>", "\n")
196 cat("apiUrl: ", object@apiUrl, "\n")
197})
198
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200199##' Funtion KorAPConnection()
200##'
201##' Wrappper function for new("KorAPConnection")
202##'
203##' @rdname KorAPConnection-constructor
204##' @name KorAPConnection-constructor
205##' @export
206## XKorAPConnection <- function(...) new("KorAPConnection", ...)