Skip to content

Commit

Permalink
Merge pull request #30 from nationalparkservice/congruence-checks
Browse files Browse the repository at this point in the history
Add ability to run metadata-only checks
  • Loading branch information
wright13 authored Jan 18, 2023
2 parents eb04f91 + a220b3a commit 9b6de67
Show file tree
Hide file tree
Showing 4 changed files with 82 additions and 41 deletions.
94 changes: 54 additions & 40 deletions R/tabular_data_congruence.R
Original file line number Diff line number Diff line change
Expand Up @@ -667,6 +667,7 @@ test_date_range <- function(directory = here::here(), metadata = load_metadata(d

#' Run all congruence checks
#'
#' @param check_metadata_only Only run checks on the metadata and skip anything involving data files.
#' @inheritParams load_data
#' @inheritParams test_metadata_version
#'
Expand All @@ -677,12 +678,17 @@ test_date_range <- function(directory = here::here(), metadata = load_metadata(d
#' dir <- DPchecker_example("BICY_veg")
#' run_congruence_checks(dir)
#'
run_congruence_checks <- function(directory = here::here(), metadata = load_metadata(directory)) {
run_congruence_checks <- function(directory = here::here(), metadata = load_metadata(directory), check_metadata_only = FALSE) {

err_count <- 0
warn_count <- 0
total_count <- 10 # Don't forget to update this number when adding more checks!

cli::cli_h1("Running all congruence checks")
if (check_metadata_only) {
cli::cli_h1("Running metadata-only checks (skipping checks against data files)")
} else {
cli::cli_h1("Running all congruence checks")
}
cli::cli_h2("Checking metadata compliance")
tryCatch(test_validate_schema(metadata),
error = function(e) {
Expand Down Expand Up @@ -739,45 +745,48 @@ run_congruence_checks <- function(directory = here::here(), metadata = load_meta
cli::cli_bullets(c(e$message, e$body))
})

cli::cli_h2("Checking that metadata is consistent with data file(s)")
tryCatch(test_file_name_match(directory, metadata),
error = function(e) {
err_count <<- err_count + 1
cli::cli_bullets(c(e$message, e$body))
cli::cli_abort(c("x" = "You must correct the above error before the rest of the congruence checks can run."))
if (!check_metadata_only) {
cli::cli_h2("Checking that metadata is consistent with data file(s)")
tryCatch(test_file_name_match(directory, metadata),
error = function(e) {
err_count <<- err_count + 1
cli::cli_bullets(c(e$message, e$body))
cli::cli_abort(c("x" = "You must correct the above error before the rest of the congruence checks can run."))
},
warning = function(w) {
warn_count <<- warn_count + 1
cli::cli_bullets(c(e$message, e$body))
})
tryCatch(test_fields_match(directory, metadata),
error = function(e) {
err_count <<- err_count + 1
cli::cli_bullets(c(e$message, e$body))
cli::cli_abort(c("x" = "You must correct the above error before the rest of the congruence checks can run."))
warning = function(w) {
warn_count <<- warn_count + 1
cli::cli_bullets(c(e$message, e$body))
})
tryCatch(test_fields_match(directory, metadata),
error = function(e) {
err_count <<- err_count + 1
cli::cli_bullets(c(e$message, e$body))
cli::cli_abort(c("x" = "You must correct the above error before the rest of the congruence checks can run."))
},
warning = function(w) {
warn_count <<- warn_count + 1
cli::cli_bullets(c(e$message, e$body))
})
tryCatch(test_numeric_fields(directory, metadata),
error = function(e) {
err_count <<- err_count + 1
cli::cli_bullets(c(e$message, e$body))
},
warning = function(w) {
warn_count <<- warn_count + 1
cli::cli_bullets(c(w$message, w$body))
})
tryCatch(test_date_range(directory, metadata),
error = function(e) {
err_count <<- err_count + 1
cli::cli_bullets(c(e$message, e$body))
},
warning = function(w) {
warn_count <<- warn_count + 1
cli::cli_bullets(c(w$message, w$body))
})
warning = function(w) {
warn_count <<- warn_count + 1
cli::cli_bullets(c(e$message, e$body))
})
tryCatch(test_numeric_fields(directory, metadata),
error = function(e) {
err_count <<- err_count + 1
cli::cli_bullets(c(e$message, e$body))
},
warning = function(w) {
warn_count <<- warn_count + 1
cli::cli_bullets(c(w$message, w$body))
})
tryCatch(test_date_range(directory, metadata),
error = function(e) {
err_count <<- err_count + 1
cli::cli_bullets(c(e$message, e$body))
},
warning = function(w) {
warn_count <<- warn_count + 1
cli::cli_bullets(c(w$message, w$body))
})
}

cli::cli_h2("Summary")
if (err_count > 0) {
cli::cli_alert_danger("{err_count} errors to address")
Expand All @@ -786,7 +795,12 @@ run_congruence_checks <- function(directory = here::here(), metadata = load_meta
cli::cli_alert_warning("{warn_count} warnings to look into")
}
if (warn_count + err_count == 0) {
cli::cli_alert_success("Success! All congruence checks passed.")
check_type <- if (check_metadata_only) {
"metadata"
} else {
"congruence"
}
cli::cli_alert_success("Success! All {check_type} checks passed.")
}

return(invisible(c("errors" = err_count, "warnings" = warn_count)))
Expand Down
5 changes: 4 additions & 1 deletion man/run_congruence_checks.Rd

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

23 changes: 23 additions & 0 deletions tests/testthat/_snaps/tabular_data_congruence.md
Original file line number Diff line number Diff line change
Expand Up @@ -30,3 +30,26 @@
v Success! All congruence checks passed.

---

Code
run_congruence_checks(here::here(good_dir, "BICY_good"), check_metadata_only = TRUE)
Message <cliMessage>
-- Running metadata-only checks (skipping checks against data files) -----------
-- Checking metadata compliance --
Message <rlang_message>
v Your metadata is schema valid.
v Each data file name is used exactly once in the metadata file.
v Your EML version is supported.
v Metadata indicates that each data file contains a field delimiter that is a single character
v Metadata indicates that each data file contains exactly one header row.
v Metadata indicates data files do not have footers.
Message <cliMessage>
-- Summary --
v Success! All metadata checks passed.

1 change: 1 addition & 0 deletions tests/testthat/test-tabular_data_congruence.R
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ cli::test_that_cli("run_congruence_checks works", configs = "plain", {
expect_error(run_congruence_checks(here::here(bad_dir, "data_metadata_mismatch", "BICY_files")),
"You must correct the above error")
expect_snapshot(run_congruence_checks(here::here(good_dir, "BICY_good")))
expect_snapshot(run_congruence_checks(here::here(good_dir, "BICY_good"), check_metadata_only = TRUE))
})

# ---- test_metadata_version ----
Expand Down

0 comments on commit 9b6de67

Please sign in to comment.