You are viewing a plain text version of this content. The canonical link for it is here.
Posted to commits@sedona.apache.org by ji...@apache.org on 2023/03/05 05:46:21 UTC

[sedona] branch master updated: [SEDONA-254] R – Add tests for RasterUDT (#785)

This is an automated email from the ASF dual-hosted git repository.

jiayu pushed a commit to branch master
in repository https://gitbox.apache.org/repos/asf/sedona.git


The following commit(s) were added to refs/heads/master by this push:
     new 097efb66 [SEDONA-254] R – Add tests for RasterUDT (#785)
097efb66 is described below

commit 097efb66875f60fc75df30ca5a3d63a7b0dd5db7
Author: gregleleu <33...@users.noreply.github.com>
AuthorDate: Sun Mar 5 00:46:15 2023 -0500

    [SEDONA-254] R – Add tests for RasterUDT (#785)
---
 R/tests/testthat/test-data-interface-raster.R | 195 +++++++++++++++++++++++++-
 1 file changed, 190 insertions(+), 5 deletions(-)

diff --git a/R/tests/testthat/test-data-interface-raster.R b/R/tests/testthat/test-data-interface-raster.R
index 3442efd8..35f0ffb7 100644
--- a/R/tests/testthat/test-data-interface-raster.R
+++ b/R/tests/testthat/test-data-interface-raster.R
@@ -302,7 +302,7 @@ test_that("Should Pass geotiff file writing with coalesce", {
   ## Load
   sdf_name <- random_string("spatial_sdf")
   geotiff_sdf <- spark_read_geotiff(sc, path = test_data("raster/"), name = sdf_name, options = list(dropInvalid = TRUE, readToCRS = "EPSG:4326"))
-
+  
   ## Write
   tmp_dest <- tempfile()
   
@@ -312,12 +312,12 @@ test_that("Should Pass geotiff file writing with coalesce", {
   geotiff_df %>% 
     sdf_coalesce(1L) %>% 
     spark_write_geotiff(path = tmp_dest)
- 
+  
   ## not clear what the issue is here
   for (file in dir(path = tmp_dest, full.names = TRUE)) load_path <- path.expand(file)
   
   geotiff_2_sdf <- spark_read_geotiff(sc, path = load_path, options = list(dropInvalid = TRUE))
-
+  
   row <- sc %>% 
     DBI::dbGetQuery("SELECT 
              image.geometry as Geom, 
@@ -438,7 +438,7 @@ test_that("Should Pass geotiff file writing with nested schema", {
   
   ## Write
   tmp_dest <- tempfile()
-
+  
   geotiff_sdf %>% 
     spark_write_geotiff(path = tmp_dest)
   
@@ -473,7 +473,7 @@ test_that("Should Pass geotiff file writing with renamed fields", {
                           fieldOrigin   = "source",
                           fieldGeometry = "geom",
                           fieldNBands   = "bands"
-                          ))
+                        ))
   
   
   ## Count created files
@@ -579,4 +579,189 @@ test_that("Should Pass geotiff file writing with handling invalid schema", {
 })
 
 
+# Binary and RS_functions  -----------------
+# Only functions related to reading
+
+test_that("Passed RS_FromGeoTiff from binary", {
+  ## Load
+  sdf_name <- random_string("spatial_sdf")
+  binary_sdf <- spark_read_binary(sc, dir = test_data("raster/test1.tiff"), name = sdf_name)
+  
+  raster_sdf <- 
+    binary_sdf %>% 
+    mutate(raster = RS_FromGeoTiff(content))
+  
+  expect_equal(
+    raster_sdf %>% sdf_schema() ,
+    list(
+      path             = list(name = "path", type = "StringType"),
+      modificationTime = list(name = "modificationTime", type = "TimestampType"),
+      length           = list(name = "length", type = "LongType"),
+      content          = list(name = "content", type = "BinaryType"),
+      raster           = list(name = "raster", type = "RasterUDT"))
+  )
+  
+  a <- raster_sdf %>% head(1) %>%  collect()
+  expect_equal(
+    a$raster[[1]] %>% sparklyr::invoke("getClass") %>% sparklyr::invoke("getSimpleName"),
+    "GridCoverage2D"
+  )
+  
+  ## Cleanup
+  sc %>% DBI::dbExecute(paste0("DROP TABLE ", sdf_name))
+  # sc %>% DBI::dbExecute(paste0("DROP TABLE ", dbplyr::remote_name(raster_sdf)))
+  rm(a)
+  
+})
+
+test_that("Passed RS_FromArcInfoAsciiGrid from binary", {
+  ## Load
+  sdf_name <- random_string("spatial_sdf")
+  binary_sdf <- spark_read_binary(sc, dir = test_data("raster_asc/test1.asc"), name = sdf_name)
+  
+  raster_sdf <- 
+    binary_sdf %>% 
+    mutate(raster = RS_FromArcInfoAsciiGrid(content))
+  
+  expect_equal(
+    raster_sdf %>% sdf_schema() ,
+    list(
+      path             = list(name = "path", type = "StringType"),
+      modificationTime = list(name = "modificationTime", type = "TimestampType"),
+      length           = list(name = "length", type = "LongType"),
+      content          = list(name = "content", type = "BinaryType"),
+      raster           = list(name = "raster", type = "RasterUDT"))
+  )
+  
+  a <- raster_sdf %>% head(1) %>%  collect()
+  expect_equal(
+    a$raster[[1]] %>% sparklyr::invoke("getClass") %>% sparklyr::invoke("getSimpleName"),
+    "GridCoverage2D"
+  )
+  
+  ## Cleanup
+  sc %>% DBI::dbExecute(paste0("DROP TABLE ", sdf_name))
+  # sc %>% DBI::dbExecute(paste0("DROP TABLE ", dbplyr::remote_name(raster_sdf)))
+  rm(a)
+  
+})
+
+
+test_that("Passed RS_Envelope with raster", {
+  ## Load
+  sdf_name <- random_string("spatial_sdf")
+  binary_sdf <- spark_read_binary(sc, dir = test_data("raster/test1.tiff"), name = sdf_name)
+  
+  raster_sdf <- 
+    binary_sdf %>% 
+    mutate(
+      raster = RS_FromGeoTiff(content),
+      env = RS_Envelope(raster)
+    )
+  
+  expect_equal(
+    raster_sdf %>% sdf_schema() ,
+    list(
+      path             = list(name = "path", type = "StringType"),
+      modificationTime = list(name = "modificationTime", type = "TimestampType"),
+      length           = list(name = "length", type = "LongType"),
+      content          = list(name = "content", type = "BinaryType"),
+      raster           = list(name = "raster", type = "RasterUDT"),
+      env              = list(name = "env", type = "GeometryUDT")
+    )
+  )
+  
+  a <- 
+    raster_sdf %>% 
+    mutate(env = env %>% st_astext()) %>% 
+    select(env) %>% 
+    head(1) %>%  collect()
+  expect_equal(
+    a$env[1] %>% substr(1, 129),
+    "POLYGON ((-13095817.809482181 3983868.8560156375, -13095817.809482181 4021262.7487925636, -13058785.559768861 4021262.7487925636,"
+  )
+  
+  ## Cleanup
+  sc %>% DBI::dbExecute(paste0("DROP TABLE ", sdf_name))
+  # sc %>% DBI::dbExecute(paste0("DROP TABLE ", dbplyr::remote_name(raster_sdf)))
+  rm(a)
+})
+
+
+test_that("Passed RS_NumBands with raster", {
+  ## Load
+  sdf_name <- random_string("spatial_sdf")
+  binary_sdf <- spark_read_binary(sc, dir = test_data("raster"), name = sdf_name)
+  
+  a <-
+    binary_sdf %>% 
+    mutate(
+      raster = RS_FromGeoTiff(content),
+      nbands = RS_NumBands(raster)
+    ) %>% 
+    select(nbands) %>% 
+    collect()
+  
+  expect_equal(
+    a %>% as.list(),
+    list(nbands = c(1, 1, 4))
+    
+  )
+  
+  
+  ## Cleanup
+  sc %>% DBI::dbExecute(paste0("DROP TABLE ", sdf_name))
+  rm(a)
+})
 
+
+test_that("Passed RS_Value with raster", {
+  ## Load
+  sdf_name <- random_string("spatial_sdf")
+  binary_sdf <- spark_read_binary(sc, dir = test_data("raster/test1.tiff"), name = sdf_name)
+  
+  a <-
+    binary_sdf %>% 
+    mutate(
+      raster = RS_FromGeoTiff(content),
+      val = RS_Value(raster, ST_Point(-13077301.685, 4002565.802))
+    ) %>% 
+    select(val) %>% 
+    collect()
+  
+  expect_equal(
+    a %>% as.list(),
+    list(val = c(255))
+    
+  )
+  
+  
+  ## Cleanup
+  sc %>% DBI::dbExecute(paste0("DROP TABLE ", sdf_name))
+  rm(a)
+})
+
+test_that("Passed RS_Values with raster", {
+  ## Load
+  sdf_name <- random_string("spatial_sdf")
+  binary_sdf <- spark_read_binary(sc, dir = test_data("raster"), name = sdf_name)
+  
+  a <-
+    binary_sdf %>% 
+    mutate(
+      raster = RS_FromGeoTiff(content),
+      val = RS_Values(raster, array(ST_Point(-13077301.685, 4002565.802), NULL))
+    ) %>% 
+    select(val) %>%
+    collect()
+  
+  expect_equal(
+    a %>% as.list(),
+    list(val = list(c(255, NA_real_), c(255, NA_real_), c(NA_real_, NA_real_)))
+    
+  )
+  
+  ## Cleanup
+  sc %>% DBI::dbExecute(paste0("DROP TABLE ", sdf_name))
+  rm(a)
+})