[spcopula-commits] r132 - in pkg: . R data demo man tests/Examples

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Mon Mar 24 20:35:13 CET 2014


Author: ben_graeler
Date: 2014-03-24 20:35:13 +0100 (Mon, 24 Mar 2014)
New Revision: 132

Added:
   pkg/data/EU_RB.RData
   pkg/demo/stCoVarVineCop.R
   pkg/man/EU_RB.Rd
Modified:
   pkg/DESCRIPTION
   pkg/NAMESPACE
   pkg/R/returnPeriods.R
   pkg/R/spCopula.R
   pkg/demo/00Index
   pkg/man/qCopula_u.Rd
   pkg/tests/Examples/spcopula-Ex.Rout.save
Log:
- added demo and smaller data set for JSS paper in preparation
- added qCopula_v along the lines of qCopula_u
- spcopula-Ex.Rout.save has been updated accordingly

Modified: pkg/DESCRIPTION
===================================================================
--- pkg/DESCRIPTION	2014-03-18 11:48:49 UTC (rev 131)
+++ pkg/DESCRIPTION	2014-03-24 19:35:13 UTC (rev 132)
@@ -2,7 +2,7 @@
 Type: Package
 Title: copula driven spatial analysis
 Version: 0.2-0
-Date: 2014-03-18
+Date: 2014-03-24
 Authors at R: c(person("Benedikt", "Graeler", role = c("aut", "cre"),
                     email = "ben.graeler at uni-muenster.de"),
              person("Marius", "Appel",role = "ctb"))
@@ -12,6 +12,7 @@
 LazyLoad: yes
 Depends: copula (>= 0.999-7), VineCopula (>= 1.2-1), R (>= 2.15.0)
 Imports: sp, spacetime (>= 1.0-9), methods
+Suggests: evd
 URL: http://r-forge.r-project.org/projects/spcopula/
 Collate:
   Classes.R

Modified: pkg/NAMESPACE
===================================================================
--- pkg/NAMESPACE	2014-03-18 11:48:49 UTC (rev 131)
+++ pkg/NAMESPACE	2014-03-24 19:35:13 UTC (rev 132)
@@ -16,7 +16,7 @@
 export(fitCopula)
 export(dduCopula,ddvCopula)
 export(invdduCopula, invddvCopula)
-export(qCopula_u)
+export(qCopula_u, qCopula_v)
 export(condSpVine,spCopPredict)
 export(condStVine,stCopPredict)
 export(condStCoVarVine, condCovariate)

Modified: pkg/R/returnPeriods.R
===================================================================
--- pkg/R/returnPeriods.R	2014-03-18 11:48:49 UTC (rev 131)
+++ pkg/R/returnPeriods.R	2014-03-24 19:35:13 UTC (rev 132)
@@ -125,6 +125,44 @@
 setMethod("qCopula_u", signature("copula"), qCopula_u.def)
 
 
+setGeneric("qCopula_v",function(copula,p,v,...) {standardGeneric("qCopula_v")})
+
+qCopula_v.def <- function(copula,p,v, tol=.Machine$double.eps^.5) { # sample=NULL
+  dim <- copula at dimension
+  if(length(p) != length(v)) stop("Length of p and v differ!")
+  
+  params <- NULL
+  for(i in 1:length(p)) { # i <- 1
+    if (v[i] < p[i]) {
+      params <- rbind(params,rep(NA,dim-1))
+    } else {
+      if (dim == 2) {
+        params <- rbind(params, 
+                        optimize(function(u) abs(pCopula(cbind(u, rep(v[i],length(u))),copula)-p[i]),
+                                 c(p,1), tol=tol)$minimum)
+      } else {
+        opt <- optim(par=rep(p[i],dim-1), 
+                     function(uw) abs(pCopula(c(uw[1],v[i],uw[2]), copula)-p[i]), 
+                     lower=rep(p[i],dim-1), upper=rep(1,dim-1), method="L-BFGS-B")
+        params <- rbind(params, opt$par)
+      }
+    }
+  }
+  
+  if (dim == 2) {
+    return(cbind(params,v))
+  } else {
+    if (is.matrix(params))
+      return(cbind(params[,1], v, params[,2]))
+    else
+      return(cbind(params[1], v, params[2]))
+  }
+  
+}
+
+setMethod("qCopula_v", signature("copula"), qCopula_v.def)
+
+
 ## kendall distribution
 
 # empirical default

