[Distr-commits] r1357 - branches/distr-2.9/pkg/distrMod/R branches/distr-2.9/pkg/distrMod/inst branches/distr-2.9/pkg/distrMod/man branches/distr-2.9/pkg/distrMod/tests/Examples pkg/distrMod pkg/distrMod/R pkg/distrMod/inst pkg/distrMod/man pkg/distrMod/tests/Examples pkg/utils www

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Fri Mar 6 22:11:19 CET 2020


Author: ruckdeschel
Date: 2020-03-06 22:11:18 +0100 (Fri, 06 Mar 2020)
New Revision: 1357

Modified:
   branches/distr-2.9/pkg/distrMod/R/mleCalc-methods.R
   branches/distr-2.9/pkg/distrMod/R/setAs.R
   branches/distr-2.9/pkg/distrMod/inst/NEWS
   branches/distr-2.9/pkg/distrMod/man/MLEstimator.Rd
   branches/distr-2.9/pkg/distrMod/man/internalmleHelpers.Rd
   branches/distr-2.9/pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save
   pkg/distrMod/DESCRIPTION
   pkg/distrMod/R/mleCalc-methods.R
   pkg/distrMod/R/setAs.R
   pkg/distrMod/inst/NEWS
   pkg/distrMod/man/0distrMod-package.Rd
   pkg/distrMod/man/MLEstimator.Rd
   pkg/distrMod/man/internalmleHelpers.Rd
   pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save
   pkg/utils/DESCRIPTIONutilsExamples.R
   www/distrMod.html
Log:
[distrMod] branch 2.9 and trunk: 
+ adapted S4-method setAs to coerce from MCEstimate to class stats4::mle after stats::mle4 
  changed its slot structure


Modified: branches/distr-2.9/pkg/distrMod/R/mleCalc-methods.R
===================================================================
--- branches/distr-2.9/pkg/distrMod/R/mleCalc-methods.R	2020-02-01 09:06:07 UTC (rev 1356)
+++ branches/distr-2.9/pkg/distrMod/R/mleCalc-methods.R	2020-03-06 21:11:18 UTC (rev 1357)
@@ -120,7 +120,7 @@
        filterDots <- function(dots){
           if(length(dots)){
                dotsOptIz <- NULL
-               nfmlsOptiz <- NULL
+               nfmlsOptIz <- NULL
 
                dotsNames <- names(dots)
                if(length(param(PFam)) == 1){
@@ -260,7 +260,7 @@
                else  names(theta) <- names(main(ParamFamily))
                distr.new <- ParamFamily at modifyParam(theta)
                crit1 <- do.call(criterion, c(list(Data, distr.new),
-                                dotsToPass$dotsCrit))
+                                dotsTP$dotsCrit))
                return(crit1)}
 
     crit.fct <- get.criterion.fct(theta, Data = x, ParamFam = PFam,

Modified: branches/distr-2.9/pkg/distrMod/R/setAs.R
===================================================================
--- branches/distr-2.9/pkg/distrMod/R/setAs.R	2020-02-01 09:06:07 UTC (rev 1356)
+++ branches/distr-2.9/pkg/distrMod/R/setAs.R	2020-03-06 21:11:18 UTC (rev 1357)
@@ -55,14 +55,16 @@
       to at call <- substitute(mle(minuslogl = crit.f, start = startPar), 
                             list(crit.f = crit.f0,
                                  startPar = start.f0))
-      to at coef <- from at estimate
-      fe <- if(is.null(from at untransformed.estimate))
-               from at estimate else from at untransformed.estimate
+      to at coef <- fe <- from at estimate
       to at fullcoef <- c(fe,from at fixed)
       to at vcov <- if(!is.null(from at asvar)) 
                  from at asvar/from at samplesize else matrix(NA,1,1)
       to at min <- from at criterion
       to at details <- as.list(c(from at Infos))
+      if(base::version$major >= 4){
+         to at fixed <- to at fullcoef
+         if(is.null(from at fixed)) to at fixed <- to at fixed+NA
+      }
       to at method <- from at method
       to at minuslogl <- crit.f0
 to})

Modified: branches/distr-2.9/pkg/distrMod/inst/NEWS
===================================================================
--- branches/distr-2.9/pkg/distrMod/inst/NEWS	2020-02-01 09:06:07 UTC (rev 1356)
+++ branches/distr-2.9/pkg/distrMod/inst/NEWS	2020-03-06 21:11:18 UTC (rev 1357)
@@ -13,6 +13,13 @@
 under the hood:
 
 ##############
+v 2.8.4
+##############
+under the hood:
++ adapted S4-method setAs to coerce from MCEstimate to class stats4::mle after stats::mle4 
+  changed its slot structure
+
+##############
 v 2.8.3
 ##############
 under the hood:

Modified: branches/distr-2.9/pkg/distrMod/man/MLEstimator.Rd
===================================================================
--- branches/distr-2.9/pkg/distrMod/man/MLEstimator.Rd	2020-02-01 09:06:07 UTC (rev 1356)
+++ branches/distr-2.9/pkg/distrMod/man/MLEstimator.Rd	2020-03-06 21:11:18 UTC (rev 1357)
@@ -68,6 +68,8 @@
 ## 1. Binomial data
 #############################
 ## (empirical) data
+# seed for reproducibility:
+set.seed(20200306)
 x <- rbinom(100, size=25, prob=.25)
 
 ## ML-estimate
@@ -90,6 +92,8 @@
 ## 3. Normal (Gaussian) location and scale
 #############################
 ## (empirical) data
