Skip to content

Commit 564fc66

Browse files
committed
working with ML
1 parent fccadfa commit 564fc66

File tree

5 files changed

+30
-19
lines changed

5 files changed

+30
-19
lines changed

R/ML_models.R

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ errorsarlm <- function(formula, data = list(), listw, na.action, weights=NULL,
1313
super=NULL, spamPivot="MMD", in_coef=0.1, type="MC",
1414
correct=TRUE, trunc=TRUE, SE_method="LU", nrho=200,
1515
interpn=2000, small_asy=TRUE, small=1500, SElndet=NULL,
16-
LU_order=FALSE, pre_eig=NULL, glht=FALSE)
16+
LU_order=FALSE, pre_eig=NULL, return_impacts=TRUE)
1717
nmsC <- names(con)
1818
con[(namc <- names(control))] <- control
1919
if (length(noNms <- namc[!namc %in% nmsC]))
@@ -29,7 +29,7 @@ errorsarlm <- function(formula, data = list(), listw, na.action, weights=NULL,
2929
# stopifnot(is.logical(con$super))
3030
stopifnot(is.logical(con$compiled_sse))
3131
stopifnot(is.character(con$spamPivot))
32-
stopifnot(is.logical(con$glht))
32+
stopifnot(is.logical(con$return_impacts))
3333
if (!inherits(formula, "formula")) formula <- as.formula(formula)
3434
# mt <- terms(formula, data = data)
3535
# mf <- lm(formula, data, na.action=na.action, method="model.frame")
@@ -270,7 +270,8 @@ errorsarlm <- function(formula, data = list(), listw, na.action, weights=NULL,
270270
names(coef.lambda) <- xcolnames
271271
sum_lm_target <- summary.lm(lm.target, correlation = FALSE)
272272
emixedImps <- NULL
273-
if (etype == "emixed") {
273+
if (any(sum_lm_target$aliased)) warning("aliased variables found")
274+
if (con$return_impacts && etype == "emixed") {
274275
if (isTRUE(Durbin)) {
275276
m.1 <- m > 1
276277
if (m.1 && K == 2) {

R/SLX_WX.R

Lines changed: 14 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11

22

3-
lmSLX <- function(formula, data = list(), listw, na.action, weights=NULL, Durbin=TRUE, zero.policy=NULL) {
3+
lmSLX <- function(formula, data = list(), listw, na.action, weights=NULL, Durbin=TRUE, zero.policy=NULL, return_impacts=TRUE) {
44
if (is.null(zero.policy))
55
zero.policy <- get("zeroPolicy", envir = .spatialregOptions)
66
stopifnot(is.logical(zero.policy))
@@ -108,17 +108,19 @@ lmSLX <- function(formula, data = list(), listw, na.action, weights=NULL, Durbin
108108
lm.model <- lm(formula(paste("y ~ 0 + ", paste(colnames(x), collapse="+"))), data=as.data.frame(x), weights=weights)
109109
}
110110
sum_lm_model <- summary.lm(lm.model, correlation = FALSE)
111+
if (any(sum_lm_model$aliased)) warning("aliased variables found")
111112
mixedImps <- NULL
112-
K <- ifelse(isTRUE(grep("Intercept",
113+
if (return_impacts) {
114+
K <- ifelse(isTRUE(grep("Intercept",
113115
names(coefficients(lm.model))[1]) == 1L), 2, 1)
114-
if (isTRUE(Durbin)) {
115-
m <- length(coefficients(lm.model))
116-
m.1 <- m > 1
117-
if (m.1 && K == 2) { #TR: without intercept and m.1 use m/2
116+
if (isTRUE(Durbin)) {
117+
m <- length(coefficients(lm.model))
118+
m.1 <- m > 1
119+
if (m.1 && K == 2) { #TR: without intercept and m.1 use m/2
118120
m2 <- (m-1)/2
119-
} else {
121+
} else {
120122
m2 <- m/2
121-
}
123+
}
122124
cm <- matrix(0, ncol=m, nrow=m2)
123125
if (K == 2) {
124126
if (m.1) {
@@ -143,7 +145,7 @@ lmSLX <- function(formula, data = list(), listw, na.action, weights=NULL, Durbin
143145
}
144146
suppressWarnings(lc <- summary(multcomp::glht(lm.model, linfct=cm)))
145147
totImps <- cbind("Estimate"=lc$test$coefficients, "Std. Error"=lc$test$sigma)
146-
} else if (is.formula(Durbin)) {
148+
} else if (is.formula(Durbin)) {
147149
#FIXME
148150
LI <- ifelse(listw$style != "W"
149151
&& attr(terms(Durbin), "intercept") == 1, 1, 0) #TR: lagged intercept if not W and in Durbin formula
@@ -195,10 +197,11 @@ lmSLX <- function(formula, data = list(), listw, na.action, weights=NULL, Durbin
195197
}
196198
}
197199
rownames(totImps) <- xn
198-
} else stop("undefined Durbin state")
199-
mixedImps <- list(dirImps=dirImps, indirImps=indirImps,
200+
} else stop("undefined Durbin state")
201+
mixedImps <- list(dirImps=dirImps, indirImps=indirImps,
200202
totImps=totImps)
201203

204+
}
202205
attr(lm.model, "mixedImps") <- mixedImps
203206
attr(lm.model, "dvars") <- dvars
204207
if (is.formula(Durbin)) attr(lm.model, "Durbin") <- deparse(Durbin)

R/sarlm_functions.R

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -297,15 +297,15 @@ getVmate <- function(coefs, env, s2, trs, tol.solve=1.0e-10, optim=FALSE,
297297
if (optim) {
298298
if (optimM == "nlm") {
299299
options(warn=-1)
300-
opt <- nlm(f=f_laglm_hess_nlm, p=coefs, env=env, hessian=TRUE)
300+
opt <- nlm(f=f_errlm_hess_nlm, p=coefs, env=env, hessian=TRUE)
301301
options(warn=0)
302302
mat <- opt$hessian
303-
# opt <- optimHess(par=coefs, fn=f_laglm_hess, env=env)
303+
# opt <- optimHess(par=coefs, fn=f_errlm_hess, env=env)
304304
# mat <- opt
305305
} else if (optimM == "optimHess") {
306-
mat <- optimHess(par=coefs, fn=f_laglm_hess, env=env)
306+
mat <- optimHess(par=coefs, fn=f_errlm_hess, env=env)
307307
} else {
308-
opt <- optim(par=coefs, fn=f_laglm_hess, env=env, method=optimM,
308+
opt <- optim(par=coefs, fn=f_errlm_hess, env=env, method=optimM,
309309
hessian=TRUE)
310310
mat <- opt$hessian
311311
}
@@ -354,6 +354,11 @@ f_errlm_hess <- function(coefs, env) {
354354
ret
355355
}
356356

357+
f_errlm_hess_nlm <- function(coefs, env) {
358+
ret <- f_errlm_hess(coefs, env)
359+
-ret
360+
}
361+
357362
insert_asye <- function(coefs, env, s2, mat, trs) {
358363
lambda <- coefs[1]
359364
p <- length(coefs)-1L

man/ML_models.Rd

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -147,6 +147,7 @@ Because numerical optimisation is used to find the values of lambda and rho in \
147147
\item{SElndet}{default NULL, may be used to pass a pre-computed SE toolbox style matrix of coefficients and their lndet values to the "SE_classic" and "SE_whichMin" methods}
148148
\item{LU_order}{default FALSE; used in \dQuote{LU_prepermutate}, note warnings given for \code{lu} method}
149149
\item{pre_eig}{default NULL; may be used to pass a pre-computed vector of eigenvalues}
150+
\item{return_impacts}{default TRUE; may be set FALSE to avoid problems calculating impacts with aliased variables}
150151
\item{OrdVsign}{default 1; used to set the sign of the final component to negative if -1 (alpha times ((sigma squared) squared) in Ord (1975) equation B.1).}
151152
\item{opt_method:}{default \dQuote{nlminb}, may be set to \dQuote{L-BFGS-B} to use box-constrained optimisation in \code{optim}}
152153
\item{opt_control:}{default \code{list()}, a control list to pass to \code{nlminb} or \code{optim}}

man/SLX.Rd

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@
1616
}
1717
\usage{
1818
lmSLX(formula, data = list(), listw, na.action, weights=NULL, Durbin=TRUE,
19-
zero.policy=NULL)
19+
zero.policy=NULL, return_impacts=TRUE)
2020
\method{print}{SlX}(x, digits = max(3L, getOption("digits") - 3L), ...)
2121
\method{summary}{SlX}(object, correlation = FALSE, symbolic.cor = FALSE, ...)
2222
\method{print}{summary.SlX}(x, digits = max(3L, getOption("digits") - 3L),
@@ -39,6 +39,7 @@ is called.}
3939
\item{weights}{an optional vector of weights to be used in the fitting process. Non-NULL weights can be used to indicate that different observations have different variances (with the values in weights being inversely proportional to the variances); or equivalently, when the elements of weights are positive integers w_i, that each response y_i is the mean of w_i unit-weight observations (including the case that there are w_i observations equal to y_i and the data have been summarized) - \code{\link{lm}}}
4040
\item{Durbin}{default TRUE for \code{lmSLX} (Durbin model including WX); if TRUE, full spatial Durbin model; if a formula object, the subset of explanatory variables to lag}
4141
\item{zero.policy}{default NULL, use global option value; if TRUE assign zero to the lagged value of zones without neighbours, if FALSE assign NA}
42+
\item{return_impacts}{default TRUE; may be set FALSE to avoid problems calculating impacts with aliased variables}
4243
\item{digits}{the number of significant digits to use when printing}
4344
\item{correlation}{logical; if \code{TRUE}, the correlation matrix of the estimated parameters is returned and printed}
4445
\item{symbolic.cor}{logical. If \code{TRUE}, print the correlations in a symbolic form (see 'symnum') rather than as numbers}

0 commit comments

Comments
 (0)