From ca4aafa34d79124e078b0175a66d0ff050a69b94 Mon Sep 17 00:00:00 2001 From: pdiakumis Date: Mon, 6 May 2024 17:34:41 +1000 Subject: [PATCH 1/8] devtools check/styler - part1 --- R/purple.R | 80 +++++++++---------- R/sv.R | 36 ++++----- R/umccrise.R | 2 +- man/cancer_rmd.Rd | 1 + man/purple_cnv_som_gene_process.Rd | 4 +- .../test-roxytest-testexamples-purple.R | 8 +- 6 files changed, 64 insertions(+), 67 deletions(-) diff --git a/R/purple.R b/R/purple.R index 713e20c..5881d70 100644 --- a/R/purple.R +++ b/R/purple.R @@ -124,7 +124,6 @@ purple_cnv_som_gene_process <- function(x, g = NULL) { } sash_read_cnv_tsv <- function(x) { - nm <- c( "chromosome" = "c", "start" = "i", @@ -152,7 +151,6 @@ sash_read_cnv_tsv <- function(x) { } filter_and_split_annotations_cnv <- function(x) { - filter_conditions <- list( # Chromosome effects stringr::str_starts(x$Detail, "chrom_"), @@ -162,34 +160,34 @@ filter_and_split_annotations_cnv <- function(x) { x.grouped <- x |> dplyr::group_by( - filter=ifelse(purrr::reduce(filter_conditions, `|`), "filter", "retain") + filter = ifelse(purrr::reduce(filter_conditions, `|`), "filter", "retain") ) keys <- x.grouped |> dplyr::group_keys() |> - dplyr::pull(filter) + dplyr::pull("filter") x.split <- x.grouped |> - dplyr::group_split(.keep=FALSE) |> + dplyr::group_split(.keep = FALSE) |> purrr::set_names(keys) list( retained = purrr::pluck(x.split, "retain"), - filtered = purrr::pluck(x.split, "filter") |> dplyr::arrange(Tier, `Event ID`) + filtered = purrr::pluck(x.split, "filter") |> dplyr::arrange("Tier", "Event ID") ) } collapse_effect_group <- function(x) { x.tmp <- dplyr::first(x) genes <- x.tmp |> - dplyr::pull(Genes.unique) |> + dplyr::pull("Genes.unique") |> unlist() x.tmp |> dplyr::mutate( - Genes = paste0(genes, collapse=", "), + Genes = paste0(genes, collapse = ", "), Transcripts = "", - Detail = paste0(unique(x$Detail) |> sort(), collapse=", "), + Detail = paste0(unique(x$Detail) |> sort(), collapse = ", "), Tier = min(x$Tier), `Annotation ID` = NA, ) @@ -201,16 +199,16 @@ set_many_genes_cnv <- function(x) { x.counts <- x |> dplyr::group_by(`Event ID`, Effect) |> dplyr::mutate( - Genes.unique = Genes |> stringr::str_split(", ") |> unlist() |> unique() |> list(), - `Gene count (effect group)` = Genes.unique |> dplyr::first() |> length(), - collapse = `Gene count (effect group)` > 2 & Effect %in% collapse_effects, + Genes.unique = .data$Genes |> stringr::str_split(", ") |> unlist() |> unique() |> list(), + `Gene count (effect group)` = .data$Genes.unique |> dplyr::first() |> length(), + collapse = .data$`Gene count (effect group)` > 2 & .data$Effect %in% collapse_effects, ) |> - dplyr::select(-`Gene count (effect group)`) + dplyr::select(-"Gene count (effect group)") # Collapse target groups x.collapsed <- x.counts |> dplyr::filter(collapse) |> - dplyr::select(-collapse) |> + dplyr::select(-"collapse") |> dplyr::group_modify(~ collapse_effect_group(.x)) |> # Update top tier, referring to complete data set within each group dplyr::mutate( @@ -226,7 +224,7 @@ set_many_genes_cnv <- function(x) { x.tmp <- x.counts |> dplyr::filter(!collapse) |> dplyr::bind_rows(x.collapsed) |> - dplyr::select(-c(collapse, Genes.unique, Tier)) |> + dplyr::select(-c("collapse", "Genes.unique", "Tier")) |> dplyr::rowwise() |> dplyr::mutate( `Gene count` = Genes |> stringr::str_split(", ") |> unlist() |> unique() |> length(), @@ -267,7 +265,7 @@ set_many_genes_cnv <- function(x) { ), Transcripts = ifelse(many_genes == "few_genes" | is.na(many_genes), Transcripts, ""), ) |> - dplyr::select(-c(many_genes, `Gene count`)) + dplyr::select(-c("many_genes", "Gene count")) list( ready = x.ready, @@ -314,7 +312,7 @@ set_many_transcripts_cnv <- function(x) { paste0("Many transcripts (", `Transcript count`, ")") ) ) |> - dplyr::select(-c(many_transcripts, `Transcript count`)) + dplyr::select(-c("many_transcripts", "Transcript count")) list( ready = x.ready, @@ -330,29 +328,27 @@ process_cnv_tsv <- function(x) { # Prepare input cnv.ready <- cnv.input |> dplyr::mutate( - chrom_simple = stringr::str_remove(chromosome, "chr"), - start = paste(chrom_simple, base::format(start, big.mark = ",", trim = TRUE), sep=":"), - end = paste(chrom_simple, base::format(end, big.mark = ",", trim = TRUE), sep=":"), + chrom_simple = stringr::str_remove(.data$chromosome, "chr"), + start = paste(.data$chrom_simple, base::format(.data$start, big.mark = ",", trim = TRUE), sep = ":"), + end = paste(.data$chrom_simple, base::format(.data$end, big.mark = ",", trim = TRUE), sep = ":"), ) |> - dplyr::select(-c( - chromosome, - chrom_simple, - )) + dplyr::select(-c("chromosome", "chrom_simple")) # Melt annotations cnv.tmp <- cnv.ready |> dplyr::mutate(`Event ID` = dplyr::row_number()) |> # Split into individual annotations - dplyr::mutate(annotation = strsplit(simple_ann, ",")) |> + dplyr::mutate(annotation = strsplit(.data$simple_ann, ",")) |> # Convert annotation fields into columns - tidyr::unnest(annotation) |> + tidyr::unnest("annotation") |> tidyr::separate( - annotation, c("Event", "Effect", "Genes", "Transcripts", "Detail", "Tier"), + "annotation", + c("Event", "Effect", "Genes", "Transcripts", "Detail", "Tier"), sep = "\\|", convert = FALSE ) |> # Create new columns and modify existing ones dplyr::mutate( - copyNumber = as.numeric(copyNumber) |> round(2) %>% sprintf("%.2f", .), + copyNumber = as.numeric(.data$copyNumber) |> round(2) %>% sprintf("%.2f", .), minorAlleleCopyNumber = as.numeric(minorAlleleCopyNumber) |> round(2) %>% sprintf("%.2f", .), majorAlleleCopyNumber = as.numeric(majorAlleleCopyNumber) |> round(2) %>% sprintf("%.2f", .), "PURPLE CN Min+Maj" = paste0(minorAlleleCopyNumber, "+", majorAlleleCopyNumber), @@ -361,18 +357,18 @@ process_cnv_tsv <- function(x) { ) |> # Remove unused columns dplyr::select(-c( - baf, - bafCount, - depthWindowCount, - Event, - gcContent, - majorAlleleCopyNumber, - method, - minorAlleleCopyNumber, - segmentEndSupport, - segmentStartSupport, - sv_top_tier, - simple_ann, + "baf", + "bafCount", + "depthWindowCount", + "Event", + "gcContent", + "majorAlleleCopyNumber", + "method", + "minorAlleleCopyNumber", + "segmentEndSupport", + "segmentStartSupport", + "sv_top_tier", + "simple_ann", )) # Abbreviate effects @@ -411,7 +407,7 @@ process_cnv_tsv <- function(x) { "PURPLE CN" = "copyNumber", "PURPLE CN Min+Maj" ) - cnv.tmp <- dplyr::select(cnv.tmp, tidyselect::all_of(c(column_selector, "Tier"))) + cnv.tmp <- dplyr::select("cnv.tmp", tidyselect::all_of(c(column_selector, "Tier"))) cnv.filtered <- dplyr::select(cnv.annotations.split$filtered, tidyselect::any_of(column_selector)) # Collapse selected annotations and set many genes @@ -744,7 +740,7 @@ purple_kataegis <- function(x) { data <- d$data |> dplyr::filter(!is.na(.data$KT)) |> - dplyr::select(c("CHROM", "POS", info_cols)) + dplyr::select(c("CHROM", "POS", tidyselect::all_of(info_cols))) description <- d$description |> dplyr::filter(.data$ID %in% info_cols) |> diff --git a/R/sv.R b/R/sv.R index 69df9ec..9afdda8 100644 --- a/R/sv.R +++ b/R/sv.R @@ -126,7 +126,6 @@ abbreviate_effect <- function(effects) { } sash_read_sv_tsv <- function(x) { - tab <- dplyr::tribble( ~Column, ~Description, ~Type, "chrom", "CHROM column in VCF", "c", @@ -162,11 +161,11 @@ sash_read_sv_tsv <- function(x) { } split_svs <- function(x) { - bps_types <- c("BND", "DEL", "DUP"," INS", "INV") + bps_types <- c("BND", "DEL", "DUP", " INS", "INV") x.grouped <- x |> dplyr::group_by( - record_type=ifelse(Type %in% bps_types, "bps", "other") + record_type = ifelse(Type %in% bps_types, "bps", "other") ) keys <- x.grouped |> @@ -174,7 +173,7 @@ split_svs <- function(x) { dplyr::pull(record_type) x.split <- x.grouped |> - dplyr::group_split(.keep=FALSE) |> + dplyr::group_split(.keep = FALSE) |> purrr::set_names(keys) list( @@ -186,8 +185,8 @@ split_svs <- function(x) { join_breakpoint_entries <- function(x) { # Group by GRIDSS identifier (clipping trailing h/o [h: High, o: lOwer]) bps <- x |> - tidyr::separate(ID, into = c("BND_group", "BND_mate"), sep = -1, convert = TRUE, remove = FALSE)|> - dplyr::group_by(BND_group) + tidyr::separate("ID", into = c("BND_group", "BND_mate"), sep = -1, convert = TRUE, remove = FALSE) |> + dplyr::group_by("BND_group") # Set a sequential breakpoint identifier bps_groups <- bps |> dplyr::n_groups() @@ -195,15 +194,17 @@ join_breakpoint_entries <- function(x) { dplyr::mutate( # Assign a unique ID based on current group BND_ID = sprintf(paste0("%0", nchar(bps_groups), "d"), dplyr::cur_group_id()), - BND_mate = ifelse(BND_mate == "o", "A", "B"), + BND_mate = ifelse(.data$BND_mate == "o", "A", "B"), ) |> dplyr::ungroup() |> dplyr::mutate( - end_position = sub("^.*:(\\d+).*$", "\\1", ALT) |> as.numeric() |> base::format(big.mark = ",", trim = TRUE), - end_chrom = sub("^.*chr(.*):.*$", "\\1", ALT), - end = paste0(end_chrom, ":", end_position), + end_position = sub("^.*:(\\d+).*$", "\\1", .data$ALT) |> + as.numeric() |> + base::format(big.mark = ",", trim = TRUE), + end_chrom = sub("^.*chr(.*):.*$", "\\1", .data$ALT), + end = paste0(.data$end_chrom, ":", .data$end_position), ) |> - dplyr::select(-c(end_position, end_chrom)) + dplyr::select(-c("end_position", "end_chrom")) } remove_gene_fusion_dups <- function(.data, columns) { @@ -211,7 +212,7 @@ remove_gene_fusion_dups <- function(.data, columns) { v.groups <- c("frameshift_variant&gene_fusion", "gene_fusion") v.effects_ordered <- sapply(.data$Effect, function(s) { c <- stringr::str_split(s, "&") |> unlist() - paste0(sort(c), collapse="&") + paste0(sort(c), collapse = "&") }) if (all(v.groups %in% v.effects_ordered)) { @@ -222,7 +223,6 @@ remove_gene_fusion_dups <- function(.data, columns) { } filter_and_split_annotations_sv <- function(x) { - filter_conditions <- list( # Empty Gene field x$Genes == "", @@ -236,16 +236,16 @@ filter_and_split_annotations_sv <- function(x) { x.grouped <- x |> dplyr::group_by( - filter=ifelse(purrr::reduce(filter_conditions, `|`), "filter", "retain") + filter = ifelse(purrr::reduce(filter_conditions, `|`), "filter", "retain") ) |> - dplyr::select(-c(Type, `Top Tier`)) + dplyr::select(-c("Type", "Top Tier")) keys <- x.grouped |> dplyr::group_keys() |> - dplyr::pull(filter) + dplyr::pull("filter") x.split <- x.grouped |> - dplyr::group_split(.keep=FALSE) |> + dplyr::group_split(.keep = FALSE) |> purrr::set_names(keys) list( @@ -325,7 +325,7 @@ process_sv <- function(x) { is.na(PR_asm_alt) ~ SR_asm_alt, .default = SR_asm_alt + PR_asm_alt, ), - start = paste(chrom, base::format(start, big.mark = ",", trim = TRUE), sep=":"), + start = paste(chrom, base::format(start, big.mark = ",", trim = TRUE), sep = ":"), Type = ifelse(is.na(PURPLE_status), svtype, "PURPLE_inf"), "Record ID" = dplyr::row_number(), ) |> diff --git a/R/umccrise.R b/R/umccrise.R index 1c81b27..4a5b212 100644 --- a/R/umccrise.R +++ b/R/umccrise.R @@ -26,7 +26,7 @@ bcftools_stats_plot <- function(x = NULL) { dplyr::select("qual", "snps", "indels") |> tidyr::uncount(.data$snps + .data$indels) |> dplyr::select("qual") - med <- median(d$qual, na.rm = TRUE) + med <- stats::median(d$qual, na.rm = TRUE) tot <- nrow(d) p <- d |> ggplot2::ggplot(ggplot2::aes(x = .data$qual)) + diff --git a/man/cancer_rmd.Rd b/man/cancer_rmd.Rd index ccc1012..e13b101 100644 --- a/man/cancer_rmd.Rd +++ b/man/cancer_rmd.Rd @@ -8,6 +8,7 @@ cancer_rmd( af_global, af_keygenes, batch_name, + bcftools_stats, conda_list, dragen_hrd, img_dir, diff --git a/man/purple_cnv_som_gene_process.Rd b/man/purple_cnv_som_gene_process.Rd index e5aaf00..a859cad 100644 --- a/man/purple_cnv_som_gene_process.Rd +++ b/man/purple_cnv_som_gene_process.Rd @@ -11,8 +11,8 @@ purple_cnv_som_gene_process(x, g = NULL) \item{g}{Path to gene file containing at least three columns: \itemize{ -\item \code{symbol}: gene name (character). -\item \code{tumorsuppressor}: is this gene a tumor suppressor (TRUE/FALSE). +\item \code{ensembl_gene_symbol}: gene name (character). +\item \code{tsgene}: is this gene a tumor suppressor (TRUE/FALSE). \item \code{oncogene}: is this gene an oncogene (TRUE/FALSE). }} } diff --git a/tests/testthat/test-roxytest-testexamples-purple.R b/tests/testthat/test-roxytest-testexamples-purple.R index a9fde90..46bdedc 100644 --- a/tests/testthat/test-roxytest-testexamples-purple.R +++ b/tests/testthat/test-roxytest-testexamples-purple.R @@ -19,7 +19,7 @@ test_that("Function purple_cnv_som_gene_process() @ L60", { }) -test_that("Function purple_cnv_som_read() @ L449", { +test_that("Function purple_cnv_som_read() @ L447", { x <- system.file("extdata/purple/purple.cnv.somatic.tsv", package = "gpgr") (p <- purple_cnv_som_read(x)) @@ -27,7 +27,7 @@ test_that("Function purple_cnv_som_read() @ L449", { }) -test_that("Function purple_cnv_som_process() @ L482", { +test_that("Function purple_cnv_som_process() @ L480", { x <- system.file("extdata/purple/purple.cnv.somatic.tsv", package = "gpgr") (pp <- purple_cnv_som_process(x)) @@ -35,7 +35,7 @@ test_that("Function purple_cnv_som_process() @ L482", { }) -test_that("Function purple_qc_read() @ L550", { +test_that("Function purple_qc_read() @ L548", { x <- system.file("extdata/purple/purple.qc", package = "gpgr") (q <- purple_qc_read(x)) @@ -43,7 +43,7 @@ test_that("Function purple_qc_read() @ L550", { }) -test_that("Function purple_purity_read() @ L608", { +test_that("Function purple_purity_read() @ L606", { x <- system.file("extdata/purple/purple.purity.tsv", package = "gpgr") (p <- purple_purity_read(x)) From baf18147b66b099cd3289bd3a13eaebc8343e204 Mon Sep 17 00:00:00 2001 From: pdiakumis Date: Mon, 6 May 2024 18:36:46 +1000 Subject: [PATCH 2/8] devtools check/styler - part2 --- R/oncokb.R | 8 +- R/purple.R | 46 +++++------ R/sv.R | 80 +++++++++---------- R/umccrise.R | 2 +- .../test-roxytest-testexamples-purple.R | 8 +- 5 files changed, 73 insertions(+), 71 deletions(-) diff --git a/R/oncokb.R b/R/oncokb.R index 03954aa..8f3963f 100644 --- a/R/oncokb.R +++ b/R/oncokb.R @@ -2,7 +2,7 @@ read_oncokb <- function(x) { readr::read_tsv(x) |> dplyr::filter( - `OncoKB Annotated` == "Yes" + .data$`OncoKB Annotated` == "Yes" ) |> dplyr::pull("Hugo Symbol") } @@ -16,9 +16,11 @@ get_oncokb_genes <- function(x, oncokb_genes) { # Create regexes for each match, utilising delimiters for boundaries. Handles most cases where a gene symbol contains the '-' delimiter purrr::map(function(n) paste0("(?<=^|", delimiter_re, ")", n, "(?=", delimiter_re, "|$)")) |> # Loop with nm iterations through regex and gene symbols - purrr::map(function(n) stringr::str_detect(x, n) |> tibble::as_tibble_row(.name_repair="unique_quiet")) |> + purrr::map(function(n) stringr::str_detect(x, n) |> tibble::as_tibble_row(.name_repair = "unique_quiet")) |> # Combine as tibble to access dplyr::summarise and compile list of detected OncoKB gene symbols for each effect dplyr::bind_rows() |> - dplyr::summarise(dplyr::across(dplyr::everything(), function(v) { paste0(sort(oncokb_genes[v]), collapse=", ") })) |> + dplyr::summarise(dplyr::across(dplyr::everything(), function(v) { + paste0(sort(oncokb_genes[v]), collapse = ", ") + })) |> unlist() } diff --git a/R/purple.R b/R/purple.R index 5881d70..6a7fbbe 100644 --- a/R/purple.R +++ b/R/purple.R @@ -173,7 +173,7 @@ filter_and_split_annotations_cnv <- function(x) { list( retained = purrr::pluck(x.split, "retain"), - filtered = purrr::pluck(x.split, "filter") |> dplyr::arrange("Tier", "Event ID") + filtered = purrr::pluck(x.split, "filter") |> dplyr::arrange(.data$Tier, .data$`Event ID`) ) } @@ -197,7 +197,7 @@ set_many_genes_cnv <- function(x) { # Count genes and set eligibility for collapsing collapse_effects <- c("DelG", "Dup", "DelTx", "UpstreamGV", "DnstreamGV", "IntergenReg") x.counts <- x |> - dplyr::group_by(`Event ID`, Effect) |> + dplyr::group_by(.data$`Event ID`, .data$Effect) |> dplyr::mutate( Genes.unique = .data$Genes |> stringr::str_split(", ") |> unlist() |> unique() |> list(), `Gene count (effect group)` = .data$Genes.unique |> dplyr::first() |> length(), @@ -207,12 +207,12 @@ set_many_genes_cnv <- function(x) { # Collapse target groups x.collapsed <- x.counts |> - dplyr::filter(collapse) |> + dplyr::filter(.data$collapse) |> dplyr::select(-"collapse") |> dplyr::group_modify(~ collapse_effect_group(.x)) |> # Update top tier, referring to complete data set within each group dplyr::mutate( - `Tier (top)` = paste0(Tier, " (", min(x$Tier[x$`Event ID` == `Event ID`]), ")"), + `Tier (top)` = paste0(.data$Tier, " (", min(x$Tier[x$`Event ID` == .data$`Event ID`]), ")"), ) |> # Create new annotation ID dplyr::ungroup() |> @@ -222,26 +222,26 @@ set_many_genes_cnv <- function(x) { # Bind collapsed rows with uncollapsed rows, then count genes per entry x.tmp <- x.counts |> - dplyr::filter(!collapse) |> + dplyr::filter(!.data$collapse) |> dplyr::bind_rows(x.collapsed) |> dplyr::select(-c("collapse", "Genes.unique", "Tier")) |> dplyr::rowwise() |> dplyr::mutate( - `Gene count` = Genes |> stringr::str_split(", ") |> unlist() |> unique() |> length(), + `Gene count` = .data$Genes |> stringr::str_split(", ") |> unlist() |> unique() |> length(), ) |> dplyr::ungroup() |> # Sort rows - dplyr::arrange(`Tier (top)`, `Event ID`) + dplyr::arrange(.data$`Tier (top)`, .data$`Event ID`) # Set many genes x.tmp <- x.tmp |> dplyr::mutate( - many_genes = ifelse(`Gene count` > 2, "many_genes", "few_genes"), + many_genes = ifelse(.data$`Gene count` > 2, "many_genes", "few_genes"), ) # Build the many genes table x.many_genes <- x.tmp |> - dplyr::filter(many_genes == "many_genes") |> + dplyr::filter(.data$many_genes == "many_genes") |> # Remove unneeded columns and rename others dplyr::select( "Event ID", @@ -259,11 +259,11 @@ set_many_genes_cnv <- function(x) { x.ready <- x.tmp |> dplyr::mutate( Genes = ifelse( - many_genes == "few_genes" | is.na(many_genes), - Genes, - paste0("Many genes (", `Gene count`, ")") + .data$many_genes == "few_genes" | is.na(.data$many_genes), + .data$Genes, + paste0("Many genes (", .data$`Gene count`, ")") ), - Transcripts = ifelse(many_genes == "few_genes" | is.na(many_genes), Transcripts, ""), + Transcripts = ifelse(.data$many_genes == "few_genes" | is.na(.data$many_genes), .data$Transcripts, ""), ) |> dplyr::select(-c("many_genes", "Gene count")) @@ -278,18 +278,18 @@ set_many_transcripts_cnv <- function(x) { x.tmp <- x |> dplyr::rowwise() |> dplyr::mutate( - `Transcript count` = stringr::str_split(Transcripts, ", ") |> unlist() |> unique() |> length() + `Transcript count` = stringr::str_split(.data$Transcripts, ", ") |> unlist() |> unique() |> length() ) |> dplyr::ungroup() |> dplyr::mutate( - many_transcripts = ifelse(`Transcript count` > 2, "many_transcripts", "few_transcripts"), + many_transcripts = ifelse(.data$`Transcript count` > 2, "many_transcripts", "few_transcripts"), ) |> # Sort rows - dplyr::arrange(`Tier (top)`, `Event ID`) + dplyr::arrange(.data$`Tier (top)`, .data$`Event ID`) # Build the many transcripts table x.many_transcripts <- x.tmp |> - dplyr::filter(many_transcripts == "many_transcripts") |> + dplyr::filter(.data$many_transcripts == "many_transcripts") |> # Remove unneeded columns and rename others dplyr::select( "Event ID", @@ -307,9 +307,9 @@ set_many_transcripts_cnv <- function(x) { x.ready <- x.tmp |> dplyr::mutate( Transcripts = ifelse( - many_transcripts == "few_transcripts" | is.na(many_transcripts), - Transcripts, - paste0("Many transcripts (", `Transcript count`, ")") + .data$many_transcripts == "few_transcripts" | is.na(.data$many_transcripts), + .data$Transcripts, + paste0("Many transcripts (", .data$`Transcript count`, ")") ) ) |> dplyr::select(-c("many_transcripts", "Transcript count")) @@ -383,14 +383,14 @@ process_cnv_tsv <- function(x) { # Reset sv_top_tier after removing annotations dplyr::group_by(`Event ID`) |> dplyr::mutate( - sv_top_tier = min(Tier), - "Tier (top)" = paste0(Tier, " (", sv_top_tier, ")"), + sv_top_tier = min(.data$Tier), + "Tier (top)" = paste0(.data$Tier, " (", .data$sv_top_tier, ")"), ) |> dplyr::ungroup() |> # Set unique annotation ID dplyr::mutate(`Annotation ID` = as.character(dplyr::row_number())) |> # Sort rows - dplyr::arrange(`Tier (top)`, `Event ID`) + dplyr::arrange(.data$`Tier (top)`, .data$`Event ID`) # Set column names column_selector <- c( diff --git a/R/sv.R b/R/sv.R index 9afdda8..a321919 100644 --- a/R/sv.R +++ b/R/sv.R @@ -165,12 +165,12 @@ split_svs <- function(x) { x.grouped <- x |> dplyr::group_by( - record_type = ifelse(Type %in% bps_types, "bps", "other") + record_type = ifelse(.data$Type %in% bps_types, "bps", "other") ) keys <- x.grouped |> dplyr::group_keys() |> - dplyr::pull(record_type) + dplyr::pull("record_type") x.split <- x.grouped |> dplyr::group_split(.keep = FALSE) |> @@ -211,12 +211,12 @@ remove_gene_fusion_dups <- function(.data, columns) { # Order elements of multi-entry effect values for reliable comparison v.groups <- c("frameshift_variant&gene_fusion", "gene_fusion") v.effects_ordered <- sapply(.data$Effect, function(s) { - c <- stringr::str_split(s, "&") |> unlist() - paste0(sort(c), collapse = "&") + c1 <- stringr::str_split(s, "&") |> unlist() + paste0(sort(c1), collapse = "&") }) if (all(v.groups %in% v.effects_ordered)) { - .data |> dplyr::filter(Effect != "gene_fusion") + .data |> dplyr::filter(.data$Effect != "gene_fusion") } else { .data } @@ -259,16 +259,16 @@ set_many_transcripts_sv <- function(x) { x.tmp <- x |> dplyr::rowwise() |> dplyr::mutate( - `Transcript count` = stringr::str_split(Transcripts, ", ") |> unlist() |> unique() |> length() + `Transcript count` = stringr::str_split(.data$Transcripts, ", ") |> unlist() |> unique() |> length() ) |> dplyr::ungroup() |> dplyr::mutate( - many_transcripts = ifelse(`Transcript count` > 2, "many_transcripts", "few_transcripts") + many_transcripts = ifelse(.data$`Transcript count` > 2, "many_transcripts", "few_transcripts") ) # Build the many transcripts table mt <- x.tmp |> - dplyr::filter(many_transcripts == "many_transcripts") |> + dplyr::filter(.data$many_transcripts == "many_transcripts") |> # Remove unneeded columns and rename others dplyr::select( "Record ID", @@ -284,12 +284,12 @@ set_many_transcripts_sv <- function(x) { x.ready <- x.tmp |> dplyr::mutate( Transcripts = ifelse( - many_transcripts == "few_transcripts" | is.na(many_transcripts), - Transcripts, - paste0("Many transcripts (", `Transcript count`, ")") + .data$many_transcripts == "few_transcripts" | is.na(.data$many_transcripts), + .data$Transcripts, + paste0("Many transcripts (", .data$`Transcript count`, ")") ) ) |> - dplyr::select(-c(many_transcripts, `Transcript count`)) + dplyr::select(-c("many_transcripts", "Transcript count")) list( many_transcripts = mt, @@ -310,30 +310,30 @@ process_sv <- function(x) { # Prepare input sv.ready <- sv.input$data |> dplyr::mutate( - "annotation_count" = count_pieces(annotation, ","), - "Top Tier" = tier, - "SR_PR_ref" = paste0(SR_ref, ",", PR_ref), + "annotation_count" = count_pieces(.data$annotation, ","), + "Top Tier" = .data$tier, + "SR_PR_ref" = paste0(.data$SR_ref, ",", .data$PR_ref), "SR_PR_sum" = dplyr::case_when( - is.na(SR_alt) & is.na(PR_alt) ~ NA, - is.na(SR_alt) ~ PR_alt, - is.na(PR_alt) ~ SR_alt, - .default = SR_alt + PR_alt, + is.na(.data$SR_alt) & is.na(.data$PR_alt) ~ NA, + is.na(.data$SR_alt) ~ .data$PR_alt, + is.na(.data$PR_alt) ~ .data$SR_alt, + .default = .data$SR_alt + .data$PR_alt, ), "SR_PR_asm_sum" = dplyr::case_when( - is.na(SR_asm_alt) & is.na(PR_asm_alt) ~ NA, - is.na(SR_asm_alt) ~ PR_asm_alt, - is.na(PR_asm_alt) ~ SR_asm_alt, - .default = SR_asm_alt + PR_asm_alt, + is.na(.data$SR_asm_alt) & is.na(.data$PR_asm_alt) ~ NA, + is.na(.data$SR_asm_alt) ~ .data$PR_asm_alt, + is.na(.data$PR_asm_alt) ~ .data$SR_asm_alt, + .default = .data$SR_asm_alt + .data$PR_asm_alt, ), - start = paste(chrom, base::format(start, big.mark = ",", trim = TRUE), sep = ":"), - Type = ifelse(is.na(PURPLE_status), svtype, "PURPLE_inf"), + start = paste(.data$chrom, base::format(.data$start, big.mark = ",", trim = TRUE), sep = ":"), + Type = ifelse(is.na(.data$PURPLE_status), .data$svtype, "PURPLE_inf"), "Record ID" = dplyr::row_number(), ) |> dplyr::select(-c( - chrom, - PURPLE_status, - tier, - svtype, + "chrom", + "PURPLE_status", + "tier", + "svtype", )) # Split out breakpoints for merging @@ -347,7 +347,7 @@ process_sv <- function(x) { cols_to_split <- c("AF_PURPLE", "CN_PURPLE") double_cols <- split_double_col(sv.tmp, cols_to_split) sv.tmp <- sv.tmp |> - dplyr::select(-c(cols_to_split)) |> + dplyr::select(-c("cols_to_split")) |> dplyr::bind_cols(double_cols) # Format a table for to be used as the SV Map @@ -372,33 +372,33 @@ process_sv <- function(x) { "PURPLE AF" = "AF_PURPLE", "PURPLE CN" = "CN_PURPLE", ) |> - dplyr::arrange(`Record ID`) + dplyr::arrange(.data$`Record ID`) # Melt annotations sv.melted_all <- sv.tmp |> # Split into individual annotations - dplyr::mutate(annotation = strsplit(annotation, ",")) |> + dplyr::mutate(annotation = strsplit(.data$annotation, ",")) |> # Convert annotation fields into columns - tidyr::unnest(annotation) |> + tidyr::unnest(.data$annotation) |> tidyr::separate( - annotation, c("Event", "Effect", "Genes", "Transcripts", "Detail", "Tier"), + .data$annotation, c("Event", "Effect", "Genes", "Transcripts", "Detail", "Tier"), sep = "\\|", convert = FALSE ) |> # Remove gene_fusion annotations for variants where frameshift_variant&gene_fusion already exist - dplyr::group_by(across(-Effect)) |> + dplyr::group_by(dplyr::across(-.data$Effect)) |> dplyr::group_modify(remove_gene_fusion_dups) |> dplyr::ungroup() |> # Remove unused columns - dplyr::select(c(-Event, -ALT)) |> + dplyr::select(c(-.data$Event, -.data$ALT)) |> # Create columns, modify others dplyr::mutate( "Annotation ID" = dplyr::row_number(), - "Tier (top)" = paste0(Tier, " (", `Top Tier`, ")"), - "Genes" = stringr::str_replace_all(Genes, "&", ", "), - "Transcripts" = stringr::str_replace_all(Transcripts, "&", ", "), + "Tier (top)" = paste0(.data$Tier, " (", .data$`Top Tier`, ")"), + "Genes" = stringr::str_replace_all(.data$Genes, "&", ", "), + "Transcripts" = stringr::str_replace_all(.data$Transcripts, "&", ", "), ) |> # Sort rows - dplyr::arrange(`Tier (top)`, `Record ID`, Genes, Effect) + dplyr::arrange(.data$`Tier (top)`, .data$`Record ID`, .data$Genes, .data$Effect) # Abbreviate effects abbreviate_effectv <- Vectorize(abbreviate_effect) diff --git a/R/umccrise.R b/R/umccrise.R index 4a5b212..98ee386 100644 --- a/R/umccrise.R +++ b/R/umccrise.R @@ -30,7 +30,7 @@ bcftools_stats_plot <- function(x = NULL) { tot <- nrow(d) p <- d |> ggplot2::ggplot(ggplot2::aes(x = .data$qual)) + - ggplot2::geom_histogram(ggplot2::aes(y = ggplot2::after_stat(density)), binwidth = 4, fill = "lightblue") + + ggplot2::geom_histogram(ggplot2::aes(y = ggplot2::after_stat(stats::density)), binwidth = 4, fill = "lightblue") + ggplot2::geom_density(alpha = 0.6) + ggplot2::geom_vline(xintercept = med, colour = "blue", linetype = "dashed") + ggplot2::scale_x_continuous(n.breaks = 10) + diff --git a/tests/testthat/test-roxytest-testexamples-purple.R b/tests/testthat/test-roxytest-testexamples-purple.R index 46bdedc..81d1054 100644 --- a/tests/testthat/test-roxytest-testexamples-purple.R +++ b/tests/testthat/test-roxytest-testexamples-purple.R @@ -19,7 +19,7 @@ test_that("Function purple_cnv_som_gene_process() @ L60", { }) -test_that("Function purple_cnv_som_read() @ L447", { +test_that("Function purple_cnv_som_read() @ L445", { x <- system.file("extdata/purple/purple.cnv.somatic.tsv", package = "gpgr") (p <- purple_cnv_som_read(x)) @@ -27,7 +27,7 @@ test_that("Function purple_cnv_som_read() @ L447", { }) -test_that("Function purple_cnv_som_process() @ L480", { +test_that("Function purple_cnv_som_process() @ L478", { x <- system.file("extdata/purple/purple.cnv.somatic.tsv", package = "gpgr") (pp <- purple_cnv_som_process(x)) @@ -35,7 +35,7 @@ test_that("Function purple_cnv_som_process() @ L480", { }) -test_that("Function purple_qc_read() @ L548", { +test_that("Function purple_qc_read() @ L546", { x <- system.file("extdata/purple/purple.qc", package = "gpgr") (q <- purple_qc_read(x)) @@ -43,7 +43,7 @@ test_that("Function purple_qc_read() @ L548", { }) -test_that("Function purple_purity_read() @ L606", { +test_that("Function purple_purity_read() @ L604", { x <- system.file("extdata/purple/purple.purity.tsv", package = "gpgr") (p <- purple_purity_read(x)) From 12310d4dbc8ddde192f0cf504b004bd32330a836 Mon Sep 17 00:00:00 2001 From: pdiakumis Date: Mon, 6 May 2024 19:18:38 +1000 Subject: [PATCH 3/8] devtools check/styler - part3 --- R/oncoviral.R | 45 +++++++++---------- R/purple.R | 2 +- R/rmd.R | 2 + man/cancer_rmd.Rd | 4 ++ .../test-roxytest-testexamples-oncoviral.R | 6 +-- .../test-roxytest-testexamples-purple.R | 2 +- 6 files changed, 32 insertions(+), 29 deletions(-) diff --git a/R/oncoviral.R b/R/oncoviral.R index 7c87f0d..df33fc5 100644 --- a/R/oncoviral.R +++ b/R/oncoviral.R @@ -12,11 +12,10 @@ #' x <- system.file("extdata/virusbreakend/virusbreakend.vcf.summary.tsv", package = "gpgr") #' (vb <- virusbreakend_summary_read(x)) #' @testexamples -#' expect_equal(colnames(vb)[ncol(vb)], "QCStatus") +#' expect_equal(colnames(vb$tab)[ncol(vb$tab)], "QC") #' #' @export virusbreakend_summary_read <- function(x) { - nm <- c( "taxid_genus" = "c", "name_genus" = "c", @@ -44,7 +43,6 @@ virusbreakend_summary_read <- function(x) { "integrations" = "i", "QCStatus" = "c" ) - ctypes <- paste(nm, collapse = "") virusbreakend_summary <- readr::read_tsv(x, col_types = ctypes) @@ -54,13 +52,13 @@ virusbreakend_summary_read <- function(x) { virusbreakend_summary <- virusbreakend_summary |> dplyr::select( - Virus="name_assigned", - Length="endpos", - Reads="numreads", - Coverage="coverage", - `Mean depth`="meandepth", - Intergrations="integrations", - QC="QCStatus", + Virus = "name_assigned", + Length = "endpos", + Reads = "numreads", + Coverage = "coverage", + `Mean depth` = "meandepth", + Intergrations = "integrations", + QC = "QCStatus", ) } @@ -71,7 +69,7 @@ virusbreakend_summary_read <- function(x) { "Reads", "Number of reads mapped to adjusted viral reference", "Coverage", "Percentage of viral positions with at least one read mapped", "Mean depth", "Mean alignment depth", - "Intergrations", "Number of detected integration breakpoints", + "Integrations", "Number of detected integration breakpoints", "QC", "QC status of viral intergrations", ) @@ -95,29 +93,28 @@ virusbreakend_summary_read <- function(x) { #' x <- system.file("extdata/virusbreakend/virusbreakend.vcf", package = "gpgr") #' (vb <- virusbreakend_vcf_read(x)) #' @testexamples -#' expect_equal(colnames(vb)[ncol(vb)], "QC") +#' expect_equal(colnames(vb$tab)[ncol(vb$tab)], "QC") #' #' @export virusbreakend_vcf_read <- function(x) { - d <- bedr::read.vcf(x, split.info = TRUE, verbose = FALSE) if (nrow(d$vcf) > 0) { virusbreakend_integrations <- tibble::as_tibble(d$vcf) |> dplyr::select( - Contig="CHROM", - Position="POS", - "Fragment support"="BVF", - "Fragment support (unmapped)"="BUM", - "Softclip read support"="BSC", - Reference="REF", - Alt="ALT", - `Breakend ID`="ID", - `Mate ID`="MATEID", - QC="FILTER", + Contig = "CHROM", + Position = "POS", + "Fragment support" = "BVF", + "Fragment support (unmapped)" = "BUM", + "Softclip read support" = "BSC", + Reference = "REF", + Alt = "ALT", + `Breakend ID` = "ID", + `Mate ID` = "MATEID", + QC = "FILTER", ) } else { - virusbreakend_integrations <- tibble::tibble() + virusbreakend_integrations <- tibble::tibble() } descr <- dplyr::tribble( diff --git a/R/purple.R b/R/purple.R index 6a7fbbe..78f491f 100644 --- a/R/purple.R +++ b/R/purple.R @@ -12,7 +12,7 @@ #' x <- system.file("extdata/purple/purple.cnv.gene.tsv", package = "gpgr") #' (p <- purple_cnv_som_gene_read(x)) #' @testexamples -#' expect_equal(colnames(p)[ncol(p)], "minMinorAlleleCopyNumber") +#' expect_equal(colnames(p)[ncol(p)], "depthWindowCount") #' #' @export purple_cnv_som_gene_read <- function(x) { diff --git a/R/rmd.R b/R/rmd.R index 25a454c..6ca8f73 100644 --- a/R/rmd.R +++ b/R/rmd.R @@ -29,6 +29,8 @@ #' @param tumor_name Name of tumor sample. #' @param out_file Path to output HTML file (needs '.html' suffix) (def: `{tumor_name}_cancer_report.html`). #' @param quiet Suppress log printing during rendering. +#' @param bcftools_stats Path to `bcftools_stats.txt` file. +#' @param dragen_hrd Path to DRAGEN `hrdscore.csv` file. #' #' @return Path to rendered HTML report. #' @export diff --git a/man/cancer_rmd.Rd b/man/cancer_rmd.Rd index e13b101..c361f4f 100644 --- a/man/cancer_rmd.Rd +++ b/man/cancer_rmd.Rd @@ -39,8 +39,12 @@ cancer_rmd( \item{batch_name}{Name of batch sample.} +\item{bcftools_stats}{Path to \code{bcftools_stats.txt} file.} + \item{conda_list}{Path to \code{conda_pkg_list.txt} file.} +\item{dragen_hrd}{Path to DRAGEN \code{hrdscore.csv} file.} + \item{img_dir}{Path to directory containing PURPLE plots.} \item{key_genes}{Path to UMCCR cancer gene file.} diff --git a/tests/testthat/test-roxytest-testexamples-oncoviral.R b/tests/testthat/test-roxytest-testexamples-oncoviral.R index cad645a..a1c116d 100644 --- a/tests/testthat/test-roxytest-testexamples-oncoviral.R +++ b/tests/testthat/test-roxytest-testexamples-oncoviral.R @@ -6,14 +6,14 @@ test_that("Function virusbreakend_summary_read() @ L18", { x <- system.file("extdata/virusbreakend/virusbreakend.vcf.summary.tsv", package = "gpgr") (vb <- virusbreakend_summary_read(x)) - expect_equal(colnames(vb)[ncol(vb)], "QCStatus") + expect_equal(colnames(vb$tab)[ncol(vb$tab)], "QC") }) -test_that("Function virusbreakend_vcf_read() @ L101", { +test_that("Function virusbreakend_vcf_read() @ L99", { x <- system.file("extdata/virusbreakend/virusbreakend.vcf", package = "gpgr") (vb <- virusbreakend_vcf_read(x)) - expect_equal(colnames(vb)[ncol(vb)], "QC") + expect_equal(colnames(vb$tab)[ncol(vb$tab)], "QC") }) diff --git a/tests/testthat/test-roxytest-testexamples-purple.R b/tests/testthat/test-roxytest-testexamples-purple.R index 81d1054..19d2926 100644 --- a/tests/testthat/test-roxytest-testexamples-purple.R +++ b/tests/testthat/test-roxytest-testexamples-purple.R @@ -6,7 +6,7 @@ test_that("Function purple_cnv_som_gene_read() @ L18", { x <- system.file("extdata/purple/purple.cnv.gene.tsv", package = "gpgr") (p <- purple_cnv_som_gene_read(x)) - expect_equal(colnames(p)[ncol(p)], "minMinorAlleleCopyNumber") + expect_equal(colnames(p)[ncol(p)], "depthWindowCount") }) From bd1715a848a9700635cd90a3f62191ed9a72339e Mon Sep 17 00:00:00 2001 From: pdiakumis Date: Mon, 6 May 2024 22:19:00 +1000 Subject: [PATCH 4/8] devnotes: replace pcgr reference --- vignettes/devnotes.Rmd | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vignettes/devnotes.Rmd b/vignettes/devnotes.Rmd index a43ef8a..808f998 100644 --- a/vignettes/devnotes.Rmd +++ b/vignettes/devnotes.Rmd @@ -18,7 +18,7 @@ then work with `devtools`. You'll also need to install | `devtools::load_all()` | load the pkg (`Cmd+Shift+L`) | | `devtools::check()` | check the pkg (`Cmd+Shift+E`) | | `devtools::install()` | install the pkg (`Cmd+Shift+B`) | -| `R CMD INSTALL --no-multiarch --with-keep.source pcgr.git/pcgrr` | install the pkg into the first library of `.libPaths()` (useful when using in conda env) | +| `R CMD INSTALL --no-multiarch --with-keep.source git/gpgr` | install the pkg into the first library of `.libPaths()` (useful when using in conda env) | ### Data Version Control From 39b3cdf32daff1d0ae06be436b2a286eca840e1d Mon Sep 17 00:00:00 2001 From: pdiakumis Date: Mon, 6 May 2024 23:45:16 +1000 Subject: [PATCH 5/8] use v24.03.0 umccr cancer gene panel --- R/purple.R | 21 ++++++------ data-raw/umccr_cancer_genes.R | 33 ++++++++----------- man/purple_cnv_som_gene_process.Rd | 8 ++--- .../test-roxytest-testexamples-purple.R | 10 +++--- 4 files changed, 32 insertions(+), 40 deletions(-) diff --git a/R/purple.R b/R/purple.R index 78f491f..2cc74f4 100644 --- a/R/purple.R +++ b/R/purple.R @@ -36,12 +36,12 @@ purple_cnv_som_gene_read <- function(x) { #' Process PURPLE CNV Gene File for UMCCRISE #' #' Processes the `purple.cnv.gene.tsv` file. Keeps genes that are in the -#' [UMCCR cancer gene list](https://github.com/umccr/genes/blob/893a655801ce92715f05517b5052e4e81904e870/panels/umccr_2019-03-20.tsv) -#' and selects columns of interest. +#' UMCCR cancer gene list +#' ([v24.03.0](https://raw.githubusercontent.com/umccr/gene_panels/v24.03.0/somatic_panel/3_final_panel/final_panel.tsv)) and selects columns of interest. #' #' @param x Path to `purple.cnv.gene.tsv` file. #' @param g Path to gene file containing at least three columns: -#' * `ensembl_gene_symbol`: gene name (character). +#' * `symbol`: gene name (character). #' * `tsgene`: is this gene a tumor suppressor (TRUE/FALSE). #' * `oncogene`: is this gene an oncogene (TRUE/FALSE). #' @@ -51,7 +51,7 @@ purple_cnv_som_gene_read <- function(x) { #' #' @examples #' x <- system.file("extdata/purple/purple.cnv.gene.tsv", package = "gpgr") -#' g <- system.file("extdata/ref/umccr_cancer_genes_2019-03-20.tsv", package = "gpgr") +#' g <- system.file("extdata/ref/umccr_cancer_genes_v24.03.0.tsv", package = "gpgr") #' (pp <- purple_cnv_som_gene_process(x, g)) #' @testexamples #' expect_equal(colnames(pp$tab)[ncol(pp$tab)], "minRegSupportStartEndMethod") @@ -60,22 +60,21 @@ purple_cnv_som_gene_read <- function(x) { purple_cnv_som_gene_process <- function(x, g = NULL) { purple_cnv_gene <- purple_cnv_som_gene_read(x) if (is.null(g)) { - g <- system.file("extdata/ref/umccr_cancer_genes_2019-03-20.tsv", package = "gpgr") + g <- system.file("extdata/ref/umccr_cancer_genes_v24.03.0.tsv", package = "gpgr") } genes <- readr::read_tsv(g, col_types = readr::cols( - ensembl_gene_symbol = "c", oncogene = "l", tsgene = "l" + symbol = "c", oncogene = "l", tumorsuppressor = "l" )) |> - dplyr::select("ensembl_gene_symbol", "oncogene", "tsgene") + dplyr::select("symbol", "oncogene", tsgene = "tumorsuppressor") oncogenes <- genes |> dplyr::filter(.data$oncogene) |> - dplyr::pull(.data$ensembl_gene_symbol) + dplyr::pull(.data$symbol) tsgenes <- genes |> dplyr::filter(.data$tsgene) |> - dplyr::pull(.data$ensembl_gene_symbol) - + dplyr::pull(.data$symbol) purple_cnv_gene <- purple_cnv_gene |> - dplyr::filter(.data$gene %in% genes$ensembl_gene_symbol) |> + dplyr::filter(.data$gene %in% genes$symbol) |> dplyr::mutate( chromosome = as.factor(.data$chromosome), transcriptID = paste0(.data$transcriptId), diff --git a/data-raw/umccr_cancer_genes.R b/data-raw/umccr_cancer_genes.R index 2da79d6..636cfa9 100644 --- a/data-raw/umccr_cancer_genes.R +++ b/data-raw/umccr_cancer_genes.R @@ -1,23 +1,16 @@ # UMCCR Cancer Genes -require(here) -require(readr) +require(here, include.only = "here") +require(readr, include.only = "read_tsv") require(dplyr) +require(glue, include.only = "glue") -tmp <- tempfile() -download.file( - url = "https://raw.githubusercontent.com/umccr/genes/893a655801ce92715f05517b5052e4e81904e870/panels/umccr_2019-03-20.tsv", - destfile = tmp -) - -readr::read_tsv(tmp) |> - dplyr::select(symbol, tumorsuppressor, oncogene) |> - readr::write_tsv(here("inst/extdata/ref/umccr_cancer_genes_2019-03-20.tsv")) - -tmp2 <- tempfile() -download.file( - "https://raw.githubusercontent.com/umccr/workflows/8d06a16a0199ccf94b666f9ec027efce8af1110b/genes/cancer_genes/umccr_cancer_genes.hg38.coding.bed", - destfile = tmp2 -) - -readr::read_tsv(tmp2, col_names = c("chr", "start", "end", "symbol"), col_types = "ciic") |> - readr::write_tsv(here("inst/extdata/ref/umccr_cancer_genes_hg38_coding.bed")) +version <- "24.03.0" +read_umccr_genes_final_panel <- function(version) { + repo <- "https://raw.githubusercontent.com/umccr/gene_panels" + tsv_url <- glue::glue("{repo}/v{version}/somatic_panel/3_final_panel/final_panel.tsv") + d <- readr::read_tsv(tsv_url, col_types = readr::cols(.default = "c", "tsgene" = "l", "oncogene" = "l")) |> + dplyr::select(symbol = "hgnc_symbol", tumorsuppressor = "tsgene", "oncogene") + d +} +read_umccr_genes_final_panel(version) |> + readr::write_tsv(here(glue("inst/extdata/ref/umccr_cancer_genes_v{version}.tsv"))) diff --git a/man/purple_cnv_som_gene_process.Rd b/man/purple_cnv_som_gene_process.Rd index a859cad..853cb94 100644 --- a/man/purple_cnv_som_gene_process.Rd +++ b/man/purple_cnv_som_gene_process.Rd @@ -11,7 +11,7 @@ purple_cnv_som_gene_process(x, g = NULL) \item{g}{Path to gene file containing at least three columns: \itemize{ -\item \code{ensembl_gene_symbol}: gene name (character). +\item \code{symbol}: gene name (character). \item \code{tsgene}: is this gene a tumor suppressor (TRUE/FALSE). \item \code{oncogene}: is this gene an oncogene (TRUE/FALSE). }} @@ -25,11 +25,11 @@ List with two elements: } \description{ Processes the \code{purple.cnv.gene.tsv} file. Keeps genes that are in the -\href{https://github.com/umccr/genes/blob/893a655801ce92715f05517b5052e4e81904e870/panels/umccr_2019-03-20.tsv}{UMCCR cancer gene list} -and selects columns of interest. +UMCCR cancer gene list +(\href{https://raw.githubusercontent.com/umccr/gene_panels/v24.03.0/somatic_panel/3_final_panel/final_panel.tsv}{v24.03.0}) and selects columns of interest. } \examples{ x <- system.file("extdata/purple/purple.cnv.gene.tsv", package = "gpgr") -g <- system.file("extdata/ref/umccr_cancer_genes_2019-03-20.tsv", package = "gpgr") +g <- system.file("extdata/ref/umccr_cancer_genes_v24.03.0.tsv", package = "gpgr") (pp <- purple_cnv_som_gene_process(x, g)) } diff --git a/tests/testthat/test-roxytest-testexamples-purple.R b/tests/testthat/test-roxytest-testexamples-purple.R index 19d2926..eac038f 100644 --- a/tests/testthat/test-roxytest-testexamples-purple.R +++ b/tests/testthat/test-roxytest-testexamples-purple.R @@ -13,13 +13,13 @@ test_that("Function purple_cnv_som_gene_read() @ L18", { test_that("Function purple_cnv_som_gene_process() @ L60", { x <- system.file("extdata/purple/purple.cnv.gene.tsv", package = "gpgr") - g <- system.file("extdata/ref/umccr_cancer_genes_2019-03-20.tsv", package = "gpgr") + g <- system.file("extdata/ref/umccr_cancer_genes_v24.03.0.tsv", package = "gpgr") (pp <- purple_cnv_som_gene_process(x, g)) expect_equal(colnames(pp$tab)[ncol(pp$tab)], "minRegSupportStartEndMethod") }) -test_that("Function purple_cnv_som_read() @ L445", { +test_that("Function purple_cnv_som_read() @ L444", { x <- system.file("extdata/purple/purple.cnv.somatic.tsv", package = "gpgr") (p <- purple_cnv_som_read(x)) @@ -27,7 +27,7 @@ test_that("Function purple_cnv_som_read() @ L445", { }) -test_that("Function purple_cnv_som_process() @ L478", { +test_that("Function purple_cnv_som_process() @ L477", { x <- system.file("extdata/purple/purple.cnv.somatic.tsv", package = "gpgr") (pp <- purple_cnv_som_process(x)) @@ -35,7 +35,7 @@ test_that("Function purple_cnv_som_process() @ L478", { }) -test_that("Function purple_qc_read() @ L546", { +test_that("Function purple_qc_read() @ L545", { x <- system.file("extdata/purple/purple.qc", package = "gpgr") (q <- purple_qc_read(x)) @@ -43,7 +43,7 @@ test_that("Function purple_qc_read() @ L546", { }) -test_that("Function purple_purity_read() @ L604", { +test_that("Function purple_purity_read() @ L603", { x <- system.file("extdata/purple/purple.purity.tsv", package = "gpgr") (p <- purple_purity_read(x)) From 00c8b2eb68c276287a1b4a46b8e0ce0bee73c1ef Mon Sep 17 00:00:00 2001 From: pdiakumis Date: Tue, 7 May 2024 00:16:14 +1000 Subject: [PATCH 6/8] devtools check/styler - part4 --- R/oncokb.R | 5 +++++ R/purple.R | 11 +++++++---- R/sv.R | 2 ++ tests/testthat/test-roxytest-testexamples-purple.R | 4 ++-- 4 files changed, 16 insertions(+), 6 deletions(-) diff --git a/R/oncokb.R b/R/oncokb.R index 8f3963f..f506629 100644 --- a/R/oncokb.R +++ b/R/oncokb.R @@ -1,3 +1,5 @@ +#' @param x Path to something. +#' #' @export read_oncokb <- function(x) { readr::read_tsv(x) |> @@ -7,6 +9,9 @@ read_oncokb <- function(x) { dplyr::pull("Hugo Symbol") } +#' @param x Path to something. +#' @param oncokb_genes Tibble of something. +#' #' @export get_oncokb_genes <- function(x, oncokb_genes) { delimiters <- " ,&-" diff --git a/R/purple.R b/R/purple.R index 2cc74f4..08f33b7 100644 --- a/R/purple.R +++ b/R/purple.R @@ -319,6 +319,8 @@ set_many_transcripts_cnv <- function(x) { ) } +#' @param x Path to something. +#' #' @export process_cnv_tsv <- function(x) { # Read input @@ -539,7 +541,7 @@ purple_cnv_som_process <- function(x) { #' x <- system.file("extdata/purple/purple.qc", package = "gpgr") #' (q <- purple_qc_read(x)) #' @testexamples -#' expect_true(q$raw[1, "value", drop = TRUE] == "WARN_DELETED_GENES") +#' expect_true(q$raw[1, "value", drop = TRUE] == "FAIL_CONTAMINATION") #' #' @export purple_qc_read <- function(x) { @@ -551,7 +553,7 @@ purple_qc_read <- function(x) { "QCStatus", "Method", "CopyNumberSegments", "UnsupportedCopyNumberSegments", "Purity", "AmberGender", "CobaltGender", "DeletedGenes", "Contamination", "GermlineAberrations", - "AmberMeanDepth", "LohPercent" + "AmberMeanDepth" ) assertthat::assert_that(all(purple_qc$key == nm)) @@ -597,7 +599,7 @@ purple_qc_read <- function(x) { #' (p <- purple_purity_read(x)) #' @testexamples #' expect_equal(p$raw[1, "column", drop = TRUE], "purity") -#' expect_equal(p$raw[nrow(p$raw), "column", drop = TRUE], "svTumorMutationalBurden") +#' expect_equal(p$raw[nrow(p$raw), "column", drop = TRUE], "targeted") #' #' @export purple_purity_read <- function(x) { @@ -617,6 +619,7 @@ purple_purity_read <- function(x) { "maxPloidy", "d", "minDiploidProportion", "d", "maxDiploidProportion", "d", + "version", "c", "somaticPenalty", "d", "wholeGenomeDuplication", "c", "msIndelsPerMb", "d", @@ -637,7 +640,7 @@ purple_purity_read <- function(x) { purple_purity <- purple_purity |> dplyr::mutate( - dplyr::across(tidyselect::vars_select_helpers$where(is.numeric), round, 2), + dplyr::across(tidyselect::where(is.numeric), \(x) round(x, 2)), dplyr::across(dplyr::everything(), as.character) ) |> tidyr::pivot_longer(dplyr::everything(), names_to = "column", values_to = "value") |> diff --git a/R/sv.R b/R/sv.R index a321919..0c4adad 100644 --- a/R/sv.R +++ b/R/sv.R @@ -297,6 +297,8 @@ set_many_transcripts_sv <- function(x) { ) } +#' @param x Path to something. +#' #' @export process_sv <- function(x) { # Read input and set column information diff --git a/tests/testthat/test-roxytest-testexamples-purple.R b/tests/testthat/test-roxytest-testexamples-purple.R index eac038f..3f83ec0 100644 --- a/tests/testthat/test-roxytest-testexamples-purple.R +++ b/tests/testthat/test-roxytest-testexamples-purple.R @@ -39,7 +39,7 @@ test_that("Function purple_qc_read() @ L545", { x <- system.file("extdata/purple/purple.qc", package = "gpgr") (q <- purple_qc_read(x)) - expect_true(q$raw[1, "value", drop = TRUE] == "WARN_DELETED_GENES") + expect_true(q$raw[1, "value", drop = TRUE] == "FAIL_CONTAMINATION") }) @@ -48,6 +48,6 @@ test_that("Function purple_purity_read() @ L603", { x <- system.file("extdata/purple/purple.purity.tsv", package = "gpgr") (p <- purple_purity_read(x)) expect_equal(p$raw[1, "column", drop = TRUE], "purity") - expect_equal(p$raw[nrow(p$raw), "column", drop = TRUE], "svTumorMutationalBurden") + expect_equal(p$raw[nrow(p$raw), "column", drop = TRUE], "targeted") }) From bb85163450e0134ee903a0f8afd0da6af71815d5 Mon Sep 17 00:00:00 2001 From: pdiakumis Date: Tue, 7 May 2024 01:31:26 +1000 Subject: [PATCH 7/8] devtools check/styler - part5 --- R/oncokb.R | 8 ++++- R/purple.R | 33 +++++++++-------- R/rmd.R | 4 +-- R/sv.R | 35 ++++++++++--------- man/cancer_rmd.Rd | 4 +-- man/get_oncokb_genes.Rd | 19 ++++++++++ man/plot_bnd_sr_pr_tot_hist.Rd | 4 +-- man/plot_bnd_sr_pr_tot_lines.Rd | 4 +-- man/process_cnv_tsv.Rd | 17 +++++++++ man/process_sv.Rd | 17 +++++++++ man/read_oncokb.Rd | 17 +++++++++ .../test-roxytest-testexamples-purple.R | 8 ++--- 12 files changed, 126 insertions(+), 44 deletions(-) create mode 100644 man/get_oncokb_genes.Rd create mode 100644 man/process_cnv_tsv.Rd create mode 100644 man/process_sv.Rd create mode 100644 man/read_oncokb.Rd diff --git a/R/oncokb.R b/R/oncokb.R index f506629..de557ef 100644 --- a/R/oncokb.R +++ b/R/oncokb.R @@ -1,5 +1,8 @@ +#' Read OncoKB +#' #' @param x Path to something. #' +#' @return Vector of genes. #' @export read_oncokb <- function(x) { readr::read_tsv(x) |> @@ -9,8 +12,11 @@ read_oncokb <- function(x) { dplyr::pull("Hugo Symbol") } +#' Get OncoKB Genes From Somewhere +#' #' @param x Path to something. -#' @param oncokb_genes Tibble of something. +#' @param oncokb_genes A tibble of something. +#' @return A vector I think. #' #' @export get_oncokb_genes <- function(x, oncokb_genes) { diff --git a/R/purple.R b/R/purple.R index 08f33b7..1046aa4 100644 --- a/R/purple.R +++ b/R/purple.R @@ -319,8 +319,12 @@ set_many_transcripts_cnv <- function(x) { ) } +#' Process CNV TSV +#' #' @param x Path to something. #' +#' @return List of many things. +#' #' @export process_cnv_tsv <- function(x) { # Read input @@ -342,19 +346,18 @@ process_cnv_tsv <- function(x) { dplyr::mutate(annotation = strsplit(.data$simple_ann, ",")) |> # Convert annotation fields into columns tidyr::unnest("annotation") |> - tidyr::separate( - "annotation", - c("Event", "Effect", "Genes", "Transcripts", "Detail", "Tier"), - sep = "\\|", convert = FALSE + tidyr::separate_wider_delim( + cols = "annotation", delim = "|", + names = c("Event", "Effect", "Genes", "Transcripts", "Detail", "Tier") ) |> # Create new columns and modify existing ones dplyr::mutate( - copyNumber = as.numeric(.data$copyNumber) |> round(2) %>% sprintf("%.2f", .), - minorAlleleCopyNumber = as.numeric(minorAlleleCopyNumber) |> round(2) %>% sprintf("%.2f", .), - majorAlleleCopyNumber = as.numeric(majorAlleleCopyNumber) |> round(2) %>% sprintf("%.2f", .), - "PURPLE CN Min+Maj" = paste0(minorAlleleCopyNumber, "+", majorAlleleCopyNumber), - "Genes" = stringr::str_replace_all(Genes, "&", ", "), - "Transcripts" = stringr::str_replace_all(Transcripts, "&", ", "), + copyNumber = sprintf("%.2f", round(as.numeric(.data$copyNumber), 2)), + minorAlleleCopyNumber = sprintf("%.2f", round(as.numeric(.data$minorAlleleCopyNumber), 2)), + majorAlleleCopyNumber = sprintf("%.2f", round(as.numeric(.data$majorAlleleCopyNumber), 2)), + "PURPLE CN Min+Maj" = paste0(.data$minorAlleleCopyNumber, "+", .data$majorAlleleCopyNumber), + "Genes" = stringr::str_replace_all(.data$Genes, "&", ", "), + "Transcripts" = stringr::str_replace_all(.data$Transcripts, "&", ", ") ) |> # Remove unused columns dplyr::select(-c( @@ -369,7 +372,7 @@ process_cnv_tsv <- function(x) { "segmentEndSupport", "segmentStartSupport", "sv_top_tier", - "simple_ann", + "simple_ann" )) # Abbreviate effects @@ -382,10 +385,10 @@ process_cnv_tsv <- function(x) { # Complete processing cnv.tmp <- cnv.annotations.split$retained |> # Reset sv_top_tier after removing annotations - dplyr::group_by(`Event ID`) |> + dplyr::group_by(.data$`Event ID`) |> dplyr::mutate( sv_top_tier = min(.data$Tier), - "Tier (top)" = paste0(.data$Tier, " (", .data$sv_top_tier, ")"), + "Tier (top)" = paste0(.data$Tier, " (", .data$sv_top_tier, ")") ) |> dplyr::ungroup() |> # Set unique annotation ID @@ -408,8 +411,8 @@ process_cnv_tsv <- function(x) { "PURPLE CN" = "copyNumber", "PURPLE CN Min+Maj" ) - cnv.tmp <- dplyr::select("cnv.tmp", tidyselect::all_of(c(column_selector, "Tier"))) - cnv.filtered <- dplyr::select(cnv.annotations.split$filtered, tidyselect::any_of(column_selector)) + cnv.tmp <- dplyr::select(cnv.tmp, dplyr::all_of(c(column_selector, "Tier"))) + cnv.filtered <- dplyr::select(cnv.annotations.split$filtered, dplyr::any_of(column_selector)) # Collapse selected annotations and set many genes cnv.many_genes_data <- set_many_genes_cnv(cnv.tmp) diff --git a/R/rmd.R b/R/rmd.R index 6ca8f73..dde3d6e 100644 --- a/R/rmd.R +++ b/R/rmd.R @@ -24,8 +24,8 @@ #' @param result_outdir Path to directory to write tidy JSON/TSV results. #' @param somatic_snv_vcf Path to `somatic-PASS.vcf.gz` SNV VCF. #' @param somatic_snv_summary Path to `somatic_snv_summary.json` JSON. -#' @param somatic_sv_tsv Path to `manta.tsv` TSV file. -#' @param somatic_sv_vcf Path to `manta.vcf.gz` VCF file. +#' @param somatic_sv_tsv Path to SV TSV file. +#' @param somatic_sv_vcf Path to SV VCF file. #' @param tumor_name Name of tumor sample. #' @param out_file Path to output HTML file (needs '.html' suffix) (def: `{tumor_name}_cancer_report.html`). #' @param quiet Suppress log printing during rendering. diff --git a/R/sv.R b/R/sv.R index 0c4adad..6a4ede5 100644 --- a/R/sv.R +++ b/R/sv.R @@ -297,7 +297,10 @@ set_many_transcripts_sv <- function(x) { ) } -#' @param x Path to something. +#' Process SV TSV +#' +#' @param x Path to SV TSV. +#' @return List of many things. #' #' @export process_sv <- function(x) { @@ -329,13 +332,13 @@ process_sv <- function(x) { ), start = paste(.data$chrom, base::format(.data$start, big.mark = ",", trim = TRUE), sep = ":"), Type = ifelse(is.na(.data$PURPLE_status), .data$svtype, "PURPLE_inf"), - "Record ID" = dplyr::row_number(), + "Record ID" = dplyr::row_number() ) |> dplyr::select(-c( "chrom", "PURPLE_status", "tier", - "svtype", + "svtype" )) # Split out breakpoints for merging @@ -349,7 +352,7 @@ process_sv <- function(x) { cols_to_split <- c("AF_PURPLE", "CN_PURPLE") double_cols <- split_double_col(sv.tmp, cols_to_split) sv.tmp <- sv.tmp |> - dplyr::select(-c("cols_to_split")) |> + dplyr::select(-c(dplyr::all_of(cols_to_split))) |> dplyr::bind_cols(double_cols) # Format a table for to be used as the SV Map @@ -372,7 +375,7 @@ process_sv <- function(x) { "IC_alt", "SR_PR_ref", "PURPLE AF" = "AF_PURPLE", - "PURPLE CN" = "CN_PURPLE", + "PURPLE CN" = "CN_PURPLE" ) |> dplyr::arrange(.data$`Record ID`) @@ -381,17 +384,17 @@ process_sv <- function(x) { # Split into individual annotations dplyr::mutate(annotation = strsplit(.data$annotation, ",")) |> # Convert annotation fields into columns - tidyr::unnest(.data$annotation) |> - tidyr::separate( - .data$annotation, c("Event", "Effect", "Genes", "Transcripts", "Detail", "Tier"), - sep = "\\|", convert = FALSE + tidyr::unnest("annotation") |> + tidyr::separate_wider_delim( + cols = "annotation", delim = "|", + names = c("Event", "Effect", "Genes", "Transcripts", "Detail", "Tier") ) |> # Remove gene_fusion annotations for variants where frameshift_variant&gene_fusion already exist - dplyr::group_by(dplyr::across(-.data$Effect)) |> + dplyr::group_by(dplyr::across(-"Effect")) |> dplyr::group_modify(remove_gene_fusion_dups) |> dplyr::ungroup() |> # Remove unused columns - dplyr::select(c(-.data$Event, -.data$ALT)) |> + dplyr::select(-c("Event", "ALT")) |> # Create columns, modify others dplyr::mutate( "Annotation ID" = dplyr::row_number(), @@ -432,7 +435,7 @@ process_sv <- function(x) { "PURPLE CN" = "CN_PURPLE", # Dropped after ops for non-map outputs "Top Tier", - "Type", + "Type" ) # Create and set many transcript values @@ -464,8 +467,8 @@ process_sv <- function(x) { #' @return A ggplot2 plot object. #' #' @examples -#' x <- system.file("extdata/umccrise/sv/manta.tsv", package = "gpgr") -#' d <- process_sv(x)$unmelted +#' x <- system.file("extdata/sash/sv.prioritised.tsv", package = "gpgr") +#' d <- process_sv(x)$map #' plot_bnd_sr_pr_tot_lines(d) #' @export plot_bnd_sr_pr_tot_lines <- function(d, @@ -527,8 +530,8 @@ plot_bnd_sr_pr_tot_lines <- function(d, #' @return A ggplot2 plot object. #' #' @examples -#' x <- system.file("extdata/umccrise/sv/manta.tsv", package = "gpgr") -#' d <- process_sv(x)$unmelted +#' x <- system.file("extdata/sash/sv.prioritised.tsv", package = "gpgr") +#' d <- process_sv(x)$map #' plot_bnd_sr_pr_tot_hist(d, "a title") #' @export plot_bnd_sr_pr_tot_hist <- function(d, diff --git a/man/cancer_rmd.Rd b/man/cancer_rmd.Rd index c361f4f..8845848 100644 --- a/man/cancer_rmd.Rd +++ b/man/cancer_rmd.Rd @@ -71,9 +71,9 @@ cancer_rmd( \item{somatic_snv_summary}{Path to \code{somatic_snv_summary.json} JSON.} -\item{somatic_sv_tsv}{Path to \code{manta.tsv} TSV file.} +\item{somatic_sv_tsv}{Path to SV TSV file.} -\item{somatic_sv_vcf}{Path to \code{manta.vcf.gz} VCF file.} +\item{somatic_sv_vcf}{Path to SV VCF file.} \item{result_outdir}{Path to directory to write tidy JSON/TSV results.} diff --git a/man/get_oncokb_genes.Rd b/man/get_oncokb_genes.Rd new file mode 100644 index 0000000..21bd062 --- /dev/null +++ b/man/get_oncokb_genes.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/oncokb.R +\name{get_oncokb_genes} +\alias{get_oncokb_genes} +\title{Get OncoKB Genes From Somewhere} +\usage{ +get_oncokb_genes(x, oncokb_genes) +} +\arguments{ +\item{x}{Path to something.} + +\item{oncokb_genes}{A tibble of something.} +} +\value{ +A vector I think. +} +\description{ +Get OncoKB Genes From Somewhere +} diff --git a/man/plot_bnd_sr_pr_tot_hist.Rd b/man/plot_bnd_sr_pr_tot_hist.Rd index c060067..19538fd 100644 --- a/man/plot_bnd_sr_pr_tot_hist.Rd +++ b/man/plot_bnd_sr_pr_tot_hist.Rd @@ -25,7 +25,7 @@ Plots histograms for the number of split reads (\code{SR}), paired end reads (\c sum (\code{tot}) across all BNDs. Observations where the SR or PR value is 0 (NA) are not shown. } \examples{ -x <- system.file("extdata/umccrise/sv/manta.tsv", package = "gpgr") -d <- process_sv(x)$unmelted +x <- system.file("extdata/sash/sv.prioritised.tsv", package = "gpgr") +d <- process_sv(x)$map plot_bnd_sr_pr_tot_hist(d, "a title") } diff --git a/man/plot_bnd_sr_pr_tot_lines.Rd b/man/plot_bnd_sr_pr_tot_lines.Rd index 82e8e51..b0cae9d 100644 --- a/man/plot_bnd_sr_pr_tot_lines.Rd +++ b/man/plot_bnd_sr_pr_tot_lines.Rd @@ -25,7 +25,7 @@ Plots the number of split reads (\code{SR}), paired end reads (\code{PR}), and t sum (\code{tot}) across all BNDs, sorted by \code{tot}. } \examples{ -x <- system.file("extdata/umccrise/sv/manta.tsv", package = "gpgr") -d <- process_sv(x)$unmelted +x <- system.file("extdata/sash/sv.prioritised.tsv", package = "gpgr") +d <- process_sv(x)$map plot_bnd_sr_pr_tot_lines(d) } diff --git a/man/process_cnv_tsv.Rd b/man/process_cnv_tsv.Rd new file mode 100644 index 0000000..1b5d772 --- /dev/null +++ b/man/process_cnv_tsv.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/purple.R +\name{process_cnv_tsv} +\alias{process_cnv_tsv} +\title{Process CNV TSV} +\usage{ +process_cnv_tsv(x) +} +\arguments{ +\item{x}{Path to something.} +} +\value{ +List of many things. +} +\description{ +Process CNV TSV +} diff --git a/man/process_sv.Rd b/man/process_sv.Rd new file mode 100644 index 0000000..38986b5 --- /dev/null +++ b/man/process_sv.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/sv.R +\name{process_sv} +\alias{process_sv} +\title{Process SV TSV} +\usage{ +process_sv(x) +} +\arguments{ +\item{x}{Path to SV TSV.} +} +\value{ +List of many things. +} +\description{ +Process SV TSV +} diff --git a/man/read_oncokb.Rd b/man/read_oncokb.Rd new file mode 100644 index 0000000..43313e0 --- /dev/null +++ b/man/read_oncokb.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/oncokb.R +\name{read_oncokb} +\alias{read_oncokb} +\title{Read OncoKB} +\usage{ +read_oncokb(x) +} +\arguments{ +\item{x}{Path to something.} +} +\value{ +Vector of genes. +} +\description{ +Read OncoKB +} diff --git a/tests/testthat/test-roxytest-testexamples-purple.R b/tests/testthat/test-roxytest-testexamples-purple.R index 3f83ec0..528f853 100644 --- a/tests/testthat/test-roxytest-testexamples-purple.R +++ b/tests/testthat/test-roxytest-testexamples-purple.R @@ -19,7 +19,7 @@ test_that("Function purple_cnv_som_gene_process() @ L60", { }) -test_that("Function purple_cnv_som_read() @ L444", { +test_that("Function purple_cnv_som_read() @ L449", { x <- system.file("extdata/purple/purple.cnv.somatic.tsv", package = "gpgr") (p <- purple_cnv_som_read(x)) @@ -27,7 +27,7 @@ test_that("Function purple_cnv_som_read() @ L444", { }) -test_that("Function purple_cnv_som_process() @ L477", { +test_that("Function purple_cnv_som_process() @ L482", { x <- system.file("extdata/purple/purple.cnv.somatic.tsv", package = "gpgr") (pp <- purple_cnv_som_process(x)) @@ -35,7 +35,7 @@ test_that("Function purple_cnv_som_process() @ L477", { }) -test_that("Function purple_qc_read() @ L545", { +test_that("Function purple_qc_read() @ L550", { x <- system.file("extdata/purple/purple.qc", package = "gpgr") (q <- purple_qc_read(x)) @@ -43,7 +43,7 @@ test_that("Function purple_qc_read() @ L545", { }) -test_that("Function purple_purity_read() @ L603", { +test_that("Function purple_purity_read() @ L608", { x <- system.file("extdata/purple/purple.purity.tsv", package = "gpgr") (p <- purple_purity_read(x)) From 327f170424acaca503dd7b0626af3873322d8622 Mon Sep 17 00:00:00 2001 From: pdiakumis Date: Tue, 7 May 2024 09:49:32 +1000 Subject: [PATCH 8/8] can use dplyr instead of tidyselect --- DESCRIPTION | 3 +-- R/purple.R | 4 ++-- R/sv.R | 4 ++-- conda/recipe/meta.yaml | 2 -- 4 files changed, 5 insertions(+), 8 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index dfc9657..e06fa33 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -43,8 +43,7 @@ Suggests: scales, sigrap, testthat (>= 3.0.0), - tibble, - tidyselect, + tibble Roxygen: list(markdown = TRUE, roclets = c("namespace", "rd", "roxytest::testthat_roclet")) biocViews: diff --git a/R/purple.R b/R/purple.R index 1046aa4..16c00f3 100644 --- a/R/purple.R +++ b/R/purple.R @@ -643,7 +643,7 @@ purple_purity_read <- function(x) { purple_purity <- purple_purity |> dplyr::mutate( - dplyr::across(tidyselect::where(is.numeric), \(x) round(x, 2)), + dplyr::across(dplyr::where(is.numeric), \(x) round(x, 2)), dplyr::across(dplyr::everything(), as.character) ) |> tidyr::pivot_longer(dplyr::everything(), names_to = "column", values_to = "value") |> @@ -745,7 +745,7 @@ purple_kataegis <- function(x) { data <- d$data |> dplyr::filter(!is.na(.data$KT)) |> - dplyr::select(c("CHROM", "POS", tidyselect::all_of(info_cols))) + dplyr::select(c("CHROM", "POS", dplyr::all_of(info_cols))) description <- d$description |> dplyr::filter(.data$ID %in% info_cols) |> diff --git a/R/sv.R b/R/sv.R index 6a4ede5..1803bee 100644 --- a/R/sv.R +++ b/R/sv.R @@ -29,9 +29,9 @@ split_double_col <- function(d, nms) { assertthat::assert_that(is.character(nms)) outd <- d |> - dplyr::select(tidyselect::all_of(nms)) |> + dplyr::select(dplyr::all_of(nms)) |> dplyr::mutate(num = dplyr::row_number()) |> - tidyr::pivot_longer(cols = tidyselect::all_of(nms), names_to = "col_nm", values_to = "x1_x2") |> + tidyr::pivot_longer(cols = dplyr::all_of(nms), names_to = "col_nm", values_to = "x1_x2") |> tidyr::separate(.data$x1_x2, into = c("x1", "x2"), sep = ",", fill = "right") |> dplyr::mutate( x1 = round(as.double(.data$x1), 2), diff --git a/conda/recipe/meta.yaml b/conda/recipe/meta.yaml index 23a2291..2a58a59 100644 --- a/conda/recipe/meta.yaml +++ b/conda/recipe/meta.yaml @@ -43,7 +43,6 @@ requirements: - r-scales - r-testthat - r-tibble - - r-tidyselect run: - r-base @@ -73,7 +72,6 @@ requirements: - r-scales - r-testthat - r-tibble - - r-tidyselect test: commands: