Skip to content

Commit

Permalink
Removed redundant 'gppois:::' qualifiers
Browse files Browse the repository at this point in the history
I was a little overzealous adding 'gppois:::' before each private
method.  This appears to be unnecessary for code that is WITHIN the
package.  (Code "outside" the package, such as the steelStrain.R demo,
still needs this qualifier.)
  • Loading branch information
Charles R. Hogg III committed Jul 11, 2012
1 parent 8f020a9 commit 68b1e78
Show file tree
Hide file tree
Showing 7 changed files with 51 additions and 51 deletions.
2 changes: 1 addition & 1 deletion GPPois.R
Expand Up @@ -145,7 +145,7 @@ setMethodS3("PlotCovariance2D", "Model", conflict="quiet",
# Construct a data.frame for all the matrices # Construct a data.frame for all the matrices
point.out <- matrix(d$X[i, ], nrow=1) point.out <- matrix(d$X[i, ], nrow=1)
K.data <<- data.frame(X.1=d$X[, 1], X.2=d$X[, 2], K.data <<- data.frame(X.1=d$X[, 1], X.2=d$X[, 2],
Cov=gppois:::KTotal(this, d=d)[i, ], Cov=KTotal(this, d=d)[i, ],
M=t(this$PredictionMatrix(d=d, X.out=point.out, M=t(this$PredictionMatrix(d=d, X.out=point.out,
contributions=this$contributionIds[ contributions=this$contributionIds[
which(this$contributionIds != 'noise')])) which(this$contributionIds != 'noise')]))
Expand Down
32 changes: 16 additions & 16 deletions R/Covariance.R
Expand Up @@ -103,7 +103,7 @@ setMethodS3("getParamNames", "Covariance", conflict="quiet",
if (!is.character(getId(this)) || nchar(getId(this)) < 1) { if (!is.character(getId(this)) || nchar(getId(this)) < 1) {
return (getParamNamesPlain(this)) return (getParamNamesPlain(this))
} }
return (gppois:::PrependId(this=this, strings=getParamNamesPlain(this))) return (PrependId(this=this, strings=getParamNamesPlain(this)))
}) })


