Skip to content

Commit

Permalink
Improved handling of offline behaviors
Browse files Browse the repository at this point in the history
  • Loading branch information
equitable-equations committed Nov 5, 2023
1 parent 306d11f commit d299f7e
Show file tree
Hide file tree
Showing 6 changed files with 46 additions and 9 deletions.
14 changes: 10 additions & 4 deletions R/is_assessment.R
Original file line number Diff line number Diff line change
Expand Up @@ -9,14 +9,20 @@

is_assessment <- function(possible_assessment) {

return <- TRUE
return <- FALSE

tryCatch({

if (!is.data.frame(possible_assessment)) {
if (is.data.frame(possible_assessment)) {
return <- TRUE
}},
error = function(e) {
return <- FALSE
}
},
warning = function(w){
return <- FALSE
})

tryCatch({
if (ncol(possible_assessment) == 1) {

new <- rbind(names(possible_assessment), possible_assessment)
Expand Down
9 changes: 8 additions & 1 deletion R/species_acronym.R
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,12 @@ species_acronym <-function(species,

if (!is.null(database_id)) {
db <- download_database(database_id)

if (nrow(db) == 0){
message("Specified database is empty.")
return(invisible(NULL))
}

database_inventory <- database_inventory(db)
}

Expand All @@ -65,7 +71,8 @@ species_acronym <-function(species,
}

if (!(species %in% database_inventory$scientific_name)) {
stop("Species not found in specified database.", call. = FALSE)
message("Species not found in specified database.")
return(invisible(NULL))
}

species_row <- database_inventory |>
Expand Down
26 changes: 23 additions & 3 deletions R/transect_phys.R
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ transect_phys <- function(data_set) {

if (!is_transect(data_set)) {
message(
"data_set must be a dataframe obtained from the universalFQA.org website. Type ?download_assessment for help."
"data_set must be a dataframe obtained from the universalFQA.org website. Type ?download_transect for help."
)
return(invisible(empty_df))
}
Expand All @@ -72,9 +72,29 @@ transect_phys <- function(data_set) {
2 + which(data_set$V1 == "Physiognomic Relative Importance Values:")
end_row <-
-2 + which(data_set$V1 == "Species Relative Importance Values:")
if (end_row < start_row) {
stop("No physiognometric data found")

if (length(end_row) == 0) {
message("No physiognometric data found")
return(invisible(TRUE))
}

tryCatch({
if (end_row < start_row) {
message("No physiognometric data found")
return(invisible(empty_df))
}
},

error = function(e) {
message("No physiognometric data foundd")
return(invisible(empty_df))
},

warning = function(w){
message("No physiognometric data found")
return(invisible(empty_df))
})

phys <- data_set[start_row:end_row, 1:6]

names(phys) <- c(
Expand Down
2 changes: 2 additions & 0 deletions tests/testthat/test-is_assessment.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,8 @@ test_that("is_assessment works", {
expect_false(is_assessment("hi"))
expect_false(is_assessment(data.frame()))

skip_on_cran()

test_raw <- download_assessment(25002)
expect_true(is_assessment(test_raw))
})
2 changes: 2 additions & 0 deletions tests/testthat/test-is_transect.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@ test_that("is_transect works", {
expect_false(is_transect("hi"))
expect_false(is_transect(data.frame()))

skip_on_cran()

test_raw <- download_transect(4492)
expect_true(is_transect(test_raw))

Expand Down
2 changes: 1 addition & 1 deletion tests/testthat/test-species_acronym.R
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ test_that("species_acronym works", {
"database_inventory must be a species inventory in the format provided by database_inventory().")
expect_error(species_acronym(species, database_id = "hi"),
"database_id must be an integer.")
expect_error(species_acronym("fake_species", database_inventory = db_inv),
expect_message(species_acronym("fake_species", database_inventory = db_inv),
"Species not found in specified database.")

expect_equal(species_acronym(species, 149), "ANECAN")
Expand Down

0 comments on commit d299f7e

Please sign in to comment.