Start tidyverse migration

Change-Id: Ifc972de789c22e2ff43159740d7f1fa7125e1ef2
diff --git a/DESCRIPTION b/DESCRIPTION
index 561a849..962840c 100644
--- a/DESCRIPTION
+++ b/DESCRIPTION
@@ -12,6 +12,11 @@
 RoxygenNote: 6.1.1
 Imports:
     R.cache,
+    magrittr,
+    tidyr,
+    dplyr,
+    purrr,
+    lubridate,
     curl,
     jsonlite,
     utils,
@@ -21,3 +26,4 @@
     'KorAPConnection.R'
     'KorAPCorpusStats.R'
     'KorAPQuery.R'
+    'reexports.R'
diff --git a/NAMESPACE b/NAMESPACE
index 58e75e0..3074a48 100644
--- a/NAMESPACE
+++ b/NAMESPACE
@@ -1,9 +1,17 @@
 # Generated by roxygen2: do not edit by hand
 
 S3method(format,KorAPQuery)
+export("%>%")
+export(complete)
+export(group_by)
+export(mutate)
+export(select)
+export(summarise)
+export(year)
 exportClasses(KorAPConnection)
 exportClasses(KorAPCorpusStats)
 exportClasses(KorAPQuery)
+exportMethods(apiCall)
 exportMethods(clearCache)
 exportMethods(corpusQuery)
 exportMethods(corpusStats)
@@ -13,7 +21,17 @@
 exportMethods(initialize)
 exportMethods(show)
 import(R.cache)
+import(dplyr)
 import(httr)
-import(jsonlite)
 import(methods)
+import(purrr)
+import(tidyr)
 import(utils)
+importFrom(dplyr,group_by)
+importFrom(dplyr,mutate)
+importFrom(dplyr,select)
+importFrom(dplyr,summarise)
+importFrom(jsonlite,fromJSON)
+importFrom(lubridate,year)
+importFrom(magrittr,"%>%")
+importFrom(tidyr,complete)
diff --git a/R/KorAPConnection.R b/R/KorAPConnection.R
index 7eface5..fa8f1f5 100644
--- a/R/KorAPConnection.R
+++ b/R/KorAPConnection.R
@@ -4,10 +4,11 @@
 #' New \code{KorAPConnection} objects can be created by \code{KorAPConnection()}.
 #'
 #' @import R.cache
-#' @import jsonlite
 #' @import utils
 #' @import methods
-#'
+#' @import dplyr
+#' @import purrr
+#' @import tidyr
 #'
 
 #' @export
@@ -64,6 +65,8 @@
 #' @rdname KorAPConnection-class
 #' @param kco KorAPConnection object
 #' @param url request url
