Commit ef089fc1 authored by Daria Zenkova's avatar Daria Zenkova

there are labels in morpheus.js now

parent b7b95736
createES <- function(data, pData, labelDescription, colNames, rowNames) {
exprs <- data
exprs <- t(data)
colnames(exprs) <- colNames
truePData <- pData
pd <- data.frame(truePData, row.names = colNames)
......
......@@ -5,11 +5,13 @@
#' @examples
#' pcaPlot(es.norm, 1, 2) + aes(color=time)
#' @export
pcaPlot <- function(es, columns=c(), rows=c(), c1, c2, size="", colour="") {
pcaPlot <- function(es, columns=c(), rows=c(), c1, c2, size="", colour="", label="") {
n1 <- as.numeric(c1)
n2 <- as.numeric(c2)
stopifnot(require(ggplot2))
stopifnot(require(ggrepel))
stopifnot(require(Biobase))
stopifnot(require(svglite))
if (is.null(rows)) {
rows <- 1:nrow(exprs(es))
......@@ -24,17 +26,17 @@ pcaPlot <- function(es, columns=c(), rows=c(), c1, c2, size="", colour="") {
data <- t(exprs(es)[rows,columns])
pca <- prcomp(data)
explained <- (pca$sdev)^2 / sum(pca$sdev^2)
xs <- sprintf("PC%s", seq_along(explained))
xlabs <- sprintf("%s (%.1f%%)", xs, explained * 100)
pData <- pData(es)[!(rownames(pData(es)) %in% setdiff(rownames(pData(es)), rownames(pca$x))),]
if (size != "") {
pData[[size]] <- as.numeric(pData[[size]])
}
pp <- ggplot(data=cbind(as.data.frame(pca$x), pData))
pp <- ggplot(data=cbind(as.data.frame(pca$x), pData, sampleNames(es)))
if (size != "" && colour != "") {
aes <- aes_string(x=xs[n1],
......@@ -42,16 +44,32 @@ pcaPlot <- function(es, columns=c(), rows=c(), c1, c2, size="", colour="") {
} else if (colour != "") {
aes <- aes_string(x=xs[n1],
y=xs[n2], colour=colour)
y=xs[n2], colour=colour)
} else if (size != "") {
aes <- aes_string(x=xs[n1],
y=xs[n2], size=size)
y=xs[n2], size=size)
} else {
aes <- aes_string(x=xs[n1],
y=xs[n2])
}
pp +
geom_point(aes) +
g <- pp + aes +
geom_point() +
xlab(xlabs[n1]) + ylab(xlabs[n2])
if (label == "id") {
label <- "sampleNames(es)"
}
if (label != "") {
message("i'm here 2s")
g <- g + geom_text_repel(aes_string(label=label))
}
f <- tempfile(pattern="plot",tmpdir="~/morpheus.js/tmp",fileext=".svg")
ggsave(f, g)
print(capture.output(str(g)))
return(f)
}
Markdown is supported
0%
or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment