Skip to content

Commit

Permalink
Rename arg to follow color_* pattern
Browse files Browse the repository at this point in the history
  • Loading branch information
IndrajeetPatil committed Nov 19, 2024
1 parent cb8ccb9 commit 14238e0
Show file tree
Hide file tree
Showing 16 changed files with 71 additions and 71 deletions.
6 changes: 3 additions & 3 deletions R/plot.bayesfactor_parameters.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@
#'
#' @param size_point Numeric specifying size of point-geoms.
#' @param rope_alpha Numeric specifying transparency level of ROPE ribbon.
#' @param rope_color Character specifying color of ROPE ribbon.
#' @param color_rope Character specifying color of ROPE ribbon.
#' @param show_intercept Logical, if `TRUE`, the intercept-parameter is included
#' in the plot. By default, it is hidden because in many cases the
#' intercept-parameter has a posterior distribution on a very different
Expand All @@ -19,7 +19,7 @@
#' @export
plot.see_bayesfactor_parameters <- function(x,
size_point = 2,
rope_color = "#0171D3",
color_rope = "#0171D3",
rope_alpha = 0.2,
show_intercept = FALSE,
...) {
Expand Down Expand Up @@ -80,7 +80,7 @@ plot.see_bayesfactor_parameters <- function(x,
xmax = rope[2],
ymin = 0,
ymax = Inf,
fill = rope_color,
fill = color_rope,
alpha = rope_alpha
)
} else {
Expand Down
38 changes: 19 additions & 19 deletions R/plot.describe_distribution.R
Original file line number Diff line number Diff line change
Expand Up @@ -35,12 +35,12 @@ data_plot.parameters_distribution <- function(x, data = NULL, ...) {
#' @param dispersion Logical. If `TRUE`, a range of dispersion for
#' each variable to the plot will be added.
#' @param dispersion_alpha Numeric value specifying the transparency level of dispersion ribbon.
#' @param dispersion_color Character specifying the color of dispersion ribbon.
#' @param color_dispersion Character specifying the color of dispersion ribbon.
#' @param dispersion_style Character describing the style of dispersion area.
#' `"ribbon"` for a ribbon, `"curve"` for a normal-curve.
#' @param highlight A vector with names of categories in `x` that should be
#' highlighted.
#' @param highlight_color A vector of color values for highlighted categories.
#' @param color_highlight A vector of color values for highlighted categories.
#' The remaining (non-highlighted) categories will be filled with a lighter
#' grey.
#' @param size_bar Size of bar geoms.
Expand All @@ -60,11 +60,11 @@ data_plot.parameters_distribution <- function(x, data = NULL, ...) {
plot.see_parameters_distribution <- function(x,
dispersion = FALSE,
dispersion_alpha = 0.3,
dispersion_color = "#3498db",
color_dispersion = "#3498db",
dispersion_style = c("ribbon", "curve"),
size_bar = 0.7,
highlight = NULL,
highlight_color = NULL,
color_highlight = NULL,
...) {
# get data
data <- .retrieve_data(x)

Check warning on line 70 in R/plot.describe_distribution.R

View workflow job for this annotation

GitHub Actions / lint-changed-files / lint-changed-files

file=R/plot.describe_distribution.R,line=70,col=3,[object_overwrite_linter] 'data' is an exported object from package 'utils'. Avoid re-using such symbols.
Expand All @@ -85,23 +85,23 @@ plot.see_parameters_distribution <- function(x,
x,
.plot_see_parameters_distribution,
dispersion_alpha,
dispersion_color,
color_dispersion,
dispersion_style,
show_dispersion = dispersion,
size_bar = size_bar,
highlight = highlight,
highlight_color = highlight_color
color_highlight = color_highlight
)
} else {
.plot_see_parameters_distribution(
x,
dispersion_alpha,
dispersion_color,
color_dispersion,
dispersion_style,
show_dispersion = dispersion,
size_bar = size_bar,
highlight = highlight,
highlight_color = highlight_color
color_highlight = color_highlight
)
}
}
Expand All @@ -110,12 +110,12 @@ plot.see_parameters_distribution <- function(x,

.plot_see_parameters_distribution <- function(x,
dispersion_alpha,
dispersion_color,
color_dispersion,
dispersion_style,
show_dispersion,
size_bar,
highlight,
highlight_color) {
color_highlight) {
centrality <- attributes(x)$centrality
dispersion <- attributes(x)$dispersion

Expand Down Expand Up @@ -158,7 +158,7 @@ plot.see_parameters_distribution <- function(x,
if (dispersion_style == "ribbon") {
p <- p + geom_vline(
xintercept = centrality,
colour = dispersion_color,
colour = color_dispersion,
alpha = dispersion_alpha
)
}
Expand All @@ -169,7 +169,7 @@ plot.see_parameters_distribution <- function(x,
geom_vline(
xintercept = .range,
linetype = "dashed",
colour = dispersion_color,
colour = color_dispersion,
alpha = dispersion_alpha
) +
annotate(
Expand All @@ -178,31 +178,31 @@ plot.see_parameters_distribution <- function(x,
xmax = .range[2],
ymin = 0,
ymax = Inf,
fill = dispersion_color,
fill = color_dispersion,
alpha = (dispersion_alpha / 3)
)
} else {
p <- p +
geom_ribbon(
aes(ymin = 0, ymax = .data$curve_y),
alpha = dispersion_alpha,
fill = dispersion_color,
fill = color_dispersion,
colour = NA
)
}
}
}

if (!is.null(x$highlight)) {
if (is.null(highlight_color)) {
highlight_color <- palette_material("full")(insight::n_unique(x$highlight) - 1L)
if (is.null(color_highlight)) {
color_highlight <- palette_material("full")(insight::n_unique(x$highlight) - 1L)
}

names(highlight_color) <- highlight
highlight_color <- c(highlight_color, no_highlight = "grey70")
names(color_highlight) <- highlight
color_highlight <- c(color_highlight, no_highlight = "grey70")

p <- p +
scale_fill_manual(values = highlight_color) +
scale_fill_manual(values = color_highlight) +
guides(fill = "none")
}

Expand Down
12 changes: 6 additions & 6 deletions R/plot.dw_data_tabulate.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@
#' If `TRUE`, confidence intervals computed using the Wilson method are shown.
#' See Brown et al. (2001) for details.
#' @param ci Confidence Interval (CI) level. Defaults to `0.95` (`95%`).
#' @param fill_col Color to use for category columns (default: `"#87CEFA"`).
#' @param color_fill Color to use for category columns (default: `"#87CEFA"`).
#' @param color_error_bar Color to use for error bars (default: `"#607B8B"`).
#' @param ... Unused
#'
Expand All @@ -29,7 +29,7 @@ plot.datawizard_tables <- function(x, label_values = TRUE,
na_label = "(Missing)",
error_bar = TRUE,
ci = 0.95,
fill_col = "#87CEFA",
color_fill = "#87CEFA",
color_error_bar = "#607B8B",
...) {
show_na <- match.arg(show_na, choices = c("if_any", "always", "never"))
Expand All @@ -41,7 +41,7 @@ plot.datawizard_tables <- function(x, label_values = TRUE,
na_label = na_label,
error_bar = error_bar,
ci = ci,
fill_col = fill_col,
color_fill = color_fill,
color_error_bar = color_error_bar
)
} else {
Expand All @@ -53,7 +53,7 @@ plot.datawizard_tables <- function(x, label_values = TRUE,
na_label = na_label,
error_bar = error_bar,
ci = ci,
fill_col = fill_col,
color_fill = color_fill,
color_error_bar = color_error_bar
)
}
Expand All @@ -68,7 +68,7 @@ plot.datawizard_table <- function(x, label_values = TRUE,
na_label = "(Missing)",
error_bar = TRUE,
ci = 0.95,
fill_col = "#87CEFA",
color_fill = "#87CEFA",
color_error_bar = "#607B8B",
...) {
show_na <- match.arg(show_na, choices = c("if_any", "always", "never"))
Expand Down Expand Up @@ -108,7 +108,7 @@ plot.datawizard_table <- function(x, label_values = TRUE,

out <- ggplot2::ggplot(dat) +
ggplot2::aes(x = .data$Value, y = .data$N) +
ggplot2::geom_col(fill = fill_col) +
ggplot2::geom_col(fill = color_fill) +
ggplot2::labs(title = unique(dat$Variable)) +
theme_modern()

Expand Down
24 changes: 12 additions & 12 deletions R/plot.equivalence_test.R
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@
#' plot(result)
#' @export
plot.see_equivalence_test <- function(x,
rope_color = "#0171D3",
color_rope = "#0171D3",
rope_alpha = 0.2,
show_intercept = FALSE,
n_columns = 1,
Expand Down Expand Up @@ -144,20 +144,20 @@ plot.see_equivalence_test <- function(x,
xmax = .rope[2],
ymin = 0,
ymax = Inf,
fill = rope_color,
fill = color_rope,
alpha = (rope_alpha / 3),
na.rm = TRUE
) +
geom_vline(
xintercept = .rope,
linetype = "dashed",
colour = rope_color,
colour = color_rope,
alpha = rope.line.alpha,
na.rm = TRUE
) +
geom_vline(
xintercept = 0,
colour = rope_color,
colour = color_rope,
linewidth = 0.8,
alpha = rope.line.alpha,
na.rm = TRUE
Expand Down Expand Up @@ -207,7 +207,7 @@ plot.see_equivalence_test <- function(x,

#' @export
plot.see_equivalence_test_df <- function(x,
rope_color = "#0171D3",
color_rope = "#0171D3",
rope_alpha = 0.2,
data = NULL,
n_columns = 1,
Expand Down Expand Up @@ -290,19 +290,19 @@ plot.see_equivalence_test_df <- function(x,
xmax = .rope[2],
ymin = 0,
ymax = Inf,
fill = rope_color,
fill = color_rope,
alpha = (rope_alpha / 3)
) +
geom_vline(
xintercept = .rope,
linetype = "dashed",
colour = rope_color,
colour = color_rope,
alpha = rope.line.alpha,
na.rm = TRUE
) +
geom_vline(
xintercept = 0,
colour = rope_color,
colour = color_rope,
linewidth = 0.8,
alpha = rope.line.alpha,
na.rm = TRUE
Expand Down Expand Up @@ -333,7 +333,7 @@ plot.see_equivalence_test_df <- function(x,
#' @export
plot.see_equivalence_test_lm <- function(x,
size_point = 0.7,
rope_color = "#0171D3",
color_rope = "#0171D3",
rope_alpha = 0.2,
show_intercept = FALSE,
n_columns = 1,
Expand Down Expand Up @@ -412,20 +412,20 @@ plot.see_equivalence_test_lm <- function(x,
xmax = .rope[2],
ymin = 0,
ymax = Inf,
fill = rope_color,
fill = color_rope,
alpha = (rope_alpha / 3)
) +
geom_vline(
xintercept = .rope,
linetype = "dashed",
colour = rope_color,
colour = color_rope,
linewidth = 0.8,
alpha = rope.line.alpha,
na.rm = TRUE
) +
geom_vline(
xintercept = 0,
colour = rope_color,
colour = color_rope,
linewidth = 0.8,
alpha = rope.line.alpha,
na.rm = TRUE
Expand Down
4 changes: 2 additions & 2 deletions R/plot.parameters_brms_meta.R
Original file line number Diff line number Diff line change
Expand Up @@ -144,7 +144,7 @@ plot.see_parameters_brms_meta <- function(x,
size_text = 3.5,
posteriors_alpha = 0.7,
rope_alpha = 0.15,
rope_color = "cadetblue",
color_rope = "cadetblue",
normalize_height = TRUE,
show_labels = TRUE,
...) {
Expand Down Expand Up @@ -175,7 +175,7 @@ plot.see_parameters_brms_meta <- function(x,
xmax = rope[2],
ymin = 0,
ymax = Inf,
fill = rope_color,
fill = color_rope,
alpha = rope_alpha
)
}
Expand Down
6 changes: 3 additions & 3 deletions R/plot.parameters_pca.R
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ data_plot.parameters_efa <- data_plot.parameters_pca
#' Options are three different shapes to represent component loadings;
#' `"bar"` (default) for a horizontal bar chart, or
#' `"line"` for a horizontal point and line chart.
#' @param text_color Character specifying color of text labels.
#' @param color_text Character specifying color of text labels.
#' @inheritParams data_plot
#' @inheritParams plot.see_bayesfactor_parameters
#' @inheritParams plot.see_check_outliers
Expand All @@ -80,7 +80,7 @@ data_plot.parameters_efa <- data_plot.parameters_pca
plot.see_parameters_pca <- function(x,
type = c("bar", "line"),
size_text = 3.5,
text_color = "black",
color_text = "black",
size = 1,
show_labels = TRUE,
...) {
Expand Down Expand Up @@ -123,7 +123,7 @@ plot.see_parameters_pca <- function(x,
p <- p +
geom_text(
aes(x = abs(.data$y), label = round(.data$y, 2)),
color = text_color,
color = color_text,
size = size_text,
nudge_y = 0.15
)
Expand Down
4 changes: 2 additions & 2 deletions R/plot.rope.R
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,7 @@ data_plot.rope <- function(x, data = NULL, show_intercept = FALSE, ...) {
plot.see_rope <- function(x,
data = NULL,
rope_alpha = 0.5,
rope_color = "cadetblue",
color_rope = "cadetblue",
show_intercept = FALSE,
n_columns = 1,
...) {
Expand Down Expand Up @@ -122,7 +122,7 @@ plot.see_rope <- function(x,
xmax = attributes(x)$info$rope_range[2],
ymin = 0,
ymax = Inf,
fill = rope_color,
fill = color_rope,
alpha = rope_alpha
) +
add_plot_attributes(x)
Expand Down
Loading

0 comments on commit 14238e0

Please sign in to comment.