[spcopula-commits] r125 - in pkg: . R man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Fri Feb 14 11:34:30 CET 2014


Author: ben_graeler
Date: 2014-02-14 11:34:29 +0100 (Fri, 14 Feb 2014)
New Revision: 125

Added:
   pkg/man/condCovariate.Rd
Modified:
   pkg/DESCRIPTION
   pkg/NAMESPACE
   pkg/R/spCopula.R
   pkg/R/spVineCopula.R
   pkg/R/spatio-temporalPreparation.R
   pkg/R/stCoVarVineCopula.R
   pkg/R/stCopula.R
   pkg/R/stVineCopula.R
   pkg/man/calcBins.Rd
   pkg/man/dropSpTree.Rd
   pkg/man/dropStTree.Rd
   pkg/man/neighbourhood-class.Rd
   pkg/man/spCopPredict.Rd
   pkg/man/spGaussLogLik.Rd
   pkg/man/stCopPredict.Rd
   pkg/man/stNeighbourhood-class.Rd
Log:
- subsequent changes due to the redesign of neighbourhood classes

Modified: pkg/DESCRIPTION
===================================================================
--- pkg/DESCRIPTION	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/DESCRIPTION	2014-02-14 10:34:29 UTC (rev 125)
@@ -2,7 +2,7 @@
 Type: Package
 Title: copula driven spatial analysis
 Version: 0.2-0
-Date: 2014-02-13
+Date: 2014-02-14
 Authors at R: c(person("Benedikt", "Graeler", role = c("aut", "cre"),
                     email = "ben.graeler at uni-muenster.de"),
              person("Marius", "Appel",role = "ctb"))

Modified: pkg/NAMESPACE
===================================================================
--- pkg/NAMESPACE	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/NAMESPACE	2014-02-14 10:34:29 UTC (rev 125)
@@ -19,7 +19,7 @@
 export(qCopula_u)
 export(condSpVine,spCopPredict)
 export(condStVine,stCopPredict)
-export(condStCoVarVine)
+export(condStCoVarVine, condCovariate)
 export(spGaussCopPredict, spGaussLogLik)
 
 # tweaks

Modified: pkg/R/spCopula.R
===================================================================
--- pkg/R/spCopula.R	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/R/spCopula.R	2014-02-14 10:34:29 UTC (rev 125)
@@ -640,7 +640,7 @@
 }
 
 ## dropping a spatial tree, returning a conditional neighbourhood
-dropSpTree <- function(neigh, spCop) {
+dropSpTree <- function(neigh, dataLocs, spCop) {
   u1 <- matrix(NA,nrow(neigh at data),ncol(neigh at data)-1)
   h1 <- matrix(NA,nrow(neigh at distances),ncol(neigh at distances)-1)
 
@@ -649,7 +649,7 @@
                      neigh at distances[,i])
     if (i < ncol(neigh at distances)) {
       h1[,i] <- apply(neigh at index[,c(2,2+i)],1, 
-                   function(x) spDists(neigh at dataLocs[x,])[1,2])
+                   function(x) spDists(dataLocs[x,])[1,2])
     }
   }
   

Modified: pkg/R/spVineCopula.R
===================================================================
--- pkg/R/spVineCopula.R	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/R/spVineCopula.R	2014-02-14 10:34:29 UTC (rev 125)
@@ -190,13 +190,9 @@
 
 # interpolation
 
-spCopPredict.expectation <- function(data, spVine, margin, ..., stop.on.error=F) {
-  stopifnot(is.function(margin$q))
+spCopPredict.expectation <- function(predNeigh, dataLocs, predLocs, spVine, margin, ..., stop.on.error=F) {
+  dists <- calcSpTreeDists(predNeigh, dataLocs, length(spVine at spCop))
   
-  predNeigh <- data[[1]]
-  
-  dists <- calcSpTreeDists(predNeigh, data[[2]], length(spVine at spCop))
-  
   predMean <- NULL
   
   pb <- txtProgressBar(0,nrow(predNeigh at data), 0, width=getOption("width")-10, style=3)
@@ -217,7 +213,6 @@
   }
   close(pb)
   
-  predLocs <- data[[3]]
   if ("data" %in% slotNames(predLocs)) {
     res <- predNeigh at predLocs
     res at data[["expect"]] <- predMean
@@ -229,12 +224,9 @@
   }
 }
 
