... | ... |
@@ -137,13 +137,12 @@ annotateTRM = function(g, target) { |
137 | 137 |
else |
138 | 138 |
default |
139 | 139 |
} |
140 |
- |
|
141 | 140 |
plotTRM = function(g, layout = layout.fruchterman.reingold, mar = .5, vertex.col, vertex.cex, vertex.lwd, edge.col, edge.lwd, edge.lty, label = TRUE, label.cex, label.col, label.pos = NULL, label.offset = 1.5, adjust.label.col = FALSE, normalize.layout=TRUE) { |
142 | 141 |
|
143 |
- if(class(layout) == "function") |
|
142 |
+ if(is(layout, "function")) |
|
144 | 143 |
l = layout(g) |
145 | 144 |
else |
146 |
- l = layout |
|
145 |
+ l = as.matrix(layout) |
|
147 | 146 |
|
148 | 147 |
# normalize layout. |
149 | 148 |
if(normalize.layout) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/rTRM@86450 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -320,14 +320,14 @@ annotateModule = function(g, enrich, trm, targets, ppi, exprs, tfs) { |
320 | 320 |
} |
321 | 321 |
|
322 | 322 |
E(g)$lty = "dotted" |
323 |
- el = get.edgelist(graph.intersection.by.name(ppi, g)) |
|
323 |
+ el = get.edgelist(graph.intersection(ppi, g)) |
|
324 | 324 |
for(j in 1:nrow(el)) { |
325 | 325 |
E(g, P = which(V(g)$name %in% el[j,]), directed = FALSE)$lty = "solid" |
326 | 326 |
} |
327 | 327 |
|
328 | 328 |
E(g)$color = "grey" |
329 | 329 |
E(g)$width = 1 |
330 |
- el = get.edgelist(graph.intersection.by.name(trm, g)) |
|
330 |
+ el = get.edgelist(graph.intersection(trm, g)) |
|
331 | 331 |
for(j in 1:nrow(el)) { |
332 | 332 |
E(g, P = which(V(g)$name %in% el[j,]), directed = FALSE)$color = "black" |
333 | 333 |
# E(g, P = which(V(g)$name %in% el[j,]), directed = FALSE)$width = 3 |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/rTRM@86443 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -105,7 +105,8 @@ plotDegree = function(g) { |
105 | 105 |
V(g)$family = family |
106 | 106 |
|
107 | 107 |
col = c("unclassified" = "white", .getTFclassColors()) |
108 |
- V(g)$piecolor = lapply(V(g)$family, function(f) col[f]) |
|
108 |
+ V(g)$pie.color = lapply(V(g)$family, function(f) col[f]) |
|
109 |
+ V(g)$pie = lapply(V(g)$pie.color, function(f) rep(1,length(f))) |
|
109 | 110 |
g |
110 | 111 |
} |
111 | 112 |
|
... | ... |
@@ -161,7 +162,7 @@ plotTRM = function(g, layout = layout.fruchterman.reingold, mar = .5, vertex.col |
161 | 162 |
if (adjust.label.col) { |
162 | 163 |
col.range = range(.lum2(colors())) |
163 | 164 |
col.cut = round(diff(col.range)/2) |
164 |
- lum.mean = sapply(V(g)$piecolor, function(x) mean(.lum2(x))) |
|
165 |
+ lum.mean = sapply(V(g)$pie.color, function(x) mean(.lum2(x))) |
|
165 | 166 |
label.col = ifelse(lum.mean < col.cut, "snow", "gray20") |
166 | 167 |
} |
167 | 168 |
|
... | ... |
@@ -176,8 +177,9 @@ plotTRM = function(g, layout = layout.fruchterman.reingold, mar = .5, vertex.col |
176 | 177 |
lines(c(x1[1], x2[1]), c(x1[2], x2[2]), col = edge.col, lwd = edge.lwd[i], lty = edge.lty[i]) |
177 | 178 |
} |
178 | 179 |
for(i in 1:nrow(l)) { |
179 |
- np = rep(1, length(V(g)[ i ]$piecolor)) |
|
180 |
- .floating.pie(l[i,1], l[i,2], x = np, col = V(g)[ i ]$piecolor, radius=vertex.cex[i]/100, frame.width = vertex.lwd[i], frame.color = vertex.col[i]) |
|
180 |
+ np=V(g)$pie[[i]] |
|
181 |
+ col=V(g)$pie.color[[i]] |
|
182 |
+ .floating.pie(l[i,1], l[i,2], x=np, col=col, radius=vertex.cex[i]/100, frame.width=vertex.lwd[i], frame.color=vertex.col[i]) |
|
181 | 183 |
} |
182 | 184 |
if(label) { |
183 | 185 |
ll = as.character(V(g)) |
... | ... |
@@ -218,7 +220,7 @@ plotTRMlegend = function (x, title = NULL, cex = 1) |
218 | 220 |
|
219 | 221 |
if (!is.null(col)) |
220 | 222 |
col <- rep(col, length.out = nx) |
221 |
- |
|
223 |
+ |
|
222 | 224 |
if (!is.null(lty)) |
223 | 225 |
lty <- rep(lty, length.out = nx) |
224 | 226 |
|
... | ... |
@@ -263,7 +265,7 @@ plotGraph = function(g, layout = layout.fruchterman.reingold, mar = .5, vertex.p |
263 | 265 |
if (adjust.label.col) { |
264 | 266 |
col.range = range(.lum2(colors())) |
265 | 267 |
col.cut = round(diff(col.range)/2) |
266 |
- lum.mean = sapply(V(g)$piecolor, function(x) mean(.lum2(x))) |
|
268 |
+ lum.mean = sapply(V(g)$pie.color, function(x) mean(.lum2(x))) |
|
267 | 269 |
label.col = ifelse(lum.mean < col.cut, "snow", "gray20") |
268 | 270 |
} |
269 | 271 |
|
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/rTRM@79429 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -137,7 +137,7 @@ annotateTRM = function(g, target) { |
137 | 137 |
default |
138 | 138 |
} |
139 | 139 |
|
140 |
-plotTRM = function(g, layout = layout.fruchterman.reingold, mar = .5, vertex.col, vertex.cex, vertex.lwd, edge.col, edge.lwd, edge.lty, label = TRUE, label.cex, label.col, label.pos = NULL, label.offset = 1.5, adjust.label.col = FALSE, normalizr.layout=TRUE) { |
|
140 |
+plotTRM = function(g, layout = layout.fruchterman.reingold, mar = .5, vertex.col, vertex.cex, vertex.lwd, edge.col, edge.lwd, edge.lty, label = TRUE, label.cex, label.col, label.pos = NULL, label.offset = 1.5, adjust.label.col = FALSE, normalize.layout=TRUE) { |
|
141 | 141 |
|
142 | 142 |
if(class(layout) == "function") |
143 | 143 |
l = layout(g) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/rTRM@79428 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -137,7 +137,7 @@ annotateTRM = function(g, target) { |
137 | 137 |
default |
138 | 138 |
} |
139 | 139 |
|
140 |
-plotTRM = function(g, layout = layout.fruchterman.reingold, mar = .5, vertex.col, vertex.cex, vertex.lwd, edge.col, edge.lwd, edge.lty, label = TRUE, label.cex, label.col, label.pos = NULL, label.offset = 1.5, adjust.label.col = FALSE) { |
|
140 |
+plotTRM = function(g, layout = layout.fruchterman.reingold, mar = .5, vertex.col, vertex.cex, vertex.lwd, edge.col, edge.lwd, edge.lty, label = TRUE, label.cex, label.col, label.pos = NULL, label.offset = 1.5, adjust.label.col = FALSE, normalizr.layout=TRUE) { |
|
141 | 141 |
|
142 | 142 |
if(class(layout) == "function") |
143 | 143 |
l = layout(g) |
... | ... |
@@ -145,7 +145,8 @@ plotTRM = function(g, layout = layout.fruchterman.reingold, mar = .5, vertex.col |
145 | 145 |
l = layout |
146 | 146 |
|
147 | 147 |
# normalize layout. |
148 |
- l = layout.norm(l, -1, 1, -1, 1) |
|
148 |
+ if(normalize.layout) |
|
149 |
+ l = layout.norm(l, -1, 1, -1, 1) |
|
149 | 150 |
|
150 | 151 |
vertex.col = .checkParam(vertex.col, V(g)$frame.color, "black", multi = vcount(g)) |
151 | 152 |
vertex.cex = .checkParam(vertex.cex, V(g)$size, 10, multi = vcount(g)) |
... | ... |
@@ -238,14 +239,15 @@ plotTRMlegend = function (x, title = NULL, cex = 1) |
238 | 239 |
symbols(xpos, ypos, circles = radius, inches = FALSE, add = TRUE, fg = frame.color, lwd = frame.width) |
239 | 240 |
} |
240 | 241 |
|
241 |
-plotGraph = function(g, layout = layout.fruchterman.reingold, mar = .5, vertex.pch = 21, vertex.cex, vertex.col, vertex.bg, vertex.lwd, edge.col, edge.lwd, edge.lty, label = TRUE, label.col, label.cex, label.pos = NULL, label.offset = 1.5, adjust.label.col = FALSE) { |
|
242 |
+plotGraph = function(g, layout = layout.fruchterman.reingold, mar = .5, vertex.pch = 21, vertex.cex, vertex.col, vertex.bg, vertex.lwd, edge.col, edge.lwd, edge.lty, label = TRUE, label.col, label.cex, label.pos = NULL, label.offset = 1.5, adjust.label.col = FALSE, normalize.layout=TRUE) { |
|
242 | 243 |
if(class(layout) == "function") |
243 | 244 |
l = layout(g) |
244 | 245 |
else |
245 | 246 |
l = layout |
246 | 247 |
|
247 | 248 |
# normalize layout. |
248 |
- l = layout.norm(l, -1, 1, -1, 1) |
|
249 |
+ if(normalize.layout) |
|
250 |
+ l = layout.norm(l, -1, 1, -1, 1) |
|
249 | 251 |
|
250 | 252 |
vertex.cex = .checkParam(vertex.cex, V(g)$size, 5) |
251 | 253 |
vertex.col = .checkParam(vertex.col, V(g)$frame.color, "grey") |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/rTRM@78001 bc3139a8-67e5-0310-9ffc-ced21a209358
1 | 1 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,368 @@ |
1 |
+## Package: rTRM (c) |
|
2 |
+## |
|
3 |
+## File: plot.R |
|
4 |
+## Description: support plotting functions for rTRM |
|
5 |
+## |
|
6 |
+## Author: Diego Diez |
|
7 |
+## Contact: [email protected] |
|
8 |
+## |
|
9 |
+ |
|
10 |
+ |
|
11 |
+## plots the degree distribution of the graph object. |
|
12 |
+plotDegree = function(g) { |
|
13 |
+ d = table(igraph::degree(g)) |
|
14 |
+ x = as.numeric(names(d)) |
|
15 |
+ y = as.numeric(d) |
|
16 |
+ |
|
17 |
+ x0 = x[! x == 0 ] |
|
18 |
+ y0 = y[! x == 0 ] |
|
19 |
+ |
|
20 |
+ plot(x0, y0, log = "xy", xlab = "Degree", ylab = "# Nodes", pch = 21, bg = "gray") |
|
21 |
+ |
|
22 |
+ dl = lm(log10(y0) ~ log10(x0)) |
|
23 |
+ abline(dl) |
|
24 |
+ l = .getLegend(dl) |
|
25 |
+ legend("topright", l, bg = "white", lty = "solid", cex = 0.7) |
|
26 |
+} |
|
27 |
+ |
|
28 |
+.getLegend <- function(m) { |
|
29 |
+ s <- summary(m) |
|
30 |
+ r2 = format(s$r.squared, nsmall = 2, digits = 2) |
|
31 |
+ a = format(m$coef[1], nsmall = 2, digits = 2) |
|
32 |
+ if (m$coef[2] > 0) { |
|
33 |
+ b = format(m$coef[2], nsmall = 2, digits = 2) |
|
34 |
+ l <- eval(substitute(expression(paste(R^2 == r2, |
|
35 |
+ ", ", y == a + b * x)), list(r2 = r2, a = a, |
|
36 |
+ b = b))) |
|
37 |
+ } |
|
38 |
+ else { |
|
39 |
+ b = format(abs(m$coef[2]), nsmall = 2, digits = 2) |
|
40 |
+ l <- eval(substitute(expression(paste(r^2 == r2, |
|
41 |
+ ", ", y == a - b * x)), list(r2 = r2, a = a, |
|
42 |
+ b = b))) |
|
43 |
+ } |
|
44 |
+} |
|
45 |
+ |
|
46 |
+ |
|
47 |
+.lum = function(col) { |
|
48 |
+ tmp = col2rgb(col) |
|
49 |
+ apply(tmp, 2, function(x) { |
|
50 |
+ (0.2126*x[1]) + (0.7152*x[2]) + (0.0722*x[3]) |
|
51 |
+ }) |
|
52 |
+} |
|
53 |
+ |
|
54 |
+ |
|
55 |
+.lum2 = function (col) |
|
56 |
+{ |
|
57 |
+ tmp = col2rgb(col) |
|
58 |
+ apply(tmp, 2, function(x) { |
|
59 |
+ (0.2126 * x[1]^2) + (0.7152 * x[2]^2) + (0.0722 * x[3]^2) |
|
60 |
+ }) |
|
61 |
+} |
|
62 |
+ |
|
63 |
+ |
|
64 |
+.getNiceColors = function (n, eq.spaced = TRUE, order.by = TRUE, min.lum, max.lum) |
|
65 |
+{ |
|
66 |
+ cs = grep("^grey|^gray", colors(), value = TRUE, invert = TRUE) |
|
67 |
+ cs = grep("white", cs, value = TRUE, invert = TRUE) |
|
68 |
+ cols = c(cs, grey.colors(10)) |
|
69 |
+ |
|
70 |
+ cols.lum = .lum2(cols) |
|
71 |
+ |
|
72 |
+ if (order.by) { |
|
73 |
+ #cols.lum = lum2(cols) |
|
74 |
+ sel = order(cols.lum, decreasing = TRUE) |
|
75 |
+ cols = cols[sel] |
|
76 |
+ cols.lum = cols.lum[sel] |
|
77 |
+ } |
|
78 |
+ |
|
79 |
+ if(!missing(min.lum)) |
|
80 |
+ cols = cols[cols.lum >= min.lum] |
|
81 |
+ |
|
82 |
+ if(!missing(max.lum)) |
|
83 |
+ cols = cols[cols.lum <= max.lum] |
|
84 |
+ |
|
85 |
+ if(!missing(n)) { |
|
86 |
+ if(eq.spaced) { |
|
87 |
+ ns = floor(length(cols)/n) |
|
88 |
+ sel = seq(1, ns * n, ns) |
|
89 |
+ cols = cols[sel] |
|
90 |
+ } else cols = cols[1:n] |
|
91 |
+ } |
|
92 |
+ cols |
|
93 |
+} |
|
94 |
+ |
|
95 |
+.getTFclassColors = function(subset = "Class") { |
|
96 |
+ terms = getTFterms(subset) |
|
97 |
+ col = .getNiceColors(length(unique(terms))) |
|
98 |
+ names(col) = unique(terms) |
|
99 |
+ col |
|
100 |
+} |
|
101 |
+ |
|
102 |
+.annotateTFclass = function(g) { |
|
103 |
+ family = getTFclassFromEntrezgene(V(g)$name) |
|
104 |
+ family[sapply(family, is.null)] = "unclassified" |
|
105 |
+ V(g)$family = family |
|
106 |
+ |
|
107 |
+ col = c("unclassified" = "white", .getTFclassColors()) |
|
108 |
+ V(g)$piecolor = lapply(V(g)$family, function(f) col[f]) |
|
109 |
+ g |
|
110 |
+} |
|
111 |
+ |
|
112 |
+.annotateTarget = function(g, target) { |
|
113 |
+ target = target[ target %in% V(g)$name ] |
|
114 |
+ V(g)$frame.color = "grey" |
|
115 |
+ V(g)[ target ]$frame.color = "black" |
|
116 |
+ V(g)$frame.width = 1 |
|
117 |
+ V(g)[ target ]$frame.width = 2 |
|
118 |
+ g |
|
119 |
+} |
|
120 |
+ |
|
121 |
+annotateTRM = function(g, target) { |
|
122 |
+ g = .annotateTarget(g, target) |
|
123 |
+ .annotateTFclass(g) |
|
124 |
+} |
|
125 |
+ |
|
126 |
+.checkParam = function(p1, p2, default, multi) { |
|
127 |
+ if(!missing(p1)) |
|
128 |
+ if(!missing(multi) & length(p1) == 1) |
|
129 |
+ return(rep(p1, multi)) |
|
130 |
+ else |
|
131 |
+ return(p1) |
|
132 |
+ if(!is.null(p2)) |
|
133 |
+ return(p2) |
|
134 |
+ if(!missing(multi)) |
|
135 |
+ rep(default, multi) |
|
136 |
+ else |
|
137 |
+ default |
|
138 |
+} |
|
139 |
+ |
|
140 |
+plotTRM = function(g, layout = layout.fruchterman.reingold, mar = .5, vertex.col, vertex.cex, vertex.lwd, edge.col, edge.lwd, edge.lty, label = TRUE, label.cex, label.col, label.pos = NULL, label.offset = 1.5, adjust.label.col = FALSE) { |
|
141 |
+ |
|
142 |
+ if(class(layout) == "function") |
|
143 |
+ l = layout(g) |
|
144 |
+ else |
|
145 |
+ l = layout |
|
146 |
+ |
|
147 |
+ # normalize layout. |
|
148 |
+ l = layout.norm(l, -1, 1, -1, 1) |
|
149 |
+ |
|
150 |
+ vertex.col = .checkParam(vertex.col, V(g)$frame.color, "black", multi = vcount(g)) |
|
151 |
+ vertex.cex = .checkParam(vertex.cex, V(g)$size, 10, multi = vcount(g)) |
|
152 |
+ vertex.lwd = .checkParam(vertex.lwd, V(g)$frame.width, 1, multi = vcount(g)) |
|
153 |
+ |
|
154 |
+ edge.col = .checkParam(edge.col, E(g)$color, "grey") |
|
155 |
+ edge.lwd = .checkParam(edge.lwd, E(g)$width, 1, multi = ecount(g)) |
|
156 |
+ edge.lty = .checkParam(edge.lty, E(g)$lty, "solid", multi = ecount(g)) |
|
157 |
+ |
|
158 |
+ label.col = .checkParam(label.col, V(g)$label.color, "black") |
|
159 |
+ label.cex = .checkParam(label.cex, V(g)$label.cex, 1) |
|
160 |
+ if (adjust.label.col) { |
|
161 |
+ col.range = range(.lum2(colors())) |
|
162 |
+ col.cut = round(diff(col.range)/2) |
|
163 |
+ lum.mean = sapply(V(g)$piecolor, function(x) mean(.lum2(x))) |
|
164 |
+ label.col = ifelse(lum.mean < col.cut, "snow", "gray20") |
|
165 |
+ } |
|
166 |
+ |
|
167 |
+ mat = get.edgelist(g) |
|
168 |
+ |
|
169 |
+ op = par(mar = rep(mar,4), xpd = TRUE) |
|
170 |
+ plot(0, xlim = range(l[,1]), ylim = range(l[,2]), cex = 0, axes = FALSE, xlab = "", ylab = "", asp = 1) |
|
171 |
+ for(i in 1:nrow(mat)){ |
|
172 |
+ ni = as.numeric(V(g)[ mat[i,] ]) |
|
173 |
+ x1 = l[ni[1] ,] |
|
174 |
+ x2 = l[ni[2] ,] |
|
175 |
+ lines(c(x1[1], x2[1]), c(x1[2], x2[2]), col = edge.col, lwd = edge.lwd[i], lty = edge.lty[i]) |
|
176 |
+ } |
|
177 |
+ for(i in 1:nrow(l)) { |
|
178 |
+ np = rep(1, length(V(g)[ i ]$piecolor)) |
|
179 |
+ .floating.pie(l[i,1], l[i,2], x = np, col = V(g)[ i ]$piecolor, radius=vertex.cex[i]/100, frame.width = vertex.lwd[i], frame.color = vertex.col[i]) |
|
180 |
+ } |
|
181 |
+ if(label) { |
|
182 |
+ ll = as.character(V(g)) |
|
183 |
+ if(!is.null(V(g)$name)) |
|
184 |
+ ll = V(g)$name |
|
185 |
+ if(!is.null(V(g)$label)) |
|
186 |
+ ll = V(g)$label |
|
187 |
+ text(l, labels = ll, cex = label.cex, col = label.col, pos = label.pos, offset = label.offset) |
|
188 |
+ } |
|
189 |
+ par(op) |
|
190 |
+} |
|
191 |
+ |
|
192 |
+plotTRMlegend = function (x, title = NULL, cex = 1) |
|
193 |
+{ |
|
194 |
+ |
|
195 |
+ if(class(x) == "igraph") |
|
196 |
+ family = sort(unique(unlist(V(x)$family))) |
|
197 |
+ else |
|
198 |
+ family = x |
|
199 |
+ |
|
200 |
+ col = .getTFclassColors() |
|
201 |
+ col = c(col, unclassified = "white") |
|
202 |
+ |
|
203 |
+ op = par(mar = rep(0, 4)) |
|
204 |
+ plot(0, col = "transparent", axes = FALSE) |
|
205 |
+ legend("center", legend = family, fill = col[family], bty = "n", cex = cex, title = title) |
|
206 |
+ par(op) |
|
207 |
+} |
|
208 |
+ |
|
209 |
+.floating.pie = function (xpos, ypos, x, edges = 200, radius = 0.8, col = NULL, border = TRUE, lty = NULL, frame.color = "black", frame.width = 1) |
|
210 |
+{ |
|
211 |
+ if (!is.numeric(x) || any(is.na(x) | x < 0)) |
|
212 |
+ stop("'x' values must be positive.") |
|
213 |
+ |
|
214 |
+ x <- c(0, cumsum(x)/sum(x)) |
|
215 |
+ dx <- diff(x) |
|
216 |
+ nx <- length(dx) |
|
217 |
+ |
|
218 |
+ if (!is.null(col)) |
|
219 |
+ col <- rep(col, length.out = nx) |
|
220 |
+ |
|
221 |
+ if (!is.null(lty)) |
|
222 |
+ lty <- rep(lty, length.out = nx) |
|
223 |
+ |
|
224 |
+ |
|
225 |
+ init.angle = 90 |
|
226 |
+ |
|
227 |
+ t2xy = function(t) { |
|
228 |
+ t2p <- -2 * pi * t + init.angle * pi/180 |
|
229 |
+ list(x = radius * cos(t2p), y = radius * sin(t2p)) |
|
230 |
+ } |
|
231 |
+ |
|
232 |
+ for (i in 1L:nx) { |
|
233 |
+ n <- max(2, floor(edges * dx[i])) |
|
234 |
+ P <- t2xy(seq.int(x[i], x[i + 1], length.out = n)) |
|
235 |
+ polygon(c(P$x+xpos, xpos), c(P$y+ypos, ypos), border = NA, col = col[i], lty = lty[i]) |
|
236 |
+ } |
|
237 |
+ if (border) |
|
238 |
+ symbols(xpos, ypos, circles = radius, inches = FALSE, add = TRUE, fg = frame.color, lwd = frame.width) |
|
239 |
+} |
|
240 |
+ |
|
241 |
+plotGraph = function(g, layout = layout.fruchterman.reingold, mar = .5, vertex.pch = 21, vertex.cex, vertex.col, vertex.bg, vertex.lwd, edge.col, edge.lwd, edge.lty, label = TRUE, label.col, label.cex, label.pos = NULL, label.offset = 1.5, adjust.label.col = FALSE) { |
|
242 |
+ if(class(layout) == "function") |
|
243 |
+ l = layout(g) |
|
244 |
+ else |
|
245 |
+ l = layout |
|
246 |
+ |
|
247 |
+ # normalize layout. |
|
248 |
+ l = layout.norm(l, -1, 1, -1, 1) |
|
249 |
+ |
|
250 |
+ vertex.cex = .checkParam(vertex.cex, V(g)$size, 5) |
|
251 |
+ vertex.col = .checkParam(vertex.col, V(g)$frame.color, "grey") |
|
252 |
+ vertex.bg = .checkParam(vertex.bg, V(g)$color, "white") |
|
253 |
+ vertex.lwd = .checkParam(vertex.lwd, V(g)$frame.width, 1) |
|
254 |
+ |
|
255 |
+ edge.col = .checkParam(edge.col, E(g)$color, "grey", multi = ecount(g)) |
|
256 |
+ edge.lwd = .checkParam(edge.lwd, E(g)$width, 1, multi = ecount(g)) |
|
257 |
+ edge.lty = .checkParam(edge.lty, E(g)$lty, "solid", multi = ecount(g)) |
|
258 |
+ |
|
259 |
+ label.col = .checkParam(label.col, V(g)$label.color, "black") |
|
260 |
+ label.cex = .checkParam(label.cex, V(g)$label.cex, 1) |
|
261 |
+ if (adjust.label.col) { |
|
262 |
+ col.range = range(.lum2(colors())) |
|
263 |
+ col.cut = round(diff(col.range)/2) |
|
264 |
+ lum.mean = sapply(V(g)$piecolor, function(x) mean(.lum2(x))) |
|
265 |
+ label.col = ifelse(lum.mean < col.cut, "snow", "gray20") |
|
266 |
+ } |
|
267 |
+ |
|
268 |
+ mat = get.edgelist(g) |
|
269 |
+ op = par(mar = rep(mar,4), xpd = TRUE) |
|
270 |
+ plot(0, xlim = range(l[,1]), ylim = range(l[,2]), cex = 0, axes = FALSE, xlab = "", ylab = "", asp = 1) |
|
271 |
+ for(i in 1:nrow(mat)){ |
|
272 |
+ ni = as.numeric(V(g)[ mat[i,] ]) |
|
273 |
+ x1 = l[ni[1] ,] |
|
274 |
+ x2 = l[ni[2] ,] |
|
275 |
+ lines(c(x1[1], x2[1]), c(x1[2], x2[2]), col = edge.col[i], lwd = edge.lwd[i], lty = edge.lty[i]) |
|
276 |
+ } |
|
277 |
+ points(l, pch = vertex.pch, cex = vertex.cex, bg = vertex.bg, col = vertex.col, lwd = vertex.lwd) |
|
278 |
+ if(label) { |
|
279 |
+ ll = as.character(V(g)) |
|
280 |
+ if(!is.null(V(g)$name)) |
|
281 |
+ ll = V(g)$name |
|
282 |
+ if(!is.null(V(g)$label)) |
|
283 |
+ ll = V(g)$label |
|
284 |
+ text(l, labels = ll, cex = label.cex, pos = label.pos, offset=label.offset) |
|
285 |
+ } |
|
286 |
+ par(op) |
|
287 |
+} |
|
288 |
+ |
|
289 |
+ |
|
290 |
+## annotation functions to compare modules. |
|
291 |
+# annotate a graph based on the information in other module, as well as expression and targets, etc. |
|
292 |
+annotateModule = function(g, enrich, trm, targets, ppi, exprs, tfs) { |
|
293 |
+ trm_genes = .checkInNetwork(g, V(trm)$name) |
|
294 |
+ enrich_genes = .checkInNetwork(g, enrich) |
|
295 |
+ targets_found = targets[targets %in% trm] |
|
296 |
+ targets_found = .checkInNetwork(g, targets_found) |
|
297 |
+ exprs = .checkInNetwork(g, exprs) |
|
298 |
+ |
|
299 |
+ V(g)$color = "white" |
|
300 |
+ V(g)[ trm_genes ]$color = "white" |
|
301 |
+ V(g)[ enrich_genes ]$color = "steelblue2" |
|
302 |
+ |
|
303 |
+ V(g)[ targets_found ]$color = "steelblue4" |
|
304 |
+ V(g)$size = 1 |
|
305 |
+ V(g)[ exprs ]$size = 15 |
|
306 |
+ |
|
307 |
+ V(g)$frame.color = "gray" |
|
308 |
+ V(g)$frame.width = 1 |
|
309 |
+ V(g)[ trm_genes ]$frame.color = "black" |
|
310 |
+ V(g)[ trm_genes ]$frame.width = 3 |
|
311 |
+ |
|
312 |
+ if(!missing(tfs)) { |
|
313 |
+ tfs = .checkInNetwork(g, tfs) |
|
314 |
+ V(g)$shape = "circle" |
|
315 |
+ V(g)[ tfs ]$shape = "square" |
|
316 |
+ } |
|
317 |
+ |
|
318 |
+ E(g)$lty = "dotted" |
|
319 |
+ el = get.edgelist(graph.intersection.by.name(ppi, g)) |
|
320 |
+ for(j in 1:nrow(el)) { |
|
321 |
+ E(g, P = which(V(g)$name %in% el[j,]), directed = FALSE)$lty = "solid" |
|
322 |
+ } |
|
323 |
+ |
|
324 |
+ E(g)$color = "grey" |
|
325 |
+ E(g)$width = 1 |
|
326 |
+ el = get.edgelist(graph.intersection.by.name(trm, g)) |
|
327 |
+ for(j in 1:nrow(el)) { |
|
328 |
+ E(g, P = which(V(g)$name %in% el[j,]), directed = FALSE)$color = "black" |
|
329 |
+ # E(g, P = which(V(g)$name %in% el[j,]), directed = FALSE)$width = 3 |
|
330 |
+ } |
|
331 |
+ |
|
332 |
+ g |
|
333 |
+} |
|
334 |
+ |
|
335 |
+ |
|
336 |
+# annotate a graph based on the frequency the nodes and edges appear in |
|
337 |
+# a set of other graphs, provided as graph_list. |
|
338 |
+annotateFreq = function(g, graph_list) { |
|
339 |
+ s = sapply(V(g)$name, function(x) { |
|
340 |
+ 10*length(which(sapply(graph_list, function(s) if(!is.null(s)) any(V(s)$name %in% x) else FALSE)))/length(graph_list[!sapply(graph_list, is.null)]) |
|
341 |
+ }) |
|
342 |
+ |
|
343 |
+ ew = apply(get.edgelist(g), 1, function(e) { |
|
344 |
+ sum(sapply(names(graph_list), function(n) { |
|
345 |
+ |
|
346 |
+ s = graph_list[[n]] |
|
347 |
+ if(!is.null(s)) { |
|
348 |
+ e = .checkInNetwork(s, e) |
|
349 |
+ if(length(V(s)[ e ]) == 2) |
|
350 |
+ if(are.connected(s, e[1], e[2])) return(1) |
|
351 |
+ } |
|
352 |
+ return(0) |
|
353 |
+ })) |
|
354 |
+ }) |
|
355 |
+ |
|
356 |
+ et = rep("solid", length(ew)) |
|
357 |
+ et[ew == 0] = "dotted" |
|
358 |
+ ew[ew == 0] = 1 |
|
359 |
+ |
|
360 |
+ V(g)$size = s |
|
361 |
+ E(g)$width = ew |
|
362 |
+ E(g)$lty = et |
|
363 |
+ g |
|
364 |
+} |
|
365 |
+ |
|
366 |
+.checkInNetwork = function(g, x) { |
|
367 |
+ x[ x %in% V(g)$name ] |
|
368 |
+} |