[Distr-commits] r793 - in branches/distr-2.4/pkg/distrMod: R man tests/Examples

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Tue Feb 21 00:58:13 CET 2012


Author: stamats
Date: 2012-02-21 00:58:12 +0100 (Tue, 21 Feb 2012)
New Revision: 793

Modified:
   branches/distr-2.4/pkg/distrMod/R/0distrModUtils.R
   branches/distr-2.4/pkg/distrMod/R/SimpleL2ParamFamilies.R
   branches/distr-2.4/pkg/distrMod/R/modifyModel.R
   branches/distr-2.4/pkg/distrMod/man/modifyModel-methods.Rd
   branches/distr-2.4/pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save
Log:
analogous updates as in trunk ... (checked separately)

Modified: branches/distr-2.4/pkg/distrMod/R/0distrModUtils.R
===================================================================
--- branches/distr-2.4/pkg/distrMod/R/0distrModUtils.R	2012-02-20 23:37:31 UTC (rev 792)
+++ branches/distr-2.4/pkg/distrMod/R/0distrModUtils.R	2012-02-20 23:58:12 UTC (rev 793)
@@ -277,12 +277,12 @@
          else  Delta <- function(x) Delta1(x)
          Map.Delta[[i]] <- Delta
          env.i <- environment(Map.Delta[[i]]) <- new.env()
-         assign("i", i, env=env.i)
-         assign("fct", fct, env=env.i)
-         assign("fct0", fct0, env=env.i)
-         assign("Delta", Delta, env=env.i)
-         assign("Delta0", Delta0, env=env.i)
-         assign("Delta1", Delta1, env=env.i)
+         assign("i", i, envir=env.i)
+         assign("fct", fct, envir=env.i)
+         assign("fct0", fct0, envir=env.i)
+         assign("Delta", Delta, envir=env.i)
+         assign("Delta0", Delta0, envir=env.i)
+         assign("Delta1", Delta1, envir=env.i)
          if(withplot){ 
            windows()
            plot(x.seq, sapply(x.seq,Map.Delta[[i]]),
@@ -307,7 +307,7 @@
    for(i in 1:Dim)
        { Map.phi1[[i]] <- function(x) evalRandVar(phi,x)[i] * p(distr)(x)
          env.i <- environment(Map.phi1[[i]]) <- new.env()
-         assign("i", i, env=env.i)
+         assign("i", i, envir=env.i)
          }
 
    phi1 <- EuclRandVariable(Map = Map.phi1, Domain = Reals())
@@ -333,19 +333,19 @@
               
        phi0a <- approxfun(x.mu.seq, phi0, yleft = 0, yright = rev(phi0)[1])
        env.i <- environment(phi1) <- new.env()
-       assign("i", i, env=env.i)
+       assign("i", i, envir=env.i)
        if(is(distr,"DiscreteDistribution"))
              psi0 <- function(x) phi0a(x) * (x %in% support(mu))
        else  psi0 <- function(x) phi0a(x)
 
        Map.psi[[i]] <- psi0
        env.i <- environment(Map.psi[[i]]) <- new.env()
-       assign("i", i, env=env.i)
-       assign("fct", fct, env=env.i)
-       assign("fct0", fct0, env=env.i)
-       assign("psi0", psi0, env=env.i)
-       assign("phi0a", phi0a, env=env.i)
-       assign("phi0", phi0, env=env.i)
+       assign("i", i, envir=env.i)
+       assign("fct", fct, envir=env.i)
+       assign("fct0", fct0, envir=env.i)
+       assign("psi0", psi0, envir=env.i)
+       assign("phi0a", phi0a, envir=env.i)
+       assign("phi0", phi0, envir=env.i)
     }
    psi <-  EuclRandVariable(Map = Map.psi, Domain = Reals())
 

Modified: branches/distr-2.4/pkg/distrMod/R/SimpleL2ParamFamilies.R
===================================================================
--- branches/distr-2.4/pkg/distrMod/R/SimpleL2ParamFamilies.R	2012-02-20 23:37:31 UTC (rev 792)
+++ branches/distr-2.4/pkg/distrMod/R/SimpleL2ParamFamilies.R	2012-02-20 23:58:12 UTC (rev 793)
@@ -215,7 +215,7 @@
                    prob <- main(param)["prob"]
                    size <- main(param)["size"]
                    xn <- 0:min(max(support(distribution)),
-                               qnbinom(1e-6,size=size,prob=prob,lower=FALSE),
+                               qnbinom(1e-6,size=size,prob=prob,lower.tail=FALSE),
                                1e5)
                    I11 <- -sum((trigamma(xn+size)-trigamma(size))*dnbinom(xn,size=size,prob=prob))
                    I12 <- -1/prob
@@ -299,7 +299,7 @@
                    size <- main(param)["size"]
                    prob.0 <- size/(size+mean)
                    xn <- 0:min(max(support(distribution)),
-                               qnbinom(1e-6,size=size,prob=prob.0,lower=FALSE),
+                               qnbinom(1e-6,size=size,prob=prob.0,lower.tail=FALSE),
                                1e5)
                    I11 <- -sum((trigamma(xn+size)-trigamma(size))*dnbinom(xn,size=size,prob=prob.0))
                    I12 <- -1/prob.0
@@ -694,7 +694,7 @@
                                             EvenSymmetric(SymmCenter = loc)),
                   L2derivDistrSymm = DistrSymmList(SphericalSymmetry(), 
                                                    NoSymmetry()),
