Skip to content

Commit

Permalink
geocode cadastral function from ESmisc
Browse files Browse the repository at this point in the history
  • Loading branch information
verajosemanuel committed May 6, 2019
1 parent c70fa54 commit ce81abc
Show file tree
Hide file tree
Showing 2 changed files with 135 additions and 0 deletions.
45 changes: 45 additions & 0 deletions R/cadastral_references-data.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,45 @@
#' Cadastral references test data
#'
#' Randomly selected data from catastro to test geocode_cadastral function
#'
#' @docType data
#'
#' @usage data(cadastral_references)
#'
#' @format A data frame.
#'
#' @keywords datasets
#'
#' @references Catastro. Ministerio de Hacienda y función pública.
#' (\href{http://www.catastro.meh.es/}{Catastro})
#'
#' @source \href{http://www.catastro.meh.es/}{Sede Electrónica del Catastro}
#'
#' @examples
#' ## source is cadastral reference number ##
#'
#' geocode_cadastral("0636105UF3403N", parse_files = FALSE)
#'
#' ## Use lapply to geocode cadastral references from dataframe columns.
#'
#' cadastral_references$new <- lapply(cadastral_references$cadref1, geocode_cadastral)
#'
#' ## separate previously generated "new" data into columns usign tidyr
#'
#' library(tidyr)
#' separate(cadastral_references, new, into = c('longitude','latitude'), sep = "," )
#'
#' ## source is folder. A loop is needed to process each kml file ##
#'
#' \dontrun{
#' files <- list.files("folder", full.names = T)
#'
#' for (f in files) {
#' coords <- geocode_cadastral(f, parse_files = TRUE)
#' d <- as.data.frame(rbind(d , as.data.frame(coords, stringsAsFactors = F )))
#' }
#'
#'# separate lat/lon into columns if you prefer using tidyr
#' d <- tidyr::separate(coords, into = c("longitude","latitude"), sep = "," )
#'}
"cadastral_references"
90 changes: 90 additions & 0 deletions R/geocode_cadastral.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,90 @@
#' geocode by longitude and latitude from cadastral references.
#'
#' Get longitude/latitude from valid cadastral ref. or kml files from catastro.
#'
#' @keywords geocoding, latitude, longitude, cadastre, cadastral reference.
#' @param x A valid spanish cadastral reference.
#' @param parse_files bool. Default to FALSE. Set TRUE if source are KML files.
#' @return A string for longitude/latitude if found. NA if not found.
#' @section Warning: You may be banned if many requests in short time are made.
#' @export
#' @examples
#' ## source is cadastral reference number ##
#' \dontrun{
#' # geocode_cadastral("0636105UF3403N", parse_files = FALSE)
#'
#' ##"36.5209422288168,-4.89298751473745"
#'
#' ## Use lapply to geocode cadastral references from dataframe columns.
#'
#' cadastral_references$new <- lapply(cadastral_references$cadref1, geocode_cadastral)
#'
#' ## separate previously generated "new" data into columns usign tidyr
#'
#' # library(tidyr)
#' # separate(cadastral_references, new, into = c('longitude','latitude'), sep = "," )
#'
#' ## source is folder. A loop is needed to process each kml file ##
#'
#' # files <- list.files("folder", full.names = T)
#'
#' # for (f in files) {
#' # coords <- geocode_cadastral(f, parse_files = TRUE)
#' # d <- as.data.frame(rbind(d , as.data.frame(coords, stringsAsFactors = F )))
#' # }
#'
#'# separate lat/lon into columns if you prefer using tidyr
#' # d <- tidyr::separate(coords, into = c("longitude","latitude"), sep = "," )
#'}

utils::globalVariables(".")

geocode_cadastral <- function(x, parse_files) {

if (missing(parse_files)) {
parse_files <- FALSE
}

if (!requireNamespace("magrittr", quietly = TRUE)) {
stop("magrittr needed for this function to work. Please install it.",
call. = FALSE)
}

if (!requireNamespace("xml2", quietly = TRUE)) {
stop("xml2 needed for this function to work. Please install it.",
call. = FALSE)
}


if (parse_files) {

con <- file(x, "rb")

} else {

con <-
paste0(
"http://ovc.catastro.meh.es/Cartografia/WMS/BuscarParcelaGoogle.aspx?RefCat=",
x
)
Sys.sleep(2)

}

try(
coords <- xml2::read_xml(con) %>%
sub("kml xmlns", "kml xmlns:X", .) %>%
xml2::as_xml_document() %>%
xml2::xml_find_all("//Point/coordinates") %>%
xml2::xml_text() %>%
gsub('.{2}$', '', .),
silent = TRUE)

if (length(coords) == 0) coords <- NA

if (parse_files) close(con)

return(coords)

}

0 comments on commit ce81abc

Please sign in to comment.