... | ... |
@@ -38,6 +38,8 @@ export(modify) |
38 | 38 |
export(pileupToCoverage) |
39 | 39 |
export(plotCompare) |
40 | 40 |
export(plotCompareByCoord) |
41 |
+export(plotData) |
|
42 |
+export(plotDataByCoord) |
|
41 | 43 |
export(plotROC) |
42 | 44 |
export(replicates) |
43 | 45 |
export(sequenceData) |
... | ... |
@@ -46,8 +48,6 @@ export(settings) |
46 | 48 |
export(subsetByCoord) |
47 | 49 |
export(validAggregate) |
48 | 50 |
export(validModification) |
49 |
-export(visualizeData) |
|
50 |
-export(visualizeDataByCoord) |
|
51 | 51 |
exportClasses(CoverageSequenceData) |
52 | 52 |
exportClasses(End3SequenceData) |
53 | 53 |
exportClasses(End5SequenceData) |
... | ... |
@@ -89,6 +89,8 @@ exportMethods(modify) |
89 | 89 |
exportMethods(names) |
90 | 90 |
exportMethods(pileupToCoverage) |
91 | 91 |
exportMethods(plotCompareByCoord) |
92 |
+exportMethods(plotData) |
|
93 |
+exportMethods(plotDataByCoord) |
|
92 | 94 |
exportMethods(plotROC) |
93 | 95 |
exportMethods(ranges) |
94 | 96 |
exportMethods(replicates) |
... | ... |
@@ -99,8 +101,6 @@ exportMethods(settings) |
99 | 101 |
exportMethods(subsetByCoord) |
100 | 102 |
exportMethods(validAggregate) |
101 | 103 |
exportMethods(validModification) |
102 |
-exportMethods(visualizeData) |
|
103 |
-exportMethods(visualizeDataByCoord) |
|
104 | 104 |
import(GenomicRanges) |
105 | 105 |
import(Gviz) |
106 | 106 |
import(S4Vectors) |
... | ... |
@@ -16,7 +16,7 @@ NULL |
16 | 16 |
#' @export |
17 | 17 |
setGeneric( |
18 | 18 |
name = "plotROC", |
19 |
- signature = c("x"), |
|
19 |
+ signature = "x", |
|
20 | 20 |
def = function(x, coord, ...) |
21 | 21 |
standardGeneric("plotROC") |
22 | 22 |
) |
... | ... |
@@ -81,35 +81,35 @@ setGeneric( |
81 | 81 |
#' @rdname Modifier-functions |
82 | 82 |
#' @export |
83 | 83 |
setGeneric( |
84 |
- name = "settings", |
|
85 |
- def = function(x, name = NULL) standardGeneric("settings") |
|
84 |
+ name = "validAggregate", |
|
85 |
+ def = function(x) standardGeneric("validAggregate") |
|
86 | 86 |
) |
87 | 87 |
#' @rdname Modifier-functions |
88 | 88 |
#' @export |
89 | 89 |
setGeneric( |
90 |
- name = "settings<-", |
|
91 |
- def = function(x, name, value) standardGeneric("settings<-") |
|
90 |
+ name = "validModification", |
|
91 |
+ def = function(x) standardGeneric("validModification") |
|
92 | 92 |
) |
93 |
-#' @rdname Modifier-functions |
|
93 |
+ |
|
94 |
+#' @rdname settings |
|
94 | 95 |
#' @export |
95 | 96 |
setGeneric( |
96 |
- name = "validAggregate", |
|
97 |
- def = function(x) standardGeneric("validAggregate") |
|
97 |
+ name = "settings", |
|
98 |
+ def = function(x, name = NULL) standardGeneric("settings") |
|
98 | 99 |
) |
99 |
-#' @rdname Modifier-functions |
|
100 |
+#' @rdname settings |
|
100 | 101 |
#' @export |
101 | 102 |
setGeneric( |
102 |
- name = "validModification", |
|
103 |
- def = function(x) standardGeneric("validModification") |
|
103 |
+ name = "settings<-", |
|
104 |
+ def = function(x, name, value) standardGeneric("settings<-") |
|
104 | 105 |
) |
105 |
- |
|
106 | 106 |
# Modifier/ModifierSet functions ----------------------------------------------- |
107 | 107 |
|
108 | 108 |
#' @rdname modify |
109 | 109 |
#' @export |
110 | 110 |
setGeneric( |
111 | 111 |
name = "modify", |
112 |
- signature = c("x"), |
|
112 |
+ signature = "x", |
|
113 | 113 |
def = function(x, ...) standardGeneric("modify") |
114 | 114 |
) |
115 | 115 |
|
... | ... |
@@ -117,7 +117,7 @@ setGeneric( |
117 | 117 |
#' @export |
118 | 118 |
setGeneric( |
119 | 119 |
name = "findMod", |
120 |
- signature = c("x"), |
|
120 |
+ signature = "x", |
|
121 | 121 |
def = function(x) standardGeneric("findMod") |
122 | 122 |
) |
123 | 123 |
|
... | ... |
@@ -128,7 +128,7 @@ setGeneric( |
128 | 128 |
#' @export |
129 | 129 |
setGeneric( |
130 | 130 |
name = "aggregate", |
131 |
- signature = c("x"), |
|
131 |
+ signature = "x", |
|
132 | 132 |
def = function(x, ...) standardGeneric("aggregate") |
133 | 133 |
) |
134 | 134 |
#' @rdname aggregate |
... | ... |
@@ -141,14 +141,14 @@ setGeneric( |
141 | 141 |
#' @export |
142 | 142 |
setGeneric( |
143 | 143 |
name = "getAggregateData", |
144 |
- signature = c("x"), |
|
144 |
+ signature = "x", |
|
145 | 145 |
def = function(x) standardGeneric("getAggregateData") |
146 | 146 |
) |
147 | 147 |
#' @rdname aggregate |
148 | 148 |
#' @export |
149 | 149 |
setGeneric( |
150 | 150 |
name = "hasAggregateData", |
151 |
- signature = c("x"), |
|
151 |
+ signature = "x", |
|
152 | 152 |
def = function(x) standardGeneric("hasAggregateData") |
153 | 153 |
) |
154 | 154 |
|
... | ... |
@@ -170,27 +170,27 @@ setGeneric( |
170 | 170 |
def = function(x, coord, ...) |
171 | 171 |
standardGeneric("labelByCoord") |
172 | 172 |
) |
173 |
-#' @rdname visualizeData |
|
173 |
+#' @rdname plotData |
|
174 | 174 |
#' @export |
175 | 175 |
setGeneric( |
176 |
- name = "visualizeData", |
|
177 |
- signature = c("x"), |
|
176 |
+ name = "plotData", |
|
177 |
+ signature = "x", |
|
178 | 178 |
def = function(x, name, from = 1L, to = 30L, type, ...) |
179 |
- standardGeneric("visualizeData") |
|
179 |
+ standardGeneric("plotData") |
|
180 | 180 |
) |
181 |
-#' @rdname visualizeData |
|
181 |
+#' @rdname plotData |
|
182 | 182 |
#' @export |
183 | 183 |
setGeneric( |
184 |
- name = "visualizeDataByCoord", |
|
184 |
+ name = "plotDataByCoord", |
|
185 | 185 |
signature = c("x","coord"), |
186 | 186 |
def = function(x, coord, type, window.size = 15L, ...) |
187 |
- standardGeneric("visualizeDataByCoord") |
|
187 |
+ standardGeneric("plotDataByCoord") |
|
188 | 188 |
) |
189 |
-#' @rdname visualizeData |
|
189 |
+#' @rdname plotData |
|
190 | 190 |
#' @export |
191 | 191 |
setGeneric( |
192 | 192 |
name = "getDataTrack", |
193 |
- signature = c("x"), |
|
193 |
+ signature = "x", |
|
194 | 194 |
def = function(x, name, ...) |
195 | 195 |
standardGeneric("getDataTrack") |
196 | 196 |
) |
... | ... |
@@ -201,7 +201,7 @@ setGeneric( |
201 | 201 |
#' @export |
202 | 202 |
setGeneric( |
203 | 203 |
name = "compare", |
204 |
- signature = c("x"), |
|
204 |
+ signature = "x", |
|
205 | 205 |
def = function(x, name, from = 1L, to = 30L, ...) |
206 | 206 |
standardGeneric("compare") |
207 | 207 |
) |
... | ... |
@@ -217,7 +217,7 @@ setGeneric( |
217 | 217 |
#' @export |
218 | 218 |
setGeneric( |
219 | 219 |
name = "plotCompare", |
220 |
- signature = c("x"), |
|
220 |
+ signature = "x", |
|
221 | 221 |
def = function(x, name, from = 1L, to = 30L, normalize, ...) |
222 | 222 |
standardGeneric("plotCompare") |
223 | 223 |
) |
... | ... |
@@ -105,10 +105,10 @@ NULL |
105 | 105 |
#' see also the man pages for the functions mentioned below. |
106 | 106 |
#' @param value See \code{\link[RNAmodR:Modifier-functions]{settings}} |
107 | 107 |
#' @param coord,name,from,to,type,window.size,... See |
108 |
-#' \code{\link{visualizeData}} |
|
108 |
+#' \code{\link{plotData}} |
|
109 | 109 |
#' |
110 | 110 |
#' @details |
111 |
-#' \code{ModInosine} specific arguments for \link{visualizeData}: |
|
111 |
+#' \code{ModInosine} specific arguments for \link{plotData}: |
|
112 | 112 |
#' \itemize{ |
113 | 113 |
#' \item{\code{colour.bases} - }{a named character vector of \code{length = 4} |
114 | 114 |
#' for the colours of the individual bases. The names are expected to be |
... | ... |
@@ -122,9 +122,9 @@ NULL |
122 | 122 |
#' \item{\code{modify}} {See \code{\link{modify}}.} |
123 | 123 |
#' \item{\code{getDataTrack}} {a list of |
124 | 124 |
#' \code{\link[Gviz:DataTrack-class]{DataTrack}} objects. See |
125 |
-#' \code{\link{visualizeDataByCoord}}.} |
|
126 |
-#' \item{\code{visualizeData}} {See \code{\link{visualizeDataByCoord}}.} |
|
127 |
-#' \item{\code{visualizeDataByCoord}} {See \code{\link{visualizeDataByCoord}}.} |
|
125 |
+#' \code{\link{plotDataByCoord}}.} |
|
126 |
+#' \item{\code{plotData}} {See \code{\link{plotDataByCoord}}.} |
|
127 |
+#' \item{\code{plotDataByCoord}} {See \code{\link{plotDataByCoord}}.} |
|
128 | 128 |
#' } |
129 | 129 |
#' |
130 | 130 |
#' @examples |
... | ... |
@@ -227,7 +227,7 @@ setMethod(f = "aggregateData", |
227 | 227 |
|
228 | 228 |
.find_inosine <- function(x){ |
229 | 229 |
if(!hasAggregateData(x)){ |
230 |
- stop("Something went wrong.") |
|
230 |
+ stop("") |
|
231 | 231 |
} |
232 | 232 |
letters <- IRanges::CharacterList(strsplit(as.character(sequences(x)),"")) |
233 | 233 |
# get the aggregate data |
... | ... |
@@ -243,7 +243,7 @@ setMethod(f = "aggregateData", |
243 | 243 |
# find inosine positions by looking for A to G conversion at position with |
244 | 244 |
# enough coverage |
245 | 245 |
grl <- ranges(x) |
246 |
- modifications <- mapply( |
|
246 |
+ modifications <- Map( |
|
247 | 247 |
function(m,c,l,r){ |
248 | 248 |
m <- m[l == "A" & |
249 | 249 |
m$score >= minScore & |
... | ... |
@@ -257,19 +257,17 @@ setMethod(f = "aggregateData", |
257 | 257 |
mod, |
258 | 258 |
coverage, |
259 | 259 |
letters, |
260 |
- grl, |
|
261 |
- SIMPLIFY = FALSE) |
|
260 |
+ grl) |
|
262 | 261 |
f <- !vapply(modifications, |
263 | 262 |
is.null, |
264 | 263 |
logical(1)) |
265 |
- modifications <- mapply( |
|
264 |
+ modifications <- Map( |
|
266 | 265 |
function(m,name){ |
267 | 266 |
m$Parent <- name |
268 | 267 |
m |
269 | 268 |
}, |
270 | 269 |
modifications[f], |
271 |
- names(grl)[f], |
|
272 |
- SIMPLIFY = FALSE) |
|
270 |
+ names(grl)[f]) |
|
273 | 271 |
modifications <- GenomicRanges::GRangesList(modifications) |
274 | 272 |
unname(unlist(modifications)) |
275 | 273 |
} |
... | ... |
@@ -2,10 +2,10 @@ |
2 | 2 |
#' @include Modifier-Inosine-class.R |
3 | 3 |
NULL |
4 | 4 |
|
5 |
-RNAMODR_I_PLOT_DATA <- c("score") |
|
6 |
-RNAMODR_I_PLOT_DATA_DEFAULT <- c("score") |
|
5 |
+RNAMODR_I_PLOT_DATA <- "score" |
|
6 |
+RNAMODR_I_PLOT_DATA_DEFAULT <- "score" |
|
7 | 7 |
|
8 |
-RNAMODR_I_PLOT_DATA_COLOURS <- c("score" = "#ABABAB") |
|
8 |
+RNAMODR_I_PLOT_DATA_COLOURS <- c(score = "#ABABAB") |
|
9 | 9 |
RNAMODR_I_PLOT_DATA_NAMES <- c(score = "Score Inosine") |
10 | 10 |
|
11 | 11 |
.norm_viz_mod_inosine_args <- function(input, type){ |
... | ... |
@@ -66,7 +66,7 @@ setMethod( |
66 | 66 |
#' @rdname ModInosine-functions |
67 | 67 |
#' @export |
68 | 68 |
setMethod( |
69 |
- f = "visualizeDataByCoord", |
|
69 |
+ f = "plotDataByCoord", |
|
70 | 70 |
signature = signature(x = "ModInosine", coord = "GRanges"), |
71 | 71 |
definition = function(x, coord, type = "score", window.size = 15L, ...) { |
72 | 72 |
if(missing(type)){ |
... | ... |
@@ -80,7 +80,7 @@ setMethod( |
80 | 80 |
#' @rdname ModInosine-functions |
81 | 81 |
#' @export |
82 | 82 |
setMethod( |
83 |
- f = "visualizeData", |
|
83 |
+ f = "plotData", |
|
84 | 84 |
signature = signature(x = "ModInosine"), |
85 | 85 |
definition = function(x, name, from, to, type = "score", ...) { |
86 | 86 |
if(missing(type)){ |
... | ... |
@@ -94,7 +94,7 @@ setMethod( |
94 | 94 |
#' @rdname ModInosine-functions |
95 | 95 |
#' @export |
96 | 96 |
setMethod( |
97 |
- f = "visualizeDataByCoord", |
|
97 |
+ f = "plotDataByCoord", |
|
98 | 98 |
signature = signature(x = "ModSetInosine", coord = "GRanges"), |
99 | 99 |
definition = function(x, coord, type = "score", window.size = 15L, ...) { |
100 | 100 |
if(missing(type)){ |
... | ... |
@@ -108,7 +108,7 @@ setMethod( |
108 | 108 |
#' @rdname ModInosine-functions |
109 | 109 |
#' @export |
110 | 110 |
setMethod( |
111 |
- f = "visualizeData", |
|
111 |
+ f = "plotData", |
|
112 | 112 |
signature = signature(x = "ModSetInosine"), |
113 | 113 |
definition = function(x, name, from, to, type = "score", ...) { |
114 | 114 |
if(missing(type)){ |
... | ... |
@@ -5,6 +5,10 @@ |
5 | 5 |
#' @include Modifier-utils.R |
6 | 6 |
NULL |
7 | 7 |
|
8 |
+invalidMessage <- paste0("Settings were changed after data aggregation or ", |
|
9 |
+ "modification search. Rerun with modify(x,force = ", |
|
10 |
+ "TRUE) to update with current settings.") |
|
11 |
+ |
|
8 | 12 |
#' @name Modifier-class |
9 | 13 |
#' @aliases Modifier |
10 | 14 |
#' |
... | ... |
@@ -61,6 +65,11 @@ NULL |
61 | 65 |
#' For this example a \code{list} of \code{character} vectors is expected. |
62 | 66 |
#' Each element must be named according to the names of \code{dataType()} and |
63 | 67 |
#' contain a \code{character} vector for creating a \code{SequenceData} object. |
68 |
+#' |
|
69 |
+#' All additional options must be named and will be passed to the |
|
70 |
+#' \code{\link[=settings]{settings}} function and onto the \code{SequenceData} |
|
71 |
+#' objects, if \code{x} is not a \code{SequenceData} object or a list of |
|
72 |
+#' \code{SequenceData} objects. |
|
64 | 73 |
#' |
65 | 74 |
#' @param className The name of the class which should be constructed. |
66 | 75 |
#' @param x the input which can be of the following types |
... | ... |
@@ -89,10 +98,12 @@ NULL |
89 | 98 |
#' \item{\code{find.mod}:} {\code{TRUE} or \code{FALSE}: should the search for |
90 | 99 |
#' for modifications be triggered upon construction? If not the search can be |
91 | 100 |
#' started by calling the \code{modify()} function.} |
101 |
+#' \item{additional parameters depending on the specific \code{Modifier} class} |
|
92 | 102 |
#' } |
93 |
-#' All other arguments will be passed onto the \code{SequenceData} objects, if |
|
94 |
-#' \code{x} is not a \code{SequenceData} object or a list of \code{SequenceData} |
|
95 |
-#' objects. |
|
103 |
+#' All additional options must be named and will be passed to the |
|
104 |
+#' \code{\link[=settings]{settings}} function and onto the \code{SequenceData} |
|
105 |
+#' objects, if \code{x} is not a \code{SequenceData} object or a list of |
|
106 |
+#' \code{SequenceData} objects. |
|
96 | 107 |
#' |
97 | 108 |
#' @slot mod a \code{character} value, which needs to contain one or more |
98 | 109 |
#' elements from the alphabet of a |
... | ... |
@@ -125,10 +136,13 @@ NULL |
125 | 136 |
#' @description |
126 | 137 |
#' For the \code{Modifier} and \code{ModifierSet} classes a number of functions |
127 | 138 |
#' are implemented to access the data stored by the object. |
139 |
+#' |
|
140 |
+#' The \code{validAggregate} and \code{validModification} functions check if |
|
141 |
+#' \code{\link[=settings]{settings}} have been modified, after the data was |
|
142 |
+#' loaded. This potentially invalidates them. To update the data, run the |
|
143 |
+#' \code{aggregate} or the \code{modify} function. |
|
128 | 144 |
#' |
129 | 145 |
#' @param x,object a \code{Modifier} or \code{ModifierSet} class |
130 |
-#' @param name For \code{settings}: name of the setting to be returned or set |
|
131 |
-#' @param value For \code{settings}: value of the setting to be set |
|
132 | 146 |
#' @param modified For \code{sequences}: \code{TRUE} or \code{FALSE}: Should |
133 | 147 |
#' the sequences be returned as a \code{ModRNAString} with the found |
134 | 148 |
#' modifications added on top of the \code{RNAString}? See |
... | ... |
@@ -142,7 +156,6 @@ NULL |
142 | 156 |
#' \item{\code{modifierType}:} {a character vector with the appropriate class |
143 | 157 |
#' Name of a \code{\link[=Modifier-class]{Modifier}}.} |
144 | 158 |
#' \item{\code{mainScore}:} {a character vector.} |
145 |
-#' \item{\code{settings}:} {a \code{Seqinfo} object.} |
|
146 | 159 |
#' \item{\code{sequenceData}:} {a \code{SequenceData} object.} |
147 | 160 |
#' \item{\code{modifications}:} {a \code{GRanges} or \code{GRangesList} object |
148 | 161 |
#' describing the found modifications.} |
... | ... |
@@ -151,7 +164,13 @@ NULL |
151 | 164 |
#' \item{\code{ranges}:} {a \code{GRangesList} object with each element per |
152 | 165 |
#' transcript.} |
153 | 166 |
#' \item{\code{bamfiles}:} {a \code{BamFileList} object.} |
167 |
+#' \item{\code{validAggregate}:} {\code{TRUE} or \code{FALSE}. Checks if current |
|
168 |
+#' settings are the same for which the data was aggregate} |
|
169 |
+#' \item{\code{validModification}:} {\code{TRUE} or \code{FALSE}. Checks if |
|
170 |
+#' current settings are the same for which modification were found} |
|
154 | 171 |
#' } |
172 |
+#' |
|
173 |
+#' @seealso \code{\link[=settings]{settings}} |
|
155 | 174 |
#' |
156 | 175 |
#' @examples |
157 | 176 |
#' data(msi,package="RNAmodR") |
... | ... |
@@ -159,7 +178,6 @@ NULL |
159 | 178 |
#' modifierType(mi) # The class name of the Modifier object |
160 | 179 |
#' modifierType(msi) # |
161 | 180 |
#' mainScore(mi) |
162 |
-#' settings(mi) |
|
163 | 181 |
#' sequenceData(mi) |
164 | 182 |
#' modifications(mi) |
165 | 183 |
#' # general accessors |
... | ... |
@@ -196,18 +214,18 @@ setClass("Modifier", |
196 | 214 |
|
197 | 215 |
# validity --------------------------------------------------------------------- |
198 | 216 |
|
199 |
-.check_SequenceData_elements <- function(x, list){ |
|
200 |
- if(is(list,"SequenceData")){ |
|
201 |
- list <- list(list) |
|
202 |
- } else if(is(list,"list")){ |
|
203 |
- elementTypeMatch <- !vapply(list,is,logical(1),"SequenceData") |
|
217 |
+.check_SequenceData_elements <- function(x, data){ |
|
218 |
+ if(is(data,"SequenceData")){ |
|
219 |
+ data <- list(data) |
|
220 |
+ } else if(is(data,"list")){ |
|
221 |
+ elementTypeMatch <- !vapply(data,is,logical(1),"SequenceData") |
|
204 | 222 |
if(any(elementTypeMatch)){ |
205 | 223 |
stop("Not all elements are 'SequenceData' objects.", call. = FALSE) |
206 | 224 |
} |
207 |
- } else if(!is(list,"SequenceDataSet")){ |
|
208 |
- stop("Something went wrong.") |
|
225 |
+ } else if(!is(data,"SequenceDataSet")){ |
|
226 |
+ stop("") |
|
209 | 227 |
} |
210 |
- elementTypes <- vapply(list,class,character(1)) |
|
228 |
+ elementTypes <- vapply(data,class,character(1)) |
|
211 | 229 |
if(length(elementTypes) != length(dataType(x))){ |
212 | 230 |
stop("Number of 'SequenceData' elements does not match the requirements of", |
213 | 231 |
" ",class(x),". '",paste(dataType(x), collapse = "','"),"' are ", |
... | ... |
@@ -222,8 +240,8 @@ setClass("Modifier", |
222 | 240 |
NULL |
223 | 241 |
} |
224 | 242 |
|
225 |
-.check_SequenceDataList_data_elements <- function(x, list){ |
|
226 |
- ans <- lapply(list, .check_SequenceData_elements, x) |
|
243 |
+.check_SequenceDataList_data_elements <- function(x, data){ |
|
244 |
+ ans <- lapply(data, .check_SequenceData_elements, x) |
|
227 | 245 |
if(all(vapply(ans,is.null))) { |
228 | 246 |
return(NULL) |
229 | 247 |
} |
... | ... |
@@ -296,9 +314,9 @@ S4Vectors::setValidity2(Class = "Modifier", .valid_Modifier) |
296 | 314 |
settings[,f,drop = FALSE] |
297 | 315 |
}) |
298 | 316 |
if(is.null(rownames(settings[[1]]))){ |
299 |
- names <- rep(" ",nrow(settings[[1]])) |
|
317 |
+ setting_names <- rep(" ",nrow(settings[[1]])) |
|
300 | 318 |
} else { |
301 |
- names <- rownames(settings[[1]]) |
|
319 |
+ setting_names <- rownames(settings[[1]]) |
|
302 | 320 |
} |
303 | 321 |
for(i in seq_along(settings)){ |
304 | 322 |
out <- |
... | ... |
@@ -312,7 +330,7 @@ S4Vectors::setValidity2(Class = "Modifier", .valid_Modifier) |
312 | 330 |
}), use.names = FALSE), nrow = 1, |
313 | 331 |
dimnames = list("", colnames(out))) |
314 | 332 |
out <- rbind(classinfo, out) |
315 |
- rownames(out) <- c(" ",names) |
|
333 |
+ rownames(out) <- c(" ",setting_names) |
|
316 | 334 |
print(out, quote = FALSE, right = TRUE) |
317 | 335 |
} |
318 | 336 |
} |
... | ... |
@@ -347,9 +365,7 @@ setMethod( |
347 | 365 |
.show_settings(settings) |
348 | 366 |
valid <- c(validAggregate(object), validModification(object)) |
349 | 367 |
if(!all(valid)){ |
350 |
- warning("Settings were changed after data aggregation or modification ", |
|
351 |
- "search. Rerun with modify(x,force = TRUE) to update with ", |
|
352 |
- "current settings.", call. = FALSE) |
|
368 |
+ warning(invalidMessage, call. = FALSE) |
|
353 | 369 |
} |
354 | 370 |
} |
355 | 371 |
) |
... | ... |
@@ -404,6 +420,10 @@ setMethod(f = "modifications", |
404 | 420 |
if(!assertive::is_a_bool(perTranscript)){ |
405 | 421 |
stop("'perTranscript' has to be a single logical value.") |
406 | 422 |
} |
423 |
+ valid <- c(validAggregate(x), validModification(x)) |
|
424 |
+ if(!all(valid)){ |
|
425 |
+ warning(invalidMessage, call. = FALSE) |
|
426 |
+ } |
|
407 | 427 |
if(perTranscript){ |
408 | 428 |
return(.get_modifications_per_transcript(x)) |
409 | 429 |
} |
... | ... |
@@ -457,7 +477,7 @@ setMethod(f = "sequences", |
457 | 477 |
stop("'modified' has to be a single logical value.", |
458 | 478 |
call. = FALSE) |
459 | 479 |
} |
460 |
- if(modified == FALSE){ |
|
480 |
+ if(!modified){ |
|
461 | 481 |
return(sequences(sequenceData(x))) |
462 | 482 |
} |
463 | 483 |
mod <- .get_modifications_per_transcript(x) |
... | ... |
@@ -511,6 +531,59 @@ setMethod(f = "seqinfo", |
511 | 531 |
|
512 | 532 |
#' @rdname Modifier-functions |
513 | 533 |
#' @export |
534 |
+setMethod(f = "validAggregate", |
|
535 |
+ signature = signature(x = "Modifier"), |
|
536 |
+ definition = function(x) x@aggregateValidForCurrentArguments |
|
537 |
+) |
|
538 |
+#' @rdname Modifier-functions |
|
539 |
+#' @export |
|
540 |
+setMethod(f = "validModification", |
|
541 |
+ signature = signature(x = "Modifier"), |
|
542 |
+ definition = function(x) x@modificationsValidForCurrentArguments |
|
543 |
+) |
|
544 |
+ |
|
545 |
+# settings --------------------------------------------------------------------- |
|
546 |
+ |
|
547 |
+#' @name settings |
|
548 |
+#' |
|
549 |
+#' @title Settings for \code{Modifier} objects |
|
550 |
+#' |
|
551 |
+#' @description |
|
552 |
+#' Depending on data prepation, quality and desired stringency of a modification |
|
553 |
+#' strategy, settings for cut off parameters or other variables may need to be |
|
554 |
+#' adjusted. This should be rarely the case, but a function for changing these |
|
555 |
+#' settings, is implemented as the... \code{settings} function. |
|
556 |
+#' |
|
557 |
+#' For changing values the input can be either a \code{list} or something |
|
558 |
+#' coercible to a \code{list}. Upon changing a setting, the validity of the |
|
559 |
+#' value in terms of type(!) and dimensions will be checked. |
|
560 |
+#' |
|
561 |
+#' If settings have been modified after the data was loaded, the data is |
|
562 |
+#' potentially invalid. To update the data, run the \code{aggregate} or the |
|
563 |
+#' \code{modify} function. |
|
564 |
+#' |
|
565 |
+#' @param x a \code{Modifier} or \code{ModifierSet} class |
|
566 |
+#' @param name name of the setting to be returned or set |
|
567 |
+#' @param value value of the setting to be set |
|
568 |
+#' |
|
569 |
+#' @return |
|
570 |
+#' If \code{name} is omitted, \code{settings} returns a list of all settings. |
|
571 |
+#' If \code{name} is set, \code{settings} returns a single settings or |
|
572 |
+#' \code{NULL}, if a value for \code{name} is not available. |
|
573 |
+#' |
|
574 |
+#' @examples |
|
575 |
+#' data(msi,package="RNAmodR") |
|
576 |
+#' mi <- msi[[1]] |
|
577 |
+#' # returns a list of all settings |
|
578 |
+#' settings(mi) |
|
579 |
+#' # accesses a specific setting |
|
580 |
+#' settings(mi,"minCoverage") |
|
581 |
+#' # modification of setting |
|
582 |
+#' settings(mi) <- list(minCoverage = 11L) |
|
583 |
+NULL |
|
584 |
+ |
|
585 |
+#' @rdname settings |
|
586 |
+#' @export |
|
514 | 587 |
setMethod(f = "settings", |
515 | 588 |
signature = signature(x = "Modifier"), |
516 | 589 |
definition = function(x, name){ |
... | ... |
@@ -523,36 +596,24 @@ setMethod(f = "settings", |
523 | 596 |
x@arguments[[name]] |
524 | 597 |
} |
525 | 598 |
) |
526 |
-#' @rdname Modifier-functions |
|
527 |
-#' @export |
|
528 |
-setReplaceMethod(f = "settings", |
|
529 |
- signature = signature(x = "Modifier"), |
|
530 |
- definition = function(x, value){ |
|
531 |
- if(is.null(names(value)) && length(value) > 0L){ |
|
532 |
- stop("'value' has to be a named.") |
|
533 |
- } |
|
534 |
- if(!is.list(value)){ |
|
535 |
- value <- as.list(value) |
|
536 |
- } |
|
537 |
- value <- .norm_args(value) |
|
538 |
- x@arguments[names(value)] <- unname(value) |
|
539 |
- x@aggregateValidForCurrentArguments <- FALSE |
|
540 |
- x@modificationsValidForCurrentArguments <- FALSE |
|
541 |
- x |
|
542 |
- }) |
|
543 | 599 |
|
544 |
-#' @rdname Modifier-functions |
|
545 |
-#' @export |
|
546 |
-setMethod(f = "validAggregate", |
|
547 |
- signature = signature(x = "Modifier"), |
|
548 |
- definition = function(x) x@aggregateValidForCurrentArguments |
|
549 |
-) |
|
550 |
-#' @rdname Modifier-functions |
|
600 |
+#' @rdname settings |
|
551 | 601 |
#' @export |
552 |
-setMethod(f = "validModification", |
|
553 |
- signature = signature(x = "Modifier"), |
|
554 |
- definition = function(x) x@modificationsValidForCurrentArguments |
|
555 |
-) |
|
602 |
+setReplaceMethod(f = "settings", |
|
603 |
+ signature = signature(x = "Modifier"), |
|
604 |
+ definition = function(x, value){ |
|
605 |
+ if(is.null(names(value)) && length(value) > 0L){ |
|
606 |
+ stop("'value' has to be a named.") |
|
607 |
+ } |
|
608 |
+ if(!is.list(value)){ |
|
609 |
+ value <- as.list(value) |
|
610 |
+ } |
|
611 |
+ value <- .norm_args(value) |
|
612 |
+ x@arguments[names(value)] <- unname(value) |
|
613 |
+ x@aggregateValidForCurrentArguments <- FALSE |
|
614 |
+ x@modificationsValidForCurrentArguments <- FALSE |
|
615 |
+ x |
|
616 |
+ }) |
|
556 | 617 |
|
557 | 618 |
# constructors ----------------------------------------------------------------- |
558 | 619 |
|
... | ... |
@@ -560,7 +621,7 @@ setMethod(f = "validModification", |
560 | 621 |
if(is(ans,"character") && extends(ans,"Modifier")){ |
561 | 622 |
ans <- getClass(ans)@prototype |
562 | 623 |
} else if(!is(ans,"Modifier")) { |
563 |
- stop("Something went wrong.") |
|
624 |
+ stop("") |
|
564 | 625 |
} |
565 | 626 |
.check_Modifier_data_elements(ans, list) |
566 | 627 |
if(length(list) == 1L){ |
... | ... |
@@ -604,7 +665,8 @@ setMethod(f = "validModification", |
604 | 665 |
bamfiles <- bamfiles[match(class,names(bamfiles))] |
605 | 666 |
data <- BiocParallel::bpmapply(.load_SequenceData, classes, bamfiles, |
606 | 667 |
MoreArgs = list(annotation, sequences, |
607 |
- seqinfo, args)) |
|
668 |
+ seqinfo, args), |
|
669 |
+ SIMPLIFY = FALSE) |
|
608 | 670 |
} else { |
609 | 671 |
data <- BiocParallel::bplapply(classes, .load_SequenceData, bamfiles, |
610 | 672 |
annotation, sequences, seqinfo, args) |
... | ... |
@@ -621,7 +683,7 @@ setMethod(f = "validModification", |
621 | 683 |
}) |
622 | 684 |
data <- as(data,"SequenceDataSet") |
623 | 685 |
} else { |
624 |
- stop("Something went wrong.") |
|
686 |
+ stop("") |
|
625 | 687 |
} |
626 | 688 |
data |
627 | 689 |
} |
... | ... |
@@ -678,7 +740,7 @@ setMethod(f = "validModification", |
678 | 740 |
#' @export |
679 | 741 |
setGeneric( |
680 | 742 |
name = "Modifier", |
681 |
- signature = c("x"), |
|
743 |
+ signature = "x", |
|
682 | 744 |
def = function(className, x, annotation, sequences, seqinfo, ...) |
683 | 745 |
standardGeneric("Modifier") |
684 | 746 |
) |
... | ... |
@@ -842,9 +904,6 @@ setMethod(f = "aggregate", |
842 | 904 |
signature = signature(x = "Modifier"), |
843 | 905 |
definition = |
844 | 906 |
function(x, force = FALSE){ |
845 |
- if(missing(force)){ |
|
846 |
- force <- FALSE |
|
847 |
- } |
|
848 | 907 |
assertive::assert_is_a_bool(force) |
849 | 908 |
if(!hasAggregateData(x) || force){ |
850 | 909 |
x@aggregate <- .check_aggregate_modifier(aggregateData(x), x) |
... | ... |
@@ -935,9 +994,6 @@ setMethod(f = "modify", |
935 | 994 |
signature = signature(x = "Modifier"), |
936 | 995 |
definition = |
937 | 996 |
function(x, force = FALSE){ |
938 |
- if(missing(force)){ |
|
939 |
- force <- FALSE |
|
940 |
- } |
|
941 | 997 |
assertive::assert_is_a_bool(force) |
942 | 998 |
if(!validAggregate(x) | force){ |
943 | 999 |
x <- aggregate(x, force = TRUE) |
... | ... |
@@ -62,9 +62,6 @@ NULL |
62 | 62 |
NULL |
63 | 63 |
|
64 | 64 |
.norm_prediction_args <- function(input){ |
65 |
- if(missing(input)){ |
|
66 |
- input <- list() |
|
67 |
- } |
|
68 | 65 |
if(!is.list(input)){ |
69 | 66 |
stop("'prediction.args' must be a list.") |
70 | 67 |
} |
... | ... |
@@ -79,9 +76,6 @@ NULL |
79 | 76 |
|
80 | 77 |
.rocr_exclusive_functions <- c("rch","auc","prbe","mxe","rmse","ecost") |
81 | 78 |
.norm_performance_args <- function(input, x){ |
82 |
- if(missing(input)){ |
|
83 |
- input <- list() |
|
84 |
- } |
|
85 | 79 |
if(!is.list(input)){ |
86 | 80 |
stop("'performance.args' must be a list.") |
87 | 81 |
} |
... | ... |
@@ -102,11 +96,8 @@ NULL |
102 | 96 |
} |
103 | 97 |
} |
104 | 98 |
if(!is.null(input[["x.measure"]])){ |
105 |
- if(length(input[["x.measure"]]) == 0L){ |
|
106 |
- x.measure <- "cutoff" |
|
107 |
- } else if(is.na(input[["x.measure"]])){ |
|
108 |
- x.measure <- "cutoff" |
|
109 |
- } else if(input[["x.measure"]] == ""){ |
|
99 |
+ if(length(input[["x.measure"]]) == 0L || is.na(input[["x.measure"]]) || |
|
100 |
+ input[["x.measure"]] == ""){ |
|
110 | 101 |
x.measure <- "cutoff" |
111 | 102 |
} else { |
112 | 103 |
x.measure <- input[["x.measure"]] |
... | ... |
@@ -136,9 +127,6 @@ NULL |
136 | 127 |
} |
137 | 128 |
|
138 | 129 |
.norm_plot_args <- function(input){ |
139 |
- if(missing(input)){ |
|
140 |
- input <- list() |
|
141 |
- } |
|
142 | 130 |
if(!is.list(input)){ |
143 | 131 |
stop("'plot.args' must be a list.") |
144 | 132 |
} |
... | ... |
@@ -232,9 +220,9 @@ NULL |
232 | 220 |
colnames <- colnames[colnames != "labels"] |
233 | 221 |
data <- lapply(seq_along(colnames), |
234 | 222 |
function(i){ |
235 |
- c <- colnames[i] |
|
236 |
- c <- c("labels",c) |
|
237 |
- d <- data[,c] |
|
223 |
+ cn <- colnames[i] |
|
224 |
+ cn <- c("labels",cn) |
|
225 |
+ d <- data[,cn] |
|
238 | 226 |
colnames(d) <- c("labels","predictions") |
239 | 227 |
d <- unlist(d) |
240 | 228 |
rownames(d) <- NULL |
... | ... |
@@ -246,8 +234,8 @@ NULL |
246 | 234 |
|
247 | 235 |
.get_prediction_data_ModifierSet <- function(x, coord, score){ |
248 | 236 |
data <- lapply(x, .get_prediction_data_Modifier, coord, score) |
249 |
- names <- names(data[[1]]) |
|
250 |
- data <- lapply(names, |
|
237 |
+ data_names <- names(data[[1]]) |
|
238 |
+ data <- lapply(data_names, |
|
251 | 239 |
function(name){ |
252 | 240 |
lapply(data,"[[",name) |
253 | 241 |
}) |
... | ... |
@@ -260,7 +248,7 @@ NULL |
260 | 248 |
list(predictions = predictions, |
261 | 249 |
labels = labels) |
262 | 250 |
}) |
263 |
- names(data) <- names |
|
251 |
+ names(data) <- data_names |
|
264 | 252 |
data |
265 | 253 |
} |
266 | 254 |
|
... | ... |
@@ -289,7 +277,7 @@ NULL |
289 | 277 |
plot.args[["add"]] <- FALSE |
290 | 278 |
} |
291 | 279 |
# |
292 |
- mapply( |
|
280 |
+ Map( |
|
293 | 281 |
function(d, name, colour, prediction.args, performance.args, plot.args){ |
294 | 282 |
pred <- do.call(ROCR::prediction, c(list(predictions = d$predictions, |
295 | 283 |
labels = d$labels), |
... | ... |
@@ -301,10 +289,10 @@ NULL |
301 | 289 |
stop("Error during plotting of performance object: ",tmp) |
302 | 290 |
} |
303 | 291 |
graphics::title(main = name) |
304 |
- if(plot.args[["abline"]] == TRUE){ |
|
292 |
+ if(plot.args[["abline"]]){ |
|
305 | 293 |
graphics::abline(a = 0, b = 1) |
306 | 294 |
} |
307 |
- if(plot.args[["AUC"]] == TRUE){ |
|
295 |
+ if(plot.args[["AUC"]]){ |
|
308 | 296 |
auc <- unlist(slot(performance(pred,"auc"),"y.values")) |
309 | 297 |
auc <- paste(c("AUC = "), round(auc,2L), sep = "") |
310 | 298 |
graphics::legend(0.55, 0.25, auc, bty = "n", cex = 1) |
... | ... |
@@ -314,8 +302,7 @@ NULL |
314 | 302 |
names(data), |
315 | 303 |
MoreArgs = list(prediction.args = prediction.args, |
316 | 304 |
performance.args = performance.args, |
317 |
- plot.args = plot.args), |
|
318 |
- SIMPLIFY = FALSE) |
|
305 |
+ plot.args = plot.args)) |
|
319 | 306 |
for(i in seq_len(n_remaining)){ |
320 | 307 |
graphics::plot.new() |
321 | 308 |
} |
... | ... |
@@ -328,11 +315,8 @@ NULL |
328 | 315 |
setMethod( |
329 | 316 |
f = "plotROC", |
330 | 317 |
signature = signature(x = "Modifier"), |
331 |
- definition = function(x, coord, score = NULL, prediction.args, |
|
332 |
- performance.args, plot.args){ |
|
333 |
- if(missing(score)){ |
|
334 |
- score <- NULL |
|
335 |
- } |
|
318 |
+ definition = function(x, coord, score = NULL, prediction.args = list(), |
|
319 |
+ performance.args = list(), plot.args = list()){ |
|
336 | 320 |
coord <- .norm_coord(coord, modType(x)) |
337 | 321 |
data <- .get_prediction_data_Modifier(x, coord, score) |
338 | 322 |
.plot_ROCR(data, |
... | ... |
@@ -348,11 +332,8 @@ setMethod( |
348 | 332 |
setMethod( |
349 | 333 |
f = "plotROC", |
350 | 334 |
signature = signature(x = "ModifierSet"), |
351 |
- definition = function(x, coord, score = NULL, prediction.args, |
|
352 |
- performance.args, plot.args){ |
|
353 |
- if(missing(score)){ |
|
354 |
- score <- NULL |
|
355 |
- } |
|
335 |
+ definition = function(x, coord, score = NULL, prediction.args = list(), |
|
336 |
+ performance.args = list(), plot.args = list()){ |
|
356 | 337 |
coord <- .norm_coord(coord, modType(x)) |
357 | 338 |
data <- .get_prediction_data_ModifierSet(x, coord, score) |
358 | 339 |
.plot_ROCR(data, |
... | ... |
@@ -98,10 +98,10 @@ NULL |
98 | 98 |
lapply(x, |
99 | 99 |
function(z){ |
100 | 100 |
data <- getAggregateData(z) |
101 |
- names <- .get_element_names(data, coord, args[["name"]], |
|
101 |
+ element_names <- .get_element_names(data, coord, args[["name"]], |
|
102 | 102 |
args[["type"]]) |
103 |
- data <- data[match(names, names(data))] |
|
104 |
- coord <- coord[match(names, names(coord))] |
|
103 |
+ data <- data[match(element_names, names(data))] |
|
104 |
+ coord <- coord[match(element_names, names(coord))] |
|
105 | 105 |
.perform_subset(data, coord, args[["flanking"]], |
106 | 106 |
args[["perTranscript"]]) |
107 | 107 |
}) |
... | ... |
@@ -67,12 +67,12 @@ setMethod(f = "constructModRanges", |
67 | 67 |
if(any(length(positions) != data_length)){ |
68 | 68 |
stop("Number of positions and scores do not match.") |
69 | 69 |
} |
70 |
- seqnames <- .get_unique_seqnames(range) |
|
70 |
+ seqnames_unique <- .get_unique_seqnames(range) |
|
71 | 71 |
ranges <- IRanges::IRanges(start = positions, |
72 | 72 |
width = 1L) |
73 | 73 |
strand <- .get_unique_strand(range) |
74 | 74 |
mranges <- |
75 |
- GenomicRanges::GRanges(seqnames = seqnames, |
|
75 |
+ GenomicRanges::GRanges(seqnames = seqnames_unique, |
|
76 | 76 |
ranges = ranges, |
77 | 77 |
strand = strand, |
78 | 78 |
seqinfo = GenomeInfoDb::seqinfo(range), |
... | ... |
@@ -2,15 +2,15 @@ |
2 | 2 |
#' @include Modifier-class.R |
3 | 3 |
NULL |
4 | 4 |
|
5 |
-#' @name visualizeData |
|
6 |
-#' @aliases visualizeData visualizeDataByCoord getDataTrack |
|
5 |
+#' @name plotData |
|
6 |
+#' @aliases plotData plotDataByCoord getDataTrack |
|
7 | 7 |
#' |
8 | 8 |
#' @title Visualizing data data from a \code{SequenceData}, |
9 | 9 |
#' \code{SequenceDataSet}, \code{SequenceDataList}, \code{Modifier} or |
10 | 10 |
#' \code{ModifierSet} object. |
11 | 11 |
#' |
12 | 12 |
#' @description |
13 |
-#' With the \code{visualizeData} and \code{visualizeDataByCoord} functions data |
|
13 |
+#' With the \code{plotData} and \code{plotDataByCoord} functions data |
|
14 | 14 |
#' from a \code{SequenceData}, \code{SequenceDataSet}, \code{SequenceDataList}, |
15 | 15 |
#' \code{Modifier} or \code{ModifierSet} object can be visualized. |
16 | 16 |
#' |
... | ... |
@@ -27,9 +27,9 @@ NULL |
27 | 27 |
#' @param coord coordinates of a positions to subset to as a |
28 | 28 |
#' \code{GRanges} object. The 'Parent' column is expected to match the |
29 | 29 |
#' transcript name. |
30 |
-#' @param name Only for \code{visualizeData}: the transcript name |
|
31 |
-#' @param from Only for \code{visualizeData}: start position |
|
32 |
-#' @param to Only for \code{visualizeData}: end position |
|
30 |
+#' @param name Only for \code{plotData}: the transcript name |
|
31 |
+#' @param from Only for \code{plotData}: start position |
|
32 |
+#' @param to Only for \code{plotData}: end position |
|
33 | 33 |
#' @param type the data type of data show as data tracks. |
34 | 34 |
#' @param showSequenceData \code{TRUE} or \code{FALSE}: should the sequence data |
35 | 35 |
#' be shown? (default: \code{seqdata = FALSE}) |
... | ... |
@@ -60,14 +60,14 @@ NULL |
60 | 60 |
#' |
61 | 61 |
#' @examples |
62 | 62 |
#' data(msi,package="RNAmodR") |
63 |
-#' visualizeData(msi[[1]], "2", from = 10L, to = 45L) |
|
63 |
+#' plotData(msi[[1]], "2", from = 10L, to = 45L) |
|
64 | 64 |
#' \dontrun{ |
65 |
-#' visualizeData(msi, "2", from = 10L, to = 45L) |
|
65 |
+#' plotData(msi, "2", from = 10L, to = 45L) |
|
66 | 66 |
#' } |
67 | 67 |
NULL |
68 | 68 |
|
69 | 69 |
.norm_show_argument <- function(show_arg, default = FALSE){ |
70 |
- if(missing(show_arg) || !assertive::is_a_bool(show_arg)){ |
|
70 |
+ if(!assertive::is_a_bool(show_arg)){ |
|
71 | 71 |
show_arg <- default |
72 | 72 |
} |
73 | 73 |
show_arg |
... | ... |
@@ -143,23 +143,23 @@ NULL |
143 | 143 |
|
144 | 144 |
# ------------------------------------------------------------------------------ |
145 | 145 |
|
146 |
-#' @rdname visualizeData |
|
146 |
+#' @rdname plotData |
|
147 | 147 |
setMethod( |
148 |
- f = "visualizeDataByCoord", |
|
148 |
+ f = "plotDataByCoord", |
|
149 | 149 |
signature = signature(x = "Modifier", coord = "GRanges"), |
150 | 150 |
definition = function(x, coord, type = NA, window.size = 15L, ...) { |
151 | 151 |
# input check |
152 | 152 |
coord <- .norm_coord_for_visualization(ranges(x), coord) |
153 | 153 |
from_to <- .get_viz_from_to_coord(ranges(x), coord, window.size) |
154 |
- visualizeData(x, name = coord$Parent, from = from_to$from, |
|
154 |
+ plotData(x, name = coord$Parent, from = from_to$from, |
|
155 | 155 |
to = from_to$to, type = type, ...) |
156 | 156 |
} |
157 | 157 |
) |
158 | 158 |
|
159 |
-#' @rdname visualizeData |
|
159 |
+#' @rdname plotData |
|
160 | 160 |
#' @export |
161 | 161 |
setMethod( |
162 |
- f = "visualizeData", |
|
162 |
+ f = "plotData", |
|
163 | 163 |
signature = signature(x = "Modifier"), |
164 | 164 |
definition = function(x, name, from, to, type = NA, showSequenceData = FALSE, |
165 | 165 |
showSequence = TRUE, showAnnotation = FALSE, ...) { |
... | ... |
@@ -203,7 +203,7 @@ setMethod( |
203 | 203 |
} |
204 | 204 |
) |
205 | 205 |
|
206 |
-#' @rdname visualizeData |
|
206 |
+#' @rdname plotData |
|
207 | 207 |
#' @export |
208 | 208 |
setMethod( |
209 | 209 |
f = "getDataTrack", |
... | ... |
@@ -174,9 +174,9 @@ setMethod(f = "relistToClass", |
174 | 174 |
return(FALSE) |
175 | 175 |
} |
176 | 176 |
namedRequired <- x[classNames %in% c("character","list")] |
177 |
- names <- unique(names(unlist(namedRequired))) |
|
178 |
- if(is.null(names) || |
|
179 |
- !all(tolower(names) %in% c("treated","control"))){ |
|
177 |
+ namedRequired_names <- unique(names(unlist(namedRequired))) |
|
178 |
+ if(is.null(namedRequired_names) || |
|
179 |
+ !all(tolower(namedRequired_names) %in% c("treated","control"))){ |
|
180 | 180 |
return(FALSE) |
181 | 181 |
} |
182 | 182 |
x <- lapply(x,.norm_bamfiles) |
... | ... |
@@ -193,27 +193,24 @@ setMethod(f = "relistToClass", |
193 | 193 |
|
194 | 194 |
#' @importFrom BiocParallel SerialParam register bpmapply bplapply |
195 | 195 |
.bamfiles_to_ModifierSet <- function(className, x, annotation, sequences, |
196 |
- seqinfo, ...){ |
|
196 |
+ seqinfo = NULL, ...){ |
|
197 | 197 |
# check and normalize input |
198 | 198 |
args <- .norm_ModifierSet_args(list(...)) |
199 | 199 |
className <- .norm_modifiertype(className) |
200 | 200 |
if(!is.list(x)){ |
201 | 201 |
x <- list(x) |
202 | 202 |
} |
203 |
- names <- as.list(names(x)) |
|
204 |
- if(length(names) == 0L){ |
|
205 |
- names <- vector(mode = "list", length = length(x)) |
|
203 |
+ x_names <- as.list(names(x)) |
|
204 |
+ if(length(x_names) == 0L){ |
|
205 |
+ x_names <- vector(mode = "list", length = length(x)) |
|
206 | 206 |
} |
207 | 207 |
x <- lapply(x, .norm_bamfiles, className) |
208 | 208 |
annotation <- .norm_annotation(annotation, className) |
209 | 209 |
annotation <- .load_annotation(annotation) |
210 | 210 |
sequences <- .norm_sequences(sequences, className) |
211 |
- if(missing(seqinfo)){ |
|
212 |
- seqinfo <- NA |
|
213 |
- } |
|
214 | 211 |
ni <- seq_along(x) |
215 | 212 |
# choose were to use parallelization |
216 |
- if(args[["internalBP"]] == TRUE){ |
|
213 |
+ if(args[["internalBP"]]){ |
|
217 | 214 |
BiocParallel::register(BiocParallel::SerialParam()) |
218 | 215 |
} |
219 | 216 |
# do analysis by calling the Modifier classes |
... | ... |
@@ -228,7 +225,7 @@ setMethod(f = "relistToClass", |
228 | 225 |
message(i,". ",className," analysis:") |
229 | 226 |
} |
230 | 227 |
# choose were to use parallelization |
231 |
- if(args[["internalBP"]] == FALSE){ |
|
228 |
+ if(!args[["internalBP"]]){ |
|
232 | 229 |
BiocParallel::register(BiocParallel::SerialParam()) |
233 | 230 |
} |
234 | 231 |
# do not pass this argument along to objects |
... | ... |
@@ -243,7 +240,7 @@ setMethod(f = "relistToClass", |
243 | 240 |
PACKAGE <- getClass(className)@package |
244 | 241 |
CLASSFUN <- get(className) |
245 | 242 |
x <- BiocParallel::bpmapply(FUN, |
246 |
- ni, x, names, |
|
243 |
+ ni, x, x_names, |
|
247 | 244 |
MoreArgs = list(args = args, |
248 | 245 |
className = className, |
249 | 246 |
PACKAGE = PACKAGE, |
... | ... |
@@ -253,9 +250,9 @@ setMethod(f = "relistToClass", |
253 | 250 |
seqinfo = seqinfo, |
254 | 251 |
...), |
255 | 252 |
SIMPLIFY = FALSE) |
256 |
- f <- vapply(names,is.null,logical(1)) |
|
257 |
- names[f] <- as.list(as.character(seq_along(x))[f]) |
|
258 |
- names(x) <- unlist(names) |
|
253 |
+ f <- vapply(x_names,is.null,logical(1)) |
|
254 |
+ x_names[f] <- as.list(as.character(seq_along(x))[f]) |
|
255 |
+ names(x) <- unlist(x_names) |
|
259 | 256 |
# pass results to ModifierSet object |
260 | 257 |
.ModifierSet(className, x) |
261 | 258 |
} |
... | ... |
@@ -267,7 +264,7 @@ setMethod(f = "relistToClass", |
267 | 264 |
elementType <- modifierType(x[[1]]) |
268 | 265 |
className <- .get_classname_for_ModifierSet_from_modifier_type(className) |
269 | 266 |
if(className != .norm_classname_ModifierSet(elementType)){ |
270 |
- stop("Something went wrong.") |
|
267 |
+ stop("") |
|
271 | 268 |
} |
272 | 269 |
if (!all(vapply(x, |
273 | 270 |
function(xi) extends(class(xi), elementType), |
... | ... |
@@ -282,7 +279,7 @@ setMethod(f = "relistToClass", |
282 | 279 |
#' @export |
283 | 280 |
setGeneric( |
284 | 281 |
name = "ModifierSet", |
285 |
- signature = c("x"), |
|
282 |
+ signature = "x", |
|
286 | 283 |
def = function(className, x, annotation, sequences, seqinfo, ...) |
287 | 284 |
standardGeneric("ModifierSet") |
288 | 285 |
) |
... | ... |
@@ -358,7 +355,7 @@ setMethod( |
358 | 355 |
optional = TRUE))) |
359 | 356 |
colnames(out) <- rep(" ",ncol(mf)) |
360 | 357 |
if(is.null(names(object))){ |
361 |
- rownames(out) <- c("| Modifications found:") |
|
358 |
+ rownames(out) <- "| Modifications found:" |
|
362 | 359 |
} else { |
363 | 360 |
rownames(out) <- c(" ", |
364 | 361 |
"| Modifications found:") |
... | ... |
@@ -469,26 +466,6 @@ setMethod(f = "seqinfo", |
469 | 466 |
) |
470 | 467 |
#' @rdname Modifier-functions |
471 | 468 |
#' @export |
472 |
-setMethod(f = "settings", |
|
473 |
- signature = signature(x = "ModifierSet"), |
|
474 |
- definition = function(x, name){ |
|
475 |
- ans <- lapply(x,settings,name) |
|
476 |
- names(ans) <- names(x) |
|
477 |
- ans |
|
478 |
- } |
|
479 |
-) |
|
480 |
-#' @rdname Modifier-functions |
|
481 |
-#' @export |
|
482 |
-setReplaceMethod(f = "settings", |
|
483 |
- signature = signature(x = "ModifierSet"), |
|
484 |
- definition = function(x, value){ |
|
485 |
- for(i in seq_along(x)){ |
|
486 |
- settings(x[[i]]) <- value |
|
487 |
- } |
|
488 |
- x |
|
489 |
- }) |
|
490 |
-#' @rdname Modifier-functions |
|
491 |
-#' @export |
|
492 | 469 |
setMethod(f = "sequences", |
493 | 470 |
signature = signature(x = "ModifierSet"), |
494 | 471 |
definition = |
... | ... |
@@ -497,7 +474,7 @@ setMethod(f = "sequences", |
497 | 474 |
stop("'modified' has to be a single logical value.", |
498 | 475 |
call. = FALSE) |
499 | 476 |
} |
500 |
- if(modified == FALSE){ |
|
477 |
+ if(!modified){ |
|
501 | 478 |
return(sequences(sequenceData(x[[1]]))) |
502 | 479 |
} |
503 | 480 |
mod <- .get_modifications_per_transcript(x) |
... | ... |
@@ -512,6 +489,29 @@ setMethod(f = "sequences", |
512 | 489 |
} |
513 | 490 |
) |
514 | 491 |
|
492 |
+# settings --------------------------------------------------------------------- |
|
493 |
+ |
|
494 |
+#' @rdname settings |
|
495 |
+#' @export |
|
496 |
+setMethod(f = "settings", |
|
497 |
+ signature = signature(x = "ModifierSet"), |
|
498 |
+ definition = function(x, name){ |
|
499 |
+ ans <- lapply(x,settings,name) |
|
500 |
+ names(ans) <- names(x) |
|
501 |
+ ans |
|
502 |
+ } |
|
503 |
+) |
|
504 |
+#' @rdname settings |
|
505 |
+#' @export |
|
506 |
+setReplaceMethod(f = "settings", |
|
507 |
+ signature = signature(x = "ModifierSet"), |
|
508 |
+ definition = function(x, value){ |
|
509 |
+ for(i in seq_along(x)){ |
|
510 |
+ settings(x[[i]]) <- value |
|
511 |
+ } |
|
512 |
+ x |
|
513 |
+ }) |
|
514 |
+ |
|
515 | 515 |
# aggregate/modify ------------------------------------------------------------- |
516 | 516 |
|
517 | 517 |
#' @rdname aggregate |
... | ... |
@@ -84,8 +84,8 @@ NULL |
84 | 84 |
stop("Values in 'tx_id' have to be unique.", |
85 | 85 |
call. = FALSE) |
86 | 86 |
} |
87 |
- names <- names(ranges(x)) |
|
88 |
- if(!all(alias$tx_id %in% names)){ |
|
87 |
+ ranges_names <- names(ranges(x)) |
|
88 |
+ if(!all(alias$tx_id %in% ranges_names)){ |
|
89 | 89 |
stop("All values in 'tx_id' have to be valid transcript ids used as ", |
90 | 90 |
"names for the data.", call. = FALSE) |
91 | 91 |
} |
... | ... |
@@ -161,10 +161,10 @@ NULL |
161 | 161 |
coord <- coord[match(names(data), names(coord))] |
162 | 162 |
# keep rownames/names and unlist data |
163 | 163 |
positions <- rownames(data) |
164 |
- names <- as.character(S4Vectors::Rle(names(data), lengths(data))) |
|
164 |
+ data_names <- as.character(S4Vectors::Rle(names(data), lengths(data))) |
|
165 | 165 |
data <- unlist(data) |
166 | 166 |
# add names and positions column as factors |
167 |
- data$names <- factor(names) |
|
167 |
+ data$names <- factor(data_names) |
|
168 | 168 |
data$positions <- factor(as.integer(unlist(positions))) |
169 | 169 |
rownames(data) <- NULL |
170 | 170 |
# add activity information if present |
... | ... |
@@ -245,7 +245,6 @@ setMethod("compareByCoord", |
245 | 245 |
) |
246 | 246 |
|
247 | 247 |
.normlize_data_against_one_sample <- function(data, normalize){ |
248 |
- |
|
249 | 248 |
if(!missing(normalize)){ |
250 | 249 |
colnames <- colnames(data) |
251 | 250 |
colnames <- colnames[!(colnames %in% c("positions","names","mod","Activity"))] |
... | ... |
@@ -260,7 +259,7 @@ setMethod("compareByCoord", |
260 | 259 |
data[,normalize] |
261 | 260 |
} else if(is.logical(normalize)){ |
262 | 261 |
assertive::assert_is_a_bool(normalize) |
263 |
- if(normalize == TRUE){ |
|
262 |
+ if(normalize){ |
|
264 | 263 |
data[,colnames] <- as.data.frame(data[,colnames,drop = FALSE]) - |
265 | 264 |
apply(data[,colnames],1,max) |
266 | 265 |
} |
... | ... |
@@ -289,10 +288,10 @@ setMethod("compareByCoord", |
289 | 288 |
if(is.factor(positions)){ |
290 | 289 |
positions <- as.numeric(as.character(positions)) |
291 | 290 |
} |
292 |
- list <- list(as.character(positions), |
|
293 |
- mod, |
|
294 |
- activity) |
|
295 |
- spacer <- lapply(list, |
|
291 |
+ tmp <- list(as.character(positions), |
|
292 |
+ mod, |
|
293 |
+ activity) |
|
294 |
+ spacer <- lapply(tmp, |
|
296 | 295 |
function(el){ |
297 | 296 |
if(is.null(el)) return(NULL) |
298 | 297 |
length <- nchar(el) |
... | ... |
@@ -302,15 +301,15 @@ setMethod("compareByCoord", |
302 | 301 |
paste0(rep(" ",n),collapse = "") |
303 | 302 |
})) |
304 | 303 |
}) |
305 |
- sep <- lapply(seq_along(list), |
|
304 |
+ sep <- lapply(seq_along(tmp), |
|
306 | 305 |
function(i){ |
307 | 306 |
if(i > 1L){ |
308 |
- rep(" - ",length(list[[i]])) |
|
307 |
+ rep(" - ",length(tmp[[i]])) |
|
309 | 308 |
} else { |
310 |
- rep("",length(list[[i]])) |
|
309 |
+ rep("",length(tmp[[i]])) |
|
311 | 310 |
} |
312 | 311 |
}) |
313 |
- labels <- mapply(paste0, spacer, list, sep, SIMPLIFY = FALSE) |
|
312 |
+ labels <- Map(paste0, spacer, tmp, sep) |
|
314 | 313 |
labels <- Reduce(paste0, rev(labels)) |
315 | 314 |
f <- factor(labels, levels = unique(labels)) |
316 | 315 |
stats::reorder(f,positions) |
... | ... |
@@ -32,7 +32,7 @@ NULL |
32 | 32 |
} |
33 | 33 |
|
34 | 34 |
.add_viz_colours <- function(dts, colours){ |
35 |
- dts <- mapply( |
|
35 |
+ dts <- Map( |
|
36 | 36 |
function(dt, colour){ |
37 | 37 |
if(is.list(dt)){ |
38 | 38 |
dt <- lapply(dt, |
... | ... |
@@ -48,13 +48,12 @@ NULL |
48 | 48 |
dt |
49 | 49 |
}, |
50 | 50 |
dts, |
51 |
- colours, |
|
52 |
- SIMPLIFY = FALSE) |
|
51 |
+ colours) |
|
53 | 52 |
dts |
54 | 53 |
} |
55 | 54 |
|
56 | 55 |
.add_viz_names <- function(dts, names){ |
57 |
- dts <- mapply( |
|
56 |
+ dts <- Map( |
|
58 | 57 |
function(dt, name){ |
59 | 58 |
if(is.list(dt)){ |
60 | 59 |
dt <- lapply(dt, |
... | ... |
@@ -68,8 +67,7 @@ NULL |
68 | 67 |
dt |
69 | 68 |
}, |
70 | 69 |
dts, |
71 |
- names, |
|
72 |
- SIMPLIFY = FALSE) |
|
70 |
+ names) |
|
73 | 71 |
dts |
74 | 72 |
} |
75 | 73 |
|
... | ... |
@@ -94,7 +92,7 @@ NULL |
94 | 92 |
max |
95 | 93 |
}) |
96 | 94 |
names(max) <- types |
97 |
- dts <- mapply( |
|
95 |
+ dts <- Map( |
|
98 | 96 |
function(dt,t){ |
99 | 97 |
ylim <- c(0,max[[t]]) |
100 | 98 |
if(sum(ylim) != 0L){ |
... | ... |
@@ -107,25 +105,25 @@ NULL |
107 | 105 |
dts |
108 | 106 |
} |
109 | 107 |
|
110 |
-#' @rdname visualizeData |
|
108 |
+#' @rdname plotData |
|
111 | 109 |
#' @export |
112 | 110 |
setMethod( |
113 |
- f = "visualizeDataByCoord", |
|
111 |
+ f = "plotDataByCoord", |
|
114 | 112 |
signature = signature(x = "ModifierSet", coord = "GRanges"), |
115 | 113 |
definition = function(x, coord, type = NA, window.size = 15L, ...) { |
116 | 114 |
# input check |
117 | 115 |
coord <- .norm_coord_for_visualization(ranges(x), coord) |
118 | 116 |
from_to <- .get_viz_from_to_coord(ranges(x), coord, window.size) |
119 |
- visualizeData(x, name = coord$Parent, from = from_to$from, |
|
117 |
+ plotData(x, name = coord$Parent, from = from_to$from, |
|
120 | 118 |
to = from_to$to, type = type, ...) |
121 | 119 |
|
122 | 120 |
} |
123 | 121 |
) |
124 | 122 |
|
125 |
-#' @rdname visualizeData |
|
123 |
+#' @rdname plotData |
|
126 | 124 |
#' @export |
127 | 125 |
setMethod( |
128 |
- f = "visualizeData", |
|
126 |
+ f = "plotData", |
|
129 | 127 |
signature = signature(x = "ModifierSet"), |
130 | 128 |
definition = function(x, name, from, to, type = NA, showSequenceData = FALSE, |
131 | 129 |
showSequence = TRUE, showAnnotation = FALSE, ...) { |
... | ... |
@@ -35,12 +35,12 @@ NULL |
35 | 35 |
} |
36 | 36 |
|
37 | 37 |
.merge_summary_data <- function(bamfilesstats,datastats){ |
38 |
- names <- c(rownames(bamfilesstats),rownames(datastats)) |
|
38 |
+ bf_d_names <- c(rownames(bamfilesstats),rownames(datastats)) |
|
39 | 39 |
stats <- data.frame(mapply(c, |
40 | 40 |
as.list(bamfilesstats), |
41 | 41 |
as.list(datastats)), |
42 | 42 |
stringsAsFactors = FALSE) |
43 |
- rownames(stats) <- names |
|
43 |
+ rownames(stats) <- bf_d_names |
|
44 | 44 |
colnames(stats) <- colnames(bamfilesstats) |
45 | 45 |
stats |
46 | 46 |
} |
... | ... |
@@ -161,9 +161,9 @@ NULL |
161 | 161 |
#' \code{findMod} for each \code{Modifier} class. See also |
162 | 162 |
#' \code{\link[=modify]{findMod}}. |
163 | 163 |
#' |
164 |
-#' \code{visualizeData}/\code{visualizeDataByCoord} for each \code{Modifier} |
|
164 |
+#' \code{plotData}/\code{plotDataByCoord} for each \code{Modifier} |
|
165 | 165 |
#' and \code{ModifierSet} class. See also |
166 |
-#' \code{\link[=visualizeData]{visualizeData}}. |
|
166 |
+#' \code{\link[=plotData]{plotData}}. |
|
167 | 167 |
#' |
168 | 168 |
#' The following helper function can be called from within \code{findMod} to |
169 | 169 |
#' construct a coordinate for each modification found: |
... | ... |
@@ -232,7 +232,7 @@ NULL |
232 | 232 |
#' ) |
233 | 233 |
#' setMethod( |
234 | 234 |
#' f = "getDataTrack", |
235 |
-#' signature = signature(x = "ExampleSequenceData"), |
|
235 |
+#' signature = c(x = "ExampleSequenceData"), |
|
236 | 236 |
#' definition = function(x, name, ...) { |
237 | 237 |
#' ### |
238 | 238 |
#' } |
... | ... |
@@ -240,7 +240,7 @@ NULL |
240 | 240 |
#' |
241 | 241 |
#' # new Modifier class |
242 | 242 |
#' setClass("ModExample", |
243 |
-#' contains = c("Modifier"), |
|
243 |
+#' contains = "Modifier", |
|
244 | 244 |
#' prototype = list(mod = "X", |
245 | 245 |
#' score = "score", |
246 | 246 |
#' dataType = "ExampleSequenceData")) |
... | ... |
@@ -250,7 +250,7 @@ NULL |
250 | 250 |
#' } |
251 | 251 |
#' |
252 | 252 |
#' setMethod(f = "aggregateData", |
253 |
-#' signature = signature(x = "ModExample"), |
|
253 |
+#' signature = c(x = "ModExample"), |
|
254 | 254 |
#' definition = |
255 | 255 |
#' function(x, force = FALSE){ |
256 | 256 |
#' # Some data with element per transcript |
... | ... |
@@ -270,13 +270,13 @@ NULL |
270 | 270 |
#' } |
271 | 271 |
#' ) |
272 | 272 |
#' setMethod( |
273 |
-#' f = "visualizeDataByCoord", |
|
273 |
+#' f = "plotDataByCoord", |
|
274 | 274 |
#' signature = signature(x = "ModExample", coord = "GRanges"), |
275 | 275 |
#' definition = function(x, coord, type = "score", window.size = 15L, ...) { |
276 | 276 |
#' } |
277 | 277 |
#' ) |
278 | 278 |
#' setMethod( |
279 |
-#' f = "visualizeData", |
|
279 |
+#' f = "plotData", |
|
280 | 280 |
#' signature = signature(x = "ModExample"), |
281 | 281 |
#' definition = function(x, name, from, to, type = "score", ...) { |
282 | 282 |
#' } |
... | ... |
@@ -292,13 +292,13 @@ NULL |
292 | 292 |
#' } |
293 | 293 |
#' |
294 | 294 |
#' setMethod( |
295 |
-#' f = "visualizeDataByCoord", |
|
295 |
+#' f = "plotDataByCoord", |
|
296 | 296 |
#' signature = signature(x = "ModSetExample", coord = "GRanges"), |
297 | 297 |
#' definition = function(x, coord, type = "score", window.size = 15L, ...) { |
298 | 298 |
#' } |
299 | 299 |
#' ) |
300 | 300 |
#' setMethod( |
301 |
-#' f = "visualizeData", |
|
301 |
+#' f = "plotData", |
|
302 | 302 |
#' signature = signature(x = "ModSetExample"), |
303 | 303 |
#' definition = function(x, name, from, to, type = "score", ...) { |
304 | 304 |
#' } |
... | ... |
@@ -458,7 +458,7 @@ setMethod("rownames", "SequenceData", |
458 | 458 |
} |
459 | 459 |
data <- do.call(cbind,data) |
460 | 460 |
} else { |
461 |
- stop("Something went wrong.") |
|
461 |
+ stop("") |
|
462 | 462 |
} |
463 | 463 |
data |
464 | 464 |
} |
... | ... |
@@ -490,8 +490,8 @@ setMethod("rownames", "SequenceData", |
490 | 490 |
############################################################################## |
491 | 491 |
# setup additional variables |
492 | 492 |
############################################################################## |
493 |
- if(missing(args) || !is.list(args)){ |
|
494 |
- args <- list() |
|
493 |
+ if(!is.list(args)){ |
|
494 |
+ args <- as.list(args) |
|
495 | 495 |
} |
496 | 496 |
proto <- new(className) |
497 | 497 |
minQuality <- .norm_min_quality(args, proto@minQuality) |
... | ... |
@@ -545,7 +545,7 @@ setMethod("rownames", "SequenceData", |
545 | 545 |
names(data) <- names(ranges) |
546 | 546 |
if(any(names(ranges) != names(sequences)) || |
547 | 547 |
any(names(ranges) != names(data))){ |
548 |
- stop("Something went wrong.") |
|
548 |
+ stop("") |
|
549 | 549 |
} |
550 | 550 |
message("OK") |
551 | 551 |
############################################################################## |
... | ... |
@@ -62,13 +62,12 @@ CoverageSequenceData <- function(bamfiles, annotation, sequences, seqinfo, ...){ |
62 | 62 |
coverage <- as(coverage,"IntegerList") |
63 | 63 |
# subset per transcript |
64 | 64 |
seqs <- .seqs_rl_strand(grl, force_continous = TRUE) |
65 |
- coverage <- IRanges::IntegerList(mapply( |
|
65 |
+ coverage <- IRanges::IntegerList(Map( |
|
66 | 66 |
function(gr,s){ |
67 | 67 |
coverage[[unique(GenomicRanges::seqnames(gr))]][s] |
68 | 68 |
}, |
69 | 69 |
grl, |
70 |
- seqs, |
|
71 |
- SIMPLIFY = FALSE)) |
|
70 |
+ seqs)) |
|
72 | 71 |
coverage |
73 | 72 |
} |
74 | 73 |
|
... | ... |
@@ -24,7 +24,7 @@ NULL |
24 | 24 |
#' \code{\link[=SequenceData-functions]{SequenceData-functions}} |
25 | 25 |
#' @param x a \code{End5SequenceData}, \code{End3SequenceData} or |
26 | 26 |
#' \code{EndSequenceData} object |
27 |
-#' @param name For \code{\link[=visualizeDataByCoord]{getDataTrack}}: a valid |
|
27 |
+#' @param name For \code{\link[=plotDataByCoord]{getDataTrack}}: a valid |
|
28 | 28 |
#' transcript name. Must be a name of \code{ranges(x).} |
29 | 29 |
#' @param condition For \code{\link{aggregate}}: condition for which the data |
30 | 30 |
#' should be aggregated. |
... | ... |
@@ -175,7 +175,7 @@ EndSequenceData <- function(bamfiles, annotation, sequences, seqinfo, ...){ |
175 | 175 |
# calculate tables and add empty positions |
176 | 176 |
# also remove overhanging read data |
177 | 177 |
seqs <- .seqs_rl(grl) |
178 |
- data <- IRanges::IntegerList(mapply( |
|
178 |
+ data <- IRanges::IntegerList(Map( |
|
179 | 179 |
function(d,s){ |
180 | 180 |
bg <- table(s) - 1L |
181 | 181 |
d <- d[d %in% s] |
... | ... |
@@ -189,16 +189,14 @@ EndSequenceData <- function(bamfiles, annotation, sequences, seqinfo, ...){ |
189 | 189 |
as.integer(d) |
190 | 190 |
}, |
191 | 191 |
data, |
192 |
- seqs[f], |
|
193 |
- SIMPLIFY = FALSE)) |
|
192 |
+ seqs[f])) |
|
194 | 193 |
# get data for empty transcripts |
195 |
- data_not_found <- IRanges::IntegerList(mapply( |
|
194 |
+ data_not_found <- IRanges::IntegerList(Map( |
|
196 | 195 |
function(s){ |
197 | 196 |
d <- table(s) - 1 |
198 | 197 |
as.integer(d) |
199 | 198 |
}, |
200 |
- seqs[f_not_found], |
|
201 |
- SIMPLIFY = FALSE)) |
|
199 |
+ seqs[f_not_found])) |
|
202 | 200 |
# merge and order |
203 | 201 |
data <- c(data,data_not_found) |
204 | 202 |
data <- data[match(names(grl),names(data))] |
... | ... |
@@ -27,7 +27,7 @@ NULL |
27 | 27 |
#' \code{\link[=SequenceData-class]{SequenceData}} and |
28 | 28 |
#' \code{\link[=SequenceData-functions]{SequenceData-functions}} |
29 | 29 |
#' @param x a \code{CoverageSequenceData} |
30 |
-#' @param name For \code{\link[=visualizeDataByCoord]{getDataTrack}}: a valid |
|
30 |
+#' @param name For \code{\link[=plotDataByCoord]{getDataTrack}}: a valid |
|
31 | 31 |
#' transcript name. Must be a name of \code{ranges(x)} |
32 | 32 |
#' @param condition For \code{\link{aggregate}}: condition for which the data |
33 | 33 |
#' should be aggregated. |
... | ... |
@@ -126,7 +126,7 @@ setMethod("summary", |
126 | 126 |
enddata <- .summarize_to_position_data(data, strands_u[f], type) |
127 | 127 |
# tabulate the counts per position |
128 | 128 |
seqs <- .seqs_rl_strand(grl, force_continous = TRUE) |
129 |
- enddata <- IRanges::IntegerList(mapply( |
|
129 |
+ enddata <- IRanges::IntegerList(Map( |
|
130 | 130 |
function(d,s){ |
131 | 131 |
bg <- table(s) - 1L |
132 | 132 |
d <- d[d %in% s] |
... | ... |
@@ -140,12 +140,11 @@ setMethod("summary", |
140 | 140 |
as.integer(d) |
141 | 141 |
}, |
142 | 142 |
enddata, |
143 |
- seqs[f], |
|
144 |
- SIMPLIFY = FALSE)) |
|
143 |
+ seqs[f])) |
|
145 | 144 |
# noralize against total number transcript or against the overlap per position |
146 | 145 |
normTranscript <- (enddata / lengths(data)) * 1000 |
147 | 146 |
normTranscript <- IRanges::NumericList(lapply(normTranscript,unname)) |
148 |
- normOverlap <- IRanges::NumericList(mapply( |
|
147 |
+ normOverlap <- IRanges::NumericList(Map( |
|
149 | 148 |
function(d,end,pos){ |
150 | 149 |
gr <- GenomicRanges::GRanges( |
151 | 150 |
seqnames = as.character(unique(seqnames(d))), |
... | ... |
@@ -155,16 +154,14 @@ setMethod("summary", |
155 | 154 |
}, |
156 | 155 |
data, |
157 | 156 |
enddata, |
158 |
- seqs[f], |
|
159 |
- SIMPLIFY = FALSE)) |
|
157 |
+ seqs[f])) |
|
160 | 158 |
# calculate tables and add empty positions |
161 |
- data_not_found <- IRanges::IntegerList(mapply( |
|
159 |
+ data_not_found <- IRanges::IntegerList(Map( |
|
162 | 160 |
function(s){ |
163 | 161 |
d <- table(s) - 1 |
164 | 162 |
as.integer(d) |
165 | 163 |
}, |
166 |
- seqs[f_not_found], |
|
167 |
- SIMPLIFY = FALSE)) |
|
164 |
+ seqs[f_not_found])) |
|
168 | 165 |
# merge data with empty data and order based on factor numbers |
169 | 166 |
enddata <- c(enddata,data_not_found) |
170 | 167 |
enddata@unlistData[is.na(enddata@unlistData)] <- 0L |
... | ... |
@@ -24,7 +24,7 @@ NULL |
24 | 24 |
#' \code{\link[=SequenceData-class]{SequenceData}} and |
25 | 25 |
#' \code{\link[=SequenceData-functions]{SequenceData-functions}} |
26 | 26 |
#' @param x a \code{PileupSequenceData} |
27 |
-#' @param name For \code{\link[=visualizeDataByCoord]{getDataTrack}}: a valid |
|
27 |
+#' @param name For \code{\link[=plotDataByCoord]{getDataTrack}}: a valid |
|
28 | 28 |
#' transcript name. Must be a name of \code{ranges(x)} |
29 | 29 |
#' @param condition For \code{\link{aggregate}}: condition for which the data |
30 | 30 |
#' should be aggregated. |
... | ... |
@@ -138,7 +138,7 @@ PileupSequenceData <- function(bamfiles, annotation, sequences, seqinfo, ...){ |
138 | 138 |
# object and using it to relist |
139 | 139 |
pileup <- .splitPileupAsList_transcript(pileup, grl) |
140 | 140 |
if(length(pileup) != length(grl)){ |
141 |
- stop("Something went wrong.") |
|
141 |
+ stop("") |
|
142 | 142 |
} |
143 | 143 |
# sanitize pilup data |
144 | 144 |
# - keep only data for correct strand |
... | ... |
@@ -146,7 +146,7 @@ PileupSequenceData <- function(bamfiles, annotation, sequences, seqinfo, ...){ |
146 | 146 |
strands_u <- .get_strand_u_GRangesList(grl) |
147 | 147 |
seqs <- .seqs_rl(grl) |
148 | 148 |
pileup <- IRanges::SplitDataFrameList( |
149 |
- mapply( |
|
149 |
+ Map( |
|
150 | 150 |
function(d,seq,strand){ |
151 | 151 |
ans <- NULL |
152 | 152 |
d <- d[d$strand == strand,] |
... | ... |
@@ -165,8 +165,7 @@ PileupSequenceData <- function(bamfiles, annotation, sequences, seqinfo, ...){ |
165 | 165 |
}, |
166 | 166 |
pileup, |
167 | 167 |
seqs, |
168 |
- strands_u, |
|
169 |
- SIMPLIFY = FALSE)) |
|
168 |
+ strands_u)) |
|
170 | 169 |
names(pileup) <- names(grl) |
171 | 170 |
pileup |
172 | 171 |
} |
... | ... |
@@ -394,7 +393,7 @@ setMethod( |
394 | 393 |
#' @rdname PileupSequenceData-class |
395 | 394 |
#' @export |
396 | 395 |
setGeneric(name = "pileupToCoverage", |
397 |
- signature = c("x"), |
|
396 |
+ signature = "x", |
|
398 | 397 |
def = function(x) standardGeneric("pileupToCoverage")) |
399 | 398 |
|
400 | 399 |
.aggregate_pile_up_to_coverage <- function(data){ |
... | ... |
@@ -34,7 +34,7 @@ RNAMODR_PROT_SEQDATA_PLOT_DATA_COLOURS <- c(means = "#FBB4AE", |
34 | 34 |
#' \code{\link[=SequenceData-class]{SequenceData}} and |
35 | 35 |
#' \code{\link[=SequenceData-functions]{SequenceData-functions}} |
36 | 36 |
#' @param x a \code{ProtectedEndSequenceData} |
37 |
-#' @param name For \code{\link[=visualizeDataByCoord]{getDataTrack}}: a valid |
|
37 |
+#' @param name For \code{\link[=plotDataByCoord]{getDataTrack}}: a valid |
|
38 | 38 |
#' transcript name. Must be a name of \code{ranges(x)} |
39 | 39 |
#' @param condition For \code{\link{aggregate}}: condition for which the data |
40 | 40 |
#' should be aggregated. |
... | ... |
@@ -95,7 +95,7 @@ NULL |
95 | 95 |
coord <- coord[!duplicated(coord)] |
96 | 96 |
return(.norm_coord(coord, type, merge)) |
97 | 97 |
} else { |
98 |
- stop("Something went wrong.") |
|
98 |
+ stop("") |
|
99 | 99 |
} |
100 | 100 |
if(unique(unlist(width(ranges(coord)))) != 1L){ |
101 | 101 |
stop("Elements with a width != 1L are not supported.", |
... | ... |
@@ -132,30 +132,29 @@ NULL |
132 | 132 |
paste(type, collapse = "','"), "'") |
133 | 133 |
} |
134 | 134 |
if(is.na(name)){ |
135 |
- names <- intersect(namesData, namesCoord) |
|
135 |
+ intersect_names <- intersect(namesData, namesCoord) |
|
136 | 136 |
message <- c("No intersection between names in data of 'x' and Parent in ", |
137 | 137 |
"'coord'\n ",messageType) |
138 | 138 |
} else { |
139 |
- names <- Reduce(intersect, |
|
140 |
- list(namesData,namesCoord),name) |
|
139 |
+ intersect_names <- Reduce(intersect, |
|
140 |
+ list(namesData,namesCoord),name) |
|
141 | 141 |
message <- c("No intersection between names in data of 'x', Parent in ", |
142 | 142 |
"'coord'\n ",messageType," and the selected name.") |
143 | 143 |
} |
144 |
- if(length(names) == 0L){ |
|
144 |
+ if(length(intersect_names) == 0L){ |
|
145 | 145 |
stop(message, |
146 | 146 |
call. = FALSE) |
147 | 147 |
} |
148 |
- names |
|
148 |
+ intersect_names |
|
149 | 149 |
} |
150 | 150 |
|
151 | 151 |
.check_for_invalid_positions <- function(data, coord){ |
152 | 152 |
lengths <- lengths(data) |
153 | 153 |
positions <- start(ranges(coord)) |
154 | 154 |
f_names <- match(names(positions),names(lengths)) |
155 |
- f <- IRanges::LogicalList(mapply(function(i,j){i >= j}, |
|
156 |
- positions, |
|
157 |
- lengths[f_names], |
|
158 |
- SIMPLIFY = FALSE)) |
|
155 |
+ f <- IRanges::LogicalList(Map(function(i,j){i >= j}, |
|
156 |
+ positions, |
|
157 |
+ lengths[f_names])) |
|
159 | 158 |
if(!any(lengths(BiocGenerics::which(f)) > 0L )){ |
160 | 159 |
return(NULL) |
161 | 160 |
} |
... | ... |
@@ -203,13 +202,12 @@ NULL |
203 | 202 |
flank)) |
204 | 203 |
ans <- data[m][ff] |
205 | 204 |
if(perTranscript){ |
206 |
- pos <- IRanges::CharacterList(mapply( |
|
205 |
+ pos <- IRanges::CharacterList(Map( |
|
207 | 206 |
function(d,i){ |
208 | 207 |
BiocGenerics::which(rownames(d) %in% i) |
209 | 208 |
}, |
210 | 209 |
data[m], |
211 |
- flank, |
|
212 |
- SIMPLIFY = FALSE)) |
|
210 |
+ flank)) |
|
213 | 211 |
rownames(ans) <- pos |
214 | 212 |
} |
215 | 213 |
return(ans) |
... | ... |
@@ -221,9 +219,10 @@ NULL |
221 | 219 |
args <- .norm_subset_args(list(...), NULL) |
222 | 220 |
data <- .norm_data(data) |
223 | 221 |
coord <- .norm_coord(coord, NA, args[["merge"]]) |
224 |
- names <- .get_element_names(data, coord, args[["name"]], args[["type"]]) |
|
225 |
- data <- data[match(names, names(data))] |
|
226 |
- coord <- coord[names(coord) %in% names] |
|
222 |
+ element_names <- .get_element_names(data, coord, args[["name"]], |
|
223 |
+ args[["type"]]) |
|
224 |
+ data <- data[match(element_names, names(data))] |
|
225 |
+ coord <- coord[names(coord) %in% element_names] |
|
227 | 226 |
.perform_subset(data, coord, args[["flanking"]], args[["perTranscript"]]) |
228 | 227 |
} |
229 | 228 |
|
... | ... |
@@ -237,9 +236,10 @@ NULL |
237 | 236 |
data <- .norm_aggregate_data(aggregate(x)) |
238 | 237 |
} |
239 | 238 |
data <- .norm_data(data) |
240 |
- names <- .get_element_names(data, coord, args[["name"]], args[["type"]]) |
|
241 |
- data <- data[match(names, names(data))] |
|
242 |
- coord <- coord[names(coord) %in% names] |
|
239 |
+ element_names <- .get_element_names(data, coord, args[["name"]], |
|
240 |
+ args[["type"]]) |
|
241 |
+ data <- data[match(element_names, names(data))] |
|
242 |
+ coord <- coord[names(coord) %in% element_names] |
|
243 | 243 |
.perform_subset(data, coord, args[["flanking"]], args[["perTranscript"]]) |
244 | 244 |
} |
245 | 245 |
|
... | ... |
@@ -266,7 +266,7 @@ NULL |
266 | 266 |
} else if(is(z,"SequenceDataSet")) { |
267 | 267 |
return(.subset_SequenceDataSet_by_GRangesList(z, coord, ...)) |
268 | 268 |
} else { |
269 |
- stop("Something went wrong.") |
|
269 |
+ stop("") |
|
270 | 270 |
} |
271 | 271 |
}) |
272 | 272 |
ans <- do.call(cbind,ans) |
... | ... |
@@ -346,10 +346,9 @@ setMethod("subsetByCoord", |
346 | 346 |
} |
347 | 347 |
labels <- IRanges::LogicalList(lapply(lengths(data), |
348 | 348 |
function(l){rep(FALSE,l)})) |
349 |
- labels[f_rn] <- IRanges::LogicalList(mapply("%in%", |
|
350 |
- rn_d[f_rn], |
|
351 |
- positions[f_p], |
|
352 |
- SIMPLIFY = FALSE)) |
|
349 |
+ labels[f_rn] <- IRanges::LogicalList(Map("%in%", |
|
350 |
+ rn_d[f_rn], |
|
351 |
+ positions[f_p])) |
|
353 | 352 |
unlisted_data <- unlist(data, use.names = FALSE) |
354 | 353 |
unlisted_data$labels <- unlist(labels, use.names = FALSE) |
355 | 354 |
return(relist(unlisted_data, data)) |
... | ... |
@@ -407,7 +406,7 @@ setMethod("subsetByCoord", |
407 | 406 |
} else if(is(z,"SequenceDataSet")) { |
408 | 407 |
return(.label_SequenceDataSet_by_GRangesList(z, coord,...)) |
409 | 408 |
} else { |
410 |
- stop("Something went wrong.") |
|
409 |
+ stop("") |
|
411 | 410 |
} |
412 | 411 |
}) |
413 | 412 |
.keep_one_labels_column(ans) |
... | ... |
@@ -28,13 +28,6 @@ NULL |
28 | 28 |
window.size |
29 | 29 |
} |
30 | 30 |
|
31 |
-.norm_viz_name <- function(name){ |
|
32 |
- if(missing(name)){ |
|
33 |
- name <- NULL |
|
34 |
- } |
|
35 |
- name |
|
36 |
-} |
|
37 |
- |
|
38 | 31 |
.get_viz_from_to_coord <- function(ranges, coord, window.size){ |
39 | 32 |
window.size <- .norm_viz_windows.size(window.size) |
40 | 33 |
start <- start(coord) - window.size |
... | ... |
@@ -185,8 +178,8 @@ NULL |
185 | 178 |
if(length(ranges) == 0L){ |
186 | 179 |
stop("No ranges with seqnames = '",chromosome,"' found.") |
187 | 180 |
} |
188 |
- names <- names(ranges) |
|
189 |
- seq <- seq[names(seq) %in% names] |
|
181 |
+ ranges_names <- names(ranges) |
|
182 |
+ seq <- seq[names(seq) %in% ranges_names] |
|
190 | 183 |
if(length(seq) == 0L){ |
191 | 184 |
stop("No sequences for seqnames = '",chromosome,"' found.") |
192 | 185 |
} |
... | ... |
@@ -268,7 +261,7 @@ NULL |
268 | 261 |
} else if(is(seq,"ModRNAStringSet")){ |
269 | 262 |
st <- FUN("ModRNASequenceTrack","ModRNAStringSet", seq, args) |
270 | 263 |
} else { |
271 |
- stop("Something went wrong.") |
|
264 |
+ stop("") |
|
272 | 265 |
} |
273 | 266 |
st |
274 | 267 |
} |
... | ... |
@@ -288,14 +281,14 @@ NULL |
288 | 281 |
x <- x[name] |
289 | 282 |
data <- aggregate(x) |
290 | 283 |
} else { |
291 |
- stop("Something went wrong.") |
|
284 |
+ stop("") |
|
292 | 285 |
} |
293 | 286 |
strand_u <- .get_strand_u_GRangesList(ranges) |
294 | 287 |
seqs <- .seqs_rl(ranges) |
295 | 288 |
seqs[strand_u == "-"] <- rev(seqs[strand_u == "-"]) |
296 |
- seqnames <- .seqnames_rl(ranges) |
|
289 |
+ ranges_seqnames <- .seqnames_rl(ranges) |
|
297 | 290 |
strands <- .strands_rl(ranges) |
298 |
- ans <- GenomicRanges::GRanges(seqnames = unlist(seqnames), |
|
291 |
+ ans <- GenomicRanges::GRanges(seqnames = unlist(ranges_seqnames), |
|
299 | 292 |
ranges = IRanges::IRanges(start = unlist(seqs), |
300 | 293 |
width = 1), |
301 | 294 |
strand = unlist(strands), |
... | ... |
@@ -307,25 +300,25 @@ NULL |
307 | 300 |
|
308 | 301 |
################################################################################ |
309 | 302 |
|
310 |
-#' @rdname visualizeData |
|
303 |
+#' @rdname plotData |
|
311 | 304 |
#' @export |
312 | 305 |
setMethod( |
313 |
- f = "visualizeDataByCoord", |
|
306 |
+ f = "plotDataByCoord", |
|
314 | 307 |
signature = signature(x = "SequenceData", coord = "GRanges"), |
315 | 308 |
definition = function(x, coord, type = NA, window.size = 15L, ...) { |
316 | 309 |
# input check |
317 | 310 |
coord <- .norm_coord_for_visualization(ranges(x), coord) |
318 | 311 |
from_to <- .get_viz_from_to_coord(ranges(x), coord, window.size) |
319 |
- visualizeData(x, name = coord$Parent, from = from_to$from, |
|
312 |
+ plotData(x, name = coord$Parent, from = from_to$from, |
|
320 | 313 |
to = from_to$to, type = type, ...) |
321 | 314 |
} |
322 | 315 |
) |
323 | 316 |
|
324 |
-#' @rdname visualizeData |
|
317 |
+#' @rdname plotData |
|
325 | 318 |
#' @importFrom Gviz plotTracks |
326 | 319 |
#' @export |
327 | 320 |
setMethod( |
328 |
- f = "visualizeData", |
|
321 |
+ f = "plotData", |
|
329 | 322 |
signature = signature(x = "SequenceData"), |
330 | 323 |
definition = function(x, name, from, to, perTranscript = FALSE, |
331 | 324 |
showSequence = TRUE, showAnnotation = FALSE, ...) { |
... | ... |
@@ -358,7 +351,7 @@ setMethod( |
358 | 351 |
} |
359 | 352 |
) |
360 | 353 |
|
361 |
-#' @rdname visualizeData |
|
354 |
+#' @rdname plotData |
|
362 | 355 |
#' @export |
363 | 356 |
setMethod( |
364 | 357 |
f = "getDataTrack", |
... | ... |
@@ -2,7 +2,7 @@ |
2 | 2 |
#' @include SequenceDataSet-class.R |
3 | 3 |
NULL |
4 | 4 |
|
5 |
-#' @rdname visualizeData |
|
5 |
+#' @rdname plotData |
|
6 | 6 |
#' @export |
7 | 7 |
setMethod( |
8 | 8 |
f = "getDataTrack", |
... | ... |
@@ -18,25 +18,25 @@ setMethod( |
18 | 18 |
) |
19 | 19 |
|
20 | 20 |
|
21 |
-#' @rdname visualizeData |
|
21 |
+#' @rdname plotData |
|
22 | 22 |
#' @export |
23 | 23 |
setMethod( |
24 |
- f = "visualizeDataByCoord", |
|
24 |
+ f = "plotDataByCoord", |
|
25 | 25 |
signature = signature(x = "SequenceDataList", coord = "GRanges"), |
26 | 26 |
definition = function(x, coord, type = NA, window.size = 15L, ...) { |
27 | 27 |
# input check |
28 | 28 |
coord <- .norm_coord_for_visualization(ranges(x), coord) |
29 | 29 |
from_to <- .get_viz_from_to_coord(ranges(x), coord, window.size) |
30 |
- visualizeData(x, name = coord$Parent, from = from_to$from, |
|
30 |
+ plotData(x, name = coord$Parent, from = from_to$from, |
|
31 | 31 |
to = from_to$to, type = type, ...) |
32 | 32 |
} |
33 | 33 |
) |
34 | 34 |
|
35 |
-#' @rdname visualizeData |
|
35 |
+#' @rdname plotData |
|
36 | 36 |
#' @importFrom Gviz plotTracks |
37 | 37 |
#' @export |
38 | 38 |
setMethod( |
39 |
- f = "visualizeData", |
|
39 |
+ f = "plotData", |
|
40 | 40 |
signature = signature(x = "SequenceDataList"), |
41 | 41 |
definition = function(x, name, from, to, perTranscript = FALSE, |
42 | 42 |
showSequence = TRUE, showAnnotation = FALSE, ...) { |
... | ... |
@@ -2,7 +2,7 @@ |
2 | 2 |
#' @include SequenceDataSet-class.R |
3 | 3 |
NULL |
4 | 4 |
|
5 |
-#' @rdname visualizeData |
|
5 |
+#' @rdname plotData |
|
6 | 6 |
#' @export |
7 | 7 |
setMethod( |
8 | 8 |
f = "getDataTrack", |
... | ... |
@@ -18,25 +18,25 @@ setMethod( |
18 | 18 |
) |
19 | 19 |
|
20 | 20 |
|
21 |
-#' @rdname visualizeData |
|
21 |
+#' @rdname plotData |
|
22 | 22 |
#' @export |
23 | 23 |
setMethod( |
24 |
- f = "visualizeDataByCoord", |
|
24 |
+ f = "plotDataByCoord", |
|
25 | 25 |
signature = signature(x = "SequenceDataSet", coord = "GRanges"), |
26 | 26 |
definition = function(x, coord, type = NA, window.size = 15L, ...) { |
27 | 27 |
# input check |
28 | 28 |
coord <- .norm_coord_for_visualization(ranges(x), coord) |
29 | 29 |
from_to <- .get_viz_from_to_coord(ranges(x), coord, window.size) |
30 |
- visualizeData(x, name = coord$Parent, from = from_to$from, |
|
30 |
+ plotData(x, name = coord$Parent, from = from_to$from, |
|
31 | 31 |
to = from_to$to, type = type, ...) |
32 | 32 |
} |
33 | 33 |
) |
34 | 34 |
|
35 |
-#' @rdname visualizeData |
|
35 |
+#' @rdname plotData |
|
36 | 36 |
#' @importFrom Gviz plotTracks |
37 | 37 |
#' @export |
38 | 38 |
setMethod( |
39 |
- f = "visualizeData", |
|
39 |
+ f = "plotData", |
|
40 | 40 |
signature = signature(x = "SequenceDataSet"), |
41 | 41 |
definition = function(x, name, from, to, perTranscript = FALSE, |
42 | 42 |
showSequence = TRUE, showAnnotation = FALSE, ...) { |
... | ... |
@@ -123,8 +123,8 @@ SAMPLE_TYPES <- c("treated","control") |
123 | 123 |
stop("Names of BamFileList must either be 'treated' or 'control' (case ", |
124 | 124 |
"insensitive). No names found.") |
125 | 125 |
} |
126 |
- names <- tolower(unique(names(x))) |
|
127 |
- if(!all(names %in% SAMPLE_TYPES)){ |
|
126 |
+ x_names <- tolower(unique(names(x))) |
|
127 |
+ if(!all(x_names %in% SAMPLE_TYPES)){ |
|
128 | 128 |
stop("Names of BamFileList must either be 'treated' or 'control' (case ", |
129 | 129 |
"insensitive).", |
130 | 130 |
call. = FALSE) |
... | ... |
@@ -185,9 +185,12 @@ SAMPLE_TYPES <- c("treated","control") |
185 | 185 |
#' @importFrom BSgenome seqnames |
186 | 186 |
#' @importFrom Rsamtools scanFa |
187 | 187 |
.norm_seqnames <- function(bamfiles, annotation, sequences, seqinfo, className){ |
188 |
+ if(missing(seqinfo)){ |
|
189 |
+ seqinfo <- NULL |
|
190 |
+ } |
|
188 | 191 |
# norm seqinfo |
189 |
- if(missing(seqinfo) || |
|
190 |
- (!is(seqinfo,"Seqinfo") && (is.na(seqinfo) || is.null(seqinfo)))){ |
|
192 |
+ if(is.null(seqinfo) || |
|
193 |
+ (!is(seqinfo,"Seqinfo") && (is.na(seqinfo)))){ |
|
191 | 194 |
seqinfo <- .bam_header_to_seqinfo(bamfiles) |
192 | 195 |
} |
193 | 196 |
if(!is(seqinfo,"Seqinfo") && |
... | ... |
@@ -199,19 +202,21 @@ SAMPLE_TYPES <- c("treated","control") |
199 | 202 |
} |
200 | 203 |
# norm annotation |
201 | 204 |
if(!is(annotation,"GRangesList") & !is(annotation,"TxDb")){ |
202 |
- stop("Something went wrong.") |
|
205 |
+ stop("") |
|
203 | 206 |
} |
204 | 207 |
if(!is(sequences,"FaFile") & !is(sequences,"BSgenome")){ |
205 |
- stop("Something went wrong.") |
|
208 |
+ stop("") |
|
206 | 209 |
} |
207 | 210 |
# norm sequences input |
208 | 211 |
if(is(sequences,"FaFile")){ |
209 |
- seqnames <- names(Rsamtools::scanFa(sequences)) |
|
212 |
+ seq_seqnames <- names(Rsamtools::scanFa(sequences)) |
|
210 | 213 |
} else { |
211 |
- seqnames <- BSgenome::seqnames(sequences) |
|
214 |
+ seq_seqnames <- BSgenome::seqnames(sequences) |
|
212 | 215 |
} |
213 |
- seqnames <- seqnames[seqnames %in% GenomeInfoDb::seqlevels(annotation)] |
|
214 |
- seqnames <- seqnames[seqnames %in% GenomeInfoDb::seqnames(seqinfo)] |
|
216 |
+ seq_seqnames <- |
|
217 |
+ seq_seqnames[seq_seqnames %in% GenomeInfoDb::seqlevels(annotation)] |
|
218 |
+ seq_seqnames <- |
|
219 |
+ seq_seqnames[seq_seqnames %in% GenomeInfoDb::seqnames(seqinfo)] |
|
215 | 220 |
if( length(seqnames) == 0L ) { |
216 | 221 |
stop("No intersection between chromosome names in fasta, ", |
217 | 222 |
"annotation and seqinfo data.", |
... | ... |
@@ -31,9 +31,9 @@ NULL |
31 | 31 |
#' @importFrom Rsamtools idxstatsBam |
32 | 32 |
# Extracts sequence names aka. chromosome identifier from list of bam files |
33 | 33 |
.get_acceptable_chrom_ident <- function(bamFiles){ |
34 |
- seqnames <- lapply(bamFiles, function(file){ |
|
34 |
+ bf_seqnames <- lapply(bamFiles, function(file){ |
|
35 | 35 |
res <- Rsamtools::idxstatsBam(file) |
36 | 36 |
return(as.character(res$seqnames)) |
37 | 37 |
}) |
38 |
- return(unique(unlist(seqnames))) |
|
38 |
+ return(unique(unlist(bf_seqnames))) |
|
39 | 39 |
} |
... | ... |
@@ -42,10 +42,10 @@ NULL |
42 | 42 |
# seqlengths related functions |
43 | 43 |
.rebase_GRanges <- function(gr){ |
44 | 44 |
usn <- .get_unique_seqnames(gr) |
45 |
- seqnames <- Rle(factor(GenomicRanges::seqnames(gr), levels = usn)) |
|
45 |
+ gr_seqnames <- Rle(factor(GenomicRanges::seqnames(gr), levels = usn)) |
|
46 | 46 |
seqlengths <- GenomeInfoDb::seqlengths(gr)[usn] |
47 | 47 |
seqinfo <- GenomeInfoDb::Seqinfo(usn, seqlengths) |
48 |
- GenomicRanges::GRanges(seqnames = seqnames, |
|
48 |
+ GenomicRanges::GRanges(seqnames = gr_seqnames, |
|
49 | 49 |
ranges = IRanges::ranges(gr), |
50 | 50 |
strand = BiocGenerics::strand(gr), |
51 | 51 |
seqinfo = seqinfo, |
... | ... |
@@ -75,27 +75,25 @@ NULL |
75 | 75 |
# per positions of each element |
76 | 76 |
|
77 | 77 |
.seqnames_rl <- function(rl){ |
78 |
- seqnames <- as.character(seqnames(rl@unlistData)) |
|
78 |
+ ul_seqnames <- as.character(seqnames(rl@unlistData)) |
|
79 | 79 |
width <- as.integer(width(rl@unlistData)) |
80 |
- seqnames <- mapply(rep,seqnames,width,SIMPLIFY = FALSE) |
|
81 |
- seqnames <- IRanges::CharacterList(lapply(mapply(seq.int, |
|
80 |
+ ul_seqnames <- Map(rep,ul_seqnames,width) |
|
81 |
+ ul_seqnames <- IRanges::CharacterList(lapply(Map(seq.int, |
|
82 | 82 |
start(rl@partitioning), |
83 |
- end(rl@partitioning), |
|
84 |
- SIMPLIFY = FALSE), |
|
85 |
- function(i){ |
|
86 |
- unname(unlist(seqnames[i])) |
|
87 |
- })) |
|
88 |
- seqnames |
|
83 |
+ end(rl@partitioning)), |
|
84 |
+ function(i){ |
|
85 |
+ unname(unlist(ul_seqnames[i])) |
|
86 |
+ })) |
|
87 |
+ ul_seqnames |
|
89 | 88 |
} |
90 | 89 |
|
91 | 90 |
.strands_rl <- function(rl){ |
92 | 91 |
strands <- as.character(strand(rl@unlistData)) |
93 | 92 |
width <- as.integer(width(rl@unlistData)) |
94 |
- strands <- mapply(rep,strands,width,SIMPLIFY = FALSE) |
|
95 |
- strands <- IRanges::CharacterList(lapply(mapply(seq.int, |
|
96 |
- start(rl@partitioning), |
|
97 |
- end(rl@partitioning), |
|
98 |
- SIMPLIFY = FALSE), |
|
93 |
+ strands <- Map(rep,strands,width) |
|
94 |
+ strands <- IRanges::CharacterList(lapply(Map(seq.int, |
|
95 |
+ start(rl@partitioning), |
|
96 |
+ end(rl@partitioning)), |
|
99 | 97 |
function(i){ |
100 | 98 |
unname(unlist(strands[i])) |
101 | 99 |
})) |
... | ... |
@@ -152,13 +150,12 @@ NULL |
152 | 150 |
from <- tmp |
153 | 151 |
rm(tmp) |
154 | 152 |
} |
155 |
- ans <- mapply( |
|
153 |
+ ans <- Map( |
|
156 | 154 |
function(f,t){ |
157 | 155 |
seq.int(f,t,by) |
158 | 156 |
}, |
159 | 157 |
from, |
160 |
- to, |
|
161 |
- SIMPLIFY = FALSE) |
|
158 |
+ to) |
|
162 | 159 |
ans <- IRanges::IntegerList(ans) |
163 | 160 |
width_x <- IRanges::IntegerList(split(width(ans@partitioning), |
164 | 161 |
names(ans@partitioning))) |
... | ... |
@@ -201,7 +198,7 @@ NULL |
201 | 198 |
.subset_to_condition <- function(conditions, condition){ |
202 | 199 |
if(condition != "both"){ |
203 | 200 |
f <- conditions == condition |
204 |
- if(all(f == FALSE)){ |
|
201 |
+ if(all(!f)){ |
|
205 | 202 |
stop("No data for condition '",condition,"' found.") |
206 | 203 |
} |
207 | 204 |
} else { |
... | ... |
@@ -63,7 +63,7 @@ EndSequenceData(bamfiles, annotation, sequences, seqinfo, ...) |
63 | 63 |
\item{condition}{For \code{\link{aggregate}}: condition for which the data |
64 | 64 |
should be aggregated.} |
65 | 65 |
|
66 |
-\item{name}{For \code{\link[=visualizeDataByCoord]{getDataTrack}}: a valid |
|
66 |
+\item{name}{For \code{\link[=plotDataByCoord]{getDataTrack}}: a valid |
|
67 | 67 |
transcript name. Must be a name of \code{ranges(x).}} |
68 | 68 |
} |
69 | 69 |
\value{ |
... | ... |
@@ -8,10 +8,10 @@ |
8 | 8 |
\alias{aggregateData,ModInosine-method} |
9 | 9 |
\alias{findMod,ModInosine-method} |
10 | 10 |
\alias{getDataTrack,ModInosine-method} |
11 |
-\alias{visualizeDataByCoord,ModInosine,GRanges-method} |
|
12 |
-\alias{visualizeData,ModInosine-method} |
|
13 |
-\alias{visualizeDataByCoord,ModSetInosine,GRanges-method} |
|
14 |
-\alias{visualizeData,ModSetInosine-method} |
|
11 |
+\alias{plotDataByCoord,ModInosine,GRanges-method} |
|
12 |
+\alias{plotData,ModInosine-method} |
|
13 |
+\alias{plotDataByCoord,ModSetInosine,GRanges-method} |
|
14 |
+\alias{plotData,ModSetInosine-method} |
|
15 | 15 |
\title{Functions for ModInosine} |
16 | 16 |
\usage{ |
17 | 17 |
\S4method{settings}{ModInosine}(x) <- value |
... | ... |
@@ -22,16 +22,16 @@ |
22 | 22 |
|
23 | 23 |
\S4method{getDataTrack}{ModInosine}(x, name, type, ...) |
24 | 24 |
|
25 |
-\S4method{visualizeDataByCoord}{ModInosine,GRanges}(x, coord, |
|
26 |
- type = "score", window.size = 15L, ...) |
|
25 |
+\S4method{plotDataByCoord}{ModInosine,GRanges}(x, coord, type = "score", |
|
26 |
+ window.size = 15L, ...) |
|
27 | 27 |
|
28 |
-\S4method{visualizeData}{ModInosine}(x, name, from = 1L, to = 30L, |
|
28 |
+\S4method{plotData}{ModInosine}(x, name, from = 1L, to = 30L, |
|
29 | 29 |
type = "score", ...) |
30 | 30 |
|
31 |
-\S4method{visualizeDataByCoord}{ModSetInosine,GRanges}(x, coord, |
|
31 |
+\S4method{plotDataByCoord}{ModSetInosine,GRanges}(x, coord, |
|
32 | 32 |
type = "score& |