Modified: pkg/R/spCopula.R
===================================================================
--- pkg/R/spCopula.R	2014-03-18 11:48:49 UTC (rev 131)
+++ pkg/R/spCopula.R	2014-03-24 19:35:13 UTC (rev 132)
@@ -521,7 +521,9 @@
                                                       cor.method, weighted)
   }
   
-  corFun <- function(h, time, tlags=sort(tlags,decreasing=TRUE)) {
+  tlsort <- sort(tlags,decreasing=TRUE)
+  
+  corFun <- function(h, time, tlags=tlsort) {
     t <- which(tlags==time)
     calcKTau[[time]](h)
   }

Added: pkg/data/EU_RB.RData
===================================================================
(Binary files differ)


Property changes on: pkg/data/EU_RB.RData
___________________________________________________________________
Added: svn:mime-type
   + application/octet-stream

Modified: pkg/demo/00Index
===================================================================
--- pkg/demo/00Index	2014-03-18 11:48:49 UTC (rev 131)
+++ pkg/demo/00Index	2014-03-24 19:35:13 UTC (rev 132)
@@ -3,3 +3,4 @@
 pureSpVineCopula  	A demo illustrating the estiamtion of a pure spatial vine copula for a SpatialPointsDataFrame.
 stVineCopFit    A demo corresponding to the vignette estimating a spatio-temporal vine copula.
 tailDepFunctions    A demo illustrating the empirical tail dependece function with parametric parametric tail dependence functions for different families of copulas.
+stCoVarVineCop    A demo redoing the estimation of spatio-temporal covariate vine copula as it is illustrated in a paper to be submitted to JSS. The demo uses a temporal subset and a reduced felxibility yielding a different spatio-temporal covariate vine copula stCVVC.

Added: pkg/demo/stCoVarVineCop.R
===================================================================
--- pkg/demo/stCoVarVineCop.R	                        (rev 0)
+++ pkg/demo/stCoVarVineCop.R	2014-03-24 19:35:13 UTC (rev 132)
@@ -0,0 +1,171 @@
+# demo related to the JSS paper 
+##
+library(evd)
+
+data(EU_RB)
+
+# estimate a GEV at each location for PM10 and EMEP
+parPM10 <- matrix(NA, length(EU_RB at sp), 3)
+parEMEP <- matrix(NA, length(EU_RB at sp), 3)
+
+marPM10 <- matrix(NA, length(EU_RB at sp), 61)
+marEMEP <- matrix(NA, length(EU_RB at sp), 61)
+
+for (loc in 1:length(EU_RB at sp)) {
+  parPM10[loc, 1:3] <- fgev(EU_RB[loc,,"PM10",drop=F]@data[[1]])$estimate
+  parEMEP[loc, 1:3] <- fgev(EU_RB[loc,,"EMEP",drop=F]@data[[1]])$estimate
+  
+  marPM10[loc,] <- pgev(EU_RB[loc,,"PM10",drop=F]@data[[1]], parPM10[loc,1], parPM10[loc,2], parPM10[loc,3])
+  marEMEP[loc,] <- pgev(EU_RB[loc,,"EMEP",drop=F]@data[[1]], parEMEP[loc,1], parEMEP[loc,2], parEMEP[loc,3])
+}
+
+EU_RB at data$marPM10 <- as.vector(marPM10)
+EU_RB at data$marEMEP <- as.vector(marEMEP)
+
+########################################
+## correlation between EMEP and PM10? ##
+########################################
+
+# monCor <- NULL
+# monCop <- NULL
+# for(month in c("2005-01", "2005-02", "2005-03", "2005-04",
+#                "2005-05", "2005-06", "2005-07", "2005-08",
+#                "2005-09", "2005-10", "2005-11", "2005-12")) {
+#   
+#   smpl <- cbind(EU_RB_2005[,month,"marPM10"]@data[[1]],
+#                 EU_RB_2005[,month,"marEMEP"]@data[[1]])
+#   bool <- !apply(smpl,1,function(row) any(is.na(row)))
+#   smpl <- smpl[bool,]
+#   
+#   monCor <- c(monCor, VineCopula:::fasttau(smpl[,1], smpl[,2]))
+#   monCop <- append(monCop,list(BiCopSelect(smpl[,1], smpl[,2], familyset=c(2,4))))
+# }
+# 
+# plot(monCor)
+# 
+# table(sapply(monCop, function(x) x$family))
+
+dayCor <- numeric(61)
+for(day in 1:61) {
+  smpl <- cbind(EU_RB[,day, "marPM10"]@data[[1]],
+                EU_RB[,day, "marEMEP"]@data[[1]])
+  bool <- !apply(smpl,1,function(row) any(is.na(row)))
+  smpl <- smpl[bool,]
+  
+  dayCor[day] <- TauMatrix(smpl)[1,2]
+}
+
+weekCor <- numeric(9)
+weekCop <- NULL
+for(week in 1:9) {
+  smpl <- cbind(EU_RB[,pmin((week-1)*7+1:7,61), "marPM10"]@data[[1]],
+                EU_RB[,pmin((week-1)*7+1:7,61), "marEMEP"]@data[[1]])
+  bool <- !apply(smpl,1,function(row) any(is.na(row)))
+  smpl <- smpl[bool,]
+  
+  weekCor[week] <- TauMatrix(smpl)[1,2]
+  weekCop <- append(weekCop,list(BiCopSelect(smpl[,1], smpl[,2], familyset=1:6)))
+}
+
+
+par(mar=c(5.1, 4.1, 4.1,6))
+plot(dayCor, type="l", col="gray", xlab="day in 2005-06-01::2005-07-31", 
+     ylab="Kendall's tau", main="correlation structure of PM10 and EMEP over time")
+points(rep(weekCor,each=7), type="s", col="red")
+segments(0:8*7+1,sapply(weekCop, function(x) x$family)/10, 1:9*7+1, sapply(weekCop, function(x) x$family)/10)
+axis(4,at=1:6/10, labels=c("Gauss", "Student", "Clayton", "Gumbel", "Frank", "Joe"),las=2)
+mtext("copula family",4,4.5)
+
+#############################
+# the paper starts here ... #
+#############################
+
+# define the coVariate Copula function
+coVarCop <- function(stInd) {
+  week <- min(ceiling(stInd[2]/7), 9)
+  copulaFromFamilyIndex(weekCop[[week]]$family, weekCop[[week]]$par, 
+                        weekCop[[week]]$par2)
+}
+
+## spatio-temporal copula
+# binning
+stBins <- calcBins(EU_RB, "marPM10", nbins=20, tlags=-(0:2))
+stDepFun <- fitCorFun(stBins, rep(3, 5), tlags=-(0:4))
+
+
+## 
+fiveColors <- c("#fed976", "#feb24c", "#fd8d3c", "#f03b20", "#bd0026")
+par(mar=c(4.1, 4.1, 2.1, 1.1))
+plot(stBins$meanDists/1000, stBins$lagCor[1,], 
+     ylim=c(0,0.7), xlab="distance [km]", ylab="correlation [Kendall's tau]",
+     col=fiveColors[5])
+points(stBins$meanDists/1000, stBins$lagCor[2,], col=fiveColors[3])
+points(stBins$meanDists/1000, stBins$lagCor[3,], col=fiveColors[1])
+abline(h=0)
+abline(h=0.025,col="grey")
+
+which(tlags==time)
+
+fun1 <- function(x) stDepFun(x*1000, 1, 5:1)
+curve(fun1, 0, 1600, add=T, col=fiveColors[5])
+fun2 <- function(x) stDepFun(x*1000, 2, 5:1)
+curve(fun2, 0, 1600, add=T, col=fiveColors[3])
+fun3 <- function(x) stDepFun(x*1000, 3, 5:1)
+curve(fun3, 0, 1600, add=T, col=fiveColors[1])
+
+legend("topright",c("same day", "1 day before", "2 days before"),
+       lty=1, pch=1, col=fiveColors[c(5,3,1)])
+title("Spatio-Temporal Dependence Structure")
+##
+
+families <- c(normalCopula(), tCopula(),
+              claytonCopula(), frankCopula(), gumbelCopula(), 
+              joeBiCopula())
+
+loglikTau <- loglikByCopulasStLags(stBins, EU_RB, families, stDepFun)
+
+bestFitTau <- lapply(loglikTau, 
+                     function(x) apply(apply(x$loglik[,1:6], 1, rank),
+                                       2, which.max))
+
+bestFitTau
+
+# define the spatio-temporal copula components
+listDists <- NULL
+listDists[[1]] <- stBins$meanDists[sort(unique(c(which(diff(bestFitTau$loglik1)!=0),
+                                                 which(diff(bestFitTau$loglik1)!=0)+1,1,20)))]
+listDists[[2]] <- stBins$meanDists[sort(unique(c(which(diff(bestFitTau$loglik2)!=0),
+                                                 which(diff(bestFitTau$loglik2)!=0)+1,1,20)))]
+listDists[[3]] <- stBins$meanDists[sort(unique(c(which(diff(bestFitTau$loglik3)!=0),
+                                                 which(diff(bestFitTau$loglik3)!=0)+1,1,20)))]
+
+listCops <- NULL
+listCops[[1]] <- families[bestFitTau$loglik1[sort(unique(c(which(diff(bestFitTau$loglik1)!=0),
+                                                           which(diff(bestFitTau$loglik1)!=0)+1,1,20)))]]
+listCops[[2]] <- families[bestFitTau$loglik2[sort(unique(c(which(diff(bestFitTau$loglik2)!=0),
+                                                           which(diff(bestFitTau$loglik2)!=0)+1,1,20)))]]
+listCops[[3]] <- families[bestFitTau$loglik3[sort(unique(c(which(diff(bestFitTau$loglik3)!=0),
+                                                           which(diff(bestFitTau$loglik3)!=0)+1,1,20)))]]
+
+stBiCop <- stCopula(components = listCops, distances = listDists, 
+                    tlags=-c(0:2), stDepFun=stDepFun)
+
+
+## get the neighbours
+stNeigh <- getStNeighbours(EU_RB, spSize=9, var="marPM10", coVar="marEMEP",
+                           tlags=-(0:2), timeSteps=20, min.dist=10)
+stRedNeigh <- reduceNeighbours(stNeigh, stDepFun, 5)
+
+# condition on the spatio-temporal tree
+condData <- dropStTree(stRedNeigh, EU_RB, stBiCop)
+
+# condition the covariate on the observed phenomenon
+condCoVa <- condCovariate(stRedNeigh, coVarCop)
+
+secTreeData <- cbind(condCoVa, as.matrix(condData at data))
+
+vineFit <- fitCopula(vineCopula(6L), secTreeData, method=list(familyset=1:6))
+
+stCVVC <- stCoVarVineCopula(coVarCop, stBiCop, vineFit at copula)
+
+stCVVC
\ No newline at end of file

Added: pkg/man/EU_RB.Rd
===================================================================
--- pkg/man/EU_RB.Rd	                        (rev 0)
+++ pkg/man/EU_RB.Rd	2014-03-24 19:35:13 UTC (rev 132)
@@ -0,0 +1,55 @@
+\name{EU_RB}
+\alias{EU_RB}
+\docType{data}
+\title{
+Daily mean PM10 concentrations over Europe in June and July 2005
+}
+\description{
+Daily mean PM10 concentrations over Europe in June and July 2005
+}
+\usage{data(EU_RB)}
+\format{
+  The format is:
+Formal class 'STSDF' [package "spacetime"] with 5 slots
+  ..@ data   :'data.frame':	11834 obs. of  2 variables:
+  .. ..$ PM10: num [1:11834] 14 9.7 7.8 21.9 11.2 9 11 6.1 7.4 7.4 ...
+  .. ..$ EMEP: num [1:11834] 11.62 5.02 3.94 3.82 7.01 ...
+  ..@ index  : int [1:11834, 1:2] 1 2 3 4 5 6 7 8 9 10 ...
+  ..@ sp     :Formal class 'SpatialPointsDataFrame' [package "sp"] with 5 slots
+  .. .. ..@ data       :'data.frame':	194 obs. of  1 variable:
+  .. .. .. ..$ station_altitude: int [1:194] 525 581 918 560 172 117 665 1137 330 330 ...
+  .. .. ..@ coords.nrs : num(0) 
+  .. .. ..@ coords     : num [1:194, 1:2] 4592866 4761515 4658756 4690954 4799839 ...
+  .. .. .. ..- attr(*, "dimnames")=List of 2
+  .. .. .. .. ..$ : NULL
+  .. .. .. .. ..$ : chr [1:2] "coords.x1" "coords.x2"
+  .. .. ..@ bbox       : num [1:2, 1:2] 2749697 1647732 6412269 4604814
+  .. .. .. ..- attr(*, "dimnames")=List of 2
+  .. .. .. .. ..$ : chr [1:2] "coords.x1" "coords.x2"
+  .. .. .. .. ..$ : chr [1:2] "min" "max"
+  .. .. ..@ proj4string:Formal class 'CRS' [package "sp"] with 1 slots
+  .. .. .. .. ..@ projargs: chr " +proj=laea +lat_0=52 +lon_0=10 +x_0=4321000 +y_0=3210000 +ellps=GRS80 +units=m +no_defs"
+  ..@ time   :An ?xts? object on 2005-06-01/2005-07-31 containing:
+  Data: int [1:61, 1] 5266 5267 5268 5269 5270 5271 5272 5273 5274 5275 ...
+ - attr(*, "dimnames")=List of 2
+  ..$ : NULL
+  ..$ : chr "..1"
+  Indexed by objects of class: [POSIXct,POSIXt] TZ: GMT
+  xts Attributes:  
+ NULL
+  ..@ endTime: POSIXct[1:61], format: "2005-06-02 02:00:00" "2005-06-03 02:00:00" "2005-06-04 02:00:00" ...
+}
+\source{
+Obtained from the european Air Qualtiy airbase http://acm.eionet.europa.eu/databases/airbase/.
+}
+\references{
+http://acm.eionet.europa.eu/databases/airbase/
+
+Graeler, B., L. E. Gerharz, & E. Pebesma (2012): Spatio-temporal analysis and interpolation of PM10 measurements in Europe. ETC/ACM Technical Paper 2011/10, January 2012.
+http://acm.eionet.europa.eu/reports/ETCACM_TP_2011_10_spatio-temp_AQinterpolation
+}
+\examples{
+data(EU_RB)
+str(EU_RB)
+}
+\keyword{datasets}

Modified: pkg/man/qCopula_u.Rd
===================================================================
--- pkg/man/qCopula_u.Rd	2014-03-18 11:48:49 UTC (rev 131)
+++ pkg/man/qCopula_u.Rd	2014-03-24 19:35:13 UTC (rev 132)
@@ -2,14 +2,18 @@
 \alias{qCopula_u}
 \alias{qCopula_u,copula-method}
 
+\alias{qCopula_v}
+\alias{qCopula_v,copula-method}
+
 \title{
-The inverse of a bivariate copula given u
+The inverse of a bivariate copula given u or v
 }
 \description{
-The inverse of a bivariate copula is calculated for a given u.
+The inverse of a bivariate copula is calculated for a given u or v respectively.
 }
 \usage{
 qCopula_u(copula, p, u, ...)
+qCopula_v(copula, p, v, ...)
 }
 \arguments{
   \item{copula}{
@@ -21,6 +25,9 @@
   \item{u}{
 the conditioning variable u
 }
+  \item{v}{
+the conditioning variable v
+}
   \item{\dots}{
 Passed on to \code{\link{optim}} in the background.
 }
@@ -29,7 +36,7 @@
 The evaluation is done numerically using either \code{\link{optim}} or \code{\link{optimise}}.
 }
 \value{
-A matrix having the same number of rows as \code{u} providing u and the other arguments.
+A matrix having the same number of rows as the length of \code{u} or \code{v} respectively.
 }
 \author{
 Benedikt Graeler
@@ -38,6 +45,9 @@
 \examples{
 uv <- qCopula_u(asCopula(c(-1,1)), p=rep(0.9,10), u=runif(10,0.9,1))
 pCopula(uv,asCopula(c(-1,1)))-0.9
+
+uv <- qCopula_v(asCopula(c(-1,1)), p=rep(0.9,10), v=runif(10,0.9,1))
+pCopula(uv,asCopula(c(-1,1)))-0.9
 }
 
 \keyword{ distribution }

Modified: pkg/tests/Examples/spcopula-Ex.Rout.save
===================================================================
--- pkg/tests/Examples/spcopula-Ex.Rout.save	2014-03-18 11:48:49 UTC (rev 131)
+++ pkg/tests/Examples/spcopula-Ex.Rout.save	2014-03-24 19:35:13 UTC (rev 132)
@@ -27,6 +27,51 @@
 > 
 > base::assign(".oldSearch", base::search(), pos = 'CheckExEnv')
 > cleanEx()
+> nameEx("EU_RB")
+> ### * EU_RB
+> 
+> flush(stderr()); flush(stdout())
+> 
+> ### Name: EU_RB
+> ### Title: Daily mean PM10 concentrations over Europe in June and July 2005
+> ### Aliases: EU_RB
+> ### Keywords: datasets
+> 
+> ### ** Examples
+> 
+> data(EU_RB)
+> str(EU_RB)
+Formal class 'STFDF' [package "spacetime"] with 4 slots
+  ..@ data   :'data.frame':	11834 obs. of  2 variables:
+  .. ..$ PM10: num [1:11834] 14 9.7 7.8 21.9 11.2 9 11 6.1 7.4 7.4 ...
+  .. ..$ EMEP: num [1:11834] 11.62 5.02 3.94 3.82 7.01 ...
+  ..@ sp     :Formal class 'SpatialPointsDataFrame' [package "sp"] with 5 slots
+  .. .. ..@ data       :'data.frame':	194 obs. of  1 variable:
+  .. .. .. ..$ station_altitude: int [1:194] 525 581 918 560 172 117 665 1137 330 330 ...
+  .. .. ..@ coords.nrs : num(0) 
+  .. .. ..@ coords     : num [1:194, 1:2] 4592866 4761515 4658756 4690954 4799839 ...
+  .. .. .. ..- attr(*, "dimnames")=List of 2
+  .. .. .. .. ..$ : NULL
+  .. .. .. .. ..$ : chr [1:2] "coords.x1" "coords.x2"
+  .. .. ..@ bbox       : num [1:2, 1:2] 2749697 1647732 6412269 4604814
+  .. .. .. ..- attr(*, "dimnames")=List of 2
+  .. .. .. .. ..$ : chr [1:2] "coords.x1" "coords.x2"
+  .. .. .. .. ..$ : chr [1:2] "min" "max"
+  .. .. ..@ proj4string:Formal class 'CRS' [package "sp"] with 1 slots
+  .. .. .. .. ..@ projargs: chr " +proj=laea +lat_0=52 +lon_0=10 +x_0=4321000 +y_0=3210000 +ellps=GRS80 +units=m +no_defs"
+  ..@ time   :An 'xts' object on 2005-06-01/2005-07-31 containing:
+  Data: int [1:61, 1] 5266 5267 5268 5269 5270 5271 5272 5273 5274 5275 ...
+ - attr(*, "dimnames")=List of 2
+  ..$ : NULL
+  ..$ : chr "..1"
+  Indexed by objects of class: [POSIXct,POSIXt] TZ: GMT
+  xts Attributes:  
+ NULL
+  ..@ endTime: POSIXct[1:61], format: "2005-06-02 02:00:00" "2005-06-03 02:00:00" ...
+> 
+> 
+> 
+> cleanEx()
 > nameEx("asCopula-class")
 > ### * asCopula-class
 > 
@@ -1403,8 +1448,9 @@
 > flush(stderr()); flush(stdout())
 > 
 > ### Name: qCopula_u
-> ### Title: The inverse of a bivariate copula given u
-> ### Aliases: qCopula_u qCopula_u,copula-method
+> ### Title: The inverse of a bivariate copula given u or v
+> ### Aliases: qCopula_u qCopula_u,copula-method qCopula_v
+> ###   qCopula_v,copula-method
 > ### Keywords: distribution multivariate
 > 
 > ### ** Examples
@@ -1414,8 +1460,13 @@
  [1] -5.285787e-09 -1.979502e-10  7.899040e-09 -5.241861e-09  2.531447e-09
  [6]  8.471355e-09 -6.502292e-09 -1.261782e-09  3.313125e-09  7.337630e-09
 > 
+> uv <- qCopula_v(asCopula(c(-1,1)), p=rep(0.9,10), v=runif(10,0.9,1))
+> pCopula(uv,asCopula(c(-1,1)))-0.9
+ [1] -1.033849e-09  4.513519e-09  8.776860e-09  2.134065e-09  3.399305e-09
+ [6]  4.947090e-09  2.469908e-10  4.513539e-09  6.891024e-09 -3.606405e-09
 > 
 > 
+> 
 > cleanEx()
 > nameEx("rankTransform")
 > ### * rankTransform
@@ -2692,7 +2743,7 @@
 > ###
 > options(digits = 7L)
 > base::cat("Time elapsed: ", proc.time() - base::get("ptime", pos = 'CheckExEnv'),"\n")
-Time elapsed:  14.21 0.18 14.52 NA NA 
+Time elapsed:  15.31 0.21 15.71 NA NA 
 > grDevices::dev.off()
 null device 
           1 



More information about the spcopula-commits mailing list