+# seed for reproducibility:
+set.seed(20200306)
 x <- rnorm(100)
 
 ## ML-estimate
@@ -102,6 +106,8 @@
 ## 4. Gamma model
 #############################
 ## (empirical) data
+# seed for reproducibility:
+set.seed(20200306)
 x <- rgamma(50, scale = 0.5, shape = 3)
 
 ## parametric family of probability measures
@@ -170,6 +176,8 @@
 scl.true <- 2
 
 ## (empirical) data
+# seed for reproducibility:
+set.seed(20200306)
 x <- rcauchy(50, location = loc.true, scale = scl.true)
 
 ## Maximum likelihood estimator

Modified: branches/distr-2.9/pkg/distrMod/man/internalmleHelpers.Rd
===================================================================
--- branches/distr-2.9/pkg/distrMod/man/internalmleHelpers.Rd	2020-02-01 09:06:07 UTC (rev 1356)
+++ branches/distr-2.9/pkg/distrMod/man/internalmleHelpers.Rd	2020-03-06 21:11:18 UTC (rev 1357)
@@ -1,7 +1,6 @@
 \name{internal_mlehelpers_for_distrMod}
 \alias{internal_mlehelpers_for_distrMod}
 \alias{.negLoglikelihood}
-\alias{.get.criterion.fct}
 \alias{.process.meCalcRes}
 \alias{.samplesize}
 \alias{.callParamFamParameter}
@@ -55,15 +54,6 @@
 \code{.negLoglikelihood} uses the \code{log} -argument of the corresponding \code{d}-slot
  of the distribution if available; else produces \code{log(d(Distribution)(x))}.
  
-\code{.get.criterion.fct} produces a function \code{criterion.fct} 
-      to fill slot \code{minuslogl} when an object of class \code{MCEstimate}
-      is coerced to class \code{mle} (from package \pkg{stats4});
-      this way we may use profiling methods introduced there also for objects
-      of our classes. More specifically, we produce a function where all 
-      coordinates/components of \code{theta} appear as separate named 
-      arguments, which then calls \code{fun} with these separate arguments 
-      again stacked to one (named) vector argument;
-
 \code{.process.meCalcRes} processes the resulting return value list of methods
 \code{mceCalc} and \code{mleCalc} to give a corresponding object of
 class \code{MCEstimate}. 

Modified: branches/distr-2.9/pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save
===================================================================
--- branches/distr-2.9/pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save	2020-02-01 09:06:07 UTC (rev 1356)
+++ branches/distr-2.9/pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save	2020-03-06 21:11:18 UTC (rev 1357)
@@ -1,5 +1,5 @@
 
-R Under development (unstable) (2020-01-16 r77668) -- "Unsuffered Consequences"
+R Under development (unstable) (2020-03-05 r77909) -- "Unsuffered Consequences"
 Copyright (C) 2020 The R Foundation for Statistical Computing
 Platform: i386-w64-mingw32/i386 (32-bit)
 
@@ -81,7 +81,7 @@
     IQR, mad, median, var
 
 Loading required package: RandVar
-:RandVar>  Implementation of Random Variables (version 1.2.0)
+:RandVar>  Implementation of Random Variables (version 1.2.1)
 :RandVar> 
 :RandVar>  For more information see ?"RandVar", NEWS("RandVar"), as
 :RandVar>  well as
@@ -92,7 +92,7 @@
 Loading required package: MASS
 Loading required package: stats4
 :distrMod>  Object Oriented Implementation of Probability Models
-:distrMod>  (version 2.8.3)
+:distrMod>  (version 2.8.4)
 :distrMod> 
 :distrMod>  Some functions from pkg's 'base' and 'stats' are
 :distrMod>  intentionally masked ---see distrModMASK().
@@ -169,7 +169,7 @@
 shape2 -0.6449341  1.0000000
 > ## IGNORE_RDIFF_BEGIN
 > 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.8511e-05  1.6483e-06
@@ -421,7 +421,7 @@
         dimnames = list(nms, nms0))
     list(fval = fval0, mat = mat0)
 }
-<bytecode: 0x065e9eb0>
+<bytecode: 0x0bc6d9d0>
 Trafo / derivative matrix at which estimate was produced:
        scale shape
 shape  0.000     1
@@ -622,11 +622,11 @@
         1)/c(scale = 1)
     return(y)
 }
-<environment: 0x0adb3bf0>
+<environment: 0x0c16b990>
 
 > ## IGNORE_RDIFF_BEGIN
 > checkL2deriv(E1)
-precision of centering:	 -2.04266e-06 
+precision of centering:	 -2.042661e-06 
 precision of Fisher information:
             scale
 scale -3.5986e-05
@@ -755,7 +755,7 @@
 shape     1 1.644934
 > ## IGNORE_RDIFF_BEGIN
 > checkL2deriv(G1)
-precision of centering:	 -2.04266e-06 1.791171e-06 
+precision of centering:	 -2.042661e-06 1.791171e-06 
 precision of Fisher information:
             scale       shape
 scale -3.5986e-05 -9.5036e-06
@@ -796,8 +796,8 @@
 
 Slot "fct":
 function(x) QuadFormNorm(x, A = A)
-<bytecode: 0x083c6bd0>
-<environment: 0x083c2300>
+<bytecode: 0x0d604ac8>
+<environment: 0x0d6068a8>
 
 > 
 > ## The function is currently defined as
