Skip to content

Commit

Permalink
feat: cleaner decomp_plot() using cols instead of areas + ref line in…
Browse files Browse the repository at this point in the history
… 0 (#1061)

* feat: cleaner decomp_plot() using cols instead of areas + ref line in 0
* fix: sort variables by baseline first & amount of absolute impact + exclude 0 impact from legend/plot
* fix: baseline and then rest of variables
  • Loading branch information
laresbernardo authored Sep 24, 2024
1 parent bf761e1 commit 6324d6d
Show file tree
Hide file tree
Showing 2 changed files with 34 additions and 8 deletions.
2 changes: 1 addition & 1 deletion R/DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Package: Robyn
Type: Package
Title: Semi-Automated Marketing Mix Modeling (MMM) from Meta Marketing Science
Version: 3.11.1.9002
Version: 3.11.1.9003
Authors@R: c(
person("Gufeng", "Zhou", , "[email protected]", c("aut")),
person("Bernardo", "Lares", , "[email protected]", c("cre","aut")),
Expand Down
40 changes: 33 additions & 7 deletions R/R/plots.R
Original file line number Diff line number Diff line change
Expand Up @@ -1570,6 +1570,7 @@ decomp_plot <- function(
))
varType <- str_to_title(InputCollect$dep_var_type)
pal <- names(lares::lares_pal()$palette)

df <- OutputCollect$xDecompVecCollect[OutputCollect$xDecompVecCollect$solID %in% solID, ] %>%
select(
"solID", "ds", "dep_var", any_of("intercept"),
Expand All @@ -1579,24 +1580,49 @@ decomp_plot <- function(
filter(!.data$variable %in% exclude) %>%
mutate(variable = ifelse(
.data$variable %in% bvars, paste0("Baseline_L", baseline_level), as.character(.data$variable)
)) %>%
))

# Sort variables by baseline first & amount of absolute impact
levs <- df %>%
group_by(.data$variable) %>%
summarize(impact = sum(abs(.data$value))) %>%
mutate(is_baseline = grepl("Baseline_L", .data$variable)) %>%
arrange(desc(.data$is_baseline), desc(.data$impact)) %>%
filter(.data$impact > 0) %>%
pull(.data$variable)
df <- df %>%
group_by(.data$solID, .data$ds, .data$variable) %>%
summarise(
value = sum(.data$value, na.rm = TRUE),
value = sum(.data$value, na.rm = TRUE),
.groups = "drop"
) %>%
arrange(abs(.data$value)) %>%
mutate(variable = factor(.data$variable, levels = unique(.data$variable)))
p <- ggplot(df, aes(x = .data$ds, y = .data$value, fill = .data$variable)) +
facet_grid(.data$solID ~ .) +
filter(.data$variable %in% levs) %>%
mutate(variable = factor(.data$variable, levels = rev(levs)))

p <- ggplot(df, aes(x = as.character(ds), y = value, fill = variable)) +
facet_grid(solID ~ .) +
labs(
title = paste(varType, "Decomposition by Variable"),
x = NULL, y = paste(intType, varType), fill = NULL
) +
geom_area() +
geom_col(width = 1) +
theme_lares(background = "white", legend = "right") +
geom_hline(yintercept = 0) +
scale_fill_manual(values = rev(pal[seq(length(unique(df$variable)))])) +
scale_y_abbr()
scale_y_abbr() +
# Must create custom splits because dates is character to be able to be bars
scale_x_discrete(
breaks = get_evenly_separated_dates(df$ds, n = 6),
labels = function(x) format(as.Date(x), "%m/%y")
)
return(p)
}

get_evenly_separated_dates <- function(dates, n = 6) {
dates <- sort(dates)
intervals <- n - 1
indices <- round(seq(1, length(dates), length.out = n))
selected_dates <- dates[indices]
return(as.character(selected_dates))
}

0 comments on commit 6324d6d

Please sign in to comment.