Skip to content

Commit

Permalink
drop calculateNMatrix per USEPA/useeior#317, resolves #13
Browse files Browse the repository at this point in the history
  • Loading branch information
bl-young committed Oct 30, 2024
1 parent 761bec4 commit cf3a3b9
Show file tree
Hide file tree
Showing 4 changed files with 2 additions and 29 deletions.
25 changes: 0 additions & 25 deletions R/StateEEIOCalculations.R
Original file line number Diff line number Diff line change
Expand Up @@ -316,31 +316,6 @@ calculateHouseholdShares <- function(model, indicator) {
return(lcia)
}

# Calculate N matrix, not created by default w/ import factors
calculateNMatrix <- function(model, state) {
loc <- paste0("US-", state)
year <- toString(model$specs$IOYear)
result <- calculateEEIOModel(model, demand = "Consumption", perspective="FINAL", location = loc)
N_df <- as.data.frame(reshape2::melt(t(result[[2]])))
colnames(N_df) <- c("Indicator", "Sector", "Value")
demand_total <- model[["DemandVectors"]][["vectors"]][[paste0(year, "_", loc, "_Consumption_Complete")]]
demand_domestic <- model[["DemandVectors"]][["vectors"]][[paste0(year, "_", loc, "_Consumption_Domestic")]]
demand_imports <- demand_total - demand_domestic
## Note demand_imports only has values assigned to SoI

N_df <- merge(N_df, demand_total, by.x = "Sector", by.y=0)
N_df <- merge(N_df, demand_domestic, by.x = "Sector", by.y=0, suffixes=c("", "_d"))
N_df <- merge(N_df, demand_imports, by.x = "Sector", by.y=0, suffixes=c("", "_m"))
N_df["N_coeff"] <- N_df["Value"] / N_df["y"]
N_df["N_coeff"][is.na(N_df["N_coeff"])] <- 0
mat <- as.matrix(N_df["N_coeff"])
rownames(mat) <- N_df[["Sector"]]
mat <- t(as.matrix(mat[match(colnames(model[["D"]]), rownames(mat)),]))
rownames(mat) <- "Greenhouse Gases"
model[["N"]] <- mat
return(model)
}

#make into a matrix and transpose
matricizeandflip <- function(StateResult) {
m <- t(as.matrix(colSums(StateResult, na.rm = TRUE)))
Expand Down
3 changes: 0 additions & 3 deletions R/StateEEIOFigures.R
Original file line number Diff line number Diff line change
Expand Up @@ -121,9 +121,6 @@ twoRegionTimeSeriesPlot <- function(df,


contributionToImpactBySectorChart <- function(model, sector, indicator, state) {
if(is.null(model[["N"]])) {
model <- calculateNMatrix(model, state)
}
df0 <- useeior::disaggregateTotalToDirectAndTier1(model, indicator)

sector_codes <- c(paste0(sector, "/US-", state), paste0(sector, "/RoUS"))
Expand Down
2 changes: 1 addition & 1 deletion R/utils.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
# useeior_ver = "v1.6.0"
# useeior_ver = "v1.6.1"
useeior_ver = "develop"

#' Install useeior (via pak).
Expand Down
1 change: 1 addition & 0 deletions examples/BuildandSaveModelsLocally.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -82,6 +82,7 @@ for(state in states) {
m <- useeior:::loadandbuildIndicators(m)
m <- useeior:::loadDemandVectors(m)
m <- useeior:::constructEEIOMatrices(m)
printValidationResults(m)
saveRDS(m, file.path("..","models",paste0(modelname,".rds")))
if(params$write) {
Expand Down

0 comments on commit cf3a3b9

Please sign in to comment.