Working on TerraPower Impacts

This commit is contained in:
Alex 2025-12-05 19:37:34 -07:00
parent 38ce251327
commit 6d855bca9f
7 changed files with 136 additions and 45 deletions

View File

@ -13,6 +13,7 @@ source("Scripts/Load_Custom_Functions/Migration_Simulation_Functions.r")
source("Scripts/Load_Custom_Functions/Birth_Simulation_Functions.r") source("Scripts/Load_Custom_Functions/Birth_Simulation_Functions.r")
source("Scripts/Load_Custom_Functions/Increment_Data_Year.r") source("Scripts/Load_Custom_Functions/Increment_Data_Year.r")
source("Scripts/Load_Custom_Functions/Single_Age_Mortality_Trend_Simulation.r") source("Scripts/Load_Custom_Functions/Single_Age_Mortality_Trend_Simulation.r")
source("Scripts/Load_Custom_Functions/Induced_Migration_Functions.r")
#######Preliminary Model Inputs #######Preliminary Model Inputs
YEARS_AHEAD <- 43 YEARS_AHEAD <- 43
@ -26,6 +27,11 @@ BIRTH_DATA <- readRDS("Data/Intermediate_Inputs/Birth_Regressions/Regression_Dat
MIGRATION_ARIMA <- readRDS("Data/Intermediate_Inputs/Migration_ARIMA_Models/Kemmerer_Diamondville_Net_Migration_ARIMA.Rds") MIGRATION_ARIMA <- readRDS("Data/Intermediate_Inputs/Migration_ARIMA_Models/Kemmerer_Diamondville_Net_Migration_ARIMA.Rds")
MIGRATION_ODDS <- readRDS("Data/Intermediate_Inputs/Migration_Trends/Migration_Age_Probability_Zero_to_85.Rds") MIGRATION_ODDS <- readRDS("Data/Intermediate_Inputs/Migration_Trends/Migration_Age_Probability_Zero_to_85.Rds")
####
OPERATORS <- readRDS("Data/Cleaned_Data/TerraPower_Impact/Operating_Worker_Related_Migration.Rds")
CONSTRUCTION <- readRDS("Data/Cleaned_Data/TerraPower_Impact/Construction_Related_Migration.Rds")
INDUCED_MIGRATION_MULTIPLIERS <- readRDS("Data/Cleaned_Data/TerraPower_Impact/Induced_Jobs.Rds")
############## ##############
#Data for death rate trends #Data for death rate trends
SINGLE_AGE_MODS <- readRDS("Data/Intermediate_Inputs/Mortality_Regression_Data/Single_Sex_Age_Time_Series_Regression.Rds") SINGLE_AGE_MODS <- readRDS("Data/Intermediate_Inputs/Mortality_Regression_Data/Single_Sex_Age_Time_Series_Regression.Rds")
@ -83,12 +89,24 @@ TOTAL_POP <- sum(DEMO)
return(list(DEMO,BIRTH_DATA,c(TOTAL_POP,TOTAL_BIRTHS,TOTAL_DEATHS,TOTAL_MIGRATION))) return(list(DEMO,BIRTH_DATA,c(TOTAL_POP,TOTAL_BIRTHS,TOTAL_DEATHS,TOTAL_MIGRATION)))
} }
MIGRATION_ARIMA_MODEL <- MIGRATION_ARIMA MIGRATION_ARIMA_MODEL <- MIGRATION_ARIMA
SINGLE_SIM <- function(DEMO,BIRTH_DATA,ST_YEAR,YEARS_AHEAD,MIGRATION_ARIMA_MODEL){ SINGLE_SIM <- function(DEMO,BIRTH_DATA,ST_YEAR,YEARS_AHEAD,MIGRATION_ARIMA_MODEL,OPERATOR_TOTAL,CONSTRUCTION_TOTAL,MIGRATION_MULTIPLIERS ){
TERRA_POWER_EFFECT <- rep(0,YEARS_AHEAD)
POP_WORK_RATIO <-3716/1920.54 #Total population of Kemmerer in 2024 divided total employment both are found in IMPLAN region details for zip code 83101
TERRA_POWER_EFFECT[3:7] <- POP_WORK_RATIO*310.75/5 #Total IMPLAN job estimate times adjusted for families and spread over five years
MIGRATION_SIM_VALUES <- round(as.vector(simulate(nsim=YEARS_AHEAD,MIGRATION_ARIMA_MODEL)+runif(1,-55,0))+TERRA_POWER_EFFECT) TERRA_POWER_EFFECT <- rep(0,YEARS_AHEAD)
OPERATOR_MIGRATION <-OPERATOR_TOTAL%>% pull("Operator_Emp_Migrated")
CONSTRUCTION_MIGRATION <- CONSTRUCTION_TOTAL%>% pull("Construction_Emp_Migrated")
OPERATOR_MIGRATION <- LOCAL_WORK_ADJ(OPERATOR_MIGRATION ,0.85) #Assume between 85%-100% operators live in Kemmerer
CONSTRUCTION_MIGRATION <- LOCAL_WORK_ADJ(CONSTRUCTION_MIGRATION,0.41) #Assume between 41%-100% operators live in Kemmerer
OPERATOR_MIGRATION <- OPERATOR_MIGRATION %>% pull("Operator_Emp_Migrated")
CONSTRUCTION_MIGRATION <- CONSTRUCTION_MIGRATION %>% pull("Construction_Emp_Migrated")
CONSTRUCTION_POPULATION_ADDED <- cumsum(CONSTRUCTION_MIGRATION)
PERMANENT_TERRAPOWER_MIGRATION <- INDUCED_SIMULATION(CONSTRUCTION_MIGRATION,OPERATOR_MIGRATION,RES)+OPERATOR_MIGRATION
TEMP_TERRAPOWER_MIGRATION_<- TERRA_POWER_EFFECT+CONSTRUCTION_MIGRATION
MIGRATION_SIM_VALUES <- round(as.vector(simulate(nsim=YEARS_AHEAD,MIGRATION_ARIMA_MODEL)+runif(1,-55,0))+PERMANENT_TERRAPOWER_MIGRATION)
#The runif applies a downshift ranging from the historic decline rate all the way to the Lincoln rate applied in the model #The runif applies a downshift ranging from the historic decline rate all the way to the Lincoln rate applied in the model
FINAL_REPORT_VALUES <- matrix(NA,ncol=6,nrow=YEARS_AHEAD) FINAL_REPORT_VALUES <- matrix(NA,ncol=6,nrow=YEARS_AHEAD)

View File

@ -10,4 +10,4 @@ Data is manually gathered from CDC WONDER data queries.
4) The world pandemic uncertainty index as collected from FRED which is used to account for pandemics in the regression, making the age time series stationary. 4) The world pandemic uncertainty index as collected from FRED which is used to account for pandemics in the regression, making the age time series stationary.
These are used to project mortality trends over time. In the case of the age adjusted data, this has local trends that can be compared to the national average. The single age-sex data is only at a national level but can be imparted to local levels as a general trend in the distribution of deaths These are used to project mortality trends over time. In the case of the age adjusted data, this has local trends that can be compared to the national average. The single age-sex data is only at a national level but can be imparted to local levels as a general trend in the distribution of deaths
--- Run Date: 2025-12-03 14:11:57 --- --- Run Date: 2025-12-05 19:32:50 ---