@@ -1080,7 +1080,7 @@
         1)/c(meanlog = 1)
     return(y)
 }
-<environment: 0x0773a0e0>
+<environment: 0x11315a18>
 
 > checkL2deriv(L1)
 precision of centering:	 -0.003003394 
@@ -1328,10 +1328,10 @@
 samplesize:   50
 estimate:
     scale     shape 
-0.2829625 5.0197311 
+0.2829687 5.0197306 
 Criterion:
 Total variation distance 
-               0.4819868 
+               0.4866141 
 > ## IGNORE_RDIFF_END
 > 
 > ## or smooth empirical distribution (takes some time!)
@@ -1450,6 +1450,8 @@
 > ## 1. Binomial data
 > #############################
 > ## (empirical) data
+> # seed for reproducibility:
+> set.seed(20200306)
 > x <- rbinom(100, size=25, prob=.25)
 > 
 > ## ML-estimate
@@ -1462,16 +1464,16 @@
 samplesize:   100
 estimate:
               
-  0.254000000 
- (0.008705952)
+  0.246000000 
+ (0.008613571)
 fixed part of the parameter:
 size 
   25 
 asymptotic (co)variance (multiplied with samplesize):
-[1] 0.00757936
+[1] 0.00741936
 Criterion:
 negative log-likelihood 
-               207.2445 
+               220.6748 
 > 
 > 
 > #############################
@@ -1505,6 +1507,8 @@
 > ## 3. Normal (Gaussian) location and scale
 > #############################
 > ## (empirical) data
+> # seed for reproducibility:
+> set.seed(20200306)
 > x <- rnorm(100)
 > 
 > ## ML-estimate
@@ -1517,18 +1521,18 @@
 samplesize:   100
 estimate:
       mean           sd     
-  -0.01757949    0.93530600 
- ( 0.09353060) ( 0.06613612)
+  -0.03255591    1.02007192 
+ ( 0.10200719) ( 0.07212998)
 asymptotic (co)variance (multiplied with samplesize):
-          mean        sd
-mean 0.8747973 0.0000000
-sd   0.0000000 0.4373987
+         mean        sd
+mean 1.040547 0.0000000
+sd   0.000000 0.5202734
 Criterion:
 negative log-likelihood 
-               135.2057 
+               143.8812 
 > ## compare:
 > c(mean(x),sd(x))
-[1] -0.01757949  0.94001789
+[1] -0.03255591  1.02521086
 > 
 > 
 > #############################
@@ -1535,6 +1539,8 @@
 > ## 4. Gamma model
 > #############################
 > ## (empirical) data
+> # seed for reproducibility:
+> set.seed(20200306)
 > x <- rgamma(50, scale = 0.5, shape = 3)
 > 
 > ## parametric family of probability measures
@@ -1550,22 +1556,22 @@
 samplesize:   50
 estimate:
      scale       shape  
-  0.5360537   3.0117887 
- (0.1108070) (0.5721441)
+  0.4421995   3.5180238 
+ (0.0909164) (0.6729136)
 asymptotic (co)variance (multiplied with samplesize):
            scale     shape
-scale  0.6139092 -2.913162
-shape -2.9131624 16.367446
+scale  0.4132896 -2.845824
+shape -2.8458244 22.640637
 Criterion:
 negative log-likelihood 
-               61.32426 
+               56.51362 
 > 
 > ## Asymptotic (CLT-based) confidence interval
 > confint(res)
 A[n] asymptotic (CLT-based) confidence interval:
-         2.5 %    97.5 %
-scale 0.318876 0.7532313
-shape 1.890407 4.1331707
+          2.5 %    97.5 %
+scale 0.2640066 0.6203924
+shape 2.1991373 4.8369102
 Type of estimator: Maximum likelihood estimate
 samplesize:   50
 Call by which estimate was produced:
@@ -1579,19 +1585,20 @@
 > ## implementation of ML-estimator of package MASS
 > require(MASS)
 > (res1 <- fitdistr(x, "gamma"))
+Warning in densfun(x, parm[1], parm[2], ...) : NaNs produced
      shape       rate   
-  3.0117885   1.8655681 
- (0.5721425) (0.3856279)
+  3.5180020   2.2612888 
+ (0.6729072) (0.4649203)
 > 
 > ## comparison
 > ## shape
 > estimate(res)[2]
    shape 
-3.011789 
+3.518024 
 > ## rate
 > 1/estimate(res)[1]
    scale 
-1.865485 
+2.261423 
 > 
 > ## minor differences due to the fact that by default, fitdistr uses
 > ## BFGS, while we use Nelder-Mead instead
@@ -1598,11 +1605,11 @@
 > 
 > ## log-likelihood
 > res1$loglik
-[1] -61.32426
+[1] -56.51362
 > ## negative log-likelihood
 > criterion(res)
 negative log-likelihood 
-               61.32426 
+               56.51362 
 > 
 > 
 > ## explicitely transforming to
@@ -1624,14 +1631,14 @@
 > distrModoptions("show.details" = "minimal")
 > res1
      shape       rate   
-  3.0117885   1.8655681 
- (0.5721425) (0.3856279)
+  3.5180020   2.2612888 
+ (0.6729072) (0.4649203)
 > res2
 Evaluations of Maximum likelihood estimate:
 -------------------------------------------
      shape       rate   
-  3.0117887   1.8654848 
- (0.5721441) (0.3856120)
+  3.5180238   2.2614228 
+ (0.6729136) (0.4649495)
 > 
 > ## some profiling
 > par(mfrow=c(1,2))
