blob: 6601655f6c9e352b5adac707a741227910d79555 [file] [log] [blame]
Marc Kupietz91145b02020-01-29 15:58:36 +01001#' Experimental: Plot interactive frequency by year graphs with confidence intervals using highcharter
2#'
3#' Experimental convenience function for plotting typical frequency by year graphs with confidence intervals using highcharter.
4#' \bold{Warning:} This function may be moved to a new package.
5#'
6#' @import highcharter
7#' @export
8#'
9#' @param df data frame like the value of a \code{\link{frequencyQuery}}
Marc Kupietz43a6ade2020-02-18 17:01:44 +010010#' @param as.alternatives boolean decides whether queries should be treated as mutually exclusive and exhaustive wrt. to some meaningful class (e.g. spelling variants of a certain word form).
Marc Kupietz91145b02020-01-29 15:58:36 +010011#' @param ylabel defaults to \% if \code{as.alternatives} is \code{true} and to "ipm" otherwise.
12#'
13#' @examples
Marc Kupietz657d8e72020-02-25 18:31:50 +010014#' \donttest{year <- c(1990:2018)}\dontshow{year <- c(2013:2013)}
15#' \donttest{alternatives <- c("macht []{0,3} Sinn", "ergibt []{0,3} Sinn")}\dontshow{alternatives <- c("macht []{0,3} Sinn")}
Marc Kupietz91145b02020-01-29 15:58:36 +010016#' new("KorAPConnection", verbose = TRUE) %>%
Marc Kupietz657d8e72020-02-25 18:31:50 +010017#' frequencyQuery(query = alternatives,
Marc Kupietz05b22772020-02-18 21:58:42 +010018#' vc = paste("textType = /Zeit.*/ & pubDate in", year),
Marc Kupietz91145b02020-01-29 15:58:36 +010019#' as.alternatives = TRUE) %>%
20#' hc_freq_by_year_ci(as.alternatives = TRUE)
21#'
Marc Kupietz05b22772020-02-18 21:58:42 +010022#' \donttest{
Marc Kupietz10f65c42020-01-31 15:18:24 +010023#' kco <- new("KorAPConnection", verbose = TRUE)
24#' expand_grid(
25#' condition = c("textDomain = /Wirtschaft.*/", "textDomain != /Wirtschaft.*/"),
26#' year = (2005:2011)
27#' ) %>%
28#' cbind(frequencyQuery(
29#' kco,
30#' "[tt/l=Heuschrecke]",
31#' paste0(.$condition, " & pubDate in ", .$year)
32#' )) %>%
33#' hc_freq_by_year_ci()
Marc Kupietz05b22772020-02-18 21:58:42 +010034#' }
Marc Kupietz10f65c42020-01-31 15:18:24 +010035#'
Marc Kupietzcf1771d2020-03-04 16:03:04 +010036hc_freq_by_year_ci <- function(df, as.alternatives = FALSE, ylabel = if(as.alternatives) "%" else "ipm") {
Marc Kupietz91145b02020-01-29 15:58:36 +010037 title <- ""
38 df <- df %>%
39 { if(! as.alternatives) ipm(.) else RKorAPClient::percent(.) }
40
41 if (!"year" %in% colnames(df)) {
Marc Kupietzcf1771d2020-03-04 16:03:04 +010042 df <- df %>% mutate(year = as.integer(queryStringToLabel(df$vc, pubDateOnly = TRUE)))
Marc Kupietz91145b02020-01-29 15:58:36 +010043 }
44 if (!"condition" %in% colnames(df)) {
45 if (length(base::unique(df$query)) > 1) {
46 df <- df %>% mutate(condition = query)
Marc Kupietzcf1771d2020-03-04 16:03:04 +010047 if(length(base::unique(queryStringToLabel(df$vc, excludePubDate = TRUE ))) > 1) {
Marc Kupietz91145b02020-01-29 15:58:36 +010048 df <- df %>% mutate(condition = paste(condition, " & ",
Marc Kupietzcf1771d2020-03-04 16:03:04 +010049 queryStringToLabel(vc, excludePubDate = TRUE )))
Marc Kupietz91145b02020-01-29 15:58:36 +010050 }
51 } else {
Marc Kupietz5d70ffe2020-03-12 11:16:43 +010052 if (length(base::unique(queryStringToLabel(df$vc, excludePubDate = TRUE ))) > 1) {
53 title <- base::unique(df$query)
Marc Kupietzcf1771d2020-03-04 16:03:04 +010054 df <- df %>% mutate(condition = queryStringToLabel(vc, excludePubDate = TRUE ))
Marc Kupietz5d70ffe2020-03-12 11:16:43 +010055 } else {
56 df <- df %>% mutate(condition = query)
Marc Kupietz91145b02020-01-29 15:58:36 +010057 }
58 }
59 }
60 # use the D3 palette which provides 20 attractive and distinguishable colours
61 palette <- c("#1F77B4", "#FF7F0E", "#2CA02C", "#D62728", "#9467BD", "#8C564B", "#E377C2", "#7F7F7F", "#BCBD22", "#17BECF", "#AEC7E8", "#FFBB78", "#98DF8A", "#FF9896", "#C5B0D5", "#C49C94", "#F7B6D2", "#C7C7C7", "#DBDB8D", "#9EDAE5")
62 highcharter::highchart() %>%
63 hc_title(text=title) %>%
64 hc_chart(zoomType="xy") %>%
65 hc_yAxis(
66 title = list(text = if (as.alternatives) "" else ylabel),
67 ceiling = if (as.alternatives) 100 else NULL,
68 floor = 0,
69 labels = if(as.alternatives) list(format = paste0("{value}\U2009", ylabel)) else NULL
70 ) %>%
Marc Kupietzcf1771d2020-03-04 16:03:04 +010071 hc_xAxis(allowDecimals=FALSE) %>%
Marc Kupietz91145b02020-01-29 15:58:36 +010072 hc_add_theme(hc_theme_google(colors=palette)) %>%
73 hc_plotOptions(
Marc Kupietzcf1771d2020-03-04 16:03:04 +010074 series = list(enabled = TRUE),
Marc Kupietz91145b02020-01-29 15:58:36 +010075 line = list(cursor = 'pointer', point = list(events = list(
76 click = JS("function() { window.open(this.click, 'korap'); }")
77 )))) %>%
Marc Kupietzcf1771d2020-03-04 16:03:04 +010078 hc_credits(enabled = TRUE,
Marc Kupietz91145b02020-01-29 15:58:36 +010079 text = "KorAP R Client Pakckage",
80 href = "//github.com/KorAP/RKorAPClient/") %>%
Marc Kupietzcf1771d2020-03-04 16:03:04 +010081 hc_exporting(enabled = TRUE) %>%
Marc Kupietz91145b02020-01-29 15:58:36 +010082 hc_tooltip(
83 formatter = JS(paste0("function (tooltip) {
84 var str = tooltip.defaultFormatter.call(this, tooltip);
85 if(Array.isArray(str)) {
86 str = str.join('');
87 }
88 for (var i = 0; i < this.points.length; i++) {
89 str = str.replace(/([0-9.,]+.?)", ylabel, "/, this.points[i].point.count+' ($1@)');
90 }
91 return str.replace(/@/g, '", ylabel, "')
92 } ")),
Marc Kupietzcf1771d2020-03-04 16:03:04 +010093 crosshairs = TRUE,
Marc Kupietz91145b02020-01-29 15:58:36 +010094 valueDecimals = 2,
Marc Kupietzcf1771d2020-03-04 16:03:04 +010095 shared = TRUE,
Marc Kupietz91145b02020-01-29 15:58:36 +010096 valueSuffix = paste0('\U2009', ylabel)
97 ) %>%
98 hc_add_series_korap_frequencies(df, as.alternatives)
99}
100
Marc Kupietza4f36532020-02-03 22:50:08 +0100101## Mute notes: "no visible binding for global variable:"
102globalVariables(c("value", "query", "condition", "vc"))
103
Marc Kupietzcf1771d2020-03-04 16:03:04 +0100104hc_add_series_korap_frequencies <- function(hc, df, as.alternatives = FALSE) {
Marc Kupietz91145b02020-01-29 15:58:36 +0100105 index <- 0
106 for(q in unique(df$condition)) {
107 dat <- df[df$condition==q,]
108 hc <- hc %>% hc_add_series(
109 marker = list(radius = 2),
110 name = q,
111 data = data.frame(
112 year = dat$year,
113 value = if (as.alternatives) dat$f else dat$ipm,
114 count = dat$totalResults,
115 click = dat$webUIRequestUrl
116 ),
117 hcaes(year, value),
118 type = 'line',
119 colorIndex = index,
120 zIndex = 1
121 ) %>%
122 hc_add_series(
123 name = "ci",
124 data = dat[,c('year', 'conf.low', 'conf.high')],
125 hcaes(x = year, low = conf.low, high = conf.high),
126 type = 'arearange',
127 fillOpacity = 0.3,
128 lineWidth = 0,
Marc Kupietzcf1771d2020-03-04 16:03:04 +0100129 marker = list(enabled = FALSE),
130 enableMouseTracking = FALSE,
Marc Kupietz91145b02020-01-29 15:58:36 +0100131 linkedTo= ':previous',
132 colorIndex = index,
133 zIndex = 0
134 )
135 index <- index+1
136 }
137 hc
138}
Marc Kupietz882f08c2020-03-18 13:30:31 +0100139
140.onAttach <- function(libname = find.package("RKorAPClient"),
141 pkgname = "RKorAPClient") {
142 packageStartupMessage(
143 "If you intend to use the Highcharts plot options, please note that Highcharts (www.highcharts.com) is a Highsoft software product which is not free for commercial and governmental use."
144 )
145}
146