#' Parameter values for this Covariance #' Parameter values for this Covariance
Expand Down Expand Up @@ -173,16 +173,16 @@ setMethodS3("getParams", "Covariance", conflict="quiet",
p <- getParamsPlain(this) p <- getParamsPlain(this)
names(p) <- getParamNames(this) names(p) <- getParamNames(this)
if (for.training) { if (for.training) {
p <- gppois:::EncodeForTraining(this, p) p <- EncodeForTraining(this, p)
} }
return (p) return (p)
}) })
setMethodS3("setParams", "Covariance", conflict="quiet", setMethodS3("setParams", "Covariance", conflict="quiet",
function(this, p, for.training=FALSE, ...) { function(this, p, for.training=FALSE, ...) {
if (for.training) { if (for.training) {
p <- gppois:::DecodeForTraining(p) p <- DecodeForTraining(p)
} }
p.plain <- gppois:::UndecorateNames(this, p=p) p.plain <- UndecorateNames(this, p=p)
this$setParamsPlain(p=p.plain) this$setParamsPlain(p=p.plain)
return (invisible(this)) return (invisible(this))
}) })
Expand Down Expand Up @@ -237,11 +237,11 @@ setMethodS3("setParamsPlain", "Covariance", conflict="quiet",
p.good.names[to.change] <- p[to.change] p.good.names[to.change] <- p[to.change]
# paramsPlainImplementation requires a vector with a value for every # paramsPlainImplementation requires a vector with a value for every
# parameter; we took care of this above. # parameter; we took care of this above.
gppois:::paramsPlainImplementation(this, p=p.good.names) paramsPlainImplementation(this, p=p.good.names)
p.clamped <- gppois:::ClampedParamVals(this, p=p.good.names) p.clamped <- ClampedParamVals(this, p=p.good.names)
p.names <- names(p.clamped) p.names <- names(p.clamped)
clamped <- which(p.good.names[p.names] != p.clamped[p.names]) clamped <- which(p.good.names[p.names] != p.clamped[p.names])
gppois:::paramsPlainImplementation(this, p=p.clamped) paramsPlainImplementation(this, p=p.clamped)
if (any(clamped)) { if (any(clamped)) {
culprits <- paste(sep='', collapse=' ', '"', p.names[clamped], '"') culprits <- paste(sep='', collapse=' ', '"', p.names[clamped], '"')
warning(paste("These parameters had to be clamped:\n", culprits, "\n")) warning(paste("These parameters had to be clamped:\n", culprits, "\n"))
Expand Down Expand Up @@ -282,16 +282,16 @@ setMethodS3("getLower", "Covariance", conflict="quiet",
L <- this$getLowerPlain() L <- this$getLowerPlain()
names(L) <- this$getParamNames() names(L) <- this$getParamNames()
if (for.training) { if (for.training) {
L <- gppois:::EncodeForTraining(this, L) L <- EncodeForTraining(this, L)
} }
return (L) return (L)
}) })
setMethodS3("setLower", "Covariance", conflict="quiet", setMethodS3("setLower", "Covariance", conflict="quiet",
function(this, L, for.training=FALSE, ...) { function(this, L, for.training=FALSE, ...) {
if (for.training) { if (for.training) {
L <- gppois:::DecodeForTraining(L) L <- DecodeForTraining(L)
} }
L.plain <- gppois:::UndecorateNames(this, L) L.plain <- UndecorateNames(this, L)
this$setLowerPlain(L=L.plain) this$setLowerPlain(L=L.plain)
return (invisible(this)) return (invisible(this))
}) })
Expand Down Expand Up @@ -329,16 +329,16 @@ setMethodS3("getUpper", "Covariance", conflict="quiet",
U <- this$getUpperPlain() U <- this$getUpperPlain()
names(U) <- this$getParamNames() names(U) <- this$getParamNames()
if (for.training) { if (for.training) {
U <- gppois:::EncodeForTraining(this, U) U <- EncodeForTraining(this, U)
} }
return (U) return (U)
}) })
setMethodS3("setUpper", "Covariance", conflict="quiet", setMethodS3("setUpper", "Covariance", conflict="quiet",
function(this, U, for.training=FALSE, ...) { function(this, U, for.training=FALSE, ...) {
if (for.training) { if (for.training) {
U <- gppois:::DecodeForTraining(U) U <- DecodeForTraining(U)
} }
U.plain <- gppois:::UndecorateNames(this, U) U.plain <- UndecorateNames(this, U)
this$setUpperPlain(U=U.plain) this$setUpperPlain(U=U.plain)
return (invisible(this)) return (invisible(this))
}) })
Expand Down Expand Up @@ -374,7 +374,7 @@ setMethodS3("EncodeForTraining", "Covariance", conflict="quiet",
# Returns: # Returns:
# 'values', but with scale-type parameters changed to their log (and # 'values', but with scale-type parameters changed to their log (and
# appropriately renamed) # appropriately renamed)
logspace.names <- gppois:::PrependId(this, this$logspaceNames) logspace.names <- PrependId(this, this$logspaceNames)
i.log <- which(names(values) %in% logspace.names) i.log <- which(names(values) %in% logspace.names)
values[i.log] <- log(values[i.log]) values[i.log] <- log(values[i.log])
names(values)[i.log] <- paste(sep="", names(values)[i.log], LogspaceTag()) names(values)[i.log] <- paste(sep="", names(values)[i.log], LogspaceTag())
Expand Down Expand Up @@ -502,7 +502,7 @@ setMethodS3("KInInDeriv", "Covariance", conflict="quiet",
function(this, d, param, ...) { function(this, d, param, ...) {
if (param %in% this$paramNames) { if (param %in% this$paramNames) {
names(param) <- param names(param) <- param
param.plain <- names(gppois:::UndecorateNames(this, p=param)) param.plain <- names(UndecorateNames(this, p=param))
K.deriv <- this$KDerivImplementation(d=d, param=param.plain) K.deriv <- this$KDerivImplementation(d=d, param=param.plain)
} else { } else {
K.deriv <- matrix(0, nrow=d$n, ncol=d$n) K.deriv <- matrix(0, nrow=d$n, ncol=d$n)
Expand Down Expand Up @@ -607,7 +607,7 @@ setMethodS3("ClampParams", "Covariance", private=TRUE, conflict="quiet",


# The following *should* be OK, as long as neither setParams nor # The following *should* be OK, as long as neither setParams nor
# setParamsPlain calls ClampParams... # setParamsPlain calls ClampParams...
this$setParamsPlain(p=gppois:::ClampedParamVals(this, warn=warn)) this$setParamsPlain(p=ClampedParamVals(this, warn=warn))
return (invisible(this)) return (invisible(this))
}) })


Expand Down
8 changes: 4 additions & 4 deletions R/CovarianceNoise.R
Expand Up @@ -163,12 +163,12 @@ setMethodS3("setLowerPlain", "CovarianceNoise", conflict="quiet",
L.posdef <- pmax(L, 0) # Noise cannot be negative L.posdef <- pmax(L, 0) # Noise cannot be negative


# Adjust upper bounds to make way for the new values of L # Adjust upper bounds to make way for the new values of L
L.change <- gppois:::PushUpperBounds(this, U.min=L.posdef) L.change <- PushUpperBounds(this, U.min=L.posdef)


L.vals <- this$getLowerPlain() L.vals <- this$getLowerPlain()
L.vals[names(L.change)] <- L.change[names(L.change)] L.vals[names(L.change)] <- L.change[names(L.change)]
this$.sigma.bounds[1] <- L.vals["sigma"] this$.sigma.bounds[1] <- L.vals["sigma"]
gppois:::ClampParams(this, warn=TRUE) ClampParams(this, warn=TRUE)
return (this) return (this)
}) })