@@ -1662,6 +1669,8 @@
 > scl.true <- 2
 > 
 > ## (empirical) data
+> # seed for reproducibility:
+> set.seed(20200306)
 > x <- rcauchy(50, location = loc.true, scale = scl.true)
 > 
 > ## Maximum likelihood estimator
@@ -1668,15 +1677,15 @@
 > (res <- MLEstimator(x = x, ParamFamily = C))
 Evaluations of Maximum likelihood estimate:
 -------------------------------------------
-     loc       scale  
-  1.088544   1.527400 
- (0.305480) (0.305480)
+      loc        scale  
+  1.0723789   1.9896397 
+ (0.3979279) (0.3979279)
 > ## Asymptotic (CLT-based) confidence interval
 > confint(res)
 A[n] asymptotic (CLT-based) confidence interval:
           2.5 %   97.5 %
-loc   0.4898137 1.687273
-scale 0.9286703 2.126130
+loc   0.2924544 1.852303
+scale 1.2097153 2.769564
 > 
 > 
 > 
@@ -2123,7 +2132,7 @@
     else 
         return(sqrt(colSums(x^2)))
 }
-<bytecode: 0x0bfb1e38>
+<bytecode: 0x11d86f90>
 <environment: namespace:distrMod>
 > name(EuclNorm)
 [1] "EuclideanNorm"
@@ -2157,7 +2166,7 @@
     else 
         return(sqrt(colSums(x^2)))
 }
-<bytecode: 0x0bfb1e38>
+<bytecode: 0x11d86f90>
 <environment: namespace:distrMod>
 
 > ## IGNORE_RDIFF_END
@@ -2614,8 +2623,8 @@
 
 Slot "fct":
 function(x) QuadFormNorm(x, A= A0)
-<bytecode: 0x09408548>
-<environment: 0x09406db8>
+<bytecode: 0x11329fe8>
+<environment: 0x1132aa08>
 
 > 
 > ## The function is currently defined as
@@ -2654,8 +2663,8 @@
 
 Slot "fct":
 function(x) QuadFormNorm(x, A = A)
-<bytecode: 0x0926fd98>
-<environment: 0x0926f178>
+<bytecode: 0x14974540>
+<environment: 0x14975140>
 
 > 
 > ## The function is currently defined as
@@ -2683,7 +2692,7 @@
 > 
 > ## IGNORE_RDIFF_BEGIN
 >   addAlphTrsp2col(rgb(1,0.3,0.03), 25)
-[1] "#FF4C0819"
+[1] "#FF4D0819"
 >   ## gives "#FF4C0819" on 32bit and "#FF4D0819" on 64bit
 > ## IGNORE_RDIFF_END
 >   addAlphTrsp2col("darkblue", 25)
@@ -3678,7 +3687,7 @@
     dimnames(mat) <- list(nfval, c("mean", "sd"))
     return(list(fval = fval, mat = mat))
 }
-<bytecode: 0x06616820>
+<bytecode: 0x14981bb0>
 > print(param(NS), show.details = "minimal")
 An object of class "ParamWithScaleFamParameter"
 name:	location and scale
@@ -3727,7 +3736,7 @@
     dimnames(mat) <- list(nfval, c("mean", "sd"))
     return(list(fval = fval, mat = mat))
 }
-<bytecode: 0x06616820>
+<bytecode: 0x14981bb0>
 Trafo / derivative matrix:
             mean         sd
 mu/sig 0.3668695 -0.3024814
@@ -3770,7 +3779,7 @@
     dimnames(mat) <- list(nfval, c("mean", "sd"))
     return(list(fval = fval, mat = mat))
 }
-<bytecode: 0x06616820>
+<bytecode: 0x14981bb0>
 Trafo / derivative matrix:
          mean      sd
 mu/sig 0.3669 -0.3025
@@ -4136,7 +4145,7 @@
 > cleanEx()
 > options(digits = 7L)
 > base::cat("Time elapsed: ", proc.time() - base::get("ptime", pos = 'CheckExEnv'),"\n")
-Time elapsed:  44.57 1.22 73.66 NA NA 
+Time elapsed:  84.49 2.45 148.6 NA NA 
 > grDevices::dev.off()
 null device 
           1 

Modified: pkg/distrMod/DESCRIPTION
===================================================================
--- pkg/distrMod/DESCRIPTION	2020-02-01 09:06:07 UTC (rev 1356)
+++ pkg/distrMod/DESCRIPTION	2020-03-06 21:11:18 UTC (rev 1357)
@@ -1,6 +1,6 @@
 Package: distrMod
-Version: 2.8.3
-Date: 2020-01-18
+Version: 2.8.4
+Date: 2020-03-06
 Title: Object Oriented Implementation of Probability Models
 Description: Implements S4 classes for probability models based on packages 'distr' and
             'distrEx'.
@@ -18,4 +18,4 @@
 URL: http://distr.r-forge.r-project.org/
 LastChangedDate: {$LastChangedDate$}
 LastChangedRevision: {$LastChangedRevision$}
-VCS/SVNRevision: 1352
+VCS/SVNRevision: 1356

