Browse Source

pretty much feature complete

master
boB Rudis 5 years ago
parent
commit
d6256cb655
No known key found for this signature in database GPG Key ID: 1D7529BE14E2BBA9
  1. 1
      .Rbuildignore
  2. 1
      .gitignore
  3. 8
      DESCRIPTION
  4. 3
      NAMESPACE
  5. 59
      R/a-geom-rect.R
  6. 15
      R/datasets.R
  7. 72
      R/geom-chicklet.R
  8. 15
      R/ggchicklet-package.R
  9. 4
      R/utils-infix-helpers.R
  10. 75
      README.Rmd
  11. 88
      README.md
  12. BIN
      README_files/figure-gfm/unnamed-chunk-1-1.png
  13. 14
      data-raw/debates2019.R
  14. BIN
      data/debates2019.rda
  15. 23
      man/debates2019.Rd
  16. BIN
      man/figures/README-unnamed-chunk-1-1.png
  17. BIN
      man/figures/chickletex.png
  18. 49
      man/geom_chicklet.Rd
  19. 13
      man/ggchicklet.Rd
  20. 2
      vignettes/.gitignore
  21. BIN
      vignettes/nytimes.png
  22. 133
      vignettes/using-ggchicklet.Rmd

1
.Rbuildignore

@ -14,3 +14,4 @@
^tmp$
^notes$
^\.gitlab-ci\.yml$
^data-raw$

1
.gitignore

@ -7,3 +7,4 @@ README_cache
src/*.o
src/*.so
src/*.dll
inst/doc

8
DESCRIPTION

@ -1,6 +1,6 @@
Package: ggchicklet
Type: Package
Title: Create Chicklet (Rounded Segmented Column) Charts
Title: Create 'Chicklet' (Rounded Segmented Column) Charts
Version: 0.1.0
Date: 2019-06-28
Authors@R: c(
@ -19,7 +19,10 @@ Suggests:
testthat,
covr,
hrbrthemes,
stringi
dplyr,
forcats,
knitr,
rmarkdown
Depends:
R (>= 3.2.0)
Imports:
@ -27,3 +30,4 @@ Imports:
grid
Roxygen: list(markdown = TRUE)
RoxygenNote: 6.1.1
VignetteBuilder: knitr

3
NAMESPACE

@ -3,4 +3,7 @@
export(GeomChicklet)
export(geom_chicklet)
import(ggplot2)
importFrom(grid,gpar)
importFrom(grid,grobName)
importFrom(grid,roundrectGrob)
importFrom(grid,unit)

59
R/a-geom-rect.R

@ -21,45 +21,46 @@ geom_rrect <- function(mapping = NULL, data = NULL,
)
}
GeomRrect <- ggplot2::ggproto("GeomRrect", ggplot2::Geom,
GeomRrect <- ggplot2::ggproto(
"GeomRrect", ggplot2::Geom,
default_aes = ggplot2::aes(
colour = NA, fill = "grey35", size = 0.5, linetype = 1, alpha = NA
),
default_aes = ggplot2::aes(
colour = NA, fill = "grey35", size = 0.5, linetype = 1, alpha = NA
),
required_aes = c("xmin", "xmax", "ymin", "ymax"),
required_aes = c("xmin", "xmax", "ymin", "ymax"),
draw_panel = function(self, data, panel_params, coord,
radius = grid::unit(6, "pt")) {
draw_panel = function(self, data, panel_params, coord,
radius = grid::unit(6, "pt")) {
coords <- coord$transform(data, panel_params)
coords <- coord$transform(data, panel_params)
lapply(1:length(coords$xmin), function(i) {
lapply(1:length(coords$xmin), function(i) {
grid::roundrectGrob(
coords$xmin[i], coords$ymax[i],
width = (coords$xmax[i] - coords$xmin[i]),
height = (coords$ymax[i] - coords$ymin)[i],
r = radius,
default.units = "native",
just = c("left", "top"),
gp = grid::gpar(
col = coords$colour[i],
fill = alpha(coords$fill[i], coords$alpha[i]),
lwd = coords$size[i] * .pt,
lty = coords$linetype[i],
lineend = "butt"
)
)
grid::roundrectGrob(
coords$xmin[i], coords$ymax[i],
width = (coords$xmax[i] - coords$xmin[i]),
height = (coords$ymax[i] - coords$ymin)[i],
r = radius,
default.units = "native",
just = c("left", "top"),
gp = grid::gpar(
col = coords$colour[i],
fill = alpha(coords$fill[i], coords$alpha[i]),
lwd = coords$size[i] * .pt,
lty = coords$linetype[i],
lineend = "butt"
)
)
}) -> gl
}) -> gl
grobs <- do.call(grid::gList, gl)
grobs <- do.call(grid::gList, gl)
ggname("geom_rrect", grid::grobTree(children = grobs))
ggname("geom_rrect", grid::grobTree(children = grobs))
},
},
draw_key = ggplot2::draw_key_polygon
draw_key = ggplot2::draw_key_polygon
)

15
R/datasets.R

@ -0,0 +1,15 @@
#' @md
#' @title June 2019 U.S. Democratic Debate Candidate/Topic Times
#' @description The New York Times and other media outlets kept track of the time each
#' candidate spent talking including the timestamp of the start of the blathering
#' and the topic up for debate. This dataset only includes candidates and
#' topic times. The complete datasets (See References) also include moderator
#' metadata and opening/closing statement records.
#' @format data frame with columns: `elapsed` (dbl), `timestamp` (drtn), `speaker` (chr), `topic` (chr)
#' @docType data
#' @keywords datasets
#' @name debates2019
#' @references <https://www.nytimes.com/interactive/2019/admin/100000006581096.embedded.html>
#' @references <https://www.nytimes.com/interactive/2019/admin/100000006584572.embedded.html>
#' @usage data("debates2019")
NULL

72
R/geom-chicklet.R

@ -1,5 +1,21 @@
#' Chicklet (rounded segmented column) charts
#'
#' This geom behaves much like [ggplot2::geom_col()] but provides the option to
#' set a corner radius to turn sharp-edged bars into rounded rectangles; it also
#' sets some sane defaults for making chicklet charts.
#'
#' \if{html}{
#' A sample of the output from \code{geom_chicklet()}:
#'
#' \figure{chickletex.png}{options: width="100\%" alt="Figure: chickletex.png"}
#' }
#'
#' \if{latex}{
#' A sample of the output from \code{geom_chicklet()}:
#'
#' \figure{chickletex.png}{options: width=10cm}
#' }
#'
#' @section Aesthetics:
#' `geom_chicklet()` understands the following aesthetics:
#' - `x`
@ -10,14 +26,38 @@
#' - `group`
#' - `linetype`
#' - `size`
#'
#' @inheritParams ggplot2::layer
#' @inheritParams ggplot2::geom_point
#' @inheritParams ggplot2::geom_col
#' @param radius corner radius (default 6pt)
#' @param radius corner radius (default 3px)
#' @note the chicklet/segment stack positions are default set to be reversed (i.e.
#' left-to-right/bottom-to-top == earliest to latest order).
#' @export
#' @rdname geom_chicklet
geom_chicklet <- function(mapping = NULL, data = NULL, position = "stack",
radius = grid::unit(6, "pt"), ..., width = NULL,
#' @examples
#' library(ggplot2)
#'
#' data("debates2019")
#'
#' # set the speaker order
#' spkr_ordr <- aggregate(elapsed ~ speaker, data = debates2019, sum)
#' spkr_ordr <- spkr_ordr[order(spkr_ordr[["elapsed"]]),]
#'
#' debates2019$speaker <- factor(debates2019$speaker, spkr_ordr$speaker)
#'
#' ggplot(debates2019) +
#' # use 'group' to control left-to-right order
#' geom_chicklet(aes(speaker, elapsed, group = timestamp, fill = topic)) +
#' scale_y_continuous(expand = c(0, 0.01), position = "right") +
#' coord_flip() +
#' labs(x = NULL, y = "Minutes Spoken", fill = NULL) +
#' theme_minimal() +
#' theme(panel.grid.major.y = element_blank()) +
#' theme(legend.position = "bottom")
geom_chicklet <- function(mapping = NULL, data = NULL,
position = ggplot2::position_stack(reverse = TRUE),
radius = grid::unit(3, "pt"), ..., width = NULL,
na.rm = FALSE, show.legend = NA, inherit.aes = TRUE) {
layer(
data = data, mapping = mapping, stat = "identity",
@ -28,14 +68,33 @@ geom_chicklet <- function(mapping = NULL, data = NULL, position = "stack",
)
}
draw_key_rrect <- function(data, params, size) {
grid::roundrectGrob(
r = params$radius,
default.units = "native",
width = 1, height = 0.6,
name = "lkey",
gp = grid::gpar(
col = params$color %l0% "white",
fill = alpha(data$fill %||% data$colour %||% "grey20", data$alpha),
lty = data$linetype %||% 1
)
)
}
#' ggchicklet-ggplot2-ggproto
#' @format NULL
#' @usage NULL
#' @export
GeomChicklet <- ggproto(
"GeomChicklet", GeomRrect,
required_aes = c("x", "y"),
default_aes = ggplot2::aes(
colour = "white", fill = "grey35", size = 0.5, linetype = 1, alpha = NA
),
non_missing_aes = c("xmin", "xmax", "ymin", "ymax"),
setup_data = function(data, params) {
@ -47,7 +106,10 @@ GeomChicklet <- ggproto(
)
},
draw_panel = function(self, data, panel_params, coord,width = NULL, radius = grid::unit(6, "pt")) {
draw_panel = function(self, data, panel_params, coord,width = NULL, radius = grid::unit(3, "pt")) {
ggproto_parent(GeomRrect, self)$draw_panel(data, panel_params, coord, radius = radius)
}
},
draw_key = draw_key_rrect
)

15
R/ggchicklet-package.R

@ -4,13 +4,22 @@
#' than just bland rectangles. Methods are provided to create rounded
#' rectangle segmented column charts (i.e. "chicklets").
#'
#' - URL: <https://gitlab.com/hrbrmstr/ggchicklet>
#' - BugReports: <https://gitlab.com/hrbrmstr/ggchicklet/issues>
#' \if{html}{
#' A sample of the output from \code{geom_chicklet()}:
#'
#' \figure{chickletex.png}{options: width="100\%" alt="Figure: chickletex.png"}
#' }
#'
#' \if{latex}{
#' A sample of the output from \code{geom_chicklet()}:
#'
#' \figure{chickletex.png}{options: width=10cm}
#' }
#'
#' @md
#' @name ggchicklet
#' @docType package
#' @author Bob Rudis (bob@@rud.is)
#' @import ggplot2
#' @importFrom grid unit
#' @importFrom grid unit gpar roundrectGrob grobName
"_PACKAGE"

4
R/utils-infix-helpers.R

@ -0,0 +1,4 @@
`%l0%` <- function(x, y) if (length(x) == 0) y else x
`%||%` <- function(x, y) if (is.null(x)) y else x
`%@%` <- function(x, name) attr(x, name, exact = TRUE)
`%nin%` <- function(x, table) match(x, table, nomatch = 0) == 0

75
README.Rmd

@ -5,7 +5,8 @@ editor_options:
---
```{r pkg-knitr-opts, include=FALSE}
knitr::opts_chunk$set(
collapse=TRUE, fig.retina=2, message=FALSE, warning=FALSE
collapse=TRUE, fig.retina=2, message=FALSE, warning=FALSE,
fig.path = "man/figures/README-"
)
options(width=120)
```
@ -31,9 +32,15 @@ The following functions are implemented:
## Installation
```{r install-ex, eval=FALSE}
devtools::install_git("https://sr.ht.com/~hrbrmstr/ggchicklet.git")
install.packages("ggchicklet", repos = "https://cinc.rud.is")
# or
devtools::install_git("https://git.rud.is/hrbrmstr/ggchicklet.git")
# or
devtools::install_git("https://git.sr.ht/~hrbrmstr/ggchicklet")
# or
devtools::install_git("https://gitlab.com/hrbrmstr/ggchicklet.git")
devtools::install_gitlab("hrbrmstr/ggchicklet")
# or
devtools::install_bitbucket("hrbrmstr/ggchicklet")
# or (if you must)
devtools::install_github("hrbrmstr/ggchicklet")
```
@ -50,46 +57,54 @@ packageVersion("ggchicklet")
### From the NYTimes
```{r fig.width=10, fig.height=10, out.width="100%"}
library(stringi)
```{r fig.width=10, fig.height=9, out.width="100%"}
library(hrbrthemes)
library(tidyverse)
(debates_df <- read_csv("https://rud.is/data/2019-dem-debates.csv.gz"))
debates_df %>%
{ .ordr <<- count(., speaker, wt=elapsed, sort=TRUE) ; . } %>% # order by who had the most time
mutate(speaker = factor(speaker, levels = rev(.ordr$speaker))) %>%
ggplot() +
geom_chicklet(
aes(speaker, elapsed, group = timestamp, fill = topic), # group lets us use temporal order vs fill order
position = position_stack(reverse=TRUE), # reverse otherwise earliest is at end
radius = unit(3, "pt"),
width = 0.6,
color = "white"
) +
coord_flip() +
ggthemes::scale_fill_tableau("Tableau 20") +
scale_x_discrete(expand = c(0, 0.5)) +
data("debates2019")
debates2019 %>%
mutate(speaker = fct_reorder(speaker, elapsed, sum, .desc=FALSE)) %>%
mutate(topic = fct_other(
topic,
c("Immigration", "Economy", "Climate Change", "Gun Control", "Healthcare", "Foreign Policy"))
) %>%
ggplot(aes(speaker, elapsed, group = timestamp, fill = topic)) +
geom_chicklet(width = 0.75) +
scale_y_continuous(
expand = c(0, 0.0625),
expand = c(0, 0.0625),
position = "right",
breaks = seq(0, 14, 2),
labels = c(0, sprintf("%d min.", seq(2, 14, 2)))
) +
scale_fill_manual(
name = NULL,
values = c(
"Immigration" = "#ae4544",
"Economy" = "#d8cb98",
"Climate Change" = "#a4ad6f",
"Gun Control" = "#cc7c3a",
"Healthcare" = "#436f82",
"Foreign Policy" = "#7c5981",
"Other" = "#cccccc"
),
breaks = setdiff(unique(debates2019$topic), "Other")
) +
guides(
fill = guide_legend(nrow = 1)
) +
coord_flip() +
labs(
x = NULL, y = NULL, fill = NULL,
title = "How Long Each Candidate Spoke",
subtitle = "Nights 1 & 2 of the June 2019 Democratic Debates",
caption = "Originals <https://www.nytimes.com/interactive/2019/admin/100000006581096.embedded.html?>\n<https://www.nytimes.com/interactive/2019/admin/100000006584572.embedded.html?>\nby @nytimes Weiyi Cai, Jason Kao, Jasmine C. Lee, Alicia Parlapiano and Jugal K. Patel\nEach bar segment represents the length of a candidate’s response to a question.\n#rstats reproduction by @hrbrmstr"
caption = "Each bar segment represents the length of a candidate’s response to a question.\n\nOriginals <https://www.nytimes.com/interactive/2019/admin/100000006581096.embedded.html?>\n<https://www.nytimes.com/interactive/2019/admin/100000006584572.embedded.html?>\nby @nytimes Weiyi Cai, Jason Kao, Jasmine C. Lee, Alicia Parlapiano and Jugal K. Patel\n\n#rstats reproduction by @hrbrmstr"
) +
theme_ipsum_rc(grid="") +
theme(axis.text.x = element_text(color = "gray60", size = 9)) +
theme(axis.ticks = element_line(color = "gray60", size = 0.15)) +
theme(axis.ticks.x = element_line(color = "gray0", size = 0.15)) +
theme(axis.ticks.length = grid::unit(5, "pt")) +
theme(axis.ticks.length.x = grid::unit(5, "pt")) +
theme(legend.position = "bottom")
theme_ipsum_rc(grid="X") +
theme(axis.text.x = element_text(color = "gray60", size = 10)) +
theme(legend.position = "top")
```
## ggchicklet Metrics

88
README.md

@ -22,9 +22,15 @@ The following functions are implemented:
## Installation
``` r
devtools::install_git("https://sr.ht.com/~hrbrmstr/ggchicklet.git")
install.packages("ggchicklet", repos = "https://cinc.rud.is")
# or
devtools::install_git("https://git.rud.is/hrbrmstr/ggchicklet.git")
# or
devtools::install_git("https://git.sr.ht/~hrbrmstr/ggchicklet")
# or
devtools::install_git("https://gitlab.com/hrbrmstr/ggchicklet.git")
devtools::install_gitlab("hrbrmstr/ggchicklet")
# or
devtools::install_bitbucket("hrbrmstr/ggchicklet")
# or (if you must)
devtools::install_github("hrbrmstr/ggchicklet")
```
@ -42,69 +48,61 @@ packageVersion("ggchicklet")
### From the NYTimes
``` r
library(stringi)
library(hrbrthemes)
library(tidyverse)
(debates_df <- read_csv("https://rud.is/data/2019-dem-debates.csv.gz"))
## # A tibble: 192 x 4
## elapsed timestamp speaker topic
## <dbl> <drtn> <chr> <chr>
## 1 0.222 21:04 Sanders Healthcare
## 2 1.08 21:05 Biden Economy
## 3 0.975 21:06 Harris Economy
## 4 1.05 21:07 Hickenlooper Other
## 5 0.716 21:09 Sanders Trump
## 6 1.26 21:10 Bennet Healthcare
## 7 0.218 21:12 Gillibrand Healthcare
## 8 1.03 21:12 Buttigieg Education
## 9 0.378 21:13 Swalwell Education
## 10 1.08 21:14 Yang Economy
## # … with 182 more rows
debates_df %>%
{ .ordr <<- count(., speaker, wt=elapsed, sort=TRUE) ; . } %>% # order by who had the most time
mutate(speaker = factor(speaker, levels = rev(.ordr$speaker))) %>%
ggplot() +
geom_chicklet(
aes(speaker, elapsed, group = timestamp, fill = topic), # group lets us use temporal order vs fill order
position = position_stack(reverse=TRUE), # reverse otherwise earliest is at end
radius = unit(3, "pt"),
width = 0.6,
color = "white"
) +
coord_flip() +
ggthemes::scale_fill_tableau("Tableau 20") +
scale_x_discrete(expand = c(0, 0.5)) +
data("debates2019")
debates2019 %>%
mutate(speaker = fct_reorder(speaker, elapsed, sum, .desc=FALSE)) %>%
mutate(topic = fct_other(
topic,
c("Immigration", "Economy", "Climate Change", "Gun Control", "Healthcare", "Foreign Policy"))
) %>%
ggplot(aes(speaker, elapsed, group = timestamp, fill = topic)) +
geom_chicklet(width = 0.75) +
scale_y_continuous(
expand = c(0, 0.0625),
expand = c(0, 0.0625),
position = "right",
breaks = seq(0, 14, 2),
labels = c(0, sprintf("%d min.", seq(2, 14, 2)))
) +
scale_fill_manual(
name = NULL,
values = c(
"Immigration" = "#ae4544",
"Economy" = "#d8cb98",
"Climate Change" = "#a4ad6f",
"Gun Control" = "#cc7c3a",
"Healthcare" = "#436f82",
"Foreign Policy" = "#7c5981",
"Other" = "#cccccc"
),
breaks = setdiff(unique(debates2019$topic), "Other")
) +
guides(
fill = guide_legend(nrow = 1)
) +
coord_flip() +
labs(
x = NULL, y = NULL, fill = NULL,
title = "How Long Each Candidate Spoke",
subtitle = "Nights 1 & 2 of the June 2019 Democratic Debates",
caption = "Originals <https://www.nytimes.com/interactive/2019/admin/100000006581096.embedded.html?>\n<https://www.nytimes.com/interactive/2019/admin/100000006584572.embedded.html?>\nby @nytimes Weiyi Cai, Jason Kao, Jasmine C. Lee, Alicia Parlapiano and Jugal K. Patel\nEach bar segment represents the length of a candidate’s response to a question.\n#rstats reproduction by @hrbrmstr"
caption = "Each bar segment represents the length of a candidate’s response to a question.\n\nOriginals <https://www.nytimes.com/interactive/2019/admin/100000006581096.embedded.html?>\n<https://www.nytimes.com/interactive/2019/admin/100000006584572.embedded.html?>\nby @nytimes Weiyi Cai, Jason Kao, Jasmine C. Lee, Alicia Parlapiano and Jugal K. Patel\n\n#rstats reproduction by @hrbrmstr"
) +
theme_ipsum_rc(grid="") +
theme(axis.text.x = element_text(color = "gray60", size = 9)) +
theme(axis.ticks = element_line(color = "gray60", size = 0.15)) +
theme(axis.ticks.x = element_line(color = "gray0", size = 0.15)) +
theme(axis.ticks.length = grid::unit(5, "pt")) +
theme(axis.ticks.length.x = grid::unit(5, "pt")) +
theme(legend.position = "bottom")
theme_ipsum_rc(grid="X") +
theme(axis.text.x = element_text(color = "gray60", size = 10)) +
theme(legend.position = "top")
```
<img src="README_files/figure-gfm/unnamed-chunk-1-1.png" width="100%" />
<img src="man/figures/README-unnamed-chunk-1-1.png" width="100%" />
## ggchicklet Metrics
| Lang | \# Files | (%) | LoC | (%) | Blank lines | (%) | \# Lines | (%) |
| :--- | -------: | ---: | --: | ---: | ----------: | ---: | -------: | ---: |
| R | 6 | 0.86 | 89 | 0.65 | 19 | 0.48 | 42 | 0.54 |
| Rmd | 1 | 0.14 | 47 | 0.35 | 21 | 0.52 | 36 | 0.46 |
| R | 9 | 0.82 | 123 | 0.51 | 27 | 0.37 | 105 | 0.54 |
| Rmd | 2 | 0.18 | 116 | 0.49 | 46 | 0.63 | 90 | 0.46 |
## Code of Conduct

BIN
README_files/figure-gfm/unnamed-chunk-1-1.png

Binary file not shown.

Before

Width:  |  Height:  |  Size: 270 KiB

After

Width:  |  Height:  |  Size: 250 KiB

14
data-raw/debates2019.R

@ -0,0 +1,14 @@
## code to prepare `debates2019` dataset goes here
read_csv(
file = "https://rud.is/data/2019-dem-debates.csv.gz",
col_types = cols(
elapsed = col_double(),
timestamp = col_time(format = ""),
speaker = col_character(),
topic = col_character()
)
) -> debates2019
usethis::use_data(debates2019, overwrite = TRUE)

BIN
data/debates2019.rda

Binary file not shown.

23
man/debates2019.Rd

@ -0,0 +1,23 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/datasets.R
\docType{data}
\name{debates2019}
\alias{debates2019}
\title{June 2019 U.S. Democratic Debate Candidate/Topic Times}
\format{data frame with columns: \code{elapsed} (dbl), \code{timestamp} (drtn), \code{speaker} (chr), \code{topic} (chr)}
\usage{
data("debates2019")
}
\description{
The New York Times and other media outlets kept track of the time each
candidate spent talking including the timestamp of the start of the blathering
and the topic up for debate. This dataset only includes candidates and
topic times. The complete datasets (See References) also include moderator
metadata and opening/closing statement records.
}
\references{
\url{https://www.nytimes.com/interactive/2019/admin/100000006581096.embedded.html}
\url{https://www.nytimes.com/interactive/2019/admin/100000006584572.embedded.html}
}
\keyword{datasets}

BIN
man/figures/README-unnamed-chunk-1-1.png

Binary file not shown.

After

Width:  |  Height:  |  Size: 257 KiB

BIN
man/figures/chickletex.png

Binary file not shown.

After

Width:  |  Height:  |  Size: 107 KiB

49
man/geom_chicklet.Rd

@ -4,8 +4,9 @@
\alias{geom_chicklet}
\title{Chicklet (rounded segmented column) charts}
\usage{
geom_chicklet(mapping = NULL, data = NULL, position = "stack",
radius = grid::unit(6, "pt"), ..., width = NULL, na.rm = FALSE,
geom_chicklet(mapping = NULL, data = NULL,
position = ggplot2::position_stack(reverse = TRUE),
radius = grid::unit(3, "pt"), ..., width = NULL, na.rm = FALSE,
show.legend = NA, inherit.aes = TRUE)
}
\arguments{
@ -32,7 +33,7 @@ from a \code{formula} (e.g. \code{~ head(.x, 10)}).}
\item{position}{Position adjustment, either as a string, or the result of
a call to a position adjustment function.}
\item{radius}{corner radius (default 6pt)}
\item{radius}{corner radius (default 3px)}
\item{...}{Other arguments passed on to \code{\link[=layer]{layer()}}. These are
often aesthetics, used to set an aesthetic to a fixed value, like
@ -56,7 +57,26 @@ that define both data and aesthetics and shouldn't inherit behaviour from
the default plot specification, e.g. \code{\link[=borders]{borders()}}.}
}
\description{
Chicklet (rounded segmented column) charts
This geom behaves much like \code{\link[ggplot2:geom_col]{ggplot2::geom_col()}} but provides the option to
set a corner radius to turn sharp-edged bars into rounded rectangles; it also
sets some sane defaults for making chicklet charts.
}
\details{
\if{html}{
A sample of the output from \code{geom_chicklet()}:
\figure{chickletex.png}{options: width="100\%" alt="Figure: chickletex.png"}
}
\if{latex}{
A sample of the output from \code{geom_chicklet()}:
\figure{chickletex.png}{options: width=10cm}
}
}
\note{
the chicklet/segment stack positions are default set to be reversed (i.e.
left-to-right/bottom-to-top == earliest to latest order).
}
\section{Aesthetics}{
@ -73,3 +93,24 @@ Chicklet (rounded segmented column) charts
}
}
\examples{
library(ggplot2)
data("debates2019")
# set the speaker order
spkr_ordr <- aggregate(elapsed ~ speaker, data = debates2019, sum)
spkr_ordr <- spkr_ordr[order(spkr_ordr[["elapsed"]]),]
debates2019$speaker <- factor(debates2019$speaker, spkr_ordr$speaker)
ggplot(debates2019) +
# use 'group' to control left-to-right order
geom_chicklet(aes(speaker, elapsed, group = timestamp, fill = topic)) +
scale_y_continuous(expand = c(0, 0.01), position = "right") +
coord_flip() +
labs(x = NULL, y = "Minutes Spoken", fill = NULL) +
theme_minimal() +
theme(panel.grid.major.y = element_blank()) +
theme(legend.position = "bottom")
}

13
man/ggchicklet.Rd

@ -11,9 +11,16 @@ than just bland rectangles. Methods are provided to create rounded
rectangle segmented column charts (i.e. "chicklets").
}
\details{
\itemize{
\item URL: \url{https://gitlab.com/hrbrmstr/ggchicklet}
\item BugReports: \url{https://gitlab.com/hrbrmstr/ggchicklet/issues}
\if{html}{
A sample of the output from \code{geom_chicklet()}:
\figure{chickletex.png}{options: width="100\%" alt="Figure: chickletex.png"}
}
\if{latex}{
A sample of the output from \code{geom_chicklet()}:
\figure{chickletex.png}{options: width=10cm}
}
}
\seealso{

2
vignettes/.gitignore

@ -0,0 +1,2 @@
*.html
*.R

BIN
vignettes/nytimes.png

Binary file not shown.

After

Width:  |  Height:  |  Size: 102 KiB

133
vignettes/using-ggchicklet.Rmd

@ -0,0 +1,133 @@
---
title: "Using {ggchicklet}"
output:
rmarkdown::html_vignette:
df_print: kable
vignette: >
%\VignetteIndexEntry{Using {ggchicklet}}
%\VignetteEncoding{UTF-8}
%\VignetteEngine{knitr::rmarkdown}
editor_options:
chunk_output_type: console
---
```{r, include = FALSE}
knitr::opts_chunk$set(
message = FALSE,
warning = FALSE,
collapse = TRUE,
comment = "## "
)
```
The New York Times reporters [kept track of the candiate speaking time spent per-topic](https://www.nytimes.com/interactive/2019/admin/100000006581096.embedded.html) for the June 2019 initial U.S. Democratic debates. They used a segmented, rounded-corner bar chart --- ordered by timestamp --- that I've dubbed a "chicklet" chart since they look like the fairly well-known gum/candy. This is the image from one of them:
![](nytimes.png)
The rounded corners aesthetic looked great and said feature begat the creation of {ggchicklet}.
Let's load up the packages we'll need:
```{r setup}
library(hrbrthemes) # my preferred theme
library(ggchicklet) # this pacakge!
library(dplyr) # we need to do a bit of data wrangling
library(forcats) # so we include {dplyr} and {forcats}
library(ggplot2) # duh!
```
If you peek at the source code for the New York Times javascript-created charts you'll see
that all the data is right there. Rather than make you figure out how to wrangle it, a majority
subset has been included in the package and can be accessed via:
```{r data}
data("debates2019")
head(debates2019, 10)
```
The `elapsed` column contains how long the candidate spoke and `timestamp` is the time they started speaking. We'll use both to control the look and feel of the {ggchicklet} chart.
There are also candidates:
```{r data-ex-01}
distinct(debates2019, speaker) %>%
arrange(speaker) %>%
print(n=nrow(.))
```
and the topics debates:
```{r data-ex-02}
distinct(debates2019, topic) %>%
arrange(topic) %>%
print(n=nrow(.))
```
First, we'll use `forcats::fct_reorder()` to reorder the `speaker`s by total speaking time to
make it easier to compare the differences in total time spoken between candidate.
Then, we'll use `forcats::fct_other()` to limit the number of `topic`s to only those highlighted
by the New York Times (and to show how to do that).
We need to use `group = timestamp` to ensure the segments are ordered by time (vs category/topic)
and `fill = topic` to color them appropriately. Note that just using `fill = topic` would group
the segments by topic.
```{r chicklet, fig.width=600/72, fig.height=600/72}
debates2019 %>%
mutate(speaker = fct_reorder(speaker, elapsed, sum, .desc=FALSE)) %>%
mutate(topic = fct_other(
topic,
c("Immigration", "Economy", "Climate Change", "Gun Control", "Healthcare", "Foreign Policy"))
) %>%
ggplot(aes(speaker, elapsed, group = timestamp, fill = topic)) +
geom_chicklet(width = 0.75) +
scale_y_continuous(
expand = c(0, 0.0625),
position = "right",
breaks = seq(0, 14, 2),
labels = c(0, sprintf("%d min.", seq(2, 14, 2)))
) +
scale_fill_manual(
name = NULL,
values = c( # NYTimes colors
"Immigration" = "#ae4544",
"Economy" = "#d8cb98",
"Climate Change" = "#a4ad6f",
"Gun Control" = "#cc7c3a",
"Healthcare" = "#436f82",
"Foreign Policy" = "#7c5981",
"Other" = "#cccccc"
),
breaks = setdiff(unique(debates2019$topic), "Other")
) +
guides(
fill = guide_legend(nrow = 1)
) +
coord_flip() +
labs(
x = NULL, y = NULL, fill = NULL,
title = "How Long Each Candidate Spoke",
subtitle = "Nights 1 & 2 of the June 2019 Democratic Debates",
caption = "Each bar segment represents the length of a candidate’s response to a question.\n\nOriginals <https://www.nytimes.com/interactive/2019/admin/100000006581096.embedded.html?>\n<https://www.nytimes.com/interactive/2019/admin/100000006584572.embedded.html?>\nby @nytimes Weiyi Cai, Jason Kao, Jasmine C. Lee, Alicia Parlapiano and Jugal K. Patel\n\n#rstats reproduction by @hrbrmstr"
) +
theme_ipsum_rc(grid="X") +
theme(axis.text.x = element_text(color = "gray60", size = 10)) +
theme(legend.position = "top")
```
You can use `ggplot2::geom_col()` to create a similar chart without the rounded rectangles but `geom_chicklet()` sets some useful defaults:
- "`white`" stroke for the chicklet/segment (`geom_col()` has `NA` for the stroke)
- automatic reversing of the `group` order (`geom_col()` uses the standard sort order)
- radius setting of `unit(3, "px")`
- chicklet legend geom
You will need to modify `colour`/`color` to use something besides "`white`" if you are using
a non-white background and do not want a white stroke. Larger width chicklet segments may
look better with a larger radius.
Note also that the `group`ing column does not need to be a time-like object; any type of
ordered column will work to set the display order.
Loading…
Cancel
Save