Skip to content

Commit

Permalink
Add cross year tests using SLFhelper WIP
Browse files Browse the repository at this point in the history
WIP - still need to add write to disk and possibly develop visuals
  • Loading branch information
Jennit07 committed Apr 15, 2024
1 parent 641d175 commit c209066
Show file tree
Hide file tree
Showing 4 changed files with 78 additions and 1 deletion.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -123,6 +123,7 @@ export(process_tests_ae)
export(process_tests_alarms_telecare)
export(process_tests_care_home)
export(process_tests_cmh)
export(process_tests_cross_year)
export(process_tests_delayed_discharges)
export(process_tests_district_nursing)
export(process_tests_episode_file)
Expand Down
57 changes: 57 additions & 0 deletions R/process_tests_cross_year.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,57 @@
#' Process cross year tests
#'
#' @description Process high level tests (e.g the number of records in each recid)
#' across years.
#'
#' @param year Year of the file to be read, you can specify multiple years
#' which will then be returned as one file. See SLFhelper for more info.
#'
#' @return a tibble with a test summary across years
#' @export
#'
process_tests_cross_year <- function(year) {
ep_file <- read_dev_slf_file(year,
type = "episode",
col_select = c("year", "recid", "anon_chi", "record_keydate1", "record_keydate2")
)

total_test <- ep_file %>%
dplyr::group_by(.data$year, .data$recid) %>%
dplyr::mutate(
n_records = 1L
) %>%
dplyr::summarise(
n = sum(n_records)
) %>%
dplyr::mutate(
fy_qtr = "total"
)

qtr_test <- ep_file %>%
dplyr::mutate(
fy_qtr = dplyr::if_else(recid != "PIS", lubridate::quarter(record_keydate1, fiscal_start = 4), NA)
) %>%
dplyr::group_by(.data$year, .data$recid, .data$fy_qtr) %>%
dplyr::mutate(
n_records = 1L
) %>%
dplyr::summarise(
n = sum(n_records)
) %>%
dplyr::mutate(
fy_qtr = as.character(fy_qtr)
)

join_tests <- dplyr::bind_rows(total_test, qtr_test) %>%
dplyr::arrange(year, recid, fy_qtr)

pivot_tests <- join_tests %>%
tidyr::pivot_wider(
names_from = c("year", "fy_qtr"),
names_glue = "{year}_qtr_{fy_qtr}",
values_from = "n"
) %>%
dplyr::select(-tidyselect::ends_with("NA"))

return(pivot_tests)
}
19 changes: 19 additions & 0 deletions man/process_tests_cross_year.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion man/read_dev_slf_file.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit c209066

Please sign in to comment.