[Distr-commits] r1180 - in pkg/distrMod: . R inst man tests/Examples vignettes

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Sun Jul 8 16:23:41 CEST 2018


Author: ruckdeschel
Date: 2018-07-08 16:23:40 +0200 (Sun, 08 Jul 2018)
New Revision: 1180

Modified:
   pkg/distrMod/DESCRIPTION
   pkg/distrMod/NAMESPACE
   pkg/distrMod/R/0distrModUtils.R
   pkg/distrMod/R/L2GroupFamilies.R
   pkg/distrMod/R/qqplot.R
   pkg/distrMod/R/returnlevelplot.R
   pkg/distrMod/inst/NEWS
   pkg/distrMod/man/0distrMod-package.Rd
   pkg/distrMod/man/MDEstimator.Rd
   pkg/distrMod/man/internals-qqplot.Rd
   pkg/distrMod/man/internals.Rd
   pkg/distrMod/man/qqplot.Rd
   pkg/distrMod/man/returnlevelplot.Rd
   pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save
   pkg/distrMod/vignettes/Estimate.pdf
   pkg/distrMod/vignettes/ParamFamParameter.pdf
   pkg/distrMod/vignettes/ProbFamily.pdf
   pkg/distrMod/vignettes/distrMod.Rnw
   pkg/distrMod/vignettes/distrMod.bib
Log:
[distrMod] merged branch 2.7 back to trunk

Modified: pkg/distrMod/DESCRIPTION
===================================================================
--- pkg/distrMod/DESCRIPTION	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/DESCRIPTION	2018-07-08 14:23:40 UTC (rev 1180)
@@ -1,6 +1,6 @@
 Package: distrMod
-Version: 2.6.2
-Date: 2016-09-04
+Version: 2.7
+Date: 2015-11-07
 Title: Object Oriented Implementation of Probability Models
 Description: Implements S4 classes for probability models based on packages 'distr' and
         'distrEx'.
@@ -10,11 +10,12 @@
 Depends: R(>= 2.14.0), distr(>= 2.5.2), distrEx(>= 2.4), RandVar(>= 0.6.3), MASS, stats4,
         methods
 Imports: startupmsg, sfsmisc, graphics, stats, grDevices
-Suggests: ismev, evd, RobExtremes
+Suggests: ismev, evd, 
+Enhances: RobExtremes
 ByteCompile: yes
 License: LGPL-3
 Encoding: latin1
 URL: http://distr.r-forge.r-project.org/
 LastChangedDate: {$LastChangedDate$}
 LastChangedRevision: {$LastChangedRevision$}
-SVNRevision: 1104
+SVNRevision: 1080

Modified: pkg/distrMod/NAMESPACE
===================================================================
--- pkg/distrMod/NAMESPACE	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/NAMESPACE	2018-07-08 14:23:40 UTC (rev 1180)
@@ -92,4 +92,4 @@
 export("L2LocationUnknownScaleFamily", "L2ScaleUnknownLocationFamily")
 export("meRes", "get.criterion.fct")
 export("addAlphTrsp2col")
-export(".deleteDim",".isUnitMatrix", ".CvMMDCovariance")
+export(".deleteDim",".isUnitMatrix",".CvMMDCovariance")

