Skip to content

Commit

Permalink
new attribute dpi for AssSpec2d
Browse files Browse the repository at this point in the history
  • Loading branch information
lgessl committed Feb 22, 2024
1 parent 178ae74 commit 3957a72
Show file tree
Hide file tree
Showing 6 changed files with 31 additions and 19 deletions.
8 changes: 6 additions & 2 deletions R/ass_spec_2d.R
Original file line number Diff line number Diff line change
Expand Up @@ -61,6 +61,7 @@
#' [`ggplot2::theme()`] or a complete ggplot2 theme like [`ggplot2::theme_light()`]).
#' The theme of the plot. Default is `NULL`, which means the default theme of ggplot2.
#' @param units string. The units of `width` and `height`. Default is `"in"` (inches).
#' @param dpi numeric. Plot resolution in dots per inch. Default is `300`.
#' @return An AssSpec2d S3 object.
#' @export
AssSpec2d <- function(
Expand Down Expand Up @@ -93,7 +94,8 @@ AssSpec2d <- function(
height = 4,
colors = NULL,
theme = NULL,
units = "in"
units = "in",
dpi = 300
){
if(is.null(x_lab)){
x_lab <- x_metric
Expand Down Expand Up @@ -134,6 +136,7 @@ AssSpec2d <- function(
stopifnot(is.numeric(height) && height > 0)
stopifnot((inherits(theme, "theme") && inherits(theme, "gg")) || is.null(theme))
stopifnot(is.character(units))
stopifnot(is.numeric(dpi) && dpi > 0)

ass_spec_2d <- list(
"file" = file,
Expand Down Expand Up @@ -165,7 +168,8 @@ AssSpec2d <- function(
"width" = width,
"height" = height,
"theme" = theme,
"units" = units
"units" = units,
"dpi" = dpi
)
return(structure(ass_spec_2d, class = "AssSpec2d"))
}
Expand Down
3 changes: 2 additions & 1 deletion R/plot.R
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,8 @@ plot_2d_metric <- function(
plt,
width = ass_spec_2d$width,
height = ass_spec_2d$height,
units = ass_spec_2d$units
units = ass_spec_2d$units,
dpi = ass_spec_2d$dpi
)

# Save to csv (if wanted)
Expand Down
5 changes: 4 additions & 1 deletion man/AssSpec2d.Rd

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

9 changes: 5 additions & 4 deletions tests/testthat/test-assess_2d.R
Original file line number Diff line number Diff line change
Expand Up @@ -46,15 +46,16 @@ test_that("assess_2d() works", {
response_type = "binary"
)
ass_spec_2d <- AssSpec2d(
file = file.path(dir, "rpp.pdf"),
file = file.path(dir, "rpp.jpeg"),
x_metric = "rpp",
y_metric = "prec",
pivot_time_cutoff = 2.,
benchmark = "ipi",
smooth_se = TRUE,
show_plots = FALSE,
text = list(ggplot2::aes(x = .5, y = .5, label = "this text"),
color = "red", angle = 45)
color = "red", angle = 45),
dpi = 250
)

for(model_spec in list(model_spec_1, model_spec_2)){
Expand All @@ -79,7 +80,7 @@ test_that("assess_2d() works", {


ass_spec_2d$benchmark <- "ipi"
ass_spec_2d$directory <- file.path(dir, "logrank.pdf")
ass_spec_2d$directory <- file.path(dir, "logrank.jpeg")
ass_spec_2d$y_metric <- "logrank"
ass_spec_2d$scale_y <- "log10"
tbl <- assess_2d(
Expand All @@ -94,7 +95,7 @@ test_that("assess_2d() works", {

ass_spec_2d$y_metric <- "precision_ci"
ass_spec_2d$ci_level <- .95
ass_spec_2d$directory <- file.path(dir, "precision_ci.pdf")
ass_spec_2d$directory <- file.path(dir, "precision_ci.jpeg")
ass_spec_2d$scale_y <- "identity"
ass_spec_2d$title <- "Lower precision CI boundary (upper for ipi)"
ass_spec_2d$show_plots <- FALSE
Expand Down
13 changes: 7 additions & 6 deletions tests/testthat/test-assess_2d_center.R
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,7 @@ test_that("assess_2d_center() works", {

res_dir <- file.path(base_dir, "results")
ass_spec_2d <- AssSpec2d(
file = file.path(model_dir, "perf_plot.pdf"),
file = file.path(model_dir, "perf_plot.jpeg"),
x_metric = "rpp",
y_metric = "prec",
show_plots = FALSE,
Expand All @@ -72,7 +72,8 @@ test_that("assess_2d_center() works", {
text = list(ggplot2::aes(x = .5, y = .5, label = "hello"),
color = "red", angle = 90),
theme = ggplot2::theme_minimal() +
ggplot2::theme(plot.background = ggplot2::element_rect(fill = "red"))
ggplot2::theme(plot.background = ggplot2::element_rect(fill = "red")),
dpi = 250
)

assess_2d_center(
Expand All @@ -83,13 +84,13 @@ test_that("assess_2d_center() works", {
quiet = TRUE
)
expect_true(file.exists(ass_spec_2d$file))
expect_true(file.exists(file.path(res_dir, "logistic/2/scores.pdf")))
expect_true(file.exists(file.path(res_dir, "logistic/2/scores.jpeg")))
expect_true(file.exists(file.path(res_dir, "cox/2/rpp_vs_prec.csv")))

model_spec_1$split_index <- 1
ass_spec_2d$y_metric <- "logrank"
ass_spec_2d$scale_y <- "log10"
ass_spec_2d$file <- file.path(model_dir, "logrank.pdf")
ass_spec_2d$file <- file.path(model_dir, "logrank.jpeg")
ass_spec_2d$benchmark <- NULL
ass_spec_2d$text <- NULL
ass_spec_2d$scores_plot <- FALSE
Expand All @@ -105,7 +106,7 @@ test_that("assess_2d_center() works", {
model_spec_2$time_cutoffs <- 1.5
ass_spec_2d$y_metric <- "precision_ci"
ass_spec_2d$ci_level <- .95
ass_spec_2d$file <- file.path(model_dir, "precision_ci.pdf")
ass_spec_2d$file <- file.path(model_dir, "precision_ci.jpeg")
ass_spec_2d$benchmark <- "ipi"
assess_2d_center(
model_spec_list = list(model_spec_2),
Expand All @@ -115,5 +116,5 @@ test_that("assess_2d_center() works", {
cohorts = "train",
quiet = TRUE
)
expect_true(file.exists(file.path(model_dir, "logistic/1-5/rpp_vs_precision_ci.pdf")))
expect_true(file.exists(file.path(model_dir, "logistic/1-5/rpp_vs_precision_ci.jpeg")))
})
12 changes: 7 additions & 5 deletions tests/testthat/test-plot.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ test_that("plot_2d_metric() works", {

dir <- withr::local_tempdir()
ass_spec_2d <- AssSpec2d(
file = file.path(dir, "test.pdf"),
file = file.path(dir, "test.jpeg"),
x_metric = "rpp",
y_metric = "prec",
pivot_time_cutoff = 2.,
Expand All @@ -24,7 +24,8 @@ test_that("plot_2d_metric() works", {
text = list(ggplot2::aes(x = 0.5, y = 0.5, label = "this text")),
colors = c("black", "blue", "yellow", "red"),
theme = ggplot2::theme_dark() +
ggplot2::theme(plot.background = ggplot2::element_rect(grDevices::rgb(1, 1, 1, .98)))
ggplot2::theme(plot.background = ggplot2::element_rect(grDevices::rgb(1, 1, 1, .98))),
dpi = 200
)
ass_spec_2d$data <- tibble::tibble(
rpp = runif(n_row),
Expand Down Expand Up @@ -64,12 +65,13 @@ test_that("plot_risk_scores() works", {
predicted <- l[[2]]
dir <- withr::local_tempdir()
ass_spec_2d <- AssSpec2d(
file = file.path(dir, "scores.pdf"),
file = file.path(dir, "scores.jpeg"),
x_metric = "rank",
y_metric = "scores",
title = "this title",
fellow_csv = TRUE,
show_plots = FALSE
show_plots = FALSE,
dpi = 250
)

expect_no_error(
Expand All @@ -81,7 +83,7 @@ test_that("plot_risk_scores() works", {
)
)
expect_true(all(
file.exists(file.path(dir, "scores.pdf")),
file.exists(file.path(dir, "scores.jpeg")),
file.exists(file.path(dir, "scores.csv"))
))
})

0 comments on commit 3957a72

Please sign in to comment.