Browse code

Added check for presence of exon annotation

shians authored on 27/05/2024 07:45:34
Showing 1 changed files
... ...
@@ -21,7 +21,9 @@ plot_agg_genes <- function(
21 21
     span = 0.05,
22 22
     palette = ggplot2::scale_colour_brewer(palette = "Set1")
23 23
 ) {
24
-    gene_regions <- exons_to_genes(exons(x))
24
+    assertthat::assert_that(nrow(exons(x)) > 0, msg = "no exon annotations found in object")
25
+
26
+    gene_regions <- exons_to_genes(x)
25 27
     if (!is.null(genes)) {
26 28
         gene_regions <- gene_regions %>%
27 29
             filter(.data$symbol %in% genes)
... ...
@@ -49,7 +51,9 @@ plot_agg_tss <- function(
49 51
     span = 0.05,
50 52
     palette = ggplot2::scale_colour_brewer(palette = "Set1")
51 53
 ) {
52
-    gene_regions <- exons_to_genes(exons(x))
54
+    assertthat::assert_that(nrow(exons(x)) > 0, msg = "no exon annotations found in object")
55
+
56
+    gene_regions <- exons_to_genes(x)
53 57
     if (!is.null(genes)) {
54 58
         gene_regions <- gene_regions %>%
55 59
             filter(.data$symbol %in% genes)
... ...
@@ -103,7 +107,9 @@ plot_agg_tes <- function(
103 107
     span = 0.05,
104 108
     palette = ggplot2::scale_colour_brewer(palette = "Set1")
105 109
 ) {
106
-    gene_regions <- exons_to_genes(exons(x))
110
+    assertthat::assert_that(nrow(exons(x)) > 0, msg = "no exon annotations found in object")
111
+
112
+    gene_regions <- exons_to_genes(x)
107 113
     if (!is.null(genes)) {
108 114
         gene_regions <- gene_regions %>%
109 115
             filter(.data$symbol %in% genes)
Browse code

Linting

shians authored on 29/02/2024 05:18:23
Showing 1 changed files
... ...
@@ -63,7 +63,7 @@ plot_agg_tss <- function(
63 63
         ) %>%
64 64
         mutate(
65 65
             start = .data$start - flank,
66
-            end = .data$start + 2*flank
66
+            end = .data$start + 2 * flank
67 67
         )
68 68
     kb_marker <- round(flank / 1000, 1)
69 69
     labels <- c(
... ...
@@ -117,7 +117,7 @@ plot_agg_tes <- function(
117 117
         ) %>%
118 118
         mutate(
119 119
             start = .data$start - flank,
120
-            end = .data$start + 2*flank
120
+            end = .data$start + 2 * flank
121 121
         )
122 122
     kb_marker <- round(flank / 1000, 1)
123 123
     labels <- c(
Browse code

Exported `plot_agg_genes()`

Shians authored on 10/10/2022 06:34:21
Showing 1 changed files
... ...
@@ -5,6 +5,8 @@
5 5
 #'
6 6
 #' @return a ggplot object containing the aggregate methylation trend of genes.
7 7
 #'
8
+#' @export
9
+#'
8 10
 #' @examples
9 11
 #' nmr <- load_example_nanomethresult()
10 12
 #' plot_agg_genes(nmr)
... ...
@@ -55,13 +57,13 @@ plot_agg_tss <- function(
55 57
     tss_regions <- gene_regions %>%
56 58
         mutate(
57 59
             start = case_when(
58
-                strand == "+" ~ start,
59
-                strand == "-" ~ end,
60
-                TRUE ~ start)
60
+                strand == "+" ~ .data$start,
61
+                strand == "-" ~ .data$end,
62
+                TRUE ~ .data$start)
61 63
         ) %>%
62 64
         mutate(
63
-            start = start - flank,
64
-            end = start + 2*flank
65
+            start = .data$start - flank,
66
+            end = .data$start + 2*flank
65 67
         )
66 68
     kb_marker <- round(flank / 1000, 1)
67 69
     labels <- c(
... ...
@@ -109,13 +111,13 @@ plot_agg_tes <- function(
109 111
     tes_regions <- gene_regions %>%
110 112
         mutate(
111 113
             start = case_when(
112
-                strand == "+" ~ end,
113
-                strand == "-" ~ start,
114
-                TRUE ~ end)
114
+                strand == "+" ~ .data$end,
115
+                strand == "-" ~ .data$start,
116
+                TRUE ~ .data$end)
115 117
         ) %>%
116 118
         mutate(
117
-            start = start - flank,
118
-            end = start + 2*flank
119
+            start = .data$start - flank,
120
+            end = .data$start + 2*flank
119 121
         )
120 122
     kb_marker <- round(flank / 1000, 1)
121 123
     labels <- c(
Browse code

Fixed TES location when strand is *

Shians authored on 26/09/2022 01:46:55
Showing 1 changed files
... ...
@@ -111,7 +111,7 @@ plot_agg_tes <- function(
111 111
             start = case_when(
112 112
                 strand == "+" ~ end,
113 113
                 strand == "-" ~ start,
114
-                TRUE ~ start)
114
+                TRUE ~ end)
115 115
         ) %>%
116 116
         mutate(
117 117
             start = start - flank,
Browse code

Added utility aggregate plots `plot_agg_genes()`, `plot_agg_tss()` and `plot_agg_tes()`.

Shians authored on 08/09/2022 03:44:21
Showing 1 changed files
1 1
new file mode 100644
... ...
@@ -0,0 +1,146 @@
1
+#' Plot gene aggregate plot
2
+#'
3
+#' @param genes a character vector of genes to include in aggregate plot, if NULL then all genes are used.
4
+#' @inheritParams plot_agg_regions
5
+#'
6
+#' @return a ggplot object containing the aggregate methylation trend of genes.
7
+#'
8
+#' @examples
9
+#' nmr <- load_example_nanomethresult()
10
+#' plot_agg_genes(nmr)
11
+#'
12
+plot_agg_genes <- function(
13
+    x,
14
+    genes = NULL,
15
+    binary_threshold = 0.5,
16
+    group_col = NULL,
17
+    flank = 2000,
18
+    stranded = TRUE,
19
+    span = 0.05,
20
+    palette = ggplot2::scale_colour_brewer(palette = "Set1")
21
+) {
22
+    gene_regions <- exons_to_genes(exons(x))
23
+    if (!is.null(genes)) {
24
+        gene_regions <- gene_regions %>%
25
+            filter(.data$symbol %in% genes)
26
+    }
27
+
28
+    plot_agg_regions(
29
+        x,
30
+        regions = gene_regions,
31
+        binary_threshold = binary_threshold,
32
+        group_col = group_col,
33
+        flank = flank,
34
+        stranded = stranded,
35
+        span = span,
36
+        palette = palette
37
+    )
38
+}
39
+
40
+plot_agg_tss <- function(
41
+    x,
42
+    genes = NULL,
43
+    binary_threshold = 0.5,
44
+    group_col = NULL,
45
+    flank = 2000,
46
+    stranded = TRUE,
47
+    span = 0.05,
48
+    palette = ggplot2::scale_colour_brewer(palette = "Set1")
49
+) {
50
+    gene_regions <- exons_to_genes(exons(x))
51
+    if (!is.null(genes)) {
52
+        gene_regions <- gene_regions %>%
53
+            filter(.data$symbol %in% genes)
54
+    }
55
+    tss_regions <- gene_regions %>%
56
+        mutate(
57
+            start = case_when(
58
+                strand == "+" ~ start,
59
+                strand == "-" ~ end,
60
+                TRUE ~ start)
61
+        ) %>%
62
+        mutate(
63
+            start = start - flank,
64
+            end = start + 2*flank
65
+        )
66
+    kb_marker <- round(flank / 1000, 1)
67
+    labels <- c(
68
+        glue::glue("-{kb_marker}kb"),
69
+        "TSS",
70
+        glue::glue("+{kb_marker}kb")
71
+    )
72
+
73
+    p <- plot_agg_regions(
74
+        x,
75
+        regions = tss_regions,
76
+        binary_threshold = binary_threshold,
77
+        group_col = group_col,
78
+        flank = 0,
79
+        stranded = stranded,
80
+        span = span,
81
+        palette = palette
82
+    )
83
+    # hack to delete existing to avoid warning
84
+    p$scales$scales[[which(p$scales$find("x"))]] <- NULL
85
+
86
+    p + ggplot2::scale_x_continuous(
87
+        name = glue::glue(""),
88
+        breaks = c(0, 0.5, 1),
89
+        limits = c(0, 1),
90
+        labels = labels
91
+    )
92
+}
93
+
94
+plot_agg_tes <- function(
95
+    x,
96
+    genes = NULL,
97
+    binary_threshold = 0.5,
98
+    group_col = NULL,
99
+    flank = 2000,
100
+    stranded = TRUE,
101
+    span = 0.05,
102
+    palette = ggplot2::scale_colour_brewer(palette = "Set1")
103
+) {
104
+    gene_regions <- exons_to_genes(exons(x))
105
+    if (!is.null(genes)) {
106
+        gene_regions <- gene_regions %>%
107
+            filter(.data$symbol %in% genes)
108
+    }
109
+    tes_regions <- gene_regions %>%
110
+        mutate(
111
+            start = case_when(
112
+                strand == "+" ~ end,
113
+                strand == "-" ~ start,
114
+                TRUE ~ start)
115
+        ) %>%
116
+        mutate(
117
+            start = start - flank,
118
+            end = start + 2*flank
119
+        )
120
+    kb_marker <- round(flank / 1000, 1)
121
+    labels <- c(
122
+        glue::glue("-{kb_marker}kb"),
123
+        "TES",
124
+        glue::glue("+{kb_marker}kb")
125
+    )
126
+
127
+    p <- plot_agg_regions(
128
+        x,
129
+        regions = tes_regions,
130
+        binary_threshold = binary_threshold,
131
+        group_col = group_col,
132
+        flank = 0,
133
+        stranded = stranded,
134
+        span = span,
135
+        palette = palette
136
+    )
137
+    # hack to delete existing to avoid warning
138
+    p$scales$scales[[which(p$scales$find("x"))]] <- NULL
139
+
140
+    p + ggplot2::scale_x_continuous(
141
+        name = glue::glue(""),
142
+        breaks = c(0, 0.5, 1),
143
+        limits = c(0, 1),
144
+        labels = labels
145
+    )
146
+}