Modified: pkg/distrMod/R/mleCalc-methods.R
===================================================================
--- pkg/distrMod/R/mleCalc-methods.R	2020-02-01 09:06:07 UTC (rev 1356)
+++ pkg/distrMod/R/mleCalc-methods.R	2020-03-06 21:11:18 UTC (rev 1357)
@@ -120,7 +120,7 @@
        filterDots <- function(dots){
           if(length(dots)){
                dotsOptIz <- NULL
-               nfmlsOptiz <- NULL
+               nfmlsOptIz <- NULL
 
                dotsNames <- names(dots)
                if(length(param(PFam)) == 1){
@@ -260,7 +260,7 @@
                else  names(theta) <- names(main(ParamFamily))
                distr.new <- ParamFamily at modifyParam(theta)
                crit1 <- do.call(criterion, c(list(Data, distr.new),
-                                dotsToPass$dotsCrit))
+                                dotsTP$dotsCrit))
                return(crit1)}
 
     crit.fct <- get.criterion.fct(theta, Data = x, ParamFam = PFam,

Modified: pkg/distrMod/R/setAs.R
===================================================================
--- pkg/distrMod/R/setAs.R	2020-02-01 09:06:07 UTC (rev 1356)
+++ pkg/distrMod/R/setAs.R	2020-03-06 21:11:18 UTC (rev 1357)
@@ -55,14 +55,16 @@
       to at call <- substitute(mle(minuslogl = crit.f, start = startPar), 
                             list(crit.f = crit.f0,
                                  startPar = start.f0))
-      to at coef <- from at estimate
-      fe <- if(is.null(from at untransformed.estimate))
-               from at estimate else from at untransformed.estimate
+      to at coef <- fe <- from at estimate
       to at fullcoef <- c(fe,from at fixed)
       to at vcov <- if(!is.null(from at asvar)) 
                  from at asvar/from at samplesize else matrix(NA,1,1)
       to at min <- from at criterion
       to at details <- as.list(c(from at Infos))
+      if(base::version$major >= 4){
+         to at fixed <- to at fullcoef
+         if(is.null(from at fixed)) to at fixed <- to at fixed+NA
+      }
       to at method <- from at method
       to at minuslogl <- crit.f0
 to})

Modified: pkg/distrMod/inst/NEWS
===================================================================
--- pkg/distrMod/inst/NEWS	2020-02-01 09:06:07 UTC (rev 1356)
+++ pkg/distrMod/inst/NEWS	2020-03-06 21:11:18 UTC (rev 1357)
@@ -8,6 +8,13 @@
  information)
 
 ##############
+v 2.8.4
+##############
+under the hood:
++ adapted S4-method setAs to coerce from MCEstimate to class stats4::mle after stats::mle4 
+  changed its slot structure
+
+##############
 v 2.8.3
 ##############
 under the hood:

Modified: pkg/distrMod/man/0distrMod-package.Rd
===================================================================
--- pkg/distrMod/man/0distrMod-package.Rd	2020-02-01 09:06:07 UTC (rev 1356)
+++ pkg/distrMod/man/0distrMod-package.Rd	2020-03-06 21:11:18 UTC (rev 1357)
@@ -13,8 +13,8 @@
 \details{
 \tabular{ll}{
 Package: \tab distrMod \cr
-Version: \tab 2.8.3 \cr
-Date: \tab 2020-01-18 \cr
+Version: \tab 2.8.4 \cr
+Date: \tab 2020-03-06 \cr
 Depends: \tab R(>= 3.4), distr(>= 2.8.0), distrEx(>= 2.8.0), RandVar(>= 1.2.0), MASS, stats4,methods \cr
 Imports: \tab startupmsg, sfsmisc, graphics, stats, grDevices \cr
 Suggests: \tab ismev, evd, \cr
@@ -22,7 +22,7 @@
 ByteCompile: \tab yes \cr
 License: \tab LGPL-3 \cr
 URL: \tab http://distr.r-forge.r-project.org/\cr
-VCS/SVNRevision: \tab 1352 \cr
+VCS/SVNRevision: \tab 1356 \cr
 }}
 \section{Classes}{
 \preformatted{

Modified: pkg/distrMod/man/MLEstimator.Rd
===================================================================
--- pkg/distrMod/man/MLEstimator.Rd	2020-02-01 09:06:07 UTC (rev 1356)
+++ pkg/distrMod/man/MLEstimator.Rd	2020-03-06 21:11:18 UTC (rev 1357)
@@ -68,6 +68,8 @@
 ## 1. Binomial data
 #############################
 ## (empirical) data
+# seed for reproducibility:
+set.seed(20200306)
 x <- rbinom(100, size=25, prob=.25)
 
 ## ML-estimate
@@ -90,6 +92,8 @@
 ## 3. Normal (Gaussian) location and scale
 #############################
 ## (empirical) data
+# seed for reproducibility:
+set.seed(20200306)
 x <- rnorm(100)
 
 ## ML-estimate
@@ -102,6 +106,8 @@
 ## 4. Gamma model
 #############################
 ## (empirical) data
+# seed for reproducibility:
+set.seed(20200306)
 x <- rgamma(50, scale = 0.5, shape = 3)
 
 ## parametric family of probability measures
@@ -170,6 +176,8 @@
 scl.true <- 2
 
 ## (empirical) data
+# seed for reproducibility:
+set.seed(20200306)
 x <- rcauchy(50, location = loc.true, scale = scl.true)
 
 ## Maximum likelihood estimator

Modified: pkg/distrMod/man/internalmleHelpers.Rd
===================================================================
--- pkg/distrMod/man/internalmleHelpers.Rd	2020-02-01 09:06:07 UTC (rev 1356)
+++ pkg/distrMod/man/internalmleHelpers.Rd	2020-03-06 21:11:18 UTC (rev 1357)
@@ -1,7 +1,6 @@
 \name{internal_mlehelpers_for_distrMod}
 \alias{internal_mlehelpers_for_distrMod}
 \alias{.negLoglikelihood}
-\alias{.get.criterion.fct}
 \alias{.process.meCalcRes}
 \alias{.samplesize}
 \alias{.callParamFamParameter}
@@ -55,15 +54,6 @@
 \code{.negLoglikelihood} uses the \code{log} -argument of the corresponding \code{d}-slot
  of the distribution if available; else produces \code{log(d(Distribution)(x))}.
  
-\code{.get.criterion.fct} produces a function \code{criterion.fct} 
-      to fill slot \code{minuslogl} when an object of class \code{MCEstimate}
-      is coerced to class \code{mle} (from package \pkg{stats4});
-      this way we may use profiling methods introduced there also for objects
-      of our classes. More specifically, we produce a function where all 
-      coordinates/components of \code{theta} appear as separate named 
-      arguments, which then calls \code{fun} with these separate arguments 
-      again stacked to one (named) vector argument;
-
 \code{.process.meCalcRes} processes the resulting return value list of methods
 \code{mceCalc} and \code{mleCalc} to give a corresponding object of
 class \code{MCEstimate}. 

Modified: pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save
===================================================================
--- pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save	2020-02-01 09:06:07 UTC (rev 1356)
+++ pkg/distrMod/tests/Examples/distrMod-Ex.Rout.save	2020-03-06 21:11:18 UTC (rev 1357)
@@ -1,5 +1,5 @@
 
-R Under development (unstable) (2020-01-16 r77668) -- "Unsuffered Consequences"
+R Under development (unstable) (2020-03-05 r77909) -- "Unsuffered Consequences"
 Copyright (C) 2020 The R Foundation for Statistical Computing
 Platform: i386-w64-mingw32/i386 (32-bit)
 
@@ -81,7 +81,7 @@
     IQR, mad, median, var
 
 Loading required package: RandVar
-:RandVar>  Implementation of Random Variables (version 1.2.0)
+:RandVar>  Implementation of Random Variables (version 1.2.1)
 :RandVar> 
 :RandVar>  For more information see ?"RandVar", NEWS("RandVar"), as
 :RandVar>  well as
@@ -92,7 +92,7 @@
 Loading required package: MASS
 Loading required package: stats4
 :distrMod>  Object Oriented Implementation of Probability Models
-:distrMod>  (version 2.8.3)
+:distrMod>  (version 2.8.4)
 :distrMod> 
 :distrMod>  Some functions from pkg's 'base' and 'stats' are
 :distrMod>  intentionally masked ---see distrModMASK().
@@ -169,7 +169,7 @@
 shape2 -0.6449341  1.0000000
 > ## IGNORE_RDIFF_BEGIN
 > 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.8511e-05  1.6483e-06
@@ -421,7 +421,7 @@
         dimnames = list(nms, nms0))
     list(fval = fval0, mat = mat0)
 }
