Skip to content

Commit

Permalink
improvement
Browse files Browse the repository at this point in the history
  • Loading branch information
cparsania committed Jan 8, 2024
1 parent 705c8fa commit aa8be69
Show file tree
Hide file tree
Showing 9 changed files with 23 additions and 7 deletions.
18 changes: 13 additions & 5 deletions R/splicewiz_wrappers.R
Original file line number Diff line number Diff line change
Expand Up @@ -326,10 +326,12 @@ get_ase_data_matrix_heatmap <- function(se,
#' SpliceWiz::colData(se)$replicate <- rep(c("P","Q","R"), 2)
#' res_edgeR <- SpliceWiz::ASE_edgeR(se, "treatment", "A", "B", useQL = FALSE)
#' get_genes_from_event_name(res_edgeR$EventName)
get_genes_from_event_name <- function(x){
get_genes_from_event_name <- function(x ){

x %>% stringr::str_replace( pattern = ".*;(.*)-.*-.*", replacement = "\\1") %>%
stringr::str_replace(pattern = "\\/.*", replacement = "")


x %>% stringr::str_replace( pattern = ".*;(.*)-.*-.*", replacement = "\\1") %>%
stringr::str_replace(pattern = "\\/.*", replacement = "")
}


Expand Down Expand Up @@ -678,7 +680,9 @@ get_ASEsets_by_regulation <- function(x, sample_comparisons, regulation = "both"
#' @param facet_drop pass to the argument `drop` of [ggplot2::facet_wrap()].
#' @param facet_dir pass to the argument `dir` of [ggplot2::facet_wrap()].
#' @param facet_strip.position pass to the argument `position` of [ggplot2::facet_wrap()].
#' @param event_type a character string, default "IR" denoting valid event_type to display in the volcano plot. Values could be one of the "IR","SE","AFE","ALE","MXE","A3SS","A5SS".
#' @param ... other parameters to be passed to [EnhancedVolcano::EnhancedVolcano()].
#'
#' @details
#' + repair_ASE: Internally event names are taken from SpliceWiz. When repair_genes is set to TRUE the string corresponding to gene symbol will be extracted.
#' if one gene symbol assinged to more than one events, even names will be used instead of gene symbol (usually the case). This is useful when gene names to be revealed in the volcano plot.
Expand All @@ -699,6 +703,7 @@ get_ASEsets_by_regulation <- function(x, sample_comparisons, regulation = "both"
#' get_ase_volcano_plot(res, sample_comparison = res$de_comparisons[1], pval_cutoff = 1,ASE_to_display = "") %>% print()
get_ase_volcano_plot <- function(x,
sample_comparison,
event_type = "IR",
log2fc_cutoff = 1,
pval_cutoff = 0.05,
ASE_to_display = NULL,
Expand Down Expand Up @@ -735,7 +740,8 @@ get_ase_volcano_plot <- function(x,
# prepare volcano plots

# filter by sample_comparison
volcano_data <- x$res_ase_diff_tibble[[sample_comparison]] %>%dplyr::select(event_name, log2FoldChange , pvalue, event_type)
volcano_data <- x$res_ase_diff_tibble[[sample_comparison]] %>%
dplyr::filter(event_type %in% !!rlang::enquo(event_type)) %>%dplyr::select(event_name, log2FoldChange , pvalue, event_type)


# Fix ASE names. It gives gene names if it's unique. Otherwise event names will be returned.
Expand Down Expand Up @@ -768,7 +774,9 @@ get_ase_volcano_plot <- function(x,
if(facet_event_type){
pp <- pp + ggplot2::facet_wrap(~event_type,
nrow = facte_nrow,
scales = facet_scale, ncol = facet_ncol, shrink = facet_shrink,labeller = facet_labeller,as.table = facet_as.table,
scales = facet_scale,
ncol = facet_ncol,
shrink = facet_shrink,labeller = facet_labeller,as.table = facet_as.table,
drop = facet_drop, dir = facet_dir,strip.position = facet_strip.position)
}

Expand Down
Binary file modified docs/reference/Rplot001.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file modified docs/reference/Rplot002.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file modified docs/reference/Rplot003.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file modified docs/reference/get_ase_volcano_plot-1.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file modified docs/reference/get_ase_volcano_plot-2.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file modified docs/reference/get_ase_volcano_plot-3.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
9 changes: 7 additions & 2 deletions docs/reference/get_ase_volcano_plot.html

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

3 changes: 3 additions & 0 deletions man/get_ase_volcano_plot.Rd

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

0 comments on commit aa8be69

Please sign in to comment.