apexcharter/R/apex.R

295 lines
7.6 KiB
R
Raw Normal View History

2019-02-14 15:50:58 +01:00
2019-07-24 12:20:22 +02:00
#' @title Quick ApexChart
#'
2020-02-12 11:57:24 +01:00
#' @description Initialize a chart with three main parameters :
#' data, mapping and type of chart.
2019-02-14 15:50:58 +01:00
#'
2020-02-12 11:57:24 +01:00
#' @param data Default dataset to use for chart. If not already
#' a \code{data.frame}, it will be coerced to with \code{as.data.frame}.
2019-02-14 15:50:58 +01:00
#' @param mapping Default list of aesthetic mappings to use for chart
2020-03-04 21:51:40 +01:00
#' @param type Specify the chart type. Available options:
2020-02-12 11:57:24 +01:00
#' \code{"column"}, \code{"bar"}, \code{"line"},
#' \code{"area"}, \code{"spline"}, \code{"pie"}, \code{"donut"},
2020-02-12 16:37:47 +01:00
#' \code{"radialBar"}, \code{"radar"}, \code{"scatter"}, \code{"heatmap"},
#' \code{"timeline"}.
2019-02-14 15:50:58 +01:00
#' @param ... Other arguments passed on to methods. Not currently used.
2020-02-12 11:57:24 +01:00
#' @param auto_update In Shiny application, update existing chart
2020-02-12 18:21:40 +01:00
#' rather than generating new one. Can be \code{TRUE}/\code{FALSE} or
#' use \code{\link{config_update}} for more control.
2020-02-12 16:37:47 +01:00
#' @param serie_name Name for the serie displayed in tooltip,
#' only used for single serie.
2019-02-14 15:50:58 +01:00
#' @param width A numeric input in pixels.
#' @param height A numeric input in pixels.
#' @param elementId Use an explicit element ID for the widget.
2019-07-24 12:20:22 +02:00
#'
#' @return A \code{apexcharts} \code{htmlwidget} object.
2019-02-14 15:50:58 +01:00
#'
#' @export
#'
2019-02-18 20:29:34 +01:00
#' @importFrom rlang eval_tidy as_label
2019-02-14 15:50:58 +01:00
#' @importFrom utils modifyList
#'
2019-11-26 11:26:47 +01:00
#' @example examples/apex.R
2020-02-12 11:57:24 +01:00
apex <- function(data, mapping, type = "column", ...,
2020-02-12 18:21:40 +01:00
auto_update = TRUE,
2020-02-12 16:37:47 +01:00
serie_name = NULL,
2020-02-12 11:57:24 +01:00
width = NULL, height = NULL, elementId = NULL) {
2020-02-12 16:37:47 +01:00
type <- match.arg(
arg = type,
choices = c(
"column", "bar", "line", "area", "spline", "area-spline",
"pie", "donut", "radialBar", "radar", "scatter", "heatmap",
"timeline"
)
)
2019-02-14 15:50:58 +01:00
data <- as.data.frame(data)
2019-07-19 14:11:41 +02:00
if (identical(type, "heatmap")) {
mapping <- rename_aes_heatmap(mapping)
}
if (identical(type, "scatter") & is_sized(mapping)) {
type <- "bubble"
}
2019-02-14 16:37:40 +01:00
mapdata <- lapply(mapping, rlang::eval_tidy, data = data)
2019-02-18 20:29:34 +01:00
if (type %in% c("pie", "donut", "radialBar")) {
2019-02-14 18:33:28 +01:00
opts <- list(
chart = list(type = correct_type(type)),
series = list1(mapdata$y),
labels = list1(mapdata$x)
)
} else {
opts <- list(
chart = list(type = correct_type(type)),
2020-02-12 16:37:47 +01:00
series = make_series(mapdata, mapping, type, serie_name)
2019-02-14 18:33:28 +01:00
)
}
opts <- modifyList(opts, choose_config(type, mapdata))
2020-04-02 19:33:39 +02:00
ax <- apexchart(
2020-02-12 11:57:24 +01:00
ax_opts = opts,
width = width, height = height,
elementId = elementId,
2020-02-12 18:21:40 +01:00
auto_update = auto_update
2019-02-15 23:33:40 +01:00
)
2020-04-02 19:33:39 +02:00
if (inherits(mapdata$x, c("character", "Date", "POSIXt", "numeric", "integer"))) {
ax$x$xaxis <- list(
min = min(mapdata$x, na.rm = TRUE),
max = max(mapdata$x, na.rm = TRUE)
)
}
return(ax)
2019-02-14 15:50:58 +01:00
}
# Construct series
2020-02-12 16:37:47 +01:00
make_series <- function(mapdata, mapping, type = NULL, serie_name = NULL) {
if (identical(type, "timeline")) {
if (!all(c("x", "start", "end") %in% names(mapping)))
stop("For timeline charts 'x', 'start', and 'end' aesthetice must be provided.", call. = FALSE)
if (is.null(mapdata$group))
mapdata$group <- serie_name %||% rlang::as_label(mapping$x)
series <- parse_timeline_data(mapdata)
2019-05-20 15:47:01 +02:00
} else {
mapdata <- as.data.frame(mapdata, stringsAsFactors = FALSE)
if (is.character(mapdata$x))
mapdata$x[is.na(mapdata$x)] <- "NA"
2020-02-12 16:37:47 +01:00
x_order <- unique(mapdata$x)
if (is_x_datetime(mapdata)) {
add_names <- FALSE
} else {
add_names <- names(mapping)
2020-01-14 11:09:24 +01:00
}
2020-02-12 16:37:47 +01:00
if (is.null(serie_name) & !is.null(mapping$y))
serie_name <- rlang::as_label(mapping$y)
series <- list(list(
name = serie_name,
data = parse_df(mapdata, add_names = add_names)
))
if (is_grouped(mapping)) {
2020-02-12 16:37:47 +01:00
mapdata <- rename_aes(mapdata)
len_grp <- tapply(mapdata$group, mapdata$group, length)
if (length(unique(len_grp)) > 1) {
warning("apex: all groups must have same length! You can use `tidyr::complete` for this.")
2019-02-14 15:50:58 +01:00
}
2020-02-12 16:37:47 +01:00
series <- lapply(
X = unique(mapdata$group),
FUN = function(x) {
data <- mapdata[mapdata$group %in% x, ]
data <- data[, setdiff(names(data), "group"), drop = FALSE]
data <- data[match(x = x_order, table = data$x, nomatch = 0L), , drop = FALSE]
list(
name = x,
data = parse_df(
data = data,
add_names = add_names
)
)
}
)
}
2019-02-14 15:50:58 +01:00
}
series
}
2019-02-18 20:29:34 +01:00
is_grouped <- function(x) {
any(c("colour", "fill", "group") %in% names(x))
}
is_sized <- function(x) {
any(c("size", "z") %in% names(x))
2019-02-18 20:29:34 +01:00
}
2019-07-19 14:11:41 +02:00
rename_aes_heatmap <- function(mapping) {
n_mapping <- names(mapping)
n_mapping[n_mapping == "y"] <- "group"
if ("fill" %in% n_mapping) {
n_mapping[n_mapping == "fill"] <- "y"
}
if ("colour" %in% n_mapping) {
n_mapping[n_mapping == "colour"] <- "y"
}
names(mapping) <- n_mapping
return(mapping)
}
2019-02-18 20:29:34 +01:00
rename_aes <- function(mapping) {
if ("colour" %in% names(mapping)) {
names(mapping)[names(mapping) == "colour"] <- "group"
}
if ("fill" %in% names(mapping)) {
names(mapping)[names(mapping) == "fill"] <- "group"
}
if ("size" %in% names(mapping)) {
names(mapping)[names(mapping) == "size"] <- "z"
}
2019-02-18 20:29:34 +01:00
mapping
}
2019-02-14 15:50:58 +01:00
2019-02-16 19:14:54 +01:00
is_x_datetime <- function(mapdata) {
2019-02-14 16:37:40 +01:00
inherits(mapdata$x, what = c("Date", "POSIXt"))
}
2019-02-14 18:33:28 +01:00
list1 <- function(x) {
if (length(x) == 1) {
list(x)
} else {
x
}
}
2019-02-14 15:50:58 +01:00
# Change type of charts for helpers type
correct_type <- function(type) {
if (identical(type, "column")) {
"bar"
2019-02-14 16:37:40 +01:00
} else if (identical(type, "spline")) {
"line"
2020-02-12 16:37:47 +01:00
} else if (identical(type, "timeline")) {
"rangeBar"
2019-02-14 15:50:58 +01:00
} else {
type
}
}
range_num <- function(x) {
if (is.numeric(x)) {
range(pretty(x))
} else {
NULL
}
}
2019-02-14 15:50:58 +01:00
# Switch between auto configs according to type & mapping
choose_config <- function(type, mapdata) {
datetime <- is_x_datetime(mapdata)
range_x <- range_num(mapdata$x)
range_y <- range_num(mapdata$y)
2019-02-14 15:50:58 +01:00
switch(
type,
"bar" = config_bar(horizontal = TRUE),
"column" = config_bar(horizontal = FALSE),
2019-02-14 16:37:40 +01:00
"line" = config_line(datetime = datetime),
"area" = config_line(datetime = datetime),
"spline" = config_line(curve = "smooth", datetime = datetime),
"scatter" = config_scatter(range_x = range_x, range_y = range_y),
"bubble" = config_scatter(range_x = range_x, range_y = range_y),
2020-02-12 16:37:47 +01:00
"timeline" = config_timeline(),
2019-02-14 15:50:58 +01:00
list()
)
}
# Config for column & bar charts
config_bar <- function(horizontal = FALSE) {
config <- list(
dataLabels = list(enabled = FALSE),
2019-02-14 15:50:58 +01:00
plotOptions = list(
bar = list(
horizontal = horizontal
)
)
)
if (isTRUE(horizontal)) {
config <- c(config, list(
grid = list(
yaxis = list(lines = list(show = FALSE)),
xaxis = list(lines = list(show = TRUE))
)
))
}
config
}
2019-02-14 16:37:40 +01:00
# Config for line, spline, area, area-spline
config_line <- function(curve = "straight", datetime = FALSE) {
config <- list(
dataLabels = list(enabled = FALSE),
2019-02-14 16:37:40 +01:00
stroke = list(
curve = curve,
width = 2
2019-02-14 16:37:40 +01:00
)
)
if (isTRUE(datetime)) {
config <- c(config, list(
xaxis = list(type = "datetime")
))
}
config
}
config_scatter <- function(range_x, range_y) {
config <- list(
dataLabels = list(enabled = FALSE),
xaxis = list(
2020-01-27 18:20:54 +01:00
type = "numeric",
min = range_x[1], max = range_x[2]
),
yaxis = list(
min = range_y[1], max = range_y[2]
2020-03-04 21:51:40 +01:00
),
grid = list(
xaxis = list(
lines = list(
show = TRUE
)
)
)
)
}
2020-02-12 16:37:47 +01:00
config_timeline <- function() {
list(
plotOptions = list(
bar = list(
horizontal = TRUE
)
),
xaxis = list(
type = "datetime"
)
)
}