Skip to content

Commit

Permalink
paginate over compare runs endpoint
Browse files Browse the repository at this point in the history
  • Loading branch information
austin3dickey committed Nov 3, 2023
1 parent 4e0a932 commit 3eb0f13
Show file tree
Hide file tree
Showing 10 changed files with 216 additions and 94 deletions.
3 changes: 2 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,8 @@

export(benchmark_results)
export(benchmarks)
export(compare)
export(compare_results)
export(compare_runs)
export(conbench_perform)
export(conbench_request)
export(hardware)
Expand Down
86 changes: 73 additions & 13 deletions R/compare.R
Original file line number Diff line number Diff line change
@@ -1,30 +1,27 @@
#' Compare runs, benchmarks, batches, or commits
#' Compare benchmark results
#'
#' @param type the type of comparison to make (one of: runs, benchmarks, batches, commits)
#' @param baseline the baseline sha of the entity to compare
#' @param contender the contender sha of the entity to compare
#' @param zscore_threshold the zscore threshold to mark regressions and improvements.
#' @param baseline the ID of the baseline result to compare
#' @param contender the ID of the contender result to compare
#' @param zscore_threshold the zscore threshold to mark regressions and improvements.
#' Default is defined at the Conbench api level.
#' @param pairwise_percent_threshold the pairwise_percent_threshold to mark regressions and improvements.
#' Default is defined at the Conbench api level.
#' @inheritDotParams httr2::resp_body_json
#'
#' @return the JSON response
#' @export
compare <- function(type = c("runs", "benchmarks", "batches", "commits"),
baseline,
contender,
zscore_threshold = NULL,
pairwise_percent_threshold = NULL,
...) {
type <- match.arg(type)
compare_results <- function(baseline,
contender,
zscore_threshold = NULL,
pairwise_percent_threshold = NULL,
...) {
stopifnot("zscore_threshold must be numeric" = is.numeric(zscore_threshold) || is.null(zscore_threshold))
stopifnot("pairwise_percent_threshold must be numeric" = is.numeric(pairwise_percent_threshold) || is.null(pairwise_percent_threshold))

req <- req_url_path_append(
conbench_request(),
"compare",
type,
"benchmark-results",
paste0(baseline, "...", contender)
)

Expand All @@ -40,3 +37,66 @@ compare <- function(type = c("runs", "benchmarks", "batches", "commits"),

resp_body_json(resp, ...)
}

#' Compare runs
#'
#' @param baseline the ID of the baseline run to compare
#' @param contender the ID of the contender run to compare
#' @param zscore_threshold the zscore threshold to mark regressions and improvements.
#' Default is defined at the Conbench api level.
#' @param pairwise_percent_threshold the pairwise_percent_threshold to mark regressions and improvements.
#' Default is defined at the Conbench api level.
#'
#' @return a tibble of run comparisons
#' @export
compare_runs <- function(baseline,
contender,
zscore_threshold = NULL,
pairwise_percent_threshold = NULL) {
stopifnot("zscore_threshold must be numeric" = is.numeric(zscore_threshold) || is.null(zscore_threshold))
stopifnot("pairwise_percent_threshold must be numeric" = is.numeric(pairwise_percent_threshold) || is.null(pairwise_percent_threshold))

req <- req_url_path_append(
conbench_request(),
"compare",
"runs",
paste0(baseline, "...", contender)
)
req <- req_url_query(req, page_size = 500)
if (!is.null(zscore_threshold)) {
req <- req_url_query(req, threshold_z = zscore_threshold)
}
if (!is.null(pairwise_percent_threshold)) {
req <- req_url_query(req, threshold = pairwise_percent_threshold)
}

resp <- conbench_perform(req)
json <- resp_body_json(resp, simplifyVector = TRUE, flatten = TRUE)
data <- dplyr::as_tibble(json[["data"]])

while (!is.null(json[["metadata"]][["next_page_cursor"]])) {
req <- req_url_path_append(
conbench_request(),
"compare",
"runs",
paste0(baseline, "...", contender)
)
req <- req_url_query(
req,
page_size = 500,
cursor = json[["metadata"]][["next_page_cursor"]]
)
if (!is.null(zscore_threshold)) {
req <- req_url_query(req, threshold_z = zscore_threshold)
}
if (!is.null(pairwise_percent_threshold)) {
req <- req_url_query(req, threshold = pairwise_percent_threshold)
}

resp <- conbench_perform(req)
json <- resp_body_json(resp, simplifyVector = TRUE, flatten = TRUE)
data <- dplyr::bind_rows(data, dplyr::as_tibble(json[["data"]]))
}

data
}
17 changes: 7 additions & 10 deletions man/compare.Rd → man/compare_results.Rd

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

30 changes: 30 additions & 0 deletions man/compare_runs.Rd

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

Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
{
"analysis": {
"lookback_z_score": {
"improvement_indicated": false,
"regression_indicated": false,
"z_score": -0.5,
"z_threshold": 11.1
},
"pairwise": {
"improvement_indicated": false,
"percent_change": -26,
"percent_threshold": 20.2,
"regression_indicated": true
}
}
}
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
{
"data": [
{
"analysis": {
"lookback_z_score": {
"improvement_indicated": false,
"regression_indicated": false,
"z_score": -0.5,
"z_threshold": 11.1
},
"pairwise": {
"improvement_indicated": false,
"percent_change": -26,
"percent_threshold": 20.2,
"regression_indicated": true
}
}
}
],
"metadata": {
"next_page_cursor": "curse"
}
}

This file was deleted.

Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
{
"data": [
{
"analysis": {
"lookback_z_score": {
"improvement_indicated": false,
"regression_indicated": false,
"z_score": -0.5,
"z_threshold": 11.1
},
"pairwise": {
"improvement_indicated": false,
"percent_change": -26,
"percent_threshold": 20.2,
"regression_indicated": true
}
}
}
],
"metadata": {
"next_page_cursor": null
}
}

This file was deleted.

Loading

0 comments on commit 3eb0f13

Please sign in to comment.