Skip to content

Commit

Permalink
sync v241
Browse files Browse the repository at this point in the history
  • Loading branch information
dpavlushko committed Jul 9, 2020
1 parent 62e4e1b commit 214d86d
Show file tree
Hide file tree
Showing 17 changed files with 50 additions and 26 deletions.
4 changes: 2 additions & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: arcgisbinding
Version: 1.0.1.239
Date: 2020-01-16
Version: 1.0.1.241
Date: 2020-07-01
Title: Bindings for ArcGIS
Author: Esri
Maintainer: Esri <[email protected]>
Expand Down
4 changes: 2 additions & 2 deletions DESCRIPTION.in
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: arcgisbinding
Version: 1.0.1.239
Date: 2020-01-16
Version: 1.0.1.241
Date: 2020-07-01
Title: Bindings for ArcGIS
Author: Esri
Maintainer: Esri <[email protected]>
Expand Down
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,8 @@ export(repr_html.leaflet)
#leaflet
export(pointData.arc.data)
export(polygonData.arc.data)
S3method(leaflet::pointData, arc.data, pointData.arc.data)
S3method(leaflet::polygonData, arc.data, polygonData.arc.data)

#dplyr methods as S3 methods
export(arrange.arc.data)
Expand Down
21 changes: 14 additions & 7 deletions R/arc.data2sf.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
#arc.data2sf.default <- function(x) stop()
# Convert an arc.dataframe object to an sf Simple Feature object
#' @export
arc.data2sf <- function (x)
arc.data2sf <- function (x, ...)
{
stopifnot(inherits(x, "arc.data"))

Expand All @@ -15,25 +15,32 @@ arc.data2sf <- function (x)
stopifnot(!is.null(shape))
info <- arc.shapeinfo(shape)
stopifnot(!is.null(info))

crs <- list(...)$crs
if (is.null(crs))
crs <- arc.fromWktToP4(info$WKT)

if (info$type == "-Point") #alternative
{
d2<-data.frame(df, "Shape.."=shape)
coords<-paste0("Shape...", names(shape))
#dim<-toupper(paste(names(shape), collapse=""))
dim<-.shapeinfo_dim(info)
sf::st_as_sf(d2,coords=coords, dim=dim, crs=arc.fromWktToP4(info$WKT))
sf::st_as_sf(d2,coords=coords, dim=dim, crs=crs)
}
sf::st_sf(df, geom=arc.shape2sf(shape))
sf::st_sf(df, geom=arc.shape2sf(shape, crs=crs))
}

# Convert Esri shape to sfc simple feature geometry
#' @export
arc.shape2sf <- function (shape)
arc.shape2sf <- function (shape, ...)
{
stopifnot(inherits(shape, "arc.shape"))
info <- arc.shapeinfo(shape)
#if (missing(wkt))
wkt <- info$WKT

crs <- list(...)$crs
if (is.null(crs))
crs <- arc.fromWktToP4(info$WKT)

t <- .shapeinfo_dim(info)

Expand All @@ -56,7 +63,7 @@ arc.shape2sf <- function (shape)
}
else
lapply(shape[[1]], function(sh) .shp2sfg(sh, info$type, t))
return(sf::st_sfc(sfgs, crs = arc.fromWktToP4(wkt)))
return(sf::st_sfc(sfgs, crs = crs))
}

#create 'sfg' object from Esri shape buffer
Expand Down
24 changes: 18 additions & 6 deletions R/arc.data2sp.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
# Convert an arc.dataframe or arc.raster object to an sp SpatialDataFrame object
#' @export
arc.data2sp <- function(x)
arc.data2sp <- function(x, ...)
{
if (!requireNamespace("sp", quietly = TRUE))
stop("This function requires the sp package.")
Expand All @@ -24,7 +24,12 @@ arc.data2sp <- function(x)
shp <- arc.shape(x)
}

spl <- arc.shape2sp(shape = shp, wkt = info$WKT)
crs <- list(...)$crs
if (is.null(crs))
spl <- arc.shape2sp(shape = shp, wkt = info$WKT)
else
spl <- arc.shape2sp(shape = shp, crs = crs)

class(x) <- setdiff(class(x), "arc.data")
attr(x, "shape") <- NULL

Expand Down Expand Up @@ -54,14 +59,21 @@ arc.data2sp <- function(x)

