Skip to content

Commit

Permalink
Fix url encoding of ampersand in corpusStats value
Browse files Browse the repository at this point in the history
Change-Id: I17e72a979df5ed69f8de2fd762dd33fd121214c9
  • Loading branch information
kupietz committed Nov 19, 2023
1 parent 58bffe8 commit 1c994ee
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 3 deletions.
3 changes: 2 additions & 1 deletion R/KorAPCorpusStats.R
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ setGeneric("corpusStats", function(kco, ...) standardGeneric("corpusStats") )
#' @param as.df return result as data frame instead of as S4 object?
#' @return `KorAPCorpusStats` object with the slots `documents`, `tokens`, `sentences`, `paragraphs`
#'
#' @importFrom urltools url_encode
#' @examples
#'
#' \dontrun{
Expand All @@ -50,7 +51,7 @@ setMethod("corpusStats", "KorAPConnection", function(kco,
URLencode(enc2utf8(vc), reserved = TRUE))
log_info(verbose, "Getting size of virtual corpus \"", vc, "\"", sep = "")
res <- apiCall(kco, url)
webUIRequestUrl <- paste0(kco@KorAPUrl, sprintf("?q=<base/s=t>&cq=%s", URLencode(enc2utf8(vc))))
webUIRequestUrl <- paste0(kco@KorAPUrl, sprintf("?q=<base/s=t>&cq=%s", url_encode(enc2utf8(vc))))
if(is.null(res)) {
res <- data.frame(documents=NA, tokens=NA, sentences=NA, paragraphs=NA)
}
Expand Down
13 changes: 11 additions & 2 deletions tests/testthat/test-corpusStats.R
Original file line number Diff line number Diff line change
@@ -1,11 +1,20 @@
test_that("corpusStats works", {
skip_if_offline()
stats <- new("KorAPConnection") %>% corpusStats()
stats <- new("KorAPConnection") %>% corpusStats("pubDate since 2020 & pubDate until 2021")
expect_gt(stats@tokens, 0)
expect_gt(stats@paragraphs, 0)
expect_gt(stats@documents, 0)
expect(grepl("%26", stats@webUIRequestUrl), "webUIRequestUrl not properly url encoded")
})

test_that("corpusStats with result as df works", {
skip_if_offline()
stats <- new("KorAPConnection") %>% corpusStats("pubDate since 2020 & pubDate until 2021", as.df = TRUE)
expect_gt(stats$tokens, 0)
expect_gt(stats$paragraphs, 0)
expect_gt(stats$documents, 0)
expect(grepl("%26", stats$webUIRequestUrl), "webUIRequestUrl not properly url encoded")
})

test_that("Printing corpusStats for the whole corpus works", {
skip_if_offline()
Expand All @@ -15,6 +24,6 @@ test_that("Printing corpusStats for the whole corpus works", {

test_that("Printing corpusStats for a sub-corpus works", {
skip_if_offline()
stats <- new("KorAPConnection") %>% corpusStats("pubDate in 2018")
stats <- new("KorAPConnection") %>% corpusStats("pubDate since 2020 & pubDate until 2021")
expect_error(print(stats), NA)
})

0 comments on commit 1c994ee

Please sign in to comment.