Skip to content

Commit

Permalink
update readme
Browse files Browse the repository at this point in the history
  • Loading branch information
mikejohnson51 committed Dec 30, 2019
1 parent 0ee869d commit 85293e2
Show file tree
Hide file tree
Showing 42 changed files with 11,426 additions and 48 deletions.
65 changes: 65 additions & 0 deletions R/aoi_describe.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,65 @@
#' @title Describe an AOI
#' @description Describe a spatial (sf/sp/raster) object in terms of a reproducable AOI (e.g. \code{\link{aoi_get}}) parameters.
#' @param AOI a spatial object (\code{raster}, \code{sf}, \code{sp}).
#' @param full if TRUE, reverse geocoding descriptions returned, else just lat, lon, width, height, and origin (default = FALSE)
#' @param km if TRUE, units are in kilometers, else in miles (default = FALSE)
#' @return a data.frame of AOI descriptors including (at minimum):
#' \describe{
#' \item{lat}{the AOI center latitude }
#' \item{lon}{the AOI center longitude}
#' \item{height}{ height in (miles)}
#' \item{width}{width in(miles)}
#' \item{origin}{AOI origin}
#' }
#' @export
#' @examples
#' library(AOI)
#' aoi_get("UCSB") %>% aoi_describe()
#' aoi_get("UCSB") %>% aoi_describe(full = TRUE)
#' }

aoi_describe = function(AOI, full = FALSE, km = FALSE){

if(methods::is(AOI, 'raster')){ AOI = bbox_get(AOI)}

bb = st_transform(AOI, aoiProj) %>% bbox_coords()

latCent = (bb$ymin + bb$ymax) / 2

df = data.frame(
lat = latCent,
lon = (bb$xmin + bb$xmax) / 2,
height = round(69 * (abs(bb$ymax - bb$ymin)), 2),
width = round(69 * cos(latCent * pi/180) * abs(abs(bb$xmax) - abs(bb$xmin)), 2),
origin = "center",
units = "miles",
stringsAsFactors = F
)

if(km){
df$height = df$height / 1.609
df$width = df$width / 1.609
df$units = "kilometers"
}

if(full) {
rc = geocode_rev(x = c(df$lat, df$lon))
if (!is.null(rc$match_addr)) {
df[["name"]] = rc$match_addr
} else {
df[["name"]] = rc[1]
}

df[['area']] = df$height * df$width
}

rownames(df) = NULL

return(df)

}





92 changes: 92 additions & 0 deletions R/aoi_functions.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,92 @@
#' @title Buffer AOI
#' @description Add or subtract a uniform distance to/from a spatial object in either miles or kilometers.
#' @param AOI a spatial, raster or simple features object
#' @param d \code{numeric}.The distance by which to modify each edge
#' @param km \code{logical}. If \code{TRUE} distances are in kilometers, default is \code{FALSE} with distances in miles
#' @return a spatial geometry of the same class as the input AOI (if Raster sp returned)
#' @export
#' @examples
#' \dontrun{
#' # get an AOI of 'Garden of the Gods' and add a 2 mile buffer
#' AOI = aoi_get("Garden of the Gods") %>% modify(2)
#'
#' # get an AOI of 'Garden of the Gods' and add a 2 kilometer buffer
#' getAOI("Garden of the Gods") %>% modify(2, km = TRUE)
#'
#' # get and AOI for Colorado Springs and subtract 3 miles
#' getAOI("Colorado Springs") %>% modify(-3)
#' }

aoi_buffer = function(AOI, d, km = FALSE){

AOI = make_sf(AOI)

crs = st_crs(AOI)

if(km) { u = d * 3280.84} # kilometers to feet
if(!km) { u = d * 5280 } # miles to feet

st_transform(AOI, 6829) %>%
st_buffer(u, joinStyle = 'MITRE', endCapStyle = "SQUARE", mitreLimit = 2) %>%
st_transform(crs)
}