# Convert Esri shape to sp spatial geometry
#' @export
arc.shape2sp <- function(shape, wkt)
arc.shape2sp <- function(shape, ...)
{
if (!requireNamespace("sp", quietly = TRUE))
stop("This function requires the sp package.")
info <- arc.shapeinfo(shape)
if (missing(wkt))
wkt = info$WKT
p4 <- sp::CRS(arc.fromWktToP4(wkt))

args <- list(...)
if (!is.null(args$crs))
crs <- args$crs
else if (!is.null(args$wkt))
crs <- arc.fromWktToP4(args$wkt)
else
crs <- arc.fromWktToP4(info$WKT)

p4 <- sp::CRS(crs)
parts <- function(x) lapply(seq_along(x), function(i) .shp2sp(x[[i]], i, info$type))

switch(info$type,
Expand Down
4 changes: 2 additions & 2 deletions R/arc.dataset.feature.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ setIs("arc.dataset", "arc.feature",
coerce = function(from) new("arc.feature_impl", from),
replace = function(obj, value) value)

.write_feature <- function(path, data, coords, shape_info, overwrite, simplify=FALSE)
.write_feature <- function(path, data, coords, shape_info, overwrite, validate=FALSE)
{
if(missing(data) && missing(coords))
stop("arc.write() - 'coords' and 'data' are missing", call. = FALSE)
Expand Down Expand Up @@ -113,6 +113,6 @@ setIs("arc.dataset", "arc.feature",
}
else stop(paste("unsupported 'data' type:", class(data)) , call. = FALSE)
}
.call_proxy("arc_write", path, pairlist(data=data, coords=coords, shape_info=shape_info, overwrite=overwrite, simplify=simplify))
.call_proxy("arc_write", path, pairlist(data=data, coords=coords, shape_info=shape_info, overwrite=overwrite, simplify=validate))
return (invisible(TRUE))
}
2 changes: 2 additions & 0 deletions R/arc.shapeinfo.R
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,8 @@ setMethod("arc.shapeinfo", "arc.shape", function(object) object@shapeinfo)
#arc.shapeinfo.arc.feature <- function(object) object@shapeinfo
setMethod("arc.shapeinfo", "arc.feature", function(object) object@shapeinfo)

setMethod("arc.shapeinfo", "arc.data", function(object) arc.shape(object)@shapeinfo)

#arc.shapeinfo.Spatial <- function(x) .get_shape_info_from_sp(x)

#setMethod("show", "arc.shapeinfo", function(object)
Expand Down
4 changes: 2 additions & 2 deletions R/notebook-helpers.R
Original file line number Diff line number Diff line change
Expand Up @@ -36,9 +36,9 @@ repr_html.leaflet <- function(obj, ...)
if (is.null(obj$elementId))
stop("$elementId == NULL. Required property $elementId.")

dir_maps <-'~/../.ipython/nbextensions/maps'
dir_maps <-normalizePath('~/../.ipython/nbextensions/maps', mustWork = FALSE)
libdir <- 'mlib'
dir.create(dir_maps, showWarnings = FALSE, recursive = FALSE, mode = "0777")
dir.create(dir_maps, showWarnings = FALSE, recursive = TRUE, mode = "0777")
#oldwd <- setwd(dir_maps); on.exit(setwd(oldwd), add = TRUE)

name<-paste0(obj$elementId, '.html')
Expand Down
Binary file modified inst/doc/arcgisbinding.pdf
Binary file not shown.
Binary file modified libs/Win32/libobjects.dll
Binary file not shown.
Binary file modified libs/Win32/rarcproxy.dll
Binary file not shown.
Binary file modified libs/x64/libobjects.dll
Binary file not shown.
Binary file modified libs/x64/libobjects_pro.dll
Binary file not shown.
Binary file modified libs/x64/rarcproxy.dll
Binary file not shown.
Binary file modified libs/x64/rarcproxy_pro.dll
Binary file not shown.
5 changes: 3 additions & 2 deletions man/arc.data2sp-sf.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,12 @@
\title{
Convert 'arc.data' or 'arc.raster' object to 'sp' - SpatialDataFrame object or 'sf' - Simple Feature object}
\usage{
arc.data2sp(x)
arc.data2sf(x)
arc.data2sp(x, \dots)
arc.data2sf(x, \dots)
}
\arguments{
\item{x}{\code{\link{arc.data}} object, result of \code{\link{arc.select}} or \code{\link{arc.raster}}. }
\item{\dots}{ optional additional argument such \code{crs} coordinate reference string to assign to return object}
}
\value{
sp::Spatial*DataFrame object.
Expand Down
6 changes: 3 additions & 3 deletions man/arc.shape2sp-sf.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -3,12 +3,12 @@
\alias{arc.shape2sf}
\title{Convert 'arc.shape' geometry object to sp::Spatial* - Spatial geometry or sf::sfc - simple feature geometry}
\usage{
arc.shape2sp(shape, wkt)
arc.shape2sf(shape)
arc.shape2sp(shape, \dots)
arc.shape2sf(shape, \dots)
}
\arguments{
\item{shape}{\code{\link{arc.shape-class}}}
\item{wkt}{optional, WKT spatial reference}
\item{\dots}{optional \code{wkt} WKT spatial reference or \code{crs} spatial reference string to assigne to return object}
}

\value{
Expand Down

0 comments on commit 214d86d

Please sign in to comment.