-spCopPredict.quantile <- function(data, spVine, margin, p=0.5) {
-  stopifnot(is.function(margin$q))
+spCopPredict.quantile <- function(predNeigh, dataLocs, predLocs, spVine, margin, p=0.5) {
+  dists <- calcSpTreeDists(predNeigh, dataLocs, length(spVine at spCop))
   
-  predNeigh <- data[[1]]
-  dists <- calcSpTreeDists(predNeigh, data[[2]], length(spVine at spCop))
-  
   predQuantile <- NULL
   pb <- txtProgressBar(0, nrow(predNeigh at data), 0, width=getOption("width")-10, style=3)
   for(i in 1:nrow(predNeigh at data)) { # i <-1
@@ -255,7 +247,6 @@
   }
   close(pb)
   
-  predLocs <- data[[3]]
   if ("data" %in% slotNames(predLocs)) {
     res <- predLocs
     res at data[[paste("quantile.",p,sep="")]] <- predQuantile
@@ -267,13 +258,15 @@
   }
 }
 
-spCopPredict <- function(data, spVine, margin, method="quantile", p=0.5, ...) {
-  stopifnot(is.list(data))
-  stopifnot(length(data)==3)
+spCopPredict <- function(predNeigh, dataLocs, predLocs, spVine, margin, method="quantile", p=0.5, ...) {
+  stopifnot(is.function(margin$q))
+  stopifnot(class(predNeigh) == "neighbourhood")
+  stopifnot(inherits(dataLocs, "Spatial"))
+  stopifnot(inherits(predLocs, "Spatial"))
   
   switch(method,
-         quantile=spCopPredict.quantile(data, spVine, margin, p),
-         expectation=spCopPredict.expectation(data, spVine, margin, ...))
+         quantile=spCopPredict.quantile(predNeigh, dataLocs, predLocs, spVine, margin, p),
+         expectation=spCopPredict.expectation(predNeigh, dataLocs, predLocs, spVine, margin, ...))
 }
 
 # draw from a spatial vine

Modified: pkg/R/spatio-temporalPreparation.R
===================================================================
--- pkg/R/spatio-temporalPreparation.R	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/R/spatio-temporalPreparation.R	2014-02-14 10:34:29 UTC (rev 125)
@@ -29,7 +29,7 @@
   colnames(data) <- paste(paste("N", (0+prediction):dimDists[2], sep=""), var, sep=".")
   
   if(length(coVar)>0)
-    colnames(data)[dimDists[2] + 1:length(coVar)] <- paste("N0", coVar)
+    colnames(data)[ncol(data) + 1 - (length(coVar):1)] <- paste("N0", coVar)
   
   if (anyDuplicated(rownames(data))>0)
     rownames <- 1:length(rownames)
@@ -167,12 +167,15 @@
   dimStNeigh <- dim(stNeigh at distances)
   corMat <- matrix(NA, dimStNeigh[1], dimStNeigh[2])
   
+  pb <- txtProgressBar(0, dimStNeigh[2], style=3)
   for (i in 1:dimStNeigh[2]) {
     boolNA <- is.na(stNeigh at data[[1]]) | is.na(stNeigh at data[[1+i]])
     stNeigh at distances[boolNA,i,] <- c(NA,NA)
     tLag <- -1*stNeigh at distances[!boolNA,i,2][1]+1
     corMat[!boolNA,i] <- stDepFun(stNeigh at distances[!boolNA,i,1], tLag)
+    setTxtProgressBar(pb, i)
   }
+  close(pb)
   
   highCorMat <- t(apply(corMat, 1, function(x) order(x, na.last=TRUE, decreasing=TRUE)[1:n]))
   nrCM <- nrow(highCorMat)
@@ -206,8 +209,8 @@
 }
 
 ## to be redone
