Skip to content

Commit

Permalink
replace DisaggregatedSectorCodes with NewSectorCodes to align wit…
Browse files Browse the repository at this point in the history
…h useeior v1.5
  • Loading branch information
bl-young committed Apr 9, 2024
1 parent 1a487a2 commit 3e69c4f
Showing 1 changed file with 14 additions and 16 deletions.
30 changes: 14 additions & 16 deletions R/StateDisaggFunctions.R
Original file line number Diff line number Diff line change
Expand Up @@ -30,8 +30,6 @@ getStateModelDisaggSpecs <- function(configfile, statefile = NULL){
#' @param disaggConfigpath str, path for statefile
#' @return A stateior model object with the state-specific disaggregation specs included in model$specs$STateDisaggSpecs object
getStateSpecificDisaggSpecs <- function(disaggConfigpath, statefile){

temp <-1
filename <- file.path(dirname(disaggConfigpath), statefile)
stateFileDF <- utils::read.table(filename, sep = ",", header = TRUE, stringsAsFactors = FALSE, check.names = FALSE)
return(stateFileDF)
Expand Down Expand Up @@ -285,7 +283,7 @@ calculateStateIndustryCommodityOuput <- function(model){
disaggregateStateSectorLists <- function(code_vector, disagg) {

originalSectorCode <- gsub("\\/.*","",disagg$OriginalSectorCode) # remove everything after "/"
disaggCodes <- gsub("\\/.*","",disagg$DisaggregatedSectorCodes) # remove everything after "/"
disaggCodes <- gsub("\\/.*","",disagg$NewSectorCodes) # remove everything after "/"
originalIndex <- grep(paste0("^",originalSectorCode,"$"), code_vector) # the ^ and $ are required to find an exact match

newList <- append(code_vector[1:originalIndex -1], disaggCodes)
Expand Down Expand Up @@ -319,37 +317,37 @@ createDisaggFilesFromProxyData <- function(model, disagg, disaggYear, disaggStat
# If the state/year combination is not found, assume a uniform split between sectors
if(dim(stateDFYear)[1] == 0){

activity <- unlist(disagg$DisaggregatedSectorCodes)
uniformAllocationVector <- 1/length(disagg$DisaggregatedSectorCodes)
share <- rep(uniformAllocationVector,length(disagg$DisaggregatedSectorCodes))
activity <- unlist(disagg$NewSectorCodes)
uniformAllocationVector <- 1/length(disagg$NewSectorCodes)
share <- rep(uniformAllocationVector,length(disagg$NewSectorCodes))

stateDFYear <- data.frame(State = rep(disaggState, length(disagg$DisaggregatedSectorCodes)),
stateDFYear <- data.frame(State = rep(disaggState, length(disagg$NewSectorCodes)),
Activity = activity,
Share = share,
Year = rep(disaggYear, length(disagg$DisaggregatedSectorCodes)))
Year = rep(disaggYear, length(disagg$NewSectorCodes)))

}

print(paste0("For ",disaggState,"-",disaggYear, " the allocation to disaggregate ",
disagg$OriginalSectorCode, " into ", disagg$DisaggregatedSectorCodes, " is ", stateDFYear$Share))
disagg$OriginalSectorCode, " into ", disagg$NewSectorCodes, " is ", stateDFYear$Share))

# Default Make DF based on proxy employment values
# Specifying commodity disaggregation (column splits) for Make DF
industries <- c(rep(disagg$OriginalSectorCode,length(disagg$DisaggregatedSectorCodes)))
commodities <- unlist(disagg$DisaggregatedSectorCodes)
PercentMake <- stateDFYear$Share # need to add code to ensure that the order of stateDF$Share is the same as the order of disagg$DisaggregatedSectorCodes
note <- c(rep("CommodityDisagg", length(disagg$DisaggregatedSectorCodes)))
industries <- c(rep(disagg$OriginalSectorCode,length(disagg$NewSectorCodes)))
commodities <- unlist(disagg$NewSectorCodes)
PercentMake <- stateDFYear$Share # need to add code to ensure that the order of stateDF$Share is the same as the order of disagg$NewSectorCodes
note <- c(rep("CommodityDisagg", length(disagg$NewSectorCodes)))

makeDF <- data.frame(cbind(data.frame(industries), data.frame(commodities), data.frame(PercentMake), data.frame(note))) #need to rename the columns with the correct column names
colnames(makeDF) <- c("IndustryCode","CommodityCode", "PercentMake", "Note")


# Default Use DF based on employment ratios
# Specifying industry disaggregation (column splits) for Use DF
industries <- unlist(disagg$DisaggregatedSectorCodes)
commodities <- c(rep(disagg$OriginalSectorCode,length(disagg$DisaggregatedSectorCodes)))
industries <- unlist(disagg$NewSectorCodes)
commodities <- c(rep(disagg$OriginalSectorCode,length(disagg$NewSectorCodes)))
PercentUse <- stateDFYear$Share
note <- c(rep("IndustryDisagg", length(disagg$DisaggregatedSectorCodes)))
note <- c(rep("IndustryDisagg", length(disagg$NewSectorCodes)))

useDF <- data.frame(cbind(data.frame(industries), data.frame(commodities), data.frame(PercentUse), data.frame(note))) #need to rename the columns with the correct column names
useDF_2 <- makeDF # so that colnames match
Expand Down

0 comments on commit 3e69c4f

Please sign in to comment.