Expand Down Expand Up @@ -207,12 +207,12 @@ setMethodS3("setUpperPlain", "CovarianceNoise", conflict="quiet",
U.posdef <- pmax(U, 0) # SE has no possibly-negative parameters U.posdef <- pmax(U, 0) # SE has no possibly-negative parameters


# Adjust lower bounds to make way for the new values of U # Adjust lower bounds to make way for the new values of U
U.change <- gppois:::PushLowerBounds(this, L.max=U.posdef) U.change <- PushLowerBounds(this, L.max=U.posdef)


U.vals <- this$getUpperPlain() U.vals <- this$getUpperPlain()
U.vals[names(U.change)] <- U.change[names(U.change)] U.vals[names(U.change)] <- U.change[names(U.change)]
this$.sigma.bounds[2] <- U.vals["sigma"] this$.sigma.bounds[2] <- U.vals["sigma"]
gppois:::ClampParams(this, warn=TRUE) ClampParams(this, warn=TRUE)
return (this) return (this)
}) })


Expand Down
8 changes: 4 additions & 4 deletions R/CovarianceSE.R
Expand Up @@ -175,12 +175,12 @@ setMethodS3("setLowerPlain", "CovarianceSE", conflict="quiet",
} }
L.posdef <- pmax(L, 0) # SE has no possibly-negative parameters L.posdef <- pmax(L, 0) # SE has no possibly-negative parameters
# Adjust upper bounds to make way for the new values of L # Adjust upper bounds to make way for the new values of L
L.change <- gppois:::PushUpperBounds(this, U.min=L.posdef) L.change <- PushUpperBounds(this, U.min=L.posdef)
L.vals <- this$getLowerPlain() L.vals <- this$getLowerPlain()
L.vals[names(L.change)] <- L.change[names(L.change)] L.vals[names(L.change)] <- L.change[names(L.change)]
this$.ell.bounds[1] <- L.vals["ell"] this$.ell.bounds[1] <- L.vals["ell"]
this$.sigma.f.bounds[1] <- L.vals["sigma.f"] this$.sigma.f.bounds[1] <- L.vals["sigma.f"]
gppois:::ClampParams(this, warn=TRUE) ClampParams(this, warn=TRUE)
return (this) return (this)
}) })


Expand Down Expand Up @@ -218,13 +218,13 @@ setMethodS3("setUpperPlain", "CovarianceSE", conflict="quiet",
} }
U.posdef <- pmax(U, 0) # SE has no possibly-negative parameters U.posdef <- pmax(U, 0) # SE has no possibly-negative parameters
# Adjust lower bounds to make way for the new values of U # Adjust lower bounds to make way for the new values of U
U.change <- gppois:::PushLowerBounds(this, L.max=U.posdef) U.change <- PushLowerBounds(this, L.max=U.posdef)


