Change breast data to voom transformed version,
remove use of paste() in stop() and warning(),
update news to reflect latest changes and move
it to main directory
1 | 1 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,10 @@ |
1 |
+# Changes in version 0.99.0 (2016-10-23) |
|
2 |
+- Submitted to Bioconductor |
|
3 |
+ |
|
4 |
+# Changes in version 1.17.1 (2021-10-14) |
|
5 |
+- Changes C backend to C++ |
|
6 |
+- Adds within -omics subsampling |
|
7 |
+- Improves vignette |
|
8 |
+- Fixes several bugs |
|
9 |
+ - Labels for createVectors() now correct |
|
10 |
+ - C (now C++) backend no longer crashes R when things go wrong |
|
0 | 11 |
\ No newline at end of file |
... | ... |
@@ -145,10 +145,10 @@ discordantRun <- function(v1, v2, x, y = NULL, transform = TRUE, |
145 | 145 |
} |
146 | 146 |
|
147 | 147 |
if (repeats >= floor(iter * .1)) { |
148 |
- stop(paste0("\nInsufficient data for subsampling. Increase number of", |
|
148 |
+ stop("\nInsufficient data for subsampling. Increase number of", |
|
149 | 149 |
"\nfeatures, reduce numberof components used, or increase", |
150 | 150 |
"\nsubSize if not at default value. Alternatively, set", |
151 |
- "\nsubsampling=FALSE.")) |
|
151 |
+ "\nsubsampling=FALSE.") |
|
152 | 152 |
} |
153 | 153 |
|
154 | 154 |
mu <- total_mu / iter |
... | ... |
@@ -165,9 +165,8 @@ discordantRun <- function(v1, v2, x, y = NULL, transform = TRUE, |
165 | 165 |
pd <- tryCatch({em.normal.partial.concordant(pdata, class, components)}, |
166 | 166 |
error = function(unused) return(NULL)) |
167 | 167 |
if (is.null(pd)) { |
168 |
- stop( |
|
169 |
- paste0("\nInsufficient data for component estimation. Increase", |
|
170 |
- "\nnumber of features or reduce number of components used.")) |
|
168 |
+ stop("\nInsufficient data for component estimation. Increase", |
|
169 |
+ "\nnumber of features or reduce number of components used.") |
|
171 | 170 |
} |
172 | 171 |
zTable <- pd$z |
173 | 172 |
classVector <- pd$class |
... | ... |
@@ -343,16 +342,16 @@ em.normal.partial.concordant <- function(data, class, components) { |
343 | 342 |
subSize <- floor(length(rownames(x)) / 2) |
344 | 343 |
} else if (subSize > floor(length(rownames(x)) / 2)) { |
345 | 344 |
subSize <- floor(length(rownames(x)) / 2) |
346 |
- warning(paste0("subSize argument too large. Using subSize ", subSize, |
|
347 |
- " See vignette for more information.")) |
|
345 |
+ warning("subSize argument too large. Using subSize ", subSize, |
|
346 |
+ " See vignette for more information.") |
|
348 | 347 |
} |
349 | 348 |
} else { |
350 | 349 |
if (is.null(subSize)) { |
351 | 350 |
subSize <- min(nrow(x), nrow(y)) |
352 | 351 |
} else if (subSize > min(nrow(x), nrow(y))) { |
353 | 352 |
subSize <- min(nrow(x), nrow(y)) |
354 |
- warning(paste0("subSize argument to large. Using subSize ", subSize, |
|
355 |
- " See vignette for more information.")) |
|
353 |
+ warning("subSize argument to large. Using subSize ", subSize, |
|
354 |
+ " See vignette for more information.") |
|
356 | 355 |
} |
357 | 356 |
} |
358 | 357 |
return(subSize) |
... | ... |
@@ -471,22 +471,22 @@ involved in drawing subsamples, and results may differ using different seeds. |
471 | 471 |
|
472 | 472 |
```{r} |
473 | 473 |
# Load Data |
474 |
-data(TCGA_Breast_miRNASeq) |
|
475 |
-data(TCGA_Breast_RNASeq) |
|
474 |
+data(TCGA_Breast_miRNASeq_voom) |
|
475 |
+data(TCGA_Breast_RNASeq_voom) |
|
476 | 476 |
|
477 | 477 |
# Prepare groups |
478 | 478 |
groups <- c(rep(1, 15), rep(2, 42)) |
479 | 479 |
|
480 | 480 |
# Create correlation vectors |
481 |
-sub_vectors <- createVectors(x = TCGA_Breast_miRNASeq, |
|
482 |
- y = TCGA_Breast_RNASeq, |
|
481 |
+sub_vectors <- createVectors(x = TCGA_Breast_miRNASeq_voom, |
|
482 |
+ y = TCGA_Breast_RNASeq_voom, |
|
483 | 483 |
groups = groups) |
484 | 484 |
|
485 | 485 |
# Run analysis with subsampling |
486 | 486 |
set.seed(126) |
487 | 487 |
sub_result <- discordantRun(sub_vectors$v1, sub_vectors$v2, |
488 |
- x = TCGA_Breast_miRNASeq, |
|
489 |
- y = TCGA_Breast_RNASeq, |
|
488 |
+ x = TCGA_Breast_miRNASeq_voom, |
|
489 |
+ y = TCGA_Breast_RNASeq_voom, |
|
490 | 490 |
components = 3, subsampling = TRUE) |
491 | 491 |
|
492 | 492 |
# Results |