apexcharter/R/parse-data.R

195 lines
4.3 KiB
R
Raw Normal View History

2018-09-03 23:52:53 +02:00
#' @title Convert a \code{data.frame} to a \code{list}
#'
#' @description Convert data to a format suitable for ApexCharts.js
#'
#' @param data A \code{data.frame} or an object coercible to \code{data.frame}.
2018-12-18 18:02:09 +01:00
#' @param add_names Use names of columns in output. Can be logical to
#' reuse \code{data} names or a character vector of new names.
2019-07-24 12:20:22 +02:00
#'
#' @return A \code{list} that can be used to specify data in \code{\link{ax_series}} for example.
2018-09-03 23:52:53 +02:00
#'
#' @export
2018-12-18 18:02:09 +01:00
#' @importFrom stats setNames
2019-07-24 12:20:22 +02:00
#'
#' @examples
#'
#' # All iris dataset
#' parse_df(iris)
#'
#' # Keep variables names
#' parse_df(iris[, 1:2], add_names = TRUE)
#'
#' # Use custom names
#'
#' parse_df(iris[, 1:2], add_names = c("x", "y"))
2018-09-03 23:52:53 +02:00
#'
2018-12-18 18:02:09 +01:00
parse_df <- function(data, add_names = FALSE) {
2018-09-03 23:52:53 +02:00
data <- as.data.frame(data)
2018-12-18 18:02:09 +01:00
names_ <- names(data)
2018-09-03 23:52:53 +02:00
l <- lapply(
X = data[],
FUN = function(x) {
if (inherits(x, "Date")) {
2020-12-16 14:12:57 +01:00
# js_date(x)
as.numeric(x) * 1000 * 60*60*24
2019-02-15 23:06:11 +01:00
} else if (inherits(x, "POSIXt")) {
2020-12-16 14:12:57 +01:00
# js_date(x)
as.numeric(x) * 1000
2018-09-03 23:52:53 +02:00
} else if (inherits(x, "factor")) {
as.character(x)
} else {
2019-02-14 17:40:03 +01:00
# if (!identical(add_names, FALSE)) {
# formatNoSci(x)
# } else {
# x
# }
x
2018-09-03 23:52:53 +02:00
}
}
)
2019-02-14 15:50:58 +01:00
ll <- lapply(
X = seq_len(nrow(data)),
FUN = function(i) {
res <- lapply(l, `[[`, i)
if (identical(add_names, FALSE)) {
res <- unname(res)
}
if (is.character(add_names) & length(add_names) == length(names_)) {
res <- setNames(res, nm = add_names)
}
return(res)
}
)
2018-12-18 18:02:09 +01:00
return(ll)
2018-09-03 23:52:53 +02:00
}
2020-02-12 16:37:47 +01:00
#' @importFrom htmlwidgets JS
js_date <- function(x) {
2020-06-13 12:18:02 +02:00
if (inherits(x, "POSIXt"))
x <- format(x, format = "%Y-%m-%d %H:%M:%S")
2020-02-14 17:25:52 +01:00
lapply(sprintf("new Date('%s').getTime()", x), JS)
2020-02-12 16:37:47 +01:00
}
parse_timeline_data <- function(.list) {
if (is.null(.list$group)) {
lapply(
X = seq_len(length(.list[[1]])),
FUN = function(i) {
val <- lapply(.list, `[[`, i)
l <- list(
2020-03-19 10:00:35 +01:00
x = as.character(val$x),
2020-02-14 17:25:52 +01:00
y = js_date(c(val$start, val$end))
2020-02-12 16:37:47 +01:00
)
if (!is.null(val$fill)) {
l$fillColor <- val$fill
}
l
}
)
} else {
grouped <- as.data.frame(.list, stringsAsFactors = FALSE)
grouped$group <- NULL
grouped <- split(
x = grouped,
f = .list$group
)
grouped <- lapply(grouped, as.list)
lapply(
X = names(grouped),
FUN = function(name) {
list(
name = name,
data = parse_timeline_data(grouped[[name]])
)
}
)
}
}
2023-06-13 18:01:21 +02:00
parse_dumbbell_data <- function(.list) {
if (is.null(.list$group)) {
lapply(
X = seq_len(length(.list[[1]])),
FUN = function(i) {
val <- lapply(.list, `[[`, i)
l <- list(
x = as.character(val$y),
y = list(val$x, val$xend)
)
if (!is.null(val$fill)) {
l$fillColor <- val$fill
}
l
}
)
} else {
grouped <- as.data.frame(.list, stringsAsFactors = FALSE)
grouped$group <- NULL
grouped <- split(
x = grouped,
f = .list$group
)
grouped <- lapply(grouped, as.list)
lapply(
X = names(grouped),
FUN = function(name) {
list(
name = name,
data = parse_dumbbell_data(grouped[[name]])
)
}
)
}
}
2020-06-13 12:18:02 +02:00
parse_candlestick_data <- function(.list) {
list(list(
2020-12-15 19:14:25 +01:00
type = "candlestick",
2020-06-13 12:18:02 +02:00
data = lapply(
X = seq_len(length(.list[[1]])),
FUN = function(i) {
val <- lapply(.list, `[[`, i)
list(
2020-12-16 14:12:57 +01:00
# x = js_date(val$x)[[1]],
x = as.numeric(val$x) * 1000,
2020-06-13 12:18:02 +02:00
y = c(val$open, val$high, val$low, val$close)
)
}
)
))
}
2020-02-12 16:37:47 +01:00
2023-02-22 10:45:29 +01:00
2023-02-22 10:49:40 +01:00
#' @importFrom graphics boxplot
2023-02-22 10:45:29 +01:00
parse_boxplot_data <- function(.list, serie_name = NULL) {
if (!is.numeric(.list$y) & is.numeric(.list$x)) {
.list[c("x", "y")] <- .list[c("y", "x")]
}
boxed <- boxplot(y ~ x, data = .list, plot = FALSE)
list(dropNulls(list(
serie_name = serie_name,
type = "boxPlot",
data = lapply(
X = seq_along(boxed$names),
FUN = function(i) {
list(
x = boxed$names[i],
y = c(
boxed$stats[1, i],
boxed$stats[2, i],
boxed$stats[3, i],
boxed$stats[4, i],
boxed$stats[5, i]
)
)
}
)
)))
}