Skip to content

Commit

Permalink
fix: remove rgdal dependency (#23)
Browse files Browse the repository at this point in the history
  • Loading branch information
salvafern committed Aug 21, 2023
1 parent 46fef32 commit acce7be
Show file tree
Hide file tree
Showing 5 changed files with 19 additions and 8 deletions.
4 changes: 2 additions & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ Imports:
stats,
utils,
raster,
rgdal
terra
Authors@R: c(
person("Samuel", "Bosch", email = "[email protected]", role = c("aut")),
person("Lennert", "Tyberghein", email = "[email protected]", role = c("ctb")),
Expand All @@ -35,5 +35,5 @@ Suggests:
rmarkdown,
httr,
httr2
RoxygenNote: 7.2.0
RoxygenNote: 7.2.3
VignetteBuilder: knitr
1 change: 0 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,6 @@ export(lonlatproj)
export(pearson_correlation_matrix)
export(plot_correlation)
export(sdm_to_bo)
import(rgdal)
import(stats)
import(utils)
importFrom(raster,raster)
Expand Down
12 changes: 11 additions & 1 deletion R/load.R
Original file line number Diff line number Diff line change
Expand Up @@ -109,7 +109,7 @@ load_layers <- function(layercodes, equalarea = FALSE, rasterstack = TRUE, datad
if(max(counts) != NROW(layercodes)) {
warning("Layers from different eras (current, future, paleo) are being loaded together")
}
if(!rgdal::GDALis3ormore()){
if(gdal_is_lower_than_3()){
warning("GDAL is lower than version 3. Consider updating GDAL to avoid errors.")
}
datadir <- get_datadir(datadir)
Expand Down Expand Up @@ -180,3 +180,13 @@ lonlatproj <- sp::CRS("+proj=longlat +datum=WGS84 +no_defs")
#' using load_layers with equal_area = TRUE
#' @export
equalareaproj <- sp::CRS("+proj=cea +lon_0=0 +lat_ts=30 +x_0=0 +y_0=0 +datum=WGS84 +units=m +no_defs")

#' Is gdal v3 or more?
#' @noRd
gdal_is_lower_than_3 <- function(){
vgdal <- terra::gdal()
vgdal <- strsplit(vgdal, ".", fixed = TRUE)[[1]][1]
vgdal <- as.numeric(vgdal)
is_less_than_3 <- vgdal < 3
is_less_than_3
}
2 changes: 1 addition & 1 deletion R/sdmpredictors.R
Original file line number Diff line number Diff line change
Expand Up @@ -33,5 +33,5 @@
#' @name sdmpredictors
#'
#' @importFrom raster raster stack
#' @import stats utils rgdal
#' @import stats utils
NULL
8 changes: 5 additions & 3 deletions tests/testthat/test_load.R
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
library(sdmpredictors)
library(raster)
suppressWarnings({library(raster)})

test_dir <- file.path(tempdir(), "sdmpredictors")
options(sdmpredictors_datadir = test_dir)
Expand Down Expand Up @@ -58,7 +58,9 @@ test_that("load_layer equal area layer works", {
})
test_that("load_layer works with different datadir options", {
normalize <- function(p) {
normalizePath(paste0(p,"/"), winslash = "/", mustWork = TRUE)
suppressWarnings({
normalizePath(paste0(p,"/"), winslash = "/", mustWork = TRUE)
})
}
rpath <- function(rs) {
path <- gsub("/vsizip/", "", dirname(raster::raster(rs,1)@file@name), fixed = TRUE)
Expand Down Expand Up @@ -174,7 +176,7 @@ test_that("GDAL virtual file system works to read zipped raster files", {
rs <- raster::raster(url)

expect_equal(class(rs)[1], "RasterLayer")
expect_true(rgdal::GDALis3ormore())
expect_false(gdal_is_lower_than_3())
})


Expand Down

0 comments on commit acce7be

Please sign in to comment.