... | ... |
@@ -1024,7 +1024,7 @@ plotCorGraph <- function( |
1024 | 1024 |
indLowCor <- which(abs(E(ig)$weight)<=0.4) |
1025 | 1025 |
E(ig)$weight <- 1/abs(log2(abs(E(ig)$weight))) |
1026 | 1026 |
E(ig)$weight[indHighCor] <- E(ig)$weight[indHighCor]+6 |
1027 |
- E(ig)$weight[indLowCor] <- E(ig)$weight[indLowCor]-0.25 |
|
1027 |
+ #E(ig)$weight[indLowCor] <- E(ig)$weight[indLowCor] -0.25 |
|
1028 | 1028 |
|
1029 | 1029 |
if (!missing(reciproCol)) { |
1030 | 1030 |
if (reciproCol %in% colnames(dataGraph)) { |
... | ... |
@@ -267,13 +267,12 @@ hypergeoAn <- function ( icaSet, |
267 | 267 |
`addGenesToGoReport` <- |
268 | 268 |
function(hgOver, universe, db = c("GO","KEGG"), onto = c("CC", "MF", "BP"), annotation = NULL, entrez2symbol = NULL) { |
269 | 269 |
|
270 |
- require(GOstats) |
|
271 | 270 |
|
272 | 271 |
db <- match.arg(tolower(db), choices = c("go","kegg")) |
273 | 272 |
onto <- match.arg(toupper(onto), choices = c("CC", "MF", "BP")) |
274 | 273 |
|
275 |
- a <- geneIdsByCategory(hgOver) |
|
276 |
- b <- geneIdUniverse(hgOver, cond=conditional(hgOver)) |
|
274 |
+ a <- GOstats::geneIdsByCategory(hgOver) |
|
275 |
+ b <- GOstats::geneIdUniverse(hgOver, cond=conditional(hgOver)) |
|
277 | 276 |
|
278 | 277 |
a <- a[sigCategories(hgOver)] |
279 | 278 |
b <- b[sigCategories(hgOver)] |