]> git.donarmstrong.com Git - xtable.git/commitdiff
Added extra methods for spatial econometrics provided by Martin Gubri
authordscott <dscott@edb9625f-4e0d-4859-8d74-9fd3b1da38cb>
Mon, 11 Jan 2016 05:06:34 +0000 (05:06 +0000)
committerdscott <dscott@edb9625f-4e0d-4859-8d74-9fd3b1da38cb>
Mon, 11 Jan 2016 05:06:34 +0000 (05:06 +0000)
git-svn-id: svn://scm.r-forge.r-project.org/svnroot/xtable@88 edb9625f-4e0d-4859-8d74-9fd3b1da38cb

pkg/NAMESPACE
pkg/R/xtable.R
pkg/man/xtable.Rd
pkg/vignettes/OtherPackagesGallery.Rnw

index 810fa7f064b567feb33539b128c6ecfbbd5dab95..3e815f64e34a849dc0b9f6af80144526d2fd7eae 100644 (file)
@@ -50,6 +50,8 @@ S3method("xtable", "gmsar")
 S3method("xtable", "summary.gmsar")
 S3method("xtable", "stsls")
 S3method("xtable", "summary.stsls")
+S3method("xtable", "sarlm.pred")
+S3method("xtable", "lagImpact")
 S3method("xtable", "splm")
 S3method("xtable", "summary.splm")
 S3method("xtable", "sphet")
index 647276d704205a90b81783466933d99d59a80485..36146d9a4bcf04b2988caf756f103ff0461d745a 100644 (file)
@@ -386,11 +386,24 @@ xtable.summary.stsls <- function(x, caption = NULL, label = NULL, align = NULL,
                               display = display, auto = auto))
 }
 