-<bytecode: 0x065e9eb0>
+<bytecode: 0x0bc6d9d0>
 Trafo / derivative matrix at which estimate was produced:
        scale shape
 shape  0.000     1
@@ -622,11 +622,11 @@
         1)/c(scale = 1)
     return(y)
 }
-<environment: 0x0adb3bf0>
+<environment: 0x0c16b990>
 
 > ## IGNORE_RDIFF_BEGIN
 > checkL2deriv(E1)
-precision of centering:	 -2.04266e-06 
+precision of centering:	 -2.042661e-06 
 precision of Fisher information:
             scale
 scale -3.5986e-05
@@ -755,7 +755,7 @@
 shape     1 1.644934
 > ## IGNORE_RDIFF_BEGIN
 > checkL2deriv(G1)
-precision of centering:	 -2.04266e-06 1.791171e-06 
+precision of centering:	 -2.042661e-06 1.791171e-06 
 precision of Fisher information:
             scale       shape
 scale -3.5986e-05 -9.5036e-06
@@ -796,8 +796,8 @@
 
 Slot "fct":
 function(x) QuadFormNorm(x, A = A)
-<bytecode: 0x083c6bd0>
-<environment: 0x083c2300>
+<bytecode: 0x0d604ac8>
+<environment: 0x0d6068a8>
 
 > 
 > ## The function is currently defined as
@@ -1080,7 +1080,7 @@
         1)/c(meanlog = 1)
     return(y)
 }
-<environment: 0x0773a0e0>
+<environment: 0x11315a18>
 
 > checkL2deriv(L1)
 precision of centering:	 -0.003003394 
@@ -1328,10 +1328,10 @@
 samplesize:   50
 estimate:
     scale     shape 
-0.2829625 5.0197311 
+0.2829687 5.0197306 
 Criterion:
 Total variation distance 
-               0.4819868 
+               0.4866141 
 > ## IGNORE_RDIFF_END
 > 
 > ## or smooth empirical distribution (takes some time!)
@@ -1450,6 +1450,8 @@
 > ## 1. Binomial data
 > #############################
 > ## (empirical) data
+> # seed for reproducibility:
+> set.seed(20200306)
 > x <- rbinom(100, size=25, prob=.25)
 > 
 > ## ML-estimate
@@ -1462,16 +1464,16 @@
 samplesize:   100
 estimate:
               
-  0.254000000 
- (0.008705952)
+  0.246000000 
+ (0.008613571)
 fixed part of the parameter:
 size 
   25 
 asymptotic (co)variance (multiplied with samplesize):