Modified: pkg/distrMod/R/0distrModUtils.R
===================================================================
--- pkg/distrMod/R/0distrModUtils.R	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/R/0distrModUtils.R	2018-07-08 14:23:40 UTC (rev 1180)
@@ -16,8 +16,8 @@
              lowerTruncQuantile = getdistrExOption("ElowerTruncQuantile"), 
              upperTruncQuantile = getdistrExOption("EupperTruncQuantile"), 
                          IQR.fac = getdistrExOption("IQR.fac")){
-  low0 <- q(distr)(lowerTruncQuantile)
-  upp0 <- q(distr)(upperTruncQuantile,lower.tail=FALSE)
+  low0 <- q.l(distr)(lowerTruncQuantile)
+  upp0 <- q.l(distr)(upperTruncQuantile,lower.tail=FALSE)
   me <- median(distr)
   s1 <- IQR(distr)
   low1 <- me - IQR.fac * s1 
@@ -103,69 +103,58 @@
    N1 <- 2*N+1
    odd <- (1:N1)%%2==1
 
-   ## shift L2family to a parameter value as given in main(param)
    param0 <- L2Fam at param
    dim0 <- dimension(param0)
+#   print(param0)
    paramP <- param0
    paramP at main <- main(param)
    paramP at trafo <- diag(dim0)
+#   print(paramP)
    L2Fam <- modifyModel(L2Fam, paramP)
 
+#   print(L2deriv(L2Fam)[[1]]@Map)
    distr <- L2Fam at distribution
    
    ### get a sensible integration range:
-   if(is(distr,"DiscreteDistribution")){
-       x.seq0 <- x.seq <- support(distr)
-       low <- min(x.seq)
-       up <- max(x.seq) 
-   }else{
+   low0 <- q.l(distr)(TruncQuantile)
+   up0 <- q.l(distr)(TruncQuantile, lower.tail = FALSE)
+   m0 <- median(distr); s0 <- IQR(distr)
+   low1 <- m0 - IQR.fac * s0
+   up1  <- m0 + IQR.fac * s0
+   low <- max(low0,low1); up <- min(up0,up1)
+
    ### get a sensible integration range:
-       low0 <- q(distr)(TruncQuantile) 
-       up0 <- q(distr)(TruncQuantile, lower.tail = FALSE) 
-       m0 <- median(distr); s0 <- IQR(distr)
-       low1 <- m0 - IQR.fac * s0
-       up1  <- m0 + IQR.fac * s0
-       low <- max(low0,low1); up <- min(up0,up1)
-       if(is(distr,"AbscontDistribution")){
-          x.seq0 <- seq(low, up, length = N1)
-          h0 <- x.seq0[1:2]%*%c(-1,1)
-          x.seq <- x.seq0[odd]
-       }else{ 
-          x.seq0 <- x.seq <- seq(low,up, length = N)
-       }
-   }
+   if(missing(mu)) mu <- distr
+   low0.mu <- q.l(mu)(TruncQuantile)
+   up0.mu <- q.l(mu)(TruncQuantile, lower.tail = FALSE)
+   m0.mu <- median(mu); s0.mu <- IQR(mu)
+   low1.mu <- m0.mu - IQR.fac * s0.mu
+   up1.mu  <- m0.mu + IQR.fac * s0.mu
+   low.mu <- max(low0.mu,low1.mu); up.mu <- min(up0.mu,up1.mu)
 
-   ## similar for mu
-   if(missing(mu)){
-      mu <- distr
-      low.mu <- low
-      up.mu <- up
-      x.mu.seq <- x.seq
-      if(is(distr,"AbscontDistribution")){
-         x.mu.seq0 <- x.seq0
-         h0.mu <- h0
-      }   
-   }else{
-     if(is(distr,"DiscreteDistribution")){
+
+   if(is(distr,"DiscreteDistribution"))
+       x.seq <-support(distr)
+   else
+       {if(is(distr,"AbscontDistribution")){
+           x.seq0 <- seq(low, up, length = N1)
+           h0 <- diff(x.seq0[2:1])
+           x.seq <- x.seq0[odd]
+          }else{ 
+           x.seq <- seq(low,up, length = N)
+          }
+       }
+   if(is(mu,"DiscreteDistribution"))
        x.mu.seq <- support(mu)
-       low.mu <- min(x.mu.seq)
-       up.mu <- max(x.mu.seq)
-     }else{ 
-       low0.mu <- q(mu)(TruncQuantile) 
-       up0.mu <- q(mu)(TruncQuantile, lower.tail = FALSE) 
-       m0.mu <- median(mu); s0.mu <- IQR(mu)
-       low1.mu <- m0.mu - IQR.fac * s0.mu
-       up1.mu  <- m0.mu + IQR.fac * s0.mu
-       low.mu <- max(low0.mu,low1.mu); up.mu <- min(up0.mu,up1.mu)
-       if(is(mu,"AbscontDistribution")){
+   else
+       {if(is(mu,"AbscontDistribution")){
            x.mu.seq0 <- seq(low.mu, up.mu, length = N1)
-           h0.mu <- x.mu.seq0[1:2]%*%c(-1,1)
+           h0.mu <- diff(x.mu.seq0[2:1])
            x.mu.seq <- x.mu.seq0[odd]
-       }else{ 
+          }else{ 
            x.mu.seq <- seq(low.mu, up.mu, length = N)
+          }
        }
-     }
-   }
    
    L2deriv <- L2deriv(L2Fam)[[1]]
 #   y.seq <- sapply(x.seq, function(x) evalRandVar(L2deriv, x))
@@ -188,35 +177,30 @@
                  d(distr)(x.seq0)
       Delta0 <-  h0*.csimpsum(Delta0x)   
    }else{
-      if(is(distr,"DiscreteDistribution")){
-         Delta0x <- sapply(x.seq0, function(x) 
-                                evalRandVar(L2deriv, x)) * 
-                    d(distr)(x.seq0)
-         Delta0 <- cumsum(Delta0x)           
-      }else{
-         L2x  <- function(x,y)  (x<=y)*evalRandVar(L2deriv, x)
-         Delta0 <- sapply(x.seq, function(Y){ fct <- function(x) L2x(x,y=Y)
+      L2x  <- function(x,y)  (x<=y)*evalRandVar(L2deriv, x)
+      Delta0 <- sapply(x.seq, function(Y){ fct <- function(x) L2x(x,y=Y)
                                         return(E(object=distr, fun = fct))})
-      }                                  
    }
  #  print(Delta0)
    Delta1 <- approxfun(x.seq, Delta0, yleft = 0, yright = 0)
    if(is(distr,"DiscreteDistribution"))         
       Delta <- function(x) Delta1(x) * (x %in% support(distr))
-   else  Delta <- Delta1
-#   print(Delta(x.seq))
+   else  Delta <- function(x) Delta1(x)
+ #  print(Delta(x.seq))
  #  print(Delta(rnorm(100)))
 
    ## J = Var_Ptheta Delta
+   J1 <- E(object=distr, fun = Delta)
 #   print(J1)
+   Delta.0 <- function(x) Delta(x) - J1
  #  print(Delta.0(x.seq))
  #  print(Delta.0(r(distr)(100))^2)
    #J <- distrExIntegrate(function(x) d(distr)(x)*Delta.0(x)^2, lower=low, upper=up)
-   J <- E(object=distr, fun = function(x) Delta(x)^2 )
+   J <- E(object=distr, fun = function(x) Delta.0(x)^2 )
 #   print(J)
    
    ### CvM-IC phi
-   phi <- function(x) Delta(x)/J
+   phi <- function(x) Delta.0(x)/J
 
    ## integrand phi x Ptheta in formula (51) [ibid]
    phi1 <- function(x) phi(x) * p(distr)(x)
@@ -251,14 +235,13 @@
    psi.01 <- function(x) psi.0(x)/E3
    if(withplot)
        { dev.new() #windows()
-         
          plot(x.seq, psi.01(x.seq),
                      type = if(is(distr,"DiscreteDistribution")) "p" else "l")
        }
    E4 <- E(object=distr, fun = function(x) psi.01(x)^2)
    psi.01 <- EuclRandVariable(Map = list(psi.01), Domain = Reals())
 
-#   print(list(E1,E2,E4,E2-E4))
+#   print(list(E2,E4,E2-E4))
 
       }else{
 
@@ -396,7 +379,7 @@
 B0 <- BinomFamily(size=8, prob=0.3);.CvMMDCovariance(B0,par=ParamFamParameter("",.3), withplot=TRUE)
 N0 <- NormLocationFamily();.CvMMDCovariance(N0,par=ParamFamParameter("",0), withplot=TRUE, N = 200)
 C0 <- L2LocationFamily(central=Cauchy());.CvMMDCovariance(C0,par=ParamFamParameter("",0), withplot=TRUE, N = 200)
-N1 <- NormScaleFamily(); re=.CvMMDCovariance(N1,par=ParamFamParameter("",1), withpreIC,withplot=TRUE, N = 200)
+N1 <- NormScaleFamily(); re=.CvMMDCovariance(N1,par=ParamFamParameter("",1), withICwithplot=TRUE, N = 200)
 NS <- NormLocationScaleFamily();paramP <- ParamFamParameter(name = "locscale", main = c("loc"=0,"scale"=1),trafo = diag(2));
       .CvMMDCovariance(NS,par=paramP, withplot=TRUE, N = 100)
 cls <- CauchyLocationScaleFamily();.CvMMDCovariance(cls,par=ParamFamParameter("",0:1), withplot=TRUE, N = 200)
@@ -635,8 +618,8 @@
 
 .NotInSupport <- function(x,D){
   if(length(x)==0) return(logical(0))
-  nInSupp <- which(x < q(D)(0))
-  nInSupp <- unique(sort(c(nInSupp,which(x > q(D)(1)))))
+  nInSupp <- which(x < q.l(D)(0))
+  nInSupp <- unique(sort(c(nInSupp,which(x > q.l(D)(1)))))
 
   nInSuppo <-
       if("support" %in% names(getSlots(class(D))))
@@ -664,7 +647,7 @@
 
   lx[.NotInSupport(x,D)] <- 4
 
-  idx.0 <- ((x>q(D)(1)) | (x<q(D)(0)))
+  idx.0 <- ((x>q.l(D)(1)) | (x<q.l(D)(0)))
   iG <- rep(FALSE,length(x))
 
   if(is(D, "DiscreteDistribution")){

Modified: pkg/distrMod/R/L2GroupFamilies.R
===================================================================
--- pkg/distrMod/R/L2GroupFamilies.R	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/R/L2GroupFamilies.R	2018-07-08 14:23:40 UTC (rev 1180)
@@ -333,7 +333,7 @@
     }
 
     mad.const <- 1/ if (is(distrSymm, "NoSymmetry")) 
-                        mad(centraldistribution) else q(centraldistribution)(.75)
+                        mad(centraldistribution) else q.l(centraldistribution)(.75)
     
     param0 <- c(loc, scale)
     names(param0) <- locscalename

Modified: pkg/distrMod/R/qqplot.R
===================================================================
--- pkg/distrMod/R/qqplot.R	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/R/qqplot.R	2018-07-08 14:23:40 UTC (rev 1180)
@@ -122,7 +122,7 @@
     ord.x <- order(xj)
 
     pp <- ppoints(n)
-    yc <- q(y)(pp)
+    yc <- q.l(y)(pp)
 
     yc.o <- yc
 
@@ -146,9 +146,9 @@
 
     if(check.NotInSupport){
        xo <- x[ord.x]
-       nInSupp <- which(xo < q(y)(0))
+       nInSupp <- which(xo < q.l(y)(0))
 
-       nInSupp <- unique(sort(c(nInSupp,which( xo > q(y)(1)))))
+       nInSupp <- unique(sort(c(nInSupp,which( xo > q.l(y)(1)))))
        if("support" %in% names(getSlots(class(y))))
           nInSupp <- unique(sort(c(nInSupp,which( ! xo %in% support(y)))))
        if("gaps" %in% names(getSlots(class(y))))
@@ -270,7 +270,7 @@
         }
        }
     }
-    qqplotInfo <- c(ret, qqplotInfo, qqb)
+    qqplotInfo <- c(call=mc, ret, qqplotInfo, qqb)
     class(qqplotInfo) <- c("qqplotInfo","DiagnInfo")
     return(invisible(qqplotInfo))
     })
