...
|
...
|
@@ -3,7 +3,7 @@
|
3
|
3
|
|
4
|
4
|
setClass("DEGs",
|
5
|
5
|
representation(
|
6
|
|
- DEGs.table="matrix", method="character",
|
|
6
|
+ DEGs.table="matrix", method="character",
|
7
|
7
|
significance.threshold="numeric", FC.threshold="numeric",
|
8
|
8
|
label.level.DEGs="character", label.condition="character"
|
9
|
9
|
)
|
...
|
...
|
@@ -13,52 +13,52 @@ setClass("DEGs",
|
13
|
13
|
## Generics declaration (getters, setters and methods)
|
14
|
14
|
###############################################################################
|
15
|
15
|
|
16
|
|
-setGeneric("DEGs.table", signature="object",
|
|
16
|
+setGeneric("DEGs.table", signature="object",
|
17
|
17
|
function(object) standardGeneric("DEGs.table"))
|
18
|
|
-
|
19
|
|
-setGeneric("getDEGsMethod", signature="object",
|
|
18
|
+
|
|
19
|
+setGeneric("getDEGsMethod", signature="object",
|
20
|
20
|
function(object) standardGeneric("getDEGsMethod"))
|
21
|
21
|
|
22
|
|
-setGeneric("significance.threshold", signature="object",
|
|
22
|
+setGeneric("significance.threshold", signature="object",
|
23
|
23
|
function(object) standardGeneric("significance.threshold"))
|
24
|
|
-
|
25
|
|
-setGeneric("FC.threshold", signature="object",
|
|
24
|
+
|
|
25
|
+setGeneric("FC.threshold", signature="object",
|
26
|
26
|
function(object) standardGeneric("FC.threshold"))
|
27
|
|
-
|
28
|
|
-setGeneric("label.level.DEGs", signature="object",
|
|
27
|
+
|
|
28
|
+setGeneric("label.level.DEGs", signature="object",
|
29
|
29
|
function(object) standardGeneric("label.level.DEGs"))
|
30
|
|
-
|
31
|
|
-setGeneric("label.condition", signature="object",
|
|
30
|
+
|
|
31
|
+setGeneric("label.condition", signature="object",
|
32
|
32
|
function(object) standardGeneric("label.condition"))
|
33
|
33
|
|
34
|
|
-setGeneric("MAplot", signature="object",
|
35
|
|
- function(object, outputformat="on screen",track="")
|
|
34
|
+setGeneric("MAplot", signature="object",
|
|
35
|
+ function(object, outputformat="on screen",track="")
|
36
|
36
|
standardGeneric("MAplot"))
|
37
|
|
-
|
38
|
|
-setGeneric("CVplot", signature="object",
|
39
|
|
- function(object, outputformat="on screen",track="")
|
|
37
|
+
|
|
38
|
+setGeneric("CVplot", signature="object",
|
|
39
|
+ function(object, outputformat="on screen",track="")
|
40
|
40
|
standardGeneric("CVplot"))
|
41
|
|
-
|
42
|
|
-setGeneric("SDplot", signature="object",
|
43
|
|
- function(object, outputformat="on screen",track="")
|
|
41
|
+
|
|
42
|
+setGeneric("SDplot", signature="object",
|
|
43
|
+ function(object, outputformat="on screen",track="")
|
44
|
44
|
standardGeneric("SDplot"))
|
45
|
|
-
|
46
|
|
-setGeneric("Histogram", signature="object",
|
47
|
|
- function(object, plottype="summary", outputformat="on screen")
|
|
45
|
+
|
|
46
|
+setGeneric("Histogram", signature="object",
|
|
47
|
+ function(object, plottype="summary", outputformat="on screen")
|
48
|
48
|
standardGeneric("Histogram"))
|
49
|
|
-
|
|
49
|
+
|
50
|
50
|
setGeneric("Scatterplot", signature="object",
|
51
|
|
- function(object, outputformat="on screen",track="")
|
|
51
|
+ function(object, outputformat="on screen",track="")
|
52
|
52
|
standardGeneric("Scatterplot"))
|
53
|
|
-
|
54
|
|
-setGeneric("GOEnrichment", signature="object",
|
55
|
|
- function(object, ontology="all",
|
|
53
|
+
|
|
54
|
+setGeneric("GOEnrichment", signature="object",
|
|
55
|
+ function(object, ontology="all",
|
56
|
56
|
classOfDEGs="both", test.method="classic",
|
57
|
|
- test.threshold = 0.05, mult.cor=TRUE)
|
|
57
|
+ test.threshold = 0.05, mult.cor=TRUE)
|
58
|
58
|
standardGeneric("GOEnrichment"))
|
59
|
|
-
|
60
|
|
-setGeneric("RegulatoryEnrichment", signature="object",
|
61
|
|
- function(object, classOfDEGs="both",
|
|
59
|
+
|
|
60
|
+setGeneric("RegulatoryEnrichment", signature="object",
|
|
61
|
+ function(object, classOfDEGs="both",
|
62
|
62
|
significance.threshold = 0.05, mult.cor=TRUE, regulated.identities=NULL, regulated.counts=NULL)
|
63
|
63
|
standardGeneric("RegulatoryEnrichment"))
|
64
|
64
|
|
...
|
...
|
@@ -127,13 +127,13 @@ setMethod("CVplot", "DEGs",
|
127
|
127
|
c <- grep(c("avg"), colnames(resultMatrix),value=TRUE)
|
128
|
128
|
b <- grep(c("sd"), colnames(resultMatrix),value=TRUE)
|
129
|
129
|
|
130
|
|
- vector1 <- rowMeans(resultMatrix[,b[1:2]]) /
|
|
130
|
+ vector1 <- rowMeans(resultMatrix[,b[1:2]]) /
|
131
|
131
|
abs(rowMeans(resultMatrix[,c[1:2]]))
|
132
|
|
- vector2 <- resultMatrix[,a[1]]
|
|
132
|
+ vector2 <- resultMatrix[,a[1]]
|
133
|
133
|
|
134
|
134
|
vector3 <- rowMeans(resultMatrix[,b[3:4]]) /
|
135
|
135
|
abs(rowMeans(resultMatrix[,c[3:4]]))
|
136
|
|
- vector4 <- resultMatrix[,a[2]]
|
|
136
|
+ vector4 <- resultMatrix[,a[2]]
|
137
|
137
|
|
138
|
138
|
xlabel <- "CV"
|
139
|
139
|
ylabel <- "log2 FC"
|
...
|
...
|
@@ -142,13 +142,13 @@ setMethod("CVplot", "DEGs",
|
142
|
142
|
if (outputformat == "postscript") postscript(file="CVplot.ps")
|
143
|
143
|
if (outputformat == "jpeg") jpeg(filename="CVplot.jpeg")
|
144
|
144
|
|
145
|
|
- par(fig=c(0,1,0,1), mar=c(4,4,1,2), mgp=c(2, 0.75, 0))
|
|
145
|
+ par(fig=c(0,1,0,1), mar=c(4,4,1,2), mgp=c(2, 0.75, 0))
|
146
|
146
|
layout(matrix(c(1,2), 2, 1, byrow = TRUE))
|
147
|
|
- plot(vector1, vector2, xlab=xlabel, ylab=ylabel,
|
148
|
|
- col="grey", pch=20, frame.plot=TRUE,cex=0.8,
|
|
147
|
+ plot(vector1, vector2, xlab=xlabel, ylab=ylabel,
|
|
148
|
+ col="grey", pch=20, frame.plot=TRUE,cex=0.8,
|
149
|
149
|
main=substr(a[1], 10, nchar(a[1])-1))
|
150
|
150
|
|
151
|
|
- list1 <- rownames(resultMatrix)[which(resultMatrix[,"level1Up"]==1 |
|
|
151
|
+ list1 <- rownames(resultMatrix)[which(resultMatrix[,"level1Up"]==1 |
|
152
|
152
|
resultMatrix[,"level1Down"]==1)]
|
153
|
153
|
variable <- which(rownames(resultMatrix) %in% list1)
|
154
|
154
|
color <- "steelblue3"
|
...
|
...
|
@@ -163,12 +163,12 @@ setMethod("CVplot", "DEGs",
|
163
|
163
|
text(vector1[variable],vector2[variable],labels=listm,pos=3,cex=0.7)
|
164
|
164
|
}
|
165
|
165
|
|
166
|
|
- plot(vector3, vector4, xlab=xlabel, ylab=ylabel,
|
|
166
|
+ plot(vector3, vector4, xlab=xlabel, ylab=ylabel,
|
167
|
167
|
col="grey", pch=20, frame.plot=TRUE,cex=0.8,
|
168
|
168
|
main=substr(a[2], 10, nchar(a[2])-1))
|
169
|
169
|
abline(h=0,lty=2,col="darkgray")
|
170
|
170
|
|
171
|
|
- list2 <- rownames(resultMatrix)[which(resultMatrix[,"level2Up"]==1 |
|
|
171
|
+ list2 <- rownames(resultMatrix)[which(resultMatrix[,"level2Up"]==1 |
|
172
|
172
|
resultMatrix[,"level2Down"]==1)]
|
173
|
173
|
variable <- which(rownames(resultMatrix) %in% list2)
|
174
|
174
|
color <- "gold1"
|
...
|
...
|
@@ -197,10 +197,10 @@ setMethod("MAplot", "DEGs",
|
197
|
197
|
b <- grep(c("avg"),colnames(resultMatrix),value=TRUE)
|
198
|
198
|
|
199
|
199
|
vector1 <- rowMeans(resultMatrix[,b[1:2]])
|
200
|
|
- vector2 <- resultMatrix[,a[1]]
|
|
200
|
+ vector2 <- resultMatrix[,a[1]]
|
201
|
201
|
|
202
|
202
|
vector3 <- rowMeans(resultMatrix[,b[3:4]])
|
203
|
|
- vector4 <- resultMatrix[,a[2]]
|
|
203
|
+ vector4 <- resultMatrix[,a[2]]
|
204
|
204
|
|
205
|
205
|
xlabel="log2 avg signal (A)"
|
206
|
206
|
ylabel="log2 FC (M)"
|
...
|
...
|
@@ -209,13 +209,13 @@ setMethod("MAplot", "DEGs",
|
209
|
209
|
if (outputformat == "postscript") postscript(file="MAplot.DEGs.ps")
|
210
|
210
|
if (outputformat == "jpeg") jpeg(filename="MAplot.DEGs.jpeg")
|
211
|
211
|
|
212
|
|
- par(fig=c(0,1,0,1), mar=c(4,4,1,2), mgp=c(2, 0.75, 0))
|
|
212
|
+ par(fig=c(0,1,0,1), mar=c(4,4,1,2), mgp=c(2, 0.75, 0))
|
213
|
213
|
layout(matrix(c(1,2), 2, 1, byrow = TRUE))
|
214
|
|
- plot(vector1, vector2, xlab=xlabel, ylab=ylabel,
|
215
|
|
- col="grey", pch=20, frame.plot=TRUE, cex=0.8,
|
|
214
|
+ plot(vector1, vector2, xlab=xlabel, ylab=ylabel,
|
|
215
|
+ col="grey", pch=20, frame.plot=TRUE, cex=0.8,
|
216
|
216
|
main=substr(a[1], 10, nchar(a[1])-1))
|
217
|
217
|
|
218
|
|
- list1 <- rownames(resultMatrix)[which(resultMatrix[,"level1Up"]==1 |
|
|
218
|
+ list1 <- rownames(resultMatrix)[which(resultMatrix[,"level1Up"]==1 |
|
219
|
219
|
resultMatrix[,"level1Down"]==1)]
|
220
|
220
|
variable <- which(rownames(resultMatrix) %in% list1)
|
221
|
221
|
color <- "steelblue3"
|
...
|
...
|
@@ -230,12 +230,12 @@ setMethod("MAplot", "DEGs",
|
230
|
230
|
text(vector1[variable],vector2[variable],labels=listm,pos=3,cex=0.7)
|
231
|
231
|
}
|
232
|
232
|
|
233
|
|
- plot(vector3, vector4, xlab=xlabel, ylab=ylabel,
|
|
233
|
+ plot(vector3, vector4, xlab=xlabel, ylab=ylabel,
|
234
|
234
|
col="grey", pch=20, frame.plot=TRUE,cex=0.8,
|
235
|
235
|
main=substr(a[2], 10, nchar(a[2])-1))
|
236
|
236
|
abline(h=0,lty=2,col="darkgray")
|
237
|
237
|
|
238
|
|
- list2 <- rownames(resultMatrix)[which(resultMatrix[,"level2Up"]==1 |
|
|
238
|
+ list2 <- rownames(resultMatrix)[which(resultMatrix[,"level2Up"]==1 |
|
239
|
239
|
resultMatrix[,"level2Down"]==1)]
|
240
|
240
|
variable <- which(rownames(resultMatrix) %in% list2)
|
241
|
241
|
color <- "gold1"
|
...
|
...
|
@@ -278,21 +278,21 @@ setMethod("Histogram", "DEGs",
|
278
|
278
|
if (outputformat == "pdf") pdf(file="Histogram.DEGs.pdf")
|
279
|
279
|
if (outputformat == "postscript") postscript(file="Histogram.DEGs.ps")
|
280
|
280
|
if (outputformat == "jpeg") jpeg(filename="Histogram.DEGs.jpeg")
|
281
|
|
-
|
|
281
|
+
|
282
|
282
|
if (plottype=="summary") {
|
283
|
283
|
inputforsummaryplot <- matrix(c(length(list1stlevelUP),
|
284
|
|
- length(list1stlevelDOWN),
|
285
|
|
- length(list2ndlevelUP),
|
|
284
|
+ length(list1stlevelDOWN),
|
|
285
|
+ length(list2ndlevelUP),
|
286
|
286
|
length(list2ndlevelDOWN),
|
287
|
287
|
0, 0), nrow=2, byrow=FALSE)
|
288
|
288
|
|
289
|
289
|
par(fig=c(0, 1, 0, 1), mar=c(4, 5, 4, 2), mgp=c(2, 0.75, 0))
|
290
|
290
|
barplot(as.table(inputforsummaryplot), xlab="number of DEGs",
|
291
|
|
- names.arg=c(substr(a[1], 10, nchar(a[1])-1),
|
292
|
|
- substr(a[2], 10, nchar(a[2])-1),""),
|
293
|
|
- col=c("grey25","grey75"), las=1,
|
294
|
|
- border=NA, horiz=TRUE, beside=FALSE)
|
295
|
|
-
|
|
291
|
+ names.arg=c(substr(a[1], 10, nchar(a[1])-1),
|
|
292
|
+ substr(a[2], 10, nchar(a[2])-1),""),
|
|
293
|
+ col=c("grey25","grey75"), las=1,
|
|
294
|
+ border=NA, horiz=TRUE, beside=FALSE)
|
|
295
|
+
|
296
|
296
|
legend("topright", c("up", "down"), fill=c("grey25", "grey75"), bty="n")
|
297
|
297
|
}
|
298
|
298
|
|
...
|
...
|
@@ -303,19 +303,19 @@ setMethod("Histogram", "DEGs",
|
303
|
303
|
length(list1stlevelDOWN) - (length(listDOWNDOWN) + length(listDOWNUP)),
|
304
|
304
|
length(list2ndlevelUP) - (length(listUPUP) + length(listDOWNUP)),
|
305
|
305
|
length(list2ndlevelDOWN) - (length(listDOWNDOWN) + length(listUPDOWN)),
|
306
|
|
- length(listUPUP), length(listDOWNDOWN),
|
|
306
|
+ length(listUPUP), length(listDOWNDOWN),
|
307
|
307
|
length(listUPDOWN), length(listDOWNUP)),
|
308
|
308
|
nrow=1, byrow=FALSE)
|
309
|
|
-
|
|
309
|
+
|
310
|
310
|
par(fig=c(0,1,0,1), mar=c(4,7,4,2), mgp=c(2, 0.75, 0))
|
311
|
311
|
barplot(as.table(inputfordetailedplot),
|
312
|
|
- names.arg= c("up / -","down / -","- / up","- / down",
|
|
312
|
+ names.arg= c("up / -","down / -","- / up","- / down",
|
313
|
313
|
"up / up","down / down","up / down","down / up"),
|
314
|
314
|
las=1,border=NA,horiz=TRUE,
|
315
|
|
- col=c("steelblue","steelblue4","gold","orange",
|
|
315
|
+ col=c("steelblue","steelblue4","gold","orange",
|
316
|
316
|
"chartreuse","chartreuse4","red","red3"),
|
317
|
317
|
beside=TRUE,xlab="number of DEGs")
|
318
|
|
-
|
|
318
|
+
|
319
|
319
|
mtext(paste(substr(a[1], 10, nchar(a[1])-1),
|
320
|
320
|
substr(a[2], 10, nchar(a[2])-1), sep="/"),
|
321
|
321
|
adj=0, line=0, cex=1)
|
...
|
...
|
@@ -325,15 +325,15 @@ setMethod("Histogram", "DEGs",
|
325
|
325
|
if (!(outputformat == "on screen")) dev.off()
|
326
|
326
|
}
|
327
|
327
|
)
|
328
|
|
-
|
329
|
|
-
|
330
|
|
-## Implementation of the Scatterplot method
|
|
328
|
+
|
|
329
|
+
|
|
330
|
+## Implementation of the Scatterplot method
|
331
|
331
|
setMethod("Scatterplot", "DEGs",
|
332
|
332
|
function(object, outputformat="on screen", track="") {
|
333
|
|
-
|
|
333
|
+
|
334
|
334
|
resultMatrix <- DEGs.table(object)
|
335
|
335
|
a <- grep(c("FC"), colnames(resultMatrix), value=TRUE)
|
336
|
|
-
|
|
336
|
+
|
337
|
337
|
vector1 <- resultMatrix[,a[1]]
|
338
|
338
|
vector2 <- resultMatrix[,a[2]]
|
339
|
339
|
|
...
|
...
|
@@ -347,31 +347,31 @@ setMethod("Scatterplot", "DEGs",
|
347
|
347
|
if (outputformat == "postscript") postscript(file="Scatterplot.DEGs.ps")
|
348
|
348
|
if (outputformat == "jpeg") jpeg(filename="Scatterplot.DEGs.jpeg")
|
349
|
349
|
|
350
|
|
- plot(originalFCvalX, originalFCvalY, xlab=xlabel, ylab=ylabel,
|
|
350
|
+ plot(originalFCvalX, originalFCvalY, xlab=xlabel, ylab=ylabel,
|
351
|
351
|
col="grey", pch=20, frame.plot=TRUE, cex=0.8, log="xy")
|
352
|
352
|
|
353
|
|
- mtext(paste("Spearman all:",
|
|
353
|
+ mtext(paste("Spearman all:",
|
354
|
354
|
round(cor.test(vector1, vector2, method="spearman")$estimate, 2),
|
355
|
355
|
" "),
|
356
|
356
|
side=1, adj=1, line=-2.5, cex=0.8)
|
357
|
357
|
|
358
|
|
- list0 <- rownames(resultMatrix)[c(which(resultMatrix[,"level1Up"]==1),
|
|
358
|
+ list0 <- rownames(resultMatrix)[c(which(resultMatrix[,"level1Up"]==1),
|
359
|
359
|
which(resultMatrix[,"level1Down"]==1),
|
360
|
|
- which(resultMatrix[,"level2Up"]==1),
|
|
360
|
+ which(resultMatrix[,"level2Up"]==1),
|
361
|
361
|
which(resultMatrix[,"level2Down"]==1))]
|
362
|
362
|
variable <- which(rownames(resultMatrix)%in%list0)
|
363
|
363
|
|
364
|
364
|
if (length(list0)>1)
|
365
|
365
|
mtext(paste("Spearman DEGs:",
|
366
|
|
- round(cor.test(vector1[list0],
|
|
366
|
+ round(cor.test(vector1[list0],
|
367
|
367
|
vector2[list0],
|
368
|
368
|
method="spearman")$estimate, 2),
|
369
|
|
- " "),
|
|
369
|
+ " "),
|
370
|
370
|
side=1, adj=1, line=-1.5, cex=0.8)
|
371
|
371
|
|
372
|
372
|
leg <- NULL
|
373
|
373
|
leg.col <- NULL
|
374
|
|
- list1 <- rownames(resultMatrix)[which(resultMatrix[,"level1Up"]==1 |
|
|
374
|
+ list1 <- rownames(resultMatrix)[which(resultMatrix[,"level1Up"]==1 |
|
375
|
375
|
resultMatrix[,"level1Down"]==1)]
|
376
|
376
|
variable <- which(rownames(resultMatrix) %in% list1)
|
377
|
377
|
color <- "steelblue3"
|
...
|
...
|
@@ -380,11 +380,11 @@ setMethod("Scatterplot", "DEGs",
|
380
|
380
|
leg <- c(leg, paste(substr(a[1], 10, nchar(a[1])-1), "only"))
|
381
|
381
|
leg.col <- c(leg.col, color)
|
382
|
382
|
|
383
|
|
- list2 <- rownames(resultMatrix)[which(resultMatrix[,"level2Up"]==1 |
|
|
383
|
+ list2 <- rownames(resultMatrix)[which(resultMatrix[,"level2Up"]==1 |
|
384
|
384
|
resultMatrix[,"level2Down"]==1)]
|
385
|
385
|
variable <- which(rownames(resultMatrix) %in% list2)
|
386
|
386
|
color <- "gold1"
|
387
|
|
- points(originalFCvalX[variable], originalFCvalY[variable],
|
|
387
|
+ points(originalFCvalX[variable], originalFCvalY[variable],
|
388
|
388
|
col=color, pch=20, cex=0.8)
|
389
|
389
|
leg <- c(leg, paste(substr(a[2], 10, nchar(a[2])-1), "only"))
|
390
|
390
|
leg.col <- c(leg.col, color)
|
...
|
...
|
@@ -393,12 +393,12 @@ setMethod("Scatterplot", "DEGs",
|
393
|
393
|
resultMatrix[,"DownDown"]==1)]
|
394
|
394
|
variable <- which(rownames(resultMatrix) %in% list3)
|
395
|
395
|
color <- "chartreuse3"
|
396
|
|
- points(originalFCvalX[variable], originalFCvalY[variable],
|
|
396
|
+ points(originalFCvalX[variable], originalFCvalY[variable],
|
397
|
397
|
col=color, pch=20, cex=0.8)
|
398
|
398
|
leg <- c(leg, "homodirectional")
|
399
|
399
|
leg.col <- c(leg.col, color)
|
400
|
400
|
|
401
|
|
- list4 <- rownames(resultMatrix)[which(resultMatrix[,"UpDown"]==1 |
|
|
401
|
+ list4 <- rownames(resultMatrix)[which(resultMatrix[,"UpDown"]==1 |
|
402
|
402
|
resultMatrix[,"DownUp"]==1)]
|
403
|
403
|
variable <- which(rownames(resultMatrix) %in% list4)
|
404
|
404
|
color <- "red2"
|
...
|
...
|
@@ -414,9 +414,9 @@ setMethod("Scatterplot", "DEGs",
|
414
|
414
|
listm <- rownames(resultMatrix)[rownames(resultMatrix) %in% track]
|
415
|
415
|
if (length(listm) > 0) {
|
416
|
416
|
variable <- which(rownames(resultMatrix) %in% track)
|
417
|
|
- points(originalFCvalX[variable], originalFCvalY[variable],
|
|
417
|
+ points(originalFCvalX[variable], originalFCvalY[variable],
|
418
|
418
|
col="white", pch=4, cex=0.5)
|
419
|
|
- text(originalFCvalX[variable], originalFCvalY[variable],
|
|
419
|
+ text(originalFCvalX[variable], originalFCvalY[variable],
|
420
|
420
|
labels=listm, pos=3, cex=0.7)
|
421
|
421
|
}
|
422
|
422
|
|
...
|
...
|
@@ -429,16 +429,16 @@ setMethod("Scatterplot", "DEGs",
|
429
|
429
|
## Implementation of the SDplot method
|
430
|
430
|
setMethod("SDplot", "DEGs",
|
431
|
431
|
function(object, outputformat="on screen", track="") {
|
432
|
|
-
|
|
432
|
+
|
433
|
433
|
resultMatrix <- DEGs.table(object)
|
434
|
434
|
a <- grep(c("FC"), colnames(resultMatrix), value=TRUE)
|
435
|
435
|
b <- grep(c("sd"), colnames(resultMatrix), value=TRUE)
|
436
|
436
|
|
437
|
437
|
vector1 <- rowMeans(resultMatrix[,b[1:2]])
|
438
|
|
- vector2 <- resultMatrix[,a[1]]
|
|
438
|
+ vector2 <- resultMatrix[,a[1]]
|
439
|
439
|
|
440
|
440
|
vector3 <- rowMeans(resultMatrix[,b[3:4]])
|
441
|
|
- vector4 <- resultMatrix[,a[2]]
|
|
441
|
+ vector4 <- resultMatrix[,a[2]]
|
442
|
442
|
|
443
|
443
|
xlabel="SD"
|
444
|
444
|
ylabel="log2 FC"
|
...
|
...
|
@@ -446,18 +446,18 @@ setMethod("SDplot", "DEGs",
|
446
|
446
|
if (outputformat == "pdf") pdf(file="SDplot.DEGs.pdf")
|
447
|
447
|
if (outputformat == "ps") postscript(file="SDplot.DEGs.ps")
|
448
|
448
|
if (outputformat == "jpeg") jpeg(filename="SDplot.DEGs.jpeg")
|
449
|
|
-
|
450
|
|
- par(fig=c(0,1,0,1), mar=c(4,4,1,2), mgp=c(2, 0.75, 0))
|
|
449
|
+
|
|
450
|
+ par(fig=c(0,1,0,1), mar=c(4,4,1,2), mgp=c(2, 0.75, 0))
|
451
|
451
|
layout(matrix(c(1,2), 2, 1, byrow = TRUE))
|
452
|
|
- plot(vector1, vector2, xlab=xlabel, ylab=ylabel,
|
|
452
|
+ plot(vector1, vector2, xlab=xlabel, ylab=ylabel,
|
453
|
453
|
col="grey", pch=20, frame.plot=TRUE,cex=0.8,
|
454
|
454
|
main=substr(a[1], 10, nchar(a[1])-1))
|
455
|
455
|
|
456
|
|
- list1 <- rownames(resultMatrix)[which(resultMatrix[,"level1Up"]==1 |
|
|
456
|
+ list1 <- rownames(resultMatrix)[which(resultMatrix[,"level1Up"]==1 |
|
457
|
457
|
resultMatrix[,"level1Down"]==1)]
|
458
|
458
|
variable <- which(rownames(resultMatrix) %in% list1)
|
459
|
459
|
color <- "steelblue3"
|
460
|
|
- points(vector1[variable], vector2[variable],
|
|
460
|
+ points(vector1[variable], vector2[variable],
|
461
|
461
|
col=color, pch=20, cex=0.8)
|
462
|
462
|
abline(h=0, lty=2, col="darkgray")
|
463
|
463
|
legend("topright", c("DEGs"), fill=c(color), bty="n", cex=0.8)
|
...
|
...
|
@@ -469,12 +469,12 @@ setMethod("SDplot", "DEGs",
|
469
|
469
|
text(vector1[variable], vector2[variable], labels=listm, pos=3, cex=0.7)
|
470
|
470
|
}
|
471
|
471
|
|
472
|
|
- plot(vector3, vector4, xlab=xlabel, ylab=ylabel,
|
|
472
|
+ plot(vector3, vector4, xlab=xlabel, ylab=ylabel,
|
473
|
473
|
col="grey", pch=20, frame.plot=TRUE, cex=0.8,
|
474
|
474
|
main=substr(a[2], 10, nchar(a[2])-1))
|
475
|
475
|
abline(h=0, lty=2, col="darkgray")
|
476
|
476
|
|
477
|
|
- list2 <- rownames(resultMatrix)[which(resultMatrix[,"level2Up"]==1 |
|
|
477
|
+ list2 <- rownames(resultMatrix)[which(resultMatrix[,"level2Up"]==1 |
|
478
|
478
|
resultMatrix[,"level2Down"]==1)]
|
479
|
479
|
variable <- which(rownames(resultMatrix) %in% list2)
|
480
|
480
|
color <- "gold1"
|
...
|
...
|
@@ -486,7 +486,7 @@ setMethod("SDplot", "DEGs",
|
486
|
486
|
listm <- rownames(resultMatrix)[rownames(resultMatrix) %in% track]
|
487
|
487
|
if (length(listm) > 0) {
|
488
|
488
|
variable <- which(rownames(resultMatrix) %in% track)
|
489
|
|
- points(vector3[variable], vector4[variable],
|
|
489
|
+ points(vector3[variable], vector4[variable],
|
490
|
490
|
col="white", pch=4, cex=0.5)
|
491
|
491
|
text(vector3[variable], vector4[variable], labels=listm, pos=3, cex=0.7)
|
492
|
492
|
}
|
...
|
...
|
@@ -499,26 +499,26 @@ setMethod("SDplot", "DEGs",
|
499
|
499
|
|
500
|
500
|
## Implementation of the GOenrichment method
|
501
|
501
|
setMethod("GOEnrichment", "DEGs",
|
502
|
|
- function(object, ontology="all", classOfDEGs="both", test.method="classic",
|
|
502
|
+ function(object, ontology="all", classOfDEGs="both", test.method="classic",
|
503
|
503
|
test.threshold = 0.05, mult.cor=TRUE) {
|
504
|
|
-
|
|
504
|
+
|
505
|
505
|
resultMatrix <- DEGs.table(object)
|
506
|
506
|
a <- grep(c("FC"), colnames(resultMatrix), value=TRUE)
|
507
|
507
|
|
508
|
508
|
myInterestedGenes1stlevel <- rownames(resultMatrix)[
|
509
|
|
- which(resultMatrix[,"level1Up"]==1 |
|
|
509
|
+ which(resultMatrix[,"level1Up"]==1 |
|
510
|
510
|
resultMatrix[,"level1Down"]==1)]
|
511
|
511
|
myInterestedGenes2ndlevel <- rownames(resultMatrix)[
|
512
|
|
- which(resultMatrix[,"level2Up"]==1 |
|
|
512
|
+ which(resultMatrix[,"level2Up"]==1 |
|
513
|
513
|
resultMatrix[,"level2Down"]==1)]
|
514
|
|
-
|
|
514
|
+
|
515
|
515
|
if (classOfDEGs == "up") {
|
516
|
516
|
myInterestedGenes1stlevel <- rownames(resultMatrix)[
|
517
|
517
|
which(resultMatrix[,"level1Up"]==1)]
|
518
|
518
|
myInterestedGenes2ndlevel <- rownames(resultMatrix)[
|
519
|
519
|
which(resultMatrix[,"level2Up"]==1)]
|
520
|
520
|
}
|
521
|
|
-
|
|
521
|
+
|
522
|
522
|
if (classOfDEGs == "down") {
|
523
|
523
|
myInterestedGenes1stlevel <- rownames(resultMatrix)[
|
524
|
524
|
which(resultMatrix[,"level1Down"]==1)]
|
...
|
...
|
@@ -526,7 +526,7 @@ setMethod("GOEnrichment", "DEGs",
|
526
|
526
|
which(resultMatrix[,"level2Down"]==1)]
|
527
|
527
|
}
|
528
|
528
|
|
529
|
|
- if (length(myInterestedGenes1stlevel) == 0 &&
|
|
529
|
+ if (length(myInterestedGenes1stlevel) == 0 &&
|
530
|
530
|
length(myInterestedGenes2ndlevel) == 0) {
|
531
|
531
|
print("There are no genes selected for enrichment analysis.")
|
532
|
532
|
print("Please try to use a less stringent gene filter.")
|
...
|
...
|
@@ -537,47 +537,47 @@ setMethod("GOEnrichment", "DEGs",
|
537
|
537
|
substr(a[2], 10, nchar(a[2])-1))
|
538
|
538
|
|
539
|
539
|
# Choice of the ontology
|
540
|
|
-
|
|
540
|
+
|
541
|
541
|
if (ontology != "all") {
|
542
|
|
- onto.first <- createspecifictable(background,
|
543
|
|
- myInterestedGenes1stlevel, ontology,
|
544
|
|
- test.method, test.threshold, mult.cor,
|
|
542
|
+ onto.first <- createspecifictable(background,
|
|
543
|
+ myInterestedGenes1stlevel, ontology,
|
|
544
|
+ test.method, test.threshold, mult.cor,
|
545
|
545
|
label.level.DEGs[1])
|
546
|
|
-
|
|
546
|
+
|
547
|
547
|
onto.second <- createspecifictable(background,
|
548
|
|
- myInterestedGenes2ndlevel, ontology,
|
549
|
|
- test.method, test.threshold, mult.cor,
|
|
548
|
+ myInterestedGenes2ndlevel, ontology,
|
|
549
|
+ test.method, test.threshold, mult.cor,
|
550
|
550
|
label.level.DEGs[2])
|
551
|
|
-
|
|
551
|
+
|
552
|
552
|
final.table <- rbind(onto.first, onto.second)
|
553
|
|
-
|
554
|
|
- allRes <- new("GOsets", enriched.table = final.table,
|
|
553
|
+
|
|
554
|
+ allRes <- new("GOsets", enriched.table = final.table,
|
555
|
555
|
label.level.enriched = label.level.DEGs)
|
556
|
|
- }
|
557
|
|
- else {
|
558
|
|
- BP.first <- createspecifictable(background, myInterestedGenes1stlevel,
|
559
|
|
- "BP", test.method, test.threshold,
|
|
556
|
+ }
|
|
557
|
+ else {
|
|
558
|
+ BP.first <- createspecifictable(background, myInterestedGenes1stlevel,
|
|
559
|
+ "BP", test.method, test.threshold,
|
560
|
560
|
mult.cor, label.level.DEGs[1])
|
561
|
|
- MF.first <- createspecifictable(background, myInterestedGenes1stlevel,
|
|
561
|
+ MF.first <- createspecifictable(background, myInterestedGenes1stlevel,
|
562
|
562
|
"MF", test.method, test.threshold,
|
563
|
563
|
mult.cor, label.level.DEGs[1])
|
564
|
|
- CC.first <- createspecifictable(background, myInterestedGenes1stlevel,
|
|
564
|
+ CC.first <- createspecifictable(background, myInterestedGenes1stlevel,
|
565
|
565
|
"CC", test.method, test.threshold,
|
566
|
566
|
mult.cor, label.level.DEGs[1])
|
567
|
|
-
|
568
|
|
- BP.second <- createspecifictable(background, myInterestedGenes2ndlevel,
|
|
567
|
+
|
|
568
|
+ BP.second <- createspecifictable(background, myInterestedGenes2ndlevel,
|
569
|
569
|
"BP", test.method, test.threshold,
|
570
|
570
|
mult.cor, label.level.DEGs[2])
|
571
|
|
- MF.second <- createspecifictable(background, myInterestedGenes2ndlevel,
|
|
571
|
+ MF.second <- createspecifictable(background, myInterestedGenes2ndlevel,
|
572
|
572
|
"MF", test.method, test.threshold,
|
573
|
573
|
mult.cor, label.level.DEGs[2])
|
574
|
574
|
CC.second <- createspecifictable(background, myInterestedGenes2ndlevel,
|
575
|
575
|
"CC", test.method, test.threshold,
|
576
|
576
|
mult.cor, label.level.DEGs[2])
|
577
|
577
|
|
578
|
|
- final.table <- rbind(BP.first, MF.first, CC.first,
|
|
578
|
+ final.table <- rbind(BP.first, MF.first, CC.first,
|
579
|
579
|
BP.second, MF.second, CC.second)
|
580
|
|
- allRes <- new("GOsets", enriched.table=final.table,
|
|
580
|
+ allRes <- new("GOsets", enriched.table=final.table,
|
581
|
581
|
label.level.enriched=label.level.DEGs)
|
582
|
582
|
}
|
583
|
583
|
}
|
...
|
...
|
@@ -587,30 +587,30 @@ setMethod("GOEnrichment", "DEGs",
|
587
|
587
|
|
588
|
588
|
|
589
|
589
|
## Implementation of the RegulatoryEnrichment method
|
590
|
|
-setMethod("RegulatoryEnrichment", "DEGs",
|
591
|
|
- function(object, classOfDEGs="both",
|
|
590
|
+setMethod("RegulatoryEnrichment", "DEGs",
|
|
591
|
+ function(object, classOfDEGs="both",
|
592
|
592
|
significance.threshold= 0.05, mult.cor=TRUE, regulated.identities=NULL, regulated.counts=NULL) {
|
593
|
|
-
|
|
593
|
+
|
594
|
594
|
resultMatrix <- DEGs.table(object)
|
595
|
595
|
label.fc <- grep(c("FC"), colnames(resultMatrix), value=TRUE)
|
596
|
596
|
label.level.DEGs <- c(substr(label.fc[1], 10, nchar(label.fc[1])-1),
|
597
|
597
|
substr(label.fc[2], 10, nchar(label.fc[2])-1))
|
598
|
598
|
|
599
|
|
-
|
|
599
|
+
|
600
|
600
|
genes.1stlevel <- rownames(resultMatrix)[
|
601
|
|
- which(resultMatrix[,"level1Up"]==1 |
|
|
601
|
+ which(resultMatrix[,"level1Up"]==1 |
|
602
|
602
|
resultMatrix[,"level1Down"]==1)]
|
603
|
603
|
genes.2ndlevel <- rownames(resultMatrix)[
|
604
|
|
- which(resultMatrix[,"level2Up"]==1 |
|
|
604
|
+ which(resultMatrix[,"level2Up"]==1 |
|
605
|
605
|
resultMatrix[,"level2Down"]==1)]
|
606
|
|
-
|
|
606
|
+
|
607
|
607
|
if (classOfDEGs == "up") {
|
608
|
608
|
genes.1stlevel <- rownames(resultMatrix)[
|
609
|
609
|
which(resultMatrix[,"level1Up"]==1)]
|
610
|
610
|
genes.2ndlevel <- rownames(resultMatrix)[
|
611
|
611
|
which(resultMatrix[,"level2Up"]==1)]
|
612
|
612
|
}
|
613
|
|
-
|
|
613
|
+
|
614
|
614
|
if (classOfDEGs == "down") {
|
615
|
615
|
genes.1stlevel <- rownames(resultMatrix)[
|
616
|
616
|
which(resultMatrix[,"level1Down"]==1)]
|
...
|
...
|
@@ -627,9 +627,9 @@ setMethod("RegulatoryEnrichment", "DEGs",
|
627
|
627
|
label.level.DEGs[1], significance.threshold, mult.cor, regulated.identities, regulated.counts)
|
628
|
628
|
enriched.2 <- computeGeneListEnrichment(genes.2ndlevel,
|
629
|
629
|
label.level.DEGs[2], significance.threshold, mult.cor, regulated.identities, regulated.counts)
|
630
|
|
-
|
631
|
|
- return(new("EnrichedSets", enriched.table=rbind(enriched.1, enriched.2),
|
632
|
|
- label.level.enriched=label.level.DEGs))
|
|
630
|
+
|
|
631
|
+ return(new("EnrichedSets", enriched.table=rbind(enriched.1, enriched.2),
|
|
632
|
+ label.level.enriched=label.level.DEGs))
|
633
|
633
|
}
|
634
|
634
|
}
|
635
|
635
|
)
|
...
|
...
|
@@ -640,58 +640,58 @@ setMethod("RegulatoryEnrichment", "DEGs",
|
640
|
640
|
|
641
|
641
|
createspecifictable <- function(background,myInterestedGenes,ontology,
|
642
|
642
|
test.method,test.threshold,mult.cor,level.label) {
|
643
|
|
-
|
644
|
|
- xx <- annFUN.org(ontology, feasibleGenes=background,
|
|
643
|
+
|
|
644
|
+ xx <- annFUN.org(ontology, feasibleGenes=background,
|
645
|
645
|
mapping="org.Hs.eg.db", ID="symbol")
|
646
|
646
|
xxxx <- inverseList(xx)
|
647
|
647
|
geneNames <- names(xxxx)
|
648
|
648
|
geneList <- factor(as.integer(geneNames %in% myInterestedGenes))
|
649
|
649
|
names(geneList) <- geneNames
|
650
|
650
|
str(geneList)
|
651
|
|
-
|
|
651
|
+
|
652
|
652
|
GOdata <- new("topGOdata", ontology = ontology, allGenes = geneList,
|
653
|
653
|
annot = annFUN.gene2GO, gene2GO = xxxx, nodeSize= 5)
|
654
|
|
-
|
655
|
|
- if (test.method == "classic")
|
656
|
|
- resultFisher <- runTest(GOdata, algorithm = "classic",
|
|
654
|
+
|
|
655
|
+ if (test.method == "classic")
|
|
656
|
+ resultFisher <- runTest(GOdata, algorithm = "classic",
|
657
|
657
|
statistic = "fisher")
|
658
|
|
- if (test.method == "elim")
|
659
|
|
- resultFisher <- runTest(GOdata, algorithm = "elim",
|
|
658
|
+ if (test.method == "elim")
|
|
659
|
+ resultFisher <- runTest(GOdata, algorithm = "elim",
|
660
|
660
|
statistic = "fisher")
|
661
|
|
- if (test.method == "weight")
|
662
|
|
- resultFisher <- runTest(GOdata, algorithm = "weight",
|
|
661
|
+ if (test.method == "weight")
|
|
662
|
+ resultFisher <- runTest(GOdata, algorithm = "weight",
|
663
|
663
|
statistic = "fisher")
|
664
|
|
- if (test.method == "weight01")
|
|
664
|
+ if (test.method == "weight01")
|
665
|
665
|
resultFisher <- runTest(GOdata, algorithm = "weight01",
|
666
|
666
|
statistic = "fisher")
|
667
|
|
- if (test.method == "parentchild")
|
668
|
|
- resultFisher <- runTest(GOdata, algorithm = "parentchild",
|
|
667
|
+ if (test.method == "parentchild")
|
|
668
|
+ resultFisher <- runTest(GOdata, algorithm = "parentchild",
|
669
|
669
|
statistic = "fisher")
|
670
|
670
|
|
671
|
671
|
s <- score(resultFisher)
|
672
|
|
-
|
673
|
|
- enrich.table <- GenTable(GOdata, Fisher.result = resultFisher,
|
674
|
|
- orderBy = "Fisher.result",
|
|
672
|
+
|
|
673
|
+ enrich.table <- GenTable(GOdata, Fisher.result = resultFisher,
|
|
674
|
+ orderBy = "Fisher.result",
|
675
|
675
|
ranksOf = "Fisher.result", topNodes = length(s))
|
676
|
676
|
enrich.table$Fisher.classic.BH <- p.adjust(
|
677
|
677
|
as.numeric(enrich.table[,"Fisher.result"]),
|
678
|
|
- "BH",
|
|
678
|
+ "BH",
|
679
|
679
|
n=length(enrich.table[,"Fisher.result"]))
|
680
|
|
-
|
|
680
|
+
|
681
|
681
|
if (!mult.cor) {
|
682
|
682
|
enrich.table <- enrich.table[
|
683
|
683
|
which(
|
684
|
|
- enrich.table[,"Fisher.result"] <= test.threshold),]
|
|
684
|
+ as.numeric(enrich.table[,"Fisher.result"]) <= test.threshold),]
|
685
|
685
|
}
|
686
|
686
|
else {
|
687
|
687
|
enrich.table <- enrich.table[
|
688
|
688
|
which(
|
689
|
|
- enrich.table[,"Fisher.classic.BH"] <= test.threshold),]
|
|
689
|
+ as.numeric(enrich.table[,"Fisher.classic.BH"]) <= test.threshold),]
|
690
|
690
|
}
|
691
|
|
-
|
692
|
|
- enrich.table <- enrich.table[order(enrich.table[,"Fisher.result"],
|
|
691
|
+
|
|
692
|
+ enrich.table <- enrich.table[order(as.numeric(enrich.table[,"Fisher.result"]),
|
693
|
693
|
na.last = TRUE, decreasing = FALSE),]
|
694
|
|
-
|
|
694
|
+
|
695
|
695
|
OntologyLevel <- matrix(,nrow=dim(enrich.table)[1], ncol=2)
|
696
|
696
|
colnames(OntologyLevel) <- c("ontology", "level")
|
697
|
697
|
OntologyLevel[,1] <- ontology
|
...
|
...
|
@@ -700,19 +700,19 @@ createspecifictable <- function(background,myInterestedGenes,ontology,
|
700
|
700
|
colnames(final.table) <- c("ontology", "level","GO.ID", "term", "annotated",
|
701
|
701
|
"significant", "expected",
|
702
|
702
|
"pv.fisher", "pv.fisher.BH")
|
703
|
|
-
|
|
703
|
+
|
704
|
704
|
return (final.table)
|
705
|
705
|
}
|
706
|
706
|
|
707
|
707
|
|
708
|
|
-computeGeneListEnrichment <-
|
|
708
|
+computeGeneListEnrichment <-
|
709
|
709
|
function(DEGs.genes, level.label, significance.threshold, mult.cor, regulated.identities=NULL, regulated.counts=NULL) {
|
710
|
|
-
|
|
710
|
+
|
711
|
711
|
# explicitly define the two tables (contained in tRanslatomeDataset)
|
712
|
|
- # to avoid Rcmd check complaining as it does not see these
|
|
712
|
+ # to avoid Rcmd check complaining as it does not see these
|
713
|
713
|
regulatory.elements.regulated <- NULL
|
714
|
714
|
regulatory.elements.counts <- NULL
|
715
|
|
-
|
|
715
|
+
|
716
|
716
|
# if the user specified custom regulator-target identities and regulated
|
717
|
717
|
# counts matrices, use these
|
718
|
718
|
if (!is.null(regulated.identities) && !is.null(regulated.counts)){
|
...
|
...
|
@@ -720,27 +720,27 @@ computeGeneListEnrichment <-
|
720
|
720
|
regulatory.elements.counts <- regulated.counts
|
721
|
721
|
}
|
722
|
722
|
else {
|
723
|
|
- # we need our default regulatory element data contained
|
|
723
|
+ # we need our default regulatory element data contained
|
724
|
724
|
# in tRanslatome dataset, so load it
|
725
|
725
|
data(tRanslatomeSampleData, envir=environment())
|
726
|
726
|
}
|
727
|
|
-
|
|
727
|
+
|
728
|
728
|
enrichments <- c()
|
729
|
|
-
|
|
729
|
+
|
730
|
730
|
for (i in c(1:nrow(regulatory.elements.regulated))) {
|
731
|
731
|
regulated.list <- strsplit(
|
732
|
|
- as.character(regulatory.elements.regulated[i,2]),
|
|
732
|
+ as.character(regulatory.elements.regulated[i,2]),
|
733
|
733
|
split=",")[[1]]
|
734
|
|
-
|
|
734
|
+
|
735
|
735
|
regel.name <- as.character(regulatory.elements.regulated[i,1])
|
736
|
736
|
regelIdx <- which(regulatory.elements.counts[,1] == regel.name)
|
737
|
737
|
regel.regulated <- as.integer(regulatory.elements.counts[regelIdx,2])
|
738
|
738
|
regel.nonregulated <- as.integer(regulatory.elements.counts[regelIdx,3])
|
739
|
|
-
|
|
739
|
+
|
740
|
740
|
# get genes from input list regulated by this regulator
|
741
|
741
|
regel.input.regulated <- DEGs.genes[
|
742
|
|
- which(DEGs.genes %in% regulated.list)]
|
743
|
|
-
|
|
742
|
+ which(DEGs.genes %in% regulated.list)]
|
|
743
|
+
|
744
|
744
|
# build the contingency table for fisher test
|
745
|
745
|
cont.table <- matrix(nrow=2, ncol=2)
|
746
|
746
|
# number of input genes regulated by this element
|
...
|
...
|
@@ -750,27 +750,33 @@ computeGeneListEnrichment <-
|
750
|
750
|
# number of non-input genes regulated by this element
|
751
|
751
|
cont.table[2,1] <- as.integer(regel.regulated) - cont.table[1,1]
|
752
|
752
|
# number of non-input genes NOT regulated by this element
|
753
|
|
- cont.table[2,2] <- (regel.regulated + regel.nonregulated) -
|
|
753
|
+ cont.table[2,2] <- (regel.regulated + regel.nonregulated) -
|
754
|
754
|
cont.table[2,1]
|
755
|
|
-
|
|
755
|
+
|
756
|
756
|
# compute the fisher test p-value and report the regulator only if
|
757
|
757
|
# the enrichment p-value is below the given significance threshold
|
758
|
758
|
pvalue <- fisher.test(cont.table)$p.value
|
759
|
|
- if (pvalue <= significance.threshold)
|
760
|
|
- enrichments <- rbind(enrichments, c(regel.name, level.label,
|
|
759
|
+ if (pvalue <= significance.threshold)
|
|
760
|
+ enrichments <- rbind(enrichments, c(regel.name, level.label,
|
761
|
761
|
cont.table[1,1],
|
762
|
762
|
paste(regel.input.regulated, collapse=","),
|
763
|
763
|
pvalue))
|
764
|
|
- }
|
765
|
|
-
|
766
|
|
- colnames(enrichments) <- c("ID", "level", "number","list","pv.fisher")
|
|
764
|
+ }
|
|
765
|
+
|
|
766
|
+ colnames(enrichments) <- c("ID", "level", "number","list","pv.fisher")
|
767
|
767
|
# if requested, adjust the p-value for multiple testing and add
|
768
|
|
- # the corrected p-value to the enrichments table
|
769
|
|
- if (mult.cor)
|
770
|
|
- enrichments <- cbind(enrichments,
|
771
|
|
- "pv.fisher.BH"=p.adjust(enrichments[,5],
|
|
768
|
+ # the corrected p-value to the enrichments table, and end by
|
|
769
|
+ # filtering by significance threshold on adjusted p-value
|
|
770
|
+ if (mult.cor) {
|
|
771
|
+ enrichments <- cbind(enrichments,
|
|
772
|
+ "pv.fisher.BH"=p.adjust(enrichments[,5],
|
772
|
773
|
method="BH",n=nrow(regulatory.elements.counts)))
|
773
|
|
-
|
774
|
|
- return(as.data.frame(enrichments[order(as.numeric(enrichments[,5])),],
|
|
774
|
+ enrichments <- enrichments[which(enrichments[,6] <= significance.threshold),]
|
|
775
|
+ return(as.data.frame(enrichments[order(as.numeric(enrichments[,6])),],
|
775
|
776
|
stringsAsFactors=F))
|
|
777
|
+ }
|
|
778
|
+ else {
|
|
779
|
+ return(as.data.frame(enrichments[order(as.numeric(enrichments[,5])),],
|
|
780
|
+ stringsAsFactors=F))
|
|
781
|
+ }
|
776
|
782
|
}
|
777
|
783
|
\ No newline at end of file
|