View File

@ -5,6 +5,8 @@ Rscript "./Scripts/1C_Download_and_Process_Demographic_Data.r"
Rscript "./Scripts/1D_Use_ACS_Census_Data_to_Estimate_Kemmerer_Demographics.r" Rscript "./Scripts/1D_Use_ACS_Census_Data_to_Estimate_Kemmerer_Demographics.r"
Rscript "./Scripts/1E_Process_WONDER_Mortality_Data.r" Rscript "./Scripts/1E_Process_WONDER_Mortality_Data.r"
Rscript "./Scripts/1F_Process_WONDER_Single_Age_Sex_Mortality_Data.r" Rscript "./Scripts/1F_Process_WONDER_Single_Age_Sex_Mortality_Data.r"
Rscript "./Scripts/1G_Terra_Power_Migration_Rates.r"
#Create data sets used in later simulations, produce some results for the report when related to this process. #Create data sets used in later simulations, produce some results for the report when related to this process.
Rscript "./Scripts/2A_Birth_Rate_Regression_and_Impart_Kemmerer_Births.r" Rscript "./Scripts/2A_Birth_Rate_Regression_and_Impart_Kemmerer_Births.r"

View File

@ -0,0 +1,82 @@
library(tidyverse)
#setwd("../")
PERM <- read_csv("./Data/Raw_Data/TerraPower_Report_Data/Monthly_In_Migration_Operations_Workforce.csv")
NUM_YEARS <- ceiling(nrow(PERM)/12)
DATES <- as.Date(paste0(2025,"-",8:12,"-",18))
for(YEAR in 2026:(2026+NUM_YEARS)){
DATES <- c(DATES,as.Date(paste0(YEAR,"-",1:12,"-",18)))
}
PERM$Date <- DATES[1:nrow(PERM)]
PERM$Year <- year(PERM$Date)
PERM$Add_Emp <- c(0,diff(PERM$In_Migration))
PERM$Perm_Migration_Including_Families <- PERM[,"In_Migration"]*0.8*3.05 #TerraPower assumes 80% have families and the average family is 3.2 people, but in wyoming the average is stated as 3.05
OPERATOR <- PERM %>% group_by(Year) %>% summarize(Operator_Emp_Average =mean(In_Migration),Operator_Emp_Migrated=sum(Add_Emp),Total_Op_and_Fam_Migration=max(Perm_Migration_Including_Families))
OPERATOR[,"Total_Op_and_Fam_Migration"] <- c(0,diff(round(pull(OPERATOR,"Total_Op_and_Fam_Migration"))))
TEMP <- read_csv("./Data/Raw_Data/TerraPower_Report_Data/Monthly_In_Migration_Construction_Workforce.csv")
TEMP$Date <- DATES[1:nrow(TEMP)]
TEMP$Year <- year(TEMP$Date)
TEMP[,1] <- 0.41*TEMP[,1] #TerraPower assumes 41% migrate into Lincoln
TEMP$Add_Emp <- c(0,diff(TEMP$In_Migration))
TEMP <- TEMP %>% group_by(Year) %>% summarize(Temp_Emp_Migration=round(sum(Add_Emp)),Average_Temp_Workers=round(mean(In_Migration) ))
TEMP[,"Total_Migration"] <- round(TEMP[,2]+TEMP[,2]*0.37*3.05) #TerraPower assumes 37% will bring families and the average family is 3.2 people, but states Wyoming averages 3.05 family save
CONSTRUCTION <-TEMP %>% select(Year,Construction_Emp_Average=Average_Temp_Workers,Construction_Emp_Migrated=Temp_Emp_Migration,Total_Con_and_Fam_Migration=Total_Migration)
TEMP$End_Year_Temp_Workers <- c(cumsum(TEMP$Temp_Emp_Migration))
#Set the total to zero
#Employment
CONSTRUCTION[4:7,3] <- CONSTRUCTION[4:7,3] -1
CONSTRUCTION[6:7,3] <- CONSTRUCTION[6:7,3] -1
#Family Migration
CONSTRUCTION[4:7,4] <- CONSTRUCTION[4:7,4] -3
#colSums(CONSTRUCTION[,3:4])
#colSums(OPERATOR[,3:4])
if(!exists("SAVE_LOC")){SAVE_LOC <-"./Data/Cleaned_Data/TerraPower_Impact/"}
dir.create(SAVE_LOC, recursive = TRUE, showWarnings = FALSE)
saveRDS(CONSTRUCTION,paste0(SAVE_LOC,"Construction_Related_Migration.Rds"))
saveRDS(OPERATOR,paste0(SAVE_LOC,"Operating_Worker_Related_Migration.Rds"))
#####Double check that Kemmere can house all people
#1,451 tota units required acording to TerraPower
REQUIRED_IN_LIN <- 1451*0.41
TOTAL_IN_KEM <- 333 #According to ACS data
EXPECTED_NEW_IN_KEM <- 750 #According to TerraPower Kemmerer is agressively zoning and will conservativley add 750 houses available to the project
(0.75*TOTAL_IN_KEM+750)/REQUIRED_IN_LIN #Shows a surplus of houses in Kemmerer
############################################################TerraPower IMPLAN estimates
CLEAN_IMPLAN <- function(DF){
DF <- DF[,-1]
COLNAMES <- c("Industry","Direct","Indirect","Induced","Total")
colnames(DF) <- COLNAMES
DF<- DF %>% filter(!is.na(Industry))
DF[,1] <- trimws(str_replace_all(str_replace_all(t(DF[,1]), "[:digit:]|-| |A |B ", "")," ",""))
return(DF)
}
KEM_CON_IMPLAN <- CLEAN_IMPLAN(read_csv("Data/Raw_Data/IMPLAN_Employment_Outputs_2_Difit_NAICS/Kemmerer_100_Construction_Workers.csv"))
LIN_CON_IMPLAN <- CLEAN_IMPLAN(read_csv("Data/Raw_Data/IMPLAN_Employment_Outputs_2_Difit_NAICS/Lincoln_100_Construction_Workers.csv"))
CON_DIFF <- LIN_CON_IMPLAN %>% mutate(LIN_CON_TOTAL=Total-Direct) %>% select(Industry,LIN_CON_TOTAL) %>% full_join(KEM_CON_IMPLAN %>% mutate(KEM_CON_TOTAL=Total-Direct) %>% select(Industry,KEM_CON_TOTAL))
CON_DIFF[,"Gap"] <- CON_DIFF[,2]-CON_DIFF[,3]
CON_DIFF %>% print(n=100)
CON_DIFF$Adjustable_Industry <- CON_DIFF$Industry %in% c('Accommodation and Food Services','Retail Trade','Health Care and Social Assistance','Real Estate and Rental and Leasing','Arts, Entertainment, and Recreation','Manufacturing','Other Services (except Public Administration)')
CON_DIFF[which(CON_DIFF$Adjustable_Industry),]
CONSTRUCTION_ADDED_JOBS <- CON_DIFF %>% mutate(KEM_POSSIBLE_INDUCED=Gap*Adjustable_Industry) %>% select(KEM_INDUCED= KEM_CON_TOTAL,KEM_POSSIBLE_INDUCED)
CONSTRUCTION_ADDED_JOBS <- colSums(CONSTRUCTION_ADDED_JOBS)/100
KEM_OP_IMPLAN <- CLEAN_IMPLAN(read_csv("Data/Raw_Data/IMPLAN_Employment_Outputs_2_Difit_NAICS/Kemmerer_100_Nuclear_Operators.csv"))
LIN_OP_IMPLAN <- CLEAN_IMPLAN(read_csv("Data/Raw_Data/IMPLAN_Employment_Outputs_2_Difit_NAICS/Lincoln_100_Nuclear_Operators.csv"))
OP_DIFF <- LIN_OP_IMPLAN %>% mutate(LIN_OP_TOTAL=Total-Direct) %>% select(Industry,LIN_OP_TOTAL) %>% full_join(KEM_OP_IMPLAN %>% mutate(KEM_OP_TOTAL=Total-Direct) %>% select(Industry,KEM_OP_TOTAL))
OP_DIFF
OP_DIFF[,"Gap"] <- OP_DIFF[,2]-OP_DIFF[,3]
OP_DIFF$Adjustable_Industry <- OP_DIFF$Industry %in% c('Accommodation and Food Services','Retail Trade','Health Care and Social Assistance','Real Estate and Rental and Leasing','Arts, Entertainment, and Recreation','Manufacturing','Other Services (except Public Administration)')
OP_DIFF
OPERATION_ADDED_JOBS <- OP_DIFF %>% mutate(KEM_POSSIBLE_INDUCED=Gap*Adjustable_Industry) %>% select(KEM_INDUCED= KEM_OP_TOTAL,KEM_POSSIBLE_INDUCED)
OPERATION_ADDED_JOBS <- colSums(OPERATION_ADDED_JOBS )/100
RES <- rbind(CONSTRUCTION_ADDED_JOBS,OPERATION_ADDED_JOBS) %>% as_tibble
POP_WORK_RATIO <-3716/1920.54 #Total population of Kemmerer in 2024 divided total employment both are found in IMPLAN region details for zip code 83101
RES*POP_WORK_RATIO #Total family included migration, converted per person (rather than per 100 jobs)
RES$Job_Type <- c("Construction","Operator")
RES <- RES[,c(3,1:2)]
saveRDS(RES,paste0(SAVE_LOC,"Induced_Jobs.Rds"))

