28ca343e |
plot_region_impl <- function(
|
ab9a50cb |
x,
chr,
start,
end,
anno_regions = NULL,
binary_threshold = NULL,
avg_method = c("mean", "median"),
spaghetti = FALSE,
|
28ca343e |
heatmap = TRUE,
|
31e7ca42 |
heatmap_subsample = 50,
|
ad7d8e6f |
smoothing_window = 2000,
|
851790c0 |
gene_anno = TRUE,
|
ab9a50cb |
window_prop = 0,
palette = ggplot2::scale_colour_brewer(palette = "Set1"),
|
8d6266e0 |
line_size = 1,
|
d0abf45a |
mod_scale = c(0, 1),
span = NULL
|
8822bde7 |
) {
|
7aa2a454 |
sample_anno <- samples(x)
|
851790c0 |
chr <- as.character(chr)
start <- as.numeric(start)
end <- as.numeric(end)
|
97023ecf |
|
9a1cc2e3 |
if (length(window_prop) == 1) {
window_prop <- c(window_prop, window_prop)
}
|
d285ae73 |
feature_width <- end - start
window_left <- feature_width * window_prop[1]
window_right <- feature_width * window_prop[2]
|
7aa2a454 |
|
7258dbe3 |
# query data
methy_data <- query_methy(
x,
chr,
floor(start - window_left * 1.1),
ceiling(end + window_right * 1.1),
simplify = TRUE
)
|
7aa2a454 |
|
97023ecf |
if (nrow(methy_data) == 0) {
|
7258dbe3 |
warning("no methylation data in region, returning empty plot")
|
97023ecf |
return(ggplot() + theme_void())
}
|
06fc6748 |
methy_data <- methy_data %>%
dplyr::select(-"strand") %>%
tibble::as_tibble()
|
7258dbe3 |
# setup base plot
|
87424cdf |
title <- glue::glue("{chr}:{start}-{end}")
|
a85f4c4d |
xlim <- round(c(start - window_left, end + window_right))
|
aa613f61 |
p1 <- plot_methylation_data(
|
517b58a9 |
methy_data = methy_data,
start = start,
end = end,
chr = chr,
title = title,
anno_regions = anno_regions,
binary_threshold = binary_threshold,
avg_method = avg_method,
spaghetti = spaghetti,
sample_anno = sample_anno,
smoothing_window = smoothing_window,
palette_col = palette,
line_size = line_size,
mod_scale = mod_scale
) +
ggplot2::coord_cartesian(xlim = xlim, expand = FALSE) +
|
00d2a794 |
ggplot2::labs(x = "Position", y = "Mean Modification Probability")
|
7aa2a454 |
|
d2b5a6db |
p_out <- p1
|
7aa2a454 |
|
7258dbe3 |
# if exon anno exists, append it to plot
|
851790c0 |
if (gene_anno && nrow(exons(x)) != 0) {
exons_anno <- query_exons_region(x, chr = chr, start = start, end = end)
|
d2b5a6db |
p2 <- plot_gene_annotation(exons_anno, xlim[1], xlim[2]) +
|
7258dbe3 |
ggplot2::coord_cartesian(xlim = xlim, expand = FALSE) +
ggplot2::scale_x_continuous(labels = scales::label_number(scale_cut = scales::cut_si("b")))
|
7aa2a454 |
|
7258dbe3 |
anno_height <- attr(p2, "plot_height")
|
d2b5a6db |
heights <- c(1, 0.075 * anno_height)
|
7258dbe3 |
|
d2b5a6db |
p_out <- p1 / p2 + patchwork::plot_layout(heights = heights)
}
|
f288966d |
|
7258dbe3 |
# if heatmap requested, append it to plot
|
f288966d |
if (heatmap) {
|
31e7ca42 |
p_heatmap <- plot_region_heatmap(x, chr, start, end, window_prop = window_prop, subsample = heatmap_subsample) +
|
a85f4c4d |
ggplot2::coord_cartesian(
|
53eb726a |
xlim = xlim
|
5950d856 |
)
|
ca260337 |
p_out <- stack_plots(p_out, ggrastr::rasterise(p_heatmap, dpi = 300))
|
f288966d |
}
p_out
|
7aa2a454 |
}
|
28ca343e |
#' @rdname plot_region
#'
#' @param anno_regions the data.frame of regions to be annotated.
#' @param binary_threshold the modification probability such that calls with
#' modification probability above the threshold are set to 1 and probabilities
#' equal to or below the threshold are set to 0.
#' @param avg_method the average method for pre-smoothing at each genomic position.
#' Data is pre-smoothed at each genomic position before the smoothed aggregate line
#' is generated for performance reasons. The default is "mean" which corresponds
#' to the average methylation fraction. The alternative "median" option is
#' closer to an average within the more common methylation state.
#' @param spaghetti whether or not individual reads should be shown.
#' @param heatmap whether or not read-methylation heatmap should be shown.
#' @param heatmap_subsample how many packed rows of reads to subsample to.
#' @param smoothing_window the window size for smoothing the trend line.
#' @param gene_anno whether to show gene annotation.
#' @param window_prop the size of flanking region to plot. Can be a vector of two
#' values for left and right window size. Values indicate proportion of gene
#' length.
#' @param palette the ggplot colour palette used for groups.
#' @param line_size the size of the lines.
#' @param mod_scale the scale range for modification probabilities. Default c(0, 1), set to "auto" for automatic
#' limits.
#' @param span DEPRECATED, use smoothing_window instead. Will be removed in next version.
#'
#' @details
|
1fa5ca22 |
#' This function plots the methylation data for a given region. The main trendline plot shows the average methylation
#' probability across the region. The heatmap plot shows the methylation probability for each read across the region.
#' The gene annotation plot shows the exons of the region. In the heatmap, each row represents one or more
#' non-overlapping reads where the coloured segments represent the methylation probability at each position. Data along
#' a read is connected by a grey line. The gene annotation plot shows the isoforms and exons of genes within the region,
#' with arrows indicating the direction of transcription.
#'
#' Since V3.0.0 NanoMethViz has changed the smoothing strategy from a loess smoothing to a weighted moving average. This
#' is because the loess smoothing was too computationally expensive for large datasets and had a span parameter that was
#' difficult to tune. The new smoothing strategy is controlled by the smoothing_window argument.
|
28ca343e |
#'
#' @examples
#' nmr <- load_example_nanomethresult()
#' plot_region(nmr, "chr7", 6703892, 6730431)
#'
#' @export
setMethod("plot_region",
signature(x = "NanoMethResult", chr = "character", start = "numeric", end = "numeric"),
plot_region_impl
)
#' @rdname plot_region
#' @export
setMethod("plot_region",
signature(x = "ModBamResult", chr = "character", start = "numeric", end = "numeric"),
plot_region_impl
)
#' @rdname plot_region
#' @export
setMethod("plot_region",
signature(x = "NanoMethResult", chr = "factor", start = "numeric", end = "numeric"),
plot_region_impl
)
#' @rdname plot_region
#' @export
setMethod("plot_region",
signature(x = "ModBamResult", chr = "factor", start = "numeric", end = "numeric"),
plot_region_impl
)
|