#' @title Is Inside
#' @description A check to see if one object is inside another
#' @param obj object 1
#' @param AOI object 2
#' @param total boolean. If \code{TRUE} then check if obj is competely inside the AOI.
#' If \code{FALSE}, then check if at least part of obj is in the AOI.
#' @return boolean value
#' @export
#' @author Mike Johnson
#' @examples
#' \dontrun{
#' AOI = getAOI(state = "CA")
#' obj = getAOI(state = "CA", county = "Santa Barbara")
#' is_inside(AOI, obj)
#'
#' AOI = getAOI(state = "CA")
#' obj = getAOI(state = "CO", county = "El Paso")
#' is_inside(AOI, obj)
#' }


aoi_inside = function(AOI, obj, total = T){

AOI = make_sf(AOI)
obj = make_sf(obj) %>% sf::st_transform(sf::st_crs(AOI))

int = suppressMessages( sf::st_intersects(obj, AOI) )

if (!apply(int, 1, any)) {
return(FALSE)
} else {
x = suppressWarnings(
suppressMessages( sf::st_intersection(obj, AOI) ))

inside = any(x$geometry == AOI$geometry, x$geometry == obj$geometry)

if (total) {
return(inside)
} else{
return(TRUE)
}
}
}

#' @title Convert raster and sp objects to sf
#' @description Convert raster and sp objects to sf
#' @param x any spatial object
#' @return an sf object
#' @keywords internal
#' @author Mike Johnson

make_sf = function(x){
if (methods::is(x, "raster")) { AOI = bbox_get(x) }
if (methods::is(x, "sp")) { AOI = st_as_sf(x) }
if (methods::is(x, "sf")) { AOI = st_as_sf(x) }
return(AOI)
}