-                  L2derivDistr = UnivarDistrList(Arcsine(),abs(Arcsine())),
+                  L2derivDistr.0 = UnivarDistrList(Arcsine(),abs(Arcsine())),
                   FisherInfo.0 = matrix(c(1,0,0,1)/2,2,2, 
                                            dimnames = list(c("loc","scale"),
                                                            c("loc","scale"))),

Modified: branches/distr-2.4/pkg/distrMod/R/modifyModel.R
===================================================================
--- branches/distr-2.4/pkg/distrMod/R/modifyModel.R	2012-02-20 23:37:31 UTC (rev 792)
+++ branches/distr-2.4/pkg/distrMod/R/modifyModel.R	2012-02-20 23:58:12 UTC (rev 793)
@@ -1,4 +1,52 @@
 ### move model from one parameter to the next...
+setMethod("modifyModel", signature(model = "ParamFamily", param = "ParamFamParameter"),
+          function(model, param, .withCall = TRUE, ...){
+          M <- model
+          theta <- c(main(param),nuisance(param))
+          M at distribution <- model at modifyParam(theta)
+          M at param <- param
+          #we loose symmetry if available ...
+          M at distrSymm <- NoSymmetry()
+          
+          if(paste(M at fam.call[1]) == "ParamFamily")
+             fam.call <- eval(substitute(
+                      call("ParamFamily",
+                              name = name0,
+                              distribution = distribution0,
+                              distrSymm = distrSymm0,
+                              param = param0,
+                              props = props0,
+                              startPar = startPar0,
+                              makeOKPar = makeOKPar0,
+                              modifyParam = modifyParam0,
+                           ),
+                      list(   name0 = M at name,
+                              distribution0 = M at distribution,
+                              distrSymm0 = M at distrSymm,
+                              param0 = M at param,
+                              props0 = M at props,
+                              startPar0 = M at startPar,
+                              makeOKPar0 = M at startPar,
+                              modifyParam0 = M at modifyParam,
+                          )
+                      ))
+          else{
+             fam.call <- model at fam.call
+             par.names <- names(theta)
+             call.n <- names(fam.call)
+             w <- which(call.n %in% par.names)
+             if(length(w))
+                fam.call <- fam.call[-w]
+             fam.call <-  as.call(c(as.list(fam.call),theta))
+          }
+
+          M at fam.call <- fam.call
+          class(M) <- class(model)
+          return(M)
+          })
+
+
+### move model from one parameter to the next...
 setMethod("modifyModel", signature(model = "L2ParamFamily", param = "ParamFamParameter"),
           function(model, param, .withCall = TRUE, .withL2derivDistr = TRUE,
                    ...){

Modified: branches/distr-2.4/pkg/distrMod/man/modifyModel-methods.Rd
===================================================================
--- branches/distr-2.4/pkg/distrMod/man/modifyModel-methods.Rd	2012-02-20 23:37:31 UTC (rev 792)
+++ branches/distr-2.4/pkg/distrMod/man/modifyModel-methods.Rd	2012-02-20 23:58:12 UTC (rev 793)
@@ -2,6 +2,7 @@
 \docType{methods}
 \alias{modifyModel-methods}
 \alias{modifyModel}
+\alias{modifyModel,ParamFamily,ParamFamParameter-method}
 \alias{modifyModel,L2ParamFamily,ParamFamParameter-method}
 \alias{modifyModel,L2LocationFamily,ParamFamParameter-method}
 \alias{modifyModel,L2ScaleFamily,ParamFamParameter-method}
@@ -16,6 +17,8 @@
  }
 \usage{
 modifyModel(model, param,...)
+\S4method{modifyModel}{ParamFamily,ParamFamParameter}(model,param, 
+                       .withCall = TRUE, ...)
 \S4method{modifyModel}{L2ParamFamily,ParamFamParameter}(model,param, 
                        .withCall = TRUE, .withL2derivDistr = TRUE, ...)
 \S4method{modifyModel}{L2LocationFamily,ParamFamParameter}(model,param, ...)
@@ -26,7 +29,7 @@
 \S4method{modifyModel}{ExpScaleFamily,ParamFamParameter}(model,param, ...)
 }
 \arguments{
-  \item{model}{an object of class \code{L2ParamFamily}  --- the model to move.}
+  \item{model}{an object of class \code{ParamFamily}  --- the model to move.}
   \item{param}{an object of class \code{ParamFamParameter} --- the parameter to move to.}
   \item{.withCall}{logical: shall slot \code{fam.call} be updated?}
   \item{.withL2derivDistr}{logical: shall slot \code{L2derivDistr} be updated?}

Modified: branches/distr-2.4/pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save
===================================================================
--- branches/distr-2.4/pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save	2012-02-20 23:37:31 UTC (rev 792)
+++ branches/distr-2.4/pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save	2012-02-20 23:58:12 UTC (rev 793)
@@ -1,7 +1,8 @@
 
-R version 2.10.0 beta (2009-10-15 r50107)
-Copyright (C) 2009 The R Foundation for Statistical Computing
+R version 2.14.2 beta (2012-02-20 r58436)
+Copyright (C) 2012 The R Foundation for Statistical Computing
 ISBN 3-900051-07-0
+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.
@@ -17,77 +18,12 @@
 'help.start()' for an HTML browser interface to help.
 Type 'q()' to quit R.
 
-> ### * <HEADER>
-> ###
-> attach(NULL, name = "CheckExEnv")
-> assign("nameEx",
-+        local({
-+ 	   s <- "__{must remake R-ex/*.R}__"
-+            function(new) {
-+                if(!missing(new)) s <<- new else s
-+            }
-+        }),
-+        pos = "CheckExEnv")
-> ## Add some hooks to label plot pages for base and grid graphics
-> assign("base_plot_hook",
-+        function() {
-+            pp <- par(c("mfg","mfcol","oma","mar"))
-+            if(all(pp$mfg[1:2] == c(1, pp$mfcol[2]))) {
-+                outer <- (oma4 <- pp$oma[4]) > 0; mar4 <- pp$mar[4]
-+                mtext(sprintf("help(\"%s\")", nameEx()), side = 4,
-+                      line = if(outer)max(1, oma4 - 1) else min(1, mar4 - 1),
-+                outer = outer, adj = 1, cex = .8, col = "orchid", las=3)
-+            }
-+        },
-+        pos = "CheckExEnv")
-> assign("grid_plot_hook",
-+        function() {
-+            grid::pushViewport(grid::viewport(width=grid::unit(1, "npc") -
-+                               grid::unit(1, "lines"), x=0, just="left"))
-+            grid::grid.text(sprintf("help(\"%s\")", nameEx()),
-+                            x=grid::unit(1, "npc") + grid::unit(0.5, "lines"),
-+                            y=grid::unit(0.8, "npc"), rot=90,
-+                            gp=grid::gpar(col="orchid"))
-+        },
-+        pos = "CheckExEnv")
-> setHook("plot.new",     get("base_plot_hook", pos = "CheckExEnv"))
-> setHook("persp",        get("base_plot_hook", pos = "CheckExEnv"))
-> setHook("grid.newpage", get("grid_plot_hook", pos = "CheckExEnv"))
-> assign("cleanEx",
-+        function(env = .GlobalEnv) {
-+ 	   rm(list = ls(envir = env, all.names = TRUE), envir = env)
-+            RNGkind("default", "default")
-+ 	   set.seed(1)
-+    	   options(warn = 1)
-+ 	   .CheckExEnv <- as.environment("CheckExEnv")
-+ 	   delayedAssign("T", stop("T used instead of TRUE"),
-+ 		  assign.env = .CheckExEnv)
-+ 	   delayedAssign("F", stop("F used instead of FALSE"),
-+ 		  assign.env = .CheckExEnv)
-+ 	   sch <- search()
-+ 	   newitems <- sch[! sch %in% .oldSearch]
-+ 	   for(item in rev(newitems))
-+                eval(substitute(detach(item), list(item=item)))
-+ 	   missitems <- .oldSearch[! .oldSearch %in% sch]
-+ 	   if(length(missitems))
-+ 	       warning("items ", paste(missitems, collapse=", "),
-+ 		       " have been removed from the search path")
-+        },
-+        pos = "CheckExEnv")
-> assign("ptime", proc.time(), pos = "CheckExEnv")
-> ## at least one package changes these via ps.options(), so do this
-> ## before loading the package.
-> ## Use postscript as incomplete files may be viewable, unlike PDF.
-> ## Choose a size that is close to on-screen devices, fix paper
-> grDevices::ps.options(width = 7, height = 7, paper = "a4", reset = TRUE)
-> grDevices::postscript("distrMod-Ex.ps")
-> 
-> assign("par.postscript", graphics::par(no.readonly = TRUE), pos = "CheckExEnv")
-> options(contrasts = c(unordered = "contr.treatment", ordered = "contr.poly"))
+> pkgname <- "distrMod"
+> source(file.path(R.home("share"), "R", "examples-header.R"))
 > options(warn = 1)
 > library('distrMod')
 Loading required package: startupmsg
-:startupmsg>  Utilities for start-up messages (version 0.7)
+:startupmsg>  Utilities for start-up messages (version 0.7.3)
 :startupmsg> 
 :startupmsg>  For more information see ?"startupmsg",
 :startupmsg>  NEWS("startupmsg")
@@ -96,7 +32,8 @@
 Loading required package: sfsmisc
 Loading required package: SweaveListingUtils
 :SweaveListingUtils>  Utilities for Sweave together with
-:SweaveListingUtils>  TeX listings package (version 0.4)
+:SweaveListingUtils>  TeX listings package (version
+:SweaveListingUtils>  0.5.5)
 :SweaveListingUtils> 
 :SweaveListingUtils>  Some functions from package 'base'
 :SweaveListingUtils>  are intentionally masked ---see
@@ -115,16 +52,14 @@
 :SweaveListingUtils>  vignette("ExampleSweaveListingUtils").
 
 
-Attaching package: 'SweaveListingUtils'
+Attaching package: ‘SweaveListingUtils’
 
+The following object(s) are masked from ‘package:base’:
 
-	The following object(s) are masked from package:base :
+    library, require
 
-	 library,
-	 require 
-
-:distr>  Object orientated implementation of distributions (version
-:distr>  2.2)
+:distr>  Object oriented implementation of distributions (version
+:distr>  2.3.4)
 :distr> 
 :distr>  Attention: Arithmetics on distribution objects are
 :distr>  understood as operations on corresponding random variables
@@ -143,27 +78,23 @@
 :distr>  vignette("distr").
 
 
-Attaching package: 'distr'
+Attaching package: ‘distr’
 
+The following object(s) are masked from ‘package:stats’:
 
-	The following object(s) are masked from package:stats :
+    df, qqplot, sd
 
-	 df,
-	 qqplot,
-	 sd 
-
 Loading required package: distrEx
 Loading required package: evd
 Loading required package: actuar
 
-Attaching package: 'actuar'
+Attaching package: ‘actuar’
 
+The following object(s) are masked from ‘package:grDevices’:
 
-	The following object(s) are masked from package:grDevices :
+    cm
 
-	 cm 
-
-:distrEx>  Extensions of package distr (version 2.2)
+:distrEx>  Extensions of package distr (version 2.3.2)
 :distrEx> 
 :distrEx>  Note: Packages "e1071", "moments", "fBasics" should be
 :distrEx>  attached /before/ package "distrEx". See distrExMASK().
@@ -176,18 +107,14 @@
 :distrEx>  vignette("distr").
 
 
-Attaching package: 'distrEx'
+Attaching package: ‘distrEx’
 
+The following object(s) are masked from ‘package:stats’:
 
-	The following object(s) are masked from package:stats :
+    IQR, mad, median, var
 
-	 IQR,
-	 mad,
-	 median,
-	 var 
-
 Loading required package: RandVar
-:RandVar>  Implementation of random variables (version 0.7)
+:RandVar>  Implementation of random variables (version 0.8.1)
 :RandVar> 
 :RandVar>  For more information see ?"RandVar", NEWS("RandVar"), as
 :RandVar>  well as
@@ -197,8 +124,8 @@
 
 Loading required package: MASS
 Loading required package: stats4
-:distrMod>  Object orientated implementation of probability models
-:distrMod>  (version 2.2)
+:distrMod>  Object oriented implementation of probability models
+:distrMod>  (version 2.4)
 :distrMod> 
 :distrMod>  Some functions from pkg's 'base' and 'stats' are
 :distrMod>  intentionally masked ---see distrModMASK().
@@ -209,27 +136,32 @@
 :distrMod>  For more information see ?"distrMod",
 :distrMod>  NEWS("distrMod"), as well as
 :distrMod>    http://distr.r-forge.r-project.org/
-:distrMod>  Package "distrDoc" provides a vignette to this package
+:distrMod>  There is a vignette to this package; try
+:distrMod>  vignette("distrMod").
+:distrMod>  Package "distrDoc" provides a vignette to the other
+:distrMod>  distrXXX packages,
 :distrMod>  as well as to several related packages; try
 :distrMod>  vignette("distr").
 
 
-Attaching package: 'distrMod'
+Attaching package: ‘distrMod’
 
+The following object(s) are masked from ‘package:stats4’:
 
-	The following object(s) are masked from package:stats4 :
+    confint
 
-	 confint 
+The following object(s) are masked from ‘package:stats’:
 
+    confint
 
-	The following object(s) are masked from package:stats :
+The following object(s) are masked from ‘package:base’:
 
-	 confint 
+    norm
 
 > 
 > assign(".oldSearch", search(), pos = 'CheckExEnv')
-> assign(".oldNS", loadedNamespaces(), pos = 'CheckExEnv')
-> cleanEx(); nameEx("BetaFamily")
+> cleanEx()
+> nameEx("BetaFamily")
 > ### * BetaFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -263,7 +195,7 @@
 [1] "The Beta family is invariant in the following sense"
 [2] "if (x_i)~Beta(s1,s2) then (1-x_i)~Beta(s2,s1)"      
 > FisherInfo(B1)
-An object of class “PosSemDefSymmMatrix”
+An object of class "PosSemDefSymmMatrix"
            shape1     shape2
 shape1  1.0000000 -0.6449341
 shape2 -0.6449341  1.0000000
@@ -279,7 +211,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("BiasType-class")
+> cleanEx()
+> nameEx("BiasType-class")
 > ### * BiasType-class
 > 
 > flush(stderr()); flush(stdout())
@@ -297,7 +230,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("BinomFamily")
+> cleanEx()
+> nameEx("BinomFamily")
 > ### * BinomFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -331,7 +265,7 @@
 [2] "i.e., d(Binom(size, prob))(k)=d(Binom(size,1-prob))(size-k)" 
 > plot(B1)
 > FisherInfo(B1)
-An object of class “PosSemDefSymmMatrix”
+An object of class "PosSemDefSymmMatrix"
          prob
 prob 133.3333
 > checkL2deriv(B1)
@@ -345,7 +279,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("CauchyLocationScaleFamily")
+> cleanEx()
+> nameEx("CauchyLocationScaleFamily")
 > ### * CauchyLocationScaleFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -380,7 +315,7 @@
 [3] "with location parameter 'loc' and scale parameter 'scale'"
 > plot(C1)
 > FisherInfo(C1)
-An object of class “PosDefSymmMatrix”
+An object of class "PosDefSymmMatrix"
       loc scale
 loc   0.5   0.0
 scale 0.0   0.5
@@ -399,7 +334,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("Confint-class")
+> cleanEx()
+> nameEx("Confint-class")
 > ### * Confint-class
 > 
 > flush(stderr()); flush(stdout())
@@ -457,9 +393,9 @@
     list(fval = fval0, mat = mat0)
 }
 Trafo / derivative matrix at which estimate was produced:
-      scale shape
-shape  0.00     1
-rate  -8.55     0
+       scale shape
+shape  0.000     1
+rate  -8.549     0
 > print(ci, digits = 4, show.details="medium")
 A[n] asymptotic (CLT-based) confidence interval:
       2.5 % 97.5 %
@@ -477,7 +413,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("Estimate-class")
+> cleanEx()
+> nameEx("Estimate-class")
 > ### * Estimate-class
 > 
 > flush(stderr()); flush(stdout())
@@ -519,7 +456,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("Estimator")
+> cleanEx()
+> nameEx("Estimator")
 > ### * Estimator
 > 
 > flush(stderr()); flush(stdout())
@@ -555,7 +493,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("EvenSymmetric-class")
+> cleanEx()
+> nameEx("EvenSymmetric-class")
 > ### * EvenSymmetric-class
 > 
 > flush(stderr()); flush(stdout())
@@ -574,7 +513,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("EvenSymmetric")
+> cleanEx()
+> nameEx("EvenSymmetric")
 > ### * EvenSymmetric
 > 
 > flush(stderr()); flush(stdout())
@@ -602,7 +542,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("ExpScaleFamily")
+> cleanEx()
+> nameEx("ExpScaleFamily")
 > ### * ExpScaleFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -642,10 +583,10 @@
 {
     ((x - 0)/1 * LogDeriv((x - 0)/1) - 1)/1
 }
-<environment: 0x7f7e928>
+<environment: 0x6fe53e8>
 
 > checkL2deriv(E1)
-precision of centering:	 -1.511810e-06 
+precision of centering:	 -1.51181e-06 
 precision of Fisher information:
              scale
 scale -2.61793e-05
@@ -655,7 +596,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("FunSymmList-class")
+> cleanEx()
+> nameEx("FunSymmList-class")
 > ### * FunSymmList-class
 > 
 > flush(stderr()); flush(stdout())
@@ -669,7 +611,7 @@
 > 
 > new("FunSymmList", list(NonSymmetric(), EvenSymmetric(SymmCenter = 1), 
 +                         OddSymmetric(SymmCenter = 2)))
-An object of class “FunSymmList”
+An object of class "FunSymmList"
 [[1]]
 type of symmetry:	non-symmetric function
 NULL
@@ -687,7 +629,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("FunSymmList")
+> cleanEx()
+> nameEx("FunSymmList")
 > ### * FunSymmList
 > 
 > flush(stderr()); flush(stdout())
@@ -701,7 +644,7 @@
 > 
 > FunSymmList(NonSymmetric(), EvenSymmetric(SymmCenter = 1), 
 +             OddSymmetric(SymmCenter = 2))
-An object of class “FunSymmList”
+An object of class "FunSymmList"
 [[1]]
 type of symmetry:	non-symmetric function
 NULL
@@ -728,7 +671,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("GammaFamily")
+> cleanEx()
+> nameEx("GammaFamily")
 > ### * GammaFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -761,12 +705,12 @@
 [1] "The Gamma family is scale invariant via the parametrization"
 [2] "'(nu,shape)=(log(scale),shape)'"                            
 > FisherInfo(G1)
-An object of class “PosSemDefSymmMatrix”
+An object of class "PosSemDefSymmMatrix"
       scale    shape
 scale     1 1.000000
 shape     1 1.644934
 > checkL2deriv(G1)
-precision of centering:	 -1.511810e-06 1.312514e-06 
+precision of centering:	 -1.51181e-06 1.312514e-06 
 precision of Fisher information:
               scale         shape
 scale -2.617930e-05 -7.165188e-06
@@ -777,7 +721,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("GumbelLocationFamily")
+> cleanEx()
+> nameEx("GumbelLocationFamily")
 > ### * GumbelLocationFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -815,10 +760,10 @@
 {
     LogDeriv(x - 0)
 }
-<environment: 0x85ba170>
+<environment: 0x237d900>
 
 > checkL2deriv(G1)
-precision of centering:	 1.511810e-06 
+precision of centering:	 1.51181e-06 
 precision of Fisher information:
              loc
 loc -2.61793e-05
@@ -828,7 +773,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("InfoNorm")
+> cleanEx()
+> nameEx("InfoNorm")
 > ### * InfoNorm
 > 
 > flush(stderr()); flush(stdout())
@@ -841,9 +787,9 @@
 > ### ** Examples
 > 
 > InfoNorm()
-An object of class “InfoNorm”
+An object of class "InfoNorm"
 Slot "QuadForm":
-An object of class “PosSemDefSymmMatrix”
+An object of class "PosSemDefSymmMatrix"
      [,1]
 [1,]    1
 
@@ -853,7 +799,8 @@
 Slot "fct":
 function (x) 
 QuadFormNorm(x, A = A)
-<environment: 0x7e98768>
+<bytecode: 0x7971630>
+<environment: 0x7970930>
 
 > 
 > ## The function is currently defined as
@@ -865,7 +812,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("L2GroupFamily-class")
+> cleanEx()
+> nameEx("L2GroupFamily-class")
 > ### * L2GroupFamily-class
 > 
 > flush(stderr()); flush(stdout())
@@ -884,7 +832,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("L2LocationFamily-class")
+> cleanEx()
+> nameEx("L2LocationFamily-class")
 > ### * L2LocationFamily-class
 > 
 > flush(stderr()); flush(stdout())
@@ -901,7 +850,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("L2LocationFamily")
+> cleanEx()
+> nameEx("L2LocationFamily")
 > ### * L2LocationFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -918,7 +868,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("L2LocationScaleFamily-class")
+> cleanEx()
+> nameEx("L2LocationScaleFamily-class")
 > ### * L2LocationScaleFamily-class
 > 
 > flush(stderr()); flush(stdout())
@@ -935,7 +886,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("L2LocationScaleFamily")
+> cleanEx()
+> nameEx("L2LocationScaleFamily")
 > ### * L2LocationScaleFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -952,7 +904,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("L2LocationUnknownScaleFamily")
+> cleanEx()
+> nameEx("L2LocationUnknownScaleFamily")
 > ### * L2LocationUnknownScaleFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -970,7 +923,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("L2ParamFamily-class")
+> cleanEx()
+> nameEx("L2ParamFamily-class")
 > ### * L2ParamFamily-class
 > 
 > flush(stderr()); flush(stdout())
@@ -1007,7 +961,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("L2ParamFamily")
+> cleanEx()
+> nameEx("L2ParamFamily")
 > ### * L2ParamFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -1024,7 +979,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("L2ScaleFamily-class")
+> cleanEx()
+> nameEx("L2ScaleFamily-class")
 > ### * L2ScaleFamily-class
 > 
 > flush(stderr()); flush(stdout())
@@ -1041,7 +997,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("L2ScaleFamily")
+> cleanEx()
+> nameEx("L2ScaleFamily")
 > ### * L2ScaleFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -1058,7 +1015,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("L2ScaleUnknownLocationFamily")
+> cleanEx()
+> nameEx("L2ScaleUnknownLocationFamily")
 > ### * L2ScaleUnknownLocationFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -1076,7 +1034,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("LnormScaleFamily")
+> cleanEx()
+> nameEx("LnormScaleFamily")
 > ### * LnormScaleFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -1119,7 +1078,7 @@
 {
     ((x - 0)/1 * LogDeriv((x - 0)/1) - 1)/1
 }
-<environment: 0x8275218>
+<environment: 0x9d15510>
 
 > checkL2deriv(L1)
 precision of centering:	 -0.003003394 
@@ -1132,7 +1091,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("MCEstimate-class")
+> cleanEx()
+> nameEx("MCEstimate-class")
 > ### * MCEstimate-class
 > 
 > flush(stderr()); flush(stdout())
@@ -1193,7 +1153,8 @@
 > 
 > 
 > graphics::par(get("par.postscript", pos = 'CheckExEnv'))
-> cleanEx(); nameEx("MCEstimator")
+> cleanEx()
+> nameEx("MCEstimator")
 > ### * MCEstimator
 > 
 > flush(stderr()); flush(stdout())
@@ -1320,7 +1281,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("MDEstimator")
+> cleanEx()
+> nameEx("MDEstimator")
 > ### * MDEstimator
 > 
 > flush(stderr()); flush(stdout())
@@ -1363,10 +1325,10 @@
 samplesize:   50
 estimate:
     scale     shape 
-0.3296938 4.2907460 
+0.3419487 4.1663559 
 Criterion:
 CvM distance 
-  0.02872404 
+  0.02879881 
 > 
 > ## von Mises minimum distance estimator with default mu
 > MDEstimator(x = x, ParamFamily = G, distance = CvMDist,
@@ -1379,15 +1341,15 @@
 samplesize:   50
 estimate:
      scale        shape   
-  0.32969378   4.29074603 
- (0.08369777) (1.03063291)
+  0.34194869   4.16635591 
+ (0.08687677) (0.99985006)
 asymptotic (co)variance (multiplied with samplesize):
            scale     shape
-scale  0.3502659 -4.007671
-shape -4.0076714 53.110210
+scale  0.3773787 -4.026502
+shape -4.0265023 49.985008
 Criterion:
 CvM distance 
-  0.02872404 
+  0.02879881 
 > #*** variance routine is still in testing phase so not yet
 > #*** exported to namespace
 > ## von Mises minimum distance estimator with mu = N(0,1)
@@ -1400,10 +1362,10 @@
 samplesize:   50
 estimate:
     scale     shape 
-0.3543892 4.0587606 
+0.3407495 4.2127808 
 Criterion:
 CvM distance 
-  0.01586171 
+  0.01574483 
 > 
 > ## Total variation minimum distance estimator
 > ## gamma distributions are discretized
@@ -1446,7 +1408,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("MLEstimator")
+> cleanEx()
+> nameEx("MLEstimator")
 > ### * MLEstimator
 > 
 > flush(stderr()); flush(stdout())
@@ -1592,8 +1555,8 @@
 > require(MASS)
 > (res1 <- fitdistr(x, "gamma"))
      shape       rate   
-  3.0117832   1.8655645 
- (0.5721423) (0.3856279)
+  3.0117885   1.8655681 
+ (0.5721425) (0.3856279)
 > 
 > ## comparison
 > ## shape
@@ -1636,8 +1599,8 @@
 > distrModoptions("show.details" = "minimal")
 > res1
      shape       rate   
-  3.0117832   1.8655645 
- (0.5721423) (0.3856279)
+  3.0117885   1.8655681 
+ (0.5721425) (0.3856279)
 > res2
 Evaluations of Maximum likelihood estimate:
 -------------------------------------------
@@ -1694,7 +1657,114 @@
 > 
 > 
 > graphics::par(get("par.postscript", pos = 'CheckExEnv'))
-> cleanEx(); nameEx("NonSymmetric-class")
+> cleanEx()
+> nameEx("NBinomFamily")
+> ### * NBinomFamily
+> 
+> flush(stderr()); flush(stdout())
+> 
+> ### Name: NbinomFamily
+> ### Title: Generating function for Nbinomial families
+> ### Aliases: NbinomFamily NbinomwithSizeFamily NbinomMeanSizeFamily
+> ### Keywords: models
+> 
+> ### ** Examples
+> 
+> (N1 <- NbinomFamily(size = 25, prob = 0.25))
+An object of class "NbinomFamily"
+### name:	Negative Binomial family
+
+### distribution:	Distribution Object of Class: Nbinom
+ size: 25
+ prob: 0.25
+
+### param:	An object of class "ParamFamParameter"
+name:	probability of success
+prob:	0.25
+fixed part of param.:
+	size:	25
+
+### props:
+[1] ""
+> plot(N1)
+> FisherInfo(N1)
+An object of class "PosSemDefSymmMatrix"
+         prob
+prob 533.3333
+> checkL2deriv(N1)
+precision of centering:	 0.001177892 
+precision of Fisher information:
+           prob
+prob -0.1601189
+$maximum.deviation
+[1] 0.1601189
+
+> (N1.w <- NbinomwithSizeFamily(size = 25, prob = 0.25))
+An object of class "NbinomwithSizeFamily"
+### name:	Negative Binomial family
+
+### distribution:	Distribution Object of Class: Nbinom
+ size: 25
+ prob: 0.25
+
+### param:	An object of class "ParamFamParameter"
+name:	NegBinomParameter
+size:	25
+prob:	0.25
+
+### props:
+[1] ""
+> plot(N1.w)
+> FisherInfo(N1.w)
+An object of class "PosSemDefSymmMatrix"
+            size     prob
+size  0.03044946  -4.0000
+prob -4.00000000 533.3333
+> checkL2deriv(N1.w)
+precision of centering:	 -6.245978e-06 0.001177892 
+precision of Fisher information:
+              size          prob
+size -4.182531e-06  0.0008481424
+prob  8.481424e-04 -0.1601189384
+$maximum.deviation
+[1] 0.1601189
+
+> (N2.w <- NbinomMeanSizeFamily(size = 25, mean = 75))
+An object of class "NbinomMeanSizeFamily"
+### name:	Negative Binomial family
+
+### distribution:	Distribution Object of Class: Nbinom
+ size: 25
+ prob: 0.25
+
+### param:	An object of class "ParamFamParameter"
+name:	probability of success
+size:	25
+mean:	75
+
+### props:
+[1] ""
+> plot(N2.w)
+> FisherInfo(N2.w)
+An object of class "PosSemDefSymmMatrix"
+             size         mean
+size 3.044946e-02     1600.091
+mean 1.600091e+03 85342933.607
+> checkL2deriv(N2.w)
+precision of centering:	 -6.245978e-06 -0.4711755 
+precision of Fisher information:
+              size          mean
+size -4.182531e-06 -3.392695e-01
+mean -3.392695e-01 -2.562107e+04
+$maximum.deviation
+[1] 25621.07
+
+> 
+> 
+> 
+> 
+> cleanEx()
+> nameEx("NonSymmetric-class")
 > ### * NonSymmetric-class
 > 
 > flush(stderr()); flush(stdout())
@@ -1712,7 +1782,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("NonSymmetric")
+> cleanEx()
+> nameEx("NonSymmetric")
 > ### * NonSymmetric
 > 
 > flush(stderr()); flush(stdout())
@@ -1737,7 +1808,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("NormLocationFamily")
+> cleanEx()
+> nameEx("NormLocationFamily")
 > ### * NormLocationFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -1777,7 +1849,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("NormLocationScaleFamily")
+> cleanEx()
+> nameEx("NormLocationScaleFamily")
 > ### * NormLocationScaleFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -1811,7 +1884,7 @@
 [3] "with location parameter 'loc' and scale parameter 'scale'"
 > plot(N1)
 > FisherInfo(N1)
-An object of class “PosDefSymmMatrix”
+An object of class "PosDefSymmMatrix"
      mean sd
 mean    1  0
 sd      0  2
@@ -1827,7 +1900,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("NormLocationUnknownScaleFamily")
+> cleanEx()
+> nameEx("NormLocationUnknownScaleFamily")
 > ### * NormLocationUnknownScaleFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -1863,7 +1937,7 @@
 [3] "with location parameter 'loc' and scale parameter 'scale'"                     
 > plot(N1)
 > FisherInfo(N1)
-An object of class “PosDefSymmMatrix”
+An object of class "PosDefSymmMatrix"
      mean sd
 mean    1  0
 sd      0  2
@@ -1879,7 +1953,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("NormScaleFamily")
+> cleanEx()
+> nameEx("NormScaleFamily")
 > ### * NormScaleFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -1914,7 +1989,7 @@
 [3] "with scale parameter 'scale'"                 
 > plot(N1)
 > FisherInfo(N1)
-An object of class “PosDefSymmMatrix”
+An object of class "PosDefSymmMatrix"
    sd
 sd  2
 > checkL2deriv(N1)
@@ -1928,7 +2003,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("NormScaleUnknownLocationFamily")
+> cleanEx()
+> nameEx("NormScaleUnknownLocationFamily")
 > ### * NormScaleUnknownLocationFamily
 > 
 > flush(stderr()); flush(stdout())
@@ -1964,7 +2040,7 @@
 [3] "with location parameter 'loc' and scale parameter 'scale'"                     
 > plot(N1)
 > FisherInfo(N1)
-An object of class “PosDefSymmMatrix”
+An object of class "PosDefSymmMatrix"
      sd mean
 sd    1    0
 mean  0    2
@@ -1980,7 +2056,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("NormType-class")
+> cleanEx()
+> nameEx("NormType-class")
 > ### * NormType-class
 > 
 > flush(stderr()); flush(stdout())
@@ -2001,13 +2078,15 @@
         return(abs(x))
     else return(sqrt(colSums(x^2)))
 }
+<bytecode: 0x72c71b8>
 <environment: namespace:distrMod>
 > name(EuclNorm)
 [1] "EuclideanNorm"
 > 
 > 
 > 
-> cleanEx(); nameEx("NormType")
+> cleanEx()
+> nameEx("NormType")
 > ### * NormType
 > 
 > flush(stderr()); flush(stdout())
@@ -2020,7 +2099,7 @@
 > ### ** Examples
 > 
 > NormType()
-An object of class “NormType”
+An object of class "NormType"
 Slot "name":
 [1] "EuclideanNorm"
 
@@ -2031,12 +2110,14 @@
         return(abs(x))
     else return(sqrt(colSums(x^2)))
 }
+<bytecode: 0x72c71b8>
 <environment: namespace:distrMod>
 
 > 
 > 
 > 
-> cleanEx(); nameEx("OddSymmetric-class")
+> cleanEx()
+> nameEx("OddSymmetric-class")
 > ### * OddSymmetric-class
 > 
 > flush(stderr()); flush(stdout())
@@ -2055,7 +2136,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("OddSymmetric")
+> cleanEx()
+> nameEx("OddSymmetric")
 > ### * OddSymmetric
 > 
 > flush(stderr()); flush(stdout())
@@ -2083,7 +2165,8 @@
 > 
 > 
 > 
-> cleanEx(); nameEx("ParamFamParameter-class")
+> cleanEx()
+> nameEx("ParamFamParameter-class")
 > ### * ParamFamParameter-class
 > 
[TRUNCATED]

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


More information about the Distr-commits mailing list