blob: 9894d8794a8d92651bb2dfb37380fe00d798e92f [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 Kupietze95108e2019-09-18 13:23:58 +02007#' @import httr
8#'
Marc Kupietz4de53ec2019-10-04 09:12:00 +02009#' @include RKorAPClient.R
Marc Kupietz5bbc9db2019-08-30 16:30:45 +020010
Marc Kupietze95108e2019-09-18 13:23:58 +020011#' @export
12KorAPQuery <- setClass("KorAPQuery", slots = c(
Marc Kupietzb8972182019-09-20 21:33:46 +020013 "korapConnection",
Marc Kupietze95108e2019-09-18 13:23:58 +020014 "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 …
Marc Kupietzb8972182019-09-20 21:33:46 +020030#' @param korapConnection KorAPConnection object
Marc Kupietze95108e2019-09-18 13:23:58 +020031#' @param request query part of the request URL
32#' @param vc definition of a virtual corpus
33#' @param totalResults number of hits the query has yielded
34#' @param nextStartIndex at what index to start the next fetch of query results
35#' @param fields what data / metadata fields should be collected
36#' @param requestUrl complete URL of the API request
37#' @param webUIRequestUrl URL of a web frontend request corresponding to the API request
38#' @param apiResponse data-frame representation of the JSON response of the API request
Marc Kupietz7776dec2019-09-27 16:59:02 +020039#' @param hasMoreMatches logical that signals if more query results can be fetched
Marc Kupietze95108e2019-09-18 13:23:58 +020040#' @param collectedMatches matches already fetched from the KorAP-API-server
Marc Kupietz97a1bca2019-10-04 22:52:09 +020041#'
42#' @importFrom tibble tibble
Marc Kupietze95108e2019-09-18 13:23:58 +020043#' @export
44setMethod("initialize", "KorAPQuery",
Marc Kupietzb8972182019-09-20 21:33:46 +020045 function(.Object, korapConnection = NULL, request = NULL, vc="", totalResults=0, nextStartIndex=0, fields=c("corpusSigle", "textSigle", "pubDate", "pubPlace",
Marc Kupietze95108e2019-09-18 13:23:58 +020046 "availability", "textClass", "snippet"),
47 requestUrl="", webUIRequestUrl = "", apiResponse = NULL, hasMoreMatches= FALSE, collectedMatches = NULL) {
48 .Object <- callNextMethod()
Marc Kupietzb8972182019-09-20 21:33:46 +020049 .Object@korapConnection = korapConnection
Marc Kupietze95108e2019-09-18 13:23:58 +020050 .Object@request = request
51 .Object@vc = vc
52 .Object@totalResults = totalResults
53 .Object@nextStartIndex = nextStartIndex
54 .Object@fields = fields
55 .Object@requestUrl = requestUrl
56 .Object@webUIRequestUrl = webUIRequestUrl
57 .Object@apiResponse = apiResponse
58 .Object@hasMoreMatches = hasMoreMatches
59 .Object@collectedMatches = collectedMatches
60 .Object
61 })
Marc Kupietz632cbd42019-09-06 16:04:51 +020062
Marc Kupietze95108e2019-09-18 13:23:58 +020063setGeneric("corpusQuery", function(kco, ...) standardGeneric("corpusQuery") )
64setGeneric("fetchAll", function(kqo, ...) standardGeneric("fetchAll") )
65setGeneric("fetchNext", function(kqo, ...) standardGeneric("fetchNext") )
66setGeneric("fetchRest", function(kqo, ...) standardGeneric("fetchRest") )
Marc Kupietz3f575282019-10-04 14:46:04 +020067setGeneric("frequencyQuery", function(kco, ...) standardGeneric("frequencyQuery") )
Marc Kupietze95108e2019-09-18 13:23:58 +020068
69maxResultsPerPage <- 50
Marc Kupietz62da2b52019-09-12 17:43:34 +020070
Marc Kupietz632cbd42019-09-06 16:04:51 +020071QueryParameterFromUrl <- function(url, parameter) {
72 regex <- paste0(".*[?&]", parameter, "=([^&]*).*")
73 if (grepl(regex, url)) {
74 return(gsub(regex, '\\1', url, perl = TRUE))
75 } else {
76 return("")
77 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +020078}
79
Marc Kupietz4de53ec2019-10-04 09:12:00 +020080## quiets concerns of R CMD check re: the .'s that appear in pipelines
81if(getRversion() >= "2.15.1") utils::globalVariables(c("."))
Marc Kupietz632cbd42019-09-06 16:04:51 +020082
Marc Kupietze95108e2019-09-18 13:23:58 +020083#' Method corpusQuery
84#'
85#' Perform a corpus query via a connection to a KorAP-API-server.
86#'
87#' @param kco \code{\link{KorAPConnection}} object (obtained e.g. from \code{new("KorAPConnection")}
Akron5e135462019-09-27 16:31:38 +020088#' @param query string that contains the corpus query. The query language depends on the \code{ql} parameter. Either \code{query} must be provided or \code{KorAPUrl}.
Marc Kupietz632cbd42019-09-06 16:04:51 +020089#' @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.
90#' @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 Kupietz7776dec2019-09-27 16:59:02 +020091#' @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, unless the connection is authorized (currently not possible).
Marc Kupietz3c531f62019-09-13 12:17:24 +020092#' @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.
Akron5e135462019-09-27 16:31:38 +020093#' @param fields (meta)data fields that will be fetched for every match.
94#' @param accessRewriteFatal abort if query or given vc had to be rewritten due to insufficent rights (not yet implemented).
Marc Kupietz25aebc32019-09-16 18:40:50 +020095#' @param verbose print some info
Marc Kupietz4de53ec2019-10-04 09:12:00 +020096#' @param as.df return result as data frame instead of as S4 object?
Marc Kupietz3f575282019-10-04 14:46:04 +020097#' @param expand logical that deicdes if \code{query} and \code{vc} parameters are expanded to all of their combinations
98#' @return Depending on the \code{as.df} parameter, a table or 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}}).
Marc Kupietze95108e2019-09-18 13:23:58 +020099#' A corresponding URL to be used within a web browser is contained in \code{@webUIRequestUrl}
Marc Kupietz62da2b52019-09-12 17:43:34 +0200100#' 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 +0200101#'
102#' @examples
Marc Kupietz603491f2019-09-18 14:01:02 +0200103#' # Fetch metadata of every query hit for "Ameisenplage" and show a summary
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200104#' new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchAll()
Marc Kupietz3c531f62019-09-13 12:17:24 +0200105#'
Marc Kupietz603491f2019-09-18 14:01:02 +0200106#' # Use the copy of a KorAP-web-frontend URL for an API query of "Ameise" in a virtual corpus
107#' # and show the number of query hits (but don't fetch them).
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200108#'
109#' new("KorAPConnection", verbose = TRUE) %>%
110#' corpusQuery(KorAPUrl =
111#' "https://korap.ids-mannheim.de/?q=Ameise&cq=pubDate+since+2017&ql=poliqarp")
Marc Kupietz3c531f62019-09-13 12:17:24 +0200112#'
Marc Kupietz603491f2019-09-18 14:01:02 +0200113#' # Plot the time/frequency curve of "Ameisenplage"
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200114#' new("KorAPConnection", verbose=TRUE) %>%
115#' { . ->> kco } %>%
116#' corpusQuery("Ameisenplage") %>%
117#' fetchAll() %>%
118#' slot("collectedMatches") %>%
119#' mutate(year = lubridate::year(pubDate)) %>%
Marc Kupietz19e2ebd2019-10-07 11:45:30 +0200120#' dplyr::select(year) %>%
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200121#' group_by(year) %>%
122#' summarise(Count = n()) %>%
123#' mutate(Freq = mapply(function(f, y)
124#' f / corpusStats(kco, paste("pubDate in", y))@tokens, Count, year)) %>%
Marc Kupietz19e2ebd2019-10-07 11:45:30 +0200125#' dplyr::select(-Count) %>%
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200126#' complete(year = min(year):max(year), fill = list(Freq = 0)) %>%
127#' plot(type = "l")
Marc Kupietz37b8ef12019-09-16 18:37:49 +0200128#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200129#' @seealso \code{\link{KorAPConnection}}, \code{\link{fetchNext}}, \code{\link{fetchRest}}, \code{\link{fetchAll}}, \code{\link{corpusStats}}
Marc Kupietz632cbd42019-09-06 16:04:51 +0200130#'
131#' @references
132#' \url{https://ids-pub.bsz-bw.de/frontdoor/index/index/docId/9026}
133#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200134#' @aliases corpusQuery
Marc Kupietz632cbd42019-09-06 16:04:51 +0200135#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +0200136setMethod("corpusQuery", "KorAPConnection",
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200137 function(kco,
138 query = ifelse(missing(KorAPUrl),
139 stop("At least one of the parameters query and KorAPUrl must be specified.", call. = FALSE),
140 httr::parse_url(KorAPUrl)$query$q),
141 vc = ifelse(missing(KorAPUrl), "", httr::parse_url(KorAPUrl)$query$cq),
142 KorAPUrl,
143 metadataOnly = TRUE,
144 ql = ifelse(missing(KorAPUrl), "poliqarp", httr::parse_url(KorAPUrl)$query$ql),
145 fields = c("corpusSigle", "textSigle", "pubDate", "pubPlace",
146 "availability", "textClass", "snippet"),
147 accessRewriteFatal = TRUE,
148 verbose = kco@verbose,
Marc Kupietz3f575282019-10-04 14:46:04 +0200149 expand = length(vc) != length(query),
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200150 as.df = FALSE) {
Marc Kupietz3f575282019-10-04 14:46:04 +0200151 ifelse(length(query) > 1 || length(vc) > 1, {
152 grid <- { if (expand) expand_grid(query=query, vc=vc) else tibble(query=query, vc=vc) }
153 return(
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200154 do.call(rbind,
Marc Kupietz3f575282019-10-04 14:46:04 +0200155 Map(function(q, cq) corpusQuery(kco, query=q, vc=cq, ql=ql,
156 verbose=verbose, as.df = TRUE), grid$query, grid$vc)) %>%
157 remove_rownames()
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200158 )}, {
159 contentFields <- c("snippet")
160 fields <- fields[!fields %in% contentFields]
161 request <- paste0('?q=', URLencode(query, reserved=TRUE),
162 ifelse(vc != '', paste0('&cq=', URLencode(vc, reserved=TRUE)), ''), '&ql=', ql)
163 webUIRequestUrl <- paste0(kco@KorAPUrl, request)
164 requestUrl <- paste0(kco@apiUrl, 'search', request,
165 '&fields=', paste(fields, collapse = ","),
166 ifelse(metadataOnly, '&access-rewrite-disabled=true', ''))
167 log.info(verbose, "Searching \"", query, "\" in \"", vc, "\"", sep="")
168 res = apiCall(kco, paste0(requestUrl, '&count=0'))
169 log.info(verbose, " took ", res$meta$benchmark, "\n", sep="")
170 ifelse(as.df,
171 return(data.frame(query=query,
172 totalResults=res$meta$totalResults,
173 vc=vc,
174 webUIRequestUrl=webUIRequestUrl, stringsAsFactors = FALSE)),
175 return(KorAPQuery(
176 korapConnection = kco,
177 nextStartIndex = 0,
178 fields = fields,
179 requestUrl = requestUrl,
180 request = request,
181 totalResults = res$meta$totalResults,
182 vc = vc,
183 apiResponse = res,
184 webUIRequestUrl = webUIRequestUrl,
185 hasMoreMatches = (res$meta$totalResults > 0),
186 )))})
187 })
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200188
Marc Kupietz62da2b52019-09-12 17:43:34 +0200189#' Fetch the next bunch of results of a KorAP query.
Marc Kupietze95108e2019-09-18 13:23:58 +0200190#'
Marc Kupietz3f575282019-10-04 14:46:04 +0200191#' \bold{\code{fetchNext}} fetches the next bunch of results of a KorAP query.
192#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200193#' @param kqo object obtained from \code{\link{corpusQuery}}
Marc Kupietz62da2b52019-09-12 17:43:34 +0200194#' @param offset start offset for query results to fetch
195#' @param maxFetch maximum number of query results to fetch
Marc Kupietz25aebc32019-09-16 18:40:50 +0200196#' @param verbose print progress information if true
Marc Kupietze95108e2019-09-18 13:23:58 +0200197#' @return The \code{kqo} input object with updated slots \code{collectedMatches}, \code{apiResponse}, \code{nextStartIndex}, \code{hasMoreMatches}
Marc Kupietz62da2b52019-09-12 17:43:34 +0200198#'
199#' @references
200#' \url{https://ids-pub.bsz-bw.de/frontdoor/index/index/docId/9026}
201#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200202#' @aliases fetchNext
203#' @rdname KorAPQuery-class
Marc Kupietz97a1bca2019-10-04 22:52:09 +0200204#' @importFrom purrr map_dfr
Marc Kupietz19e2ebd2019-10-07 11:45:30 +0200205#' @importFrom dplyr rowwise bind_rows select
Marc Kupietz632cbd42019-09-06 16:04:51 +0200206#' @export
Marc Kupietzf6f71312019-09-23 18:35:27 +0200207setMethod("fetchNext", "KorAPQuery", function(kqo, offset = kqo@nextStartIndex, maxFetch = maxResultsPerPage, verbose = kqo@korapConnection@verbose) {
Marc Kupietze95108e2019-09-18 13:23:58 +0200208 if (kqo@totalResults == 0 || offset >= kqo@totalResults) {
209 return(kqo)
Marc Kupietz62da2b52019-09-12 17:43:34 +0200210 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200211
212 page <- 1
213 results <- 0
Marc Kupietz25aebc32019-09-16 18:40:50 +0200214 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 +0200215 collectedMatches <- kqo@collectedMatches
Marc Kupietz62da2b52019-09-12 17:43:34 +0200216
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200217 repeat {
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200218 res <- apiCall(kqo@korapConnection, paste0(kqo@requestUrl, '&count=', min(ifelse(!is.na(maxFetch), maxFetch - results, maxResultsPerPage), maxResultsPerPage) ,'&offset=', offset + results))
Marc Kupietze95108e2019-09-18 13:23:58 +0200219 if (res$meta$totalResults == 0) { return(kqo) }
220 for (field in kqo@fields) {
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200221 if (!field %in% colnames(res$matches)) {
222 res$matches[, field] <- NA
223 }
224 }
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200225 currentMatches <-
226 kqo@fields %>%
227 map_dfr( ~tibble(!!.x := logical() ) ) %>%
228 bind_rows(res$matches) %>%
Marc Kupietz19e2ebd2019-10-07 11:45:30 +0200229 dplyr::select(kqo@fields)
Marc Kupietz36d12d92019-09-27 18:13:27 +0200230 if ("pubDate" %in% kqo@fields) {
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200231 currentMatches$pubDate <- currentMatches$pubDate %>% as.Date(format = "%Y-%m-%d")
232 factorCols <- currentMatches %>% select(-pubDate) %>% colnames()
Marc Kupietz36d12d92019-09-27 18:13:27 +0200233 } else {
234 factorCols <- colnames(currentMatches)
235 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200236 currentMatches[factorCols] <- lapply(currentMatches[factorCols], factor)
Marc Kupietz62da2b52019-09-12 17:43:34 +0200237 if (!is.list(collectedMatches)) {
238 collectedMatches <- currentMatches
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200239 } else {
Marc Kupietz62da2b52019-09-12 17:43:34 +0200240 collectedMatches <- rbind(collectedMatches, currentMatches)
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200241 }
Marc Kupietzc2c59bd2019-08-30 16:50:49 +0200242 if (verbose) {
Marc Kupietzf6f71312019-09-23 18:35:27 +0200243 cat(paste0("Retrieved page ", page, "/", ceiling((res$meta$totalResults) / res$meta$itemsPerPage), ' in ', res$meta$benchmark, '\n'))
Marc Kupietzc2c59bd2019-08-30 16:50:49 +0200244 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200245 page <- page + 1
246 results <- results + res$meta$itemsPerPage
Marc Kupietz62da2b52019-09-12 17:43:34 +0200247 if (offset + results >= res$meta$totalResults || (!is.na(maxFetch) && results >= maxFetch)) {
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200248 break
249 }
250 }
Marc Kupietze95108e2019-09-18 13:23:58 +0200251 nextStartIndex <- min(res$meta$startIndex + res$meta$itemsPerPage, res$meta$totalResults)
252 KorAPQuery(nextStartIndex = nextStartIndex,
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200253 korapConnection = kqo@korapConnection,
Marc Kupietze95108e2019-09-18 13:23:58 +0200254 fields = kqo@fields,
255 requestUrl = kqo@requestUrl,
256 request = kqo@request,
257 totalResults = res$meta$totalResults,
258 vc = kqo@vc,
259 webUIRequestUrl = kqo@webUIRequestUrl,
260 hasMoreMatches = (res$meta$totalResults > nextStartIndex),
261 apiResponse = res,
262 collectedMatches = collectedMatches)
263})
Marc Kupietz62da2b52019-09-12 17:43:34 +0200264
265#' Fetch all results of a KorAP query.
Marc Kupietz62da2b52019-09-12 17:43:34 +0200266#'
267#' @examples
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200268#' q <- new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchAll()
Marc Kupietze95108e2019-09-18 13:23:58 +0200269#' q@collectedMatches
Marc Kupietz62da2b52019-09-12 17:43:34 +0200270#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200271#' @aliases fetchAll
272#' @rdname KorAPQuery-class
Marc Kupietz62da2b52019-09-12 17:43:34 +0200273#' @export
Marc Kupietzf6f71312019-09-23 18:35:27 +0200274setMethod("fetchAll", "KorAPQuery", function(kqo, verbose = kqo@korapConnection@verbose) {
Marc Kupietze95108e2019-09-18 13:23:58 +0200275 return(fetchNext(kqo, offset = 0, maxFetch = NA, verbose = verbose))
276})
277
278#' Fetches the remaining results of a KorAP query.
279#'
280#' @examples
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200281#' q <- new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchAll()
Marc Kupietze95108e2019-09-18 13:23:58 +0200282#' q@collectedMatches
283#'
284#' @aliases fetchRest
285#' @rdname KorAPQuery-class
286#' @export
Marc Kupietzf6f71312019-09-23 18:35:27 +0200287setMethod("fetchRest", "KorAPQuery", function(kqo, verbose = kqo@korapConnection@verbose) {
Marc Kupietze95108e2019-09-18 13:23:58 +0200288 return(fetchNext(kqo, maxFetch = NA, verbose = verbose))
289})
290
Marc Kupietz3f575282019-10-04 14:46:04 +0200291#' Query relative frequency of search term(s)
292#'
293#' \bold{\code{frequencyQuery}} combines \code{\link{corpusQuery}}, \code{\link{corpusStats}} and
294#' \code{\link{ci}} to compute a table with the relative frequencies and
295#' confidence intervals of one ore multiple search terms across one or multiple
296#' virtual corpora.
297#'
298#' @aliases frequencyQuery
299#' @rdname KorAPQuery-class
300#' @examples
301#' new("KorAPConnection", verbose = TRUE) %>%
302#' frequencyQuery(c("Mücke", "Schnake"), paste0("pubDate in ", 2000:2003))
303#'
304#' @param kco \code{\link{KorAPConnection}} object (obtained e.g. from \code{new("KorAPConnection")}
305#' @param query string that contains the corpus query. The query language depends on the \code{ql} parameter. Either \code{query} must be provided or \code{KorAPUrl}.
306#' @export
307setMethod("frequencyQuery", "KorAPConnection",
308 function(kco, query, vc = "", ...) {
309 corpusQuery(kco, query, vc, metadataOnly = TRUE, as.df=TRUE, ...) %>%
310 mutate(tokens=corpusStats(kco, vc=vc, as.df=TRUE)$tokens) %>%
311 ci()
312})
313
Marc Kupietze95108e2019-09-18 13:23:58 +0200314#´ format()
315#' @rdname KorAPQuery-class
316#' @param x KorAPQuery object
317#' @param ... further arguments passed to or from other methods
318#' @export
319format.KorAPQuery <- function(x, ...) {
320 cat("<KorAPQuery>\n")
321 q <- x
322 aurl = parse_url(q@request)
323 cat(" Query: ", aurl$query$q, "\n")
324 if (!is.null(aurl$query$vc) && aurl$query$vc != "") {
325 cat("Virtual corpus: ", aurl$query$vc, "\n")
326 }
327 if (!is.null(q@collectedMatches)) {
328 cat("==============================================================================================================", "\n")
329 print(summary(q@collectedMatches))
330 cat("==============================================================================================================", "\n")
331 }
332 cat(" Total results: ", q@totalResults, "\n")
333 cat(" Fetched results: ", q@nextStartIndex, "\n")
Marc Kupietz62da2b52019-09-12 17:43:34 +0200334}
335
Marc Kupietze95108e2019-09-18 13:23:58 +0200336#' show()
Marc Kupietz62da2b52019-09-12 17:43:34 +0200337#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200338#' @rdname KorAPQuery-class
339#' @param object KorAPQuery object
Marc Kupietz62da2b52019-09-12 17:43:34 +0200340#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +0200341setMethod("show", "KorAPQuery", function(object) {
342 format(object)
343})