1 | 1 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,125 @@ |
1 |
+1.7.8 |
|
2 |
+----- |
|
3 |
+Attempt to check if PTHREAD_STACK_MIN is defined |
|
4 |
+ |
|
5 |
+ |
|
6 |
+1.7.7 |
|
7 |
+----- |
|
8 |
+Include <limits.h> on pthreads builds |
|
9 |
+ |
|
10 |
+ |
|
11 |
+1.7.5 |
|
12 |
+----- |
|
13 |
+ |
|
14 |
+Fix bug when scale estimate provided to rcModelPLM() |
|
15 |
+ |
|
16 |
+1.7.3/1.7.4 |
|
17 |
+----------- |
|
18 |
+ |
|
19 |
+Fix bug with floating point argument provided where integer expected. Use of non intialized value. |
|
20 |
+ |
|
21 |
+ |
|
22 |
+1.7.2 |
|
23 |
+----- |
|
24 |
+ |
|
25 |
+Returned scale estimates are computed using residuals at last iteration rather than n-1 iteration |
|
26 |
+ |
|
27 |
+ |
|
28 |
+1.7.1 |
|
29 |
+----- |
|
30 |
+ |
|
31 |
+rcModelPLM, rcModelWPLM now accept an "input.scale" argument (and also return scale value) |
|
32 |
+ |
|
33 |
+ |
|
34 |
+1.5.3 |
|
35 |
+------ |
|
36 |
+fix VECTOR_ELT/STRING_ELT issues |
|
37 |
+ |
|
38 |
+ |
|
39 |
+1.5.2 |
|
40 |
+----- |
|
41 |
+normalize.quantiles.determine.target() and normalize.quantiles.use.target() now have a "subset" argument |
|
42 |
+ |
|
43 |
+ |
|
44 |
+1.5.1 |
|
45 |
+----- |
|
46 |
+Default rcModelPLM() returns both probe coef and se for constraint row (previously SE was not properly returned) |
|
47 |
+ |
|
48 |
+ |
|
49 |
+1.3.6 |
|
50 |
+----- |
|
51 |
+Fix issue with non double arguements to normalize.quantiles.use.target() |
|
52 |
+ |
|
53 |
+ |
|
54 |
+ |
|
55 |
+1.3.4 |
|
56 |
+----- |
|
57 |
+Fix memory leak in determine_target |
|
58 |
+Set pthread stack size where appropriate |
|
59 |
+ |
|
60 |
+ |
|
61 |
+1.3.3 |
|
62 |
+----- |
|
63 |
+Fix memory leak in use_target |
|
64 |
+ |
|
65 |
+ |
|
66 |
+1.3.2 |
|
67 |
+----- |
|
68 |
+ |
|
69 |
+R_subColSummary functions are now exposed at the C level |
|
70 |
+ |
|
71 |
+1.3.1 |
|
72 |
+----- |
|
73 |
+rma.background.correct() was not correctly returning value when copy ==TRUE |
|
74 |
+ |
|
75 |
+1.1.9 |
|
76 |
+----- |
|
77 |
+Commit missing c source files |
|
78 |
+ |
|
79 |
+ |
|
80 |
+1.1.8 |
|
81 |
+----- |
|
82 |
+Commit missing header files |
|
83 |
+ |
|
84 |
+ |
|
85 |
+1.1.7 |
|
86 |
+----- |
|
87 |
+Fix background function bindings (for use by other packages). The implementation themselves is unchanged. |
|
88 |
+ |
|
89 |
+ |
|
90 |
+1.1.6 |
|
91 |
+----- |
|
92 |
+Addition of PLM-r and PLM-d |
|
93 |
+Adjust rcModelPLM so that it takes optional row-effect estimates |
|
94 |
+quantile normalization functions normalize.quantiles(), normalization.quantiles.determine.target(),normalize.quantiles.use.target() all now have multi-threaded support, user controlled using the R_THREADS environment variable |
|
95 |
+Move weightedkerneldensity.c from affyPLM to preprocessCore |
|
96 |
+subColSummarize* functions all now have basic multi-threaded support, user controlled using the R_THREADS |
|
97 |
+rma background correction method (also multi-threaded) |
|
98 |
+ |
|
99 |
+ |
|
100 |
+ |
|
101 |
+1.1.5 |
|
102 |
+----- |
|
103 |
+ The subColSummarize* functions now return a matrix with rownames. Now it is clear which rows of the resulting summary matrix correspond to which values of the group.labels variable. This helps clarify the previous situation where it done alphabetically. |
|
104 |
+ |
|
105 |
+ |
|
106 |
+ |
|
107 |
+1.1.3 |
|
108 |
+----- |
|
109 |
+Fix broken Makevars.in |
|
110 |
+ |
|
111 |
+ |
|
112 |
+1.1.2 |
|
113 |
+----- |
|
114 |
+ |
|
115 |
+Add missing Makevars.in |
|
116 |
+ |
|
117 |
+ |
|
118 |
+1.1.1 |
|
119 |
+----- |
|
120 |
+ |
|
121 |
+Add experimental support for pthreads based multi-threaded quantile normalization via code contributed by Paul Gordon <gordonp@ucalgary.ca> |
|
122 |
+ |
|
123 |
+This is only implemented for the RMA quantile normalization (ie accessible via calling the rma() function. |
|
124 |
+ |
|
125 |
+The number of threads is user controlled by setting the R_THREADS environment variable |
|
0 | 126 |
\ No newline at end of file |
1 | 127 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,12 @@ |
1 |
+Package: preprocessCore |
|
2 |
+Version: 1.27.1 |
|
3 |
+Title: A collection of pre-processing functions |
|
4 |
+Author: Benjamin Milo Bolstad <bmb@bmbolstad.com> |
|
5 |
+Maintainer: Benjamin Milo Bolstad <bmb@bmbolstad.com> |
|
6 |
+Depends: methods |
|
7 |
+Imports: stats |
|
8 |
+Description: A library of core preprocessing routines |
|
9 |
+License: LGPL (>= 2) |
|
10 |
+Collate: normalize.quantiles.R quantile_extensions.R rma.background.correct.R rcModel.R colSummarize.R subColSummarize.R plmr.R plmd.R |
|
11 |
+LazyLoad: yes |
|
12 |
+biocViews: Infrastructure |
0 | 7 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,146 @@ |
1 |
+## |
|
2 |
+## file: colSummarize.R |
|
3 |
+## |
|
4 |
+## Author: B. M. Bolstad <bmb@bmbolstad.com> |
|
5 |
+## |
|
6 |
+## History |
|
7 |
+## Sept 15, 2007 - Initial verison |
|
8 |
+## |
|
9 |
+ |
|
10 |
+ |
|
11 |
+ |
|
12 |
+ |
|
13 |
+colSummarizeAvgLog <- function(y){ |
|
14 |
+ if (!is.matrix(y)) |
|
15 |
+ stop("argument should be matrix") |
|
16 |
+ |
|
17 |
+ if (!is.double(y) & is.numeric(y)) |
|
18 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
19 |
+ else if (!is.numeric(y)) |
|
20 |
+ stop("argument should be numeric matrix") |
|
21 |
+ |
|
22 |
+ .Call("R_colSummarize_avg_log",y,PACKAGE="preprocessCore") |
|
23 |
+} |
|
24 |
+ |
|
25 |
+ |
|
26 |
+colSummarizeLogAvg <- function(y){ |
|
27 |
+ if (!is.matrix(y)) |
|
28 |
+ stop("argument should be matrix") |
|
29 |
+ |
|
30 |
+ if (!is.double(y) & is.numeric(y)) |
|
31 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
32 |
+ else if (!is.numeric(y)) |
|
33 |
+ stop("argument should be numeric matrix") |
|
34 |
+ |
|
35 |
+ .Call("R_colSummarize_log_avg",y,PACKAGE="preprocessCore") |
|
36 |
+} |
|
37 |
+ |
|
38 |
+ |
|
39 |
+colSummarizeAvg <- function(y){ |
|
40 |
+ if (!is.matrix(y)) |
|
41 |
+ stop("argument should be matrix") |
|
42 |
+ |
|
43 |
+ if (!is.double(y) & is.numeric(y)) |
|
44 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
45 |
+ else if (!is.numeric(y)) |
|
46 |
+ stop("argument should be numeric matrix") |
|
47 |
+ |
|
48 |
+ .Call("R_colSummarize_avg",y,PACKAGE="preprocessCore") |
|
49 |
+} |
|
50 |
+ |
|
51 |
+ |
|
52 |
+colSummarizeLogMedian <- function(y){ |
|
53 |
+ if (!is.matrix(y)) |
|
54 |
+ stop("argument should be matrix") |
|
55 |
+ |
|
56 |
+ if (!is.double(y) & is.numeric(y)) |
|
57 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
58 |
+ else if (!is.numeric(y)) |
|
59 |
+ stop("argument should be numeric matrix") |
|
60 |
+ |
|
61 |
+ .Call("R_colSummarize_log_median",y,PACKAGE="preprocessCore") |
|
62 |
+} |
|
63 |
+ |
|
64 |
+ |
|
65 |
+ |
|
66 |
+ |
|
67 |
+colSummarizeMedianLog <- function(y){ |
|
68 |
+ if (!is.matrix(y)) |
|
69 |
+ stop("argument should be matrix") |
|
70 |
+ |
|
71 |
+ if (!is.double(y) & is.numeric(y)) |
|
72 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
73 |
+ else if (!is.numeric(y)) |
|
74 |
+ stop("argument should be numeric matrix") |
|
75 |
+ |
|
76 |
+ .Call("R_colSummarize_median_log",y,PACKAGE="preprocessCore") |
|
77 |
+} |
|
78 |
+ |
|
79 |
+ |
|
80 |
+colSummarizeMedian <- function(y){ |
|
81 |
+ if (!is.matrix(y)) |
|
82 |
+ stop("argument should be matrix") |
|
83 |
+ |
|
84 |
+ if (!is.double(y) & is.numeric(y)) |
|
85 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
86 |
+ else if (!is.numeric(y)) |
|
87 |
+ stop("argument should be numeric matrix") |
|
88 |
+ |
|
89 |
+ .Call("R_colSummarize_median",y,PACKAGE="preprocessCore") |
|
90 |
+} |
|
91 |
+ |
|
92 |
+ |
|
93 |
+ |
|
94 |
+colSummarizeBiweightLog <- function(y){ |
|
95 |
+ if (!is.matrix(y)) |
|
96 |
+ stop("argument should be matrix") |
|
97 |
+ |
|
98 |
+ if (!is.double(y) & is.numeric(y)) |
|
99 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
100 |
+ else if (!is.numeric(y)) |
|
101 |
+ stop("argument should be numeric matrix") |
|
102 |
+ |
|
103 |
+ .Call("R_colSummarize_biweight_log",y,PACKAGE="preprocessCore") |
|
104 |
+} |
|
105 |
+ |
|
106 |
+colSummarizeBiweight <- function(y){ |
|
107 |
+ if (!is.matrix(y)) |
|
108 |
+ stop("argument should be matrix") |
|
109 |
+ |
|
110 |
+ if (!is.double(y) & is.numeric(y)) |
|
111 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
112 |
+ else if (!is.numeric(y)) |
|
113 |
+ stop("argument should be numeric matrix") |
|
114 |
+ |
|
115 |
+ .Call("R_colSummarize_biweight",y,PACKAGE="preprocessCore") |
|
116 |
+} |
|
117 |
+ |
|
118 |
+ |
|
119 |
+ |
|
120 |
+colSummarizeMedianpolishLog <- function(y){ |
|
121 |
+ if (!is.matrix(y)) |
|
122 |
+ stop("argument should be matrix") |
|
123 |
+ |
|
124 |
+ if (!is.double(y) & is.numeric(y)) |
|
125 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
126 |
+ else if (!is.numeric(y)) |
|
127 |
+ stop("argument should be numeric matrix") |
|
128 |
+ |
|
129 |
+ .Call("R_colSummarize_medianpolish_log",y,PACKAGE="preprocessCore") |
|
130 |
+} |
|
131 |
+ |
|
132 |
+ |
|
133 |
+colSummarizeMedianpolish <- function(y){ |
|
134 |
+ if (!is.matrix(y)) |
|
135 |
+ stop("argument should be matrix") |
|
136 |
+ |
|
137 |
+ if (!is.double(y) & is.numeric(y)) |
|
138 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
139 |
+ else if (!is.numeric(y)) |
|
140 |
+ stop("argument should be numeric matrix") |
|
141 |
+ |
|
142 |
+ .Call("R_colSummarize_medianpolish",y,PACKAGE="preprocessCore") |
|
143 |
+} |
|
144 |
+ |
|
145 |
+ |
|
146 |
+ |
0 | 147 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,108 @@ |
1 |
+################################################################## |
|
2 |
+## |
|
3 |
+## file: normalize.quantiles.R |
|
4 |
+## |
|
5 |
+## For a description of quantile normalization method see |
|
6 |
+## |
|
7 |
+## Bolstad, B. M., Irizarry R. A., Astrand, M, and Speed, T. P. (2003)(2003) |
|
8 |
+## A Comparison of Normalization Methods for High |
|
9 |
+## Density Oligonucleotide Array Data Based on Bias and Variance. |
|
10 |
+## Bioinformatics 19,2,pp 185-193 |
|
11 |
+## |
|
12 |
+## History |
|
13 |
+## Pre Aug 23, 2003 Two years worth of stuff |
|
14 |
+## Aug 23, 2003 - Added use.log2 to "robust", |
|
15 |
+## added ability to pass additional parameters |
|
16 |
+## to normalize.AffyBatch.Quantiles.robust |
|
17 |
+## changed pmonly parameters on functions |
|
18 |
+## so that it is now a string argument "type" |
|
19 |
+## the options are pmonly, mmonly, together, separate |
|
20 |
+## Jan 31, 2004 - put a check for an integer matrix and force coercision to |
|
21 |
+## doubles if required in normalize.quantiles |
|
22 |
+## Mar 13, 2005 - Modifications to normalize.quantiles.robust including removing |
|
23 |
+## approx.method which never got implemented. Making it a use a .Call() |
|
24 |
+## rather than a .C() |
|
25 |
+## |
|
26 |
+## Sep 20, 2006 - fix .Call in normalize.quantiles.robust |
|
27 |
+## May 20, 2007 - port to preprocessCore. Remove anything to do with AffyBatch Objects |
|
28 |
+## |
|
29 |
+################################################################## |
|
30 |
+ |
|
31 |
+normalize.quantiles <- function(x,copy=TRUE){ |
|
32 |
+ |
|
33 |
+ rows <- dim(x)[1] |
|
34 |
+ cols <- dim(x)[2] |
|
35 |
+ |
|
36 |
+ if (!is.matrix(x)){ |
|
37 |
+ stop("Matrix expected in normalize.quantiles") |
|
38 |
+ } |
|
39 |
+ |
|
40 |
+ if (is.integer(x)){ |
|
41 |
+ x <- matrix(as.double(x),rows,cols) |
|
42 |
+ copy <- FALSE |
|
43 |
+ } |
|
44 |
+ |
|
45 |
+ #matrix(.C("qnorm_c", as.double(as.vector(x)), as.integer(rows), as.integer(cols))[[1]], rows, cols) |
|
46 |
+ |
|
47 |
+## .Call("R_qnorm_c",x,copy, PACKAGE="preprocessCore"); |
|
48 |
+ .Call("R_qnorm_c_handleNA",x,copy, PACKAGE="preprocessCore"); |
|
49 |
+} |
|
50 |
+ |
|
51 |
+ |
|
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){ |
|
53 |
+ |
|
54 |
+ calc.var.ratios <- function(x){ |
|
55 |
+ cols <- dim(x)[2] |
|
56 |
+ vars <- apply(x,2,var) |
|
57 |
+ results <- matrix(0,cols,cols) |
|
58 |
+ for (i in 1:cols-1) |
|
59 |
+ for (j in (i+1):cols){ |
|
60 |
+ results[i,j] <- vars[i]/vars[j] |
|
61 |
+ results[j,i] <- vars[j]/vars[i] |
|
62 |
+ } |
|
63 |
+ results |
|
64 |
+ } |
|
65 |
+ |
|
66 |
+ calc.mean.dists <- function(x){ |
|
67 |
+ cols <- dim(x)[2] |
|
68 |
+ means <- colMeans(x) |
|
69 |
+ results <- matrix(0,cols,cols) |
|
70 |
+ for (i in 1:cols-1) |
|
71 |
+ for (j in (i+1):cols){ |
|
72 |
+ results[i,j] <- means[i] - means[j] |
|
73 |
+ results[j,i] <- means[j] - means[i] |
|
74 |
+ } |
|
75 |
+ results |
|
76 |
+ } |
|
77 |
+ |
|
78 |
+ use.huber <- FALSE |
|
79 |
+ remove.extreme <- match.arg(remove.extreme) |
|
80 |
+ |
|
81 |
+ rows <- dim(x)[1] |
|
82 |
+ cols <- dim(x)[2] |
|
83 |
+ |
|
84 |
+ if (is.null(weights)){ |
|
85 |
+ weights <- .Call("R_qnorm_robust_weights",x,remove.extreme,as.integer(n.remove),PACKAGE="preprocessCore") |
|
86 |
+ } else { |
|
87 |
+ if (is.numeric(weights)){ |
|
88 |
+ if (length(weights) != cols){ |
|
89 |
+ stop("Weights vector incorrect length\n") |
|
90 |
+ } |
|
91 |
+ if (sum(weights > 0) < 1){ |
|
92 |
+ stop("Need at least one non negative weights\n") |
|
93 |
+ } |
|
94 |
+ if (any(weights < 0)){ |
|
95 |
+ stop("Can't have negative weights") |
|
96 |
+ } |
|
97 |
+ } else { |
|
98 |
+ if (weights =="huber"){ |
|
99 |
+ use.huber <- TRUE |
|
100 |
+ weights <- rep(1,cols) |
|
101 |
+ } else { |
|
102 |
+ stop("Don't recognise weights argument as valid.") |
|
103 |
+ } |
|
104 |
+ } |
|
105 |
+ } |
|
106 |
+ |
|
107 |
+ .Call("R_qnorm_robust_c",x,copy,weights,as.integer(use.median),as.integer(use.log2),as.integer(use.huber),PACKAGE="preprocessCore") |
|
108 |
+} |
0 | 109 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,28 @@ |
1 |
+rcModelPLMd <- function(y,group.labels){ |
|
2 |
+ if (!is.matrix(y)) |
|
3 |
+ stop("argument should be matrix") |
|
4 |
+ |
|
5 |
+ if (length(group.labels) != ncol(y)){ |
|
6 |
+ stop("group labels is of incorrect length") |
|
7 |
+ } |
|
8 |
+ |
|
9 |
+ if (!is.factor(group.labels)){ |
|
10 |
+ group.labels <- as.factor(group.labels) |
|
11 |
+ } |
|
12 |
+ |
|
13 |
+ if (any(table(group.labels) < 2)){ |
|
14 |
+ stop("Must be at least two arrays in each group") |
|
15 |
+ } |
|
16 |
+ |
|
17 |
+ |
|
18 |
+ group.int <- as.integer(group.labels) -1 |
|
19 |
+ |
|
20 |
+ PsiCode <- 0 |
|
21 |
+ PsiK <- 1.345 |
|
22 |
+ |
|
23 |
+ |
|
24 |
+ .Call("R_plmd_model",y,PsiCode,PsiK,as.integer(group.int),as.integer(length(unique(group.labels))),PACKAGE="preprocessCore") |
|
25 |
+ |
|
26 |
+} |
|
27 |
+ |
|
28 |
+ |
0 | 29 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,106 @@ |
1 |
+rcModelPLMr <- function(y){ |
|
2 |
+ if (!is.matrix(y)) |
|
3 |
+ stop("argument should be matrix") |
|
4 |
+ PsiCode <- 0 |
|
5 |
+ PsiK <- 1.345 |
|
6 |
+ .Call("R_plmr_model",y,PsiCode,PsiK,PACKAGE="preprocessCore") |
|
7 |
+} |
|
8 |
+ |
|
9 |
+rcModelPLMrr <- function(y){ |
|
10 |
+ if (!is.matrix(y)) |
|
11 |
+ stop("argument should be matrix") |
|
12 |
+ PsiCode <- 0 |
|
13 |
+ PsiK <- 1.345 |
|
14 |
+ .Call("R_plmrr_model",y,PsiCode,PsiK,PACKAGE="preprocessCore") |
|
15 |
+} |
|
16 |
+ |
|
17 |
+ |
|
18 |
+rcModelPLMrc <- function(y){ |
|
19 |
+ if (!is.matrix(y)) |
|
20 |
+ stop("argument should be matrix") |
|
21 |
+ PsiCode <- 0 |
|
22 |
+ PsiK <- 1.345 |
|
23 |
+ .Call("R_plmrc_model",y,PsiCode,PsiK,PACKAGE="preprocessCore") |
|
24 |
+} |
|
25 |
+ |
|
26 |
+ |
|
27 |
+ |
|
28 |
+ |
|
29 |
+ |
|
30 |
+rcModelWPLMr <- function(y, w){ |
|
31 |
+ if (!is.matrix(y)) |
|
32 |
+ stop("argument should be matrix") |
|
33 |
+ if (is.vector(w)){ |
|
34 |
+ if (length(w) != prod(dim(y))){ |
|
35 |
+ stop("weights are not correct length") |
|
36 |
+ } |
|
37 |
+ } else if (is.matrix(w)){ |
|
38 |
+ if (!all(dim(w) == dim(y))){ |
|
39 |
+ stop("weights should be same dimension as input matrix") |
|
40 |
+ } |
|
41 |
+ |
|
42 |
+ } |
|
43 |
+ if (any(w < 0)){ |
|
44 |
+ stop("weights should be non negative") |
|
45 |
+ } |
|
46 |
+ |
|
47 |
+ |
|
48 |
+ |
|
49 |
+ PsiCode <- 0 |
|
50 |
+ PsiK <- 1.345 |
|
51 |
+ .Call("R_wplmr_model",y,PsiCode,PsiK,as.double(w),PACKAGE="preprocessCore") |
|
52 |
+ |
|
53 |
+} |
|
54 |
+ |
|
55 |
+ |
|
56 |
+rcModelWPLMrr <- function(y, w){ |
|
57 |
+ if (!is.matrix(y)) |
|
58 |
+ stop("argument should be matrix") |
|
59 |
+ if (is.vector(w)){ |
|
60 |
+ if (length(w) != prod(dim(y))){ |
|
61 |
+ stop("weights are not correct length") |
|
62 |
+ } |
|
63 |
+ } else if (is.matrix(w)){ |
|
64 |
+ if (!all(dim(w) == dim(y))){ |
|
65 |
+ stop("weights should be same dimension as input matrix") |
|
66 |
+ } |
|
67 |
+ |
|
68 |
+ } |
|
69 |
+ if (any(w < 0)){ |
|
70 |
+ stop("weights should be non negative") |
|
71 |
+ } |
|
72 |
+ |
|
73 |
+ |
|
74 |
+ |
|
75 |
+ PsiCode <- 0 |
|
76 |
+ PsiK <- 1.345 |
|
77 |
+ .Call("R_wplmrr_model",y,PsiCode,PsiK,as.double(w),PACKAGE="preprocessCore") |
|
78 |
+ |
|
79 |
+} |
|
80 |
+ |
|
81 |
+ |
|
82 |
+rcModelWPLMrc <- function(y, w){ |
|
83 |
+ if (!is.matrix(y)) |
|
84 |
+ stop("argument should be matrix") |
|
85 |
+ if (is.vector(w)){ |
|
86 |
+ if (length(w) != prod(dim(y))){ |
|
87 |
+ stop("weights are not correct length") |
|
88 |
+ } |
|
89 |
+ } else if (is.matrix(w)){ |
|
90 |
+ if (!all(dim(w) == dim(y))){ |
|
91 |
+ stop("weights should be same dimension as input matrix") |
|
92 |
+ } |
|
93 |
+ |
|
94 |
+ } |
|
95 |
+ if (any(w < 0)){ |
|
96 |
+ stop("weights should be non negative") |
|
97 |
+ } |
|
98 |
+ |
|
99 |
+ |
|
100 |
+ |
|
101 |
+ PsiCode <- 0 |
|
102 |
+ PsiK <- 1.345 |
|
103 |
+ .Call("R_wplmrc_model",y,PsiCode,PsiK,as.double(w),PACKAGE="preprocessCore") |
|
104 |
+ |
|
105 |
+} |
|
106 |
+ |
0 | 107 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,106 @@ |
1 |
+ |
|
2 |
+ |
|
3 |
+normalize.quantiles.determine.target <- function(x,target.length=NULL,subset=NULL){ |
|
4 |
+ |
|
5 |
+ if (!is.matrix(x)){ |
|
6 |
+ stop("This function expects supplied argument to be matrix") |
|
7 |
+ } |
|
8 |
+ if (!is.numeric(x)){ |
|
9 |
+ stop("Supplied argument should be a numeric matrix") |
|
10 |
+ } |
|
11 |
+ rows <- dim(x)[1] |
|
12 |
+ cols <- dim(x)[2] |
|
13 |
+ |
|
14 |
+ if (is.integer(x)){ |
|
15 |
+ x <- matrix(as.double(x), rows, cols) |
|
16 |
+ } |
|
17 |
+ |
|
18 |
+ if (is.null(target.length)){ |
|
19 |
+ target.length <- rows |
|
20 |
+ } |
|
21 |
+ |
|
22 |
+ if (target.length <= 0){ |
|
23 |
+ stop("Need positive length for target.length") |
|
24 |
+ } |
|
25 |
+ |
|
26 |
+ if (is.null(subset)){ |
|
27 |
+ return(.Call("R_qnorm_determine_target",x,target.length,PACKAGE="preprocessCore")) |
|
28 |
+ } else { |
|
29 |
+ if (length(subset) != rows){ |
|
30 |
+ stop("subset should have same length as nrows(x)") |
|
31 |
+ } |
|
32 |
+ subset <- as.integer(subset) |
|
33 |
+ return(.Call("R_qnorm_determine_target_via_subset",x, subset,target.length,PACKAGE="preprocessCore")) |
|
34 |
+ } |
|
35 |
+ |
|
36 |
+} |
|
37 |
+ |
|
38 |
+ |
|
39 |
+ |
|
40 |
+normalize.quantiles.use.target <- function(x,target,copy=TRUE,subset=NULL){ |
|
41 |
+ |
|
42 |
+ if (!is.matrix(x)){ |
|
43 |
+ stop("This function expects supplied argument to be matrix") |
|
44 |
+ } |
|
45 |
+ if (!is.numeric(x)){ |
|
46 |
+ stop("Supplied argument should be a numeric matrix") |
|
47 |
+ } |
|
48 |
+ rows <- dim(x)[1] |
|
49 |
+ cols <- dim(x)[2] |
|
50 |
+ |
|
51 |
+ if (is.integer(x)){ |
|
52 |
+ x <- matrix(as.double(x), rows, cols) |
|
53 |
+ } |
|
54 |
+ |
|
55 |
+ if (!is.vector(target)){ |
|
56 |
+ stop("This function expects target to be vector") |
|
57 |
+ } |
|
58 |
+ if (!is.numeric(target)){ |
|
59 |
+ stop("Supplied target argument should be a numeric vector") |
|
60 |
+ } |
|
61 |
+ |
|
62 |
+ if (is.integer(target)){ |
|
63 |
+ target <- as.double(target) |
|
64 |
+ } |
|
65 |
+ if (is.null(subset)){ |
|
66 |
+ return(.Call("R_qnorm_using_target",x,target,copy,PACKAGE="preprocessCore")) |
|
67 |
+ } else { |
|
68 |
+ if (length(subset) != rows){ |
|
69 |
+ stop("subset should have same length as nrows(x)") |
|
70 |
+ } |
|
71 |
+ subset <- as.integer(subset) |
|
72 |
+ return(.Call("R_qnorm_using_target_via_subset",x, subset, target, copy, PACKAGE="preprocessCore")) |
|
73 |
+ } |
|
74 |
+ |
|
75 |
+ |
|
76 |
+} |
|
77 |
+ |
|
78 |
+ |
|
79 |
+ |
|
80 |
+normalize.quantiles.in.blocks <- function(x,blocks,copy=TRUE){ |
|
81 |
+ |
|
82 |
+ rows <- dim(x)[1] |
|
83 |
+ cols <- dim(x)[2] |
|
84 |
+ |
|
85 |
+ if (rows != length(blocks)){ |
|
86 |
+ stop("blocks is not vector of correct length") |
|
87 |
+ } |
|
88 |
+ |
|
89 |
+ if (is.factor(blocks)){ |
|
90 |
+ blocks <- as.integer(blocks) |
|
91 |
+ } |
|
92 |
+ |
|
93 |
+ if (!is.numeric(blocks)){ |
|
94 |
+ stop("non-numeric vector used for blocks") |
|
95 |
+ } |
|
96 |
+ |
|
97 |
+ |
|
98 |
+ return(.Call("R_qnorm_within_blocks",x,blocks,copy,PACKAGE="preprocessCore")) |
|
99 |
+ |
|
100 |
+ |
|
101 |
+ |
|
102 |
+} |
|
103 |
+ |
|
104 |
+ |
|
105 |
+ |
|
106 |
+ |
0 | 107 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,125 @@ |
1 |
+ |
|
2 |
+ |
|
3 |
+ |
|
4 |
+rcModelPLM <- function(y,row.effects=NULL, input.scale=NULL){ |
|
5 |
+ if (!is.matrix(y)) |
|
6 |
+ stop("argument should be matrix") |
|
7 |
+ PsiCode <- 0 |
|
8 |
+ PsiK <- 1.345 |
|
9 |
+ if (is.null(row.effects)){ |
|
10 |
+ .Call("R_rlm_rma_default_model",y,PsiCode,PsiK,input.scale,PACKAGE="preprocessCore") |
|
11 |
+ } else { |
|
12 |
+ if (length(row.effects) != nrow(y)){ |
|
13 |
+ stop("row.effects parameter should be same length as number of rows") |
|
14 |
+ } |
|
15 |
+ if (abs(sum(row.effects)) > length(row.effects)*.Machine$double.eps){ |
|
16 |
+ stop("row.effects should sum to zero") |
|
17 |
+ } |
|
18 |
+ .Call("R_rlm_rma_given_probe_effects",y,as.double(row.effects),PsiCode,PsiK,input.scale,PACKAGE="preprocessCore") |
|
19 |
+ } |
|
20 |
+} |
|
21 |
+ |
|
22 |
+ |
|
23 |
+ |
|
24 |
+rcModelWPLM <- function(y, w, row.effects=NULL, input.scale=NULL){ |
|
25 |
+ if (!is.matrix(y)) |
|
26 |
+ stop("argument should be matrix") |
|
27 |
+ if (is.vector(w)){ |
|
28 |
+ if (length(w) != prod(dim(y))){ |
|
29 |
+ stop("weights are not correct length") |
|
30 |
+ } |
|
31 |
+ } else if (is.matrix(w)){ |
|
32 |
+ if (!all(dim(w) == dim(y))){ |
|
33 |
+ stop("weights should be same dimension as input matrix") |
|
34 |
+ } |
|
35 |
+ |
|
36 |
+ } |
|
37 |
+ if (any(w < 0)){ |
|
38 |
+ stop("weights should be no negative") |
|
39 |
+ } |
|
40 |
+ |
|
41 |
+ |
|
42 |
+ |
|
43 |
+ PsiCode <- 0 |
|
44 |
+ PsiK <- 1.345 |
|
45 |
+ if (is.null(row.effects)){ |
|
46 |
+ .Call("R_wrlm_rma_default_model",y,PsiCode,PsiK,as.double(w),input.scale,PACKAGE="preprocessCore") |
|
47 |
+ } else { |
|
48 |
+ if (length(row.effects) != nrow(y)){ |
|
49 |
+ stop("row.effects parameter should be same length as number of rows") |
|
50 |
+ } |
|
51 |
+ if (abs(sum(row.effects)) > length(row.effects)*.Machine$double.eps){ |
|
52 |
+ stop("row.effects should sum to zero") |
|
53 |
+ } |
|
54 |
+ .Call("R_wrlm_rma_given_probe_effects",y,as.double(row.effects),PsiCode,PsiK,as.double(w),input.scale,PACKAGE="preprocessCore") |
|
55 |
+ } |
|
56 |
+ |
|
57 |
+} |
|
58 |
+ |
|
59 |
+ |
|
60 |
+ |
|
61 |
+rcModelMedianPolish <- function(y){ |
|
62 |
+ if (!is.matrix(y)) |
|
63 |
+ stop("argument should be matrix") |
|
64 |
+ PsiCode <- 0 |
|
65 |
+ PsiK <- 1.345 |
|
66 |
+ .Call("R_medianpolish_rma_default_model",y,PACKAGE="preprocessCore") |
|
67 |
+} |
|
68 |
+ |
|
69 |
+ |
|
70 |
+ |
|
71 |
+ |
|
72 |
+subrcModelMedianPolish <- function(y,group.labels){ |
|
73 |
+ |
|
74 |
+ if (!is.matrix(y)) |
|
75 |
+ stop("argument should be matrix") |
|
76 |
+ |
|
77 |
+ if (!is.double(y) & is.numeric(y)) |
|
78 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
79 |
+ else if (!is.numeric(y)) |
|
80 |
+ stop("argument should be numeric matrix") |
|
81 |
+ |
|
82 |
+ rowIndexList <- convert.group.labels(group.labels) |
|
83 |
+ |
|
84 |
+ x <- .Call("R_sub_rcModelSummarize_medianpolish", y, rowIndexList,PACKAGE="preprocessCore") |
|
85 |
+ |
|
86 |
+ names(x) <- names(rowIndexList) |
|
87 |
+ x |
|
88 |
+} |
|
89 |
+ |
|
90 |
+ |
|
91 |
+ |
|
92 |
+ |
|
93 |
+ |
|
94 |
+subrcModelPLM <- function(y,group.labels,row.effects=NULL, input.scale=NULL){ |
|
95 |
+ |
|
96 |
+ if (!is.matrix(y)) |
|
97 |
+ stop("argument should be matrix") |
|
98 |
+ |
|
99 |
+ if (!is.double(y) & is.numeric(y)) |
|
100 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
101 |
+ else if (!is.numeric(y)) |
|
102 |
+ stop("argument should be numeric matrix") |
|
103 |
+ |
|
104 |
+ rowIndexList <- convert.group.labels(group.labels) |
|
105 |
+ |
|
106 |
+ PsiCode <- 0 |
|
107 |
+ PsiK <- 1.345 |
|
108 |
+ |
|
109 |
+ if (is.null(row.effects)){ |
|
110 |
+ x <- .Call("R_sub_rcModelSummarize_plm", y, rowIndexList, PsiCode, PsiK, input.scale,PACKAGE="preprocessCore") |
|
111 |
+ names(x) <- names(rowIndexList) |
|
112 |
+ x |
|
113 |
+ |
|
114 |
+ } else { |
|
115 |
+ stop("row.effects not yet implemented for subrcModelPLM") |
|
116 |
+ if (length(row.effects) != nrow(y)){ |
|
117 |
+ stop("row.effects parameter should be same length as number of rows") |
|
118 |
+ } |
|
119 |
+ if (abs(sum(row.effects)) > 10*.Machine$double.eps){ |
|
120 |
+ stop("row.effects should sum to zero") |
|
121 |
+ } |
|
122 |
+ .Call("R_rlm_rma_given_probe_effects",y,as.double(row.effects),PsiCode,PsiK,input.scale,PACKAGE="preprocessCore") |
|
123 |
+ } |
|
124 |
+} |
|
125 |
+ |
0 | 126 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,54 @@ |
1 |
+################################################################## |
|
2 |
+## |
|
3 |
+## file: rma.background.correct.R |
|
4 |
+## |
|
5 |
+## implements the normal boackground + exponential signal background |
|
6 |
+## correction traditionally used in RMA computations |
|
7 |
+## |
|
8 |
+## for more details see |
|
9 |
+## Bolstad, BM (2004) Low Level Analysis of High-density Oligonucleotide Array Data: Background, Normalization and Summarization. Dissertation. University of California, Berkeley. |
|
10 |
+## pages 17-21 |
|
11 |
+## |
|
12 |
+## |
|
13 |
+## History |
|
14 |
+## Mar 22, 2008 - Initial version (in preprocessCore) |
|
15 |
+## |
|
16 |
+## |
|
17 |
+ |
|
18 |
+rma.background.correct <- function(x,copy=TRUE){ |
|
19 |
+ |
|
20 |
+ rows <- dim(x)[1] |
|
21 |
+ cols <- dim(x)[2] |
|
22 |
+ |
|
23 |
+ if (!is.matrix(x)){ |
|
24 |
+ stop("Matrix expected in normalize.quantiles") |
|
25 |
+ } |
|
26 |
+ |
|
27 |
+ if (is.integer(x)){ |
|
28 |
+ x <- matrix(as.double(x),rows,cols) |
|
29 |
+ copy <- FALSE |
|
30 |
+ } |
|
31 |
+ |
|
32 |
+ .Call("R_rma_bg_correct", x, copy, PACKAGE="preprocessCore"); |
|
33 |
+} |
|
34 |
+ |
|
35 |
+ |
|
36 |
+ |
|
37 |
+ |
|
38 |
+ |
|
39 |
+ |
|
40 |
+ |
|
41 |
+ |
|
42 |
+ |
|
43 |
+ |
|
44 |
+ |
|
45 |
+ |
|
46 |
+ |
|
47 |
+ |
|
48 |
+ |
|
49 |
+ |
|
50 |
+ |
|
51 |
+ |
|
52 |
+ |
|
53 |
+ |
|
54 |
+ |
0 | 55 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,218 @@ |
1 |
+## |
|
2 |
+## file: subColSummarize.R |
|
3 |
+## |
|
4 |
+## Author: B. M. Bolstad <bmb@bmbolstad.com> |
|
5 |
+## |
|
6 |
+## History |
|
7 |
+## Sept 18, 2007 - Initial verison |
|
8 |
+## Dec 10, 2007 - add rownames to output |
|
9 |
+## |
|
10 |
+ |
|
11 |
+ |
|
12 |
+convert.group.labels <- function(group.labels){ |
|
13 |
+ |
|
14 |
+ if (!is.factor(group.labels)) |
|
15 |
+ group.labels <- as.factor(group.labels) |
|
16 |
+ |
|
17 |
+ split(0:(length(group.labels) -1),group.labels) |
|
18 |
+ |
|
19 |
+} |
|
20 |
+ |
|
21 |
+ |
|
22 |
+ |
|
23 |
+ |
|
24 |
+subColSummarizeAvgLog <- function(y, group.labels){ |
|
25 |
+ if (!is.matrix(y)) |
|
26 |
+ stop("argument should be matrix") |
|
27 |
+ |
|
28 |
+ if (!is.double(y) & is.numeric(y)) |
|
29 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
30 |
+ else if (!is.numeric(y)) |
|
31 |
+ stop("argument should be numeric matrix") |
|
32 |
+ |
|
33 |
+ rowIndexList <- convert.group.labels(group.labels) |
|
34 |
+ |
|
35 |
+ x <- .Call("R_subColSummarize_avg_log", y, rowIndexList, PACKAGE="preprocessCore") |
|
36 |
+ |
|
37 |
+ rownames(x) <- names(rowIndexList) |
|
38 |
+ x |
|
39 |
+} |
|
40 |
+ |
|
41 |
+ |
|
42 |
+ |
|
43 |
+ |
|
44 |
+ |
|
45 |
+subColSummarizeLogAvg <- function(y, group.labels){ |
|
46 |
+ if (!is.matrix(y)) |
|
47 |
+ stop("argument should be matrix") |
|
48 |
+ |
|
49 |
+ if (!is.double(y) & is.numeric(y)) |
|
50 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
51 |
+ else if (!is.numeric(y)) |
|
52 |
+ stop("argument should be numeric matrix") |
|
53 |
+ |
|
54 |
+ rowIndexList <- convert.group.labels(group.labels) |
|
55 |
+ |
|
56 |
+ x <- .Call("R_subColSummarize_log_avg", y, rowIndexList, PACKAGE="preprocessCore") |
|
57 |
+ rownames(x) <- names(rowIndexList) |
|
58 |
+ x |
|
59 |
+} |
|
60 |
+ |
|
61 |
+ |
|
62 |
+ |
|
63 |
+ |
|
64 |
+subColSummarizeAvg <- function(y, group.labels){ |
|
65 |
+ if (!is.matrix(y)) |
|
66 |
+ stop("argument should be matrix") |
|
67 |
+ |
|
68 |
+ if (!is.double(y) & is.numeric(y)) |
|
69 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
70 |
+ else if (!is.numeric(y)) |
|
71 |
+ stop("argument should be numeric matrix") |
|
72 |
+ |
|
73 |
+ rowIndexList <- convert.group.labels(group.labels) |
|
74 |
+ |
|
75 |
+ x <- .Call("R_subColSummarize_avg", y, rowIndexList, PACKAGE="preprocessCore") |
|
76 |
+ rownames(x) <- names(rowIndexList) |
|
77 |
+ x |
|
78 |
+ |
|
79 |
+} |
|
80 |
+ |
|
81 |
+ |
|
82 |
+ |
|
83 |
+ |
|
84 |
+subColSummarizeBiweightLog <- function(y, group.labels){ |
|
85 |
+ if (!is.matrix(y)) |
|
86 |
+ stop("argument should be matrix") |
|
87 |
+ |
|
88 |
+ if (!is.double(y) & is.numeric(y)) |
|
89 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
90 |
+ else if (!is.numeric(y)) |
|
91 |
+ stop("argument should be numeric matrix") |
|
92 |
+ |
|
93 |
+ rowIndexList <- convert.group.labels(group.labels) |
|
94 |
+ |
|
95 |
+ x <- .Call("R_subColSummarize_biweight_log", y, rowIndexList, PACKAGE="preprocessCore") |
|
96 |
+ rownames(x) <- names(rowIndexList) |
|
97 |
+ x |
|
98 |
+} |
|
99 |
+ |
|
100 |
+ |
|
101 |
+ |
|
102 |
+ |
|
103 |
+subColSummarizeBiweight <- function(y, group.labels){ |
|
104 |
+ if (!is.matrix(y)) |
|
105 |
+ stop("argument should be matrix") |
|
106 |
+ |
|
107 |
+ if (!is.double(y) & is.numeric(y)) |
|
108 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
109 |
+ else if (!is.numeric(y)) |
|
110 |
+ stop("argument should be numeric matrix") |
|
111 |
+ |
|
112 |
+ rowIndexList <- convert.group.labels(group.labels) |
|
113 |
+ |
|
114 |
+ x <- .Call("R_subColSummarize_biweight", y, rowIndexList, PACKAGE="preprocessCore") |
|
115 |
+ rownames(x) <- names(rowIndexList) |
|
116 |
+ x |
|
117 |
+ |
|
118 |
+ |
|
119 |
+} |
|
120 |
+ |
|
121 |
+ |
|
122 |
+ |
|
123 |
+ |
|
124 |
+ |
|
125 |
+subColSummarizeMedianLog <- function(y, group.labels){ |
|
126 |
+ if (!is.matrix(y)) |
|
127 |
+ stop("argument should be matrix") |
|
128 |
+ |
|
129 |
+ if (!is.double(y) & is.numeric(y)) |
|
130 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
131 |
+ else if (!is.numeric(y)) |
|
132 |
+ stop("argument should be numeric matrix") |
|
133 |
+ |
|
134 |
+ rowIndexList <- convert.group.labels(group.labels) |
|
135 |
+ |
|
136 |
+ x <- .Call("R_subColSummarize_median_log", y, rowIndexList, PACKAGE="preprocessCore") |
|
137 |
+ rownames(x) <- names(rowIndexList) |
|
138 |
+ x |
|
139 |
+} |
|
140 |
+ |
|
141 |
+ |
|
142 |
+ |
|
143 |
+ |
|
144 |
+ |
|
145 |
+subColSummarizeLogMedian <- function(y, group.labels){ |
|
146 |
+ if (!is.matrix(y)) |
|
147 |
+ stop("argument should be matrix") |
|
148 |
+ |
|
149 |
+ if (!is.double(y) & is.numeric(y)) |
|
150 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
151 |
+ else if (!is.numeric(y)) |
|
152 |
+ stop("argument should be numeric matrix") |
|
153 |
+ |
|
154 |
+ rowIndexList <- convert.group.labels(group.labels) |
|
155 |
+ |
|
156 |
+ x <- .Call("R_subColSummarize_log_median", y, rowIndexList, PACKAGE="preprocessCore") |
|
157 |
+ rownames(x) <- names(rowIndexList) |
|
158 |
+ x |
|
159 |
+} |
|
160 |
+ |
|
161 |
+ |
|
162 |
+ |
|
163 |
+ |
|
164 |
+subColSummarizeMedian <- function(y, group.labels){ |
|
165 |
+ if (!is.matrix(y)) |
|
166 |
+ stop("argument should be matrix") |
|
167 |
+ |
|
168 |
+ if (!is.double(y) & is.numeric(y)) |
|
169 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
170 |
+ else if (!is.numeric(y)) |
|
171 |
+ stop("argument should be numeric matrix") |
|
172 |
+ |
|
173 |
+ rowIndexList <- convert.group.labels(group.labels) |
|
174 |
+ |
|
175 |
+ x <- .Call("R_subColSummarize_median", y, rowIndexList, PACKAGE="preprocessCore") |
|
176 |
+ rownames(x) <- names(rowIndexList) |
|
177 |
+ x |
|
178 |
+} |
|
179 |
+ |
|
180 |
+ |
|
181 |
+ |
|
182 |
+ |
|
183 |
+ |
|
184 |
+ |
|
185 |
+ |
|
186 |
+subColSummarizeMedianpolishLog <- function(y, group.labels){ |
|
187 |
+ if (!is.matrix(y)) |
|
188 |
+ stop("argument should be matrix") |
|
189 |
+ |
|
190 |
+ if (!is.double(y) & is.numeric(y)) |
|
191 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
192 |
+ else if (!is.numeric(y)) |
|
193 |
+ stop("argument should be numeric matrix") |
|
194 |
+ |
|
195 |
+ rowIndexList <- convert.group.labels(group.labels) |
|
196 |
+ |
|
197 |
+ x <- .Call("R_subColSummarize_medianpolish_log", y, rowIndexList, PACKAGE="preprocessCore") |
|
198 |
+ rownames(x) <- names(rowIndexList) |
|
199 |
+ x |
|
200 |
+} |
|
201 |
+ |
|
202 |
+ |
|
203 |
+subColSummarizeMedianpolish <- function(y, group.labels){ |
|
204 |
+ if (!is.matrix(y)) |
|
205 |
+ stop("argument should be matrix") |
|
206 |
+ |
|
207 |
+ if (!is.double(y) & is.numeric(y)) |
|
208 |
+ y <- matrix(as.double(y),dim(y)[1],dim(y)[2]) |
|
209 |
+ else if (!is.numeric(y)) |
|
210 |
+ stop("argument should be numeric matrix") |
|
211 |
+ |
|
212 |
+ rowIndexList <- convert.group.labels(group.labels) |
|
213 |
+ |
|
214 |
+ x <- .Call("R_subColSummarize_medianpolish", y, rowIndexList, PACKAGE="preprocessCore") |
|
215 |
+ rownames(x) <- names(rowIndexList) |
|
216 |
+ x |
|
217 |
+} |
|
218 |
+ |
0 | 219 |
new file mode 100755 |
... | ... |
@@ -0,0 +1,4497 @@ |
1 |
+#! /bin/sh |
|
2 |
+# Guess values for system-dependent variables and create Makefiles. |
|
3 |
+# Generated by GNU Autoconf 2.68. |
|
4 |
+# |
|
5 |
+# |
|
6 |
+# Copyright (C) 1992, 1993, 1994, 1995, 1996, 1998, 1999, 2000, 2001, |
|
7 |
+# 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010 Free Software |
|
8 |
+# Foundation, Inc. |
|
9 |
+# |
|
10 |
+# |
|
11 |
+# This configure script is free software; the Free Software Foundation |
|
12 |
+# gives unlimited permission to copy, distribute and modify it. |
|
13 |
+## -------------------- ## |
|
14 |
+## M4sh Initialization. ## |
|
15 |
+## -------------------- ## |
|
16 |
+ |
|
17 |
+# Be more Bourne compatible |
|
18 |
+DUALCASE=1; export DUALCASE # for MKS sh |
|
19 |
+if test -n "${ZSH_VERSION+set}" && (emulate sh) >/dev/null 2>&1; then : |
|
20 |
+ emulate sh |
|
21 |
+ NULLCMD=: |
|
22 |
+ # Pre-4.2 versions of Zsh do word splitting on ${1+"$@"}, which |
|
23 |
+ # is contrary to our usage. Disable this feature. |
|
24 |
+ alias -g '${1+"$@"}'='"$@"' |
|
25 |
+ setopt NO_GLOB_SUBST |
|
26 |
+else |
|
27 |
+ case `(set -o) 2>/dev/null` in #( |
|
28 |
+ *posix*) : |
|
29 |
+ set -o posix ;; #( |
|
30 |
+ *) : |
|
31 |
+ ;; |
|
32 |
+esac |
|
33 |
+fi |
|
34 |
+ |
|
35 |
+ |
|
36 |
+as_nl=' |
|
37 |
+' |
|
38 |
+export as_nl |
|
39 |
+# Printing a long string crashes Solaris 7 /usr/bin/printf. |
|
40 |
+as_echo='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' |
|
41 |
+as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo |
|
42 |
+as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo$as_echo |
|
43 |
+# Prefer a ksh shell builtin over an external printf program on Solaris, |
|
44 |
+# but without wasting forks for bash or zsh. |
|
45 |
+if test -z "$BASH_VERSION$ZSH_VERSION" \ |
|
46 |
+ && (test "X`print -r -- $as_echo`" = "X$as_echo") 2>/dev/null; then |
|
47 |
+ as_echo='print -r --' |
|
48 |
+ as_echo_n='print -rn --' |
|
49 |
+elif (test "X`printf %s $as_echo`" = "X$as_echo") 2>/dev/null; then |
|
50 |
+ as_echo='printf %s\n' |
|
51 |
+ as_echo_n='printf %s' |
|
52 |
+else |
|
53 |
+ if test "X`(/usr/ucb/echo -n -n $as_echo) 2>/dev/null`" = "X-n $as_echo"; then |
|
54 |
+ as_echo_body='eval /usr/ucb/echo -n "$1$as_nl"' |
|
55 |
+ as_echo_n='/usr/ucb/echo -n' |
|
56 |
+ else |
|
57 |
+ as_echo_body='eval expr "X$1" : "X\\(.*\\)"' |
|
58 |
+ as_echo_n_body='eval |
|
59 |
+ arg=$1; |
|
60 |
+ case $arg in #( |
|
61 |
+ *"$as_nl"*) |
|
62 |
+ expr "X$arg" : "X\\(.*\\)$as_nl"; |
|
63 |
+ arg=`expr "X$arg" : ".*$as_nl\\(.*\\)"`;; |
|
64 |
+ esac; |
|
65 |
+ expr "X$arg" : "X\\(.*\\)" | tr -d "$as_nl" |
|
66 |
+ ' |
|
67 |
+ export as_echo_n_body |
|
68 |
+ as_echo_n='sh -c $as_echo_n_body as_echo' |
|
69 |
+ fi |
|
70 |
+ export as_echo_body |
|
71 |
+ as_echo='sh -c $as_echo_body as_echo' |
|
72 |
+fi |
|
73 |
+ |
|
74 |
+# The user is always right. |
|
75 |
+if test "${PATH_SEPARATOR+set}" != set; then |
|
76 |
+ PATH_SEPARATOR=: |
|
77 |
+ (PATH='/bin;/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 && { |
|
78 |
+ (PATH='/bin:/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 || |
|
79 |
+ PATH_SEPARATOR=';' |
|
80 |
+ } |
|
81 |
+fi |
|
82 |
+ |
|
83 |
+ |
|
84 |
+# IFS |
|
85 |
+# We need space, tab and new line, in precisely that order. Quoting is |
|
86 |
+# there to prevent editors from complaining about space-tab. |
|
87 |
+# (If _AS_PATH_WALK were called with IFS unset, it would disable word |
|
88 |
+# splitting by setting IFS to empty value.) |
|
89 |
+IFS=" "" $as_nl" |
|
90 |
+ |
|
91 |
+# Find who we are. Look in the path if we contain no directory separator. |
|
92 |
+as_myself= |
|
93 |
+case $0 in #(( |
|
94 |
+ *[\\/]* ) as_myself=$0 ;; |
|
95 |
+ *) as_save_IFS=$IFS; IFS=$PATH_SEPARATOR |
|
96 |
+for as_dir in $PATH |
|
97 |
+do |
|
98 |
+ IFS=$as_save_IFS |
|
99 |
+ test -z "$as_dir" && as_dir=. |
|
100 |
+ test -r "$as_dir/$0" && as_myself=$as_dir/$0 && break |
|
101 |
+ done |
|
102 |
+IFS=$as_save_IFS |
|
103 |
+ |
|
104 |
+ ;; |
|
105 |
+esac |
|
106 |
+# We did not find ourselves, most probably we were run as `sh COMMAND' |
|
107 |
+# in which case we are not to be found in the path. |
|
108 |
+if test "x$as_myself" = x; then |
|
109 |
+ as_myself=$0 |
|
110 |
+fi |
|
111 |
+if test ! -f "$as_myself"; then |
|
112 |
+ $as_echo "$as_myself: error: cannot find myself; rerun with an absolute file name" >&2 |
|
113 |
+ exit 1 |
|
114 |
+fi |
|
115 |
+ |
|
116 |
+# Unset variables that we do not need and which cause bugs (e.g. in |
|
117 |
+# pre-3.0 UWIN ksh). But do not cause bugs in bash 2.01; the "|| exit 1" |
|
118 |
+# suppresses any "Segmentation fault" message there. '((' could |
|
119 |
+# trigger a bug in pdksh 5.2.14. |
|
120 |
+for as_var in BASH_ENV ENV MAIL MAILPATH |
|
121 |
+do eval test x\${$as_var+set} = xset \ |
|
122 |
+ && ( (unset $as_var) || exit 1) >/dev/null 2>&1 && unset $as_var || : |
|
123 |
+done |
|
124 |
+PS1='$ ' |
|
125 |
+PS2='> ' |
|
126 |
+PS4='+ ' |
|
127 |
+ |
|
128 |
+# NLS nuisances. |
|
129 |
+LC_ALL=C |
|
130 |
+export LC_ALL |
|
131 |
+LANGUAGE=C |
|
132 |
+export LANGUAGE |
|
133 |
+ |
|
134 |
+# CDPATH. |
|
135 |
+(unset CDPATH) >/dev/null 2>&1 && unset CDPATH |
|
136 |
+ |
|
137 |
+if test "x$CONFIG_SHELL" = x; then |
|
138 |
+ as_bourne_compatible="if test -n \"\${ZSH_VERSION+set}\" && (emulate sh) >/dev/null 2>&1; then : |
|
139 |
+ emulate sh |
|
140 |
+ NULLCMD=: |
|
141 |
+ # Pre-4.2 versions of Zsh do word splitting on \${1+\"\$@\"}, which |
|
142 |
+ # is contrary to our usage. Disable this feature. |
|
143 |
+ alias -g '\${1+\"\$@\"}'='\"\$@\"' |
|
144 |
+ setopt NO_GLOB_SUBST |
|
145 |
+else |
|
146 |
+ case \`(set -o) 2>/dev/null\` in #( |
|
147 |
+ *posix*) : |
|
148 |
+ set -o posix ;; #( |
|
149 |
+ *) : |
|
150 |
+ ;; |
|
151 |
+esac |
|
152 |
+fi |
|
153 |
+" |
|
154 |
+ as_required="as_fn_return () { (exit \$1); } |
|
155 |
+as_fn_success () { as_fn_return 0; } |
|
156 |
+as_fn_failure () { as_fn_return 1; } |
|
157 |
+as_fn_ret_success () { return 0; } |
|
158 |
+as_fn_ret_failure () { return 1; } |
|
159 |
+ |
|
160 |
+exitcode=0 |
|
161 |
+as_fn_success || { exitcode=1; echo as_fn_success failed.; } |
|
162 |
+as_fn_failure && { exitcode=1; echo as_fn_failure succeeded.; } |
|
163 |
+as_fn_ret_success || { exitcode=1; echo as_fn_ret_success failed.; } |
|
164 |
+as_fn_ret_failure && { exitcode=1; echo as_fn_ret_failure succeeded.; } |
|
165 |
+if ( set x; as_fn_ret_success y && test x = \"\$1\" ); then : |
|
166 |
+ |
|
167 |
+else |
|
168 |
+ exitcode=1; echo positional parameters were not saved. |
|
169 |
+fi |
|
170 |
+test x\$exitcode = x0 || exit 1" |
|
171 |
+ as_suggested=" as_lineno_1=";as_suggested=$as_suggested$LINENO;as_suggested=$as_suggested" as_lineno_1a=\$LINENO |
|
172 |
+ as_lineno_2=";as_suggested=$as_suggested$LINENO;as_suggested=$as_suggested" as_lineno_2a=\$LINENO |
|
173 |
+ eval 'test \"x\$as_lineno_1'\$as_run'\" != \"x\$as_lineno_2'\$as_run'\" && |
|
174 |
+ test \"x\`expr \$as_lineno_1'\$as_run' + 1\`\" = \"x\$as_lineno_2'\$as_run'\"' || exit 1 |
|
175 |
+test \$(( 1 + 1 )) = 2 || exit 1" |
|
176 |
+ if (eval "$as_required") 2>/dev/null; then : |
|
177 |
+ as_have_required=yes |
|
178 |
+else |
|
179 |
+ as_have_required=no |
|
180 |
+fi |
|
181 |
+ if test x$as_have_required = xyes && (eval "$as_suggested") 2>/dev/null; then : |
|
182 |
+ |
|
183 |
+else |
|
184 |
+ as_save_IFS=$IFS; IFS=$PATH_SEPARATOR |
|
185 |
+as_found=false |
|
186 |
+for as_dir in /bin$PATH_SEPARATOR/usr/bin$PATH_SEPARATOR$PATH |
|
187 |
+do |
|
188 |
+ IFS=$as_save_IFS |
|
189 |
+ test -z "$as_dir" && as_dir=. |
|
190 |
+ as_found=: |
|
191 |
+ case $as_dir in #( |
|
192 |
+ /*) |
|
193 |
+ for as_base in sh bash ksh sh5; do |
|
194 |
+ # Try only shells that exist, to save several forks. |
|
195 |
+ as_shell=$as_dir/$as_base |
|
196 |
+ if { test -f "$as_shell" || test -f "$as_shell.exe"; } && |
|
197 |
+ { $as_echo "$as_bourne_compatible""$as_required" | as_run=a "$as_shell"; } 2>/dev/null; then : |
|
198 |
+ CONFIG_SHELL=$as_shell as_have_required=yes |
|
199 |
+ if { $as_echo "$as_bourne_compatible""$as_suggested" | as_run=a "$as_shell"; } 2>/dev/null; then : |
|
200 |
+ break 2 |
|
201 |
+fi |
|
202 |
+fi |
|
203 |
+ done;; |
|
204 |
+ esac |
|
205 |
+ as_found=false |
|
206 |
+done |
|
207 |
+$as_found || { if { test -f "$SHELL" || test -f "$SHELL.exe"; } && |
|
208 |
+ { $as_echo "$as_bourne_compatible""$as_required" | as_run=a "$SHELL"; } 2>/dev/null; then : |
|
209 |
+ CONFIG_SHELL=$SHELL as_have_required=yes |
|
210 |
+fi; } |
|
211 |
+IFS=$as_save_IFS |
|
212 |
+ |
|
213 |
+ |
|
214 |
+ if test "x$CONFIG_SHELL" != x; then : |
|
215 |
+ # We cannot yet assume a decent shell, so we have to provide a |
|
216 |
+ # neutralization value for shells without unset; and this also |
|
217 |
+ # works around shells that cannot unset nonexistent variables. |
|
218 |
+ # Preserve -v and -x to the replacement shell. |
|
219 |
+ BASH_ENV=/dev/null |
|
220 |
+ ENV=/dev/null |
|
221 |
+ (unset BASH_ENV) >/dev/null 2>&1 && unset BASH_ENV ENV |
|
222 |
+ export CONFIG_SHELL |
|
223 |
+ case $- in # (((( |
|
224 |
+ *v*x* | *x*v* ) as_opts=-vx ;; |
|
225 |
+ *v* ) as_opts=-v ;; |
|
226 |
+ *x* ) as_opts=-x ;; |
|
227 |
+ * ) as_opts= ;; |
|
228 |
+ esac |
|
229 |
+ exec "$CONFIG_SHELL" $as_opts "$as_myself" ${1+"$@"} |
|
230 |
+fi |
|
231 |
+ |
|
232 |
+ if test x$as_have_required = xno; then : |
|
233 |
+ $as_echo "$0: This script requires a shell more modern than all" |
|
234 |
+ $as_echo "$0: the shells that I found on your system." |
|
235 |
+ if test x${ZSH_VERSION+set} = xset ; then |
|
236 |
+ $as_echo "$0: In particular, zsh $ZSH_VERSION has bugs and should" |
|
237 |
+ $as_echo "$0: be upgraded to zsh 4.3.4 or later." |
|
238 |
+ else |
|
239 |
+ $as_echo "$0: Please tell bug-autoconf@gnu.org about your system, |
|
240 |
+$0: including any error possibly output before this |
|
241 |
+$0: message. Then install a modern shell, or manually run |
|
242 |
+$0: the script under such a shell if you do have one." |
|
243 |
+ fi |
|
244 |
+ exit 1 |
|
245 |
+fi |
|
246 |
+fi |
|
247 |
+fi |
|
248 |
+SHELL=${CONFIG_SHELL-/bin/sh} |
|
249 |
+export SHELL |
|
250 |
+# Unset more variables known to interfere with behavior of common tools. |
|
251 |
+CLICOLOR_FORCE= GREP_OPTIONS= |
|
252 |
+unset CLICOLOR_FORCE GREP_OPTIONS |
|
253 |
+ |
|
254 |
+## --------------------- ## |
|
255 |
+## M4sh Shell Functions. ## |
|
256 |
+## --------------------- ## |
|
257 |
+# as_fn_unset VAR |
|
258 |
+# --------------- |
|
259 |
+# Portably unset VAR. |
|
260 |
+as_fn_unset () |
|
261 |
+{ |
|
262 |
+ { eval $1=; unset $1;} |
|
263 |
+} |
|
264 |
+as_unset=as_fn_unset |
|
265 |
+ |
|
266 |
+# as_fn_set_status STATUS |
|
267 |
+# ----------------------- |
|
268 |
+# Set $? to STATUS, without forking. |
|
269 |
+as_fn_set_status () |
|
270 |
+{ |
|
271 |
+ return $1 |
|
272 |
+} # as_fn_set_status |
|
273 |
+ |
|
274 |
+# as_fn_exit STATUS |
|
275 |
+# ----------------- |
|
276 |
+# Exit the shell with STATUS, even in a "trap 0" or "set -e" context. |
|
277 |
+as_fn_exit () |
|
278 |
+{ |
|
279 |
+ set +e |
|
280 |
+ as_fn_set_status $1 |
|
281 |
+ exit $1 |
|
282 |
+} # as_fn_exit |
|
283 |
+ |
|
284 |
+# as_fn_mkdir_p |
|
285 |
+# ------------- |
|
286 |
+# Create "$as_dir" as a directory, including parents if necessary. |
|
287 |
+as_fn_mkdir_p () |
|
288 |
+{ |
|
289 |
+ |
|
290 |
+ case $as_dir in #( |
|
291 |
+ -*) as_dir=./$as_dir;; |
|
292 |
+ esac |
|
293 |
+ test -d "$as_dir" || eval $as_mkdir_p || { |
|
294 |
+ as_dirs= |
|
295 |
+ while :; do |
|
296 |
+ case $as_dir in #( |
|
297 |
+ *\'*) as_qdir=`$as_echo "$as_dir" | sed "s/'/'\\\\\\\\''/g"`;; #'( |
|
298 |
+ *) as_qdir=$as_dir;; |
|
299 |
+ esac |
|
300 |
+ as_dirs="'$as_qdir' $as_dirs" |
|
301 |
+ as_dir=`$as_dirname -- "$as_dir" || |
|
302 |
+$as_expr X"$as_dir" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ |
|
303 |
+ X"$as_dir" : 'X\(//\)[^/]' \| \ |
|
304 |
+ X"$as_dir" : 'X\(//\)$' \| \ |
|
305 |
+ X"$as_dir" : 'X\(/\)' \| . 2>/dev/null || |
|
306 |
+$as_echo X"$as_dir" | |
|
307 |
+ sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ |
|
308 |
+ s//\1/ |
|
309 |
+ q |
|
310 |
+ } |
|
311 |
+ /^X\(\/\/\)[^/].*/{ |
|
312 |
+ s//\1/ |
|
313 |
+ q |
|
314 |
+ } |
|
315 |
+ /^X\(\/\/\)$/{ |
|
316 |
+ s//\1/ |
|
317 |
+ q |
|
318 |
+ } |
|
319 |
+ /^X\(\/\).*/{ |
|
320 |
+ s//\1/ |
|
321 |
+ q |
|
322 |
+ } |
|
323 |
+ s/.*/./; q'` |
|
324 |
+ test -d "$as_dir" && break |
|
325 |
+ done |
|
326 |
+ test -z "$as_dirs" || eval "mkdir $as_dirs" |
|
327 |
+ } || test -d "$as_dir" || as_fn_error $? "cannot create directory $as_dir" |
|
328 |
+ |
|
329 |
+ |
|
330 |
+} # as_fn_mkdir_p |
|
331 |
+# as_fn_append VAR VALUE |
|
332 |
+# ---------------------- |
|
333 |
+# Append the text in VALUE to the end of the definition contained in VAR. Take |
|