Skip to content

Commit

Permalink
removed asset_type column
Browse files Browse the repository at this point in the history
  • Loading branch information
bergalli committed Apr 10, 2024
1 parent 0eb5820 commit d2936a3
Show file tree
Hide file tree
Showing 5 changed files with 46 additions and 24 deletions.
55 changes: 40 additions & 15 deletions R/crispy_trisk_lineplot.R
Original file line number Diff line number Diff line change
Expand Up @@ -13,20 +13,22 @@ pipeline_crispy_trisk_line_plot <- function(
trajectories_data,
x_var = "year",
facet_var = "ald_business_unit",
linecolor = "ald_sector") {
linecolor = "ald_sector",
y_in_percent=TRUE) {
linecolor <- dplyr::intersect(colnames(trajectories_data), linecolor)

data_trisk_line_plot <- prepare_for_trisk_line_plot(
trajectories_data = trajectories_data,
facet_var = facet_var,
linecolor = linecolor
)
)

trisk_line_plot <- draw_trisk_line_plot(
data_trisk_line_plot,
x_var = x_var,
facet_var = facet_var,
linecolor = linecolor
linecolor = linecolor,
y_in_percent=y_in_percent
)

return(trisk_line_plot)
Expand Down Expand Up @@ -75,28 +77,51 @@ draw_trisk_line_plot <- function(
data_trisk_line_plot,
x_var,
facet_var,
linecolor) {
linecolor,
y_in_percent) {

if (y_in_percent){
trisk_line_plot <- ggplot2::ggplot(
data_trisk_line_plot,
ggplot2::aes(
x = !!rlang::sym(x_var),
y = production_pct,
color = !!rlang::sym(linecolor),
linetype = scenario
)
) +
ggplot2::scale_y_continuous(labels = scales::percent_format(scale = 1)) +
ggplot2::labs(
y = "Production as a percentage of the maximum"
)
} else {
trisk_line_plot <- ggplot2::ggplot(
data_trisk_line_plot,
ggplot2::aes(
x = !!rlang::sym(x_var),
y = production,
color = !!rlang::sym(linecolor),
linetype = scenario
)
) +
ggplot2::scale_y_continuous(labels = function(x) scales::scientific(x)) +
ggplot2::labs(
y = "Production in raw unit"
)
}


facets_colors <- r2dii.colours::palette_2dii_plot[seq_along(unique(data_trisk_line_plot[[linecolor]])), ]$hex
trisk_line_plot <- ggplot2::ggplot(
data_trisk_line_plot,
ggplot2::aes(
x = !!rlang::sym(x_var),
y = production_pct,
color = !!rlang::sym(linecolor),
linetype = scenario
)
) +
trisk_line_plot <- trisk_line_plot +
ggplot2::geom_line() +
# ggplot2::geom_point(size = 0.1) +
ggplot2::scale_y_continuous(labels = scales::percent_format(scale = 1)) +
ggplot2::scale_linetype_manual(values = c(
"production_baseline_scenario" = "dotted",
"production_target_scenario" = "dashed",
"production_shock_scenario" = "solid"
)) +
ggplot2::labs(
x = "Year",
y = "Production as a percentage of the maximum",
linetype = "Scenario"
) +
ggplot2::scale_color_manual(values = facets_colors) +
Expand Down
2 changes: 1 addition & 1 deletion R/data_load_main.R
Original file line number Diff line number Diff line change
Expand Up @@ -130,7 +130,7 @@ main_load_analysis_data <-
main_load_portfolio_data <-
function(portfolio_data,
granularity,
param_cols = c("portfolio_id", "term", "asset_type"),
param_cols = c("portfolio_id", "term"),
trisk_start_year) {
group_cols <- unique(c(granularity, param_cols))

Expand Down
8 changes: 4 additions & 4 deletions R/data_load_portfolio.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,6 @@ load_portfolio_data <- function(portfolio_data_path) {
portfolio_id = "c",
company_id = "c",
company_name = "c",
asset_type = "c",
ald_sector = "c",
ald_business_unit = "c",
ald_location = "c",
Expand All @@ -23,7 +22,6 @@ load_portfolio_data <- function(portfolio_data_path) {
} else {
portfolio_data <- tibble::tibble(
portfolio_id = character(),
asset_type = character(),
company_id = character(),
company_name = character(),
ald_sector = character(),
Expand Down Expand Up @@ -64,9 +62,11 @@ map_portfolio_maturity_to_term <-
dplyr::mutate(term = 1)
}

# replace term by 1 if asset_type is equity
# replace term by 1 if asset type is equity
portfolio_data <- portfolio_data |>
dplyr::mutate(term = dplyr::if_else(asset_type == "equity", 1, .data$term))
dplyr::mutate(
term = dplyr::if_else(is.na(.data$term), 1, .data$term)
portfolio_id=dplyr::if_else(is.na(.data$portfolio_id), 1, .data$portfolio_id))
return(portfolio_data)
}

Expand Down
2 changes: 1 addition & 1 deletion R/prepare_for_cdi_plots.R
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ prepare_for_cdi_npv_plots <-


#' Title
#'
#' TODO IS THIS FUNCTION USED ANYWHERE ?
#' @param analysis_data analysis_data
#' @param group_variables_vec group_variables_vec
#' @param weight_variable_char weight_variable_char
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,6 @@ portfolio_values <- abcd_stress_test_input |>
companies_fixed_income <-
portfolio_values |>
sample_n(200) |>
mutate(asset_type = "fixed_income") |>
left_join(eikon_data |> select(company_id, isin) |> sample_frac(0.3),
by = "company_id",
relationship = "many-to-many"
Expand All @@ -27,7 +26,6 @@ companies_equities <-
portfolio_values |>
sample_n(200) |>
mutate(
asset_type = "equity",
expiration_date = NA
)

Expand Down Expand Up @@ -72,7 +70,6 @@ portfolio_data <- portfolio_data |> select(
portfolio_id,
company_name,
company_id,
asset_type,
ald_sector,
ald_business_unit,
ald_location,
Expand Down

0 comments on commit d2936a3

Please sign in to comment.