-[1] 0.00757936
+[1] 0.00741936
 Criterion:
 negative log-likelihood 
-               207.2445 
+               220.6748 
 > 
 > 
 > #############################
@@ -1505,6 +1507,8 @@
 > ## 3. Normal (Gaussian) location and scale
 > #############################
 > ## (empirical) data
+> # seed for reproducibility:
+> set.seed(20200306)
 > x <- rnorm(100)
 > 
 > ## ML-estimate
@@ -1517,18 +1521,18 @@
 samplesize:   100
 estimate:
       mean           sd     
-  -0.01757949    0.93530600 
- ( 0.09353060) ( 0.06613612)
+  -0.03255591    1.02007192 
+ ( 0.10200719) ( 0.07212998)
 asymptotic (co)variance (multiplied with samplesize):
-          mean        sd
-mean 0.8747973 0.0000000
-sd   0.0000000 0.4373987
+         mean        sd
+mean 1.040547 0.0000000
+sd   0.000000 0.5202734
 Criterion:
 negative log-likelihood 
-               135.2057 
+               143.8812 
 > ## compare:
 > c(mean(x),sd(x))
-[1] -0.01757949  0.94001789
+[1] -0.03255591  1.02521086
 > 
 > 
 > #############################
@@ -1535,6 +1539,8 @@
 > ## 4. Gamma model
 > #############################
 > ## (empirical) data
+> # seed for reproducibility:
+> set.seed(20200306)
 > x <- rgamma(50, scale = 0.5, shape = 3)
 > 
 > ## parametric family of probability measures
@@ -1550,22 +1556,22 @@
 samplesize:   50
 estimate:
      scale       shape  
-  0.5360537   3.0117887 
- (0.1108070) (0.5721441)
+  0.4421995   3.5180238 
+ (0.0909164) (0.6729136)
 asymptotic (co)variance (multiplied with samplesize):
            scale     shape
-scale  0.6139092 -2.913162
-shape -2.9131624 16.367446
+scale  0.4132896 -2.845824
+shape -2.8458244 22.640637
 Criterion:
 negative log-likelihood 
-               61.32426 
+               56.51362 
 > 
 > ## Asymptotic (CLT-based) confidence interval
 > confint(res)
 A[n] asymptotic (CLT-based) confidence interval:
-         2.5 %    97.5 %
-scale 0.318876 0.7532313
-shape 1.890407 4.1331707
+          2.5 %    97.5 %
+scale 0.2640066 0.6203924
+shape 2.1991373 4.8369102
 Type of estimator: Maximum likelihood estimate
 samplesize:   50
 Call by which estimate was produced:
@@ -1579,19 +1585,20 @@
 > ## implementation of ML-estimator of package MASS
 > require(MASS)
 > (res1 <- fitdistr(x, "gamma"))
+Warning in densfun(x, parm[1], parm[2], ...) : NaNs produced
      shape       rate   
-  3.0117885   1.8655681 
- (0.5721425) (0.3856279)
+  3.5180020   2.2612888 
+ (0.6729072) (0.4649203)
 > 
 > ## comparison
 > ## shape
 > estimate(res)[2]
    shape 
-3.011789 
+3.518024 
 > ## rate
 > 1/estimate(res)[1]
    scale 
-1.865485 
+2.261423 
 > 
 > ## minor differences due to the fact that by default, fitdistr uses
 > ## BFGS, while we use Nelder-Mead instead
@@ -1598,11 +1605,11 @@
 > 
 > ## log-likelihood
 > res1$loglik
-[1] -61.32426
+[1] -56.51362
 > ## negative log-likelihood
 > criterion(res)
 negative log-likelihood 
-               61.32426 
+               56.51362 
 > 
 > 
 > ## explicitely transforming to
@@ -1624,14 +1631,14 @@
 > distrModoptions("show.details" = "minimal")
 > res1
      shape       rate   
-  3.0117885   1.8655681 
- (0.5721425) (0.3856279)
+  3.5180020   2.2612888 
+ (0.6729072) (0.4649203)
 > res2
 Evaluations of Maximum likelihood estimate:
 -------------------------------------------
      shape       rate   
-  3.0117887   1.8654848 
- (0.5721441) (0.3856120)
+  3.5180238   2.2614228 
+ (0.6729136) (0.4649495)
 > 
 > ## some profiling
 > par(mfrow=c(1,2))
@@ -1662,6 +1669,8 @@
 > scl.true <- 2
 > 
 > ## (empirical) data
+> # seed for reproducibility:
+> set.seed(20200306)
 > x <- rcauchy(50, location = loc.true, scale = scl.true)
 > 
 > ## Maximum likelihood estimator
@@ -1668,15 +1677,15 @@
 > (res <- MLEstimator(x = x, ParamFamily = C))
 Evaluations of Maximum likelihood estimate:
 -------------------------------------------
-     loc       scale  
-  1.088544   1.527400 
- (0.305480) (0.305480)
+      loc        scale  
+  1.0723789   1.9896397 
+ (0.3979279) (0.3979279)
 > ## Asymptotic (CLT-based) confidence interval
 > confint(res)
 A[n] asymptotic (CLT-based) confidence interval:
           2.5 %   97.5 %
-loc   0.4898137 1.687273
-scale 0.9286703 2.126130
+loc   0.2924544 1.852303
+scale 1.2097153 2.769564
 > 
 > 
 > 
@@ -2123,7 +2132,7 @@
     else 
         return(sqrt(colSums(x^2)))
 }
