Marc Kupietz | bb7d232 | 2019-10-06 21:42:34 +0200 | [diff] [blame] | 1 | |
| 2 | #' Convert corpus frequency table to instances per million. |
| 3 | #' |
| 4 | #' Convenience function for converting frequency tables to instances per |
| 5 | #' million. |
| 6 | #' |
| 7 | #' Given a table with columns \code{f}, \code{conf.low}, and \code{conf.high}, \code{ipm} ads a \code{column ipm} |
| 8 | #' und multiplies conf.low and \code{conf.high} with 10^6. |
| 9 | #' |
| 10 | #' @param df table returned from \code{\link{frequencyQuery}} |
| 11 | #' |
| 12 | #' @return original table with additional column \code{ipm} and converted columns \code{conf.low} and \code{conf.high} |
| 13 | #' @export |
| 14 | #' |
| 15 | #' @importFrom dplyr .data |
| 16 | #' |
| 17 | #' @examples |
| 18 | #' new("KorAPConnection") %>% frequencyQuery("Test", paste0("pubDate in ", 2000:2002)) %>% ipm() |
| 19 | ipm <- function(df) { |
| 20 | df %>% |
| 21 | mutate(ipm = .data$f * 10^6, conf.low = .data$conf.low * 10^6, conf.high = .data$conf.high * 10^6) |
| 22 | } |
| 23 | |
| 24 | |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 25 | ## Mute notes: "Undefined global functions or variables:" |
| 26 | globalVariables(c("conf.high", "conf.low", "onRender", "webUIRequestUrl")) |
| 27 | |
| 28 | |
| 29 | #' Experimental: Plot frequency by year graphs with confidence intervals |
Marc Kupietz | d68f971 | 2019-10-06 21:48:00 +0200 | [diff] [blame] | 30 | #' |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 31 | #' Experimental convenience function for plotting typical frequency by year graphs with confidence intervals using ggplot2. |
| 32 | #' \bold{Warning:} This function may be moved to a new package. |
| 33 | #' |
| 34 | #' @param mapping Set of aesthetic mappings created by aes() or aes_(). If specified and inherit.aes = TRUE (the default), it is combined with the default mapping at the top level of the plot. You must supply mapping if there is no plot mapping. |
| 35 | #' @param ... Other arguments passed to geom_ribbon, geom_line, and geom_click_point. |
Marc Kupietz | d68f971 | 2019-10-06 21:48:00 +0200 | [diff] [blame] | 36 | #' |
| 37 | #' @examples |
| 38 | #' library(ggplot2) |
| 39 | #' kco <- new("KorAPConnection", verbose=TRUE) |
| 40 | #' expand_grid(condition = c("textDomain = /Wirtschaft.*/", "textDomain != /Wirtschaft.*/"), |
| 41 | #' year = (2002:2018)) %>% |
| 42 | #' cbind(frequencyQuery(kco, "[tt/l=Heuschrecke]", |
| 43 | #' paste0(.$condition," & pubDate in ", .$year))) %>% |
| 44 | #' ipm() %>% |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 45 | #' ggplot(aes(year, ipm, fill = condition, color = condition)) + |
Marc Kupietz | d68f971 | 2019-10-06 21:48:00 +0200 | [diff] [blame] | 46 | #' geom_freq_by_year_ci() |
| 47 | #' |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 48 | #' @importFrom ggplot2 ggplot aes geom_ribbon geom_line geom_point theme element_text scale_x_continuous |
Marc Kupietz | d68f971 | 2019-10-06 21:48:00 +0200 | [diff] [blame] | 49 | #' |
| 50 | #' @export |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 51 | geom_freq_by_year_ci <- function(mapping = aes(ymin=conf.low, ymax=conf.high), ...) { |
Marc Kupietz | d68f971 | 2019-10-06 21:48:00 +0200 | [diff] [blame] | 52 | list( |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 53 | geom_ribbon(mapping, |
| 54 | alpha = .3, linetype = 0, show.legend = FALSE, ...), |
| 55 | geom_line(...), |
| 56 | geom_click_point(aes(url=webUIRequestUrl), ...), |
| 57 | theme(axis.text.x = element_text(angle = 45, hjust = 1), legend.position = c(0.8, 0.2)), |
Marc Kupietz | d68f971 | 2019-10-06 21:48:00 +0200 | [diff] [blame] | 58 | scale_x_continuous(breaks = function(x) seq(ceiling(x[1]), floor(x[2]), by = 1 + floor(((x[2]-x[1])/30))))) |
| 59 | } |
| 60 | |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 61 | #' @importFrom ggplot2 ggproto aes GeomPoint |
| 62 | GeomClickPoint <- ggproto( |
| 63 | "GeomPoint", |
| 64 | GeomPoint, |
| 65 | required_aes = c("x", "y"), |
| 66 | default_aes = aes( |
| 67 | shape = 19, colour = "black", size = 1.5, fill = NA, |
| 68 | alpha = NA, stroke = 0.5, url = NA |
| 69 | ), |
| 70 | extra_params = c("na.rm", "url"), |
| 71 | draw_panel = function(data, panel_params, |
| 72 | coord, na.rm = FALSE, showpoints = TRUE, url = NULL) { |
| 73 | GeomPoint$draw_panel(data, panel_params, coord, na.rm = na.rm) |
| 74 | } |
| 75 | ) |
| 76 | |
| 77 | #' @importFrom ggplot2 layer |
| 78 | geom_click_point <- function(mapping = NULL, data = NULL, stat = "identity", |
| 79 | position = "identity", na.rm = FALSE, show.legend = NA, |
| 80 | inherit.aes = TRUE, url = NA, ...) { |
| 81 | layer( |
| 82 | geom = GeomClickPoint, mapping = mapping, data = data, stat = stat, |
| 83 | position = position, show.legend = show.legend, inherit.aes = inherit.aes, |
| 84 | params = list(na.rm = na.rm, ...) |
| 85 | ) |
| 86 | } |
| 87 | |
| 88 | |
| 89 | #' @importFrom htmlwidgets onRender |
| 90 | tooltip2hyperlink <- function(p, attribute="webUIRequestUrl") { |
| 91 | pattern <- paste0(attribute, ": ([^<]+)") |
| 92 | for(i in grep(attribute, p$x$data)) { |
| 93 | x <- p[["x"]][["data"]][[i]][["text"]] |
| 94 | m <- regexpr(pattern, x) |
| 95 | matches <- sub(paste0(attribute, ": "), "", regmatches(x, m)) |
| 96 | p$x$data[[i]]$customdata <- matches |
| 97 | p[["x"]][["data"]][[i]][["text"]] <- sub(paste0(attribute, ":[^<]*<br ?/?>"), "", p[["x"]][["data"]][[i]][["text"]] ) |
| 98 | } |
| 99 | onRender(p, "function(el, x) { el.on('plotly_click', function(d) { var url=d.points[0].customdata; if(url) { window.open(url, 'korap') } })}") |
| 100 | } |
| 101 | |
| 102 | #' Experimental: Convert ggplot2 to plotly with hyperlinks to KorAP queries |
| 103 | #' |
| 104 | #' \code{RKorAPClient::ggplotly} converts a \code{ggplot2::ggplot()} object to a plotly |
| 105 | #' object with hyperlinks from data points to corresponding KorAP queries. |
| 106 | #' \bold{Warning:} This function may be moved to a new package. |
| 107 | #' |
| 108 | #' @param p a ggplot object. |
| 109 | #' @param tooltip a character vector specifying which aesthetic mappings to show |
| 110 | #' in the tooltip. If you want hyperlinks to KorAP queries you need to include |
| 111 | #' \code{"url"} here. |
| 112 | #' @param ... Other arguments passed to \code{plotly::ggplotly} |
| 113 | #' |
| 114 | #' @examples |
| 115 | #' library(ggplot2) |
| 116 | #' kco <- new("KorAPConnection", verbose=TRUE) |
| 117 | #' g <- expand_grid(condition = c("textDomain = /Wirtschaft.*/", "textDomain != /Wirtschaft.*/"), |
| 118 | #' year = (2002:2018)) %>% |
| 119 | #' cbind(frequencyQuery(kco, "[tt/l=Heuschrecke]", |
| 120 | #' paste0(.$condition," & pubDate in ", .$year))) %>% |
| 121 | #' ipm() %>% |
| 122 | #' ggplot(aes(year, ipm, fill = condition, color = condition)) + |
| 123 | #' ## theme_light(base_size = 20) + |
| 124 | #' geom_freq_by_year_ci() |
| 125 | #' p <- ggplotly(g) |
| 126 | #' print(p) |
| 127 | #' ## saveWidget(p, paste0(tmpdir(), "heuschrecke.html") |
| 128 | #' |
| 129 | #' |
| 130 | #' @importFrom plotly ggplotly |
| 131 | #' @importFrom htmlwidgets saveWidget |
| 132 | #' @export |
| 133 | ggplotly <- function(p = ggplot2::last_plot(), tooltip = c("x", "y", "colour", "url"), ...) { |
| 134 | pp <- plotly::ggplotly(p = p, tooltip = tooltip, ...) |
| 135 | tooltip2hyperlink(pp) |
| 136 | } |