-calcStNeighBins <- function(data, var="uniPM10", nbins=9, t.lags=-(0:2),
-                            boundaries=NA, cutoff=NA, cor.method="fasttau") {
+# calcStNeighBins <- function(data, var="uniPM10", nbins=9, t.lags=-(0:2),
+#                             boundaries=NA, cutoff=NA, cor.method="fasttau") {
 #   dists <- data at distances[,,1]
 #   
 #   corFun <- switch(cor.method,
@@ -310,11 +313,11 @@
 #   res <- list(np=np, meanDists = meanDists, lagCor=moa, lagData=lagData)
 #   attr(res,"cor.method") <- switch(cor.method, fasttau="kendall", cor.method)
 #   return(res)
-}
+# }
+# 
+# setMethod(calcBins, signature="stNeighbourhood", calcStNeighBins)
 
-setMethod(calcBins, signature="stNeighbourhood", calcStNeighBins)
 
-
 # instances: number  -> number of randomly choosen temporal intances
 #            NA      -> all observations
 #            other   -> temporal indexing as in spacetime/xts, the parameter t.lags is set to 0 in this case.

Modified: pkg/R/stCoVarVineCopula.R
===================================================================
--- pkg/R/stCoVarVineCopula.R	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/R/stCoVarVineCopula.R	2014-02-14 10:34:29 UTC (rev 125)
@@ -166,6 +166,25 @@
   return(condVineFun)
 }
 
+# condition the covariate on the central location
+condCovariate <- function(stNeigh, coVarCop) {
+  stopifnot(length(stNeigh at coVar) == 1)
+  
+  nrNeigh <- nrow(stNeigh at index)
+  ncData <- ncol(stNeigh at data)
+  
+  vddu <- numeric(nrNeigh)
+  uv <- as.matrix(stNeigh at data[,c(1,ncData)])
+  stInd <- stNeigh at index[,1,]
+  
+  for (i in 1:nrNeigh) {
+    vddu[i] <- dduCopula(uv[i,], coVarCop(stInd[i,]))
+  }
+  
+  return(vddu)
+}
+
+
 ## interpolation ##
 ###################
 # 

Modified: pkg/R/stCopula.R
===================================================================
--- pkg/R/stCopula.R	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/R/stCopula.R	2014-02-14 10:34:29 UTC (rev 125)
@@ -177,4 +177,46 @@
 
 setMethod("ddvCopula", signature("numeric","stCopula"), 
           function(u, copula, ...) ddvStCopula(matrix(u,ncol=2), copula, ...))
-setMethod("ddvCopula", signature("matrix","stCopula"), ddvStCopula)
\ No newline at end of file
+setMethod("ddvCopula", signature("matrix","stCopula"), ddvStCopula)
+
+# dropping a sptio-temporal tree
+dropStTree <- function (stNeigh, dataLocs, stCop) {
+  stopifnot(class(stNeigh) == "stNeighbourhood")
+  
+  u0 <- as.matrix(stNeigh at data)
+  h0 <- stNeigh at distances
+  u1 <- matrix(NA, nrow(u0), ncol(u0)-1-length(stNeigh at coVar))
+  h1 <- array(dim = c(nrow(u0), ncol(h0)-1, 2))
+  
+  pb <- txtProgressBar(0,dim(h0)[2],style=3)
+  for (i in 1:dim(h0)[2]) {
+    u1[,i] <- dduCopula(u0[, c(1, i + 1)], stCop, h = h0[, i, ])
+    if (i < ncol(h0)) {
+      h1[,i,1] <- apply(stNeigh at index[, c(1, i + 1), 1], 1, 
+                        function(x) spDists(dataLocs at sp[x, ])[1, 2])
+      h1[,i,2] <- apply(stNeigh at index[, c(1, i + 1), 2], 1, 
+                        function(x) diff(x))
+    }
+    setTxtProgressBar(pb, i)
+  }
+  close(pb)
+  
+#   # add covariate to the conditioned neighbourhood?
+#   if (length(stNeigh at coVar) > 0)
+#     u1[,ncol(u0)-(1:length(stNeigh at coVar))] <- u0[,ncol(u0) + 1 - (1:length(stNeigh at coVar))]
+  
+  varSplit <- strsplit(stNeigh at var, "|", fixed = TRUE)[[1]]
+  cond <- suppressWarnings(as.numeric(varSplit[length(varSplit)]))
+  
+  if (is.na(cond)) {
+#     coVar <- paste(stNeigh at coVar, "|0", sep = "")
+    cond <- paste(stNeigh at var, "|0", sep = "")
+  }
+  else {
+#     coVar <- stNeigh at coVar
+    cond <- paste(stNeigh at var, cond + 1, sep = "")
+  }
+  
+  return(stNeighbourhood(data = u1, distances = h1, index = stNeigh at index[, -1, ],
+                         var = cond, prediction = stNeigh at prediction))
+}
\ No newline at end of file

