Remove aes_string()

This commit is contained in:
2024-09-04 02:07:23 -04:00
parent d52903f8fa
commit 0cb47077f8

View File

@@ -311,90 +311,14 @@ calculate_interaction_scores <- function(df_ref, df, max_conc, variables, group_
} }
# generate_rf_plots <- function(df_calculations, df_interactions, output_dir, file_prefix = "RF") {
# variables <- c("Delta_L", "Delta_K", "Delta_r", "Delta_AUC")
# WT_sds <- list(WT_sd_l = 2, WT_sd_K = 2, WT_sd_r = 0.65, WT_sd_AUC = 6500)
# plot_list <- lapply(seq_along(variables), function(i) {
# var <- variables[i]
# WT_sd <- WT_sds[[i]]
# ggplot(df_calculations, aes(conc_num_factor, !!sym(var))) +
# geom_point() + geom_smooth(method = "lm", formula = y ~ x, se = FALSE) +
# coord_cartesian(ylim = c(-WT_sd, WT_sd)) +
# geom_errorbar(aes(ymin = 0 - (2 * WT_sd), ymax = 0 + (2 * WT_sd)), alpha = 0.3) +
# ggtitle(paste(df_calculations$OrfRep[1], df_calculations$Gene[1], sep = " ")) +
# annotate("text", x = 1, y = 0.9 * WT_sd, label = paste("ZShift =", round(df_interactions[[paste0("Z_Shift_", var)]], 2))) +
# annotate("text", x = 1, y = 0.7 * WT_sd, label = paste("lm Zscore =", round(df_interactions[[paste0("Z_lm_", var)]], 2))) +
# annotate("text", x = 1, y = -0.7 * WT_sd, label = paste("NG =", df_interactions$NG)) +
# annotate("text", x = 1, y = -0.9 * WT_sd, label = paste("DB =", df_interactions$DB)) +
# annotate("text", x = 1, y = -1.1 * WT_sd, label = paste("SM =", df_interactions$SM)) +
# scale_x_continuous(
# name = unique(df_calculations$Drug[1]),
# breaks = unique(df_calculations$conc_num_factor),
# labels = unique(as.character(df_calculations$conc_num))) +
# theme_publication()
# })
# save_plots(file_prefix, plot_list, output_dir)
# }
# generate_summary_plots <- function(df, output_dir) {
# variables <- c("L", "K", "r", "AUC")
# plot_list <- lapply(variables, function(var) {
# generate_plot(df, x_var = "conc_num_factor", y_var = var, plot_type = "scatter", title = paste("Summary Plot for", var))
# })
# save_plots("Summary_Plots", plot_list, output_dir)
# }
# # Generate ranked plots for a specific metric
# generate_ranked_plot <- function(df, rank_var, zscore_var, sd_threshold, title_prefix) {
# ggplot(df, aes(x = {{rank_var}}, y = {{zscore_var}})) +
# ggtitle(paste(title_prefix, "above", sd_threshold, "SD")) +
# xlab("Rank") + ylab(paste("Avg Z score", title_prefix)) +
# annotate("rect", xmin = -Inf, xmax = Inf, ymin = sd_threshold, ymax = Inf, fill = "#542788", alpha = 0.3) +
# annotate("rect", xmin = -Inf, xmax = Inf, ymin = -sd_threshold, ymax = -Inf, fill = "orange", alpha = 0.3) +
# geom_hline(yintercept = c(-sd_threshold, sd_threshold)) +
# geom_point(size = 0.1, shape = 3) +
# theme_publication()
# }
# # Generate and save all ranked plots
# generate_and_save_ranked_plots <- function(df, output_dir, prefix) {
# rank_metrics <- list(
# list("L_Rank", "Avg_Zscore_L", "L"),
# list("K_Rank", "Avg_Zscore_K", "K"),
# list("r_Rank", "Avg_Zscore_r", "r"),
# list("AUC_Rank", "Avg_Zscore_AUC", "AUC"),
# list("L_Rank_lm", "Z_lm_L", "L"),
# list("K_Rank_lm", "Z_lm_K", "K"),
# list("r_Rank_lm", "Z_lm_r", "r"),
# list("AUC_Rank_lm", "Z_lm_AUC", "AUC")
# )
# pdf(file.path(output_dir, paste0(prefix, ".pdf")), width = 18, height = 12, onefile = TRUE)
# for (sd_threshold in c(1, 2, 3)) {
# for (metric in rank_metrics) {
# plot <- generate_ranked_plot(df, sym(metric[[1]]), sym(metric[[2]]), sd_threshold, metric[[3]])
# print(plot)
# }
# }
# dev.off()
# }
generate_plot <- function(df, x_var, y_var = NULL, plot_type, color_var = "conc_num", generate_plot <- function(df, x_var, y_var = NULL, plot_type, color_var = "conc_num",
title, x_label = NULL, y_label = NULL, ylim_vals = NULL) { title, x_label = NULL, y_label = NULL, ylim_vals = NULL) {
plot <- ggplot(df, aes_string(x = x_var, color = color_var))
# Use tidy evaluation with aes() and !!sym() for dynamic column names
plot <- ggplot(df, aes(x = !!sym(x_var), color = !!sym(color_var)))
if (!is.null(y_var)) { if (!is.null(y_var)) {
plot <- plot + aes_string(y = y_var) plot <- plot + aes(y = !!sym(y_var))
} }
# Set up the plot based on the requested plot type # Set up the plot based on the requested plot type