-<bytecode: 0x0bfb1e38>
+<bytecode: 0x11d86f90>
 <environment: namespace:distrMod>
 > name(EuclNorm)
 [1] "EuclideanNorm"
@@ -2157,7 +2166,7 @@
     else 
         return(sqrt(colSums(x^2)))
 }
-<bytecode: 0x0bfb1e38>
+<bytecode: 0x11d86f90>
 <environment: namespace:distrMod>
 
 > ## IGNORE_RDIFF_END
@@ -2614,8 +2623,8 @@
 
 Slot "fct":
 function(x) QuadFormNorm(x, A= A0)
-<bytecode: 0x09408548>
-<environment: 0x09406db8>
+<bytecode: 0x11329fe8>
+<environment: 0x1132aa08>
 
 > 
 > ## The function is currently defined as
@@ -2654,8 +2663,8 @@
 
 Slot "fct":
 function(x) QuadFormNorm(x, A = A)
-<bytecode: 0x0926fd98>
-<environment: 0x0926f178>
+<bytecode: 0x14974540>
+<environment: 0x14975140>
 
 > 
 > ## The function is currently defined as
@@ -2683,7 +2692,7 @@
 > 
 > ## IGNORE_RDIFF_BEGIN
 >   addAlphTrsp2col(rgb(1,0.3,0.03), 25)
-[1] "#FF4C0819"
+[1] "#FF4D0819"
 >   ## gives "#FF4C0819" on 32bit and "#FF4D0819" on 64bit
 > ## IGNORE_RDIFF_END
 >   addAlphTrsp2col("darkblue", 25)
@@ -3678,7 +3687,7 @@
     dimnames(mat) <- list(nfval, c("mean", "sd"))
     return(list(fval = fval, mat = mat))
 }
-<bytecode: 0x06616820>
+<bytecode: 0x14981bb0>
 > print(param(NS), show.details = "minimal")
 An object of class "ParamWithScaleFamParameter"
 name:	location and scale
@@ -3727,7 +3736,7 @@
     dimnames(mat) <- list(nfval, c("mean", "sd"))
     return(list(fval = fval, mat = mat))
 }
-<bytecode: 0x06616820>
+<bytecode: 0x14981bb0>
 Trafo / derivative matrix:
             mean         sd
 mu/sig 0.3668695 -0.3024814
@@ -3770,7 +3779,7 @@
     dimnames(mat) <- list(nfval, c("mean", "sd"))
     return(list(fval = fval, mat = mat))
 }
-<bytecode: 0x06616820>
+<bytecode: 0x14981bb0>
 Trafo / derivative matrix:
          mean      sd
 mu/sig 0.3669 -0.3025
@@ -4136,7 +4145,7 @@
 > cleanEx()
 > options(digits = 7L)
 > base::cat("Time elapsed: ", proc.time() - base::get("ptime", pos = 'CheckExEnv'),"\n")
-Time elapsed:  44.57 1.22 73.66 NA NA 
+Time elapsed:  84.49 2.45 148.6 NA NA 
 > grDevices::dev.off()
 null device 
           1 

Modified: pkg/utils/DESCRIPTIONutilsExamples.R
===================================================================
--- pkg/utils/DESCRIPTIONutilsExamples.R	2020-02-01 09:06:07 UTC (rev 1356)
+++ pkg/utils/DESCRIPTIONutilsExamples.R	2020-03-06 21:11:18 UTC (rev 1357)
@@ -411,8 +411,8 @@
 
 if(FALSE){## nur distrMod Version 2.8.3 in trunk
 Pkgs <- c("distrMod")
-Names <- c("Version")
-Values <- matrix(c("2.8.3"),1,length(Pkgs))
+Names <- c("Version")    ## 20200306
+Values <- matrix(c("2.8.4"),1,length(Pkgs))
 ReqRVersion0 <- c(NA,rep("R(>= 3.4)",length(Pkgs)-1))
 ReqDistrPkgVersion0 <- vector("list",length(Pkgs))
 names(ReqDistrPkgVersion0) <- Pkgs
@@ -425,6 +425,6 @@
 changeDescription(startDir = "C:/rtest/distr",names=Names,
                   pkgs=Pkgs, values=Values,ReqRVersion =ReqRVersion0,
                   ReqDistrPkgVersion =ReqDistrPkgVersion0)
-updateHTMLpages(pkgNames ="distrMod", pkgVersions = "2.8.3")
+updateHTMLpages(pkgNames ="distrMod", pkgVersions = "2.8.4")
 }
 

Modified: www/distrMod.html
===================================================================
--- www/distrMod.html	2020-02-01 09:06:07 UTC (rev 1356)
+++ www/distrMod.html	2020-03-06 21:11:18 UTC (rev 1357)
@@ -29,11 +29,11 @@
 
 
 <hr style="width: 100%; height: 2px;">
-<div style="text-align: justify;"> Version: 2.8.3 <br>
+<div style="text-align: justify;"> Version: 2.8.4 <br>
 
 
 
-Release Date: 2020-01-18 <br>
+Release Date: 2020-03-06 <br>
 
 
 
@@ -1028,7 +1028,7 @@
 <div style="text-align: justify; color: rgb(0, 0, 0);">This page is
 maintained by <a href="mailto:peter.ruckdeschel at uni-oldenburg.de?subject=distr-package">Peter
 Ruckdeschel</a>
-and last updated on 2020-01-18. <br>
+and last updated on 2020-03-06. <br>
 
 
 



More information about the Distr-commits mailing list