Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
60 changes: 12 additions & 48 deletions R/diffDashboard.R
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ diffDashboard <- function(.file) {
ui <- bslib::page_sidebar(
title = htmltools::div(
style = "display:flex; gap:.35rem; align-items:baseline; font-weight:600;",
htmltools::span("Visual diff:"),
htmltools::span("Revision Comparison:"),
htmltools::span(
style = "opacity:.7; font-weight:400;",
fs::path_rel(.file)
Expand Down Expand Up @@ -104,65 +104,29 @@ diffDashboard <- function(.file) {
server <- function(input, output, session) {
session$onSessionEnded(function() shiny::stopApp())

# Selected IDs (strings): numeric revisions as strings + 'LOCAL'
# Default to newest vs LOCAL for immediate utility
# Unified selection state using extracted helpers
default_sel <- c(as.character(newest), "Local")
sel <- shiny::reactiveVal(default_sel)
selection <- shiny::reactiveVal(compute_selection(default_sel))

# show hint once the server has started
show_app_exit_hint("diffDashboard")

shiny::observeEvent(
input$rev_clicked,
{
r <- as.character(input$rev_clicked)
cur <- sel()
if (r %in% cur) {
sel(setdiff(cur, r))
} else {
new <- c(cur, r)
new <- new[!duplicated(new)]
if (length(new) > 2) {
new <- utils::tail(new, 2)
}
sel(new)
}
new_ids <- update_selection(
selection()$ids,
input$rev_clicked,
max_sel = 2L
)
selection(compute_selection(new_ids))
},
ignoreInit = TRUE
)

# Pairing logic: if LOCAL is present, force it to be `newer`
picked <- shiny::reactive({
x <- sel()
if (length(x) < 2) {
return(NULL)
}
if ("Local" %in% x) {
other <- setdiff(x, "Local")
if (!length(other)) {
return(NULL)
}
# choose the numeric rev as prior (use min in case of oddities)
other_num <- suppressWarnings(as.numeric(other))
other_num <- other_num[!is.na(other_num)]
if (!length(other_num)) {
return(NULL)
}
list(prior = min(other_num), newer = NULL)
} else {
# both numeric
nums <- suppressWarnings(as.numeric(x))
nums <- sort(nums)
if (length(nums) < 2) {
return(NULL)
}
list(prior = nums[1], newer = nums[2])
}
})

# --- Timeline UI (LOCAL first, then SVN revisions) ---
output$timeline_ui <- shiny::renderUI({
chosen <- sel()
chosen <- selection()$ids

rev_items <- lapply(seq_len(nrow(svn_log)), function(i) {
row <- svn_log[i, ]
Expand Down Expand Up @@ -195,8 +159,8 @@ diffDashboard <- function(.file) {
})

output$diff_html <- shiny::renderUI({
p <- picked()
shiny::req(p)
p <- selection()
shiny::req(!is.null(p$prior))

sbs <- shiny::isTruthy(input$side_by_side)
igw <- shiny::isTruthy(input$ignore_ws)
Expand Down
94 changes: 94 additions & 0 deletions R/utils-dashboard.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,94 @@
#' Update selected revision IDs based on a timeline click
#'
#' @description
#' Toggle a clicked revision in the current selection, enforcing a maximum
#' number of selections (default 2). Duplicates are removed while preserving
#' first-occurrence order; when adding beyond the limit, the most recent
#' selections are retained.
#'
#' @param ids `character()`
#' Current selected revision identifiers (e.g., `"Local"`, `"105"`).
#' @param clicked `character(1)`
#' The revision identifier that was clicked.
#' @param max_sel `integer(1)`
#' Maximum number of selections to retain. Defaults to `2L`.
#'
#' @return `character()` updated selection.
#' @noRd
update_selection <- function(ids, clicked, max_sel = 2L) {
clicked <- as.character(clicked)
ids <- as.character(ids)

if (length(clicked) != 1L || is.na(clicked) || !nzchar(clicked)) {
return(ids)
}

if (clicked %in% ids) {
new <- setdiff(ids, clicked)
} else {
new <- c(ids, clicked)
new <- new[!duplicated(new)]
if (length(new) > max_sel) new <- utils::tail(new, max_sel)
}

new
}

#' Compute a paired selection (prior/newer) from selected revision IDs
#'
#' @description
#' Given a character vector of selected revision identifiers (e.g., `"Local"`
#' and/or numeric revisions as strings), compute the revision pair used for
#' diffing. If `"Local"` is present, the local working copy is treated as the
#' **newer** side and the minimum numeric revision among the other selections is
#' treated as **prior**. If only numeric revisions are present, the two smallest
#' numeric revisions are used as `prior` and `newer` respectively.
#'
#' @param ids `character()`
#' Selected revision identifiers. May include `"Local"` and/or numeric
#' revisions represented as character strings. Duplicates are ignored.
#'
#' @return `list` with elements:
#' \describe{
#' \item{ids}{The de-duplicated input `ids` (character).}
#' \item{prior}{`numeric(1)` the prior revision number, or `NULL` if a pair
#' cannot be determined.}
#' \item{newer}{`numeric(1)` the newer revision number, or `NULL` to indicate
#' the local working copy when `"Local"` is selected.}
#' }
#'
#' @details
#' If fewer than two valid selections are provided, both `prior` and `newer`
#' are `NULL`. Non-numeric entries other than `"Local"` are ignored when
#' computing numeric revisions.
#'
#' @examples
#' compute_selection(c("105", "Local"))
#' compute_selection(c("101", "103"))
#' compute_selection("Local")
#'
#' @noRd
compute_selection <- function(ids) {
ids <- ids[!duplicated(ids)]
if (length(ids) < 2) {
return(list(ids = ids, prior = NULL, newer = NULL))
}

if ("Local" %in% ids) {
other <- setdiff(ids, "Local")
other_num <- suppressWarnings(as.numeric(other))
other_num <- other_num[!is.na(other_num)]
if (!length(other_num)) {
return(list(ids = ids, prior = NULL, newer = NULL))
}
return(list(ids = ids, prior = min(other_num), newer = NULL))
} else {
nums <- suppressWarnings(as.numeric(ids))
nums <- sort(nums)
if (length(nums) < 2) {
return(list(ids = ids, prior = NULL, newer = NULL))
}
return(list(ids = ids, prior = nums[1], newer = nums[2]))
}
}

4 changes: 2 additions & 2 deletions pkgr.yml
Original file line number Diff line number Diff line change
Expand Up @@ -11,9 +11,9 @@ Packages:

Repos:
- CRAN: https://cran.rstudio.com
- MPN: https://mpn.metworx.com/snapshots/stable/2024-06-12 # used for mrg packages
- MPN: https://mpn.metworx.com/snapshots/stable/2025-09-17 # used for mrg packages

Lockfile:
Type: renv

Rpath: ${R_EXE_4_3}
Rpath: ${R_EXE_4_5}
129 changes: 129 additions & 0 deletions tests/testthat/test-selection.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,129 @@
# tests/testthat/test-selection.R

testthat::test_that("update_selection: adds, toggles, de-duplicates, enforces max 2", {
# start empty, add one
ids <- character()
ids <- update_selection(ids, "105")
testthat::expect_identical(ids, c("105"))

# add second
ids <- update_selection(ids, "Local")
testthat::expect_identical(ids, c("105", "Local"))

# add third -> keeps the most recent two (tail)
ids <- update_selection(ids, "103")
testthat::expect_identical(ids, c("Local", "103"))

# clicking an existing id removes it (toggle off)
ids <- update_selection(ids, "Local")
testthat::expect_identical(ids, c("103"))

# adding a duplicate doesn't create another copy
ids <- update_selection(ids, "103")
testthat::expect_identical(ids, character())
})

testthat::test_that("update_selection: preserves first-occurrence order before truncation", {
ids <- c("Local", "110")
ids <- update_selection(ids, "105") # => c("Local","110","105") -> tail 2
testthat::expect_identical(ids, c("110", "105")) # last two kept in order they appeared
})

testthat::test_that("update_selection: accepts non-character & invalid clicks gracefully", {
# numeric click coerces to character
ids <- update_selection(character(), 105)
testthat::expect_identical(ids, "105")
testthat::expect_true(is.character(ids))

# empty string: no-op
ids2 <- update_selection(ids, "")
testthat::expect_identical(ids2, ids)

# NA: no-op
ids3 <- update_selection(ids, NA_character_)
testthat::expect_identical(ids3, ids)
})

testthat::test_that("update_selection: configurable max_sel works", {
ids <- character()
ids <- update_selection(ids, "101", max_sel = 3L)
ids <- update_selection(ids, "102", max_sel = 3L)
ids <- update_selection(ids, "103", max_sel = 3L)
testthat::expect_identical(ids, c("101", "102", "103"))

# adding a 4th keeps the last three
ids <- update_selection(ids, "104", max_sel = 3L)
testthat::expect_identical(ids, c("102", "103", "104"))
})

testthat::test_that("compute_selection: returns NULLs when fewer than two selections", {
s1 <- compute_selection(character())
testthat::expect_true(is.null(s1$prior))
testthat::expect_true(is.null(s1$newer))
testthat::expect_identical(s1$ids, character())

s2 <- compute_selection("Local")
testthat::expect_true(is.null(s2$prior))
testthat::expect_true(is.null(s2$newer))
testthat::expect_identical(s2$ids, "Local")

s3 <- compute_selection("abc")
testthat::expect_true(is.null(s3$prior))
testthat::expect_true(is.null(s3$newer))
testthat::expect_identical(s3$ids, "abc")
})

testthat::test_that("compute_selection: Local + one numeric => prior numeric, newer NULL", {
s <- compute_selection(c("105", "Local"))
testthat::expect_identical(s$prior, 105)
testthat::expect_true(is.null(s$newer))
testthat::expect_identical(s$ids, c("105", "Local"))
})

testthat::test_that("compute_selection: Local + multiple numerics => prior is min(other), newer NULL", {
s <- compute_selection(c("Local", "110", "105", "107"))
testthat::expect_identical(s$prior, 105)
testthat::expect_true(is.null(s$newer))
testthat::expect_identical(s$ids, c("Local", "110", "105", "107"))
})

testthat::test_that("compute_selection: two numerics => prior/newer are the two smallest", {
s <- compute_selection(c("110", "105"))
testthat::expect_identical(s$prior, 105)
testthat::expect_identical(s$newer, 110)
testthat::expect_identical(s$ids, c("110", "105"))
})

testthat::test_that("compute_selection: >2 numerics => uses the two smallest", {
s <- compute_selection(c("110", "105", "107", "200"))
testthat::expect_identical(s$prior, 105)
testthat::expect_identical(s$newer, 107)
testthat::expect_identical(s$ids, c("110", "105", "107", "200"))
})

testthat::test_that("compute_selection: ignores non-numeric strings (besides 'Local') for pairing", {
s <- compute_selection(c("foo", "105", "bar", "107"))
testthat::expect_identical(s$prior, 105)
testthat::expect_identical(s$newer, 107)
testthat::expect_identical(s$ids, c("foo", "105", "bar", "107"))
})

testthat::test_that("compute_selection: de-duplicates while preserving first occurrences", {
s <- compute_selection(c("Local", "105", "105", "Local", "107", "107"))
testthat::expect_identical(s$ids, c("Local", "105", "107"))
testthat::expect_identical(s$prior, 105)
testthat::expect_true(is.null(s$newer)) # Local present => newer is NULL
})

testthat::test_that("integration: update_selection + compute_selection behave as intended", {
ids <- character()
ids <- update_selection(ids, "105")
ids <- update_selection(ids, "Local")
# adding a third keeps last 2
ids <- update_selection(ids, "103")
testthat::expect_identical(ids, c("Local", "103"))

sel <- compute_selection(ids)
testthat::expect_identical(sel$prior, 103)
testthat::expect_true(is.null(sel$newer)) # Local implies newer is local
})