blob: c02b87b9df99703acb43c778f55b1de61d72b263 [file] [log] [blame]
Marc Kupietze95108e2019-09-18 13:23:58 +02001#' Class KorAPQuery
2#'
3#' \code{KorAPQuery} objetcs represent the current state of a query to a KorAP server.
4#' New \code{KorAPQuery} objects are typically created by the \code{\link{corpusQuery}} method.
5#'
6#' @include KorAPConnection.R
Marc Kupietz5bbc9db2019-08-30 16:30:45 +02007#' @import jsonlite
Marc Kupietze95108e2019-09-18 13:23:58 +02008#' @import httr
9#'
10#'
Marc Kupietz5bbc9db2019-08-30 16:30:45 +020011
Marc Kupietze95108e2019-09-18 13:23:58 +020012#' @export
13KorAPQuery <- setClass("KorAPQuery", slots = c(
14 "request",
15 "vc",
16 "totalResults",
17 "nextStartIndex",
18 "fields",
19 "requestUrl",
20 "webUIRequestUrl",
21 "apiResponse",
22 "collectedMatches",
23 "hasMoreMatches"
24))
Marc Kupietz5bbc9db2019-08-30 16:30:45 +020025
Marc Kupietze95108e2019-09-18 13:23:58 +020026#' Method initialize
27#'
28#' @rdname KorAPQuery-class
29#' @param .Object …
30#' @param request query part of the request URL
31#' @param vc definition of a virtual corpus
32#' @param totalResults number of hits the query has yielded
33#' @param nextStartIndex at what index to start the next fetch of query results
34#' @param fields what data / metadata fields should be collected
35#' @param requestUrl complete URL of the API request
36#' @param webUIRequestUrl URL of a web frontend request corresponding to the API request
37#' @param apiResponse data-frame representation of the JSON response of the API request
38#' @param hasMoreMatches boolean that signals if more query results can be fetched
39#' @param collectedMatches matches already fetched from the KorAP-API-server
40#' @export
41setMethod("initialize", "KorAPQuery",
42 function(.Object, request = NULL, vc="", totalResults=0, nextStartIndex=0, fields=c("corpusSigle", "textSigle", "pubDate", "pubPlace",
43 "availability", "textClass", "snippet"),
44 requestUrl="", webUIRequestUrl = "", apiResponse = NULL, hasMoreMatches= FALSE, collectedMatches = NULL) {
45 .Object <- callNextMethod()
46 .Object@request = request
47 .Object@vc = vc
48 .Object@totalResults = totalResults
49 .Object@nextStartIndex = nextStartIndex
50 .Object@fields = fields
51 .Object@requestUrl = requestUrl
52 .Object@webUIRequestUrl = webUIRequestUrl
53 .Object@apiResponse = apiResponse
54 .Object@hasMoreMatches = hasMoreMatches
55 .Object@collectedMatches = collectedMatches
56 .Object
57 })
Marc Kupietz632cbd42019-09-06 16:04:51 +020058
Marc Kupietze95108e2019-09-18 13:23:58 +020059setGeneric("corpusQuery", function(kco, ...) standardGeneric("corpusQuery") )
60setGeneric("fetchAll", function(kqo, ...) standardGeneric("fetchAll") )
61setGeneric("fetchNext", function(kqo, ...) standardGeneric("fetchNext") )
62setGeneric("fetchRest", function(kqo, ...) standardGeneric("fetchRest") )
63
64maxResultsPerPage <- 50
Marc Kupietz62da2b52019-09-12 17:43:34 +020065
Marc Kupietz632cbd42019-09-06 16:04:51 +020066QueryParameterFromUrl <- function(url, parameter) {
67 regex <- paste0(".*[?&]", parameter, "=([^&]*).*")
68 if (grepl(regex, url)) {
69 return(gsub(regex, '\\1', url, perl = TRUE))
70 } else {
71 return("")
72 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +020073}
74
Marc Kupietz632cbd42019-09-06 16:04:51 +020075KorAPQueryStringFromUrl <- function(KorAPUrl) {
76 return(URLdecode(gsub(".*[?&]q=([^&]*).*", '\\1', KorAPUrl, perl = TRUE)))
77}
78
Marc Kupietze95108e2019-09-18 13:23:58 +020079#' Method corpusQuery
80#'
81#' Perform a corpus query via a connection to a KorAP-API-server.
82#'
83#' @param kco \code{\link{KorAPConnection}} object (obtained e.g. from \code{new("KorAPConnection")}
Marc Kupietz632cbd42019-09-06 16:04:51 +020084#' @param query string that contains the corpus query. The query langauge depends on the \code{ql} parameter. Either \code{query} must be provided or \code{KorAPUrl}
85#' @param vc string describing the virtual corpus in which the query should be performed. An empty string (default) means the whole corpus, as far as it is license-wise accessible.
86#' @param KorAPUrl instead of providing the query and vc string parameters, you can also simply copy a KorAP query URL from your browser and use it here (and in \code{KorAPConnection}) to provide all necessary information for the query.
Marc Kupietzb125bdd2019-09-09 12:05:59 +020087#' @param metadataOnly boolean that determines whether queries should return only metadata without any snippets. This can also be useful to prevent access rewrites. Note that the default value is TRUE, unless the connection is authorized (currently not possible).
Marc Kupietz3c531f62019-09-13 12:17:24 +020088#' @param ql string to choose the query language (see \href{https://github.com/KorAP/Kustvakt/wiki/Service:-Search-GET#user-content-parameters}{section on Query Parameters} in the Kustvakt-Wiki for possible values.
Marc Kupietzb125bdd2019-09-09 12:05:59 +020089#' @param fields (meta)data fields that will be fetched for every match
Marc Kupietz25aebc32019-09-16 18:40:50 +020090#' @param accessRewriteFatal abort if query or given vc had to be rewritten due to insufficent rights (not yet implemented)
91#' @param verbose print some info
Marc Kupietze95108e2019-09-18 13:23:58 +020092#' @return A \code{\link{KorAPQuery}} object that, among other information, contains the total number of results in \code{@totalResults}. The resulting object can be used to fetch all query results (with \code{\link{fetchAll}}) or the next page of results (with \code{\link{fetchNext}}).
93#' A corresponding URL to be used within a web browser is contained in \code{@webUIRequestUrl}
Marc Kupietz62da2b52019-09-12 17:43:34 +020094#' Please make sure to check \code{$collection$rewrites} to see if any unforseen access rewrites of the query's virtual corpus had to be performed.
Marc Kupietz632cbd42019-09-06 16:04:51 +020095#'
96#' @examples
Marc Kupietze95108e2019-09-18 13:23:58 +020097#' kco <- new("KorAPConnection")
98#' kqo <- corpusQuery(kco, "Ameisenplage")
99#' kqo <- fetchAll(kqo)
100#' kqo
Marc Kupietz3c531f62019-09-13 12:17:24 +0200101#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200102#' kqo <- corpusQuery(kco,
Marc Kupietz37b8ef12019-09-16 18:37:49 +0200103#' KorAPUrl = "https://korap.ids-mannheim.de/?q=Ameise&cq=pubDate+since+2017&ql=poliqarp")
Marc Kupietze95108e2019-09-18 13:23:58 +0200104#' kqo
Marc Kupietz3c531f62019-09-13 12:17:24 +0200105#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200106#' q <- corpusQuery(kco, "Ameisenplage")
107#' q <- fetchAll(q, verbose=TRUE)
108#' tokensPerYear <- function(year) { return(corpusStats(kco, paste("pubDate in", year))@tokens) }
109#' df <- as.data.frame(table(as.numeric(format(q@collectedMatches$pubDate,"%Y")), dnn="year"),
Marc Kupietz37b8ef12019-09-16 18:37:49 +0200110#' stringsAsFactors = FALSE)
111#' df$ipm <- 1000000 * df$Freq / tokensPerYear(df$year)
112#' plot(df$year, df$ipm, type="l")
113#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200114#' @seealso \code{\link{KorAPConnection}}, \code{\link{fetchNext}}, \code{\link{fetchRest}}, \code{\link{fetchAll}}, \code{\link{corpusStats}}
Marc Kupietz632cbd42019-09-06 16:04:51 +0200115#'
116#' @references
117#' \url{https://ids-pub.bsz-bw.de/frontdoor/index/index/docId/9026}
118#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200119#' @aliases corpusQuery
Marc Kupietz632cbd42019-09-06 16:04:51 +0200120#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +0200121setMethod("corpusQuery", "KorAPConnection",
122 function(kco, query, vc="", KorAPUrl, metadataOnly = TRUE, ql = "poliqarp", fields = defaultFields,
123 accessRewriteFatal = TRUE, verbose=FALSE) {
124 defaultFields <- c("corpusSigle", "textSigle", "pubDate", "pubPlace",
125 "availability", "textClass", "snippet")
126 contentFields <- c("snippet")
127
128 if (missing(query) && missing(KorAPUrl) || ! (missing(query) || missing(KorAPUrl))) {
129 stop("Exactly one of the parameters query and KorAPUrl must be specified.")
130 }
131 if (missing(query)) {
132 query <- QueryParameterFromUrl(KorAPUrl, "q")
133 vc <- QueryParameterFromUrl(KorAPUrl, "vc")
134 ql <- QueryParameterFromUrl(KorAPUrl, "ql")
135 }
136 request <- paste0('?q=', URLencode(query, reserved=TRUE),
137 ifelse(vc != '', paste0('&cq=', URLencode(vc, reserved=TRUE)), ''), '&ql=', ql)
138 webUIRequestUrl <- paste0(kco@KorAPUrl, request)
139 requestUrl <- paste0(kco@apiUrl, 'search', request,
140 '&fields=', paste(defaultFields, collapse = ","),
141 ifelse(metadataOnly, '&access-rewrite-disabled=true', ''))
142 if (verbose) {
143 cat(paste0(webUIRequestUrl, "\n"))
144 }
145 res = fromJSON(paste0(requestUrl, '&count=1'))
146 KorAPQuery(
147 nextStartIndex = 0,
148 fields = fields[!fields %in% contentFields],
149 requestUrl = requestUrl,
150 request = request,
151 totalResults = res$meta$totalResults,
152 vc = vc,
153 apiResponse = res,
154 webUIRequestUrl = webUIRequestUrl,
155 hasMoreMatches = (res$meta$totalResults > 0),
156 )
157 })
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200158
Marc Kupietz62da2b52019-09-12 17:43:34 +0200159#' Fetch the next bunch of results of a KorAP query.
Marc Kupietze95108e2019-09-18 13:23:58 +0200160#'
161#' @param kqo object obtained from \code{\link{corpusQuery}}
Marc Kupietz62da2b52019-09-12 17:43:34 +0200162#' @param offset start offset for query results to fetch
163#' @param maxFetch maximum number of query results to fetch
Marc Kupietz25aebc32019-09-16 18:40:50 +0200164#' @param verbose print progress information if true
Marc Kupietze95108e2019-09-18 13:23:58 +0200165#' @return The \code{kqo} input object with updated slots \code{collectedMatches}, \code{apiResponse}, \code{nextStartIndex}, \code{hasMoreMatches}
Marc Kupietz62da2b52019-09-12 17:43:34 +0200166#'
167#' @references
168#' \url{https://ids-pub.bsz-bw.de/frontdoor/index/index/docId/9026}
169#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200170#' @aliases fetchNext
171#' @rdname KorAPQuery-class
Marc Kupietz632cbd42019-09-06 16:04:51 +0200172#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +0200173setMethod("fetchNext", "KorAPQuery", function(kqo, offset = kqo@nextStartIndex, maxFetch = maxResultsPerPage, verbose = FALSE) {
174 if (kqo@totalResults == 0 || offset >= kqo@totalResults) {
175 return(kqo)
Marc Kupietz62da2b52019-09-12 17:43:34 +0200176 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200177
178 page <- 1
179 results <- 0
Marc Kupietz25aebc32019-09-16 18:40:50 +0200180 pubDate <- NULL # https://stackoverflow.com/questions/8096313/no-visible-binding-for-global-variable-note-in-r-cmd-check
Marc Kupietze95108e2019-09-18 13:23:58 +0200181 collectedMatches <- kqo@collectedMatches
Marc Kupietz62da2b52019-09-12 17:43:34 +0200182
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200183 repeat {
Marc Kupietze95108e2019-09-18 13:23:58 +0200184 res <- fromJSON(paste0(kqo@requestUrl, '&count=', min(ifelse(!is.na(maxFetch), maxFetch - results, maxResultsPerPage), maxResultsPerPage) ,'&offset=', offset + results))
185 if (res$meta$totalResults == 0) { return(kqo) }
186 for (field in kqo@fields) {
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200187 if (!field %in% colnames(res$matches)) {
188 res$matches[, field] <- NA
189 }
190 }
Marc Kupietze95108e2019-09-18 13:23:58 +0200191 currentMatches <- res$matches[kqo@fields]
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200192 factorCols <- colnames(subset(currentMatches, select=-c(pubDate)))
193 currentMatches[factorCols] <- lapply(currentMatches[factorCols], factor)
194 currentMatches$pubDate = as.Date(currentMatches$pubDate, format = "%Y-%m-%d")
Marc Kupietz62da2b52019-09-12 17:43:34 +0200195 if (!is.list(collectedMatches)) {
196 collectedMatches <- currentMatches
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200197 } else {
Marc Kupietz62da2b52019-09-12 17:43:34 +0200198 collectedMatches <- rbind(collectedMatches, currentMatches)
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200199 }
Marc Kupietzc2c59bd2019-08-30 16:50:49 +0200200 if (verbose) {
Marc Kupietz62da2b52019-09-12 17:43:34 +0200201 cat(paste0("Retrieved page: ", page, "/", ceiling((res$meta$totalResults) / res$meta$itemsPerPage), ': ', res$meta$benchmark, '\n'))
Marc Kupietzc2c59bd2019-08-30 16:50:49 +0200202 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200203 page <- page + 1
204 results <- results + res$meta$itemsPerPage
Marc Kupietz62da2b52019-09-12 17:43:34 +0200205 if (offset + results >= res$meta$totalResults || (!is.na(maxFetch) && results >= maxFetch)) {
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200206 break
207 }
208 }
Marc Kupietze95108e2019-09-18 13:23:58 +0200209 nextStartIndex <- min(res$meta$startIndex + res$meta$itemsPerPage, res$meta$totalResults)
210 KorAPQuery(nextStartIndex = nextStartIndex,
211 fields = kqo@fields,
212 requestUrl = kqo@requestUrl,
213 request = kqo@request,
214 totalResults = res$meta$totalResults,
215 vc = kqo@vc,
216 webUIRequestUrl = kqo@webUIRequestUrl,
217 hasMoreMatches = (res$meta$totalResults > nextStartIndex),
218 apiResponse = res,
219 collectedMatches = collectedMatches)
220})
Marc Kupietz62da2b52019-09-12 17:43:34 +0200221
222#' Fetch all results of a KorAP query.
Marc Kupietz62da2b52019-09-12 17:43:34 +0200223#'
224#' @examples
Marc Kupietze95108e2019-09-18 13:23:58 +0200225#' q <- fetchAll(corpusQuery(new("KorAPConnection"), "Ameisenplage"))
226#' q@collectedMatches
Marc Kupietz62da2b52019-09-12 17:43:34 +0200227#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200228#' @aliases fetchAll
229#' @rdname KorAPQuery-class
Marc Kupietz62da2b52019-09-12 17:43:34 +0200230#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +0200231setMethod("fetchAll", "KorAPQuery", function(kqo, verbose = FALSE) {
232 return(fetchNext(kqo, offset = 0, maxFetch = NA, verbose = verbose))
233})
234
235#' Fetches the remaining results of a KorAP query.
236#'
237#' @examples
238#' q <- fetchRest(fetchNext(corpusQuery(new("KorAPConnection"), "Ameisenplage")))
239#' q@collectedMatches
240#'
241#' @aliases fetchRest
242#' @rdname KorAPQuery-class
243#' @export
244setMethod("fetchRest", "KorAPQuery", function(kqo, verbose = FALSE) {
245 return(fetchNext(kqo, maxFetch = NA, verbose = verbose))
246})
247
248#´ format()
249#' @rdname KorAPQuery-class
250#' @param x KorAPQuery object
251#' @param ... further arguments passed to or from other methods
252#' @export
253format.KorAPQuery <- function(x, ...) {
254 cat("<KorAPQuery>\n")
255 q <- x
256 aurl = parse_url(q@request)
257 cat(" Query: ", aurl$query$q, "\n")
258 if (!is.null(aurl$query$vc) && aurl$query$vc != "") {
259 cat("Virtual corpus: ", aurl$query$vc, "\n")
260 }
261 if (!is.null(q@collectedMatches)) {
262 cat("==============================================================================================================", "\n")
263 print(summary(q@collectedMatches))
264 cat("==============================================================================================================", "\n")
265 }
266 cat(" Total results: ", q@totalResults, "\n")
267 cat(" Fetched results: ", q@nextStartIndex, "\n")
Marc Kupietz62da2b52019-09-12 17:43:34 +0200268}
269
Marc Kupietze95108e2019-09-18 13:23:58 +0200270#' show()
Marc Kupietz62da2b52019-09-12 17:43:34 +0200271#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200272#' @rdname KorAPQuery-class
273#' @param object KorAPQuery object
Marc Kupietz62da2b52019-09-12 17:43:34 +0200274#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +0200275setMethod("show", "KorAPQuery", function(object) {
276 format(object)
277})