Skip to content

Commit

Permalink
draft bi-variate moran plot
Browse files Browse the repository at this point in the history
  • Loading branch information
rsbivand committed Jun 5, 2024
1 parent 0152f72 commit 895c520
Show file tree
Hide file tree
Showing 3 changed files with 27 additions and 6 deletions.
27 changes: 23 additions & 4 deletions R/moran.plot.R
Original file line number Diff line number Diff line change
@@ -1,13 +1,14 @@
# Copyright 2001 by Roger Bivand
# Copyright 2001-24 by Roger Bivand
#

moran.plot <- function(x, listw, zero.policy=attr(listw, "zero.policy"), spChk=NULL,
moran.plot <- function(x, listw, y=NULL, zero.policy=attr(listw, "zero.policy"), spChk=NULL,
labels=NULL, xlab=NULL, ylab=NULL, quiet=NULL, plot=TRUE, return_df=TRUE, ...)
{
if (!inherits(listw, "listw")) stop(paste(deparse(substitute(listw)),
"is not a listw object"))
if (is.null(quiet)) quiet <- !get("verbose", envir = .spdepOptions)
stopifnot(is.vector(x))
if (!is.null(y)) stopifnot(is.vector(y))
stopifnot(is.logical(quiet))
if (is.null(zero.policy))
zero.policy <- get("zeroPolicy", envir = .spdepOptions)
Expand All @@ -20,14 +21,32 @@ moran.plot <- function(x, listw, zero.policy=attr(listw, "zero.policy"), spChk=N
if (is.null(spChk)) spChk <- get.spChkOption()
if (spChk && !chkIDs(x, listw))
stop("Check of data and weights ID integrity failed")
if (!is.null(y)) {
yname <- deparse(substitute(y))
if (!is.numeric(y)) stop(paste(yname, "is not a numeric vector"))
if (any(is.na(y))) stop("NA in Y")
if (n != length(y)) stop("objects of different length")
if (spChk && !chkIDs(y, listw))
stop("Check of data and weights ID integrity failed")
}
labs <- TRUE
if (is.logical(labels) && !labels) labs <- FALSE
if (is.null(labels) || length(labels) != n)
labels <- as.character(attr(listw, "region.id"))
wx <- lag.listw(listw, x, zero.policy=zero.policy)
if (!is.null(y)) {
wx <- lag.listw(listw, y, zero.policy=zero.policy)
} else {
wx <- lag.listw(listw, x, zero.policy=zero.policy)
}
if (anyNA(wx)) warning("no-neighbour observation(s) in moran.plot() - use zero.policy=TRUE")
if (is.null(xlab)) xlab <- xname
if (is.null(ylab)) ylab <- paste("spatially lagged", xname)
if (is.null(ylab)) {
if (!is.null(y)) {
ylab <- paste("spatially lagged", yname)
} else {
ylab <- paste("spatially lagged", xname)
}
}
if (plot) plot(x, wx, xlab=xlab, ylab=ylab, ...)
if (plot && zero.policy) {
n0 <- wx == 0.0
Expand Down
1 change: 1 addition & 0 deletions man/localmoran_bv.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@ columbus$hs <- hotspot(res, Prname="Pr(folded) Sim", cutoff=0.05,
if (require("tmap", quietly=TRUE)) {
tm_shape(columbus) + tm_fill("hs")
}
moran.plot(x=columbus$CRIME, y=columbus$INC, listw=listw)
}
\references{
Anselin, Luc, Ibnu Syabri, and Oleg Smirnov. 2002.Visualizing Multivariate Spatial Correlation with Dynamically Linked Windows.In New Tools for Spatial Data Analysis: Proceedings of the Specialist Meeting, edited by Luc Anselin and Sergio Rey. University of California, Santa Barbara: Center for Spatially Integrated Social Science (CSISS).
Expand Down
5 changes: 3 additions & 2 deletions man/moran.plot.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -8,12 +8,13 @@ between the data and the lag. If zero policy is TRUE, such observations
are also marked if they occur.
}
\usage{
moran.plot(x, listw, zero.policy=attr(listw, "zero.policy"), spChk=NULL, labels=NULL,
xlab=NULL, ylab=NULL, quiet=NULL, plot=TRUE, return_df=TRUE, ...)
moran.plot(x, listw, y=NULL, zero.policy=attr(listw, "zero.policy"), spChk=NULL,
labels=NULL, xlab=NULL, ylab=NULL, quiet=NULL, plot=TRUE, return_df=TRUE, ...)
}
\arguments{
\item{x}{a numeric vector the same length as the neighbours list in listw}
\item{listw}{a \code{listw} object created for example by \code{nb2listw}}
\item{y}{an optional numeric vector the same length as the neighbours list in listw for a bi-variate plot}
\item{zero.policy}{default \code{attr(listw, "zero.policy")} as set when \code{listw} was created, if attribute not set, use global option value; if TRUE assign zero to the lagged value of zones without neighbours, if FALSE assign NA}
\item{spChk}{should the data vector names be checked against the spatial objects for identity integrity, TRUE, or FALSE, default NULL to use \code{get.spChkOption()}}
\item{labels}{character labels for points with high influence measures, if set to FALSE, no labels are plotted for points with large influence}
Expand Down

0 comments on commit 895c520

Please sign in to comment.