diff --git a/NAMESPACE b/NAMESPACE index 5e47854..1b80fa3 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -3,6 +3,7 @@ export("%+%") export(.default_colours) export(.default_glyphs) +export(.default_limits) export(GeomSwimArrow) export(GeomSwimLane) export(GeomSwimMarker) diff --git a/R/scale_marker.R b/R/scale_marker.R index 312d932..5de149c 100644 --- a/R/scale_marker.R +++ b/R/scale_marker.R @@ -35,8 +35,19 @@ #' @export scale_marker_discrete <- function(glyphs = NULL, colours = NULL, limits = NULL, ...) { - markers <- data.frame(glyphs = glyphs, colours = colours, labels = limits) |> - distinct() + # Define max value lengths for core params + n_values <- max(c(length(glyphs), length(colours), length(limits))) + + # If no params assigned (default when using geom_swim_marker), return empty + # Else, intelligently create equal length core vectors + if (n_values == 0) { + markers <- data.frame() + } else { + markers <- data.frame(glyphs = glyphs %||% .default_glyphs[0:n_values], + colours = colours %||% .default_colours[0:n_values], + labels = limits %||% .default_limits[0:n_values]) |> + distinct() + } palette <- pal_markers( glyphs = markers$glyphs, @@ -84,6 +95,7 @@ pal_markers <- function(glyphs = NULL, colours = NULL, n_values = NULL) { #' @examples #' ggswim::.default_glyphs #' ggswim::.default_colours +#' ggswim::.default_limits #' #' @export # Set default glyphs and colours @@ -92,3 +104,7 @@ pal_markers <- function(glyphs = NULL, colours = NULL, n_values = NULL) { #' @rdname dot-default_glyphs #' @export .default_colours <- scales::brewer_pal(palette = "Set1")(9) # 9 is max for brewer + +#' @rdname dot-default_glyphs +#' @export +.default_limits <- c("val1", "val2", "val3", "val4", "val5", "val6", "val7", "val8", "val9") diff --git a/man/dot-default_glyphs.Rd b/man/dot-default_glyphs.Rd index 8ae97f4..17cc572 100644 --- a/man/dot-default_glyphs.Rd +++ b/man/dot-default_glyphs.Rd @@ -4,16 +4,21 @@ \name{.default_glyphs} \alias{.default_glyphs} \alias{.default_colours} +\alias{.default_limits} \title{ggswim marker defaults} \format{ An object of class \code{character} of length 9. +An object of class \code{character} of length 9. + An object of class \code{character} of length 9. } \usage{ .default_glyphs .default_colours + +.default_limits } \description{ ggswim marker defaults @@ -21,6 +26,7 @@ ggswim marker defaults \examples{ ggswim::.default_glyphs ggswim::.default_colours +ggswim::.default_limits } \keyword{datasets} diff --git a/tests/testthat/_snaps/geom_swim_marker/geom-swim-lane-works-with-inherited-data-and-params.svg b/tests/testthat/_snaps/geom_swim_marker/geom-swim-lane-works-with-inherited-data-and-params.svg index 8b7dff3..c3d4c58 100644 --- a/tests/testthat/_snaps/geom_swim_marker/geom-swim-lane-works-with-inherited-data-and-params.svg +++ b/tests/testthat/_snaps/geom_swim_marker/geom-swim-lane-works-with-inherited-data-and-params.svg @@ -21,31 +21,88 @@ - - + + - - - - - - - - - - - - - - - - - - - - - + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + 01 @@ -78,26 +135,35 @@ - - - - - -0 -1 -2 -3 -4 -time_from_initial_infusion + + + + + +-5 +0 +5 +10 +15 +start_time pt_id - -label - - - - -Initial Infusion -Reinfusion + +disease_assessment + + + + + + + + + + +CR +CR/CRi + B Cell Aplasia +CR/CRi + B Cell Recovery +CRi +RD geom_swim_lane works with inherited data and params diff --git a/tests/testthat/_snaps/geom_swim_marker/geom-swim-marker-works-with-inherited-data-and-params.svg b/tests/testthat/_snaps/geom_swim_marker/geom-swim-marker-works-with-inherited-data-and-params.svg new file mode 100644 index 0000000..9476f7e --- /dev/null +++ b/tests/testthat/_snaps/geom_swim_marker/geom-swim-marker-works-with-inherited-data-and-params.svg @@ -0,0 +1,103 @@ + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +01 +02 +03 +04 +05 +06 +08 +09 +12 +13 +14 +15 +17 +18 +19 + + + + + + + + + + + + + + + + + + + + +0 +1 +2 +3 +4 +time_from_initial_infusion +pt_id + +label + + + + +Initial Infusion +Reinfusion +geom_swim_marker works with inherited data and params + + diff --git a/tests/testthat/test-geom_swim_marker.R b/tests/testthat/test-geom_swim_marker.R index 89554e3..e36a3d3 100644 --- a/tests/testthat/test-geom_swim_marker.R +++ b/tests/testthat/test-geom_swim_marker.R @@ -32,17 +32,32 @@ test_that("all expected attributes exist in geom_swim_lane", { expect_true(all(expected_attrs %in% attrs)) }) -test_that("geom_swim_lane works when inheriting data and associated params", { - p <- patient_data |> - ggplot( - data = infusion_events, - mapping = aes( - x = time_from_initial_infusion, y = pt_id, - marker = label - ) - ) + +test_that("geom_swim_marker works when inheriting data and associated params", { + p <- ggplot( + data = infusion_events, + mapping = aes( + x = time_from_initial_infusion, y = pt_id, + marker = label + ) + ) + geom_swim_marker() + skip_on_ci() + vdiffr::expect_doppelganger( + title = "geom_swim_marker works with inherited data and params", + fig = p + ) +}) + +test_that("geom_swim_lane works when inheriting data and associated params", { + p <- ggplot( + data = patient_data, + mapping = aes( + x = start_time, xend = end_time, y = pt_id, colour = disease_assessment + ) + ) + + geom_swim_lane() + skip_on_ci() vdiffr::expect_doppelganger( title = "geom_swim_lane works with inherited data and params", diff --git a/tests/testthat/test-scale_marker.R b/tests/testthat/test-scale_marker.R index 823d489..1ddb1bd 100644 --- a/tests/testthat/test-scale_marker.R +++ b/tests/testthat/test-scale_marker.R @@ -73,3 +73,23 @@ test_that("scale_marker_discrete warns when more markers are requested than avai expect_error(scale$palette(5), "Can't subset elements past the end.") |> suppressWarnings() }) + +test_that("scale_marker_discrete uses default glyphs when missing", { + colours <- c("red", "green", "blue") + limits <- c("A", "B", "C") + + scale <- scale_marker_discrete(glyphs = NULL, colours = colours, limits = limits) + + expect_equal(length(scale$palette(3)), 3) + expect_equal(vctrs::field(scale$palette(3), "glyphs"), .default_glyphs[1:3]) # First 3 default glyphs +}) + +test_that("scale_marker_discrete uses default colours when missing", { + glyphs <- c("●", "■", "▲") + limits <- c("A", "B", "C") + + scale <- scale_marker_discrete(glyphs = glyphs, colours = NULL, limits = limits) + + expect_equal(length(scale$palette(3)), 3) + expect_equal(vctrs::field(scale$palette(3), "colour"), .default_colours[1:3]) # First 3 default glyphs +}) diff --git a/vignettes/articles/gallery.Rmd b/vignettes/articles/gallery.Rmd index e2c5f51..50ae3e5 100644 --- a/vignettes/articles/gallery.Rmd +++ b/vignettes/articles/gallery.Rmd @@ -19,9 +19,70 @@ library(ggplot2) library(dplyr) ``` -To support some of these visuals, we'll set up some of the datasets similar to the README: +## Random Data Sets -```{r setup data} +In this example, we'll set up a random dataset for reproducibility by separately defining a dataframe for our lanes and our markers. + +```{r} +set.seed(123) +lane_data <- tibble( + x = 0, + xend = sample(5:20, 30, replace = TRUE), + y = factor(rep(1:15, each = 2)), + colour = sample(c('red', 'blue', 'green', 'yellow', 'purple'), 30, replace = TRUE) +) + +set.seed(123) +marker_data <- tibble( + x = sample(5:20, 30, replace = TRUE), + y = factor(rep(1:15, each = 2)), + label = sample(c("A", "B", "C", "D", "E"), 30, replace = TRUE), + glyph = sample(c("😊", "🎉", "✅", "💥", "✨"), 30, replace = TRUE) +) |> + mutate( + glyph = dplyr::case_when( + label == "A" ~ "😊", + label == "B" ~ "🎉", + label == "C" ~ "✅", + label == "D" ~ "💥", + label == "E" ~ "✨", + .default = NA + ) + ) + +lane_data |> + rmarkdown::paged_table() +marker_data |> + rmarkdown::paged_table() +``` + +And then we'll call those datasets into their appropriate swim and marker geom functions: + +```{r} +ggplot() + + geom_swim_lane( + data = lane_data, + aes(x = x, xend = xend, y = y, colour = colour), + linewidth = 3 + ) + + geom_swim_marker( + data = marker_data, + aes(x = x, y = y, marker = label), + size = 8 + ) + + scale_colour_brewer(name = "Lanes", palette = "Set1") + + with(marker_data, + scale_marker_discrete(glyphs = glyph, limits = label, name = "Markers")) + + labs(title = "Sample Swimmer Plot", + x = "Time", y = "Record ID") + + theme_ggswim() +``` + +## Themeing with ggswim + +Here are some example of the themeing functions available in ggswim using the dataset examples from the README: + +```{r} arrow_data <- patient_data |> dplyr::left_join( end_study_events |> @@ -37,13 +98,7 @@ all_events <- dplyr::bind_rows( infusion_events, end_study_events ) -``` - -## Themeing with ggswim -Here are some example of the themeing functions available in ggswim using the dataset examples from the README: - -```{r} p <- patient_data |> ggplot() + geom_swim_lane( @@ -91,4 +146,3 @@ p + theme_ggswim() ```{r} p + theme_ggswim_dark() ``` -