@@ -292,8 +292,10 @@
     if(!is(yD,"UnivariateDistribution"))
        stop("Not yet implemented.")
 
-    return(invisible(do.call(getMethod("qqplot", signature(x="ANY", y="UnivariateDistribution")),
-            args=mcl)))
+    retv <- do.call(getMethod("qqplot", signature(x="ANY", y="UnivariateDistribution")),
+            args=mcl)
+    retv$call <- mc        
+    return(invisible(retv))
     })
 
 setMethod("qqplot", signature(x = "ANY",
@@ -321,7 +323,9 @@
 
     PFam0 <- modifyModel(PFam, param)
     mcl$y <- PFam0
-    return(invisible(do.call(getMethod("qqplot", signature(x="ANY", y="ProbFamily")),
-            args=mcl)))
+    retv <- do.call(getMethod("qqplot", signature(x="ANY", y="ProbFamily")),
+            args=mcl)
+    retv$call <- mc        
+    return(invisible(retv))
     })
 

Modified: pkg/distrMod/R/returnlevelplot.R
===================================================================
--- pkg/distrMod/R/returnlevelplot.R	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/R/returnlevelplot.R	2018-07-08 14:23:40 UTC (rev 1180)
@@ -54,7 +54,7 @@
              col.pch = par("col"),## color for the plotted symbols
              cex.lbl = par("cex"),## magnification factor for the plotted observation labels
              col.lbl = par("col"),## color for the plotted observation labels
