Skip to content

Commit

Permalink
Merge pull request #114 from umccr/interopqc
Browse files Browse the repository at this point in the history
Interopqc MultiQC JSON support
  • Loading branch information
pdiakumis authored Apr 15, 2024
2 parents 35ae4b6 + 799967e commit 92b072f
Show file tree
Hide file tree
Showing 8 changed files with 71 additions and 1,012 deletions.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,7 @@ export(multiqc_parse_bargraph_plot)
export(multiqc_parse_gen)
export(multiqc_parse_plots)
export(multiqc_parse_raw)
export(multiqc_parse_raw_interop)
export(multiqc_parse_xyline_plot)
export(multiqc_parse_xyline_plot_contig_cvg)
export(multiqc_tidy_json)
Expand Down
52 changes: 52 additions & 0 deletions R/multiqc.R
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,11 @@ multiqc_tidy_json <- function(j) {
# use raw instead
return(dracarys::multiqc_parse_raw(p))
}
if (workflow == "interop") {
# general_stats_data is empty
# use raw instead
return(dracarys::multiqc_parse_raw_interop(p))
}
d <- d |>
# get rid of duplicated elements - see umccr/dracarys#96
purrr::map(\(x) {
Expand Down Expand Up @@ -190,6 +195,9 @@ multiqc_rename_cols <- function(d) {
if (length(ds) == 1 && ds == "bclconvert") {
return("bcl_convert")
}
if (length(ds) == 1 && ds == "Illumina InterOp Statistics") {
return("interop")
}
return("UNKNOWN")
}

Expand Down Expand Up @@ -241,6 +249,50 @@ multiqc_parse_raw <- function(p) {
dplyr::bind_rows(.id = "multiqc_tool")
}

#' Parse Interop MultiQC 'report_saved_raw_data' JSON Element
#'
#' Parses Interop MultiQC 'report_saved_raw_data' JSON Element.
#' @param p Parsed Interop MultiQC JSON.
#' @return A list with summary and per-lane tibbles.
#' @export
multiqc_parse_raw_interop <- function(p) {
x <- p[["report_saved_raw_data"]]
tool_nms <- names(x)
assertthat::assert_that(length(tool_nms) == 1, tool_nms == "interop_runsummary")
res <- list()
d <- x[[tool_nms]]
assertthat::assert_that(length(d) == 1, names(d) == "interop")
d <- d[["interop"]]
assertthat::assert_that(length(d) == 2, all(names(d) %in% c("summary", "details")))
# read metrics summary
d_sumy <- d[["summary"]] |>
purrr::map(\(x) unlist(x) |> tibble::as_tibble_row()) |>
dplyr::bind_rows(.id = "Read")
# read metrics per lane
dbl_cols <- c(
"Tiles", "Density", "Cluster PF",
"Reads", "Reads PF", "%>=Q30",
"Yield", "Aligned", "Error",
"Error (35)", "Error (75)", "Error (100)",
"% Occupied", "Intensity C1"
)
d_det <- d[["details"]] |>
purrr::discard(\(x) length(x) == 0) |>
purrr::map(\(x) {
tibble::as_tibble_row(x) |>
dplyr::mutate(dplyr::across(dplyr::everything(), .fns = as.character))
}) |>
dplyr::bind_rows(.id = "Lane-Read") |>
dplyr::arrange(.data$`Lane-Read`) |>
dplyr::mutate(dplyr::across(dplyr::all_of(dbl_cols), .fns = as.numeric)) |>
dplyr::mutate(dplyr::across(dplyr::all_of(dbl_cols), ~ replace(.x, is.nan(.x), NA_real_)))
list(
summary = d_sumy,
per_lane = d_det
)
}


# From https://github.com/multimeric/TidyMultiqc
multiqc_kv_map <- function(l, func, map_keys = FALSE) {
mapper <- ifelse(map_keys, purrr::imap, purrr::map)
Expand Down
210 changes: 0 additions & 210 deletions inst/rmd/multiqc/multi.Rmd

This file was deleted.

67 changes: 0 additions & 67 deletions inst/rmd/pcgr/pcgr_multi.Rmd

This file was deleted.

1 change: 0 additions & 1 deletion inst/rmd/umccr_portal/.gitignore

This file was deleted.

Loading

0 comments on commit 92b072f

Please sign in to comment.