فهرست منبع

Temporarily print plotly plots separately for debug

Bryan Roessler 6 ماه پیش
والد
کامیت
28edcd5f33
1فایلهای تغییر یافته به همراه47 افزوده شده و 27 حذف شده
  1. 47 27
      qhtcp-workflow/apps/r/calculate_interaction_zscores.R

+ 47 - 27
qhtcp-workflow/apps/r/calculate_interaction_zscores.R

@@ -393,9 +393,6 @@ calculate_interaction_scores <- function(df, max_conc, bg_stats,
 generate_and_save_plots <- function(out_dir, filename, plot_configs) {
   message("Generating ", filename, ".pdf and ", filename, ".html")
 
-  grid_nrow <- ifelse(is.null(plot_configs$grid_layout$nrow), 1, plot_configs$grid_layout$nrow)
-  grid_ncol <- ifelse(is.null(plot_configs$grid_layout$ncol), length(plot_configs$plots), plot_configs$grid_layout$ncol)
-
   static_plots <- list()
   plotly_plots <- list()
 
@@ -403,26 +400,35 @@ generate_and_save_plots <- function(out_dir, filename, plot_configs) {
     config <- plot_configs$plots[[i]]
     df <- config$df
 
-    # Define aes_mapping and handle color_var defaulting
-    aes_mapping <- if (config$plot_type == "bar") {
-      if (!is.null(config$color_var)) {
+    message("Processing plot ", i, ": ", config$title)
+    message("Plot type: ", config$plot_type)
+
+    if (is.null(df)) {
+      message("Dataframe for plot ", i, " is NULL.")
+      next
+    }
+
+    # Define aes_mapping, ensuring y_var is only used when it's not NULL
+    aes_mapping <- switch(config$plot_type,
+      "bar" = if (!is.null(config$color_var)) {
         aes(x = .data[[config$x_var]], fill = .data[[config$color_var]], color = .data[[config$color_var]])
       } else {
         aes(x = .data[[config$x_var]])
-      }
-    } else if (config$plot_type == "density") {
-      if (!is.null(config$color_var)) {
+      },
+      "density" = if (!is.null(config$color_var)) {
         aes(x = .data[[config$x_var]], color = .data[[config$color_var]])
       } else {
         aes(x = .data[[config$x_var]])
-      }
-    } else {
-      if (!is.null(config$color_var)) {
+      },
+      # For other plot types, only include y_var if it's not NULL
+      if (!is.null(config$y_var) && !is.null(config$color_var)) {
         aes(x = .data[[config$x_var]], y = .data[[config$y_var]], color = .data[[config$color_var]])
-      } else {
+      } else if (!is.null(config$y_var)) {
         aes(x = .data[[config$x_var]], y = .data[[config$y_var]])
+      } else {
+        aes(x = .data[[config$x_var]])  # no y_var needed for density and bar plots
       }
-    }
+    )
 
     # Apply theme_publication with legend_position
     plot <- ggplot(df, aes_mapping) + theme_publication(legend_position = config$legend_position)
@@ -432,8 +438,8 @@ generate_and_save_plots <- function(out_dir, filename, plot_configs) {
       "scatter" = generate_scatter_plot(plot, config),
       "box" = generate_box_plot(plot, config),
       "density" = plot + geom_density(),
-      "bar" = plot + geom_bar(),
-      plot  # default case
+      "bar" = plot + geom_bar(stat = "count"), # count occurrences
+      plot  # default (unused)
     )
 
     # Add titles and labels
@@ -442,13 +448,17 @@ generate_and_save_plots <- function(out_dir, filename, plot_configs) {
     if (!is.null(config$y_label)) plot <- plot + ylab(config$y_label)
     if (!is.null(config$coord_cartesian)) plot <- plot + coord_cartesian(ylim = config$coord_cartesian)
 
-    # Add interactive tooltips for plotly
-    tooltip_vars <- ifelse(!is.null(config$tooltip_vars), config$tooltip_vars, "none")
-    plotly_plot <- suppressWarnings(plotly::ggplotly(plot, tooltip = tooltip_vars))
+    # Convert ggplot to plotly, skipping subplot
+    if (!is.null(config$tooltip_vars)) {
+      plotly_plot <- suppressWarnings(plotly::ggplotly(plot, tooltip = config$tooltip_vars))
+    } else {
+      plotly_plot <- suppressWarnings(plotly::ggplotly(plot))
+    }
 
     # Adjust legend position in plotly
     if (!is.null(config$legend_position) && config$legend_position == "bottom") {
       plotly_plot <- plotly_plot %>% layout(legend = list(orientation = "h"))
+      plotly_plot <- plotly_plot + theme(legend.direction = NULL)
     }
 
     # Add static and interactive plots to lists
@@ -458,17 +468,27 @@ generate_and_save_plots <- function(out_dir, filename, plot_configs) {
 
   # Save static PDF plots
   pdf(file.path(out_dir, paste0(filename, ".pdf")), width = 16, height = 9)
-  grid.arrange(grobs = static_plots, ncol = grid_ncol, nrow = grid_nrow)
-  dev.off()
 
-  # Save combined interactive HTML plots
-  if (length(plotly_plots) == 1) {
-    combined_plot <- plotly_plots[[1]]
+  if (is.null(plot_configs$grid_layout)) {
+    # Print each plot on a new page if grid_layout is not set
+    for (plot in static_plots) {
+      print(plot)
+    }
   } else {
-    combined_plot <- plotly::subplot(plotly_plots, nrows = grid_nrow, ncols = grid_ncol, margin = 0.05)
+    # Use grid.arrange if grid_layout is set
+    grid_nrow <- ifelse(is.null(plot_configs$grid_layout$nrow), length(plot_configs$plots), plot_configs$grid_layout$nrow)
+    grid_ncol <- ifelse(is.null(plot_configs$grid_layout$ncol), 1, plot_configs$grid_layout$ncol)
+    grid.arrange(grobs = static_plots, ncol = grid_ncol, nrow = grid_nrow)
+  }
+
+  dev.off()
+
+  # Save individual interactive HTML plots without subplot
+  for (i in seq_along(plotly_plots)) {
+    html_file <- file.path(out_dir, paste0(filename, "_plot_", i, ".html"))
+    message("Saving HTML plot ", i, ": ", html_file)
+    htmlwidgets::saveWidget(plotly_plots[[i]], file = html_file, selfcontained = TRUE)
   }
-  html_file <- file.path(out_dir, paste0(filename, ".html"))
-  saveWidget(combined_plot, file = html_file, selfcontained = TRUE)
 }
 
 generate_scatter_plot <- function(plot, config) {