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 | |
Marc Kupietz | 23daf5b | 2019-11-27 10:28:07 +0100 | [diff] [blame] | 24 | #' Convert corpus frequency table of alternatives to percent |
| 25 | #' |
| 26 | #' Convenience function for converting frequency tables of alternative variants |
| 27 | #' (generated with \code{as.alternatives=T}) to percent. |
| 28 | #' |
| 29 | #' @param df table returned from \code{\link{frequencyQuery}} |
| 30 | #' |
| 31 | #' @return original table with converted columns \code{f}, \code{conf.low} and \code{conf.high} |
| 32 | #' @export |
| 33 | #' |
| 34 | #' @importFrom dplyr .data |
| 35 | #' |
| 36 | #' @examples |
| 37 | #' new("KorAPConnection") %>% |
| 38 | #' frequencyQuery(c("Tollpatsch", "Tolpatsch"), |
| 39 | #' vc=paste0("pubDate in ", 2000:2002), |
| 40 | #' as.alternatives = TRUE) %>% |
| 41 | #' percent() |
| 42 | percent <- function(df) { |
| 43 | df %>% |
| 44 | mutate(f = .data$f * 10^2, conf.low = .data$conf.low * 10^2, conf.high = .data$conf.high * 10^2) |
| 45 | } |
| 46 | |
Marc Kupietz | 95240e9 | 2019-11-27 18:19:04 +0100 | [diff] [blame] | 47 | #' Convert query or vc strings to plot labels |
| 48 | #' |
| 49 | #' Converts a vector of query or vc strings to typically appropriate legend labels |
| 50 | #' by clipping off prefixes and suffixes that are common to all query strings. |
| 51 | #' |
| 52 | #' @param data string or vector of query or vc definition strings |
Marc Kupietz | 62d29a1 | 2020-01-18 12:38:36 +0100 | [diff] [blame^] | 53 | #' @param pubDateOnly discard all but the publication date |
| 54 | #' @param excludePubDate discard publication date constraints |
Marc Kupietz | 95240e9 | 2019-11-27 18:19:04 +0100 | [diff] [blame] | 55 | #' @return string or vector of strings with clipped off common prefixes and suffixes |
| 56 | #' |
| 57 | #' @examples |
| 58 | #' queryStringToLabel(paste("textType = /Zeit.*/ & pubDate in", c(2010:2019))) |
| 59 | #' queryStringToLabel(c("[marmot/m=mood:subj]", "[marmot/m=mood:ind]")) |
| 60 | #' queryStringToLabel(c("wegen dem [tt/p=NN]", "wegen des [tt/p=NN]")) |
| 61 | #' |
| 62 | #' @importFrom PTXQC lcpCount |
| 63 | #' @importFrom PTXQC lcsCount |
| 64 | #' |
| 65 | #' @export |
Marc Kupietz | 62d29a1 | 2020-01-18 12:38:36 +0100 | [diff] [blame^] | 66 | queryStringToLabel <- function(data, pubDateOnly = F, excludePubDate = F) { |
| 67 | if (pubDateOnly) { |
| 68 | data <-substring(data, regexpr("pubDate", data)+7) |
| 69 | } else if(excludePubDate) { |
| 70 | data <-substring(data, 1, regexpr("pubDate", data)) |
| 71 | } |
Marc Kupietz | 95240e9 | 2019-11-27 18:19:04 +0100 | [diff] [blame] | 72 | leftCommon = lcpCount(data) |
Marc Kupietz | 62d29a1 | 2020-01-18 12:38:36 +0100 | [diff] [blame^] | 73 | while (leftCommon > 0 && grepl("[[:alnum:]/=.*!]", substring(data[1], leftCommon, leftCommon))) { |
Marc Kupietz | 95240e9 | 2019-11-27 18:19:04 +0100 | [diff] [blame] | 74 | leftCommon <- leftCommon - 1 |
| 75 | } |
| 76 | rightCommon = lcsCount(data) |
Marc Kupietz | 62d29a1 | 2020-01-18 12:38:36 +0100 | [diff] [blame^] | 77 | while (rightCommon > 0 && grepl("[[:alnum:]/=.*!]", substring(data[1], 1+nchar(data[1]) - rightCommon, 1+nchar(data[1]) - rightCommon))) { |
Marc Kupietz | 95240e9 | 2019-11-27 18:19:04 +0100 | [diff] [blame] | 78 | rightCommon <- rightCommon - 1 |
| 79 | } |
| 80 | substring(data, leftCommon + 1, nchar(data) - rightCommon) |
| 81 | } |
| 82 | |
Marc Kupietz | bb7d232 | 2019-10-06 21:42:34 +0200 | [diff] [blame] | 83 | |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 84 | ## Mute notes: "Undefined global functions or variables:" |
| 85 | globalVariables(c("conf.high", "conf.low", "onRender", "webUIRequestUrl")) |
| 86 | |
| 87 | |
| 88 | #' Experimental: Plot frequency by year graphs with confidence intervals |
Marc Kupietz | d68f971 | 2019-10-06 21:48:00 +0200 | [diff] [blame] | 89 | #' |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 90 | #' Experimental convenience function for plotting typical frequency by year graphs with confidence intervals using ggplot2. |
| 91 | #' \bold{Warning:} This function may be moved to a new package. |
| 92 | #' |
| 93 | #' @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. |
| 94 | #' @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] | 95 | #' |
| 96 | #' @examples |
| 97 | #' library(ggplot2) |
| 98 | #' kco <- new("KorAPConnection", verbose=TRUE) |
| 99 | #' expand_grid(condition = c("textDomain = /Wirtschaft.*/", "textDomain != /Wirtschaft.*/"), |
| 100 | #' year = (2002:2018)) %>% |
| 101 | #' cbind(frequencyQuery(kco, "[tt/l=Heuschrecke]", |
| 102 | #' paste0(.$condition," & pubDate in ", .$year))) %>% |
| 103 | #' ipm() %>% |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 104 | #' ggplot(aes(year, ipm, fill = condition, color = condition)) + |
Marc Kupietz | d68f971 | 2019-10-06 21:48:00 +0200 | [diff] [blame] | 105 | #' geom_freq_by_year_ci() |
| 106 | #' |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 107 | #' @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] | 108 | #' |
| 109 | #' @export |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 110 | 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] | 111 | list( |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 112 | geom_ribbon(mapping, |
| 113 | alpha = .3, linetype = 0, show.legend = FALSE, ...), |
| 114 | geom_line(...), |
| 115 | geom_click_point(aes(url=webUIRequestUrl), ...), |
| 116 | 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] | 117 | scale_x_continuous(breaks = function(x) seq(ceiling(x[1]), floor(x[2]), by = 1 + floor(((x[2]-x[1])/30))))) |
| 118 | } |
| 119 | |
Marc Kupietz | 865760f | 2019-10-07 19:29:44 +0200 | [diff] [blame] | 120 | #' @importFrom ggplot2 ggproto aes GeomPoint |
| 121 | GeomClickPoint <- ggproto( |
| 122 | "GeomPoint", |
| 123 | GeomPoint, |
| 124 | required_aes = c("x", "y"), |
| 125 | default_aes = aes( |
| 126 | shape = 19, colour = "black", size = 1.5, fill = NA, |
| 127 | alpha = NA, stroke = 0.5, url = NA |
| 128 | ), |
| 129 | extra_params = c("na.rm", "url"), |
| 130 | draw_panel = function(data, panel_params, |
| 131 | coord, na.rm = FALSE, showpoints = TRUE, url = NULL) { |
| 132 | GeomPoint$draw_panel(data, panel_params, coord, na.rm = na.rm) |
| 133 | } |
| 134 | ) |
| 135 | |
| 136 | #' @importFrom ggplot2 layer |
| 137 | geom_click_point <- function(mapping = NULL, data = NULL, stat = "identity", |
| 138 | position = "identity", na.rm = FALSE, show.legend = NA, |
| 139 | inherit.aes = TRUE, url = NA, ...) { |
| 140 | layer( |
| 141 | geom = GeomClickPoint, mapping = mapping, data = data, stat = stat, |
| 142 | position = position, show.legend = show.legend, inherit.aes = inherit.aes, |
| 143 | params = list(na.rm = na.rm, ...) |
| 144 | ) |
| 145 | } |
| 146 | |
| 147 | |
| 148 | #' @importFrom htmlwidgets onRender |
| 149 | tooltip2hyperlink <- function(p, attribute="webUIRequestUrl") { |
| 150 | pattern <- paste0(attribute, ": ([^<]+)") |
| 151 | for(i in grep(attribute, p$x$data)) { |
| 152 | x <- p[["x"]][["data"]][[i]][["text"]] |
| 153 | m <- regexpr(pattern, x) |
| 154 | matches <- sub(paste0(attribute, ": "), "", regmatches(x, m)) |
| 155 | p$x$data[[i]]$customdata <- matches |
| 156 | p[["x"]][["data"]][[i]][["text"]] <- sub(paste0(attribute, ":[^<]*<br ?/?>"), "", p[["x"]][["data"]][[i]][["text"]] ) |
| 157 | } |
| 158 | onRender(p, "function(el, x) { el.on('plotly_click', function(d) { var url=d.points[0].customdata; if(url) { window.open(url, 'korap') } })}") |
| 159 | } |
| 160 | |
| 161 | #' Experimental: Convert ggplot2 to plotly with hyperlinks to KorAP queries |
| 162 | #' |
| 163 | #' \code{RKorAPClient::ggplotly} converts a \code{ggplot2::ggplot()} object to a plotly |
| 164 | #' object with hyperlinks from data points to corresponding KorAP queries. |
| 165 | #' \bold{Warning:} This function may be moved to a new package. |
| 166 | #' |
| 167 | #' @param p a ggplot object. |
| 168 | #' @param tooltip a character vector specifying which aesthetic mappings to show |
| 169 | #' in the tooltip. If you want hyperlinks to KorAP queries you need to include |
| 170 | #' \code{"url"} here. |
| 171 | #' @param ... Other arguments passed to \code{plotly::ggplotly} |
| 172 | #' |
| 173 | #' @examples |
| 174 | #' library(ggplot2) |
| 175 | #' kco <- new("KorAPConnection", verbose=TRUE) |
| 176 | #' g <- expand_grid(condition = c("textDomain = /Wirtschaft.*/", "textDomain != /Wirtschaft.*/"), |
| 177 | #' year = (2002:2018)) %>% |
| 178 | #' cbind(frequencyQuery(kco, "[tt/l=Heuschrecke]", |
| 179 | #' paste0(.$condition," & pubDate in ", .$year))) %>% |
| 180 | #' ipm() %>% |
| 181 | #' ggplot(aes(year, ipm, fill = condition, color = condition)) + |
| 182 | #' ## theme_light(base_size = 20) + |
| 183 | #' geom_freq_by_year_ci() |
| 184 | #' p <- ggplotly(g) |
| 185 | #' print(p) |
| 186 | #' ## saveWidget(p, paste0(tmpdir(), "heuschrecke.html") |
| 187 | #' |
| 188 | #' |
| 189 | #' @importFrom plotly ggplotly |
| 190 | #' @importFrom htmlwidgets saveWidget |
| 191 | #' @export |
| 192 | ggplotly <- function(p = ggplot2::last_plot(), tooltip = c("x", "y", "colour", "url"), ...) { |
| 193 | pp <- plotly::ggplotly(p = p, tooltip = tooltip, ...) |
| 194 | tooltip2hyperlink(pp) |
| 195 | } |