-             adj.lbl = NULL,      ## adj parameter for the plotted observation labels
+             adj.lbl = par("adj"),## adj parameter for the plotted observation labels
              alpha.trsp = NA,     ## alpha transparency to be added afterwards
              jit.fac = 0,         ## jittering factor used for discrete distributions
              jit.tol = .Machine$double.eps, ## tolerance for jittering: if distance 
@@ -120,13 +120,13 @@
     }
 
     pp <- ppoints(length(xj))
-    yc.o <- q(y)(pp)
+    yc.o <- q.l(y)(pp)
     ycl <- p2rl(yc.o)
 
     ### extend range somewhat
 #    pyn <- p(y)(10^(seq(-1, 3.75 + log10(npy), by = 0.1)))
     xyall <- force(sort(unique(c(yc.o,x,
-                    q(y)(c(seq(0.01, 0.09, by = 0.01),(1:9)/10,
+                    q.l(y)(c(seq(0.01, 0.09, by = 0.01),(1:9)/10,
                          0.95, 0.99, 0.995, 0.999))
                          ))))
     rxyall  <- (max(xyall)-min(xyall))*0.6
@@ -162,9 +162,9 @@
 
     if(check.NotInSupport){
        xo <- x[ord.x]
-       nInSupp <- which(xo < q(y)(0))
+       nInSupp <- which(xo < q.l(y)(0))
 
-       nInSupp <- unique(sort(c(nInSupp,which( xo > q(y)(1)))))
+       nInSupp <- unique(sort(c(nInSupp,which( xo > q.l(y)(1)))))
        if("support" %in% names(getSlots(class(y))))
           nInSupp <- unique(sort(c(nInSupp,which( ! xo %in% support(y)))))
        if("gaps" %in% names(getSlots(class(y))))

Modified: pkg/distrMod/inst/NEWS
===================================================================
--- pkg/distrMod/inst/NEWS	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/inst/NEWS	2018-07-08 14:23:40 UTC (rev 1180)
@@ -8,6 +8,20 @@
  information)
 
 ##############
+v 2.7
+##############
+
+user-visible CHANGES:
++ replaced http://CRAN... by https://CRAN... (also in CITATION and similar files) 
++ exported .CvMMDCovariance in distrMod
++ added call to return value of qqplot
+
+under the hood:
++ wherever possible also use q.l internally instead of q to 
+  provide functionality in IRKernel
++ fixed omegahat.net issue (raised by K.Hornik,(24.10.2016, 18:08)
+
+##############
 v 2.6
 ##############
 
@@ -64,7 +78,6 @@
   BUGFIXES:
 
 
-+ fixed an issue with MDEstimator and validParameter
 + fixed issue with slot withPosRestr in ParamFamParameter.R 
 + fixed issue with check.validity (reported by B.Spangl)
 + fixed some minor issue in existsPIC (in case we get 0 matrix, and less strict tolerance) 

Modified: pkg/distrMod/man/0distrMod-package.Rd
===================================================================
--- pkg/distrMod/man/0distrMod-package.Rd	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/man/0distrMod-package.Rd	2018-07-08 14:23:40 UTC (rev 1180)
@@ -15,16 +15,17 @@
 \details{
 \tabular{ll}{
 Package: \tab distrMod \cr
-Version: \tab 2.6 \cr
-Date: \tab 2016-04-23 \cr
+Version: \tab 2.7 \cr
+Date: \tab 2015-11-07 \cr
 Depends: \tab R(>= 2.14.0), distr(>= 2.5.2), distrEx(>= 2.4), RandVar(>= 0.6.3), MASS, stats4,
         methods \cr
 Imports: \tab startupmsg, sfsmisc, graphics, stats, grDevices \cr
-Suggests: \tab ismev, evd, RobExtremes \cr
+Suggests: \tab ismev, evd\cr
+Enhances: RobExtremes\cr
 ByteCompile: \tab yes \cr
 License: \tab LGPL-3 \cr
 URL: \tab http://distr.r-forge.r-project.org/\cr
-SVNRevision: \tab 1104 \cr
+SVNRevision: \tab 1080 \cr
 }}
 
 \section{Classes}{
@@ -291,7 +292,7 @@
 M. Kohl and P. Ruckdeschel (2010):
 R Package distrMod: S4 Classes and Methods for Probability Models.
 Journal of Statistical Software, 35(10), 1-27.
-\url{http://www.jstatsoft.org/v35/i10/}
+\url{https://www.jstatsoft.org/v35/i10/}
 (see also \code{vignette("distrMod")})
 
 

Modified: pkg/distrMod/man/MDEstimator.Rd
===================================================================
--- pkg/distrMod/man/MDEstimator.Rd	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/man/MDEstimator.Rd	2018-07-08 14:23:40 UTC (rev 1180)
@@ -74,7 +74,7 @@
 %\note{}
 \seealso{\code{\link{ParamFamily-class}}, \code{\link{ParamFamily}}, 
          \code{\link{MCEstimator}}, \code{\link{MCEstimate-class}},
-          \code{\link[MASS]{fitdistr}}, \code{\link{.CvMMDCovariance}}}
+          \code{\link[MASS]{fitdistr}} }
 \examples{
 ## (empirical) Data
 x <- rgamma(50, scale = 0.5, shape = 3)
@@ -90,7 +90,9 @@
 
 ## von Mises minimum distance estimator with default mu
 MDEstimator(x = x, ParamFamily = G, distance = CvMDist,
-            asvar.fct = .CvMMDCovariance)
+            asvar.fct = distrMod:::.CvMMDCovariance)
+#*** variance routine is still in testing phase so not yet
+#*** exported to namespace
 ## von Mises minimum distance estimator with mu = N(0,1)
 MDEstimator(x = x, ParamFamily = G, distance = CvMDist, mu = Norm())
 

Modified: pkg/distrMod/man/internals-qqplot.Rd
===================================================================
--- pkg/distrMod/man/internals-qqplot.Rd	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/man/internals-qqplot.Rd	2018-07-08 14:23:40 UTC (rev 1180)
@@ -18,7 +18,7 @@
 \item{y}{a (numeric) vector of same length as \code{x}}
 \item{cex.lbl}{magnification factor for the plotted observation labels}
 \item{col.lbl}{color for the plotted observation labels}
-\item{adj.lbl}{adj parameter for the plotted observation labels}
+\item{adj.lbl}{adjustment factor for the plotted observation labels}
 \item{lab.pts}{character or \code{NULL}; observation labels to be used}
 \item{which.lbs}{integer or \code{NULL}; which observations shall be labelled}
 \item{which.Order}{integer or \code{NULL}; which of the ordered (remaining) observations shall be labelled}
@@ -45,7 +45,6 @@
 \code{lab} (the thinned out and ordered vector of labels \code{lab.pts}),
 \code{col} (the thinned out and ordered vector of colors \code{col.lbs}),
 \code{cex} (the thinned out and ordered vector of magnification factors \code{cex.lbs}).
-\code{adj} (the thinned out and ordered vector of adjacencies \code{adj.lbs}).
 }
 }
 

Modified: pkg/distrMod/man/internals.Rd
===================================================================
--- pkg/distrMod/man/internals.Rd	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/man/internals.Rd	2018-07-08 14:23:40 UTC (rev 1180)
@@ -18,7 +18,7 @@
 .isUnitMatrix(m)
 .csimpsum(fx)
 .validTrafo(trafo, dimension, dimensionwithN)
-.CvMMDCovariance(L2Fam, param, mu = distribution(L2Fam),  
+.CvMMDCovariance(L2Fam, param, mu = distribution(L2Fam),
                  withplot = FALSE, withpreIC = FALSE,
                  N = getdistrOption("DefaultNrGridPoints")+1,
                  rel.tol=.Machine$double.eps^0.3, 
@@ -42,30 +42,29 @@
   \item{trafo}{an object of class \code{MatrixorFunction}}
   \item{dimension}{a numeric --- length of main part of the parameter}
   \item{dimensionwithN}{a numeric --- length of main and nuisance part of the parameter}
-
   \item{L2Fam}{an object of class \code{L2ParamFamily} --- for
   which we want to determine the IC resp. the as. [co]variance of the corresponding
   Minimum CvM estimator}
+  \item{param}{an object of class \code{ParamFamParameter}, the parameter value
+  at which we want to determine the IC resp. the as. [co]variance of the corresponding
+  Minimum CvM estimator}
   \item{mu}{an object of class \code{UnivariateDistribution}: integration 
             measure (resp. distribution) for CvM distance}
-  \item{withplot}{logical; defaults to \code{FALSE}; if \code{TRUE} for diagnostic  
-                  purposes plots the influence function of the CvM-MDE}
+  \item{rel.tol}{relative tolerance for \code{distrExIntegrate}.} 
+  \item{TruncQuantile}{quantile for quantile based integration range.}
+  \item{lowerTruncQuantile}{lower quantile for quantile based integration range.}
+  \item{upperTruncQuantile}{upper quantile for quantile based integration range.}
+  \item{IQR.fac}{factor for scale based integration range (i.e.; 
+  median of the distribution \eqn{\pm}{+-}\code{IQR.fac}\eqn{\times}{*}IQR).}
+  \item{withplot}{logical: shall we plot corresponding ICs?}
   \item{withpreIC}{logical: shall we return a list with components \code{preIC} 
        and \code{var} or just \code{var}; here \code{var} is the corresponding
        asymptotic variance and \code{preIC} the corresponding
    \code{EuclRandVarList} featuring as argument \code{Curve} in \code{IC}s of
    package \pkg{RobAStBase}}
-  \item{\dots}{currently not used} 
-  \item{N}{integer; the number of grid points at which to evaluate the antiderivative
-          in case of an absolutely continuous distribution; more precisely, internally
-		  this becomes \eqn{2N+1}}
-  \item{rel.tol}{relative tolerance for \code{distrExIntegrate}.} 
-  \item{TruncQuantile}{numeric in (0,1); in case of an unbounded support of the 
-                       distribution the quantile level at which to cut the distribution}
-  \item{IQR.fac}{a positive numeric; a factor by which to multiply the IQR of the distribution
-                 to obtain a sensible cut of point for the integration bounds}
-  \item{lowerTruncQuantile}{lower quantile for quantile based integration range.}
-  \item{upperTruncQuantile}{upper quantile for quantile based integration range.}
+  \item{N}{a numeric: the number of gridpoints for constructing the 
+           \eqn{\mu}{mu}- resp. \eqn{P_\theta}{P_theta}-``primitive''
+           function}
  \item{fx}{a vector of function evaluations multiplied by the gridwidth}
  \item{distr}{an object of class \code{AbscontDistribution}}
   \item{\dots}{further argument to be passed through --- so 
@@ -88,8 +87,9 @@
 
 \code{.validTrafo} checks whether the argument is a valid transformation.
 
-\code{.CvMMDCovariance} computes the asymptotic covariance of the CvM-MDE 
-according to H. Rieder (1994) "Robust Asymptotic Statistics".
+\code{.CvMMDCovariance} determines the IC resp. the as. [co]variance of 
+   the corresponding Minimum CvM estimator. Still some checking / optimization /
+   improvement needed.
 
 \code{.show.with.sd} is code borrowed from \code{print.fitdistr} in  
 package \pkg{MASS} by B.D. Ripley. It pretty-prints estimates with corresponding
@@ -115,9 +115,6 @@
    \code{preIC} and \code{var} ---see above}
 \item{.show.with.sd}{\code{invisible()}}
 \item{.deleteDim}{vector \code{x} without \code{dim} attribute}
-\item{.CvMMDCovariance}{if argument \code{withpreIC} is \code{TRUE}, then
-a list with elements the IC of the CvM-MDE and its covariance is returned, otherwise
-just the covariance}
 }
 
 \author{

Modified: pkg/distrMod/man/qqplot.Rd
===================================================================
--- pkg/distrMod/man/qqplot.Rd	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/man/qqplot.Rd	2018-07-08 14:23:40 UTC (rev 1180)
@@ -144,54 +144,12 @@
 }
 }
 \value{
-  A list of elements containing the information needed to compute the 
-  respective QQ plot, in particular it extends the elements of the 
-  return value of function \code{\link[stats:qqnorm]{qqplot}} 
-  from package \pkg{stats}, i.e., a
-  list with components \code{x} and \code{y} for x and y coordinates
-  of the plotted points; this list is of S3 class 
-  \code{c("qqplotInfo","DiagnInfo")}, and more specifically it contains
+    As for function \code{\link[stats:qqnorm]{qqplot}} from package \pkg{stats}: a
+  list with components
 \item{x}{The x coordinates of the points that were/would be plotted}
   \item{y}{The corresponding quantiles of the second distribution,
            \emph{including \code{\link{NA}}s}.}
-           
- \item{xy.0}{xy} 
- \item{y.0}{y}
- \item{datax}{argument \code{datax} from the call.} 
- \item{withConf.pw}{argument \code{withConf.pw} from the call.} 
- \item{withConf.sim}{argument \code{withConf.sim} from the call.} 
- \item{alpha.CI}{argument \code{alpha.CI } from the call.}
- \item{col.pCI}{argument \code{col.pCI} from the call.} 
- \item{lty.pCI}{argument \code{lty.pCI} from the call.} 
- \item{lwd.pCI}{argument \code{lwd.pCI} from the call.} 
- \item{pch.pCI}{argument \code{pch.pCI} from the call.} 
- \item{cex.pCI}{argument \code{cex.pCI} from the call.} 
- \item{col.sCI}{argument \code{col.sCI} from the call.} 
- \item{lty.sCI}{argument \code{lty.sCI} from the call.} 
- \item{lwd.sCI}{argument \code{lwd.sCI} from the call.} 
- \item{pch.sCI}{argument \code{pch.sCI} from the call.} 
- \item{cex.sCI}{argument \code{cex.sCI} from the call.} 
- \item{n}{argument \code{n} from the call.} 
- \item{exact.sCI}{argument \code{exact.sCI} from the call.}
- \item{exact.pCI}{argument \code{exact.pCI} from the call.}
- \item{nosym.pCI}{argument \code{nosym.pCI} from the call.}
- \item{with.legend}{argument \code{with.legend} from the call.}
- \item{legend.bg}{argument \code{legend.bg} from the call.}
- \item{legend.pos}{argument \code{legend.pos} from the call.}
- \item{legend.cex}{argument \code{legend.cex} from the call.} 
- \item{legend.pref}{argument \code{legend.pref} from the call.}
- \item{legend.postf}{argument \code{legend.postf} from the call.} 
- \item{legend.alpha}{argument \code{legend.alpha} from the call.} 
- \item{debug}{argument \code{debug} from the call.}
- \item{args.stats.qqplot}{the arguments of the call to \code{mcl} from the call.}
- \item{withLab}{argument \code{withLab} from the call to
- \code{stats::qqplot} from within this QQ plot method.}
- \item{lbprep}{the return value of the label preparation from within
-               this function, i.e., a list with elements 
-      \code{x0}, \code{y0}, \code{lab}, \code{col}, \code{cex}, 
-      \code{adj}.}
-
- \item{crit}{A matrix with the lower and upper confidence bounds
+  \item{crit}{A matrix with the lower and upper confidence bounds
                (computed by \code{qqbounds}).}
   \item{err}{logical vector of length 2.}
   (elements \code{crit} and \code{err} are taken from the return
@@ -239,9 +197,9 @@
 }
 \examples{
 set.seed(123)
-x <- rnorm(40,mean=5,sd=sqrt(10))
-qqplot(x, Chisq(df=5))
-NF <- NormLocationScaleFamily(mean=5, sd=30^.5)
+x <- rnorm(40,mean=15,sd=30)
+qqplot(x, Chisq(df=15))
+NF <- NormLocationScaleFamily(mean=15, sd=30)
 qqplot(x, NF)
 mlE <- MLEstimator(x, NF)
 qqplot(x, mlE)

Modified: pkg/distrMod/man/returnlevelplot.Rd
===================================================================
--- pkg/distrMod/man/returnlevelplot.Rd	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/man/returnlevelplot.Rd	2018-07-08 14:23:40 UTC (rev 1180)
@@ -21,7 +21,7 @@
     col.sCI = "tomato2", lty.sCI = 4, lwd.sCI = 2, pch.sCI = par("pch"),
     cex.sCI = par("cex"), added.points.CI = TRUE,
     cex.pch = par("cex"), col.pch = par("col"),
-    cex.lbl = par("cex"), col.lbl = par("col"), adj.lbl = NULL,
+    cex.lbl = par("cex"), col.lbl = par("col"), adj.lbl = par("adj"),
     alpha.trsp = NA, jit.fac = 0,  jit.tol = .Machine$double.eps,
     check.NotInSupport = TRUE, col.NotInSupport = "red",
     with.legend = TRUE, legend.bg = "white",

Modified: pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save
===================================================================
--- pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save	2018-07-08 14:23:04 UTC (rev 1179)
+++ pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save	2018-07-08 14:23:40 UTC (rev 1180)
@@ -1,7 +1,7 @@
 
-R Under development (unstable) (2016-08-31 r71184) -- "Unsuffered Consequences"
-Copyright (C) 2016 The R Foundation for Statistical Computing
-Platform: i386-w64-mingw32/i386 (32-bit)
+R Under development (unstable) (2015-05-02 r68310) -- "Unsuffered Consequences"
+Copyright (C) 2015 The R Foundation for Statistical Computing
+Platform: x86_64-unknown-linux-gnu (64-bit)
 
 R is free software and comes with ABSOLUTELY NO WARRANTY.
 You are welcome to redistribute it under certain conditions.
@@ -20,23 +20,10 @@
 > pkgname <- "distrMod"
 > source(file.path(R.home("share"), "R", "examples-header.R"))
 > options(warn = 1)
-> options(pager = "console")
-> base::assign(".ExTimings", "distrMod-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')
-> 
-> ### * </HEADER>
 > library('distrMod')
 Loading required package: distr
 Loading required package: startupmsg
-:startupmsg>  Utilities for Start-Up Messages (version 0.9.3)
+:startupmsg>  Utilities for Start-Up Messages (version 0.9.1)
 :startupmsg> 
 :startupmsg>  For more information see ?"startupmsg",
 :startupmsg>  NEWS("startupmsg")
@@ -45,7 +32,7 @@
 Loading required package: SweaveListingUtils
 :SweaveListingUtils>  Utilities for Sweave Together with
 :SweaveListingUtils>  TeX 'listings' Package (version
-:SweaveListingUtils>  0.7.5)
+:SweaveListingUtils>  0.7)
 :SweaveListingUtils> 
 :SweaveListingUtils>  NOTE: Support for this package
 :SweaveListingUtils>  will stop soon.
@@ -71,9 +58,9 @@
 :SweaveListingUtils>  vignette("ExampleSweaveListingUtils").
 
 
-Attaching package: 'SweaveListingUtils'
+Attaching package: ‘SweaveListingUtils’
 
-The following objects are masked from 'package:base':
+The following objects are masked from ‘package:base’:
 
     library, require
 
@@ -97,9 +84,9 @@
 :distr>  vignette("distr").
 
 
-Attaching package: 'distr'
+Attaching package: ‘distr’
 
-The following objects are masked from 'package:stats':
+The following objects are masked from ‘package:stats’:
 
     df, qqplot, sd
 
@@ -121,14 +108,14 @@
 :distrEx>  vignette("distr").
 
 
-Attaching package: 'distrEx'
+Attaching package: ‘distrEx’
 
-The following objects are masked from 'package:stats':
+The following objects are masked from ‘package:stats’:
 
     IQR, mad, median, var
 
 Loading required package: RandVar
-:RandVar>  Implementation of Random Variables (version 1.0)
+:RandVar>  Implementation of random variables (version 0.9.2)
 :RandVar> 
 :RandVar>  For more information see ?"RandVar", NEWS("RandVar"), as
 :RandVar>  well as
@@ -139,7 +126,7 @@
 Loading required package: MASS
 Loading required package: stats4
 :distrMod>  Object Oriented Implementation of Probability Models
-:distrMod>  (version 2.6.1)
+:distrMod>  (version 2.6)
 :distrMod> 
 :distrMod>  Some functions from pkg's 'base' and 'stats' are
 :distrMod>  intentionally masked ---see distrModMASK().
@@ -158,17 +145,17 @@
 :distrMod>  vignette("distr").
 
 
-Attaching package: 'distrMod'
+Attaching package: ‘distrMod’
 
-The following object is masked from 'package:stats4':
+The following object is masked from ‘package:stats4’:
 
     confint
 
-The following object is masked from 'package:stats':
+The following object is masked from ‘package:stats’:
 
     confint
 
-The following object is masked from 'package:base':
+The following object is masked from ‘package:base’:
 
     norm
 
@@ -180,7 +167,6 @@
 > 
 > flush(stderr()); flush(stdout())
 > 
-> base::assign(".ptime", proc.time(), pos = "CheckExEnv")
 > ### Name: BetaFamily
 > ### Title: Generating function for Beta families
 > ### Aliases: BetaFamily
@@ -215,7 +201,7 @@
 shape1  1.0000000 -0.6449341
 shape2 -0.6449341  1.0000000
 > checkL2deriv(B1)
-precision of centering:	 3.963281e-05 3.963334e-05 
+precision of centering:	 3.96327e-05 3.963591e-05 
 precision of Fisher information:
               shape1        shape2
 shape1 -1.851068e-05  1.648326e-06
@@ -227,20 +213,17 @@
 condition of Fisher information:
 [1] 5.277691
 $maximum.deviation
-[1] 3.963334e-05
+[1] 3.963591e-05
 
 > 
 > 
 > 
-> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv")
-> base::cat("BetaFamily", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t")
 > cleanEx()
 > nameEx("BiasType-class")
 > ### * BiasType-class
 > 
 > flush(stderr()); flush(stdout())
 > 
-> base::assign(".ptime", proc.time(), pos = "CheckExEnv")
 > ### Name: BiasType-class
 > ### Title: Bias Type
 > ### Aliases: BiasType-class name,BiasType-method name<-,BiasType-method
@@ -254,15 +237,12 @@
 > 
 > 
 > 
-> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv")
-> base::cat("BiasType-class", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t")
 > cleanEx()
 > nameEx("BinomFamily")
 > ### * BinomFamily
 > 
 > flush(stderr()); flush(stdout())
 > 
-> base::assign(".ptime", proc.time(), pos = "CheckExEnv")
 > ### Name: BinomFamily
 > ### Title: Generating function for Binomial families
 > ### Aliases: BinomFamily
@@ -296,13 +276,13 @@
          prob
 prob 133.3333
 > checkL2deriv(B1)
-precision of centering:	 -2.855253e-15 
+precision of centering:	 -1.099042e-15 
 precision of Fisher information:
-              prob
-prob -2.842171e-14
+             prob
+prob 2.842171e-14
 precision of Fisher information - relativ error [%]:
-              prob
-prob -2.131628e-14
+             prob
+prob 2.131628e-14
 condition of Fisher information:
 [1] 1
 $maximum.deviation
@@ -311,15 +291,12 @@
 > 
 > 
 > 
-> base::assign(".dptime", (proc.time() - get(".ptime", pos = "CheckExEnv")), pos = "CheckExEnv")
-> base::cat("BinomFamily", base::get(".format_ptime", pos = 'CheckExEnv')(get(".dptime", pos = "CheckExEnv")), "\n", file=base::get(".ExTimings", pos = 'CheckExEnv'), append=TRUE, sep="\t")
[TRUNCATED]

To get the complete diff run:
    svnlook diff /svnroot/distr -r 1180


More information about the Distr-commits mailing list