blob: 868089c4fb247cb8fdd20276da1feea762c6be59 [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 Kupietz4de53ec2019-10-04 09:12:00 +02007#' @import jsonlite
Marc Kupietz69cc54a2019-09-30 12:06:54 +02008#' @import tidyr
9#' @import dplyr
Marc Kupietze95108e2019-09-18 13:23:58 +020010#' @import httr
11#'
Marc Kupietz4de53ec2019-10-04 09:12:00 +020012#' @include RKorAPClient.R
Marc Kupietz5bbc9db2019-08-30 16:30:45 +020013
Marc Kupietze95108e2019-09-18 13:23:58 +020014#' @export
15KorAPQuery <- setClass("KorAPQuery", slots = c(
Marc Kupietzb8972182019-09-20 21:33:46 +020016 "korapConnection",
Marc Kupietze95108e2019-09-18 13:23:58 +020017 "request",
18 "vc",
19 "totalResults",
20 "nextStartIndex",
21 "fields",
22 "requestUrl",
23 "webUIRequestUrl",
24 "apiResponse",
25 "collectedMatches",
26 "hasMoreMatches"
27))
Marc Kupietz5bbc9db2019-08-30 16:30:45 +020028
Marc Kupietze95108e2019-09-18 13:23:58 +020029#' Method initialize
30#'
31#' @rdname KorAPQuery-class
32#' @param .Object …
Marc Kupietzb8972182019-09-20 21:33:46 +020033#' @param korapConnection KorAPConnection object
Marc Kupietze95108e2019-09-18 13:23:58 +020034#' @param request query part of the request URL
35#' @param vc definition of a virtual corpus
36#' @param totalResults number of hits the query has yielded
37#' @param nextStartIndex at what index to start the next fetch of query results
38#' @param fields what data / metadata fields should be collected
39#' @param requestUrl complete URL of the API request
40#' @param webUIRequestUrl URL of a web frontend request corresponding to the API request
41#' @param apiResponse data-frame representation of the JSON response of the API request
Marc Kupietz7776dec2019-09-27 16:59:02 +020042#' @param hasMoreMatches logical that signals if more query results can be fetched
Marc Kupietze95108e2019-09-18 13:23:58 +020043#' @param collectedMatches matches already fetched from the KorAP-API-server
44#' @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 Kupietz632cbd42019-09-06 16:04:51 +020072QueryParameterFromUrl <- function(url, parameter) {
73 regex <- paste0(".*[?&]", parameter, "=([^&]*).*")
74 if (grepl(regex, url)) {
75 return(gsub(regex, '\\1', url, perl = TRUE))
76 } else {
77 return("")
78 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +020079}
80
Marc Kupietz4de53ec2019-10-04 09:12:00 +020081## quiets concerns of R CMD check re: the .'s that appear in pipelines
82if(getRversion() >= "2.15.1") utils::globalVariables(c("."))
Marc Kupietz632cbd42019-09-06 16:04:51 +020083
Marc Kupietze95108e2019-09-18 13:23:58 +020084#' Method corpusQuery
85#'
86#' Perform a corpus query via a connection to a KorAP-API-server.
87#'
88#' @param kco \code{\link{KorAPConnection}} object (obtained e.g. from \code{new("KorAPConnection")}
Akron5e135462019-09-27 16:31:38 +020089#' @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 +020090#' @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.
91#' @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 +020092#' @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 +020093#' @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 +020094#' @param fields (meta)data fields that will be fetched for every match.
95#' @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 +020096#' @param verbose print some info
Marc Kupietz4de53ec2019-10-04 09:12:00 +020097#' @param as.df return result as data frame instead of as S4 object?
Marc Kupietz3f575282019-10-04 14:46:04 +020098#' @param expand logical that deicdes if \code{query} and \code{vc} parameters are expanded to all of their combinations
99#' @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 +0200100#' A corresponding URL to be used within a web browser is contained in \code{@webUIRequestUrl}
Marc Kupietz62da2b52019-09-12 17:43:34 +0200101#' 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 +0200102#'
103#' @examples
Marc Kupietz603491f2019-09-18 14:01:02 +0200104#' # Fetch metadata of every query hit for "Ameisenplage" and show a summary
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200105#' new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchAll()
Marc Kupietz3c531f62019-09-13 12:17:24 +0200106#'
Marc Kupietz603491f2019-09-18 14:01:02 +0200107#' # Use the copy of a KorAP-web-frontend URL for an API query of "Ameise" in a virtual corpus
108#' # and show the number of query hits (but don't fetch them).
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200109#'
110#' new("KorAPConnection", verbose = TRUE) %>%
111#' corpusQuery(KorAPUrl =
112#' "https://korap.ids-mannheim.de/?q=Ameise&cq=pubDate+since+2017&ql=poliqarp")
Marc Kupietz3c531f62019-09-13 12:17:24 +0200113#'
Marc Kupietz603491f2019-09-18 14:01:02 +0200114#' # Plot the time/frequency curve of "Ameisenplage"
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200115#' new("KorAPConnection", verbose=TRUE) %>%
116#' { . ->> kco } %>%
117#' corpusQuery("Ameisenplage") %>%
118#' fetchAll() %>%
119#' slot("collectedMatches") %>%
120#' mutate(year = lubridate::year(pubDate)) %>%
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200121#' select(year) %>%
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200122#' group_by(year) %>%
123#' summarise(Count = n()) %>%
124#' mutate(Freq = mapply(function(f, y)
125#' f / corpusStats(kco, paste("pubDate in", y))@tokens, Count, year)) %>%
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200126#' select(-Count) %>%
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200127#' complete(year = min(year):max(year), fill = list(Freq = 0)) %>%
128#' plot(type = "l")
Marc Kupietz37b8ef12019-09-16 18:37:49 +0200129#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200130#' @seealso \code{\link{KorAPConnection}}, \code{\link{fetchNext}}, \code{\link{fetchRest}}, \code{\link{fetchAll}}, \code{\link{corpusStats}}
Marc Kupietz632cbd42019-09-06 16:04:51 +0200131#'
132#' @references
133#' \url{https://ids-pub.bsz-bw.de/frontdoor/index/index/docId/9026}
134#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200135#' @aliases corpusQuery
Marc Kupietz632cbd42019-09-06 16:04:51 +0200136#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +0200137setMethod("corpusQuery", "KorAPConnection",
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200138 function(kco,
139 query = ifelse(missing(KorAPUrl),
140 stop("At least one of the parameters query and KorAPUrl must be specified.", call. = FALSE),
141 httr::parse_url(KorAPUrl)$query$q),
142 vc = ifelse(missing(KorAPUrl), "", httr::parse_url(KorAPUrl)$query$cq),
143 KorAPUrl,
144 metadataOnly = TRUE,
145 ql = ifelse(missing(KorAPUrl), "poliqarp", httr::parse_url(KorAPUrl)$query$ql),
146 fields = c("corpusSigle", "textSigle", "pubDate", "pubPlace",
147 "availability", "textClass", "snippet"),
148 accessRewriteFatal = TRUE,
149 verbose = kco@verbose,
Marc Kupietz3f575282019-10-04 14:46:04 +0200150 expand = length(vc) != length(query),
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200151 as.df = FALSE) {
Marc Kupietz3f575282019-10-04 14:46:04 +0200152 ifelse(length(query) > 1 || length(vc) > 1, {
153 grid <- { if (expand) expand_grid(query=query, vc=vc) else tibble(query=query, vc=vc) }
154 return(
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200155 do.call(rbind,
Marc Kupietz3f575282019-10-04 14:46:04 +0200156 Map(function(q, cq) corpusQuery(kco, query=q, vc=cq, ql=ql,
157 verbose=verbose, as.df = TRUE), grid$query, grid$vc)) %>%
158 remove_rownames()
Marc Kupietz4de53ec2019-10-04 09:12:00 +0200159 )}, {
160 contentFields <- c("snippet")
161 fields <- fields[!fields %in% contentFields]
162 request <- paste0('?q=', URLencode(query, reserved=TRUE),
163 ifelse(vc != '', paste0('&cq=', URLencode(vc, reserved=TRUE)), ''), '&ql=', ql)
164 webUIRequestUrl <- paste0(kco@KorAPUrl, request)
165 requestUrl <- paste0(kco@apiUrl, 'search', request,
166 '&fields=', paste(fields, collapse = ","),
167 ifelse(metadataOnly, '&access-rewrite-disabled=true', ''))
168 log.info(verbose, "Searching \"", query, "\" in \"", vc, "\"", sep="")
169 res = apiCall(kco, paste0(requestUrl, '&count=0'))
170 log.info(verbose, " took ", res$meta$benchmark, "\n", sep="")
171 ifelse(as.df,
172 return(data.frame(query=query,
173 totalResults=res$meta$totalResults,
174 vc=vc,
175 webUIRequestUrl=webUIRequestUrl, stringsAsFactors = FALSE)),
176 return(KorAPQuery(
177 korapConnection = kco,
178 nextStartIndex = 0,
179 fields = fields,
180 requestUrl = requestUrl,
181 request = request,
182 totalResults = res$meta$totalResults,
183 vc = vc,
184 apiResponse = res,
185 webUIRequestUrl = webUIRequestUrl,
186 hasMoreMatches = (res$meta$totalResults > 0),
187 )))})
188 })
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200189
Marc Kupietz62da2b52019-09-12 17:43:34 +0200190#' Fetch the next bunch of results of a KorAP query.
Marc Kupietze95108e2019-09-18 13:23:58 +0200191#'
Marc Kupietz3f575282019-10-04 14:46:04 +0200192#' \bold{\code{fetchNext}} fetches the next bunch of results of a KorAP query.
193#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200194#' @param kqo object obtained from \code{\link{corpusQuery}}
Marc Kupietz62da2b52019-09-12 17:43:34 +0200195#' @param offset start offset for query results to fetch
196#' @param maxFetch maximum number of query results to fetch
Marc Kupietz25aebc32019-09-16 18:40:50 +0200197#' @param verbose print progress information if true
Marc Kupietze95108e2019-09-18 13:23:58 +0200198#' @return The \code{kqo} input object with updated slots \code{collectedMatches}, \code{apiResponse}, \code{nextStartIndex}, \code{hasMoreMatches}
Marc Kupietz62da2b52019-09-12 17:43:34 +0200199#'
200#' @references
201#' \url{https://ids-pub.bsz-bw.de/frontdoor/index/index/docId/9026}
202#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200203#' @aliases fetchNext
204#' @rdname KorAPQuery-class
Marc Kupietz632cbd42019-09-06 16:04:51 +0200205#' @export
Marc Kupietzf6f71312019-09-23 18:35:27 +0200206setMethod("fetchNext", "KorAPQuery", function(kqo, offset = kqo@nextStartIndex, maxFetch = maxResultsPerPage, verbose = kqo@korapConnection@verbose) {
Marc Kupietze95108e2019-09-18 13:23:58 +0200207 if (kqo@totalResults == 0 || offset >= kqo@totalResults) {
208 return(kqo)
Marc Kupietz62da2b52019-09-12 17:43:34 +0200209 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200210
211 page <- 1
212 results <- 0
Marc Kupietz25aebc32019-09-16 18:40:50 +0200213 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 +0200214 collectedMatches <- kqo@collectedMatches
Marc Kupietz62da2b52019-09-12 17:43:34 +0200215
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200216 repeat {
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200217 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 +0200218 if (res$meta$totalResults == 0) { return(kqo) }
219 for (field in kqo@fields) {
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200220 if (!field %in% colnames(res$matches)) {
221 res$matches[, field] <- NA
222 }
223 }
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200224 currentMatches <-
225 kqo@fields %>%
226 map_dfr( ~tibble(!!.x := logical() ) ) %>%
227 bind_rows(res$matches) %>%
228 select(kqo@fields)
Marc Kupietz36d12d92019-09-27 18:13:27 +0200229 if ("pubDate" %in% kqo@fields) {
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200230 currentMatches$pubDate <- currentMatches$pubDate %>% as.Date(format = "%Y-%m-%d")
231 factorCols <- currentMatches %>% select(-pubDate) %>% colnames()
Marc Kupietz36d12d92019-09-27 18:13:27 +0200232 } else {
233 factorCols <- colnames(currentMatches)
234 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200235 currentMatches[factorCols] <- lapply(currentMatches[factorCols], factor)
Marc Kupietz62da2b52019-09-12 17:43:34 +0200236 if (!is.list(collectedMatches)) {
237 collectedMatches <- currentMatches
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200238 } else {
Marc Kupietz62da2b52019-09-12 17:43:34 +0200239 collectedMatches <- rbind(collectedMatches, currentMatches)
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200240 }
Marc Kupietzc2c59bd2019-08-30 16:50:49 +0200241 if (verbose) {
Marc Kupietzf6f71312019-09-23 18:35:27 +0200242 cat(paste0("Retrieved page ", page, "/", ceiling((res$meta$totalResults) / res$meta$itemsPerPage), ' in ', res$meta$benchmark, '\n'))
Marc Kupietzc2c59bd2019-08-30 16:50:49 +0200243 }
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200244 page <- page + 1
245 results <- results + res$meta$itemsPerPage
Marc Kupietz62da2b52019-09-12 17:43:34 +0200246 if (offset + results >= res$meta$totalResults || (!is.na(maxFetch) && results >= maxFetch)) {
Marc Kupietz5bbc9db2019-08-30 16:30:45 +0200247 break
248 }
249 }
Marc Kupietze95108e2019-09-18 13:23:58 +0200250 nextStartIndex <- min(res$meta$startIndex + res$meta$itemsPerPage, res$meta$totalResults)
251 KorAPQuery(nextStartIndex = nextStartIndex,
Marc Kupietzd0d3e9b2019-09-24 17:36:03 +0200252 korapConnection = kqo@korapConnection,
Marc Kupietze95108e2019-09-18 13:23:58 +0200253 fields = kqo@fields,
254 requestUrl = kqo@requestUrl,
255 request = kqo@request,
256 totalResults = res$meta$totalResults,
257 vc = kqo@vc,
258 webUIRequestUrl = kqo@webUIRequestUrl,
259 hasMoreMatches = (res$meta$totalResults > nextStartIndex),
260 apiResponse = res,
261 collectedMatches = collectedMatches)
262})
Marc Kupietz62da2b52019-09-12 17:43:34 +0200263
264#' Fetch all results of a KorAP query.
Marc Kupietz62da2b52019-09-12 17:43:34 +0200265#'
266#' @examples
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200267#' q <- new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchAll()
Marc Kupietze95108e2019-09-18 13:23:58 +0200268#' q@collectedMatches
Marc Kupietz62da2b52019-09-12 17:43:34 +0200269#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200270#' @aliases fetchAll
271#' @rdname KorAPQuery-class
Marc Kupietz62da2b52019-09-12 17:43:34 +0200272#' @export
Marc Kupietzf6f71312019-09-23 18:35:27 +0200273setMethod("fetchAll", "KorAPQuery", function(kqo, verbose = kqo@korapConnection@verbose) {
Marc Kupietze95108e2019-09-18 13:23:58 +0200274 return(fetchNext(kqo, offset = 0, maxFetch = NA, verbose = verbose))
275})
276
277#' Fetches the remaining results of a KorAP query.
278#'
279#' @examples
Marc Kupietz69cc54a2019-09-30 12:06:54 +0200280#' q <- new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchAll()
Marc Kupietze95108e2019-09-18 13:23:58 +0200281#' q@collectedMatches
282#'
283#' @aliases fetchRest
284#' @rdname KorAPQuery-class
285#' @export
Marc Kupietzf6f71312019-09-23 18:35:27 +0200286setMethod("fetchRest", "KorAPQuery", function(kqo, verbose = kqo@korapConnection@verbose) {
Marc Kupietze95108e2019-09-18 13:23:58 +0200287 return(fetchNext(kqo, maxFetch = NA, verbose = verbose))
288})
289
Marc Kupietz3f575282019-10-04 14:46:04 +0200290#' Query relative frequency of search term(s)
291#'
292#' \bold{\code{frequencyQuery}} combines \code{\link{corpusQuery}}, \code{\link{corpusStats}} and
293#' \code{\link{ci}} to compute a table with the relative frequencies and
294#' confidence intervals of one ore multiple search terms across one or multiple
295#' virtual corpora.
296#'
297#' @aliases frequencyQuery
298#' @rdname KorAPQuery-class
299#' @examples
300#' new("KorAPConnection", verbose = TRUE) %>%
301#' frequencyQuery(c("Mücke", "Schnake"), paste0("pubDate in ", 2000:2003))
302#'
303#' @param kco \code{\link{KorAPConnection}} object (obtained e.g. from \code{new("KorAPConnection")}
304#' @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}.
305#' @export
306setMethod("frequencyQuery", "KorAPConnection",
307 function(kco, query, vc = "", ...) {
308 corpusQuery(kco, query, vc, metadataOnly = TRUE, as.df=TRUE, ...) %>%
309 mutate(tokens=corpusStats(kco, vc=vc, as.df=TRUE)$tokens) %>%
310 ci()
311})
312
Marc Kupietze95108e2019-09-18 13:23:58 +0200313#´ format()
314#' @rdname KorAPQuery-class
315#' @param x KorAPQuery object
316#' @param ... further arguments passed to or from other methods
317#' @export
318format.KorAPQuery <- function(x, ...) {
319 cat("<KorAPQuery>\n")
320 q <- x
321 aurl = parse_url(q@request)
322 cat(" Query: ", aurl$query$q, "\n")
323 if (!is.null(aurl$query$vc) && aurl$query$vc != "") {
324 cat("Virtual corpus: ", aurl$query$vc, "\n")
325 }
326 if (!is.null(q@collectedMatches)) {
327 cat("==============================================================================================================", "\n")
328 print(summary(q@collectedMatches))
329 cat("==============================================================================================================", "\n")
330 }
331 cat(" Total results: ", q@totalResults, "\n")
332 cat(" Fetched results: ", q@nextStartIndex, "\n")
Marc Kupietz62da2b52019-09-12 17:43:34 +0200333}
334
Marc Kupietze95108e2019-09-18 13:23:58 +0200335#' show()
Marc Kupietz62da2b52019-09-12 17:43:34 +0200336#'
Marc Kupietze95108e2019-09-18 13:23:58 +0200337#' @rdname KorAPQuery-class
338#' @param object KorAPQuery object
Marc Kupietz62da2b52019-09-12 17:43:34 +0200339#' @export
Marc Kupietze95108e2019-09-18 13:23:58 +0200340setMethod("show", "KorAPQuery", function(object) {
341 format(object)
342})