U.vals <- this$getUpperPlain() U.vals <- this$getUpperPlain()
U.vals[names(U.change)] <- U.change[names(U.change)] U.vals[names(U.change)] <- U.change[names(U.change)]
this$.ell.bounds[2] <- U.vals["ell"] this$.ell.bounds[2] <- U.vals["ell"]
this$.sigma.f.bounds[2] <- U.vals["sigma.f"] this$.sigma.f.bounds[2] <- U.vals["sigma.f"]
gppois:::ClampParams(this, warn=TRUE) ClampParams(this, warn=TRUE)
return (this) return (this)
}) })


Expand Down
8 changes: 4 additions & 4 deletions R/CovarianceSEAniso2D.R
Expand Up @@ -197,15 +197,15 @@ setMethodS3("getLowerPlain", "CovarianceSEAniso2D", conflict="quiet",
setMethodS3("setLowerPlain", "CovarianceSEAniso2D", conflict="quiet", setMethodS3("setLowerPlain", "CovarianceSEAniso2D", conflict="quiet",
function(this, L, ...) { function(this, L, ...) {
# Adjust upper bounds to make way for the new values of L # Adjust upper bounds to make way for the new values of L
L.change <- gppois:::PushUpperBounds(this, U.min=L) L.change <- PushUpperBounds(this, U.min=L)


L.vals <- this$getLowerPlain() L.vals <- this$getLowerPlain()
L.vals[names(L.change)] <- L.change[names(L.change)] L.vals[names(L.change)] <- L.change[names(L.change)]
this$.ell.1.bounds[1] <- L.vals["ell.1"] this$.ell.1.bounds[1] <- L.vals["ell.1"]
this$.ell.2.bounds[1] <- L.vals["ell.2"] this$.ell.2.bounds[1] <- L.vals["ell.2"]
this$.theta.1.bounds[1] <- L.vals["theta.1"] this$.theta.1.bounds[1] <- L.vals["theta.1"]
this$.sigma.f.bounds[1] <- L.vals["sigma.f"] this$.sigma.f.bounds[1] <- L.vals["sigma.f"]
gppois:::ClampParams(this, warn=TRUE) ClampParams(this, warn=TRUE)
return (this) return (this)
}) })


Expand Down Expand Up @@ -241,15 +241,15 @@ setMethodS3("getUpperPlain", "CovarianceSEAniso2D", conflict="quiet",
setMethodS3("setUpperPlain", "CovarianceSEAniso2D", conflict="quiet", setMethodS3("setUpperPlain", "CovarianceSEAniso2D", conflict="quiet",
function(this, U, ...) { function(this, U, ...) {
# Adjust lower bounds to make way for the new values of U # Adjust lower bounds to make way for the new values of U
U.change <- gppois:::PushLowerBounds(this, L.max=U) U.change <- PushLowerBounds(this, L.max=U)


U.vals <- this$getUpperPlain() U.vals <- this$getUpperPlain()
U.vals[names(U.change)] <- U.change[names(U.change)] U.vals[names(U.change)] <- U.change[names(U.change)]
this$.ell.1.bounds[2] <- U.vals["ell.1"] this$.ell.1.bounds[2] <- U.vals["ell.1"]
this$.ell.2.bounds[2] <- U.vals["ell.2"] this$.ell.2.bounds[2] <- U.vals["ell.2"]
this$.theta.1.bounds[2] <- U.vals["theta.1"] this$.theta.1.bounds[2] <- U.vals["theta.1"]
this$.sigma.f.bounds[2] <- U.vals["sigma.f"] this$.sigma.f.bounds[2] <- U.vals["sigma.f"]
gppois:::ClampParams(this, warn=TRUE) ClampParams(this, warn=TRUE)
return (this) return (this)
}) })


Expand Down
8 changes: 4 additions & 4 deletions R/CovarianceSELocalized.R
Expand Up @@ -238,15 +238,15 @@ setMethodS3("setLowerPlain", "CovarianceSELocalized", conflict="quiet",
posdef.names <- c('ell', 'sigma.f') posdef.names <- c('ell', 'sigma.f')
L[posdef.names] <- pmax(L[posdef.names], 0) L[posdef.names] <- pmax(L[posdef.names], 0)
# Adjust upper bounds to make way for the new values of L # Adjust upper bounds to make way for the new values of L
L.change <- gppois:::PushUpperBounds(this, U.min=L) L.change <- PushUpperBounds(this, U.min=L)


L.vals <- this$getLowerPlain() L.vals <- this$getLowerPlain()
L.vals[names(L.change)] <- L.change[names(L.change)] L.vals[names(L.change)] <- L.change[names(L.change)]
this$.ell.bounds[1] <- L.vals["ell"] this$.ell.bounds[1] <- L.vals["ell"]
this$.sigma.f.bounds[1] <- L.vals["sigma.f"] this$.sigma.f.bounds[1] <- L.vals["sigma.f"]
this$.X.L.bounds[1] <- L.vals["X.L"] this$.X.L.bounds[1] <- L.vals["X.L"]
this$.X.R.bounds[1] <- L.vals["X.R"] this$.X.R.bounds[1] <- L.vals["X.R"]
gppois:::ClampParams(this, warn=TRUE) ClampParams(this, warn=TRUE)
return (this) return (this)
}) })


