Add unit tests

Change-Id: Ic8ad5c8fc6a14d6220bc049400c440bb91732e9e
diff --git a/tests/testthat/test-KorAPConnection.R b/tests/testthat/test-KorAPConnection.R
new file mode 100644
index 0000000..883b10c
--- /dev/null
+++ b/tests/testthat/test-KorAPConnection.R
@@ -0,0 +1,29 @@
+test_that("KorAPConnection is printable", {
+  kco <- new("KorAPConnection")
+  expect_error(print(kco), NA)
+})
+
+test_that("KorAPConnection without access token prints ToS message", {
+  expect_message(new("KorAPConnection", accessToken = NULL),
+                 ".*By using.*non-commercial.*purposes", perl = TRUE)
+})
+
+test_that("Opening KorAPConnection with apiToken works", {
+  kco <- new("KorAPConnection", accessToken="test token")
+  persistAccessToken(kco)
+  kco <- new("KorAPConnection")
+  expect_equal(kco@accessToken, "test token")
+  clearAccessToken(kco)
+  kco <- new("KorAPConnection")
+  expect_null(kco@accessToken)
+  expect_error(persistAccessToken(kco),
+               ".*not supplied any access token.*",
+               perl = TRUE)
+})
+
+test_that("Opening KorAPConnection with KorAPUrl works", {
+  kco <- new("KorAPConnection", KorAPUrl="https://korap.ids-mannheim.de")
+  expect_equal(kco@apiUrl, paste0("https://korap.ids-mannheim.de/api/", kco@apiVersion, "/"))
+  kco <- new("KorAPConnection", KorAPUrl="https://korap.ids-mannheim.de/")
+  expect_equal(kco@apiUrl, paste0("https://korap.ids-mannheim.de/api/", kco@apiVersion, "/"))
+})
diff --git a/tests/testthat/test-corpusQuery.R b/tests/testthat/test-corpusQuery.R
new file mode 100644
index 0000000..ab97765
--- /dev/null
+++ b/tests/testthat/test-corpusQuery.R
@@ -0,0 +1,44 @@
+test_that("corpusQuery returns results", {
+  q <- new("KorAPConnection") %>%
+    corpusQuery("Ameisenplage")
+  expect_gt(q@totalResults, 0)
+})
+
+test_that("fetchAll fetches all results", {
+  q <- new("KorAPConnection", verbose = TRUE) %>%
+    corpusQuery("Ameisenplage", vc = "pubDate since 2014")
+  expectedResults <- q@totalResults
+  matches <- fetchAll(q)@collectedMatches
+  expect_equal(nrow(matches), expectedResults)
+})
+
+test_that("Uncached query for non-matching search string return 0 results", {
+  q <- new("KorAPConnection", cache = FALSE) %>% corpusQuery("Xmeisenplagx")
+  expect_equal( q@totalResults, 0)
+})
+
+test_that("Empty query result is printable", {
+  q <- new("KorAPConnection", cache = TRUE, verbose = TRUE) %>%
+    corpusQuery("Xmeisenplagx", vc = "pubDate in 2012") %>%
+    fetchNext()
+  expect_output(print(q), "Xmeisenplagx.*pubDate in 2012")
+})
+
+test_that("Non-empty query result is printable", {
+  q <- new("KorAPConnection", cache = TRUE, verbose = TRUE) %>%
+    corpusQuery("Ameisenplage", "pubDate since 2014", fields=c("sigle")) %>%
+    fetchRest()
+  expect_output(print(q), "Ameisenplage.*pubDate since 2014")
+})
+
+test_that("Query from KorAP URL returns as many results as corresponding direct query", {
+  kco <- new("KorAPConnection")
+  r1 <- corpusQuery(kco, KorAPUrl = "https://korap.ids-mannheim.de/?q=Ameisenplage&cq=pubDate+since+2014&ql=poliqarp")@totalResults
+  r2 <- corpusQuery(kco, "Ameisenplage", "pubDate since 2014")@totalResults
+  expect_equal(r1, r2)
+})
+
+test_that("Typo in query causes error", {
+  kco <- new("KorAPConnection", verbose = TRUE)
+  expect_error(kco %>% corpusQuery("[[xx"), "unbalanced")
+})
diff --git a/tests/testthat/test-corpusStats.R b/tests/testthat/test-corpusStats.R
new file mode 100644
index 0000000..8143886
--- /dev/null
+++ b/tests/testthat/test-corpusStats.R
@@ -0,0 +1,17 @@
+test_that("corpusStats works", {
+  stats <- new("KorAPConnection") %>% corpusStats()
+  expect_gt(stats@tokens, 0)
+  expect_gt(stats@paragraphs, 0)
+  expect_gt(stats@documents, 0)
+})
+
+
+test_that("Printing corpusStats for the whole corpus works", {
+  stats <- new("KorAPConnection") %>% corpusStats()
+  expect_error(print(stats), NA)
+})
+
+test_that("Printing corpusStats for a sub-corpus works", {
+  stats <- new("KorAPConnection") %>% corpusStats("pubDate in 2018")
+  expect_error(print(stats), NA)
+})
diff --git a/tests/testthat/test-demos.R b/tests/testthat/test-demos.R
new file mode 100644
index 0000000..1269760
--- /dev/null
+++ b/tests/testthat/test-demos.R
@@ -0,0 +1,143 @@
+test_that("Alternatives over time highcharter example works", {
+  year <- c(1990:2018)
+  alternatives <- c("macht []{0,3} Sinn", "ergibt []{0,3} Sinn")
+
+  hc <- new("KorAPConnection", verbose = TRUE) %>%
+    frequencyQuery(
+      query = alternatives,
+      vc = paste("textType = /Zeit.*/ & pubDate in", year),
+      as.alternatives = TRUE
+    ) %>%
+    hc_freq_by_year_ci(as.alternatives = TRUE)
+  expect_true(all(class(hc) %in% c("highchart", "htmlwidget")))
+})
+
+test_that("Multiple queries over time highcharter example works", {
+  year <- c(2013:2018)
+  alternatives <- c("macht []{0,3} Sinn", "ergibt []{0,3} Sinn")
+
+  hc <- new("KorAPConnection", verbose = TRUE) %>%
+    frequencyQuery(
+      query = alternatives,
+      vc = paste("textType = /Zeit.*/ & pubDate in", year),
+      as.alternatives = FALSE
+    ) %>%
+    hc_freq_by_year_ci(as.alternatives = FALSE)
+  expect_true(all(class(hc) %in% c("highchart", "htmlwidget")))
+})
+
+test_that("Single query in multiple over time highcharter example works", {
+  year <- c(2013:2018)
+  alternatives <- c("macht []{0,3} Sinn", "ergibt []{0,3} Sinn")
+
+  hc <- new("KorAPConnection", verbose = TRUE) %>%
+    frequencyQuery(
+      query = alternatives,
+      vc = paste("textType = /Zeit.*/ & pubDate in", year),
+      as.alternatives = FALSE
+    ) %>%
+    hc_freq_by_year_ci(as.alternatives = FALSE)
+  expect_true(all(class(hc) %in% c("highchart", "htmlwidget")))
+})
+
+test_that("Single query over time highcharter example works", {
+  year <- c(2013:2018)
+  q <- c("macht []{0,3} Sinn")
+
+  hc <- new("KorAPConnection", verbose = TRUE) %>%
+    frequencyQuery(
+      query = q,
+      vc = paste("textType = /Zeit.*/ & pubDate in", year),
+      as.alternatives = FALSE
+    ) %>%
+    hc_freq_by_year_ci(as.alternatives = FALSE)
+  expect_true(all(class(hc) %in% c("highchart", "htmlwidget")))
+})
+
+test_that("Auto conditions over time highcharter example works", {
+  kco <- new("KorAPConnection", verbose=TRUE)
+  hc <- expand_grid(
+    myconditions = c("textDomain = /Wirtschaft.*/",
+                  "textDomain != /Wirtschaft.*/"),
+    year = (2009:2013)
+  ) %>%
+    cbind(frequencyQuery(
+      kco,
+      c("[tt/l=Heuschrecke]", "Ameise"),
+      paste(.$myconditions, "& pubDate in", .$year)
+    ))  %>%
+    hc_freq_by_year_ci()
+  expect_true(all(class(hc) %in% c("highchart", "htmlwidget")))
+})
+
+test_that("Single condition over time highcharter example works", {
+  kco <- new("KorAPConnection", verbose=TRUE)
+  hc <- expand_grid(
+    condition = c("textDomain = /Wirtschaft.*/"),
+    year = (2009:2013)
+  ) %>%
+    cbind(frequencyQuery(
+      kco,
+      c("[tt/l=Heuschrecke]", "Ameise"),
+      paste(.$condition, "& pubDate in", .$year),
+    ))  %>%
+    hc_freq_by_year_ci()
+  expect_true(all(class(hc) %in% c("highchart", "htmlwidget")))
+})
+
+test_that("Multiple conditions over time highcharter example works", {
+  kco <- new("KorAPConnection", verbose=TRUE)
+  hc <- expand_grid(
+    condition = c("textDomain = /Wirtschaft.*/",
+                  "textDomain != /Wirtschaft.*/"),
+    year = (2009:2013)
+  ) %>%
+    cbind(frequencyQuery(
+      kco,
+      c("[tt/l=Heuschrecke]", "Ameise"),
+      paste(.$condition, "& pubDate in", .$year),
+    ))  %>%
+    hc_freq_by_year_ci()
+  expect_true(all(class(hc) %in% c("highchart", "htmlwidget")))
+})
+
+test_that("Multiple conditions and queries over time highcharter example works", {
+  kco <- new("KorAPConnection", verbose=TRUE)
+  hc <- expand_grid(
+    qx = c("[tt/l=Heuschrecke]", "Ameise"),
+    condition = c("textDomain = /Wirtschaft.*/",
+                  "textDomain != /Wirtschaft.*/"),
+    year = (2009:2013)
+  ) %>%
+    cbind(frequencyQuery(
+      kco,
+      .$qx,
+      paste(.$condition, "& pubDate in", .$year),
+    ))  %>%
+    hc_freq_by_year_ci()
+  expect_true(all(class(hc) %in% c("highchart", "htmlwidget")))
+})
+
+test_that("Conditions over time ggplotly example works", {
+  kco <- new("KorAPConnection")
+  p <- expand_grid(
+    condition = c("textDomain = /Wirtschaft.*/",
+                  "textDomain != /Wirtschaft.*/"),
+    year = (2009:2013)
+  ) %>%
+    cbind(frequencyQuery(
+      kco,
+      "[tt/l=Heuschrecke]",
+      paste(.$condition, "& pubDate in", .$year)
+    ))  %>%
+    ipm() %>%
+    ggplot(aes(
+      x = year,
+      y = ipm,
+      fill = condition,
+      colour = condition
+    )) +
+    geom_freq_by_year_ci()
+  pp <- ggplotly(p)
+  expect_error(print(pp), NA)
+})