diff --git a/DESCRIPTION b/DESCRIPTION index 494710d..81bac66 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: rren Title: Renaissance Benchmark Data Processing Package -Version: 0.0.7 +Version: 0.0.8 Authors@R: person ("Petr", "Tuma", email = "petr.tuma@d3s.mff.cuni.cz", role = c ("aut", "cre"), comment = c (ORCID = "0000-0002-7035-2322")) Description: A utility package for processing the data produced by the Renaissance benchmark suite (https://renaissance.dev). @@ -19,11 +19,14 @@ Imports: cli (>= 3.6.1), digest (>= 0.6.33), dplyr (>= 1.1.3), + forcats (>= 1.0.0), fs (>= 1.6.3), + ggplot2 (>= 3.4.4), glue (>= 1.6.2), jsonlite (>= 1.8.7), logger (>= 0.2.2), prettyunits (>= 1.2.0), + readr (>= 2.1.4), rlang (>= 1.1.1), stringr (>= 1.5.0), tibble (>= 3.2.1), diff --git a/NAMESPACE b/NAMESPACE index 98beddf..1d46437 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -3,10 +3,14 @@ export(assert_renaissance) export(check_renaissance) export(compute_flat_percentile_ci) +export(compute_flat_relative_percentile_ci) export(compute_hierarchical_percentile_ci) +export(compute_hierarchical_relative_percentile_ci) export(compute_list_vectors_hierarchical_percentile_ci) +export(compute_list_vectors_pair_hierarchical_percentile_ci) export(compute_trends) export(compute_vector_flat_percentile_ci) +export(compute_vector_pair_flat_percentile_ci) export(expect_renaissance) export(flag_outliers_global) export(flag_outliers_window) @@ -21,6 +25,9 @@ export(list_segment_boundaries) export(load_file_json) export(load_path_json) export(locate_vector_segments) +export(plot_default_labels) +export(plot_website_stripes) +export(plot_website_violins) export(preserve_last_n) export(preserve_last_sec) export(remove_outliers_global) @@ -31,6 +38,8 @@ export(rren_example) import(checkmate) import(cli) import(dplyr) +import(forcats) +import(ggplot2) import(glue) import(logger) import(prettyunits) diff --git a/R/example.R b/R/example.R index 032d8a7..b4e675e 100644 --- a/R/example.R +++ b/R/example.R @@ -13,21 +13,33 @@ rren_example <- function (file_name = '') { #' Return data frame with artificial data. #' -#' @param data Data to use. -#' @param vm_count Count of VM combinations to generate. -#' @param run_count Count of run combinations to generate. -#' @param benchmark_count Count of benchmark combinations to generate. -#' @return data Frame with artificial data. +#' Data to use for each run is the same. The result tibble +#' is arranged to first iterate runs, then benchmarks, +#' then virtual machines. This guarantee is useful +#' when difference between runs is to be +#' injected later. +#' +#' @param data Data to use for each run. +#' @param run_count Count of run combinations to generate per virtual machine and benchmark. +#' @param benchmark_count Count of benchmark combinations to generate per virtual machine. +#' @param vm_count Count of virtual machine combinations to generate. +#' @return data Tibble with artificial data. #' @export -rren_artificial <- function (data, vm_count = 1L, run_count = 1L, benchmark_count = 1L) { +rren_artificial <- function (data, run_count = 1L, benchmark_count = 1L, vm_count = 1L) { result <- tibble (time = data) |> mutate ( index = row_number (), total = cumsum (data)) + list_times_run <- lapply (seq (run_count), function (x) result |> mutate (run = factor (glue::glue ('Run {x}')))) + result_times_run <- bind_rows (list_times_run) + + list_times_benchmark <- lapply (seq (benchmark_count), function (x) result_times_run |> mutate (benchmark = factor (glue::glue ('Benchmark {x}')))) + result_times_benchmark <- bind_rows (list_times_benchmark) + list_times_vm <- lapply (seq (vm_count), - function (x) result |> mutate ( + function (x) result_times_benchmark |> mutate ( vm_name = factor (glue::glue ('Name {x}')), vm_version = factor (glue::glue ('Version {x}')), vm_configuration = factor (glue::glue ('Configuration {x}')), @@ -35,11 +47,5 @@ rren_artificial <- function (data, vm_count = 1L, run_count = 1L, benchmark_coun result_times_vm <- bind_rows (list_times_vm) - list_times_run <- lapply (seq (run_count), function (x) result_times_vm |> mutate (run = factor (glue::glue ('Run {x}')))) - result_times_run <- bind_rows (list_times_run) - - list_times_benchmark <- lapply (seq (benchmark_count), function (x) result_times_run |> mutate (benchmark = factor (glue::glue ('Benchmark {x}')))) - result_times_benchmark <- bind_rows (list_times_benchmark) - - return (result_times_benchmark) + return (result_times_vm) } diff --git a/R/filter.R b/R/filter.R index 40b43fc..d30b86e 100644 --- a/R/filter.R +++ b/R/filter.R @@ -149,8 +149,8 @@ identify_vector_outliers_window <- function (.input, .window = 333, .limit = 0.0 limits_hi <- limits [2, ] + ranges * .slack # Stretch limits across border samples. - limits_lo <- c (rep.int (first (limits_lo), floor ((.window - 1) / 2)), limits_lo, rep (last (limits_lo), ceiling ((.window - 1) / 2))) - limits_hi <- c (rep.int (first (limits_hi), floor ((.window - 1) / 2)), limits_hi, rep (last (limits_hi), ceiling ((.window - 1) / 2))) + limits_lo <- c (rep.int (first (limits_lo), floor ((.window - 1) / 2)), limits_lo, rep.int (last (limits_lo), ceiling ((.window - 1) / 2))) + limits_hi <- c (rep.int (first (limits_hi), floor ((.window - 1) / 2)), limits_hi, rep.int (last (limits_hi), ceiling ((.window - 1) / 2))) return (.input < limits_lo | .input > limits_hi) } diff --git a/R/interval.R b/R/interval.R index 51c339e..a7c86bb 100644 --- a/R/interval.R +++ b/R/interval.R @@ -1,34 +1,42 @@ # ---------------------------------------------------------------- # Bootstrap -bootstrap_replicates_vector <- function (.input, .statistic, .R) { - # Sample one less than length to compensate variability bias. - # This may not make much sense for some statistics ? - length_reduced <- length (.input) - 1 +bootstrap_replicates_vector <- function (.input, .statistic, .R, .reduction) { + + # Reduction in sample size can help compensate bootstrap standard error bias. + length_original <- length (.input) + length_reduced <- length (.input) - .reduction + result <- rep.int (NA, .R) # TODO This can be made (much) faster by blocking. for (counter in seq.int (1, .R)) { - indices <- sample (length_reduced, replace = TRUE) + indices <- sample (length_original, length_reduced, replace = TRUE) samples <- .input [indices] result [counter] <- .statistic (samples) } + return (result) } -bootstrap_replicates_list_vectors <- function (.input, .statistic_outer, .statistic_inner, .R) { - # Sample one less than length to compensate variability bias. - # This may not make much sense for some statistics ? - length_reduced <- length (.input) - 1 - if (length_reduced < 1) { +bootstrap_replicates_list_vectors <- function (.input, .statistic_outer, .statistic_inner, .R, .reduction) { + + # Reduction in sample size can help compensate bootstrap standard error bias. + length_original <- length (.input) + length_reduced <- length (.input) - .reduction + + if (length_original == 1) { + # Just one outer level, perform one level bootstrap. - result <- bootstrap_replicates_vector (.input [[1]], function (x) .statistic_outer (.statistic_inner (x)), .R) + # Note that this does not reduce sample size in inner level. + result <- bootstrap_replicates_vector (.input [[1]], function (x) .statistic_outer (.statistic_inner (x)), .R, 0) + } else { # More outer levels, perform two level bootstrap. result <- rep.int (NA, .R) for (counter_result in seq.int (1, .R)) { # TODO This can be made (much) faster by blocking. - indices_outer <- sample (length_reduced, replace = TRUE) + indices_outer <- sample (length_original, length_reduced, replace = TRUE) samples_outer <- rep.int (NA, length_reduced) for (counter_outer in seq.int (1, length_reduced)) { index_outer <- indices_outer [counter_outer] @@ -39,6 +47,7 @@ bootstrap_replicates_list_vectors <- function (.input, .statistic_outer, .statis result [counter_result] <- .statistic_outer (samples_outer) } } + return (result) } @@ -52,11 +61,12 @@ bootstrap_replicates_list_vectors <- function (.input, .statistic_outer, .statis #' @param .statistic Statistic to compute confidence interval for. #' @param .confidence Confidence level. #' @param .R Number of replicates. +#' @param .reduction Replicate size reduction. #' @return Tibble with confidence interval. #' @export -compute_vector_flat_percentile_ci <- function (.input, .statistic = mean, .confidence = 0.99, .R = 10000) { +compute_vector_flat_percentile_ci <- function (.input, .statistic = mean, .confidence = 0.99, .R = 10000, .reduction = 0) { - replicates <- bootstrap_replicates_vector (.input, .statistic, .R) + replicates <- bootstrap_replicates_vector (.input, .statistic, .R, .reduction) interval <- stats::quantile (replicates, probs = c ((1 - .confidence)/2, (1 + .confidence)/2)) middle <- .statistic (.input) @@ -71,11 +81,12 @@ compute_vector_flat_percentile_ci <- function (.input, .statistic = mean, .confi #' @param .statistic_inner Statistic to apply at the inner leve. #' @param .confidence Confidence level. #' @param .R Number of replicates. +#' @param .reduction Replicate size reduction. #' @return Tibble with confidence interval. #' @export -compute_list_vectors_hierarchical_percentile_ci <- function (.input, .statistic_outer = mean, .statistic_inner = mean, .confidence = 0.99, .R = 10000) { +compute_list_vectors_hierarchical_percentile_ci <- function (.input, .statistic_outer = mean, .statistic_inner = mean, .confidence = 0.99, .R = 10000, .reduction = 0) { - replicates <- bootstrap_replicates_list_vectors (.input, .statistic_outer, .statistic_inner, .R) + replicates <- bootstrap_replicates_list_vectors (.input, .statistic_outer, .statistic_inner, .R, .reduction) interval <- stats::quantile (replicates, probs = c ((1 - .confidence)/2, (1 + .confidence)/2)) middle <- .statistic_outer (vapply (.input, .statistic_inner, numeric (1))) @@ -83,6 +94,55 @@ compute_list_vectors_hierarchical_percentile_ci <- function (.input, .statistic_ } +#' Compute flat percentile bootstrap confidence interval on data set pair. +#' +#' @param .input_one Data set one to compute with. +#' @param .input_two Data set two to compute with. +#' @param .combination Combination to compute for both data sets. +#' @param .statistic Statistic to compute for each data set. +#' @param .confidence Confidence level. +#' @param .R Number of replicates. +#' @param .reduction Replicate size reduction. +#' @return Tibble with confidence interval. +#' @export +compute_vector_pair_flat_percentile_ci <- function (.input_one, .input_two, .combination = .Primitive ('-'), .statistic = mean, .confidence = 0.99, .R = 10000, .reduction = 0) { + + replicates_one <- bootstrap_replicates_vector (.input_one, .statistic, .R, .reduction) + replicates_two <- bootstrap_replicates_vector (.input_two, .statistic, .R, .reduction) + replicates <- .combination (replicates_one, replicates_two) + interval <- stats::quantile (replicates, probs = c ((1 - .confidence)/2, (1 + .confidence)/2)) + middle <- .combination (.statistic (.input_one), .statistic (.input_two)) + + tibble (lo = interval [1], hi = interval [2], mid = middle) +} + + +#' Compute hierarchical percentile bootstrap confidence interval on data set pair. +#' +#' @param .input_one Data set one to compute with. +#' @param .input_two Data set two to compute with. +#' @param .combination Combination to compute for both data sets. +#' @param .statistic_outer Statistic to compute at the outer level. +#' @param .statistic_inner Statistic to compute at the inner leve. +#' @param .confidence Confidence level. +#' @param .R Number of replicates. +#' @param .reduction Replicate size reduction. +#' @return Tibble with confidence interval. +#' @export +compute_list_vectors_pair_hierarchical_percentile_ci <- function (.input_one, .input_two, .combination = .Primitive ('-'), .statistic_outer = mean, .statistic_inner = mean, .confidence = 0.99, .R = 10000, .reduction = 0) { + + replicates_one <- bootstrap_replicates_list_vectors (.input_one, .statistic_outer, .statistic_inner, .R, .reduction) + replicates_two <- bootstrap_replicates_list_vectors (.input_two, .statistic_outer, .statistic_inner, .R, .reduction) + replicates <- .combination (replicates_one, replicates_two) + interval <- stats::quantile (replicates, probs = c ((1 - .confidence)/2, (1 + .confidence)/2)) + middle <- .combination ( + .statistic_outer (vapply (.input_one, .statistic_inner, numeric (1))), + .statistic_outer (vapply (.input_two, .statistic_inner, numeric (1)))) + + tibble (lo = interval [1], hi = interval [2], mid = middle) +} + + #' Compute flat percentile bootstrap confidence interval. #' #' Uses [compute_vector_flat_percentile_ci()] to compute percentile confidence interval on data that is not structured into runs. @@ -96,7 +156,7 @@ compute_flat_percentile_ci <- function (.input, .column, ...) { assert_renaissance (.input, .check_index = FALSE, .check_total = FALSE, .check_metadata = FALSE) .input |> - group_by (.data $ vm, .data $ benchmark) |> + group_by (.data $ vm, across (starts_with ('vm_')), .data $ benchmark) |> reframe (compute_vector_flat_percentile_ci ({{ .column }}, ...)) } @@ -107,13 +167,81 @@ compute_flat_percentile_ci <- function (.input, .column, ...) { #' #' @param .input Data structured into runs. #' @param .column Column to compute confidence interval for. -#' @param ... Parameters to [compute_vector_flat_percentile_ci()]. +#' @param ... Parameters to [compute_list_vectors_hierarchical_percentile_ci()]. #' @return Summarized tibble with confidence interval columns. #' @export compute_hierarchical_percentile_ci <- function (.input, .column, ...) { assert_renaissance (.input, .check_index = FALSE, .check_total = FALSE, .check_metadata = FALSE) .input |> - group_by (.data $ vm, .data $ benchmark) |> + group_by (.data $ vm, across (starts_with ('vm_')), .data $ benchmark) |> reframe (compute_list_vectors_hierarchical_percentile_ci (split ({{ .column }}, .data $ run, drop = TRUE), ...)) } + + +#' Compute flat relative percentile bootstrap confidence interval. +#' +#' Uses [compute_vector_pair_flat_percentile_ci()] to compute percentile +#' confidence interval on data that is not structured into runs. +#' +#' The statistic is computed relative to baseline virtual machine. +#' +#' @param .input Data not structured into runs. +#' @param .baseline Baseline virtual machine. +#' @param .column Column to compute confidence interval for. +#' @param ... Parameters to [compute_vector_pair_flat_percentile_ci()]. +#' @return Summarized tibble with confidence interval columns. +#' @export +compute_flat_relative_percentile_ci <- function (.input, .baseline, .column, ...) { + assert_renaissance (.input, .check_index = FALSE, .check_total = FALSE, .check_metadata = FALSE) + + # Subset baseline to reduce amount of filtering per benchmark. + baseline_for_vm <- .input |> filter (.data $ vm == .baseline) + + baseline_for_benchmark <- function (benchmark) { + force (benchmark) + baseline <- baseline_for_vm |> filter (.data $ benchmark == .env $ benchmark) + return (baseline |> pull ({{ .column }})) + } + + .input |> + group_by (.data $ vm, across (starts_with ('vm_')), .data $ benchmark) |> + reframe (compute_vector_pair_flat_percentile_ci ( + {{ .column }}, + baseline_for_benchmark (cur_group () $ benchmark), + ...)) +} + + +#' Compute hierarchical relative percentile bootstrap confidence interval. +#' +#' Uses [compute_list_vectors_pair_hierarchical_percentile_ci()] to compute percentile +#' confidence interval on data that is structured into runs. +#' +#' The statistic is computed relative to baseline virtual machine. +#' +#' @param .input Data structured into runs. +#' @param .baseline Baseline virtual machine. +#' @param .column Column to compute confidence interval for. +#' @param ... Parameters to [compute_list_vectors_pair_hierarchical_percentile_ci()]. +#' @return Summarized tibble with confidence interval columns. +#' @export +compute_hierarchical_relative_percentile_ci <- function (.input, .baseline, .column, ...) { + assert_renaissance (.input, .check_index = FALSE, .check_total = FALSE, .check_metadata = FALSE) + + # Subset baseline to reduce amount of filtering per benchmark. + baseline_for_vm <- .input |> filter (.data $ vm == .baseline) + + baseline_for_benchmark <- function (benchmark) { + force (benchmark) + baseline <- baseline_for_vm |> filter (.data $ benchmark == .env $ benchmark) + return (split (baseline_for_vm |> pull ({{ .column }}), baseline_for_vm $ run, drop = TRUE)) + } + + .input |> + group_by (.data $ vm, across (starts_with ('vm_')), .data $ benchmark) |> + reframe (compute_list_vectors_pair_hierarchical_percentile_ci ( + split ({{ .column }}, .data $ run, drop = TRUE), + baseline_for_benchmark (cur_group () $ benchmark), + ...)) +} diff --git a/R/report.R b/R/report.R index 10894a2..dd4a4f0 100644 --- a/R/report.R +++ b/R/report.R @@ -1,5 +1,26 @@ # ---------------------------------------------------------------- -# Reporting +# Labels + +#' Prepare default plot labels. +#' +#' @param data Data to generate labels for. +#' @return Tibble with default plot labels. +#' @export +plot_default_labels <- function (data) { + data |> + distinct (.data $ vm, .data $ vm_name, .data $ vm_version, .data $ vm_configuration) |> + mutate (vm_label = glue ('{vm_name} {vm_version} ({vm})')) |> + arrange (.data $ vm_label) |> + mutate (vm_order = seq.int (1, n ())) |> + mutate (vm_jdk = NA) |> + relocate ( + .data $ vm_label, .data $ vm_order, .data $ vm_jdk, + .data $ vm, .data $ vm_name, .data $ vm_version, .data $ vm_configuration) +} + + +# ---------------------------------------------------------------- +# Reporting summaries #' Group helper for report result summaries. #' @@ -13,29 +34,43 @@ report_summaries_benchmark_group_helper <- function (group, key) { # Summarize every numeric column except index and total with time first. metrics <- c ('time', sort (setdiff (names (group |> select_if (is.numeric)), c ('index', 'time', 'total')))) + SEPARATOR <- ' ' WIDTH_VALUES <- 24 WIDTH_METRIC <- min (max (c (8, str_length (metrics))), console_width () - 2*WIDTH_VALUES - 8) cli_h2 (key $ benchmark) - cat_line (sprintf (glue ('%-{WIDTH_METRIC}s %-{WIDTH_VALUES}s %-{WIDTH_VALUES}s'), 'metric', 'mean', 'median')) + cli_verbatim (glue ( + '{style_bold (ansi_align ("metric", WIDTH_METRIC))}', + SEPARATOR, + '{style_bold (ansi_align ("mean", WIDTH_VALUES))}', + SEPARATOR, + '{style_bold (ansi_align ("median", WIDTH_VALUES))}', + )) + + format_ci <- function (ci) { + mid_textual <- style_bold (pretty_num (ci $ mid, style = '6')) + lo_textual <- str_trim (pretty_num (ci $ lo, style = '6')) + hi_textual <- str_trim (pretty_num (ci $ hi, style = '6')) + ci_textual <- glue ('{mid_textual} {col_silver ("(")}{lo_textual} {col_silver ("-")} {hi_textual}{col_silver (")")}') + ci_aligned <- ansi_align (ci_textual, WIDTH_VALUES) + + return (ci_aligned) + } for (metric in metrics) { ci_mean <- compute_hierarchical_percentile_ci (group, .data [[metric]], base::mean, base::mean) ci_median <- compute_hierarchical_percentile_ci (group, .data [[metric]], stats::median, stats::median) - cat_line (sprintf (glue ('%-{WIDTH_METRIC}s %s (%s - %s) %s (%s - %s)'), - str_trunc (metric, WIDTH_METRIC, 'center'), - pretty_num (ci_mean $ mid, style = '6'), - pretty_num (ci_mean $ lo, style = '6'), - pretty_num (ci_mean $ hi, style = '6'), - pretty_num (ci_median $ mid, style = '6'), - pretty_num (ci_median $ lo, style = '6'), - pretty_num (ci_median $ hi, style = '6'))) + cli_verbatim (glue ( + '{ansi_align (ansi_strtrim (metric, WIDTH_METRIC), WIDTH_METRIC)}', + SEPARATOR, + '{format_ci (ci_mean)}', + SEPARATOR, + '{format_ci (ci_median)}', + )) } - - cat_line () } @@ -87,3 +122,144 @@ report_summaries <- function (input = '.', warmup = 5*60) { cli_rule () } + + +# ---------------------------------------------------------------- +# Plotting summaries + +plot_website_stripes_group_helper <- function (group, key) { + + STRIPE_ROWS <- 2 + STRIPE_WIDTH <- 400 + STRIPE_HEIGHT <- 250 + + # Group walk calls us once even with empty tibble. + if (nrow (group) == 0) return () + + # Compute confidence intervals relative to baseline. + baseline <- group |> distinct (.data $ vm, .data $ vm_order) |> filter (.data $ vm_order == min (.data $ vm_order)) |> pull (.data $ vm) + relative <- compute_hierarchical_relative_percentile_ci (group, baseline, .data $ time, .combination = .Primitive ('/')) + + nice <- ggplot (relative, + aes ( + x = fct_reorder (.data $ vm_label, .data $ vm_order), + y = 100 / .data $ mid, + ymin = 100 / .data $ hi, + ymax = 100 / .data $ lo, + fill = fct_reorder (.data $ vm_label, .data $ vm_order))) + + geom_col () + + geom_errorbar (width = 0.5, color = '#555555') + + facet_wrap (vars (.data $ benchmark), nrow = STRIPE_ROWS, scales = 'free_y', strip.position = 'bottom') + + labs (x = NULL, y = 'Average throughput relative to baseline [%]', fill = 'JVM implementation') + + theme ( + text = element_text (family = 'Serif', color = '#555555'), + legend.position = 'bottom', + axis.text.x = element_blank (), + axis.ticks.x = element_blank (), + axis.title.y = element_text (size = 14, margin = margin (r = 10)), + strip.text.x = element_text (angle = 90, vjust = 0.5, hjust = 1, size = 14, color = '#555555'), + strip.background = element_blank (), + legend.text = element_text (size = 14), + legend.title = element_text (size = 14), + legend.background = element_rect (fill = 'transparent', color = NA), + legend.box.background = element_rect (fill = 'transparent', color = NA), + plot.background = element_rect (fill = 'transparent', color = NA)) + + ggsave (glue ('stripe-jdk-{key $ vm_jdk}.png'), nice, width = STRIPE_WIDTH, height = STRIPE_HEIGHT, units = 'mm', bg = 'transparent') + + readr::write_csv (group, glue ('summary-jdk-{key $ vm_jdk}.csv')) +} + + +#' Plot stripe image used on benchmark website. +#' +#' @param input Data path or data tibble to summarize. +#' @param warmup Duration to discard as warm up time. +#' @param labels Labels file or labels tibble. +#' +#' @examples +#' data <- load_path_json (rren_example ()) +#' # Edit labels manually to provide JDK version. +#' labels <- plot_default_labels (data) +#' plot_website_stripes (data, labels = labels) +#' +#' @export +plot_website_stripes <- function (input = '.', warmup = 5*60, labels = 'labels.csv') { + + # To offer maximum simplicity in use, load data if input is data path. + if (is.character (input)) input <- load_path_json (input) + if (is.character (labels)) labels <- readr::read_csv (labels, col_types = readr::cols (vm_jdk = 'i', vm_order = 'i', .default = 'f')) + + input |> + # Drop warm up data. + filter (.data $ total >= warmup) |> + # Reduce data volume. + select (.data $ vm, starts_with ('vm_'), .data $ benchmark, .data $ run, .data $ index, .data $ time) |> + # Inject labels. + left_join (labels, by = c ('vm', 'vm_name', 'vm_version', 'vm_configuration')) |> + # Plot. + group_by (.data $ vm_jdk) |> + group_walk (plot_website_stripes_group_helper) +} + + +plot_website_violins_group_helper <- function (group, key) { + + PLOT_ROWS <- 4 + PLOT_WIDTH <- 300 + PLOT_HEIGHT <- 300 + + # Group walk calls us once even with empty tibble. + if (nrow (group) == 0) return () + + nice <- ggplot (group, + aes ( + x = fct_reorder (.data $ vm_label, .data $ vm_order), + y = .data $ time, + fill = fct_reorder (.data $ vm_label, .data $ vm_order))) + + geom_violin (scale = 'width', width = 1) + + geom_boxplot (width = 0.2) + + facet_wrap (vars (.data $ benchmark), nrow = PLOT_ROWS, scales = 'free_y') + + theme (legend.position = 'none', axis.text.x = element_text (angle = 90, vjust = 0.5, hjust = 1)) + + labs ( + x = NULL, + y = 'Single repetition time [s]', + title = glue ('Warm repetition time distribution except outliers on JDK {key $ vm_jdk}')) + + scale_fill_brewer (palette = 'Blues', type = 'qual') + + ggsave (glue ('violin-jdk-{key $ vm_jdk}.png'), nice, width = PLOT_WIDTH, height = PLOT_HEIGHT, units = 'mm') +} + + +#' Plot violin image used on benchmark website. +#' +#' @param input Data path or data tibble to summarize. +#' @param warmup Duration to discard as warm up time. +#' @param labels Labels file or labels tibble. +#' +#' @examples +#' data <- load_path_json (rren_example ()) +#' # Edit labels manually to provide JDK version. +#' labels <- plot_default_labels (data) +#' plot_website_violins (data, labels = labels) +#' +#' @export +plot_website_violins <- function (input = '.', warmup = 5*60, labels = 'labels.csv') { + + # To offer maximum simplicity in use, load data if input is data path. + if (is.character (input)) input <- load_path_json (input) + if (is.character (labels)) labels <- readr::read_csv (labels, col_types = readr::cols (vm_jdk = 'i', vm_order = 'i', .default = 'f')) + + input |> + # Drop warm up data. + filter (.data $ total >= warmup) |> + # Reduce data volume. + select (.data $ vm, starts_with ('vm_'), .data $ benchmark, .data $ run, .data $ index, .data $ time) |> + # Filter outliers. + remove_outliers_window (.data $ time) |> + # Inject labels. + left_join (labels, by = c ('vm', 'vm_name', 'vm_version', 'vm_configuration')) |> + # Plot. + group_by (.data $ vm_jdk) |> + group_walk (plot_website_violins_group_helper) +} diff --git a/R/rren-package.R b/R/rren-package.R index 47e6153..06407b2 100644 --- a/R/rren-package.R +++ b/R/rren-package.R @@ -5,6 +5,8 @@ #' @import utils #' @import logger #' @import tibble +#' @import forcats +#' @import ggplot2 #' @import stringr #' @import checkmate #' @import prettyunits diff --git a/README.md b/README.md index c5ab8a4..270bcc8 100644 --- a/README.md +++ b/README.md @@ -30,7 +30,7 @@ GC before operation: completed in 62.114 ms, heap usage 188.729 MB -> 77.885 MB. ── scrabble ── metric mean median -time 388 m ( 371 m - 415 m) 373 m ( 363 m - 392 m) +time 388 m (371 m - 415 m) 373 m (363 m - 392 m) ──────────────────────────────────────────────────────────────────────────────── ``` diff --git a/_pkgdown.yml b/_pkgdown.yml index e57377b..2bbf701 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -15,7 +15,9 @@ reference: contents: - matches ('^(compute)_trends') - matches ('^(compute)_(flat|hierarchical)_percentile_ci') + - matches ('^(compute)_(flat|hierarchical)_relative_percentile_ci') - matches ('^(compute)_(vector_flat|list_vectors_hierarchical)_percentile_ci') + - matches ('^(compute)_(vector_pair_flat|list_vectors_pair_hierarchical)_percentile_ci') - matches ('^(locate|identify)_vector_segments$') - matches ('^(list)_dimensions$') - matches ('^(list)_segment_boundaries$') @@ -25,6 +27,8 @@ reference: - rren_example - rren_artificial - report_summaries + - plot_default_labels + - matches ('plot_website_(stripes|violins)') - title: internal contents: diff --git a/docs/404.html b/docs/404.html index 29e3f7d..51d2dda 100644 --- a/docs/404.html +++ b/docs/404.html @@ -24,7 +24,7 @@ rren - 0.0.7 + 0.0.8 + + + + + +
+
+
+ +
+

Uses compute_vector_pair_flat_percentile_ci() to compute percentile +confidence interval on data that is not structured into runs.

+
+ +
+

Usage

+
compute_flat_relative_percentile_ci(.input, .baseline, .column, ...)
+
+ +
+

Arguments

+
.input
+

Data not structured into runs.

+ + +
.baseline
+

Baseline virtual machine.

+ + +
.column
+

Column to compute confidence interval for.

+ + +
...
+

Parameters to compute_vector_pair_flat_percentile_ci().

+ +
+
+

Value

+ + +

Summarized tibble with confidence interval columns.

+
+
+

Details

+

The statistic is computed relative to baseline virtual machine.

+
+ +
+ + +
+ + + + + + + diff --git a/docs/reference/compute_hierarchical_percentile_ci.html b/docs/reference/compute_hierarchical_percentile_ci.html index 3f85bd6..84cc5bc 100644 --- a/docs/reference/compute_hierarchical_percentile_ci.html +++ b/docs/reference/compute_hierarchical_percentile_ci.html @@ -10,7 +10,7 @@ rren - 0.0.7 + 0.0.8 + + + + + +
+
+
+ +
+

Uses compute_list_vectors_pair_hierarchical_percentile_ci() to compute percentile +confidence interval on data that is structured into runs.

+
+ +
+

Usage

+
compute_hierarchical_relative_percentile_ci(.input, .baseline, .column, ...)
+
+ +
+

Arguments

+
.input
+

Data structured into runs.

+ + +
.baseline
+

Baseline virtual machine.

+ + +
.column
+

Column to compute confidence interval for.

+ + +
...
+

Parameters to compute_list_vectors_pair_hierarchical_percentile_ci().

+ +
+
+

Value

+ + +

Summarized tibble with confidence interval columns.

+
+
+

Details

+

The statistic is computed relative to baseline virtual machine.

+
+ +
+ + +
+ + + + + + + diff --git a/docs/reference/compute_list_vectors_hierarchical_percentile_ci.html b/docs/reference/compute_list_vectors_hierarchical_percentile_ci.html index ddc3084..c1a05a0 100644 --- a/docs/reference/compute_list_vectors_hierarchical_percentile_ci.html +++ b/docs/reference/compute_list_vectors_hierarchical_percentile_ci.html @@ -10,7 +10,7 @@ rren - 0.0.7 + 0.0.8 + + + + + +
+
+
+ +
+

Compute hierarchical percentile bootstrap confidence interval on data set pair.

+
+ +
+

Usage

+
compute_list_vectors_pair_hierarchical_percentile_ci(
+  .input_one,
+  .input_two,
+  .combination = .Primitive("-"),
+  .statistic_outer = mean,
+  .statistic_inner = mean,
+  .confidence = 0.99,
+  .R = 10000,
+  .reduction = 0
+)
+
+ +
+

Arguments

+
.input_one
+

Data set one to compute with.

+ + +
.input_two
+

Data set two to compute with.

+ + +
.combination
+

Combination to compute for both data sets.

+ + +
.statistic_outer
+

Statistic to compute at the outer level.

+ + +
.statistic_inner
+

Statistic to compute at the inner leve.

+ + +
.confidence
+

Confidence level.

+ + +
.R
+

Number of replicates.

+ + +
.reduction
+

Replicate size reduction.

+ +
+
+

Value

+ + +

Tibble with confidence interval.

+
+ +
+ + +
+ + + + + + + diff --git a/docs/reference/compute_trends.html b/docs/reference/compute_trends.html index 8025bbd..bf3f2c3 100644 --- a/docs/reference/compute_trends.html +++ b/docs/reference/compute_trends.html @@ -10,7 +10,7 @@ rren - 0.0.7 + 0.0.8 + + + + + +
+
+
+ +
+

Compute flat percentile bootstrap confidence interval on data set pair.

+
+ +
+

Usage

+
compute_vector_pair_flat_percentile_ci(
+  .input_one,
+  .input_two,
+  .combination = .Primitive("-"),
+  .statistic = mean,
+  .confidence = 0.99,
+  .R = 10000,
+  .reduction = 0
+)
+
+ +
+

Arguments

+
.input_one
+

Data set one to compute with.

+ + +
.input_two
+

Data set two to compute with.

+ + +
.combination
+

Combination to compute for both data sets.

+ + +
.statistic
+

Statistic to compute for each data set.

+ + +
.confidence
+

Confidence level.

+ + +
.R
+

Number of replicates.

+ + +
.reduction
+

Replicate size reduction.

+ +
+
+

Value

+ + +

Tibble with confidence interval.

+
+ +
+ + +
+ + + + + + + diff --git a/docs/reference/expect_renaissance.html b/docs/reference/expect_renaissance.html index 4f06559..ef011e6 100644 --- a/docs/reference/expect_renaissance.html +++ b/docs/reference/expect_renaissance.html @@ -10,7 +10,7 @@ rren - 0.0.7 + 0.0.8 + + + + + +
+
+
+ +
+

Prepare default plot labels.

+
+ +
+

Usage

+
plot_default_labels(data)
+
+ +
+

Arguments

+
data
+

Data to generate labels for.

+ +
+
+

Value

+ + +

Tibble with default plot labels.

+
+ +
+ + +
+ + + + + + + diff --git a/docs/reference/plot_website_stripes.html b/docs/reference/plot_website_stripes.html new file mode 100644 index 0000000..58ec7af --- /dev/null +++ b/docs/reference/plot_website_stripes.html @@ -0,0 +1,97 @@ + +Plot stripe image used on benchmark website. — plot_website_stripes • rren + Skip to contents + + +
+
+
+ +
+

Plot stripe image used on benchmark website.

+
+ +
+

Usage

+
plot_website_stripes(input = ".", warmup = 5 * 60, labels = "labels.csv")
+
+ +
+

Arguments

+
input
+

Data path or data tibble to summarize.

+ + +
warmup
+

Duration to discard as warm up time.

+ + +
labels
+

Labels file or labels tibble.

+ +
+ +
+

Examples

+
data <- load_path_json (rren_example ())
+# Edit labels manually to provide JDK version.
+labels <- plot_default_labels (data)
+plot_website_stripes (data, labels = labels)
+
+
+
+
+ + +
+ + + + + + + diff --git a/docs/reference/plot_website_violins.html b/docs/reference/plot_website_violins.html new file mode 100644 index 0000000..1d968d5 --- /dev/null +++ b/docs/reference/plot_website_violins.html @@ -0,0 +1,97 @@ + +Plot violin image used on benchmark website. — plot_website_violins • rren + Skip to contents + + +
+
+
+ +
+

Plot violin image used on benchmark website.

+
+ +
+

Usage

+
plot_website_violins(input = ".", warmup = 5 * 60, labels = "labels.csv")
+
+ +
+

Arguments

+
input
+

Data path or data tibble to summarize.

+ + +
warmup
+

Duration to discard as warm up time.

+ + +
labels
+

Labels file or labels tibble.

+ +
+ +
+

Examples

+
data <- load_path_json (rren_example ())
+# Edit labels manually to provide JDK version.
+labels <- plot_default_labels (data)
+plot_website_violins (data, labels = labels)
+
+
+
+
+ + +
+ + + + + + + diff --git a/docs/reference/preserve_last_n.html b/docs/reference/preserve_last_n.html index 68176c7..64153d7 100644 --- a/docs/reference/preserve_last_n.html +++ b/docs/reference/preserve_last_n.html @@ -16,7 +16,7 @@ rren - 0.0.7 + 0.0.8