Add rCharts demo using Highcharts
Change-Id: I4d348937b5db7888def2ccc763d9171de2cfbc46
diff --git a/NAMESPACE b/NAMESPACE
index 86db8dc..8a84580 100644
--- a/NAMESPACE
+++ b/NAMESPACE
@@ -12,6 +12,7 @@
export(group_by)
export(ipm)
export(mutate)
+export(percent)
export(queryStringToLabel)
export(select)
export(summarise)
diff --git a/R/misc.R b/R/misc.R
index 26ae123..9327a32 100644
--- a/R/misc.R
+++ b/R/misc.R
@@ -21,6 +21,29 @@
mutate(ipm = .data$f * 10^6, conf.low = .data$conf.low * 10^6, conf.high = .data$conf.high * 10^6)
}
+#' Convert corpus frequency table of alternatives to percent
+#'
+#' Convenience function for converting frequency tables of alternative variants
+#' (generated with \code{as.alternatives=T}) to percent.
+#'
+#' @param df table returned from \code{\link{frequencyQuery}}
+#'
+#' @return original table with converted columns \code{f}, \code{conf.low} and \code{conf.high}
+#' @export
+#'
+#' @importFrom dplyr .data
+#'
+#' @examples
+#' new("KorAPConnection") %>%
+#' frequencyQuery(c("Tollpatsch", "Tolpatsch"),
+#' vc=paste0("pubDate in ", 2000:2002),
+#' as.alternatives = TRUE) %>%
+#' percent()
+percent <- function(df) {
+ df %>%
+ mutate(f = .data$f * 10^2, conf.low = .data$conf.low * 10^2, conf.high = .data$conf.high * 10^2)
+}
+
#' Convert query or vc strings to plot labels
#'
#' Converts a vector of query or vc strings to typically appropriate legend labels
diff --git a/demo/00Index b/demo/00Index
index b954748..f16c2dc 100644
--- a/demo/00Index
+++ b/demo/00Index
@@ -4,3 +4,4 @@
alternativesOverTime Plot proportion of alternative spellings/variants over time
regional Map plot regional frequencies of query expression
mosaicplot Visualize frequencies of alternative query terms in relation to other variables
+rcharts-highcharts Visualize term frqequencies over time with interactive HTML and JavaScript elements
diff --git a/demo/rcharts-highcharts.R b/demo/rcharts-highcharts.R
new file mode 100644
index 0000000..231662b
--- /dev/null
+++ b/demo/rcharts-highcharts.R
@@ -0,0 +1,86 @@
+library(RKorAPClient)
+library(rCharts)
+
+plotHighchart <- function(query = "Schlumpf",
+ years = c(2000:2010),
+ as.alternatives = length(query) > 1,
+ vc = "textType = /Zeit.*/ & availability!=QAO-NC-LOC:ids & pubDate in",
+ kco = new("KorAPConnection", verbose=T) ) {
+ palette <- c("#1f77b4", "#ff7f0e", "#2ca02c", "#d62728", "#9467bd", "#8c564b", "#e377c2", "#7f7f7f", "#bcbd22", "#17becf")
+ h1 <- Highcharts$new()
+ df <-
+ frequencyQuery(kco, query, paste(vc, years), as.alternatives=as.alternatives) %>%
+ { if(! as.alternatives) ipm(.) else percent(.) } %>%
+ mutate(year=as.numeric(queryStringToLabel(vc)))
+
+ ylabel = if(as.alternatives) "%" else "ipm"
+ for(q in query) {
+ dat <- df[df$query==q,]
+ h1$series(
+ marker = list(radius = 2),
+ name = q,
+ data = toJSONArray(data.frame(x=dat$year,
+ y = if (as.alternatives) dat$f else dat$ipm,
+ percentage = dat$f ,
+ count = dat$totalResults,
+ click=dat$webUIRequestUrl), json = F),
+ type = 'line',
+ color = palette[1+length(h1$params$series)/2],
+ zIndex = 1
+ )
+ h1$series(
+ name = "ci",
+ data = toJSONArray2(dat[,c('year', 'conf.low', 'conf.high')], names = F, json = F),
+ type = 'arearange',
+ fillOpacity = 0.3,
+ lineWidth = 0,
+ marker = list(enabled = F),
+ enableMouseTracking = F,
+ linkedTo= ':previous',
+ color = palette[1+(length(h1$params$series)-1)/2],
+ zIndex = 0
+ )
+ }
+ h1$plotOptions(line = list(cursor = 'pointer', point = list(
+ events = list(click = "#! function() { window.open(this.click, 'korap'); } !#")
+ )))
+ h1$set(
+ credits = list(text="KorAP R Client Pakckage", href="//github.com/KorAP/RKorAPClient/"),
+ zoomType = "Y",
+# xAxis = list(title = list(text="year")),
+ yAxis = if (as.alternatives)
+ list(ceiling=100, floor=0, labels = list(format="{value}\U2009%"))
+ else
+ list(title = list(text=ylabel), floor=0),
+ tooltip = list(
+ formatter = paste0("#! function (tooltip) {
+ var str = tooltip.defaultFormatter.call(this, tooltip);
+ if(Array.isArray(str)) {
+ str = str.join('');
+ }
+ for (var i = 0; i < this.points.length; i++) {
+ str = str.replace(/([0-9.,]+.?)", ylabel, "/, this.points[i].point.count+' ($1@)');
+ }
+ return str.replace(/@/g, '", ylabel, "')
+ } !#"),
+ crosshairs = T,
+ valueDecimals = 2,
+ shared = T,
+ valueSuffix = paste0('\U2009', ylabel)
+ )
+ )
+ print(h1)
+ h1
+}
+
+saveHPlot <- function(h, fname, local = F) {
+ capture.output(h$show('inline', include_assets = TRUE, cdn = TRUE)) %>%
+ paste(collapse = '\n') %>%
+ { if (local) gsub("=//", "=https://", .) else . } %>%
+ cat(file=fname)
+}
+
+#h1 <-plotHighchart(c("macht []{0,3} Sinn", "ergibt []{0,3} Sinn"), c(1980:2018))
+h1 <- plotHighchart(c("Leser | Lesern | Lesers", 'Leserin | Leserinnen', 'LeserIn | LeserInnen', '"Leser[_\\*]in.*"'), c(1985:2018))
+#plotHighchart(c("Tollpatsch", "Tolpatsch"), c(1991:2018))
+
diff --git a/man/percent.Rd b/man/percent.Rd
new file mode 100644
index 0000000..06e2fb3
--- /dev/null
+++ b/man/percent.Rd
@@ -0,0 +1,25 @@
+% Generated by roxygen2: do not edit by hand
+% Please edit documentation in R/misc.R
+\name{percent}
+\alias{percent}
+\title{Convert corpus frequency table of alternatives to percent}
+\usage{
+percent(df)
+}
+\arguments{
+\item{df}{table returned from \code{\link{frequencyQuery}}}
+}
+\value{
+original table with converted columns \code{f}, \code{conf.low} and \code{conf.high}
+}
+\description{
+Convenience function for converting frequency tables of alternative variants
+(generated with \code{as.alternatives=T}) to percent.
+}
+\examples{
+new("KorAPConnection") \%>\%
+ frequencyQuery(c("Tollpatsch", "Tolpatsch"),
+ vc=paste0("pubDate in ", 2000:2002),
+ as.alternatives = TRUE) \%>\%
+ percent()
+}