+#' @importFrom jsonlite fromJSON
+#' @export
 setMethod("apiCall", "KorAPConnection",  function(kco, url) {
   if (kco@cache) {
     parsed <- R.cache::loadCache(dir=KorAPCacheSubDir(), key=list(url))
diff --git a/R/KorAPQuery.R b/R/KorAPQuery.R
index 0b9ee7c..3cc0b37 100644
--- a/R/KorAPQuery.R
+++ b/R/KorAPQuery.R
@@ -4,7 +4,8 @@
 #' New \code{KorAPQuery} objects are typically created by the \code{\link{corpusQuery}} method.
 #'
 #' @include KorAPConnection.R
-#' @import jsonlite
+#' @import tidyr
+#' @import dplyr
 #' @import httr
 #'
 #'
@@ -98,28 +99,30 @@
 #'
 #' @examples
 #' # Fetch metadata of every query hit for "Ameisenplage" and show a summary
-#' kco <- new("KorAPConnection")
-#' kqo <- corpusQuery(kco, "Ameisenplage")
-#' kqo <- fetchAll(kqo)
-#' kqo
+#' new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchAll()
 #'
 #' # Use the copy of a KorAP-web-frontend URL for an API query of "Ameise" in a virtual corpus
 #' # and show the number of query hits (but don't fetch them).
-#' kco <- new("KorAPConnection")
-#' kqo <- corpusQuery(kco,
-#'        KorAPUrl = "https://korap.ids-mannheim.de/?q=Ameise&cq=pubDate+since+2017&ql=poliqarp")
-#' kqo
+#'
+#' new("KorAPConnection", verbose = TRUE) %>%
+#'  corpusQuery(KorAPUrl =
+#'    "https://korap.ids-mannheim.de/?q=Ameise&cq=pubDate+since+2017&ql=poliqarp")
 #'
 #' # Plot the time/frequency curve of "Ameisenplage"
-#' kco <- new("KorAPConnection", verbose=TRUE)
-#' q <- fetchAll(corpusQuery(kco, "Ameisenplage"))
-#' df <- as.data.frame(table(as.numeric(format(q@collectedMatches$pubDate,"%Y")), dnn="year"),
-#'                     stringsAsFactors = FALSE)
-#' df$Freq <- mapply(function(f, y) f / corpusStats(kco, paste("pubDate in", y))@tokens,
-#'                   df$Freq, df$year)
-#' df <- merge(data.frame(year=min(df$year):max(df$year)), df, all = TRUE)
-#' df[is.na(df$Freq),]$Freq <- 0
-#' plot(df, type="l")
+#' new("KorAPConnection", verbose=TRUE) %>%
+#'   { . ->> kco } %>%
+#'   corpusQuery("Ameisenplage") %>%
+#'   fetchAll() %>%
+#'   slot("collectedMatches") %>%
+#'   mutate(year = lubridate::year(pubDate)) %>%
+#'   dplyr::select(year) %>%
+#'   group_by(year) %>%
+#'   summarise(Count = n()) %>%
+#'   mutate(Freq = mapply(function(f, y)
+#'     f / corpusStats(kco, paste("pubDate in", y))@tokens, Count, year)) %>%
+#'   dplyr::select(-Count) %>%
+#'   complete(year = min(year):max(year), fill = list(Freq = 0)) %>%
+#'   plot(type = "l")
 #'
 #' @seealso \code{\link{KorAPConnection}}, \code{\link{fetchNext}}, \code{\link{fetchRest}}, \code{\link{fetchAll}}, \code{\link{corpusStats}}
 #'
@@ -203,10 +206,14 @@
         res$matches[, field] <- NA
       }
     }
-    currentMatches <- res$matches[kqo@fields]
+    currentMatches <-
+      kqo@fields %>%
+      map_dfr( ~tibble(!!.x := logical() ) ) %>%
+      bind_rows(res$matches) %>%
+      select(kqo@fields)
     if ("pubDate" %in% kqo@fields) {
-      currentMatches$pubDate = as.Date(currentMatches$pubDate, format = "%Y-%m-%d")
-      factorCols <- colnames(subset(currentMatches, select=-c(pubDate)))
+      currentMatches$pubDate <-  currentMatches$pubDate %>% as.Date(format = "%Y-%m-%d")
+      factorCols <- currentMatches %>% select(-pubDate) %>% colnames()
     } else {
       factorCols <- colnames(currentMatches)
     }
@@ -242,7 +249,7 @@
 #' Fetch all results of a KorAP query.
 #'
 #' @examples
-#' q <- fetchAll(corpusQuery(new("KorAPConnection"), "Ameisenplage"))
+#' q <- new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchAll()
 #' q@collectedMatches
 #'
 #' @aliases fetchAll
@@ -255,7 +262,7 @@
 #' Fetches the remaining results of a KorAP query.
 #'
 #' @examples
-#' q <- fetchRest(fetchNext(corpusQuery(new("KorAPConnection"), "Ameisenplage")))
+#' q <- new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchAll()
 #' q@collectedMatches
 #'
 #' @aliases fetchRest
diff --git a/R/reexports.R b/R/reexports.R
new file mode 100644
index 0000000..f6624ba
--- /dev/null
+++ b/R/reexports.R
@@ -0,0 +1,30 @@
+
+#' Pipe operator
+#'
+#' See \code{magrittr::\link[magrittr:pipe]{\%>\%}} for details.
+#'
+#' @name %>%
+#' @rdname pipe
+#' @keywords internal
+#' @export
+#' @importFrom magrittr %>%
+#' @usage lhs \%>\% rhs
+NULL
+#' @importFrom dplyr mutate
+#' @export
+dplyr::mutate
+#' @importFrom dplyr select
+#' @export
+dplyr::select
+#' @importFrom dplyr group_by
+#' @export
+dplyr::group_by
+#' @importFrom dplyr summarise
+#' @export
+dplyr::summarise
+#' @importFrom tidyr complete
+#' @export
+tidyr::complete
+#' @importFrom lubridate year
+#' @export
+lubridate::year
diff --git a/RKorAPClient.Rproj b/RKorAPClient.Rproj
index 6608f32..2611ff5 100644
--- a/RKorAPClient.Rproj
+++ b/RKorAPClient.Rproj
@@ -19,3 +19,4 @@
 PackageUseDevtools: Yes
 PackageInstallArgs: --no-multiarch --with-keep.source
 PackageRoxygenize: rd,collate,namespace
+DisableExecuteRprofile: Yes
diff --git a/Readme.md b/Readme.md
index aeef143..e2b5358 100644
--- a/Readme.md
+++ b/Readme.md
@@ -24,8 +24,7 @@
 
 ```R
 library(RKorAPClient)
-kqo <- corpusQuery(new("KorAPConnection", verbose=TRUE), "Hello world")
-fetchAll(kqo)
+new("KorAPConnection", verbose=TRUE) %>% corpusQuery("Hello world") %>% fetchAll()
 ```
 ## Demos
 
diff --git a/demo/alternativesOverTime.R b/demo/alternativesOverTime.R
index 7866121..443fbe4 100755
--- a/demo/alternativesOverTime.R
+++ b/demo/alternativesOverTime.R
@@ -4,26 +4,25 @@
 #
 library(RKorAPClient)
 library(ggplot2)
-library(reshape2)
+library(tidyr)
+library(dplyr)
 library(plotly)
 library(htmlwidgets)
 
 alternativesOverTime <- function(alternatives, years, kco = new("KorAPConnection", verbose=TRUE)) {
-  df = data.frame(year=years)
   vc = "textType = /Zeit.*/ & pubDate in"
-  urls <- data.frame()
-  for (v in alternatives) {
-    df[v] <- sapply(df$year, function(y) {
-        kqo <- corpusQuery(kco, query=v, vc=paste(vc, y))
-        urls <<- rbind(urls, data.frame(Variant=v, year=y, url=kqo@webUIRequestUrl))
-        kqo@totalResults
-    })
-  }
-  df$total <- apply(df[,alternatives], 1, sum)
-  df <- merge(melt(df, measure.vars = alternatives, value.name = "afreq", variable.name = "Variant"),
-              urls, by=c("Variant", "year"))
-  df$ci <- t(sapply(Map(prop.test, df$afreq, df$total), "[[","conf.int"))
-  df$share <- df$afreq / df$total
+  df <- data.frame(matrix(ncol = length(alternatives), nrow = length(years))) %>%
+    setNames(alternatives) %>%
+    mutate(year = years) %>%
+    pivot_longer(cols = alternatives) %>%
+    rowwise %>% mutate(value = corpusQuery(kco, query=name, vc=paste(vc, year))@totalResults) %>%
+    pivot_wider(id_cols= year, names_from = name) %>%
+    mutate(total = rowSums(.[alternatives])) %>%
+    pivot_longer(cols = alternatives) %>%
+    mutate(share = value / total) %>%
+    rowwise %>% mutate(url =  corpusQuery(kco, query=name, vc=paste(vc, year))@webUIRequestUrl) %>%
+    rename(Variant = name)
+  df$ci <- t(sapply(Map(prop.test, df$value, df$total), "[[","conf.int"))
   g <- ggplot(data = df, mapping = aes(x = year, y = share, color=Variant, fill=Variant)) +
     geom_ribbon(aes(ymin=ci[, 1], ymax=ci[, 2], color=Variant, fill=Variant), alpha=.3, linetype=0) +
     geom_line() +
@@ -36,7 +35,7 @@
   for (i in 1:length(alternatives)) {
     vdata <- df[df$Variant==alternatives[i],]
     pp$x$data[[2+i]]$customdata <- vdata$url
-    pp$x$data[[2+i]]$text <- sprintf("%s<br />absolute: %d / %d", pp$x$data[[2+i]]$text, vdata$afreq, vdata$total)
+    pp$x$data[[2+i]]$text <- sprintf("%s<br />absolute: %d / %d", pp$x$data[[2+i]]$text, vdata$value, vdata$total)
   }
   ppp <- onRender(pp, "function(el, x) { el.on('plotly_click', function(d) { var url=d.points[0].customdata; window.open(url, 'korap') })}")
   print(ppp)
diff --git a/demo/regional.R b/demo/regional.R
index 067e3e2..60ea5c7 100755
--- a/demo/regional.R
+++ b/demo/regional.R
@@ -73,7 +73,7 @@
   map$region <- sapply(map$grp, function(grp) regions$region[grp])
   map$url <- sapply(map$grp, function(grp) regions$url[grp])
   regionsPlot <- ggplot(map) +
-    geom_polygon(aes(x=long, y=lat, group=group, fill=ipm, text=region), colour= "black", size=.1) +
+    geom_polygon(aes(x=long, y=lat, group=group, fill=ipm, hack=region), colour= "black", size=.1) +
     theme(axis.line.x = element_blank(),
           axis.line.y = element_blank(),
           panel.grid.major = element_blank(),
diff --git a/man/KorAPQuery-class.Rd b/man/KorAPQuery-class.Rd
index 1bc7bd4..b5c9a8a 100644
--- a/man/KorAPQuery-class.Rd
+++ b/man/KorAPQuery-class.Rd
@@ -82,10 +82,10 @@
 New \code{KorAPQuery} objects are typically created by the \code{\link{corpusQuery}} method.
 }
 \examples{
-q <- fetchAll(corpusQuery(new("KorAPConnection"), "Ameisenplage"))
+q <- new("KorAPConnection") \%>\% corpusQuery("Ameisenplage") \%>\% fetchAll()
 q@collectedMatches
 
-q <- fetchRest(fetchNext(corpusQuery(new("KorAPConnection"), "Ameisenplage")))
+q <- new("KorAPConnection") \%>\% corpusQuery("Ameisenplage") \%>\% fetchAll()
 q@collectedMatches
 
 }
diff --git a/man/corpusQuery-KorAPConnection-method.Rd b/man/corpusQuery-KorAPConnection-method.Rd
index 86d98e5..e623297 100644
--- a/man/corpusQuery-KorAPConnection-method.Rd
+++ b/man/corpusQuery-KorAPConnection-method.Rd
@@ -39,28 +39,30 @@
 }
 \examples{
 # Fetch metadata of every query hit for "Ameisenplage" and show a summary
-kco <- new("KorAPConnection")
-kqo <- corpusQuery(kco, "Ameisenplage")
-kqo <- fetchAll(kqo)
-kqo
+new("KorAPConnection") \%>\% corpusQuery("Ameisenplage") \%>\% fetchAll()
 
 # Use the copy of a KorAP-web-frontend URL for an API query of "Ameise" in a virtual corpus
 # and show the number of query hits (but don't fetch them).
-kco <- new("KorAPConnection")
-kqo <- corpusQuery(kco,
-       KorAPUrl = "https://korap.ids-mannheim.de/?q=Ameise&cq=pubDate+since+2017&ql=poliqarp")
-kqo
+
+new("KorAPConnection", verbose = TRUE) \%>\%
+ corpusQuery(KorAPUrl =
+   "https://korap.ids-mannheim.de/?q=Ameise&cq=pubDate+since+2017&ql=poliqarp")
 
 # Plot the time/frequency curve of "Ameisenplage"
-kco <- new("KorAPConnection", verbose=TRUE)
-q <- fetchAll(corpusQuery(kco, "Ameisenplage"))
-df <- as.data.frame(table(as.numeric(format(q@collectedMatches$pubDate,"\%Y")), dnn="year"),
-                    stringsAsFactors = FALSE)
-df$Freq <- mapply(function(f, y) f / corpusStats(kco, paste("pubDate in", y))@tokens,
-                  df$Freq, df$year)
-df <- merge(data.frame(year=min(df$year):max(df$year)), df, all = TRUE)
-df[is.na(df$Freq),]$Freq <- 0
-plot(df, type="l")
+new("KorAPConnection", verbose=TRUE) \%>\%
+  { . ->> kco } \%>\%
+  corpusQuery("Ameisenplage") \%>\%
+  fetchAll() \%>\%
+  slot("collectedMatches") \%>\%
+  mutate(year = lubridate::year(pubDate)) \%>\%
+  dplyr::select(year) \%>\%
+  group_by(year) \%>\%
+  summarise(Count = n()) \%>\%
+  mutate(Freq = mapply(function(f, y)
+    f / corpusStats(kco, paste("pubDate in", y))@tokens, Count, year)) \%>\%
+  dplyr::select(-Count) \%>\%
+  complete(year = min(year):max(year), fill = list(Freq = 0)) \%>\%
+  plot(type = "l")
 
 }
 \references{
diff --git a/man/pipe.Rd b/man/pipe.Rd
new file mode 100644
index 0000000..32004dc
--- /dev/null
+++ b/man/pipe.Rd
@@ -0,0 +1,12 @@
+% Generated by roxygen2: do not edit by hand
+% Please edit documentation in R/reexports.R
+\name{\%>\%}
+\alias{\%>\%}
+\title{Pipe operator}
+\usage{
+lhs \%>\% rhs
+}
+\description{
+See \code{magrittr::\link[magrittr:pipe]{\%>\%}} for details.
+}
+\keyword{internal}
diff --git a/man/reexports.Rd b/man/reexports.Rd
new file mode 100644
index 0000000..81287d2
--- /dev/null
+++ b/man/reexports.Rd
@@ -0,0 +1,25 @@
+% Generated by roxygen2: do not edit by hand
+% Please edit documentation in R/reexports.R
+\docType{import}
+\name{reexports}
+\alias{reexports}
+\alias{mutate}
+\alias{select}
+\alias{group_by}
+\alias{summarise}
+\alias{complete}
+\alias{year}
+\title{Objects exported from other packages}
+\keyword{internal}
+\description{
+These objects are imported from other packages. Follow the links
+below to see their documentation.
+
+\describe{
+  \item{dplyr}{\code{\link[dplyr]{mutate}}, \code{\link[dplyr]{select}}, \code{\link[dplyr]{group_by}}, \code{\link[dplyr]{summarise}}}
+
+  \item{lubridate}{\code{\link[lubridate]{year}}}
+
+  \item{tidyr}{\code{\link[tidyr]{complete}}}
+}}
+