blob: 46d3e8e5e8e32e2790b3c95ec4a6e9f8cc4442bf [file] [log] [blame]
#' Experimental: Plot interactive frequency by year graphs with confidence intervals using highcharter
#'
#' Experimental convenience function for plotting typical frequency by year graphs with confidence intervals using highcharter.
#' \bold{Warning:} This function may be moved to a new package.
#'
#' @import highcharter
#' @export
#'
#' @param df data frame like the value of a \code{\link{frequencyQuery}}
#' @param as.alternatives boolean decides whether queries should be treatet queries as mutually exclusive and exahustive wrt. to some meaningful class (e.g. spelling variants of a certain word form).
#' @param ylabel defaults to \% if \code{as.alternatives} is \code{true} and to "ipm" otherwise.
#'
#' @examples
#' \donttest{year <- c(1990:2018)}\dontshow{year <- c(2013:2014)}
#' new("KorAPConnection", verbose = TRUE) %>%
#' frequencyQuery(query = c("macht []{0,3} Sinn", "ergibt []{0,3} Sinn"),
#' vc = paste("textType = /Zeit.*/ & pubDate in", year),
#' as.alternatives = TRUE) %>%
#' hc_freq_by_year_ci(as.alternatives = TRUE)
#'
#' \donttest{
#' kco <- new("KorAPConnection", verbose = TRUE)
#' expand_grid(
#' condition = c("textDomain = /Wirtschaft.*/", "textDomain != /Wirtschaft.*/"),
#' year = (2005:2011)
#' ) %>%
#' cbind(frequencyQuery(
#' kco,
#' "[tt/l=Heuschrecke]",
#' paste0(.$condition, " & pubDate in ", .$year)
#' )) %>%
#' hc_freq_by_year_ci()
#' }
#'
hc_freq_by_year_ci <- function(df, as.alternatives = F, ylabel = if(as.alternatives) "%" else "ipm") {
title <- ""
df <- df %>%
{ if(! as.alternatives) ipm(.) else RKorAPClient::percent(.) }
if (!"year" %in% colnames(df)) {
df <- df %>% mutate(year = as.integer(queryStringToLabel(df$vc, pubDateOnly = T)))
}
if (!"condition" %in% colnames(df)) {
if (length(base::unique(df$query)) > 1) {
df <- df %>% mutate(condition = query)
if(length(base::unique(queryStringToLabel(df$vc, excludePubDate = T ))) > 1) {
df <- df %>% mutate(condition = paste(condition, " & ",
queryStringToLabel(vc, excludePubDate = T )))
}
} else {
title <- base::unique(df$query)
if(length(base::unique(queryStringToLabel(df$vc, excludePubDate = T ))) > 1) {
df <- df %>% mutate(condition = queryStringToLabel(vc, excludePubDate = T ))
}
}
}
# use the D3 palette which provides 20 attractive and distinguishable colours
palette <- c("#1F77B4", "#FF7F0E", "#2CA02C", "#D62728", "#9467BD", "#8C564B", "#E377C2", "#7F7F7F", "#BCBD22", "#17BECF", "#AEC7E8", "#FFBB78", "#98DF8A", "#FF9896", "#C5B0D5", "#C49C94", "#F7B6D2", "#C7C7C7", "#DBDB8D", "#9EDAE5")
highcharter::highchart() %>%
hc_title(text=title) %>%
hc_chart(zoomType="xy") %>%
hc_yAxis(
title = list(text = if (as.alternatives) "" else ylabel),
ceiling = if (as.alternatives) 100 else NULL,
floor = 0,
labels = if(as.alternatives) list(format = paste0("{value}\U2009", ylabel)) else NULL
) %>%
hc_xAxis(allowDecimals=F) %>%
hc_add_theme(hc_theme_google(colors=palette)) %>%
hc_plotOptions(
series = list(enabled = T),
line = list(cursor = 'pointer', point = list(events = list(
click = JS("function() { window.open(this.click, 'korap'); }")
)))) %>%
hc_credits(enabled = T,
text = "KorAP R Client Pakckage",
href = "//github.com/KorAP/RKorAPClient/") %>%
hc_exporting(enabled = T) %>%
hc_tooltip(
formatter = JS(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)
) %>%
hc_add_series_korap_frequencies(df, as.alternatives)
}
## Mute notes: "no visible binding for global variable:"
globalVariables(c("value", "query", "condition", "vc"))
hc_add_series_korap_frequencies <- function(hc, df, as.alternatives = F) {
index <- 0
for(q in unique(df$condition)) {
dat <- df[df$condition==q,]
hc <- hc %>% hc_add_series(
marker = list(radius = 2),
name = q,
data = data.frame(
year = dat$year,
value = if (as.alternatives) dat$f else dat$ipm,
count = dat$totalResults,
click = dat$webUIRequestUrl
),
hcaes(year, value),
type = 'line',
colorIndex = index,
zIndex = 1
) %>%
hc_add_series(
name = "ci",
data = dat[,c('year', 'conf.low', 'conf.high')],
hcaes(x = year, low = conf.low, high = conf.high),
type = 'arearange',
fillOpacity = 0.3,
lineWidth = 0,
marker = list(enabled = F),
enableMouseTracking = F,
linkedTo= ':previous',
colorIndex = index,
zIndex = 0
)
index <- index+1
}
hc
}