Skip to content
Snippets Groups Projects
Commit 1f281102 authored by Jannes Breier's avatar Jannes Breier
Browse files

add review recomendations, add test folder

parent a05ac42e
No related branches found
No related tags found
2 merge requests!6Merge reviewed package into main,!5Merge review_paper version to master
......@@ -30,3 +30,6 @@ Imports:
grDevices,
maps,
methods
Suggests:
testthat (>= 3.0.0)
\ No newline at end of file
......@@ -64,7 +64,7 @@ average_nyear_window <- function(x, # nolint
interpolate_spline <- function(x, y, nyear_window) {
rep(NA, dim(y)["year"]) %>%
`[<-`(seq(round(nyear_window / 2), dim(y)["year"], nyear_window),
value = x) %>%
value = x) %>%
zoo::na.spline()
}
......
......@@ -62,7 +62,7 @@ classify_biomes <- function(path_reference = NULL,
stop("files_reference or path_reference must be provided")
} else if (!is.null(path_reference) && is.null(files_reference)) {
# Get main file type (meta, clm)
file_ext <- get_file_ext(path_reference)
file_ext <- get_major_file_ext(path_reference)
# List required output files for each boundary
output_files <- list_outputs("biome",
......
# function to get file extension
get_file_ext <- function(path) {
get_major_file_ext <- function(path) {
# Get all files in path
all_files <- list.files(
path,
......@@ -10,12 +10,17 @@ get_file_ext <- function(path) {
all_file_types <- all_files %>%
strsplit("/") %>%
sapply(utils::tail, 1) %>%
strsplit("^([^\\.]+)") %>%
strsplit("\\.") %>%
sapply(function(x) {
y <- x[2]
return(y)
y <- x[-1]
if ("json" %in% y) {
return(paste(tail(strsplit(y, "\\."), 2), collapse = "."))
} else {
return(tail(strsplit(y, "\\."), 1))
}
}) %>%
substr(2, nchar(.))
unlist()
# Get most frequent file types
# TODO not yet working
......@@ -229,4 +234,4 @@ higher_res <- function(x, y) {
# Avoid note for "."...
utils::globalVariables(".") # nolint:undesirable_function_linter
utils::globalVariables(".") # nolint:undesirable_function_linter
\ No newline at end of file
library(testthat)
library(biospheremetrics)
test_check("biospheremetrics")
test_that("Detect valid I/O types", {
expect_equal(
detect_io_type("../testdata/output/pft_npp.bin.json"),
"meta"
)
expect_equal(
detect_io_type("../testdata/output/pft_npp.bin"),
"raw"
)
expect_equal(
detect_io_type("../testdata/output/pft_npp.clm"),
"clm"
)
# Simple text file
tmp_filename <- tempfile("lpjmlkit")
writeLines("Hello World", tmp_filename)
expect_equal(detect_io_type(tmp_filename), "text")
file.remove(tmp_filename)
# Error for non-existing file
expect_error(
detect_io_type(tmp_filename),
"File.*does not exist"
)
})
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment