Skip to content

Commit

Permalink
Remove sc_client from individual file and add to ep file (#853)
Browse files Browse the repository at this point in the history
* removed `join_client_demog` from `create_individual_file` and added it to `process_lookup_sc_client` instead

* Style code

* removed client lookup from individual year social care scripts.
Also, fixed get boxi extract paths. R
TO DO - add in code to episode file

* Update documentation

* Remove sc_client from individual file and add to ep file

* Update documentation

* Style code

* add sc_send_lca and remove sending_location

* update targets

* Update documentation

* Style code

* Remove redundant function

* Simplify code where specified in a parameter

* remove redundant code

* simplify `join_sc_client` function

* declare client variables

* use `join_sc_client`

* Add parameter for `sc_client` lookup

* Use `join_sc_client` in indiv file

* simplify code/use demographic file in client

* add sc client parameter in ep file

* Use processed demographic lookup target

* Update documentation

* Style code

* Remove commented code

* Update targets to remove `client_lookup`

---------

Co-authored-by: marjom02 <[email protected]>
Co-authored-by: SwiftySalmon <[email protected]>
Co-authored-by: lizihao-anu <[email protected]>
Co-authored-by: Jennit07 <[email protected]>
Co-authored-by: Jennifer Thom <[email protected]>
Co-authored-by: Jennit07 <[email protected]>
  • Loading branch information
7 people authored Nov 21, 2023
1 parent a2892eb commit a79b686
Show file tree
Hide file tree
Showing 17 changed files with 214 additions and 246 deletions.
49 changes: 41 additions & 8 deletions R/create_episode_file.R
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ create_episode_file <- function(
col_select = c("gpprac", "cluster", "hbpraccode")
),
slf_deaths_lookup = read_file(get_slf_deaths_lookup_path(year)),
sc_client = read_file(get_sc_client_lookup_path(year)),
write_to_disk = TRUE,
anon_chi_out = TRUE) {
episode_file <- dplyr::bind_rows(processed_data_list) %>%
Expand Down Expand Up @@ -132,19 +133,12 @@ create_episode_file <- function(
year,
slf_deaths_lookup
) %>%
join_sc_client(year, sc_client = sc_client, file_type = "episode") %>%
load_ep_file_vars(year)

if (!check_year_valid(year, type = c("CH", "HC", "AT", "SDS"))) {
episode_file <- episode_file %>%
dplyr::mutate(
sc_send_lca = NA,
sc_living_alone = NA,
sc_support_from_unpaid_carer = NA,
sc_social_worker = NA,
sc_type_of_housing = NA,
sc_meals = NA,
sc_day_care = NA,
sc_latest_submission = NA,
ch_chi_cis = NA,
sc_id_cis = NA,
ch_name = NA,
Expand All @@ -163,6 +157,12 @@ create_episode_file <- function(
hc_provider = NA,
hc_reablement = NA,
sds_option_4 = NA,
sc_living_alone = NA,
sc_support_from_unpaid_carer = NA,
sc_social_worker = NA,
sc_type_of_housing = NA,
sc_meals = NA,
sc_day_care = NA
)
}

Expand Down Expand Up @@ -428,3 +428,36 @@ join_cohort_lookups <- function(

return(join_cohort_lookups)
}


#' Join sc client variables onto episode file
#'
#' @description Match on sc client variables.
#'
#' @param individual_file the processed individual file
#' @param year financial year.
#' @param sc_client SC client lookup
#' @param file_type episode or individual file
join_sc_client <- function(data,
year,
sc_client = read_file(get_sc_client_lookup_path(year)),
file_type = c("episode", "individual")) {
if (file_type == "episode") {
# Match on client variables by chi
data_file <- data %>%
dplyr::left_join(sc_client,
by = "chi",
relationship = "many-to-one"
)
} else {
data_file <- data %>%
dplyr::left_join(
sc_client,
by = "chi",
relationship = "one-to-one"
) %>%
dplyr::select(!c("sending_location", "social_care_id", "sc_latest_submission"))
}

return(data_file)
}
57 changes: 3 additions & 54 deletions R/create_individual_file.R
Original file line number Diff line number Diff line change
Expand Up @@ -82,8 +82,7 @@ create_individual_file <- function(
individual_file <- individual_file %>%
aggregate_ch_episodes() %>%
clean_up_ch(year) %>%
aggregate_by_chi(exclude_sc_var = FALSE) %>%
join_sc_client(year)
aggregate_by_chi(exclude_sc_var = FALSE)
}

individual_file <- individual_file %>%
Expand All @@ -96,7 +95,8 @@ create_individual_file <- function(
join_sparra_hhg(year) %>%
join_slf_lookup_vars() %>%
dplyr::mutate(year = year) %>%
add_hri_variables(chi_variable = "chi")
add_hri_variables(chi_variable = "chi") %>%
join_sc_client(year, file_type = "individual")

if (!check_year_valid(year, type = c("CH", "HC", "AT", "SDS"))) {
individual_file <- individual_file %>%
Expand Down Expand Up @@ -794,54 +794,3 @@ join_slf_lookup_vars <- function(individual_file,

return(individual_file)
}
# TODO Remove the client data from the individual Social Care extracts
# and instead, use this function in the episode file to match on the client
# data to all episodes.
#' Join sc client variables onto individual file
#'
#' @description Match on sc client variables.
#'
#' @param individual_file the processed individual file
#' @param year financial year.
#' @param sc_client SC client lookup
#' @param sc_demographics SC Demographic lookup
join_sc_client <- function(
individual_file,
year,
sc_client = read_file(get_sc_client_lookup_path(year)),
sc_demographics = read_file(get_sc_demog_lookup_path(),
col_select = c("sending_location", "social_care_id", "chi")
)) {
# TODO Update the client lookup processing script to match
# on demographics there so the client lookup already has CHI.

# Match to demographics lookup to get CHI
join_client_demog <- sc_client %>%
dplyr::left_join(
sc_demographics %>%
dplyr::select("sending_location", "social_care_id", "chi"),
by = c("sending_location", "social_care_id")
) %>%
dplyr::mutate(count_not_known = rowSums(dplyr::select(., all_of(
c(
"sc_living_alone",
"sc_support_from_unpaid_carer",
"sc_social_worker",
"sc_meals",
"sc_day_care"
)
)) == "Not Known")) %>%
dplyr::arrange(chi, count_not_known) %>%
dplyr::distinct(chi, .keep_all = TRUE)

# Match on client variables by chi
individual_file <- individual_file %>%
dplyr::left_join(
join_client_demog,
by = "chi",
relationship = "one-to-one"
) %>%
dplyr::select(!c("sending_location", "social_care_id", "sc_latest_submission"))

return(individual_file)
}
26 changes: 13 additions & 13 deletions R/get_boxi_extract_path.R
Original file line number Diff line number Diff line change
Expand Up @@ -41,19 +41,19 @@ get_boxi_extract_path <- function(

file_name <- dplyr::case_match(
type,
"ae" ~ "a&e-episode-level-extract",
"ae_cup" ~ "a&e-ucd-cup-extract",
"acute" ~ "acute-episode-level-extract",
"cmh" ~ "community-mh-contact-level-extract",
"dn" ~ "district-nursing-contact-level-extract",
"gp_ooh-c" ~ "gp-ooh-consultations-extract",
"gp_ooh-d" ~ "gp-ooh-diagnosis-extract",
"gp_ooh-o" ~ "gp-ooh-outcomes-extract",
"homelessness" ~ "homelessness-extract",
"maternity" ~ "maternity-episode-level-extract",
"mh" ~ "mental-health-episode-level-extract",
"deaths" ~ "nrs-death-registrations-extract",
"outpatients" ~ "outpatients-episode-level-extract"
"ae" ~ "A&E-episode-level-extract",
"ae_cup" ~ "A&E-UCD-CUP-extract",
"acute" ~ "Acute-episode-level-extract",
"cmh" ~ "Community-MH-contact-level-extract",
"dn" ~ "District-Nursing-contact-level-extract",
"gp_ooh-c" ~ "GP-OoH-consultations-extract",
"gp_ooh-d" ~ "GP-OoH-diagnosis-extract",
"gp_ooh-o" ~ "GP-OoH-outcomes-extract",
"homelessness" ~ "Homelessness-extract",
"maternity" ~ "Maternity-episode-level-extract",
"mh" ~ "Mental-Health-episode-level-extract",
"deaths" ~ "NRS-death-registrations-extract",
"outpatients" ~ "Outpatients-episode-level-extract"
)

boxi_extract_path_csv_gz <- fs::path(
Expand Down
13 changes: 1 addition & 12 deletions R/process_extract_alarms_telecare.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,6 @@
process_extract_alarms_telecare <- function(
data,
year,
client_lookup,
write_to_disk = TRUE) {
# Only run for a single year
stopifnot(length(year) == 1L)
Expand All @@ -33,10 +32,6 @@ process_extract_alarms_telecare <- function(
.data[["record_keydate1"]],
.data[["record_keydate2"]]
)) %>%
dplyr::left_join(
client_lookup,
by = c("sending_location", "social_care_id")
) %>%
dplyr::mutate(
year = year
) %>%
Expand All @@ -52,13 +47,7 @@ process_extract_alarms_telecare <- function(
"record_keydate1",
"record_keydate2",
"person_id",
"sc_latest_submission",
"sc_living_alone",
"sc_support_from_unpaid_carer",
"sc_social_worker",
"sc_type_of_housing",
"sc_meals",
"sc_day_care"
"sc_latest_submission"
)

if (write_to_disk) {
Expand Down
9 changes: 1 addition & 8 deletions R/process_extract_care_home.R
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,6 @@
process_extract_care_home <- function(
data,
year,
client_lookup,
ch_costs,
write_to_disk = TRUE) {
# Only run for a single year
Expand All @@ -44,11 +43,6 @@ process_extract_care_home <- function(
# remove any episodes where the latest submission was before the current year
dplyr::filter(
substr(.data$sc_latest_submission, 1L, 4L) >= convert_fyyear_to_year(year)
) %>%
# Match to client data
dplyr::left_join(
client_lookup,
by = c("sending_location", "social_care_id")
)


Expand Down Expand Up @@ -136,8 +130,7 @@ process_extract_care_home <- function(
"stay",
"cost_total_net",
dplyr::ends_with("_beddays"),
dplyr::ends_with("_cost"),
dplyr::starts_with("sc_")
dplyr::ends_with("_cost")
)

if (write_to_disk) {
Expand Down
6 changes: 1 addition & 5 deletions R/process_extract_home_care.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,6 @@
process_extract_home_care <- function(
data,
year,
client_lookup,
write_to_disk = TRUE) {
# Only run for a single year
stopifnot(length(year) == 1L)
Expand All @@ -37,8 +36,6 @@ process_extract_home_care <- function(
dplyr::filter(
substr(.data$sc_latest_submission, 1L, 4L) >= convert_fyyear_to_year(year)
) %>%
# Match to client data
dplyr::left_join(client_lookup, by = c("sending_location", "social_care_id")) %>%
dplyr::mutate(year = year)

# Home Care Hours ---------------------------------------
Expand Down Expand Up @@ -97,8 +94,7 @@ process_extract_home_care <- function(
"cost_total_net",
"hc_provider",
"hc_reablement",
"person_id",
tidyselect::starts_with("sc_")
"person_id"
)

if (write_to_disk) {
Expand Down
10 changes: 1 addition & 9 deletions R/process_extract_sds.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,6 @@
process_extract_sds <- function(
data,
year,
client_lookup,
write_to_disk = TRUE) {
# Only run for a single year
stopifnot(length(year) == 1L)
Expand All @@ -33,7 +32,6 @@ process_extract_sds <- function(
.data[["record_keydate1"]],
.data[["record_keydate2"]]
)) %>%
dplyr::left_join(client_lookup, by = c("sending_location", "social_care_id")) %>%
dplyr::mutate(
year = year
) %>%
Expand All @@ -47,13 +45,7 @@ process_extract_sds <- function(
"postcode",
"record_keydate1",
"record_keydate2",
"sc_send_lca",
"sc_living_alone",
"sc_support_from_unpaid_carer",
"sc_social_worker",
"sc_type_of_housing",
"sc_meals",
"sc_day_care"
"sc_send_lca"
)

if (write_to_disk) {
Expand Down
1 change: 0 additions & 1 deletion R/process_lookup_homelessness.R
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,6 @@ create_homelessness_lookup <- function(
#' @export
add_homelessness_flag <- function(data, year,
lookup = create_homelessness_lookup(year)) {
## need to decide which recids this relates to
data <- data %>%
dplyr::left_join(
lookup %>%
Expand Down
Loading

0 comments on commit a79b686

Please sign in to comment.