plots: Use branded colors

This commit is contained in:
Elias Projahn 2022-12-16 11:31:30 +01:00
parent 588bf61673
commit 373238b4bc

View file

@ -18,6 +18,7 @@ overview_plot <- function(ranked_data,
)], )],
x = ~percentile, x = ~percentile,
y = ~score, y = ~score,
line = list(color = base_color()),
hoverinfo = "skip" hoverinfo = "skip"
) |> ) |>
plotly::layout( plotly::layout(
@ -54,6 +55,7 @@ overview_plot <- function(ranked_data,
"Rank: {rank}<br>", "Rank: {rank}<br>",
"Percentile: {round(percentile * 100, digits = 2)}%" "Percentile: {round(percentile * 100, digits = 2)}%"
), ),
marker = list(color = highlight_color()),
hoverinfo = "text", hoverinfo = "text",
showlegend = FALSE showlegend = FALSE
) )
@ -71,23 +73,33 @@ overview_plot <- function(ranked_data,
#' #'
#' @export #' @export
box_plot <- function(ranked_data, highlighted_genes) { box_plot <- function(ranked_data, highlighted_genes) {
data <- data.table::copy(ranked_data) fig <- plotly::plot_ly() |>
data[, group := data.table::fifelse(
gene %chin% highlighted_genes,
"Your genes",
"Other genes"
)]
plotly::plot_ly() |>
plotly::add_boxplot( plotly::add_boxplot(
data = data, data = ranked_data[!gene %chin% highlighted_genes],
x = ~score, x = ~score,
y = ~group, y = "Other genes",
line = list(color = base_color()),
fillcolor = transparent(base_color()),
showlegend = FALSE,
boxpoints = FALSE boxpoints = FALSE
) |> plotly::layout(
xaxis = list(title = "Score"),
yaxis = list(title = "")
) )
if (length(highlighted_genes) >= 1) {
fig <- fig |> plotly::add_boxplot(
data = ranked_data[gene %chin% highlighted_genes],
x = ~score,
y = "Your genes",
line = list(color = highlight_color()),
fillcolor = transparent(highlight_color()),
showlegend = FALSE,
boxpoints = FALSE
)
}
fig |> plotly::layout(
xaxis = list(title = "Score"),
yaxis = list(title = "")
)
} }
#' Create plot showing the distribution of scores using `plotly`. #' Create plot showing the distribution of scores using `plotly`.
@ -98,7 +110,7 @@ box_plot <- function(ranked_data, highlighted_genes) {
#' `NULL`, all ranks will be shown. #' `NULL`, all ranks will be shown.
#' #'
#' @return A `plotly` figure for rendering. #' @return A `plotly` figure for rendering.
#' #'
#' @export #' @export
scores_plot <- function(ranked_data, highlighted_genes = NULL, ranks = 1000) { scores_plot <- function(ranked_data, highlighted_genes = NULL, ranks = 1000) {
data <- if (is.null(ranks)) { data <- if (is.null(ranks)) {
@ -119,6 +131,21 @@ scores_plot <- function(ranked_data, highlighted_genes = NULL, ranks = 1000) {
"All genes" "All genes"
)] )]
data[, color := data.table::fifelse(
gene %chin% highlighted_genes,
highlight_color(),
base_color()
)]
data[, size := data.table::fifelse(
gene %chin% highlighted_genes,
8,
4
)]
# Draw "Your genes" on top of "All genes".
setorder(data, group)
plotly::plot_ly() |> plotly::plot_ly() |>
plotly::add_markers( plotly::add_markers(
data = data, data = data,
@ -131,6 +158,12 @@ scores_plot <- function(ranked_data, highlighted_genes = NULL, ranks = 1000) {
"Rank: {rank}<br>", "Rank: {rank}<br>",
"Percentile: {round(percentile * 100, digits = 2)}%" "Percentile: {round(percentile * 100, digits = 2)}%"
), ),
marker = ~ list(
color = color,
size = size,
opacity = 1,
line = list(width = 0)
),
hoverinfo = "text", hoverinfo = "text",
showlegend = FALSE showlegend = FALSE
) |> ) |>
@ -180,3 +213,17 @@ vlineannotation <- function(x) {
) )
) )
} }
#' Base color for plots.
#' @noRd
base_color <- function() "#7d19bf"
#' Highlight color for plots.
#' @noRd
highlight_color <- function() "#ff7f2a"
#' Return the half-transparent version of the color.
#' @noRd
transparent <- function(color) {
paste0(color, "80")
}