blob: 9e981144fbbe853a40ebef618e9e08b008f09bdc [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 Kupietz05b22772020-02-18 21:58:42 +010014#' \donttest{year <- c(1990:2018)}\dontshow{year <- c(2013:2014)}
Marc Kupietz91145b02020-01-29 15:58:36 +010015#' new("KorAPConnection", verbose = TRUE) %>%
16#' frequencyQuery(query = c("macht []{0,3} Sinn", "ergibt []{0,3} Sinn"),
Marc Kupietz05b22772020-02-18 21:58:42 +010017#' vc = paste("textType = /Zeit.*/ & pubDate in", year),
Marc Kupietz91145b02020-01-29 15:58:36 +010018#' as.alternatives = TRUE) %>%
19#' hc_freq_by_year_ci(as.alternatives = TRUE)
20#'
Marc Kupietz05b22772020-02-18 21:58:42 +010021#' \donttest{
Marc Kupietz10f65c42020-01-31 15:18:24 +010022#' kco <- new("KorAPConnection", verbose = TRUE)
23#' expand_grid(
24#' condition = c("textDomain = /Wirtschaft.*/", "textDomain != /Wirtschaft.*/"),
25#' year = (2005:2011)
26#' ) %>%
27#' cbind(frequencyQuery(
28#' kco,
29#' "[tt/l=Heuschrecke]",
30#' paste0(.$condition, " & pubDate in ", .$year)
31#' )) %>%
32#' hc_freq_by_year_ci()
Marc Kupietz05b22772020-02-18 21:58:42 +010033#' }
Marc Kupietz10f65c42020-01-31 15:18:24 +010034#'
Marc Kupietz91145b02020-01-29 15:58:36 +010035hc_freq_by_year_ci <- function(df, as.alternatives = F, ylabel = if(as.alternatives) "%" else "ipm") {
36 title <- ""
37 df <- df %>%
38 { if(! as.alternatives) ipm(.) else RKorAPClient::percent(.) }
39
40 if (!"year" %in% colnames(df)) {
41 df <- df %>% mutate(year = as.integer(queryStringToLabel(df$vc, pubDateOnly = T)))
42 }
43 if (!"condition" %in% colnames(df)) {
44 if (length(base::unique(df$query)) > 1) {
45 df <- df %>% mutate(condition = query)
46 if(length(base::unique(queryStringToLabel(df$vc, excludePubDate = T ))) > 1) {
47 df <- df %>% mutate(condition = paste(condition, " & ",
48 queryStringToLabel(vc, excludePubDate = T )))
49 }
50 } else {
51 title <- base::unique(df$query)
52 if(length(base::unique(queryStringToLabel(df$vc, excludePubDate = T ))) > 1) {
53 df <- df %>% mutate(condition = queryStringToLabel(vc, excludePubDate = T ))
54 }
55 }
56 }
57 # use the D3 palette which provides 20 attractive and distinguishable colours
58 palette <- c("#1F77B4", "#FF7F0E", "#2CA02C", "#D62728", "#9467BD", "#8C564B", "#E377C2", "#7F7F7F", "#BCBD22", "#17BECF", "#AEC7E8", "#FFBB78", "#98DF8A", "#FF9896", "#C5B0D5", "#C49C94", "#F7B6D2", "#C7C7C7", "#DBDB8D", "#9EDAE5")
59 highcharter::highchart() %>%
60 hc_title(text=title) %>%
61 hc_chart(zoomType="xy") %>%
62 hc_yAxis(
63 title = list(text = if (as.alternatives) "" else ylabel),
64 ceiling = if (as.alternatives) 100 else NULL,
65 floor = 0,
66 labels = if(as.alternatives) list(format = paste0("{value}\U2009", ylabel)) else NULL
67 ) %>%
68 hc_xAxis(allowDecimals=F) %>%
69 hc_add_theme(hc_theme_google(colors=palette)) %>%
70 hc_plotOptions(
71 series = list(enabled = T),
72 line = list(cursor = 'pointer', point = list(events = list(
73 click = JS("function() { window.open(this.click, 'korap'); }")
74 )))) %>%
75 hc_credits(enabled = T,
76 text = "KorAP R Client Pakckage",
77 href = "//github.com/KorAP/RKorAPClient/") %>%
78 hc_exporting(enabled = T) %>%
79 hc_tooltip(
80 formatter = JS(paste0("function (tooltip) {
81 var str = tooltip.defaultFormatter.call(this, tooltip);
82 if(Array.isArray(str)) {
83 str = str.join('');
84 }
85 for (var i = 0; i < this.points.length; i++) {
86 str = str.replace(/([0-9.,]+.?)", ylabel, "/, this.points[i].point.count+' ($1@)');
87 }
88 return str.replace(/@/g, '", ylabel, "')
89 } ")),
90 crosshairs = T,
91 valueDecimals = 2,
92 shared = T,
93 valueSuffix = paste0('\U2009', ylabel)
94 ) %>%
95 hc_add_series_korap_frequencies(df, as.alternatives)
96}
97
Marc Kupietza4f36532020-02-03 22:50:08 +010098## Mute notes: "no visible binding for global variable:"
99globalVariables(c("value", "query", "condition", "vc"))
100
Marc Kupietz91145b02020-01-29 15:58:36 +0100101hc_add_series_korap_frequencies <- function(hc, df, as.alternatives = F) {
102 index <- 0
103 for(q in unique(df$condition)) {
104 dat <- df[df$condition==q,]
105 hc <- hc %>% hc_add_series(
106 marker = list(radius = 2),
107 name = q,
108 data = data.frame(
109 year = dat$year,
110 value = if (as.alternatives) dat$f else dat$ipm,
111 count = dat$totalResults,
112 click = dat$webUIRequestUrl
113 ),
114 hcaes(year, value),
115 type = 'line',
116 colorIndex = index,
117 zIndex = 1
118 ) %>%
119 hc_add_series(
120 name = "ci",
121 data = dat[,c('year', 'conf.low', 'conf.high')],
122 hcaes(x = year, low = conf.low, high = conf.high),
123 type = 'arearange',
124 fillOpacity = 0.3,
125 lineWidth = 0,
126 marker = list(enabled = F),
127 enableMouseTracking = F,
128 linkedTo= ':previous',
129 colorIndex = index,
130 zIndex = 0
131 )
132 index <- index+1
133 }
134 hc
135}