Skip to content

Commit

Permalink
fix(gsea): fix margin too large error (#45)
Browse files Browse the repository at this point in the history
* fix(gsea): fix margin too large error

* fix(gsea): only use try instead of tryCatch
  • Loading branch information
iblacksand authored May 7, 2024
1 parent 5df4289 commit 481ea5e
Show file tree
Hide file tree
Showing 2 changed files with 82 additions and 69 deletions.
74 changes: 41 additions & 33 deletions R/gseaEnrichment.R
Original file line number Diff line number Diff line change
Expand Up @@ -129,39 +129,47 @@ gseaEnrichment <- function(hostName, outputDirectory, projectName, geneRankList,

#' @importFrom svglite svglite
plotEnrichmentPlot <- function(title, outputDir, fileName, format = "png", runningSums, ranks, scores, peakIndex) {
if (format == "png") {
png(file.path(outputDir, paste0(sanitizeFileName(fileName), ".png")), bg = "transparent", width = 2000, height = 2000)
cex <- list(main = 5, axis = 2.5, lab = 3.2)
} else if (format == "svg") {
svglite(file.path(outputDir, paste0(sanitizeFileName(fileName), ".svg")), bg = "transparent", width = 7, height = 7)
cex <- list(main = 1.5, axis = 0.6, lab = 0.8)
# svg seems to have a problem with long title (figure margins too large)
if (!is.na(nchar(title))) {
if (nchar(title) > 80) {
title <- paste0(substr(title, 1, 80), "...")
try(
{
if (format == "png") {
output_file <- file.path(outputDir, paste0(sanitizeFileName(fileName), ".png"))
png(output_file, bg = "transparent", width = 2000, height = 2000)
cex <- list(main = 5, axis = 2.5, lab = 3.2)
} else if (format == "svg") {
output_file <- file.path(outputDir, paste0(sanitizeFileName(fileName), ".svg"))
svglite(output_file, bg = "transparent", width = 7, height = 7)
cex <- list(main = 1.5, axis = 0.6, lab = 0.8)
# svg seems to have a problem with long title (figure margins too large)
if (!is.na(nchar(title))) {
if (nchar(title) > 80) {
title <- paste0(substr(title, 1, 80), "...")
}
}
}
}
}
wrappedTitle <- strwrap(paste0("Enrichment plot: ", title), 60)
plot.new()
par(fig = c(0, 1, 0.5, 1), mar = c(0, 6, 6 * length(wrappedTitle), 2), cex.axis = cex$axis, cex.main = cex$main, cex.lab = cex$lab, lwd = 2, new = TRUE)
plot(1:length(runningSums), runningSums,
type = "l", main = paste(wrappedTitle, collapse = "\n"),
xlab = "", ylab = "Enrichment Score", xaxt = "n", lwd = 3
)
abline(v = peakIndex, lty = 3)
par(fig = c(0, 1, 0.35, 0.5), mar = c(0, 6, 0, 2), new = TRUE)
plot(ranks, rep(1, length(ranks)),
type = "h",
xlim = c(1, length(scores)), ylim = c(0, 1), axes = FALSE, ann = FALSE
)
par(fig = c(0, 1, 0, 0.35), mar = c(6, 6, 0, 2), cex.axis = cex$axis, cex.lab = cex$lab, new = TRUE)
# use polygon to greatly reduce file size of SVG
plot(1:length(scores), scores,
type = "n",
ylab = "Ranked list metric", xlab = "Rank in Ordered Dataset"
wrappedTitle <- strwrap(paste0("Enrichment plot: ", title), 60)
plot.new()
par(fig = c(0, 1, 0.5, 1), mar = c(0, 6, 6 * length(wrappedTitle), 2), cex.axis = cex$axis, cex.main = cex$main, cex.lab = cex$lab, lwd = 2, new = TRUE)
plot(1:length(runningSums), runningSums,
type = "l", main = paste(wrappedTitle, collapse = "\n"),
xlab = "", ylab = "Enrichment Score", xaxt = "n", lwd = 3
)
abline(v = peakIndex, lty = 3)
par(fig = c(0, 1, 0.35, 0.5), mar = c(0, 6, 0, 2), new = TRUE)
plot(ranks, rep(1, length(ranks)),
type = "h",
xlim = c(1, length(scores)), ylim = c(0, 1), axes = FALSE, ann = FALSE
)
par(fig = c(0, 1, 0, 0.35), mar = c(6, 6, 0, 2), cex.axis = cex$axis, cex.lab = cex$lab, new = TRUE)
# use polygon to greatly reduce file size of SVG
plot(1:length(scores), scores,
type = "n",
ylab = "Ranked list metric", xlab = "Rank in Ordered Dataset"
)
polygon(c(1, 1:length(scores), length(scores)), c(0, scores, 0), col = "black")
abline(v = peakIndex, lty = 3)
dev.off()
return(output_file)
},
silent = TRUE
)
polygon(c(1, 1:length(scores), length(scores)), c(0, scores, 0), col = "black")
abline(v = peakIndex, lty = 3)
dev.off()
}
77 changes: 41 additions & 36 deletions R/multiGseaEnrichment.R
Original file line number Diff line number Diff line change
Expand Up @@ -208,42 +208,47 @@ multiGseaEnrichment <- function(hostName = NULL, outputDirectory = NULL, project

#' @importFrom svglite svglite
plotEnrichmentPlot <- function(title, outputDir, fileName, format = "png", runningSums, ranks, scores, peakIndex) {
if (format == "png") {
output_file <- file.path(outputDir, paste0(sanitizeFileName(fileName), ".png"))
png(output_file, bg = "transparent", width = 2000, height = 2000)
cex <- list(main = 5, axis = 2.5, lab = 3.2)
} else if (format == "svg") {
output_file <- file.path(outputDir, paste0(sanitizeFileName(fileName), ".svg"))
svglite(output_file, bg = "transparent", width = 7, height = 7)
cex <- list(main = 1.5, axis = 0.6, lab = 0.8)
# svg seems to have a problem with long title (figure margins too large)
if (!is.na(nchar(title))) {
if (nchar(title) > 80) {
title <- paste0(substr(title, 1, 80), "...")
try(
{
if (format == "png") {
output_file <- file.path(outputDir, paste0(sanitizeFileName(fileName), ".png"))
png(output_file, bg = "transparent", width = 2000, height = 2000)
cex <- list(main = 5, axis = 2.5, lab = 3.2)
} else if (format == "svg") {
output_file <- file.path(outputDir, paste0(sanitizeFileName(fileName), ".svg"))
svglite(output_file, bg = "transparent", width = 7, height = 7)
cex <- list(main = 1.5, axis = 0.6, lab = 0.8)
# svg seems to have a problem with long title (figure margins too large)
if (!is.na(nchar(title))) {
if (nchar(title) > 80) {
title <- paste0(substr(title, 1, 80), "...")
}
}
}
}
}
wrappedTitle <- strwrap(paste0("Enrichment plot: ", title), 60)
plot.new()
par(fig = c(0, 1, 0.5, 1), mar = c(0, 6, 6 * length(wrappedTitle), 2), cex.axis = cex$axis, cex.main = cex$main, cex.lab = cex$lab, lwd = 2, new = TRUE)
plot(1:length(runningSums), runningSums,
type = "l", main = paste(wrappedTitle, collapse = "\n"),
xlab = "", ylab = "Enrichment Score", xaxt = "n", lwd = 3
)
abline(v = peakIndex, lty = 3)
par(fig = c(0, 1, 0.35, 0.5), mar = c(0, 6, 0, 2), new = TRUE)
plot(ranks, rep(1, length(ranks)),
type = "h",
xlim = c(1, length(scores)), ylim = c(0, 1), axes = FALSE, ann = FALSE
)
par(fig = c(0, 1, 0, 0.35), mar = c(6, 6, 0, 2), cex.axis = cex$axis, cex.lab = cex$lab, new = TRUE)
# use polygon to greatly reduce file size of SVG
plot(1:length(scores), scores,
type = "n",
ylab = "Ranked list metric", xlab = "Rank in Ordered Dataset"
wrappedTitle <- strwrap(paste0("Enrichment plot: ", title), 60)
plot.new()
par(fig = c(0, 1, 0.5, 1), mar = c(0, 6, 6 * length(wrappedTitle), 2), cex.axis = cex$axis, cex.main = cex$main, cex.lab = cex$lab, lwd = 2, new = TRUE)
plot(1:length(runningSums), runningSums,
type = "l", main = paste(wrappedTitle, collapse = "\n"),
xlab = "", ylab = "Enrichment Score", xaxt = "n", lwd = 3
)
abline(v = peakIndex, lty = 3)
par(fig = c(0, 1, 0.35, 0.5), mar = c(0, 6, 0, 2), new = TRUE)
plot(ranks, rep(1, length(ranks)),
type = "h",
xlim = c(1, length(scores)), ylim = c(0, 1), axes = FALSE, ann = FALSE
)
par(fig = c(0, 1, 0, 0.35), mar = c(6, 6, 0, 2), cex.axis = cex$axis, cex.lab = cex$lab, new = TRUE)
# use polygon to greatly reduce file size of SVG
plot(1:length(scores), scores,
type = "n",
ylab = "Ranked list metric", xlab = "Rank in Ordered Dataset"
)
polygon(c(1, 1:length(scores), length(scores)), c(0, scores, 0), col = "black")
abline(v = peakIndex, lty = 3)
dev.off()
return(output_file)
},
silent = TRUE
)
polygon(c(1, 1:length(scores), length(scores)), c(0, scores, 0), col = "black")
abline(v = peakIndex, lty = 3)
dev.off()
return(output_file)
}

0 comments on commit 481ea5e

Please sign in to comment.