Remove references to ranked df
This commit is contained in:
@@ -660,73 +660,69 @@ generate_plate_analysis_plot_configs <- function(variables, stages = c("before",
|
|||||||
return(plots)
|
return(plots)
|
||||||
}
|
}
|
||||||
|
|
||||||
generate_interaction_plot_configs <- function(df, variables) {
|
generate_interaction_plot_configs <- function(df, variables, limits_map = NULL) {
|
||||||
|
# Default limits_map if not provided
|
||||||
configs <- list()
|
if (is.null(limits_map)) {
|
||||||
|
limits_map <- list(
|
||||||
# Set the y-limits for each variable
|
L = c(-65, 65),
|
||||||
df_filtered <- df %>%
|
K = c(-65, 65),
|
||||||
filter(
|
r = c(-0.65, 0.65),
|
||||||
!is.na(L) & between(L, -65, 65),
|
AUC = c(-6500, 6500)
|
||||||
!is.na(K) & between(K, -65, 65),
|
|
||||||
!is.na(r) & between(r, -0.65, 0.65),
|
|
||||||
!is.na(AUC) & between(AUC, -6500, 6500)
|
|
||||||
)
|
|
||||||
|
|
||||||
# Define annotation label functions
|
|
||||||
generate_annotation_labels <- function(df, var, annotation_name) {
|
|
||||||
switch(annotation_name,
|
|
||||||
ZShift = paste("ZShift =", round(df[[paste0("Z_Shift_", var)]], 2)),
|
|
||||||
lm_ZScore = paste("lm ZScore =", round(df[[paste0("Z_lm_", var)]], 2)),
|
|
||||||
NG = paste("NG =", df$NG),
|
|
||||||
DB = paste("DB =", df$DB),
|
|
||||||
SM = paste("SM =", df$SM),
|
|
||||||
NULL # Default case for unrecognized annotation names
|
|
||||||
)
|
)
|
||||||
}
|
}
|
||||||
|
|
||||||
# Define annotation positions relative to the y-axis range
|
# Filter data
|
||||||
calculate_annotation_positions <- function(y_range) {
|
df_filtered <- df
|
||||||
|
for (var in names(limits_map)) {
|
||||||
|
df_filtered <- df_filtered %>%
|
||||||
|
filter(!is.na(!!sym(var)) &
|
||||||
|
!!sym(var) >= limits_map[[var]][1] &
|
||||||
|
!!sym(var) <= limits_map[[var]][2])
|
||||||
|
}
|
||||||
|
|
||||||
|
configs <- list()
|
||||||
|
|
||||||
|
for (variable in variables) {
|
||||||
|
y_range <- limits_map[[variable]]
|
||||||
|
|
||||||
|
# Calculate annotation positions
|
||||||
y_min <- min(y_range)
|
y_min <- min(y_range)
|
||||||
y_max <- max(y_range)
|
y_max <- max(y_range)
|
||||||
y_span <- y_max - y_min
|
y_span <- y_max - y_min
|
||||||
|
annotation_positions <- list(
|
||||||
list(
|
|
||||||
ZShift = y_max - 0.1 * y_span,
|
ZShift = y_max - 0.1 * y_span,
|
||||||
lm_ZScore = y_max - 0.2 * y_span,
|
lm_ZScore = y_max - 0.2 * y_span,
|
||||||
NG = y_min + 0.2 * y_span,
|
NG = y_min + 0.2 * y_span,
|
||||||
DB = y_min + 0.1 * y_span,
|
DB = y_min + 0.1 * y_span,
|
||||||
SM = y_min + 0.05 * y_span
|
SM = y_min + 0.05 * y_span
|
||||||
)
|
)
|
||||||
}
|
|
||||||
|
|
||||||
# Create configurations for each variable
|
# Prepare linear model line
|
||||||
for (variable in variables) {
|
|
||||||
|
|
||||||
y_range <- limits_map[[variable]]
|
|
||||||
annotation_positions <- calculate_annotation_positions(y_range)
|
|
||||||
lm_line <- list(
|
lm_line <- list(
|
||||||
intercept = df_filtered[[paste0("lm_intercept_", variable)]],
|
intercept = df_filtered[[paste0("lm_intercept_", variable)]],
|
||||||
slope = df_filtered[[paste0("lm_slope_", variable)]]
|
slope = df_filtered[[paste0("lm_slope_", variable)]]
|
||||||
)
|
)
|
||||||
|
|
||||||
# Determine x-axis midpoint
|
# Calculate x-axis position for annotations
|
||||||
num_levels <- length(levels(df_filtered$conc_num_factor))
|
num_levels <- length(levels(df_filtered$conc_num_factor))
|
||||||
x_pos <- (1 + num_levels) / 2 # Midpoint of x-axis
|
x_pos <- (1 + num_levels) / 2
|
||||||
|
|
||||||
# Generate annotations
|
# Generate annotations
|
||||||
annotations <- lapply(names(annotation_positions), function(annotation_name) {
|
annotations <- lapply(names(annotation_positions), function(annotation_name) {
|
||||||
label <- generate_annotation_labels(df_filtered, variable, annotation_name)
|
label <- switch(annotation_name,
|
||||||
y_pos <- annotation_positions[[annotation_name]]
|
ZShift = paste("ZShift =", round(df_filtered[[paste0("Z_Shift_", variable)]], 2)),
|
||||||
|
lm_ZScore = paste("lm ZScore =", round(df_filtered[[paste0("Z_lm_", variable)]], 2)),
|
||||||
|
NG = paste("NG =", df_filtered$NG),
|
||||||
|
DB = paste("DB =", df_filtered$DB),
|
||||||
|
SM = paste("SM =", df_filtered$SM),
|
||||||
|
NULL
|
||||||
|
)
|
||||||
if (!is.null(label)) {
|
if (!is.null(label)) {
|
||||||
list(x = x_pos, y = y_pos, label = label)
|
list(x = x_pos, y = annotation_positions[[annotation_name]], label = label)
|
||||||
} else {
|
} else {
|
||||||
message(paste("Warning: No annotation found for", annotation_name))
|
|
||||||
NULL
|
NULL
|
||||||
}
|
}
|
||||||
})
|
})
|
||||||
|
|
||||||
# Remove NULL annotations
|
|
||||||
annotations <- Filter(Negate(is.null), annotations)
|
annotations <- Filter(Negate(is.null), annotations)
|
||||||
|
|
||||||
# Shared plot settings
|
# Shared plot settings
|
||||||
@@ -740,7 +736,7 @@ generate_interaction_plot_configs <- function(df, variables) {
|
|||||||
x_breaks = levels(df_filtered$conc_num_factor),
|
x_breaks = levels(df_filtered$conc_num_factor),
|
||||||
x_labels = levels(df_filtered$conc_num_factor),
|
x_labels = levels(df_filtered$conc_num_factor),
|
||||||
x_label = unique(df_filtered$Drug[1]),
|
x_label = unique(df_filtered$Drug[1]),
|
||||||
coord_cartesian = y_range # Use the actual y-limits
|
coord_cartesian = y_range
|
||||||
)
|
)
|
||||||
|
|
||||||
# Scatter plot config
|
# Scatter plot config
|
||||||
@@ -1422,7 +1418,7 @@ main <- function() {
|
|||||||
|
|
||||||
message("Generating filtered ranked plots")
|
message("Generating filtered ranked plots")
|
||||||
rank_plot_filtered_configs <- generate_rank_plot_configs(
|
rank_plot_filtered_configs <- generate_rank_plot_configs(
|
||||||
df = zscores_interactions_filtered_ranked,
|
df = zscores_interactions_filtered,
|
||||||
variables = interaction_vars,
|
variables = interaction_vars,
|
||||||
is_lm = FALSE,
|
is_lm = FALSE,
|
||||||
adjust = FALSE,
|
adjust = FALSE,
|
||||||
@@ -1437,7 +1433,7 @@ main <- function() {
|
|||||||
|
|
||||||
message("Generating filtered ranked linear model plots")
|
message("Generating filtered ranked linear model plots")
|
||||||
rank_plot_lm_filtered_configs <- generate_rank_plot_configs(
|
rank_plot_lm_filtered_configs <- generate_rank_plot_configs(
|
||||||
df = zscores_interactions_filtered_ranked,
|
df = zscores_interactions_filtered,
|
||||||
variables = interaction_vars,
|
variables = interaction_vars,
|
||||||
is_lm = TRUE,
|
is_lm = TRUE,
|
||||||
adjust = FALSE,
|
adjust = FALSE,
|
||||||
|
|||||||
Reference in New Issue
Block a user