blob: c743fa8daf1c1cb5697dc38c76c6f653e90e130c [file] [log] [blame]
Marc Kupietz6ddece42023-12-18 17:02:36 +01001setGeneric("textMetadata", function(kco, ...) standardGeneric("textMetadata") )
2
3#' Retrieve metadata for a text, identified by its sigle (id)
4#'
5#' @aliases textMetadata
6#'
7#' @description
8#' Retrieves metadata for a text, identified by its sigle (id) using the corresponding KorAP API
9#' (see [Kustvakt Wiki](https://github.com/KorAP/Kustvakt/wiki/Service:-Metadata-Retrieval)).
10#'
11#'
12#' @param kco [KorAPConnection()] object (obtained e.g. from `new("KorAPConnection")`)
13#' @param textSigle unique text id (concatenation of corpus, document and text ids, separated by `/`, e.g. ) or vector thereof
14#' @param verbose logical. If `TRUE`, additional diagnostics are printed. Defaults to `kco@verbose`.
15#'
16#' @return Tibble with columns for every metadata property. In case of errors, like non-existing texts/sigles, the tibble will also contain a row called `errors`.
17#'
18#' @importFrom urltools url_encode
19#' @importFrom dplyr bind_rows relocate mutate
20#'
21#' @examples
22#' \dontrun{
23#' new("KorAPConnection") %>% textMetadata(c("WUD17/A97/08542", "WUD17/B96/57558", "WUD17/A97/08541"))
24#' }
25#'
26#' @export
27setMethod("textMetadata", "KorAPConnection",
28 function(kco, textSigle, verbose = kco@verbose) {
29 if (length(textSigle) > 1)
30 do.call(bind_rows, Map(function(atomicSigle)
31 textMetadata(kco, atomicSigle), textSigle))
32 else {
33 url <-
34 paste0(kco@apiUrl, 'corpus/',
35 URLencode(enc2utf8(textSigle), reserved = TRUE))
36 log_info(verbose, "Getting metadata for ", textSigle, sep = "")
37 res <- apiCall(kco, url)
38 log_info(verbose, ifelse(is.null(res) || "errors" %in% names(res), " [error]\n", "\n"))
39
40 if(is.null(res)) {
41 res <- tibble(errors="API request failed")
42 } else {
43 res <- lapply(res, function(x) paste0(x, collapse = "\\t")) # flatten list
44 res <- as_tibble(res) %>%
45 head(n=1) %>%
46 mutate(
47 requestUrl = url,
48 textSigle = textSigle,
49 webUIRequestUrl = paste0(kco@KorAPUrl, sprintf('?q=<base/s=t>&cq=textSigle+%%3D+"%s"', url_encode(enc2utf8(textSigle))))) %>%
50 relocate(textSigle)
51 }
52 res
53 }
54})
55
56