Skip to content

Commit

Permalink
multiqc: include more metrics in map
Browse files Browse the repository at this point in the history
  • Loading branch information
pdiakumis committed Sep 25, 2023
1 parent cc82391 commit a83bd4c
Show file tree
Hide file tree
Showing 7 changed files with 207 additions and 6 deletions.
5 changes: 3 additions & 2 deletions R/ica.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,15 +8,16 @@
#' @param include Use PresignedUrl to include presigned URLs to all files within
#' @param page_size Page size (def: 100).
#' the GDS directory.
#' @param regexes Tibble with regex and function name.
#'
#' @return A tibble with type, bname, size, file_id, path, and presigned URL.
#' @export
gds_files_list_filter_relevant <- function(gdsdir, token, pattern = NULL, include = NULL, page_size = 100) {
gds_files_list_filter_relevant <- function(gdsdir, token, pattern = NULL, include = NULL, page_size = 100, regexes = DR_FILE_REGEX) {
pattern <- pattern %||% ".*" # keep all recognisable files by default
cols_sel <- c("type", "bname", "size", "file_id", "path", "presigned_url")
d <- dracarys::gds_files_list(gdsdir, token, include = include, page_size = page_size) |>
dplyr::rowwise() |>
dplyr::mutate(type = purrr::map_chr(.data$bname, match_regex)) |>
dplyr::mutate(type = purrr::map_chr(.data$bname, \(x) match_regex(x, regexes))) |>
dplyr::ungroup() |>
dplyr::filter(!is.na(.data$type), grepl(pattern, .data$type)) |>
dplyr::select(dplyr::any_of(cols_sel))
Expand Down
2 changes: 1 addition & 1 deletion R/multiqc.R
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,7 @@ multiqc_rename_cols <- function(d) {
rename_vec <- purrr::set_names(m[["raw"]], m[["clean"]])
d <- dplyr::rename(d, !!!rename_vec)
}
return(d)
return(dplyr::distinct(d))
}

.multiqc_guess_workflow <- function(p) {
Expand Down
2 changes: 2 additions & 0 deletions R/portal_meta.R
Original file line number Diff line number Diff line change
Expand Up @@ -462,6 +462,7 @@ meta_main_cols <- function() {
#' @param params String containing additional params to pass to the `/workflows`
#' endpoint, e.g. `'&type_name=bclconvert'`.
#' @param pmeta Path to downloaded portal metadata file, or already parsed metadata tibble.
#' @param account UMCCR portal account (one of "prod", "dev", "stg").
#'
#' @return A tibble of the results from the given query.
#' @export
Expand All @@ -471,6 +472,7 @@ meta_main_cols <- function() {
#' portal_meta_read(params = "&type_name=rnasum", rows = 4)
#' }
portal_meta_read <- function(pmeta = NULL, rows = 100, params = "", account = "prod") {
assertthat::assert_that(account %in% c("prod", "dev", "stg"))
au_tz <- "Australia/Melbourne"
utc_tz <- "UTC"
if (!is.null(pmeta)) {
Expand Down
193 changes: 193 additions & 0 deletions inst/extdata/multiqc_column_map.tsv

Large diffs are not rendered by default.

5 changes: 4 additions & 1 deletion man/gds_files_list_filter_relevant.Rd

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

4 changes: 3 additions & 1 deletion man/portal_meta_read.Rd

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

2 changes: 1 addition & 1 deletion tests/testthat/test-roxytest-testexamples-multiqc.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@

# File R/multiqc.R: @testexamples

test_that("Function multiqc_date_fmt() @ L279", {
test_that("Function multiqc_date_fmt() @ L284", {

cdate <- "2023-04-07, 09:09 UTC"
(res1 <- multiqc_date_fmt(cdate))
Expand Down

0 comments on commit a83bd4c

Please sign in to comment.