... | ... |
@@ -2,20 +2,27 @@ |
2 | 2 |
|
3 | 3 |
export("settings<-") |
4 | 4 |
export(CoverageSequenceData) |
5 |
+export(CoverageSequenceDataFrame) |
|
5 | 6 |
export(End3SequenceData) |
7 |
+export(End3SequenceDataFrame) |
|
6 | 8 |
export(End5SequenceData) |
9 |
+export(End5SequenceDataFrame) |
|
7 | 10 |
export(EndSequenceData) |
11 |
+export(EndSequenceDataFrame) |
|
8 | 12 |
export(ModInosine) |
9 | 13 |
export(ModRNASequenceTrack) |
10 | 14 |
export(ModSetInosine) |
11 | 15 |
export(Modifier) |
12 | 16 |
export(ModifierSet) |
13 | 17 |
export(NormEnd3SequenceData) |
18 |
+export(NormEnd3SequenceDataFrame) |
|
14 | 19 |
export(NormEnd5SequenceData) |
20 |
+export(NormEnd5SequenceDataFrame) |
|
15 | 21 |
export(PileupSequenceData) |
22 |
+export(PileupSequenceDataFrame) |
|
16 | 23 |
export(ProtectedEndSequenceData) |
24 |
+export(ProtectedEndSequenceDataFrame) |
|
17 | 25 |
export(RNASequenceTrack) |
18 |
-export(SequenceDataFrame) |
|
19 | 26 |
export(SequenceDataList) |
20 | 27 |
export(SequenceDataSet) |
21 | 28 |
export(aggregate) |
... | ... |
@@ -49,18 +56,26 @@ export(subsetByCoord) |
49 | 56 |
export(validAggregate) |
50 | 57 |
export(validModification) |
51 | 58 |
exportClasses(CoverageSequenceData) |
59 |
+exportClasses(CoverageSequenceDataFrame) |
|
52 | 60 |
exportClasses(End3SequenceData) |
61 |
+exportClasses(End3SequenceDataFrame) |
|
53 | 62 |
exportClasses(End5SequenceData) |
63 |
+exportClasses(End5SequenceDataFrame) |
|
54 | 64 |
exportClasses(EndSequenceData) |
65 |
+exportClasses(EndSequenceDataFrame) |
|
55 | 66 |
exportClasses(ModInosine) |
56 | 67 |
exportClasses(ModRNASequenceTrack) |
57 | 68 |
exportClasses(ModSetInosine) |
58 | 69 |
exportClasses(Modifier) |
59 | 70 |
exportClasses(ModifierSet) |
60 | 71 |
exportClasses(NormEnd3SequenceData) |
72 |
+exportClasses(NormEnd3SequenceDataFrame) |
|
61 | 73 |
exportClasses(NormEnd5SequenceData) |
74 |
+exportClasses(NormEnd5SequenceDataFrame) |
|
62 | 75 |
exportClasses(PileupSequenceData) |
76 |
+exportClasses(PileupSequenceDataFrame) |
|
63 | 77 |
exportClasses(ProtectedEndSequenceData) |
78 |
+exportClasses(ProtectedEndSequenceDataFrame) |
|
64 | 79 |
exportClasses(RNASequenceTrack) |
65 | 80 |
exportClasses(SequenceDataFrame) |
66 | 81 |
exportClasses(SequenceDataList) |
... | ... |
@@ -140,8 +155,13 @@ importFrom(GenomicFeatures,makeTxDbFromGFF) |
140 | 155 |
importFrom(Gviz,AnnotationTrack) |
141 | 156 |
importFrom(Gviz,DataTrack) |
142 | 157 |
importFrom(Gviz,plotTracks) |
158 |
+importFrom(IRanges,CharacterList) |
|
159 |
+importFrom(IRanges,IRanges) |
|
160 |
+importFrom(IRanges,IntegerList) |
|
161 |
+importFrom(IRanges,LogicalList) |
|
143 | 162 |
importFrom(IRanges,PartitioningByEnd) |
144 | 163 |
importFrom(IRanges,PartitioningByWidth) |
164 |
+importFrom(IRanges,SplitDataFrameList) |
|
145 | 165 |
importFrom(IRanges,splitAsList) |
146 | 166 |
importFrom(Modstrings,ModRNAString) |
147 | 167 |
importFrom(Modstrings,ModRNAStringSet) |
... | ... |
@@ -283,7 +283,7 @@ setClass("Modifier", |
283 | 283 |
} |
284 | 284 |
if(hasAggregateData(x)){ |
285 | 285 |
data <- getAggregateData(x) |
286 |
- if(is.null(rownames(data@unlistData))){ |
|
286 |
+ if(is.null(rownames(unlist(data, use.names = FALSE)))){ |
|
287 | 287 |
return("rownames of aggregate data is not set.") |
288 | 288 |
} else { |
289 | 289 |
seqs <- .seqs_rl_strand(ranges(x)) |
... | ... |
@@ -871,7 +871,7 @@ NULL |
871 | 871 |
.check_aggregate_modifier <- function(data, x){ |
872 | 872 |
score <- x@score |
873 | 873 |
if(is(data,"CompressedSplitDataFrameList")){ |
874 |
- columns <- colnames(data@unlistData) |
|
874 |
+ columns <- colnames(unlist(data, use.names = FALSE)) |
|
875 | 875 |
} else { |
876 | 876 |
stop("aggregate data has to be a 'CompressedSplitDataFrameList' object. ", |
877 | 877 |
"Contact the maintainer of the class used.", |
... | ... |
@@ -22,14 +22,15 @@ NULL |
22 | 22 |
} |
23 | 23 |
|
24 | 24 |
.get_data_stats <- function(object){ |
25 |
- stats <- lapply(seq_len(ncol(object@unlistData)), |
|
25 |
+ unlisted_object <- unlist(object, use.names = FALSE) |
|
26 |
+ stats <- lapply(seq_len(ncol(unlisted_object)), |
|
26 | 27 |
function(i){ |
27 |
- as.data.frame(as.list(summary(object@unlistData[,i]))) |
|
28 |
+ as.data.frame(as.list(summary(unlisted_object[,i]))) |
|
28 | 29 |
}) |
29 | 30 |
stats <- Reduce(rbind,stats) |
30 | 31 |
stats <- as.data.frame(t(stats), |
31 | 32 |
stringsAsFactors = FALSE) |
32 |
- colnames(stats) <- colnames(object@unlistData) |
|
33 |
+ colnames(stats) <- colnames(unlisted_object) |
|
33 | 34 |
rownames(stats) <- paste0("Data.",rownames(stats)) |
34 | 35 |
stats |
35 | 36 |
} |
... | ... |
@@ -73,7 +73,9 @@ NULL |
73 | 73 |
#' @importFrom Modstrings ModRNAString ModRNAStringSet combineIntoModstrings |
74 | 74 |
#' shortName fullName |
75 | 75 |
#' @importClassesFrom IRanges IntegerList CharacterList LogicalList IRanges |
76 |
-#' SplitDataFrameList |
|
76 |
+#' SplitDataFrameList PartitioningByEnd PartitioningByWidth |
|
77 |
+#' @importFrom IRanges IntegerList CharacterList LogicalList IRanges |
|
78 |
+#' SplitDataFrameList PartitioningByEnd PartitioningByWidth |
|
77 | 79 |
NULL |
78 | 80 |
|
79 | 81 |
# constants for annotation ----------------------------------------------------- |
... | ... |
@@ -95,20 +95,14 @@ NULL |
95 | 95 |
|
96 | 96 |
setClass("SequenceData", |
97 | 97 |
contains = c("VIRTUAL", "CompressedSplitDataFrameList"), |
98 |
- slots = c(ranges = "GRangesList", |
|
99 |
- sequences = "XStringSet", |
|
100 |
- sequencesType = "character", |
|
98 |
+ slots = c(sequencesType = "character", |
|
101 | 99 |
bamfiles = "BamFileList", |
102 |
- condition = "factor", |
|
103 |
- replicate = "factor", |
|
104 | 100 |
seqinfo = "Seqinfo", |
105 | 101 |
minQuality = "integer", |
102 |
+ unlistData = "SequenceDataFrame", |
|
106 | 103 |
unlistType = "character", |
107 | 104 |
dataDescription = "character"), |
108 |
- prototype = list(ranges = GRangesList(), |
|
109 |
- sequencesType = "RNAStringSet", |
|
110 |
- sequences = RNAStringSet(), |
|
111 |
- unlistType = "SequenceDataFrame")) |
|
105 |
+ prototype = list(sequencesType = "RNAStringSet")) |
|
112 | 106 |
|
113 | 107 |
setMethod( |
114 | 108 |
f = "initialize", |
... | ... |
@@ -131,22 +125,17 @@ sequenceDataClass <- function(dataType){ |
131 | 125 |
if(is(tmp,"try-error")){ |
132 | 126 |
stop("Class '",ans,"' not found: ",tmp) |
133 | 127 |
} |
134 |
- |
|
135 | 128 |
ans |
136 | 129 |
} |
137 | 130 |
|
138 |
-# for concat |
|
139 |
-#' @rdname RNAmodR-internals |
|
140 |
-setMethod("parallelSlotNames", "SequenceData", |
|
141 |
- function(x) c("ranges","sequences", callNextMethod()) |
|
142 |
-) |
|
143 |
- |
|
144 | 131 |
#' @rdname SequenceData-functions |
145 | 132 |
setMethod("show", "SequenceData", |
146 | 133 |
function(object){ |
147 | 134 |
k <- length(object) |
148 |
- data_nc <- ncol(object@unlistData) |
|
149 |
- ranges_mcols <- mcols(object@ranges@unlistData, use.names = FALSE) |
|
135 |
+ unlisted_object <- object@unlistData |
|
136 |
+ data_nc <- ncol(unlisted_object) |
|
137 |
+ unlisted_ranges <- unlist(ranges(object),use.names = FALSE) |
|
138 |
+ ranges_mcols <- mcols(unlisted_ranges, use.names = FALSE) |
|
150 | 139 |
ranges_nmc <- if (is.null(ranges_mcols)) 0L else ncol(ranges_mcols) |
151 | 140 |
cat(classNameForDisplay(object), " with ", k, " elements ", |
152 | 141 |
"containing ",sep = "") |
... | ... |
@@ -157,9 +146,9 @@ setMethod("show", "SequenceData", |
157 | 146 |
out_data <- NULL |
158 | 147 |
# data |
159 | 148 |
if (data_nc > 0) { |
160 |
- data_col_names <- colnames(object@unlistData) |
|
149 |
+ data_col_names <- colnames(unlisted_object) |
|
161 | 150 |
data_col_types <- |
162 |
- lapply(object@unlistData, function(x) { |
|
151 |
+ lapply(unlisted_object, function(x) { |
|
163 | 152 |
paste0("<", classNameForDisplay(x)[1],">") |
164 | 153 |
}) |
165 | 154 |
out_data <- |
... | ... |
@@ -168,21 +157,22 @@ setMethod("show", "SequenceData", |
168 | 157 |
} |
169 | 158 |
cat("- Data columns:\n") |
170 | 159 |
print(out_data, quote = FALSE, right = TRUE) |
171 |
- cat("- ",class(object@seqinfo), " object with ", |
|
172 |
- summary(object@seqinfo), ":\n", sep = "") |
|
160 |
+ cat("- ",class(seqinfo(object)), " object with ", |
|
161 |
+ summary(seqinfo(object)), ":\n", sep = "") |
|
173 | 162 |
} |
174 | 163 |
) |
175 | 164 |
# validity --------------------------------------------------------------------- |
176 | 165 |
|
177 | 166 |
.valid.SequenceData_elements <- function(x){ |
178 |
- nrow <- sum(unlist(width(ranges(x)))) |
|
179 |
- if(nrow != nrow(x@unlistData)){ |
|
167 |
+ unlisted_x <- unlist(x, use.names=FALSE) |
|
168 |
+ nrow <- sum(width(ranges(unlisted_x))) |
|
169 |
+ if(nrow != nrow(unlisted_x)){ |
|
180 | 170 |
return("row number of data does not match position covered by annotation.") |
181 | 171 |
} |
182 |
- if(nrow != sum(width(x@sequences))){ |
|
172 |
+ if(nrow != sum(width(sequences(x)))){ |
|
183 | 173 |
return("Length of sequences does not match position covered by annotation.") |
184 | 174 |
} |
185 |
- if(is.null(rownames(x@unlistData))){ |
|
175 |
+ if(is.null(rownames(unlisted_x))){ |
|
186 | 176 |
return("rownames of data is not set.") |
187 | 177 |
} else { |
188 | 178 |
seqs <- .seqs_rl_strand(ranges(x)) |
... | ... |
@@ -200,100 +190,16 @@ setMethod("show", "SequenceData", |
200 | 190 |
} |
201 | 191 |
S4Vectors::setValidity2(Class = "SequenceData", .valid.SequenceData) |
202 | 192 |
|
203 |
-# replacing -------------------------------------------------------------------- |
|
193 |
+# coercion --------------------------------------------------------------------- |
|
204 | 194 |
|
205 |
-#' @rdname RNAmodR-internals |
|
206 |
-setReplaceMethod("[", "SequenceData", |
|
207 |
- function(x, i, j, ..., value) { |
|
208 |
- if (length(list(...)) > 0L){ |
|
209 |
- stop("invalid replacement") |
|
210 |
- } |
|
211 |
- if(!missing(j)){ |
|
212 |
- stop("replacement of columns not supported") |
|
213 |
- } |
|
214 |
- if(!is(value,class(x))){ |
|
215 |
- stop("replacement 'value' must be of the same class than 'x'") |
|
216 |
- } |
|
217 |
- if (missing(i)){ |
|
218 |
- x <- value |
|
219 |
- } else { |
|
220 |
- if(length(i) != length(value)){ |
|
221 |
- warning("number of items to replace is not a multiple of replacement ", |
|
222 |
- "length") |
|
223 |
- value <- value[seq_along(i)] |
|
224 |
- } |
|
225 |
- x@ranges[i] <- ranges(value) |
|
226 |
- names(x@ranges)[i] <- names(ranges(value)) # must be set explicitly |
|
227 |
- x@sequences[i] <- sequences(value) |
|
228 |
- names(x@sequences)[i] <- names(sequences(value)) # must be set explicitly |
|
229 |
- # rownames needs to be savid since a replace removes them |
|
230 |
- rownames <- rownames(x) |
|
231 |
- rownames[i] <- rownames(value) |
|
232 |
- tmp <- callNextMethod(x = as(x,"SplitDataFrameList"), i = i, |
|
233 |
- value = as(value,"SplitDataFrameList")) |
|
234 |
- x@unlistData <- tmp@unlistData |
|
235 |
- x@partitioning <- tmp@partitioning |
|
236 |
- rownames(x) <- rownames |
|
237 |
- } |
|
238 |
- validObject(x) |
|
239 |
- return(x) |
|
240 |
- } |
|
241 |
-) |
|
242 |
- |
|
243 |
-#' @rdname RNAmodR-internals |
|
244 |
-setMethod("setListElement", "SequenceData", |
|
245 |
- function(x, i, value){ |
|
246 |
- if(!is(value,"SequenceDataFrame")){ |
|
247 |
- stop("invalid value. must be 'SequenceDataFrame'.") |
|
248 |
- } |
|
249 |
- i2 <- S4Vectors::normalizeDoubleBracketSubscript(i, x, allow.append = TRUE, |
|
250 |
- allow.nomatch = TRUE) |
|
251 |
- if(any(colnames(value) != colnames(unlist(x, use.names=FALSE)))){ |
|
252 |
- stop("'value' does not have matching colnames.") |
|
253 |
- } |
|
254 |
- x@ranges[[i2]] <- ranges(value) |
|
255 |
- x@sequences[[i2]] <- sequences(value) |
|
256 |
- # rownames needs to be savid since a replace removes them |
|
257 |
- rownames <- rownames(x) |
|
258 |
- rownames[[i2]] <- rownames(value) |
|
259 |
- tmp <- callNextMethod(x = as(x,"SplitDataFrameList"), i = i, |
|
260 |
- value = as(value,"DataFrame")) |
|
261 |
- x@unlistData <- tmp@unlistData |
|
262 |
- x@partitioning <- tmp@partitioning |
|
263 |
- rownames(x) <- rownames |
|
264 |
- validObject(x) |
|
265 |
- x |
|
266 |
- } |
|
267 |
-) |
|
268 |
- |
|
269 |
-# looping ---------------------------------------------------------------------- |
|
270 |
- |
|
271 |
-#' @importFrom IRanges PartitioningByEnd |
|
272 |
-lapply_SequenceData <- function(X, FUN, ...){ |
|
273 |
- FUN <- match.fun(FUN) |
|
274 |
- ans <- vector(mode = "list", length = length(X)) |
|
275 |
- X_partitioning <- IRanges::PartitioningByEnd(X) |
|
276 |
- X_elt_width <- width(X_partitioning) |
|
277 |
- empty_idx <- which(X_elt_width == 0L) |
|
278 |
- if (length(empty_idx) != 0L){ |
|
279 |
- ans[empty_idx] <- NULL |
|
280 |
- } |
|
281 |
- non_empty_idx <- which(X_elt_width != 0L) |
|
282 |
- if (length(non_empty_idx) == 0L){ |
|
283 |
- return(ans) |
|
284 |
- } |
|
285 |
- ans[non_empty_idx] <- |
|
286 |
- lapply(non_empty_idx, function(i){ FUN(getListElement(X,i), ...) }) |
|
287 |
- ans |
|
195 |
+.as_SplitDataFrameList <- function(from){ |
|
196 |
+ relist(as(unlist(from, use.names = FALSE),"DataFrame"), |
|
197 |
+ IRanges::PartitioningByWidth(from)) |
|
288 | 198 |
} |
199 |
+setAs("SequenceData", "SplitDataFrameList", .as_SplitDataFrameList) |
|
289 | 200 |
|
290 |
-setMethod("lapply", "SequenceData", |
|
291 |
- function(X, FUN, ...){ |
|
292 |
- ans <- lapply_SequenceData(X, FUN, ...) |
|
293 |
- names(ans) <- names(X) |
|
294 |
- ans |
|
295 |
- } |
|
296 |
-) |
|
201 |
+ |
|
202 |
+# internals -------------------------------------------------------------------- |
|
297 | 203 |
|
298 | 204 |
#' @importClassesFrom IRanges PartitioningByEnd |
299 | 205 |
#' @importFrom IRanges PartitioningByEnd |
... | ... |
@@ -312,44 +218,36 @@ setMethod("extractROWS", "SequenceData", |
312 | 218 |
idx_on_unlisted_x <- |
313 | 219 |
IRanges::IRanges(end = extractROWS(end(IRanges::PartitioningByEnd(x)), i), |
314 | 220 |
width = ans_eltNROWS) |
315 |
- ans_unlistData <- extractROWS(x@unlistData, idx_on_unlisted_x) |
|
316 |
- ans_partitioning <- new2("PartitioningByEnd", end = ans_breakpoints, |
|
317 |
- NAMES = extractROWS(names(x), i), check = FALSE) |
|
221 |
+ ans_unlistData <- extractROWS(unlist(x,use.names = FALSE), |
|
222 |
+ idx_on_unlisted_x) |
|
223 |
+ ans_partitioning <- new("PartitioningByEnd", end = ans_breakpoints, |
|
224 |
+ NAMES = extractROWS(names(x), i)) |
|
318 | 225 |
ans_elementMetadata <- extractROWS(x@elementMetadata, i) |
319 |
- ans_ranges <- extractROWS(x@ranges, i) |
|
320 |
- ans_sequences <- extractROWS(x@sequences, i) |
|
321 |
- initialize(x, ranges = ans_ranges, sequences = ans_sequences, |
|
322 |
- replicate = x@replicate, condition = x@condition, |
|
323 |
- bamfiles = x@bamfiles, seqinfo = x@seqinfo, |
|
226 |
+ initialize(x, bamfiles = x@bamfiles, seqinfo = x@seqinfo, |
|
324 | 227 |
minQuality = x@minQuality, unlistData = ans_unlistData, |
325 | 228 |
partitioning = ans_partitioning, |
326 | 229 |
elementMetadata = ans_elementMetadata) |
327 | 230 |
} |
328 | 231 |
) |
329 | 232 |
|
330 |
-#' @rdname RNAmodR-internals |
|
331 |
-#' @importFrom IRanges PartitioningByEnd |
|
332 |
-setMethod("getListElement", "SequenceData", |
|
333 |
- function(x, i, exact=TRUE){ |
|
334 |
- i2 <- normalizeDoubleBracketSubscript(i, x, exact = exact, |
|
335 |
- allow.NA = TRUE, |
|
336 |
- allow.nomatch = TRUE) |
|
337 |
- if (is.na(i2)){ |
|
338 |
- return(NULL) |
|
339 |
- } |
|
340 |
- unlisted_x <- unlist(x, use.names = FALSE) |
|
341 |
- x_partitioning <- IRanges::PartitioningByEnd(x) |
|
342 |
- window_start <- start(x_partitioning)[i2] |
|
343 |
- window_end <- end(x_partitioning)[i2] |
|
344 |
- new(x@unlistType, |
|
345 |
- S4Vectors:::Vector_window(unlisted_x, |
|
346 |
- start = window_start, |
|
347 |
- end = window_end), |
|
348 |
- ranges = x@ranges[[i2]], |
|
349 |
- sequence = x@sequences[[i2]], |
|
350 |
- condition = x@condition, |
|
351 |
- replicate = x@replicate) |
|
352 |
- } |
|
233 |
+setMethod("rownames", "SequenceData", |
|
234 |
+ function (x){ |
|
235 |
+ ans <- rownames(unlist(x,use.names = FALSE), do.NULL = TRUE) |
|
236 |
+ relist(ans,x) |
|
237 |
+ } |
|
238 |
+) |
|
239 |
+ |
|
240 |
+# methods inherited from List and CompressedList, contain a coercion step |
|
241 |
+# x <- as(x, "List", strict = FALSE) |
|
242 |
+# |
|
243 |
+# This does not keep the SequenceData object intact resulting in coercion |
|
244 |
+# to a CompressedSplitDataFrameList. |
|
245 |
+setMethod("[[", "SequenceData", |
|
246 |
+ function(x, i, j, ...) |
|
247 |
+ { |
|
248 |
+ METHOD <- selectMethod("[[", "List") |
|
249 |
+ METHOD(x, i, j, ...) |
|
250 |
+ } |
|
353 | 251 |
) |
354 | 252 |
|
355 | 253 |
|
... | ... |
@@ -359,7 +257,7 @@ setMethod("cbind", "SequenceData", |
359 | 257 |
function(...){ |
360 | 258 |
arg1 <- list(...)[[1L]] |
361 | 259 |
stop("'rbind' is not supported for ",class(arg1),".") |
362 |
- } |
|
260 |
+ } |
|
363 | 261 |
) |
364 | 262 |
setMethod("rbind", "SequenceData", |
365 | 263 |
function(...){ |
... | ... |
@@ -368,26 +266,6 @@ setMethod("rbind", "SequenceData", |
368 | 266 |
} |
369 | 267 |
) |
370 | 268 |
|
371 |
-# unlisting -------------------------------------------------------------------- |
|
372 |
- |
|
373 |
-setMethod("unlist", "SequenceData", |
|
374 |
- function(x, recursive=TRUE, use.names=TRUE){ |
|
375 |
- if (!isTRUEorFALSE(use.names)){ |
|
376 |
- stop("'use.names' must be TRUE or FALSE") |
|
377 |
- } |
|
378 |
- unlisted_x <- x@unlistData |
|
379 |
- if (use.names){ |
|
380 |
- unlisted_x <- S4Vectors:::set_unlisted_names(unlisted_x, x) |
|
381 |
- } |
|
382 |
- new(x@unlistType, |
|
383 |
- unlisted_x, |
|
384 |
- ranges = unlist(ranges(x), use.names = use.names), |
|
385 |
- sequence = unlist(sequences(x)), |
|
386 |
- condition = x@condition, |
|
387 |
- replicate = x@replicate) |
|
388 |
- } |
|
389 |
-) |
|
390 |
- |
|
391 | 269 |
# constructor ------------------------------------------------------------------ |
392 | 270 |
|
393 | 271 |
.quality_settings <- data.frame( |
... | ... |
@@ -538,24 +416,25 @@ setMethod("unlist", "SequenceData", |
538 | 416 |
any(names(ranges) != names(data))){ |
539 | 417 |
stop("") |
540 | 418 |
} |
541 |
- message("OK") |
|
542 | 419 |
############################################################################## |
543 | 420 |
# Create SequenceData object |
544 | 421 |
############################################################################## |
545 |
- new2(className, |
|
546 |
- ranges = ranges, |
|
547 |
- sequences = sequences, |
|
548 |
- bamfiles = bamfiles, |
|
549 |
- condition = condition, |
|
550 |
- replicate = replicate, |
|
551 |
- seqinfo = seqinfo, |
|
552 |
- minQuality = minQuality, |
|
553 |
- unlistData = unlist(data, use.names = FALSE), |
|
554 |
- partitioning = IRanges::PartitioningByEnd(data), |
|
555 |
- ...) |
|
422 |
+ ans <- new(className, |
|
423 |
+ bamfiles = bamfiles, |
|
424 |
+ seqinfo = seqinfo, |
|
425 |
+ minQuality = minQuality, |
|
426 |
+ unlistData = .SequenceDataFrame(gsub("SequenceData","",className), |
|
427 |
+ unlist(data, use.names = FALSE), |
|
428 |
+ unlist(ranges, use.names = FALSE), |
|
429 |
+ unlist(sequences, use.names = FALSE), |
|
430 |
+ replicate, |
|
431 |
+ condition), |
|
432 |
+ partitioning = IRanges::PartitioningByEnd(data), |
|
433 |
+ ...) |
|
434 |
+ message("OK") |
|
435 |
+ ans |
|
556 | 436 |
} |
557 | 437 |
|
558 |
- |
|
559 | 438 |
.SequenceData_settings <- data.frame( |
560 | 439 |
variable = c("max_depth", |
561 | 440 |
"minLength", |
... | ... |
@@ -603,10 +482,18 @@ setMethod("unlist", "SequenceData", |
603 | 482 |
# get annotation and sequence data |
604 | 483 |
annotation <- .norm_annotation(annotation, className) |
605 | 484 |
sequences <- .norm_sequences(sequences, className) |
485 |
+ seqinfo_missing <- missing(seqinfo) |
|
606 | 486 |
seqinfo <- .norm_seqnames(bamfiles, annotation, sequences, seqinfo, className) |
607 | 487 |
# load transcript data and sequence data |
608 | 488 |
grl <- .load_annotation(annotation) |
609 | 489 |
grl <- .subset_by_seqinfo(grl, seqinfo) |
490 |
+ if(length(grl) == 0L){ |
|
491 |
+ if(seqinfo_missing){ |
|
492 |
+ stop("No overlap between bamfiles and annotation.") |
|
493 |
+ } else { |
|
494 |
+ stop("No overlap between bamfiles, annotation and seqinfo.") |
|
495 |
+ } |
|
496 |
+ } |
|
610 | 497 |
sequences <- .load_transcript_sequences(sequences, grl) |
611 | 498 |
# create the class |
612 | 499 |
.SequenceData(className, bamfiles, grl, sequences, seqinfo, args) |
... | ... |
@@ -777,17 +664,29 @@ setMethod(f = "bamfiles", |
777 | 664 |
#' @export |
778 | 665 |
setMethod(f = "conditions", |
779 | 666 |
signature = signature(object = "SequenceData"), |
780 |
- definition = function(object){object@condition}) |
|
667 |
+ definition = function(object){conditions(unlist(object))}) |
|
781 | 668 |
#' @rdname SequenceData-functions |
782 | 669 |
#' @export |
783 |
-setMethod(f = "ranges", |
|
784 |
- signature = signature(x = "SequenceData"), |
|
785 |
- definition = function(x){x@ranges}) |
|
670 |
+setMethod( |
|
671 |
+ f = "ranges", |
|
672 |
+ signature = signature(x = "SequenceData"), |
|
673 |
+ definition = |
|
674 |
+ function(x){ |
|
675 |
+ partitioning <- IRanges::PartitioningByEnd(x) |
|
676 |
+ unlisted_ranges <- ranges(unlist(x)) |
|
677 |
+ ends <- cumsum(width(unlisted_ranges)) == cumsum(width(partitioning)) |
|
678 |
+ partitioning_relist <- IRanges::PartitioningByEnd(which(ends)) |
|
679 |
+ names(partitioning_relist) <- names(x) |
|
680 |
+ if(length(x) != length(partitioning_relist)){ |
|
681 |
+ stop("ranges could not be relisted.") |
|
682 |
+ } |
|
683 |
+ relist(unlisted_ranges, partitioning_relist) |
|
684 |
+ }) |
|
786 | 685 |
#' @rdname SequenceData-functions |
787 | 686 |
#' @export |
788 | 687 |
setMethod(f = "replicates", |
789 | 688 |
signature = signature(x = "SequenceData"), |
790 |
- definition = function(x){x@replicate}) |
|
689 |
+ definition = function(x){replicates(unlist(x))}) |
|
791 | 690 |
#' @rdname SequenceData-functions |
792 | 691 |
#' @export |
793 | 692 |
setMethod(f = "seqinfo", |
... | ... |
@@ -797,7 +696,7 @@ setMethod(f = "seqinfo", |
797 | 696 |
#' @export |
798 | 697 |
setMethod(f = "sequences", |
799 | 698 |
signature = signature(x = "SequenceData"), |
800 |
- definition = function(x){x@sequences}) |
|
699 |
+ definition = function(x){relist(sequences(unlist(x)),x)}) |
|
801 | 700 |
|
802 | 701 |
# dummy functions -------------------------------------------------------------- |
803 | 702 |
# this needs to be implemented by each subclass |
... | ... |
@@ -39,18 +39,31 @@ NULL |
39 | 39 |
#' sequences = sequences) |
40 | 40 |
NULL |
41 | 41 |
|
42 |
+ |
|
43 |
+#' @rdname CoverageSequenceData-class |
|
44 |
+#' @export |
|
45 |
+setClass(Class = "CoverageSequenceDataFrame", |
|
46 |
+ contains = "SequenceDataFrame") |
|
47 |
+#' @rdname CoverageSequenceData-class |
|
48 |
+#' @export |
|
49 |
+CoverageSequenceDataFrame <- function(df, ranges, sequence, replicate, |
|
50 |
+ condition){ |
|
51 |
+ .SequenceDataFrame("Coverage",df, ranges, sequence, replicate, condition) |
|
52 |
+} |
|
42 | 53 |
#' @rdname CoverageSequenceData-class |
43 | 54 |
#' @export |
44 | 55 |
setClass(Class = "CoverageSequenceData", |
45 | 56 |
contains = "SequenceData", |
46 |
- prototype = list(minQuality = 5L, |
|
57 |
+ slots = c(unlistData = "CoverageSequenceDataFrame"), |
|
58 |
+ prototype = list(unlistData = CoverageSequenceDataFrame(), |
|
59 |
+ unlistType = "CoverageSequenceDataFrame", |
|
60 |
+ minQuality = 5L, |
|
47 | 61 |
dataDescription = "Coverage data")) |
48 |
- |
|
49 | 62 |
#' @rdname CoverageSequenceData-class |
50 | 63 |
#' @export |
51 | 64 |
CoverageSequenceData <- function(bamfiles, annotation, sequences, seqinfo, ...){ |
52 |
- SequenceData("Coverage", bamfiles = bamfiles, annotation = annotation, |
|
53 |
- sequences = sequences, seqinfo = seqinfo, ...) |
|
65 |
+ .new_SequenceData("Coverage", bamfiles = bamfiles, annotation = annotation, |
|
66 |
+ sequences = sequences, seqinfo = seqinfo, ...) |
|
54 | 67 |
} |
55 | 68 |
|
56 | 69 |
# CoverageSequenceData --------------------------------------------------------- |
... | ... |
@@ -142,7 +155,7 @@ setMethod( |
142 | 155 |
# clean meta data columns |
143 | 156 |
seqdata <- .clean_mcols_coverage(seqdata) |
144 | 157 |
seqdata <- unlist(seqdata) |
145 |
- conditions <- unique(x@condition) |
|
158 |
+ conditions <- unique(conditions(x)) |
|
146 | 159 |
if("control" %in% conditions){ |
147 | 160 |
d <- seqdata[,stringr::str_detect(colnames(mcols(seqdata)),"control")] |
148 | 161 |
colnames(mcols(d)) <- gsub(".control","",colnames(mcols(d))) |
... | ... |
@@ -43,47 +43,83 @@ NULL |
43 | 43 |
#' sequences = sequences) |
44 | 44 |
NULL |
45 | 45 |
|
46 |
+#' @rdname EndSequenceData-class |
|
47 |
+#' @export |
|
48 |
+setClass(Class = "End5SequenceDataFrame", |
|
49 |
+ contains = "SequenceDataFrame") |
|
50 |
+#' @rdname EndSequenceData-class |
|
51 |
+#' @export |
|
52 |
+End5SequenceDataFrame <- function(df, ranges, sequence, replicate, |
|
53 |
+ condition){ |
|
54 |
+ .SequenceDataFrame("End5",df, ranges, sequence, replicate, condition) |
|
55 |
+} |
|
46 | 56 |
#' @rdname EndSequenceData-class |
47 | 57 |
#' @export |
48 | 58 |
setClass(Class = "End5SequenceData", |
49 | 59 |
contains = "SequenceData", |
50 |
- prototype = list(minQuality = 5L, |
|
60 |
+ slots = c(unlistData = "End5SequenceDataFrame"), |
|
61 |
+ prototype = list(unlistData = End5SequenceDataFrame(), |
|
62 |
+ unlistType = "End5SequenceDataFrame", |
|
63 |
+ minQuality = 5L, |
|
51 | 64 |
dataDescription = "5'-end position data")) |
52 | 65 |
|
66 |
+#' @rdname EndSequenceData-class |
|
67 |
+#' @export |
|
68 |
+setClass(Class = "End3SequenceDataFrame", |
|
69 |
+ contains = "SequenceDataFrame") |
|
70 |
+#' @rdname EndSequenceData-class |
|
71 |
+#' @export |
|
72 |
+End3SequenceDataFrame <- function(df, ranges, sequence, replicate, condition){ |
|
73 |
+ .SequenceDataFrame("End3",df, ranges, sequence, replicate, condition) |
|
74 |
+} |
|
53 | 75 |
#' @rdname EndSequenceData-class |
54 | 76 |
#' @export |
55 | 77 |
setClass(Class = "End3SequenceData", |
56 | 78 |
contains = "SequenceData", |
57 |
- prototype = list(minQuality = 5L, |
|
79 |
+ slots = c(unlistData = "End3SequenceDataFrame"), |
|
80 |
+ prototype = list(unlistData = End3SequenceDataFrame(), |
|
81 |
+ unlistType = "End3SequenceDataFrame", |
|
82 |
+ minQuality = 5L, |
|
58 | 83 |
dataDescription = "3'-end position data")) |
59 | 84 |
|
60 | 85 |
#' @rdname EndSequenceData-class |
61 | 86 |
#' @export |
87 |
+EndSequenceDataFrame <- function(df, ranges, sequence, replicate, condition){ |
|
88 |
+ .SequenceDataFrame("End",df, ranges, sequence, replicate, condition) |
|
89 |
+} |
|
90 |
+#' @rdname EndSequenceData-class |
|
91 |
+#' @export |
|
92 |
+setClass(Class = "EndSequenceDataFrame", |
|
93 |
+ contains = "SequenceDataFrame") |
|
94 |
+#' @rdname EndSequenceData-class |
|
95 |
+#' @export |
|
62 | 96 |
setClass(Class = "EndSequenceData", |
63 | 97 |
contains = "SequenceData", |
64 |
- prototype = list(minQuality = 5L, |
|
98 |
+ slots = c(unlistData = "EndSequenceDataFrame"), |
|
99 |
+ prototype = list(unlistData = EndSequenceDataFrame(), |
|
100 |
+ unlistType = "EndSequenceDataFrame", |
|
101 |
+ minQuality = 5L, |
|
65 | 102 |
dataDescription = "read end position data (5' and 3')")) |
66 | 103 |
|
67 | 104 |
#' @rdname EndSequenceData-class |
68 | 105 |
#' @export |
69 | 106 |
End5SequenceData <- function(bamfiles, annotation, sequences, seqinfo, ...){ |
70 |
- SequenceData("End5", bamfiles = bamfiles, annotation = annotation, |
|
71 |
- sequences = sequences, seqinfo = seqinfo, ...) |
|
107 |
+ .new_SequenceData("End5", bamfiles = bamfiles, annotation = annotation, |
|
108 |
+ sequences = sequences, seqinfo = seqinfo, ...) |
|
72 | 109 |
} |
73 | 110 |
#' @rdname EndSequenceData-class |
74 | 111 |
#' @export |
75 | 112 |
End3SequenceData <- function(bamfiles, annotation, sequences, seqinfo, ...){ |
76 |
- SequenceData("End3", bamfiles = bamfiles, annotation = annotation, |
|
77 |
- sequences = sequences, seqinfo = seqinfo, ...) |
|
113 |
+ .new_SequenceData("End3", bamfiles = bamfiles, annotation = annotation, |
|
114 |
+ sequences = sequences, seqinfo = seqinfo, ...) |
|
78 | 115 |
} |
79 | 116 |
#' @rdname EndSequenceData-class |
80 | 117 |
#' @export |
81 | 118 |
EndSequenceData <- function(bamfiles, annotation, sequences, seqinfo, ...){ |
82 |
- SequenceData("End", bamfiles = bamfiles, annotation = annotation, |
|
83 |
- sequences = sequences, seqinfo = seqinfo, ...) |
|
119 |
+ .new_SequenceData("End", bamfiles = bamfiles, annotation = annotation, |
|
120 |
+ sequences = sequences, seqinfo = seqinfo, ...) |
|
84 | 121 |
} |
85 | 122 |
|
86 |
- |
|
87 | 123 |
# End5SequenceData ------------------------------------------------------------------ |
88 | 124 |
|
89 | 125 |
.summarize_to_position_data <- function(data, hits, names, strands, type){ |
... | ... |
@@ -221,27 +257,28 @@ setMethod("getData", |
221 | 257 |
|
222 | 258 |
#' @importFrom matrixStats rowSds |
223 | 259 |
.aggregate_list_data_mean_sd <- function(x, condition){ |
224 |
- f <- .subset_to_condition(x@condition, condition) |
|
225 |
- df <- x@unlistData[f] |
|
226 |
- conditions <- unique(x@condition[f]) |
|
260 |
+ conditions <- conditions(x) |
|
261 |
+ f <- .subset_to_condition(conditions, condition) |
|
262 |
+ df <- as(unlist(x,use.names=FALSE),"DataFrame") |
|
263 |
+ conditions_u <- unique(conditions[f]) |
|
227 | 264 |
# set up some base values. replicates is here the same as the number of |
228 | 265 |
# columns, since a list per replicate is assumed |
229 | 266 |
# get means |
230 | 267 |
means <- IRanges::NumericList( |
231 |
- lapply(conditions, |
|
268 |
+ lapply(conditions_u, |
|
232 | 269 |
function(con){ |
233 |
- rowMeans(as.data.frame(df[,x@condition[f] == con]), |
|
270 |
+ rowMeans(as.data.frame(df[,conditions[f] == con]), |
|
234 | 271 |
na.rm = TRUE) |
235 | 272 |
})) |
236 |
- names(means) <- paste0("means.", conditions) |
|
273 |
+ names(means) <- paste0("means.", conditions_u) |
|
237 | 274 |
# get sds |
238 | 275 |
sds <- IRanges::NumericList( |
239 |
- lapply(conditions, |
|
276 |
+ lapply(conditions_u, |
|
240 | 277 |
function(con){ |
241 |
- matrixStats::rowSds(as.matrix(df[,x@condition[f] == con]), |
|
278 |
+ matrixStats::rowSds(as.matrix(df[,conditions[f] == con]), |
|
242 | 279 |
na.rm = TRUE) |
243 | 280 |
})) |
244 |
- names(sds) <- paste0("sds.", conditions) |
|
281 |
+ names(sds) <- paste0("sds.", conditions_u) |
|
245 | 282 |
# assemble data |
246 | 283 |
ans <- cbind(do.call(DataFrame, means), |
247 | 284 |
do.call(DataFrame, sds)) |
... | ... |
@@ -306,7 +343,7 @@ setMethod( |
306 | 343 |
# clean meta data columns |
307 | 344 |
seqdata <- .clean_mcols_end(seqdata) |
308 | 345 |
seqdata <- unlist(seqdata) |
309 |
- conditions <- unique(x@condition) |
|
346 |
+ conditions <- unique(conditions(x)) |
|
310 | 347 |
if("control" %in% conditions){ |
311 | 348 |
d <- seqdata[,stringr::str_detect(colnames(mcols(seqdata)),"control")] |
312 | 349 |
colnames(mcols(d)) <- gsub(".control","",colnames(mcols(d))) |
... | ... |
@@ -355,7 +392,7 @@ setMethod( |
355 | 392 |
# clean meta data columns |
356 | 393 |
seqdata <- .clean_mcols_end(seqdata) |
357 | 394 |
seqdata <- unlist(seqdata) |
358 |
- conditions <- unique(x@condition) |
|
395 |
+ conditions <- unique(conditions(x)) |
|
359 | 396 |
if("control" %in% conditions){ |
360 | 397 |
d <- seqdata[,stringr::str_detect(colnames(mcols(seqdata)),"control")] |
361 | 398 |
colnames(mcols(d)) <- gsub(".control","",colnames(mcols(d))) |
... | ... |
@@ -404,7 +441,7 @@ setMethod( |
404 | 441 |
# clean meta data columns |
405 | 442 |
seqdata <- .clean_mcols_end(seqdata) |
406 | 443 |
seqdata <- unlist(seqdata) |
407 |
- conditions <- unique(x@condition) |
|
444 |
+ conditions <- unique(conditions(x)) |
|
408 | 445 |
if("control" %in% conditions){ |
409 | 446 |
d <- seqdata[,stringr::str_detect(colnames(mcols(seqdata)),"control")] |
410 | 447 |
colnames(mcols(d)) <- gsub(".control","",colnames(mcols(d))) |
... | ... |
@@ -47,31 +47,57 @@ NULL |
47 | 47 |
#' } |
48 | 48 |
NULL |
49 | 49 |
|
50 |
+#' @rdname NormEndSequenceData-class |
|
51 |
+#' @export |
|
52 |
+setClass(Class = "NormEnd5SequenceDataFrame", |
|
53 |
+ contains = "SequenceDataFrame") |
|
54 |
+#' @rdname NormEndSequenceData-class |
|
55 |
+#' @export |
|
56 |
+NormEnd5SequenceDataFrame <- function(df, ranges, sequence, replicate, |
|
57 |
+ condition){ |
|
58 |
+ .SequenceDataFrame("NormEnd5",df, ranges, sequence, replicate, condition) |
|
59 |
+} |
|
50 | 60 |
#' @rdname NormEndSequenceData-class |
51 | 61 |
#' @export |
52 | 62 |
setClass(Class = "NormEnd5SequenceData", |
53 | 63 |
contains = "SequenceData", |
54 |
- prototype = list(minQuality = 5L, |
|
64 |
+ slots = c(unlistData = "NormEnd5SequenceDataFrame"), |
|
65 |
+ prototype = list(unlistData = NormEnd5SequenceDataFrame(), |
|
66 |
+ unlistType = "NormEnd5SequenceDataFrame", |
|
67 |
+ minQuality = 5L, |
|
55 | 68 |
dataDescription = "normalized 5'-end position data")) |
56 | 69 |
|
70 |
+#' @rdname NormEndSequenceData-class |
|
71 |
+#' @export |
|
72 |
+setClass(Class = "NormEnd3SequenceDataFrame", |
|
73 |
+ contains = "SequenceDataFrame") |
|
74 |
+#' @rdname NormEndSequenceData-class |
|
75 |
+#' @export |
|
76 |
+NormEnd3SequenceDataFrame <- function(df, ranges, sequence, replicate, |
|
77 |
+ condition){ |
|
78 |
+ .SequenceDataFrame("NormEnd3",df, ranges, sequence, replicate, condition) |
|
79 |
+} |
|
57 | 80 |
#' @rdname NormEndSequenceData-class |
58 | 81 |
#' @export |
59 | 82 |
setClass(Class = "NormEnd3SequenceData", |
60 | 83 |
contains = "SequenceData", |
61 |
- prototype = list(minQuality = 5L, |
|
84 |
+ slots = c(unlistData = "NormEnd3SequenceDataFrame"), |
|
85 |
+ prototype = list(unlistData = NormEnd3SequenceDataFrame(), |
|
86 |
+ unlistType = "NormEnd3SequenceDataFrame", |
|
87 |
+ minQuality = 5L, |
|
62 | 88 |
dataDescription = "normalized 3'-end position data")) |
63 | 89 |
|
64 | 90 |
#' @rdname NormEndSequenceData-class |
65 | 91 |
#' @export |
66 | 92 |
NormEnd5SequenceData <- function(bamfiles, annotation, sequences, seqinfo, ...){ |
67 |
- SequenceData("NormEnd5", bamfiles = bamfiles, annotation = annotation, |
|
68 |
- sequences = sequences, seqinfo = seqinfo, ...) |
|
93 |
+ .new_SequenceData("NormEnd5", bamfiles = bamfiles, annotation = annotation, |
|
94 |
+ sequences = sequences, seqinfo = seqinfo, ...) |
|
69 | 95 |
} |
70 | 96 |
#' @rdname NormEndSequenceData-class |
71 | 97 |
#' @export |
72 | 98 |
NormEnd3SequenceData <- function(bamfiles, annotation, sequences, seqinfo, ...){ |
73 |
- SequenceData("NormEnd3", bamfiles = bamfiles, annotation = annotation, |
|
74 |
- sequences = sequences, seqinfo = seqinfo, ...) |
|
99 |
+ .new_SequenceData("NormEnd3", bamfiles = bamfiles, annotation = annotation, |
|
100 |
+ sequences = sequences, seqinfo = seqinfo, ...) |
|
75 | 101 |
} |
76 | 102 |
|
77 | 103 |
# summary ---------------------------------------------------------------------- |
... | ... |
@@ -218,12 +244,13 @@ setMethod("getData", |
218 | 244 |
# - calculate sd per observation |
219 | 245 |
#' @importFrom matrixStats rowSds |
220 | 246 |
.aggregate_data_frame_mean_sd <- function(x, condition){ |
221 |
- f <- .subset_to_condition(x@condition, condition) |
|
222 |
- df <- x@unlistData[f] |
|
223 |
- conditions <- unique(x@condition[f]) |
|
224 |
- replicates <- x@replicate[f] |
|
247 |
+ conditions <- conditions(x) |
|
248 |
+ f <- .subset_to_condition(conditions, condition) |
|
249 |
+ df <- as(unlist(x,use.names=FALSE)[,f],"DataFrame") |
|
250 |
+ conditions_u <- unique(conditions[f]) |
|
251 |
+ replicates <- replicates(x)[f] |
|
225 | 252 |
# set up some base values |
226 |
- sample_width <- length(replicates[x@condition[f] == conditions[1] & |
|
253 |
+ sample_width <- length(replicates[conditions[f] == conditions_u[1] & |
|
227 | 254 |
replicates == unique(replicates)[1]]) |
228 | 255 |
colNames <- strsplit(colnames(df)[seq_len(sample_width)],"\\.") |
229 | 256 |
colNames <- IRanges::CharacterList(colNames)[as.list(lengths(colNames))] |
... | ... |
@@ -232,12 +259,12 @@ setMethod("getData", |
232 | 259 |
# get means |
233 | 260 |
means <- do.call( |
234 | 261 |
c, |
235 |
- lapply(conditions, |
|
262 |
+ lapply(conditions_u, |
|
236 | 263 |
function(con){ |
237 |
- ff <- x@condition[f] == con |
|
264 |
+ ff <- conditions[f] == con |
|
238 | 265 |
ncol <- ncol(df[,ff,drop = FALSE] |
239 | 266 |
[,replicates[ff] == unique(replicates[ff])[1], |
240 |
- drop = FALSE]) |
|
267 |
+ drop = FALSE]) |
|
241 | 268 |
seqAdd <- seq.int(from = 0, |
242 | 269 |
to = ncol(df[,ff,drop=FALSE]) - 1, |
243 | 270 |
by = sample_width) |
... | ... |
@@ -253,9 +280,9 @@ setMethod("getData", |
253 | 280 |
# get sds |
254 | 281 |
sds <- do.call( |
255 | 282 |
c, |
256 |
- lapply(conditions, |
|
283 |
+ lapply(conditions_u, |
|
257 | 284 |
function(con){ |
258 |
- ff <- x@condition[f] == con |
|
285 |
+ ff <- conditions[f] == con |
|
259 | 286 |
ncol <- ncol(df[,ff,drop = FALSE] |
260 | 287 |
[,replicates[ff] == unique(replicates[ff])[1], |
261 | 288 |
drop = FALSE]) |
... | ... |
@@ -266,7 +293,7 @@ setMethod("getData", |
266 | 293 |
lapply(seq_len(ncol), |
267 | 294 |
function(i){ |
268 | 295 |
unname(matrixStats::rowSds(as.matrix(df[,ff,drop=FALSE][,i + seqAdd,drop=FALSE]), |
269 |
- na.rm = TRUE)) |
|
296 |
+ na.rm = TRUE)) |
|
270 | 297 |
})) |
271 | 298 |
names(means) <- paste0("sds.", con, ".", colNames) |
272 | 299 |
means |
... | ... |
@@ -328,8 +355,8 @@ setMethod( |
328 | 355 |
# clean meta data columns |
329 | 356 |
seqdata <- .clean_mcols_normend(seqdata) |
330 | 357 |
seqdata <- unlist(seqdata) |
331 |
- conditions <- unique(x@condition) |
|
332 |
- if("control" %in% conditions){ |
|
358 |
+ conditions_u <- unique(conditions(x)) |
|
359 |
+ if("control" %in% conditions_u){ |
|
333 | 360 |
d <- seqdata[,stringr::str_detect(colnames(mcols(seqdata)),"control")] |
334 | 361 |
colnames(mcols(d)) <- gsub(".control","",colnames(mcols(d))) |
335 | 362 |
dt.control.tx <- Gviz::DataTrack( |
... | ... |
@@ -357,7 +384,7 @@ setMethod( |
357 | 384 |
tracks <- list("NormEnd5tx" = dt.control.tx, |
358 | 385 |
"NormEnd5ol" = dt.control.ol) |
359 | 386 |
} |
360 |
- if("treated" %in% conditions){ |
|
387 |
+ if("treated" %in% conditions_u){ |
|
361 | 388 |
d <- seqdata[,stringr::str_detect(colnames(mcols(seqdata)),"treated")] |
362 | 389 |
colnames(mcols(d)) <- gsub(".treated","",colnames(mcols(d))) |
363 | 390 |
dt.treated.tx <- Gviz::DataTrack( |
... | ... |
@@ -383,7 +410,7 @@ setMethod( |
383 | 410 |
tracks <- list("NormEnd5tx" = dt.treated.tx, |
384 | 411 |
"NormEnd5ol" = dt.treated.ol) |
385 | 412 |
} |
386 |
- if(length(conditions) == 2L){ |
|
413 |
+ if(length(conditions_u) == 2L){ |
|
387 | 414 |
tracks <- list("NormEnd5tx" = dt.control.tx, |
388 | 415 |
"NormEnd5ol" = dt.control.ol, |
389 | 416 |
"NormEnd5tx" = dt.treated.tx, |
... | ... |
@@ -405,8 +432,8 @@ setMethod( |
405 | 432 |
# clean meta data columns |
406 | 433 |
seqdata <- .clean_mcols_normend(seqdata) |
407 | 434 |
seqdata <- unlist(seqdata) |
408 |
- conditions <- unique(x@condition) |
|
409 |
- if("control" %in% conditions){ |
|
435 |
+ conditions_u <- unique(conditions(x)) |
|
436 |
+ if("control" %in% conditions_u){ |
|
410 | 437 |
d <- seqdata[,stringr::str_detect(colnames(mcols(seqdata)),"control")] |
411 | 438 |
colnames(mcols(d)) <- gsub(".control","",colnames(mcols(d))) |
412 | 439 |
dt.control.tx <- Gviz::DataTrack( |
... | ... |
@@ -434,7 +461,7 @@ setMethod( |
434 | 461 |
tracks <- list("NormEnd3tx" = dt.control.tx, |
435 | 462 |
"NormEnd3ol" = dt.control.ol) |
436 | 463 |
} |
437 |
- if("treated" %in% conditions){ |
|
464 |
+ if("treated" %in% conditions_u){ |
|
438 | 465 |
d <- seqdata[,stringr::str_detect(colnames(mcols(seqdata)),"treated")] |
439 | 466 |
colnames(mcols(d)) <- gsub(".treated","",colnames(mcols(d))) |
440 | 467 |
dt.treated.tx <- Gviz::DataTrack( |
... | ... |
@@ -460,7 +487,7 @@ setMethod( |
460 | 487 |
tracks <- list("NormEnd3tx" = dt.treated.tx, |
461 | 488 |
"NormEnd3ol" = dt.treated.ol) |
462 | 489 |
} |
463 |
- if(length(conditions) == 2L){ |
|
490 |
+ if(length(conditions_u) == 2L){ |
|
464 | 491 |
tracks <- list("NormEnd3tx" = dt.control.tx, |
465 | 492 |
"NormEnd3ol" = dt.control.ol, |
466 | 493 |
"NormEnd3tx" = dt.treated.tx, |
... | ... |
@@ -42,11 +42,23 @@ NULL |
42 | 42 |
#' sequences = sequences) |
43 | 43 |
NULL |
44 | 44 |
|
45 |
+#' @rdname PileupSequenceData-class |
|
46 |
+#' @export |
|
47 |
+setClass(Class = "PileupSequenceDataFrame", |
|
48 |
+ contains = "SequenceDataFrame") |
|
49 |
+#' @rdname PileupSequenceData-class |
|
50 |
+#' @export |
|
51 |
+PileupSequenceDataFrame <- function(df, ranges, sequence, replicate, condition){ |
|
52 |
+ .SequenceDataFrame("Pileup", df, ranges, sequence, replicate, condition) |
|
53 |
+} |
|
45 | 54 |
#' @rdname PileupSequenceData-class |
46 | 55 |
#' @export |
47 | 56 |
setClass(Class = "PileupSequenceData", |
48 | 57 |
contains = "SequenceData", |
49 |
- prototype = list(minQuality = 5L, |
|
58 |
+ slots = c(unlistData = "PileupSequenceDataFrame"), |
|
59 |
+ prototype = list(unlistData = PileupSequenceDataFrame(), |
|
60 |
+ unlistType = "PileupSequenceDataFrame", |
|
61 |
+ minQuality = 5L, |
|
50 | 62 |
dataDescription = "Pileup data")) |
51 | 63 |
|
52 | 64 |
#' @rdname PileupSequenceData-class |
... | ... |
@@ -166,18 +178,19 @@ setMethod("summary", |
166 | 178 |
# - calculate sd per observation |
167 | 179 |
#' @importFrom matrixStats rowSds |
168 | 180 |
.aggregate_data_frame_percentage_mean_sd <- function(x,condition){ |
169 |
- f <- .subset_to_condition(x@condition, condition) |
|
170 |
- df <- x@unlistData[f] |
|
171 |
- conditions <- unique(x@condition[f]) |
|
172 |
- replicates <- x@replicate[f] |
|
181 |
+ conditions <- conditions(x) |
|
182 |
+ f <- .subset_to_condition(conditions, condition) |
|
183 |
+ df <- as(unlist(x,use.names=FALSE)[,f],"DataFrame") |
|
184 |
+ conditions_u <- unique(conditions[f]) |
|
185 |
+ replicates <- replicates(x)[f] |
|
173 | 186 |
# set up some base values |
174 |
- sample_width <- length(replicates[x@condition[f] == conditions[1] & |
|
187 |
+ sample_width <- length(replicates[conditions[f] == conditions_u[1] & |
|
175 | 188 |
replicates == unique(replicates)[1]]) |
176 | 189 |
colNames <- strsplit(colnames(df)[seq_len(sample_width)],"\\.") |
177 | 190 |
colNames <- IRanges::CharacterList(colNames)[as.list(lengths(colNames))] |
178 | 191 |
# get percentage per replicate |
179 |
- for(con in conditions){ |
|
180 |
- ff <- x@condition[f] == con |
|
192 |
+ for(con in conditions_u){ |
|
193 |
+ ff <- conditions[f] == con |
|
181 | 194 |
for(i in unique(replicates[ff])){ |
182 | 195 |
df[,ff][,replicates[ff] == i] <- |
183 | 196 |
as.data.frame(df[,ff,drop = FALSE][,replicates[ff] == i,drop = FALSE]) / |
... | ... |
@@ -187,9 +200,9 @@ setMethod("summary", |
187 | 200 |
# get means |
188 | 201 |
means <- do.call( |
189 | 202 |
c, |
190 |
- lapply(conditions, |
|
203 |
+ lapply(conditions_u, |
|
191 | 204 |
function(con){ |
192 |
- ff <- x@condition[f] == con |
|
205 |
+ ff <- conditions[f] == con |
|
193 | 206 |
ncol <- ncol(df[,ff,drop = FALSE] |
194 | 207 |
[,replicates[ff] == unique(replicates[ff])[1], |
195 | 208 |
drop = FALSE]) |
... | ... |
@@ -208,9 +221,9 @@ setMethod("summary", |
208 | 221 |
# get sds |
209 | 222 |
sds <- do.call( |
210 | 223 |
c, |
211 |
- lapply(conditions, |
|
224 |
+ lapply(conditions_u, |
|
212 | 225 |
function(con){ |
213 |
- ff <- x@condition[f] == con |
|
226 |
+ ff <- conditions[f] == con |
|
214 | 227 |
ncol <- ncol(df[,ff,drop = FALSE] |
215 | 228 |
[,replicates[ff] == unique(replicates[ff])[1], |
216 | 229 |
drop = FALSE]) |
... | ... |
@@ -307,8 +320,8 @@ setMethod( |
307 | 320 |
# clean meta data columns |
308 | 321 |
seqdata <- .clean_mcols_pileup(seqdata, colour.bases) |
309 | 322 |
seqdata <- unlist(seqdata) |
310 |
- conditions <- unique(x@condition) |
|
311 |
- if("control" %in% conditions){ |
|
323 |
+ conditions_u <- unique(conditions(x)) |
|
324 |
+ if("control" %in% conditions_u){ |
|
312 | 325 |
d <- seqdata[,stringr::str_detect(colnames(mcols(seqdata)),"control")] |
313 | 326 |
colnames(mcols(d)) <- gsub("control.","",colnames(mcols(d))) |
314 | 327 |
dt.control <- Gviz::DataTrack(range = d, |
... | ... |
@@ -324,7 +337,7 @@ setMethod( |
324 | 337 |
Gviz::displayPars(dt.control) <- args |
325 | 338 |
track <- list("Pileup" = dt.control) |
326 | 339 |
} |
327 |
- if("treated" %in% conditions){ |
|
340 |
+ if("treated" %in% conditions_u){ |
|
328 | 341 |
d <- seqdata[,stringr::str_detect(colnames(mcols(seqdata)),"treated")] |
329 | 342 |
colnames(mcols(d)) <- gsub("treated.","",colnames(mcols(d))) |
330 | 343 |
dt.treated <- Gviz::DataTrack(range = d, |
... | ... |
@@ -340,7 +353,7 @@ setMethod( |
340 | 353 |
Gviz::displayPars(dt.treated) <- args |
341 | 354 |
track <- list("Pileup" = dt.treated) |
342 | 355 |
} |
343 |
- if(length(conditions) == 2L){ |
|
356 |
+ if(length(conditions_u) == 2L){ |
|
344 | 357 |
track <- list("Pileup" = dt.control, |
345 | 358 |
"Pileup" = dt.treated) |
346 | 359 |
} |
... | ... |
@@ -54,11 +54,24 @@ RNAMODR_PROT_SEQDATA_PLOT_DATA_COLOURS <- c(means = "#FBB4AE", |
54 | 54 |
#' } |
55 | 55 |
NULL |
56 | 56 |
|
57 |
+#' @rdname ProtectedEndSequenceData-class |
|
58 |
+#' @export |
|
59 |
+setClass(Class = "ProtectedEndSequenceDataFrame", |
|
60 |
+ contains = "SequenceDataFrame") |
|
61 |
+#' @rdname ProtectedEndSequenceData-class |
|
62 |
+#' @export |
|
63 |
+ProtectedEndSequenceDataFrame <- function(df, ranges, sequence, replicate, |
|
64 |
+ condition){ |
|
65 |
+ .SequenceDataFrame("ProtectedEnd",df, ranges, sequence, replicate, condition) |
|
66 |
+} |
|
57 | 67 |
#' @rdname ProtectedEndSequenceData-class |
58 | 68 |
#' @export |
59 | 69 |
setClass(Class = "ProtectedEndSequenceData", |
60 | 70 |
contains = "SequenceData", |
61 |
- prototype = list(minQuality = 5L, |
|
71 |
+ slots = c(unlistData = "ProtectedEndSequenceDataFrame"), |
|
72 |
+ prototype = list(unlistData = ProtectedEndSequenceDataFrame(), |
|
73 |
+ unlistType = "ProtectedEndSequenceDataFrame", |
|
74 |
+ minQuality = 5L, |
|
62 | 75 |
dataDescription = "protected end data")) |
63 | 76 |
|
64 | 77 |
#' @rdname ProtectedEndSequenceData-class |
... | ... |
@@ -120,7 +133,7 @@ setMethod( |
120 | 133 |
# clean meta data columns |
121 | 134 |
seqdata <- .clean_mcols_end(seqdata) |
122 | 135 |
seqdata <- unlist(seqdata) |
123 |
- conditions <- unique(x@condition) |
|
136 |
+ conditions <- unique(conditions(x)) |
|
124 | 137 |
if("control" %in% conditions){ |
125 | 138 |
d <- seqdata[,stringr::str_detect(colnames(mcols(seqdata)),"control")] |
126 | 139 |
colnames(mcols(d)) <- gsub(".control","",colnames(mcols(d))) |
... | ... |
@@ -85,15 +85,51 @@ NULL |
85 | 85 |
#' @rdname SequenceDataFrame-class |
86 | 86 |
#' @export |
87 | 87 |
setClass(Class = "SequenceDataFrame", |
88 |
- contains = c("DataFrame"), |
|
88 |
+ contains = c("VIRTUAL","DataFrame"), |
|
89 | 89 |
slots = c(ranges = "GRanges", |
90 | 90 |
sequence = "XString", |
91 | 91 |
condition = "factor", |
92 |
- replicate = "factor")) |
|
92 |
+ replicate = "factor"), |
|
93 |
+ prototype = list(ranges = GRanges(), |
|
94 |
+ sequence = RNAString(), |
|
95 |
+ condition = factor(), |
|
96 |
+ replicate = factor())) |
|
97 |
+ |
|
98 |
+setMethod("relistToClass", "SequenceDataFrame", |
|
99 |
+ function(x) gsub("DataFrame","Data",class(x)) |
|
100 |
+) |
|
93 | 101 |
|
94 | 102 |
# constructor ------------------------------------------------------------------ |
95 | 103 |
|
96 |
-.SequenceDataFrame <- function(df, ranges, sequence, replicate, condition){ |
|
104 |
+# class names must be compatible with this class name generation function |
|
105 |
+sequenceDataFrameClass <- function(dataType){ |
|
106 |
+ ans <- paste0(dataType,"SequenceDataFrame") |
|
107 |
+ tmp <- try(getClass(ans)) |
|
108 |
+ if(is(tmp,"try-error")){ |
|
109 |
+ stop("Class '",ans,"' not found: ",tmp) |
|
110 |
+ } |
|
111 |
+ ans |
|
112 |
+} |
|
113 |
+ |
|
114 |
+.SequenceDataFrame <- function(class, df, ranges, sequence, replicate, |
|
115 |
+ condition){ |
|
116 |
+ # defaults from function are strangly not set |
|
117 |
+ if(missing(df)){ |
|
118 |
+ df <- DataFrame() |
|
119 |
+ } |
|
120 |
+ if(missing(ranges)){ |
|
121 |
+ ranges <- GRanges() |
|
122 |
+ } |
|
123 |
+ if(missing(sequence)){ |
|
124 |
+ sequence <- RNAString() |
|
125 |
+ } |
|
126 |
+ if(missing(replicate)){ |
|
127 |
+ replicate <- factor() |
|
128 |
+ } |
|
129 |
+ if(missing(condition)){ |
|
130 |
+ condition <- factor() |
|
131 |
+ } |
|
132 |
+ # check inputs |
|
97 | 133 |
if(!is(df,"DataFrame")){ |
98 | 134 |
stop("Invalid data object: ", class(df), " found, DataFrame expected.") |
99 | 135 |
} |
... | ... |
@@ -108,22 +144,16 @@ setClass(Class = "SequenceDataFrame", |
108 | 144 |
if(!is(sequence,"XString")){ |
109 | 145 |
stop("Invalid data object: ", class(sequence), " found, XString expected.") |
110 | 146 |
} |
111 |
- new2("SequenceDataFrame", |
|
112 |
- ranges = ranges, |
|
113 |
- sequence = sequence, |
|
114 |
- condition = condition, |
|
115 |
- replicate = replicate, |
|
116 |
- rownames = df@rownames, |
|
117 |
- nrows = df@nrows, |
|
118 |
- listData = df@listData, |
|
119 |
- elementMetadata = df@elementMetadata, |
|
120 |
- metadata = df@metadata) |
|
121 |
-} |
|
122 |
- |
|
123 |
-#' @rdname SequenceDataFrame-class |
|
124 |
-#' @export |
|
125 |
-SequenceDataFrame <- function(df, ranges, sequence, replicate, condition){ |
|
126 |
- .SequenceDataFrame(df, ranges, sequence, replicate, condition) |
|
147 |
+ new(paste0(class,"SequenceDataFrame"), |
|
148 |
+ ranges = ranges, |
|
149 |
+ sequence = sequence, |
|
150 |
+ condition = condition, |
|
151 |
+ replicate = replicate, |
|
152 |
+ rownames = df@rownames, |
|
153 |
+ nrows = df@nrows, |
|
154 |
+ listData = df@listData, |
|
155 |
+ elementMetadata = df@elementMetadata, |
|
156 |
+ metadata = df@metadata) |
|
127 | 157 |
} |
128 | 158 |
|
129 | 159 |
.valid_SequenceDataFrame <- function(x){ |
... | ... |
@@ -151,14 +181,6 @@ setMethod("show", "SequenceDataFrame", |
151 | 181 |
show(object@sequence) |
152 | 182 |
}) |
153 | 183 |
|
154 |
-# relisting -------------------------------------------------------------------- |
|
155 |
- |
|
156 |
-setMethod("relist", c(flesh = "SequenceDataFrame", skeleton = "ANY"), |
|
157 |
- function(flesh, skeleton){ |
|
158 |
- stop("Relisting is not supported for 'SequenceDataFrame'") |
|
159 |
- } |
|
160 |
-) |
|
161 |
- |
|
162 | 184 |
# accessors -------------------------------------------------------------------- |
163 | 185 |
|
164 | 186 |
#' @rdname SequenceData-functions |
... | ... |
@@ -187,58 +209,99 @@ setMethod( |
187 | 209 |
signature = signature(object = "SequenceDataFrame"), |
188 | 210 |
definition = function(object){object@condition}) |
189 | 211 |
|
212 |
+# internals -------------------------------------------------------------------- |
|
213 |
+ |
|
214 |
+#' @importClassesFrom IRanges PartitioningByEnd |
|
215 |
+#' @importFrom IRanges PartitioningByEnd |
|
216 |
+setMethod( |
|
217 |
+ "extractROWS", "SequenceDataFrame", |
|
218 |
+ function(x, i){ |
|
219 |
+ i <- normalizeSingleBracketSubscript(i, x, exact = FALSE, |
|
220 |
+ allow.NAs = TRUE, as.NSBS = TRUE) |
|
221 |
+ start <- which(start(PartitioningByWidth(ranges(x))) == i@subscript[[1L]]) |
|
222 |
+ end <- which(end(PartitioningByWidth(ranges(x))) == i@subscript[[2L]]) |
|
223 |
+ slot(x, "listData", check = FALSE) <- lapply(as.list(x), extractROWS, i) |
|
224 |
+ slot(x, "nrows", check = FALSE) <- length(i) |
|
225 |
+ slot(x, "ranges", check = FALSE) <- extractROWS(ranges(x), |
|
226 |
+ seq.int(start,end)) |
|
227 |
+ slot(x, "sequence", check = FALSE) <- extractROWS(sequences(x), i) |
|
228 |
+ if (!is.null(rownames(x))) { |
|
229 |
+ slot(x, "rownames", check = FALSE) <- extractROWS(rownames(x), i) |
|
230 |
+ } |
|
231 |
+ validObject(x) |
|
232 |
+ x |
|
233 |
+ } |
|
234 |
+) |
|
235 |
+ |
|
236 |
+setMethod( |
|
237 |
+ "bindROWS", "SequenceDataFrame", |
|
238 |
+ function (x, objects = list(), use.names = TRUE, ignore.mcols = FALSE, |
|
239 |
+ check = TRUE) |
|
240 |
+ { |
|
241 |
+ objects <- S4Vectors:::prepare_objects_to_bind(x, objects) |
|
242 |
+ all_objects <- c(list(x), objects) |
|
243 |
+ ans_ranges <- unlist(GenomicRanges::GRangesList(lapply(all_objects,ranges))) |
|
244 |
+ ans_sequence <- do.call(xscat,lapply(all_objects,sequences)) |
|
245 |
+ BiocGenerics:::replaceSlots(callNextMethod(), |
|
246 |
+ ranges = ans_ranges, |
|
247 |
+ sequence = ans_sequence, |
|
248 |
+ check = check) |
|
249 |
+ } |
|
250 |
+) |
|
251 |
+ |
|
190 | 252 |
#' @importFrom stats setNames |
191 | 253 |
#' @rdname SequenceDataFrame-class |
192 | 254 |
#' @export |
193 |
-setMethod("[", "SequenceDataFrame", |
|
194 |
- function(x, i, j, ..., drop = TRUE){ |
|
195 |
- if (!isTRUEorFALSE(drop)){ |
|
196 |
- stop("'drop' must be TRUE or FALSE") |
|
197 |
- } |
|
198 |
- if (length(list(...)) > 0L){ |
|
199 |
- warning("parameters in '...' not supported") |
|
200 |
- } |
|
201 |
- ## We do list-style subsetting when [ was called with no ','. |
|
202 |
- ## NOTE: matrix-style subsetting by logical matrix not supported. |
|
203 |
- list_style_subsetting <- (nargs() - !missing(drop)) < 3L |
|
204 |
- if (list_style_subsetting || !missing(j)) { |
|
205 |
- if (list_style_subsetting) { |
|
206 |
- if (!missing(drop)) |
|
207 |
- warning("'drop' argument ignored by list-style subsetting") |
|
208 |
- if (missing(i)) |
|
209 |
- return(x) |
|
210 |
- j <- i |
|
211 |
- } |
|
212 |
- if (!is(j, "IntegerRanges")) { |
|
213 |
- xstub <- stats::setNames(seq_along(x), names(x)) |
|
214 |
- j <- normalizeSingleBracketSubscript(j, xstub) |
|
215 |
- } |
|
216 |
- x <- initialize(x, as(x,"DataFrame")[, j, drop = FALSE], |
|
217 |
- ranges = x@ranges, |
|
218 |
- sequence = x@sequence, |
|
219 |
- replicate = x@replicate[j], |
|
220 |
- condition = x@condition[j]) |
|
221 |
- if (anyDuplicated(names(x))){ |
|
222 |
- names(x) <- make.unique(names(x)) |
|
223 |
- } |
|
224 |
- if (list_style_subsetting){ |
|
225 |
- return(x) |
|
226 |
- } |
|
227 |
- } |
|
228 |
- if (!missing(i)){ |
|
229 |
- x <- extractROWS(x, i) |
|
230 |
- } else { |
|
231 |
- return(x) # early exit if subset is column-only |
|
232 |
- } |
|
233 |
- if (missing(drop)){ |
|
234 |
- drop <- TRUE |
|
235 |
- } |
|
236 |
- if (drop) { |
|
237 |
- ## one row left |
|
238 |
- if (nrow(x) == 1L){ |
|
239 |
- return(as(x, "list")) |
|
240 |
- } |
|
241 |
- } |
|
242 |
- as(x,"DataFrame") |
|
243 |
- } |
|
255 |
+setMethod( |
|
256 |
+ "[", "SequenceDataFrame", |
|
257 |
+ function(x, i, j, ..., drop = TRUE){ |
|
258 |
+ if (!isTRUEorFALSE(drop)){ |
|
259 |
+ stop("'drop' must be TRUE or FALSE") |
|
260 |
+ } |
|
261 |
+ if (length(list(...)) > 0L){ |
|
262 |
+ warning("parameters in '...' not supported") |
|
263 |
+ } |
|
264 |
+ ## We do list-style subsetting when [ was called with no ','. |
|
265 |
+ ## NOTE: matrix-style subsetting by logical matrix not supported. |
|
266 |
+ list_style_subsetting <- (nargs() - !missing(drop)) < 3L |
|
267 |
+ if (list_style_subsetting || !missing(j)) { |
|
268 |
+ if (list_style_subsetting) { |
|
269 |
+ if (!missing(drop)) |
|
270 |
+ warning("'drop' argument ignored by list-style subsetting") |
|
271 |
+ if (missing(i)) |
|
272 |
+ return(x) |
|
273 |
+ j <- i |
|
274 |
+ } |
|
275 |
+ if (!is(j, "IntegerRanges")) { |
|
276 |
+ xstub <- stats::setNames(seq_along(x), names(x)) |
|
277 |
+ j <- normalizeSingleBracketSubscript(j, xstub) |
|
278 |
+ } |
|
279 |
+ x <- initialize(x, as(x,"DataFrame")[, j, drop = FALSE], |
|
280 |
+ ranges = x@ranges, |
|
281 |
+ sequence = x@sequence, |
|
282 |
+ replicate = x@replicate[j], |
|
283 |
+ condition = x@condition[j]) |
|
284 |
+ if (anyDuplicated(names(x))){ |
|
285 |
+ names(x) <- make.unique(names(x)) |
|
286 |
+ } |
|
287 |
+ if (list_style_subsetting){ |
|
288 |
+ return(x) |
|
289 |
+ } |
|
290 |
+ } |
|
291 |
+ if (!missing(i)){ |
|
292 |
+ x <- extractROWS(as(x,"DataFrame"), i) |
|
293 |
+ } else { |
|
294 |
+ return(x) # early exit if subset is column-only |
|
295 |
+ } |
|
296 |
+ if (missing(drop)){ |
|
297 |
+ drop <- TRUE |
|
298 |
+ } |
|
299 |
+ if (drop) { |
|
300 |
+ ## one row left |
|
301 |
+ if (nrow(x) == 1L){ |
|
302 |
+ return(as(x, "list")) |
|
303 |
+ } |
|
304 |
+ } |
|
305 |
+ x |
|
306 |
+ } |
|
244 | 307 |
) |
... | ... |
@@ -47,8 +47,8 @@ setMethod("show", "SequenceDataSet", |
47 | 47 |
"\n", sep = "") |
48 | 48 |
if (!is.null(names(object))) |
49 | 49 |
cat(S4Vectors:::labeledLine("names", names(object))) |
50 |
- ranges_mcols <- mcols(object@listData[[1]]@ranges@unlistData, |
|
51 |
- use.names = FALSE) |
|
50 |
+ unlisted_ranges <- unlist(ranges(object[[1]]),use.names = FALSE) |
|
51 |
+ ranges_mcols <- mcols(unlisted_ranges, use.names = FALSE) |
|
52 | 52 |
nhead <- S4Vectors::get_showHeadLines() |
53 | 53 |
ntail <- S4Vectors::get_showTailLines() |
54 | 54 |
nc <- if (is.null(ranges_mcols)) 0L else ncol(ranges_mcols) |
... | ... |
@@ -182,3 +182,13 @@ NULL |
182 | 182 |
} |
183 | 183 |
f |
184 | 184 |
} |
185 |
+ |
|
186 |
+# partitioning object ---------------------------------------------------------- |
|
187 |
+ |
|
188 |
+.seqs_partitioning <- function(partitioning){ |
|
189 |
+ from <- rep.int(1,length(partitioning)) |
|
190 |
+ to <- width(partitioning) |
|
191 |
+ names(from) <- names(partitioning) |
|
192 |
+ names(to) <- names(partitioning) |
|
193 |
+ .seqs_l_by(from,to) |
|
194 |
+} |
... | ... |
@@ -4,11 +4,15 @@ |
4 | 4 |
\name{CoverageSequenceData-class} |
5 | 5 |
\alias{CoverageSequenceData-class} |
6 | 6 |
\alias{CoverageSequenceData} |
7 |
+\alias{CoverageSequenceDataFrame-class} |
|
8 |
+\alias{CoverageSequenceDataFrame} |
|
7 | 9 |
\alias{getData,CoverageSequenceData,BamFileList,GRangesList,XStringSet,ScanBamParam-method} |
8 | 10 |
\alias{aggregateData,CoverageSequenceData-method} |
9 | 11 |
\alias{getDataTrack,CoverageSequenceData-method} |
10 | 12 |
\title{CoverageSequenceData} |
11 | 13 |
\usage{ |
14 |
+CoverageSequenceDataFrame(df, ranges, sequence, replicate, condition) |
|
15 |
+ |
|
12 | 16 |
CoverageSequenceData(bamfiles, annotation, sequences, seqinfo, ...) |
13 | 17 |
|
14 | 18 |
|
... | ... |
@@ -21,14 +25,14 @@ CoverageSequenceData(bamfiles, annotation, sequences, seqinfo, ...) |
21 | 25 |
\S4method{getDataTrack}{CoverageSequenceData}(x, name, ...) |
22 | 26 |
} |
23 | 27 |
\arguments{ |
28 |
+\item{condition}{For \code{\link{aggregate}}: condition for which the data |
|
29 |
+should be aggregated.} |
|
30 |
+ |
|
24 | 31 |
\item{bamfiles, annotation, seqinfo, grl, sequences, param, args, ...}{See |
25 | 32 |
\code{\link[=SequenceData-class]{SequenceData}}} |
26 | 33 |
|
27 | 34 |
\item{x}{a \code{CoverageSequenceData}} |
28 | 35 |
|
29 |
-\item{condition}{For \code{\link{aggregate}}: condition for which the data |
|
30 |
-should be aggregated.} |
|
31 |
- |
|
32 | 36 |
\item{name}{For \code{getDataTrack}: a valid transcript name. Must be a name |
33 | 37 |
of \code{ranges(x)}} |
34 | 38 |
} |
... | ... |
@@ -6,8 +6,14 @@ |
6 | 6 |
\alias{End5SequenceData} |
7 | 7 |
\alias{End3SequenceData} |
8 | 8 |
\alias{EndSequenceData} |
9 |
+\alias{End5SequenceDataFrame-class} |
|
10 |
+\alias{End5SequenceDataFrame} |
|
9 | 11 |
\alias{End5SequenceData-class} |
12 |
+\alias{End3SequenceDataFrame-class} |
|
13 |
+\alias{End3SequenceDataFrame} |
|
10 | 14 |
\alias{End3SequenceData-class} |
15 |
+\alias{EndSequenceDataFrame} |
|
16 |
+\alias{EndSequenceDataFrame-class} |
|
11 | 17 |
\alias{getData,End5SequenceData,BamFileList,GRangesList,XStringSet,ScanBamParam-method} |
12 | 18 |
\alias{getData,End3SequenceData,BamFileList,GRangesList,XStringSet,ScanBamParam-method} |
13 | 19 |
\alias{getData,EndSequenceData,BamFileList,GRangesList,XStringSet,ScanBamParam-method} |
... | ... |
@@ -19,6 +25,12 @@ |
19 | 25 |
\alias{getDataTrack,End3SequenceData-method} |
20 | 26 |
\title{End5SequenceData/End3SequenceData/EndSequenceData} |
21 | 27 |
\usage{ |
28 |
+End5SequenceDataFrame(df, ranges, sequence, replicate, condition) |
|
29 |
+ |
|
30 |
+End3SequenceDataFrame(df, ranges, sequence, replicate, condition) |
|
31 |
+ |
|
32 |
+EndSequenceDataFrame(df, ranges, sequence, replicate, condition) |
|
33 |
+ |
|
22 | 34 |
End5SequenceData(bamfiles, annotation, sequences, seqinfo, ...) |
23 | 35 |
|
24 | 36 |
End3SequenceData(bamfiles, annotation, sequences, seqinfo, ...) |
... | ... |
@@ -53,6 +65,9 @@ EndSequenceData(bamfiles, annotation, sequences, seqinfo, ...) |
53 | 65 |
\S4method{getDataTrack}{End3SequenceData}(x, name, ...) |
54 | 66 |
} |
55 | 67 |
\arguments{ |
68 |
+\item{condition}{For \code{\link{aggregate}}: condition for which the data |
|
69 |
+should be aggregated.} |
|
70 |
+ |
|
56 | 71 |
\item{bamfiles, annotation, seqinfo, grl, sequences, param, args, ...}{See |
57 | 72 |
\code{\link[=SequenceData-class]{SequenceData}} and |
58 | 73 |
\code{\link[=SequenceData-functions]{SequenceData-functions}}} |
... | ... |
@@ -60,9 +75,6 @@ EndSequenceData(bamfiles, annotation, sequences, seqinfo, ...) |
60 | 75 |
\item{x}{a \code{End5SequenceData}, \code{End3SequenceData} or |
61 | 76 |
\code{EndSequenceData} object} |
62 | 77 |
|
63 |
-\item{condition}{For \code{\link{aggregate}}: condition for which the data |
|
64 |
-should be aggregated.} |
|
65 |
- |
|
66 | 78 |
\item{name}{For \code{\link[=plotDataByCoord]{getDataTrack}}: a valid |
67 | 79 |
transcript name. Must be a name of \code{ranges(x).}} |
68 | 80 |
} |
... | ... |
@@ -5,7 +5,11 @@ |
5 | 5 |
\alias{NormEndSequenceData-class} |
6 | 6 |
\alias{NormEnd5SequenceData} |
7 | 7 |
\alias{NormEnd3SequenceData} |
8 |
+\alias{NormEnd5SequenceDataFrame-class} |
|
9 |
+\alias{NormEnd5SequenceDataFrame} |
|
8 | 10 |
\alias{NormEnd5SequenceData-class} |
11 |
+\alias{NormEnd3SequenceDataFrame-class} |
|
12 |
+\alias{NormEnd3SequenceDataFrame} |
|
9 | 13 |
\alias{NormEnd3SequenceData-class} |
10 | 14 |
\alias{getData,NormEnd5SequenceData,BamFileList,GRangesList,XStringSet,ScanBamParam-method} |
11 | 15 |
\alias{getData,NormEnd3SequenceData,BamFileList,GRangesList,XStringSet,ScanBamParam-method} |
... | ... |
@@ -15,6 +19,10 @@ |
15 | 19 |
\alias{getDataTrack,NormEnd3SequenceData-method} |
16 | 20 |
\title{NormEnd5SequenceData/NormEnd3SequenceData} |
17 | 21 |
\usage{ |
22 |
+NormEnd5SequenceDataFrame(df, ranges, sequence, replicate, condition) |
|
23 |
+ |
|
24 |
+NormEnd3SequenceDataFrame(df, ranges, sequence, replicate, condition) |
|
25 |
+ |
|
18 | 26 |
NormEnd5SequenceData(bamfiles, annotation, sequences, seqinfo, ...) |
19 | 27 |
|
20 | 28 |
NormEnd3SequenceData(bamfiles, annotation, sequences, seqinfo, ...) |
... | ... |
@@ -38,15 +46,15 @@ NormEnd3SequenceData(bamfiles, annotation, sequences, seqinfo, ...) |
38 | 46 |
\S4method{getDataTrack}{NormEnd3SequenceData}(x, name, ...) |
39 | 47 |
} |
40 | 48 |
\arguments{ |
49 |
+\item{condition}{For \code{\link{aggregate}}: condition for which the data |
|
50 |
+should be aggregated.} |
|
51 |
+ |
|
41 | 52 |
\item{bamfiles, annotation, seqinfo, grl, sequences, param, args, ...}{See |
42 | 53 |
\code{\link[=SequenceData-class]{SequenceData}} and |
43 | 54 |
\code{\link[=SequenceData-functions]{SequenceData-functions}}} |
44 | 55 |
|
45 | 56 |
\item{x}{a \code{CoverageSequenceData}} |
46 | 57 |
|
47 |
-\item{condition}{For \code{\link{aggregate}}: condition for which the data |
|
48 |
-should be aggregated.} |
|
49 |
- |
|
50 | 58 |
\item{name}{For \code{\link[=plotDataByCoord]{getDataTrack}}: a valid |
51 | 59 |
transcript name. Must be a name of \code{ranges(x)}} |
52 | 60 |
} |
... | ... |
@@ -4,6 +4,8 @@ |
4 | 4 |
\name{PileupSequenceData-class} |
5 | 5 |
\alias{PileupSequenceData-class} |
6 | 6 |
\alias{PileupSequenceData} |
7 |
+\alias{PileupSequenceDataFrame-class} |
|
8 |
+\alias{PileupSequenceDataFrame} |
|
7 | 9 |
\alias{getData,PileupSequenceData,BamFileList,GRangesList,XStringSet,ScanBamParam-method} |
8 | 10 |
\alias{aggregateData,PileupSequenceData-method} |
9 | 11 |
\alias{getDataTrack,PileupSequenceData-method} |
... | ... |
@@ -11,6 +13,8 @@ |
11 | 13 |
\alias{pileupToCoverage,PileupSequenceData-method} |
12 | 14 |
\title{PileupSequenceData} |
13 | 15 |
\usage{ |
16 |
+PileupSequenceDataFrame(df, ranges, sequence, replicate, condition) |
|
17 |
+ |
|
14 | 18 |
PileupSequenceData(bamfiles, annotation, sequences, seqinfo, ...) |
15 | 19 |
|
16 | 20 |
|
... | ... |
@@ -27,15 +31,15 @@ pileupToCoverage(x) |
27 | 31 |
\S4method{pileupToCoverage}{PileupSequenceData}(x) |
28 | 32 |
} |
29 | 33 |
\arguments{ |
34 |
+\item{condition}{For \code{\link{aggregate}}: condition for which the data |
|
35 |
+should be aggregated.} |
|
36 |
+ |
|
30 | 37 |
\item{bamfiles, annotation, seqinfo, grl, sequences, param, args, ...}{See |
31 | 38 |
\code{\link[=SequenceData-class]{SequenceData}} and |
32 | 39 |
\code{\link[=SequenceData-functions]{SequenceData-functions}}} |
33 | 40 |
|
34 | 41 |
\item{x}{a \code{PileupSequenceData}} |
35 | 42 |
|
36 |
-\item{condition}{For \code{\link{aggregate}}: condition for which the data |
|
37 |
-should be aggregated.} |
|
38 |
- |
|
39 | 43 |
\item{name}{For \code{\link[=plotDataByCoord]{getDataTrack}}: a valid |
40 | 44 |
transcript name. Must be a name of \code{ranges(x)}} |
41 | 45 |
} |
... | ... |
@@ -4,11 +4,15 @@ |
4 | 4 |
\name{ProtectedEndSequenceData-class} |
5 | 5 |
\alias{ProtectedEndSequenceData-class} |
6 | 6 |
\alias{ProtectedEndSequenceData} |
7 |
+\alias{ProtectedEndSequenceDataFrame-class} |
|
8 |
+\alias{ProtectedEndSequenceDataFrame} |
|
7 | 9 |
\alias{getData,ProtectedEndSequenceData,BamFileList,GRangesList,XStringSet,ScanBamParam-method} |
8 | 10 |
\alias{aggregateData,ProtectedEndSequenceData-method} |
9 | 11 |
\alias{getDataTrack,ProtectedEndSequenceData-method} |
10 | 12 |
\title{ProtectedEndSequenceData} |
11 | 13 |
\usage{ |
14 |
+ProtectedEndSequenceDataFrame(df, ranges, sequence, replicate, condition) |
|
15 |
+ |
|
12 | 16 |
ProtectedEndSequenceData(bamfiles, annotation, sequences, seqinfo, ...) |
13 | 17 |
|
14 | 18 |
|
... | ... |
@@ -21,15 +25,15 @@ ProtectedEndSequenceData(bamfiles, annotation, sequences, seqinfo, ...) |
21 | 25 |
\S4method{getDataTrack}{ProtectedEndSequenceData}(x, name, ...) |
22 | 26 |
} |
23 | 27 |
\arguments{ |
28 |
+\item{condition}{For \code{\link{aggregate}}: condition for which the data |
|
29 |
+should be aggregated.} |
|
30 |
+ |
|
24 | 31 |
\item{bamfiles, annotation, seqinfo, grl, sequences, param, args, ...}{See |
25 | 32 |
\code{\link[=SequenceData-class]{SequenceData}} and |
26 | 33 |
\code{\link[=SequenceData-functions]{SequenceData-functions}}} |
27 | 34 |
|
28 | 35 |
\item{x}{a \code{ProtectedEndSequenceData}} |
29 | 36 |
|
30 |
-\item{condition}{For \code{\link{aggregate}}: condition for which the data |
|
31 |
-should be aggregated.} |
|
32 |
- |
|
33 | 37 |
\item{name}{For \code{\link[=plotDataByCoord]{getDataTrack}}: a valid |
34 | 38 |
transcript name. Must be a name of \code{ranges(x)}} |
35 | 39 |
} |
... | ... |
@@ -1,18 +1,13 @@ |
1 | 1 |
% Generated by roxygen2: do not edit by hand |
2 | 2 |
% Please edit documentation in R/RNAmodR.R, |
3 | 3 |
% R/Gviz-ModifiedSequenceTrack-class.R, R/Gviz-functions.R, |
4 |
-% R/SequenceData-class.R, R/SequenceDataSet-class.R, |
|
5 |
-% R/SequenceDataList-class.R |
|
4 |
+% R/SequenceDataSet-class.R, R/SequenceDataList-class.R |
|
6 | 5 |
\docType{methods} |
7 | 6 |
\name{RNAmodR-internals} |
8 | 7 |
\alias{RNAmodR-internals} |
9 | 8 |
\alias{.getData} |
10 | 9 |
\alias{show,ModifiedSequenceTrack-method} |
11 | 10 |
\alias{length,ModifiedSequenceTrack-method} |
12 |
-\alias{parallelSlotNames,SequenceData-method} |
|
13 |
-\alias{[<-,SequenceData,ANY,ANY,ANY-method} |
|
14 |
-\alias{setListElement,SequenceData-method} |
|
15 |
-\alias{getListElement,SequenceData-method} |
|
16 | 11 |
\alias{parallelSlotNames,SequenceDataSet-method} |
17 | 12 |
\alias{getListElement,SequenceDataSet-method} |
18 | 13 |
\alias{parallelSlotNames,SequenceDataList-method} |
... | ... |
@@ -23,14 +18,6 @@ |
23 | 18 |
|
24 | 19 |
\S4method{length}{ModifiedSequenceTrack}(x) |
25 | 20 |
|
26 |
-\S4method{parallelSlotNames}{SequenceData}(x) |
|
27 |
- |
|
28 |
-\S4method{[}{SequenceData,ANY,ANY,ANY}(x, i, j, ...) <- value |
|
29 |
- |
|
30 |
-\S4method{setListElement}{SequenceData}(x, i, value) |
|
31 |
- |
|
32 |
-\S4method{getListElement}{SequenceData}(x, i, exact = TRUE) |
|
33 |
- |
|
34 | 21 |
\S4method{parallelSlotNames}{SequenceDataSet}(x) |
35 | 22 |
|
36 | 23 |
\S4method{getListElement}{SequenceDataSet}(x, i, exact = TRUE) |
... | ... |
@@ -7,11 +7,12 @@ |
7 | 7 |
\alias{[,SequenceDataFrame,ANY,ANY,ANY-method} |
8 | 8 |
\title{The SequenceDataFrame class} |
9 | 9 |
\usage{ |
10 |
-SequenceDataFrame(df, ranges, sequence, replicate, condition) |
|
11 |
- |
|
12 | 10 |
\S4method{[}{SequenceDataFrame,ANY,ANY,ANY}(x, i, j, ..., drop = TRUE) |
13 | 11 |
} |
14 | 12 |
\arguments{ |
13 |
+\item{x, i, j, ..., drop}{arguments used for |
|
14 |
+\code{\link[S4Vectors:DataFrame-class]{subsetting}}.} |
|
15 |
+ |
|
15 | 16 |
\item{df}{the data as a \code{DataFrame}.} |
16 | 17 |
|
17 | 18 |
\item{ranges}{a \code{GRanges} object containing all annotation elements |
... | ... |
@@ -20,14 +21,11 @@ for a transcript.} |
20 | 21 |
\item{sequence}{\code{XString} object describing the nucleotide sequence of |
21 | 22 |
the transcript.} |
22 | 23 |
|
23 |
-\item{replicate}{The replicate of each column or set of columns for the |
|
24 |
-individual conditions} |
|
25 |
- |
|
26 | 24 |
\item{condition}{The condition of each column or set of columns. Either |
27 | 25 |
\code{control} or \code{treated}.} |
28 | 26 |
|
29 |
-\item{x, i, j, ..., drop}{arguments used for |
|
30 |
-\code{\link[S4Vectors:DataFrame-class]{subsetting}}.} |
|
27 |
+\item{replicate}{The replicate of each column or set of columns for the |
|
28 |
+individual conditions} |
|
31 | 29 |
} |
32 | 30 |
\value{ |
33 | 31 |
a \code{SequenceDataFrame} object |
34 | 32 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,59 @@ |
1 |
+context("SequenceDataFrame") |
|
2 |
+test_that("SequenceDataFrame:",{ |
|
3 |
+ data(psd,package = "RNAmodR") |
|
4 |
+ sdf <- psd[[1]] |
|
5 |
+ #Accessors |
|
6 |
+ expect_type(names(sdf),"character") |
|
7 |
+ expect_s4_class(sequences(sdf),"RNAString") |
|
8 |
+ expect_s4_class(ranges(sdf),"GRanges") |
|
9 |
+ expect_true(is.factor(conditions(sdf))) |
|
10 |
+ expect_equal(replicates(sdf),factor(c(1,1,1,1,1,2,2,2,2,2,3,3,3,3,3))) |
|
11 |
+ expect_equal(conditions(sdf),factor(rep("treated",ncol(sdf)))) |
|
12 |
+ # |
|
13 |
+ sdf2 <- PileupSequenceDataFrame(as(sdf,"DataFrame"), |
|
14 |
+ ranges(sdf), |
|
15 |
+ sequences(sdf), |
|
16 |
+ replicates(sdf), |
|
17 |
+ conditions(sdf)) |
|
18 |
+ expect_equal(sdf,sdf2) |
|
19 |
+ ############################################################################## |
|
20 |
+ # errors |
|
21 |
+ skip_on_bioc() |
|
22 |
+ expect_error(PileupSequenceDataFrame(as(sdf,"DataFrame"), |
|
23 |
+ BString(), |
|
24 |
+ sequences(sdf), |
|
25 |
+ replicates(sdf), |
|
26 |
+ conditions(sdf)), |
|
27 |
+ "Invalid data object: BString found, GRanges expected") |
|
28 |
+ expect_error(PileupSequenceDataFrame(as(sdf,"DataFrame"), |
|
29 |
+ ranges(sdf), |
|
30 |
+ GRanges(), |
|
31 |
+ replicates(sdf), |
|
32 |
+ conditions(sdf)), |
|
33 |
+ "Invalid data object: GRanges found, XString expected") |
|
34 |
+ expect_error(PileupSequenceDataFrame(BString(), |
|
35 |
+ ranges(sdf), |
|
36 |
+ sequences(sdf), |
|
37 |
+ replicates(sdf), |
|
38 |
+ conditions(sdf)), |
|
39 |
+ "Invalid data object: BString found, DataFrame expected") |
|
40 |
+ expect_error(PileupSequenceDataFrame(as(sdf,"DataFrame"), |
|
41 |
+ ranges(sdf), |
|
42 |
+ sequences(sdf), |
|
43 |
+ replicates(sdf)[1], |
|
44 |
+ conditions(sdf)[1]), |
|
45 |
+ "Replicate and Conditions information must match the DataFrame") |
|
46 |
+ # subsetting |
|
47 |
+ expect_type(sdf[1,],"list") |
|
48 |
+ expect_equal(length(sdf[1,]),ncol(sdf)) |
|
49 |
+ expect_s4_class(sdf[1,,drop = FALSE],"DataFrame") |
|
50 |
+ expect_equal(ncol(sdf[1,,drop = FALSE]),ncol(sdf)) |
|
51 |
+ expect_s4_class(sdf[,1],"PileupSequenceDataFrame") |
|
52 |
+ expect_equal(ncol(sdf[,1]),1L) |
|
53 |
+ expect_type(sdf["1",],"list") |
|
54 |
+ expect_equal(length(sdf["1",]),ncol(sdf)) |
|
55 |
+ expect_s4_class(sdf["1",,drop = FALSE],"DataFrame") |
|
56 |
+ expect_equal(ncol(sdf["1",,drop = FALSE]),ncol(sdf)) |
|
57 |
+ expect_s4_class(sdf[,"pileup.treated.1.G"],"PileupSequenceDataFrame") |
|
58 |
+ expect_equal(ncol(sdf[,"pileup.treated.1.G"]),1L) |
|
59 |
+}) |
0 | 60 |
deleted file mode 100644 |
... | ... |
@@ -1,59 +0,0 @@ |
1 |
-context("SequenceDataFrame") |
|
2 |
-test_that("SequenceDataFrame:",{ |
|
3 |
- data(psd,package = "RNAmodR") |
|
4 |
- sdf <- psd[[1]] |
|
5 |
- #Accessors |
|
6 |
- expect_type(names(sdf),"character") |
|
7 |
- expect_s4_class(sequences(sdf),"RNAString") |
|
8 |
- expect_s4_class(ranges(sdf),"GRanges") |
|
9 |
- expect_true(is.factor(conditions(sdf))) |
|
10 |
- expect_equal(replicates(sdf),factor(c(1,1,1,1,1,2,2,2,2,2,3,3,3,3,3))) |
|
11 |
- expect_equal(conditions(sdf),factor(rep("treated",ncol(sdf)))) |
|
12 |
- # |
|
13 |
- sdf2 <- SequenceDataFrame(as(sdf,"DataFrame"), |
|
14 |
- ranges(sdf), |
|
15 |
- sequences(sdf), |
|
16 |
- replicates(sdf), |
|
17 |
- conditions(sdf)) |
|
18 |
- expect_equal(sdf,sdf2) |
|
19 |
- ############################################################################## |
|
20 |
- # errors |
|
21 |
- skip_on_bioc() |
|
22 |
- expect_error(SequenceDataFrame(as(sdf,"DataFrame"), |
|
23 |
- BString(), |
|
24 |
- sequences(sdf), |
|
25 |
- replicates(sdf), |
|
26 |
- conditions(sdf)), |
|
27 |
- "Invalid data object: BString found, GRanges expected") |
|
28 |
- expect_error(SequenceDataFrame(as(sdf,"DataFrame"), |
|
29 |
- ranges(sdf), |
|
30 |
- GRanges(), |
|
31 |
- replicates(sdf), |
|
32 |
- conditions(sdf)), |
|
33 |
- "Invalid data object: GRanges found, XString expected") |
|
34 |
- expect_error(SequenceDataFrame(BString(), |
|
35 |
- ranges(sdf), |
|
36 |
- sequences(sdf), |
|
37 |
- replicates(sdf), |
|
38 |
- conditions(sdf)), |
|
39 |
- "Invalid data object: BString found, DataFrame expected") |
|
40 |
- expect_error(SequenceDataFrame(as(sdf,"DataFrame"), |
|
41 |
- ranges(sdf), |
|
42 |
- sequences(sdf), |
|
43 |
- replicates(sdf)[1], |
|
44 |
- conditions(sdf)[1]), |
|
45 |
- "Replicate and Conditions information must match the DataFrame") |
|
46 |
- # subsetting |
|
47 |
- expect_type(sdf[1,],"list") |
|
48 |
- expect_equal(length(sdf[1,]),ncol(sdf)) |
|
49 |
- expect_s4_class(sdf[1,,drop = FALSE],"DataFrame") |
|
50 |
- expect_equal(ncol(sdf[1,,drop = FALSE]),ncol(sdf)) |
|
51 |
- expect_s4_class(sdf[,1],"SequenceDataFrame") |
|
52 |
- expect_equal(ncol(sdf[,1]),1L) |
|
53 |
- expect_type(sdf["1",],"list") |
|
54 |
- expect_equal(length(sdf["1",]),ncol(sdf)) |
|
55 |
- expect_s4_class(sdf["1",,drop = FALSE],"DataFrame") |
|
56 |
- expect_equal(ncol(sdf["1",,drop = FALSE]),ncol(sdf)) |
|
57 |
- expect_s4_class(sdf[,"pileup.treated.1.G"],"SequenceDataFrame") |
|
58 |
- expect_equal(ncol(sdf[,"pileup.treated.1.G"]),1L) |
|
59 |
-}) |