Skip to content

Commit

Permalink
read_RAST(), write_RAST(): drop GDAL-driver use (revert e1f026d, a06e782
Browse files Browse the repository at this point in the history
, 4389249) *

In the course of this fiddling with mapsets, it was seen (by accident) that the mapset
region settings are not respected by the GDAL driver.

This only affects raster.

This is a no-go for the GDAL-GRASS raster driver as long as it doesn't expose an option to
respect the mapset's current region, or at least to set a region.

A feature request has been made at the driver's repo
(OSGeo/gdal-grass#49). As long as it's not implemented, we
cannot consider using the driver for rasters since results with and without using the
driver must of course have the same extent and resolution.
  • Loading branch information
florisvdh committed Jun 18, 2024
1 parent 0775029 commit a828acf
Show file tree
Hide file tree
Showing 2 changed files with 37 additions and 74 deletions.
85 changes: 31 additions & 54 deletions R/rast_link.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@

read_RAST <- function(
vname, cat = NULL, NODATA = NULL, return_format = "terra",
use_gdal_grass_driver = TRUE, close_OK = return_format == "SGDF",
close_OK = return_format == "SGDF",
flags = NULL, Sys_ignore.stdout = FALSE,
ignore.stderr = get.ignore.stderrOption()) {
if (!is.null(cat)) {
Expand All @@ -19,7 +19,6 @@ read_RAST <- function(
openedConns <- as.integer(row.names(showConnections()))
}
stopifnot(is.logical(ignore.stderr), !is.na(ignore.stderr))
stopifnot(is.logical(use_gdal_grass_driver), !is.na(use_gdal_grass_driver))

if (!is.null(NODATA)) {
if (any(!is.finite(NODATA)) || any(!is.numeric(NODATA))) {
Expand Down Expand Up @@ -53,23 +52,20 @@ read_RAST <- function(
if (!(requireNamespace("terra", quietly = TRUE))) {
stop("terra required for SpatRaster output")
}
has_grassraster_drv <- gdal_has_grassraster_driver()
if (!has_grassraster_drv || !use_gdal_grass_driver) {
drv <- "RRASTER"
fxt <- ".grd"
ro <- FALSE
o <- execGRASS("r.out.gdal", flags = "l", intern = TRUE)
oo <- grep("RRASTER", o)
if (length(oo) == 0L) ro <- TRUE
if (!ro) {
RR <- o[oo]
RRs <- strsplit(RR, " ")[[1]]
if (length(grep("\\(rw", RRs)) == 0L) ro <- TRUE
}
if (ro) {
drv <- "GTiff"
fxt <- ".tif"
}
drv <- "RRASTER"
fxt <- ".grd"
ro <- FALSE
o <- execGRASS("r.out.gdal", flags = "l", intern = TRUE)
oo <- grep("RRASTER", o)
if (length(oo) == 0L) ro <- TRUE
if (!ro) {
RR <- o[oo]
RRs <- strsplit(RR, " ")[[1]]
if (length(grep("\\(rw", RRs)) == 0L) ro <- TRUE
}
if (ro) {
drv <- "GTiff"
fxt <- ".tif"
}
reslist <- vector(mode = "list", length = length(vname))
names(reslist) <- gsub("@", "_", vname)
Expand Down Expand Up @@ -174,31 +170,24 @@ read_RAST <- function(
} else {
NODATAi <- NODATA[i]
}
if (has_grassraster_drv && use_gdal_grass_driver) {
args <- list(name = vca[1], type = "raster")
if (length(vca) == 2L) args <- c(args, mapset = vca[2])
tmplist[[i]] <- do.call(generate_header_path, args)
tmplist[[i]] <- tempfile(fileext = fxt)
if (is.null(flags)) flags <- c("overwrite", "c", "m")
if (!is.null(cat) && cat[i]) flags <- c(flags, "t")
if (is.null(typei)) {
execGRASS("r.out.gdal",
input = vname[i], output = tmplist[[i]],
format = drv, nodata = NODATAi, flags = flags,
ignore.stderr = ignore.stderr,
Sys_ignore.stdout = Sys_ignore.stdout
)
} else {
tmplist[[i]] <- tempfile(fileext = fxt)
if (is.null(flags)) flags <- c("overwrite", "c", "m")
if (!is.null(cat) && cat[i]) flags <- c(flags, "t")
if (is.null(typei)) {
execGRASS("r.out.gdal",
input = vname[i], output = tmplist[[i]],
format = drv, nodata = NODATAi, flags = flags,
ignore.stderr = ignore.stderr,
Sys_ignore.stdout = Sys_ignore.stdout
)
} else {
execGRASS("r.out.gdal",
input = vname[i], output = tmplist[[i]],
format = drv, nodata = NODATAi, type = typei, flags = flags,
ignore.stderr = ignore.stderr,
Sys_ignore.stdout = Sys_ignore.stdout
)
}
execGRASS("r.out.gdal",
input = vname[i], output = tmplist[[i]],
format = drv, nodata = NODATAi, type = typei, flags = flags,
ignore.stderr = ignore.stderr,
Sys_ignore.stdout = Sys_ignore.stdout
)
}
# message("Reading ", tmplist[[i]])
reslist[[i]] <- getMethod("rast", "character")(tmplist[[i]])
}
resa <- getMethod("rast", "list")(reslist)
Expand Down Expand Up @@ -578,18 +567,6 @@ write_RAST <- function(
} else {
tf <- ""
}
# exit when the source is a GRASS database layer already:
if (grepl("[/\\\\]cellhd[/\\\\][^/\\\\]+$", tf)) {
grass_layername <- regmatches(
tf,
regexpr("(?<=[/\\\\]cellhd[/\\\\])[^/\\\\]+$", tf, perl = TRUE)
)
stop(
"This SpatRaster already links to the following raster layer in the ",
"GRASS GIS database: ",
grass_layername
)
}
if (!file.exists(tf)) {
drv <- "RRASTER"
fxt <- ".grd"
Expand Down
26 changes: 6 additions & 20 deletions man/readRAST.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ Read GRASS raster files from GRASS into R \pkg{terra} \code{"SpatRaster"} or \pk

\usage{
read_RAST(vname, cat=NULL, NODATA=NULL,
return_format="terra", use_gdal_grass_driver = TRUE, close_OK=return_format=="SGDF",
return_format="terra", close_OK=return_format=="SGDF",
flags=NULL, Sys_ignore.stdout = FALSE, ignore.stderr=get.ignore.stderrOption())
write_RAST(x, vname, zcol = 1, NODATA=NULL, flags=NULL,
ignore.stderr = get.ignore.stderrOption(), overwrite=FALSE, verbose=TRUE)
Expand All @@ -21,7 +21,6 @@ write_RAST(x, vname, zcol = 1, NODATA=NULL, flags=NULL,
\item{vname}{A vector of GRASS raster file names in mapsets in the current search path, as set by \dQuote{g.mapsets}; the file names may be given as fully-qualified map names using \dQuote{name@mapset}, in which case only the mapset given in the full path will be searched for the existence of the raster; if more than one raster with the same name is found in mapsets in the current search path, an error will occur, in which case the user should give the fully-qualified map name. If the fully-qualified name is used, \code{@} will be replaced by underscore in the output object.}
\item{cat}{default NULL; if not NULL, must be a logical vector matching vname, stating which (CELL) rasters to return as factor}
\item{return_format}{default \code{"terra"}, optionally \code{"SGDF"}}
\item{use_gdal_grass_driver}{Default \code{TRUE}. The \href{https://github.com/OSGeo/gdal-grass}{standalone GDAL-GRASS driver} for the raster format will be used if \code{return_format} is \code{"terra"} and if the driver is installed. The advantage is that no intermediate file(s) need to be written from GRASS GIS and subsequently read into R; instead the raster dataset(s) are read directly from the GRASS GIS database. Please read the \strong{Note} further below!}
\item{Sys_ignore.stdout}{Passed to \code{system}.}
\item{ignore.stderr}{default taking the value set by \code{set.ignore.stderrOption}; can be set to TRUE to silence \code{system()} output to standard error; does not apply on Windows platforms}
\item{close_OK}{default TRUE - clean up possible open connections used for reading metadata; may be set to FALSE to avoid the side-effect of other user-opened connections being broken}
Expand All @@ -35,10 +34,6 @@ write_RAST(x, vname, zcol = 1, NODATA=NULL, flags=NULL,

\value{\code{read_RAST} by default returns a SpatRaster object, but may return a legacy SpatialGridDataFrame object if \code{return_format="SGDF"}. \code{write_RAST} silently returns the object being written to GRASS.}

\note{
Be aware that the GDAL-GRASS driver may currently return incomplete metadata about the coordinate reference system, e.g. it may miss the EPSG code.
}

\author{Roger S. Bivand, e-mail: \email{Roger.Bivand@nhh.no}}

\examples{
Expand Down Expand Up @@ -76,11 +71,9 @@ if (run) {
inMemory(v1)
}
if (run) {
try({
write_RAST(v1, "landuse1", flags=c("o", "overwrite"))
execGRASS("r.stats", flags="c", input="landuse1")
execGRASS("g.remove", flags="f", name="landuse1", type="raster")
})
write_RAST(v1, "landuse1", flags=c("o", "overwrite"))
execGRASS("r.stats", flags="c", input="landuse1")
execGRASS("g.remove", flags="f", name="landuse1", type="raster")
}
Sys.setenv("_SP_EVOLUTION_STATUS_"="2")
run <- run && require("sp", quietly=TRUE)
Expand Down Expand Up @@ -108,17 +101,10 @@ if (run) {
}
if (run) {
print(system.time(sqdem <- read_RAST(c("sqdemSP", "elevation"),
return_format="terra",
use_gdal_grass_driver = FALSE)))
}
# install the GDAL-GRASS driver to achieve higher speed:
if (run) {
print(system.time(sqdem <- read_RAST(c("sqdemSP", "elevation"),
return_format="terra",
use_gdal_grass_driver = TRUE)))
return_format="terra")))
}
if (run) {
names(sqdem)
names(sqdem)
}
if (run) {
sqdem1 <- read_RAST(c("sqdemSP@RGRASS_EXAMPLES", "elevation@PERMANENT"))
Expand Down

0 comments on commit a828acf

Please sign in to comment.