diff --git a/R/00-update_refs.R b/R/00-update_refs.R index a4a21ea73..33022edf6 100644 --- a/R/00-update_refs.R +++ b/R/00-update_refs.R @@ -64,19 +64,6 @@ get_dd_period <- function() { "Jul16_Jun24" } -#' The latest financial year for Cost uplift setting -#' -#' @description Get the latest year for cost uplift -#' -#' @return The financial year format -#' -#' @export -#' -#' @family initialisation -latest_cost_year <- function() { - "2324" -} - #' The year list for slf to update #' #' @description Get the vector of years to update slf diff --git a/R/add_activity_after_death_flag.R b/R/add_activity_after_death_flag.R index a45e4296a..5e800c80b 100644 --- a/R/add_activity_after_death_flag.R +++ b/R/add_activity_after_death_flag.R @@ -26,7 +26,7 @@ add_activity_after_death_flag <- function( by = "chi", suffix = c("", "_boxi") ) %>% - dplyr::filter(.data$deceased == TRUE | .data$deceased_boxi == TRUE) %>% + dplyr::filter(.data$deceased == TRUE) %>% dplyr::distinct() @@ -72,16 +72,6 @@ add_activity_after_death_flag <- function( )) - # Check and print error message for records which already are TRUE for the deceased variable in the episode file, but this doesn't match the - # BOXI deceased variable - check_deceased_match <- flag_data %>% - dplyr::filter(.data$deceased != .data$deceased_boxi) - - if (nrow(check_deceased_match) != 0) { - warning("There were records in the episode file which have a deceased variable which does not match the BOXI NRS deceased variable") - } - - # Fill in date of death if missing in the episode file but available in BOXI lookup, due to historic dates of death not being carried # over from previous financial years flag_data <- flag_data %>% @@ -94,13 +84,15 @@ add_activity_after_death_flag <- function( final_data <- data %>% dplyr::left_join( flag_data, + # TODO: this join_by is not 100% accurate. Consider use ep_file_row_id to join by = c("year", "chi", "record_keydate1", "record_keydate2"), na_matches = "never" ) %>% dplyr::mutate(death_date = lubridate::as_date(ifelse(is.na(death_date) & !(is.na(death_date_boxi)), death_date_boxi, death_date ))) %>% - dplyr::select(-death_date_boxi) + dplyr::select(-death_date_boxi) %>% + dplyr::distinct() diff --git a/R/check_year_valid.R b/R/check_year_valid.R index 2197d8c0e..217aa1c2b 100644 --- a/R/check_year_valid.R +++ b/R/check_year_valid.R @@ -46,7 +46,7 @@ check_year_valid <- function( return(FALSE) } else if (year >= "2425" && type %in% "sparra") { return(FALSE) - } else if (year >= "2425" && type %in% c("ch", "hc", "sds", "at")) { + } else if (year >= "2526" && type %in% c("ch", "hc", "sds", "at")) { return(FALSE) } diff --git a/R/cost_uplift.R b/R/cost_uplift.R index f14600da6..abbbd9b5a 100644 --- a/R/cost_uplift.R +++ b/R/cost_uplift.R @@ -86,3 +86,21 @@ lookup_uplift <- function(data) { return(data) } + +#' The latest financial year for Cost uplift setting +#' +#' @description Get the latest year for cost uplift +#' latest_cost_year() is hard coded in cost_uplift(). +#' 2223 is not changed automatically with time passes. +#' It is changed only when we get a new instruction from somewhere about cost uplift. +#' Do not change unless specific instructions. +#' Changing this means that we need to change cost_uplift(). +#' +#' @return The financial year format +#' +#' @export +#' +#' @family initialisation +latest_cost_year <- function() { + "2223" +} diff --git a/R/create_episode_file.R b/R/create_episode_file.R index 7909e2e7f..dd22dbc1d 100644 --- a/R/create_episode_file.R +++ b/R/create_episode_file.R @@ -179,6 +179,14 @@ create_episode_file <- function( ) } + if (!check_year_valid(year, type = "dn")) { + episode_file <- episode_file %>% + dplyr::mutate( + ccm = NA, + total_no_dn_contacts = NA + ) + } + if (anon_chi_out) { episode_file <- slfhelper::get_anon_chi(episode_file) } diff --git a/R/create_individual_file.R b/R/create_individual_file.R index dc15fcb0e..f826294d1 100644 --- a/R/create_individual_file.R +++ b/R/create_individual_file.R @@ -78,7 +78,7 @@ create_individual_file <- function( if (!check_year_valid(year, type = c("ch", "hc", "at", "sds"))) { individual_file <- individual_file %>% - aggregate_by_chi(exclude_sc_var = TRUE) + aggregate_by_chi(year = year, exclude_sc_var = TRUE) } else { individual_file <- individual_file %>% aggregate_ch_episodes() %>% diff --git a/R/join_deaths_data.R b/R/join_deaths_data.R index d2fc51b91..5e61a2082 100644 --- a/R/join_deaths_data.R +++ b/R/join_deaths_data.R @@ -15,7 +15,8 @@ join_deaths_data <- function( return( data %>% dplyr::left_join( - slf_deaths_lookup, + slf_deaths_lookup %>% + dplyr::distinct(chi, .keep_all = TRUE), by = "chi", na_matches = "never", relationship = "many-to-one" diff --git a/R/link_delayed_discharge_eps.R b/R/link_delayed_discharge_eps.R index a28ee3b0f..b80b35807 100644 --- a/R/link_delayed_discharge_eps.R +++ b/R/link_delayed_discharge_eps.R @@ -14,6 +14,8 @@ link_delayed_discharge_eps <- function( dd_data = read_file(get_source_extract_path(year, "dd")) %>% slfhelper::get_chi()) { cli::cli_alert_info("Link delayed discharge to episode file function started at {Sys.time()}") + names_ep <- names(episode_file) + episode_file <- episode_file %>% dplyr::mutate( # remember to revoke the cij_end_date with dummy_cij_end @@ -286,6 +288,11 @@ link_delayed_discharge_eps <- function( )) %>% dplyr::group_by(.data$chi, .data$cij_marker) %>% dplyr::mutate(cij_delay = max(.data$has_delay)) %>% + dplyr::mutate(cij_delay = dplyr::if_else(cij_delay == "0", + FALSE, + TRUE, + missing = NA + )) %>% dplyr::ungroup() %>% # add yearstay and monthly beddays # count_last = TRUE because DD counts last day and not the first @@ -299,37 +306,43 @@ link_delayed_discharge_eps <- function( yearstay = rowSums(dplyr::pick(dplyr::ends_with("_beddays"))) ) %>% # tidy up and rename columns to match the format of episode files + # keep variables from ep files dplyr::select( + -c( + "ep_file_row_id", + "year", + "recid", + "record_keydate1", + "record_keydate2", + "postcode", + "hbtreatcode", + "location", + "spec", + ## following are dummy variables + "cij_start_date_lower", + "cij_end_date_upper", + "cij_end_month", + "is_dummy_cij_start", + "dummy_cij_start", + "is_dummy_cij_end", + "dummy_cij_end", + "datediff_start", + "datediff_end", + "has_delay", + "is_dummy_keydate2", + "dummy_keydate2", + "dummy_id" + ) + ) %>% + dplyr::rename( "year" = "year_dd", "recid" = "recid_dd", "record_keydate1" = "record_keydate1_dd", "record_keydate2" = "record_keydate2_dd", - "smrtype", - "chi", - "gender", - "dob", - "age", - "gpprac", "postcode" = "postcode_dd", - "dd_responsible_lca", "hbtreatcode" = "hbtreatcode_dd", - "delay_end_reason", - "primary_delay_reason", - "secondary_delay_reason", - "cij_marker", - "cij_start_date", - "cij_end_date", - "cij_pattype_code", - "cij_ipdc", - "cij_admtype", - "cij_adm_spec", - "cij_dis_spec", - "cij_delay", - "location", "spec" = "spec_dd", - "dd_quality", - dplyr::ends_with("_beddays"), - "yearstay" + "location" = "location_dd" ) %>% # Combine DD with episode data dplyr::bind_rows( @@ -345,7 +358,19 @@ link_delayed_discharge_eps <- function( "dummy_cij_end" ) ) - ) + ) %>% + # populate cij_delay dd details back to ep + dplyr::group_by(chi, cij_marker) %>% + dplyr::mutate( + has_dd = any(recid == "DD"), + delay_dd = any(cij_delay) + ) %>% + dplyr::ungroup() %>% + dplyr::mutate(cij_delay = dplyr::if_else(has_dd, + delay_dd, + cij_delay + )) %>% + dplyr::select(-c("has_dd", "delay_dd")) return(linked_data) } diff --git a/R/process_extract_alarms_telecare.R b/R/process_extract_alarms_telecare.R index 6c481c3a4..9d47dd5f0 100644 --- a/R/process_extract_alarms_telecare.R +++ b/R/process_extract_alarms_telecare.R @@ -41,7 +41,7 @@ process_extract_alarms_telecare <- function( "smrtype", "chi", "dob", - "person_id", + # "person_id", "gender", "postcode", "sc_send_lca", diff --git a/R/process_extract_care_home.R b/R/process_extract_care_home.R index db7997061..dbf817af4 100644 --- a/R/process_extract_care_home.R +++ b/R/process_extract_care_home.R @@ -115,7 +115,7 @@ process_extract_care_home <- function( "recid", "smrtype", "chi", - "person_id", + # "person_id", "dob", "gender", "postcode", diff --git a/R/process_extract_home_care.R b/R/process_extract_home_care.R index 831496bd2..651be172d 100644 --- a/R/process_extract_home_care.R +++ b/R/process_extract_home_care.R @@ -96,7 +96,7 @@ process_extract_home_care <- function( "cost_total_net", "hc_provider", "hc_reablement", - "person_id" + # "person_id" ) %>% slfhelper::get_anon_chi() diff --git a/R/process_extract_sds.R b/R/process_extract_sds.R index ce317c8b9..f8e5f8579 100644 --- a/R/process_extract_sds.R +++ b/R/process_extract_sds.R @@ -41,7 +41,7 @@ process_extract_sds <- function( "smrtype", "chi", "dob", - "person_id", + # "person_id", "gender", "postcode", "sc_send_lca", diff --git a/R/process_lookup_sc_client.R b/R/process_lookup_sc_client.R index f1e03ee95..b8fc2fb6d 100644 --- a/R/process_lookup_sc_client.R +++ b/R/process_lookup_sc_client.R @@ -195,7 +195,7 @@ process_lookup_sc_client <- ) %>% dplyr::arrange(.data$chi, .data$count_not_known) %>% dplyr::distinct(.data$chi, .keep_all = TRUE) %>% - dplyr::select(-.data$sending_location) %>% + dplyr::select(-.data$sending_location, -.data$count_not_known) %>% slfhelper::get_anon_chi() if (write_to_disk) { diff --git a/R/process_refined_death.R b/R/process_refined_death.R index 48f14fd43..dc7663221 100644 --- a/R/process_refined_death.R +++ b/R/process_refined_death.R @@ -50,11 +50,12 @@ process_refined_death <- function( fy = phsmethods::extract_fin_year(death_date), fy = as.character(paste0(substr(fy, 3, 4), substr(fy, 6, 7))) ) + # TODO: check distinct death data by chi while keeping chi==NA records if (write_to_disk) { write_file( refined_death, - get_combined_slf_deaths_lookup_path() + get_combined_slf_deaths_lookup_path(create = TRUE) ) } diff --git a/R/process_sc_all_alarms_telecare.R b/R/process_sc_all_alarms_telecare.R index c583fa8a7..aafc3d727 100644 --- a/R/process_sc_all_alarms_telecare.R +++ b/R/process_sc_all_alarms_telecare.R @@ -87,11 +87,11 @@ process_sc_all_alarms_telecare <- function( # Replace social_care_id with latest if needed (assuming replace_sc_id_with_latest is a custom function) data <- replace_sc_id_with_latest(data) - data$person_id <- paste0( - data$sending_location, - "-", - data$social_care_id - ) + # data$person_id <- paste0( + # data$sending_location, + # "-", + # data$social_care_id + # ) # Deal with episodes that have a package across quarters data[, pkg_count := seq_len(.N), by = list( @@ -125,7 +125,7 @@ process_sc_all_alarms_telecare <- function( dob = data.table::last(dob), postcode = data.table::last(postcode), recid = data.table::last(recid), - person_id = data.table::last(person_id), + # person_id = data.table::last(person_id), sc_send_lca = data.table::last(sc_send_lca) ), by = list( sending_location, diff --git a/R/process_sc_all_care_home.R b/R/process_sc_all_care_home.R index 524be1b2f..5478d50cc 100644 --- a/R/process_sc_all_care_home.R +++ b/R/process_sc_all_care_home.R @@ -203,7 +203,8 @@ process_sc_all_care_home <- function( # match ch_episode data with deaths data matched_deaths_data <- ch_episode %>% dplyr::left_join(refined_death, - by = "chi" + by = "chi", + na_matches = "never" ) %>% # compare discharge date with NRS and CHI death date # if either of the dates are 5 or fewer days before discharge @@ -367,7 +368,6 @@ process_sc_all_care_home <- function( ch_data_final <- adm_reason_recoded %>% - create_person_id() %>% dplyr::rename( record_keydate1 = "ch_admission_date", record_keydate2 = "ch_discharge_date", @@ -385,7 +385,7 @@ process_sc_all_care_home <- function( )) %>% dplyr::select( "chi", - "person_id", + # "person_id", "gender", "dob", "postcode", diff --git a/R/process_sc_all_home_care.R b/R/process_sc_all_home_care.R index 52cab0568..352c4fff3 100644 --- a/R/process_sc_all_home_care.R +++ b/R/process_sc_all_home_care.R @@ -194,8 +194,6 @@ process_sc_all_home_care <- function( TRUE ~ "HC-Unknown" ) ) %>% - # person_id - create_person_id(type = "SC") %>% # compute lca variable from sending_location dplyr::mutate( sc_send_lca = convert_sc_sending_location_to_lca(.data$sending_location) diff --git a/R/process_sc_all_sds.R b/R/process_sc_all_sds.R index 5306c0956..c5b7d43eb 100644 --- a/R/process_sc_all_sds.R +++ b/R/process_sc_all_sds.R @@ -128,11 +128,11 @@ process_sc_all_sds <- function( "SDS", convert_sc_sending_location_to_lca(sending_location) )] - sds_full_clean_long$person_id <- paste0( - sds_full_clean_long$sending_location, - "-", - sds_full_clean_long$social_care_id - ) + # sds_full_clean_long$person_id <- paste0( + # sds_full_clean_long$sending_location, + # "-", + # sds_full_clean_long$social_care_id + # ) # Group, arrange and create flags for episodes sds_full_clean_long[, @@ -176,7 +176,7 @@ process_sc_all_sds <- function( dob = data.table::last(dob), postcode = data.table::last(postcode), recid = data.table::last(recid), - person_id = data.table::last(person_id), + # person_id = data.table::last(person_id), sc_send_lca = data.table::last(sc_send_lca) ), by = list(sending_location, social_care_id, smrtype, episode_counter)] rm(sds_full_clean_long) diff --git a/R/process_tests_episode_file.R b/R/process_tests_episode_file.R index ccf8e495c..c45992938 100644 --- a/R/process_tests_episode_file.R +++ b/R/process_tests_episode_file.R @@ -31,7 +31,9 @@ process_tests_episode_file <- function(data, year) { recid = TRUE ) %>% dplyr::arrange(.data[["recid"]]) %>% - write_tests_xlsx(sheet_name = "ep_file", year, workbook_name = "ep_file") + write_tests_xlsx(sheet_name = stringr::str_glue({ + "ep_file_{year}" + }), workbook_name = "ep_file") return(comparison) } diff --git a/R/process_tests_individual_file.R b/R/process_tests_individual_file.R index 9643a4f3f..900ce7f03 100644 --- a/R/process_tests_individual_file.R +++ b/R/process_tests_individual_file.R @@ -34,7 +34,9 @@ process_tests_individual_file <- function(data, year) { old_data = produce_individual_file_tests(old_data), new_data = produce_individual_file_tests(data) ) %>% - write_tests_xlsx(sheet_name = "indiv_file", year, workbook_name = "indiv_file") + write_tests_xlsx(sheet_name = stringr::str_glue({ + "indiv_file_{year}" + }), workbook_name = "indiv_file") return(comparison) } diff --git a/R/process_tests_sc_all_at_episodes.R b/R/process_tests_sc_all_at_episodes.R index c23a4f6ed..8b5580334 100644 --- a/R/process_tests_sc_all_at_episodes.R +++ b/R/process_tests_sc_all_at_episodes.R @@ -10,9 +10,6 @@ #' #' @export process_tests_sc_all_at_episodes <- function(data) { - data <- data %>% - slfhelper::get_chi() - comparison <- produce_test_comparison( old_data = produce_sc_all_episodes_tests( read_file(get_sc_at_episodes_path(update = previous_update())) diff --git a/R/process_tests_sc_all_ch_episodes.R b/R/process_tests_sc_all_ch_episodes.R index d42eca2c7..7e9655c06 100644 --- a/R/process_tests_sc_all_ch_episodes.R +++ b/R/process_tests_sc_all_ch_episodes.R @@ -10,9 +10,6 @@ #' #' @export process_tests_sc_all_ch_episodes <- function(data) { - data <- data %>% - slfhelper::get_chi() - comparison <- produce_test_comparison( old_data = produce_sc_all_episodes_tests( read_file(get_sc_ch_episodes_path(update = previous_update())) diff --git a/R/process_tests_sc_all_hc_episodes.R b/R/process_tests_sc_all_hc_episodes.R index d037e7908..7194790c0 100644 --- a/R/process_tests_sc_all_hc_episodes.R +++ b/R/process_tests_sc_all_hc_episodes.R @@ -10,9 +10,6 @@ #' #' @export process_tests_sc_all_hc_episodes <- function(data) { - data <- data %>% - slfhelper::get_chi() - comparison <- produce_test_comparison( old_data = produce_sc_all_episodes_tests( read_file(get_sc_hc_episodes_path(update = previous_update())) diff --git a/R/process_tests_sc_all_sds_episodes.R b/R/process_tests_sc_all_sds_episodes.R index 91c32d450..cf87a671c 100644 --- a/R/process_tests_sc_all_sds_episodes.R +++ b/R/process_tests_sc_all_sds_episodes.R @@ -10,9 +10,6 @@ #' #' @export process_tests_sc_all_sds_episodes <- function(data) { - data <- data %>% - slfhelper::get_chi() - comparison <- produce_test_comparison( old_data = produce_sc_all_episodes_tests( read_file(get_sc_sds_episodes_path(update = previous_update())) diff --git a/R/write_tests_xlsx.R b/R/write_tests_xlsx.R index ec3cc5705..6847cc977 100644 --- a/R/write_tests_xlsx.R +++ b/R/write_tests_xlsx.R @@ -24,17 +24,42 @@ write_tests_xlsx <- function(comparison_data, "cross_year" )) { # Set up the workbook ---- - tests_workbook_name <- dplyr::case_when( - is.null(year) & workbook_name == "ep_file" ~ stringr::str_glue(latest_update(), "_ep_file_tests"), - !is.null(year) & workbook_name == "ep_file" ~ stringr::str_glue(latest_update(), "_{year}_ep_file_tests"), - is.null(year) & workbook_name == "indiv_file" ~ stringr::str_glue(latest_update(), "_indiv_file_tests"), - !is.null(year) & workbook_name == "indiv_file" ~ stringr::str_glue(latest_update(), "_{year}_indiv_file_tests"), - is.null(year) & workbook_name == "lookup" ~ stringr::str_glue(latest_update(), "_lookups_tests"), - is.null(year) & workbook_name == "sandpit" ~ stringr::str_glue(latest_update(), "_sandpit_extract_tests"), - is.null(year) & workbook_name == "cross_year" ~ stringr::str_glue(latest_update(), "_cross_year_tests"), - !is.null(year) & workbook_name == "sandpit" ~ stringr::str_glue(latest_update(), "_sandpit_extract_tests"), - !is.null(year) & workbook_name == "extract" ~ stringr::str_glue(latest_update(), "_{year}_extract_tests") - ) + if (workbook_name == "ep_file") { + if (is.null(year)) { + tests_workbook_name <- + stringr::str_glue(latest_update(), "_ep_file_tests") + } + } + if (workbook_name == "indiv_file") { + if (is.null(year)) { + tests_workbook_name <- + stringr::str_glue(latest_update(), "_indiv_file_tests") + } + } + if (workbook_name == "lookup") { + if (is.null(year)) { + tests_workbook_name <- + stringr::str_glue(latest_update(), "_lookups_tests") + } + } + if (workbook_name == "sandpit") { + tests_workbook_name <- + stringr::str_glue(latest_update(), "_sandpit_extract_tests") + } + if (workbook_name == "cross_year") { + if (is.null(year)) { + tests_workbook_name <- + stringr::str_glue(latest_update(), "_cross_year_tests") + } + } + if (workbook_name == "extract") { + if (is.null(year)) { + } else { + tests_workbook_name <- + stringr::str_glue(latest_update(), "_{year}_extract_tests") + } + } + tests_workbook_path <- fs::path( get_slf_dir(), diff --git a/Run_SLF_Files_manually/run_episode_file_1718.R b/Run_SLF_Files_manually/run_episode_file_1718.R index f679ea669..b405b5b6e 100644 --- a/Run_SLF_Files_manually/run_episode_file_1718.R +++ b/Run_SLF_Files_manually/run_episode_file_1718.R @@ -18,10 +18,6 @@ processed_data_list <- list( "source_cmh_extract_1718", store = targets_store ), - cmh = targets::tar_read( - "source_cmh_extract_1718", - store = targets_store - ), dn = targets::tar_read( "source_dn_extract_1718", store = targets_store diff --git a/Run_SLF_Files_manually/run_episode_file_1819.R b/Run_SLF_Files_manually/run_episode_file_1819.R index d7a65690e..fb3227512 100644 --- a/Run_SLF_Files_manually/run_episode_file_1819.R +++ b/Run_SLF_Files_manually/run_episode_file_1819.R @@ -18,10 +18,6 @@ processed_data_list <- list( "source_cmh_extract_1819", store = targets_store ), - cmh = targets::tar_read( - "source_cmh_extract_1819", - store = targets_store - ), dn = targets::tar_read( "source_dn_extract_1819", store = targets_store diff --git a/Run_SLF_Files_manually/run_episode_file_1920.R b/Run_SLF_Files_manually/run_episode_file_1920.R index e3c2ebeb0..e2e21bdac 100644 --- a/Run_SLF_Files_manually/run_episode_file_1920.R +++ b/Run_SLF_Files_manually/run_episode_file_1920.R @@ -18,10 +18,6 @@ processed_data_list <- list( "source_cmh_extract_1920", store = targets_store ), - cmh = targets::tar_read( - "source_cmh_extract_1920", - store = targets_store - ), dn = targets::tar_read( "source_dn_extract_1920", store = targets_store diff --git a/Run_SLF_Files_manually/run_episode_file_2021.R b/Run_SLF_Files_manually/run_episode_file_2021.R index c66f4572d..cf98e80de 100644 --- a/Run_SLF_Files_manually/run_episode_file_2021.R +++ b/Run_SLF_Files_manually/run_episode_file_2021.R @@ -18,10 +18,6 @@ processed_data_list <- list( "source_cmh_extract_2021", store = targets_store ), - cmh = targets::tar_read( - "source_cmh_extract_2021", - store = targets_store - ), dn = targets::tar_read( "source_dn_extract_2021", store = targets_store diff --git a/Run_SLF_Files_manually/run_episode_file_2122.R b/Run_SLF_Files_manually/run_episode_file_2122.R index cde974be2..3bcbf2466 100644 --- a/Run_SLF_Files_manually/run_episode_file_2122.R +++ b/Run_SLF_Files_manually/run_episode_file_2122.R @@ -18,10 +18,6 @@ processed_data_list <- list( "source_cmh_extract_2122", store = targets_store ), - cmh = targets::tar_read( - "source_cmh_extract_2122", - store = targets_store - ), dn = targets::tar_read( "source_dn_extract_2122", store = targets_store diff --git a/Run_SLF_Files_manually/run_episode_file_2223.R b/Run_SLF_Files_manually/run_episode_file_2223.R index ee83082f1..af0447eed 100644 --- a/Run_SLF_Files_manually/run_episode_file_2223.R +++ b/Run_SLF_Files_manually/run_episode_file_2223.R @@ -18,10 +18,6 @@ processed_data_list <- list( "source_cmh_extract_2223", store = targets_store ), - cmh = targets::tar_read( - "source_cmh_extract_2223", - store = targets_store - ), dn = targets::tar_read( "source_dn_extract_2223", store = targets_store diff --git a/Run_SLF_Files_manually/run_episode_file_2324.R b/Run_SLF_Files_manually/run_episode_file_2324.R index 508689f6d..bdf16e0f8 100644 --- a/Run_SLF_Files_manually/run_episode_file_2324.R +++ b/Run_SLF_Files_manually/run_episode_file_2324.R @@ -18,10 +18,6 @@ processed_data_list <- list( "source_cmh_extract_2324", store = targets_store ), - cmh = targets::tar_read( - "source_cmh_extract_2324", - store = targets_store - ), dn = targets::tar_read( "source_dn_extract_2324", store = targets_store diff --git a/Run_SLF_Files_manually/run_episode_file_2425.R b/Run_SLF_Files_manually/run_episode_file_2425.R new file mode 100644 index 000000000..699c197b3 --- /dev/null +++ b/Run_SLF_Files_manually/run_episode_file_2425.R @@ -0,0 +1,75 @@ +library(targets) +library(createslf) + +year <- "2425" + +targets_store <- fs::path("/conf/sourcedev/Source_Linkage_File_Updates/", "_targets") + +processed_data_list <- list( + acute = targets::tar_read( + "source_acute_extract_2425", + store = targets_store + ), + ae = targets::tar_read( + "source_ae_extract_2425", + store = targets_store + ), + cmh = targets::tar_read( + "source_cmh_extract_2425", + store = targets_store + ), + dn = targets::tar_read( + "source_dn_extract_2425", + store = targets_store + ), + deaths = targets::tar_read( + "source_nrs_deaths_extract_2425", + store = targets_store + ), + homelessness = targets::tar_read( + "source_homelessness_extract_2425", + store = targets_store + ), + maternity = targets::tar_read( + "source_maternity_extract_2425", + store = targets_store + ), + mental_health = targets::tar_read( + "source_mental_health_extract_2425", + store = targets_store + ), + outpatients = targets::tar_read( + "source_outpatients_extract_2425", + store = targets_store + ), + gp_ooh = targets::tar_read( + "source_ooh_extract_2425", + store = targets_store + ), + prescribing = targets::tar_read( + "source_prescribing_extract_2425", + store = targets_store + ), + care_home = targets::tar_read( + "source_sc_care_home_2425", + store = targets_store + ), + home_care = targets::tar_read( + "source_sc_home_care_2425", + store = targets_store + ), + at = targets::tar_read( + "source_sc_alarms_tele_2425", + store = targets_store + ), + sds = targets::tar_read( + "source_sc_sds_2425", + store = targets_store + ) +) + +# Run episode file +create_episode_file(processed_data_list, year = year) %>% + process_tests_episode_file(year = year) + +## End of Script ## diff --git a/Run_SLF_Files_manually/run_individual_file_2425.R b/Run_SLF_Files_manually/run_individual_file_2425.R new file mode 100644 index 000000000..843eb505c --- /dev/null +++ b/Run_SLF_Files_manually/run_individual_file_2425.R @@ -0,0 +1,9 @@ +library(createslf) + +year <- "2425" + +episode_file <- arrow::read_parquet(get_slf_episode_path(year)) + +# Run individual file +create_individual_file(episode_file, year = year) %>% + process_tests_individual_file(year = year) diff --git a/Run_SLF_Files_targets/run_targets_2425.R b/Run_SLF_Files_targets/run_targets_2425.R new file mode 100644 index 000000000..fe849ede8 --- /dev/null +++ b/Run_SLF_Files_targets/run_targets_2425.R @@ -0,0 +1,9 @@ +library(targets) + +year <- "2425" + +# use targets for the process until testing episode files +tar_make_future( + # it does not recognise `contains(year)` + names = (targets::contains("2425")) +) diff --git a/_targets.R b/_targets.R index 0fea087ca..0377e487b 100644 --- a/_targets.R +++ b/_targets.R @@ -19,7 +19,7 @@ tar_option_set( memory = "persistent" # default option ) -years_to_run <- c("1718", "1819", "1920", "2021", "2122", "2223", "2324") +years_to_run <- createslf::years_to_run() list( tar_rds(write_to_disk, TRUE), diff --git a/man/latest_cost_year.Rd b/man/latest_cost_year.Rd index 0f50b3ac6..0045b4efb 100644 --- a/man/latest_cost_year.Rd +++ b/man/latest_cost_year.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/00-update_refs.R +% Please edit documentation in R/cost_uplift.R \name{latest_cost_year} \alias{latest_cost_year} \title{The latest financial year for Cost uplift setting} @@ -11,6 +11,11 @@ The financial year format } \description{ Get the latest year for cost uplift +latest_cost_year() is hard coded in cost_uplift(). +2223 is not changed automatically with time passes. +It is changed only when we get a new instruction from somewhere about cost uplift. +Do not change unless specific instructions. +Changing this means that we need to change cost_uplift(). } \seealso{ Other initialisation: