From noreply at r-forge.r-project.org Thu Jan 8 14:19:13 2015 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Thu, 8 Jan 2015 14:19:13 +0100 (CET) Subject: [Vinecopula-commits] r71 - / pkg/R pkg/src Message-ID: <20150108131913.BD28418442E@r-forge.r-project.org> Author: tnagler Date: 2015-01-08 14:19:13 +0100 (Thu, 08 Jan 2015) New Revision: 71 Modified: / pkg/R/BiCopEst.r pkg/R/BiCopSelect.r pkg/R/RVineStructureSelect.r pkg/src/hfunc.c Log: - RVineStructureSelect: correct handling of rotated BBs and Tawns (fit.ACopula, as.RVM) - BiCopSelect, BiCopEst: improved starting values for Tawn MLE - hfunc.c: correct Hfunc1 for Tawns; bound all results to lie in [0,1] Property changes on: ___________________________________________________________________ Modified: svn:ignore - .Rproj.user .Rhistory .RData + .Rproj.user .Rhistory .RData VineCopula.Rproj Modified: pkg/R/BiCopEst.r =================================================================== --- pkg/R/BiCopEst.r 2014-11-21 16:37:23 UTC (rev 70) +++ pkg/R/BiCopEst.r 2015-01-08 13:19:13 UTC (rev 71) @@ -1,435 +1,429 @@ BiCopEst <- -function(u1,u2,family, method="mle", se=FALSE, max.df=30, max.BB=list(BB1=c(5,6),BB6=c(6,6),BB7=c(5,6),BB8=c(6,1)),weights=NA) -{ - # Function that estimates the parameter(s) of the bivatiate copula - #--------------------------------------------------------- - # INPUT: - # u1,u2 Data for which to estimate parameter - # family The array definig the copulas in the pcc copula construction - # OUTPUT: - # theta Estimated Parameters - #---------------------------------------------------------- - # Author: Carlos Almeida - # Update: Ulf Schepsmeier - # Date: 2008-12-08 - # Update date: 2011-05-27 - # Version: 1.1 - #--------------------------------------------------------------- - - # Sicherheitsabfragen - if(is.null(u1)==TRUE || is.null(u2)==TRUE) stop("u1 and/or u2 are not set or have length zero.") - if(length(u1) != length(u2)) stop("Lengths of 'u1' and 'u2' do not match.") - if(length(u1)<2) stop("Number of observations has to be at least 2.") - if(any(u1>1) || any(u1<0)) stop("Data has be in the interval [0,1].") - if(any(u2>1) || any(u2<0)) stop("Data has be in the interval [0,1].") - if(!(family %in% c(0,1,2,3,4,5,6,7,8,9,10,13,14,16,17,18,19,20,23,24,26,27,28,29,30,33,34,36,37,38,39,40,41,51,61,71,104,114,124,134,204,214,224,234))) stop("Copula family not implemented.") - - if(max.df<=2) stop("The upper bound for the degrees of freedom parameter has to be larger than 2.") - if(!is.list(max.BB)) stop("'max.BB' has to be a list.") - if(max.BB$BB1[1] < 0.001) stop("The upper bound for the first parameter of the BB1 copula should be greater than 0.001 (lower bound for estimation).") - if(max.BB$BB1[2] < 1.001) stop("The upper bound for the second parameter of the BB1 copula should be greater than 1.001 (lower bound for estimation).") - if(max.BB$BB6[1] < 1.001) stop("The upper bound for the first parameter of the BB6 copula should be greater than 1.001 (lower bound for estimation).") - if(max.BB$BB6[2] < 1.001) stop("The upper bound for the second parameter of the BB6 copula should be greater than 1.001 (lower bound for estimation).") - if(max.BB$BB7[1] < 1.001) stop("The upper bound for the first parameter of the BB7 copula should be greater than 1.001 (lower bound for estimation).") - if(max.BB$BB7[2] < 0.001) stop("The upper bound for the second parameter of the BB7 copula should be greater than 0.001 (lower bound for estimation).") - if(max.BB$BB8[1] < 1.001) stop("The upper bound for the first parameter of the BB1 copula should be greater than 0.001 (lower bound for estimation).") - if(max.BB$BB8[2] < 0.001 || max.BB$BB8[2] > 1) stop("The upper bound for the second parameter of the BB1 copula should be in the interval [0,1].") - - - if(method!="mle" && method!="itau") stop("Estimation method has to be either 'mle' or 'itau'.") - - if(is.logical(se)==FALSE) stop("'se' has to be a logical variable (TRUE or FALSE).") - - if(method=="itau" && family %in% c(2,7,8,9,10,17,18,19,20,27,28,29,30,37,38,39,40,104,114,124,134,204,214,224,234)) + function(u1,u2,family, method="mle", se=FALSE, max.df=30, max.BB=list(BB1=c(5,6),BB6=c(6,6),BB7=c(5,6),BB8=c(6,1)),weights=NA) { - message("For two parameter copulas the estimation method 'itau' cannot be used. The method is automatically set to 'mle'.") - method="mle" - } - - if(family!=0) - { - #tau <- cor(u1,u2,method="kendall") - tau <- fasttau(u1,u2) - } - + # Function that estimates the parameter(s) of the bivatiate copula + #--------------------------------------------------------- + # INPUT: + # u1,u2 Data for which to estimate parameter + # family The array definig the copulas in the pcc copula construction + # OUTPUT: + # theta Estimated Parameters + #---------------------------------------------------------- + # Author: Carlos Almeida + # Update: Ulf Schepsmeier + # Date: 2008-12-08 + # Update date: 2011-05-27 + # Version: 1.1 + #--------------------------------------------------------------- + + # sanity checks + if(is.null(u1)==TRUE || is.null(u2)==TRUE) stop("u1 and/or u2 are not set or have length zero.") + if(length(u1) != length(u2)) stop("Lengths of 'u1' and 'u2' do not match.") + if(length(u1)<2) stop("Number of observations has to be at least 2.") + if(any(u1>1) || any(u1<0)) stop("Data has be in the interval [0,1].") + if(any(u2>1) || any(u2<0)) stop("Data has be in the interval [0,1].") + if(!(family %in% c(0,1,2,3,4,5,6,7,8,9,10,13,14,16,17,18,19,20,23,24,26,27,28,29,30,33,34,36,37,38,39,40,41,51,61,71,104,114,124,134,204,214,224,234))) stop("Copula family not implemented.") + + if(max.df<=2) stop("The upper bound for the degrees of freedom parameter has to be larger than 2.") + if(!is.list(max.BB)) stop("'max.BB' has to be a list.") + if(max.BB$BB1[1] < 0.001) stop("The upper bound for the first parameter of the BB1 copula should be greater than 0.001 (lower bound for estimation).") + if(max.BB$BB1[2] < 1.001) stop("The upper bound for the second parameter of the BB1 copula should be greater than 1.001 (lower bound for estimation).") + if(max.BB$BB6[1] < 1.001) stop("The upper bound for the first parameter of the BB6 copula should be greater than 1.001 (lower bound for estimation).") + if(max.BB$BB6[2] < 1.001) stop("The upper bound for the second parameter of the BB6 copula should be greater than 1.001 (lower bound for estimation).") + if(max.BB$BB7[1] < 1.001) stop("The upper bound for the first parameter of the BB7 copula should be greater than 1.001 (lower bound for estimation).") + if(max.BB$BB7[2] < 0.001) stop("The upper bound for the second parameter of the BB7 copula should be greater than 0.001 (lower bound for estimation).") + if(max.BB$BB8[1] < 1.001) stop("The upper bound for the first parameter of the BB1 copula should be greater than 0.001 (lower bound for estimation).") + if(max.BB$BB8[2] < 0.001 || max.BB$BB8[2] > 1) stop("The upper bound for the second parameter of the BB1 copula should be in the interval [0,1].") + + if(method!="mle" && method!="itau") stop("Estimation method has to be either 'mle' or 'itau'.") + if(method=="itau" && family %in% c(2,7,8,9,10,17,18,19,20,27,28,29,30,37,38,39,40,104,114,124,134,204,214,224,234)) + { + message("For two parameter copulas the estimation method 'itau' cannot be used. The method is automatically set to 'mle'.") + method="mle" + } + if(is.logical(se)==FALSE) stop("'se' has to be a logical variable (TRUE or FALSE).") + + + ## calculate empirical kendall's tau + if(family!=0) + { + #tau <- cor(u1,u2,method="kendall") + tau <- fasttau(u1,u2) + } + + ## inversion of kendall's tau theta=0 if(family==0) # independent { - theta=0; + theta=0; } else if(family==1) ## Gaussian { - theta <- sin(tau*pi/2) + theta <- sin(tau*pi/2) } else if(family==3 || family==13) ## Clayton { - if(tau<=0) {warning("Clayton copula cannot be used for negatively dependent data."); tau=0.05} - theta <- max(0,2*tau/(1-tau)) + if(tau<=0) {warning("Clayton copula cannot be used for negatively dependent data."); tau=0.05} + theta <- max(0,2*tau/(1-tau)) } else if(family==4 || family==14) ## Gumbel { - if(tau<0) {warning("Gumbel copula cannot be used for negatively dependent data."); tau=0.05} - theta <- max(1,1/(1-tau)) + if(tau<0) {warning("Gumbel copula cannot be used for negatively dependent data."); tau=0.05} + theta <- max(1,1/(1-tau)) } else if(family==5) ## Frank { - theta=Frank.itau.JJ(tau) + theta=Frank.itau.JJ(tau) } else if(family==6 || family==16) ## Joe { - if(tau<=0) {warning("Joe copula cannot be used for negatively dependent data."); tau=0.05} - theta=Joe.itau.JJ(tau) + if(tau<=0) {warning("Joe copula cannot be used for negatively dependent data."); tau=0.05} + theta=Joe.itau.JJ(tau) } else if(family==23 || family==33) { - if(tau>=0) {warning("Rotated Clayton copula cannot be used for positively dependent data."); tau=-0.05} - theta <- (2*tau/(1+tau)) + if(tau>=0) {warning("Rotated Clayton copula cannot be used for positively dependent data."); tau=-0.05} + theta <- (2*tau/(1+tau)) } else if(family==24 || family==34) { - if(tau>0) {warning("Rotated Gumbel copula cannot be used for positively dependent data."); tau=-0.05} - theta <- -(1/(1+tau)) + if(tau>0) {warning("Rotated Gumbel copula cannot be used for positively dependent data."); tau=-0.05} + theta <- -(1/(1+tau)) } else if(family==26 || family==36) { - if(tau>=0) {warning("Rotated Joe copula cannot be used for positively dependent data."); tau=-0.05} - theta=-Joe.itau.JJ(-tau) + if(tau>=0) {warning("Rotated Joe copula cannot be used for positively dependent data."); tau=-0.05} + theta=-Joe.itau.JJ(-tau) } - else if(family %in% c(41,51)){ - theta = ipsA.tau2cpar(tau) - } - else if(family %in% c(61,71)){ - theta=-ipsA.tau2cpar(-tau) - } - + else if(family %in% c(41,51)){ + theta = ipsA.tau2cpar(tau) + } + else if(family %in% c(61,71)){ + theta=-ipsA.tau2cpar(-tau) + } + + ## standard errors for method itau se1=0 if(method=="itau" && se==TRUE) { - p = 2 - n = length(u1) - ec = numeric(n) - u = cbind(u1,u2) - v = matrix(0,n,p*(p-1)/2) - - if(family == 1) tauder = function(x) 2/(pi * sqrt(1-x^2)) - else if(family %in% c(3,13,23,33)) tauder = function(x) 2*(2+x)^(-2) - else if(family %in% c(4,14,24,34)) tauder=function(x) x^(-2) - else if(family == 5) - { - tauder=function(x) - { - f = function(x) x/(exp(x) - 1) - 4/x^2 - 8/x^3 * integrate(f, lower = 0+.Machine$double.eps^0.5, upper = x)$value +4/(x*(exp(x)-1)) - } - } - else if(family %in% c(6,16,26,36)) - { - tauder=function(x) - { - euler=0.5772156649015328606 - -((-2+2*euler+2*log(2)+digamma(1/x)+digamma(1/2*(2+x)/x)+x)/(-2+x)^2)+((-trigamma(1/x)/x^2+trigamma(1/2*(2+x)/x)*(1/(2+x)-(2+x)/(2*x^2))+1)/(-2+x)) - } - } - else if(family %in% c(41,51,61,71)) - { - tauder=function(x) - { - 2*sqrt(pi)*gamma(0.5+x)*(digamma(1+x)-digamma(0.5+x))/gamma(1+x) - } - } - - l <- 1 - for (j in 1:(p-1)) - { - for (i in (j+1):p) - { - for (k in 1:n) - ec[k] <- sum(u[,i] <= u[k,i] & u[,j] <= u[k,j])/n - v[,l] <- 2 * ec - u[,i] - u[,j] - l <- l + 1 - } - } - - if(family == 0) - D = 0 - else if(family %in% c(1,3,4,5,6,13,14,16,41,51)) - D = 1 / tauder(theta) - else if(family %in% c(23,33,24,34,26,36,61,71)) - D = 1 / tauder(-theta) - - - se1 = as.numeric(sqrt(16/n * var(v %*% D))) + p = 2 + n = length(u1) + ec = numeric(n) + u = cbind(u1,u2) + v = matrix(0,n,p*(p-1)/2) + + if(family == 1) tauder = function(x) 2/(pi * sqrt(1-x^2)) + else if(family %in% c(3,13,23,33)) tauder = function(x) 2*(2+x)^(-2) + else if(family %in% c(4,14,24,34)) tauder = function(x) x^(-2) + else if(family == 5) + { + tauder=function(x) + { + f = function(x) x/(exp(x) - 1) + 4/x^2 - 8/x^3 * integrate(f, lower = 0+.Machine$double.eps^0.5, upper = x)$value +4/(x*(exp(x)-1)) + } + } + else if(family %in% c(6,16,26,36)) + { + tauder=function(x) + { + euler=0.5772156649015328606 + -((-2+2*euler+2*log(2)+digamma(1/x)+digamma(1/2*(2+x)/x)+x)/(-2+x)^2)+((-trigamma(1/x)/x^2+trigamma(1/2*(2+x)/x)*(1/(2+x)-(2+x)/(2*x^2))+1)/(-2+x)) + } + } + else if(family %in% c(41,51,61,71)) + { + tauder=function(x) + { + 2*sqrt(pi)*gamma(0.5+x)*(digamma(1+x)-digamma(0.5+x))/gamma(1+x) + } + } + + l <- 1 + for (j in 1:(p-1)) + { + for (i in (j+1):p) + { + for (k in 1:n) + ec[k] <- sum(u[,i] <= u[k,i] & u[,j] <= u[k,j])/n + v[,l] <- 2 * ec - u[,i] - u[,j] + l <- l + 1 + } + } + + if(family == 0) + D = 0 + else if(family %in% c(1,3,4,5,6,13,14,16,41,51)) + D = 1 / tauder(theta) + else if(family %in% c(23,33,24,34,26,36,61,71)) + D = 1 / tauder(-theta) + + + se1 = as.numeric(sqrt(16/n * var(v %*% D))) } + + ## set starting parameters for maximum likelihood estimation + if(method=="mle") + { + theta1=0 + delta=0 + + if(!(family%in%c(2,6,7,8,9,10,17,18,19,20,27,28,29,30,37,38,39,40,104,114,124,134,204,214,224,234))) + { + theta1=theta + } + if(family==2) ## t + { + theta1 <- sin(tau*pi/2) + delta1 <- min(10,(max.df+2)/2 ) # Nehme die Mitte zwischen 2S und max.df So kann man mit dem Startwert auch nicht auerhalb des vom User gesetzten Bereiches sein. + delta = MLE_intern(cbind(u1,u2),c(theta1,delta1),family=family,se=FALSE,max.df,max.BB,cor.fixed=TRUE,weights)$par[2] + } + else if(family==7 || family==17) ## BB1 + { + if(tau<0) + { + print("The BB1 or survival BB1 copula cannot be used for negatively dependent data.") + delta=1.001 + theta1=0.001 + } + else + { + delta=min(1.5,max((max.BB$BB1[2]+1.001)/2,1.001)) + theta1=min(0.5,max((max.BB$BB1[1]+0.001)/2,0.001)) + } + } + else if(family==27 || family==37) ## BB1 + { + if(tau>0) + { + print("The rotated BB1 copulas cannot be used for positively dependent data.") + delta=-1.001 + theta1=-0.001 + } + else + { + delta=max(-1.5,-max((max.BB$BB1[2]+1.001)/2,1.001)) + theta1=max(-0.5,-max((max.BB$BB1[1]+0.001)/2,0.001)) + } + } + else if(family==8 || family==18) ## BB6 + { + if(tau<0) + { + print("The BB6 or survival BB6 copula cannot be used for negatively dependent data.") + delta=1.001 + theta1=1.001 + } + else + { + delta=min(1.5,max((max.BB$BB6[2]+1.001)/2,1.001)) + theta1=min(1.5,max((max.BB$BB6[1]+1.001)/2,1.001)) + } + } + else if(family==28 || family==38) ## BB6 + { + if(tau>0) + { + print("The rotated BB6 copulas cannot be used for positively dependent data.") + delta=-1.001 + theta1=-1.001 + } + else + { + delta=max(-1.5,-max((max.BB$BB6[2]+1.001)/2,1.001)) + theta1=max(-1.5,-max((max.BB$BB6[1]+1.001)/2,1.001)) + } + } + else if(family==9 || family==19) ## BB7 + { + if(tau<0) + { + print("The BB7 or survival BB7 copula cannot be used for negatively dependent data.") + delta=0.001 + theta=1.001 + } + else + { + delta=min(0.5,max((max.BB$BB7[2]+0.001)/2,0.001)) + theta1=min(1.5,max((max.BB$BB7[1]+1.001)/2,1.001)) + } + } + else if(family==29 || family==39) ## BB7 + { + if(tau>0) + { + print("The rotated BB7 copulas cannot be used for positively dependent data.") + delta=-0.001 + theta1=-1.001 + } + else + { + delta=max(-0.5,-max((max.BB$BB7[2]+0.001)/2,0.001)) + theta1=max(-1.5,-max((max.BB$BB7[1]+1.001)/2,1.001)) + } + } + else if(family==10 || family==20) ## BB8 + { + if(tau<0) + { + print("The BB8 or survival BB8 copula cannot be used for negatively dependent data.") + delta=0.001 + theta=1.001 + } + else + { + delta=min(0.5,max((max.BB$BB8[2]+0.001)/2,0.001)) + theta1=min(1.5,max((max.BB$BB8[1]+1.001)/2,1.001)) + } + } + else if(family==30 || family==40) ## BB8 + { + if(tau>0) + { + print("The rotated BB8 copulas cannot be used for positively dependent data.") + delta=-0.001 + theta1=-1.001 + } + else + { + delta=max(-0.5,-max((max.BB$BB8[2]+0.001)/2,0.001)) + theta1=max(-1.5,-max((max.BB$BB8[1]+1.001)/2,1.001)) + } + } + else if(family %in% c(104, 114, 124, 134, 204, 214, 224, 234)){ ## Tawn + + # the folllowing gives a theoretical kendall's tau close to the empirical one + delta = min(abs(tau) + 0.1, 0.999) + theta1 = 1 + 6 * abs(tau) + + # check if data can be modeled by selected family + if(family %in% c(104, 114)) + { + if(tau<0) + { + print("The Tawn or survival Tawn copula cannot be used for negatively dependent data.") + delta=1 + theta1=1.001 + } + } + else if(family %in% c(124, 134)) + { + if(tau>0) + { + print("The rotated Tawn copula cannot be used for positively dependent data.") + delta=1 + theta1=-1.001 + } else theta1=-theta1 + + } + else if(family %in% c(204, 214)) + { + if(tau<0) + { + print("The Tawn2 or survival Tawn2 copula cannot be used for negatively dependent data.") + delta=1 + theta1=1.001 + } + } + else if(family %in% c(224, 234)) + { + if(tau>0) + { + print("The rotated Tawn2 copula cannot be used for positively dependent data.") + delta=1 + theta1=-1.001 + } else theta1=-theta1 + } + } + + ## likelihood optimization + if(family!=0 && family<100) + { + out=MLE_intern(cbind(u1,u2),c(theta1, delta),family=family,se,max.df,max.BB,weights) + theta=out$par + if(se==TRUE) + se1=out$se + } + else if(family!=0 && family>100) # New + { + out=MLE_intern_Tawn(cbind(u1,u2),c(theta1, delta),family=family,se) + theta=out$par + if(se==TRUE) + se1=out$se + } + } + + ## store estimated parameters + out2=list() + if(length(theta)==2) + { + out2$par=theta[1] + out2$par2=theta[2] + } + else + { + out2$par=theta + out2$par2=0 + } + + ## store standard errors (if asked for) + if(se==TRUE) + { + if(length(se1)==2) + { + out2$se=se1[1] + out2$se2=se1[2] + } + else + { + out2$se=se1 + out2$se2=0 + } + } + + ## return results + out2 + } - if(method=="mle") - { - theta1=0 - delta=0 - if(!(family%in%c(2,6,7,8,9,10,17,18,19,20,27,28,29,30,37,38,39,40,104,114,124,134,204,214,224,234))) - { - theta1=theta - } - if(family==2) ## t - { - theta1 <- sin(tau*pi/2) - delta1 <- min(10,(max.df+2)/2 ) # Nehme die Mitte zwischen 2S und max.df So kann man mit dem Startwert auch nicht auerhalb des vom User gesetzten Bereiches sein. - delta = MLE_intern(cbind(u1,u2),c(theta1,delta1),family=family,se=FALSE,max.df,max.BB,cor.fixed=TRUE,weights)$par[2] - } - else if(family==7 || family==17) ## BB1 - { - if(tau<0) - { - print("The BB1 or survival BB1 copula cannot be used for negatively dependent data.") - delta=1.001 - theta1=0.001 - } - else - { - delta=min(1.5,max((max.BB$BB1[2]+1.001)/2,1.001)) - theta1=min(0.5,max((max.BB$BB1[1]+0.001)/2,0.001)) - } - } - else if(family==27 || family==37) ## BB1 - { - if(tau>0) - { - print("The rotated BB1 copulas cannot be used for positively dependent data.") - delta=-1.001 - theta1=-0.001 - } - else - { - delta=max(-1.5,-max((max.BB$BB1[2]+1.001)/2,1.001)) - theta1=max(-0.5,-max((max.BB$BB1[1]+0.001)/2,0.001)) - } - } - else if(family==8 || family==18) ## BB6 - { - if(tau<0) - { - print("The BB6 or survival BB6 copula cannot be used for negatively dependent data.") - delta=1.001 - theta1=1.001 - } - else - { - delta=min(1.5,max((max.BB$BB6[2]+1.001)/2,1.001)) - theta1=min(1.5,max((max.BB$BB6[1]+1.001)/2,1.001)) - } - } - else if(family==28 || family==38) ## BB6 - { - if(tau>0) - { - print("The rotated BB6 copulas cannot be used for positively dependent data.") - delta=-1.001 - theta1=-1.001 - } - else - { - delta=max(-1.5,-max((max.BB$BB6[2]+1.001)/2,1.001)) - theta1=max(-1.5,-max((max.BB$BB6[1]+1.001)/2,1.001)) - } - } - else if(family==9 || family==19) ## BB7 - { - if(tau<0) - { - print("The BB7 or survival BB7 copula cannot be used for negatively dependent data.") - delta=0.001 - theta=1.001 - } - else - { - delta=min(0.5,max((max.BB$BB7[2]+0.001)/2,0.001)) - theta1=min(1.5,max((max.BB$BB7[1]+1.001)/2,1.001)) - } - } - else if(family==29 || family==39) ## BB7 - { - if(tau>0) - { - print("The rotated BB7 copulas cannot be used for positively dependent data.") - delta=-0.001 - theta1=-1.001 - } - else - { - delta=max(-0.5,-max((max.BB$BB7[2]+0.001)/2,0.001)) - theta1=max(-1.5,-max((max.BB$BB7[1]+1.001)/2,1.001)) - } - } - else if(family==10 || family==20) ## BB8 - { - if(tau<0) - { - print("The BB8 or survival BB8 copula cannot be used for negatively dependent data.") - delta=0.001 - theta=1.001 - } - else - { - delta=min(0.5,max((max.BB$BB8[2]+0.001)/2,0.001)) - theta1=min(1.5,max((max.BB$BB8[1]+1.001)/2,1.001)) - } - } - else if(family==30 || family==40) ## BB8 - { - if(tau>0) - { - print("The rotated BB8 copulas cannot be used for positively dependent data.") - delta=-0.001 - theta1=-1.001 - } - else - { - delta=max(-0.5,-max((max.BB$BB8[2]+0.001)/2,0.001)) - theta1=max(-1.5,-max((max.BB$BB8[1]+1.001)/2,1.001)) - } - } - else if(family==104 || family==114) - { - if(tau<0) - { - print("The Tawn or survival Tawn copula cannot be used for negatively dependent data.") - delta=1 - theta1=1.001 - } - else - { - delta=0.5 # psi1 - theta1=2 - } - } - else if(family==124 || family==134) - { - if(tau>0) - { - print("The rotated Tawn copula cannot be used for positively dependent data.") - delta=1 - theta1=-1.001 - } - else - { - delta=0.5 # psi1 - theta1=-2 - } - } - else if(family==204 || family==214) - { - if(tau<0) - { - print("The Tawn2 or survival Tawn2 copula cannot be used for negatively dependent data.") - delta=1 - theta1=1.001 - } - else - { - delta=0.5 # psi1 - theta1=2 - } - } - else if(family==224 || family==234) - { - if(tau>0) - { - print("The rotated Tawn2 copula cannot be used for positively dependent data.") - delta=1 - theta1=-1.001 - } - else - { - delta=0.5 # psi1 - theta1=-2 - } - } - - if(family!=0 && family<100) - { - out=MLE_intern(cbind(u1,u2),c(theta1, delta),family=family,se,max.df,max.BB,weights) - theta=out$par - if(se==TRUE) - se1=out$se - } - else if(family!=0 && family>100) # New - { - out=MLE_intern_Tawn(cbind(u1,u2),c(theta1, delta),family=family,se) - theta=out$par - if(se==TRUE) - se1=out$se - } - } - - - out2=list() - if(length(theta)==2) - { - out2$par=theta[1] - out2$par2=theta[2] - } - else - { - out2$par=theta - out2$par2=0 - } - if(se==TRUE) - { - if(length(se1)==2) - { - out2$se=se1[1] - out2$se2=se1[2] - } - else - { - out2$se=se1 - out2$se2=0 - } - } - - return(out2) -} - - - Frank.itau.JJ<-function(tau) { - a<-1 - if(tau<0) - { - a<- -1 - tau<- -tau - } - f = function(x) - { - x/(exp(x) - 1) - } - tauF=function(x) 1 - 4/x + 4/x^2 * integrate(f, lower = 0+.Machine$double.eps^0.5, upper = x)$value - v<-uniroot(function(x) tau - tauF(x) ,lower=0,upper=500, tol = .Machine$double.eps^0.5)$root - return(a*v) + a<-1 + if(tau<0) + { + a<- -1 + tau<- -tau + } + f = function(x) + { + x/(exp(x) - 1) + } + tauF=function(x) 1 - 4/x + 4/x^2 * integrate(f, lower = 0+.Machine$double.eps^0.5, upper = x)$value + v<-uniroot(function(x) tau - tauF(x) ,lower=0,upper=500, tol = .Machine$double.eps^0.5)$root + return(a*v) } Joe.itau.JJ<-function(tau) { - if(tau<0) - { - return(1.000001) - } - else - { - tauF=function(a) - { - #euler=0.5772156649015328606 - #1+((-2+2*euler+2*log(2)+digamma(1/a)+digamma(1/2*(2+a)/a)+a)/(-2+a)) - 1+4/a^2*integrate(function(x) log(x)*x*(1-x)^(2*(1-a)/a), 0, 1)$value - } - - v<-uniroot(function(x) tau - tauF(x) ,lower=1,upper=500, tol = .Machine$double.eps^0.5)$root - return(v) - } + if(tau<0) + { + return(1.000001) + } + else + { + tauF=function(a) + { + #euler=0.5772156649015328606 + #1+((-2+2*euler+2*log(2)+digamma(1/a)+digamma(1/2*(2+a)/a)+a)/(-2+a)) + 1+4/a^2*integrate(function(x) log(x)*x*(1-x)^(2*(1-a)/a), 0, 1)$value + } + + v<-uniroot(function(x) tau - tauF(x) ,lower=1,upper=500, tol = .Machine$double.eps^0.5)$root + return(v) + } } ipsA.tau2cpar=function(tau,mxiter=20, eps=1.e-6,dstart=0,iprint=FALSE) @@ -471,357 +465,361 @@ #--------------------------------------------------------------- MLE_intern <- -function(data,start.parm,family,se=FALSE,max.df=30,max.BB=list(BB1=c(5,6),BB6=c(6,6),BB7=c(5,6),BB8=c(6,1)),weights=NULL,cor.fixed=FALSE) -{ + function(data,start.parm,family,se=FALSE,max.df=30,max.BB=list(BB1=c(5,6),BB6=c(6,6),BB7=c(5,6),BB8=c(6,1)),weights=NULL,cor.fixed=FALSE) + { + + n = dim(data)[1] + if(any(is.na(weights))) weights=NULL + + if(family %in% c(7,8,9,10,17,18,19,20,27,28,29,30,37,38,39,40)) + { + t_LL = function(param) + { + + if(is.null(weights)) + { + ll = .C("LL_mod2",as.integer(family),as.integer(n),as.double(data[,1]),as.double(data[,2]),as.double(param[1]),as.double(param[2]),as.double(0),PACKAGE='VineCopula')[[7]] + } + else + { + ll = .C("LL_mod_seperate",as.integer(family),as.integer(n),as.double(data[,1]), as.double(data[,2]), as.double(param[1]),as.double(param[2]), as.double(rep(0,n)),PACKAGE='VineCopula')[[7]]%*%weights + } + + if(is.infinite(ll) || is.na(ll) || ll< -10^300) ll = -10^300 + + return(ll) + } + + if(family == 7 || family==17){ + low = c(0.001,1.001) + up = max.BB$BB1 + }else if(family == 8 || family==18){ + low = c(1.001,1.001) + up = max.BB$BB6 + }else if(family == 9 | family==19){ + low = c(1.001,0.001) + up = max.BB$BB7 + }else if(family == 10 | family==20){ + low = c(1.001,0.001) + up = max.BB$BB8 + }else if(family == 27 | family==37){ + up = c(-0.001,-1.001) + low = -max.BB$BB1 + }else if(family == 28 | family==38){ + up = c(-1.001,-1.001) + low = -max.BB$BB6 + }else if(family == 29 | family==39){ + up = c(-1.001,-0.001) + low = -max.BB$BB7 + }else if(family == 30 | family==40){ + up = c(-1.001,-0.001) + low = -max.BB$BB8 + } + + if(se == TRUE){ + optimout = optim(par=start.parm,fn=t_LL,method="L-BFGS-B",lower=low,upper=up,control=list(fnscale=-1,maxit = 500),hessian=TRUE) + }else{ + optimout = optim(par=start.parm,fn=t_LL,method="L-BFGS-B",lower=low,upper=up,control=list(fnscale=-1,maxit = 500)) + } + + } + else if(family == 2) + { + + if(cor.fixed == FALSE) + { + + t_LL = function(param) + { + if (param[1] < -0.9999 | param[1] >0.9999 | param[2]<2.0001 | param[2] > max.df) { + ll=-10^10 + }else + { + if(is.null(weights)) + { + ll = .C("LL_mod2",as.integer(family),as.integer(n),as.double(data[,1]),as.double(data[,2]),as.double(param[1]),as.double(param[2]),as.double(0),PACKAGE='VineCopula')[[7]] + } + else + { + ll = .C("LL_mod_seperate",as.integer(family),as.integer(n),as.double(data[,1]), as.double(data[,2]), as.double(param[1]),as.double(param[2]), as.double(rep(0,n)),PACKAGE='VineCopula')[[7]]%*%weights + } + + if(is.infinite(ll) || is.na(ll) || ll< -10^10) ll = -10^10 + } + return(ll) + } + + gr_LL = function(param) + { + gr=rep(0,2) + gr[1]=sum(BiCopDeriv(data[,1],data[,2],family=2,par=param[1],par2=param[2],deriv="par",log=TRUE)) + gr[2]=sum(BiCopDeriv(data[,1],data[,2],family=2,par=param[1],par2=param[2],deriv="par2",log=TRUE)) + return(gr) + } + + if(is.null(weights)){ + if(se == TRUE){ + optimout = optim(par=start.parm,fn=t_LL,gr=gr_LL,method="L-BFGS-B",control=list(fnscale=-1,maxit = 500),hessian=TRUE,lower=c(-0.9999,2.0001),upper=c(0.9999,max.df)) + }else{ + optimout = optim(par=start.parm,fn=t_LL,gr=gr_LL,method="L-BFGS-B",control=list(fnscale=-1,maxit = 500),lower=c(-0.9999,2.0001),upper=c(0.9999,max.df)) + } + }else{ + if(se == TRUE){ + optimout = optim(par=start.parm,fn=t_LL,method="L-BFGS-B",control=list(fnscale=-1,maxit = 500),hessian=TRUE,lower=c(-0.9999,2.0001),upper=c(0.9999,max.df)) + }else{ + optimout = optim(par=start.parm,fn=t_LL,method="L-BFGS-B",control=list(fnscale=-1,maxit = 500),lower=c(-0.9999,2.0001),upper=c(0.9999,max.df)) + } + } + + if(optimout$par[2] >= (max.df-0.0001)) warning(paste("Degrees of freedom of the t-copula estimated to be larger than ",max.df,". Consider using the Gaussian copula instead.",sep="")) + + } + else + { + t_LL = function(param) + { + if(is.null(weights)) + { + ll = .C("LL_mod2",as.integer(family),as.integer(n),as.double(data[,1]),as.double(data[,2]),as.double(start.parm[1]),as.double(param[1]),as.double(0),PACKAGE='VineCopula')[[7]] + } + else + { + ll = .C("LL_mod_seperate",as.integer(family),as.integer(n),as.double(data[,1]), as.double(data[,2]), as.double(start.parm[1]),as.double(param[1]), as.double(rep(0,n)),PACKAGE='VineCopula')[[7]]%*%weights + } + + if(is.infinite(ll) || is.na(ll) || ll< -10^300) ll = -10^300 + + return(ll) + } + + gr_LL = function(param) + { + gr=sum(BiCopDeriv(data[,1],data[,2],family=2,par=start.parm[1],par2=param[1],deriv="par2",log=TRUE)) + return(gr) + } + + if(se == TRUE){ + if(is.null(weights)){ + optimout = optim(par=start.parm[2],fn=t_LL,gr=gr_LL,method="L-BFGS-B",control=list(fnscale=-1,maxit = 500),hessian=TRUE,lower=2.0001,upper=max.df) + }else{ + optimout = optim(par=start.parm[2],fn=t_LL,method="L-BFGS-B",control=list(fnscale=-1,maxit = 500),hessian=TRUE,lower=2.0001,upper=max.df) + } + }else{ + optimout = optimize(f=t_LL,maximum=TRUE,interval=c(2.0001,max.df)) + optimout$par=optimout$maximum + } + optimout$par = c(0,optimout$par) + + } + + } + else + { + + t_LL = function(param) + { + if(is.null(weights)) + { + ll = .C("LL_mod2",as.integer(family),as.integer(n),as.double(data[,1]), as.double(data[,2]), as.double(param),as.double(0), as.double(0),PACKAGE='VineCopula')[[7]] + } + else + { + ll = .C("LL_mod_seperate",as.integer(family),as.integer(n),as.double(data[,1]), as.double(data[,2]), as.double(param[1]),as.double(0), as.double(rep(0,n)),PACKAGE='VineCopula')[[7]]%*%weights + } + if(is.infinite(ll) || is.na(ll) || ll< -10^300) ll = -10^300 + + return(ll) + } + + gr_LL = function(param) + { + gr=sum(BiCopDeriv(data[,1],data[,2],family=family,par=param,deriv="par", log=TRUE)) + return(gr) + } + + low = -Inf + up = Inf + + if(family == 1){ + low = -0.9999 + up = 0.9999 + }else if(family %in% c(3,13)){ + low = 0.0001 + up=BiCopTau2Par(family,0.99) + if(t_LL(up)==-10^300) up=BiCopTau2Par(family,0.95) + if(t_LL(up)==-10^300) up=BiCopTau2Par(family,0.9) + }else if(family %in% c(4,14)){ + low = 1.0001 + up=BiCopTau2Par(family,0.99) + if(t_LL(up)==-10^300) up=BiCopTau2Par(family,0.95) + if(t_LL(up)==-10^300) up=BiCopTau2Par(family,0.9) + }else if(family %in% c(5)){ + low = BiCopTau2Par(family,-0.99) + if(t_LL(low)==-10^300) low=BiCopTau2Par(family,-0.95) + if(t_LL(low)==-10^300) low=BiCopTau2Par(family,-0.9) + up=BiCopTau2Par(family,0.99) + if(t_LL(up)==-10^300) up=BiCopTau2Par(family,0.95) + if(t_LL(up)==-10^300) up=BiCopTau2Par(family,0.9) + }else if(family %in% c(6,16)){ + low = 1.0001 [TRUNCATED] To get the complete diff run: svnlook diff /svnroot/vinecopula -r 71 From noreply at r-forge.r-project.org Mon Jan 19 12:17:55 2015 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 19 Jan 2015 12:17:55 +0100 (CET) Subject: [Vinecopula-commits] r72 - in pkg: . R inst man src tests Message-ID: <20150119111755.DF1DD186997@r-forge.r-project.org> Author: etobi Date: 2015-01-19 12:17:55 +0100 (Mon, 19 Jan 2015) New Revision: 72 Added: pkg/man/pobs.Rd Modified: pkg/DESCRIPTION pkg/NAMESPACE pkg/R/BiCopSelect.r pkg/R/RVineStructureSelect.r pkg/R/gof_PIT.r pkg/inst/ChangeLog pkg/man/VineCopula-package.Rd pkg/src/hfunc.c pkg/src/incompleteBeta.c pkg/tests/additonalExampleRuns.R pkg/tests/additonalExampleRuns.Rout.save Log: * Import/Export of function 'pobs' from 'copula' package * hfunc.c: Extension of Hinv1 and Hinv2 in analogy to Hfunc1 and Hfunc2 * incompleteBeta.c: Misuse of the C function abs (as reported by CRAN) corrected to fabs * gof_PIT.r: Use of 'require()' replaced by 'requireNamespace' according to 'Writing R Extensions' * Package 'ADGofTest' removed from Suggests (see 'Writing R Extensions' for usage of Suggests) * Import of function 'ad.test' from 'ADGofTest' for 'gof_PIT.r' Modified: pkg/DESCRIPTION =================================================================== --- pkg/DESCRIPTION 2015-01-08 13:19:13 UTC (rev 71) +++ pkg/DESCRIPTION 2015-01-19 11:17:55 UTC (rev 72) @@ -1,13 +1,13 @@ Package: VineCopula Type: Package Title: Statistical inference of vine copulas -Version: 1.3-1 -Date: 2014-09-10 +Version: 1.3-2 +Date: 2015-01-19 Author: Ulf Schepsmeier, Jakob Stoeber, Eike Christian Brechmann, Benedikt Graeler Maintainer: Tobias Erhardt Depends: R (>= 2.11.0) -Imports: MASS, mvtnorm, igraph, methods, copula -Suggests: CDVine, TSP, ADGofTest +Imports: MASS, mvtnorm, igraph, methods, copula, ADGofTest +Suggests: CDVine, TSP Description: This package provides functions for statistical inference of vine copulas. It contains tools for bivariate exploratory data analysis, bivariate copula selection and (vine) tree construction. Models can be estimated either sequentially or by joint maximum likelihood estimation. Sampling algorithms and plotting methods are also included. Data is assumed to lie in the unit hypercube (so-called copula data). For C- and D-vines links to the package CDVine are provided. License: GPL (>= 2) LazyLoad: yes Modified: pkg/NAMESPACE =================================================================== --- pkg/NAMESPACE 2015-01-08 13:19:13 UTC (rev 71) +++ pkg/NAMESPACE 2015-01-19 11:17:55 UTC (rev 72) @@ -4,6 +4,10 @@ import(copula) import(methods) +importFrom(ADGofTest, ad.test) + +export(pobs) + export(BiCopEst) export(BiCopMetaContour) export(BiCopChiPlot) Modified: pkg/R/BiCopSelect.r =================================================================== --- pkg/R/BiCopSelect.r 2015-01-08 13:19:13 UTC (rev 71) +++ pkg/R/BiCopSelect.r 2015-01-19 11:17:55 UTC (rev 72) @@ -2,8 +2,8 @@ if(is.null(u1)==TRUE || is.null(u2)==TRUE) stop("u1 and/or u2 are not set or have length zero.") if(length(u1)!=length(u2)) stop("Lengths of 'u1' and 'u2' do not match.") if(length(u1)<2) stop("Number of observations has to be at least 2.") - if(any(u1>1) || any(u1<0)) stop("Data has be in the interval [0,1].") - if(any(u2>1) || any(u2<0)) stop("Data has be in the interval [0,1].") + if(any(u1>1) || any(u1<0)) stop("Data has to be in the interval [0,1].") + if(any(u2>1) || any(u2<0)) stop("Data has to be in the interval [0,1].") if(!is.na(familyset[1])) for(i in 1:length(familyset)) if(!(familyset[i] %in% c(0:10,13,14,16:20,23,24,26:30,33,34,36,37,38,39,40,104,114,124,134,204,214,224,234))) stop("Copula family not implemented.") if(selectioncrit != "AIC" && selectioncrit != "BIC") stop("Selection criterion not implemented.") if(level < 0 & level > 1) stop("Significance level has to be between 0 and 1.") @@ -246,7 +246,7 @@ optiout[[37]] = MLE_intern(cbind(data1,data2),start[[37]],37,weights=weights) if(optiout[[37]]$par[1] >= -0.1 | optiout[[37]]$par[2] >= -1.1){ if(optiout[[37]]$par[1] >= -0.1){ - todo[todo==37] = 24 + todo[todo==37] = 34 todo = unique(todo) }else if(optiout[[37]]$par[2] >= -1.1){ todo[todo==37] = 33 @@ -260,10 +260,10 @@ optiout[[38]] = MLE_intern(cbind(data1,data2),start[[38]],38,weights=weights) if(optiout[[38]]$par[1] >= -1.1 | optiout[[38]]$par[2] >= -1.1){ if(optiout[[38]]$par[1] >= -1.1){ - todo[todo==38] = 24 + todo[todo==38] = 34 todo = unique(todo) }else if(optiout[[38]]$par[2] >= -1.1){ - todo[todo==38] = 26 + todo[todo==38] = 36 todo = unique(todo) } optiout[[38]] = list() Modified: pkg/R/RVineStructureSelect.r =================================================================== --- pkg/R/RVineStructureSelect.r 2015-01-08 13:19:13 UTC (rev 71) +++ pkg/R/RVineStructureSelect.r 2015-01-19 11:17:55 UTC (rev 72) @@ -1,14 +1,14 @@ RVineStructureSelect = function(data,familyset=NA,type=0,selectioncrit="AIC",indeptest=FALSE,level=0.05,trunclevel=NA,progress=FALSE,weights=NA){ - library(igraph) + if(type == 0) type = "RVine" else if(type == 1) type = "CVine" if(type != "RVine" & type != "CVine") stop("Vine model not implemented.") - n = dim(data)[2] - d = dim(data)[1] + d = n = dim(data)[2] + N = dim(data)[1] - if(dim(data)[1]<2) stop("Number of observations has to be at least 2.") - if(d<2) stop("Dimension has to be at least 2.") - if(any(data>1) || any(data<0)) stop("Data has be in the interval [0,1].") + if(N<2) stop("Number of observations has to be at least 2.") + if(d<3) stop("Dimension has to be at least 3.") + if(any(data>1) || any(data<0)) stop("Data has to be in the interval [0,1].") if(!is.na(familyset[1])) for(i in 1:length(familyset)) if(!(familyset[i] %in% c(0,1:10,13,14,16:20,23,24,26:30,33,34,36:40, 104,114,124,134,204,214,224,234))) stop("Copula family not implemented.") if(selectioncrit != "AIC" && selectioncrit != "BIC") stop("Selection criterion not implemented.") Modified: pkg/R/gof_PIT.r =================================================================== --- pkg/R/gof_PIT.r 2015-01-08 13:19:13 UTC (rev 71) +++ pkg/R/gof_PIT.r 2015-01-19 11:17:55 UTC (rev 72) @@ -106,8 +106,11 @@ S[i]=sum(tmp[i,]) } if(statisticName==1 && method==1){ # Macht nur Sinn bei Breymann - require(ADGofTest) - pvalue=ad.test(S,pchisq,df=d)$p.value + if(requireNamespace("ADGofTest", quietly = TRUE)) { + pvalue=ADGofTest::ad.test(S,pchisq,df=d)$p.value + } else { + stop("For Anderson-Darling 'statistic' the package 'ADGofTest' has to be installed") + } } else if(statisticName==2 && method==1) pvalue=ks.test(S,"pchisq",df=d)$p.value Modified: pkg/inst/ChangeLog =================================================================== --- pkg/inst/ChangeLog 2015-01-08 13:19:13 UTC (rev 71) +++ pkg/inst/ChangeLog 2015-01-19 11:17:55 UTC (rev 72) @@ -1,10 +1,29 @@ Changes for R-package VineCopula -Current authors: Ulf Schepsmeier, Tobias Erhardt and Benedikt Graeler +Current authors: Ulf Schepsmeier, Thomas Nagler and Benedikt Graeler Former authors: Eike Brechmann and Jakob Stoeber -Maintainer: Tobias Erhardt +Maintainer: Tobias Erhardt and Thomas Nagler +Version 1.3-2 (January 19, 2015) + +- New author: Thomas Nagler + +- New functionality: + * Import/Export of function 'pobs' from 'copula' package + +- Bug fix: + * RVineStructureSelect: Bug concerning the dimensions of input data/security queries fixed (Reported by Sarka Cerna, Radek Solnicky and Ludovic Theate. Thanks a lot!) + * RVineStructureSelect: Correct handling of rotated BBs and Tawns (fit.ACopula, as.RVM) + * BiCopSelect, BiCopEst: Improved starting values for Tawn MLE + * hfunc.c: Correct Hfunc1 for Tawns; + * hfunc.c: Bound all results to lie in [0,1] (Hfunc1 and Hfunc2) + * hfunc.c: Extension of Hinv1 and Hinv2 in analogy to Hfunc1 and Hfunc2 + * incompleteBeta.c: Misuse of the C function abs (as reported by CRAN) corrected to fabs + * gof_PIT.r: Use of 'require()' replaced by 'requireNamespace' according to 'Writing R Extensions' + * Package 'ADGofTest' removed from Suggests (see 'Writing R Extensions' for usage of Suggests) + * Import of function 'ad.test' from 'ADGofTest' for 'gof_PIT.r' + Version 1.3-1 (September 10, 2014) - Bug fix: Modified: pkg/man/VineCopula-package.Rd =================================================================== --- pkg/man/VineCopula-package.Rd 2015-01-08 13:19:13 UTC (rev 71) +++ pkg/man/VineCopula-package.Rd 2015-01-19 11:17:55 UTC (rev 72) @@ -80,8 +80,8 @@ \tabular{ll}{ Package: \tab VineCopula\cr Type: \tab Package\cr -Version: \tab 1.3-1\cr -Date: \tab 2013-09-10\cr +Version: \tab 1.3-2\cr +Date: \tab 2015-01-19\cr License: \tab GPL (>=2)\cr Depends: \tab R (\eqn{\geq 2.11.0}{>= 2.11.0}) Imports: MASS, mvtnorm, igraph, methods, copula \cr Added: pkg/man/pobs.Rd =================================================================== --- pkg/man/pobs.Rd (rev 0) +++ pkg/man/pobs.Rd 2015-01-19 11:17:55 UTC (rev 72) @@ -0,0 +1,46 @@ +\name{pobs} +\alias{pobs} +\title{Pseudo-Observations} +\description{ + Compute the pseudo-observations for the given data matrix. +} +\usage{ +pobs(x, na.last = "keep", + ties.method = c("average", "first", "random", "max", "min"), + lower.tail = TRUE) +} +\arguments{ + \item{x}{\eqn{n\times d}{n x d}-matrix of random variates to be converted to + pseudo-observations.} + \item{na.last, ties.method}{are passed to \code{\link{rank}}; see + there.} + \item{lower.tail}{\code{\link{logical}} which, if \code{FALSE}, + returns the pseudo-observations when applying the + empirical marginal survival functions.} +} +\value{matrix of the same dimensions as \code{x} containing the + pseudo-observations. +} +\details{ + Given \eqn{n} realizations + \eqn{\bm{x}_i=(x_{i1},\dots,x_{id})^T}{x_i=(x_{i1},...,x_{id})}, + \eqn{i\in\{1,\dots,n\}}{i in {1,...,n}} of a random vector \eqn{\bm{X}}{X}, + the pseudo-observations are defined via \eqn{u_{ij}=r_{ij}/(n+1)} for + \eqn{i\in\{1,\dots,n\}}{i in {1,...,n}} and \eqn{j\in\{1,\dots,d\}}{j in + {1,...,d}}, where \eqn{r_{ij}} denotes the rank of \eqn{x_{ij}} among all + \eqn{x_{kj}}, \eqn{k\in\{1,\dots,n\}}{k in {1,...,n}}. The + pseudo-observations can thus also be computed by component-wise applying the + empirical distribution functions to the data and scaling the result by + \eqn{n/(n+1)}. This asymptotically negligible scaling factor is used to + force the variates to fall inside the open unit hypercube, for example, to + avoid problems with density evaluation at the boundaries. Note that + \code{pobs(, lower.tail=FALSE)} simply returns \code{1-pobs()}. +} +\note{This function is borrowed from the \code{\link[copula]{copula-package}}, see \code{\link[copula]{pobs}}.} +\author{Marius Hofert} +\examples{ +## Simple definition of the function: +pobs +} + + Modified: pkg/src/hfunc.c =================================================================== --- pkg/src/hfunc.c 2015-01-08 13:19:13 UTC (rev 71) +++ pkg/src/hfunc.c 2015-01-19 11:17:55 UTC (rev 72) @@ -973,7 +973,33 @@ else if(v[i]>UMAX) v[i]=UMAX; } - if(((*family ==23) | (*family ==24) | (*family==26) | (*family ==27) | (*family ==28) | (*family==29) | (*family==30) | (*family==61) )) + if((*family)==43) + { + nfamily=3; + if(*theta > 0){ + ntheta=2*(*theta)/(1-*theta); + Hinv(&nfamily, n, u, v, &ntheta, &nnu, out); + }else{ + ntheta=-2*(*theta)/(1+*theta); + for (int i = 0; i < *n; ++i) {negv[i]=1 - v[i];} + Hinv(&nfamily, n, u, negv, &ntheta, &nnu, out); + for (int i = 0; i < *n; i++) {out[i]=1-out[i];}; + } + } + else if((*family)==44) + { + nfamily=4; + if(*theta > 0){ + ntheta=1/(1-*theta); + Hinv(&nfamily, n, u, v, &ntheta, &nnu, out); + }else{ + ntheta=1/(1+*theta); + for (int i = 0; i < *n; ++i) {negv[i]=1 - v[i];} + Hinv(&nfamily, n, u, negv, &ntheta, &nnu, out); + for (int i = 0; i < *n; i++) {out[i]=1-out[i];}; + } + } + else if(((*family ==23) | (*family ==24) | (*family==26) | (*family ==27) | (*family ==28) | (*family==29) | (*family==30) | (*family==61) )) { nfamily=(*family)-20; for (int i = 0; i < *n; ++i) {negv[i]=1 - v[i];} @@ -1028,7 +1054,33 @@ else if(v[i]>UMAX) v[i]=UMAX; } - if(((*family ==23) | (*family ==24) | (*family==26) | (*family ==27) | (*family ==28) | (*family==29) | (*family==30) | (*family==61) )) + if((*family)==43) + { + nfamily=3; + if(*theta > 0){ + ntheta=2*(*theta)/(1-*theta); + Hinv(&nfamily, n, v, u, &ntheta, &nnu, out); + }else{ + ntheta=-2*(*theta)/(1+*theta); + for (int i = 0; i < *n; ++i) {negv[i]=1 - v[i];} + Hinv(&nfamily, n, negv, u, &ntheta, &nnu, out); + for (int i = 0; i < *n; i++) {out[i]=1-out[i];}; + } + } + else if((*family)==44) + { + nfamily=4; + if(*theta > 0){ + ntheta=1/(1-*theta); + Hinv(&nfamily, n, v, u, &ntheta, &nnu, out); + }else{ + ntheta=1/(1+*theta); + for (int i = 0; i < *n; ++i) {negv[i]=1 - v[i];} + Hinv(&nfamily, n, negv, u, &ntheta, &nnu, out); + for (int i = 0; i < *n; i++) {out[i]=1-out[i];}; + } + } + else if(((*family ==23) | (*family ==24) | (*family==26) | (*family ==27) | (*family ==28) | (*family==29) | (*family==30) | (*family==61) )) { nfamily = (*family)-20; for (int i = 0; i < *n; ++i) {negv[i]=1 - v[i];} Modified: pkg/src/incompleteBeta.c =================================================================== --- pkg/src/incompleteBeta.c 2015-01-08 13:19:13 UTC (rev 71) +++ pkg/src/incompleteBeta.c 2015-01-19 11:17:55 UTC (rev 72) @@ -326,7 +326,7 @@ // Scale derivatives to prevent overflow Rn=dan[0]; - if(abs(dbn[0])>abs(dan[0])) + if(fabs(dbn[0])>fabs(dan[0])) { Rn=dbn[0]; } @@ -339,7 +339,7 @@ dan[2]=dan[2]/Rn; dbn[1]=dbn[1]/Rn; dbn[2]=dbn[2]/Rn; - if(abs(dbn[0])>abs(dan[0])) + if(fabs(dbn[0])>fabs(dan[0])) { dan[0]=dan[0]/dbn[0]; dbn[0]=1; @@ -385,8 +385,8 @@ for(i=0;i<3;i++) { - d1[i]=MAX(err,abs(der[i])); - d1[i]=abs(der_old[i]-der[i])/d1[i]; + d1[i]=MAX(err,fabs(der[i])); + d1[i]=fabs(der_old[i]-der[i])/d1[i]; der_old[i]=der[i]; } d=MAX(MAX(d1[0],d1[1]),d1[2]); Modified: pkg/tests/additonalExampleRuns.R =================================================================== --- pkg/tests/additonalExampleRuns.R 2015-01-08 13:19:13 UTC (rev 71) +++ pkg/tests/additonalExampleRuns.R 2015-01-19 11:17:55 UTC (rev 72) @@ -1,5 +1,5 @@ ## switch for testing the following time consuming examples -docheck <- FALSE +docheck <- TRUE if(docheck){ Modified: pkg/tests/additonalExampleRuns.Rout.save =================================================================== --- pkg/tests/additonalExampleRuns.Rout.save 2015-01-08 13:19:13 UTC (rev 71) +++ pkg/tests/additonalExampleRuns.Rout.save 2015-01-19 11:17:55 UTC (rev 72) @@ -1,7 +1,7 @@ -R version 3.0.2 (2013-09-25) -- "Frisbee Sailing" -Copyright (C) 2013 The R Foundation for Statistical Computing -Platform: i386-w64-mingw32/i386 (32-bit) +R Under development (unstable) (2015-01-14 r67471) -- "Unsuffered Consequences" +Copyright (C) 2015 The R Foundation for Statistical Computing +Platform: x86_64-w64-mingw32/x64 (64-bit) R is free software and comes with ABSOLUTELY NO WARRANTY. You are welcome to redistribute it under certain conditions. @@ -16,7 +16,7 @@ Type 'q()' to quit R. > ## switch for testing the following time consuming examples -> docheck <- FALSE +> docheck <- TRUE > > if(docheck){ + @@ -245,7 +245,524 @@ + # End(Not run) + + } +iter 10 value -1111.253373 +iter 20 value -1111.562935 +iter 30 value -1111.991155 +iter 40 value -1112.008869 +iter 50 value -1112.062737 +iter 60 value -1112.114981 +iter 70 value -1112.168354 +final value -1112.174829 +converged + +Attaching package: 'copula' + +The following object is masked from 'package:VineCopula': + + fitCopula + + [,1] [,2] [,3] [,4] + [1,] 0.7743684903 0.197224191 0.9780138442 0.201327350 + [2,] 0.3612444273 0.742611942 0.9787284394 0.498113709 + [3,] 0.0133158357 0.259946129 0.7758930807 0.016379053 + [4,] 0.0957447842 0.142163540 0.2111262376 0.811256444 + [5,] 0.0365471959 0.891637413 0.4832364111 0.466664528 + [6,] 0.9842240803 0.601345547 0.0383443474 0.141495691 + [7,] 0.8063855253 0.266685676 0.0427020509 0.612174522 + [8,] 0.5533483981 0.853500765 0.4697785398 0.397616561 + [9,] 0.8046367336 0.508897385 0.6349153537 0.494251721 + [10,] 0.2801308988 0.908710354 0.7841161578 0.558997022 + [11,] 0.2444374892 0.530970655 0.1183959420 0.983383433 + [12,] 0.8977528436 0.738573763 0.3773106968 0.606168831 + [13,] 0.5121942617 0.989246660 0.0691335856 0.084620626 + [14,] 0.1299455715 0.746132021 0.0388791817 0.685635417 + [15,] 0.1439773615 0.891079958 0.0896361163 0.037732719 + [16,] 0.7748743587 0.812063878 0.2606025457 0.651594998 + [17,] 0.9238038510 0.266106121 0.2661329871 0.910917896 + [18,] 0.5905635331 0.918147645 0.6037942769 0.328263949 + [19,] 0.6661178111 0.874787498 0.0688752665 0.793463009 + [20,] 0.5714270058 0.048944066 0.9803513540 0.914537349 + [21,] 0.7659584857 0.775846373 0.3125150499 0.842217308 + [22,] 0.3141499059 0.756563893 0.9675243802 0.169422925 + [23,] 0.6968751778 0.872650789 0.1324707782 0.078513110 + [24,] 0.3782238525 0.579624758 0.5364251249 0.108531924 + [25,] 0.7403151453 0.451789635 0.6461082133 0.749298733 + [26,] 0.5782921447 0.369409172 0.8813395619 0.599252820 + [27,] 0.2417592837 0.991064092 0.2720299934 0.225755411 + [28,] 0.3065364894 0.736066050 0.2058734051 0.242183074 + [29,] 0.4066693399 0.411321262 0.2207378661 0.868450051 + [30,] 0.7642357713 0.217509840 0.8997187309 0.816142634 + [31,] 0.1601893809 0.566658863 0.1824444511 0.867856246 + [32,] 0.0937132754 0.638223762 0.9734738106 0.009292930 + [33,] 0.7511339965 0.103923442 0.3436669305 0.591091853 + [34,] 0.5735987651 0.951237907 0.6553645076 0.377351639 + [35,] 0.9499114281 0.578954988 0.4752220884 0.254485867 + [36,] 0.3758446192 0.052798728 0.4420929269 0.697271063 + [37,] 0.7591612791 0.113734436 0.5760056155 0.099177053 + [38,] 0.1097460489 0.089127219 0.4737118890 0.356403576 + [39,] 0.2159698724 0.573215632 0.0016242201 0.718207759 + [40,] 0.2651135898 0.153830340 0.2900760283 0.067229538 + [41,] 0.9318368479 0.133479226 0.8126322976 0.759258038 + [42,] 0.3713044880 0.952166667 0.0996854173 0.307502680 + [43,] 0.4942615442 0.799964843 0.8426329251 0.647393905 + [44,] 0.6565674008 0.228435223 0.9240007692 0.485242063 + [45,] 0.5546194194 0.852844047 0.0898779368 0.740950904 + [46,] 0.3131348765 0.100732039 0.1840703834 0.213704721 + [47,] 0.6256980768 0.428000274 0.6235166367 0.577644360 + [48,] 0.1489856443 0.575752754 0.6500458319 0.638607423 + [49,] 0.7874355474 0.080619973 0.2898914691 0.223104578 + [50,] 0.5703688168 0.256050143 0.5171432674 0.769378419 + [51,] 0.1717156325 0.339101385 0.0346307140 0.378165489 + [52,] 0.9764601048 0.628306977 0.7929682066 0.576068396 + [53,] 0.1587420395 0.375621754 0.7126429004 0.642280536 + [54,] 0.2176803409 0.835219718 0.7511949919 0.092663403 + [55,] 0.1462978539 0.224104125 0.2406677336 0.479203157 + [56,] 0.1708911972 0.593215867 0.4259613717 0.782201018 + [57,] 0.8910149985 0.142018785 0.0872662787 0.298543895 + [58,] 0.3779736755 0.310509426 0.8581924702 0.185521572 + [59,] 0.0457103401 0.879344751 0.3266109165 0.610508331 + [60,] 0.4137852436 0.631626930 0.0201767548 0.560452844 + [61,] 0.2195571528 0.718596233 0.8913105952 0.714111986 + [62,] 0.7382447990 0.744075007 0.8478900143 0.701567872 + [63,] 0.4122337785 0.671587694 0.8733269582 0.958611961 + [64,] 0.6021437587 0.955820256 0.3093991736 0.610134651 + [65,] 0.6450917169 0.928400521 0.1264171537 0.114088232 + [66,] 0.7526843124 0.436705104 0.7802989122 0.076146137 + [67,] 0.2997063766 0.654224689 0.1309945930 0.765423296 + [68,] 0.3087085823 0.876935426 0.6371941748 0.342596608 + [69,] 0.4284886608 0.849930797 0.0008197445 0.813576228 + [70,] 0.0874580105 0.289057647 0.8494888905 0.805416501 + [71,] 0.9950445746 0.526671264 0.1112271971 0.945346809 + [72,] 0.7236955145 0.766487946 0.9305669612 0.498757267 + [73,] 0.7239606669 0.361902371 0.1568023660 0.303363824 + [74,] 0.7426302731 0.399672838 0.9347559172 0.946996531 + [75,] 0.5447802225 0.838801894 0.5616297950 0.707813082 + [76,] 0.0706888989 0.119998450 0.0310555075 0.463001627 + [77,] 0.4483564957 0.872894669 0.5048730967 0.902939290 + [78,] 0.0438287666 0.643314284 0.6988559945 0.432357483 + [79,] 0.8284931015 0.841108692 0.9299757103 0.485348572 + [80,] 0.7633930759 0.722670076 0.1641295145 0.992984264 + [81,] 0.4222436752 0.510317259 0.8841753434 0.815883017 + [82,] 0.3102896563 0.290614294 0.9858013957 0.483377530 + [83,] 0.1074008208 0.895984350 0.7338644972 0.764169478 + [84,] 0.0669399693 0.586228112 0.9107325065 0.992980055 + [85,] 0.7499900353 0.032749303 0.2553250678 0.424626995 + [86,] 0.3636265502 0.491994663 0.4343010753 0.570558629 + [87,] 0.9078977865 0.149545077 0.4103580574 0.386177163 + [88,] 0.3463237630 0.180769041 0.2505669079 0.723566933 + [89,] 0.3568387409 0.762676157 0.0026778339 0.902502597 + [90,] 0.9372461650 0.028783082 0.5805151563 0.320475659 + [91,] 0.5341461205 0.844306072 0.0044064738 0.239406295 + [92,] 0.0869177727 0.431421488 0.8170050057 0.685073657 + [93,] 0.5969637693 0.649056442 0.8868091749 0.752216479 + [94,] 0.4407886460 0.765468751 0.6110754195 0.230400142 + [95,] 0.7709763278 0.003451970 0.3045489269 0.677755016 + [96,] 0.8306224118 0.981180732 0.0146101408 0.427443687 + [97,] 0.0260336597 0.497721859 0.7918673381 0.536566794 + [98,] 0.8351932005 0.254128620 0.7913846564 0.873722913 + [99,] 0.2165347089 0.939788748 0.1385002721 0.383461147 +[100,] 0.4339649915 0.296471564 0.7247037594 0.336028221 +[101,] 0.9783641526 0.866081857 0.9018030704 0.325471421 +[102,] 0.3971384598 0.265053156 0.9096906008 0.838811320 +[103,] 0.7162932027 0.695596617 0.4661542471 0.385693899 +[104,] 0.9766215621 0.978381113 0.9296605005 0.850788791 +[105,] 0.8914492358 0.323866647 0.5856527244 0.253404879 +[106,] 0.6137620085 0.517032054 0.7084812184 0.384624342 +[107,] 0.6937829796 0.482504157 0.2806229971 0.111000120 +[108,] 0.2252501699 0.192968889 0.7676781283 0.144796298 +[109,] 0.3975286756 0.856579141 0.7646776433 0.349135153 +[110,] 0.2514651113 0.468221299 0.2596560335 0.251388092 +[111,] 0.1048730048 0.480938709 0.5862234468 0.157663264 +[112,] 0.8533307265 0.802534590 0.0630291228 0.774797393 +[113,] 0.8543458662 0.959840256 0.5253083515 0.794741470 +[114,] 0.9343227027 0.415850785 0.5709062461 0.715303819 +[115,] 0.4945777149 0.319346633 0.4525958812 0.921565412 +[116,] 0.5938526166 0.742607552 0.3950976874 0.381024701 +[117,] 0.7792707451 0.446705242 0.8011080394 0.053082889 +[118,] 0.6759392642 0.110763745 0.5593784570 0.578903007 +[119,] 0.0537102909 0.861216648 0.5484887112 0.191311767 +[120,] 0.1262770237 0.404101574 0.2281427665 0.790996143 +[121,] 0.7423158411 0.264997610 0.0497878187 0.727313877 +[122,] 0.1385788159 0.473839645 0.2715208770 0.361259246 +[123,] 0.3941312041 0.516422224 0.5751485603 0.913428178 +[124,] 0.7122545927 0.282151025 0.7430913700 0.336726994 +[125,] 0.0864723539 0.137007158 0.8332147521 0.281362747 +[126,] 0.3166397884 0.093503658 0.6104916255 0.486205183 +[127,] 0.4951614400 0.621448159 0.2981001402 0.622220361 +[128,] 0.8094501127 0.343012312 0.2104642675 0.773515745 +[129,] 0.9557679957 0.286419369 0.0794727448 0.661053497 +[130,] 0.3118138872 0.630501184 0.6049537384 0.876706274 +[131,] 0.0342228804 0.771673130 0.9368422253 0.254222035 +[132,] 0.3931704909 0.407810160 0.6519637303 0.232840615 +[133,] 0.2398367440 0.463389060 0.0757585869 0.739007716 +[134,] 0.6477067082 0.498322295 0.8434889137 0.425229206 +[135,] 0.2592272202 0.847242712 0.3250673641 0.072640638 +[136,] 0.4135137298 0.294362260 0.0082187485 0.169481597 +[137,] 0.1102090557 0.357150810 0.4791381841 0.628914608 +[138,] 0.0291915040 0.317528534 0.3061793284 0.688495747 +[139,] 0.5546681047 0.777362950 0.7623155026 0.425375876 +[140,] 0.9654694719 0.937939378 0.4363308840 0.365133651 +[141,] 0.9337793922 0.093578767 0.1778323287 0.634321812 +[142,] 0.4263039595 0.247728514 0.6804367560 0.951060107 +[143,] 0.0055627781 0.657620627 0.4659305960 0.862668524 +[144,] 0.1916651884 0.882191312 0.1169548559 0.884029913 +[145,] 0.8443164860 0.545540991 0.3381157848 0.612806927 +[146,] 0.3035845007 0.996642929 0.2449090297 0.494586456 +[147,] 0.0983962484 0.551325806 0.0632993493 0.110916249 +[148,] 0.2652095708 0.659197510 0.1011707778 0.915162335 +[149,] 0.4929900784 0.408335317 0.9016870754 0.628590122 +[150,] 0.0489578447 0.394935755 0.2591228082 0.331622616 +[151,] 0.6669344027 0.625317686 0.5075432686 0.284504177 +[152,] 0.3621549048 0.768481911 0.2988393311 0.371669197 +[153,] 0.0326483354 0.144800921 0.4674971097 0.467041486 +[154,] 0.6198881525 0.996896958 0.9224957055 0.030758351 +[155,] 0.5376262197 0.324835435 0.9192293161 0.362162672 +[156,] 0.2576842806 0.777084367 0.0603294310 0.148089551 +[157,] 0.3500228543 0.724576649 0.1668874554 0.625389982 +[158,] 0.2161285661 0.080344860 0.8572669341 0.534154641 +[159,] 0.9111834818 0.339142072 0.2979932092 0.839897137 +[160,] 0.0560075995 0.251565638 0.1065861024 0.084512484 +[161,] 0.0462357609 0.653913901 0.5670640329 0.604898218 +[162,] 0.3610695442 0.478445034 0.2008723405 0.222925923 +[163,] 0.9494444395 0.030701017 0.4029161467 0.581024964 +[164,] 0.7975459564 0.212698670 0.7370460802 0.834826638 +[165,] 0.3424032438 0.373054494 0.7425395199 0.102290838 +[166,] 0.8210614766 0.719421685 0.9488708046 0.614808284 +[167,] 0.4656176886 0.687057783 0.8464449772 0.275338395 +[168,] 0.2352189699 0.869283458 0.4975102539 0.530897514 +[169,] 0.8449436247 0.231636410 0.0050560117 0.197853174 +[170,] 0.8511695394 0.794882977 0.4079136280 0.341474468 +[171,] 0.2390391729 0.679682165 0.1650999326 0.534640821 +[172,] 0.9170250949 0.708150995 0.7061667675 0.180957641 +[173,] 0.7601360832 0.898726894 0.7251891324 0.194109676 +[174,] 0.7113639880 0.917680320 0.8643603884 0.609830835 +[175,] 0.2820347275 0.971891471 0.5355856742 0.227349275 +[176,] 0.5997360051 0.154081805 0.4637709183 0.845961729 +[177,] 0.4354194493 0.773573316 0.0967188128 0.424934591 +[178,] 0.5771441387 0.475725745 0.1756015311 0.234882956 +[179,] 0.4343538592 0.574824400 0.9920985959 0.756193620 +[180,] 0.3622156528 0.547339699 0.1859536748 0.524521267 +[181,] 0.2250695992 0.911340973 0.7638558464 0.341152911 +[182,] 0.8203911844 0.984728851 0.4024798393 0.398337749 +[183,] 0.3553854842 0.996304989 0.4209121999 0.825072953 +[184,] 0.0540067432 0.126679682 0.9832146429 0.438097001 +[185,] 0.0977464563 0.144636228 0.6997192786 0.964076800 +[186,] 0.5718035589 0.976129007 0.7661929270 0.353297002 +[187,] 0.6672807375 0.812140311 0.6806913668 0.417172965 +[188,] 0.6312760920 0.845643334 0.3147387863 0.623067643 +[189,] 0.2489069414 0.170307136 0.0528473828 0.352397213 +[190,] 0.7154197919 0.769427613 0.0439616535 0.296600588 +[191,] 0.3728102313 0.606454670 0.1744521784 0.325637069 +[192,] 0.5313717655 0.213290896 0.1098954093 0.470625348 +[193,] 0.0183186221 0.612048755 0.3343215247 0.983097545 +[194,] 0.6339995915 0.751820059 0.2734629191 0.243564314 +[195,] 0.3502755684 0.483300012 0.9734322524 0.218934502 +[196,] 0.4920768677 0.722552758 0.5070240900 0.070143877 +[197,] 0.0194451697 0.205571976 0.7541954345 0.630418118 +[198,] 0.8489873135 0.051017051 0.8036233829 0.583407820 +[199,] 0.8866788479 0.950272547 0.0732990042 0.834296813 +[200,] 0.3632328885 0.444549295 0.9541965688 0.010449900 +[201,] 0.2735836152 0.830732305 0.8230200189 0.392719318 +[202,] 0.7352467482 0.901445550 0.0822419475 0.368879102 +[203,] 0.3630899456 0.488129941 0.8006980552 0.575974445 +[204,] 0.7874140171 0.849424730 0.1900799496 0.533960375 +[205,] 0.8334457523 0.754456814 0.4303900155 0.755243090 +[206,] 0.3164512538 0.821538813 0.6494338685 0.154915826 +[207,] 0.3741788722 0.286865845 0.8432514123 0.181860059 +[208,] 0.6069478868 0.657173519 0.8113320200 0.546618887 +[209,] 0.8379858243 0.066471890 0.9748757288 0.805784753 +[210,] 0.0663143010 0.781842248 0.5844962969 0.798303778 +[211,] 0.5553825684 0.826247105 0.2980761654 0.934750434 +[212,] 0.6941594929 0.863456176 0.2019991342 0.263072162 +[213,] 0.8025015295 0.022981469 0.7881118841 0.121721596 +[214,] 0.2573423921 0.105063497 0.3959441814 0.406720767 +[215,] 0.4574301527 0.014828125 0.9075640836 0.366266056 +[216,] 0.7250718824 0.783072366 0.4091000268 0.215065519 +[217,] 0.4007112575 0.590563430 0.5302661911 0.147716149 +[218,] 0.2249917972 0.566724799 0.2234066734 0.054572506 +[219,] 0.6243523695 0.855703998 0.0435405250 0.370553982 +[220,] 0.7651069134 0.951624621 0.4868271784 0.589320412 +[221,] 0.6758246957 0.319414223 0.6893930857 0.536409341 +[222,] 0.1508573301 0.847545645 0.3025167799 0.255791885 +[223,] 0.5158530220 0.665776487 0.5712286504 0.972977022 +[224,] 0.4382174690 0.607895790 0.8810680558 0.382243131 +[225,] 0.9040353345 0.818195505 0.1890957728 0.279341920 +[226,] 0.0956006302 0.433048549 0.1651034511 0.184365910 +[227,] 0.7956483513 0.622831352 0.5386761294 0.034711238 +[228,] 0.3661794967 0.195988555 0.2794191148 0.962412738 +[229,] 0.9471271602 0.549059042 0.9749584261 0.717982193 +[230,] 0.3556773327 0.867656888 0.2311769573 0.076064603 +[231,] 0.3916409630 0.681572748 0.9537506220 0.020585128 +[232,] 0.7171780958 0.669524003 0.6586226965 0.254619111 +[233,] 0.3992693252 0.494142564 0.1740932919 0.194849428 +[234,] 0.8798466546 0.476180211 0.1617385235 0.405467161 +[235,] 0.1666286134 0.075125683 0.2838694500 0.076784107 +[236,] 0.9361824323 0.933077563 0.1356491460 0.679490731 +[237,] 0.5197204188 0.339432430 0.0399253590 0.182384872 +[238,] 0.3721226270 0.752011640 0.1098320589 0.798284948 +[239,] 0.1836079187 0.603453786 0.6101417094 0.041103652 +[240,] 0.4993634163 0.207342210 0.3261762194 0.486902969 +[241,] 0.6467777344 0.129989076 0.6651675196 0.449809124 +[242,] 0.6536722353 0.695856193 0.7535691005 0.061294960 +[243,] 0.0499363518 0.046064124 0.8446276195 0.104884493 +[244,] 0.2620879861 0.148730939 0.1752178846 0.019662158 +[245,] 0.4427078820 0.094287481 0.8933788843 0.585570112 +[246,] 0.9169778530 0.648075843 0.7762387784 0.204912888 +[247,] 0.5732168553 0.863256845 0.5047426480 0.469652176 +[248,] 0.4276488579 0.131531685 0.1593779558 0.845790585 +[249,] 0.8587067372 0.502891751 0.5593184705 0.375858957 +[250,] 0.9890882210 0.938063616 0.9706202168 0.216183099 +[251,] 0.8379715749 0.129972132 0.5695172495 0.625571513 +[252,] 0.7212316899 0.572297784 0.0382156211 0.051894007 +[253,] 0.5216590953 0.015851347 0.9769222983 0.272455045 +[254,] 0.5143919997 0.114772279 0.1596595603 0.809009656 +[255,] 0.7357275770 0.853319851 0.2404850596 0.704516945 +[256,] 0.1952619776 0.944837198 0.3381335489 0.726653310 +[257,] 0.6910012066 0.214935871 0.4175838032 0.218764917 +[258,] 0.4867478984 0.343270314 0.2169513768 0.380788512 +[259,] 0.4428913160 0.343588427 0.5667717615 0.949275269 +[260,] 0.1775206316 0.142845772 0.0695777584 0.118463847 +[261,] 0.2351934593 0.337216868 0.9805003721 0.005284573 +[262,] 0.4857526280 0.558714604 0.5375014008 0.511780816 +[263,] 0.6552407253 0.130329409 0.7706996505 0.282453222 +[264,] 0.2740938128 0.395738140 0.1035083684 0.006252106 +[265,] 0.7483767993 0.547375288 0.6094368612 0.932357808 +[266,] 0.6706526354 0.151936714 0.9280017349 0.642849064 +[267,] 0.1692593219 0.512618867 0.8483696235 0.554460279 +[268,] 0.6046569496 0.175424204 0.5205884210 0.980532835 +[269,] 0.4171814560 0.160848656 0.0254654889 0.898504830 +[270,] 0.4675834295 0.565785344 0.8435611597 0.885702458 +[271,] 0.2869922114 0.653929896 0.0656541944 0.549899117 +[272,] 0.2903471391 0.175998944 0.2433835415 0.855399843 +[273,] 0.9098031069 0.600858136 0.0691988289 0.630983036 +[274,] 0.5219512563 0.196392351 0.9942230587 0.171735779 +[275,] 0.7468491504 0.370164049 0.7109902038 0.282020319 +[276,] 0.1262481522 0.390918806 0.8852912916 0.104233933 +[277,] 0.0300880789 0.647038511 0.1334821235 0.240433870 +[278,] 0.6879101389 0.589410251 0.4775275313 0.491272935 +[279,] 0.6160576248 0.761771664 0.2333714277 0.272765368 +[280,] 0.3549011711 0.051849936 0.8768312477 0.877099060 +[281,] 0.8581745944 0.971428056 0.5737855358 0.332571355 +[282,] 0.0207595848 0.042617511 0.7648429871 0.827382307 +[283,] 0.6349156951 0.124888753 0.7582474155 0.187631488 +[284,] 0.1530019275 0.031149091 0.9507271959 0.772281578 +[285,] 0.6720045879 0.978253266 0.1504266458 0.133118892 +[286,] 0.8485787737 0.734150176 0.8971518457 0.308240966 +[287,] 0.8162173289 0.762108188 0.0482832582 0.678645760 +[288,] 0.1517000652 0.989808477 0.5504770332 0.590718119 +[289,] 0.6345506713 0.545683430 0.0139598753 0.678947515 +[290,] 0.8936809630 0.442411056 0.1092832964 0.419108480 +[291,] 0.9164704378 0.303237157 0.7087321593 0.891897406 +[292,] 0.5595637094 0.593235709 0.8172157183 0.180815238 +[293,] 0.5450307759 0.731739299 0.7757680221 0.936030307 +[294,] 0.9844803826 0.952755239 0.7349386474 0.200063891 +[295,] 0.5252404297 0.912472579 0.1983703848 0.873221091 +[296,] 0.5562255983 0.346838131 0.2333369483 0.126236536 +[297,] 0.4020865897 0.884241141 0.2719432884 0.604082966 +[298,] 0.7625291559 0.952015422 0.6255507688 0.757415980 +[299,] 0.5018466183 0.931425986 0.1910752419 0.806532523 +[300,] 0.2368220380 0.122242337 0.3275852152 0.173029160 +[301,] 0.5842146724 0.936198387 0.8389963040 0.126142483 +[302,] 0.2276427920 0.316277360 0.5839341637 0.590474609 +[303,] 0.5422491468 0.200553625 0.5389597269 0.879883609 +[304,] 0.7374660282 0.768241838 0.9755696333 0.763199614 +[305,] 0.1471564339 0.559007475 0.9607511451 0.217728840 +[306,] 0.5889839104 0.675189323 0.5226181226 0.430570702 +[307,] 0.7506851617 0.386064682 0.4334508299 0.965842676 +[308,] 0.2637242335 0.650240324 0.3104421902 0.638478931 +[309,] 0.1803990712 0.089696390 0.2932914000 0.006119711 +[310,] 0.7184373385 0.404312139 0.1811476685 0.965097900 +[311,] 0.2377872753 0.984447725 0.8718100854 0.106952735 +[312,] 0.3503712702 0.603536791 0.8463436530 0.310144706 +[313,] 0.4495570462 0.272465356 0.5138976437 0.488285378 +[314,] 0.8614247281 0.744840986 0.1210435661 0.716413555 +[315,] 0.1381337575 0.230298426 0.9294903460 0.636520796 [TRUNCATED] To get the complete diff run: svnlook diff /svnroot/vinecopula -r 72 From noreply at r-forge.r-project.org Mon Jan 19 17:40:38 2015 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 19 Jan 2015 17:40:38 +0100 (CET) Subject: [Vinecopula-commits] r73 - in pkg: . man Message-ID: <20150119164038.2E502183E4C@r-forge.r-project.org> Author: tnagler Date: 2015-01-19 17:40:37 +0100 (Mon, 19 Jan 2015) New Revision: 73 Modified: pkg/ pkg/man/pobs.Rd Log: add example for pobs() Property changes on: pkg ___________________________________________________________________ Added: svn:ignore + .Rproj.user .Rhistory .RData pkg.Rproj .Rbuildignore Modified: pkg/man/pobs.Rd =================================================================== --- pkg/man/pobs.Rd 2015-01-19 11:17:55 UTC (rev 72) +++ pkg/man/pobs.Rd 2015-01-19 16:40:37 UTC (rev 73) @@ -41,6 +41,20 @@ \examples{ ## Simple definition of the function: pobs + +## simulate data from a multivariate normal distribution +library(mvtnorm) +set.seed(1) +Sigma <- matrix(c(2, 1, -0.2, 1, 1, 0.3, -0.2, 0.3, 0.5), 3, 3) +mu <- c(-3, 2, 1) +dat <- rmvnorm(500, sigma = Sigma) +pairs(dat) # plot observations + +## compute pseudo-observations for copula inference +udat <- pobs(dat) +pairs(udat) +# estimate vine copula model +fit <- RVineStructureSelect(udat, familyset = c(1, 2)) } From noreply at r-forge.r-project.org Tue Jan 20 09:29:48 2015 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Tue, 20 Jan 2015 09:29:48 +0100 (CET) Subject: [Vinecopula-commits] r74 - in pkg: . man tests Message-ID: <20150120082948.171001878CE@r-forge.r-project.org> Author: etobi Date: 2015-01-20 09:29:47 +0100 (Tue, 20 Jan 2015) New Revision: 74 Modified: pkg/DESCRIPTION pkg/man/VineCopula-package.Rd pkg/tests/additonalExampleRuns.R pkg/tests/additonalExampleRuns.Rout.save Log: Ready for CRAN (new version 1.4) Modified: pkg/DESCRIPTION =================================================================== --- pkg/DESCRIPTION 2015-01-19 16:40:37 UTC (rev 73) +++ pkg/DESCRIPTION 2015-01-20 08:29:47 UTC (rev 74) @@ -1,8 +1,8 @@ Package: VineCopula Type: Package Title: Statistical inference of vine copulas -Version: 1.3-2 -Date: 2015-01-19 +Version: 1.4 +Date: 2015-01-20 Author: Ulf Schepsmeier, Jakob Stoeber, Eike Christian Brechmann, Benedikt Graeler Maintainer: Tobias Erhardt Depends: R (>= 2.11.0) Modified: pkg/man/VineCopula-package.Rd =================================================================== --- pkg/man/VineCopula-package.Rd 2015-01-19 16:40:37 UTC (rev 73) +++ pkg/man/VineCopula-package.Rd 2015-01-20 08:29:47 UTC (rev 74) @@ -80,8 +80,8 @@ \tabular{ll}{ Package: \tab VineCopula\cr Type: \tab Package\cr -Version: \tab 1.3-2\cr -Date: \tab 2015-01-19\cr +Version: \tab 1.4\cr +Date: \tab 2015-01-20\cr License: \tab GPL (>=2)\cr Depends: \tab R (\eqn{\geq 2.11.0}{>= 2.11.0}) Imports: MASS, mvtnorm, igraph, methods, copula \cr Modified: pkg/tests/additonalExampleRuns.R =================================================================== --- pkg/tests/additonalExampleRuns.R 2015-01-19 16:40:37 UTC (rev 73) +++ pkg/tests/additonalExampleRuns.R 2015-01-20 08:29:47 UTC (rev 74) @@ -1,5 +1,5 @@ ## switch for testing the following time consuming examples -docheck <- TRUE +docheck <- FALSE if(docheck){ Modified: pkg/tests/additonalExampleRuns.Rout.save =================================================================== --- pkg/tests/additonalExampleRuns.Rout.save 2015-01-19 16:40:37 UTC (rev 73) +++ pkg/tests/additonalExampleRuns.Rout.save 2015-01-20 08:29:47 UTC (rev 74) @@ -16,7 +16,7 @@ Type 'q()' to quit R. > ## switch for testing the following time consuming examples -> docheck <- TRUE +> docheck <- FALSE > > if(docheck){ + @@ -245,524 +245,7 @@ + # End(Not run) + + } -iter 10 value -1111.253373 -iter 20 value -1111.562935 -iter 30 value -1111.991155 -iter 40 value -1112.008869 -iter 50 value -1112.062737 -iter 60 value -1112.114981 -iter 70 value -1112.168354 -final value -1112.174829 -converged - -Attaching package: 'copula' - -The following object is masked from 'package:VineCopula': - - fitCopula - - [,1] [,2] [,3] [,4] - [1,] 0.7743684903 0.197224191 0.9780138442 0.201327350 - [2,] 0.3612444273 0.742611942 0.9787284394 0.498113709 - [3,] 0.0133158357 0.259946129 0.7758930807 0.016379053 - [4,] 0.0957447842 0.142163540 0.2111262376 0.811256444 - [5,] 0.0365471959 0.891637413 0.4832364111 0.466664528 - [6,] 0.9842240803 0.601345547 0.0383443474 0.141495691 - [7,] 0.8063855253 0.266685676 0.0427020509 0.612174522 - [8,] 0.5533483981 0.853500765 0.4697785398 0.397616561 - [9,] 0.8046367336 0.508897385 0.6349153537 0.494251721 - [10,] 0.2801308988 0.908710354 0.7841161578 0.558997022 - [11,] 0.2444374892 0.530970655 0.1183959420 0.983383433 - [12,] 0.8977528436 0.738573763 0.3773106968 0.606168831 - [13,] 0.5121942617 0.989246660 0.0691335856 0.084620626 - [14,] 0.1299455715 0.746132021 0.0388791817 0.685635417 - [15,] 0.1439773615 0.891079958 0.0896361163 0.037732719 - [16,] 0.7748743587 0.812063878 0.2606025457 0.651594998 - [17,] 0.9238038510 0.266106121 0.2661329871 0.910917896 - [18,] 0.5905635331 0.918147645 0.6037942769 0.328263949 - [19,] 0.6661178111 0.874787498 0.0688752665 0.793463009 - [20,] 0.5714270058 0.048944066 0.9803513540 0.914537349 - [21,] 0.7659584857 0.775846373 0.3125150499 0.842217308 - [22,] 0.3141499059 0.756563893 0.9675243802 0.169422925 - [23,] 0.6968751778 0.872650789 0.1324707782 0.078513110 - [24,] 0.3782238525 0.579624758 0.5364251249 0.108531924 - [25,] 0.7403151453 0.451789635 0.6461082133 0.749298733 - [26,] 0.5782921447 0.369409172 0.8813395619 0.599252820 - [27,] 0.2417592837 0.991064092 0.2720299934 0.225755411 - [28,] 0.3065364894 0.736066050 0.2058734051 0.242183074 - [29,] 0.4066693399 0.411321262 0.2207378661 0.868450051 - [30,] 0.7642357713 0.217509840 0.8997187309 0.816142634 - [31,] 0.1601893809 0.566658863 0.1824444511 0.867856246 - [32,] 0.0937132754 0.638223762 0.9734738106 0.009292930 - [33,] 0.7511339965 0.103923442 0.3436669305 0.591091853 - [34,] 0.5735987651 0.951237907 0.6553645076 0.377351639 - [35,] 0.9499114281 0.578954988 0.4752220884 0.254485867 - [36,] 0.3758446192 0.052798728 0.4420929269 0.697271063 - [37,] 0.7591612791 0.113734436 0.5760056155 0.099177053 - [38,] 0.1097460489 0.089127219 0.4737118890 0.356403576 - [39,] 0.2159698724 0.573215632 0.0016242201 0.718207759 - [40,] 0.2651135898 0.153830340 0.2900760283 0.067229538 - [41,] 0.9318368479 0.133479226 0.8126322976 0.759258038 - [42,] 0.3713044880 0.952166667 0.0996854173 0.307502680 - [43,] 0.4942615442 0.799964843 0.8426329251 0.647393905 - [44,] 0.6565674008 0.228435223 0.9240007692 0.485242063 - [45,] 0.5546194194 0.852844047 0.0898779368 0.740950904 - [46,] 0.3131348765 0.100732039 0.1840703834 0.213704721 - [47,] 0.6256980768 0.428000274 0.6235166367 0.577644360 - [48,] 0.1489856443 0.575752754 0.6500458319 0.638607423 - [49,] 0.7874355474 0.080619973 0.2898914691 0.223104578 - [50,] 0.5703688168 0.256050143 0.5171432674 0.769378419 - [51,] 0.1717156325 0.339101385 0.0346307140 0.378165489 - [52,] 0.9764601048 0.628306977 0.7929682066 0.576068396 - [53,] 0.1587420395 0.375621754 0.7126429004 0.642280536 - [54,] 0.2176803409 0.835219718 0.7511949919 0.092663403 - [55,] 0.1462978539 0.224104125 0.2406677336 0.479203157 - [56,] 0.1708911972 0.593215867 0.4259613717 0.782201018 - [57,] 0.8910149985 0.142018785 0.0872662787 0.298543895 - [58,] 0.3779736755 0.310509426 0.8581924702 0.185521572 - [59,] 0.0457103401 0.879344751 0.3266109165 0.610508331 - [60,] 0.4137852436 0.631626930 0.0201767548 0.560452844 - [61,] 0.2195571528 0.718596233 0.8913105952 0.714111986 - [62,] 0.7382447990 0.744075007 0.8478900143 0.701567872 - [63,] 0.4122337785 0.671587694 0.8733269582 0.958611961 - [64,] 0.6021437587 0.955820256 0.3093991736 0.610134651 - [65,] 0.6450917169 0.928400521 0.1264171537 0.114088232 - [66,] 0.7526843124 0.436705104 0.7802989122 0.076146137 - [67,] 0.2997063766 0.654224689 0.1309945930 0.765423296 - [68,] 0.3087085823 0.876935426 0.6371941748 0.342596608 - [69,] 0.4284886608 0.849930797 0.0008197445 0.813576228 - [70,] 0.0874580105 0.289057647 0.8494888905 0.805416501 - [71,] 0.9950445746 0.526671264 0.1112271971 0.945346809 - [72,] 0.7236955145 0.766487946 0.9305669612 0.498757267 - [73,] 0.7239606669 0.361902371 0.1568023660 0.303363824 - [74,] 0.7426302731 0.399672838 0.9347559172 0.946996531 - [75,] 0.5447802225 0.838801894 0.5616297950 0.707813082 - [76,] 0.0706888989 0.119998450 0.0310555075 0.463001627 - [77,] 0.4483564957 0.872894669 0.5048730967 0.902939290 - [78,] 0.0438287666 0.643314284 0.6988559945 0.432357483 - [79,] 0.8284931015 0.841108692 0.9299757103 0.485348572 - [80,] 0.7633930759 0.722670076 0.1641295145 0.992984264 - [81,] 0.4222436752 0.510317259 0.8841753434 0.815883017 - [82,] 0.3102896563 0.290614294 0.9858013957 0.483377530 - [83,] 0.1074008208 0.895984350 0.7338644972 0.764169478 - [84,] 0.0669399693 0.586228112 0.9107325065 0.992980055 - [85,] 0.7499900353 0.032749303 0.2553250678 0.424626995 - [86,] 0.3636265502 0.491994663 0.4343010753 0.570558629 - [87,] 0.9078977865 0.149545077 0.4103580574 0.386177163 - [88,] 0.3463237630 0.180769041 0.2505669079 0.723566933 - [89,] 0.3568387409 0.762676157 0.0026778339 0.902502597 - [90,] 0.9372461650 0.028783082 0.5805151563 0.320475659 - [91,] 0.5341461205 0.844306072 0.0044064738 0.239406295 - [92,] 0.0869177727 0.431421488 0.8170050057 0.685073657 - [93,] 0.5969637693 0.649056442 0.8868091749 0.752216479 - [94,] 0.4407886460 0.765468751 0.6110754195 0.230400142 - [95,] 0.7709763278 0.003451970 0.3045489269 0.677755016 - [96,] 0.8306224118 0.981180732 0.0146101408 0.427443687 - [97,] 0.0260336597 0.497721859 0.7918673381 0.536566794 - [98,] 0.8351932005 0.254128620 0.7913846564 0.873722913 - [99,] 0.2165347089 0.939788748 0.1385002721 0.383461147 -[100,] 0.4339649915 0.296471564 0.7247037594 0.336028221 -[101,] 0.9783641526 0.866081857 0.9018030704 0.325471421 -[102,] 0.3971384598 0.265053156 0.9096906008 0.838811320 -[103,] 0.7162932027 0.695596617 0.4661542471 0.385693899 -[104,] 0.9766215621 0.978381113 0.9296605005 0.850788791 -[105,] 0.8914492358 0.323866647 0.5856527244 0.253404879 -[106,] 0.6137620085 0.517032054 0.7084812184 0.384624342 -[107,] 0.6937829796 0.482504157 0.2806229971 0.111000120 -[108,] 0.2252501699 0.192968889 0.7676781283 0.144796298 -[109,] 0.3975286756 0.856579141 0.7646776433 0.349135153 -[110,] 0.2514651113 0.468221299 0.2596560335 0.251388092 -[111,] 0.1048730048 0.480938709 0.5862234468 0.157663264 -[112,] 0.8533307265 0.802534590 0.0630291228 0.774797393 -[113,] 0.8543458662 0.959840256 0.5253083515 0.794741470 -[114,] 0.9343227027 0.415850785 0.5709062461 0.715303819 -[115,] 0.4945777149 0.319346633 0.4525958812 0.921565412 -[116,] 0.5938526166 0.742607552 0.3950976874 0.381024701 -[117,] 0.7792707451 0.446705242 0.8011080394 0.053082889 -[118,] 0.6759392642 0.110763745 0.5593784570 0.578903007 -[119,] 0.0537102909 0.861216648 0.5484887112 0.191311767 -[120,] 0.1262770237 0.404101574 0.2281427665 0.790996143 -[121,] 0.7423158411 0.264997610 0.0497878187 0.727313877 -[122,] 0.1385788159 0.473839645 0.2715208770 0.361259246 -[123,] 0.3941312041 0.516422224 0.5751485603 0.913428178 -[124,] 0.7122545927 0.282151025 0.7430913700 0.336726994 -[125,] 0.0864723539 0.137007158 0.8332147521 0.281362747 -[126,] 0.3166397884 0.093503658 0.6104916255 0.486205183 -[127,] 0.4951614400 0.621448159 0.2981001402 0.622220361 -[128,] 0.8094501127 0.343012312 0.2104642675 0.773515745 -[129,] 0.9557679957 0.286419369 0.0794727448 0.661053497 -[130,] 0.3118138872 0.630501184 0.6049537384 0.876706274 -[131,] 0.0342228804 0.771673130 0.9368422253 0.254222035 -[132,] 0.3931704909 0.407810160 0.6519637303 0.232840615 -[133,] 0.2398367440 0.463389060 0.0757585869 0.739007716 -[134,] 0.6477067082 0.498322295 0.8434889137 0.425229206 -[135,] 0.2592272202 0.847242712 0.3250673641 0.072640638 -[136,] 0.4135137298 0.294362260 0.0082187485 0.169481597 -[137,] 0.1102090557 0.357150810 0.4791381841 0.628914608 -[138,] 0.0291915040 0.317528534 0.3061793284 0.688495747 -[139,] 0.5546681047 0.777362950 0.7623155026 0.425375876 -[140,] 0.9654694719 0.937939378 0.4363308840 0.365133651 -[141,] 0.9337793922 0.093578767 0.1778323287 0.634321812 -[142,] 0.4263039595 0.247728514 0.6804367560 0.951060107 -[143,] 0.0055627781 0.657620627 0.4659305960 0.862668524 -[144,] 0.1916651884 0.882191312 0.1169548559 0.884029913 -[145,] 0.8443164860 0.545540991 0.3381157848 0.612806927 -[146,] 0.3035845007 0.996642929 0.2449090297 0.494586456 -[147,] 0.0983962484 0.551325806 0.0632993493 0.110916249 -[148,] 0.2652095708 0.659197510 0.1011707778 0.915162335 -[149,] 0.4929900784 0.408335317 0.9016870754 0.628590122 -[150,] 0.0489578447 0.394935755 0.2591228082 0.331622616 -[151,] 0.6669344027 0.625317686 0.5075432686 0.284504177 -[152,] 0.3621549048 0.768481911 0.2988393311 0.371669197 -[153,] 0.0326483354 0.144800921 0.4674971097 0.467041486 -[154,] 0.6198881525 0.996896958 0.9224957055 0.030758351 -[155,] 0.5376262197 0.324835435 0.9192293161 0.362162672 -[156,] 0.2576842806 0.777084367 0.0603294310 0.148089551 -[157,] 0.3500228543 0.724576649 0.1668874554 0.625389982 -[158,] 0.2161285661 0.080344860 0.8572669341 0.534154641 -[159,] 0.9111834818 0.339142072 0.2979932092 0.839897137 -[160,] 0.0560075995 0.251565638 0.1065861024 0.084512484 -[161,] 0.0462357609 0.653913901 0.5670640329 0.604898218 -[162,] 0.3610695442 0.478445034 0.2008723405 0.222925923 -[163,] 0.9494444395 0.030701017 0.4029161467 0.581024964 -[164,] 0.7975459564 0.212698670 0.7370460802 0.834826638 -[165,] 0.3424032438 0.373054494 0.7425395199 0.102290838 -[166,] 0.8210614766 0.719421685 0.9488708046 0.614808284 -[167,] 0.4656176886 0.687057783 0.8464449772 0.275338395 -[168,] 0.2352189699 0.869283458 0.4975102539 0.530897514 -[169,] 0.8449436247 0.231636410 0.0050560117 0.197853174 -[170,] 0.8511695394 0.794882977 0.4079136280 0.341474468 -[171,] 0.2390391729 0.679682165 0.1650999326 0.534640821 -[172,] 0.9170250949 0.708150995 0.7061667675 0.180957641 -[173,] 0.7601360832 0.898726894 0.7251891324 0.194109676 -[174,] 0.7113639880 0.917680320 0.8643603884 0.609830835 -[175,] 0.2820347275 0.971891471 0.5355856742 0.227349275 -[176,] 0.5997360051 0.154081805 0.4637709183 0.845961729 -[177,] 0.4354194493 0.773573316 0.0967188128 0.424934591 -[178,] 0.5771441387 0.475725745 0.1756015311 0.234882956 -[179,] 0.4343538592 0.574824400 0.9920985959 0.756193620 -[180,] 0.3622156528 0.547339699 0.1859536748 0.524521267 -[181,] 0.2250695992 0.911340973 0.7638558464 0.341152911 -[182,] 0.8203911844 0.984728851 0.4024798393 0.398337749 -[183,] 0.3553854842 0.996304989 0.4209121999 0.825072953 -[184,] 0.0540067432 0.126679682 0.9832146429 0.438097001 -[185,] 0.0977464563 0.144636228 0.6997192786 0.964076800 -[186,] 0.5718035589 0.976129007 0.7661929270 0.353297002 -[187,] 0.6672807375 0.812140311 0.6806913668 0.417172965 -[188,] 0.6312760920 0.845643334 0.3147387863 0.623067643 -[189,] 0.2489069414 0.170307136 0.0528473828 0.352397213 -[190,] 0.7154197919 0.769427613 0.0439616535 0.296600588 -[191,] 0.3728102313 0.606454670 0.1744521784 0.325637069 -[192,] 0.5313717655 0.213290896 0.1098954093 0.470625348 -[193,] 0.0183186221 0.612048755 0.3343215247 0.983097545 -[194,] 0.6339995915 0.751820059 0.2734629191 0.243564314 -[195,] 0.3502755684 0.483300012 0.9734322524 0.218934502 -[196,] 0.4920768677 0.722552758 0.5070240900 0.070143877 -[197,] 0.0194451697 0.205571976 0.7541954345 0.630418118 -[198,] 0.8489873135 0.051017051 0.8036233829 0.583407820 -[199,] 0.8866788479 0.950272547 0.0732990042 0.834296813 -[200,] 0.3632328885 0.444549295 0.9541965688 0.010449900 -[201,] 0.2735836152 0.830732305 0.8230200189 0.392719318 -[202,] 0.7352467482 0.901445550 0.0822419475 0.368879102 -[203,] 0.3630899456 0.488129941 0.8006980552 0.575974445 -[204,] 0.7874140171 0.849424730 0.1900799496 0.533960375 -[205,] 0.8334457523 0.754456814 0.4303900155 0.755243090 -[206,] 0.3164512538 0.821538813 0.6494338685 0.154915826 -[207,] 0.3741788722 0.286865845 0.8432514123 0.181860059 -[208,] 0.6069478868 0.657173519 0.8113320200 0.546618887 -[209,] 0.8379858243 0.066471890 0.9748757288 0.805784753 -[210,] 0.0663143010 0.781842248 0.5844962969 0.798303778 -[211,] 0.5553825684 0.826247105 0.2980761654 0.934750434 -[212,] 0.6941594929 0.863456176 0.2019991342 0.263072162 -[213,] 0.8025015295 0.022981469 0.7881118841 0.121721596 -[214,] 0.2573423921 0.105063497 0.3959441814 0.406720767 -[215,] 0.4574301527 0.014828125 0.9075640836 0.366266056 -[216,] 0.7250718824 0.783072366 0.4091000268 0.215065519 -[217,] 0.4007112575 0.590563430 0.5302661911 0.147716149 -[218,] 0.2249917972 0.566724799 0.2234066734 0.054572506 -[219,] 0.6243523695 0.855703998 0.0435405250 0.370553982 -[220,] 0.7651069134 0.951624621 0.4868271784 0.589320412 -[221,] 0.6758246957 0.319414223 0.6893930857 0.536409341 -[222,] 0.1508573301 0.847545645 0.3025167799 0.255791885 -[223,] 0.5158530220 0.665776487 0.5712286504 0.972977022 -[224,] 0.4382174690 0.607895790 0.8810680558 0.382243131 -[225,] 0.9040353345 0.818195505 0.1890957728 0.279341920 -[226,] 0.0956006302 0.433048549 0.1651034511 0.184365910 -[227,] 0.7956483513 0.622831352 0.5386761294 0.034711238 -[228,] 0.3661794967 0.195988555 0.2794191148 0.962412738 -[229,] 0.9471271602 0.549059042 0.9749584261 0.717982193 -[230,] 0.3556773327 0.867656888 0.2311769573 0.076064603 -[231,] 0.3916409630 0.681572748 0.9537506220 0.020585128 -[232,] 0.7171780958 0.669524003 0.6586226965 0.254619111 -[233,] 0.3992693252 0.494142564 0.1740932919 0.194849428 -[234,] 0.8798466546 0.476180211 0.1617385235 0.405467161 -[235,] 0.1666286134 0.075125683 0.2838694500 0.076784107 -[236,] 0.9361824323 0.933077563 0.1356491460 0.679490731 -[237,] 0.5197204188 0.339432430 0.0399253590 0.182384872 -[238,] 0.3721226270 0.752011640 0.1098320589 0.798284948 -[239,] 0.1836079187 0.603453786 0.6101417094 0.041103652 -[240,] 0.4993634163 0.207342210 0.3261762194 0.486902969 -[241,] 0.6467777344 0.129989076 0.6651675196 0.449809124 -[242,] 0.6536722353 0.695856193 0.7535691005 0.061294960 -[243,] 0.0499363518 0.046064124 0.8446276195 0.104884493 -[244,] 0.2620879861 0.148730939 0.1752178846 0.019662158 -[245,] 0.4427078820 0.094287481 0.8933788843 0.585570112 -[246,] 0.9169778530 0.648075843 0.7762387784 0.204912888 -[247,] 0.5732168553 0.863256845 0.5047426480 0.469652176 -[248,] 0.4276488579 0.131531685 0.1593779558 0.845790585 -[249,] 0.8587067372 0.502891751 0.5593184705 0.375858957 -[250,] 0.9890882210 0.938063616 0.9706202168 0.216183099 -[251,] 0.8379715749 0.129972132 0.5695172495 0.625571513 -[252,] 0.7212316899 0.572297784 0.0382156211 0.051894007 -[253,] 0.5216590953 0.015851347 0.9769222983 0.272455045 -[254,] 0.5143919997 0.114772279 0.1596595603 0.809009656 -[255,] 0.7357275770 0.853319851 0.2404850596 0.704516945 -[256,] 0.1952619776 0.944837198 0.3381335489 0.726653310 -[257,] 0.6910012066 0.214935871 0.4175838032 0.218764917 -[258,] 0.4867478984 0.343270314 0.2169513768 0.380788512 -[259,] 0.4428913160 0.343588427 0.5667717615 0.949275269 -[260,] 0.1775206316 0.142845772 0.0695777584 0.118463847 -[261,] 0.2351934593 0.337216868 0.9805003721 0.005284573 -[262,] 0.4857526280 0.558714604 0.5375014008 0.511780816 -[263,] 0.6552407253 0.130329409 0.7706996505 0.282453222 -[264,] 0.2740938128 0.395738140 0.1035083684 0.006252106 -[265,] 0.7483767993 0.547375288 0.6094368612 0.932357808 -[266,] 0.6706526354 0.151936714 0.9280017349 0.642849064 -[267,] 0.1692593219 0.512618867 0.8483696235 0.554460279 -[268,] 0.6046569496 0.175424204 0.5205884210 0.980532835 -[269,] 0.4171814560 0.160848656 0.0254654889 0.898504830 -[270,] 0.4675834295 0.565785344 0.8435611597 0.885702458 -[271,] 0.2869922114 0.653929896 0.0656541944 0.549899117 -[272,] 0.2903471391 0.175998944 0.2433835415 0.855399843 -[273,] 0.9098031069 0.600858136 0.0691988289 0.630983036 -[274,] 0.5219512563 0.196392351 0.9942230587 0.171735779 -[275,] 0.7468491504 0.370164049 0.7109902038 0.282020319 -[276,] 0.1262481522 0.390918806 0.8852912916 0.104233933 -[277,] 0.0300880789 0.647038511 0.1334821235 0.240433870 -[278,] 0.6879101389 0.589410251 0.4775275313 0.491272935 -[279,] 0.6160576248 0.761771664 0.2333714277 0.272765368 -[280,] 0.3549011711 0.051849936 0.8768312477 0.877099060 -[281,] 0.8581745944 0.971428056 0.5737855358 0.332571355 -[282,] 0.0207595848 0.042617511 0.7648429871 0.827382307 -[283,] 0.6349156951 0.124888753 0.7582474155 0.187631488 -[284,] 0.1530019275 0.031149091 0.9507271959 0.772281578 -[285,] 0.6720045879 0.978253266 0.1504266458 0.133118892 -[286,] 0.8485787737 0.734150176 0.8971518457 0.308240966 -[287,] 0.8162173289 0.762108188 0.0482832582 0.678645760 -[288,] 0.1517000652 0.989808477 0.5504770332 0.590718119 -[289,] 0.6345506713 0.545683430 0.0139598753 0.678947515 -[290,] 0.8936809630 0.442411056 0.1092832964 0.419108480 -[291,] 0.9164704378 0.303237157 0.7087321593 0.891897406 -[292,] 0.5595637094 0.593235709 0.8172157183 0.180815238 -[293,] 0.5450307759 0.731739299 0.7757680221 0.936030307 -[294,] 0.9844803826 0.952755239 0.7349386474 0.200063891 -[295,] 0.5252404297 0.912472579 0.1983703848 0.873221091 -[296,] 0.5562255983 0.346838131 0.2333369483 0.126236536 -[297,] 0.4020865897 0.884241141 0.2719432884 0.604082966 -[298,] 0.7625291559 0.952015422 0.6255507688 0.757415980 -[299,] 0.5018466183 0.931425986 0.1910752419 0.806532523 -[300,] 0.2368220380 0.122242337 0.3275852152 0.173029160 -[301,] 0.5842146724 0.936198387 0.8389963040 0.126142483 -[302,] 0.2276427920 0.316277360 0.5839341637 0.590474609 -[303,] 0.5422491468 0.200553625 0.5389597269 0.879883609 -[304,] 0.7374660282 0.768241838 0.9755696333 0.763199614 -[305,] 0.1471564339 0.559007475 0.9607511451 0.217728840 -[306,] 0.5889839104 0.675189323 0.5226181226 0.430570702 -[307,] 0.7506851617 0.386064682 0.4334508299 0.965842676 -[308,] 0.2637242335 0.650240324 0.3104421902 0.638478931 -[309,] 0.1803990712 0.089696390 0.2932914000 0.006119711 -[310,] 0.7184373385 0.404312139 0.1811476685 0.965097900 -[311,] 0.2377872753 0.984447725 0.8718100854 0.106952735 -[312,] 0.3503712702 0.603536791 0.8463436530 0.310144706 -[313,] 0.4495570462 0.272465356 0.5138976437 0.488285378 -[314,] 0.8614247281 0.744840986 0.1210435661 0.716413555 -[315,] 0.1381337575 0.230298426 0.9294903460 0.636520796 -[316,] 0.7497352820 0.403666644 0.8337023426 0.202122381 -[317,] 0.3304093368 0.647110599 0.3845536171 0.331561915 -[318,] 0.9508939169 0.080059566 0.0898211326 0.447491282 -[319,] 0.5857214541 0.141073883 0.1875592161 0.181189312 -[320,] 0.0435665241 0.641066964 0.0711824722 0.029968474 -[321,] 0.8272884621 0.002672554 0.7767159531 0.245260445 -[322,] 0.2731244157 0.085408063 0.2267000161 0.289309197 -[323,] 0.0462573939 0.811523305 0.1565170230 0.912522806 -[324,] 0.2103107716 0.739090083 0.2226596023 0.409184119 -[325,] 0.4961829542 0.965206025 0.6379224574 0.234194163 -[326,] 0.0008594517 0.978437975 0.9299203167 0.034800552 -[327,] 0.0392625227 0.771819892 0.3514823148 0.490745436 -[328,] 0.5656738437 0.684209259 0.3451482116 0.451761807 -[329,] 0.6252417772 0.079320913 0.2755355502 0.746796617 -[330,] 0.2451075327 0.365693996 0.8820323015 0.706722256 -[331,] 0.5734970425 0.119838247 0.1386956216 0.963373072 -[332,] 0.8048224875 0.931301645 0.6412679160 0.307184222 -[333,] 0.2925654361 0.303601390 0.7828756943 0.931845217 -[334,] 0.9969732796 0.564097288 0.8340119412 0.754510663 -[335,] 0.3455017877 0.795235615 0.0569652505 0.611305799 -[336,] 0.2326845648 0.521942220 0.2309741084 0.313772211 -[337,] 0.0869935376 0.723186854 0.8113833682 0.639738104 -[338,] 0.2045802616 0.380672575 0.5373175945 0.716390287 -[339,] 0.6589587668 0.506170188 0.9339784922 0.100771416 -[340,] 0.3214371668 0.473791970 0.2646674979 0.179875074 -[341,] 0.7434530903 0.984879570 0.4664959104 0.117323593 -[342,] 0.4472260750 0.892814937 0.5007153689 0.516901009 -[343,] 0.4599100070 0.204192071 0.5612023761 0.483082423 -[344,] 0.4270402647 0.987336002 0.7972487614 0.112641990 -[345,] 0.4507297378 0.746419842 0.8726341100 0.589500092 -[346,] 0.7132621077 0.550999165 0.0264370556 0.982933392 -[347,] 0.6183664217 0.458623182 0.2545521415 0.384219691 -[348,] 0.5129058261 0.226279549 0.9553426658 0.474686575 -[349,] 0.0139840404 0.377497884 0.3167468484 0.271984325 -[350,] 0.6544892930 0.589097009 0.7383347314 0.967833379 -[351,] 0.2483195239 0.783252000 0.4792166667 0.943698976 -[352,] 0.3341092798 0.376029821 0.5487082228 0.173540368 -[353,] 0.8799060567 0.286639028 0.5109444920 0.647152330 -[354,] 0.3399565150 0.713364316 0.7914584880 0.534581822 -[355,] 0.5333003050 0.738410240 0.5695481685 0.118196896 -[356,] 0.6283332780 0.021384809 0.3013993963 0.235892471 -[357,] 0.3496081459 0.082318803 0.8034476112 0.615855429 -[358,] 0.6827916105 0.739332259 0.4556267061 0.560452784 -[359,] 0.3037325416 0.954792430 0.5853331985 0.818992345 -[360,] 0.8175444310 0.362225051 0.7151003983 0.228975809 -[361,] 0.0063419391 0.284399928 0.5142549528 0.487628832 -[362,] 0.4775556314 0.584947050 0.5906238395 0.117727362 -[363,] 0.4372084681 0.769685948 0.2747515938 0.682309937 -[364,] 0.7498383273 0.967765797 0.8447801836 0.280101757 -[365,] 0.1267350963 0.504340193 0.0679511335 0.255510229 -[366,] 0.1332432132 0.210321337 0.5455718499 0.371653482 -[367,] 0.4835004443 0.540350976 0.6908350498 0.774367710 -[368,] 0.7049593334 0.203165571 0.7171184889 0.545066704 -[369,] 0.4783587519 0.441262098 0.2402160212 0.846125873 -[370,] 0.3122980180 0.676219228 0.6122906946 0.453429835 -[371,] 0.7974219534 0.361899156 0.3115806549 0.844481082 -[372,] 0.6184745003 0.981996044 0.3197651270 0.157665661 -[373,] 0.6590813969 0.843595678 0.6124570610 0.974553713 -[374,] 0.4819237876 0.249550602 0.3836133203 0.453789817 -[375,] 0.5730831542 0.467314963 0.3064885780 0.033655912 -[376,] 0.7225157402 0.457241144 0.7478901469 0.796643843 -[377,] 0.8063645191 0.499557219 0.0245002492 0.945755220 -[378,] 0.4178847608 0.473695976 0.7174830632 0.230468606 -[379,] 0.3640867800 0.620711620 0.4733614819 0.563877373 -[380,] 0.0611493590 0.194258613 0.4997424681 0.789781849 -[381,] 0.7475657235 0.859217947 0.6345658496 0.970325647 -[382,] 0.3332323693 0.199598975 0.2802914227 0.010655957 -[383,] 0.2150533223 0.709788083 0.5530776870 0.743368714 -[384,] 0.6805443619 0.607220354 0.4279221755 0.394690320 -[385,] 0.5582065266 0.007691594 0.7015192644 0.294321409 -[386,] 0.2983241724 0.423875528 0.6592473609 0.368042240 -[387,] 0.7625086210 0.786160679 0.0922064043 0.889377389 -[388,] 0.7098486831 0.251227863 0.6817111718 0.745813687 -[389,] 0.9735676560 0.920136021 0.6274220380 0.651534516 -[390,] 0.7743301054 0.544774732 0.4898269868 0.445321190 -[391,] 0.8847565223 0.404856124 0.3482548681 0.691706630 -[392,] 0.8659257204 0.217954148 0.8806516791 0.949878403 -[393,] 0.9289334000 0.865793303 0.8340856282 0.511615770 -[394,] 0.5516591715 0.749031011 0.5261062849 0.701813726 -[395,] 0.4214334434 0.466923875 0.3314881807 0.410330325 -[396,] 0.4553614694 0.818652601 0.5154953874 0.328631658 -[397,] 0.7040734228 0.618281393 0.9011229631 0.979763788 -[398,] 0.2238232053 0.640883545 0.7483067627 0.570441278 -[399,] 0.2522819676 0.873365106 0.5108155124 0.644385837 -[400,] 0.7545125270 0.644549186 0.1143546472 0.627281009 -[401,] 0.3164177155 0.635695940 0.2865649781 0.836701028 -[402,] 0.9811237243 0.190904356 0.5622383626 0.923269505 -[403,] 0.3227116908 0.379517097 0.7096079062 0.862924377 -[404,] 0.7429936761 0.086441899 0.3834459390 0.908614482 -[405,] 0.7694523162 0.988333698 0.2233864155 0.913187601 -[406,] 0.8093011871 0.831121516 0.6951341031 0.655903636 -[407,] 0.8530541372 0.494838888 0.2504522009 0.643939460 -[408,] 0.0776142452 0.790950005 0.5406704834 0.765040339 -[409,] 0.2458512834 0.844469580 0.9835063349 0.190881296 -[410,] 0.8844916471 0.269971595 0.8269423742 0.707157602 -[411,] 0.2149199184 0.897151966 0.2607488516 0.193738857 -[412,] 0.7742234177 0.899004401 0.4380294683 0.936016138 -[413,] 0.5878038059 0.149082543 0.2992697598 0.423564698 -[414,] 0.6609678387 0.627270590 0.0150950819 0.953805619 -[415,] 0.3028782711 0.082396913 0.5659312594 0.741202455 -[416,] 0.4600533564 0.452345563 0.0214497149 0.544668820 -[417,] 0.5039271156 0.939515311 0.5204002946 0.498414306 -[418,] 0.1686603492 0.165276090 0.0292735882 0.924069965 -[419,] 0.3560732966 0.429793423 0.5785043212 0.893840679 -[420,] 0.7226284344 0.764599458 0.7078876568 0.193169154 -[421,] 0.1514286688 0.984273796 0.2338212284 0.253472141 -[422,] 0.9915046366 0.953001114 0.1218234005 0.233221736 -[423,] 0.5811265053 0.524461516 0.6658012238 0.874910048 -[424,] 0.1873145448 0.617773264 0.5029998790 0.215476780 -[425,] 0.6326752396 0.891035941 0.3373042420 0.277082390 -[426,] 0.6685043760 0.209715080 0.0260367626 0.323245066 -[427,] 0.3915478231 0.893670052 0.7877903206 0.311938372 -[428,] 0.9751131407 0.577514792 0.0968653613 0.728618009 -[429,] 0.1436449105 0.349319551 0.4177987482 0.168554445 -[430,] 0.2593039705 0.599343111 0.9572925649 0.618933699 -[431,] 0.4549940815 0.629218970 0.2132225353 0.664408606 -[432,] 0.8414056879 0.648659217 0.2155673727 0.927485623 -[433,] 0.0536126506 0.067957489 0.9023624149 0.383444031 -[434,] 0.2189195133 0.040477929 0.7147254974 0.113089618 -[435,] 0.3792855509 0.365007456 0.5848087675 0.173416571 -[436,] 0.3150607862 0.800166768 0.8882558539 0.558242882 -[437,] 0.0325166397 0.741979415 0.9821108207 0.969644915 -[438,] 0.8812028181 0.673207889 0.6916135726 0.803342980 -[439,] 0.6713359591 0.070932230 0.9052041599 0.885460004 -[440,] 0.8755675785 0.426844865 0.0720194071 0.040594862 -[441,] 0.4640613201 0.917845586 0.0770980753 0.320827506 -[442,] 0.7899558700 0.606043878 0.5308555972 0.717911145 -[443,] 0.1804128489 0.134091402 0.8043711416 0.977149764 -[444,] 0.3264265098 0.068150678 0.1164922572 0.252503704 -[445,] 0.5777970040 0.404012336 0.0123092602 0.949841157 -[446,] 0.4000040281 0.166974100 0.3439672512 0.958505486 -[447,] 0.7181118056 0.140387560 0.2038691312 0.188195670 -[448,] 0.9133554720 0.351584171 0.1795345445 0.400630542 -[449,] 0.1937928086 0.979552586 0.8262231434 0.375924897 -[450,] 0.7492259657 0.052619456 0.7617706263 0.670483123 -[451,] 0.9213224193 0.653613240 0.3376331248 0.201285034 -[452,] 0.8218441333 0.976918009 0.1546842474 0.594470740 -[453,] 0.1938440509 0.356419227 0.9787501716 0.046199550 -[454,] 0.9108442455 0.802719879 0.1072460155 0.527842021 -[455,] 0.9923165957 0.803770601 0.4477615375 0.886121283 -[456,] 0.9211582213 0.142731794 0.2807522188 0.328247994 -[457,] 0.4821647708 0.994336465 0.7341695703 0.073967295 -[458,] 0.4346513711 0.188426985 0.5234703438 0.258969377 -[459,] 0.8354025509 0.542861188 0.1149569396 0.180574574 -[460,] 0.1249928817 0.880070754 0.6234266129 0.175475703 -[461,] 0.0131786917 0.925774553 0.7951764143 0.636924250 -[462,] 0.2232337862 0.517870123 0.2479055722 0.093815241 -[463,] 0.7409352949 0.592951744 0.7411500716 0.708057674 -[464,] 0.5213114761 0.035932635 0.5251213673 0.720009909 -[465,] 0.7646594488 0.644735194 0.7603860942 0.549982283 -[466,] 0.3196102399 0.791079991 0.9488104226 0.061198636 -[467,] 0.7752973635 0.435540424 0.2463884139 0.510544375 -[468,] 0.7874625481 0.213862279 0.1370006786 0.622952813 -[469,] 0.0745328909 0.216816646 0.4719713903 0.907391601 -[470,] 0.8817755992 0.329852495 0.6832479427 0.496731067 -[471,] 0.9013310676 0.034829894 0.4524417035 0.896870447 -[472,] 0.0517414398 0.504553244 0.4490421708 0.931787841 -[473,] 0.9515366387 0.431552263 0.8632053840 0.023747243 -[474,] 0.9683196915 0.779132628 0.5074752122 0.090629205 -[475,] 0.6380631288 0.185943191 0.2698770086 0.086474867 -[476,] 0.5898871799 0.976563449 0.4111405013 0.490001683 -[477,] 0.1948943604 0.727657019 0.5269006987 0.446843790 -[478,] 0.3189426479 0.661659849 0.3534905314 0.259430545 -[479,] 0.5031006087 0.919297140 0.0429212481 0.057736546 -[480,] 0.2720884683 0.709792360 0.6360181207 0.430870017 -[481,] 0.8732802274 0.672226139 0.0633931179 0.164927706 -[482,] 0.8168958363 0.200113487 0.6695783506 0.979309310 -[483,] 0.5323344604 0.925127439 0.1212887508 0.468892250 -[484,] 0.7582059298 0.220465179 0.0527531148 0.481854430 -[485,] 0.0534745893 0.751608602 0.9274321918 0.640348280 -[486,] 0.5273279313 0.437461634 0.7705278802 0.296806316 -[487,] 0.1841296859 0.439831004 0.8581846172 0.407613884 -[488,] 0.2110721290 0.281733499 0.4445500858 0.508451787 -[489,] 0.5172161995 0.380185867 0.7913010104 0.444226797 -[490,] 0.4481356149 0.544575689 0.2139044206 0.161247622 -[491,] 0.2847440389 0.361442873 0.0006444743 0.788667279 -[492,] 0.8338946362 0.029033367 0.2910237401 0.101507748 -[493,] 0.7203227866 0.362797651 0.9633487707 0.414969382 -[494,] 0.4813747993 0.637801260 0.9806914954 0.200667940 -[495,] 0.1825481600 0.638969197 0.1697487144 0.823323684 -[496,] 0.1720669053 0.977869589 0.5419753792 0.174292463 -[497,] 0.6621374113 0.003031325 0.7740950705 0.653777724 -[498,] 0.6787871555 0.231239350 0.8419057757 0.845386500 -[499,] 0.1530470233 0.235863829 0.4731824279 0.239403040 -[500,] 0.3042590283 0.707197251 0.3795309828 0.382067516 > > proc.time() user system elapsed - 79.53 0.09 79.67 + 0.18 0.06 0.23 From noreply at r-forge.r-project.org Tue Jan 20 11:03:00 2015 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Tue, 20 Jan 2015 11:03:00 +0100 (CET) Subject: [Vinecopula-commits] r75 - / pkg pkg/man pkg/tests/Examples Message-ID: <20150120100300.89A6F1878DC@r-forge.r-project.org> Author: etobi Date: 2015-01-20 11:02:54 +0100 (Tue, 20 Jan 2015) New Revision: 75 Modified: pkg.pdf pkg/DESCRIPTION pkg/man/VineCopula-package.Rd pkg/tests/Examples/VineCopula-Ex.Rout.save Log: some small modifications to make the package suitable for CRAN Modified: pkg/DESCRIPTION =================================================================== --- pkg/DESCRIPTION 2015-01-20 08:29:47 UTC (rev 74) +++ pkg/DESCRIPTION 2015-01-20 10:02:54 UTC (rev 75) @@ -1,6 +1,6 @@ Package: VineCopula Type: Package -Title: Statistical inference of vine copulas +Title: Statistical Inference of Vine Copulas Version: 1.4 Date: 2015-01-20 Author: Ulf Schepsmeier, Jakob Stoeber, Eike Christian Brechmann, Benedikt Graeler Modified: pkg/man/VineCopula-package.Rd =================================================================== --- pkg/man/VineCopula-package.Rd 2015-01-20 08:29:47 UTC (rev 74) +++ pkg/man/VineCopula-package.Rd 2015-01-20 10:02:54 UTC (rev 75) @@ -3,7 +3,7 @@ \alias{VineCopula} \docType{package} -\title{Statistical inference of vine copulas} +\title{Statistical Inference of Vine Copulas} \description{ This package provides functions for statistical inference of vine copulas. Modified: pkg/tests/Examples/VineCopula-Ex.Rout.save =================================================================== --- pkg/tests/Examples/VineCopula-Ex.Rout.save 2015-01-20 08:29:47 UTC (rev 74) +++ pkg/tests/Examples/VineCopula-Ex.Rout.save 2015-01-20 10:02:54 UTC (rev 75) @@ -1,6 +1,6 @@ -R version 3.0.2 (2013-09-25) -- "Frisbee Sailing" -Copyright (C) 2013 The R Foundation for Statistical Computing +R Under development (unstable) (2015-01-14 r67471) -- "Unsuffered Consequences" +Copyright (C) 2015 The R Foundation for Statistical Computing Platform: x86_64-w64-mingw32/x64 (64-bit) R is free software and comes with ABSOLUTELY NO WARRANTY. @@ -21,3333 +21,3602 @@ > source(file.path(R.home("share"), "R", "examples-header.R")) > options(warn = 1) > options(pager = "console") +> base::assign(".ExTimings", "VineCopula-Ex.timings", pos = 'CheckExEnv') +> base::cat("name\tuser\tsystem\telapsed\n", file=base::get(".ExTimings", pos = 'CheckExEnv')) +> base::assign(".format_ptime", ++ function(x) { ++ if(!is.na(x[4L])) x[1L] <- x[1L] + x[4L] ++ if(!is.na(x[5L])) x[2L] <- x[2L] + x[5L] ++ options(OutDec = '.') ++ format(x[1L:3L], digits = 7L) ++ }, ++ pos = 'CheckExEnv') +> +> ### * > library('VineCopula') -> -> base::assign(".oldSearch", base::search(), pos = 'CheckExEnv') -> cleanEx() -> nameEx("BB1Copula-class") -> ### * BB1Copula-class -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BB1Copula-class -> ### Title: Classes '"BB1Copula"', '"surBB1Copula"', '"r90BB1Copula"' and -> ### '"r270BB1Copula"' -> ### Aliases: BB1Copula-class dduCopula,numeric,BB1Copula-method -> ### ddvCopula,numeric,BB1Copula-method dduCopula,matrix,BB1Copula-method -> ### ddvCopula,matrix,BB1Copula-method getKendallDistr,BB1Copula-method -> ### kendallDistribution,BB1Copula-method surBB1Copula-class -> ### dduCopula,numeric,surBB1Copula-method -> ### ddvCopula,numeric,surBB1Copula-method -> ### dduCopula,matrix,surBB1Copula-method -> ### ddvCopula,matrix,surBB1Copula-method r90BB1Copula-class -> ### dduCopula,numeric,r90BB1Copula-method -> ### ddvCopula,numeric,r90BB1Copula-method -> ### dduCopula,matrix,r90BB1Copula-method -> ### ddvCopula,matrix,r90BB1Copula-method r270BB1Copula-class -> ### dduCopula,numeric,r270BB1Copula-method -> ### ddvCopula,numeric,r270BB1Copula-method -> ### dduCopula,matrix,r270BB1Copula-method -> ### ddvCopula,matrix,r270BB1Copula-method -> ### Keywords: classes -> -> ### ** Examples -> -> showClass("BB1Copula") -Class "BB1Copula" [package "VineCopula"] - -Slots: - -Name: family dimension parameters param.names param.lowbnd -Class: numeric integer numeric character numeric - -Name: param.upbnd fullname -Class: numeric character - -Extends: -Class "copula", directly -Class "twoParamBiCop", directly -Class "Copula", by class "copula", distance 2 -> -> -> -> cleanEx() -> nameEx("BB1Copula") -> ### * BB1Copula -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BB1Copula -> ### Title: Constructor of the BB1 family and rotated versions thereof -> ### Aliases: BB1Copula surBB1Copula r90BB1Copula r270BB1Copula -> ### Keywords: distribution copula -> -> ### ** Examples -> -> library(copula) - -Attaching package: 'copula' - -The following object is masked from 'package:VineCopula': - - fitCopula - -> -> persp(BB1Copula(c(1,1.5)),dCopula, zlim=c(0,10)) -Warning in persp.default(xis, yis, zmat, theta = theta, phi = phi, expand = expand, : - surface extends beyond the box -> persp(surBB1Copula(c(1,1.5)),dCopula, zlim=c(0,10)) -Warning in persp.default(xis, yis, zmat, theta = theta, phi = phi, expand = expand, : - surface extends beyond the box -> persp(r90BB1Copula(c(-1,-1.5)),dCopula, zlim=c(0,10)) -Warning in persp.default(xis, yis, zmat, theta = theta, phi = phi, expand = expand, : - surface extends beyond the box -> persp(r270BB1Copula(c(-1,-1.5)),dCopula, zlim=c(0,10)) -Warning in persp.default(xis, yis, zmat, theta = theta, phi = phi, expand = expand, : - surface extends beyond the box -> -> -> -> cleanEx() - -detaching 'package:copula' - -> nameEx("BB6Copula-class") -> ### * BB6Copula-class -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BB6Copula-class -> ### Title: Classes '"BB6Copula"', '"surBB6Copula"', '"r90BB6Copula"' and -> ### '"r270BB6Copula"' -> ### Aliases: BB6Copula-class dduCopula,numeric,BB6Copula-method -> ### ddvCopula,numeric,BB6Copula-method dduCopula,matrix,BB6Copula-method -> ### ddvCopula,matrix,BB6Copula-method getKendallDistr,BB6Copula-method -> ### kendallDistribution,BB6Copula-method surBB6Copula-class -> ### dduCopula,numeric,surBB6Copula-method -> ### ddvCopula,numeric,surBB6Copula-method -> ### dduCopula,matrix,surBB6Copula-method -> ### ddvCopula,matrix,surBB6Copula-method r90BB6Copula-class -> ### dduCopula,numeric,r90BB6Copula-method -> ### ddvCopula,numeric,r90BB6Copula-method -> ### dduCopula,matrix,r90BB6Copula-method -> ### ddvCopula,matrix,r90BB6Copula-method r270BB6Copula-class -> ### dduCopula,numeric,r270BB6Copula-method -> ### ddvCopula,numeric,r270BB6Copula-method -> ### dduCopula,matrix,r270BB6Copula-method -> ### ddvCopula,matrix,r270BB6Copula-method -> ### Keywords: classes -> -> ### ** Examples -> -> showClass("BB6Copula") -Class "BB6Copula" [package "VineCopula"] - -Slots: - -Name: family dimension parameters param.names param.lowbnd -Class: numeric integer numeric character numeric - -Name: param.upbnd fullname -Class: numeric character - -Extends: -Class "copula", directly -Class "twoParamBiCop", directly -Class "Copula", by class "copula", distance 2 -> -> -> -> cleanEx() -> nameEx("BB6Copula") -> ### * BB6Copula -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BB6Copula -> ### Title: Constructor of the BB6 family and its derivatives -> ### Aliases: BB6Copula surBB6Copula r90BB6Copula r270BB6Copula -> -> ### ** Examples -> -> library(copula) - -Attaching package: 'copula' - -The following object is masked from 'package:VineCopula': - - fitCopula - -> -> persp(BB6Copula(c(1,1.5)),dCopula, zlim=c(0,10)) -Warning in persp.default(xis, yis, zmat, theta = theta, phi = phi, expand = expand, : - surface extends beyond the box -> persp(surBB6Copula(c(1,1.5)),dCopula, zlim=c(0,10)) -Warning in persp.default(xis, yis, zmat, theta = theta, phi = phi, expand = expand, : - surface extends beyond the box -> persp(r90BB6Copula(c(-1,-1.5)),dCopula, zlim=c(0,10)) -Warning in persp.default(xis, yis, zmat, theta = theta, phi = phi, expand = expand, : - surface extends beyond the box -> persp(r270BB6Copula(c(-1,-1.5)),dCopula, zlim=c(0,10)) -Warning in persp.default(xis, yis, zmat, theta = theta, phi = phi, expand = expand, : - surface extends beyond the box -> -> -> -> cleanEx() - -detaching 'package:copula' - -> nameEx("BB7Copula-class") -> ### * BB7Copula-class -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BB7Copula-class -> ### Title: Classes '"BB7Copula"', '"surBB7Copula"', '"r90BB7Copula"' and -> ### '"r270BB7Copula"' -> ### Aliases: BB7Copula-class dduCopula,numeric,BB7Copula-method -> ### ddvCopula,numeric,BB7Copula-method dduCopula,matrix,BB7Copula-method -> ### ddvCopula,matrix,BB7Copula-method getKendallDistr,BB7Copula-method -> ### kendallDistribution,BB7Copula-method surBB7Copula-class -> ### dduCopula,numeric,surBB7Copula-method -> ### ddvCopula,numeric,surBB7Copula-method -> ### dduCopula,matrix,surBB7Copula-method -> ### ddvCopula,matrix,surBB7Copula-method r90BB7Copula-class -> ### dduCopula,numeric,r90BB7Copula-method -> ### ddvCopula,numeric,r90BB7Copula-method -> ### dduCopula,matrix,r90BB7Copula-method -> ### ddvCopula,matrix,r90BB7Copula-method r270BB7Copula-class -> ### dduCopula,numeric,r270BB7Copula-method -> ### ddvCopula,numeric,r270BB7Copula-method -> ### dduCopula,matrix,r270BB7Copula-method -> ### ddvCopula,matrix,r270BB7Copula-method -> ### Keywords: classes -> -> ### ** Examples -> -> showClass("BB7Copula") -Class "BB7Copula" [package "VineCopula"] - -Slots: - -Name: family dimension parameters param.names param.lowbnd -Class: numeric integer numeric character numeric - -Name: param.upbnd fullname -Class: numeric character - -Extends: -Class "copula", directly -Class "twoParamBiCop", directly -Class "Copula", by class "copula", distance 2 -> -> -> -> cleanEx() -> nameEx("BB7Copula") -> ### * BB7Copula -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BB7Copula -> ### Title: Constructor of the BB7 family and its derivatives -> ### Aliases: BB7Copula surBB7Copula r90BB7Copula r270BB7Copula -> -> ### ** Examples -> -> library(copula) - -Attaching package: 'copula' - -The following object is masked from 'package:VineCopula': - - fitCopula - -> -> persp(BB7Copula(c(1,1.5)),dCopula, zlim=c(0,10)) -Warning in persp.default(xis, yis, zmat, theta = theta, phi = phi, expand = expand, : - surface extends beyond the box -> persp(surBB7Copula(c(1,1.5)),dCopula, zlim=c(0,10)) -Warning in persp.default(xis, yis, zmat, theta = theta, phi = phi, expand = expand, : - surface extends beyond the box -> persp(r90BB7Copula(c(-1,-1.5)),dCopula, zlim=c(0,10)) -Warning in persp.default(xis, yis, zmat, theta = theta, phi = phi, expand = expand, : - surface extends beyond the box -> persp(r270BB7Copula(c(-1,-1.5)),dCopula, zlim=c(0,10)) -Warning in persp.default(xis, yis, zmat, theta = theta, phi = phi, expand = expand, : - surface extends beyond the box -> -> -> -> cleanEx() - -detaching 'package:copula' - -> nameEx("BB8Copula-class") -> ### * BB8Copula-class -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BB8Copula-class -> ### Title: Classes '"BB8Copula"', '"surBB8Copula"', '"r90BB8Copula"' and -> ### '"r270BB8Copula"' -> ### Aliases: BB8Copula-class dduCopula,numeric,BB8Copula-method -> ### ddvCopula,numeric,BB8Copula-method dduCopula,matrix,BB8Copula-method -> ### ddvCopula,matrix,BB8Copula-method getKendallDistr,BB8Copula-method -> ### kendallDistribution,BB8Copula-method surBB8Copula-class -> ### dduCopula,numeric,surBB8Copula-method -> ### ddvCopula,numeric,surBB8Copula-method -> ### dduCopula,matrix,surBB8Copula-method -> ### ddvCopula,matrix,surBB8Copula-method r90BB8Copula-class -> ### dduCopula,numeric,r90BB8Copula-method -> ### ddvCopula,numeric,r90BB8Copula-method -> ### dduCopula,matrix,r90BB8Copula-method -> ### ddvCopula,matrix,r90BB8Copula-method r270BB8Copula-class -> ### dduCopula,numeric,r270BB8Copula-method -> ### ddvCopula,numeric,r270BB8Copula-method -> ### dduCopula,matrix,r270BB8Copula-method -> ### ddvCopula,matrix,r270BB8Copula-method fitCopula,twoParamBiCop-method -> ### Keywords: classes -> -> ### ** Examples -> -> showClass("BB8Copula") -Class "BB8Copula" [package "VineCopula"] - -Slots: - -Name: family dimension parameters param.names param.lowbnd -Class: numeric integer numeric character numeric - -Name: param.upbnd fullname -Class: numeric character - -Extends: -Class "copula", directly -Class "twoParamBiCop", directly -Class "Copula", by class "copula", distance 2 -> -> -> -> cleanEx() -> nameEx("BB8Copula") -> ### * BB8Copula -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BB8Copula -> ### Title: Constructor of the BB8 family and its derivatives -> ### Aliases: BB8Copula surBB8Copula r90BB8Copula r270BB8Copula -> -> ### ** Examples -> -> library(copula) - -Attaching package: 'copula' - -The following object is masked from 'package:VineCopula': - - fitCopula - -> -> persp(BB8Copula(c(1,0.5)),dCopula, zlim=c(0,10)) -> persp(surBB8Copula(c(1,0.5)),dCopula, zlim=c(0,10)) -> persp(r90BB8Copula(c(-1,-0.5)),dCopula, zlim=c(0,10)) -> persp(r270BB8Copula(c(-1,-0.5)),dCopula, zlim=c(0,10)) -> -> -> -> cleanEx() - -detaching 'package:copula' - -> nameEx("BetaMatrix") -> ### * BetaMatrix -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BetaMatrix -> ### Title: Matrix of empirical Blomqvist's beta values -> ### Aliases: BetaMatrix -> -> ### ** Examples -> -> data(daxreturns) -> Data = as.matrix(daxreturns) -> -> # compute the empirical Blomqvist's betas -> beta = BetaMatrix(Data) -> -> -> -> cleanEx() -> nameEx("BiCopCDF") -> ### * BiCopCDF -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BiCopCDF -> ### Title: Distribution function of a bivariate copula -> ### Aliases: BiCopCDF -> -> ### ** Examples -> -> # simulate from a bivariate Clayton -> simdata = BiCopSim(300,3,3.4) -> -> # evaluate the distribution function of the bivariate t-copula -> u1 = simdata[,1] -> u2 = simdata[,2] -> BiCopCDF(u1,u2,3,3.4) - [1] 0.212083894 0.560454175 0.196829776 0.859783373 0.334142797 0.138883599 - [7] 0.552748610 0.656946696 0.716294284 0.358902123 0.657106132 0.406649144 - [13] 0.215249319 0.010762322 0.680744432 0.429168263 0.336836485 0.754999947 - [19] 0.478876720 0.591381592 0.743614123 0.684320242 0.501994536 0.019720627 - [25] 0.673692866 0.461672664 0.318172610 0.041830170 0.272430716 0.539624409 - [31] 0.690952756 0.357404390 0.478385703 0.450454976 0.081735412 0.325850276 - [37] 0.270163818 0.464160879 0.697817469 0.770254930 0.402432651 0.309902564 - [43] 0.526755239 0.440604149 0.157859951 0.125915290 0.623294168 0.739830600 - [49] 0.371783278 0.723334913 0.516814728 0.269809505 0.445858863 0.109397786 - [55] 0.822399359 0.909295094 0.294693765 0.055312093 0.427042357 0.403252652 - [61] 0.845573559 0.325266686 0.630782109 0.357571974 0.203263111 0.321058009 - [67] 0.032144353 0.826230667 0.484706552 0.844421805 0.608301620 0.175590037 - [73] 0.609058333 0.163878464 0.101571465 0.538136460 0.274644551 0.339289595 - [79] 0.294216757 0.195381304 0.277706814 0.421733480 0.720333595 0.049782599 - [85] 0.565454106 0.606022665 0.691741950 0.371062856 0.601897391 0.591440556 - [91] 0.201688601 0.758395667 0.600742911 0.704561061 0.823026172 0.574257107 - [97] 0.099157544 0.251281107 0.106087540 0.300755602 0.189355553 0.383442247 -[103] 0.156051138 0.353445260 0.237769014 0.569868697 0.754009708 0.626534957 -[109] 0.642565610 0.746343146 0.174386590 0.276468326 0.793197597 0.128246949 -[115] 0.403133907 0.218942785 0.337329582 0.358487519 0.603040975 0.358813218 -[121] 0.270584669 0.584756888 0.291400991 0.270925282 0.453995540 0.750041775 -[127] 0.419655276 0.292947806 0.211477158 0.367187001 0.403616732 0.263279705 -[133] 0.466439291 0.060463864 0.414509798 0.037596575 0.254942295 0.205299452 -[139] 0.174436459 0.449884240 0.024025747 0.703587274 0.030608188 0.210400866 -[145] 0.093855295 0.142735752 0.761364232 0.464621321 0.061121298 0.049605515 -[151] 0.394449212 0.413216316 0.374454880 0.168265886 0.055593257 0.097151257 -[157] 0.780802798 0.227744822 0.065636001 0.870926086 0.510225526 0.405327388 -[163] 0.845888486 0.768194100 0.251842178 0.746537224 0.380903910 0.061307470 -[169] 0.290451789 0.578210814 0.667105491 0.436226140 0.501831663 0.314446545 -[175] 0.343212498 0.260100773 0.643573510 0.736279214 0.480576518 0.747377388 -[181] 0.084991510 0.625430254 0.563728676 0.065672797 0.586906305 0.383323904 -[187] 0.665138618 0.182143650 0.322690699 0.150906032 0.377309335 0.652937289 -[193] 0.167981587 0.764145834 0.112547545 0.094783549 0.792890037 0.121846529 -[199] 0.506278225 0.227685925 0.449045336 0.931289729 0.876824814 0.350126804 -[205] 0.010994635 0.786543245 0.709228011 0.596225473 0.378512582 0.664875538 -[211] 0.373815801 0.426252115 0.280636713 0.083968169 0.814257670 0.515317294 -[217] 0.328967379 0.099903254 0.377995332 0.473178827 0.031442176 0.447588371 -[223] 0.217327056 0.361663573 0.067611532 0.801212727 0.247607998 0.049270220 -[229] 0.576458572 0.324353916 0.136902467 0.001605048 0.257187329 0.474040408 -[235] 0.437713533 0.456113202 0.577646467 0.085121494 0.715134572 0.457893436 -[241] 0.498003300 0.838971972 0.503169431 0.045336633 0.555881808 0.022418980 -[247] 0.194331580 0.334462487 0.373599846 0.438035879 0.509068595 0.599445606 -[253] 0.468924572 0.387566042 0.655708457 0.735283578 0.007562104 0.489784093 -[259] 0.562107349 0.302752252 0.766853423 0.218580395 0.381560134 0.755457200 -[265] 0.955922687 0.272025101 0.251443038 0.057390884 0.289182961 0.155876041 -[271] 0.393765386 0.507388247 0.120671623 0.799010545 0.523637750 0.767031675 -[277] 0.010792082 0.619446682 0.047529687 0.786968380 0.413820169 0.318351521 -[283] 0.835610923 0.218595381 0.278001748 0.129935495 0.147382642 0.715055153 -[289] 0.544744934 0.786205589 0.344101052 0.302395620 0.488473797 0.066509090 -[295] 0.889908357 0.401278597 0.705956499 0.752430964 0.408975709 0.316904963 -> -> -> -> cleanEx() -> nameEx("BiCopChiPlot") -> ### * BiCopChiPlot -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BiCopChiPlot -> ### Title: Chi-plot for bivariate copula data -> ### Aliases: BiCopChiPlot -> -> ### ** Examples -> -> ## Not run: -> ##D # chi-plots for bivariate Gaussian copula data -> ##D n = 500 -> ##D tau = 0.5 -> ##D -> ##D # simulate copula data -> ##D fam = 1 -> ##D theta = BiCopTau2Par(fam,tau) -> ##D dat = BiCopSim(n,fam,theta) -> ##D -> ##D # create chi-plots -> ##D dev.new(width=16,height=5) -> ##D par(mfrow=c(1,3)) -> ##D BiCopChiPlot(dat[,1],dat[,2],xlim=c(-1,1),ylim=c(-1,1), -> ##D main="General chi-plot") -> ##D BiCopChiPlot(dat[,1],dat[,2],mode="lower",xlim=c(-1,1), -> ##D ylim=c(-1,1),main="Lower chi-plot") -> ##D BiCopChiPlot(dat[,1],dat[,2],mode="upper",xlim=c(-1,1), -> ##D ylim=c(-1,1),main="Upper chi-plot") -> ## End(Not run) -> -> -> -> cleanEx() -> nameEx("BiCopDeriv") -> ### * BiCopDeriv -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BiCopDeriv -> ### Title: Derivatives of a bivariate copula density -> ### Aliases: BiCopDeriv -> -> ### ** Examples -> -> # simulate from a bivariate t-copula -> simdata = BiCopSim(300,2,-0.7,par2=4) -> -> # derivative of the bivariate t-copula with respect to the first parameter -> u1 = simdata[,1] -> u2 = simdata[,2] -> BiCopDeriv(u1,u2,2,-0.7,par2=4, deriv="par") - [1] -1.118981963 1.240853696 -1.001064211 0.126342186 1.175103086 - [6] 1.125284074 -2.660900650 -2.472195467 1.023015475 -1.226835099 - [11] -10.758312703 -0.060805698 -1.275771122 -0.874257992 -5.229438212 - [16] -1.996785307 -0.024314703 -0.340297829 -1.124279340 -2.830928257 - [21] -0.644128690 -1.902583339 -0.198026426 -5.534636646 -0.399781564 - [26] 0.435400718 -0.424885018 1.472901008 -2.384264853 -2.524411180 - [31] -7.785438426 -1.363561693 -1.835639592 -0.722528253 -6.472291697 - [36] -0.716665042 -0.964105867 0.829886233 -4.540361690 1.351436336 - [41] -1.503828622 -1.074008721 -2.420782826 -0.457655215 1.239990732 - [46] 1.451559193 1.125103668 0.869236569 -1.879796413 -1.231228404 - [51] -2.424107089 1.829094173 -1.221019510 -2.559081446 -1.233727812 - [56] 1.872628051 -1.838289517 0.971594798 -0.096706898 -1.937842204 - [61] -15.237257119 0.172804942 -2.778179365 -0.368238987 -3.191034202 - [66] 1.081925107 -13.105195405 -1.253692526 -2.123195334 -8.688276102 - [71] -1.503515318 0.256531438 -2.674138975 -4.198369584 -5.259632795 - [76] -1.944954160 -1.969911957 0.006893071 1.207272916 0.571959168 - [81] -0.132434126 -0.754275953 -4.565334109 0.127084068 -2.903169549 - [86] 0.771316852 -4.357864429 0.489405734 -0.218840978 1.257765042 - [91] 0.720810321 -3.023537238 -5.465362366 0.055533560 -2.703654480 - [96] -2.809374993 -2.368171453 -2.796443300 -5.602431270 -1.693541846 -[101] 0.551536277 -1.064635971 -2.851261121 0.383686061 -2.937039105 -[106] -13.728663798 1.428865348 -4.156683579 1.475522589 -11.428897046 -[111] 1.042581628 -2.329817184 -3.371593709 1.422863380 0.041637025 -[116] 1.087794501 -2.304816570 -1.944080252 -1.899435223 -2.039960766 -[121] -2.645050409 -6.650555229 0.050104775 0.851039002 1.383789144 -[126] 1.465850488 -2.014890698 0.938868515 -2.392303876 1.122254766 -[131] -1.525108901 -2.071212850 -1.173020644 -10.741866594 -0.542828355 -[136] 1.515200988 0.630401901 0.694797858 0.931185696 -0.680191222 -[141] -7.933722404 -5.163276704 1.664827305 0.960737875 1.063045879 -[146] 1.342918851 -25.249465414 -1.393407553 1.532198588 -6.911077681 -[151] 0.376116964 -2.132593253 1.552339321 -3.505820153 -1.224401790 -[156] 1.227776973 0.353972461 -2.323316239 -0.313598837 -0.566267188 -[161] -2.330830899 1.274204534 1.293889346 0.860444774 -2.469578460 -[166] -37.208160647 -0.658022946 -0.468399340 0.542603267 1.471761927 -[171] -62.570186831 -2.007473905 -2.147550775 0.259715654 -1.822814641 -[176] 1.381625780 -3.213788742 -28.991603753 -1.229075644 -3.627148879 -[181] -0.101623278 -4.587179691 0.581309497 -9.140049046 -2.507966161 -[186] -2.212019166 -9.855455970 -1.589138378 -0.337898112 -2.553649116 -[191] -2.226506883 1.333901700 0.465082093 1.189110937 0.796068401 -[196] 1.443132908 -3.501076181 -0.501800492 -2.291129850 0.935368493 -[201] -1.064749466 1.467016724 1.082767823 -1.259347011 -35.328425259 -[206] -54.951284051 0.718174055 -2.464860924 -1.312713214 0.813159659 -[211] -2.210898561 -0.448716041 -1.620526551 -2.795506995 1.473304529 -[216] -5.057278714 -2.325488643 -6.612891371 1.047891665 1.184335554 -[221] 1.067936715 -1.893917726 -1.660850454 1.235448817 1.395848509 -[226] -8.352631627 0.661067847 -10.045949778 1.301830099 1.184362514 -[231] -2.365111887 -19.375622882 0.787353636 -1.284525224 -1.465763628 -[236] 1.487875678 -2.800629638 0.974747012 -3.893986259 -1.347791384 -[241] -1.715161311 1.344923130 -2.191660590 0.729214728 -4.251170941 -[246] -15.846996489 0.963319101 -2.045913223 -2.214253517 0.123732841 -[251] -1.130187683 -0.976720057 1.550396563 -0.114614937 -2.106725798 -[256] -3.543205014 -64.153096610 -1.674467836 -2.013424285 -2.506361843 -[261] 0.171864835 1.109748552 1.058702426 0.607026838 0.841762192 -[266] 1.600486017 -0.341279447 1.218882366 -1.075804146 -3.976274166 -[271] 1.462331510 -2.327053523 1.443964144 -70.883566817 -0.662165420 -[276] -1.690102935 -50.916636504 -3.285496238 1.214680711 1.243536650 -[281] -0.209042356 -1.987493543 0.412999360 -3.236351739 1.359980628 -[286] -1.527350949 1.444523027 -2.321816594 -2.549388281 0.552707478 -[291] 1.307238920 1.553288676 -2.277551572 -4.393119872 1.180012547 -[296] -1.006935254 -0.716277972 -0.594563456 -2.172846043 -1.984262894 -> -> -> -> cleanEx() -> nameEx("BiCopDeriv2") -> ### * BiCopDeriv2 -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BiCopDeriv2 -> ### Title: Second derivatives of a bivariate copula density -> ### Aliases: BiCopDeriv2 -> -> ### ** Examples -> -> # simulate from a bivariate t-copula -> simdata = BiCopSim(300,2,-0.7,par2=4) -> -> # second derivative of the bivariate t-copula with respect to the first parameter -> u1 = simdata[,1] -> u2 = simdata[,2] -> BiCopDeriv2(u1,u2,2,-0.7,par2=4, deriv="par") - [1] 2.4126542 -6.6825108 -6.3560370 -13.7227857 -9.1816929 - [6] -7.0908205 13.7290309 10.7473379 1.2577657 2.6630769 - [11] 45.1413216 -5.6405356 3.4557714 -38.1175487 23.8842516 - [16] 10.4429381 -3.4900896 -4.0350153 -5.2822373 14.4093322 - [21] -2.3705610 6.3865847 -2.3729617 -8.3403632 -1.7953292 - [26] -5.9126744 -0.8925703 -2.7198451 12.1687196 13.2898122 - [31] 34.8767633 5.5283219 6.8140897 0.5179240 12.8722339 - [36] -1.9694262 2.3857559 -7.1967954 19.9757800 -0.8634186 - [41] 5.8194993 3.3938077 7.1423000 -5.1528390 -6.5129152 - [46] -2.6078043 -6.5350832 -6.9423348 9.5969194 1.2028442 - [51] 12.2097919 -5.3415160 2.3088684 6.2549771 -6.3055972 - [56] -20.6839367 8.6985442 1.8900924 -7.2938766 9.6259884 - [61] -15.8136161 -4.4191251 13.3567417 -1.6699869 15.6181921 - [66] -8.2228638 49.6433734 -6.8637577 11.5149595 -10.1757433 - [71] 5.7891358 -5.1789980 13.2930910 17.9367741 11.1038423 - [76] 9.7799834 9.3298570 -3.7109533 -7.6361988 -5.8621277 - [81] -7.0977482 0.3699164 18.6443999 -12.3991863 14.2560643 - [86] -6.1678671 19.3905631 -7.4826160 -2.0968065 -6.4709585 - [91] -6.1599241 7.7973748 19.3468978 -4.3365165 -3.1372378 - [96] 14.3722621 -12.2920083 14.3064742 16.3602446 4.6174577 -[101] -5.8752261 2.9774240 11.4235543 -6.1721458 13.0711948 -[106] 24.5566247 -2.0566903 19.3946357 -3.4040873 46.5514372 -[111] -6.6975421 11.8752549 4.8264870 -1.9410271 -4.8470163 -[116] -6.5319545 11.8388787 8.7842751 8.5351932 10.8108849 -[121] 13.7383533 17.5443858 -3.4835638 -6.5227577 -7.3817498 -[126] -3.1497797 10.5288361 -7.0505394 10.7116425 -9.1255948 -[131] 6.4561544 6.1147706 -0.1415321 47.2160109 -2.1404643 -[136] -3.2675803 -5.8061782 -6.0783318 -6.6882969 0.2205718 -[141] 9.2056534 22.6513172 -5.4130890 -6.4797445 -8.6119575 -[146] -6.1626208 99.0525948 5.6320135 -4.5034060 -10.8423355 -[151] -8.2161180 11.7010068 -3.1354411 10.6979666 -7.4363695 -[156] -7.9862145 -7.0399481 10.7286487 -9.0056350 -19.8533850 -[161] 10.9014112 -0.7675042 -0.2967231 -7.3862615 9.1439497 -[166] 155.9358951 -1.0080337 -9.1237377 -5.7171014 -2.9464925 -[171] 269.9285276 10.3593989 8.7543815 -4.7214883 7.2427847 -[176] -6.7186224 15.3700517 124.6436795 -9.6978141 11.7143732 -[181] -7.6979536 20.5984504 -5.7257439 40.5312907 12.7734411 -[186] 12.0655708 42.4723521 4.4524000 -4.4733160 9.1906767 -[191] 12.1270553 -0.8568985 -5.9649734 -7.0021920 -23.9452815 -[196] -6.2800218 5.3513165 -3.9053336 10.6781184 -6.4459971 -[201] 0.4934674 -2.4424125 -13.7947217 2.6918629 -15.0437654 -[206] 179.5492436 -6.4095059 12.3367635 5.0010992 -6.3084576 -[211] 12.1575256 -3.7222823 6.9552673 -14.7678286 -5.2660209 -[216] -11.0043502 12.5483203 25.2705550 -12.1320323 -7.5170928 -[221] -16.7607915 9.6529562 5.9831467 -9.2588542 -1.5943981 -[226] 19.2252029 -5.8827620 41.3950758 -0.7504865 -8.7125535 -[231] 7.1471377 -182.3423219 -11.5964015 0.1386318 5.9833540 -[236] -6.7067508 14.3516973 -9.2066813 15.6816459 5.2243435 -[241] 1.1197675 -0.8486390 11.8796392 2.1755199 7.3798075 -[246] -19.7251148 -6.5430234 10.6690874 12.1767844 -16.2087793 -[251] 3.8184437 2.4339272 -5.1251428 -4.2674313 8.5722830 -[256] 12.3852346 276.5338339 3.0855253 9.9835689 12.7594328 -[261] -6.1429545 -6.5277846 -8.7959204 -6.8613633 3.2834040 -[266] -6.8909722 -1.5026474 0.2997642 3.2883771 18.6179306 -[271] -8.1021536 11.2468036 -5.3373429 195.6539596 0.6054940 -[276] 0.9947356 122.5599083 16.1741216 0.2079989 -7.1625500 -[281] -4.9097796 7.9203020 -10.0926920 15.9586637 -11.5061335 -[286] 1.7095188 -4.9261936 7.3923584 13.3974394 -7.5603040 -[291] -9.6068616 -8.6709300 12.2354089 11.2373337 -17.6110050 -[296] 2.1594059 -0.8513871 -2.9233828 12.0301834 10.0336656 -> -> -> -> cleanEx() -> nameEx("BiCopEst") -> ### * BiCopEst -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BiCopEst -> ### Title: Parameter estimation for bivariate copula data using inversion -> ### of Kendall's tau or maximum likelihood estimation -> ### Aliases: BiCopEst -> -> ### ** Examples -> -> ## Example 1: bivariate Gaussian copula -> dat = BiCopSim(500,1,0.7) -> u1 = dat[,1] -> v1 = dat[,2] -> -> # empirical Kendall's tau -> tau1 = cor(u1,v1,method="kendall") -> -> # inversion of empirical Kendall's tau -> BiCopTau2Par(1,tau1) -[1] 0.7045111 -> BiCopEst(u1,v1,family=1,method="itau")$par -[1] 0.7045111 -> -> # maximum likelihood estimate for comparison -> BiCopEst(u1,v1,family=1,method="mle")$par -[1] 0.703239 -> -> -> ## Example 2: bivariate Clayton and survival Gumbel copulas -> # simulate from a Clayton copula -> dat = BiCopSim(500,3,2.5) -> u2 = dat[,1] -> v2 = dat[,2] -> -> # empirical Kendall's tau -> tau2 = cor(u2,v2,method="kendall") -> -> # inversion of empirical Kendall's tau for the Clayton copula -> BiCopTau2Par(3,tau2) -[1] 2.480802 -> BiCopEst(u2,v2,family=3,method="itau",se=TRUE) -$par -[1] 2.480802 - -$par2 -[1] 0 - -$se -[1] 0.2366735 - -$se2 -[1] 0 - -> -> # inversion of empirical Kendall's tau for the survival Gumbel copula -> BiCopTau2Par(14,tau2) -[1] 2.240401 -> BiCopEst(u2,v2,family=14,method="itau",se=TRUE) -$par -[1] 2.240401 - -$par2 -[1] 0 - -$se -[1] 0.1183367 - -$se2 -[1] 0 - -> -> # maximum likelihood estimates for comparison -> BiCopEst(u2,v2,family=3,method="mle",se=TRUE) -$par -[1] 2.370793 - -$par2 -[1] 0 - -$se -[1] 0.1337379 - -$se2 -[1] 0 - -> BiCopEst(u2,v2,family=14,method="mle",se=TRUE) -$par -[1] 2.244569 - -$par2 -[1] 0 - -$se -[1] 0.08094233 - -$se2 -[1] 0 - -> -> -> -> -> cleanEx() -> nameEx("BiCopGofTest") -> ### * BiCopGofTest -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BiCopGofTest -> ### Title: Goodness-of-fit test for bivariate copulas -> ### Aliases: BiCopGofTest -> -> ### ** Examples -> -> # simulate from a bivariate Clayton copula -> simdata = BiCopSim(300,3,2) -> u1 = simdata[,1] -> u2 = simdata[,2] -> -> # perform White's goodness-of-fit test for the true copula -> BiCopGofTest(u1,u2,family=3) -$p.value - [,1] -[1,] 0.174567 - -$statistic - [,1] -[1,] 1.84328 - -> -> # perform Kendall's goodness-of-fit test for the Frank copula -> BiCopGofTest(u1,u2,family=5) -$p.value - [,1] -[1,] 0.499615 - -$statistic - [,1] -[1,] 0.4557542 - -> -> ## Not run: -> ##D # perform Kendall's goodness-of-fit test for the true copula -> ##D gof = BiCopGofTest(u1,u2,family=3,method="kendall") -> ##D gof$p.value.CvM -> ##D gof$p.value.KS -> ##D -> ##D # perform Kendall's goodness-of-fit test for the Frank copula -> ##D gof = BiCopGofTest(u1,u2,family=5,method="kendall") -> ##D gof$p.value.CvM -> ##D gof$p.value.KS -> ## End(Not run) -> -> -> -> cleanEx() -> nameEx("BiCopHfunc") -> ### * BiCopHfunc -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BiCopHfunc -> ### Title: Conditional distribution function (h-function) of a bivariate -> ### copula -> ### Aliases: BiCopHfunc -> -> ### ** Examples -> -> # load data set -> data(daxreturns) -> -> # h-functions of the Gaussian copula -> h1 = BiCopHfunc(daxreturns[,2],daxreturns[,1],1,0.5) -> -> -> -> cleanEx() -> nameEx("BiCopHfuncDeriv") -> ### * BiCopHfuncDeriv -> -> flush(stderr()); flush(stdout()) -> -> ### Name: BiCopHfuncDeriv -> ### Title: Derivatives of the h-function of a bivariate copula -> ### Aliases: BiCopHfuncDeriv -> -> ### ** Examples -> -> # simulate from a bivariate t-copula -> simdata = BiCopSim(300,2,-0.7,par2=4) -> -> # derivative of the conditional bivariate t-copula -> # with respect to the first parameter -> u1 = simdata[,1] -> u2 = simdata[,2] -> BiCopHfuncDeriv(u1,u2,2,-0.7,par2=4, deriv="par") - [1] 0.188249864 -0.529552481 -0.873071979 -0.088028377 0.764465081 - [6] 0.268742673 0.225414839 0.003745044 -0.250411287 -0.552223280 - [11] 0.542208002 0.733893277 0.171342121 0.040807295 0.271432180 - [16] -0.194478681 0.539020302 -0.179847959 0.857056553 0.165863800 - [21] -0.167799319 -0.078433467 -0.493630542 0.014446390 -0.259425789 - [26] -0.611885828 0.430828031 0.081037733 -0.034159823 0.180985090 - [31] 0.348575968 0.309101636 0.490238920 -0.491592260 -0.833857762 - [36] -0.683462885 0.269070347 -0.635325777 0.174910232 -0.232964155 - [41] -0.415391436 0.301526190 0.625251401 0.781396939 0.315011241 - [46] 0.272627317 -0.447754453 -0.281985372 0.171307540 -0.133608127 [TRUNCATED] To get the complete diff run: svnlook diff /svnroot/vinecopula -r 75 From noreply at r-forge.r-project.org Tue Jan 20 12:27:38 2015 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Tue, 20 Jan 2015 12:27:38 +0100 (CET) Subject: [Vinecopula-commits] r76 - pkg/tests/Examples Message-ID: <20150120112738.CB35F1858F3@r-forge.r-project.org> Author: etobi Date: 2015-01-20 12:27:38 +0100 (Tue, 20 Jan 2015) New Revision: 76 Modified: pkg/tests/Examples/VineCopula-Ex.Rout.save Log: and once more ... (Wo Menschen arbeiten passieren Fehler) Modified: pkg/tests/Examples/VineCopula-Ex.Rout.save =================================================================== --- pkg/tests/Examples/VineCopula-Ex.Rout.save 2015-01-20 10:02:54 UTC (rev 75) +++ pkg/tests/Examples/VineCopula-Ex.Rout.save 2015-01-20 11:27:38 UTC (rev 76) @@ -21,18 +21,6 @@ > source(file.path(R.home("share"), "R", "examples-header.R")) > options(warn = 1) > options(pager = "console") -> base::assign(".ExTimings", "VineCopula-Ex.timings", pos = 'CheckExEnv') -> base::cat("name\tuser\tsystem\telapsed\n", file=base::get(".ExTimings", pos = 'CheckExEnv')) -> base::assign(".format_ptime", -+ function(x) { -+ if(!is.na(x[4L])) x[1L] <- x[1L] + x[4L] -+ if(!is.na(x[5L])) x[2L] <- x[2L] + x[5L] -+ options(OutDec = '.') -+ format(x[1L:3L], digits = 7L) -+ }, -+ pos = 'CheckExEnv') -> -> ### * > library('VineCopula') > > base::assign(".oldSearch", base::search(), pos = 'CheckExEnv') @@ -42,7 +30,6 @@ > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BB1Copula-class > ### Title: Classes '"BB1Copula"', '"surBB1Copula"', '"r90BB1Copula"' and > ### '"r270BB1Copula"' @@ -84,15 +71,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BB1Copula-class", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BB1Copula") > ### * BB1Copula > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BB1Copula > ### Title: Constructor of the BB1 family and rotated versions thereof > ### Aliases: BB1Copula surBB1Copula r90BB1Copula r270BB1Copula @@ -124,8 +108,6 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BB1Copula", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() detaching 'package:copula' @@ -135,7 +117,6 @@ > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BB6Copula-class > ### Title: Classes '"BB6Copula"', '"surBB6Copula"', '"r90BB6Copula"' and > ### '"r270BB6Copula"' @@ -177,15 +158,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BB6Copula-class", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BB6Copula") > ### * BB6Copula > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BB6Copula > ### Title: Constructor of the BB6 family and its derivatives > ### Aliases: BB6Copula surBB6Copula r90BB6Copula r270BB6Copula @@ -216,8 +194,6 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BB6Copula", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() detaching 'package:copula' @@ -227,7 +203,6 @@ > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BB7Copula-class > ### Title: Classes '"BB7Copula"', '"surBB7Copula"', '"r90BB7Copula"' and > ### '"r270BB7Copula"' @@ -269,15 +244,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BB7Copula-class", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BB7Copula") > ### * BB7Copula > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BB7Copula > ### Title: Constructor of the BB7 family and its derivatives > ### Aliases: BB7Copula surBB7Copula r90BB7Copula r270BB7Copula @@ -308,8 +280,6 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BB7Copula", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() detaching 'package:copula' @@ -319,7 +289,6 @@ > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BB8Copula-class > ### Title: Classes '"BB8Copula"', '"surBB8Copula"', '"r90BB8Copula"' and > ### '"r270BB8Copula"' @@ -361,15 +330,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BB8Copula-class", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BB8Copula") > ### * BB8Copula > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BB8Copula > ### Title: Constructor of the BB8 family and its derivatives > ### Aliases: BB8Copula surBB8Copula r90BB8Copula r270BB8Copula @@ -392,8 +358,6 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BB8Copula", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() detaching 'package:copula' @@ -403,7 +367,6 @@ > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BetaMatrix > ### Title: Matrix of empirical Blomqvist's beta values > ### Aliases: BetaMatrix @@ -418,15 +381,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BetaMatrix", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopCDF") > ### * BiCopCDF > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopCDF > ### Title: Distribution function of a bivariate copula > ### Aliases: BiCopCDF @@ -493,15 +453,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopCDF", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopChiPlot") > ### * BiCopChiPlot > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopChiPlot > ### Title: Chi-plot for bivariate copula data > ### Aliases: BiCopChiPlot @@ -531,15 +488,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopChiPlot", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopDeriv") > ### * BiCopDeriv > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopDeriv > ### Title: Derivatives of a bivariate copula density > ### Aliases: BiCopDeriv @@ -616,15 +570,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopDeriv", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopDeriv2") > ### * BiCopDeriv2 > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopDeriv2 > ### Title: Second derivatives of a bivariate copula density > ### Aliases: BiCopDeriv2 @@ -701,15 +652,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopDeriv2", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopEst") > ### * BiCopEst > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopEst > ### Title: Parameter estimation for bivariate copula data using inversion > ### of Kendall's tau or maximum likelihood estimation @@ -810,15 +758,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopEst", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopGofTest") > ### * BiCopGofTest > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopGofTest > ### Title: Goodness-of-fit test for bivariate copulas > ### Aliases: BiCopGofTest @@ -866,15 +811,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopGofTest", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopHfunc") > ### * BiCopHfunc > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopHfunc > ### Title: Conditional distribution function (h-function) of a bivariate > ### copula @@ -890,15 +832,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopHfunc", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopHfuncDeriv") > ### * BiCopHfuncDeriv > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopHfuncDeriv > ### Title: Derivatives of the h-function of a bivariate copula > ### Aliases: BiCopHfuncDeriv @@ -976,15 +915,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopHfuncDeriv", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopHfuncDeriv2") > ### * BiCopHfuncDeriv2 > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopHfuncDeriv2 > ### Title: Second derivatives of the h-function of a bivariate copula > ### Aliases: BiCopHfuncDeriv2 @@ -1062,15 +998,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopHfuncDeriv2", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopIndTest") > ### * BiCopIndTest > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopIndTest > ### Title: Independence test for bivariate copula data > ### Aliases: BiCopIndTest @@ -1108,15 +1041,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopIndTest", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopKPlot") > ### * BiCopKPlot > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopKPlot > ### Title: Kendall's plot (K-plot) for bivariate copula data > ### Aliases: BiCopKPlot @@ -1147,15 +1077,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopKPlot", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopLambda") > ### * BiCopLambda > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopLambda > ### Title: Lambda-function (plot) for bivariate copula data > ### Aliases: BiCopLambda @@ -1196,15 +1123,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopLambda", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopMetaContour") > ### * BiCopMetaContour > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopMetaContour > ### Title: Contour plot of bivariate meta distribution with different > ### margins and copula (theoretical and empirical) @@ -1236,15 +1160,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopMetaContour", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopName") > ### * BiCopName > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopName > ### Title: Bivariate copula family names > ### Aliases: BiCopName @@ -1270,15 +1191,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopName", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopPDF") > ### * BiCopPDF > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopPDF > ### Title: Density of a bivariate copula > ### Aliases: BiCopPDF @@ -1345,15 +1263,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopPDF", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopPar2Beta") > ### * BiCopPar2Beta > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopPar2Beta > ### Title: Blomqvist's beta value of a bivariate copula > ### Aliases: BiCopPar2Beta @@ -1366,15 +1281,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopPar2Beta", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopPar2TailDep") > ### * BiCopPar2TailDep > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopPar2TailDep > ### Title: Tail dependence coefficients of a bivariate copula > ### Aliases: BiCopPar2TailDep @@ -1401,15 +1313,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopPar2TailDep", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopPar2Tau") > ### * BiCopPar2Tau > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopPar2Tau > ### Title: Kendall's tau value of a bivariate copula > ### Aliases: BiCopPar2Tau @@ -1430,15 +1339,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopPar2Tau", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopSelect") > ### * BiCopSelect > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopSelect > ### Title: Selection and maximum likelihood estimation of bivariate copula > ### families @@ -1489,15 +1395,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopSelect", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopSim") > ### * BiCopSim > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopSim > ### Title: Simulation from a bivariate copula > ### Aliases: BiCopSim @@ -1509,15 +1412,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopSim", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopTau2Par") > ### * BiCopTau2Par > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopTau2Par > ### Title: Parameter of a bivariate copula for a given Kendall's tau value > ### Aliases: BiCopTau2Par @@ -1538,15 +1438,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopTau2Par", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("BiCopVuongClarke") > ### * BiCopVuongClarke > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: BiCopVuongClarke > ### Title: Scoring goodness-of-fit test based on Vuong and Clarke tests for > ### bivariate copula data @@ -1567,15 +1464,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("BiCopVuongClarke", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("C2RVine") > ### * C2RVine > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: C2RVine > ### Title: Transform C-vine to R-vine structure > ### Aliases: C2RVine @@ -1623,8 +1517,6 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("C2RVine", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() detaching 'package:CDVine', 'package:igraph', 'package:mvtnorm', @@ -1635,7 +1527,6 @@ > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: D2RVine > ### Title: Transform D-vine to R-vine structure > ### Aliases: D2RVine @@ -1683,8 +1574,6 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("D2RVine", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() detaching 'package:CDVine', 'package:igraph', 'package:mvtnorm', @@ -1695,7 +1584,6 @@ > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineAIC/BIC > ### Title: AIC and BIC of an R-vine copula model > ### Aliases: RVineAIC RVineBIC @@ -1753,15 +1641,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineAICBIC", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineClarkeTest") > ### * RVineClarkeTest > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineClarkeTest > ### Title: Clarke test comparing two R-vine copula models > ### Aliases: RVineClarkeTest @@ -1788,15 +1673,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineClarkeTest", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineCopSelect") > ### * RVineCopSelect > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineCopSelect > ### Title: Sequential copula selection and estimation of R-vine copula > ### models @@ -1838,15 +1720,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineCopSelect", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineCor2pcor") > ### * RVineCor2pcor > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineCor2pcor > ### Title: correlations to partial correlations and vice versa for R-vines > ### Aliases: RVinePcor2cor RVineCor2pcor @@ -1979,15 +1858,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineCor2pcor", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineGofTest") > ### * RVineGofTest > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineGofTest > ### Title: Goodness-of-fit tests for R-vine copula models > ### Aliases: RVineGofTest @@ -2011,15 +1887,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineGofTest", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineGrad") > ### * RVineGrad > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineGrad > ### Title: Gradient of the log-likelihood of an R-vine copula model > ### Aliases: RVineGrad @@ -2058,15 +1931,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineGrad", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineHessian") > ### * RVineHessian > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineHessian > ### Title: Hessian matrix of the log-likelihood of an R-vine copula model > ### Aliases: RVineHessian @@ -2125,15 +1995,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineHessian", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineLogLik") > ### * RVineLogLik > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineLogLik > ### Title: Log-likelihood of an R-vine copula model > ### Aliases: RVineLogLik @@ -2224,15 +2091,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineLogLik", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineMLE") > ### * RVineMLE > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineMLE > ### Title: Maximum likelihood estimation of an R-vine copula model > ### Aliases: RVineMLE @@ -2270,15 +2134,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineMLE", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineMatrix") > ### * RVineMatrix > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineMatrix > ### Title: R-vine copula model in matrix notation > ### Aliases: RVineMatrix @@ -2342,15 +2203,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineMatrix", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineMatrixNormalize") > ### * RVineMatrixNormalize > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineMatrixNormalize > ### Title: Permute the variables to achieve a natural ordering > ### Aliases: RVineMatrixNormalize @@ -2393,15 +2251,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineMatrixNormalize", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVinePIT") > ### * RVinePIT > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVinePIT > ### Title: Probability integral transformation for R-vine copula models > ### Aliases: RVinePIT @@ -2425,15 +2280,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVinePIT", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVinePar2Beta") > ### * RVinePar2Beta > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVinePar2Beta > ### Title: Blomqvist's beta values of an R-vine copula model > ### Aliases: RVinePar2Beta @@ -2465,15 +2317,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVinePar2Beta", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVinePar2Tau") > ### * RVinePar2Tau > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVinePar2Tau > ### Title: Kendall's tau values of an R-vine copula model > ### Aliases: RVinePar2Tau @@ -2505,15 +2354,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVinePar2Tau", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineSeqEst") > ### * RVineSeqEst > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineSeqEst > ### Title: Sequential estimation of an R-vine copula model > ### Aliases: RVineSeqEst @@ -2613,15 +2459,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineSeqEst", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineSim") > ### * RVineSim > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineSim > ### Title: Simulation from an R-vine copula model > ### Aliases: RVineSim @@ -2653,15 +2496,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineSim", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineStdError") > ### * RVineStdError > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineStdError > ### Title: Standard errors of an R-vine copula model > ### Aliases: RVineStdError @@ -2708,15 +2548,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineStdError", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineStructureSelect") > ### * RVineStructureSelect > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineStructureSelect > ### Title: Sequential specification of R- and C-vine copula models > ### Aliases: RVineStructureSelect @@ -2753,15 +2590,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineStructureSelect", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineTreePlot") > ### * RVineTreePlot > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineTreePlot > ### Title: Plot function for R-vine trees > ### Aliases: RVineTreePlot @@ -2807,15 +2641,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineTreePlot", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RVineVuongTest") > ### * RVineVuongTest > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineVuongTest > ### Title: Vuong test comparing two R-vine copula models > ### Aliases: RVineVuongTest @@ -2842,15 +2673,12 @@ > > > -> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv") -> base::cat("RVineVuongTest", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t") > cleanEx() > nameEx("RvineMatrixCheck") > ### * RvineMatrixCheck > > flush(stderr()); flush(stdout()) > -> base::assign(".ptime", proc.time(), pos = "CheckExEnv") > ### Name: RVineMatrixCheck > ### Title: Vine Matrix validation > ### Aliases: RVineMatrixCheck @@ -2889,15 +2717,12 @@ > > > [TRUNCATED] To get the complete diff run: svnlook diff /svnroot/vinecopula -r 76 From noreply at r-forge.r-project.org Tue Jan 20 19:18:31 2015 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Tue, 20 Jan 2015 19:18:31 +0100 (CET) Subject: [Vinecopula-commits] r77 - in pkg: . R man Message-ID: <20150120181831.C1C0D1876DE@r-forge.r-project.org> Author: etobi Date: 2015-01-20 19:18:31 +0100 (Tue, 20 Jan 2015) New Revision: 77 Added: pkg/R/as.copuladata.R pkg/R/pairs.R pkg/man/as.copuladata.Rd pkg/man/pairs.copuladata.Rd Modified: pkg/NAMESPACE pkg/R/BiCopMetaContour.r Log: * BiCopMetaContour.r: comments, aesthetics * new functions: as.copuladata (coerce to class copuladata) and pairs.copuladata (pairs plots for objects of class copuladata) Modified: pkg/NAMESPACE =================================================================== --- pkg/NAMESPACE 2015-01-20 11:27:38 UTC (rev 76) +++ pkg/NAMESPACE 2015-01-20 18:18:31 UTC (rev 77) @@ -61,6 +61,9 @@ export(RVinePar2Beta) export(BetaMatrix) +export(as.copuladata) +export(pairs.copuladata) + # compatibility to copula export(fitCopula) export(dduCopula,ddvCopula) @@ -90,5 +93,9 @@ S3method(print, RVineMatrix) +S3method(as.copuladata, data.frame) +S3method(as.copuladata, matrix) +S3method(as.copuladata, list) +S3method(pairs, copuladata) useDynLib("VineCopula") \ No newline at end of file Modified: pkg/R/BiCopMetaContour.r =================================================================== --- pkg/R/BiCopMetaContour.r 2015-01-20 11:27:38 UTC (rev 76) +++ pkg/R/BiCopMetaContour.r 2015-01-20 18:18:31 UTC (rev 77) @@ -433,7 +433,7 @@ pdf=con*tem*exp(-tem+tem1+tem2)/sm return(pdf) } - else if(copula==42) # 2-parametric asymmetric copula (thanks to Benedikt Grler) + else if(copula==42) # 2-parametric asymmetric copula (thanks to Benedikt Gr?ler) { a=param[1] b=param[2] @@ -567,23 +567,25 @@ BiCopMetaContour <- function(u1=NULL, u2=NULL, bw=1, size=100, levels=c(0.01,0.05,0.1,0.15,0.2), family="emp", par=0, par2=0, PLOT=TRUE, margins="norm", margins.par=0, xylim=NA, ...) { + + ## sanity checks if((is.null(u1)==TRUE || is.null(u2)==TRUE) && family=="emp") stop("'u1' and/or 'u2' not set or of length zero.") - if(is.null(u1)==FALSE && (any(u1>1) || any(u1<0))) stop("Data has be in the interval [0,1].") - if(is.null(u2)==FALSE && (any(u2>1) || any(u2<0))) stop("Data has be in the interval [0,1].") + if(is.null(u1)==FALSE && (any(u1>1) || any(u1<0))) stop("Data has to be in the interval [0,1].") + if(is.null(u2)==FALSE && (any(u2>1) || any(u2<0))) stop("Data has to be in the interval [0,1].") #if(length(u1)!=length(u2)) stop("Lengths of 'u1' and 'u2' do not match.") if(!(family %in% c(0,1,2,3,4,5,6,7,8,9,10,13,14,16,17,18,19,20,23,24,26,27,28,29,30,33,34,36,37,38,39,40,41,42,51,52,61,62,71,72,104,114,124,134,204,214,224,234, "emp"))) stop("Copula family not implemented.") if(c(2,7,8,9,10,17,18,19,20,27,28,29,30,37,38,39,40,42,52,62,72,104,114,124,134,204,214,224,234) %in% family && par2==0) stop("For t-, BB1, BB6, BB7, BB8 and Tawn copulas, 'par2' must be set.") if(c(1,3,4,5,6,11,13,14,16,23,24,26,33,34,36,41,51,61,71) %in% family && length(par)<1) stop("'par' not set.") - # size sollte nicht zu gross sein + ## Limits for size parameter if(size>1000) stop("Size parameter should not be greater than 1000. Otherwise computational time and memory space are too large.") if(size<50) stop("Size parameter should not be smaller than 50.") - # bw richtig + ## limits bandwidth parameter if(bw<1) stop("The bandwidth parameter 'bw' should be greater or equal to 1.") if(bw>5) stop("The bandwidth parameter 'bw' should not be greater than 5.") - # Parameterbereiche abfragen + ## sanity checks for pair-copula parameters if((family==1 || family==2) && abs(par[1])>=1) stop("The parameter of the Gaussian and t-copula has to be in the interval (-1,1).") if(family==2 && par2<=2) stop("The degrees of freedom parameter of the t-copula has to be larger than 2.") if((family==3 || family==13) && par<=0) stop("The parameter of the Clayton copula has to be positive.") @@ -635,7 +637,7 @@ if(is.null(u1) && is.null(u2) && family!="emp") { - # theoretischer contourplot + # margins for theoretical contour plot u1=runif(1000) u2=runif(1000) } @@ -646,68 +648,67 @@ { x1 <- qnorm(p=u1) x2 <- qnorm(p=u2) - if(is.na(xylim)) xylim=c(-3,3) + if(any(is.na(xylim))) xylim=c(-3,3) } else if(margins=="t") { x1 <- qt(p=u1, df=margins.par) x2 <- qt(p=u2, df=margins.par) - if(is.na(xylim)) xylim=c(-3,3) + if(any(is.na(xylim))) xylim=c(-3,3) } else if(margins=="exp") { x1=qexp(p=u1, rate=margins.par) x2=qexp(p=u2, rate=margins.par) - if(is.na(xylim)) xylim=c(0,5) + if(any(is.na(xylim))) xylim=c(0,5) } else if(margins=="gamma") { x1=qgamma(p=u1, shape=margins.par[1], scale=margins.par[2]) x2=qgamma(p=u2, shape=margins.par[1], scale=margins.par[2]) - if(is.na(xylim)) xylim=c(0,5) + if(any(is.na(xylim))) xylim=c(0,5) } else if(margins=="unif") { x1=u1 x2=u2 - if(is.na(xylim)) xylim=c(0,1) + if(any(is.na(xylim))) xylim=c(0,1) } x <- y <- seq(from=xylim[1], to=xylim[2], length.out=size) - if(family!="emp") - { - if(family %in% c(2,7,8,9,10,17,18,19,20,27,28,29,30,37,38,39,40,42,52,62,72,104,114,124,134,204,214,224,234)) - z <- matrix(data=meta.dens(x1=rep(x=x, each=size), x2=rep(x=y, times=size), param=c(par,par2), copula=family, - margins=margins, margins.par=margins.par), nrow=size, byrow=TRUE) - else - z <- matrix(data=meta.dens(x1=rep(x=x, each=size), x2=rep(x=y, times=size), param=par, copula=family, - margins=margins, margins.par=margins.par), nrow=size, byrow=TRUE) - } - else #empirical - { - bw1 <- bw * bandwidth.nrd(x1) - bw2 <- bw * bandwidth.nrd(x2) - - kd.est <- kde2d(x=x1, y=x2, h=c(bw1, bw2), n=size) - - x <- kd.est$x - y <- kd.est$y - z <- kd.est$z - } + if(family!="emp") { + ## theoretical contours + if(family %in% c(2,7,8,9,10,17,18,19,20,27,28,29,30,37,38,39,40,42,52,62,72,104,114,124,134,204,214,224,234)) + z <- matrix(data=meta.dens(x1=rep(x=x, each=size), x2=rep(x=y, times=size), param=c(par,par2), copula=family, + margins=margins, margins.par=margins.par), nrow=size, byrow=TRUE) + else + z <- matrix(data=meta.dens(x1=rep(x=x, each=size), x2=rep(x=y, times=size), param=par, copula=family, + margins=margins, margins.par=margins.par), nrow=size, byrow=TRUE) + } else { + ## empirical contours + bw1 <- bw * bandwidth.nrd(x1) + bw2 <- bw * bandwidth.nrd(x2) + + ## 2-dimensional kernel density estimation + kd.est <- kde2d(x=x1, y=x2, h=c(bw1, bw2), n=size) + + x <- kd.est$x + y <- kd.est$y + z <- kd.est$z + } - if(PLOT) - { - contour(x=x, y=y, z=z, levels=levels,ylim=xylim,xlim=xylim, ...) - } - else - { - out=list() - out$x=x - out$y=y - out$z=z - - return(out) - } + if(PLOT){ + ## plot contour lines + contour(x=x, y=y, z=z, levels=levels,ylim=xylim,xlim=xylim, ...) + } else { + ## output bivarate meta density z(x,y) + out=list() + out$x=x + out$y=y + out$z=z + + return(out) + } } Added: pkg/R/as.copuladata.R =================================================================== --- pkg/R/as.copuladata.R (rev 0) +++ pkg/R/as.copuladata.R 2015-01-20 18:18:31 UTC (rev 77) @@ -0,0 +1,32 @@ +as.copuladata <- function(data){ + ## generic function for coercion to 'copuladata' + UseMethod("as.copuladata", data) +} + +as.copuladata.data.frame <- function(data){ + ## coercion of 'data.frame' to 'copuladata' + if(any(sapply(data, mode)!="numeric")) stop("Data has to be numeric.") + if(any(data>1 || data<0)) stop("Data has to be in the interval [0,1].") + class(data) <- append("copuladata", class(data)) + return(data) +} + +as.copuladata.matrix <- function(data){ + ## coercion of 'matrix' to 'copuladata' + if(mode(data)!="numeric") stop("Data has to be numeric.") + if(any(data>1 || data<0)) stop("Data has to be in the interval [0,1].") + data <- data.frame(data) + class(data) <- append("copuladata", class(data)) + return(data) +} + +as.copuladata.list <- function(data){ + ## coercion of 'list' to 'copuladata' + if(any(sapply(data, mode)!="numeric")) stop("Data has to be numeric.") + if(any(sapply(data, length)!=length(data[[1]]))) stop("All list entries have to be of same length.") + data <- data.frame(data) + if(any(data>1 || data<0)) stop("Data has to be in the interval [0,1].") + class(data) <- append("copuladata", class(data)) + return(data) +} + Added: pkg/R/pairs.R =================================================================== --- pkg/R/pairs.R (rev 0) +++ pkg/R/pairs.R 2015-01-20 18:18:31 UTC (rev 77) @@ -0,0 +1,60 @@ +pairs.copuladata <- function(x, labels = names(x), ..., + label.pos = 0.85, cex.labels = 1, gap = 0, axes = FALSE, + pch = ".", col = "grey", cex.points = 1, + method.cor = "kendall", col.cor = "red", digits.cor = 2, cex.cor = 1, + bw = 2, size = 100, levels = seq(0.01, 0.2, length.out = 30), + margins = "norm", margins.par = 0, xylim = NA, + col.contour = terrain.colors(length(levels)), + col.hist = "grey"){ + ## pairs plot for 'copuladata' + + ## labeling of axes + if(axes){ + xaxt <- "s" + yaxt <- "s" + } else { + xaxt <- "n" + yaxt <- "n" + } + + ## lower panel: empirical contour plot + lower.panel.copuladata <- function(x, y, lower.bw = bw, lower.size = size, + lower.levels = levels, lower.margins = margins, + lower.margins.par = margins.par, lower.xylim = xylim, + col = col.contour, ...){ + op <- par(usr = c(-3, 3, -3, 3), new = TRUE) + BiCopMetaContour(x, y, bw = lower.bw, size = lower.size, + levels = lower.levels, axes = FALSE, + margins = lower.margins, margins.par = lower.margins.par, + xylim = lower.xylim, col = col, drawlabels = FALSE, ...) + on.exit(par(op)) + } + + ## upper panel: scatter plot (copula data) and correlation + upper.panel.copuladata <- function(x, y, method=method.cor, upper.pch = pch, upper.col = col, + upper.col.text = col.cor, upper.cex = cex.points, + upper.digits = digits.cor, upper.cex.cor = cex.cor, ...){ + op <- par(usr = c(0, 1, 0, 1), new = TRUE) + plot(x, y, pch = upper.pch, cex = upper.cex, col = upper.col, axes=FALSE, ...) + r <- cor(x, y, method = method) + txt <- format(r, digits = upper.digits, nsmall = upper.digits)[1] + text(0.5, 0.5, txt, cex = upper.cex.cor + abs(r)*3, col = upper.col.text) + on.exit(par(op)) + } + + ## diagonal panel: histograms (copula data) + diag.panel.copuladata <- function(x, diag.col=col.hist, ...){ + op <- par(usr = c(0, 1, 0, 1.6), new = TRUE) + hist(x, freq = FALSE, add = TRUE, col = diag.col, border = "black", main = "") + abline(h = 1, col = "black", lty=3) + on.exit(par(op)) + } + + ## pairs plot (with panel functions as defined above) + pairs.default(x, labels = labels, ..., + lower.panel = lower.panel.copuladata, + upper.panel = upper.panel.copuladata, + diag.panel = diag.panel.copuladata, + label.pos = label.pos, cex.labels = cex.labels, + gap = gap, xaxt=xaxt, yaxt=yaxt) +} \ No newline at end of file Added: pkg/man/as.copuladata.Rd =================================================================== --- pkg/man/as.copuladata.Rd (rev 0) +++ pkg/man/as.copuladata.Rd 2015-01-20 18:18:31 UTC (rev 77) @@ -0,0 +1,39 @@ +\name{as.copuladata} +\alias{as.copuladata} +\alias{as.copuladata.data.frame} +\alias{as.copuladata.matrix} +\alias{as.copuladata.list} + +\title{ +Copula Data Objects +} + +\description{ +The function \code{as.copuladata} coerces an object (\code{data.frame}, \code{matrix}, \code{list}) to a \code{copuladata} object. +} + +\usage{ +as.copuladata(data) +} + +\arguments{ + \item{data}{Either a \code{data.frame}, a \code{matrix} or a \code{list} containing copula data (i.e. data with uniform margins on [0,1]). The \code{list} elements have to be vectors of identical length.} +} + +\author{Tobias Erhardt} + +\seealso{\code{\link{pobs}}, \code{\link{pairs.copuladata}}} + +\examples{ + data(daxreturns) + + data <- as(daxreturns, "matrix") + class(as.copuladata(data)) + + data <- as(daxreturns, "data.frame") + class(as.copuladata(data)) + + data <- as(daxreturns, "list") + names(data) <- names(daxreturns) + class(as.copuladata(data)) +} Added: pkg/man/pairs.copuladata.Rd =================================================================== --- pkg/man/pairs.copuladata.Rd (rev 0) +++ pkg/man/pairs.copuladata.Rd 2015-01-20 18:18:31 UTC (rev 77) @@ -0,0 +1,82 @@ +\name{pairs.copuladata} +\alias{pairs.copuladata} + +\title{Pairs Plot of Copula Data} + +\description{ + This function provides pair plots for copula data. It plots bivariate contour plots on the lower panel, scatter plots and correlations on the upper panel and histograms on the diagonal panel. +} + +\usage{ +\method{pairs}{copuladata}(x, labels = names(x), ..., + label.pos = 0.85, cex.labels = 1, gap = 0, axes = FALSE, + pch = ".", col = "grey", cex.points = 1, + method.cor = "kendall", col.cor = "red", digits.cor = 2, cex.cor = 1, + bw = 2, size = 100, levels = seq(0.01, 0.2, length.out = 30), + margins = "norm", margins.par = 0, xylim = NA, + col.contour = terrain.colors(length(levels)), + col.hist = "grey") +} + +\arguments{ + \item{x}{\code{copuladata} object.} + \item{labels}{variable names/labels.} + \item{\dots}{other graphical parameters (see \code{\link[graphics]{par}}).} + \item{label.pos}{y position of labels in the diagonal panel; default: \code{label.pos = 0.85}.} + \item{cex.labels}{magnification to be used for the labels of the diagonal panel; default: \code{cex.labels = 1}.} + \item{gap}{distance between subplots, in margin lines; default: \code{gap = 0}.} + \item{axes}{a logical value indicating whether both axes should be drawn on the plot; default: \code{axes = FALSE}.} + \item{pch}{plotting characters/symbols to be used for the points of the scatter plots; default: \code{pch = "."}.} + \item{col}{colour to be used for the points of the scatter plots; default: \code{col = "grey"}.} + \item{cex.points}{magnification to be used for the points of the scatter plots; default: \code{cex.points = 1}.} + \item{method.cor}{a character string indicating which correlation coefficients are computed. One of \code{pearson}, \code{kendall} (default), or \code{spearman}} + \item{col.cor}{colour to be used for the correlation coefficients in the scatter plots; default: \code{col.cor = "red"}.} + \item{digits.cor}{digits to be used for the correlation coefficients in the scatter plots; default: \code{digits.cor = 2}.} + \item{cex.cor}{magnification to be used for the correlation coefficients in the scatter plots; default: \code{cex.cor = 1}.} + \item{bw}{bandwidth to be used for the contour plots (smoothing factor; default: \code{bw = 1}).} + \item{size}{number of grid points to be used for the contour plots; default: \code{size = 100}.} + \item{levels}{vector of contour levels to be used for the contour plots. + For Gaussian, Student t or exponential margins the default value (\code{levels = seq(0.01, 0.2, length.out = 30)}) typically is a good choice. + For uniform margins we recommend\cr + \code{levels = seq(0.1, 1.5, length.out = 30)}\cr + and for Gamma margins\cr + \code{levels = seq(0.005, 0.09, length.out = 30)}.} + \item{margins}{character; margins for the contour plots. Possible margins are:\cr + \code{"norm"} = standard normal margins (default)\cr + \code{"t"} = Student t margins with degrees of freedom as specified by \code{margins.par}\cr + \code{"gamma"} = Gamma margins with shape and scale as specified by \code{margins.par}\cr + \code{"exp"} = Exponential margins with rate as specified by \code{margins.par}\cr + \code{"unif"} = uniform margins} + \item{margins.par}{parameter(s) of the distribution of the margins (of the contour plots) if necessary (default: \code{margins.par = 0}), i.e., + \itemize{ + \item a positive real number for the degrees of freedom of Student t margins (see \code{\link{dt}}), + \item a 2-dimensional vector of positive real numbers for the shape and scale parameters of Gamma margins (see \code{\link{dgamma}}), + \item a positive real number for the rate parameter of exponential margins (see \code{\link{dexp}}). + }} + \item{xylim}{2-dimensional vector of the x- and y-limits to be used for the contour plots. + By default (\code{xylim = NA}) standard limits for the selected margins are used.} + \item{col.contour}{colour to be used for the contour plots; default: \code{col.contour = terrain.colors(length(levels))}.} + \item{col.hist}{colour to be used for histograms of the diagonal panel; default: \code{col.hist = "grey"}.} +} + +\author{Tobias Erhardt} + +\seealso{\code{\link[graphics]{pairs}}, \code{\link{as.copuladata}}, \code{\link{BiCopMetaContour}}} + +\examples{ + data(daxreturns) + + data <- as.copuladata(daxreturns) + + ## pairs plot with default settings + pairs(data[1:5]) + + ## pairs plot with custom settings + nlevels <- 20 + pairs(data[1:5], cex.labels = 2, gap = 1, + pch = 20, col = "black", cex.points = 0.5, + method.cor = "spearman", col.cor = "green", digits.cor = 3, cex.cor = 1.5, + bw = 1.5, levels = seq(0.01, 0.2, length.out = nlevels), + margins = "t", margins.par = 5, xylim = c(-1,2), + col.contour = heat.colors(nlevels), col.hist = "white") +} From noreply at r-forge.r-project.org Mon Jan 26 16:35:22 2015 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 26 Jan 2015 16:35:22 +0100 (CET) Subject: [Vinecopula-commits] r78 - in pkg: . R inst man tests tests/Examples Message-ID: <20150126153522.31BAC187603@r-forge.r-project.org> Author: etobi Date: 2015-01-26 16:35:21 +0100 (Mon, 26 Jan 2015) New Revision: 78 Modified: pkg/DESCRIPTION pkg/R/BiCopPar2Tau.r pkg/R/BiCopTau2Par.r pkg/inst/ChangeLog pkg/man/BiCopChiPlot.Rd pkg/man/BiCopGofTest.Rd pkg/man/BiCopKPlot.Rd pkg/man/BiCopLambda.Rd pkg/man/BiCopPar2Tau.Rd pkg/man/BiCopSelect.Rd pkg/man/BiCopTau2Par.Rd pkg/man/BiCopVuongClarke.Rd pkg/man/RVineClarkeTest.Rd pkg/man/RVineGofTest.Rd pkg/man/RVineMLE.Rd pkg/man/RVineVuongTest.Rd pkg/man/VineCopula-package.Rd pkg/tests/Examples/VineCopula-Ex.Rout.save pkg/tests/additonalExampleRuns.R pkg/tests/additonalExampleRuns.Rout.save Log: - code cosmetics of additonalExampleRuns.R and the corresponding examples in the manual - New functionality: * BiCopTau2Par and BiCopPar2Tau: fully vectorized (parameter/tau input), and sanity checks extendend. Before vector input was not prohibited. However, both functions were not intended to be used for vectorized input. Modified: pkg/DESCRIPTION =================================================================== --- pkg/DESCRIPTION 2015-01-20 18:18:31 UTC (rev 77) +++ pkg/DESCRIPTION 2015-01-26 15:35:21 UTC (rev 78) @@ -2,7 +2,7 @@ Type: Package Title: Statistical Inference of Vine Copulas Version: 1.4 -Date: 2015-01-20 +Date: 2015-01-26 Author: Ulf Schepsmeier, Jakob Stoeber, Eike Christian Brechmann, Benedikt Graeler Maintainer: Tobias Erhardt Depends: R (>= 2.11.0) Modified: pkg/R/BiCopPar2Tau.r =================================================================== --- pkg/R/BiCopPar2Tau.r 2015-01-20 18:18:31 UTC (rev 77) +++ pkg/R/BiCopPar2Tau.r 2015-01-26 15:35:21 UTC (rev 78) @@ -1,209 +1,260 @@ -BiCopPar2Tau<-function(family,par,par2=0) -{ - if(!(family %in% c(0,1,2,3,4,5,6,7,8,9,10,13,14,16,17,18,19,20,23,24,26,27,28,29,30,33,34,36,37,38,39,40,41,42,51,52,61,62,71,72,104,114,124,134,204,214,224,234))) stop("Copula family not implemented.") - if(c(7,8,9,10,17,18,19,20,27,28,29,30,37,38,39,40,42,52,62,72,104,114,124,134,204,214,224,234) %in% family && par2==0) stop("For BB1, BB6, BB7, BB8 and Tawn copulas, 'par2' must be set.") - if(c(1,3,4,5,6,11,13,14,16,23,24,26,33,34,36,41,51,61,71) %in% family && length(par)<1) stop("'par' not set.") +BiCopPar2Tau <- function(family, par, par2 = 0){ + + ## sanity checks + if(length(family) != 1){ + stop("Input for family has to be a scalar/integer.") + } + if(!(family %in% c(0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, + 13, 14, 16, 17, 18, 19, 20, + 23, 24, 26, 27, 28, 29, 30, + 33, 34, 36, 37, 38, 39, 40, + 41, 42, 51, 52, 61, 62, 71, 72, + 104, 114, 124, 134, + 204, 214, 224, 234) + )){ + stop("Copula family not implemented.") + } + + if(missing(par)){ + stop("'par' not set.") + } + + if(length(par2) > 1 && length(par) != length(par2)){ + stop("Input for 'par' and 'par2 has to be vectors of same length.") + } + + if(family %in% c(7, 8, 9, 10, + 17, 18, 19, 20, + 27, 28, 29, 30, + 37, 38, 39, 40, + 42, 52, 62, 72, + 104, 114, 124, 134, + 204, 214, 224, 234) + && par2 == 0){ + stop("For BB1, BB6, BB7, BB8 and Tawn copulas, 'par2' must be set.") + } - if((family==1 || family==2) && abs(par[1])>=1) stop("The parameter of the Gaussian and t-copula has to be in the interval (-1,1).") + if((family==1 || family==2) && any(abs(par[1])>=1)){ + stop("The (first) parameter of the Gaussian and t-copula has to be in the interval (-1,1).") + } #if(family==2 && par2<=2) stop("The degrees of freedom parameter of the t-copula has to be larger than 2.") - if((family==3 || family==13) && par<=0) stop("The parameter of the Clayton copula has to be positive.") - if((family==4 || family==14) && par<1) stop("The parameter of the Gumbel copula has to be in the interval [1,oo).") - if((family==6 || family==16) && par<=1) stop("The parameter of the Joe copula has to be in the interval (1,oo).") - if(family==5 && par==0) stop("The parameter of the Frank copula has to be unequal to 0.") - if((family==7 || family==17) && par<=0) stop("The first parameter of the BB1 copula has to be positive.") - if((family==7 || family==17) && par2<1) stop("The second parameter of the BB1 copula has to be in the interval [1,oo).") - if((family==8 || family==18) && par<=0) stop("The first parameter of the BB6 copula has to be in the interval [1,oo).") - if((family==8 || family==18) && par2<1) stop("The second parameter of the BB6 copula has to be in the interval [1,oo).") - if((family==9 || family==19) && par<1) stop("The first parameter of the BB7 copula has to be in the interval [1,oo).") - if((family==9 || family==19) && par2<=0) stop("The second parameter of the BB7 copula has to be positive.") - if((family==10 || family==20) && par<1) stop("The first parameter of the BB8 copula has to be in the interval [1,oo).") - if((family==10 || family==20) && (par2<=0 || par2>1)) stop("The second parameter of the BB8 copula has to be in the interval (0,1].") - if((family==23 || family==33) && par>=0) stop("The parameter of the rotated Clayton copula has to be negative.") - if((family==24 || family==34) && par>-1) stop("The parameter of the rotated Gumbel copula has to be in the interval (-oo,-1].") - if((family==26 || family==36) && par>=-1) stop("The parameter of the rotated Joe copula has to be in the interval (-oo,-1).") - if((family==27 || family==37) && par>=0) stop("The first parameter of the rotated BB1 copula has to be negative.") - if((family==27 || family==37) && par2>-1) stop("The second parameter of the rotated BB1 copula has to be in the interval (-oo,-1].") - if((family==28 || family==38) && par>=0) stop("The first parameter of the rotated BB6 copula has to be in the interval (-oo,-1].") - if((family==28 || family==38) && par2>-1) stop("The second parameter of the rotated BB6 copula has to be in the interval (-oo,-1].") - if((family==29 || family==39) && par>-1) stop("The first parameter of the rotated BB7 copula has to be in the interval (-oo,-1].") - if((family==29 || family==39) && par2>=0) stop("The second parameter of the rotated BB7 copula has to be negative.") - if((family==30 || family==40) && par>-1) stop("The first parameter of the rotated BB8 copula has to be in the interval (-oo,-1].") - if((family==30 || family==40) && (par2>=0 || par2<(-1))) stop("The second parameter of the rotated BB8 copula has to be in the interval [-1,0).") - if((family==41 || family==51) && par<=0) stop("The parameter of the reflection asymmetric copula has to be positive.") - if((family==61 || family==71) && par>=0) stop("The parameter of the rotated reflection asymmetric copula has to be negative.") - if(family==42) - { - a=par - b=par2 - limA=(b - 3 - sqrt(9 + 6 * b - 3 * b^2))/2 - if(abs(b)>1) stop("The second parameter of the two-parametric asymmetric copulas has to be in the interval [-1,1]") - if(a>1 || a1)) stop("Please choose 'par2' of the Tawn copula in [0,1].") - if ((family==124 || family==134 || family==224 || family==234) && par>-1) stop("Please choose 'par' of the Tawn copula in (-oo,-1].") - if ((family==124 || family==134 || family==224 || family==234) && (par2<0 || par2>1)) stop("Please choose 'par2' of the Tawn copula in [0,1].") - - if(family==0) - { - tau=0 + if((family==4 || family==14) && any(par<1)){ + stop("The parameter of the (survival) Gumbel copula has to be in the interval [1,oo).") } - else if(family==1 | family==2) - { - tau=2/pi*asin(par) + if((family==6 || family==16) && any(par<=1)){ + stop("The parameter of the (survival) Joe copula has to be in the interval (1,oo).") } - else if(family==3 || family==13) - { - tau=par/(par+2) + if(family==5 && any(par==0)){ + stop("The parameter of the Frank copula has to be different from 0.") } - else if(family==4 || family==14) - { - tau=1-1/par + if((family==7 || family==17) && any(par<=0)){ + stop("The first parameter of the BB1 copula has to be positive.") } - else if(family==5) - { - f=function(x) {x/(exp(x)-1)} - if(par>0) - { - tau=1-4/par+4/par^2*integrate(f,lower=0, upper=par)$value - } - else - { - tau=1-4/par-4/par^2*integrate(f,lower=par, upper=0)$value - } + if((family==7 || family==17) && any(par2<1)){ + stop("The second parameter of the BB1 copula has to be in the interval [1,oo).") } - else if(family==6 || family==16) - { - #tau=1+4/par^2*integrate(function(x) log(x)*x*(1-x)^(2*(1-par)/par), 0, 1)$value - param1=2/par+1 - tem=digamma(2)-digamma(param1) - tau=1+tem*2/(2-par) - tau[par==2]=1-trigamma(2) + if((family==8 || family==18) && any(par<=0)){ + stop("The first parameter of the BB6 copula has to be in the interval [1,oo).") } - else if(family==7 || family==17) - { - theta=par - delta=par2 - tau=1-2/(delta*(theta+2)) + if((family==8 || family==18) && any(par2<1)){ + stop("The second parameter of the BB6 copula has to be in the interval [1,oo).") } - else if(family==8 || family==18) - { - theta=par - delta=par2 - kt<-function(t) {- log(-(1-t)^theta+1)*(1-t-(1-t)^(-theta)+(1-t)^(-theta)*t)/(delta*theta)} - tau=1+4*integrate(kt,0,1)$value + if((family==9 || family==19) && any(par<1)){ + stop("The first parameter of the BB7 copula has to be in the interval [1,oo).") } - else if(family==9 || family==19) - { - #theta=par - #delta=par2 - #tau=1-2/(delta*(2-theta))+4/(theta^2*delta)*gamma(delta+2)*gamma((2-2*theta)/(theta)+1)/gamma(delta+3+(2-2*theta)/(theta)) - kt<-function(t) {( (1-(1-t)^par)^-par2-1 )/( -par*par2*(1-t)^(par-1)*(1-(1-t)^par)^(-par2-1) )} - tau=1+4*integrate(kt,0,1)$value - #kt<-function(t) { 1/( (1-t)^(par-1) ) } - #kt2<-function(t) { 1-t } - #kt3<-function(t) { 1/( (1-t)^(par-1)*(1-(1-t)^par)^(-par2-1) ) } - #tau=1-4/par/par2*(integrate(kt,0,1)$value-integrate(kt2,0,1)$value-integrate(kt3,0,1)$value) - + if((family==9 || family==19) && any(par2<=0)){ + stop("The second parameter of the BB7 copula has to be positive.") } - else if(family==10 || family==20) - { - theta=par - delta=par2 - kt<-function(t) {-log(((1-t*delta)^theta-1)/((1-delta)^theta-1))*(1-t*delta-(1-t*delta)^(-theta)+(1-t*delta)^(-theta)*t*delta)/(theta*delta)} - tau=1+4*integrate(kt,0,1)$value + if((family==10 || family==20) && any(par<1)){ + stop("The first parameter of the BB8 copula has to be in the interval [1,oo).") } - else if(family==23 || family==33) - { - tau=par/(-par+2) + if((family==10 || family==20) && any(par2<=0 || par2>1)){ + stop("The second parameter of the BB8 copula has to be in the interval (0,1].") } - else if(family==24 || family==34) - { - tau=-1-1/par + if((family==23 || family==33) && any(par>=0)){ + stop("The parameter of the (90/270 degree) rotated Clayton copula has to be negative.") } - else if(family==26 || family==36) - { - #tau=-1-4/par^2*integrate(function(x) log(x)*x*(1-x)^(2*(1+par)/-par), 0, 1)$value - theta=-par - param1=2/theta+1 - tem=digamma(2)-digamma(param1) - tau=1+tem*2/(2-theta) - tau[theta==2]=1-trigamma(2) - tau=-tau + if((family==24 || family==34) && any(par>-1)){ + stop("The parameter of the (90/270 degree) rotated Gumbel copula has to be in the interval (-oo,-1].") } - else if(family==27 || family==37) - { - theta=-par - delta=-par2 - tau=1-2/(delta*(theta+2)) - tau=-tau + if((family==26 || family==36) && any(par>=-1)){ + stop("The parameter of the (90/270 degree) rotated Joe copula has to be in the interval (-oo,-1).") } - else if(family==28 || family==38) - { - theta=-par - delta=-par2 - kt<-function(t) {- log(-(1-t)^theta+1)*(1-t-(1-t)^(-theta)+(1-t)^(-theta)*t)/(delta*theta)} - tau=1+4*integrate(kt,0,1)$value - tau=-tau + if((family==27 || family==37) && any(par>=0)){ + stop("The first parameter of the (90/270 degree) rotated BB1 copula has to be negative.") } - else if(family==29 || family==39) - { - theta=-par - delta=-par2 - #tau=1-2/(delta*(2-theta))+4/(theta^2*delta)*gamma(delta+2)*gamma((2-2*theta)/(theta)+1)/gamma(delta+3+(2-2*theta)/(theta)) - kt<-function(t) {( (1-(1-t)^theta)^(-delta)-1 )/( -theta*delta*(1-t)^(theta-1)*(1-(1-t)^theta)^(-delta-1) )} - tau=1+4*integrate(kt,0,1)$value - tau=-tau + if((family==27 || family==37) && any(par2>-1)){ + stop("The second parameter of the (90/270 degree) rotated BB1 copula has to be in the interval (-oo,-1].") } - else if(family==30 || family==40) - { - theta=-par - delta=-par2 - kt<-function(t) {-log(((1-t*delta)^theta-1)/((1-delta)^theta-1))*(1-t*delta-(1-t*delta)^(-theta)+(1-t*delta)^(-theta)*t*delta)/(theta*delta)} - tau=1+4*integrate(kt,0,1)$value - tau=-tau + if((family==28 || family==38) && any(par>=0)){ + stop("The first parameter of the rotated BB6 copula has to be in the interval (-oo,-1].") } - else if(family==41 || family==51) - { - de=par - ln2=log(2) - tem=(2-2*de)*ln2+lgamma(2*de)-2*lgamma(1+de) - tau=1-de*exp(tem) + if((family==28 || family==38) && any(par2>-1)){ + stop("The second parameter of the (90/270 degree) rotated BB6 copula has to be in the interval (-oo,-1].") } - else if(family==61 || family==71) - { - de=-par - ln2=log(2) - tem=(2-2*de)*ln2+lgamma(2*de)-2*lgamma(1+de) - tau=1-de*exp(tem) - tau=-tau + if((family==29 || family==39) && any(par>-1)){ + stop("The first parameter of the (90/270 degree) rotated BB7 copula has to be in the interval (-oo,-1].") } - else if(family==42) - { - tau=(75*par2-par2^2+par*(25-par2))/450 + if((family==29 || family==39) && any(par2>=0)){ + stop("The second parameter of the (90/270 degree) rotated BB7 copula has to be negative.") } - else if(family==104 || family==114 || family==204 || family==214) - { - par3=1 - tau_int=function(t) - { - Afunc = .C("Tawn2",as.double(t),as.integer(length(t)),as.double(par),as.double(par2),as.double(1),as.double(rep(0,length(t))),PACKAGE='VineCopula')[[6]] - Afunc2Deriv = .C("d2Tawn",as.double(t),as.integer(length(t)),as.double(par),as.double(par2),as.double(1),as.double(rep(0,length(t))),PACKAGE='VineCopula')[[6]] - (t*(1-t))*Afunc2Deriv/ Afunc - } - tau<-integrate(tau_int,0,1)[[1]] + if((family==30 || family==40) && any(par>-1)){ + stop("The first parameter of the (90/270 degree) rotated BB8 copula has to be in the interval (-oo,-1].") } - else if(family==124 || family==134 || family==224 || family==234) - { - par3=1 - tau_int=function(t) - { - Afunc = .C("Tawn2",as.double(t),as.integer(length(t)),as.double(-par),as.double(par2),as.double(1),as.double(rep(0,length(t))),PACKAGE='VineCopula')[[6]] - Afunc2Deriv = .C("d2Tawn",as.double(t),as.integer(length(t)),as.double(-par),as.double(par2),as.double(1),as.double(rep(0,length(t))),PACKAGE='VineCopula')[[6]] - (t*(1-t))*Afunc2Deriv/ Afunc + if((family==30 || family==40) && any(par2>=0 || par2<(-1))){ + stop("The second parameter of the (90/270 degree) rotated BB8 copula has to be in the interval [-1,0).") + } + if((family==41 || family==51) && any(par<=0)){ + stop("The parameter of the (survival) reflection asymmetric copula has to be positive.") + } + if((family==61 || family==71) && any(par>=0)){ + stop("The parameter of the (90/270 degree) rotated reflection asymmetric copula has to be negative.") + } + if(family==42){ + a <- par + b <- par2 + limA <- (b - 3 - sqrt(9 + 6 * b - 3 * b^2))/2 + if(any(abs(b)>1)) stop("The second parameter of the two-parametric asymmetric copulas has to be in the interval [-1,1]") + if(any(a>1 || a1)){ + stop("Please choose 'par2' of the (180 degree rotated) Tawn copula in [0,1].") + } + if((family==124 || family==134 || family==224 || family==234) && any(par>-1)){ + stop("Please choose 'par' of the (90/270 degree) rotated Tawn copula in (-oo,-1].") + } + if((family==124 || family==134 || family==224 || family==234) && any(par2<0 || par2>1)){ + stop("Please choose 'par2' of the (90/270 degree) rotated Tawn copula in [0,1].") + } + + ## calculation of tau(s) depending on pair-copula family + if(family==0){ + tau <- rep(0, times = length(par)) + } else if(family==1 | family==2){ + tau <- 2/pi*asin(par) + } else if(family==3 || family==13){ + tau <- par/(par+2) + } else if(family==4 || family==14){ + tau <- 1-1/par + } else if(family==5){ + f <- function(x) x/(exp(x)-1) + fu <- function(x) integrate(f, lower = 0, upper = x)$value + fl <- function(x) integrate(f, lower = x, upper = 0)$value + if(any(par>0)){ + tau <- 1 - 4/par + 4/par^2 * sapply(par, fu) + } else { + tau <- 1 - 4/par - 4/par^2 * sapply(par, fl) } - tau<-integrate(tau_int,0,1)[[1]] - tau=-tau + } else if(family==6 || family==16){ + # tau = 1 + 4/par^2 * integrate(function(x) log(x)*x*(1-x)^(2*(1-par)/par), 0, 1)$value + param1 <- 2/par + 1 + tem <- digamma(2) - digamma(param1) + tau <- 1 + tem*2/(2 - par) + tau[par==2] <- 1 - trigamma(2) + } else if(family==7 || family==17){ + theta <- par + delta <- par2 + tau <- 1 - 2/(delta*(theta+2)) + } else if(family==8 || family==18){ + theta <- par + delta <- par2 + kt <- function(t, th, de){-log(-(1-t)^th+1)*(1-t-(1-t)^(-th)+(1-t)^(-th)*t)/(de*th)} + tau <- 1 + 4*mapply(function(theta, delta){integrate(function(t){kt(t, th=theta, de=delta)}, 0, 1)$value}, + theta, delta) + } else if(family==9 || family==19){ + theta <- par + delta <- par2 + #tau=1-2/(delta*(2-theta))+4/(theta^2*delta)*gamma(delta+2)*gamma((2-2*theta)/(theta)+1)/gamma(delta+3+(2-2*theta)/(theta)) + kt <- function(t, th, de){( (1-(1-t)^th)^-de-1 )/( -th*de*(1-t)^(th-1)*(1-(1-t)^th)^(-de-1) )} + tau <- 1 + 4*mapply(function(theta, delta){integrate(function(t){kt(t, th=theta, de=delta)}, 0, 1)$value}, + theta, delta) + #kt <- function(t) { 1/( (1-t)^(par-1) ) } + #kt2 <- function(t) { 1-t } + #kt3 <- function(t) { 1/( (1-t)^(par-1)*(1-(1-t)^par)^(-par2-1) ) } + #tau <- 1-4/par/par2*(integrate(kt,0,1)$value-integrate(kt2,0,1)$value-integrate(kt3,0,1)$value) + } else if(family==10 || family==20){ + theta <- par + delta <- par2 + kt <- function(t, th, de){-log(((1-t*de)^th-1)/((1-de)^th-1))*(1-t*de-(1-t*de)^(-th)+(1-t*de)^(-th)*t*de)/(th*de)} + tau <- 1 + 4*mapply(function(theta, delta){integrate(function(t){kt(t, th=theta, de=delta)}, 0, 1)$value}, + theta, delta) + } else if(family==23 || family==33){ + tau <- par/(-par+2) + } else if(family==24 || family==34){ + tau <- -1-1/par + } else if(family==26 || family==36){ + #tau <- -1-4/par^2*integrate(function(x) log(x)*x*(1-x)^(2*(1+par)/-par), 0, 1)$value + theta <- -par + param1 <- 2/theta+1 + tem <- digamma(2)-digamma(param1) + tau <- 1+tem*2/(2-theta) + tau[theta==2] <- 1-trigamma(2) + tau <- -tau + } else if(family==27 || family==37){ + theta <- -par + delta <- -par2 + tau <- 1-2/(delta*(theta+2)) + tau <- -tau + } else if(family==28 || family==38){ + theta <- -par + delta <- -par2 + kt <- function(t, th, de){- log(-(1-t)^th+1)*(1-t-(1-t)^(-th)+(1-t)^(-th)*t)/(de*th)} + tau <- 1 + 4*mapply(function(theta, delta){integrate(function(t){kt(t, th=theta, de=delta)}, 0, 1)$value}, + theta, delta) + tau <- -tau + } else if(family==29 || family==39){ + theta <- -par + delta <- -par2 + #tau <- 1-2/(delta*(2-theta))+4/(theta^2*delta)*gamma(delta+2)*gamma((2-2*theta)/(theta)+1)/gamma(delta+3+(2-2*theta)/(theta)) + kt <- function(t, th, de){( (1-(1-t)^th)^(-de)-1 )/( -th*de*(1-t)^(th-1)*(1-(1-t)^th)^(-de-1) )} + tau <- 1 + 4*mapply(function(theta, delta){integrate(function(t){kt(t, th=theta, de=delta)}, 0, 1)$value}, + theta, delta) + tau <- -tau + } else if(family==30 || family==40){ + theta <- -par + delta <- -par2 + kt <- function(t, th, de){-log(((1-t*de)^th-1)/((1-de)^th-1))*(1-t*de-(1-t*de)^(-th)+(1-t*de)^(-th)*t*de)/(th*de)} + tau <- 1 + 4*mapply(function(theta, delta){integrate(function(t){kt(t, th=theta, de=delta)}, 0, 1)$value}, + theta, delta) + tau <- -tau + } else if(family==41 || family==51){ + de <- par + ln2 <- log(2) + tem <- (2 - 2*de)*ln2 + lgamma(2*de) - 2*lgamma(1 + de) + tau <- 1 - de*exp(tem) + } else if(family==61 || family==71){ + de <- -par + ln2 <- log(2) + tem <- (2 - 2*de)*ln2 + lgamma(2*de) - 2*lgamma(1 + de) + tau <- 1 - de*exp(tem) + tau <- -tau + } else if(family==42){ + tau <- (75*par2 - par2^2 + par*(25 - par2))/450 + } else if(family==104 || family==114 || family==204 || family==214){ + par3 <- 1 + tau_int <- function(t, th, de){ + Afunc = .C("Tawn2", as.double(t), as.integer(length(t)), as.double(th), as.double(de), as.double(1), as.double(rep(0,length(t))), PACKAGE='VineCopula')[[6]] + Afunc2Deriv = .C("d2Tawn", as.double(t), as.integer(length(t)), as.double(th), as.double(de), as.double(1), as.double(rep(0,length(t))), PACKAGE='VineCopula')[[6]] + (t*(1 - t)) * Afunc2Deriv/Afunc + } + tau <- mapply(function(par, par2){integrate(function(t){tau_int(t, th=par, de=par2)}, 0, 1)$value}, + par, par2) + } else if(family==124 || family==134 || family==224 || family==234){ + par3 <- 1 + tau_int <- function(t, th, de){ + Afunc = .C("Tawn2", as.double(t), as.integer(length(t)), as.double(-th), as.double(de), as.double(1), as.double(rep(0,length(t))), PACKAGE='VineCopula')[[6]] + Afunc2Deriv = .C("d2Tawn", as.double(t), as.integer(length(t)), as.double(-th), as.double(de), as.double(1), as.double(rep(0,length(t))), PACKAGE='VineCopula')[[6]] + (t*(1 - t)) * Afunc2Deriv/Afunc + } + tau <- mapply(function(par, par2){integrate(function(t){tau_int(t, th=par, de=par2)}, 0, 1)$value}, + par, par2) + tau <- -tau } return(tau) Modified: pkg/R/BiCopTau2Par.r =================================================================== --- pkg/R/BiCopTau2Par.r 2015-01-20 18:18:31 UTC (rev 77) +++ pkg/R/BiCopTau2Par.r 2015-01-26 15:35:21 UTC (rev 78) @@ -1,38 +1,50 @@ -BiCopTau2Par<-function(family,tau){ +BiCopTau2Par <- function(family, tau){ + + ## sanity checks + if(length(family) != 1){ + stop("Input for family has to be a scalar/integer.") + } + if(!(family %in% c(0, 1, 2, 3, 4, 5, 6, + 13, 14, 16, + 23, 24, 26, + 33, 34, 36, + 41, 51, 61, 71) + )){ + stop("Copula family not implemented.") + } - if(!(family %in% c(0,1,3,4,5,6,13,14,16,23,24,26,33,34,36,41,51,61,71))) stop("Copula family not implemented.") - + ## calculation of parameter(s) depending on pair-copula family if(family == 0){ - par = 0 - }else if(family == 1){ - par = sin(pi*tau/2) + par <- rep(0, times = length(tau)) + }else if(family %in% 1:2){ + par <- sin(pi*tau/2) }else if(family %in% c(3,13)){ - if(tau<=0) stop("Clayton copula cannot be used for tau<=0.") - par = 2*tau/(1-tau) + if(any(tau<=0)) stop("Clayton copula cannot be used for tau<=0.") + par <- 2*tau/(1-tau) }else if(family %in% c(4,14)){ - if(tau<0) stop("Gumbel copula cannot be used for tau<0.") - par = 1/(1-tau) + if(any(tau<0)) stop("Gumbel copula cannot be used for tau<0.") + par <- 1/(1-tau) }else if(family == 5){ - if(tau==0) stop("Frank copula cannot be used for tau=0.") - par = Frank.itau.JJ(tau) + if(any(tau==0)) stop("Frank copula cannot be used for tau=0.") + par <- sapply(tau, Frank.itau.JJ) }else if(family %in% c(6,16)){ - if(tau<=0) stop("Joe copula cannot be used for tau<=0.") - par = Joe.itau.JJ(tau) + if(any(tau<=0)) stop("Joe copula cannot be used for tau<=0.") + par <- sapply(tau, Joe.itau.JJ) }else if(family %in% c(23,33)){ - if(tau>=0) stop("Rotated Clayton copula cannot be used for tau>=0.") - par = 2*tau/(1+tau) + if(any(tau>=0)) stop("Rotated Clayton copula cannot be used for tau>=0.") + par <- 2*tau/(1+tau) }else if(family %in% c(24,34)){ - if(tau>0) stop("Rotated Gumbel copula cannot be used for tau>0.") - par = -(1/(1+tau)) + if(any(tau>0)) stop("Rotated Gumbel copula cannot be used for tau>0.") + par <- -(1/(1+tau)) }else if(family %in% c(26,36)){ - if(tau>=0) stop("Rotated Joe copula cannot be used for tau>=0.") - par = -Joe.itau.JJ(-tau) + if(any(tau>=0)) stop("Rotated Joe copula cannot be used for tau>=0.") + par <- -sapply(-tau, Joe.itau.JJ) } else if(family %in% c(41,51)){ - par = ipsA.tau2cpar(tau) + par <- sapply(tau, ipsA.tau2cpar) } else if(family %in% c(61,71)){ - par=-ipsA.tau2cpar(-tau) + par <- -sapply(-tau, ipsA.tau2cpar) } return(par) Modified: pkg/inst/ChangeLog =================================================================== --- pkg/inst/ChangeLog 2015-01-20 18:18:31 UTC (rev 77) +++ pkg/inst/ChangeLog 2015-01-26 15:35:21 UTC (rev 78) @@ -1,10 +1,15 @@ Changes for R-package VineCopula -Current authors: Ulf Schepsmeier, Thomas Nagler and Benedikt Graeler +Current authors: Ulf Schepsmeier, Thomas Nagler, Tobias Erhardt and Benedikt Graeler Former authors: Eike Brechmann and Jakob Stoeber Maintainer: Tobias Erhardt and Thomas Nagler +Version 1.4 (January 26, 2015) + +- New functionality: + * BiCopTau2Par and BiCopPar2Tau: fully vectorized (parameter/tau input), and sanity checks extendend. Before vector input was not prohibited. However, both functions were not intended to be used for vectorized input. + Version 1.3-2 (January 19, 2015) - New author: Thomas Nagler Modified: pkg/man/BiCopChiPlot.Rd =================================================================== --- pkg/man/BiCopChiPlot.Rd 2015-01-20 18:18:31 UTC (rev 77) +++ pkg/man/BiCopChiPlot.Rd 2015-01-26 15:35:21 UTC (rev 78) @@ -77,22 +77,22 @@ \examples{ \dontrun{ # chi-plots for bivariate Gaussian copula data -n = 500 -tau = 0.5 +n <- 500 +tau <- 0.5 # simulate copula data -fam = 1 -theta = BiCopTau2Par(fam,tau) -dat = BiCopSim(n,fam,theta) +fam <- 1 +theta <- BiCopTau2Par(fam, tau) +set.seed(123) +dat <- BiCopSim(n, fam, theta) # create chi-plots -dev.new(width=16,height=5) -par(mfrow=c(1,3)) -BiCopChiPlot(dat[,1],dat[,2],xlim=c(-1,1),ylim=c(-1,1), +par(mfrow = c(1,3)) +BiCopChiPlot(dat[,1], dat[,2], xlim = c(-1,1), ylim = c(-1,1), main="General chi-plot") -BiCopChiPlot(dat[,1],dat[,2],mode="lower",xlim=c(-1,1), - ylim=c(-1,1),main="Lower chi-plot") -BiCopChiPlot(dat[,1],dat[,2],mode="upper",xlim=c(-1,1), - ylim=c(-1,1),main="Upper chi-plot") +BiCopChiPlot(dat[,1], dat[,2], mode = "lower", xlim = c(-1,1), + ylim = c(-1,1), main = "Lower chi-plot") +BiCopChiPlot(dat[,1], dat[,2], mode = "upper", xlim = c(-1,1), + ylim = c(-1,1), main = "Upper chi-plot") } } Modified: pkg/man/BiCopGofTest.Rd =================================================================== --- pkg/man/BiCopGofTest.Rd 2015-01-20 18:18:31 UTC (rev 77) +++ pkg/man/BiCopGofTest.Rd 2015-01-26 15:35:21 UTC (rev 78) @@ -124,25 +124,26 @@ \seealso{\code{\link{BiCopDeriv2}}, \code{\link{BiCopDeriv}}, \code{\link{BiCopIndTest}}, \code{\link{BiCopVuongClarke}}} \examples{ -# simulate from a bivariate Clayton copula -simdata = BiCopSim(300,3,2) -u1 = simdata[,1] -u2 = simdata[,2] + # simulate from a bivariate Clayton copula + set.seed(123) + simdata <- BiCopSim(300, 3, 2) + u1 <- simdata[,1] + u2 <- simdata[,2] + + # perform White's goodness-of-fit test for the true copula + BiCopGofTest(u1, u2, family = 3) + + # perform Kendall's goodness-of-fit test for the Frank copula + BiCopGofTest(u1, u2, family = 5) -# perform White's goodness-of-fit test for the true copula -BiCopGofTest(u1,u2,family=3) - -# perform Kendall's goodness-of-fit test for the Frank copula -BiCopGofTest(u1,u2,family=5) - \dontrun{ # perform Kendall's goodness-of-fit test for the true copula -gof = BiCopGofTest(u1,u2,family=3,method="kendall") +gof <- BiCopGofTest(u1, u2, family = 3, method = "kendall") gof$p.value.CvM gof$p.value.KS # perform Kendall's goodness-of-fit test for the Frank copula -gof = BiCopGofTest(u1,u2,family=5,method="kendall") +gof <- BiCopGofTest(u1, u2, family = 5, method = "kendall") gof$p.value.CvM gof$p.value.KS } Modified: pkg/man/BiCopKPlot.Rd =================================================================== --- pkg/man/BiCopKPlot.Rd 2015-01-20 18:18:31 UTC (rev 77) +++ pkg/man/BiCopKPlot.Rd 2015-01-26 15:35:21 UTC (rev 78) @@ -62,23 +62,24 @@ \examples{ \dontrun{ # Gaussian and Clayton copulas -n = 500 -tau = 0.5 +n <- 500 +tau <- 0.5 # simulate from Gaussian copula -fam1 = 1 -theta1 = BiCopTau2Par(fam1,tau) -dat1 = BiCopSim(n,fam1,theta1) +fam1 <- 1 +theta1 <- BiCopTau2Par(fam1, tau) +set.seed(123) +dat1 <- BiCopSim(n, fam1, theta1) # simulate from Clayton copula -fam2 = 3 -theta2 = BiCopTau2Par(fam2,tau) -dat2 = BiCopSim(n,fam2,theta2) +fam2 <- 3 +theta2 <- BiCopTau2Par(fam2, tau) +set.seed(123) +dat2 <- BiCopSim(n, fam2, theta2) # create K-plots -dev.new(width=10,height=5) par(mfrow=c(1,2)) -BiCopKPlot(dat1[,1],dat1[,2],main="Gaussian copula") -BiCopKPlot(dat2[,1],dat2[,2],main="Clayton copula") +BiCopKPlot(dat1[,1], dat1[,2], main = "Gaussian copula") +BiCopKPlot(dat2[,1], dat2[,2], main = "Clayton copula") } } Modified: pkg/man/BiCopLambda.Rd =================================================================== --- pkg/man/BiCopLambda.Rd 2015-01-20 18:18:31 UTC (rev 77) +++ pkg/man/BiCopLambda.Rd 2015-01-26 15:35:21 UTC (rev 78) @@ -89,34 +89,34 @@ \examples{ \dontrun{ # Clayton and rotated Clayton copulas -n = 1000 -tau = 0.5 +n <- 1000 +tau <- 0.5 # simulate from Clayton copula -fam = 3 -theta = BiCopTau2Par(fam,tau) -dat = BiCopSim(n,fam,theta) +fam <- 3 +theta <- BiCopTau2Par(fam, tau) +set.seed(123) +dat <- BiCopSim(n, fam, theta) # create lambda-function plots -dev.new(width=16,height=5) -par(mfrow=c(1,3)) -BiCopLambda(dat[,1],dat[,2]) # empirical lambda-function -BiCopLambda(family=fam,par=theta) # theoretical lambda-function -BiCopLambda(dat[,1],dat[,2],family=fam,par=theta) # both +par(mfrow = c(1,3)) +BiCopLambda(dat[,1], dat[,2]) # empirical lambda-function +BiCopLambda(family = fam, par = theta) # theoretical lambda-function +BiCopLambda(dat[,1], dat[,2], family = fam, par = theta) # both # simulate from rotated Clayton copula (90 degrees) -fam = 23 -theta = BiCopTau2Par(fam,-tau) -dat = BiCopSim(n,fam,theta) - +fam <- 23 +theta <- BiCopTau2Par(fam, -tau) +set.seed(123) +dat <- BiCopSim(n, fam, theta) + # rotate the data to standard Clayton copula data -rot_dat = 1-dat[,1] +rot_dat <- 1 - dat[,1] -dev.new(width=16,height=5) -par(mfrow=c(1,3)) -BiCopLambda(rot_dat,dat[,2]) # empirical lambda-function -BiCopLambda(family=3,par=-theta) # theoretical lambda-function -BiCopLambda(rot_dat,dat[,2],family=3,par=-theta) # both +par(mfrow = c(1,3)) +BiCopLambda(rot_dat, dat[,2]) # empirical lambda-function +BiCopLambda(family=3, par = -theta) # theoretical lambda-function +BiCopLambda(rot_dat, dat[,2], family = 3, par = -theta) # both } } Modified: pkg/man/BiCopPar2Tau.Rd =================================================================== --- pkg/man/BiCopPar2Tau.Rd 2015-01-20 18:18:31 UTC (rev 77) +++ pkg/man/BiCopPar2Tau.Rd 2015-01-26 15:35:21 UTC (rev 78) @@ -54,18 +54,18 @@ \code{224} = rotated Tawn type 2 copula (90 degrees) \cr \code{234} = rotated Tawn type 2 copula (270 degrees) \cr } - \item{par}{Copula parameter.} - \item{par2}{Second parameter for the two parameter t-, BB1, BB6, BB7, BB8, Tawn type 1 and type 2 copulas (default: \code{par2 = 0}). + \item{par}{Copula parameter (vector).} + \item{par2}{Second parameter (vector of same length as \code{par}) for the two parameter t-, BB1, BB6, BB7, BB8, Tawn type 1 and type 2 copulas (default: \code{par2 = 0}). Note that the degrees of freedom parameter of the t-copula does not need to be set, because the theoretical Kendall's tau value of the t-copula is independent of this choice.} } \value{ -Theoretical value of Kendall's tau corresponding to the bivariate copula family and parameter(s) +Theoretical value of Kendall's tau (vector) corresponding to the bivariate copula family and parameter(vectors) (\eqn{\theta} for one parameter families and the first parameter of the t-copula, -\eqn{\theta} and \eqn{\delta} for the two parameter BB1, BB6, BB7 and BB8 copulas). +\eqn{\theta} and \eqn{\delta} for the two parameter BB1, BB6, BB7, BB8, Tawn type 1 and type 2 copulas). \tabular{ll}{ -No. \tab Kendall's tau \cr +No. (\code{family}) \tab Kendall's tau (\code{tau}) \cr \code{1, 2} \tab \eqn{\frac{2}{\pi}\arcsin(\theta)}{2 / \pi arcsin(\theta)} \cr \code{3, 13} \tab \eqn{\frac{\theta}{\theta+2}}{\theta / (\theta+2)} \cr \code{4, 14} \tab \eqn{1-\frac{1}{\theta}}{1-1/\theta} \cr @@ -97,7 +97,7 @@ } } -\author{Ulf Schepsmeier} +\author{Ulf Schepsmeier, Tobias Erhardt} \references{ Joe, H. (1997). @@ -113,13 +113,28 @@ \examples{ ## Example 1: Gaussian copula -tt1 = BiCopPar2Tau(1,0.7) +tau0 <- 0.5 +rho <- BiCopTau2Par(family = 1, tau = tau0) # transform back -BiCopTau2Par(1,tt1) +tau <- BiCopPar2Tau(family = 1, par = rho) +tau - 2/pi*asin(rho) ## Example 2: Clayton copula -BiCopPar2Tau(3,1.3) +theta <- BiCopTau2Par(family = 3, tau = c(0.4,0.5,0.6)) +BiCopPar2Tau(family = 3, par = theta) + + +## Example 3: +vpar <- seq(from = 1.1, to = 10, length.out = 100) +tauC <- BiCopPar2Tau(family = 3, par = vpar) +tauG <- BiCopPar2Tau(family = 4, par = vpar) +tauF <- BiCopPar2Tau(family = 5, par = vpar) [TRUNCATED] To get the complete diff run: svnlook diff /svnroot/vinecopula -r 78 From noreply at r-forge.r-project.org Tue Jan 27 18:31:26 2015 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Tue, 27 Jan 2015 18:31:26 +0100 (CET) Subject: [Vinecopula-commits] r79 - in pkg: man tests tests/Examples Message-ID: <20150127173126.B553C187972@r-forge.r-project.org> Author: etobi Date: 2015-01-27 18:31:25 +0100 (Tue, 27 Jan 2015) New Revision: 79 Modified: pkg/man/BB1Copula-class.Rd pkg/man/BB1Copula.Rd pkg/man/BB6Copula.Rd pkg/man/BB7Copula.Rd pkg/man/BB8Copula.Rd pkg/man/BetaMatrix.Rd pkg/man/BiCopCDF.Rd pkg/man/BiCopChiPlot.Rd pkg/man/BiCopDeriv.Rd pkg/man/BiCopDeriv2.Rd pkg/man/BiCopEst.Rd pkg/man/BiCopGofTest.Rd pkg/man/BiCopHfunc.Rd pkg/man/BiCopHfuncDeriv.Rd pkg/man/BiCopHfuncDeriv2.Rd pkg/man/BiCopIndTest.Rd pkg/man/BiCopKPlot.Rd pkg/man/BiCopLambda.Rd pkg/man/BiCopMetaContour.Rd pkg/man/BiCopName.Rd pkg/man/BiCopPDF.Rd pkg/man/BiCopPar2Beta.Rd pkg/man/BiCopPar2TailDep.Rd pkg/man/BiCopPar2Tau.Rd pkg/man/BiCopSelect.Rd pkg/man/BiCopSim.Rd pkg/man/BiCopTau2Par.Rd pkg/man/BiCopVuongClarke.Rd pkg/man/C2RVine.Rd pkg/man/D2RVine.Rd pkg/man/RVineAICBIC.Rd pkg/man/RVineClarkeTest.Rd pkg/man/RVineCopSelect.Rd pkg/man/RVineCor2pcor.Rd pkg/man/RVineGofTest.Rd pkg/man/RVineGrad.Rd pkg/man/RVineHessian.Rd pkg/man/RVineLogLik.Rd pkg/man/RVineMLE.Rd pkg/man/RVineMatrix.Rd pkg/man/RVineMatrixNormalize.Rd pkg/man/RVinePIT.Rd pkg/man/RVinePar2Beta.Rd pkg/man/RVinePar2Tau.Rd pkg/man/RVineSeqEst.Rd pkg/man/RVineSim.Rd pkg/man/RVineStdError.rd pkg/man/RVineStructureSelect.Rd pkg/man/RVineTreePlot.Rd pkg/man/RVineVuongTest.Rd pkg/man/RvineMatrixCheck.Rd pkg/man/TauMatrix.Rd pkg/man/VineCopula-package.Rd pkg/man/as.copuladata.Rd pkg/man/copulaFromFamilyIndex.Rd pkg/man/dduCopula.Rd pkg/man/joeBiCopula.Rd pkg/man/pairs.copuladata.Rd pkg/man/pobs.Rd pkg/man/surClaytonCopula.Rd pkg/man/surGumbelCopula.Rd pkg/man/tawnT1Copula.Rd pkg/man/tawnT2Copula.Rd pkg/man/vineCopula.Rd pkg/tests/Examples/VineCopula-Ex.Rout.save pkg/tests/additonalExampleRuns.R pkg/tests/additonalExampleRuns.Rout.save Log: - cosmetics for manual to get closer to http://developer.r-project.org/Rds.html Modified: pkg/man/BB1Copula-class.Rd =================================================================== --- pkg/man/BB1Copula-class.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BB1Copula-class.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,76 +1,76 @@ -\name{BB1Copula-class} -\Rdversion{1.1} -\docType{class} -\alias{BB1Copula-class} -\alias{dduCopula,numeric,BB1Copula-method} -\alias{ddvCopula,numeric,BB1Copula-method} -\alias{dduCopula,matrix,BB1Copula-method} -\alias{ddvCopula,matrix,BB1Copula-method} - -\alias{getKendallDistr,BB1Copula-method} -\alias{kendallDistribution,BB1Copula-method} - -\alias{surBB1Copula-class} -\alias{dduCopula,numeric,surBB1Copula-method} -\alias{ddvCopula,numeric,surBB1Copula-method} -\alias{dduCopula,matrix,surBB1Copula-method} -\alias{ddvCopula,matrix,surBB1Copula-method} - -\alias{r90BB1Copula-class} -\alias{dduCopula,numeric,r90BB1Copula-method} -\alias{ddvCopula,numeric,r90BB1Copula-method} -\alias{dduCopula,matrix,r90BB1Copula-method} -\alias{ddvCopula,matrix,r90BB1Copula-method} - -\alias{r270BB1Copula-class} -\alias{dduCopula,numeric,r270BB1Copula-method} -\alias{ddvCopula,numeric,r270BB1Copula-method} -\alias{dduCopula,matrix,r270BB1Copula-method} -\alias{ddvCopula,matrix,r270BB1Copula-method} - -\title{Classes \code{"BB1Copula"}, \code{"surBB1Copula"}, \code{"r90BB1Copula"} and \code{"r270BB1Copula"}} -\description{ -Wrapper classes representing the BB1, survival BB1, 90 degree and 270 degree rotated BB1 copula families (Joe 1997) from \code{\link{VineCopula-package}}. -} -\section{Objects from the Classes}{ -Objects can be created by calls of the form \code{new("BB1Copula", ...)}, \code{new("surBB1Copula", ...)}, \code{new("r90BB1Copula", ...)} and \code{new("r270BB1Copula", ...)} or by the functions \code{\link{BB1Copula}}, \code{\link{surBB1Copula}}, \code{\link{r90BB1Copula}} and \code{\link{r270BB1Copula}}. -} -\section{Slots}{ - \describe{ - \item{\code{family}:}{Object of class \code{"numeric"} defining the family number in \code{\link{VineCopula-package}} } - \item{\code{dimension}:}{Object of class \code{"integer"} defining the dimension of the copula } - \item{\code{parameters}:}{Object of class \code{"numeric"} the two-place parameter vector} - \item{\code{param.names}:}{Object of class \code{"character"}, parameter names. } - \item{\code{param.lowbnd}:}{Object of class \code{"numeric"}, lower bounds of the copula parameters} - \item{\code{param.upbnd}:}{Object of class \code{"numeric"}, upper bounds of the copula parameters} - \item{\code{fullname}:}{Object of class \code{"character"}, family name of the copula.} - } -} -\section{Extends}{ -Class \code{"\linkS4class{copula}"}, directly. -Class \code{"\linkS4class{Copula}"}, by class "copula", distance 2. -} -\section{Methods}{ - \describe{ - \item{dduCopula}{\code{signature(u = "matrix", copula = "BB1Copula")}: ... } - \item{dduCopula}{\code{signature(u = "numeric", copula = "BB1Copula")}: ... } - \item{ddvCopula}{\code{signature(u = "matrix", copula = "BB1Copula")}: ... } - \item{ddvCopula}{\code{signature(u = "numeric", copula = "BB1Copula")}: ... } - \item{getKendallDistr}{\code{signature(copula = "BB1Copula")}: ... } - \item{kendallDistribution}{\code{signature(copula = "BB1Copula")}: ... } - } -} -\references{ -Joe, H., (1997). Multivariate Models and Dependence Concepts. Monogra. Stat. Appl. Probab. 73, London: Chapman and Hall. -} -\author{ -Benedikt Graeler -} - -\seealso{ -See also \code{\linkS4class{BB6Copula}}, \code{\linkS4class{BB7Copula}}, \code{\linkS4class{BB8Copula}} and \code{\linkS4class{joeCopula}} for further wrapper classes to the \code{\link{VineCopula-package}}. -} -\examples{ -showClass("BB1Copula") -} +\name{BB1Copula-class} +\Rdversion{1.1} +\docType{class} +\alias{BB1Copula-class} +\alias{dduCopula,numeric,BB1Copula-method} +\alias{ddvCopula,numeric,BB1Copula-method} +\alias{dduCopula,matrix,BB1Copula-method} +\alias{ddvCopula,matrix,BB1Copula-method} + +\alias{getKendallDistr,BB1Copula-method} +\alias{kendallDistribution,BB1Copula-method} + +\alias{surBB1Copula-class} +\alias{dduCopula,numeric,surBB1Copula-method} +\alias{ddvCopula,numeric,surBB1Copula-method} +\alias{dduCopula,matrix,surBB1Copula-method} +\alias{ddvCopula,matrix,surBB1Copula-method} + +\alias{r90BB1Copula-class} +\alias{dduCopula,numeric,r90BB1Copula-method} +\alias{ddvCopula,numeric,r90BB1Copula-method} +\alias{dduCopula,matrix,r90BB1Copula-method} +\alias{ddvCopula,matrix,r90BB1Copula-method} + +\alias{r270BB1Copula-class} +\alias{dduCopula,numeric,r270BB1Copula-method} +\alias{ddvCopula,numeric,r270BB1Copula-method} +\alias{dduCopula,matrix,r270BB1Copula-method} +\alias{ddvCopula,matrix,r270BB1Copula-method} + +\title{Classes \code{"BB1Copula"}, \code{"surBB1Copula"}, \code{"r90BB1Copula"} and \code{"r270BB1Copula"}} +\description{ +Wrapper classes representing the BB1, survival BB1, 90 degree and 270 degree rotated BB1 copula families (Joe 1997) from \code{\link{VineCopula-package}}. +} +\section{Objects from the Classes}{ +Objects can be created by calls of the form \code{new("BB1Copula", ...)}, \code{new("surBB1Copula", ...)}, \code{new("r90BB1Copula", ...)} and \code{new("r270BB1Copula", ...)} or by the functions \code{\link{BB1Copula}}, \code{\link{surBB1Copula}}, \code{\link{r90BB1Copula}} and \code{\link{r270BB1Copula}}. +} +\section{Slots}{ + \describe{ + \item{\code{family}:}{Object of class \code{"numeric"} defining the family number in \code{\link{VineCopula-package}} } + \item{\code{dimension}:}{Object of class \code{"integer"} defining the dimension of the copula } + \item{\code{parameters}:}{Object of class \code{"numeric"} the two-place parameter vector} + \item{\code{param.names}:}{Object of class \code{"character"}, parameter names. } + \item{\code{param.lowbnd}:}{Object of class \code{"numeric"}, lower bounds of the copula parameters} + \item{\code{param.upbnd}:}{Object of class \code{"numeric"}, upper bounds of the copula parameters} + \item{\code{fullname}:}{Object of class \code{"character"}, family name of the copula.} + } +} +\section{Extends}{ +Class \code{"\linkS4class{copula}"}, directly. +Class \code{"\linkS4class{Copula}"}, by class "copula", distance 2. +} +\section{Methods}{ + \describe{ + \item{dduCopula}{\code{signature(u = "matrix", copula = "BB1Copula")}: ... } + \item{dduCopula}{\code{signature(u = "numeric", copula = "BB1Copula")}: ... } + \item{ddvCopula}{\code{signature(u = "matrix", copula = "BB1Copula")}: ... } + \item{ddvCopula}{\code{signature(u = "numeric", copula = "BB1Copula")}: ... } + \item{getKendallDistr}{\code{signature(copula = "BB1Copula")}: ... } + \item{kendallDistribution}{\code{signature(copula = "BB1Copula")}: ... } + } +} +\references{ +Joe, H., (1997). Multivariate Models and Dependence Concepts. Monogra. Stat. Appl. Probab. 73, London: Chapman and Hall. +} +\author{ +Benedikt Graeler +} + +\seealso{ +See also \code{\linkS4class{BB6Copula}}, \code{\linkS4class{BB7Copula}}, \code{\linkS4class{BB8Copula}} and \code{\linkS4class{joeCopula}} for further wrapper classes to the \code{\link{VineCopula-package}}. +} +\examples{ +showClass("BB1Copula") +} \keyword{classes} \ No newline at end of file Modified: pkg/man/BB1Copula.Rd =================================================================== --- pkg/man/BB1Copula.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BB1Copula.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -5,7 +5,7 @@ \alias{r270BB1Copula} \title{ -Constructor of the BB1 family and rotated versions thereof +Constructor of the BB1 Family and Rotated Versions thereof } \description{ Constructs an object of the \code{\linkS4class{BB1Copula}} (survival \code{sur}, 90 degree rotated \code{r90} and 270 degree rotated \code{r270}) family for given parameters. @@ -37,10 +37,10 @@ \examples{ library(copula) -persp(BB1Copula(c(1,1.5)),dCopula, zlim=c(0,10)) -persp(surBB1Copula(c(1,1.5)),dCopula, zlim=c(0,10)) -persp(r90BB1Copula(c(-1,-1.5)),dCopula, zlim=c(0,10)) -persp(r270BB1Copula(c(-1,-1.5)),dCopula, zlim=c(0,10)) +persp(BB1Copula(c(1,1.5)), dCopula, zlim = c(0,10)) +persp(surBB1Copula(c(1,1.5)), dCopula, zlim = c(0,10)) +persp(r90BB1Copula(c(-1,-1.5)), dCopula, zlim = c(0,10)) +persp(r270BB1Copula(c(-1,-1.5)), dCopula, zlim = c(0,10)) } \keyword{ distribution } Modified: pkg/man/BB6Copula.Rd =================================================================== --- pkg/man/BB6Copula.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BB6Copula.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -5,10 +5,10 @@ \alias{r270BB6Copula} \title{ -Constructor of the BB6 family and its derivatives +Constructor of the BB6 Family and Rotated Versions thereof } \description{ -Constructs an object of the \code{\linkS4class{BB6Copula}} (survival \code{sur}, 90 degree rotated \code{r90} and 270 degree rotated \code{r270}) family for a given parameter. +Constructs an object of the \code{\linkS4class{BB6Copula}} (survival \code{sur}, 90 degree rotated \code{r90} and 270 degree rotated \code{r270}) family for given parameters. } \usage{ BB6Copula(param) @@ -37,8 +37,8 @@ \examples{ library(copula) -persp(BB6Copula(c(1,1.5)),dCopula, zlim=c(0,10)) -persp(surBB6Copula(c(1,1.5)),dCopula, zlim=c(0,10)) -persp(r90BB6Copula(c(-1,-1.5)),dCopula, zlim=c(0,10)) -persp(r270BB6Copula(c(-1,-1.5)),dCopula, zlim=c(0,10)) +persp(BB6Copula(c(1,1.5)), dCopula, zlim = c(0,10)) +persp(surBB6Copula(c(1,1.5)), dCopula, zlim = c(0,10)) +persp(r90BB6Copula(c(-1,-1.5)), dCopula, zlim = c(0,10)) +persp(r270BB6Copula(c(-1,-1.5)), dCopula, zlim = c(0,10)) } \ No newline at end of file Modified: pkg/man/BB7Copula.Rd =================================================================== --- pkg/man/BB7Copula.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BB7Copula.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -5,10 +5,10 @@ \alias{r270BB7Copula} \title{ -Constructor of the BB7 family and its derivatives +Constructor of the BB7 Family and Rotated Versions thereof } \description{ -Constructs an object of the \code{\linkS4class{BB7Copula}} (survival \code{sur}, 90 degree rotated \code{r90} and 270 degree rotated \code{r270}) family for a given parameter. +Constructs an object of the \code{\linkS4class{BB7Copula}} (survival \code{sur}, 90 degree rotated \code{r90} and 270 degree rotated \code{r270}) family for given parameters. } \usage{ BB7Copula(param) @@ -37,8 +37,8 @@ \examples{ library(copula) -persp(BB7Copula(c(1,1.5)),dCopula, zlim=c(0,10)) -persp(surBB7Copula(c(1,1.5)),dCopula, zlim=c(0,10)) -persp(r90BB7Copula(c(-1,-1.5)),dCopula, zlim=c(0,10)) -persp(r270BB7Copula(c(-1,-1.5)),dCopula, zlim=c(0,10)) +persp(BB7Copula(c(1,1.5)), dCopula, zlim = c(0,10)) +persp(surBB7Copula(c(1,1.5)), dCopula, zlim = c(0,10)) +persp(r90BB7Copula(c(-1,-1.5)), dCopula, zlim = c(0,10)) +persp(r270BB7Copula(c(-1,-1.5)), dCopula, zlim = c(0,10)) } \ No newline at end of file Modified: pkg/man/BB8Copula.Rd =================================================================== --- pkg/man/BB8Copula.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BB8Copula.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -5,10 +5,10 @@ \alias{r270BB8Copula} \title{ -Constructor of the BB8 family and its derivatives +Constructor of the BB8 Family and Rotated Versions thereof } \description{ -Constructs an object of the \code{\linkS4class{BB8Copula}} (survival \code{sur}, 90 degree rotated \code{r90} and 270 degree rotated \code{r270}) family for a given parameter. +Constructs an object of the \code{\linkS4class{BB8Copula}} (survival \code{sur}, 90 degree rotated \code{r90} and 270 degree rotated \code{r270}) family for given parameters. } \usage{ BB8Copula(param) @@ -37,8 +37,8 @@ \examples{ library(copula) -persp(BB8Copula(c(1,0.5)),dCopula, zlim=c(0,10)) -persp(surBB8Copula(c(1,0.5)),dCopula, zlim=c(0,10)) -persp(r90BB8Copula(c(-1,-0.5)),dCopula, zlim=c(0,10)) -persp(r270BB8Copula(c(-1,-0.5)),dCopula, zlim=c(0,10)) +persp(BB8Copula(c(1,0.5)), dCopula, zlim = c(0,10)) +persp(surBB8Copula(c(1,0.5)), dCopula, zlim = c(0,10)) +persp(r90BB8Copula(c(-1,-0.5)), dCopula, zlim = c(0,10)) +persp(r270BB8Copula(c(-1,-0.5)), dCopula, zlim = c(0,10)) } \ No newline at end of file Modified: pkg/man/BetaMatrix.Rd =================================================================== --- pkg/man/BetaMatrix.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BetaMatrix.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,43 +1,43 @@ -\name{BetaMatrix} -\alias{BetaMatrix} - -\title{Matrix of empirical Blomqvist's beta values} - -\description{ -This function computes the empirical Blomqvist's beta. -} - -\usage{ -BetaMatrix(data) -} - -\arguments{ - \item{data}{An N x d data matrix.} -} - -\value{ -Matrix of the empirical Blomqvist's betas. -} - -\references{ -Blomqvist, N. (1950). -On a measure of dependence between two random variables. -The Annals of Mathematical Statistics, 21(4), 593-600. - -Nelsen, R. (2006). -An introduction to copulas. -Springer -} - -\author{Ulf Schepsmeier} - -\seealso{\code{\link{TauMatrix}}, \code{\link{BiCopPar2Beta}}, \code{\link{RVinePar2Beta}}} - -\examples{ -data(daxreturns) -Data = as.matrix(daxreturns) - -# compute the empirical Blomqvist's betas -beta = BetaMatrix(Data) -} - +\name{BetaMatrix} +\alias{BetaMatrix} + +\title{Matrix of Empirical Blomqvist's Beta Values} + +\description{ +This function computes the empirical Blomqvist's beta. +} + +\usage{ +BetaMatrix(data) +} + +\arguments{ + \item{data}{An N x d data matrix.} +} + +\value{ +Matrix of the empirical Blomqvist's betas. +} + +\references{ +Blomqvist, N. (1950). +On a measure of dependence between two random variables. +The Annals of Mathematical Statistics, 21(4), 593-600. + +Nelsen, R. (2006). +An introduction to copulas. +Springer +} + +\author{Ulf Schepsmeier} + +\seealso{\code{\link{TauMatrix}}, \code{\link{BiCopPar2Beta}}, \code{\link{RVinePar2Beta}}} + +\examples{ +data(daxreturns) +Data <- as.matrix(daxreturns) + +# compute the empirical Blomqvist's betas +BetaMatrix(Data) +} + Modified: pkg/man/BiCopCDF.Rd =================================================================== --- pkg/man/BiCopCDF.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BiCopCDF.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,14 +1,14 @@ \name{BiCopCDF} \alias{BiCopCDF} -\title{Distribution function of a bivariate copula} +\title{Distribution Function of a Bivariate Copula} \description{ This function evaluates the cumulative distribution function (CDF) of a given parametric bivariate copula. } \usage{ -BiCopCDF(u1, u2, family, par, par2=0) +BiCopCDF(u1, u2, family, par, par2 = 0) } \arguments{ @@ -55,7 +55,7 @@ \code{234} = rotated Tawn type 2 copula (270 degrees) \cr } \item{par}{Copula parameter.} - \item{par2}{Second parameter for bivariate copulas with two parameters (t, BB1, BB6, BB7, BB8, Tawn type 1 and type 2; default: \code{par2 = 0}). \code{par2} should be an positive integer for the Students's t copula \code{family=2}.} + \item{par2}{Second parameter for bivariate copulas with two parameters (t, BB1, BB6, BB7, BB8, Tawn type 1 and type 2; default: \code{par2 = 0}). \code{par2} should be an positive integer for the Students's t copula \code{family = 2}.} } \value{ @@ -63,7 +63,7 @@ } \note{ -The calculation of the cumulative distribution function (CDF) of the Student's t copula (\code{family=2}) is not implemented any more since the calculation was wrong for non-integer degrees-of-freedom. +The calculation of the cumulative distribution function (CDF) of the Student's t copula (\code{family = 2}) is not implemented any more since the calculation was wrong for non-integer degrees-of-freedom. } @@ -73,11 +73,11 @@ \examples{ # simulate from a bivariate Clayton -simdata = BiCopSim(300,3,3.4) +simdata <- BiCopSim(300, 3, 3.4) # evaluate the distribution function of the bivariate t-copula -u1 = simdata[,1] -u2 = simdata[,2] -BiCopCDF(u1,u2,3,3.4) +u1 <- simdata[,1] +u2 <- simdata[,2] +BiCopCDF(u1, u2, 3, 3.4) } Modified: pkg/man/BiCopChiPlot.Rd =================================================================== --- pkg/man/BiCopChiPlot.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BiCopChiPlot.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,14 +1,14 @@ \name{BiCopChiPlot} \alias{BiCopChiPlot} -\title{Chi-plot for bivariate copula data} +\title{Chi-plot for Bivariate Copula Data} \description{ This function creates a chi-plot of given bivariate copula data. } \usage{ -BiCopChiPlot(u1, u2, PLOT=TRUE, mode="NULL", ...) +BiCopChiPlot(u1, u2, PLOT = TRUE, mode = "NULL", ...) } \arguments{ @@ -75,7 +75,6 @@ \seealso{\code{\link{BiCopMetaContour}}, \code{\link{BiCopKPlot}}, \code{\link{BiCopLambda}}} \examples{ -\dontrun{ # chi-plots for bivariate Gaussian copula data n <- 500 tau <- 0.5 @@ -95,4 +94,3 @@ BiCopChiPlot(dat[,1], dat[,2], mode = "upper", xlim = c(-1,1), ylim = c(-1,1), main = "Upper chi-plot") } -} Modified: pkg/man/BiCopDeriv.Rd =================================================================== --- pkg/man/BiCopDeriv.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BiCopDeriv.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,14 +1,14 @@ \name{BiCopDeriv} \alias{BiCopDeriv} -\title{Derivatives of a bivariate copula density} +\title{Derivatives of a Bivariate Copula Density} \description{ This function evaluates the derivative of a given parametric bivariate copula density with respect to its parameter(s) or one of its arguments. } \usage{ -BiCopDeriv(u1, u2, family, par, par2=0, deriv="par", log=FALSE) +BiCopDeriv(u1, u2, family, par, par2 = 0, deriv = "par", log = FALSE) } \arguments{ @@ -60,11 +60,11 @@ \examples{ # simulate from a bivariate t-copula -simdata = BiCopSim(300,2,-0.7,par2=4) +simdata <- BiCopSim(300, 2, -0.7, par2 = 4) # derivative of the bivariate t-copula with respect to the first parameter -u1 = simdata[,1] -u2 = simdata[,2] -BiCopDeriv(u1,u2,2,-0.7,par2=4, deriv="par") +u1 <- simdata[,1] +u2 <- simdata[,2] +BiCopDeriv(u1, u2, 2, -0.7, par2 = 4, deriv = "par") } Modified: pkg/man/BiCopDeriv2.Rd =================================================================== --- pkg/man/BiCopDeriv2.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BiCopDeriv2.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,14 +1,14 @@ \name{BiCopDeriv2} \alias{BiCopDeriv2} -\title{Second derivatives of a bivariate copula density} +\title{Second Derivatives of a Bivariate Copula Density} \description{ This function evaluates the second derivative of a given parametric bivariate copula density with respect to its parameter(s) and/or its arguments. } \usage{ -BiCopDeriv2(u1, u2, family, par, par2=0, deriv="par") +BiCopDeriv2(u1, u2, family, par, par2 = 0, deriv = "par") } \arguments{ @@ -63,11 +63,11 @@ \examples{ # simulate from a bivariate t-copula -simdata = BiCopSim(300,2,-0.7,par2=4) +simdata <- BiCopSim(300, 2, -0.7, par2 = 4) # second derivative of the bivariate t-copula with respect to the first parameter -u1 = simdata[,1] -u2 = simdata[,2] -BiCopDeriv2(u1,u2,2,-0.7,par2=4, deriv="par") +u1 <- simdata[,1] +u2 <- simdata[,2] +BiCopDeriv2(u1, u2, 2, -0.7, par2 = 4, deriv = "par") } Modified: pkg/man/BiCopEst.Rd =================================================================== --- pkg/man/BiCopEst.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BiCopEst.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,7 +1,7 @@ \name{BiCopEst} \alias{BiCopEst} -\title{Parameter estimation for bivariate copula data using inversion of Kendall's tau or maximum likelihood estimation} +\title{Parameter Estimation for Bivariate Copula Data} \description{ This function estimates the parameter(s) for a bivariate copula using either inversion of empirical Kendall's tau for single parameter copula families @@ -9,8 +9,9 @@ } \usage{ -BiCopEst(u1, u2, family, method="mle", se=FALSE, max.df=30, - max.BB=list(BB1=c(5,6),BB6=c(6,6),BB7=c(5,6),BB8=c(6,1)),weights=NA) +BiCopEst(u1, u2, family, method = "mle", se = FALSE, max.df = 30, + max.BB = list(BB1=c(5,6), BB6=c(6,6), BB7=c(5,6), BB8=c(6,1)), + weights = NA) } \arguments{ @@ -89,7 +90,7 @@ \value{ \item{par, par2}{Estimated copula parameter(s).} - \item{se,se2}{Standard error(s) of the parameter estimate(s) (if \code{se = TRUE}).} + \item{se, se2}{Standard error(s) of the parameter estimate(s) (if \code{se = TRUE}).} } \references{ @@ -100,45 +101,45 @@ \author{Ulf Schepsmeier, Eike Brechmann, Jakob Stoeber, Carlos Almeida} -\seealso{\code{\link{BiCopPar2Tau}}, \code{\link{BiCopTau2Par}} \code{\link{RVineSeqEst}}, \code{\link{BiCopSelect}}} +\seealso{\code{\link{BiCopPar2Tau}}, \code{\link{BiCopTau2Par}}, \code{\link{RVineSeqEst}}, \code{\link{BiCopSelect}}} \examples{ ## Example 1: bivariate Gaussian copula -dat = BiCopSim(500,1,0.7) -u1 = dat[,1] -v1 = dat[,2] +dat <- BiCopSim(500, 1, 0.7) +u1 <- dat[,1] +v1 <- dat[,2] # empirical Kendall's tau -tau1 = cor(u1,v1,method="kendall") +tau1 <- cor(u1, v1, method = "kendall") # inversion of empirical Kendall's tau -BiCopTau2Par(1,tau1) -BiCopEst(u1,v1,family=1,method="itau")$par +BiCopTau2Par(1, tau1) +BiCopEst(u1, v1, family = 1, method = "itau")$par # maximum likelihood estimate for comparison -BiCopEst(u1,v1,family=1,method="mle")$par +BiCopEst(u1, v1, family = 1, method = "mle")$par ## Example 2: bivariate Clayton and survival Gumbel copulas # simulate from a Clayton copula -dat = BiCopSim(500,3,2.5) -u2 = dat[,1] -v2 = dat[,2] +dat <- BiCopSim(500, 3, 2.5) +u2 <- dat[,1] +v2 <- dat[,2] # empirical Kendall's tau -tau2 = cor(u2,v2,method="kendall") +tau2 <- cor(u2, v2, method = "kendall") # inversion of empirical Kendall's tau for the Clayton copula -BiCopTau2Par(3,tau2) -BiCopEst(u2,v2,family=3,method="itau",se=TRUE) +BiCopTau2Par(3, tau2) +BiCopEst(u2, v2, family = 3, method = "itau", se = TRUE) # inversion of empirical Kendall's tau for the survival Gumbel copula -BiCopTau2Par(14,tau2) -BiCopEst(u2,v2,family=14,method="itau",se=TRUE) +BiCopTau2Par(14, tau2) +BiCopEst(u2, v2, family = 14, method = "itau", se = TRUE) # maximum likelihood estimates for comparison -BiCopEst(u2,v2,family=3,method="mle",se=TRUE) -BiCopEst(u2,v2,family=14,method="mle",se=TRUE) +BiCopEst(u2, v2, family = 3, method = "mle", se = TRUE) +BiCopEst(u2, v2, family = 14, method = "mle", se = TRUE) } Modified: pkg/man/BiCopGofTest.Rd =================================================================== --- pkg/man/BiCopGofTest.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BiCopGofTest.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,7 +1,7 @@ \name{BiCopGofTest} \alias{BiCopGofTest} -\title{Goodness-of-fit test for bivariate copulas} +\title{Goodness-of-Fit Test for Bivariate Copulas} \description{ This function performs a goodness-of-fit test for bivariate copulas, @@ -11,11 +11,12 @@ } \usage{ -BiCopGofTest(u1, u2, family, par=0, par2=0, method="white", max.df=30, B=100) +BiCopGofTest(u1, u2, family, par = 0, par2 = 0, + method = "white", max.df = 30, B = 100) } \arguments{ - \item{u1,u2}{Numeric vectors of equal length with values in [0,1].} + \item{u1, u2}{Numeric vectors of equal length with values in [0,1].} \item{family}{An integer defining the bivariate copula family: \cr \code{0} = independence copula \cr \code{1} = Gaussian copula \cr @@ -74,7 +75,7 @@ } \details{ -\code{method="white"}:\cr +\code{method = "white"}:\cr This goodness-of fit test uses the information matrix equality of White (1982) and was investigated by Huang and Prokhorov (2011). The main contribution is that under correct model specification the Fisher Information can be equivalently calculated as minus the expected Hessian matrix or as the expected outer product of the score function. The null hypothesis is @@ -124,19 +125,18 @@ \seealso{\code{\link{BiCopDeriv2}}, \code{\link{BiCopDeriv}}, \code{\link{BiCopIndTest}}, \code{\link{BiCopVuongClarke}}} \examples{ - # simulate from a bivariate Clayton copula - set.seed(123) - simdata <- BiCopSim(300, 3, 2) - u1 <- simdata[,1] - u2 <- simdata[,2] - - # perform White's goodness-of-fit test for the true copula - BiCopGofTest(u1, u2, family = 3) - - # perform Kendall's goodness-of-fit test for the Frank copula - BiCopGofTest(u1, u2, family = 5) +# simulate from a bivariate Clayton copula +set.seed(123) +simdata <- BiCopSim(300, 3, 2) +u1 <- simdata[,1] +u2 <- simdata[,2] -\dontrun{ +# perform White's goodness-of-fit test for the true copula +BiCopGofTest(u1, u2, family = 3) + +# perform Kendall's goodness-of-fit test for the Frank copula +BiCopGofTest(u1, u2, family = 5) +\donttest{ # perform Kendall's goodness-of-fit test for the true copula gof <- BiCopGofTest(u1, u2, family = 3, method = "kendall") gof$p.value.CvM Modified: pkg/man/BiCopHfunc.Rd =================================================================== --- pkg/man/BiCopHfunc.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BiCopHfunc.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,18 +1,18 @@ \name{BiCopHfunc} \alias{BiCopHfunc} -\title{Conditional distribution function (h-function) of a bivariate copula} +\title{Conditional Distribution Function of a Bivariate Copula} \description{ This function evaluates the conditional distribution function (h-function) of a given parametric bivariate copula. } \usage{ -BiCopHfunc(u1, u2, family, par, par2=0) +BiCopHfunc(u1, u2, family, par, par2 = 0) } \arguments{ - \item{u1,u2}{Numeric vectors of equal length with values in [0,1].} + \item{u1, u2}{Numeric vectors of equal length with values in [0,1].} \item{family}{An integer defining the bivariate copula family: \cr \code{0} = independence copula \cr \code{1} = Gaussian copula \cr @@ -94,5 +94,8 @@ data(daxreturns) # h-functions of the Gaussian copula -h1 = BiCopHfunc(daxreturns[,2],daxreturns[,1],1,0.5) +h1 <- BiCopHfunc(daxreturns[,2], daxreturns[,1], 1, 0.5) +\dontshow{ +h1 } +} Modified: pkg/man/BiCopHfuncDeriv.Rd =================================================================== --- pkg/man/BiCopHfuncDeriv.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BiCopHfuncDeriv.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,18 +1,18 @@ \name{BiCopHfuncDeriv} \alias{BiCopHfuncDeriv} -\title{Derivatives of the h-function of a bivariate copula} +\title{Derivatives of the h-Function of a Bivariate Copula} \description{ This function evaluates the derivative of a given conditional parametric bivariate copula (h-function) with respect to its parameter(s) or one of its arguments. } \usage{ -BiCopHfuncDeriv(u1, u2, family, par, par2=0, deriv="par") +BiCopHfuncDeriv(u1, u2, family, par, par2 = 0, deriv = "par") } \arguments{ - \item{u1,u2}{Numeric vectors of equal length with values in [0,1].} + \item{u1, u2}{Numeric vectors of equal length with values in [0,1].} \item{family}{An integer defining the bivariate copula family: \cr \code{0} = independence copula \cr \code{1} = Gaussian copula \cr @@ -57,12 +57,12 @@ \examples{ # simulate from a bivariate t-copula -simdata = BiCopSim(300,2,-0.7,par2=4) +simdata <- BiCopSim(300, 2, -0.7, par2 = 4) # derivative of the conditional bivariate t-copula # with respect to the first parameter -u1 = simdata[,1] -u2 = simdata[,2] -BiCopHfuncDeriv(u1,u2,2,-0.7,par2=4, deriv="par") +u1 <- simdata[,1] +u2 <- simdata[,2] +BiCopHfuncDeriv(u1, u2, 2, -0.7, par2 = 4, deriv = "par") } Modified: pkg/man/BiCopHfuncDeriv2.Rd =================================================================== --- pkg/man/BiCopHfuncDeriv2.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BiCopHfuncDeriv2.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,18 +1,18 @@ \name{BiCopHfuncDeriv2} \alias{BiCopHfuncDeriv2} -\title{Second derivatives of the h-function of a bivariate copula} +\title{Second Derivatives of the h-Function of a Bivariate Copula} \description{ This function evaluates the second derivative of a given conditional parametric bivariate copula (h-function) with respect to its parameter(s) and/or its arguments. } \usage{ -BiCopHfuncDeriv2(u1, u2, family, par, par2=0, deriv="par") +BiCopHfuncDeriv2(u1, u2, family, par, par2 = 0, deriv = "par") } \arguments{ - \item{u1,u2}{Numeric vectors of equal length with values in [0,1].} + \item{u1, u2}{Numeric vectors of equal length with values in [0,1].} \item{family}{An integer defining the bivariate copula family: \cr \code{0} = independence copula \cr \code{1} = Gaussian copula \cr @@ -60,12 +60,12 @@ \examples{ # simulate from a bivariate t-copula -simdata = BiCopSim(300,2,-0.7,par2=4) +simdata <- BiCopSim(300, 2, -0.7, par2 = 4) # second derivative of the conditional bivariate t-copula # with respect to the first parameter -u1 = simdata[,1] -u2 = simdata[,2] -BiCopHfuncDeriv2(u1,u2,2,-0.7,par2=4, deriv="par") +u1 <- simdata[,1] +u2 <- simdata[,2] +BiCopHfuncDeriv2(u1, u2, 2, -0.7, par2 = 4, deriv = "par") } Modified: pkg/man/BiCopIndTest.Rd =================================================================== --- pkg/man/BiCopIndTest.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BiCopIndTest.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,7 +1,7 @@ \name{BiCopIndTest} \alias{BiCopIndTest} -\title{Independence test for bivariate copula data} +\title{Independence Test for Bivariate Copula Data} \description{ This function returns the p-value of a bivariate asymptotic independence test based on Kendall's tau. @@ -12,7 +12,7 @@ } \arguments{ - \item{u1,u2}{Data vectors of equal length with values in [0,1].} + \item{u1, u2}{Data vectors of equal length with values in [0,1].} } \value{ @@ -51,19 +51,19 @@ \examples{ ## Example 1: Gaussian copula with large dependence parameter -par1 = 0.7 -fam1 = 1 -dat1 = BiCopSim(500,fam1,par1) +par1 <- 0.7 +fam1 <- 1 +dat1 <- BiCopSim(500, fam1, par1) # perform the asymptotic independence test -BiCopIndTest(dat1[,1],dat1[,2]) +BiCopIndTest(dat1[,1], dat1[,2]) ## Example 2: Gaussian copula with small dependence parameter -par2 = 0.01 -fam2 = 1 -dat2 = BiCopSim(500,fam2,par2) +par2 <- 0.01 +fam2 <- 1 +dat2 <- BiCopSim(500, fam2, par2) # perform the asymptotic independence test -BiCopIndTest(dat2[,1],dat2[,2]) +BiCopIndTest(dat2[,1], dat2[,2]) } Modified: pkg/man/BiCopKPlot.Rd =================================================================== --- pkg/man/BiCopKPlot.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BiCopKPlot.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,18 +1,18 @@ \name{BiCopKPlot} \alias{BiCopKPlot} -\title{Kendall's plot (K-plot) for bivariate copula data} +\title{Kendall's Plot for Bivariate Copula Data} \description{ This function creates a Kendall's plot (K-plot) of given bivariate copula data. } \usage{ -BiCopKPlot(u1, u2, PLOT=TRUE, ...) +BiCopKPlot(u1, u2, PLOT = TRUE, ...) } \arguments{ - \item{u1,u2}{Data vectors of equal length with values in [0,1].} + \item{u1, u2}{Data vectors of equal length with values in [0,1].} \item{PLOT}{Logical; whether the results are plotted. If \code{PLOT = FALSE}, the values \code{W.in} and \code{Hi.sort} are returned (see below; default: \code{PLOT = TRUE}).} \item{...}{Additional plot arguments.} } @@ -60,7 +60,6 @@ \seealso{\code{\link{BiCopMetaContour}}, \code{\link{BiCopChiPlot}}, \code{\link{BiCopLambda}}, \code{\link{BiCopGofTest}}} \examples{ -\dontrun{ # Gaussian and Clayton copulas n <- 500 tau <- 0.5 @@ -82,4 +81,3 @@ BiCopKPlot(dat1[,1], dat1[,2], main = "Gaussian copula") BiCopKPlot(dat2[,1], dat2[,2], main = "Clayton copula") } -} Modified: pkg/man/BiCopLambda.Rd =================================================================== --- pkg/man/BiCopLambda.Rd 2015-01-26 15:35:21 UTC (rev 78) +++ pkg/man/BiCopLambda.Rd 2015-01-27 17:31:25 UTC (rev 79) @@ -1,19 +1,19 @@ \name{BiCopLambda} \alias{BiCopLambda} -\title{Lambda-function (plot) for bivariate copula data} +\title{Lambda-Function (Plot) for Bivariate Copula Data} \description{ -This function plots the lambda-function of given bivariate copula data. +This function plots/returns the lambda-function of given bivariate copula data. } \usage{ -BiCopLambda(u1=NULL, u2=NULL, family="emp", par=0, par2=0, - PLOT=TRUE, ...) +BiCopLambda(u1 = NULL, u2 = NULL, family = "emp", + par = 0, par2 = 0, PLOT = TRUE, ...) } \arguments{ - \item{u1,u2}{Data vectors of equal length with values in [0,1] (default: \code{u1} and \code{u2 = NULL}).} + \item{u1, u2}{Data vectors of equal length with values in [0,1] (default: \code{u1} and \code{u2 = NULL}).} \item{family}{An integer defining the bivariate copula family or indicating the empirical lambda-function: \cr \code{"emp"} = empirical lambda-function (default) \cr \code{1} = Gaussian copula; the theoretical lambda-function is simulated (no closed formula available) \cr @@ -87,7 +87,6 @@ \seealso{\code{\link{BiCopMetaContour}}, \code{\link{BiCopKPlot}}, \code{\link{BiCopChiPlot}}} \examples{ -\dontrun{ # Clayton and rotated Clayton copulas n <- 1000 tau <- 0.5 @@ -118,5 +117,4 @@ BiCopLambda(family=3, par = -theta) # theoretical lambda-function BiCopLambda(rot_dat, dat[,2], family = 3, par = -theta) # both } -} Modified: pkg/man/BiCopMetaContour.Rd =================================================================== [TRUNCATED] To get the complete diff run: svnlook diff /svnroot/vinecopula -r 79 From noreply at r-forge.r-project.org Wed Jan 28 10:34:51 2015 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Wed, 28 Jan 2015 10:34:51 +0100 (CET) Subject: [Vinecopula-commits] r80 - / pkg pkg/R pkg/man Message-ID: <20150128093451.2DE57187932@r-forge.r-project.org> Author: etobi Date: 2015-01-28 10:34:49 +0100 (Wed, 28 Jan 2015) New Revision: 80 Modified: pkg.pdf pkg/DESCRIPTION pkg/R/BiCopCDF.r pkg/R/BiCopChiPlot.r pkg/R/BiCopEst.r pkg/man/VineCopula-package.Rd Log: - changed package description on request of CRAN - ONLY ASCII characters in R code (also comments), or simply stick to English Modified: pkg/DESCRIPTION =================================================================== --- pkg/DESCRIPTION 2015-01-27 17:31:25 UTC (rev 79) +++ pkg/DESCRIPTION 2015-01-28 09:34:49 UTC (rev 80) @@ -8,6 +8,6 @@ Depends: R (>= 2.11.0) Imports: MASS, mvtnorm, igraph, methods, copula, ADGofTest Suggests: CDVine, TSP -Description: This package provides functions for statistical inference of vine copulas. It contains tools for bivariate exploratory data analysis, bivariate copula selection and (vine) tree construction. Models can be estimated either sequentially or by joint maximum likelihood estimation. Sampling algorithms and plotting methods are also included. Data is assumed to lie in the unit hypercube (so-called copula data). For C- and D-vines links to the package CDVine are provided. +Description: Tools for bivariate exploratory data analysis, bivariate copula selection and (vine) tree construction are provided. Vine copula models can be estimated either sequentially or by joint maximum likelihood estimation. Sampling algorithms and plotting methods are included. Data is assumed to lie in the unit hypercube (so-called copula data). For C- and D-vines links to the package CDVine are provided. License: GPL (>= 2) LazyLoad: yes Modified: pkg/R/BiCopCDF.r =================================================================== --- pkg/R/BiCopCDF.r 2015-01-27 17:31:25 UTC (rev 79) +++ pkg/R/BiCopCDF.r 2015-01-28 09:34:49 UTC (rev 80) @@ -1,5 +1,6 @@ -BiCopCDF<-function(u1,u2,family,par,par2=0) -{ +BiCopCDF <- function(u1, u2, family, par, par2 = 0){ + + ## sanity checks if(is.null(u1)==TRUE || is.null(u2)==TRUE) stop("u1 and/or u2 are not set or have length zero.") if(any(u1>1) || any(u1<0)) stop("Data has be in the interval [0,1].") if(any(u2>1) || any(u2<0)) stop("Data has be in the interval [0,1].") @@ -43,6 +44,7 @@ res = rep(NA, length(u1)) + ## CDFs for the different families if(family == 0){ res = u1*u2 }else if(family == 1){ @@ -60,59 +62,65 @@ res = u2-.C("archCDF",as.double(1-u1),as.double(u2),as.integer(length(u1)),as.double(c(-par,-par2)),as.integer(family-20),as.double(rep(0,length(u1))),PACKAGE='VineCopula')[[6]] }else if(family %in% c(33,34,36:40,71)){ res = u1-.C("archCDF",as.double(u1),as.double(1-u2),as.integer(length(u1)),as.double(c(-par,-par2)),as.integer(family-30),as.double(rep(0,length(u1))),PACKAGE='VineCopula')[[6]] - }else if(family %in% c(104,114,124,134,204,214,224,234)){ # Kan spter ev. mal duch C-Code ersetzt werden - ## Hilfsterme fr die Ableitung ### - ta<-function(t,par,par2,par3) {(par2*t)^par+(par3*(1-t))^par} - ######## Pickands A - A<-function(t,par,par2,par3) {(1-par3)*(1-t)+(1-par2)*t+ta(t,par,par2,par3)^(1/par)} - - w<-function(u1,u2) {log(u2)/log(u1*u2)} - C<-function(u,v,par,par2,par3) {(u1*u2)^A(w(u1,u2),par,par2,par3)} - - if(family==104) - { - par3=1 - res=C(u1,u2,par,par2,par3) - } - else if(family==114) - { - par3=1 - res=u1+u2-1+C(1-u1,1-u2,par,par2,par3) - } - else if(family==124) - { - par3=1 - res=u2-C(1-u1,u2,-par,par2,par3) - } - else if(family==134) - { - par3=1 - res=u1-C(u1,1-u2,-par,par2,par3) - } - else if(family==204) - { - par3=par2 - par2=1 - res=C(u1,u2,par,par2,par3) - } - else if(family==214) - { - par3=par2 - par2=1 - res=u1+u2-1+C(1-u1,1-u2,par,par2,par3) - } - else if(family==224) - { - par3=par2 - par2=1 - res=u2-C(1-u1,u2,-par,par2,par3) - } - else if(family==234) - { - par3=par2 - par2=1 - res=u1-C(u1,1-u2,-par,par2,par3) - } + }else if(family %in% c(104,114,124,134,204,214,224,234)){# maybe replace by C-Code + ## auxiliary functions ### + ta <- function(t,par,par2,par3){(par2*t)^par+(par3*(1-t))^par} + ######## Pickands A + A <- function(t,par,par2,par3){ + (1-par3)*(1-t)+(1-par2)*t+ta(t,par,par2,par3)^(1/par) + } + + w <- function(u1,u2){ + log(u2)/log(u1*u2) + } + C <- function(u,v,par,par2,par3){ + (u1*u2)^A(w(u1,u2),par,par2,par3) + } + + if(family==104) + { + par3=1 + res=C(u1,u2,par,par2,par3) + } + else if(family==114) + { + par3=1 + res=u1+u2-1+C(1-u1,1-u2,par,par2,par3) + } + else if(family==124) + { + par3=1 + res=u2-C(1-u1,u2,-par,par2,par3) + } + else if(family==134) + { + par3=1 + res=u1-C(u1,1-u2,-par,par2,par3) + } + else if(family==204) + { + par3=par2 + par2=1 + res=C(u1,u2,par,par2,par3) + } + else if(family==214) + { + par3=par2 + par2=1 + res=u1+u2-1+C(1-u1,1-u2,par,par2,par3) + } + else if(family==224) + { + par3=par2 + par2=1 + res=u2-C(1-u1,u2,-par,par2,par3) + } + else if(family==234) + { + par3=par2 + par2=1 + res=u1-C(u1,1-u2,-par,par2,par3) + } } return(res) Modified: pkg/R/BiCopChiPlot.r =================================================================== --- pkg/R/BiCopChiPlot.r 2015-01-27 17:31:25 UTC (rev 79) +++ pkg/R/BiCopChiPlot.r 2015-01-28 09:34:49 UTC (rev 80) @@ -1,8 +1,8 @@ #=============================================================================== # -------------------- CHI-PLOT FOR BIVARIATE DATA ----------------------------- #=============================================================================== -# Author: Natalia Djunushalieva, TU Mnchen, April 2010 -# Update: Ulf Schepsmeier, TU Mnchen, June 2010 +# Author: Natalia Djunushalieva, TU Muenchen, April 2010 +# Update: Ulf Schepsmeier, TU Muenchen, June 2010 # For more detail see "Everything you always wanted to now about copula modeling # but were afraid to ask", Christian Genest, Anne-Catherine Favre # NOTE: It is also possible to calculate chi-plot for righ upper and left lower @@ -89,8 +89,8 @@ #=============================================================================== # ----------------- KENDALL-PLOT FOR BIVARIATE DATA ---------------------------- #=============================================================================== -# Author: Natalia Djunushalieva, TU Mnchen, April 2010 -# Update: Ulf Schepsmeier, TU Mnchen, June 2010 +# Author: Natalia Djunushalieva, TU Muenchen, April 2010 +# Update: Ulf Schepsmeier, TU Muenchen, June 2010 # For more detail see "Everything you always wanted to now about copula modeling # but were afraid to ask", Christian Genest, Anne-Catherine Favre #------------------------------------------------------------------------------- @@ -118,8 +118,8 @@ W.in<-rep(NA,n) for(i in 1:n) { - f=function(w){w*(-log(w))*(w-w*log(w))^(i-1)*(1-w+w*log(w))^(n-i)} # zu integrierende Funktion - W.in[i]<-n*choose(n-1,i-1)*(integrate(f,lower=0,upper=1)$value) # W_{i:n} fr i=1:n + f=function(w){w*(-log(w))*(w-w*log(w))^(i-1)*(1-w+w*log(w))^(n-i)} # function to be integrated + W.in[i]<-n*choose(n-1,i-1)*(integrate(f,lower=0,upper=1)$value) # W_{i:n} for i=1:n } g<-function(w){w-w*log(w)} # K_{0}(w)=P(UV<=w) @@ -127,7 +127,7 @@ { plot(g,xlim=c(0,1),ylim=c(0,1),pch="x",xlab=expression(W[1:n]),ylab="H",...) #Kurve K_{0}(w) points(W.in,Hi.sort,pch="x",cex=0.4,...) - abline(a=0,b=1) # Winkelhalbierende + abline(a=0,b=1) # angle bisector } else # create output data { Modified: pkg/R/BiCopEst.r =================================================================== --- pkg/R/BiCopEst.r 2015-01-27 17:31:25 UTC (rev 79) +++ pkg/R/BiCopEst.r 2015-01-28 09:34:49 UTC (rev 80) @@ -175,7 +175,7 @@ if(family==2) ## t { theta1 <- sin(tau*pi/2) - delta1 <- min(10,(max.df+2)/2 ) # Nehme die Mitte zwischen 2S und max.df So kann man mit dem Startwert auch nicht außerhalb des vom User gesetzten Bereiches sein. + delta1 <- min(10,(max.df+2)/2 ) # Take the middle between 2 and max.df delta = MLE_intern(cbind(u1,u2),c(theta1,delta1),family=family,se=FALSE,max.df,max.BB,cor.fixed=TRUE,weights)$par[2] } else if(family==7 || family==17) ## BB1 Modified: pkg/man/VineCopula-package.Rd =================================================================== --- pkg/man/VineCopula-package.Rd 2015-01-27 17:31:25 UTC (rev 79) +++ pkg/man/VineCopula-package.Rd 2015-01-28 09:34:49 UTC (rev 80) @@ -6,10 +6,9 @@ \title{Statistical Inference of Vine Copulas} \description{ -This package provides functions for statistical inference of vine copulas. -It contains tools for bivariate exploratory data analysis, bivariate copula selection and (vine) tree construction. -Models can be estimated either sequentially or by joint maximum likelihood estimation. -Sampling algorithms and plotting methods are also included. +Tools for bivariate exploratory data analysis, bivariate copula selection and (vine) tree construction are provided. +Vine copula models can be estimated either sequentially or by joint maximum likelihood estimation. +Sampling algorithms and plotting methods are included. Data is assumed to lie in the unit hypercube (so-called copula data). For C- and D-vines links to the package CDVine are provided. } Modified: pkg.pdf =================================================================== --- pkg.pdf 2015-01-27 17:31:25 UTC (rev 79) +++ pkg.pdf 2015-01-28 09:34:49 UTC (rev 80) @@ -441,656 +441,639 @@ 293 0 obj << /S /GoTo /D [294 0 R /Fit] >> endobj -312 0 obj << -/Length 1303 +313 0 obj << +/Length 1282 /Filter /FlateDecode >> stream -xY]o6}ϯl`D}k؊5qH -#1I(*Hw)e~H,J_]'l3sg'|O~x3EQ䅳-\(E^nv$#pНy9o|cD3Q`?}$uGģv *CV}J)J#/R("HkWEkmBቭ"ULE3Va?p2g؋m$ee~ouf0z -JҀ 8:HG#rTS91)9bLF2GDC!I:.vbxlx-WI0IWWCۓj3GRWmCz5ۚ1oJi -bKH7QAe -(`J}TeД\''+Re7LˉNҔ-n_t[)Tz' jЍp %2YP ;5VY -/c8OXUzQ+Yy> -5Sqd. ݁r5fj=%+&r8'KҶ]e!AyP]L"T3XxNp ȣ^}씿t'Zg}׎S25X vFiϫU:\-3(9xBq2 |R=+y{ƫd&>ѡ"|ӯ&y0axQy$5 4L*`x|R.vQ2j/?>;ݹW!B|zό~q:hxx'Z$>"\]F:=P#_ -p!@#_x@mI!a\)|I#_0Pl^g^K#/=:LK*̟0O)NG! -=GMn8-'4q&Q]_+{RPQ9W^3ddG{`Fm,PX q4&EɌ4&O-]oiu^@-!qp:W$N\1%:%rV?w\: ;s8Ҍ n@g`Gآ`e'z0A8FQMv@ӌ}Ҭ7O}.EESVF:DQ(-ymWq ++vøTooۄ;j3<<_U3^B+3\s4F{DGCXbj1[,I?B-Em n* +E7fp!#πo~鎠HrzlFQaH֧nZFVv$+C esBS[lp%{4\r)Zx0uSB'Iؖdqe`;V澃D}m/T P͉6XzTx`5M1 (i-&LPù/=$9~)01_{:?FW=8xc5h|˝1txY{ϔ&~A!. g{x +Wl0f>4>R(7`'Ϸ=~SDI76 1;6.N) endstream endobj 294 0 obj << /Type /Page -/Contents 312 0 R -/Resources 311 0 R +/Contents 313 0 R +/Resources 312 0 R /MediaBox [0 0 595.276 841.89] -/Parent 321 0 R -/Annots [ 295 0 R 296 0 R 297 0 R 298 0 R 299 0 R 300 0 R 301 0 R 302 0 R 303 0 R 304 0 R 305 0 R 306 0 R 307 0 R ] +/Parent 322 0 R +/Annots [ 295 0 R 296 0 R 297 0 R 298 0 R 299 0 R 300 0 R 301 0 R 302 0 R 303 0 R 304 0 R 305 0 R 306 0 R 307 0 R 308 0 R ] >> endobj 295 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [506.111 256.527 513.085 265.374] +/Rect [506.111 268.568 513.085 277.414] /A << /S /GoTo /D (page.3) >> >> endobj 296 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [506.111 244.455 513.085 253.301] +/Rect [506.111 256.497 513.085 265.344] /A << /S /GoTo /D (page.6) >> >> endobj 297 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [506.111 232.382 513.085 240.96] +/Rect [506.111 244.427 513.085 253.005] /A << /S /GoTo /D (page.7) >> >> endobj 298 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [506.111 220.309 513.085 229.156] +/Rect [506.111 232.357 513.085 241.204] /A << /S /GoTo /D (page.8) >> >> endobj 299 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [506.111 208.117 513.085 217.083] +/Rect [506.111 220.167 513.085 229.133] /A << /S /GoTo /D (page.9) >> >> endobj 300 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 196.164 513.085 205.011] +/Rect [501.13 208.217 513.085 217.063] /A << /S /GoTo /D (page.10) >> >> endobj 301 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 184.191 513.085 192.938] +/Rect [501.13 196.246 513.085 204.993] /A << /S /GoTo /D (page.11) >> >> endobj 302 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 172.118 513.085 180.865] +/Rect [501.13 184.176 513.085 192.923] /A << /S /GoTo /D (page.12) >> >> endobj 303 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 159.946 513.085 168.792] +/Rect [501.13 172.006 513.085 180.853] /A << /S /GoTo /D (page.13) >> >> endobj 304 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 147.973 513.085 156.72] +/Rect [501.13 160.035 513.085 168.782] /A << /S /GoTo /D (page.14) >> >> endobj 305 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 135.8 513.085 144.647] +/Rect [501.13 147.866 513.085 156.712] /A << /S /GoTo /D (page.15) >> >> endobj 306 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 123.728 513.085 132.574] +/Rect [501.13 135.795 513.085 144.642] /A << /S /GoTo /D (page.16) >> >> endobj 307 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 111.655 513.085 120.502] +/Rect [501.13 123.725 513.085 132.572] /A << /S /GoTo /D (page.18) >> >> endobj -313 0 obj << -/D [294 0 R /XYZ 99.346 773.487 null] +308 0 obj << +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [501.13 111.655 513.085 120.502] +/A << /S /GoTo /D (page.20) >> >> endobj 314 0 obj << -/D [294 0 R /XYZ 100.346 742.532 null] +/D [294 0 R /XYZ 99.346 773.487 null] >> endobj 315 0 obj << /D [294 0 R /XYZ 100.346 742.532 null] >> endobj -319 0 obj << -/D [294 0 R /XYZ 100.346 298.028 null] +316 0 obj << +/D [294 0 R /XYZ 100.346 742.532 null] >> endobj -311 0 obj << -/Font << /F35 316 0 R /F36 317 0 R /F22 318 0 R /F39 320 0 R >> +320 0 obj << +/D [294 0 R /XYZ 100.346 310.064 null] +>> endobj +312 0 obj << +/Font << /F35 317 0 R /F36 318 0 R /F22 319 0 R /F39 321 0 R >> /ProcSet [ /PDF /Text ] >> endobj -387 0 obj << -/Length 1046 +389 0 obj << +/Length 1057 /Filter /FlateDecode >> stream -xs6+8VH5Ǻ$^vz 4\:v8NgG1~YusS/0? -BЩ4}=;+ۛMC>FGcwG8irbk1#_a "OR#')Aqv?t;:?\ٌ3A朗mj )౹F n䄘KXU6ҖIj?ɾȺ5ގcCܜb% -(yZKSPL\Or'\/@ sB 6dM\YAS - -$[/R%$3ڿ,W -v^s(ϧ|J̍OoQp]5z b̞X6fF3|3k_r, `FSv).UZΪn/J'OAc&cc -م6PI~Pfo`o7U5d[G'Y.e"HlчeSlؖͬ;2pv̲7)2{ wp{צ@ގ|@(ޅ;|Szhܰ{OO -u**ϐx>ͦ.1)Q{> T~\!HgwY>vck5U;*6mf, hM2C %uc޵%$!2ə@mV}8PПޡd1$3a䶯.X at 3$z5K!';''^I+)wOh Fw-9<؃}Bmɛ5l5k_r1fmrz߅sfpLj -jXf\M:.2N x| +xs6+8~ !qdg'eg+C'ۿ N:;^.d|ޗyzrO%'[{9s4gxW3PR)"2!7ݐ( +s.q@]mt!?fZe6C계D9&y.t/ŮB?Bpr|9Eͅr} E>vGb2,_V Fj@oۃ~o XO ؑy@W\)mbn)blǙ"{U9`'c{})Q9rl8eڙگU,ގcK d +y%O493"7 #u Ź X[X7AH$HV"-A8!~a3Pi[ l9̪\?@z23?=9?hv1|X~ 0Mf(,lYͰ rӪk- —VHmS$\-g?Veړ aL篅N,R':+fɓVu]>ބHͲf7nGYNXYM2{ôHvƂ(}lGv嶺3xm'jlh{ r@ h^- P dwMi ? ?*]Kd  lPh~Az(~.8 +*}|yHwX&)ۄo܎1c9`&B)Dbw핂@ M_Dg֐INIͭscɠ?p}/ ǐO9 b& 8>51C&|`GLQwYZ; <;n[`{;Ȼۤ5zQ$?> endobj -308 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 731.474 513.085 740.321] -/A << /S /GoTo /D (page.20) >> ->> endobj 309 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 719.42 513.085 728.167] +/Rect [501.13 731.573 513.085 740.321] /A << /S /GoTo /D (page.21) >> >> endobj 310 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 707.267 513.085 716.014] +/Rect [501.13 719.42 513.085 728.167] /A << /S /GoTo /D (page.24) >> >> endobj -335 0 obj << +311 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 695.014 513.085 703.861] +/Rect [501.13 707.167 513.085 716.014] /A << /S /GoTo /D (page.27) >> >> endobj -336 0 obj << +337 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 682.741 513.085 691.707] +/Rect [501.13 694.894 513.085 703.861] /A << /S /GoTo /D (page.29) >> >> endobj -337 0 obj << +338 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 670.707 513.085 679.554] +/Rect [501.13 682.861 513.085 691.707] /A << /S /GoTo /D (page.30) >> >> endobj -338 0 obj << +339 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 658.554 513.085 667.401] +/Rect [501.13 670.707 513.085 679.554] /A << /S /GoTo /D (page.32) >> >> endobj -339 0 obj << +340 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 646.401 513.085 655.247] +/Rect [501.13 658.554 513.085 667.401] /A << /S /GoTo /D (page.33) >> >> endobj -340 0 obj << +341 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 634.247 513.085 643.094] +/Rect [501.13 646.401 513.085 655.247] /A << /S /GoTo /D (page.35) >> >> endobj -341 0 obj << +342 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 622.094 513.085 630.941] +/Rect [501.13 634.247 513.085 643.094] /A << /S /GoTo /D (page.37) >> >> endobj -342 0 obj << +343 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 609.941 513.085 618.787] +/Rect [501.13 622.094 513.085 630.941] /A << /S /GoTo /D (page.40) >> >> endobj -343 0 obj << -/Type /Annot -/Subtype /Link -/Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 597.887 513.085 606.634] -/A << /S /GoTo /D (page.42) >> ->> endobj 344 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 585.634 513.085 594.481] -/A << /S /GoTo /D (page.43) >> +/Rect [501.13 610.04 513.085 618.787] +/A << /S /GoTo /D (page.41) >> >> endobj 345 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 573.481 513.085 582.327] -/A << /S /GoTo /D (page.46) >> +/Rect [501.13 597.787 513.085 606.634] +/A << /S /GoTo /D (page.43) >> >> endobj 346 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 561.328 513.085 570.174] -/A << /S /GoTo /D (page.48) >> +/Rect [501.13 585.634 513.085 594.481] +/A << /S /GoTo /D (page.46) >> >> endobj 347 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 549.174 513.085 558.021] -/A << /S /GoTo /D (page.50) >> +/Rect [501.13 573.481 513.085 582.327] +/A << /S /GoTo /D (page.48) >> >> endobj 348 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 537.021 513.085 545.868] -/A << /S /GoTo /D (page.53) >> +/Rect [501.13 561.328 513.085 570.174] +/A << /S /GoTo /D (page.50) >> >> endobj 349 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 524.868 513.085 533.714] -/A << /S /GoTo /D (page.54) >> +/Rect [501.13 549.174 513.085 558.021] +/A << /S /GoTo /D (page.53) >> >> endobj 350 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 512.714 513.085 521.561] -/A << /S /GoTo /D (page.56) >> +/Rect [501.13 537.021 513.085 545.868] +/A << /S /GoTo /D (page.55) >> >> endobj 351 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 500.561 513.085 509.408] -/A << /S /GoTo /D (page.58) >> +/Rect [501.13 524.868 513.085 533.714] +/A << /S /GoTo /D (page.56) >> >> endobj 352 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 488.408 513.085 497.254] -/A << /S /GoTo /D (page.60) >> +/Rect [501.13 512.595 513.085 521.561] +/A << /S /GoTo /D (page.59) >> >> endobj 353 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 476.254 513.085 485.101] +/Rect [501.13 500.561 513.085 509.408] /A << /S /GoTo /D (page.61) >> >> endobj 354 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 464.101 513.085 472.948] -/A << /S /GoTo /D (page.63) >> +/Rect [501.13 488.408 513.085 497.254] +/A << /S /GoTo /D (page.62) >> >> endobj 355 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 451.948 513.085 460.794] -/A << /S /GoTo /D (page.63) >> +/Rect [501.13 476.254 513.085 485.101] +/A << /S /GoTo /D (page.64) >> >> endobj 356 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 439.794 513.085 448.641] +/Rect [501.13 464.101 513.085 472.948] /A << /S /GoTo /D (page.64) >> >> endobj 357 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 427.641 513.085 436.488] +/Rect [501.13 451.948 513.085 460.794] /A << /S /GoTo /D (page.65) >> >> endobj 358 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 415.488 513.085 424.334] +/Rect [501.13 439.794 513.085 448.641] /A << /S /GoTo /D (page.66) >> >> endobj 359 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 403.334 513.085 412.181] +/Rect [501.13 427.641 513.085 436.488] /A << /S /GoTo /D (page.67) >> >> endobj 360 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 391.062 513.085 400.028] -/A << /S /GoTo /D (page.69) >> +/Rect [501.13 415.488 513.085 424.334] +/A << /S /GoTo /D (page.68) >> >> endobj 361 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 379.028 513.085 387.874] -/A << /S /GoTo /D (page.71) >> +/Rect [501.13 403.334 513.085 412.181] +/A << /S /GoTo /D (page.70) >> >> endobj 362 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 366.874 513.085 375.721] -/A << /S /GoTo /D (page.73) >> +/Rect [501.13 391.181 513.085 400.028] +/A << /S /GoTo /D (page.72) >> >> endobj 363 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 354.721 513.085 363.568] +/Rect [501.13 379.028 513.085 387.874] /A << /S /GoTo /D (page.75) >> >> endobj 364 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 342.448 513.085 351.415] -/A << /S /GoTo /D (page.79) >> +/Rect [501.13 366.874 513.085 375.721] +/A << /S /GoTo /D (page.76) >> >> endobj 365 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 330.415 513.085 339.261] -/A << /S /GoTo /D (page.81) >> +/Rect [501.13 354.721 513.085 363.568] +/A << /S /GoTo /D (page.80) >> >> endobj 366 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 318.261 513.085 327.108] -/A << /S /GoTo /D (page.83) >> +/Rect [501.13 342.568 513.085 351.415] +/A << /S /GoTo /D (page.82) >> >> endobj 367 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 306.108 513.085 314.955] +/Rect [501.13 330.415 513.085 339.261] /A << /S /GoTo /D (page.84) >> >> endobj 368 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 293.955 513.085 302.801] -/A << /S /GoTo /D (page.87) >> +/Rect [501.13 318.261 513.085 327.108] +/A << /S /GoTo /D (page.86) >> >> endobj 369 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 281.801 513.085 290.648] -/A << /S /GoTo /D (page.88) >> +/Rect [501.13 305.988 513.085 314.955] +/A << /S /GoTo /D (page.89) >> >> endobj 370 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 269.528 513.085 278.495] -/A << /S /GoTo /D (page.89) >> +/Rect [501.13 293.835 513.085 302.801] +/A << /S /GoTo /D (page.90) >> >> endobj 371 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 257.375 513.085 266.341] +/Rect [501.13 281.682 513.085 290.648] /A << /S /GoTo /D (page.91) >> >> endobj 372 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 245.222 513.085 254.188] -/A << /S /GoTo /D (page.92) >> +/Rect [501.13 269.528 513.085 278.495] +/A << /S /GoTo /D (page.94) >> >> endobj 373 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 233.068 513.085 242.035] -/A << /S /GoTo /D (page.93) >> +/Rect [501.13 257.375 513.085 266.341] +/A << /S /GoTo /D (page.95) >> >> endobj 374 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 220.915 513.085 229.881] -/A << /S /GoTo /D (page.95) >> +/Rect [501.13 245.222 513.085 254.188] +/A << /S /GoTo /D (page.96) >> >> endobj 375 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 208.762 513.085 217.728] -/A << /S /GoTo /D (page.96) >> +/Rect [501.13 233.068 513.085 242.035] +/A << /S /GoTo /D (page.98) >> >> endobj 376 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 196.608 513.085 205.575] -/A << /S /GoTo /D (page.97) >> +/Rect [501.13 220.915 513.085 229.881] +/A << /S /GoTo /D (page.99) >> >> endobj 377 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [501.13 184.455 513.085 193.421] -/A << /S /GoTo /D (page.99) >> +/Rect [496.149 208.881 513.085 217.728] +/A << /S /GoTo /D (page.101) >> >> endobj 378 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [496.149 172.421 513.085 181.268] -/A << /S /GoTo /D (page.102) >> +/Rect [496.149 196.728 513.085 205.575] +/A << /S /GoTo /D (page.103) >> >> endobj 379 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [496.149 160.268 513.085 169.115] -/A << /S /GoTo /D (page.104) >> +/Rect [496.149 184.575 513.085 193.421] +/A << /S /GoTo /D (page.106) >> >> endobj 380 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [496.149 148.115 513.085 156.962] -/A << /S /GoTo /D (page.105) >> +/Rect [496.149 172.421 513.085 181.268] +/A << /S /GoTo /D (page.108) >> >> endobj 381 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [496.149 135.962 513.085 144.808] -/A << /S /GoTo /D (page.106) >> +/Rect [496.149 160.149 513.085 169.115] +/A << /S /GoTo /D (page.109) >> >> endobj 382 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] -/Rect [496.149 123.808 513.085 132.655] -/A << /S /GoTo /D (page.107) >> +/Rect [496.149 148.115 513.085 156.962] +/A << /S /GoTo /D (page.110) >> >> endobj 383 0 obj << /Type /Annot /Subtype /Link /Border[0 0 0]/H/I/C[1 0 0] +/Rect [496.149 136.061 513.085 144.808] +/A << /S /GoTo /D (page.111) >> +>> endobj +384 0 obj << +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] +/Rect [496.149 123.908 513.085 132.655] +/A << /S /GoTo /D (page.112) >> +>> endobj +385 0 obj << +/Type /Annot +/Subtype /Link +/Border[0 0 0]/H/I/C[1 0 0] /Rect [496.149 111.655 513.085 120.502] -/A << /S /GoTo /D (page.108) >> +/A << /S /GoTo /D (page.113) >> >> endobj -388 0 obj << -/D [386 0 R /XYZ 99.346 773.487 null] +390 0 obj << +/D [388 0 R /XYZ 99.346 773.487 null] >> endobj -385 0 obj << -/Font << /F36 317 0 R /F39 320 0 R /F44 389 0 R >> +387 0 obj << +/Font << /F36 318 0 R /F39 321 0 R /F44 391 0 R >> /ProcSet [ /PDF /Text ] >> endobj -450 0 obj << -/Length 1965 +451 0 obj << +/Length 1917 /Filter /FlateDecode >> stream -xX[ܶ~_G]9 at 7,$@f/S_v%Ey3qlOߺ/օE~H;̹^_:<ȓ0q;3(q҄~Flc%,^yZ$K4 'p9H g)nEk/cˡ_ʜ-Cg΃YZ;8A Wdg: 5gAq'a<ȬKQr! O*9~Ѕ 0٩BTFXӈY@Y$p0 - ,MI> me3`.5ܴ -ͽ*Cx]k;gF,^04xA{OXA 8am'CV'mHQ"4P05 ܧM]#/ -lnXݴt+pItT$"A  Z0?{^0Ab~,Ii> ݀`wizA~hڮ#䡜Hthvu|DC:{5R I]^}0.b?ܶ2 FZvwߛ+CHbʕ -??]g.YQ [;ܦQRM2|w`dGjWE}4&\`R^/%$;UlP8 K%8Ɨg]pY: QF޲*J -!){n^ -)$#R -Go:]k -Fb߈qƤy3S}ZCz[0]m" 8 - ,\P7NᒝJefLeS ̿`:KAUqfl+=k -c\7z@½hV+ 'yu&J\1 Xr{-I0j[O3P(Seo/+8 -,soz*;x߶Ks)JeN"BR -6_DT#9Ma|*% ?0v(ihf.ښJu>;e5ֱt22vN$շJsF(v1 "}3ә4U٥8՘wJF9(R8אX%