Refactors createVectors a bit further, makes
all non-exported functions start with ".",
adds is() from methods package to NAMESPACE and
DESCRIPTION
... | ... |
@@ -17,7 +17,7 @@ Encoding: UTF-8 |
17 | 17 |
biocViews: ImmunoOncology, BiologicalQuestion, StatisticalMethod, |
18 | 18 |
mRNAMicroarray, Microarray, Genetics, RNASeq |
19 | 19 |
Suggests: BiocStyle, knitr, testthat |
20 |
-Imports: Rcpp, Biobase, stats, biwt, gtools, MASS, tools |
|
20 |
+Imports: Rcpp, Biobase, stats, biwt, gtools, MASS, tools, dplyr, methods |
|
21 | 21 |
License: GPL (>= 2) |
22 | 22 |
URL: https://github.com/siskac/discordant |
23 | 23 |
NeedsCompilation: yes |
... | ... |
@@ -53,22 +53,16 @@ createVectors <- function(x, y = NULL, groups, |
53 | 53 |
"sparcc")) { |
54 | 54 |
cor.method <- match.arg(cor.method) |
55 | 55 |
.checkCreateVectorsInputs(x, y, groups, cor.method) |
56 |
- #print(x) |
|
57 |
- |
|
58 |
- index1 <- which(groups == 1) |
|
59 |
- index2 <- which(groups == 2) |
|
60 |
- x <- exprs(x) |
|
61 | 56 |
|
62 | 57 |
if(is.null(y)) { |
63 |
- data <- x |
|
58 |
+ data <- exprs(x) |
|
64 | 59 |
} else { |
65 |
- y <- exprs(y) |
|
66 |
- data <- rbind(x, y) |
|
67 |
- featureSize <- dim(x)[1] |
|
60 |
+ data <- rbind(exprs(x), exprs(y)) |
|
61 |
+ featureSize <- dim(exprs(x))[1] |
|
68 | 62 |
} |
69 | 63 |
|
70 |
- data1 <- data[,index1] |
|
71 |
- data2 <- data[,index2] |
|
64 |
+ data1 <- data[, which(groups == 1)] |
|
65 |
+ data2 <- data[, which(groups == 2)] |
|
72 | 66 |
|
73 | 67 |
if (cor.method == "spearman" || cor.method == "pearson") { |
74 | 68 |
statMatrix1 <- cor(t(data1), method = cor.method) |
... | ... |
@@ -82,8 +76,6 @@ createVectors <- function(x, y = NULL, groups, |
82 | 76 |
} |
83 | 77 |
|
84 | 78 |
if (is.null(y)) { |
85 |
- statVector1 <- as.vector(statMatrix1) |
|
86 |
- statVector2 <- as.vector(statMatrix2) |
|
87 | 79 |
diag <- lower.tri(statMatrix1, diag = FALSE) |
88 | 80 |
statVector1 <- statMatrix1[diag] |
89 | 81 |
statVector2 <- statMatrix2[diag] |
... | ... |
@@ -96,7 +88,7 @@ createVectors <- function(x, y = NULL, groups, |
96 | 88 |
statVector2 <- as.vector(statMatrix2) |
97 | 89 |
} |
98 | 90 |
|
99 |
- vector_names <- getNames(x, y) |
|
91 |
+ vector_names <- .getNames(exprs(x), y) |
|
100 | 92 |
names(statVector1) <- vector_names |
101 | 93 |
names(statVector2) <- vector_names |
102 | 94 |
return(list(v1 = statVector1, v2 = statVector2)) |
... | ... |
@@ -160,7 +160,7 @@ discordantRun <- function(v1, v2, x, y = NULL, transform = TRUE, |
160 | 160 |
tau <- total_tau / iter |
161 | 161 |
pi <- total_pi / iter |
162 | 162 |
|
163 |
- finalResult <- subSampleData(pdata, class, mu, sigma, nu, tau, pi, |
|
163 |
+ finalResult <- .subSampleData(pdata, class, mu, sigma, nu, tau, pi, |
|
164 | 164 |
components) |
165 | 165 |
zTable <- finalResult$z |
166 | 166 |
classVector <- finalResult$class |
... | ... |
@@ -182,7 +182,7 @@ discordantRun <- function(v1, v2, x, y = NULL, transform = TRUE, |
182 | 182 |
colnames(discordPPMatrix) <- rownames(x) |
183 | 183 |
rownames(classMatrix) <- rownames(x) |
184 | 184 |
colnames(classMatrix) <- rownames(x) |
185 |
- vector_names <- getNames(x) |
|
185 |
+ vector_names <- .getNames(x) |
|
186 | 186 |
names(discordPPV) <- vector_names |
187 | 187 |
names(classVector) <- vector_names |
188 | 188 |
} else { |
... | ... |
@@ -194,7 +194,7 @@ discordantRun <- function(v1, v2, x, y = NULL, transform = TRUE, |
194 | 194 |
rownames(classMatrix) <- rownames(x) |
195 | 195 |
colnames(classMatrix) <- rownames(y) |
196 | 196 |
|
197 |
- vector_names <- getNames(x,y) |
|
197 |
+ vector_names <- .getNames(x,y) |
|
198 | 198 |
names(discordPPV) <- vector_names |
199 | 199 |
names(classVector) <- vector_names |
200 | 200 |
} |
... | ... |
@@ -219,8 +219,8 @@ em.normal.partial.concordant <- function(data, class, components) { |
219 | 219 |
return( c(zx[k,] %o% zy[k,]) ) |
220 | 220 |
} |
221 | 221 |
|
222 |
- zx <- unmap(class[,1], components = components) |
|
223 |
- zy <- unmap(class[,2], components = components) |
|
222 |
+ zx <- .unmap(class[,1], components = components) |
|
223 |
+ zy <- .unmap(class[,2], components = components) |
|
224 | 224 |
zxy <- sapply(1:dim(zx)[1], yl.outer, zx, zy) |
225 | 225 |
|
226 | 226 |
pi <- double(g*g) |
... | ... |
@@ -267,6 +267,7 @@ em.normal.partial.concordant <- function(data, class, components) { |
267 | 267 |
} |
268 | 268 |
|
269 | 269 |
# Internal function to validate user inputs for discordantRun() |
270 |
+#' @importFrom methods is |
|
270 | 271 |
.checkDiscordantInputs <- function(v1, v2, x, y, transform, |
271 | 272 |
subsampling, subSize, iter, |
272 | 273 |
components) { |
... | ... |
@@ -28,7 +28,7 @@ fishersTrans <- function(rho) { |
28 | 28 |
return(z) |
29 | 29 |
} |
30 | 30 |
|
31 |
-subSampleData <- function(pdata, class, mu, sigma, nu, tau, pi, components) { |
|
31 |
+.subSampleData <- function(pdata, class, mu, sigma, nu, tau, pi, components) { |
|
32 | 32 |
n <- as.integer(dim(pdata)[1]) |
33 | 33 |
g <- as.integer(nlevels(as.factor(class))) |
34 | 34 |
|
... | ... |
@@ -54,7 +54,7 @@ subSampleData <- function(pdata, class, mu, sigma, nu, tau, pi, components) { |
54 | 54 |
} |
55 | 55 |
|
56 | 56 |
# modified from package mclust |
57 |
-unmap <- function(classification, components){ |
|
57 |
+.unmap <- function(classification, components){ |
|
58 | 58 |
n <- length(classification) |
59 | 59 |
# u <- sort(unique(classification)) # OG Code |
60 | 60 |
u <- 0:(components - 1) # Max's potential fix |
... | ... |
@@ -66,8 +66,9 @@ unmap <- function(classification, components){ |
66 | 66 |
return(z) |
67 | 67 |
} |
68 | 68 |
|
69 |
-getNames <- function(x, y = NULL) { |
|
69 |
+.getNames <- function(x, y = NULL) { |
|
70 | 70 |
if(is.null(y) == FALSE) { |
71 |
+ y <- exprs(y) |
|
71 | 72 |
namesMatrix <- NULL |
72 | 73 |
for(i in 1:nrow(x)) { |
73 | 74 |
tempMatrix <- cbind(rep(rownames(x)[i], nrow(y)), rownames(y)) |
... | ... |
@@ -317,10 +317,10 @@ from x and the column names are features from y. |
317 | 317 |
|
318 | 318 |
```{r} |
319 | 319 |
# Within -omics |
320 |
-wthn_result$discordPPMatrix[1:4, 1:4] |
|
320 |
+wthn_result$discordPPMatrix[1:5, 1:4] |
|
321 | 321 |
|
322 | 322 |
# Between -omics |
323 |
-btwn_result$discordPPMatrix[1:4, 1:4] |
|
323 |
+btwn_result$discordPPMatrix[1:5, 1:4] |
|
324 | 324 |
``` |
325 | 325 |
|
326 | 326 |
__discordPPVector__ |
... | ... |
@@ -339,22 +339,22 @@ head(btwn_result$discordPPVector) |
339 | 339 |
__classMatrix__ |
340 | 340 |
|
341 | 341 |
Matrix of classes with the highest posterior probability for each pair. |
342 |
-Row and column names are the same as in discordPPMatrix and determined by |
|
342 |
+Row and column names are the same as in \code{discordPPMatrix} and determined by |
|
343 | 343 |
whether only x is inputted or both x and y. |
344 | 344 |
|
345 | 345 |
```{r} |
346 | 346 |
# Within -omics |
347 |
-wthn_result$classMatrix[1:4,1:4] |
|
347 |
+wthn_result$classMatrix[1:5,1:4] |
|
348 | 348 |
|
349 | 349 |
# Between -omics |
350 |
-btwn_result$classMatrix[1:4,1:4] |
|
350 |
+btwn_result$classMatrix[1:5,1:4] |
|
351 | 351 |
``` |
352 | 352 |
|
353 | 353 |
__classVector__ |
354 | 354 |
|
355 | 355 |
Vector of class with the highest posterior probability for each pair. The |
356 | 356 |
length is the number of feature pairs. Names of vector correspond to the |
357 |
-feature pairs, similar to discordPPVector. |
|
357 |
+feature pairs, similar to \code{discordPPVector}. |
|
358 | 358 |
|
359 | 359 |
```{r} |
360 | 360 |
# Within -omics |
... | ... |
@@ -370,9 +370,9 @@ Matrix of all posterior probabilities, where the number of rows is |
370 | 370 |
the number of feature pairs and the columns represent the class within the |
371 | 371 |
class matrix. The number of columns can be 9 or 25, depending on how many |
372 | 372 |
mixture components are chosen (discussed later). The values across each row |
373 |
-add up to 1. Posterior probabilities in discordPPMatrix and discordPPVector |
|
374 |
-are the summation of columns that correspond to differential correlation |
|
375 |
-classes (Table 1). |
|
373 |
+add up to 1. Posterior probabilities in \code{discordPPMatrix} and |
|
374 |
+\code{discordPPVector} are the summation of columns that correspond to |
|
375 |
+differential correlation classes (Table 1). |
|
376 | 376 |
|
377 | 377 |
```{r} |
378 | 378 |
# Within -omics |
... | ... |
@@ -460,13 +460,11 @@ data(TCGA_GBM_transcript_microarray) |
460 | 460 |
groups <- c(rep(1,10), rep(2,10)) |
461 | 461 |
|
462 | 462 |
#Within -Omics |
463 |
- |
|
464 | 463 |
wthn_vectors <- createVectors(TCGA_GBM_transcript_microarray, groups = groups) |
465 | 464 |
wthn_result <- discordantRun(wthn_vectors$v1, wthn_vectors$v2, |
466 | 465 |
TCGA_GBM_transcript_microarray) |
467 | 466 |
|
468 | 467 |
#Between -Omics |
469 |
- |
|
470 | 468 |
btwn_vectors <- createVectors(TCGA_GBM_miRNA_microarray, |
471 | 469 |
TCGA_GBM_transcript_microarray, groups = groups) |
472 | 470 |
btwn_result <- discordantRun(btwn_vectors$v1, btwn_vectors$v2, |