Handle legend orientation better

Tento commit je obsažen v:
2024-09-12 04:58:53 -04:00
rodič aef57dd3dc
revize 05787bdcbb

Zobrazit soubor

@@ -371,31 +371,43 @@ generate_and_save_plots <- function(output_dir, file_name, plot_configs, grid_la
return(plot)
})
# Save plots to file (PDF and HTML)
save_plots(plots, output_dir, file_name, grid_layout)
}
save_plots <- function(plots, output_dir, file_name, grid_layout = NULL) {
# PDF saving logic
pdf(file.path(output_dir, paste0(file_name, ".pdf")), width = 14, height = 9)
lapply(plots, print)
dev.off()
# HTML saving logic
plotly_plots <- lapply(plots, function(plot) suppressWarnings(ggplotly(plot) %>% layout(legend = list(orientation = "h"))))
plotly_plots <- lapply(plots, function(plot) {
config <- plot$labels$config
if (!is.null(config$legend_position) && config$legend_position == "bottom") {
suppressWarnings(ggplotly(plot, tooltip = "text") %>% layout(legend = list(orientation = "h")))
} else {
ggplotly(plot, tooltip = "text")
}
})
combined_plot <- subplot(plotly_plots, nrows = grid_layout$nrow %||% length(plots), margin = 0.05)
saveWidget(combined_plot, file = file.path(output_dir, paste0(file_name, ".html")), selfcontained = TRUE)
}
generate_scatter_plot <- function(plot, config) {
plot <- if (!is.null(config$delta_bg_point) && config$delta_bg_point) {
plot + geom_point(aes(text = paste("ORF:", OrfRep, "Gene:", Gene, "delta_bg:", delta_bg), shape = config$shape %||% 3))
plot + geom_point(aes(x = !!sym(config$x_var), y = !!sym(config$y_var),
color = as.factor(!!sym(config$color_var)),
text = paste("ORF:", OrfRep, "Gene:", Gene, "delta_bg:", delta_bg)),
shape = config$shape %||% 3)
} else if (!is.null(config$gene_point) && config$gene_point) {
plot + geom_point(aes(text = paste("ORF:", OrfRep, "Gene:", Gene)), shape = config$shape %||% 3, position = "jitter")
plot + geom_point(aes(x = !!sym(config$x_var), y = !!sym(config$y_var),
color = as.factor(!!sym(config$color_var)),
text = paste("ORF:", OrfRep, "Gene:", Gene)),
shape = config$shape %||% 3, position = "jitter")
} else if (!is.null(config$position) && config$position == "jitter") {
plot + geom_point(shape = config$shape %||% 3, size = config$size %||% 0.2, position = "jitter")
plot + geom_point(aes(x = !!sym(config$x_var), y = !!sym(config$y_var),
color = as.factor(!!sym(config$color_var))),
shape = config$shape %||% 3, size = config$size %||% 0.2, position = "jitter")
} else {
plot + geom_point(shape = config$shape %||% 3, size = config$size %||% 0.2)
plot + geom_point(aes(x = !!sym(config$x_var), y = !!sym(config$y_var),
color = as.factor(!!sym(config$color_var))),
shape = config$shape %||% 3, size = config$size %||% 0.2)
}
if (!is.null(config$add_smooth) && config$add_smooth) {