Skip to content

Commit

Permalink
add tests
Browse files Browse the repository at this point in the history
  • Loading branch information
jacobvjk committed Sep 2, 2024
1 parent 077c791 commit a9090df
Show file tree
Hide file tree
Showing 2 changed files with 101 additions and 5 deletions.
6 changes: 3 additions & 3 deletions R/run_calculate_match_success_rate.R
Original file line number Diff line number Diff line change
Expand Up @@ -422,10 +422,10 @@ combine_raw_and_matched_loan_books <- function(raw_lbk_with_sectors,
matched_prioritized <- matched_prioritized %>%
dplyr::select(-"sector") %>%
dplyr::mutate(
id_loan_matched = gsub(paste0("_", .data[["group_id"]], collapse = "|"), "", .data[["id_loan"]])
id_loan = gsub(paste0("_", .data[["group_id"]], collapse = "|"), "", .data[["id_loan"]])
) %>%
dplyr::mutate(
id_loan_matched = gsub(paste0("_", .env$all_sectors, collapse="|"), "", .data[["id_loan_matched"]])
id_loan = gsub(paste0("_", .env$all_sectors, collapse="|"), "", .data[["id_loan"]])
)

# use left_join so that unmatched loans are properly accounted for
Expand All @@ -445,7 +445,7 @@ combine_raw_and_matched_loan_books <- function(raw_lbk_with_sectors,
"sector_classification_direct_loantaker",
"lei_direct_loantaker",
"isin_direct_loantaker",
"id_loan" = "id_loan_matched",
"id_loan",
"group_id",
"sector" = "sector_abcd",
"borderline"
Expand Down
100 changes: 98 additions & 2 deletions tests/testthat/test-run_calculate_match_success_rate.R
Original file line number Diff line number Diff line change
@@ -1,3 +1,99 @@
test_that("multiplication works", {
expect_equal(2 * 2, 4)
# combine_raw_and_matched_loan_books
test_that("combine_raw_and_matched_loan_books identifies correct matched and unmatched loans", {
test_raw <- r2dii.data::loanbook_demo %>%
dplyr::mutate(group_id = "test")

possible_matches_direct <- test_raw %>%
dplyr::distinct(.data[["id_loan"]], .data[["name_direct_loantaker"]]) %>%
dplyr::semi_join(r2dii.data::abcd_demo, by = c("name_direct_loantaker" = "name_company"))

non_matches_direct <- test_raw %>%
dplyr::distinct(.data[["id_loan"]], .data[["name_direct_loantaker"]]) %>%
dplyr::anti_join(r2dii.data::abcd_demo, by = c("name_direct_loantaker" = "name_company"))

test_raw <- test_raw %>%
dplyr::filter(
.data[["id_loan"]] %in% possible_matches_direct[["id_loan"]][1] |
.data[["id_loan"]] %in% non_matches_direct[["id_loan"]][1]
)

nace_sectors <- r2dii.data::sector_classifications %>%
dplyr::filter(.data$code_system == "NACE")

test_raw_lbk_with_sectors <- add_sectors_to_raw_lbk(
raw_lbk = test_raw,
sector_classification_system = nace_sectors
)

test_matched_prio <- test_raw %>%
r2dii.match::match_name(abcd = r2dii.data::abcd_demo, by_sector = TRUE, min_score = 1)

test_lbk_match_success <- combine_raw_and_matched_loan_books(
raw_lbk_with_sectors = test_raw_lbk_with_sectors,
matched_prioritized = test_matched_prio
)

matched <- test_lbk_match_success %>%
dplyr::filter(.data[["matched"]] == "Matched") %>%
dplyr::distinct(.data[["id_loan"]], .data[["name_direct_loantaker"]])

testthat::expect_equal(matched, possible_matches_direct[1, ])

not_matched <- test_lbk_match_success %>%
dplyr::filter(.data[["matched"]] == "Not matched") %>%
dplyr::distinct(.data[["id_loan"]], .data[["name_direct_loantaker"]])

testthat::expect_equal(not_matched, non_matches_direct[1, ])
})

test_that("combine_raw_and_matched_loan_books removes group_id from id_loan where needed", {
test_raw <- r2dii.data::loanbook_demo %>%
dplyr::mutate(group_id = "test")

nace_sectors <- r2dii.data::sector_classifications %>%
dplyr::filter(.data$code_system == "NACE")

test_raw_lbk_with_sectors <- add_sectors_to_raw_lbk(
raw_lbk = test_raw,
sector_classification_system = nace_sectors
)

test_matched_prio <- test_raw %>%
r2dii.match::match_name(abcd = r2dii.data::abcd_demo, by_sector = TRUE, min_score = 1) %>%
dplyr::mutate(id_loan = paste(id_loan, group_id, sep = "_"))

test_lbk_match_success <- combine_raw_and_matched_loan_books(
raw_lbk_with_sectors = test_raw_lbk_with_sectors,
matched_prioritized = test_matched_prio
)

testthat::expect_equal(test_raw$id_loan, unique(test_lbk_match_success$id_loan))

testthat::expect_contains(test_raw$id_loan, gsub("_test", "", test_matched_prio$id_loan))
})

test_that("combine_raw_and_matched_loan_books removes sector_abcd from id_loan where needed", {
test_raw <- r2dii.data::loanbook_demo %>%
dplyr::mutate(group_id = "test")

nace_sectors <- r2dii.data::sector_classifications %>%
dplyr::filter(.data$code_system == "NACE")

test_raw_lbk_with_sectors <- add_sectors_to_raw_lbk(
raw_lbk = test_raw,
sector_classification_system = nace_sectors
)

test_matched_prio <- test_raw %>%
r2dii.match::match_name(abcd = r2dii.data::abcd_demo, by_sector = TRUE, min_score = 1) %>%
dplyr::mutate(id_loan = paste(id_loan, sector_abcd, sep = "_"))

test_lbk_match_success <- combine_raw_and_matched_loan_books(
raw_lbk_with_sectors = test_raw_lbk_with_sectors,
matched_prioritized = test_matched_prio
)

testthat::expect_equal(test_raw$id_loan, unique(test_lbk_match_success$id_loan))

testthat::expect_contains(unique(r2dii.data::sector_classifications$sector), gsub(paste0(test_raw$id_loan, "_", collapse = "|"), "", test_matched_prio$id_loan))
})

0 comments on commit a9090df

Please sign in to comment.