blob: 9114c83aad5665c29a8aa129fb691a69e77bdfd7 [file] [log] [blame]
Marc Kupietze95108e2019-09-18 13:23:58 +02001#' Class KorAPQuery
2#'
Marc Kupietza6e4ee62021-03-05 09:00:15 +01003#' This class provides methods to perform different kinds of queries on the KorAP API server.
Marc Kupietz67edcb52021-09-20 21:54:24 +02004#' `KorAPQuery` objects, which are typically created by the [corpusQuery()] method,
Marc Kupietza6e4ee62021-03-05 09:00:15 +01005#' represent the current state of a query to a KorAP server.
Marc Kupietze95108e2019-09-18 13:23:58 +02006#'
7#' @include KorAPConnection.R
Marc Kupietze95108e2019-09-18 13:23:58 +02008#' @import httr
9#'
Marc Kupietza6e4ee62021-03-05 09:00:15 +010010#' @include RKorAPClient-package.R
Marc Kupietz5bbc9db2019-08-30 16:30:45 +020011
Marc Kupietze95108e2019-09-18 13:23:58 +020012#' @export
13KorAPQuery <- setClass("KorAPQuery", slots = c(
Marc Kupietzb8972182019-09-20 21:33:46 +020014 "korapConnection",
Marc Kupietze95108e2019-09-18 13:23:58 +020015 "request",
16 "vc",
17 "totalResults",
18 "nextStartIndex",
19 "fields",
20 "requestUrl",
21 "webUIRequestUrl",
22 "apiResponse",
23 "collectedMatches",
24 "hasMoreMatches"
25))
Marc Kupietz5bbc9db2019-08-30 16:30:45 +020026
Marc Kupietze95108e2019-09-18 13:23:58 +020027#' Method initialize
28#'
29#' @rdname KorAPQuery-class
30#' @param .Object …
Marc Kupietzb8972182019-09-20 21:33:46 +020031#' @param korapConnection KorAPConnection object
Marc Kupietze95108e2019-09-18 13:23:58 +020032#' @param request query part of the request URL
33#' @param vc definition of a virtual corpus
34#' @param totalResults number of hits the query has yielded
35#' @param nextStartIndex at what index to start the next fetch of query results
36#' @param fields what data / metadata fields should be collected
37#' @param requestUrl complete URL of the API request
38#' @param webUIRequestUrl URL of a web frontend request corresponding to the API request
39#' @param apiResponse data-frame representation of the JSON response of the API request
Marc Kupietz7776dec2019-09-27 16:59:02 +020040#' @param hasMoreMatches logical that signals if more query results can be fetched
Marc Kupietze95108e2019-09-18 13:23:58 +020041#' @param collectedMatches matches already fetched from the KorAP-API-server
Marc Kupietz97a1bca2019-10-04 22:52:09 +020042#'
43#' @importFrom tibble tibble
Marc Kupietze95108e2019-09-18 13:23:58 +020044#' @export
45setMethod("initialize", "KorAPQuery",
Marc Kupietzb8972182019-09-20 21:33:46 +020046 function(.Object, korapConnection = NULL, request = NULL, vc="", totalResults=0, nextStartIndex=0, fields=c("corpusSigle", "textSigle", "pubDate", "pubPlace",
Marc Kupietze95108e2019-09-18 13:23:58 +020047 "availability", "textClass", "snippet"),
48 requestUrl="", webUIRequestUrl = "", apiResponse = NULL, hasMoreMatches= FALSE, collectedMatches = NULL) {
49 .Object <- callNextMethod()
Marc Kupietzb8972182019-09-20 21:33:46 +020050 .Object@korapConnection = korapConnection
Marc Kupietze95108e2019-09-18 13:23:58 +020051 .Object@request = request
52 .Object@vc = vc
53 .Object@totalResults = totalResults
54 .Object@nextStartIndex = nextStartIndex
55 .Object@fields = fields
56 .Object@requestUrl = requestUrl
57 .Object@webUIRequestUrl = webUIRequestUrl
58 .Object@apiResponse = apiResponse
59 .Object@hasMoreMatches = hasMoreMatches
60 .Object@collectedMatches = collectedMatches
61 .Object
62 })
Marc Kupietz632cbd42019-09-06 16:04:51 +020063
Marc Kupietze95108e2019-09-18 13:23:58 +020064setGeneric("corpusQuery", function(kco, ...) standardGeneric("corpusQuery") )
65setGeneric("fetchAll", function(kqo, ...) standardGeneric("fetchAll") )
66setGeneric("fetchNext", function(kqo, ...) standardGeneric("fetchNext") )
67setGeneric("fetchRest", function(kqo, ...) standardGeneric("fetchRest") )
Marc Kupietz3f575282019-10-04 14:46:04 +020068setGeneric("frequencyQuery", function(kco, ...) standardGeneric("frequencyQuery") )
Marc Kupietze95108e2019-09-18 13:23:58 +020069
70maxResultsPerPage <- 50
Marc Kupietz62da2b52019-09-12 17:43:34 +020071
Marc Kupietz4de53ec2019-10-04 09:12:00 +020072## quiets concerns of R CMD check re: the .'s that appear in pipelines
73if(getRversion() >= "2.15.1") utils::globalVariables(c("."))
Marc Kupietz632cbd42019-09-06 16:04:51 +020074
Marc Kupietzdbd431a2021-08-29 12:17:45 +020075#' Corpus query
76#'
Marc Kupietz67edcb52021-09-20 21:54:24 +020077#' **`corpusQuery`** performs a corpus query via a connection to a KorAP-API-server
Marc Kupietze95108e2019-09-18 13:23:58 +020078#'
Marc Kupietzdbd431a2021-08-29 12:17:45 +020079#' @rdname KorAPQuery-class
80#' @aliases corpusQuery
81#'
82#' @importFrom urltools url_encode
83#' @importFrom purrr pmap
84#' @importFrom dplyr bind_rows
85#'
Marc Kupietz67edcb52021-09-20 21:54:24 +020086#' @param kco [KorAPConnection()] object (obtained e.g. from `new("KorAPConnection")`
87#' @param query string that contains the corpus query. The query language depends on the `ql` parameter. Either `query` must be provided or `KorAPUrl`.
Marc Kupietz632cbd42019-09-06 16:04:51 +020088#' @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.
Marc Kupietz67edcb52021-09-20 21:54:24 +020089#' @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 `KorAPConnection`) to provide all necessary information for the query.
Marc Kupietz132f0052023-04-16 14:23:05 +020090#' @param metadataOnly logical 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.
91#' If you want your corpus queries to return not only metadata, but also KWICS, you need to authorize
92#' your RKorAPClient application as explained in the
93#' [authorization section](https://github.com/KorAP/RKorAPClient#authorization)
94#' of the RKorAPClient Readme on GitHub and set the `metadataOnly` parameter to
95#' `FALSE`.
Marc Kupietz67edcb52021-09-20 21:54:24 +020096#' @param ql string to choose the query language (see [section on Query Parameters](https://github.com/KorAP/Kustvakt/wiki/Service:-Search-GET#user-content-parameters) in the Kustvakt-Wiki for possible values.
Akron5e135462019-09-27 16:31:38 +020097#' @param fields (meta)data fields that will be fetched for every match.
Marc Kupietz43a6ade2020-02-18 17:01:44 +010098#' @param accessRewriteFatal abort if query or given vc had to be rewritten due to insufficient rights (not yet implemented).
Marc Kupietz25aebc32019-09-16 18:40:50 +020099#' @param verbose print some info
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200100#' @param as.df return result as data frame instead of as S4 object?
Marc Kupietz67edcb52021-09-20 21:54:24 +0200101#' @param expand logical that decides if `query` and `vc` parameters are expanded to all of their combinations
102#' @return Depending on the `as.df` parameter, a table or a [KorAPQuery()] object that, among other information, contains the total number of results in `@totalResults`. The resulting object can be used to fetch all query results (with [fetchAll()]) or the next page of results (with [fetchNext()]).
103#' A corresponding URL to be used within a web browser is contained in `@webUIRequestUrl`
104#' Please make sure to check `$collection$rewrites` to see if any unforeseen access rewrites of the query's virtual corpus had to be performed.
Marc Kupietz632cbd42019-09-06 16:04:51 +0200105#'
106#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +0200107#' \dontrun{
108#'
Marc Kupietz603491f2019-09-18 14:01:02 +0200109#' # Fetch metadata of every query hit for "Ameisenplage" and show a summary
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200110#' new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchAll()
Marc Kupietz657d8e72020-02-25 18:31:50 +0100111#' }
Marc Kupietz3c531f62019-09-13 12:17:24 +0200112#'
Marc Kupietz6ae76052021-09-21 10:34:00 +0200113#' \dontrun{
114#'
Marc Kupietz603491f2019-09-18 14:01:02 +0200115#' # Use the copy of a KorAP-web-frontend URL for an API query of "Ameise" in a virtual corpus
116#' # and show the number of query hits (but don't fetch them).
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200117#'
118#' new("KorAPConnection", verbose = TRUE) %>%
119#' corpusQuery(KorAPUrl =
120#' "https://korap.ids-mannheim.de/?q=Ameise&cq=pubDate+since+2017&ql=poliqarp")
Marc Kupietz6ae76052021-09-21 10:34:00 +0200121#' }
122#'
123#' \dontrun{
Marc Kupietz3c531f62019-09-13 12:17:24 +0200124#'
Marc Kupietz603491f2019-09-18 14:01:02 +0200125#' # Plot the time/frequency curve of "Ameisenplage"
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200126#' new("KorAPConnection", verbose=TRUE) %>%
127#' { . ->> kco } %>%
128#' corpusQuery("Ameisenplage") %>%
129#' fetchAll() %>%
130#' slot("collectedMatches") %>%
131#' mutate(year = lubridate::year(pubDate)) %>%
Marc Kupietz19e2ebd2019-10-07 11:45:30 +0200132#' dplyr::select(year) %>%
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200133#' group_by(year) %>%
Marc Kupietzcb3c59e2020-06-02 10:10:43 +0200134#' summarise(Count = dplyr::n()) %>%
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200135#' mutate(Freq = mapply(function(f, y)
136#' f / corpusStats(kco, paste("pubDate in", y))@tokens, Count, year)) %>%
Marc Kupietz19e2ebd2019-10-07 11:45:30 +0200137#' dplyr::select(-Count) %>%
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200138#' complete(year = min(year):max(year), fill = list(Freq = 0)) %>%
139#' plot(type = "l")
Marc Kupietz05b22772020-02-18 21:58:42 +0100140#' }
Marc Kupietz67edcb52021-09-20 21:54:24 +0200141#' @seealso [KorAPConnection()], [fetchNext()], [fetchRest()], [fetchAll()], [corpusStats()]
Marc Kupietz632cbd42019-09-06 16:04:51 +0200142#'
143#' @references
Marc Kupietz67edcb52021-09-20 21:54:24 +0200144#' <https://ids-pub.bsz-bw.de/frontdoor/index/index/docId/9026>
Marc Kupietz632cbd42019-09-06 16:04:51 +0200145#'
146#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +0200147setMethod("corpusQuery", "KorAPConnection",
Marc Kupietza96537f2019-11-09 23:07:44 +0100148 function(kco,
149 query = if (missing(KorAPUrl))
150 stop("At least one of the parameters query and KorAPUrl must be specified.", call. = FALSE)
151 else
152 httr::parse_url(KorAPUrl)$query$q,
153 vc = if (missing(KorAPUrl)) "" else httr::parse_url(KorAPUrl)$query$cq,
154 KorAPUrl,
155 metadataOnly = TRUE,
156 ql = if (missing(KorAPUrl)) "poliqarp" else httr::parse_url(KorAPUrl)$query$ql,
157 fields = c(
158 "corpusSigle",
159 "textSigle",
160 "pubDate",
161 "pubPlace",
162 "availability",
163 "textClass",
164 "snippet"
165 ),
166 accessRewriteFatal = TRUE,
167 verbose = kco@verbose,
168 expand = length(vc) != length(query),
169 as.df = FALSE) {
170 if (length(query) > 1 || length(vc) > 1) {
Marc Kupietzdbd431a2021-08-29 12:17:45 +0200171 grid <- if (expand) expand_grid(query=query, vc=vc) else tibble(query=query, vc=vc)
172 purrr::pmap(grid, function(query, vc, ...)
173 corpusQuery(kco, query=query, vc=vc, ql=ql, verbose=verbose, as.df = TRUE)) %>%
174 bind_rows()
175 } else {
Marc Kupietza96537f2019-11-09 23:07:44 +0100176 contentFields <- c("snippet")
177 if (metadataOnly) {
178 fields <- fields[!fields %in% contentFields]
179 }
180 request <-
181 paste0('?q=',
Marc Kupietzdbd431a2021-08-29 12:17:45 +0200182 url_encode(enc2utf8(query)),
183 ifelse (vc != '', paste0('&cq=', url_encode(enc2utf8(vc))), ''), '&ql=', ql)
Marc Kupietza96537f2019-11-09 23:07:44 +0100184 webUIRequestUrl <- paste0(kco@KorAPUrl, request)
185 requestUrl <- paste0(
186 kco@apiUrl,
187 'search',
188 request,
189 '&fields=',
190 paste(fields, collapse = ","),
191 if (metadataOnly) '&access-rewrite-disabled=true' else ''
192 )
193 log.info(verbose, "Searching \"", query, "\" in \"", vc, "\"", sep =
194 "")
195 res = apiCall(kco, paste0(requestUrl, '&count=0'))
Marc Kupietza4675722022-02-23 23:55:15 +0100196 if (is.null(res)) {
197 log.info(verbose, " [failed]\n")
198 message("API call failed.")
199 totalResults <- 0
200 } else {
201 totalResults <-res$meta$totalResults
202 log.info(verbose, ": ", totalResults, " hits")
203 if(!is.null(res$meta$cached))
204 log.info(verbose, " [cached]\n")
205 else
206 log.info(verbose, ", took ", res$meta$benchmark, "\n", sep = "")
207 }
Marc Kupietza96537f2019-11-09 23:07:44 +0100208 if (as.df)
209 data.frame(
210 query = query,
Marc Kupietza4675722022-02-23 23:55:15 +0100211 totalResults = totalResults,
Marc Kupietza96537f2019-11-09 23:07:44 +0100212 vc = vc,
213 webUIRequestUrl = webUIRequestUrl,
214 stringsAsFactors = FALSE
215 )
216 else
217 KorAPQuery(
218 korapConnection = kco,
219 nextStartIndex = 0,
220 fields = fields,
221 requestUrl = requestUrl,
222 request = request,
Marc Kupietza4675722022-02-23 23:55:15 +0100223 totalResults = totalResults,
Marc Kupietza96537f2019-11-09 23:07:44 +0100224 vc = vc,
225 apiResponse = res,
226 webUIRequestUrl = webUIRequestUrl,
Marc Kupietza4675722022-02-23 23:55:15 +0100227 hasMoreMatches = (totalResults > 0),
Marc Kupietza96537f2019-11-09 23:07:44 +0100228 )
229 }
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200230 })
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200231
Marc Kupietz62da2b52019-09-12 17:43:34 +0200232#' Fetch the next bunch of results of a KorAP query.
Marc Kupietze95108e2019-09-18 13:23:58 +0200233#'
Marc Kupietz67edcb52021-09-20 21:54:24 +0200234#' **`fetchNext`** fetches the next bunch of results of a KorAP query.
Marc Kupietz3f575282019-10-04 14:46:04 +0200235#'
Marc Kupietz67edcb52021-09-20 21:54:24 +0200236#' @param kqo object obtained from [corpusQuery()]
Marc Kupietz62da2b52019-09-12 17:43:34 +0200237#' @param offset start offset for query results to fetch
238#' @param maxFetch maximum number of query results to fetch
Marc Kupietz25aebc32019-09-16 18:40:50 +0200239#' @param verbose print progress information if true
Marc Kupietz67edcb52021-09-20 21:54:24 +0200240#' @param randomizePageOrder fetch result pages in pseudo random order if true. Use [set.seed()] to set seed for reproducible results.
241#' @return The `kqo` input object with updated slots `collectedMatches`, `apiResponse`, `nextStartIndex`, `hasMoreMatches`
Marc Kupietz62da2b52019-09-12 17:43:34 +0200242#'
Marc Kupietz05b22772020-02-18 21:58:42 +0100243#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +0200244#' \dontrun{
245#'
246#' q <- new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchNext()
Marc Kupietz05b22772020-02-18 21:58:42 +0100247#' q@collectedMatches
Marc Kupietz657d8e72020-02-25 18:31:50 +0100248#' }
Marc Kupietz05b22772020-02-18 21:58:42 +0100249#'
Marc Kupietz62da2b52019-09-12 17:43:34 +0200250#' @references
Marc Kupietz67edcb52021-09-20 21:54:24 +0200251#' <https://ids-pub.bsz-bw.de/frontdoor/index/index/docId/9026>
Marc Kupietz62da2b52019-09-12 17:43:34 +0200252#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200253#' @aliases fetchNext
254#' @rdname KorAPQuery-class
Marc Kupietzcb3c59e2020-06-02 10:10:43 +0200255#' @importFrom dplyr rowwise bind_rows select summarise n
Marc Kupietz632cbd42019-09-06 16:04:51 +0200256#' @export
Marc Kupietzdbd431a2021-08-29 12:17:45 +0200257setMethod("fetchNext", "KorAPQuery", function(kqo,
258 offset = kqo@nextStartIndex,
259 maxFetch = maxResultsPerPage,
260 verbose = kqo@korapConnection@verbose,
261 randomizePageOrder = FALSE) {
Marc Kupietze95108e2019-09-18 13:23:58 +0200262 if (kqo@totalResults == 0 || offset >= kqo@totalResults) {
263 return(kqo)
Marc Kupietz62da2b52019-09-12 17:43:34 +0200264 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200265
Marc Kupietz705488d2021-06-30 18:26:36 +0200266 page <- kqo@nextStartIndex / maxResultsPerPage + 1
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200267 results <- 0
Marc Kupietz25aebc32019-09-16 18:40:50 +0200268 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 +0200269 collectedMatches <- kqo@collectedMatches
Marc Kupietz62da2b52019-09-12 17:43:34 +0200270
Marc Kupietzdbd431a2021-08-29 12:17:45 +0200271 if (randomizePageOrder) {
272 pages <- head(sample.int(ceiling(kqo@totalResults / maxResultsPerPage)), maxFetch) - 1
273 }
274
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200275 repeat {
Marc Kupietzdbd431a2021-08-29 12:17:45 +0200276 page = length(collectedMatches[,1]) %/% maxResultsPerPage + 1
277 currentOffset = ifelse(randomizePageOrder, pages[page], page - 1) * maxResultsPerPage
278 query <- paste0(kqo@requestUrl, '&count=', min(if (!is.na(maxFetch)) maxFetch - results else maxResultsPerPage, maxResultsPerPage) ,'&offset=', currentOffset, '&cutoff=true')
Marc Kupietz68170952021-06-30 09:37:21 +0200279 res <- apiCall(kqo@korapConnection, query)
280 if (length(res$matches) == 0) {
281 break
282 }
283
Marc Kupietze95108e2019-09-18 13:23:58 +0200284 for (field in kqo@fields) {
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200285 if (!field %in% colnames(res$matches)) {
286 res$matches[, field] <- NA
287 }
288 }
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200289 currentMatches <-
Marc Kupietzf75ab0b2020-06-02 12:31:18 +0200290 res$matches %>%
Marc Kupietz19e2ebd2019-10-07 11:45:30 +0200291 dplyr::select(kqo@fields)
Marc Kupietz36d12d92019-09-27 18:13:27 +0200292 if ("pubDate" %in% kqo@fields) {
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200293 currentMatches$pubDate <- currentMatches$pubDate %>% as.Date(format = "%Y-%m-%d")
294 factorCols <- currentMatches %>% select(-pubDate) %>% colnames()
Marc Kupietz36d12d92019-09-27 18:13:27 +0200295 } else {
296 factorCols <- colnames(currentMatches)
297 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200298 currentMatches[factorCols] <- lapply(currentMatches[factorCols], factor)
Marc Kupietz62da2b52019-09-12 17:43:34 +0200299 if (!is.list(collectedMatches)) {
300 collectedMatches <- currentMatches
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200301 } else {
Marc Kupietz62da2b52019-09-12 17:43:34 +0200302 collectedMatches <- rbind(collectedMatches, currentMatches)
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200303 }
Marc Kupietzc2c59bd2019-08-30 16:50:49 +0200304 if (verbose) {
Marc Kupietzdbd431a2021-08-29 12:17:45 +0200305 cat(paste0(
306 "Retrieved page ",
307 ceiling(length(collectedMatches[, 1]) / res$meta$itemsPerPage),
308 "/",
309 if (!is.na(maxFetch) && maxFetch < kqo@totalResults)
310 sprintf("%d (%d)", ceiling(maxFetch / res$meta$itemsPerPage), ceiling(kqo@totalResults / res$meta$itemsPerPage))
311 else
312 sprintf("%d", ceiling(kqo@totalResults / res$meta$itemsPerPage)),
313 ' in ',
314 res$meta$benchmark,
315 '\n'
316 ))
Marc Kupietzc2c59bd2019-08-30 16:50:49 +0200317 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200318 page <- page + 1
319 results <- results + res$meta$itemsPerPage
Marc Kupietzdbd431a2021-08-29 12:17:45 +0200320 if (length(collectedMatches[,1]) >= kqo@totalResults || (!is.na(maxFetch) && results >= maxFetch)) {
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200321 break
322 }
323 }
Marc Kupietz68170952021-06-30 09:37:21 +0200324 nextStartIndex <- min(res$meta$startIndex + res$meta$itemsPerPage, kqo@totalResults)
Marc Kupietze95108e2019-09-18 13:23:58 +0200325 KorAPQuery(nextStartIndex = nextStartIndex,
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200326 korapConnection = kqo@korapConnection,
Marc Kupietze95108e2019-09-18 13:23:58 +0200327 fields = kqo@fields,
328 requestUrl = kqo@requestUrl,
329 request = kqo@request,
Marc Kupietz68170952021-06-30 09:37:21 +0200330 totalResults = kqo@totalResults,
Marc Kupietze95108e2019-09-18 13:23:58 +0200331 vc = kqo@vc,
332 webUIRequestUrl = kqo@webUIRequestUrl,
Marc Kupietz68170952021-06-30 09:37:21 +0200333 hasMoreMatches = (kqo@totalResults > nextStartIndex),
Marc Kupietze95108e2019-09-18 13:23:58 +0200334 apiResponse = res,
335 collectedMatches = collectedMatches)
336})
Marc Kupietz62da2b52019-09-12 17:43:34 +0200337
338#' Fetch all results of a KorAP query.
Marc Kupietz62da2b52019-09-12 17:43:34 +0200339#'
Marc Kupietz67edcb52021-09-20 21:54:24 +0200340#' **`fetchAll`** fetches all results of a KorAP query.
Marc Kupietza6e4ee62021-03-05 09:00:15 +0100341#'
Marc Kupietz62da2b52019-09-12 17:43:34 +0200342#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +0200343#' \dontrun{
344#'
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200345#' q <- new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchAll()
Marc Kupietze95108e2019-09-18 13:23:58 +0200346#' q@collectedMatches
Marc Kupietz05b22772020-02-18 21:58:42 +0100347#' }
Marc Kupietz62da2b52019-09-12 17:43:34 +0200348#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200349#' @aliases fetchAll
350#' @rdname KorAPQuery-class
Marc Kupietz62da2b52019-09-12 17:43:34 +0200351#' @export
Marc Kupietzdbd431a2021-08-29 12:17:45 +0200352setMethod("fetchAll", "KorAPQuery", function(kqo, verbose = kqo@korapConnection@verbose, ...) {
353 return(fetchNext(kqo, offset = 0, maxFetch = NA, verbose = verbose, ...))
Marc Kupietze95108e2019-09-18 13:23:58 +0200354})
355
356#' Fetches the remaining results of a KorAP query.
357#'
358#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +0200359#' \dontrun{
360#'
Marc Kupietz05b22772020-02-18 21:58:42 +0100361#' q <- new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchRest()
Marc Kupietze95108e2019-09-18 13:23:58 +0200362#' q@collectedMatches
Marc Kupietz05b22772020-02-18 21:58:42 +0100363#' }
Marc Kupietze95108e2019-09-18 13:23:58 +0200364#'
365#' @aliases fetchRest
366#' @rdname KorAPQuery-class
367#' @export
Marc Kupietzdbd431a2021-08-29 12:17:45 +0200368setMethod("fetchRest", "KorAPQuery", function(kqo, verbose = kqo@korapConnection@verbose, ...) {
369 return(fetchNext(kqo, maxFetch = NA, verbose = verbose, ...))
Marc Kupietze95108e2019-09-18 13:23:58 +0200370})
371
Marc Kupietz3f575282019-10-04 14:46:04 +0200372#' Query relative frequency of search term(s)
373#'
Marc Kupietz67edcb52021-09-20 21:54:24 +0200374#' **`frequencyQuery`** combines [corpusQuery()], [corpusStats()] and
375#' [ci()] to compute a table with the relative frequencies and
Marc Kupietz3f575282019-10-04 14:46:04 +0200376#' confidence intervals of one ore multiple search terms across one or multiple
377#' virtual corpora.
378#'
379#' @aliases frequencyQuery
380#' @rdname KorAPQuery-class
381#' @examples
Marc Kupietz6ae76052021-09-21 10:34:00 +0200382#' \dontrun{
383#'
Marc Kupietz3f575282019-10-04 14:46:04 +0200384#' new("KorAPConnection", verbose = TRUE) %>%
385#' frequencyQuery(c("Mücke", "Schnake"), paste0("pubDate in ", 2000:2003))
Marc Kupietz05b22772020-02-18 21:58:42 +0100386#' }
Marc Kupietz3f575282019-10-04 14:46:04 +0200387#'
Marc Kupietz67edcb52021-09-20 21:54:24 +0200388#' @param kco [KorAPConnection()] object (obtained e.g. from `new("KorAPConnection")`
389#' @param query string that contains the corpus query. The query language depends on the `ql` parameter. Either `query` must be provided or `KorAPUrl`.
390#' @param conf.level confidence level of the returned confidence interval (passed through [ci()] to [prop.test()]).
391#' @param as.alternatives LOGICAL that specifies if the query terms should be treated as alternatives. If `as.alternatives` is TRUE, the sum over all query hits, instead of the respective vc token sizes is used as total for the calculation of relative frequencies.
Marc Kupietz3f575282019-10-04 14:46:04 +0200392#' @export
393setMethod("frequencyQuery", "KorAPConnection",
Marc Kupietz71d6e052019-11-22 18:42:10 +0100394 function(kco, query, vc = "", conf.level = 0.95, as.alternatives = FALSE, ...) {
395 (if (as.alternatives) {
396 corpusQuery(kco, query, vc, metadataOnly = TRUE, as.df = TRUE, ...) %>%
397 group_by(vc) %>%
398 mutate(total = sum(totalResults))
399 } else {
400 corpusQuery(kco, query, vc, metadataOnly = TRUE, as.df = TRUE, ...) %>%
401 mutate(total = corpusStats(kco, vc=vc, as.df=TRUE)$tokens)
402 } ) %>%
Marc Kupietz0c29cea2019-10-09 08:44:36 +0200403 ci(conf.level = conf.level)
Marc Kupietz3f575282019-10-04 14:46:04 +0200404})
405
Marc Kupietzdbd431a2021-08-29 12:17:45 +0200406
407#' buildWebUIRequestUrl
408#'
409#' @rdname KorAPQuery-class
410#' @importFrom urltools url_encode
411#' @export
412buildWebUIRequestUrl <- function(kco,
413 query = if (missing(KorAPUrl))
414 stop("At least one of the parameters query and KorAPUrl must be specified.", call. = FALSE)
415 else
416 httr::parse_url(KorAPUrl)$query$q,
417 vc = if (missing(KorAPUrl)) "" else httr::parse_url(KorAPUrl)$query$cq,
418 KorAPUrl,
419 metadataOnly = TRUE,
420 ql = if (missing(KorAPUrl)) "poliqarp" else httr::parse_url(KorAPUrl)$query$ql,
421 fields = c(
422 "corpusSigle",
423 "textSigle",
424 "pubDate",
425 "pubPlace",
426 "availability",
427 "textClass",
428 "snippet"
429 ),
430 accessRewriteFatal = TRUE) {
431 request <-
432 paste0(
433 '?q=',
434 urltools::url_encode(enc2utf8(as.character(query))),
435 ifelse(vc != '',
436 paste0('&cq=', urltools::url_encode(enc2utf8(vc))),
437 ''),
438 '&ql=',
439 ql
440 )
441 webUIRequestUrl <- paste0(kco@KorAPUrl, request)
442 requestUrl <- paste0(
443 kco@apiUrl,
444 'search',
445 request,
446 '&fields=',
447 paste(fields, collapse = ","),
448 if (metadataOnly)
449 '&access-rewrite-disabled=true'
450 else
451 ''
452 )
453 webUIRequestUrl
454}
455
Marc Kupietze95108e2019-09-18 13:23:58 +0200456#´ format()
457#' @rdname KorAPQuery-class
458#' @param x KorAPQuery object
459#' @param ... further arguments passed to or from other methods
460#' @export
461format.KorAPQuery <- function(x, ...) {
462 cat("<KorAPQuery>\n")
463 q <- x
464 aurl = parse_url(q@request)
Marc Kupietz0d4c9092020-03-23 09:02:30 +0100465 cat(" Query: ", aurl$query$q, "\n")
466 if (!is.null(aurl$query$cq) && aurl$query$cq != "") {
467 cat(" Virtual corpus: ", aurl$query$cq, "\n")
Marc Kupietze95108e2019-09-18 13:23:58 +0200468 }
469 if (!is.null(q@collectedMatches)) {
470 cat("==============================================================================================================", "\n")
471 print(summary(q@collectedMatches))
472 cat("==============================================================================================================", "\n")
473 }
474 cat(" Total results: ", q@totalResults, "\n")
475 cat(" Fetched results: ", q@nextStartIndex, "\n")
Marc Kupietz62da2b52019-09-12 17:43:34 +0200476}
477
Marc Kupietze95108e2019-09-18 13:23:58 +0200478#' show()
Marc Kupietz62da2b52019-09-12 17:43:34 +0200479#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200480#' @rdname KorAPQuery-class
481#' @param object KorAPQuery object
Marc Kupietz62da2b52019-09-12 17:43:34 +0200482#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +0200483setMethod("show", "KorAPQuery", function(object) {
484 format(object)
485})
Marc Kupietz006b47c2021-01-13 17:00:59 +0100486