Skip to content

Commit

Permalink
read max secondary steel share from file
Browse files Browse the repository at this point in the history
  • Loading branch information
0UmfHxcvx5J7JoaOhFSs5mncnisTJJ6q committed Jul 6, 2022
1 parent b1eac09 commit fa991cc
Show file tree
Hide file tree
Showing 2 changed files with 50 additions and 35 deletions.
50 changes: 15 additions & 35 deletions R/EDGE-Industry.R
Original file line number Diff line number Diff line change
Expand Up @@ -125,28 +125,6 @@ calcSteel_Projections <- function(subtype = 'production',
'SSP5', '0.75') %>%
pivot_longer(-'scenario', names_to = 'switch'),

# secondary steel share limits ----
# Linear convergence from the historic value in the year <from> to the value
# <target> in the year <by>.
# Corresponds to code in
# REMIND:/modules/37_industry/subsectors/datainput.gms
tribble(
~scenario, ~from, ~by, ~target,
'SDP', 2015, 2050, 0.9,
'SDP_EI', 2015, 2050, 0.9,
'SDP_MC', 2015, 2050, 0.9,
'SDP_RC', 2015, 2050, 0.9,
'SSP1', 2015, 2050, 0.9,
'SSP2', 2015, 2050, 0.9,
'SSP2EU', 2015, 2050, 0.9,
'SSP3', 2015, 2050, 0.9,
'SSP4', 2015, 2050, 0.9,
'SSP5', 2015, 2050, 0.9) %>%
pivot_longer(-'scenario', names_to = 'switch',
values_transform = list(value = as.character)) %>%
mutate(switch = paste0('EDGE-Industry_secondary.steel.max.share.',
switch)),

NULL) %>%
pivot_wider(names_from = 'switch')

Expand All @@ -163,14 +141,7 @@ calcSteel_Projections <- function(subtype = 'production',
`steel.stock.lifetime.convergence.year` =
'EDGE-Industry_steel.stock.lifetime.convergence.year',
`steel.stock.lifetime.convergence.factor` =
'EDGE-Industry_steel.stock.lifetime.convergence.factor',

`secondary.steel.max.share.from` =
'EDGE-Industry_secondary.steel.max.share.from',
secondary.steel.max.share.by =
'EDGE-Industry_secondary.steel.max.share.by',
secondary.steel.max.share.target =
'EDGE-Industry_secondary.steel.max.share.target')
'EDGE-Industry_steel.stock.lifetime.convergence.factor')

# load required data ----
## region mapping for aggregation ----
Expand Down Expand Up @@ -749,9 +720,18 @@ calcSteel_Projections <- function(subtype = 'production',
assert(not_na, everything())

## calculate secondary steel max share ----
secondary.steel.max.switches <- `EDGE-Industry_scenario_switches` %>%
select('scenario',
matches('^secondary\\.steel\\.max\\.share\\.(from|by|target)$'))
secondary.steel.max.switches <- calcOutput(
type = 'industry_max_secondary_steel_share',
scenarios = unique(population$scenario),
regions = unique(region_mapping$region),
aggregate = FALSE) %>%
as.data.frame() %>%
as_tibble() %>%
select(scenario = 'Data1', region = 'Data2', name = 'Data3',
value = 'Value') %>%
mutate(name = paste0('secondary.steel.max.share.', .data$name)) %>%
pivot_wider() %>%
character.data.frame()

tmp <- full_join(
steel_historic_prod %>%
Expand Down Expand Up @@ -784,12 +764,12 @@ calcSteel_Projections <- function(subtype = 'production',
distinct(.data$scenario, .data$region, .data$iso3c) %>%
full_join(
secondary.steel.max.switches %>%
select('scenario', year = 'secondary.steel.max.share.by',
select('scenario', 'region', year = 'secondary.steel.max.share.by',
share = 'secondary.steel.max.share.target') %>%
mutate(year = as.integer(.data$year),
share = as.numeric(.data$share)),

'scenario'
c('scenario', 'region')
)
) %>%
interpolate_missing_periods_(
Expand Down
35 changes: 35 additions & 0 deletions R/calcindustry_max_secondary_steel_share.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
#' Calculate Maximum Secondary Steel Production Share
#'
#' Reads ExpertGuess/industry_max_secondary_steel_share and expands to all
#' `scenarios`/`regions` using default data. See [`tool_expand_tibble()`] for
#' details.
#'
#' @param scenarios A character vector of scenarios to expand data to.
#' @param regions A character vector of regions to expand data to.
#'
#' @return A list with a [`magpie`][magclass::magclass] object `x`.

#' @export
calcindustry_max_secondary_steel_share <- function(scenarios = NULL,
regions = NULL) {
if (is.null(scenarios)) {
stop('Scenario definitions missing.')
}

if (is.null(regions)) {
stop('Region definitions missing.')
}

. <- NULL

return(list(
x = readSource(type = 'ExpertGuess',
subtype = 'industry_max_secondary_steel_share',
convert = FALSE) %>%
madrat_mule() %>%
tool_expand_tibble(scenarios, regions) %>%
pivot_longer(
!all_of(names(which('character' == unlist(lapply(., typeof)))))) %>%
as.magpie(spatial = 0, temporal = 0, data = ncol(.)),
weight = NULL, unit = '', description = ''))
}

0 comments on commit fa991cc

Please sign in to comment.