Expand Down Expand Up @@ -288,15 +288,15 @@ setMethodS3("setUpperPlain", "CovarianceSELocalized", conflict="quiet",
posdef.names <- c('ell', 'sigma.f') posdef.names <- c('ell', 'sigma.f')
U[posdef.names] <- pmax(U[posdef.names], 0) U[posdef.names] <- pmax(U[posdef.names], 0)
# Adjust lower bounds to make way for the new values of U # Adjust lower bounds to make way for the new values of U
U.change <- gppois:::PushLowerBounds(this, L.max=U) U.change <- PushLowerBounds(this, L.max=U)


U.vals <- this$getUpperPlain() U.vals <- this$getUpperPlain()
U.vals[names(U.change)] <- U.change[names(U.change)] U.vals[names(U.change)] <- U.change[names(U.change)]
this$.ell.bounds[2] <- U.vals["ell"] this$.ell.bounds[2] <- U.vals["ell"]
this$.sigma.f.bounds[2] <- U.vals["sigma.f"] this$.sigma.f.bounds[2] <- U.vals["sigma.f"]
this$.X.L.bounds[2] <- U.vals["X.L"] this$.X.L.bounds[2] <- U.vals["X.L"]
this$.X.R.bounds[2] <- U.vals["X.R"] this$.X.R.bounds[2] <- U.vals["X.R"]
gppois:::ClampParams(this, warn=TRUE) ClampParams(this, warn=TRUE)
return (this) return (this)
}) })


