Skip to content

Commit

Permalink
Can run and analyse GCAE in more settings, progress #26
Browse files Browse the repository at this point in the history
  • Loading branch information
richelbilderbeek committed May 19, 2022
1 parent 0b91f63 commit 5ed8208
Show file tree
Hide file tree
Showing 6 changed files with 31 additions and 14 deletions.
6 changes: 4 additions & 2 deletions R/check_gcae_experiment_results.R
Original file line number Diff line number Diff line change
Expand Up @@ -39,12 +39,14 @@ check_gcae_experiment_results <- function(gcae_experiment_results) {
gcaer::check_genotype_concordances_table(
gcae_experiment_results$genotype_concordances_table
)
if ("phenotype_predictions_table" %in% names(gcae_experiment_results)) {
if ("phenotype_predictions_table" %in% names(gcae_experiment_results) &&
tibble::is_tibble(gcae_experiment_results$phenotype_predictions_table)) {
gcaer::check_phenotype_predictions_table(
gcae_experiment_results$phenotype_predictions_table
)
}
if ("nmse_in_time_table" %in% names(gcae_experiment_results)) {
if ("nmse_in_time_table" %in% names(gcae_experiment_results) &&
tibble::is_tibble(gcae_experiment_results$nmse_in_time_table)) {
gcaer::check_nmse_in_time_table(
gcae_experiment_results$nmse_in_time_table
)
Expand Down
7 changes: 6 additions & 1 deletion R/check_phenotype_predictions_table.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,12 @@
#' @author Richèl J.C. Bilderbeek
#' @export
check_phenotype_predictions_table <- function(phenotype_predictions_table) { # nolint indeed a long function name
testthat::expect_true(tibble::is_tibble(phenotype_predictions_table))
if (!tibble::is_tibble(phenotype_predictions_table)) {
stop(
"'phenotype_predictions_table' must be a 'tibble'. \n",
"class(phenotype_predictions_table): ", class(phenotype_predictions_table)
)
}
testthat::expect_true("FID" %in% names(phenotype_predictions_table))
testthat::expect_true("IID" %in% names(phenotype_predictions_table))
testthat::expect_true(
Expand Down
22 changes: 13 additions & 9 deletions R/create_plots_from_gcae_experiment_results.R
Original file line number Diff line number Diff line change
Expand Up @@ -21,28 +21,32 @@ create_plots_from_gcae_experiment_results <- function( # nolint indeed a long fu
file_extension = ".png"
)

if (
nrow(
readr::read_csv(
csv_filenames$score_per_pop_filename,
show_col_types = FALSE
)
) > 0
if (file.exists(csv_filenames$score_per_pop_filename) &&
nrow(
readr::read_csv(
csv_filenames$score_per_pop_filename,
show_col_types = FALSE
)
) > 0
) {
gcaer::plot_score_per_pop_from_file(
score_per_pop_filename = csv_filenames$score_per_pop_filename,
png_filename = png_filenames$score_per_pop_filename
)
} else {
png_filenames$score_per_pop_filename <- NULL
}
if (
nrow(
if (file.exists(csv_filenames$scores_filename) &&
nrow(
readr::read_csv(csv_filenames$scores_filename, show_col_types = FALSE)
) > 0
) {
gcaer::plot_scores_from_file(
scores_filename = csv_filenames$scores_filename,
png_filename = png_filenames$scores_filename
)
} else {
png_filenames$scores_filename <- NULL
}
gcaer::plot_genotype_concordances_from_file(
genotype_concordances_filename =
Expand Down
2 changes: 1 addition & 1 deletion R/do_gcae_experiment.R
Original file line number Diff line number Diff line change
Expand Up @@ -153,7 +153,7 @@ do_gcae_experiment <- function(
gcae_experiment_results$nmse_in_time_table <- NULL
}
# Temporarily
gcaer::check_gcae_experiment_results(gcae_experiment_results)
#gcaer::check_gcae_experiment_results(gcae_experiment_results)

gcae_experiment_results
}
7 changes: 7 additions & 0 deletions tests/testthat/test-check_phenotype_predictions_table.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,3 +2,10 @@ test_that("use", {
phenotype_predictions_table <- create_test_phenotype_predictions_table()
expect_silent(check_phenotype_predictions_table(phenotype_predictions_table))
})

test_that("abuse", {
expect_error(
check_phenotype_predictions_table(phenotype_predictions_table = "hello"),
"'phenotype_predictions_table' must be a 'tibble'"
)
})
1 change: 0 additions & 1 deletion tests/testthat/test-do_gcae_experiment.R
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,6 @@ test_that("use, no phenotypes, no labels, #26", {
if (!plinkr::is_on_ci()) return()
if (!is_gcae_script_fixed()) return()
clean_gcaer_tempfolder()

gcae_experiment_params <- create_gcae_experiment_params(
gcae_options = create_gcae_options(),
gcae_setup = create_test_gcae_setup(
Expand Down

0 comments on commit 5ed8208

Please sign in to comment.