View File

@ -97,17 +97,19 @@ try(etable(MOD_VIEW_BIRTHS,MOD_VIEW_BIRTHS_2016,MOD_VIEW_BIRTHS_1985,headers=HEA
TEMP <- REG_REDUCED_DATA
TEMP$RESID <- resid(MOD_BIRTHS )
#Kemmerer ACF/PACF #Kemmerer ACF/PACF
C_TEMP <- TEMP %>% filter(Region=='Kemmerer & Diamondville') %>% arrange(Year) C_TEMP <- TEMP %>% filter(KEM==1) %>% arrange(Year)
png(paste0(SAVE_FIG_LOC,"/Kemmerer_ACF.png"), width = 12, height = 8, units = "in", res = 600) png(paste0(SAVE_FIG_LOC,"/Kemmerer_ACF.png"), width = 12, height = 8, units = "in", res = 600)
acf(C_TEMP$RESID,main='ACF of Kemmerer & Diamondville Birth Estimate Residuals',xlab="Lag (Years)") acf(C_TEMP$RESID,main='ACF of Kemmerer & Diamondville Birth Estimate Residuals',xlab="Lag (Years)")
dev.off() dev.off()
png(paste0(SAVE_FIG_LOC,"/Kemmerer_PACF.png"), width = 12, height = 8, units = "in", res = 600) png(paste0(SAVE_FIG_LOC,"/Kemmerer_PACF.png"), width = 12, height = 8, units = "in", res = 600)
pacf(C_TEMP$RESID,main='PACF of Kemmerer & Diamondville Birth Estimate Residuals',xlab="Lag (Years)") pacf(C_TEMP$RESID,main='PACF of Kemmerer & Diamondville Birth Estimate Residuals',xlab="Lag (Years)")
dev.off() dev.off()
#Lincoln total ACF/PACF #Lincoln total ACF/PACF
C_TEMP <- TEMP %>% filter(Region=='Lincoln') %>% arrange(Year) C_TEMP <- TEMP %>% filter(Region=='Lincoln',KEM==0) %>% arrange(Year)
png(paste0(SAVE_FIG_LOC,"/Lincoln_ACF.png"), width = 12, height = 8, units = "in", res = 600) png(paste0(SAVE_FIG_LOC,"/Lincoln_ACF.png"), width = 12, height = 8, units = "in", res = 600)
acf(C_TEMP$RESID,main='ACF of Lincoln County Birth Estimate Residuals',xlab="Lag (Years)") acf(C_TEMP$RESID,main='ACF of Lincoln County Birth Estimate Residuals',xlab="Lag (Years)")
dev.off() dev.off()
@ -115,7 +117,7 @@ C_TEMP <- TEMP %>% filter(Region=='Lincoln') %>% arrange(Year)
pacf(C_TEMP$RESID,main='PACF of Lincoln County Birth Estimate Residuals',xlab="Lag (Years)") pacf(C_TEMP$RESID,main='PACF of Lincoln County Birth Estimate Residuals',xlab="Lag (Years)")
dev.off() dev.off()
#Lincoln Other (Not Kemmerer) ACF/PACF #Lincoln Other (Not Kemmerer) ACF/PACF
C_TEMP <- TEMP %>% filter(Region=='Lincoln_Other') %>% arrange(Year) C_TEMP <- TEMP %>% filter(Region=='Lincoln_Other',KEM==0) %>% arrange(Year)
png(paste0(SAVE_FIG_LOC,"/Lincoln_Other_Areas_ACF.png"), width = 12, height = 8, units = "in", res = 600) png(paste0(SAVE_FIG_LOC,"/Lincoln_Other_Areas_ACF.png"), width = 12, height = 8, units = "in", res = 600)
acf(C_TEMP$RESID,main='ACF of Other Parts of Lincoln County Birth Estimate Residuals',xlab="Lag (Years)") acf(C_TEMP$RESID,main='ACF of Other Parts of Lincoln County Birth Estimate Residuals',xlab="Lag (Years)")
dev.off() dev.off()
@ -124,7 +126,8 @@ C_TEMP <- TEMP %>% filter(Region=='Lincoln_Other') %>% arrange(Year)
dev.off() dev.off()
####Create data stubs to start a simulation. That is predict the births from this most recent year. Include records from various years of potential interest ####Create data stubs to start a simulation. That is predict the births from this most recent year. Include records from various years of potential interest
ST_REG_DATA <- REG_REDUCED_DATA %>% filter(Region=='Lincoln') %>% filter(Year==max(Year)) %>% rbind(REG_REDUCED_DATA %>% filter(Region=='Kemmerer & Diamondville') %>% filter(Year==max(Year))) %>% rbind(REG_REDUCED_DATA %>% filter(Region=='Lincoln_Other') %>% filter(Year==max(Year))) %>% rbind(REG_REDUCED_DATA %>% filter(Region=='Lincoln') %>% filter(Year==2016)) %>% rbind(REG_REDUCED_DATA %>% filter(Region=='Kemmerer & Diamondville') %>% filter(Year==2016)) %>% rbind(REG_REDUCED_DATA %>% filter(Region=='Lincoln_Other') %>% filter(Year==2016)) %>% rbind(REG_REDUCED_DATA %>% filter(Region=='Lincoln') %>% filter(Year==1985)) %>% rbind(REG_REDUCED_DATA %>% filter(KEM==1) %>% filter(Year==max(Year)))
ST_REG_DATA <- REG_REDUCED_DATA %>% filter(Region=='Lincoln') %>% filter(Year==max(Year)) %>% rbind(REG_REDUCED_DATA %>% filter(KEM==1) %>% filter(Year==max(Year))) %>% rbind(REG_REDUCED_DATA %>% filter(Region=='Lincoln_Other') %>% filter(Year==max(Year))) %>% rbind(REG_REDUCED_DATA %>% filter(Region=='Lincoln') %>% filter(Year==2016)) %>% rbind(REG_REDUCED_DATA %>% filter(Region=='Kemmerer & Diamondville') %>% filter(Year==2016)) %>% rbind(REG_REDUCED_DATA %>% filter(Region=='Lincoln_Other') %>% filter(Year==2016)) %>% rbind(REG_REDUCED_DATA %>% filter(Region=='Lincoln') %>% filter(Year==1985)) %>% rbind(REG_REDUCED_DATA %>% filter(KEM==1) %>% filter(Year==max(Year))) %>% unique %>% arrange(KEM,Year)
if(!exists("SAVE_REG_LOC")){SAVE_REG_LOC <- "Data/Intermediate_Inputs/Birth_Regressions"} if(!exists("SAVE_REG_LOC")){SAVE_REG_LOC <- "Data/Intermediate_Inputs/Birth_Regressions"}
dir.create(SAVE_REG_LOC , recursive = TRUE, showWarnings = FALSE) dir.create(SAVE_REG_LOC , recursive = TRUE, showWarnings = FALSE)

View File

@ -0,0 +1,20 @@
#Takes the added jobs table and downshift for people living outside of Kemmerer but in Lincoln
LOCAL_WORK_ADJ <- function(DF,MIN_LOCAL,MAX_LOCAL=1){
DF[,-1]<- runif(1,MIN_LOCAL,MAX_LOCAL)*DF[,-1]#Random range people choosing to live outside of Kemmerer assumed to be between 85% and 100%
DF[,-1:-2] <-round(DF[,-1:-2])
return(DF)
}
#Find the expected total of new induced jobs from TerraPower (Includes construction entering and leaving, and operators entering)
INDUCED_SIMULATION <- function(CONSTRUCTION_MIGRATION,OPERATOR_MIGRATION,INDUCED_MIGRATION_TABLE){
ADDED_FROM_BASELINE <- runif(1) #The percentage of the possible growth in industries like restaurants to add compared to the Kemmerer IMPLAN model which understates possible structural growth
EST_CONST_INDUCED <- round(CONSTRUCTION_MIGRATION* as.numeric(INDUCED_MIGRATION_TABLE[INDUCED_MIGRATION_TABLE$Job_Type=="Construction",2]+ADDED_FROM_BASELINE *INDUCED_MIGRATION_TABLE[INDUCED_MIGRATION_TABLE$Job_Type=="Construction",3]))
EST_CONST_INDUCED[7] <- EST_CONST_INDUCED[7]-sum(EST_CONST_INDUCED) #Make sure the sums are still zero after rounding takes place, if not make the last year make up the difference
#########Induced migration from operating
EST_OP_INDUCED <- round(OPERATOR_MIGRATION * as.numeric(INDUCED_MIGRATION_TABLE[INDUCED_MIGRATION_TABLE$Job_Type=="Operator",2]+ADDED_FROM_BASELINE*INDUCED_MIGRATION_TABLE[INDUCED_MIGRATION_TABLE$Job_Type=="Operator",3]))
INDUCED <- EST_OP_INDUCED +EST_CONST_INDUCED
return(INDUCED)
}

View File

@ -1,34 +0,0 @@
library(tidyverse)
PERM <- read_csv("./Data/Raw_Data/TerraPower_Report_Data/Monthly_In_Migration_Operations_Workforce.csv")
NUM_YEARS <- ceiling(nrow(PERM)/12)
c(8:12,rep(1:12,ceiling(nrow(PERM)/12)))[1:nrow(PERM)]
DATES <- as.Date(paste0(2025,"-",8:12,"-",18))
for(YEAR in 2026:(2026+NUM_YEARS)){
DATES <- c(DATES,as.Date(paste0(YEAR,"-",1:12,"-",18)))
}
PERM$Date <- DATES[1:nrow(PERM)]
PERM$Year <- year(PERM$Date)
PERM$Add_Emp <- c(0,diff(PERM$In_Migration))
PERM %>% group_by(Year) %>% mutate(Total_Wages=Average_Wages_Present_USD*In_Migration) %>% group_by(Year) %>% summarize(Total_Wages=sum(Total_Wages),Total_Wages=sum(ifelse(Year==2031,Total_Wages*3,Total_Wages)))
%>% summarize(Perm_Emp_Migration=sum(Add_Emp),Total_Wages=sum(Average_Wages_Present_USD*In_Migration),Current_Perm_Workers=round(mean(In_Migration) ))
PERM[7,3]<-PERM[7,3]*3 #4 months (1/3) year only seen in sample
PERM[,"Total_Migration"] <- round(PERM[,2]+PERM[,2]*0.8*3.05) #TerraPower assumes 80% have families and the average family is 3.2 people, but in wyoming the average is stated as 3.05
PERM
TEST <- read_csv("./Data/Raw_Data/TerraPower_Report_Data/Monthly_In_Migration_Operations_Workforce.csv")
TEST[59,]*12
TEMP <- read_csv("./Data/Raw_Data/TerraPower_Report_Data/Monthly_In_Migration_Construction_Workforce.csv")
TEMP[,1] <- TEMP[,1]*0.41 #TerraPower assumes 41% migrate into Lincoln
TEMP[,1] <- TEMP[,1]*0.80 #I assume 80% of lincoln will be in Kemmerer
TEMP$Date <- DATES[1:nrow(TEMP)]
TEMP$Year <- year(TEMP$Date)
TEMP$Add_Emp <- c(0,diff(TEMP$In_Migration))
TEMP <- TEMP %>% group_by(Year) %>% summarize(Temp_Emp_Migration=sum(Add_Emp),Total_Wages=sum(Average_Wages_Present_USD*In_Migration),Current_Temp_Workers=round(mean(In_Migration) ))
TEMP[,"Total_Migration"] <- round(TEMP[,2]+TEMP[,2]*0.37*3.05) #TerraPower assumes 37% will bring families and the average family is 3.2 people, but states Wyoming averages 3.05 family save
TEMP[,2] <- round(TEMP[,2])
TEMP[4:7,2] <- TEMP[4:7,2]-1
TEMP[7,2] <- TEMP[7,2]-1
TEMP[4:7,5] <- TEMP[4:7,5] -2
TEMP[7,5] <- TEMP[7,5] -1