Browse code

setting up git-svn bridge

Bioconductor Git-SVN Bridge authored on 31/08/2014 21:28:19
Showing 1 changed files
1 1
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
+