Expand Down
36 changes: 18 additions & 18 deletions R/Model.R
Expand Up @@ -102,12 +102,12 @@ LogML <- function(par=model$getParams(for.training=TRUE), model, d,
if (!update.params) { if (!update.params) {
model <- clone(model) model <- clone(model)
} }
model$setParams(p=gppois:::DecodeForTraining(par)) model$setParams(p=DecodeForTraining(par))
Y <- d$xformedDpts Y <- d$xformedDpts
# The following calculation is based on Equation 5.8 in # The following calculation is based on Equation 5.8 in
# Rasmussen and Williams (2005): # Rasmussen and Williams (2005):
term.data.fit <- -0.5 * t(Y) %*% gppois:::KInv(this=model, d) %*% Y term.data.fit <- -0.5 * t(Y) %*% KInv(this=model, d) %*% Y
term.complexity <- -0.5 * gppois:::LogDetK(this=model, d) term.complexity <- -0.5 * LogDetK(this=model, d)
term.num.dpts <- -0.5 * d$n * log(2 * pi) term.num.dpts <- -0.5 * d$n * log(2 * pi)
return (term.data.fit + term.complexity + term.num.dpts) return (term.data.fit + term.complexity + term.num.dpts)
} }
Expand Down Expand Up @@ -159,17 +159,17 @@ GradLogML <- function(par=model$getParams(for.training=TRUE), model, d,
if (!update.params) { if (!update.params) {
model <- clone(model) model <- clone(model)
} }
model$setParams(p=gppois:::DecodeForTraining(par)) model$setParams(p=DecodeForTraining(par))
Y <- d$xformedDpts Y <- d$xformedDpts
# The following calculations are based on Equation 5.9 in # The following calculations are based on Equation 5.9 in
# Rasmussen and Williams (2005). # Rasmussen and Williams (2005).
alpha <- gppois:::KInv(this=model, d) %*% Y alpha <- KInv(this=model, d) %*% Y
mat.for.grad <- alpha %*% t(alpha) - gppois:::KInv(this=model, d) mat.for.grad <- alpha %*% t(alpha) - KInv(this=model, d)
var.names <- names(model$getParams(for.training=TRUE)) var.names <- names(model$getParams(for.training=TRUE))
good.names <- names(par)[which(names(par) %in% var.names)] good.names <- names(par)[which(names(par) %in% var.names)]
grad <- c() grad <- c()
for (p.n in good.names) { for (p.n in good.names) {
grad[p.n] <- 0.5 * SmartTrace(gppois:::KDeriv(this=model, d=d, param=p.n), grad[p.n] <- 0.5 * SmartTrace(KDeriv(this=model, d=d, param=p.n),
mat.for.grad) mat.for.grad)
} }
return (grad) return (grad)
Expand Down Expand Up @@ -268,7 +268,7 @@ setMethodS3("getParams", "Model", conflict="quiet",
p <- c(p, covar$getParams(for.training=for.training)) p <- c(p, covar$getParams(for.training=for.training))
} }
if (for.training) { if (for.training) {
unlog.params <- gppois:::DecodeForTraining(p) unlog.params <- DecodeForTraining(p)
i.vary <- which(names(unlog.params) %in% this$getVaryingParamNames()) i.vary <- which(names(unlog.params) %in% this$getVaryingParamNames())
p <- p[i.vary] p <- p[i.vary]
} }
Expand Down Expand Up @@ -316,7 +316,7 @@ setMethodS3("getLower", "Model", conflict="quiet",
L <- c(L, covar$getLower(for.training=for.training)) L <- c(L, covar$getLower(for.training=for.training))
} }
if (for.training) { if (for.training) {
unlog.params <- gppois:::DecodeForTraining(L) unlog.params <- DecodeForTraining(L)
i.vary <- which(names(unlog.params) %in% this$getVaryingParamNames()) i.vary <- which(names(unlog.params) %in% this$getVaryingParamNames())
L <- L[i.vary] L <- L[i.vary]
} }
Expand Down Expand Up @@ -364,7 +364,7 @@ setMethodS3("getUpper", "Model", conflict="quiet",
U <- c(U, covar$getUpper(for.training=for.training)) U <- c(U, covar$getUpper(for.training=for.training))
} }
if (for.training) { if (for.training) {
unlog.params <- gppois:::DecodeForTraining(U) unlog.params <- DecodeForTraining(U)
i.vary <- which(names(unlog.params) %in% this$getVaryingParamNames()) i.vary <- which(names(unlog.params) %in% this$getVaryingParamNames())
U <- U[i.vary] U <- U[i.vary]
} }
Expand Down Expand Up @@ -571,7 +571,7 @@ setMethodS3("Freeze", "Model", conflict="quiet",
#' @seealso \code{\link{Model}} #' @seealso \code{\link{Model}}
setMethodS3("L", "Model", conflict="quiet", setMethodS3("L", "Model", conflict="quiet",
function(this, d, X.out=d$X, contributions=this$getSignalIds(), ...) { function(this, d, X.out=d$X, contributions=this$getSignalIds(), ...) {
gppois:::ComputeL(this, d=d, X.out=X.out, contributions=contributions) ComputeL(this, d=d, X.out=X.out, contributions=contributions)
return (this$.L$M) return (this$.L$M)
}) })


Expand Down Expand Up @@ -699,7 +699,7 @@ setMethodS3("PlotBubblingSurfaces2D", "Model", conflict="quiet",
setMethodS3("PosteriorMean", "Model", conflict="quiet", setMethodS3("PosteriorMean", "Model", conflict="quiet",
function(this, d, X.out=d$X, contributions=this$getSignalIds(), function(this, d, X.out=d$X, contributions=this$getSignalIds(),
untransform.result=TRUE, ...) { untransform.result=TRUE, ...) {
contributions <- gppois:::CheckContributionsAndWarn(this, contributions) contributions <- CheckContributionsAndWarn(this, contributions)
M <- this$PredictionMatrix(d=d, X.out=X.out, contributions=contributions) M <- this$PredictionMatrix(d=d, X.out=X.out, contributions=contributions)
result <- M %*% d$xformedDpts result <- M %*% d$xformedDpts
if (untransform.result) { if (untransform.result) {
Expand Down Expand Up @@ -742,7 +742,7 @@ setMethodS3("PredictionMatrix", "Model", conflict="quiet",
rm(covar.K) rm(covar.K)
gc() gc()
} }
M <- K.in.out %*% gppois:::KInv(this, d=d) M <- K.in.out %*% KInv(this, d=d)
rm(K.in.out) rm(K.in.out)
gc() gc()
return (M) return (M)
Expand Down Expand Up @@ -809,7 +809,7 @@ setMethodS3("PosteriorInterval", "Model", conflict="quiet",
#' @seealso \code{\link{Model}} #' @seealso \code{\link{Model}}
setMethodS3("PosteriorStandardDeviation", "Model", conflict="quiet", setMethodS3("PosteriorStandardDeviation", "Model", conflict="quiet",
function(this, d, X.out=d$X, contributions=this$getSignalIds(), ...) { function(this, d, X.out=d$X, contributions=this$getSignalIds(), ...) {
contributions <- gppois:::CheckContributionsAndWarn(this, contributions) contributions <- CheckContributionsAndWarn(this, contributions)
# Calculate the posterior predictive mean. # Calculate the posterior predictive mean.
N.out <- NumPoints(X.out) N.out <- NumPoints(X.out)
K.in.out <- matrix(0, nrow=N.out, ncol=d$n) K.in.out <- matrix(0, nrow=N.out, ncol=d$n)
Expand Down Expand Up @@ -996,7 +996,7 @@ setMethodS3("ComputeL", "Model", private=TRUE, conflict="quiet",
ingredients <- list(X=d$X, X.out=X.out, noiseVar=d$noiseVar, ingredients <- list(X=d$X, X.out=X.out, noiseVar=d$noiseVar,
params=this$params) params=this$params)
if (this$.L$NeedToRecalculate(ingredients=ingredients)) { if (this$.L$NeedToRecalculate(ingredients=ingredients)) {
gppois:::ComputeKChol(this, d=d) ComputeKChol(this, d=d)
K.out.out <- d$noiseVar * diag(NumPoints(X.out)) K.out.out <- d$noiseVar * diag(NumPoints(X.out))
K.in.out <- matrix(0, nrow=NumPoints(X.out), ncol=NumPoints(d$X)) K.in.out <- matrix(0, nrow=NumPoints(X.out), ncol=NumPoints(d$X))
for (c.id in contributions) { for (c.id in contributions) {
Expand Down Expand Up @@ -1024,7 +1024,7 @@ setMethodS3("ComputeKChol", "Model", private=TRUE, conflict="quiet",
# model. # model.
ingredients <- list(X=d$X, noiseVar=d$noiseVar, params=this$params) ingredients <- list(X=d$X, noiseVar=d$noiseVar, params=this$params)
if (this$.K.chol$NeedToRecalculate(ingredients=ingredients)) { if (this$.K.chol$NeedToRecalculate(ingredients=ingredients)) {
K.tot <- gppois:::KTotal(this, d=d) K.tot <- KTotal(this, d=d)
K.chol <- DebugIfError(chol.default, K.tot) K.chol <- DebugIfError(chol.default, K.tot)
this$.K.chol$StoreMatrix(M=K.chol, ingredients=ingredients) this$.K.chol$StoreMatrix(M=K.chol, ingredients=ingredients)
} }
Expand Down Expand Up @@ -1113,7 +1113,7 @@ setMethodS3("KInv", "Model", private=TRUE, conflict="quiet",
# #
# Returns: # Returns:
# The inverse total covariance matrix for this model. # The inverse total covariance matrix for this model.
gppois:::ComputeKChol(this, d=d) ComputeKChol(this, d=d)
return (chol2inv(this$.K.chol$M)) return (chol2inv(this$.K.chol$M))
}) })


Expand All @@ -1127,7 +1127,7 @@ setMethodS3("LogDetK", "Model", private=TRUE, conflict="quiet",
# #
# Returns: # Returns:
# The logarithm of the determinant of the model's covariance matrix. # The logarithm of the determinant of the model's covariance matrix.
gppois:::ComputeKChol(this, d=d) ComputeKChol(this, d=d)
return (2 * sum(log(diag(this$.K.chol$M)))) return (2 * sum(log(diag(this$.K.chol$M))))
}) })


0 comments on commit 68b1e78

Please sign in to comment.