Skip to content

Commit

Permalink
add vertical, horizontal line, text label to 2d performance plot
Browse files Browse the repository at this point in the history
  • Loading branch information
lgessl committed Jan 22, 2024
1 parent fe5531c commit a6ffda5
Show file tree
Hide file tree
Showing 5 changed files with 48 additions and 7 deletions.
20 changes: 20 additions & 0 deletions R/perf_plot_spec.R
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,9 @@ new_PerfPlotSpec <- function(
smooth_benchmark,
scale_x,
scale_y,
hline,
vline,
text,
alpha,
colors,
width,
Expand All @@ -40,6 +43,9 @@ new_PerfPlotSpec <- function(
stopifnot(is.character(smooth_method) || is.null(smooth_method) ||
is.function(smooth_method))
stopifnot(is.logical(smooth_benchmark))
stopifnot(is.null(hline) || is.list(hline))
stopifnot(is.null(vline) || is.list(vline))
stopifnot(is.null(text) || is.list(text))
stopifnot(is.numeric(alpha) && alpha >= 0 && alpha <= 1)
stopifnot(is.character(colors) || is.null(colors))
stopifnot(is.numeric(width) && width > 0)
Expand All @@ -65,6 +71,9 @@ new_PerfPlotSpec <- function(
"smooth_benchmark" = smooth_benchmark,
"scale_x" = scale_x,
"scale_y" = scale_y,
"hline" = hline,
"vline" = vline,
"text" = text,
"alpha" = alpha,
"colors" = colors,
"width" = width,
Expand Down Expand Up @@ -116,6 +125,11 @@ new_PerfPlotSpec <- function(
#' @param scale_x,scale_y string or transformation object (see [`scales::trans_new`] for the
#' latter). The scale of the axes, we will pass them to the `x` and `y` parameter of
#' [`ggplot2::coord_trans()`], respectively. Default is `"identity"`.
#' @param vline,hline list or NULL. Vertical/horizontal lines to be added to the plot. A list
#' holding the arguments to pass to [`ggplot2::geom_vline()`] and [`ggplot2::geom_hline()`],
#' respectively. Default is `NULL`.
#' @param text list or NULL. Text label added to the plot. A list holding the arguments to
#' pass to [`ggplot2::geom_text()`]. Default is `NULL`.
#' @param alpha numeric in \[0, 1\]. The alpha value for the points and lines in the
#' plot.
#' @param width numeric. The width of the plot in `units`. Default is `7`.
Expand Down Expand Up @@ -144,6 +158,9 @@ PerfPlotSpec <- function(
smooth_benchmark = FALSE,
scale_x = "identity",
scale_y = "identity",
vline = NULL,
hline = NULL,
text = NULL,
alpha = 0.5,
width = 7,
height = 4,
Expand Down Expand Up @@ -177,6 +194,9 @@ PerfPlotSpec <- function(
smooth_benchmark = smooth_benchmark,
scale_x = scale_x,
scale_y = scale_y,
vline = vline,
hline = hline,
text = text,
alpha = alpha,
width = width,
height = height,
Expand Down
12 changes: 8 additions & 4 deletions R/plot.R
Original file line number Diff line number Diff line change
Expand Up @@ -37,10 +37,14 @@ plot_2d_metric <- function(
x = perf_plot_spec$x_lab,
y = perf_plot_spec$y_lab
) +
ggplot2::coord_trans(
x = perf_plot_spec$scale_x,
y = perf_plot_spec$scale_y
)
ggplot2::scale_x_continuous(trans = perf_plot_spec$scale_x) +
ggplot2::scale_y_continuous(trans = perf_plot_spec$scale_y)
if(!is.null(perf_plot_spec$hline))
plt <- plt + do.call(ggplot2::geom_hline, perf_plot_spec$hline)
if(!is.null(perf_plot_spec$vline))
plt <- plt + do.call(ggplot2::geom_vline, perf_plot_spec$vline)
if(!is.null(perf_plot_spec$text))
plt <- plt + do.call(ggplot2::geom_text, perf_plot_spec$text)
if(!is.null(perf_plot_spec$benchmark) && !is.null(bm_data)){
bm_alpha <- ifelse(
perf_plot_spec$smooth_benchmark,
Expand Down
10 changes: 10 additions & 0 deletions man/PerfPlotSpec.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 3 additions & 1 deletion tests/testthat/test-assess_model.R
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,9 @@ test_that("assess_model() works", {
y_metric = "prec",
pivot_time_cutoff = 2.,
benchmark = "ipi",
show_plots = TRUE
show_plots = FALSE,
text = list(ggplot2::aes(x = .5, y = .5, label = "this text"),
color = "red", angle = 45)
)

for(model_spec in list(model_spec_1, model_spec_2)){
Expand Down
9 changes: 7 additions & 2 deletions tests/testthat/test-plot.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,14 +12,16 @@ test_that("plot_2d_metric() works", {
y_metric = "prec",
pivot_time_cutoff = 2.,
benchmark = "bm",
show_plots = FALSE,
show_plots = TRUE,
title = "this title",
x_lab = "this x lab",
y_lab = "that y lab",
xlim = c(0, .9),
smooth_method = "loess",
smooth_benchmark = TRUE,
scale_x = "log10"
scale_x = "log10",
hline = list(yintercept = 0.5, linetype = "dashed"),
text = list(ggplot2::aes(x = 0.5, y = 0.5, label = "this text"))
)
perf_plot_spec$data <- tibble::tibble(
rpp = runif(n_row),
Expand All @@ -34,6 +36,9 @@ test_that("plot_2d_metric() works", {
)
)
perf_plot_spec$benchmark <- NULL
perf_plot_spec$hline <- NULL
perf_plot_spec$text <- NULL
perf_plot_spec$vline <- list(xintercept = 0.5, color = "blue")
expect_no_error(
plot_2d_metric(
perf_plot_spec = perf_plot_spec,
Expand Down

0 comments on commit a6ffda5

Please sign in to comment.