... | ... |
@@ -28,7 +28,7 @@ |
28 | 28 |
## |
29 | 29 |
################################################################## |
30 | 30 |
|
31 |
-normalize.quantiles <- function(x,copy=TRUE){ |
|
31 |
+normalize.quantiles <- function(x,copy=TRUE,keep.names=FALSE){ |
|
32 | 32 |
|
33 | 33 |
rows <- dim(x)[1] |
34 | 34 |
cols <- dim(x)[2] |
... | ... |
@@ -45,11 +45,16 @@ normalize.quantiles <- function(x,copy=TRUE){ |
45 | 45 |
#matrix(.C("qnorm_c", as.double(as.vector(x)), as.integer(rows), as.integer(cols))[[1]], rows, cols) |
46 | 46 |
|
47 | 47 |
## .Call("R_qnorm_c",x,copy, PACKAGE="preprocessCore"); |
48 |
- .Call("R_qnorm_c_handleNA",x,copy, PACKAGE="preprocessCore"); |
|
48 |
+ mat <- .Call("R_qnorm_c_handleNA",x,copy, PACKAGE="preprocessCore"); |
|
49 |
+ if(keep.names){ |
|
50 |
+ rownames(mat) <- rownames(x) |
|
51 |
+ colnames(mat) <- colnames(x) |
|
52 |
+ } |
|
53 |
+ mat |
|
49 | 54 |
} |
50 | 55 |
|
51 | 56 |
|
52 |
-normalize.quantiles.robust <- function(x,copy=TRUE,weights=NULL,remove.extreme=c("variance","mean","both","none"),n.remove=1,use.median=FALSE,use.log2=FALSE){ |
|
57 |
+normalize.quantiles.robust <- function(x,copy=TRUE,weights=NULL,remove.extreme=c("variance","mean","both","none"),n.remove=1,use.median=FALSE,use.log2=FALSE,keep.names=FALSE){ |
|
53 | 58 |
|
54 | 59 |
calc.var.ratios <- function(x){ |
55 | 60 |
cols <- dim(x)[2] |
... | ... |
@@ -104,5 +109,9 @@ normalize.quantiles.robust <- function(x,copy=TRUE,weights=NULL,remove.extreme=c |
104 | 109 |
} |
105 | 110 |
} |
106 | 111 |
|
107 |
- .Call("R_qnorm_robust_c",x,copy,weights,as.integer(use.median),as.integer(use.log2),as.integer(use.huber),PACKAGE="preprocessCore") |
|
112 |
+ mat <- .Call("R_qnorm_robust_c",x,copy,weights,as.integer(use.median),as.integer(use.log2),as.integer(use.huber),PACKAGE="preprocessCore") |
|
113 |
+ if(keep.names){ |
|
114 |
+ rownames(mat) <- rownames(x) |
|
115 |
+ colnames(mat) <- colnames(x) |
|
116 |
+ } |
|
108 | 117 |
} |
... | ... |
@@ -14,6 +14,8 @@ |
14 | 14 |
\item{copy}{Make a copy of matrix before normalizing. Usually safer to |
15 | 15 |
work with a copy, but in certain situations not making a copy of the |
16 | 16 |
matrix, but instead normalizing it in place will be more memory friendly.} |
17 |
+ \item{keep.names}{Boolean option to preserve matrix row and column names in |
|
18 |
+ output.} |
|
17 | 19 |
} |
18 | 20 |
\details{This method is based upon the concept of a quantile-quantile |
19 | 21 |
plot extended to n dimensions. No special allowances are made for |
... | ... |
@@ -23,6 +23,8 @@ |
23 | 23 |
chip, otherwise uses a weighted mean} |
24 | 24 |
\item{use.log2}{work on log2 scale. This means we will be using the |
25 | 25 |
geometric mean rather than ordinary mean} |
26 |
+ \item{keep.names}{Boolean option to preserve matrix row and column names in |
|
27 |
+ output.} |
|
26 | 28 |
} |
27 | 29 |
\details{This method is based upon the concept of a quantile-quantile |
28 | 30 |
plot extended to n dimensions. Note that the matrix is of intensities |
... | ... |
@@ -51,4 +51,13 @@ if (all(abs(normalize.quantiles.use.target(y,y.norm.target.truth) - y.norm.truth |
51 | 51 |
} |
52 | 52 |
|
53 | 53 |
|
54 |
- |
|
54 |
+x <- matrix(c(100,15,200,250,110,16.5,220,275,120,18,240,300),ncol=3) |
|
55 |
+rownames(x) <- letters[1:4] |
|
56 |
+colnames(x) <- LETTERS[1:3] |
|
57 |
+y <- normalize.quantiles(x, keep.names = TRUE) |
|
58 |
+if(!all(colnames(x)==colnames(y))){ |
|
59 |
+ stop("Disagreement between initial and final column names despite keep.names=TRUE") |
|
60 |
+} |
|
61 |
+if(!all(rownames(x)==rownames(y))){ |
|
62 |
+ stop("Disagreement between initial and final row names despite keep.names=TRUE") |
|
63 |
+} |