refactored results of conditions and replicates of SequenceDataSet and SequenceDataList
... | ... |
@@ -627,12 +627,19 @@ setReplaceMethod(f = "settings", |
627 | 627 |
proto <- new(className) # create prototype object for mod normalization only |
628 | 628 |
data <- .norm_Modifier_input_SequenceData_elements(data, proto) |
629 | 629 |
bamfiles <- bamfiles(data) |
630 |
- condition <- factor(names(bamfiles)) |
|
630 |
+ # setup conditions and replicates |
|
631 |
+ conditions <- .norm_conditions(data) |
|
632 |
+ replicates <- .norm_replicates(data) |
|
633 |
+ ia <- as.integer(interaction(conditions,replicates)) |
|
634 |
+ m <- match(unique(ia),ia) |
|
635 |
+ condition <- conditions[m] |
|
636 |
+ replicate <- replicates[m] |
|
637 |
+ # create Modifier object |
|
631 | 638 |
new(className, |
632 | 639 |
mod = .norm_mod(proto@mod, className), |
633 | 640 |
bamfiles = bamfiles, |
634 | 641 |
condition = condition, |
635 |
- replicate = .get_replicate_number(condition), |
|
642 |
+ replicate = replicate, |
|
636 | 643 |
data = data) |
637 | 644 |
} |
638 | 645 |
|
... | ... |
@@ -171,16 +171,18 @@ NULL |
171 | 171 |
unlisted_coord <- unlist(coord,use.names = FALSE) |
172 | 172 |
if(!is.null(unlisted_coord$Activity) || !is.null(unlisted_coord$mod)){ |
173 | 173 |
f <- match(start(coord),relist(data$positions,partitioning_data)) |
174 |
+ ff <- !is.na(f) |
|
175 |
+ f <- f[ff] |
|
174 | 176 |
f <- f + start(IRanges::PartitioningByEnd(f)) - 1L |
175 | 177 |
f <- unlist(f) |
176 | 178 |
if(!is.null(unlisted_coord$Activity)){ |
177 | 179 |
data$Activity <- "" |
178 | 180 |
data$Activity[f] <- vapply(unlisted_coord$Activity, paste, character(1), |
179 |
- collapse = "/") |
|
181 |
+ collapse = "/")[unlist(ff)] |
|
180 | 182 |
} |
181 | 183 |
if(!is.null(unlisted_coord$mod)){ |
182 | 184 |
data$mod <- "" |
183 |
- data$mod[f] <- unlisted_coord$mod |
|
185 |
+ data$mod[f] <- unlisted_coord$mod[unlist(ff)] |
|
184 | 186 |
} |
185 | 187 |
} |
186 | 188 |
# convert ids to names for labeling if present |
... | ... |
@@ -345,16 +345,11 @@ setMethod( |
345 | 345 |
ia <- interaction(conditions(x), replicates(x)) |
346 | 346 |
if(is.character(j)){ |
347 | 347 |
j <- normalizeSingleBracketSubscript(j, xstub) |
348 |
- j <- as.integer(ia)[j] |
|
348 |
+ j <- unique(as.integer(ia)[j]) |
|
349 |
+ } else { |
|
350 |
+ conditionsFmultiplier <- length(ia) / length(unique(ia)) |
|
351 |
+ j <- normalizeSingleBracketSubscript(j, xstub[seq_len(length(ia)/conditionsFmultiplier)]) |
|
349 | 352 |
} |
350 |
- colnames <- IRanges::CharacterList(strsplit(colnames(x),"\\.")) |
|
351 |
- colnames_conditions <- colnames %in% c("treated","control") |
|
352 |
- colnames_replicates <- !is.na(suppressWarnings(IntegerList(colnames))) |
|
353 |
- colnames_f <- !(colnames_conditions | colnames_replicates) |
|
354 |
- conditionsFmultiplier <- length(unique(vapply(colnames[colnames_f], |
|
355 |
- paste,character(1), |
|
356 |
- collapse="."))) |
|
357 |
- j <- normalizeSingleBracketSubscript(j, xstub[seq_len(length(xstub)/conditionsFmultiplier)]) |
|
358 | 353 |
j2 <- which(!is.na(match(as.integer(ia), j))) |
359 | 354 |
x <- initialize(x, |
360 | 355 |
as(x,"DataFrame")[, j2, drop = FALSE], |
... | ... |
@@ -286,16 +286,30 @@ setMethod(f = "bamfiles", |
286 | 286 |
setMethod(f = "conditions", |
287 | 287 |
signature = signature(object = "SequenceDataSet"), |
288 | 288 |
definition = function(object){ |
289 |
- ans <- IRanges::FactorList(lapply(object,conditions)) |
|
290 |
- ans |
|
289 |
+ ans <- IRanges::FactorList( |
|
290 |
+ lapply(object[1L], |
|
291 |
+ function(o){ |
|
292 |
+ ia <- as.integer(interaction(conditions(o), |
|
293 |
+ replicates(o))) |
|
294 |
+ m <- match(unique(ia),ia) |
|
295 |
+ conditions(o)[m] |
|
296 |
+ })) |
|
297 |
+ ans[[1L]] |
|
291 | 298 |
}) |
292 | 299 |
#' @rdname SequenceData-functions |
293 | 300 |
#' @export |
294 | 301 |
setMethod(f = "replicates", |
295 | 302 |
signature = signature(x = "SequenceDataSet"), |
296 | 303 |
definition = function(x){ |
297 |
- ans <- IRanges::FactorList(lapply(x,replicates)) |
|
298 |
- ans |
|
304 |
+ ans <- IRanges::FactorList( |
|
305 |
+ lapply(x[1L], |
|
306 |
+ function(o){ |
|
307 |
+ ia <- as.integer(interaction(conditions(o), |
|
308 |
+ replicates(o))) |
|
309 |
+ m <- match(unique(ia),ia) |
|
310 |
+ replicates(o)[m] |
|
311 |
+ })) |
|
312 |
+ ans[[1L]] |
|
299 | 313 |
}) |
300 | 314 |
|
301 | 315 |
# aggregate -------------------------------------------------------------------- |
... | ... |
@@ -283,3 +283,21 @@ SAMPLE_TYPES <- c("treated","control") |
283 | 283 |
} |
284 | 284 |
data |
285 | 285 |
} |
286 |
+ |
|
287 |
+# conditions and replicates ---------------------------------------------------- |
|
288 |
+ |
|
289 |
+.norm_conditions <- function(x){ |
|
290 |
+ conditions <- conditions(x) |
|
291 |
+ if(is(x,"SequenceDataList")){ |
|
292 |
+ conditions <- conditions[[1L]] |
|
293 |
+ } |
|
294 |
+ conditions |
|
295 |
+} |
|
296 |
+ |
|
297 |
+.norm_replicates <- function(x){ |
|
298 |
+ replicates <- replicates(x) |
|
299 |
+ if(is(x,"SequenceDataList")){ |
|
300 |
+ replicates <- replicates[[1L]] |
|
301 |
+ } |
|
302 |
+ replicates |
|
303 |
+} |
... | ... |
@@ -14,11 +14,11 @@ test_that("SequenceDataSet:",{ |
14 | 14 |
expect_equal(sequences(sds),sequences(sds[[1]])) |
15 | 15 |
expect_equal(bamfiles(sds),bamfiles(sds[[1]])) |
16 | 16 |
actual <- conditions(sds) |
17 |
- expect_s4_class(actual,"FactorList") |
|
18 |
- expect_equal(actual[[1]],factor(c("treated","treated","treated"))) |
|
17 |
+ expect_is(actual,"factor") |
|
18 |
+ expect_equal(actual,factor(c("treated","treated","treated"))) |
|
19 | 19 |
actual <- replicates(sds) |
20 |
- expect_s4_class(actual,"FactorList") |
|
21 |
- expect_equal(actual[[1]],factor(c(1,2,3))) |
|
20 |
+ expect_is(actual,"factor") |
|
21 |
+ expect_equal(actual,factor(c(1,2,3))) |
|
22 | 22 |
############################################################################## |
23 | 23 |
# expect_equal(aggregate(sds), |
24 | 24 |
# SimpleList(End5SequenceData = aggregate(sds[[1]]), |
... | ... |
@@ -57,16 +57,14 @@ test_that("SequenceDataList:",{ |
57 | 57 |
skip_on_bioc() |
58 | 58 |
actual <- conditions(sdl) |
59 | 59 |
expect_s4_class(actual,"SimpleList") |
60 |
- expect_s4_class(actual[[1]],"FactorList") |
|
61 |
- expect_true(is.factor(actual[[1]][[1]])) |
|
62 |
- expect_equal(actual[[1]][[1]],actual[[2]]) |
|
63 |
- expect_equal(actual[[1]][[1]],factor(c("treated","treated","treated"))) |
|
60 |
+ expect_is(actual[[1]],"factor") |
|
61 |
+ expect_equal(actual[[1]],actual[[2]]) |
|
62 |
+ expect_equal(actual[[1]],factor(c("treated","treated","treated"))) |
|
64 | 63 |
actual <- replicates(sdl) |
65 | 64 |
expect_s4_class(actual,"SimpleList") |
66 |
- expect_s4_class(actual[[1]],"FactorList") |
|
67 |
- expect_true(is.factor(actual[[1]][[1]])) |
|
68 |
- expect_equal(actual[[1]][[1]],actual[[2]]) |
|
69 |
- expect_equal(actual[[1]][[1]],factor(c(1,2,3))) |
|
65 |
+ expect_is(actual[[1]],"factor") |
|
66 |
+ expect_equal(actual[[1]],actual[[2]]) |
|
67 |
+ expect_equal(actual[[1]],factor(c(1,2,3))) |
|
70 | 68 |
expect_equal(ranges(sdl),ranges(sdl[[1]])) |
71 | 69 |
expect_equal(sequences(sdl),sequences(sdl[[1]])) |
72 | 70 |
############################################################################## |