Skip to content

Commit

Permalink
Add show_RoW param to calculateEEIOModel and propogate through calcul…
Browse files Browse the repository at this point in the history
…cateExternalImportFactors.

Direct perspective calculation not working - matrix dimension problem with C %*% t(LCI_d)
  • Loading branch information
WesIngwersen committed Aug 16, 2024
1 parent 8582c81 commit 455b406
Showing 1 changed file with 40 additions and 27 deletions.
67 changes: 40 additions & 27 deletions R/CalculationFunctions.R
Original file line number Diff line number Diff line change
Expand Up @@ -13,14 +13,16 @@
#' @param use_domestic_requirements A logical value: if TRUE, use domestic demand and L_d matrix;
#' if FALSE, use complete demand and L matrix.
#' @param household_emissions, bool, if TRUE, include calculation of emissions from households
#' @param show_RoW, bool, if TRUE, include rows for commodities in RoW, e.g. `111CA/RoW` in result objects.
#' Only valid currently for models with ExternalImportFactors.
#' @export
#' @return A list with LCI and LCIA results (in data.frame format) of the EEIO model.
calculateEEIOModel <- function(model, perspective, demand = "Production", location = NULL,
use_domestic_requirements = FALSE, household_emissions = FALSE) {
use_domestic_requirements = FALSE, household_emissions = FALSE, show_RoW = FALSE) {
if (!is.null(model$specs$ExternalImportFactors) && model$specs$ExternalImportFactors) {
result <- calculateResultsWithExternalFactors(model, perspective, demand, location = location,
use_domestic_requirements = use_domestic_requirements,
household_emissions = household_emissions)
household_emissions = household_emissions, show_RoW = show_RoW)
} else {
# Standard model results calculation
f <- prepareDemandVectorForStandardResults(model, demand, location, use_domestic_requirements)
Expand Down Expand Up @@ -125,7 +127,8 @@ prepareDemandVectorForImportResults <- function(model, demand = "Production", lo
#' @param household_emissions, bool, if TRUE, include calculation of emissions from households
#' @return A list with LCI and LCIA results (in data.frame format) of the EEIO model.
calculateResultsWithExternalFactors <- function(model, perspective = "FINAL", demand = "Consumption", location = NULL,
use_domestic_requirements = FALSE, household_emissions = FALSE) {
use_domestic_requirements = FALSE, household_emissions = FALSE,
show_RoW = FALSE) {
result <- list()
y_d <- prepareDemandVectorForStandardResults(model, demand, location = location, use_domestic_requirements = TRUE)
y_m <- prepareDemandVectorForImportResults(model, demand, location = location)
Expand All @@ -135,14 +138,17 @@ calculateResultsWithExternalFactors <- function(model, perspective = "FINAL", de
hh_lcia <- calculateHouseholdEmissions(model, f=(y_d + y_m), location, characterized=TRUE)
}

if(model$specs$IODataSource=="stateior") {
row_names <- c(colnames(model$M_m),
gsub("/.*", "/RoW", colnames(model$M_m[, 1:(nrow(y_d)/2)])))
if(show_RoW) {
if(model$specs$IODataSource=="stateior") {
row_names <- c(colnames(model$M_m),
gsub("/.*", "/RoW", colnames(model$M_m[, 1:(nrow(y_d)/2)])))
} else {
row_names <- c(colnames(model$M_m),
gsub("/.*", "/RoW", colnames(model$M_m)))
}
} else {
row_names <- c(colnames(model$M_m),
gsub("/.*", "/RoW", colnames(model$M_m)))
row_names <- colnames(model$M_m)
}

# Calculate Final perspective results
if(perspective == "FINAL") {
# Calculate Final Perspective LCI (a matrix with total impacts in form of sector x flows)
Expand All @@ -158,14 +164,18 @@ calculateResultsWithExternalFactors <- function(model, perspective = "FINAL", de
r3[] <- 0
}

if(model$specs$IODataSource=="stateior") {
# collapse third term for SoI and RoUS
z <- r3[, 1:(ncol(r3)/2)] + r3[, ((ncol(r3)/2)+1):ncol(r3)]
# rowSums(z) == rowSums(r3)
r3 <- z
if(show_RoW) {
if(model$specs$IODataSource=="stateior") {
# collapse third term for SoI and RoUS
z <- r3[, 1:(ncol(r3)/2)] + r3[, ((ncol(r3)/2)+1):ncol(r3)]
# rowSums(z) == rowSums(r3)
r3 <- z
}
result$LCI_f <- cbind(r1 + r2, r3) # Term 3 is assigned to RoW
} else {
result$LCI_f <- r1 + r2 + r3 # Term 3 is assigned to RoW
}

result$LCI_f <- cbind(r1 + r2, r3) # Term 3 is assigned to RoW

# Calculate Final Perspective LCIA (matrix with direct impacts in form of sector x impacts)
logging::loginfo("Calculating Final Perspective LCIA with external import factors...")
result$LCIA_f <- model$C %*% result$LCI_f
Expand Down Expand Up @@ -197,17 +207,20 @@ calculateResultsWithExternalFactors <- function(model, perspective = "FINAL", de
r3[] <- 0
}

if(model$specs$IODataSource=="stateior") {
# collapse second and third term for SoI and RoUS
z <- r3[1:(nrow(r3)/2), ] + r3[((nrow(r3)/2)+1):nrow(r3), ]
# colSums(z) == colSums(r3)
r3 <- z
z <- r2[1:(nrow(r2)/2), ] + r2[((nrow(r2)/2)+1):nrow(r2), ]
# colSums(z) == colSums(r2)
r2 <- z
}

result$LCI_d <- rbind(r1, r2 + r3) # Term 2 and Term 3 are assigned to RoW
if(show_RoW) {
if(model$specs$IODataSource=="stateior") {
# collapse second and third term for SoI and RoUS
z <- r3[1:(nrow(r3)/2), ] + r3[((nrow(r3)/2)+1):nrow(r3), ]
# colSums(z) == colSums(r3)
r3 <- z
z <- r2[1:(nrow(r2)/2), ] + r2[((nrow(r2)/2)+1):nrow(r2), ]
# colSums(z) == colSums(r2)
r2 <- z
}
result$LCI_d <- cbind(r1, r2 + r3) # Term 2 and Term 3 are assigned to RoW
} else {
result$LCI_d <- r1 + r2 + r3 # All three terms combined and regions do not change
}
# Calculate Direct Perspective LCIA (matrix with direct impacts in form of sector x impacts)
logging::loginfo("Calculating Direct Perspective LCIA with external import factors...")
result$LCIA_d <- model$C %*% t(result$LCI_d)
Expand Down

0 comments on commit 455b406

Please sign in to comment.