blob: d1f55aa2fc3942b23a44d1d4667558b1124cd589 [file] [log] [blame]
Marc Kupietze95108e2019-09-18 13:23:58 +02001#' Class KorAPConnection
Marc Kupietz25aebc32019-09-16 18:40:50 +02002#'
Akron5e135462019-09-27 16:31:38 +02003#' \code{KorAPConnection} objects represent the connection to a KorAP server.
4#' New \code{KorAPConnection} objects can be created by \code{KorAPConnection()}.
Marc Kupietze95108e2019-09-18 13:23:58 +02005#'
Marc Kupietz0a96b282019-10-01 11:05:31 +02006#' @import R.cache
Marc Kupietze95108e2019-09-18 13:23:58 +02007#' @import utils
8#' @import methods
Marc Kupietze95108e2019-09-18 13:23:58 +02009#' @export
Marc Kupietz4862b862019-11-07 10:13:53 +010010KorAPConnection <- setClass("KorAPConnection", slots=c(KorAPUrl="character", apiVersion="character", apiUrl="character", apiToken="character", userAgent="character", timeout="numeric", verbose="logical", cache="logical"))
Marc Kupietze95108e2019-09-18 13:23:58 +020011
12#' @param .Object KorAPConnection object
13#' @param KorAPUrl the URL of the KorAP server instance you want to access.
14#' @param apiVersion which version of KorAP's API you want to connect to.
15#' @param apiUrl URL of the KorAP web service.
Marc Kupietz4862b862019-11-07 10:13:53 +010016#' @param apiToken OAuth2 API token. To use authorization based on an API token
17#' in subsequent queries, intialize your KorAP connection with
18#' \code{kco <- new("KorAPConnection", apiToken="<API Token>")}.
19#' In order to make the API
20#' token persistent for the currently used \code{KorAPUrl} (you can have one
21#' token per KorAPUrl / KorAP server instance), use
22#' \code{persistApiToken(kco)}. This will store it in your keyring using the
23#' \code{\link{keyring}} package. Subsequent new("KorAPConnection") calls will
24#' then automatically retrieve the token from your keying. To stop using a
25#' persisted token, call \code{clearApiToken(kco)}. Please note that for
26#' DeReKo, authorized queries will behave differently inside and outside the
27#' IDS, because of the special license situation. This concerns also cached
28#' results which do not take into account from where a request was issued. If
29#' you experience problems or unexpected results, please try \code{kco <-
30#' new("KorAPConnection", cache=FALSE)} or use
31#' \code{\link{clearCache}} to clear the cache completely.
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +020032#' @param userAgent user agent string.
33#' @param timeout time out in seconds.
Marc Kupietz4862b862019-11-07 10:13:53 +010034#' @param verbose logical. Decides whether following operations will default to
35#' be verbose.
36#' @param cache logical. Decides if API calls are cached locally. You can clear
37#' the cache with \code{\link{clearCache}()}.
38#' @return \code{\link{KorAPConnection}} object that can be used e.g. with
39#' \code{\link{corpusQuery}}
Marc Kupietze95108e2019-09-18 13:23:58 +020040#'
41#' @examples
Marc Kupietz5a519822019-09-20 21:43:52 +020042#' kcon <- new("KorAPConnection", verbose = TRUE)
Marc Kupietze95108e2019-09-18 13:23:58 +020043#' kq <- corpusQuery(kcon, "Ameisenplage")
Marc Kupietz5a519822019-09-20 21:43:52 +020044#' kq <- fetchAll(kq)
Marc Kupietz7915dc42019-09-12 17:44:58 +020045#'
Marc Kupietz4862b862019-11-07 10:13:53 +010046#' \dontrun{
47#' kcon <- new("KorAPConnection", verbose = TRUE, apiToken="e739u6eOzkwADQPdVChxFg")
48#' kq <- corpusQuery(kcon, "Ameisenplage", metadataOnly=FALSE)
49#' kq <- fetchAll(kq)
50#' kq@collectedMatches$snippet
51#' }
Marc Kupietz7915dc42019-09-12 17:44:58 +020052#'
Marc Kupietze95108e2019-09-18 13:23:58 +020053#' @rdname KorAPConnection-class
Marc Kupietz632cbd42019-09-06 16:04:51 +020054#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +020055setMethod("initialize", "KorAPConnection",
Marc Kupietz4862b862019-11-07 10:13:53 +010056 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 +020057 .Object <- callNextMethod()
58 m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
59 .Object@KorAPUrl <- regmatches(KorAPUrl, m)
60 if (!endsWith(.Object@KorAPUrl, '/')) {
61 .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
62 }
63 if (missing(apiUrl)) {
64 .Object@apiUrl = paste0(.Object@KorAPUrl, 'api/', apiVersion, '/')
65 } else {
66 .Object@apiUrl = apiUrl
67 }
Marc Kupietz4862b862019-11-07 10:13:53 +010068 .Object@apiToken = apiToken
Marc Kupietze95108e2019-09-18 13:23:58 +020069 .Object@apiVersion = apiVersion
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +020070 .Object@userAgent = userAgent
71 .Object@timeout = timeout
Marc Kupietz5a519822019-09-20 21:43:52 +020072 .Object@verbose = verbose
Marc Kupietz0a96b282019-10-01 11:05:31 +020073 .Object@cache = cache
Marc Kupietze95108e2019-09-18 13:23:58 +020074 .Object
75 })
76
Marc Kupietz4862b862019-11-07 10:13:53 +010077apiTokenServiceName <- "RKorAPClientAPIToken"
78
79setGeneric("persistApiToken", function(kco, apiToken) standardGeneric("persistApiToken") )
80
81#' @aliases persistApiToken
82#' @rdname KorAPConnection-class
83#' @import keyring
84#' @export
85#' @examples
86#' \dontrun{
87#' kco <- new("KorAPConnection", apiToken="e739u6eOzkwADQPdVChxFg")
88#' persistApiToken(kco)
89#' }
90#'
91setMethod("persistApiToken", "KorAPConnection", function(kco, apiToken = kco@apiToken) {
92 if (is.null(apiToken))
93 stop("It seems that you have not supplied any API token that could be persisted.", call. = FALSE)
94
95 kco@apiToken <- apiToken
96 key_set_with_value(apiTokenServiceName, kco@KorAPUrl, apiToken)
97})
98
99setGeneric("clearApiToken", function(kco) standardGeneric("clearApiToken") )
100
101#' @aliases clearApiToken
102#' @rdname KorAPConnection-class
103#' @import keyring
104#' @export
105#' @examples
106#' \dontrun{
107#' kco <- new("KorAPConnection")
108#' clearApiToken(kco)
109#' }
110#'
111setMethod("clearApiToken", "KorAPConnection", function(kco) {
112 key_delete("RKorAPClientAPIToken", kco@KorAPUrl)
113})
114
115#' @import keyring
116getApiToken <- function(KorAPUrl) {
117 ifelse("keyring" %in% installed.packages()[,1 ]&& has_keyring_support()
118 && KorAPUrl %in% key_list(service = "RKorAPClientAPIToken"),
119 key_get("RKorAPClientAPIToken", KorAPUrl), NULL)
120}
Marc Kupietz0a96b282019-10-01 11:05:31 +0200121
122KorAPCacheSubDir <- function() {
123 paste0("RKorAPClient_", packageVersion("RKorAPClient"))
124}
125
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200126setGeneric("apiCall", function(kco, ...) standardGeneric("apiCall") )
127
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200128## quiets concerns of R CMD check re: the .'s that appear in pipelines
129if(getRversion() >= "2.15.1") utils::globalVariables(c("."))
130
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200131#' @aliases apiCall
132#' @rdname KorAPConnection-class
133#' @param kco KorAPConnection object
134#' @param url request url
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200135#' @importFrom jsonlite fromJSON
136#' @export
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200137setMethod("apiCall", "KorAPConnection", function(kco, url) {
Marc Kupietz0a96b282019-10-01 11:05:31 +0200138 if (kco@cache) {
Marc Kupietz4862b862019-11-07 10:13:53 +0100139 parsed <- R.cache::loadCache(dir=KorAPCacheSubDir(), key=list(url, kco@apiToken))
Marc Kupietz0a96b282019-10-01 11:05:31 +0200140 if (!is.null(parsed)) {
141 return(parsed)
142 }
143 }
Marc Kupietz4862b862019-11-07 10:13:53 +0100144 if (!is.null(kco@apiToken))
145 resp <- GET(url, user_agent(kco@userAgent), timeout(kco@timeout), add_headers(Authorization = paste("Bearer", kco@apiToken)))
146 else
147 resp <- GET(url, user_agent(kco@userAgent), timeout(kco@timeout))
Marc Kupietz46a57672019-09-27 18:11:31 +0200148 if (!http_type(resp) %in% c("application/json", "application/ld+json")) {
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200149 stop("API did not return json", call. = FALSE)
150 }
151 parsed <- jsonlite::fromJSON(content(resp, "text"))
152 if (!is.null(parsed$warnings)) {
153 message <- ifelse (nrow(parsed$warnings) > 1,
154 sapply(parsed$warnings, function(warning) paste(sprintf("%s: %s", warning[1], warning[2]), sep="\n")),
155 sprintf("%s: %s", parsed$warnings[1], parsed$warnings[2]))
156 warning(message, call. = FALSE)
157 }
158 if (status_code(resp) != 200) {
159 message <- ifelse (!is.null(parsed$errors),
Akron36def512019-09-27 17:30:51 +0200160 sapply(parsed$errors, function(error) paste0(sprintf("\n%s: KorAP API request failed: %s", error[1], error[2]))),
161 message <- sprintf("%s: KorAP API request failed.", status_code(resp)))
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200162 stop(message, call. = FALSE)
163 }
Marc Kupietz0a96b282019-10-01 11:05:31 +0200164 if (kco@cache) {
Marc Kupietz4862b862019-11-07 10:13:53 +0100165 R.cache::saveCache(parsed, key = list(url, kco@apiToken), dir = KorAPCacheSubDir(), compress = TRUE)
Marc Kupietz0a96b282019-10-01 11:05:31 +0200166 }
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200167 parsed
168})
169
Marc Kupietz0a96b282019-10-01 11:05:31 +0200170setGeneric("clearCache", function(kco) standardGeneric("clearCache") )
171
172#' @aliases clearCache
173#' @rdname KorAPConnection-class
174#' @export
175setMethod("clearCache", "KorAPConnection", function(kco) {
176 R.cache::clearCache(dir=KorAPCacheSubDir())
177})
178
Marc Kupietze95108e2019-09-18 13:23:58 +0200179#' @rdname KorAPConnection-class
180#' @param object KorAPConnection object
181#' @export
182setMethod("show", "KorAPConnection", function(object) {
183 cat("<KorAPConnection>", "\n")
184 cat("apiUrl: ", object@apiUrl, "\n")
185})
186
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200187##' Funtion KorAPConnection()
188##'
189##' Wrappper function for new("KorAPConnection")
190##'
191##' @rdname KorAPConnection-constructor
192##' @name KorAPConnection-constructor
193##' @export
194## XKorAPConnection <- function(...) new("KorAPConnection", ...)