From 682c7fc6f1b7d4068feb01ebbbe09d7a59fa8cde Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sat, 15 Jun 2024 11:20:25 +0200 Subject: [PATCH 01/34] readRAST.Rd: apply better fix than in 8df3a86 --- man/readRAST.Rd | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/man/readRAST.Rd b/man/readRAST.Rd index 49f7c9e..6eecabc 100644 --- a/man/readRAST.Rd +++ b/man/readRAST.Rd @@ -97,10 +97,10 @@ if (run) { names(sqdem) } if (run) { - try(sqdem1 <- read_RAST(c("sqdemSP@rsb", "elevation@PERMANENT"))) + sqdem1 <- read_RAST(c("sqdemSP@PERMANENT", "elevation@PERMANENT")) } if (run) { - try(names(sqdem1)) + names(sqdem1) } if (run) { execGRASS("g.remove", flags="f", name="sqdemSP", type="raster") From afa88cb1b299dda10884fc0cfb6a16b64a5b00b8 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sat, 15 Jun 2024 11:22:51 +0200 Subject: [PATCH 02/34] read_RAST(): harden precondition for ignore.stderr --- R/rast_link.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/rast_link.R b/R/rast_link.R index aa1cc69..b9005c3 100644 --- a/R/rast_link.R +++ b/R/rast_link.R @@ -17,7 +17,7 @@ read_RAST <- function( if (close_OK) { openedConns <- as.integer(row.names(showConnections())) } - stopifnot(is.logical(ignore.stderr)) + stopifnot(is.logical(ignore.stderr), !is.na(ignore.stderr)) if (!is.null(NODATA)) { if (any(!is.finite(NODATA)) || any(!is.numeric(NODATA))) { From 0f0525b0627e6df8fd1cf1c76004b532dc23dc32 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sat, 15 Jun 2024 11:23:56 +0200 Subject: [PATCH 03/34] Add internal helpers for the GDAL-GRASS drivers (raster & vector) --- DESCRIPTION | 3 ++- R/gdal_grass.R | 43 +++++++++++++++++++++++++++++++++++++++++++ 2 files changed, 45 insertions(+), 1 deletion(-) create mode 100644 R/gdal_grass.R diff --git a/DESCRIPTION b/DESCRIPTION index f88f470..80e1491 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -18,5 +18,6 @@ SystemRequirements: GRASS (>= 7) License: GPL (>= 2) URL: https://rsbivand.github.io/rgrass/, https://grass.osgeo.org/, https://github.com/rsbivand/rgrass, https://lists.osgeo.org/mailman/listinfo/grass-stats BugReports: https://github.com/rsbivand/rgrass/issues/ -Collate: AAA.R options.R rgrass.R rast_link.R vect_link.R vect_link_ng.R initGRASS.R xml1.R +Collate: AAA.R options.R rgrass.R rast_link.R vect_link.R vect_link_ng.R + initGRASS.R xml1.R gdal_grass.R diff --git a/R/gdal_grass.R b/R/gdal_grass.R new file mode 100644 index 0000000..2a10b9e --- /dev/null +++ b/R/gdal_grass.R @@ -0,0 +1,43 @@ +gdal_has_grassraster_driver <- function() { + if (!(requireNamespace("terra", quietly = TRUE))) { + stop("terra is required to get the GDAL drivers list") + } + drv <- terra::gdal(drivers = TRUE) + "GRASS" %in% drv[drv$raster, ]$name +} + +gdal_has_grassvector_driver <- function() { + if (!(requireNamespace("terra", quietly = TRUE))) { + stop("terra is required to get the GDAL drivers list") + } + drv <- terra::gdal(drivers = TRUE) + "OGR_GRASS" %in% drv[drv$vector, ]$name +} + +generate_header_path <- function(name, type, ...) { + stopifnot( + is.character(type), + length(type) == 1L, + type %in% c("raster", "vector") + ) + stopifnot( + is.character(name), + length(name) == 1L + ) + element <- ifelse(type == "vector", "vector", "cellhd") + path <- execGRASS( + "g.findfile", + element = element, + file = name, + intern = TRUE, + ... + )[4] + path <- regmatches( + path, + regexpr("(?<==['\"]).+(?=['\"]$)", path, perl = TRUE) + ) + if (type == "vector") { + path <- file.path(path, "head") + } + path +} From 4389249b2b37a6c5ab4d52a6402ff33dc2a9e745 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sat, 15 Jun 2024 11:28:49 +0200 Subject: [PATCH 04/34] read_RAST(): implement GDAL-GRASS driver by default (only with terra) --- R/rast_link.R | 70 +++++++++++++++++++++++++++++-------------------- man/readRAST.Rd | 15 ++++++++--- 2 files changed, 53 insertions(+), 32 deletions(-) diff --git a/R/rast_link.R b/R/rast_link.R index b9005c3..4bd1e3f 100644 --- a/R/rast_link.R +++ b/R/rast_link.R @@ -5,7 +5,8 @@ read_RAST <- function( vname, cat = NULL, NODATA = NULL, ignore.stderr = get.ignore.stderrOption(), return_format = "terra", - close_OK = return_format == "SGDF", flags = NULL) { + use_gdal_grass_driver = TRUE, close_OK = return_format == "SGDF", + flags = NULL) { if (!is.null(cat)) { if (length(vname) != length(cat)) { stop("vname and cat not same length") @@ -18,6 +19,7 @@ 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))) { @@ -54,20 +56,23 @@ read_RAST <- function( if (!(requireNamespace("terra", quietly = TRUE))) { stop("terra required for SpatRaster output") } - 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" + 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" + } } reslist <- vector(mode = "list", length = length(vname)) names(reslist) <- gsub("@", "_", vname) @@ -197,22 +202,29 @@ read_RAST <- function( } else { NODATAi <- NODATA[i] } - 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 - ) + 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) } else { - execGRASS("r.out.gdal", - input = vname[i], output = tmplist[[i]], - format = drv, nodata = NODATAi, type = typei, flags = flags, - ignore.stderr = ignore.stderr - ) + 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 + ) + } else { + execGRASS("r.out.gdal", + input = vname[i], output = tmplist[[i]], + format = drv, nodata = NODATAi, type = typei, flags = flags, + ignore.stderr = ignore.stderr + ) + } } + # message("Reading ", tmplist[[i]]) reslist[[i]] <- getMethod("rast", "character")(tmplist[[i]]) } resa <- getMethod("rast", "list")(reslist) diff --git a/man/readRAST.Rd b/man/readRAST.Rd index 6eecabc..018476e 100644 --- a/man/readRAST.Rd +++ b/man/readRAST.Rd @@ -11,7 +11,8 @@ Read GRASS raster files from GRASS into R \pkg{terra} \code{"SpatRaster"} or \pk \usage{ read_RAST(vname, cat=NULL, NODATA=NULL, ignore.stderr=get.ignore.stderrOption(), - return_format="terra", close_OK=return_format=="SGDF", flags=NULL) + return_format="terra", use_gdal_grass_driver = TRUE, close_OK=return_format=="SGDF", + flags=NULL) write_RAST(x, vname, zcol = 1, NODATA=NULL, flags=NULL, ignore.stderr = get.ignore.stderrOption(), overwrite=FALSE, verbose=TRUE) } @@ -20,6 +21,7 @@ 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.} \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} \item{x}{A \pkg{terra} \code{"SpatRaster"} or \pkg{sp} \code{"SpatialGridDataFrame"} object} @@ -91,10 +93,17 @@ if (run) { } if (run) { print(system.time(sqdem <- read_RAST(c("sqdemSP", "elevation"), - return_format="terra"))) + return_format="terra", + use_gdal_grass_driver = FALSE))) } +# install the GDAL-GRASS driver to achieve higher speed: if (run) { -names(sqdem) + print(system.time(sqdem <- read_RAST(c("sqdemSP", "elevation"), + return_format="terra", + use_gdal_grass_driver = TRUE))) +} +if (run) { + names(sqdem) } if (run) { sqdem1 <- read_RAST(c("sqdemSP@PERMANENT", "elevation@PERMANENT")) From a06e78227d6eee38317532fb3795ff8b14f36666 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sat, 15 Jun 2024 11:30:31 +0200 Subject: [PATCH 05/34] write_RAST(): error in case SpatRaster already linked to GRASS db --- R/rast_link.R | 12 ++++++++++++ man/readRAST.Rd | 8 +++++--- 2 files changed, 17 insertions(+), 3 deletions(-) diff --git a/R/rast_link.R b/R/rast_link.R index 4bd1e3f..076475c 100644 --- a/R/rast_link.R +++ b/R/rast_link.R @@ -604,6 +604,18 @@ 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" diff --git a/man/readRAST.Rd b/man/readRAST.Rd index 018476e..9c74684 100644 --- a/man/readRAST.Rd +++ b/man/readRAST.Rd @@ -63,9 +63,11 @@ if (run) { inMemory(v1) } if (run) { - write_RAST(v1, "landuse1", flags=c("o", "overwrite")) - execGRASS("r.stats", flags="c", input="landuse1") - execGRASS("g.remove", flags="f", name="landuse1", type="raster") + 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") + }) } Sys.setenv("_SP_EVOLUTION_STATUS_"="2") run <- run && require("sp", quietly=TRUE) From 5162ec474e943c4d7197d58700f4ffcc221829b3 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sat, 15 Jun 2024 14:15:05 +0200 Subject: [PATCH 06/34] read_VECT(): harden precondition for ignore.stderr --- R/vect_link_ng.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/vect_link_ng.R b/R/vect_link_ng.R index 1f7214e..dbf1572 100644 --- a/R/vect_link_ng.R +++ b/R/vect_link_ng.R @@ -10,7 +10,7 @@ read_VECT <- function( if (is.null(ignore.stderr)) { ignore.stderr <- get.ignore.stderrOption() } - stopifnot(is.logical(ignore.stderr)) + stopifnot(is.logical(ignore.stderr), !is.na(ignore.stderr)) if (missing(layer)) layer <- "1" layer <- as.character(layer) if (get.suppressEchoCmdInFuncOption()) { From cd9a0eab85458ab8cdd69c2b60b735365a98a0eb Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sat, 15 Jun 2024 14:15:55 +0200 Subject: [PATCH 07/34] read_VECT(): drop superfluous coercion to character (done already) --- R/vect_link_ng.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/vect_link_ng.R b/R/vect_link_ng.R index dbf1572..9b1f126 100644 --- a/R/vect_link_ng.R +++ b/R/vect_link_ng.R @@ -27,7 +27,7 @@ read_VECT <- function( tf <- tempfile(fileext = ".gpkg") execGRASS("v.out.ogr", flags = flags, input = vname, type = type, - layer = as.character(layer), output = tf, output_layer = vname, + layer = layer, output = tf, output_layer = vname, format = "GPKG", ignore.stderr = ignore.stderr ) res <- getMethod("vect", "character")(tf) From ff0831f77adb8c5da332df85471f9750eacaf745 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sat, 15 Jun 2024 19:48:04 +0200 Subject: [PATCH 08/34] read_RAST(): isolate internal fns needed as well in read_VECT() --- DESCRIPTION | 2 +- R/rast_link.R | 42 +++++++--------------------------------- R/read_helpers.R | 50 ++++++++++++++++++++++++++++++++++++++++++++++++ 3 files changed, 58 insertions(+), 36 deletions(-) create mode 100644 R/read_helpers.R diff --git a/DESCRIPTION b/DESCRIPTION index 80e1491..2f466db 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -19,5 +19,5 @@ License: GPL (>= 2) URL: https://rsbivand.github.io/rgrass/, https://grass.osgeo.org/, https://github.com/rsbivand/rgrass, https://lists.osgeo.org/mailman/listinfo/grass-stats BugReports: https://github.com/rsbivand/rgrass/issues/ Collate: AAA.R options.R rgrass.R rast_link.R vect_link.R vect_link_ng.R - initGRASS.R xml1.R gdal_grass.R + initGRASS.R xml1.R gdal_grass.R read_helpers.R diff --git a/R/rast_link.R b/R/rast_link.R index 076475c..ecf57be 100644 --- a/R/rast_link.R +++ b/R/rast_link.R @@ -34,10 +34,7 @@ read_RAST <- function( } } - msp <- unlist(strsplit(execGRASS("g.mapsets", - flags = "p", - intern = TRUE - ), " ")) + msp <- get_mapsets() if (return_format == "SGDF") { if (!(requireNamespace("sp", quietly = TRUE))) { @@ -82,37 +79,12 @@ read_RAST <- function( # 130422 at rgdal 0.8-8 GDAL.close(DS) # 061107 Dylan Beaudette NODATA # 071009 Markus Neteler's idea to use range - vca <- unlist(strsplit(vname[i], "@")) - if (length(vca) == 1L) { - exsts <- execGRASS("g.list", - type = "raster", pattern = vca[1], - intern = TRUE, ignore.stderr = ignore.stderr - ) - if (length(exsts) > 1L) { - stop( - "multiple rasters named ", vca[1], - " found in in mapsets in search path: ", - paste(msp, collapse = ", "), - " ; use full path with @ to choose the required raster" - ) - } - if (length(exsts) == 0L || exsts != vca[1]) { - stop( - vname[i], " not found in mapsets in search path: ", - paste(msp, collapse = ", ") - ) - } - } else if (length(vca) == 2L) { - exsts <- execGRASS("g.list", - type = "raster", pattern = vca[1], - mapset = vca[2], intern = TRUE, ignore.stderr = ignore.stderr - ) - if (length(exsts) == 0L || exsts != vca[1]) { - stop(vname[i], " not found in mapset: ", vca[2]) - } - } else { - stop(vname[i], " incorrectly formatted") - } + vca <- sanitize_layername( + name = vname[i], + type = "raster", + mapsets = msp, + ignore.stderr = ignore.stderr + ) typei <- NULL if (is.null(NODATA)) { tx <- execGRASS("r.info", diff --git a/R/read_helpers.R b/R/read_helpers.R new file mode 100644 index 0000000..75e3df6 --- /dev/null +++ b/R/read_helpers.R @@ -0,0 +1,50 @@ +sanitize_layername <- function(name, type, mapsets, ignore.stderr) { + stopifnot( + is.character(type), + length(type) == 1L, + type %in% c("raster", "vector") + ) + stopifnot( + is.character(name), + length(name) == 1L + ) + vca <- unlist(strsplit(name, "@")) + if (length(vca) == 1L) { + exsts <- execGRASS("g.list", + type = type, pattern = vca[1], + intern = TRUE, ignore.stderr = ignore.stderr + ) + if (length(exsts) > 1L) { + stop( + "multiple layers named ", vca[1], + " found in in mapsets in search path: ", + paste(mapsets, collapse = ", "), + " ; use full path with @ to choose the required raster" + ) + } + if (length(exsts) == 0L || exsts != vca[1]) { + stop( + name, " not found in mapsets in search path: ", + paste(mapsets, collapse = ", ") + ) + } + } else if (length(vca) == 2L) { + exsts <- execGRASS("g.list", + type = type, pattern = vca[1], + mapset = vca[2], intern = TRUE, ignore.stderr = ignore.stderr + ) + if (length(exsts) == 0L || exsts != vca[1]) { + stop(name, " not found in mapset: ", vca[2]) + } + } else { + stop(name, " incorrectly formatted") + } + vca +} + +get_mapsets <- function() { + unlist(strsplit( + execGRASS("g.mapsets", flags = "p", intern = TRUE), + " " + )) +} From 7bc6744cb1e9fe878f41c6b64dc1d523edba0f26 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sat, 15 Jun 2024 19:52:45 +0200 Subject: [PATCH 09/34] read_VECT(), write_VECT(): set the ignore.stderr default in function() --- R/vect_link_ng.R | 11 +++-------- 1 file changed, 3 insertions(+), 8 deletions(-) diff --git a/R/vect_link_ng.R b/R/vect_link_ng.R index 9b1f126..950b944 100644 --- a/R/vect_link_ng.R +++ b/R/vect_link_ng.R @@ -3,13 +3,10 @@ # read_VECT <- function( vname, layer, type = NULL, flags = "overwrite", - ignore.stderr = NULL) { + ignore.stderr = get.ignore.stderrOption()) { if (!(requireNamespace("terra", quietly = TRUE))) { stop("terra required for SpatVector output") } - if (is.null(ignore.stderr)) { - ignore.stderr <- get.ignore.stderrOption() - } stopifnot(is.logical(ignore.stderr), !is.na(ignore.stderr)) if (missing(layer)) layer <- "1" layer <- as.character(layer) @@ -40,13 +37,11 @@ read_VECT <- function( res } -write_VECT <- function(x, vname, flags = "overwrite", ignore.stderr = NULL) { +write_VECT <- function(x, vname, flags = "overwrite", + ignore.stderr = get.ignore.stderrOption()) { if (!(requireNamespace("terra", quietly = TRUE))) { stop("terra required for SpatVector input") } - if (is.null(ignore.stderr)) { - ignore.stderr <- get.ignore.stderrOption() - } stopifnot(is.logical(ignore.stderr)) if (get.suppressEchoCmdInFuncOption()) { inEchoCmd <- set.echoCmdOption(FALSE) From 5806568d6bd566f2eb7073b7f4ac33c104b82b99 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sat, 15 Jun 2024 20:09:41 +0200 Subject: [PATCH 10/34] read_VECT(): implement GDAL-GRASS driver by default --- R/vect_link_ng.R | 58 +++++++++++++++++++++++++++++++++++++++--------- 1 file changed, 48 insertions(+), 10 deletions(-) diff --git a/R/vect_link_ng.R b/R/vect_link_ng.R index 950b944..7f3ca78 100644 --- a/R/vect_link_ng.R +++ b/R/vect_link_ng.R @@ -2,17 +2,17 @@ # Copyright (c) 2022 Roger S. Bivand # read_VECT <- function( - vname, layer, type = NULL, flags = "overwrite", - ignore.stderr = get.ignore.stderrOption()) { + vname, layer, use_gdal_grass_driver = TRUE, type = NULL, + flags = "overwrite", ignore.stderr = get.ignore.stderrOption()) { if (!(requireNamespace("terra", quietly = TRUE))) { stop("terra required for SpatVector output") } stopifnot(is.logical(ignore.stderr), !is.na(ignore.stderr)) - if (missing(layer)) layer <- "1" - layer <- as.character(layer) + stopifnot(is.logical(use_gdal_grass_driver), !is.na(use_gdal_grass_driver)) if (get.suppressEchoCmdInFuncOption()) { inEchoCmd <- set.echoCmdOption(FALSE) } + if (!missing(layer)) layer <- as.character(layer) vinfo <- vInfo(vname) types <- names(vinfo)[which(vinfo > 0)] if (is.null(type)) { @@ -21,13 +21,51 @@ read_VECT <- function( if (length(grep("areas", types)) > 0) type <- "area" if (is.null(type)) stop("Vector type not found") } - tf <- tempfile(fileext = ".gpkg") - execGRASS("v.out.ogr", - flags = flags, input = vname, type = type, - layer = layer, output = tf, output_layer = vname, - format = "GPKG", ignore.stderr = ignore.stderr + msp <- get_mapsets() + # in the v.out.ogr case we won't use vca, but this is done to run the checks + # on vname anyway: + vca <- sanitize_layername( + name = vname, + type = "vector", + mapsets = msp, + ignore.stderr = ignore.stderr ) - res <- getMethod("vect", "character")(tf) + has_grassraster_drv <- gdal_has_grassraster_driver() + if (has_grassraster_drv && use_gdal_grass_driver) { + args <- list(name = vca[1], type = "vector") + if (length(vca) == 2L) args <- c(args, mapset = vca[2]) + tf <- do.call(generate_header_path, args) + layers <- terra::vector_layers(tf) + if (missing(layer)) { + # Set index as 1 and remove this condition once GDAL-GRASS driver issue + # has been solved (https://github.com/OSGeo/gdal-grass/issues/46). + # Then also move the type assignment code (from vInfo) to the + # v.out.ogr case, where it is used as an argument + index <- ifelse(type == "area", 2, 1) + layer <- layers[index] + } else if (!(layer %in% layers)) { + stop( + "Layer ", + layer, + " not found. Available layers: ", + paste(layers, collapse = ", ") + ) + } + # message("Reading ", tf, " (layer ", layer, ")") + suppressMessages({ + res <- getMethod("vect", "character")(tf, layer) + }) + } else { + if (missing(layer)) layer <- "1" + tf <- tempfile(fileext = ".gpkg") + execGRASS("v.out.ogr", + flags = flags, input = vname, type = type, + layer = layer, output = tf, output_layer = vname, + format = "GPKG", ignore.stderr = ignore.stderr + ) + # message("Reading ", tf) + res <- getMethod("vect", "character")(tf) + } if (!all(getMethod("is.valid", "SpatVector")(res))) { res <- getMethod("makeValid", "SpatVector")(res) } From 7991839caafd2798f22e6e588c838e01534fe2d6 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sat, 15 Jun 2024 20:13:27 +0200 Subject: [PATCH 11/34] write_VECT(): harden precondition for ignore.stderr --- R/vect_link_ng.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/vect_link_ng.R b/R/vect_link_ng.R index 7f3ca78..9423e0c 100644 --- a/R/vect_link_ng.R +++ b/R/vect_link_ng.R @@ -80,7 +80,7 @@ write_VECT <- function(x, vname, flags = "overwrite", if (!(requireNamespace("terra", quietly = TRUE))) { stop("terra required for SpatVector input") } - stopifnot(is.logical(ignore.stderr)) + stopifnot(is.logical(ignore.stderr), !is.na(ignore.stderr)) if (get.suppressEchoCmdInFuncOption()) { inEchoCmd <- set.echoCmdOption(FALSE) } From 4aa9be30372e339360c64b7a0ddb9a963cae7895 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sun, 16 Jun 2024 10:50:14 +0200 Subject: [PATCH 12/34] read_VECT(): add support for SpatVectorProxy --- R/vect_link_ng.R | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/R/vect_link_ng.R b/R/vect_link_ng.R index 9423e0c..4163359 100644 --- a/R/vect_link_ng.R +++ b/R/vect_link_ng.R @@ -2,7 +2,7 @@ # Copyright (c) 2022 Roger S. Bivand # read_VECT <- function( - vname, layer, use_gdal_grass_driver = TRUE, type = NULL, + vname, layer, proxy = FALSE, use_gdal_grass_driver = TRUE, type = NULL, flags = "overwrite", ignore.stderr = get.ignore.stderrOption()) { if (!(requireNamespace("terra", quietly = TRUE))) { stop("terra required for SpatVector output") @@ -53,7 +53,7 @@ read_VECT <- function( } # message("Reading ", tf, " (layer ", layer, ")") suppressMessages({ - res <- getMethod("vect", "character")(tf, layer) + res <- getMethod("vect", "character")(tf, layer, proxy = proxy) }) } else { if (missing(layer)) layer <- "1" @@ -64,7 +64,7 @@ read_VECT <- function( format = "GPKG", ignore.stderr = ignore.stderr ) # message("Reading ", tf) - res <- getMethod("vect", "character")(tf) + res <- getMethod("vect", "character")(tf, proxy = proxy) } if (!all(getMethod("is.valid", "SpatVector")(res))) { res <- getMethod("makeValid", "SpatVector")(res) From e93f7ca87a14df9485f768edc1ec824701d34561 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sun, 16 Jun 2024 11:26:35 +0200 Subject: [PATCH 13/34] write_VECT(): don't write temp GPKG when a source file exists --- R/vect_link_ng.R | 16 ++++++++++++---- 1 file changed, 12 insertions(+), 4 deletions(-) diff --git a/R/vect_link_ng.R b/R/vect_link_ng.R index 4163359..43c46b5 100644 --- a/R/vect_link_ng.R +++ b/R/vect_link_ng.R @@ -84,16 +84,24 @@ write_VECT <- function(x, vname, flags = "overwrite", if (get.suppressEchoCmdInFuncOption()) { inEchoCmd <- set.echoCmdOption(FALSE) } + srcs <- getMethod("sources", "SpatVector")(x) + if (length(srcs) == 1L) { + tf <- srcs + } else { + tf <- "" + } + if (!file.exists(tf)) { + tf <- tempfile(fileext = ".gpkg") + getMethod("writeVector", c("SpatVector", "character"))(x, filename = tf, + filetype = "GPKG", overwrite = TRUE) + } + type <- NULL if (getMethod("geomtype", "SpatVector")(x) == "points") type <- "point" if (getMethod("geomtype", "SpatVector")(x) == "lines") type <- "line" if (getMethod("geomtype", "SpatVector")(x) == "polygons") type <- "boundary" if (is.null(type)) stop("Unknown data class") - tf <- tempfile(fileext = ".gpkg") - getMethod("writeVector", c("SpatVector", "character"))(x, filename = tf, - filetype = "GPKG", overwrite = TRUE) - execGRASS("v.in.ogr", flags = flags, input = tf, output = vname, type = type, ignore.stderr = ignore.stderr From 31ccf56831cdff0348a1428614f6610a87c6cef5 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sun, 16 Jun 2024 11:27:55 +0200 Subject: [PATCH 14/34] write_VECT(): error in case SpatVector already linked to GRASS db --- R/vect_link_ng.R | 19 +++++++++++++++++++ man/readVECT.Rd | 6 ++++++ 2 files changed, 25 insertions(+) diff --git a/R/vect_link_ng.R b/R/vect_link_ng.R index 43c46b5..fa34385 100644 --- a/R/vect_link_ng.R +++ b/R/vect_link_ng.R @@ -90,6 +90,25 @@ write_VECT <- function(x, vname, flags = "overwrite", } else { tf <- "" } + # exit when the source is a GRASS database layer already: + if (grepl("[/\\\\]head::[^/\\\\]+$", tf)) { + grass_layername <- regmatches( + tf, + regexpr("(?<=[/\\\\]head::)[^/\\\\]+$", tf, perl = TRUE) + ) + grass_dsn <- regmatches( + tf, + regexpr("(?<=[/\\\\])[^/\\\\]+(?=[/\\\\]head::)", tf, perl = TRUE) + ) + stop( + "This SpatVector already links to layer '", + grass_layername, + "' of the data source '", + grass_dsn, + "' in the GRASS GIS database." + ) + } + if (!file.exists(tf)) { tf <- tempfile(fileext = ".gpkg") getMethod("writeVector", c("SpatVector", "character"))(x, filename = tf, diff --git a/man/readVECT.Rd b/man/readVECT.Rd index 924386c..2e3544c 100644 --- a/man/readVECT.Rd +++ b/man/readVECT.Rd @@ -59,6 +59,12 @@ if (run) { schs <- read_VECT("schools") print(summary(schs)) } +if (run) { + try({ + write_VECT(schs, "newsch", flags=c("o", "overwrite")) + }) + schs <- read_VECT("schools", use_gdal_grass_driver = FALSE) +} if (run) { write_VECT(schs, "newsch", flags=c("o", "overwrite")) execGRASS("v.info", map="newsch", layer="1") From 0bc303c9bd593117cfc93027308aa64b65e41bc7 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sun, 16 Jun 2024 12:08:43 +0200 Subject: [PATCH 15/34] read_VECT(): don't suppress driver messages --- R/vect_link_ng.R | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/R/vect_link_ng.R b/R/vect_link_ng.R index fa34385..c10c116 100644 --- a/R/vect_link_ng.R +++ b/R/vect_link_ng.R @@ -52,9 +52,8 @@ read_VECT <- function( ) } # message("Reading ", tf, " (layer ", layer, ")") - suppressMessages({ - res <- getMethod("vect", "character")(tf, layer, proxy = proxy) - }) + res <- getMethod("vect", "character")(tf, layer, proxy = proxy) + } else { if (missing(layer)) layer <- "1" tf <- tempfile(fileext = ".gpkg") From bce663a394f8e60cf3dd5360a1d406e86627d888 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sun, 16 Jun 2024 12:11:24 +0200 Subject: [PATCH 16/34] read_VECT(): allow missing layer arg with GDAL-GRASS driver * vect() supports a missing layer argument, so supporting this too for GDAL-GRASS driver. Also, for efficiency reasons, this commit only requests layer names in case of polygons, to work around https://github.com/OSGeo/gdal-grass/issues/46. --- R/vect_link_ng.R | 22 ++++++++-------------- 1 file changed, 8 insertions(+), 14 deletions(-) diff --git a/R/vect_link_ng.R b/R/vect_link_ng.R index c10c116..27f2a52 100644 --- a/R/vect_link_ng.R +++ b/R/vect_link_ng.R @@ -2,7 +2,7 @@ # Copyright (c) 2022 Roger S. Bivand # read_VECT <- function( - vname, layer, proxy = FALSE, use_gdal_grass_driver = TRUE, type = NULL, + vname, layer = "", proxy = FALSE, use_gdal_grass_driver = TRUE, type = NULL, flags = "overwrite", ignore.stderr = get.ignore.stderrOption()) { if (!(requireNamespace("terra", quietly = TRUE))) { stop("terra required for SpatVector output") @@ -12,6 +12,7 @@ read_VECT <- function( if (get.suppressEchoCmdInFuncOption()) { inEchoCmd <- set.echoCmdOption(FALSE) } + stopifnot(length(layer) == 1L) if (!missing(layer)) layer <- as.character(layer) vinfo <- vInfo(vname) types <- names(vinfo)[which(vinfo > 0)] @@ -31,31 +32,24 @@ read_VECT <- function( ignore.stderr = ignore.stderr ) has_grassraster_drv <- gdal_has_grassraster_driver() + if (has_grassraster_drv && use_gdal_grass_driver) { args <- list(name = vca[1], type = "vector") if (length(vca) == 2L) args <- c(args, mapset = vca[2]) tf <- do.call(generate_header_path, args) - layers <- terra::vector_layers(tf) - if (missing(layer)) { - # Set index as 1 and remove this condition once GDAL-GRASS driver issue + if (layer == "" && type == "area") { + layers <- terra::vector_layers(tf) + # Remove this condition once GDAL-GRASS driver issue # has been solved (https://github.com/OSGeo/gdal-grass/issues/46). # Then also move the type assignment code (from vInfo) to the # v.out.ogr case, where it is used as an argument - index <- ifelse(type == "area", 2, 1) - layer <- layers[index] - } else if (!(layer %in% layers)) { - stop( - "Layer ", - layer, - " not found. Available layers: ", - paste(layers, collapse = ", ") - ) + layer <- layers[2] } # message("Reading ", tf, " (layer ", layer, ")") res <- getMethod("vect", "character")(tf, layer, proxy = proxy) } else { - if (missing(layer)) layer <- "1" + if (layer == "") layer <- "1" tf <- tempfile(fileext = ".gpkg") execGRASS("v.out.ogr", flags = flags, input = vname, type = type, From de5da4d63ab9252d4f1beece8e5f2d69293fa6ed Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sun, 16 Jun 2024 12:22:16 +0200 Subject: [PATCH 17/34] read_VECT(): update debug message --- R/vect_link_ng.R | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/R/vect_link_ng.R b/R/vect_link_ng.R index 27f2a52..d6a9b1f 100644 --- a/R/vect_link_ng.R +++ b/R/vect_link_ng.R @@ -45,7 +45,13 @@ read_VECT <- function( # v.out.ogr case, where it is used as an argument layer <- layers[2] } - # message("Reading ", tf, " (layer ", layer, ")") + # message( + # "Will get data source ", + # tf, + # " (layername ", + # ifelse(layer == "", "unknown, will get first layer", layer), + # ")" + # ) res <- getMethod("vect", "character")(tf, layer, proxy = proxy) } else { From e1f026d2ea87e8c6be85effc9d57dfc3afa015bc Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sun, 16 Jun 2024 13:13:15 +0200 Subject: [PATCH 18/34] readRAST.Rd: add note on GDAL-GRASS driver missing CRS metadata --- man/readRAST.Rd | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/man/readRAST.Rd b/man/readRAST.Rd index 9c74684..6d8a5d4 100644 --- a/man/readRAST.Rd +++ b/man/readRAST.Rd @@ -21,7 +21,7 @@ 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.} + \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{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} \item{x}{A \pkg{terra} \code{"SpatRaster"} or \pkg{sp} \code{"SpatialGridDataFrame"} object} @@ -34,6 +34,10 @@ 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{ From f712436041f9a048da02fcb6ce91642778d67641 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sun, 16 Jun 2024 13:14:47 +0200 Subject: [PATCH 19/34] readVECT.Rd: update documentation & add GDAL-GRASS note --- man/readVECT.Rd | 16 +++++++++++----- 1 file changed, 11 insertions(+), 5 deletions(-) diff --git a/man/readVECT.Rd b/man/readVECT.Rd index 2e3544c..15a332b 100644 --- a/man/readVECT.Rd +++ b/man/readVECT.Rd @@ -13,9 +13,9 @@ \code{read_VECT} moves one GRASS vector object file with attribute data through a temporary GeoPackage file to a \pkg{terra} \code{"SpatVector"} object; \code{write_VECT} moves a \pkg{terra} \code{"SpatVector"} object through a temporary GeoPackage file to a GRASS vector object file. \code{vect2neigh} returns neighbour pairs with shared boundary length as described by Markus Neteler, in \url{https://stat.ethz.ch/pipermail/r-sig-geo/2005-October/000616.html}. \code{cygwin_clean_temp} can be called to try to clean the GRASS mapset-specific temporary directory under cygwin. } \usage{ -read_VECT(vname, layer, type=NULL, flags="overwrite", - ignore.stderr = NULL) -write_VECT(x, vname, flags="overwrite", ignore.stderr = NULL) +read_VECT(vname, layer = "", proxy = FALSE, use_gdal_grass_driver = TRUE, type = NULL, + flags = "overwrite", ignore.stderr = get.ignore.stderrOption()) +write_VECT(x, vname, flags = "overwrite", ignore.stderr = get.ignore.stderrOption()) vInfo(vname, layer, ignore.stderr = NULL) vColumns(vname, layer, ignore.stderr = NULL) vDataCount(vname, layer, ignore.stderr = NULL) @@ -25,7 +25,9 @@ vect2neigh(vname, ID=NULL, ignore.stderr = NULL, remove=TRUE, vname2=NULL, %- maybe also 'usage' for other objects documented here. \arguments{ \item{vname}{A GRASS vector file name} - \item{layer}{a layer name (string); if missing set to default of \dQuote{1}} + \item{layer}{a layer name (string); if missing the first layer will be used} + \item{proxy}{Default is \code{FALSE}. Set as \code{TRUE} if you need a \code{SpatVectorProxy} object.} + \item{use_gdal_grass_driver}{Default \code{TRUE}. The \href{https://github.com/OSGeo/gdal-grass}{standalone GDAL-GRASS driver} for the vector format will be used if it is installed. The advantage is that no intermediate file needs to be written from GRASS GIS and subsequently read into R; instead the vector layer is read directly from the GRASS GIS database. Please read the \strong{Note} further below!} \item{type}{override type detection when multiple types are non-zero, passed to v.out.ogr} \item{ignore.stderr}{default the value set by \code{set.ignore.stderrOption}; NULL, 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{x}{A \code{"SpatVector"} object moved to GRASS} @@ -36,11 +38,15 @@ vect2neigh(vname, ID=NULL, ignore.stderr = NULL, remove=TRUE, vname2=NULL, \item{units}{default "k"; see GRASS 'v.to.db' manual page for alternatives} } \value{ - \code{read_VECT} imports a GRASS vector object into a \code{"SpatVector"} object. + \code{read_VECT} imports a GRASS vector layer into a \code{SpatVector} or \code{SpatVectorProxy} object. \code{vect2neigh} returns a data frame object with left and right neighbours and boundary lengths, also given class GRASSneigh and spatial.neighbour (as used in spdep). The incantation to retrieve the neighbours list is \code{sn2listw(vect2neigh())$neighbours}, and to retrieve the boundary lengths: \code{sn2listw(vect2neigh())$weights}. The GRASSneigh object has two other useful attributes: external is a vector giving the length of shared boundary between each polygon and the external area, and total giving each polygon's total boundary length. } +\note{ +Be aware that the GDAL-GRASS driver may have some \href{https://github.com/OSGeo/gdal-grass/issues}{issues} for vector data. In our experience, the error and warning messages for vector data can be ignored. Further, the returned metadata about the coordinate reference system may currently be incomplete, e.g. it may miss the EPSG code. +} + \author{Roger S. Bivand, e-mail: \email{Roger.Bivand@nhh.no}} \examples{ From c32588db338ec93deb98781e2e622f02d0d00142 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sun, 16 Jun 2024 13:31:23 +0200 Subject: [PATCH 20/34] DESCRIPTION: add codetools to Suggests --- DESCRIPTION | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 2f466db..00720d3 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -12,7 +12,7 @@ Authors@R: c( Description: An interface between the 'GRASS' geographical information system ('GIS') and 'R', based on starting 'R' from within the 'GRASS' 'GIS' environment, or running a free-standing 'R' session in a temporary 'GRASS' location; the package provides facilities for using all 'GRASS' commands from the 'R' command line. The original interface package for 'GRASS 5' (2000-2010) is described in Bivand (2000) and Bivand (2001) . This was succeeded by 'spgrass6' for 'GRASS 6' (2006-2016) and 'rgrass7' for 'GRASS 7' (2015-present). The 'rgrass' package modernizes the interface for 'GRASS 8' while still permitting the use of 'GRASS 7'. Depends: R (>= 3.5.0) Imports: stats, utils, methods, xml2 -Suggests: terra (>= 1.6-16), sp (>= 0.9), knitr, rmarkdown, sf, stars, raster (>= 3.6-3) +Suggests: terra (>= 1.6-16), sp (>= 0.9), knitr, rmarkdown, sf, stars, raster (>= 3.6-3), codetools VignetteBuilder: knitr SystemRequirements: GRASS (>= 7) License: GPL (>= 2) From f02dd46cf8f41a61195af4b946122c315490c97c Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sun, 16 Jun 2024 15:05:26 +0200 Subject: [PATCH 21/34] read_RAST(): move ignore.stderr backward in usage --- R/rast_link.R | 5 ++--- man/readRAST.Rd | 4 ++-- 2 files changed, 4 insertions(+), 5 deletions(-) diff --git a/R/rast_link.R b/R/rast_link.R index ecf57be..2800222 100644 --- a/R/rast_link.R +++ b/R/rast_link.R @@ -3,10 +3,9 @@ # read_RAST <- function( - vname, cat = NULL, NODATA = NULL, - ignore.stderr = get.ignore.stderrOption(), return_format = "terra", + vname, cat = NULL, NODATA = NULL, return_format = "terra", use_gdal_grass_driver = TRUE, close_OK = return_format == "SGDF", - flags = NULL) { + flags = NULL, ignore.stderr = get.ignore.stderrOption()) { if (!is.null(cat)) { if (length(vname) != length(cat)) { stop("vname and cat not same length") diff --git a/man/readRAST.Rd b/man/readRAST.Rd index 6d8a5d4..d5862f7 100644 --- a/man/readRAST.Rd +++ b/man/readRAST.Rd @@ -10,9 +10,9 @@ Read GRASS raster files from GRASS into R \pkg{terra} \code{"SpatRaster"} or \pk \usage{ -read_RAST(vname, cat=NULL, NODATA=NULL, ignore.stderr=get.ignore.stderrOption(), +read_RAST(vname, cat=NULL, NODATA=NULL, return_format="terra", use_gdal_grass_driver = TRUE, close_OK=return_format=="SGDF", - flags=NULL) + flags=NULL, ignore.stderr=get.ignore.stderrOption()) write_RAST(x, vname, zcol = 1, NODATA=NULL, flags=NULL, ignore.stderr = get.ignore.stderrOption(), overwrite=FALSE, verbose=TRUE) } From 6a40b38249c227e86cf9ac97ef601bddc71795db Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sun, 16 Jun 2024 15:14:32 +0200 Subject: [PATCH 22/34] read_RAST(): expose Sys_ignore.stdout argument --- R/rast_link.R | 9 ++++++--- man/readRAST.Rd | 3 ++- 2 files changed, 8 insertions(+), 4 deletions(-) diff --git a/R/rast_link.R b/R/rast_link.R index 2800222..eff387e 100644 --- a/R/rast_link.R +++ b/R/rast_link.R @@ -5,7 +5,8 @@ read_RAST <- function( vname, cat = NULL, NODATA = NULL, return_format = "terra", use_gdal_grass_driver = TRUE, close_OK = return_format == "SGDF", - flags = NULL, ignore.stderr = get.ignore.stderrOption()) { + flags = NULL, Sys_ignore.stdout = FALSE, + ignore.stderr = get.ignore.stderrOption()) { if (!is.null(cat)) { if (length(vname) != length(cat)) { stop("vname and cat not same length") @@ -185,13 +186,15 @@ read_RAST <- function( execGRASS("r.out.gdal", input = vname[i], output = tmplist[[i]], format = drv, nodata = NODATAi, flags = flags, - ignore.stderr = ignore.stderr + 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 + ignore.stderr = ignore.stderr, + Sys_ignore.stdout = Sys_ignore.stdout ) } } diff --git a/man/readRAST.Rd b/man/readRAST.Rd index d5862f7..24ae22b 100644 --- a/man/readRAST.Rd +++ b/man/readRAST.Rd @@ -12,7 +12,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", - flags=NULL, ignore.stderr=get.ignore.stderrOption()) + 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) } @@ -22,6 +22,7 @@ write_RAST(x, vname, zcol = 1, NODATA=NULL, flags=NULL, \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} \item{x}{A \pkg{terra} \code{"SpatRaster"} or \pkg{sp} \code{"SpatialGridDataFrame"} object} From a64ef0ec6c0360d8f1d7faf24a73b37439768032 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sun, 16 Jun 2024 15:17:33 +0200 Subject: [PATCH 23/34] read_VECT(): expose Sys_ignore.stdout argument --- R/vect_link_ng.R | 6 ++++-- man/readVECT.Rd | 4 +++- 2 files changed, 7 insertions(+), 3 deletions(-) diff --git a/R/vect_link_ng.R b/R/vect_link_ng.R index d6a9b1f..81eef3c 100644 --- a/R/vect_link_ng.R +++ b/R/vect_link_ng.R @@ -3,7 +3,8 @@ # read_VECT <- function( vname, layer = "", proxy = FALSE, use_gdal_grass_driver = TRUE, type = NULL, - flags = "overwrite", ignore.stderr = get.ignore.stderrOption()) { + flags = "overwrite", Sys_ignore.stdout = FALSE, + ignore.stderr = get.ignore.stderrOption()) { if (!(requireNamespace("terra", quietly = TRUE))) { stop("terra required for SpatVector output") } @@ -60,7 +61,8 @@ read_VECT <- function( execGRASS("v.out.ogr", flags = flags, input = vname, type = type, layer = layer, output = tf, output_layer = vname, - format = "GPKG", ignore.stderr = ignore.stderr + format = "GPKG", Sys_ignore.stdout = Sys_ignore.stdout, + ignore.stderr = ignore.stderr ) # message("Reading ", tf) res <- getMethod("vect", "character")(tf, proxy = proxy) diff --git a/man/readVECT.Rd b/man/readVECT.Rd index 15a332b..8842fe7 100644 --- a/man/readVECT.Rd +++ b/man/readVECT.Rd @@ -14,7 +14,8 @@ } \usage{ read_VECT(vname, layer = "", proxy = FALSE, use_gdal_grass_driver = TRUE, type = NULL, - flags = "overwrite", ignore.stderr = get.ignore.stderrOption()) + flags = "overwrite", Sys_ignore.stdout = FALSE, + ignore.stderr = get.ignore.stderrOption()) write_VECT(x, vname, flags = "overwrite", ignore.stderr = get.ignore.stderrOption()) vInfo(vname, layer, ignore.stderr = NULL) vColumns(vname, layer, ignore.stderr = NULL) @@ -29,6 +30,7 @@ vect2neigh(vname, ID=NULL, ignore.stderr = NULL, remove=TRUE, vname2=NULL, \item{proxy}{Default is \code{FALSE}. Set as \code{TRUE} if you need a \code{SpatVectorProxy} object.} \item{use_gdal_grass_driver}{Default \code{TRUE}. The \href{https://github.com/OSGeo/gdal-grass}{standalone GDAL-GRASS driver} for the vector format will be used if it is installed. The advantage is that no intermediate file needs to be written from GRASS GIS and subsequently read into R; instead the vector layer is read directly from the GRASS GIS database. Please read the \strong{Note} further below!} \item{type}{override type detection when multiple types are non-zero, passed to v.out.ogr} + \item{Sys_ignore.stdout}{Passed to \code{system}.} \item{ignore.stderr}{default the value set by \code{set.ignore.stderrOption}; NULL, 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{x}{A \code{"SpatVector"} object moved to GRASS} \item{flags}{Character vector containing additional optional flags and/or options for v.in.ogr, particularly "o" and "overwrite"} From 87adff00fd08013a008c39a05f01063d1b54be5a Mon Sep 17 00:00:00 2001 From: florisvdh Date: Sun, 16 Jun 2024 15:58:30 +0200 Subject: [PATCH 24/34] execGRASS(): always respect ignore.stderr, Sys_ignore.stdout --- R/xml1.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/xml1.R b/R/xml1.R index 0bc99ca..19aa649 100644 --- a/R/xml1.R +++ b/R/xml1.R @@ -536,8 +536,8 @@ execGRASS <- function( return(resOut) } - if (length(resOut) > 0) cat(resOut, sep = "\n") - if (length(resErr) > 0) cat(resErr, sep = "\n") + if (length(resOut) > 0 && !Sys_ignore.stdout) cat(resOut, sep = "\n") + if (length(resErr) > 0 && !ignore.stderr) cat(resErr, sep = "\n") attr(res, "resOut") <- resOut attr(res, "resErr") <- resErr From 3c749ce9c75b755e3822c69cfea73bc17b46fe2f Mon Sep 17 00:00:00 2001 From: florisvdh Date: Mon, 17 Jun 2024 16:59:11 +0200 Subject: [PATCH 25/34] readRAST.Rd examples: update code style --- man/readRAST.Rd | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/man/readRAST.Rd b/man/readRAST.Rd index 24ae22b..1170a15 100644 --- a/man/readRAST.Rd +++ b/man/readRAST.Rd @@ -44,7 +44,7 @@ Be aware that the GDAL-GRASS driver may currently return incomplete metadata abo \examples{ run <- FALSE if (nchar(Sys.getenv("GISRC")) > 0 && - read.dcf(Sys.getenv("GISRC"))[1,"LOCATION_NAME"] == "nc_basic_spm_grass7") run <- TRUE + read.dcf(Sys.getenv("GISRC"))[1,"LOCATION_NAME"] == "nc_basic_spm_grass7") run <- TRUE GV <- Sys.getenv("GRASS_VERBOSE") Sys.setenv("GRASS_VERBOSE"=0) ois <- get.ignore.stderrOption() @@ -53,13 +53,13 @@ if (run) { unlist(strsplit(execGRASS("g.mapsets", flags="p", intern=TRUE), " ")) } if (run) { -execGRASS("g.list", type="raster", pattern="soils", flags="m", intern=TRUE) + execGRASS("g.list", type="raster", pattern="soils", flags="m", intern=TRUE) } if (run) { -execGRASS("g.list", type="raster", pattern="soils@PERMANENT", mapset=".", flags="m", intern=TRUE) + execGRASS("g.list", type="raster", pattern="soils@PERMANENT", mapset=".", flags="m", intern=TRUE) } if (run) { -execGRASS("g.list", type="raster", pattern="soils", mapset="PERMANENT", flags="m", intern=TRUE) + execGRASS("g.list", type="raster", pattern="soils", mapset="PERMANENT", flags="m", intern=TRUE) } run <- run && require("terra", quietly=TRUE) if (run) { @@ -78,7 +78,7 @@ Sys.setenv("_SP_EVOLUTION_STATUS_"="2") run <- run && require("sp", quietly=TRUE) if (run) { nc_basic <- read_RAST(c("geology", "elevation"), cat=c(TRUE, FALSE), - return_format="SGDF") + return_format="SGDF") print(table(nc_basic$geology)) } if (run) { @@ -96,7 +96,7 @@ if (run) { } if (run) { print(system.time(sqdemSP <- read_RAST(c("sqdemSP", "elevation"), - return_format="SGDF"))) + return_format="SGDF"))) } if (run) { print(system.time(sqdem <- read_RAST(c("sqdemSP", "elevation"), From 7eab282052f3f1d55660cbe45a517e63183e194d Mon Sep 17 00:00:00 2001 From: florisvdh Date: Mon, 17 Jun 2024 17:00:13 +0200 Subject: [PATCH 26/34] readRAST.Rd exmpl: take control of mapsets; only write to a custom one * 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 will be made at the driver's repo, but 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. For sake of completeness, this commit takes control of the region too, in order to guarantee that things always work. But this will be dropped from the examples in a next commit, followed by dropping driver-related code from read_RAST() and write_RAST(). --- man/readRAST.Rd | 19 +++++++++++++++++-- 1 file changed, 17 insertions(+), 2 deletions(-) diff --git a/man/readRAST.Rd b/man/readRAST.Rd index 1170a15..a678868 100644 --- a/man/readRAST.Rd +++ b/man/readRAST.Rd @@ -50,7 +50,16 @@ Sys.setenv("GRASS_VERBOSE"=0) ois <- get.ignore.stderrOption() set.ignore.stderrOption(TRUE) if (run) { -unlist(strsplit(execGRASS("g.mapsets", flags="p", intern=TRUE), " ")) + meta <- gmeta() + location_path <- file.path(meta$GISDBASE, meta$LOCATION_NAME) + previous_mapset <- meta$MAPSET + example_mapset <- "RGRASS_EXAMPLES" + execGRASS("g.mapset", "c", mapset = example_mapset) + execGRASS("g.region", region = "central_10m@PERMANENT") +} + +if (run) { + unlist(strsplit(execGRASS("g.mapsets", flags="p", intern=TRUE), " ")) } if (run) { execGRASS("g.list", type="raster", pattern="soils", flags="m", intern=TRUE) @@ -113,7 +122,7 @@ if (run) { names(sqdem) } if (run) { - sqdem1 <- read_RAST(c("sqdemSP@PERMANENT", "elevation@PERMANENT")) + sqdem1 <- read_RAST(c("sqdemSP@RGRASS_EXAMPLES", "elevation@PERMANENT")) } if (run) { names(sqdem1) @@ -140,6 +149,12 @@ if (run) { if (run) { execGRASS("g.remove", flags="f", name="test_t", type="raster") } +if (run) { + execGRASS("g.mapset", mapset = previous_mapset) + if (example_mapset != previous_mapset) { + unlink(file.path(location_path, example_mapset), recursive = TRUE) + } +} Sys.setenv("GRASS_VERBOSE"=GV) set.ignore.stderrOption(ois) } From 07750294cf8c25771e0d7a4e27f0b05b8c715a43 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Mon, 17 Jun 2024 17:13:19 +0200 Subject: [PATCH 27/34] readRAST.Rd exmpl: don't control region; should work with any region * 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 will be made at the driver's repo, but 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. So next is dropping driver-related code from read_RAST() and write_RAST(). --- man/readRAST.Rd | 1 - 1 file changed, 1 deletion(-) diff --git a/man/readRAST.Rd b/man/readRAST.Rd index a678868..6aed825 100644 --- a/man/readRAST.Rd +++ b/man/readRAST.Rd @@ -55,7 +55,6 @@ if (run) { previous_mapset <- meta$MAPSET example_mapset <- "RGRASS_EXAMPLES" execGRASS("g.mapset", "c", mapset = example_mapset) - execGRASS("g.region", region = "central_10m@PERMANENT") } if (run) { From a828acfb4bf520e32c227245e18a9224ce2914a4 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Mon, 17 Jun 2024 17:25:10 +0200 Subject: [PATCH 28/34] read_RAST(), write_RAST(): drop GDAL-driver use (revert e1f026d, a06e782, 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 (https://github.com/OSGeo/gdal-grass/issues/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. --- R/rast_link.R | 85 ++++++++++++++++++------------------------------- man/readRAST.Rd | 26 ++++----------- 2 files changed, 37 insertions(+), 74 deletions(-) diff --git a/R/rast_link.R b/R/rast_link.R index eff387e..2aeff2c 100644 --- a/R/rast_link.R +++ b/R/rast_link.R @@ -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)) { @@ -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))) { @@ -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) @@ -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) @@ -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" diff --git a/man/readRAST.Rd b/man/readRAST.Rd index 6aed825..5161287 100644 --- a/man/readRAST.Rd +++ b/man/readRAST.Rd @@ -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) @@ -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} @@ -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{ @@ -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) @@ -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")) From ed4123075b7479c14f74c74117a77cbbabde4102 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Mon, 17 Jun 2024 17:50:59 +0200 Subject: [PATCH 29/34] readVECT.Rd examples: update code style --- man/readVECT.Rd | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/man/readVECT.Rd b/man/readVECT.Rd index 8842fe7..77ccb6b 100644 --- a/man/readVECT.Rd +++ b/man/readVECT.Rd @@ -54,7 +54,7 @@ Be aware that the GDAL-GRASS driver may have some \href{https://github.com/OSGeo \examples{ run <- FALSE if (nchar(Sys.getenv("GISRC")) > 0 && - read.dcf(Sys.getenv("GISRC"))[1,"LOCATION_NAME"] == "nc_basic_spm_grass7") run <- TRUE + read.dcf(Sys.getenv("GISRC"))[1,"LOCATION_NAME"] == "nc_basic_spm_grass7") run <- TRUE GV <- Sys.getenv("GRASS_VERBOSE") Sys.setenv("GRASS_VERBOSE"=0) ois <- get.ignore.stderrOption() From 94c33cc7fc63e0bf32c3699d62d251983d750e70 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Mon, 17 Jun 2024 17:51:52 +0200 Subject: [PATCH 30/34] readVECT.Rd exmpl: take control of mapsets; only write to a custom one --- man/readVECT.Rd | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/man/readVECT.Rd b/man/readVECT.Rd index 77ccb6b..2840d96 100644 --- a/man/readVECT.Rd +++ b/man/readVECT.Rd @@ -59,6 +59,14 @@ GV <- Sys.getenv("GRASS_VERBOSE") Sys.setenv("GRASS_VERBOSE"=0) ois <- get.ignore.stderrOption() set.ignore.stderrOption(TRUE) +if (run) { + meta <- gmeta() + location_path <- file.path(meta$GISDBASE, meta$LOCATION_NAME) + previous_mapset <- meta$MAPSET + example_mapset <- "RGRASS_EXAMPLES" + execGRASS("g.mapset", "c", mapset = example_mapset) +} + if (run) { execGRASS("v.info", map="schools", layer="1") } @@ -97,6 +105,10 @@ if (run) { } if (run) { execGRASS("g.remove", flags="f", name=c("newsch", "newsch1"), type="vector") + execGRASS("g.mapset", mapset = previous_mapset) + if (example_mapset != previous_mapset) { + unlink(file.path(location_path, example_mapset), recursive = TRUE) + } } Sys.setenv("GRASS_VERBOSE"=GV) set.ignore.stderrOption(ois) From 3738dd759c7c952dcc393842c70e3325affecb7c Mon Sep 17 00:00:00 2001 From: florisvdh Date: Mon, 17 Jun 2024 17:52:38 +0200 Subject: [PATCH 31/34] readVECT.Rd exmpl: don't run vect2neigh(), it still writes in PERMANENT --- man/readVECT.Rd | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/man/readVECT.Rd b/man/readVECT.Rd index 2840d96..6a88f94 100644 --- a/man/readVECT.Rd +++ b/man/readVECT.Rd @@ -99,7 +99,9 @@ if (run) { roads <- read_VECT("roadsmajor") print(summary(roads)) } -if (run) { +if (FALSE) { + # not run: vect2neigh() currently writes 3 new data sources in the PERMANENT + # mapset, despite this mapset not being the active one. cen_neig <- vect2neigh("census") str(cen_neig) } From b1e725108957438110c8c933f9b1cb769d8da4e2 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Tue, 18 Jun 2024 19:16:36 +0200 Subject: [PATCH 32/34] NEWS.md (0.4.3): use canonical name GRASS GIS --- NEWS.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index 5792a65..fb4431a 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,6 +1,6 @@ # **rgrass** version 0.4-3 (development) -- see #87 - Windows QGIS standalone installations of GRASS can be used only if R is started in the OSGeo4W shell bundled with the installation +- see #87 - Windows QGIS standalone installations of GRASS GIS can be used only if R is started in the OSGeo4W shell bundled with the installation # **rgrass** version 0.4-2 (2024-03-17) From b4c21f4e38085f1bddb61062643f20a1c2edd7b4 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Tue, 18 Jun 2024 19:17:50 +0200 Subject: [PATCH 33/34] NEWS.md: list new features for read_VECT(), write_VECT() --- NEWS.md | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/NEWS.md b/NEWS.md index fb4431a..ee12597 100644 --- a/NEWS.md +++ b/NEWS.md @@ -2,6 +2,15 @@ - see #87 - Windows QGIS standalone installations of GRASS GIS can be used only if R is started in the OSGeo4W shell bundled with the installation +- `write_VECT()`: when the `SpatVector` object already refers to a source file, an intermediate temporary file is no longer written to get the data into the GRASS GIS database (#93). +A similar shortcut was already in place for `write_RAST()`. + +- `read_VECT()`: provide access to the standalone GDAL-GRASS driver to read vector data, which skips the step of writing a intermediate file (#93). +Note that this standalone driver needs to be set up separately. +More information is in the [driver's README](https://github.com/OSGeo/gdal-grass/blob/main/README.md). + +- `read_VECT()`: support reading as `SpatVectorProxy` class of `{terra}`, by providing a `proxy` argument (#93). + # **rgrass** version 0.4-2 (2024-03-17) - see #84 - handling fully-qualified map names From 020fabc3ee8e3226e7ad2ec2492a5d542bb231e2 Mon Sep 17 00:00:00 2001 From: florisvdh Date: Tue, 18 Jun 2024 19:18:06 +0200 Subject: [PATCH 34/34] Update pkgdown site --- docs/404.html | 4 +- docs/CONTRIBUTING.html | 17 +- docs/articles/coerce.html | 35 ++--- docs/articles/index.html | 4 +- docs/articles/use.html | 6 +- docs/authors.html | 6 +- docs/index.html | 8 +- docs/news/index.html | 17 +- docs/pkgdown.yml | 6 +- docs/reference/execGRASS.html | 116 +------------- docs/reference/gmeta.html | 107 +------------ docs/reference/index.html | 4 +- docs/reference/initGRASS.html | 4 +- docs/reference/readRAST-1.png | Bin 39176 -> 0 bytes docs/reference/readRAST.html | 150 ++++-------------- docs/reference/readVECT.html | 282 ++++++---------------------------- docs/reference/rgrass.html | 132 +--------------- 17 files changed, 139 insertions(+), 759 deletions(-) delete mode 100644 docs/reference/readRAST-1.png diff --git a/docs/404.html b/docs/404.html index 0f0619e..c844dd2 100644 --- a/docs/404.html +++ b/docs/404.html @@ -6,7 +6,7 @@ Page not found (404) • rgrass - + @@ -103,7 +103,7 @@

Page not found (404)

-

Site built with pkgdown 2.0.7.

+

Site built with pkgdown 2.0.9.

diff --git a/docs/CONTRIBUTING.html b/docs/CONTRIBUTING.html index f13988c..800d47d 100644 --- a/docs/CONTRIBUTING.html +++ b/docs/CONTRIBUTING.html @@ -1,5 +1,5 @@ -NA • rgrassNA • rgrass @@ -62,15 +62,16 @@

NA

Contributing to rgrass

-

This outlines how to propose a change to rgrass as we move to support GRASS 8.0. The rgrass package is the successor to the rgrass7 package. rgrass supports both GRASS 7 and 8 and is available from CRAN; rgrass7 will be retired at the latest at the end of 2023 when rgdal retires.

+

This outlines how to propose a change to rgrass. The package supports both GRASS GIS 7 and 8 and is available from CRAN.

How to propose a change to rgrass

-

To propose a change to rgrass, please consider the roles assigned to the different branches in this repository.

-
  • The main branch is the development branch for rgrass. If you would like to contribute to rgrass (“new” package), please target your PRs and contributions to this branch.

  • -
  • The rgrass7 branch is the “target” maintenance source for the package rgrass7 (“old” package). If you would like to contribute to rgrass7, please target your PRs and contributions to this branch, but note that onlly essential PRs will be considered.

  • -
  • The next release of rgrass7 has been updated to give a startup message advising users to switch to rgrass and to deprecate all functionality.

  • -
+

The main branch is the development branch for rgrass. If you would like to contribute to rgrass, please target your PRs and contributions to this branch.

+ +
+

Note

+

The rgrass package is the successor to the rgrass7 package. The rgrass7 branch was the “target” maintenance source for the rgrass7 package, at a time that both rgrass7 and rgrass coexisted. rgrass7 development is no longer continued; the package has been archived on CRAN. The rgrass7 branch is kept for reference only.

+
@@ -88,7 +89,7 @@

How to propose a change to rgrass
-

Site built with pkgdown 2.0.7.

+

Site built with pkgdown 2.0.9.

diff --git a/docs/articles/coerce.html b/docs/articles/coerce.html index 8a9098a..42735f3 100644 --- a/docs/articles/coerce.html +++ b/docs/articles/coerce.html @@ -6,7 +6,7 @@ Coercion between object formats • rgrass - + @@ -141,10 +141,10 @@

Loading and attaching packages
 library("terra")
-
## terra 1.7.71
+
## terra 1.7.78
-
## Linking to GEOS 3.12.1, GDAL 3.8.4, PROJ 9.4.0; sf_use_s2() is TRUE
+
## Linking to GEOS 3.12.1, GDAL 3.8.4, PROJ 9.3.1; sf_use_s2() is TRUE
@@ -155,9 +155,9 @@ 

Loading and attaching packagesterra::gdal() tells us the versions of the external libraries being used by terra:

-gdal(lib="all")
+gdal(lib = "all")

##     gdal     proj     geos 
-##  "3.8.4"  "9.4.0" "3.12.1"
+## "3.8.4" "9.3.1" "3.12.1"

When using CRAN binary packages built static for Windows and macOS, the R packages will use the same versions of the external libraries, but not necessarily the same versions as those against which GRASS was @@ -173,7 +173,7 @@

"SpatVector" object is returned, and the same class of object is needed for write_VECT() for writing to GRASS.

-fv <- system.file("ex/lux.shp", package="terra")
+fv <- system.file("ex/lux.shp", package = "terra")
 (v <- vect(fv))
##  class       : SpatVector 
 ##  geometry    : polygons 
@@ -190,8 +190,7 @@ 

inMemory() method:

-
## Error in (function (classes, fdef, mtable)  : 
-##   unable to find an inherited method for function 'inMemory' for signature '"SpatVector"'
+
## Error : unable to find an inherited method for function 'inMemory' for signature 'x = "SpatVector"'

The coordinate reference system is expressed in WKT2-2019 form:

 cat(crs(v), "\n")
@@ -263,7 +262,7 @@

## 1 Diekirch 2 Diekirch 218 32543 ## 1 Diekirch 3 Redange 259 18664

-all.equal(v_sf_rt, v, check.attributes=FALSE)
+all.equal(v_sf_rt, v, check.attributes = FALSE)
## [1] TRUE
@@ -301,7 +300,7 @@

## Max. :312.0 Max. :182607
 v_sp_rt <- vect(st_as_sf(v_sp))
-all.equal(v_sp_rt, v, check.attributes=FALSE)
+all.equal(v_sp_rt, v, check.attributes = FALSE)

## [1] TRUE
@@ -315,7 +314,7 @@

returned, and the same class of object is needed for write_RAST() for writing to GRASS.

-fr <- system.file("ex/elev.tif", package="terra")
+fr <- system.file("ex/elev.tif", package = "terra")
 (r <- rast(fr))
## class       : SpatRaster 
 ## dimensions  : 90, 95, 1  (nrow, ncol, nlyr)
@@ -363,7 +362,7 @@ 

## max value : 547

When coercing to "stars_proxy" the same applies:

-(r_stars_p <- st_as_stars(r, proxy=TRUE))
+(r_stars_p <- st_as_stars(r, proxy = TRUE))
## stars_proxy object with 1 attribute in 1 file(s):
 ## $elev.tif
 ## [1] "[...]/elev.tif"
@@ -410,7 +409,7 @@ 

The WKT2-2019 CRS representation is present but not shown by default:

-cat(wkt(r_RL), "\n")
+cat(wkt(r_RL), "\n")

## GEOGCRS["unknown",
 ##     DATUM["World Geodetic System 1984",
 ##         ELLIPSOID["WGS 84",6378137,298.257223563,
@@ -475,7 +474,7 @@ 

The WKT2-2019 CRS representation is present but not shown by default:

-cat(wkt(r_sp_RL), "\n")
+cat(wkt(r_sp_RL), "\n")

## GEOGCRS["unknown",
 ##     DATUM["World Geodetic System 1984",
 ##         ELLIPSOID["WGS 84",6378137,298.257223563,
@@ -506,7 +505,7 @@ 

## names : elevation ## values : 141, 547 (min, max)

-cat(wkt(r_sp_RL_rt), "\n")
+cat(wkt(r_sp_RL_rt), "\n")
## GEOGCRS["unknown",
 ##     DATUM["World Geodetic System 1984",
 ##         ELLIPSOID["WGS 84",6378137,298.257223563,
@@ -584,7 +583,7 @@ 

## Max. :547.0 ## NA's :3942

-cat(wkt(r_sp_stars), "\n")
+cat(wkt(r_sp_stars), "\n")
## GEOGCRS["WGS 84",
 ##     ENSEMBLE["World Geodetic System 1984 ensemble",
 ##         MEMBER["World Geodetic System 1984 (Transit)"],
@@ -648,7 +647,7 @@ 

References

-
+
Bivand, R. S. 2000. “Using the R Statistical Data Analysis Language on GRASS 5.0 GIS Data Base @@ -707,7 +706,7 @@

References

-

Site built with pkgdown 2.0.7.

+

Site built with pkgdown 2.0.9.

diff --git a/docs/articles/index.html b/docs/articles/index.html index 4abb479..e037d59 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -1,5 +1,5 @@ -Articles • rgrassArticles • rgrass @@ -77,7 +77,7 @@

All vignettes

-

Site built with pkgdown 2.0.7.

+

Site built with pkgdown 2.0.9.

diff --git a/docs/articles/use.html b/docs/articles/use.html index 8013963..ba44eb3 100644 --- a/docs/articles/use.html +++ b/docs/articles/use.html @@ -6,7 +6,7 @@ Use of GRASS interface • rgrass - + @@ -367,7 +367,7 @@

Existing GRASS location

References

-
+
Bivand, R. S. 2000. “Using the R Statistical Data Analysis Language on GRASS 5.0 GIS Data Base @@ -399,7 +399,7 @@

References

-

Site built with pkgdown 2.0.7.

+

Site built with pkgdown 2.0.9.

diff --git a/docs/authors.html b/docs/authors.html index a6ff0f4..8fca3ac 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -1,5 +1,5 @@ -Authors and Citation • rgrassAuthors and Citation • rgrass @@ -57,7 +57,7 @@
@@ -117,7 +117,7 @@

Citation

-

Site built with pkgdown 2.0.7.

+

Site built with pkgdown 2.0.9.

diff --git a/docs/index.html b/docs/index.html index 414bacc..af7dfe2 100644 --- a/docs/index.html +++ b/docs/index.html @@ -6,7 +6,7 @@ Interface Between GRASS Geographical Information System and R • rgrass - + @@ -88,12 +88,12 @@

Interface Between GRASS Geographical Information System and R

Interpreted interface between GRASS geographical information system and R, based on starting R from within the GRASS GIS environment, or running free-standing R in a temporary or existing GRASS location; the package provides facilities for using all GRASS commands from the R command line, see https://rsbivand.github.io/rgrass/articles/use.html.

-

The original interface GRASS package for GRASS 5 (2000-2010) is described in Bivand (2000) (https://doi.org/10.1016/S0098-3004(00)00057-1) and Bivand (2001) (https://www.r-project.org/conferences/DSC-2001/Proceedings/Bivand.pdf). This was succeeded by spgrass6 for GRASS 6 (2006-2016) and rgrass7 for GRASS 7 (2015-2023). Note that rgrass7 will be archived on CRAN together with rgdal in October 2023. The rgrass package modernizes the interface for GRASS 8 while still permitting the use of GRASS 7.

+

The original interface GRASS package for GRASS 5 (2000-2010) is described in Bivand (2000) (https://doi.org/10.1016/S0098-3004(00)00057-1) and Bivand (2001) (https://www.r-project.org/conferences/DSC-2001/Proceedings/Bivand.pdf). This was succeeded by spgrass6 for GRASS 6 (2006-2016) and rgrass7 for GRASS 7 (2015-2023). The rgrass package modernizes the interface for GRASS 8 while still permitting the use of GRASS 7.

Installation

-

This package depends on GRASS version 8 or above (later version 7 should also be OK).

+

This package depends on GRASS GIS version 8 or above (later version 7 should also be OK).

If you use OSGeo4W on Windows (recommended), remember that you must start RStudio, Rgui or console R from within the OSGeo4W shell.

See the workshop on rgrass at FOSS4G 2022 for a detailed introduction with reproducible examples.

If you would like to contribute, please see the CONTRIBUTING file in the .github folder.

@@ -154,7 +154,7 @@

Developers

-

Site built with pkgdown 2.0.7.

+

Site built with pkgdown 2.0.9.

diff --git a/docs/news/index.html b/docs/news/index.html index 24be011..8a54119 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -1,5 +1,5 @@ -Changelog • rgrassChangelog • rgrass @@ -63,7 +63,10 @@

Changelog

-
  • see #87 - Windows QGIS standalone installations of GRASS can be used only if R is started in the OSGeo4W shell bundled with the installation
  • +
    • see #87 - Windows QGIS standalone installations of GRASS GIS can be used only if R is started in the OSGeo4W shell bundled with the installation

    • +
    • write_VECT(): when the SpatVector object already refers to a source file, an intermediate temporary file is no longer written to get the data into the GRASS GIS database (#93). A similar shortcut was already in place for write_RAST().

    • +
    • read_VECT(): provide access to the standalone GDAL-GRASS driver to read vector data, which skips the step of writing a intermediate file (#93). Note that this standalone driver needs to be set up separately. More information is in the driver’s README.

    • +
    • read_VECT(): support reading as SpatVectorProxy class of terra, by providing a proxy argument (#93).

-
  • #73 guess gisBase= in initGRASS()

  • +
    • #73 guess gisBase= in initGRASS()

    • added SP_EVOLUTION_STATUS 2 to examples

    • -
    • #66 re-examining to protect from UInt maxing out; add stop for required manual NODATA

    • -
    • #68, #69 improvements to vignettes, thanks to Floris Vanderhaeghe and Veronica Andreo

    • +
    • #66 re-examining to protect from UInt maxing out; add stop for required manual NODATA

    • +
    • #68, #69 improvements to vignettes, thanks to Floris Vanderhaeghe and Veronica Andreo

-
  • #63 and #64, detection of GRASS path for initGRASS() semi-automated if grass --config path works or if environment variable GRASS_INSTALLATION set to path, thanks to Robin Lovelace

  • +
    • #63 and #64, detection of GRASS path for initGRASS() semi-automated if grass --config path works or if environment variable GRASS_INSTALLATION set to path, thanks to Robin Lovelace

    • correct NODATA logic in read_RAST() for unsigned rasters #66 thanks to Laura Poggio

@@ -129,7 +132,7 @@
diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index c8b028a..fc5bfcb 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -1,8 +1,8 @@ -pandoc: 3.1.3 -pkgdown: 2.0.7 +pandoc: 3.1.11 +pkgdown: 2.0.9 pkgdown_sha: ~ articles: coerce: coerce.html use: use.html -last_built: 2024-03-25T16:19Z +last_built: 2024-06-18T17:06Z diff --git a/docs/reference/execGRASS.html b/docs/reference/execGRASS.html index 158a46f..eba06e8 100644 --- a/docs/reference/execGRASS.html +++ b/docs/reference/execGRASS.html @@ -1,5 +1,5 @@ -Run GRASS commands — execGRASS • rgrassRun GRASS commands — execGRASS • rgrass @@ -165,139 +165,35 @@

Examples

if (run) { print(parseGRASS("r.slope.aspect")) } -#> Command: r.slope.aspect -#> Description: Generates raster maps of slope, aspect, curvatures and partial derivatives from an elevation raster map. Aspect is calculated counterclockwise from east. -#> Keywords: raster, terrain, aspect, slope, curvature, parallel -#> Parameters: -#> name: elevation, type: string, required: yes, multiple: no -#> keydesc: name, keydesc_count: 1 -#> [Name of input elevation raster map] -#> name: slope, type: string, required: no, multiple: no -#> keydesc: name, keydesc_count: 1 -#> [Name for output slope raster map] -#> name: aspect, type: string, required: no, multiple: no -#> keydesc: name, keydesc_count: 1 -#> [Name for output aspect raster map] -#> name: format, type: string, required: no, multiple: no -#> default: degrees -#> [Format for reporting the slope] -#> name: precision, type: string, required: no, multiple: no -#> default: FCELL -#> [Storage type for resultant raster map] -#> name: pcurvature, type: string, required: no, multiple: no -#> keydesc: name, keydesc_count: 1 -#> [Name for output profile curvature raster map] -#> name: tcurvature, type: string, required: no, multiple: no -#> keydesc: name, keydesc_count: 1 -#> [Name for output tangential curvature raster map] -#> name: dx, type: string, required: no, multiple: no -#> keydesc: name, keydesc_count: 1 -#> [Name for output first order partial derivative dx (E-W slope) raster map] -#> name: dy, type: string, required: no, multiple: no -#> keydesc: name, keydesc_count: 1 -#> [Name for output first order partial derivative dy (N-S slope) raster map] -#> name: dxx, type: string, required: no, multiple: no -#> keydesc: name, keydesc_count: 1 -#> [Name for output second order partial derivative dxx raster map] -#> name: dyy, type: string, required: no, multiple: no -#> keydesc: name, keydesc_count: 1 -#> [Name for output second order partial derivative dyy raster map] -#> name: dxy, type: string, required: no, multiple: no -#> keydesc: name, keydesc_count: 1 -#> [Name for output second order partial derivative dxy raster map] -#> name: zscale, type: float, required: no, multiple: no -#> default: 1.0 -#> [Multiplicative factor to convert elevation units to horizontal units] -#> name: min_slope, type: float, required: no, multiple: no -#> default: 0.0 -#> [Minimum slope value (in percent) for which aspect is computed] -#> name: nprocs, type: integer, required: no, multiple: no -#> default: 1 -#> [Number of threads for parallel computing] -#> name: memory, type: integer, required: no, multiple: no -#> default: 300 -#> keydesc: memory in MB, keydesc_count: 1 -#> [Cache size for raster rows] -#> Flags: -#> name: a [Do not align the current region to the raster elevation map] {FALSE} -#> name: e [Compute output at edges and near NULL values] {FALSE} -#> name: n [Default: degrees counter-clockwise from East, with flat = 0] {FALSE} -#> name: overwrite [Allow output files to overwrite existing files] {FALSE} -#> name: help [Print usage summary] {FALSE} -#> name: verbose [Verbose module output] {FALSE} -#> name: quiet [Quiet module output] {FALSE} if (run) { doGRASS("r.slope.aspect", flags=c("overwrite"), elevation="elevation.dem", slope="slope", aspect="aspect") } -#> GRASS command: r.slope.aspect --overwrite elevation=elevation.dem slope=slope aspect=aspect -#> [1] "r.slope.aspect --overwrite elevation=elevation.dem slope=slope aspect=aspect" -#> attr(,"cmd") -#> [1] "r.slope.aspect" if (run) { pars <- list(elevation="elevation", slope="slope", aspect="aspect") doGRASS("r.slope.aspect", flags=c("overwrite"), parameters=pars) } -#> GRASS command: r.slope.aspect --overwrite elevation=elevation slope=slope aspect=aspect -#> [1] "r.slope.aspect --overwrite elevation=elevation slope=slope aspect=aspect" -#> attr(,"cmd") -#> [1] "r.slope.aspect" if (run) { print(parseGRASS("r.buffer")) } -#> Command: r.buffer -#> Description: Creates a raster map showing buffer zones surrounding cells that contain non-NULL category values. -#> Keywords: raster, buffer -#> Parameters: -#> name: input, type: string, required: yes, multiple: no -#> keydesc: name, keydesc_count: 1 -#> [Name of input raster map] -#> name: output, type: string, required: yes, multiple: no -#> keydesc: name, keydesc_count: 1 -#> [Name for output raster map] -#> name: distances, type: float, required: yes, multiple: yes -#> [Distance zone(s)] -#> name: units, type: string, required: no, multiple: no -#> default: meters -#> [Units of distance] -#> Flags: -#> name: z [Ignore zero (0) data cells instead of NULL cells] {FALSE} -#> name: overwrite [Allow output files to overwrite existing files] {FALSE} -#> name: help [Print usage summary] {FALSE} -#> name: verbose [Verbose module output] {FALSE} -#> name: quiet [Quiet module output] {FALSE} if (run) { doGRASS("r.buffer", flags=c("overwrite"), input="schools", output="bmap", distances=seq(1000,15000,1000)) } -#> GRASS command: r.buffer --overwrite input=schools output=bmap distances=1000,2000,3000,4000,5000,6000,7000,8000,9000,10000,11000,12000,13000,14000,15000 -#> [1] "r.buffer --overwrite input=schools output=bmap distances=1000,2000,3000,4000,5000,6000,7000,8000,9000,10000,11000,12000,13000,14000,15000" -#> attr(,"cmd") -#> [1] "r.buffer" if (run) { pars <- list(input="schools", output="bmap", distances=seq(1000,15000,1000)) doGRASS("r.buffer", flags=c("overwrite"), parameters=pars) } -#> GRASS command: r.buffer --overwrite input=schools output=bmap distances=1000,2000,3000,4000,5000,6000,7000,8000,9000,10000,11000,12000,13000,14000,15000 -#> [1] "r.buffer --overwrite input=schools output=bmap distances=1000,2000,3000,4000,5000,6000,7000,8000,9000,10000,11000,12000,13000,14000,15000" -#> attr(,"cmd") -#> [1] "r.buffer" if (run) { set.echoCmdOption(oechoCmd) try(res <- execGRASS("r.stats", input = "fire_blocksgg", # no such file flags = c("C", "n")), silent=FALSE) } -#> Error in execGRASS("r.stats", input = "fire_blocksgg", flags = c("C", : -#> The command: -#> r.stats -C -n input=fire_blocksgg -#> produced an error (1) during execution: -#> ERROR: Raster map <fire_blocksgg> not found if (run) { res <- execGRASS("r.stats", input = "fire_blocksgg", flags = c("C", "n"), legacyExec=TRUE) print(res) } -#> [1] 1 if (run) { if (res != 0) { resERR <- execGRASS("r.stats", input = "fire_blocksgg", @@ -305,18 +201,10 @@

Examples

print(resERR) } } -#> Warning: running command 'r.stats -C -n input=fire_blocksgg 2>&1' had status 1 -#> [1] "ERROR: Raster map <fire_blocksgg> not found" -#> attr(,"status") -#> [1] 1 if (run) { res <- stringexecGRASS("r.stats -p -l input=geology", intern=TRUE) print(res) } -#> [1] "217 CZfg 35.83%" "262 CZlg 9.81%" "270 CZig 34.04%" "405 CZbg 12.53%" -#> [5] "583 CZve 1.07%" "720 CZam 0.24%" "766 CZg 0.35%" "862 CZam 3.05%" -#> [9] "910 CZbg 2.22%" "921 Km 0.62%" "945 CZbg 0.00%" "946 CZam 0.20%" -#> [13] "948 CZam 0.04%" if (run) { stringexecGRASS(paste("r.random.cells --overwrite --quiet output=samples", "distance=1000 ncells=100 seed=1")) @@ -339,7 +227,7 @@

Examples

-

Site built with pkgdown 2.0.7.

+

Site built with pkgdown 2.0.9.

diff --git a/docs/reference/gmeta.html b/docs/reference/gmeta.html index fe5fa89..7eef210 100644 --- a/docs/reference/gmeta.html +++ b/docs/reference/gmeta.html @@ -1,5 +1,5 @@ -Reads GRASS metadata from the current LOCATION — gmeta • rgrassReads GRASS metadata from the current LOCATION — gmeta • rgrass @@ -125,123 +125,22 @@

Examples

G <- gmeta() print(G) } -#> gisdbase /home/rsb/topics/grassdata -#> location nc_basic_spm_grass7 -#> mapset rsb -#> rows 1350 -#> columns 1500 -#> north 228500 -#> south 215000 -#> west 630000 -#> east 645000 -#> nsres 10 -#> ewres 10 -#> projection: -#> PROJCRS["NAD83(HARN) / North Carolina", -#> BASEGEOGCRS["NAD83(HARN)", -#> DATUM["NAD83 (High Accuracy Reference Network)", -#> ELLIPSOID["GRS 1980",6378137,298.257222101, -#> LENGTHUNIT["metre",1]]], -#> PRIMEM["Greenwich",0, -#> ANGLEUNIT["degree",0.0174532925199433]], -#> ID["EPSG",4152]], -#> CONVERSION["SPCS83 North Carolina zone (meter)", -#> METHOD["Lambert Conic Conformal (2SP)", -#> ID["EPSG",9802]], -#> PARAMETER["Latitude of false origin",33.75, -#> ANGLEUNIT["degree",0.0174532925199433], -#> ID["EPSG",8821]], -#> PARAMETER["Longitude of false origin",-79, -#> ANGLEUNIT["degree",0.0174532925199433], -#> ID["EPSG",8822]], -#> PARAMETER["Latitude of 1st standard parallel",36.1666666666667, -#> ANGLEUNIT["degree",0.0174532925199433], -#> ID["EPSG",8823]], -#> PARAMETER["Latitude of 2nd standard parallel",34.3333333333333, -#> ANGLEUNIT["degree",0.0174532925199433], -#> ID["EPSG",8824]], -#> PARAMETER["Easting at false origin",609601.22, -#> LENGTHUNIT["metre",1], -#> ID["EPSG",8826]], -#> PARAMETER["Northing at false origin",0, -#> LENGTHUNIT["metre",1], -#> ID["EPSG",8827]]], -#> CS[Cartesian,2], -#> AXIS["easting (X)",east, -#> ORDER[1], -#> LENGTHUNIT["metre",1]], -#> AXIS["northing (Y)",north, -#> ORDER[2], -#> LENGTHUNIT["metre",1]], -#> USAGE[ -#> SCOPE["Engineering survey, topographic mapping."], -#> AREA["United States (USA) - North Carolina - counties of Alamance; Alexander; Alleghany; Anson; Ashe; Avery; Beaufort; Bertie; Bladen; Brunswick; Buncombe; Burke; Cabarrus; Caldwell; Camden; Carteret; Caswell; Catawba; Chatham; Cherokee; Chowan; Clay; Cleveland; Columbus; Craven; Cumberland; Currituck; Dare; Davidson; Davie; Duplin; Durham; Edgecombe; Forsyth; Franklin; Gaston; Gates; Graham; Granville; Greene; Guilford; Halifax; Harnett; Haywood; Henderson; Hertford; Hoke; Hyde; Iredell; Jackson; Johnston; Jones; Lee; Lenoir; Lincoln; Macon; Madison; Martin; McDowell; Mecklenburg; Mitchell; Montgomery; Moore; Nash; New Hanover; Northampton; Onslow; Orange; Pamlico; Pasquotank; Pender; Perquimans; Person; Pitt; Polk; Randolph; Richmond; Robeson; Rockingham; Rowan; Rutherford; Sampson; Scotland; Stanly; Stokes; Surry; Swain; Transylvania; Tyrrell; Union; Vance; Wake; Warren; Washington; Watauga; Wayne; Wilkes; Wilson; Yadkin; Yancey."], -#> BBOX[33.83,-84.33,36.59,-75.38]], -#> ID["EPSG",3358]] if (run) { cat(getLocationProj(), "\n") } -#> PROJCRS["NAD83(HARN) / North Carolina", -#> BASEGEOGCRS["NAD83(HARN)", -#> DATUM["NAD83 (High Accuracy Reference Network)", -#> ELLIPSOID["GRS 1980",6378137,298.257222101, -#> LENGTHUNIT["metre",1]]], -#> PRIMEM["Greenwich",0, -#> ANGLEUNIT["degree",0.0174532925199433]], -#> ID["EPSG",4152]], -#> CONVERSION["SPCS83 North Carolina zone (meter)", -#> METHOD["Lambert Conic Conformal (2SP)", -#> ID["EPSG",9802]], -#> PARAMETER["Latitude of false origin",33.75, -#> ANGLEUNIT["degree",0.0174532925199433], -#> ID["EPSG",8821]], -#> PARAMETER["Longitude of false origin",-79, -#> ANGLEUNIT["degree",0.0174532925199433], -#> ID["EPSG",8822]], -#> PARAMETER["Latitude of 1st standard parallel",36.1666666666667, -#> ANGLEUNIT["degree",0.0174532925199433], -#> ID["EPSG",8823]], -#> PARAMETER["Latitude of 2nd standard parallel",34.3333333333333, -#> ANGLEUNIT["degree",0.0174532925199433], -#> ID["EPSG",8824]], -#> PARAMETER["Easting at false origin",609601.22, -#> LENGTHUNIT["metre",1], -#> ID["EPSG",8826]], -#> PARAMETER["Northing at false origin",0, -#> LENGTHUNIT["metre",1], -#> ID["EPSG",8827]]], -#> CS[Cartesian,2], -#> AXIS["easting (X)",east, -#> ORDER[1], -#> LENGTHUNIT["metre",1]], -#> AXIS["northing (Y)",north, -#> ORDER[2], -#> LENGTHUNIT["metre",1]], -#> USAGE[ -#> SCOPE["Engineering survey, topographic mapping."], -#> AREA["United States (USA) - North Carolina - counties of Alamance; Alexander; Alleghany; Anson; Ashe; Avery; Beaufort; Bertie; Bladen; Brunswick; Buncombe; Burke; Cabarrus; Caldwell; Camden; Carteret; Caswell; Catawba; Chatham; Cherokee; Chowan; Clay; Cleveland; Columbus; Craven; Cumberland; Currituck; Dare; Davidson; Davie; Duplin; Durham; Edgecombe; Forsyth; Franklin; Gaston; Gates; Graham; Granville; Greene; Guilford; Halifax; Harnett; Haywood; Henderson; Hertford; Hoke; Hyde; Iredell; Jackson; Johnston; Jones; Lee; Lenoir; Lincoln; Macon; Madison; Martin; McDowell; Mecklenburg; Mitchell; Montgomery; Moore; Nash; New Hanover; Northampton; Onslow; Orange; Pamlico; Pasquotank; Pender; Perquimans; Person; Pitt; Polk; Randolph; Richmond; Robeson; Rockingham; Rowan; Rutherford; Sampson; Scotland; Stanly; Stokes; Surry; Swain; Transylvania; Tyrrell; Union; Vance; Wake; Warren; Washington; Watauga; Wayne; Wilkes; Wilson; Yadkin; Yancey."], -#> BBOX[33.83,-84.33,36.59,-75.38]], -#> ID["EPSG",3358]] if (run) { cat(getLocationProj(g.proj_WKT=FALSE), "\n") } -#> +proj=lcc +lat_0=33.75 +lon_0=-79 +lat_1=36.1666666666667 +lat_2=34.3333333333333 +x_0=609601.22 +y_0=0 +ellps=GRS80 +units=m +no_defs +type=crs if (run) { grd <- gmeta2grd() print(grd) } -#> X1 X2 -#> cellcentre.offset 630005 215005 -#> cellsize 10 10 -#> cells.dim 1500 1350 if (run) { ncells <- prod(slot(grd, "cells.dim")) df <- data.frame(k=rep(1, ncells)) - mask_SG <- sp::SpatialGridDataFrame(grd, data=df) + mask_SG <- sp::SpatialGridDataFrame(grd, data=df) print(summary(mask_SG)) } -#> Length Class Mode -#> 2025000 SpatialGridDataFrame S4
@@ -256,7 +155,7 @@

Examples

-

Site built with pkgdown 2.0.7.

+

Site built with pkgdown 2.0.9.

diff --git a/docs/reference/index.html b/docs/reference/index.html index 757baac..5203484 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -1,5 +1,5 @@ -Function reference • rgrassFunction reference • rgrass @@ -100,7 +100,7 @@

All functions
-

Site built with pkgdown 2.0.7.

+

Site built with pkgdown 2.0.9.

diff --git a/docs/reference/initGRASS.html b/docs/reference/initGRASS.html index e3234b2..40b12e5 100644 --- a/docs/reference/initGRASS.html +++ b/docs/reference/initGRASS.html @@ -1,5 +1,5 @@ -Initiate GRASS session — initGRASS • rgrassInitiate GRASS session — initGRASS • rgrassRead and write GRASS raster files — readRAST • rgrassRead and write GRASS raster files — readRAST • rgrass @@ -66,9 +66,10 @@

Read and write GRASS raster files

-
read_RAST(vname, cat=NULL, NODATA=NULL, ignore.stderr=get.ignore.stderrOption(),
- return_format="terra", close_OK=return_format=="SGDF", flags=NULL)
-write_RAST(x, vname, zcol = 1, NODATA=NULL, flags=NULL, 
+    
read_RAST(vname, cat=NULL, NODATA=NULL,
+ 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)
@@ -83,6 +84,9 @@

Arguments

return_format

default "terra", optionally "SGDF"

+
Sys_ignore.stdout
+

Passed to system.

+
ignore.stderr

default taking the value set by set.ignore.stderrOption; can be set to TRUE to silence system() output to standard error; does not apply on Windows platforms

@@ -121,83 +125,56 @@

Author

Examples

run <- FALSE
 if (nchar(Sys.getenv("GISRC")) > 0 &&
-  read.dcf(Sys.getenv("GISRC"))[1,"LOCATION_NAME"] == "nc_basic_spm_grass7") run <- TRUE
+    read.dcf(Sys.getenv("GISRC"))[1,"LOCATION_NAME"] == "nc_basic_spm_grass7") run <- TRUE
 GV <- Sys.getenv("GRASS_VERBOSE")
 Sys.setenv("GRASS_VERBOSE"=0)
 ois <- get.ignore.stderrOption()
 set.ignore.stderrOption(TRUE)
 #> [1] FALSE
 if (run) {
-unlist(strsplit(execGRASS("g.mapsets", flags="p", intern=TRUE), " "))
+  meta <- gmeta()
+  location_path <- file.path(meta$GISDBASE, meta$LOCATION_NAME)
+  previous_mapset <- meta$MAPSET
+  example_mapset <- "RGRASS_EXAMPLES"
+  execGRASS("g.mapset", "c", mapset = example_mapset)
+}
+
+if (run) {
+  unlist(strsplit(execGRASS("g.mapsets", flags="p", intern=TRUE), " "))
 }
-#> [1] "rsb"       "PERMANENT"
 if (run) {
-execGRASS("g.list", type="raster", pattern="soils", flags="m", intern=TRUE)
+  execGRASS("g.list", type="raster", pattern="soils", flags="m", intern=TRUE)
 }
-#> [1] "soils@PERMANENT"
 if (run) {
-execGRASS("g.list", type="raster", pattern="soils@PERMANENT", mapset=".", flags="m", intern=TRUE)
+  execGRASS("g.list", type="raster", pattern="soils@PERMANENT", mapset=".", flags="m", intern=TRUE)
 }
-#> character(0)
 if (run) {
-execGRASS("g.list", type="raster", pattern="soils", mapset="PERMANENT", flags="m", intern=TRUE)
+  execGRASS("g.list", type="raster", pattern="soils", mapset="PERMANENT", flags="m", intern=TRUE)
 }
-#> [1] "soils@PERMANENT"
 run <- run && require("terra", quietly=TRUE)
-#> terra 1.7.71
 if (run) {
   v1 <- read_RAST("landuse", cat=TRUE, return_format="terra")
   v1
   inMemory(v1)
 }
-#> [1] FALSE
 if (run) {
   write_RAST(v1, "landuse1", flags=c("o", "overwrite"))
   execGRASS("r.stats", flags="c", input="landuse1")
   execGRASS("g.remove", flags="f", name="landuse1", type="raster")
 }
-#> SpatRaster read into GRASS using r.in.gdal from file
-#> 1 592288
-#> 2 17347
-#> 3 206129
-#> 4 135994
-#> 5 1021725
-#> 6 42854
-#> 7 1610
-#> * 7053
 Sys.setenv("_SP_EVOLUTION_STATUS_"="2")
 run <- run && require("sp", quietly=TRUE)
 if (run) {
   nc_basic <- read_RAST(c("geology", "elevation"), cat=c(TRUE, FALSE),
-    return_format="SGDF")
+                        return_format="SGDF")
   print(table(nc_basic$geology))
 }
-#> Warning: non-unique category labels; category number appended
-#> 
-#> CZfg_217 CZlg_262 CZig_270 CZbg_405 CZve_583 CZam_720  CZg_766 CZam_862 
-#>   725562   198684   689373   253710    21609     4824     7074    61722 
-#> CZbg_910   Km_921 CZbg_945 CZam_946 CZam_948 
-#>    44964    12528        9     4068      873 
 if (run) {
   execGRASS("r.stats", flags=c("c", "l", "quiet"), input="geology")
 }
-#> 217 CZfg 725562
-#> 262 CZlg 198684
-#> 270 CZig 689373
-#> 405 CZbg 253710
-#> 583 CZve 21609
-#> 720 CZam 4824
-#> 766 CZg 7074
-#> 862 CZam 61722
-#> 910 CZbg 44964
-#> 921 Km 12528
-#> 945 CZbg 9
-#> 946 CZam 4068
-#> 948 CZam 873
 if (run) {
   boxplot(nc_basic$elevation ~ nc_basic$geology)
 }
-
 if (run) {
   nc_basic$sqdem <- sqrt(nc_basic$elevation)
 }
@@ -205,90 +182,32 @@ 

Examples

write_RAST(nc_basic, "sqdemSP", zcol="sqdem", flags=c("quiet", "overwrite")) execGRASS("r.info", map="sqdemSP") } -#> SpatialGridDataFrame read into GRASS using r.in.bin -#> +----------------------------------------------------------------------------+ -#> | Map: sqdemSP Date: Mon Mar 25 17:19:25 2024 | -#> | Mapset: rsb Login of Creator: rsb | -#> | Location: nc_basic_spm_grass7 | -#> | DataBase: /home/rsb/topics/grassdata | -#> | Title: | -#> | Timestamp: none | -#> |----------------------------------------------------------------------------| -#> | | -#> | Type of Map: raster Number of Categories: 0 | -#> | Data Type: DCELL Semantic label: (none) | -#> | Rows: 1350 | -#> | Columns: 1500 | -#> | Total Cells: 2025000 | -#> | Projection: Lambert Conformal Conic | -#> | N: 228500 S: 215000 Res: 10 | -#> | E: 645000 W: 630000 Res: 10 | -#> | Range of data: min = 7.45511854848878 max = 12.5031941719687 | -#> | | -#> | Data Description: | -#> | generated by r.in.bin | -#> | | -#> | Comments: | -#> | r.in.bin --overwrite --quiet -d input="/home/rsb/topics/grassdata/nc\ | -#> | _basic_spm_grass7/rsb/.tmp/localhost.localdomain/X834" output="sqdem\ | -#> | SP" bytes=8 header=0 bands=1 order="native" north=228500 south=21500\ | -#> | 0 east=645000 west=630000 rows=1350 cols=1500 anull=6 | -#> | | -#> +----------------------------------------------------------------------------+ -#> if (run) { print(system.time(sqdemSP <- read_RAST(c("sqdemSP", "elevation"), - return_format="SGDF"))) + return_format="SGDF"))) } -#> user system elapsed -#> 0.663 0.123 0.790 if (run) { print(system.time(sqdem <- read_RAST(c("sqdemSP", "elevation"), return_format="terra"))) } -#> user system elapsed -#> 0.573 0.129 0.708 if (run) { names(sqdem) } -#> [1] "sqdemSP" "elevation" if (run) { - try(sqdem1 <- read_RAST(c("sqdemSP@rsb", "elevation@PERMANENT"))) + sqdem1 <- read_RAST(c("sqdemSP@RGRASS_EXAMPLES", "elevation@PERMANENT")) } if (run) { -names(sqdem1) + names(sqdem1) } -#> [1] "sqdemSP_rsb" "elevation_PERMANENT" if (run) { execGRASS("g.remove", flags="f", name="sqdemSP", type="raster") execGRASS("r.mapcalc", expression="basins0 = basins - 1", flags="overwrite") execGRASS("r.stats", flags="c", input="basins0") } -#> 1 116975 -#> 3 75480 -#> 5 1137 -#> 7 80506 -#> 9 7472 -#> 11 348209 -#> 13 51456 -#> 15 81959 -#> 17 29652 -#> 19 267883 -#> 21 89465 -#> 23 63433 -#> 25 91354 -#> 27 190239 -#> 29 59727 -#> * 470053 if (run) { basins0 <- read_RAST("basins0", return_format="SGDF") print(table(basins0$basins0)) } -#> -#> 1 3 5 7 9 11 13 15 17 19 21 -#> 116975 75480 1137 80506 7472 348209 51456 81959 29652 267883 89465 -#> 23 25 27 29 -#> 63433 91354 190239 59727 if (run) { execGRASS("g.remove", flags="f", name="basins0", type="raster") } @@ -296,23 +215,18 @@

Examples

execGRASS(cmd = "r.mapcalc", expression="test_t=66000", flags="overwrite") execGRASS("r.info", flags = "r", map = "test_t", intern = TRUE) # #82 } -#> [1] "min=66000" "max=66000" if (run) { (tt = read_RAST(vname = "test_t")) } -#> WARNING: Too many values, color table cut to 65535 entries -#> class : SpatRaster -#> dimensions : 1350, 1500, 1 (nrow, ncol, nlyr) -#> resolution : 10, 10 (x, y) -#> extent : 630000, 645000, 215000, 228500 (xmin, xmax, ymin, ymax) -#> coord. ref. : NAD83(HARN) / North Carolina (EPSG:3358) -#> source : filee806331c8da49.grd -#> name : filee806331c8da49 -#> min value : 0 -#> max value : 66000 if (run) { execGRASS("g.remove", flags="f", name="test_t", type="raster") } +if (run) { + execGRASS("g.mapset", mapset = previous_mapset) + if (example_mapset != previous_mapset) { + unlink(file.path(location_path, example_mapset), recursive = TRUE) + } +} Sys.setenv("GRASS_VERBOSE"=GV) set.ignore.stderrOption(ois) #> [1] TRUE @@ -330,7 +244,7 @@

Examples

-

Site built with pkgdown 2.0.7.

+

Site built with pkgdown 2.0.9.

diff --git a/docs/reference/readVECT.html b/docs/reference/readVECT.html index 01e5778..448f071 100644 --- a/docs/reference/readVECT.html +++ b/docs/reference/readVECT.html @@ -1,5 +1,5 @@ -Read and write GRASS vector object files — readVECT • rgrassRead and write GRASS vector object files — readVECT • rgrass @@ -66,9 +66,10 @@

Read and write GRASS vector object files

-
read_VECT(vname, layer, type=NULL, flags="overwrite",
-    ignore.stderr = NULL)
-write_VECT(x, vname, flags="overwrite", ignore.stderr = NULL)
+    
read_VECT(vname, layer = "", proxy = FALSE, use_gdal_grass_driver = TRUE, type = NULL,
+    flags = "overwrite", Sys_ignore.stdout = FALSE,
+    ignore.stderr = get.ignore.stderrOption())
+write_VECT(x, vname, flags = "overwrite", ignore.stderr = get.ignore.stderrOption())
 vInfo(vname, layer, ignore.stderr = NULL)
 vColumns(vname, layer, ignore.stderr = NULL)
 vDataCount(vname, layer, ignore.stderr = NULL)
@@ -82,11 +83,20 @@ 

Arguments

A GRASS vector file name

layer
-

a layer name (string); if missing set to default of “1”

+

a layer name (string); if missing the first layer will be used

+ +
proxy
+

Default is FALSE. Set as TRUE if you need a SpatVectorProxy object.

+ +
use_gdal_grass_driver
+

Default TRUE. The standalone GDAL-GRASS driver for the vector format will be used if it is installed. The advantage is that no intermediate file needs to be written from GRASS GIS and subsequently read into R; instead the vector layer is read directly from the GRASS GIS database. Please read the Note further below!

type

override type detection when multiple types are non-zero, passed to v.out.ogr

+
Sys_ignore.stdout
+

Passed to system.

+
ignore.stderr

default the value set by set.ignore.stderrOption; NULL, taking the value set by set.ignore.stderrOption, can be set to TRUE to silence system() output to standard error; does not apply on Windows platforms

@@ -112,10 +122,14 @@

Arguments

Value

-

read_VECT imports a GRASS vector object into a "SpatVector" object.

+

read_VECT imports a GRASS vector layer into a SpatVector or SpatVectorProxy object.

vect2neigh returns a data frame object with left and right neighbours and boundary lengths, also given class GRASSneigh and spatial.neighbour (as used in spdep). The incantation to retrieve the neighbours list is sn2listw(vect2neigh())$neighbours, and to retrieve the boundary lengths: sn2listw(vect2neigh())$weights. The GRASSneigh object has two other useful attributes: external is a vector giving the length of shared boundary between each polygon and the external area, and total giving each polygon's total boundary length.

+
+
+

Note

+

Be aware that the GDAL-GRASS driver may have some issues for vector data. In our experience, the error and warning messages for vector data can be ignored. Further, the returned metadata about the coordinate reference system may currently be incomplete, e.g. it may miss the EPSG code.

Author

@@ -126,274 +140,64 @@

Author

Examples

run <- FALSE
 if (nchar(Sys.getenv("GISRC")) > 0 &&
-  read.dcf(Sys.getenv("GISRC"))[1,"LOCATION_NAME"] == "nc_basic_spm_grass7") run <- TRUE
+    read.dcf(Sys.getenv("GISRC"))[1,"LOCATION_NAME"] == "nc_basic_spm_grass7") run <- TRUE
 GV <- Sys.getenv("GRASS_VERBOSE")
 Sys.setenv("GRASS_VERBOSE"=0)
 ois <- get.ignore.stderrOption()
 set.ignore.stderrOption(TRUE)
 #> [1] FALSE
 if (run) {
+  meta <- gmeta()
+  location_path <- file.path(meta$GISDBASE, meta$LOCATION_NAME)
+  previous_mapset <- meta$MAPSET
+  example_mapset <- "RGRASS_EXAMPLES"
+  execGRASS("g.mapset", "c", mapset = example_mapset)
+}
+
+if (run) {
   execGRASS("v.info", map="schools", layer="1")
 }
-#>  +----------------------------------------------------------------------------+
-#>  | Name:            schools                                                   |
-#>  | Mapset:          PERMANENT                                                 |
-#>  | Location:        nc_basic_spm_grass7                                       |
-#>  | Database:        /home/rsb/topics/grassdata                                |
-#>  | Title:           Wake County schools (points map)                          |
-#>  | Map scale:       1:1                                                       |
-#>  | Name of creator: helena                                                    |
-#>  | Organization:    NC OneMap                                                 |
-#>  | Source date:     Tue Nov  7 19:34:09 2006                                  |
-#>  | Timestamp (first layer): none                                              |
-#>  |----------------------------------------------------------------------------|
-#>  | Map format:      native                                                    |
-#>  |----------------------------------------------------------------------------|
-#>  |   Type of map: vector (level: 2)                                           |
-#>  |                                                                            |
-#>  |   Number of points:       167             Number of centroids:  0          |
-#>  |   Number of lines:        0               Number of boundaries: 0          |
-#>  |   Number of areas:        0               Number of islands:    0          |
-#>  |                                                                            |
-#>  |   Map is 3D:              No                                               |
-#>  |   Number of dblinks:      1                                                |
-#>  |                                                                            |
-#>  |   Projection: Lambert Conformal Conic                                      |
-#>  |                                                                            |
-#>  |               N:   248159.84441077    S:   203559.01136227                 |
-#>  |               E:   671714.55110786    W:   619215.13388253                 |
-#>  |                                                                            |
-#>  |   Digitization threshold: 0                                                |
-#>  |   Comment:                                                                 |
-#>  |                                                                            |
-#>  +----------------------------------------------------------------------------+
-#> 
 if (run) {
   print(vInfo("schools"))
   schs <- read_VECT("schools")
   print(summary(schs))
 }
-#>      nodes     points      lines boundaries  centroids      areas    islands 
-#>          0        167          0          0          0          0          0 
-#> primitives      map3d 
-#>        167          0 
-#>       cat            TAG             NAMESHORT           NAMELONG        
-#>  Min.   :  1.0   Length:167         Length:167         Length:167        
-#>  1st Qu.: 42.5   Class :character   Class :character   Class :character  
-#>  Median : 84.0   Mode  :character   Mode  :character   Mode  :character  
-#>  Mean   : 84.0                                                           
-#>  3rd Qu.:125.5                                                           
-#>  Max.   :167.0                                                           
-#>                                                                          
-#>    CORECAPACI       MOBILEUNIT       MOBILECAPA      GLEVEL         
-#>  Min.   :   0.0   Min.   : 0.000   Min.   :0.00   Length:167        
-#>  1st Qu.: 498.5   1st Qu.: 0.000   1st Qu.:0.75   Class :character  
-#>  Median : 586.0   Median : 6.000   Median :1.50   Mode  :character  
-#>  Mean   : 763.7   Mean   : 7.318   Mean   :1.75                     
-#>  3rd Qu.: 903.0   3rd Qu.:11.000   3rd Qu.:2.50                     
-#>  Max.   :2294.0   Max.   :49.000   Max.   :4.00                     
-#>  NA's   :23       NA's   :19       NA's   :163                      
-#>    LOGRADE            HIGRADE            CALENDAR           HASBASE         
-#>  Length:167         Length:167         Length:167         Length:167        
-#>  Class :character   Class :character   Class :character   Class :character  
-#>  Mode  :character   Mode  :character   Mode  :character   Mode  :character  
-#>                                                                             
-#>                                                                             
-#>                                                                             
-#>                                                                             
-#>    ISMAGNET            PHONE            ADDRNUMBER         ADDRPREFIX       
-#>  Length:167         Length:167         Length:167         Length:167        
-#>  Class :character   Class :character   Class :character   Class :character  
-#>  Mode  :character   Mode  :character   Mode  :character   Mode  :character  
-#>                                                                             
-#>                                                                             
-#>                                                                             
-#>                                                                             
-#>    ADDRROOT           ADDRTYPE          ADDRSUFFIX          ADDRCITY        
-#>  Length:167         Length:167         Length:167         Length:167        
-#>  Class :character   Class :character   Class :character   Class :character  
-#>  Mode  :character   Mode  :character   Mode  :character   Mode  :character  
-#>                                                                             
-#>                                                                             
-#>                                                                             
-#>                                                                             
-#>   ADDRZIPCOD             SPED        STATUS             NODEID         
-#>  Length:167         Min.   : NA   Length:167         Length:167        
-#>  Class :character   1st Qu.: NA   Class :character   Class :character  
-#>  Mode  :character   Median : NA   Mode  :character   Mode  :character  
-#>                     Mean   :NaN                                        
-#>                     3rd Qu.: NA                                        
-#>                     Max.   : NA                                        
-#>                     NA's   :167                                        
-#>    CAPACITYTO         ESL             BOARDDIS2            PROJ_CAP     
-#>  Min.   :   0.0   Length:167         Length:167         Min.   :   0.0  
-#>  1st Qu.: 543.0   Class :character   Class :character   1st Qu.: 497.0  
-#>  Median : 761.0   Mode  :character   Mode  :character   Median : 722.0  
-#>  Mean   : 867.0                                         Mean   : 793.1  
-#>  3rd Qu.: 992.5                                         3rd Qu.: 975.0  
-#>  Max.   :2294.0                                         Max.   :2390.0  
-#>  NA's   :20                                             NA's   :2       
-#>     NOTES          
-#>  Length:167        
-#>  Class :character  
-#>  Mode  :character  
-#>                    
-#>                    
-#>                    
-#>                    
+if (run) {
+  try({
+    write_VECT(schs, "newsch", flags=c("o", "overwrite"))
+  })
+  schs <- read_VECT("schools", use_gdal_grass_driver = FALSE)
+}
 if (run) {
   write_VECT(schs, "newsch", flags=c("o", "overwrite"))
   execGRASS("v.info", map="newsch", layer="1")
 }
-#> Warning: GDAL Message 6: dataset /tmp/grass8-rsb-948300/RtmpxWgOQS/filee80636e0032e0.gpkg does not support layer creation option ENCODING
-#>  +----------------------------------------------------------------------------+
-#>  | Name:            newsch                                                    |
-#>  | Mapset:          rsb                                                       |
-#>  | Location:        nc_basic_spm_grass7                                       |
-#>  | Database:        /home/rsb/topics/grassdata                                |
-#>  | Title:                                                                     |
-#>  | Map scale:       1:1                                                       |
-#>  | Name of creator: rsb                                                       |
-#>  | Organization:                                                              |
-#>  | Source date:     Mon Mar 25 17:19:30 2024                                  |
-#>  | Timestamp (first layer): none                                              |
-#>  |----------------------------------------------------------------------------|
-#>  | Map format:      native                                                    |
-#>  |----------------------------------------------------------------------------|
-#>  |   Type of map: vector (level: 2)                                           |
-#>  |                                                                            |
-#>  |   Number of points:       167             Number of centroids:  0          |
-#>  |   Number of lines:        0               Number of boundaries: 0          |
-#>  |   Number of areas:        0               Number of islands:    0          |
-#>  |                                                                            |
-#>  |   Map is 3D:              No                                               |
-#>  |   Number of dblinks:      1                                                |
-#>  |                                                                            |
-#>  |   Projection: Lambert Conformal Conic                                      |
-#>  |                                                                            |
-#>  |               N:   248159.84441077    S:   203559.01136227                 |
-#>  |               E:   671714.55110786    W:   619215.13388253                 |
-#>  |                                                                            |
-#>  |   Digitization threshold: 0                                                |
-#>  |   Comment:                                                                 |
-#>  |                                                                            |
-#>  +----------------------------------------------------------------------------+
-#> 
 if (run) {
   nschs <- read_VECT("newsch")
   print(summary(nschs))
 }
-#>       cat             cat_           TAG             NAMESHORT        
-#>  Min.   :  1.0   Min.   :  1.0   Length:167         Length:167        
-#>  1st Qu.: 42.5   1st Qu.: 42.5   Class :character   Class :character  
-#>  Median : 84.0   Median : 84.0   Mode  :character   Mode  :character  
-#>  Mean   : 84.0   Mean   : 84.0                                        
-#>  3rd Qu.:125.5   3rd Qu.:125.5                                        
-#>  Max.   :167.0   Max.   :167.0                                        
-#>                                                                       
-#>    NAMELONG           CORECAPACI       MOBILEUNIT       MOBILECAPA  
-#>  Length:167         Min.   :   0.0   Min.   : 0.000   Min.   :0.00  
-#>  Class :character   1st Qu.: 498.5   1st Qu.: 0.000   1st Qu.:0.75  
-#>  Mode  :character   Median : 586.0   Median : 6.000   Median :1.50  
-#>                     Mean   : 763.7   Mean   : 7.318   Mean   :1.75  
-#>                     3rd Qu.: 903.0   3rd Qu.:11.000   3rd Qu.:2.50  
-#>                     Max.   :2294.0   Max.   :49.000   Max.   :4.00  
-#>                     NA's   :23       NA's   :19       NA's   :163   
-#>     GLEVEL            LOGRADE            HIGRADE            CALENDAR        
-#>  Length:167         Length:167         Length:167         Length:167        
-#>  Class :character   Class :character   Class :character   Class :character  
-#>  Mode  :character   Mode  :character   Mode  :character   Mode  :character  
-#>                                                                             
-#>                                                                             
-#>                                                                             
-#>                                                                             
-#>    HASBASE            ISMAGNET            PHONE            ADDRNUMBER       
-#>  Length:167         Length:167         Length:167         Length:167        
-#>  Class :character   Class :character   Class :character   Class :character  
-#>  Mode  :character   Mode  :character   Mode  :character   Mode  :character  
-#>                                                                             
-#>                                                                             
-#>                                                                             
-#>                                                                             
-#>   ADDRPREFIX          ADDRROOT           ADDRTYPE          ADDRSUFFIX       
-#>  Length:167         Length:167         Length:167         Length:167        
-#>  Class :character   Class :character   Class :character   Class :character  
-#>  Mode  :character   Mode  :character   Mode  :character   Mode  :character  
-#>                                                                             
-#>                                                                             
-#>                                                                             
-#>                                                                             
-#>    ADDRCITY          ADDRZIPCOD             SPED        STATUS         
-#>  Length:167         Length:167         Min.   : NA   Length:167        
-#>  Class :character   Class :character   1st Qu.: NA   Class :character  
-#>  Mode  :character   Mode  :character   Median : NA   Mode  :character  
-#>                                        Mean   :NaN                     
-#>                                        3rd Qu.: NA                     
-#>                                        Max.   : NA                     
-#>                                        NA's   :167                     
-#>     NODEID            CAPACITYTO         ESL             BOARDDIS2        
-#>  Length:167         Min.   :   0.0   Length:167         Length:167        
-#>  Class :character   1st Qu.: 543.0   Class :character   Class :character  
-#>  Mode  :character   Median : 761.0   Mode  :character   Mode  :character  
-#>                     Mean   : 867.0                                        
-#>                     3rd Qu.: 992.5                                        
-#>                     Max.   :2294.0                                        
-#>                     NA's   :20                                            
-#>     PROJ_CAP         NOTES          
-#>  Min.   :   0.0   Length:167        
-#>  1st Qu.: 497.0   Class :character  
-#>  Median : 722.0   Mode  :character  
-#>  Mean   : 793.1                     
-#>  3rd Qu.: 975.0                     
-#>  Max.   :2390.0                     
-#>  NA's   :2                          
 if (run) {
   print(all.equal(names(nschs), as.character(vColumns("newsch")[,2])))
 }
-#> [1] TRUE
 if (run) {
   print(vInfo("roadsmajor"))
 }
-#>      nodes     points      lines boundaries  centroids      areas    islands 
-#>        266          0        355          0          0          0          0 
-#> primitives      map3d 
-#>        355          0 
 if (run) {
   roads <- read_VECT("roadsmajor")
   print(summary(roads))
 }
-#>       cat          MAJORRDS_      ROAD_NAME          MULTILANE        
-#>  Min.   :  1.0   Min.   :  1.0   Length:355         Length:355        
-#>  1st Qu.: 89.5   1st Qu.: 91.5   Class :character   Class :character  
-#>  Median :178.0   Median :180.0   Mode  :character   Mode  :character  
-#>  Mean   :178.0   Mean   :179.8                                        
-#>  3rd Qu.:266.5   3rd Qu.:268.5                                        
-#>  Max.   :355.0   Max.   :357.0                                        
-#>     PROPYEAR         OBJECTID       SHAPE_LEN       
-#>  Min.   :   0.0   Min.   :  1.0   Min.   :   20.36  
-#>  1st Qu.:   0.0   1st Qu.: 89.5   1st Qu.:  763.32  
-#>  Median :   0.0   Median :178.0   Median : 1601.23  
-#>  Mean   : 192.7   Mean   :178.0   Mean   : 4934.15  
-#>  3rd Qu.:   0.0   3rd Qu.:266.5   3rd Qu.: 9555.59  
-#>  Max.   :2025.0   Max.   :355.0   Max.   :64177.26  
-if (run) {
+if (FALSE) {
+  # not run: vect2neigh() currently writes 3 new data sources in the PERMANENT
+  # mapset, despite this mapset not being the active one.
   cen_neig <- vect2neigh("census")
   str(cen_neig)
 }
-#> WARNING: Values in column <cat> will be overwritten
-#> WARNING: Values in column <left> will be overwritten
-#> WARNING: Values in column <right> will be overwritten
-#> WARNING: Values in column <length> will be overwritten
-#> Classes ‘GRASSneigh’, ‘spatial.neighbour’ and 'data.frame':	12128 obs. of  3 variables:
-#>  $ left  : int  1 1 1 1 2 2 2 2 2 3 ...
-#>  $ right : int  2 18 176 177 1 3 20 176 182 2 ...
-#>  $ length: num  0.2814 0.1166 0.0849 0.2747 0.2814 ...
-#>  - attr(*, "external")= num [1:2537] 0 0 0 0 0.239 ...
-#>  - attr(*, "total")= Named num [1:2537] 0.7577 0.9377 0.753 0.0995 1.7322 ...
-#>   ..- attr(*, "names")= chr [1:2537] "1" "2" "3" "4" ...
-#>  - attr(*, "n")= int 2537
 if (run) {
   execGRASS("g.remove", flags="f", name=c("newsch", "newsch1"), type="vector")
+  execGRASS("g.mapset", mapset = previous_mapset)
+  if (example_mapset != previous_mapset) {
+    unlink(file.path(location_path, example_mapset), recursive = TRUE)
+  }
 }
 Sys.setenv("GRASS_VERBOSE"=GV)
 set.ignore.stderrOption(ois)
@@ -412,7 +216,7 @@ 

Examples

-

Site built with pkgdown 2.0.7.

+

Site built with pkgdown 2.0.9.

diff --git a/docs/reference/rgrass.html b/docs/reference/rgrass.html index 371bcaa..9f0843f 100644 --- a/docs/reference/rgrass.html +++ b/docs/reference/rgrass.html @@ -1,5 +1,5 @@ -Interface between GRASS geographical information system and R — rgrass-package • rgrassInterface between GRASS geographical information system and R — rgrass-package • rgrass