Modified: pkg/R/stVineCopula.R
===================================================================
--- pkg/R/stVineCopula.R	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/R/stVineCopula.R	2014-02-14 10:34:29 UTC (rev 125)
@@ -136,10 +136,7 @@
 ## interpolation ##
 ###################
 
-stCopPredict.expectation <- function(data, stVine, margin, ..., stop.on.error=F) {
-  stopifnot(is.function(margin$q))
-  
-  predNeigh <- data[[1]]
+stCopPredict.expectation <- function(predNeigh, dataST, predST, stVine, margin, ..., stop.on.error=F) {
   dists <- predNeigh at distances
   
   predMean <- NULL
@@ -157,24 +154,19 @@
                     ePred$abs.error, " for location ",i,".")
     predMean <- c(predMean, ePred$value)
   }
-  
-  predLocs <- data[[3]]
-  
-  if ("data" %in% slotNames(predLocs)) {
-    res <- predLocs
+    
+  if ("data" %in% slotNames(predST)) {
+    res <- predST
     res at data[["expect"]] <- predMean
     return(res)
   } else {
     predMean <- data.frame(predMean)
     colnames(predMean) <- "expect"
-    return(addAttrToGeom(predLocs, predMean, match.ID=FALSE))
+    return(addAttrToGeom(predST, predMean, match.ID=FALSE))
   }
 }
 