+### pred.sarlm objects
+xtable.sarlm.pred <- function(x, ...) {
+  return(xtable(as.data.frame(x), ...))
+}
+### lagImpact objects
+xtable.lagImpact <- function(x, ...) {
+  xtable(spdep:::lagImpactMat(x), ...)
+}
 
 ### package splm
 ### splm objects
 xtable.splm <- function(x, caption = NULL, label = NULL, align = NULL,
                         digits = NULL, display = NULL, auto = FALSE, ...) {
+  if (!requireNamespace("splm", quietly = TRUE)) {
+    stop("Package splm is needed for this function to work.",
+      call. = FALSE)
+  }  
   return(xtable.summary.splm(summary(x), caption = caption, label = label,
                              align = align, digits = digits,
                              display = display, auto = auto))
@@ -399,6 +412,10 @@ xtable.splm <- function(x, caption = NULL, label = NULL, align = NULL,
 xtable.summary.splm <- function(x, caption = NULL, label = NULL, align = NULL,
                                 digits = NULL, display = NULL, auto = FALSE,
                                 ...) {
+  if (!requireNamespace("splm", quietly = TRUE)) {
+    stop("Package splm is needed for this function to work.",
+      call. = FALSE)
+  }
   x <- data.frame(x$CoefTable, check.names = FALSE)
 
   class(x) <- c("xtable","data.frame")
index 9b41fb9090d66baf78af627131a575bf35fa1349..9beb1a64f876fac9f5330976771c8d6e4b87d223 100644 (file)
@@ -24,6 +24,8 @@
 \alias{xtable.summary.gmsar}
 \alias{xtable.stsls}
 \alias{xtable.summary.stsls}
+\alias{xtable.sarlm.pred}
+\alias{xtable.lagImpact}
 \alias{xtable.splm}
 \alias{xtable.summary.splm}
 \alias{xtable.sphet}
index 43fbebbab9b1a511bba8742febe6b0203495b397..30d0e086481873d3328b3c560cf24593d18fcc4a 100644 (file)
@@ -32,7 +32,7 @@
 \r
 \section{Introduction}\r
 This document represents a test of the functions in \pkg{xtable} which\r
-deal with other packages\r
+deal with other packages.\r
 \r
 <<set, include=FALSE>>=\r
 library(knitr)\r
@@ -61,7 +61,7 @@ First load the package and create some objects.
 <<dataspdep>>=\r
 library(spdep)\r
 data(oldcol)\r
-COL.lag.eig <- lagsarlm(CRIME ~ INC + HOVAL, data = COL.OLD, \r
+COL.lag.eig <- lagsarlm(CRIME ~ INC + HOVAL, data = COL.OLD[]\r
                         nb2listw(COL.nb))\r
 class(COL.lag.eig)\r
 COL.errW.GM <- GMerrorsar(CRIME ~ INC + HOVAL, data = COL.OLD,\r
@@ -71,6 +71,19 @@ class(COL.errW.GM)
 COL.lag.stsls <- stsls(CRIME ~ INC + HOVAL, data = COL.OLD, \r
                        nb2listw(COL.nb))\r
 class(COL.lag.stsls)\r
+\r
+p1 <- predict(COL.lag.eig, newdata = COL.OLD[45:49,], \r
+              listw = nb2listw(COL.nb))\r
+class(p1)\r
+p2 <- predict(COL.lag.eig, newdata = COL.OLD[45:49,], \r
+              pred.type = "trend", type = "trend")\r
+#type option for retrocompatibility with spdep 0.5-92\r
+class(p2)\r
+\r
+imp.exact <- impacts(COL.lag.eig, listw = nb2listw(COL.nb))\r
+class(imp.exact)\r
+imp.sim <- impacts(COL.lag.eig, listw = nb2listw(COL.nb), R = 200)\r
+class(imp.sim)\r
 @ %def\r
 \r
 \r
@@ -116,6 +129,34 @@ xtable(COL.errW.GM)
 xtable(COL.lag.stsls)\r
 @ %def \r
 \r
+\subsubsection{\code{sarlm.pred} objects}\r
+\label{sec:codesarlmpred-objects}\r
+\r
+\code{xtable} has a method for predictions of \code{sarlm} models.\r
+\r
+<<xtablesarlmpred, results = 'asis'>>=\r
+xtable(p1)\r
+@ %def \r
+\r
+This method transforms the \code{sarlm.pred} objects into data frames, allowing any number of attributes vectors which may vary according to predictor types.\r
+\r
+<<xtablesarlmpred2, results = 'asis'>>=\r
+xtable(p2)\r
+@ %def\r
+\r
+\subsubsection{\code{lagImpact} objects}\r
+\label{sec:codelagimpact-objects}\r
+\r
+The \code{xtable} method returns the values of direct, indirect and total impacts for all the variables in the model. The class \code{lagImpact} have two different sets of attributes according to if simulations are used. But the \code{xtable} method always returns the three components of the non-simulation case.\r
+\r
+<<xtablelagimpactexact, results = 'asis'>>=\r
+xtable(imp.exact)\r
+@ %def \r
+\r
+\p\r
+<<xtablelagimpactmcmc, results = 'asis'>>=\r
+xtable(imp.sim)\r
+@ %def \r
 \r
 \r
 \subsubsection{\code{spautolm} objects}\r
@@ -126,7 +167,7 @@ by Guido Schulz (\url{schulzgu@student.hu-berlin.de}), who also
 provided an example of an object of this type. The required code was\r
 implemented by David Scott (\url{d.scott@auckland.ac.nz}).\r
 \r
-First create an object of the required type\r
+First create an object of the required type.\r
 \r
 <<minimalexample, results = 'hide'>>=\r
 library(spdep)\r
@@ -159,12 +200,15 @@ library(splm)
 data(Produc, package = "plm")\r
 data(usaww)\r
 fm <- log(gsp) ~ log(pcap) + log(pc) + log(emp) + unemp\r
-fespaterr <- spml(fm, data = Produc, listw = mat2listw(usaww),\r
-                  model = "within", spatial.error = "b", Hess = FALSE)\r
-class(fespaterr)\r
+respatlag <- spml(fm, data = Produc, listw = mat2listw(usaww),\r
+                   model="random", spatial.error="none", lag=TRUE)\r
+class(respatlag)\r
 GM <- spgm(log(gsp) ~ log(pcap) + log(pc) + log(emp) + unemp, data = Produc,\r
            listw = usaww, moments = "fullweights", spatial.error = TRUE)\r
 class(GM)\r
+\r
+imp.spml <- impacts(respatlag, listw = mat2listw(usaww, style = "W"), time = 17)\r
+class(imp.spml)\r
 @ %def\r
 \r
 \r
@@ -172,7 +216,7 @@ class(GM)
 \label{sec:codesplm-objects}\r
 \r
 <<xtablesplm, results = 'asis'>>=\r
-xtable(fespaterr)\r
+xtable(respatlag)\r
 @ %def \r
 \r
 \r
@@ -181,6 +225,11 @@ xtable(fespaterr)
 xtable(GM)\r
 @ %def \r
 \r
+The \code{xtable} method works the same on impacts of \code{splm} models.\r
+\r
+<<xtablesplmimpacts, results = 'asis'>>=\r
+xtable(imp.spml)\r
+@ %def \r
 \r
 \subsection{The package \pkg{sphet}}\r
 \label{sec:package-pkgsphet}\r
@@ -197,6 +246,9 @@ class(res.stsls)
 \r
 res.gstsls <- gstslshet(CRIME ~ HOVAL + INC, data = columbus, listw = listw)\r
 class(res.gstsls)\r
+\r
+imp.gstsls <- impacts(res.gstsls, listw = listw)\r
+class(imp.gstsls)\r
 @ %def\r
 \r
 \r
@@ -212,5 +264,10 @@ xtable(res.stsls)
 xtable(res.gstsls)\r
 @ %def \r
 \r
+\code{sphet} also provides a method for computing impacts.\r
+\r
+<<xtablesphetimpacts, results = 'asis'>>=\r
+xtable(imp.gstsls)\r
+@ %def \r
 \r
 \end{document}\r