apexcharter/R/apex.R

477 lines
13 KiB
R
Raw Permalink Normal View History

2019-02-14 15:50:58 +01:00
2020-10-05 09:44:14 +02:00
#' @title Quick ApexCharts
#'
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
2021-11-29 18:58:47 +01:00
#' a `data.frame`, it will be coerced to with `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:
2021-11-29 18:58:47 +01:00
#' `"column"`, `"bar"`,
#' `"line"`, `"step"`, `"spline"`,
#' `"area"`, `"area-step"`, `"area-spline"`,
#' `"pie"`, `"donut"`,
#' `"radialBar"`, `"radar"`, `"scatter"`,
#' `"heatmap"`, `"treemap"`,
2024-05-13 11:20:25 +02:00
#' `"timeline"`, `"dumbbell"` and `"slope"`.
2019-02-14 15:50:58 +01:00
#' @param ... Other arguments passed on to methods. Not currently used.
2020-04-15 19:32:15 +02:00
#' @param synchronize Give a common id to charts to synchronize them (tooltip and zoom).
2020-02-12 16:37:47 +01:00
#' @param serie_name Name for the serie displayed in tooltip,
#' only used for single serie.
2021-11-29 18:58:47 +01:00
#' @inheritParams apexchart
#'
2021-11-29 18:58:47 +01:00
#' @return An [apexchart()] `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
#' @importFrom stats complete.cases
2019-02-14 15:50:58 +01:00
#'
2019-11-26 11:26:47 +01:00
#' @example examples/apex.R
2021-11-29 18:58:47 +01:00
apex <- function(data, mapping,
type = "column",
...,
2020-02-12 18:21:40 +01:00
auto_update = TRUE,
2020-04-15 19:32:15 +02:00
synchronize = NULL,
2020-02-12 16:37:47 +01:00
serie_name = NULL,
2020-04-16 16:42:34 +02:00
width = NULL,
height = NULL,
2020-04-16 16:42:34 +02:00
elementId = NULL) {
2020-02-12 16:37:47 +01:00
type <- match.arg(
arg = type,
2020-02-12 16:37:47 +01:00
choices = c(
"column", "bar",
2023-06-13 18:02:54 +02:00
"rangeBar", "dumbbell",
2024-05-13 11:20:25 +02:00
"line", "spline", "step", "slope",
"area", "area-spline", "area-step",
2022-10-25 22:20:14 +02:00
"rangeArea",
"pie", "donut",
"radialBar",
"radar",
2020-10-06 09:50:27 +02:00
"polarArea",
"scatter", "bubble",
"heatmap",
"treemap",
"timeline",
2023-02-22 10:45:29 +01:00
"candlestick",
"boxplot"
2020-02-12 16:37:47 +01:00
)
)
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)
2020-12-31 09:46:32 +01:00
} else {
mapping <- rename_aes(mapping)
2019-07-19 14:11:41 +02:00
}
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)
2024-05-13 11:20:25 +02:00
type_no_compute <- c("candlestick", "boxplot", "timeline", "heatmap", "rangeArea", "rangeBar", "dumbbell", "slope")
2023-06-13 18:02:54 +02:00
if (is.null(mapdata$y) & !type %in% type_no_compute) {
2020-12-31 09:46:32 +01:00
mapdata <- compute_count(mapdata)
}
2020-10-06 09:50:27 +02:00
if (type %in% c("pie", "donut", "radialBar", "polarArea")) {
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(
2020-04-15 19:32:15 +02:00
chart = dropNulls(list(
type = correct_type(type),
2020-04-15 19:32:15 +02:00
group = synchronize
)),
2020-02-12 16:37:47 +01:00
series = make_series(mapdata, mapping, type, serie_name)
2019-02-14 18:33:28 +01:00
)
}
2020-04-15 19:32:15 +02:00
if (!is.null(synchronize)) {
opts$yaxis$labels$minWidth <- 15
}
opts <- modifyList(opts, choose_config(type, mapdata))
2020-04-29 11:35:06 +02:00
if (isTRUE(getOption("apex.axis.light", default = TRUE))) {
opts$yaxis$labels$style$colors <- "#848484"
opts$xaxis$labels$style$colors <- "#848484"
}
2020-04-02 19:33:39 +02:00
ax <- apexchart(
ax_opts = opts,
width = width,
2020-04-17 20:21:57 +02:00
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-05-27 11:42:42 +02:00
if (inherits(mapdata$x, c("character", "Date", "POSIXt", "numeric", "integer")) & length(mapdata$x) > 0) {
2020-04-02 19:33:39 +02:00
ax$x$xaxis <- list(
min = min(mapdata$x, na.rm = TRUE),
max = max(mapdata$x, na.rm = TRUE)
)
}
2020-07-26 10:46:18 +02:00
ax$x$data <- data
2020-07-26 18:38:18 +02:00
ax$x$mapping <- mapping
2020-12-02 15:50:03 +01:00
ax$x$type <- type
ax$x$serie_name <- serie_name
2020-07-26 10:46:18 +02:00
class(ax) <- c(class(ax), "apex")
2020-04-02 19:33:39 +02:00
return(ax)
2019-02-14 15:50:58 +01:00
}
# Construct series
2021-11-17 11:45:05 +01:00
#' @importFrom rlang %||%
2020-12-16 14:12:57 +01:00
make_series <- function(mapdata, mapping, type = NULL, serie_name = NULL, force_datetime_names = FALSE) {
2023-02-22 10:45:29 +01:00
if (identical(type, "boxplot")) {
series <- parse_boxplot_data(mapdata, serie_name = serie_name)
} else if (identical(type, "candlestick")) {
2020-06-13 12:18:02 +02:00
if (!all(c("x", "open", "high", "low", "close") %in% names(mapping)))
stop("For candlestick charts 'x', 'open', 'high', 'low', and 'close' aesthetics must be provided.", call. = FALSE)
if (!is.null(mapdata$group))
warning("'group' aesthetic in candlestick chart is not supported", call. = FALSE)
mapdata$group <- NULL
series <- parse_candlestick_data(mapdata)
2020-12-16 14:39:10 +01:00
} else if (isTRUE(type %in% c("rangeBar", "timeline"))) {
2020-02-12 16:37:47 +01:00
if (!all(c("x", "start", "end") %in% names(mapping)))
2020-06-13 12:18:02 +02:00
stop("For timeline charts 'x', 'start', and 'end' aesthetics must be provided.", call. = FALSE)
2020-02-12 16:37:47 +01:00
if (is.null(mapdata$group))
mapdata$group <- serie_name %||% rlang::as_label(mapping$x)
series <- parse_timeline_data(mapdata)
2023-06-13 18:02:54 +02:00
} else if (isTRUE(type %in% c("dumbbell"))) {
if (!all(c("y", "x", "xend") %in% names(mapping)))
stop("For dumbbell charts 'x', 'xend', and 'y' aesthetics must be provided.", call. = FALSE)
if (is.null(mapdata$group))
mapdata$group <- serie_name %||% rlang::as_label(mapping$x)
series <- parse_dumbbell_data(mapdata)
2019-05-20 15:47:01 +02:00
} else {
mapdata <- as.data.frame(mapdata, stringsAsFactors = FALSE)
2022-10-25 22:20:14 +02:00
if (all(rlang::has_name(mapdata, c("ymin", "ymax")))) {
mapdata$y <- lapply(
X = seq_len(nrow(mapdata)),
FUN = function(i) {
list(mapdata$ymin[i], mapdata$ymax[i])
}
)
mapdata$ymin <- mapdata$ymax <- NULL
}
if (isTRUE(type %in% c("scatter", "bubble"))) {
complete <- complete.cases(mapdata[c("x", "y")])
n_missing <- sum(!complete)
if (n_missing > 0) {
mapdata <- mapdata[complete, ]
warning(sprintf("apex: Removed %s rows containing missing values", n_missing), call. = 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)
2022-10-25 22:20:14 +02:00
if (is_x_datetime(mapdata) & !identical(type, "rangeArea")) {
2020-12-16 14:12:57 +01:00
add_names <- force_datetime_names
2020-06-09 17:03:35 +02:00
x_order <- sort(x_order)
2020-02-12 16:37:47 +01:00
} else {
2020-12-31 09:46:32 +01:00
add_names <- names(mapdata)
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)
2020-04-29 11:35:06 +02:00
series <- list(dropNulls(list(
2021-07-23 10:35:05 +02:00
name = as.character(serie_name),
2020-04-29 11:35:06 +02:00
type = multi_type(type),
2020-02-12 16:37:47 +01:00
data = parse_df(mapdata, add_names = add_names)
2020-04-29 11:35:06 +02:00
)))
if (is_grouped(mapping)) {
2020-02-12 16:37:47 +01:00
mapdata <- rename_aes(mapdata)
2024-05-13 11:20:25 +02:00
len_grp <- tapply(as.character(mapdata$group), as.character(mapdata$group), length)
2020-04-29 11:35:06 +02:00
if (length(unique(len_grp)) > 1 & !isTRUE(type %in% c("scatter", "bubble"))) {
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[order(match(x = data[["x"]], table = x_order, nomatch = 0L)), , drop = FALSE]
2020-04-29 11:35:06 +02:00
dropNulls(list(
2021-07-23 10:35:05 +02:00
name = as.character(x),
2020-04-29 11:35:06 +02:00
type = multi_type(type),
2020-02-12 16:37:47 +01:00
data = parse_df(
data = data,
2020-02-12 16:37:47 +01:00
add_names = add_names
)
2020-04-29 11:35:06 +02:00
))
2020-02-12 16:37:47 +01:00
}
)
}
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
}
2023-08-23 10:42:59 +02:00
#' @importFrom rlang quo
2019-07-19 14:11:41 +02:00
rename_aes_heatmap <- function(mapping) {
2023-08-23 10:42:59 +02:00
if (is.null(mapping["x"]))
stop("apex(..., type = 'heatmap') must have an 'x' aesthetic", call. = FALSE)
mapping[["x"]] <- quo(as.character(!!mapping[["x"]]))
2019-07-19 14:11:41 +02:00
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) {
2023-06-13 18:02:54 +02:00
if (isTRUE(type %in% c("column"))) {
2019-02-14 15:50:58 +01:00
"bar"
2024-05-13 11:20:25 +02:00
} else if (isTRUE(type %in% c("spline", "step", "slope"))) {
2019-02-14 16:37:40 +01:00
"line"
2020-04-17 20:21:57 +02:00
} else if (isTRUE(type %in% c("area-spline", "area-step"))) {
"area"
2023-06-13 18:02:54 +02:00
} else if (isTRUE(type %in% c("timeline", "dumbbell"))) {
2020-02-12 16:37:47 +01:00
"rangeBar"
2023-02-22 10:45:29 +01:00
} else if (identical(type, "boxplot")) {
"boxPlot"
2019-02-14 15:50:58 +01:00
} else {
type
}
}
2020-04-29 11:35:06 +02:00
multi_type <- function(x) {
multis <- c("column", "area", "line",
"spline", "step", "scatter",
2022-10-25 22:20:14 +02:00
"bubble", "rangeArea")
2020-04-29 11:35:06 +02:00
if (isTRUE(x %in% multis)) {
2020-04-29 18:24:39 +02:00
correct_type(x)
2020-04-29 11:35:06 +02:00
} else {
NULL
}
}
range_num <- function(x) {
2020-05-27 11:42:42 +02:00
if (is.numeric(x) & length(x) > 0) {
p <- pretty(x)
list(
values = p,
n = length(p) - 1,
range = range(p)
)
} else {
NULL
}
}
2021-11-17 11:45:05 +01:00
#' @importFrom rlang %||%
2020-12-31 09:46:32 +01:00
compute_count <- function(mapdata) {
if (!is_grouped(mapdata)) {
x <- mapdata$x
weight <- mapdata$weight %||% rep(1, length(x))
count <- tapply(weight, x, sum, na.rm = TRUE, simplify = FALSE)
mapdata$x <- names(count)
mapdata$y <- as.numeric(count)
} else {
weight <- mapdata$weight %||% rep(1, length(mapdata$x))
count <- tapply(weight, mapdata[c("x", "group")], sum, na.rm = TRUE, simplify = FALSE)
mapdata$x <- rep(rownames(count), ncol(count))
mapdata$y <- unlist(count, use.names = FALSE)
mapdata$group <- rep(colnames(count), each = nrow(count))
}
mapdata$y[is.na(mapdata$y)] <- 0
return(mapdata)
}
# Configs ----
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)
2023-02-22 10:45:29 +01:00
if (identical(type, "boxplot")) {
box_horiz <- !is.numeric(mapdata$y) & is.numeric(mapdata$x)
}
2019-02-14 15:50:58 +01:00
switch(
type,
2019-02-14 15:50:58 +01:00
"bar" = config_bar(horizontal = TRUE),
2023-06-13 18:02:54 +02:00
"dumbbell" = config_bar(horizontal = TRUE, isDumbbell = TRUE),
2020-04-17 08:57:23 +02:00
"column" = config_bar(horizontal = FALSE, datetime = datetime),
2019-02-14 16:37:40 +01:00
"line" = config_line(datetime = datetime),
"area" = config_line(datetime = datetime),
2022-10-25 22:20:14 +02:00
"rangeArea" = config_line(datetime = datetime),
2019-02-14 16:37:40 +01:00
"spline" = config_line(curve = "smooth", datetime = datetime),
2020-04-17 20:21:57 +02:00
"step" = config_line(curve = "stepline", datetime = datetime),
"area-spline" = config_line(curve = "smooth", datetime = datetime),
"area-step" = config_line(curve = "stepline", datetime = datetime),
2020-04-17 08:57:23 +02:00
"scatter" = config_scatter(range_x = range_x, range_y = range_y, datetime = datetime),
"bubble" = config_scatter(range_x = range_x, range_y = range_y, datetime = datetime),
2020-02-12 16:37:47 +01:00
"timeline" = config_timeline(),
2020-06-13 12:18:02 +02:00
"candlestick" = config_candlestick(),
2023-02-22 10:45:29 +01:00
"boxplot" = config_boxplot(horizontal = box_horiz),
2024-05-13 11:20:25 +02:00
"slope" = config_slope(),
2019-02-14 15:50:58 +01:00
list()
)
}
# Config for column & bar charts
2023-06-13 18:02:54 +02:00
config_bar <- function(horizontal = FALSE, datetime = FALSE, isDumbbell = FALSE) {
2019-02-14 15:50:58 +01:00
config <- list(
dataLabels = list(enabled = FALSE),
2019-02-14 15:50:58 +01:00
plotOptions = list(
bar = list(
2023-06-13 18:02:54 +02:00
horizontal = horizontal,
isDumbbell = isDumbbell
2019-02-14 15:50:58 +01:00
)
2020-04-17 08:57:23 +02:00
),
tooltip = list(
shared = TRUE,
intersect = FALSE,
2020-04-17 16:46:34 +02:00
followCursor = TRUE
2023-02-22 10:52:04 +01:00
),
grid = list(
yaxis = list(lines = list(show = !isTRUE(horizontal))),
xaxis = list(lines = list(show = isTRUE(horizontal)))
2019-02-14 15:50:58 +01:00
)
)
2020-04-17 08:57:23 +02:00
if (isTRUE(datetime)) {
config$xaxis$type <- "datetime"
}
2019-02-14 15:50:58 +01:00
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
),
2020-04-29 18:24:39 +02:00
yaxis = list(
decimalsInFloat = 2
2019-02-14 16:37:40 +01:00
)
)
if (isTRUE(datetime)) {
config <- c(config, list(
xaxis = list(type = "datetime")
))
}
config
}
2020-04-17 08:57:23 +02:00
config_scatter <- function(range_x, range_y, datetime = FALSE) {
config <- list(
dataLabels = list(enabled = FALSE),
xaxis = list(
2020-01-27 18:20:54 +01:00
type = "numeric",
min = range_x$range[1],
max = range_x$range[2],
tickAmount = range_x$n,
# labels = list(formatter = format_num("~r")),
2020-04-17 08:57:23 +02:00
crosshairs = list(
show = TRUE,
stroke = list(dashArray = 0)
)
),
yaxis = list(
min = range_y$range[1],
max = range_y$range[2],
tickAmount = range_y$n,
labels = list(formatter = format_num("~r")),
2020-04-17 08:57:23 +02:00
tooltip = list(
enabled = TRUE
)
2020-03-04 21:51:40 +01:00
),
grid = list(
xaxis = list(
lines = list(
show = TRUE
)
)
)
)
2020-04-17 08:57:23 +02:00
if (isTRUE(datetime)) {
config$xaxis$type <- "datetime"
}
config
}
2020-02-12 16:37:47 +01:00
config_timeline <- function() {
list(
plotOptions = list(
bar = list(
horizontal = TRUE
)
),
xaxis = list(
type = "datetime"
)
)
}
2020-06-13 12:18:02 +02:00
config_candlestick <- function() {
list(
xaxis = list(
type = "datetime"
)
)
}
2023-02-22 10:45:29 +01:00
config_boxplot <- function(horizontal = FALSE) {
list(
plotOptions = list(
bar = list(
horizontal = horizontal
)
)
)
}
2024-05-13 11:20:25 +02:00
config_slope <- function() {
list(
plotOptions = list(
line = list(
isSlopeChart = TRUE
)
)
)
}