146 changes: 146 additions & 0 deletions R/aoi_get.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,146 @@
#' @title Get Area of Interest (AOI) geometry
#' @description Generate a spatial geometry from:
#' \enumerate{
#' \item Country name, 2-digit or 3-digit ISO abbriviation(s)
#' \item US state name(s) or abbreviation
#' \item US state, county pair(s)
#' \item a spatial, sf or raster object
#' \item a clip unit (see details)
#' }
#' @param country \code{character}. Full name, ISO 3166-1 2 or 3 digit code. Not case senstive. Data comes from Natural Earth and CIA Worldfact book.
#' @param state \code{character}. Full name or two character abbriviation. Not case senstive. If \code{state = 'conus'}, the lower 48 states will be returned. If \code{state = 'all'}, all states will be returned.
#' @param county \code{character}. County name(s). Requires \code{state} input. Not case senstive. If 'all' then all counties in a state are returned
#' @param x \code{spatial}. \code{raster}, \code{sf} or a \code{list} object (see details for list parameters)
#' @param km \code{logical}. If \code{TRUE} distances are in kilometers, default is \code{FALSE} with distances in miles
#' @param union \code{logical}. If TRUE objects are unioned into a single object
#' @details A \code{clip} unit can be described by just a place name (eg 'UCSB'). In doing so the associated boundaries determined by \code{\link{geocode}} will be returned.
#' To have greater control over the clip unit it can be defined as a list with a minimum of 3 inputs:
#' \enumerate{
#' \item A point: \itemize{
#' \item 'place name' (\code{character}) ex: "UCSB" - or -
#' \item 'lat/lon' pair: ex: "-36, -120"
#' }
#' \item A bounding box height (\code{numeric}) \itemize{
#' \item{in miles} ex: 10
#' }
#' \item A bounding box width (\code{numeric})\itemize{
#' \item{in miles} ex: 10
#' }
#' }
#'
#' The bounding box is always drawn in relation to the point. By default the point is treated
#' as the center of the box. To define the realtive location of the point to the bounding box,
#' a fourth input can be used:
#' \enumerate{
#' \item Origin \itemize{
#' \item 'center' (default)
#' \item 'upperleft'
#' \item 'upperright'
#' \item 'lowerleft'
#' \item 'lowerright'
#' }
#' }
#' In total, 1 to 5 elements can be used to define \code{clip} element and \strong{ORDER MATTERS} (point, height, width, origin).
#' Acceptable variations include:
#' \itemize{
#' \item 1 member: (1) place name \itemize{
#' \item \emph{"UCSB"}}
#' \item 1 member: (1) lat/lon pair \itemize{
#' \item \emph{c(36, -119)}}
#' \item 3 members: (1) location name, (2) height, (3) width \itemize{
#' \item \emph{list("UCSB", 10, 10) }}
#' \item 4 members: (1) lat, (2) lon, (3) height, (4) width\itemize{
#' \item \emph{list(36, -120, 10, 10) }}
#' \item 4 members: (1) place name, (2) height, (3) width, (4) origin\itemize{
#' \item \emph{list("UCSB", 10, 10, "lowerright) }}
#' \item 5 members: (1) lat, (2) lon, (3) height, (4) width, (5) origin\itemize{
#' \item \emph{list(36,-120, 10, 10, "upperright) }}
#' }
#' @return a sf geometry projected to \emph{EPSG:4269}.
#' @export
#' @author Mike Johnson
#' @examples
#' \dontrun{
#' #Get AOI for a country
#' getAOI(country = "Brazil")
#'
#' # Get AOI for a location
#' getAOI("Sacramento")
#'
#' # Get AOI defined by a state(s)
#' getAOI(state = 'CA')
#' getAOI(state = c('CA', 'nevada'))
#'
#' # Get AOI defined by all states, or the lower 48
#' getAOI(state = 'all')
#' getAOI(state = 'conus')
#'
#' # Get AOI defined by state & county pair(s)
#' getAOI(state = 'California', county = 'Santa Barbara')
#' getAOI(state = 'CA', county = c('Santa Barbara', 'ventura'))
#'
#' # Get AOI defined by state & county pair(s)
#' getAOI(state = 'California', county = 'Santa Barbara')
#' getAOI(state = 'CA', county = c('Santa Barbara', 'ventura'))
#'
#' # Get AOI defined by state & all counties
#' getAOI(state = 'California', county = 'all')
#'
#' # Get AOI defined by external spatial file:
#' getAOI(sf::read_sf('./la_metro.shp'))
#' getAOI(raster('./AOI.tif'))
#'
#' # Get AOI defined by 10 mile bounding box using lat/lon
#' getAOI(clip = c(35, -119, 10, 10))
#'
#' # Get AOI defined by 10 mile2 bounding box using the 'KMART near UCSB' as lower left corner
#' getAOI(clip = list('KMART near UCSB', 10, 10, 'lowerleft'))
#'}
#'
#'

aoi_get = function(x = NULL, country = NULL, state = NULL, county = NULL,
km = FALSE, union = FALSE) {

# Error Catching

if (is.null(country)) {

if (!is.null(state)) {

if (!is.null(x)) { stop("Only 'state' or 'clip' can be used. Set the other to NULL") }

for (value in state) {

if (!is.character(value)) {stop("State must be a character value.")}

if (!(toupper(value) %in% c(state.abb, state.name, 'CONUS', 'ALL'))) {
stop("State not recongized. Full names or abbreviations can be used.")
}
}

} else {
if (!is.null(county)) { stop("The use of 'county' requires a 'state' parameter as well.")}
if ( is.null(x)) { stop("Requires a 'x' or 'state' parameter to execute.")}
}
}

methods::is(x, 'Raster')
# Fiat Boundary Defintion (Exisiting Spatial/Raster Feature or getFiat())

shp <- if (is.null(x)) {
getFiat(country = country, state = state, county = county)
} else if (any(
methods::is(x, 'Raster'),
methods::is(x, 'Spatial'),
methods::is(x, 'sf'))) {
st_transform(bbox_get(x), aoiProj)
} else {
getClip(x, km)
}

# Return AOI

if (union) { sf::st_union(shp) } else { shp }

}

0 comments on commit 85293e2

Please sign in to comment.