-stCopPredict.quantile <- function(data, stVine, margin, p=0.5) {
-  stopifnot(is.function(margin$q))
-  
-  predNeigh <- data[[1]]
+stCopPredict.quantile <- function(predNeigh, dataST, predST, stVine, margin, p=0.5) {
   dists <- predNeigh at distances
   
   predQuantile <- NULL
@@ -193,68 +185,26 @@
     
     predQuantile <- c(predQuantile, margin$q(xVals[lower]+xRes))
   }
-  
-  predLocs <- data[[3]]
-  
-  if ("data" %in% slotNames(predLocs)) {
-    res <- predLocs
+
+  if ("data" %in% slotNames(predST)) {
+    res <- predST
     res at data[[paste("quantile.",p,sep="")]] <- predQuantile
     return(res)
   } else {
     predQuantile <- data.frame(predQuantile)
     colnames(predQuantile) <- paste("quantile.",p,sep="")
-    return(addAttrToGeom(predLocs, predQuantile, match.ID=FALSE))
+    return(addAttrToGeom(predST, predQuantile, match.ID=FALSE))
   }
 }
 
-stCopPredict <- function(data, stVine, margin, method="quantile", p=0.5, ...) {
-  stopifnot(is.list(data))
-  stopifnot(length(data)==3)
+stCopPredict <- function(predNeigh, dataST, predST, stVine, margin, method="quantile", p=0.5, ...) {
+  stopifnot(class(predNeigh) == "stNeighbourhood")
+  stopifnot(inherits(dataST, "ST"))
+  stopifnot(inherits(predST, "ST"))
+  stopifnot(class(stVine) == "stVineCopula")
+  stopifnot(is.function(margin$q))
   
   switch(method,
-         quantile=stCopPredict.quantile(data, stVine, margin, p),
-         expectation=stCopPredict.expectation(data, stVine, margin, ...))
-}
-
-dropStTree <- function (data, stCop) {
-  stopifnot(is.list(data))
-  stopifnot(length(data) == 2)
-  
-  neigh <- data[[1]]
-  stopifnot(class(neigh) == "stNeighbourhood")
-  
-  u0 <- as.matrix(neigh at data)
-  h0 <- neigh at distances
-  u1 <- matrix(NA, nrow(u0), ncol(u0)-1)
-  h1 <- array(dim = c(nrow(u0), ncol(h0)-1, 2))
-  cat("[Margin ")
-  for (i in 1:dim(h0)[2]) {
-    cat(i, ", ",sep="")
-    u1[,i] <- dduCopula(u0[, c(1, i + 1)], stCop, h = h0[, i, ])
-    if (i < ncol(h0)) {
-      h1[,i,1] <- apply(neigh at index[, c(1, i + 1), 1], 1, 
-                        function(x) spDists(data[[2]]@sp[x, ])[1, 2])
-      h1[,i,2] <- apply(neigh at index[, c(1, i + 1), 2], 1, 
-                        function(x) diff(x))
-    }
-  }
-  cat("]\n")
-  
-  if (length(neigh at coVar) > 0)
-    u1[,ncol(u0)-(1:length(neigh at coVar))] <- u0[,ncol(u0) + 1 - (1:length(neigh at coVar))]
-  
-  varSplit <- strsplit(neigh at var, "|", fixed = TRUE)[[1]]
-  cond <- suppressWarnings(as.numeric(varSplit[length(varSplit)]))
-  
-  if (is.na(cond)) {
-    coVar <- paste(neigh at coVar, "|0", sep = "")
-    cond <- paste(neigh at var, "|0", sep = "")
-  }
-  else {
-    coVar <- neigh at coVar
-    cond <- paste(neigh at var, cond + 1, sep = "")
-  }
-  
-  return(stNeighbourhood(data = u1, distances = h1, index = neigh at index[, -1, ],
-                         var = cond, coVar = coVar, prediction = neigh at prediction))
+         quantile=stCopPredict.quantile(predNeigh, dataST, predST, stVine, margin, p),
+         expectation=stCopPredict.expectation(predNeigh, dataST, predST, stVine, margin, ...))
 }
\ No newline at end of file

Modified: pkg/man/calcBins.Rd
===================================================================
--- pkg/man/calcBins.Rd	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/man/calcBins.Rd	2014-02-14 10:34:29 UTC (rev 125)
@@ -1,11 +1,8 @@
 \name{calcBins}
 \alias{calcBins}
-
 \alias{calcBins-methods}
 \alias{calcBins,Spatial-method}
 \alias{calcBins,STFDF-method}
-\alias{calcBins,neighbourhood-method}
-\alias{calcBins,stNeighbourhood-method}
 
 \title{
 A function calculating the spatial/spatio-temporal bins

Added: pkg/man/condCovariate.Rd
===================================================================
--- pkg/man/condCovariate.Rd	                        (rev 0)
+++ pkg/man/condCovariate.Rd	2014-02-14 10:34:29 UTC (rev 125)
@@ -0,0 +1,45 @@
+\name{condCovariate}
+\alias{condCovariate}
+
+\title{
+Conditioning of a Covariate
+}
+\description{
+Conditions the covariate on the central location in a \code{\linkS4class{stCoVarVineCopula}}.
+}
+\usage{
+condCovariate(stNeigh, coVarCop)
+}
+
+\arguments{
+  \item{stNeigh}{a spatio-temporal neighbourhood \code{\linkS4class{stNeighbourhood}} with a covariate.}
+  \item{coVarCop}{a function taking spatial and temporal indices and returning a \code{\linkS4class{copula}} object describing the dependence between variable of interest and covariate at this location in space and time.}
+}
+
+\value{A vector of conditioned data, i.e. covariate|variable of interest}
+
+\author{
+Benedikt Graeler
+}
+
+\seealso{\code{\linkS4class{stNeighbourhood}}}
+
+\examples{
+library(sp)
+library(spacetime)
+
+sp <- SpatialPoints(matrix(c(181000,181100,333500,333600),2))
+time <- Sys.time()+60*60*24*c(0,1,2)
+data <- data.frame(var=runif(6))
+data$coVar <- invdduCopula(data$var, gumbelCopula(7), runif(6)) 
+
+stData <- STFDF(sp, time, data)
+stQuerry <- STF(SpatialPoints(matrix(c(181000,181200,333600,333600),2)),
+                time[2:3])
+
+stNeigh <- getStNeighbours(stData=stData, ST=stQuerry, 
+                           spSize=3, t.lags=-(0:1),
+                           var="var", coVar="coVar", prediction=TRUE)
+
+condCovariate(stNeigh, function(x) gumbelCopula(7))
+}

Modified: pkg/man/dropSpTree.Rd
===================================================================
--- pkg/man/dropSpTree.Rd	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/man/dropSpTree.Rd	2014-02-14 10:34:29 UTC (rev 125)
@@ -7,19 +7,16 @@
 \description{
 A spatial tree is dropped in order to fit the following spatial copula.
 }
-\usage{dropSpTree(neigh, spCop)}
+\usage{dropSpTree(neigh, dataLocs, spCop)}
 
 \arguments{
-  \item{neigh}{
-the current \code{\linkS4class{neighbourhood}}
+  \item{neigh}{the current \code{\linkS4class{neighbourhood}}}
+  \item{dataLocs}{the locations of the data already used to generate \code{neigh}}
+  \item{spCop}{the current spatial copula performing the conditioning}
 }
-  \item{spCop}{
-the current spatial copula performing the conditioning
-}
-}
 
 \value{
-A conditioned \code{\linkS4class{neighbourhood}} of dimension 1 less.
+A conditioned \code{\linkS4class{neighbourhood}} of dimension 1 smaller than the current one.
 }
 
 \author{

Modified: pkg/man/dropStTree.Rd
===================================================================
--- pkg/man/dropStTree.Rd	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/man/dropStTree.Rd	2014-02-14 10:34:29 UTC (rev 125)
@@ -5,18 +5,15 @@
 Drops a spatio-temporal tree
 }
 \description{
-A spatio-temporal tree is dropped in order to fit the following copula.
+A spatio-temporal tree is dropped in order to fit/evaluate the following copula.
 }
-\usage{dropStTree(neigh, stCop)}
+\usage{dropStTree(stNeigh, dataLocs, stCop)}
 
 \arguments{
-  \item{neigh}{
-the current spatio-temporal \code{\linkS4class{stNeighbourhood}}
+  \item{stNeigh}{the current spatio-temporal \code{\linkS4class{stNeighbourhood}}}
+  \item{dataLocs}{the data locations (the same as used for the generation of the spatio-temporal neighbourhood).}
+  \item{stCop}{the current spatio-temporal copula performing the conditioning}
 }
-  \item{stCop}{
-the current spatio-temporal copula performing the conditioning
-}
-}
 
 \value{
 A conditioned spatio-temporal \code{\linkS4class{stNeighbourhood}} of dimension 1 less.
@@ -27,7 +24,7 @@
 }
 
 \seealso{
-\code{\linkS4class{stNeighbourhood}}
+\code{\linkS4class{stNeighbourhood}} and \code{\link{dropSpTree}}
 }
 
 \keyword{ spatio-temporal }
\ No newline at end of file

Modified: pkg/man/neighbourhood-class.Rd
===================================================================
--- pkg/man/neighbourhood-class.Rd	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/man/neighbourhood-class.Rd	2014-02-14 10:34:29 UTC (rev 125)
@@ -3,8 +3,8 @@
 \docType{class}
 \alias{neighbourhood-class}
 \alias{names,neighbourhood-method}
-\alias{[[,neighbourhood,ANY,ANY-method}
-\alias{[[,neighbourhood,numeric,missing-method}
+\alias{[,neighbourhood,numeric,ANY,ANY-method}
+\alias{calcBins,neighbourhood-method}
 
 \title{Class \code{neighbourhood}}
 \description{A class representing a local spatial neighbourhood.}
@@ -26,7 +26,8 @@
   \describe{
     \item{names}{\code{signature(x = "neighbourhood")}: provides the variable names of the neighbourhood. }
     \item{show}{\code{signature(object = "neighbourhood")}: a brief description of the characteristics of the neighbourhood.}
-    \item{[[}{subsets the selection of neighbourhoods returning a subset of these ("column wise")}
+    \item{[}{\code{signature(x = "neighbourhood", i = "numeric", j = "missing")}: subsets the selection of neighbourhoods returning a subset of these ("column wise")}
+    \item{calcBins}{\code{signature(data = "neighbourhood")}: calculates bins from an existing neighbourhood for repeated application of spatio-temporal trees in a spatio-temporal vine copula.}
 	 }
 }
 \author{

Modified: pkg/man/spCopPredict.Rd
===================================================================
--- pkg/man/spCopPredict.Rd	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/man/spCopPredict.Rd	2014-02-14 10:34:29 UTC (rev 125)
@@ -8,10 +8,13 @@
 A spatial vine copula is used to predict values at unobserved locations conditioned on observations of a local neighbourhood.
 }
 \usage{
-spCopPredict(predNeigh, spVine, margin, method = "quantile", p = 0.5, ...)
+spCopPredict(predNeigh, dataLocs, predLocs, spVine, margin,
+             method = "quantile", p = 0.5, ...)
 }
 \arguments{
   \item{predNeigh}{the \code{\linkS4class{neighbourhood}} used for prediction, its slot \code{prediction} must be \code{TRUE}.}
+  \item{dataLocs}{some \code{\linkS4class{Spatial}} class providing the data for the prediction.}
+  \item{predLocs}{some \code{\linkS4class{Spatial}} class providing the prediction locations.}
   \item{spVine}{the spatial vine copula describing the spatial dependence}
   \item{margin}{the marginal distribution as a list with entries named "d" for the density function (PDF), "q" for the quantile function and "p" for cumulative distribution function (CDF).}
   \item{method}{one of \code{"quantile"} or \code{"expectation"} denoting the type of predictor.}
@@ -66,7 +69,7 @@
   qlnorm(x,mean(log(meuse$zinc)),sd(log(meuse$zinc)))
 }
 
-predMedian <- spCopPredict(list(predMeuseNeigh, dataLocs, predLocs),
+predMedian <- spCopPredict(predMeuseNeigh, dataLocs, predLocs,
                            spVineCop, list(q=qMar), "quantile", p=0.5)
 
 \dontrun{

Modified: pkg/man/spGaussLogLik.Rd
===================================================================
--- pkg/man/spGaussLogLik.Rd	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/man/spGaussLogLik.Rd	2014-02-14 10:34:29 UTC (rev 125)
@@ -2,28 +2,23 @@
 \alias{spGaussLogLik}
 
 \title{
-Density evalaution for a spatial Gaussian Copula
+Density evaluation for a spatial Gaussian Copula
 }
 \description{
 Evaluates the density for a spatial Gaussian Copula.
 }
 \usage{
-spGaussLogLik(corFun, neigh, log = T)
+spGaussLogLik(corFun, neigh, dataLocs, log = T)
 }
 
 \arguments{
-  \item{corFun}{
-A valid correlogram (i.e. producing a valid correlation matrix; e.g. based on a variogram).
+  \item{corFun}{A valid correlogram (i.e. producing a valid correlation matrix; e.g. based on a variogram).}
+  \item{neigh}{A \code{\linkS4class{neighbourhood}} object to be evaluated.}
+  \item{dataLocs}{The same \code{\linkS4class{Spatial}} object used to generate \code{neigh}.}
+  \item{log}{Should the log-likelihood be returned?}
 }
-  \item{neigh}{
-A \code{\linkS4class{neighbourhood}} object to be evaluated.
-}
-  \item{log}{
-Should the log-likelihood be returned?
-}
-}
 \details{
-Evaluates the density for all neioghbourhoods in \code{neigh} and returns the (log)-likelihood.
+Evaluates the density for all neighbourhoods in \code{neigh} and returns the (log)-likelihood.
 }
 \value{
 The (log)-likelihood value.

Modified: pkg/man/stCopPredict.Rd
===================================================================
--- pkg/man/stCopPredict.Rd	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/man/stCopPredict.Rd	2014-02-14 10:34:29 UTC (rev 125)
@@ -2,16 +2,18 @@
 \alias{stCopPredict}
 
 \title{
-spatio-temporal prediction based on a spatio-temporal vine copula
+Spatio-Temporal Prediction based on a Spatio-Temporal Vine Copula
 }
 \description{
 A spatio-temporal vine copula is used to predict values at unobserved spatio-temporal locations conditioned on observations of a local spatio-temporal neighbourhood.
 }
 \usage{
-stCopPredict(predNeigh, stVine, margin, method = "quantile", p = 0.5, ...)
+stCopPredict(predNeigh, dataST, predST, stVine, margin, method = "quantile", p = 0.5, ...)
 }
 \arguments{
   \item{predNeigh}{the \code{\linkS4class{neighbourhood}} used for prediction, its slot \code{prediction} must be \code{TRUE}.}
+  \item{dataST}{the same \code{\linkS4class{ST}} object as used in the generation of \code{predNeigh} providing the data for interpolation.}
+  \item{predST}{the same \code{\linkS4class{ST}} object as used in the generation of \code{predNeigh} providing the prediction locations for interpolation.}
   \item{stVine}{the spatio-temporal vine copula describing the spatio-temporal dependence}
   \item{margin}{the marginal distribution as a list with entries named "d" for the density function (PDF), "q" for the quantile function and "p" for cumulative distribution function (CDF).}
   \item{method}{one of \code{"quantile"} or \code{"expectation"} denoting the type of predictor.}
@@ -62,7 +64,7 @@
 stNeigh <- getStNeighbours(stData=stData, ST=stQuerry, prediction=TRUE, spSize=3,
                            t.lags=-(0:1))
 
-stCopPredict(list(stNeigh, stData, stQuerry), stVineCop, list(q=qunif), "quantile", 0.5)
+stCopPredict(stNeigh, stData, stQuerry, stVineCop, list(q=qunif), "quantile", 0.5)
 }
 
 \keyword{ distribution }

Modified: pkg/man/stNeighbourhood-class.Rd
===================================================================
--- pkg/man/stNeighbourhood-class.Rd	2014-02-13 20:05:42 UTC (rev 124)
+++ pkg/man/stNeighbourhood-class.Rd	2014-02-14 10:34:29 UTC (rev 125)
@@ -2,27 +2,39 @@
 \Rdversion{1.1}
 \docType{class}
 \alias{stNeighbourhood-class}
+\alias{[,stNeighbourhood,numeric,ANY,ANY-method}
+\alias{names,stNeighbourhood-method}
+\alias{show,stNeighbourhood-method}
 
+
 \title{Class \code{"stNeighbourhood"}}
 \description{
 An object representing a set of spatio-temporal neighbourhoods including data, spatio-temporal indices and spatio-temporal distances.
 }
+
 \section{Objects from the Class}{
 Objects can be created by calls of the form \code{new("stNeighbourhood", ...)} or through the simplified call to \code{\link{getStNeighbours}}.
 }
+
 \section{Slots}{
   \describe{
     \item{\code{data}:}{Object of class \code{"data.frame"} holding the data of spatio-temporal neighbourhoods. }
-    \item{\code{distances}:}{Object of class \code{"array"} with the following three dimensions: number of neighbourhoods, dimension of each neighbourhood, 2 (spatial and temporal distance).}
-    \item{\code{index}:}{Object of class \code{"array"} with the following three dimensions: number of neighbourhoods, dimension of each neighbourhood, 2 (spatial and temporal index). }
+    \item{\code{distances}:}{Object of class \code{"array"} with the following three dimensions: number of spatio-temporal neighbourhoods, size of each spatio-temporal neighbourhood, 2 (spatial and temporal distance).}
+    \item{\code{index}:}{Object of class \code{"array"} with the following three dimensions: number of spatio-temporal neighbourhoods, size of each spatio-temporal neighbourhood, 2 (spatial and temporal index). }
     \item{\code{var}:}{Object of class \code{"character"}; the name of the variable that is estimated.}
     \item{\code{coVar}:}{Object of class \code{"character"}; the name of the covariate.}
     \item{\code{prediction}:}{Object of class \code{"logical"} whether prediction or fitting takes place. }
   }
 }
+
 \section{Methods}{
-No methods defined with class "stNeighbourhood" in the signature.
+  \describe{
+    \item{[[}{\code{signature(x = "neighbourhood", i = "numeric", j = "missing")}: select distinct rows from the neighbourhood slots.}
+    \item{names}{\code{signature(x = "neighbourhood")}: retrieve the names of the data slot.}
+    \item{show}{\code{signature(object = "neighbourhood")}: print some useful information. }
+   }
 }
+
 \author{
 Benedikt Graeler
 }



More information about the spcopula-commits mailing list