[Distr-commits] r549 - branches/distr-2.2/pkg/distrMod branches/distr-2.2/pkg/distrMod/R branches/distr-2.2/pkg/distrMod/chm branches/distr-2.2/pkg/distrMod/man pkg/distrMod/R pkg/distrMod/chm

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Tue Aug 25 19:34:02 CEST 2009


Author: ruckdeschel
Date: 2009-08-25 19:34:02 +0200 (Tue, 25 Aug 2009)
New Revision: 549

Modified:
   branches/distr-2.2/pkg/distrMod/NAMESPACE
   branches/distr-2.2/pkg/distrMod/R/AllClass.R
   branches/distr-2.2/pkg/distrMod/R/AllGeneric.R
   branches/distr-2.2/pkg/distrMod/R/Confint-class.R
   branches/distr-2.2/pkg/distrMod/R/Estimate.R
   branches/distr-2.2/pkg/distrMod/R/Estimator.R
   branches/distr-2.2/pkg/distrMod/R/MCEstimator.R
   branches/distr-2.2/pkg/distrMod/R/MDEstimator.R
   branches/distr-2.2/pkg/distrMod/R/MLEstimator.R
   branches/distr-2.2/pkg/distrMod/chm/00Index.html
   branches/distr-2.2/pkg/distrMod/chm/Confint-class.html
   branches/distr-2.2/pkg/distrMod/chm/Estimate-class.html
   branches/distr-2.2/pkg/distrMod/chm/Estimator.html
   branches/distr-2.2/pkg/distrMod/chm/MCEstimator.html
   branches/distr-2.2/pkg/distrMod/chm/MDEstimator.html
   branches/distr-2.2/pkg/distrMod/chm/MLEstimator.html
   branches/distr-2.2/pkg/distrMod/chm/distrMod.chm
   branches/distr-2.2/pkg/distrMod/chm/distrMod.toc
   branches/distr-2.2/pkg/distrMod/man/Confint-class.Rd
   branches/distr-2.2/pkg/distrMod/man/Estimate-class.Rd
   branches/distr-2.2/pkg/distrMod/man/Estimator.Rd
   branches/distr-2.2/pkg/distrMod/man/MCEstimator.Rd
   branches/distr-2.2/pkg/distrMod/man/MDEstimator.Rd
   branches/distr-2.2/pkg/distrMod/man/MLEstimator.Rd
   pkg/distrMod/R/AllGeneric.R
   pkg/distrMod/chm/00Index.html
   pkg/distrMod/chm/Confint-class.html
   pkg/distrMod/chm/Estimate-class.html
   pkg/distrMod/chm/Estimator.html
   pkg/distrMod/chm/MCEstimator.html
   pkg/distrMod/chm/MDEstimator.html
   pkg/distrMod/chm/MLEstimator.html
   pkg/distrMod/chm/distrMod.chm
   pkg/distrMod/chm/distrMod.hhp
   pkg/distrMod/chm/distrMod.toc
Log:
accidently had written last modifications (treatment of NAs in distrMod) into trunc;
have also committed them to branch now; have checked that it works with trunc;

Modified: branches/distr-2.2/pkg/distrMod/NAMESPACE
===================================================================
--- branches/distr-2.2/pkg/distrMod/NAMESPACE	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/NAMESPACE	2009-08-25 17:34:02 UTC (rev 549)
@@ -36,6 +36,7 @@
               "dimension", "show", "print", "plot", "param", "E", "name",
               "L2deriv", "L2derivSymm", "L2derivDistr", "L2derivDistrSymm",
               "FisherInfo", "checkL2deriv", "fam.call")
+exportMethods("completecases")
 exportMethods("bound", "width")
 exportMethods("nu", "name", "sign", "nu<-", "name<-", "sign<-", "biastype", "biastype<-")
 exportMethods("existsPIC")

Modified: branches/distr-2.2/pkg/distrMod/R/AllClass.R
===================================================================
--- branches/distr-2.2/pkg/distrMod/R/AllClass.R	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/R/AllClass.R	2009-08-25 17:34:02 UTC (rev 549)
@@ -377,6 +377,7 @@
          representation(name = "character",
                         estimate = "ANY",
                         samplesize = "numeric",
+                        completecases = "logical",
                         asvar = "OptionalNumericOrMatrix",
                         Infos = "matrix",
                         estimate.call = "call",
@@ -388,6 +389,7 @@
          prototype(name = "Estimate",
                    estimate = numeric(0),
                    samplesize = numeric(0),
+                   completecases = logical(0),
                    estimate.call = call("{}"),
                    asvar = NULL,
                    Infos = matrix(c(character(0),character(0)), ncol=2,
@@ -422,6 +424,7 @@
          prototype(name = "Minimum criterion estimate",
                    estimate = numeric(0),
                    samplesize = numeric(0),
+                   completecases = logical(0),
                    asvar = NULL,
                    estimate.call = call("{}"),
                    criterion.fct =  function(){},
@@ -450,6 +453,7 @@
                         call.estimate = "call",
                         name.estimate = "character",
                         samplesize.estimate = "numeric",
+                        completecases.estimate = "logical",
                         trafo.estimate = "list",
                         nuisance.estimate = "OptionalNumeric",
                         fixed.estimate = "OptionalNumeric"
@@ -458,6 +462,7 @@
                    confint = array(0),
                    call.estimate = call("{}"),
                    samplesize.estimate = numeric(0),
+                   completecases.estimate = logical(0),
                    name.estimate = "",
                    trafo.estimate = list(fct = function(x){
                                              list(fval = x, mat = matrix(1))},

Modified: branches/distr-2.2/pkg/distrMod/R/AllGeneric.R
===================================================================
--- branches/distr-2.2/pkg/distrMod/R/AllGeneric.R	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/R/AllGeneric.R	2009-08-25 17:34:02 UTC (rev 549)
@@ -173,7 +173,7 @@
     setGeneric("nuisance.estimate", function(object) standardGeneric("nuisance.estimate"))
 }
 if(!isGeneric("samplesize.estimate")){
-    setGeneric("samplesize.estimate", function(object) standardGeneric("samplesize.estimate"))
+    setGeneric("samplesize.estimate", function(object, ...) standardGeneric("samplesize.estimate"))
 }
 if(!isGeneric("call.estimate")){
     setGeneric("call.estimate", function(object) standardGeneric("call.estimate"))
@@ -181,6 +181,9 @@
 if(!isGeneric("fixed.estimate")){
     setGeneric("fixed.estimate", function(object,... ) standardGeneric("fixed.estimate"))
 }
+if(!isGeneric("completecases.estimate")){
+  	     setGeneric("completecases.estimate", function(object) standardGeneric("completecases.estimate"))
+}
 if(!isGeneric("Infos")){
     setGeneric("Infos", function(object) standardGeneric("Infos"))
 }
@@ -196,8 +199,11 @@
 if(!isGeneric("criterion<-")){
     setGeneric("criterion<-", function(object, value) standardGeneric("criterion<-"))
 }
+if(!isGeneric("completecases")){
+  	     setGeneric("completecases", function(object) standardGeneric("completecases"))
+}
 if(!isGeneric("samplesize")){
-    setGeneric("samplesize", function(object) standardGeneric("samplesize"))
+    setGeneric("samplesize", function(object, ...) standardGeneric("samplesize"))
 }
 if(!isGeneric("asvar")){
     setGeneric("asvar", function(object) standardGeneric("asvar"))

Modified: branches/distr-2.2/pkg/distrMod/R/Confint-class.R
===================================================================
--- branches/distr-2.2/pkg/distrMod/R/Confint-class.R	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/R/Confint-class.R	2009-08-25 17:34:02 UTC (rev 549)
@@ -5,8 +5,12 @@
            function(object) object at call.estimate)
 setMethod("name.estimate", signature(object="Confint"),
            function(object) object at name.estimate)
+setMethod("completecases.estimate", signature(object="Confint"),
+           function(object) object at completecases.estimate)
 setMethod("samplesize.estimate", signature(object="Confint"),
-           function(object) object at samplesize.estimate)
+           function(object, onlycompletecases = TRUE)
+  	    (object at samplesize.estimate+
+  	     (1-onlycompletecases)*sum(object at completecases.estimate)))
 setMethod("nuisance.estimate", signature(object="Confint"),
            function(object) object at nuisance.estimate)
 setMethod("trafo.estimate", signature(object="Confint"),
@@ -16,3 +20,5 @@
 setMethod("type", signature(object="Confint"),
            function(object) object at type)
 
+
+

Modified: branches/distr-2.2/pkg/distrMod/R/Estimate.R
===================================================================
--- branches/distr-2.2/pkg/distrMod/R/Estimate.R	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/R/Estimate.R	2009-08-25 17:34:02 UTC (rev 549)
@@ -48,7 +48,9 @@
         object 
     })
 
-setMethod("samplesize", "Estimate", function(object) object at samplesize)
+setMethod("samplesize", "Estimate", function(object, onlycompletecases = TRUE)
+  	    object at samplesize+(1-onlycompletecases)*sum(object at completecases))
+setMethod("completecases", "Estimate", function(object) object at completecases)
 setMethod("asvar", "Estimate", function(object) object at asvar)
 
 setReplaceMethod("asvar", "Estimate", 

Modified: branches/distr-2.2/pkg/distrMod/R/Estimator.R
===================================================================
--- branches/distr-2.2/pkg/distrMod/R/Estimator.R	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/R/Estimator.R	2009-08-25 17:34:02 UTC (rev 549)
@@ -2,7 +2,7 @@
 ## Function to compute estimates
 ###############################################################################
 Estimator <- function(x, estimator, name, Infos, asvar = NULL, nuis.idx,
-                      trafo = NULL, fixed = NULL, asvar.fct, ...){
+                      trafo = NULL, fixed = NULL, asvar.fct, na.rm = TRUE, ...){
 
     name.est <- paste(deparse(substitute(estimator)),sep="",collapse="")     
     es.call <- match.call()
@@ -17,6 +17,9 @@
         colnames(Infos) <- c("method", "message")
     }
 
+    completecases <- complete.cases(x)
+    if(na.rm) x <- na.omit(x)
+
     samplesize <- if(is.null(dim(x))) length(x) else dim(x)[2]
 
 
@@ -79,6 +82,7 @@
     }
 
 
+    res at completecases <- completecases
     return(res)
 }
 

Modified: branches/distr-2.2/pkg/distrMod/R/MCEstimator.R
===================================================================
--- branches/distr-2.2/pkg/distrMod/R/MCEstimator.R	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/R/MCEstimator.R	2009-08-25 17:34:02 UTC (rev 549)
@@ -4,12 +4,14 @@
 MCEstimator <- function(x, ParamFamily, criterion, crit.name, 
                         startPar = NULL, 
                         Infos, trafo = NULL, penalty = 1e20, validity.check = TRUE,
-                        asvar.fct, ...){
+                        asvar.fct, na.rm = TRUE, ...){
 
     ## preparation: getting the matched call
     es.call <- match.call()
     dots <- match.call(expand.dots = FALSE)$"..."
 
+    completecases <- complete.cases(x)
+    if(na.rm) x <- na.omit(x)
 
     ## some checking
     if(!is.numeric(x))
@@ -47,6 +49,7 @@
     
     ## digesting the results of mceCalc
     res <- do.call(.process.meCalcRes, argList)
-
+    res at completecases <- completecases
+    
     return(res)
 }

Modified: branches/distr-2.2/pkg/distrMod/R/MDEstimator.R
===================================================================
--- branches/distr-2.2/pkg/distrMod/R/MDEstimator.R	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/R/MDEstimator.R	2009-08-25 17:34:02 UTC (rev 549)
@@ -4,11 +4,16 @@
 MDEstimator <- function(x, ParamFamily, distance = KolmogorovDist,
                         dist.name,  paramDepDist = FALSE,
                         startPar = NULL,  Infos, 
-                        trafo = NULL, penalty = 1e20, asvar.fct, ...){
+                        trafo = NULL, penalty = 1e20, asvar.fct, na.rm = TRUE,
+                        ...){
 
     ## preparation: getting the matched call
     es.call <- match.call()
     dots <- match.call(expand.dots = FALSE)$"..."
+
+    completecases <- complete.cases(x)
+    if(na.rm) x <- na.omit(x)
+
     ## some checking
     if(!is.numeric(x))
       stop(gettext("'x' has to be a numeric vector"))   
@@ -42,6 +47,7 @@
     ## digesting the results of mceCalc
     res <- do.call(.process.meCalcRes, argList)
 
+    res at completecases <- completecases
     return(res)
 }
 

Modified: branches/distr-2.2/pkg/distrMod/R/MLEstimator.R
===================================================================
--- branches/distr-2.2/pkg/distrMod/R/MLEstimator.R	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/R/MLEstimator.R	2009-08-25 17:34:02 UTC (rev 549)
@@ -5,12 +5,14 @@
 
 ## Maximum-Likelihood estimator
 MLEstimator <- function(x, ParamFamily, startPar = NULL, 
-                        Infos, trafo = NULL, penalty = 1e20, ...){
+                        Infos, trafo = NULL, penalty = 1e20, na.rm = TRUE, ...){
 
     ## preparation: getting the matched call
     es.call <- match.call()
     dots <- match.call(expand.dots = FALSE)$"..."
 
+    completecases <- complete.cases(x)
+    if(na.rm) x <- na.omit(x)
 
     ## some checking
     if(!is.numeric(x))
@@ -46,6 +48,7 @@
     names(res at criterion) <- "negative log-likelihood"
     res at estimate.call <- es.call
     res at name <- "Maximum likelihood estimate"
+    res at completecases <- completecases
     
     return(res)
 }

Modified: branches/distr-2.2/pkg/distrMod/chm/00Index.html
===================================================================
--- branches/distr-2.2/pkg/distrMod/chm/00Index.html	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/chm/00Index.html	2009-08-25 17:34:02 UTC (rev 549)
@@ -139,6 +139,14 @@
 <td>L2 differentiable parametric family</td></tr>
 <tr><td width="25%"><a href="MCEstimate-class.html">coerce,MCEstimate,mle-method</a></td>
 <td>MCEstimate-class.</td></tr>
+<tr><td width="25%"><a href="Estimate-class.html">completecases</a></td>
+<td>Estimate-class.</td></tr>
+<tr><td width="25%"><a href="Estimate-class.html">completecases,Estimate-method</a></td>
+<td>Estimate-class.</td></tr>
+<tr><td width="25%"><a href="Confint-class.html">completecases.estimate</a></td>
+<td>Confint-class</td></tr>
+<tr><td width="25%"><a href="Confint-class.html">completecases.estimate,Confint-method</a></td>
+<td>Confint-class</td></tr>
 <tr><td width="25%"><a href="confint-methods.html">confint</a></td>
 <td>Methods for function confint in Package 'distrMod'</td></tr>
 <tr><td width="25%"><a href="confint-methods.html">confint,ANY,missing-method</a></td>

Modified: branches/distr-2.2/pkg/distrMod/chm/Confint-class.html
===================================================================
--- branches/distr-2.2/pkg/distrMod/chm/Confint-class.html	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/chm/Confint-class.html	2009-08-25 17:34:02 UTC (rev 549)
@@ -16,6 +16,8 @@
 <param name="keyword" value="R:   trafo.estimate,Confint-method">
 <param name="keyword" value="R:   samplesize.estimate">
 <param name="keyword" value="R:   samplesize.estimate,Confint-method">
+<param name="keyword" value="R:   completecases.estimate">
+<param name="keyword" value="R:   completecases.estimate,Confint-method">
 <param name="keyword" value="R:   nuisance.estimate">
 <param name="keyword" value="R:   nuisance.estimate,Confint-method">
 <param name="keyword" value="R:   fixed.estimate">
@@ -60,8 +62,11 @@
 the estimate(s) for which the confidence intervals are produced.</dd>
 <dt><code>name.estimate</code></dt><dd>Object of class <code>"character"</code>:
 the name of the estimate(s) for which the confidence intervals are produced.</dd>
-<dt><code>samplesize.estimate</code></dt><dd>Object of class <code>"numeric"</code>:
-the sample size of the estimate(s) for which the confidence intervals are produced.</dd>
+<dt><code>samplesize.estimate</code>:</dt><dd>Object of class <code>"numeric"</code>:
+the sample size of the estimate(s) for which the confidence intervals
+are (only complete cases) produced.</dd>
+<dt><code>completecases.estimate</code>:</dt><dd>Object of class <code>"logical"</code>:
+complete cases at which the estimate was evaluated. </dd>
 <dt><code>trafo.estimate</code></dt><dd>Object of class <code>"matrix"</code>:
 the trafo/derivative matrix of the estimate(s) for which 
 the confidence intervals are produced.</dd>
@@ -101,10 +106,18 @@
 accessor function for slot <code>trafo.estimate</code>. </dd>
 </p>
 <p>
-<dt>samplesize.estimate</dt><dd><code>signature(object = "Confint")</code>: 
-accessor function for slot <code>samplesize.estimate</code>. </dd>
+<dt>samplesize.estimate</dt><dd><code>signature(object = "Confint")</code>:
+(with additional argument <code>onlycompletecases</code>
+defaulting to <code>TRUE</code> returns the sample size;
+in case there are any incomplete cases and argument
+<code>onlycompletecases</code> is <code>FALSE</code>, the number of
+these is added to slot <code>samplesize</code>. </dd>
 </p>
 <p>
+<dt>completecases.estimate</dt><dd><code>signature(object = "Confint")</code>:
+accessor function for slot <code>completecases.estimate</code>. </dd>
+</p>
+<p>
 <dt>nuisance.estimate</dt><dd><code>signature(object = "Confint")</code>: 
 accessor function for slot <code>nuisance.estimate</code>. </dd>
 </p>

Modified: branches/distr-2.2/pkg/distrMod/chm/Estimate-class.html
===================================================================
--- branches/distr-2.2/pkg/distrMod/chm/Estimate-class.html	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/chm/Estimate-class.html	2009-08-25 17:34:02 UTC (rev 549)
@@ -16,6 +16,8 @@
 <param name="keyword" value="R:   Infos,Estimate-method">
 <param name="keyword" value="R:   samplesize">
 <param name="keyword" value="R:   samplesize,Estimate-method">
+<param name="keyword" value="R:   completecases">
+<param name="keyword" value="R:   completecases,Estimate-method">
 <param name="keyword" value="R:   asvar">
 <param name="keyword" value="R:   asvar,Estimate-method">
 <param name="keyword" value="R:   fixed,Estimate-method">
@@ -71,8 +73,11 @@
 <dt><code>asvar</code></dt><dd> object of class <code>"OptionalNumericOrMatrix"</code>
 which may contain the asymptotic (co)variance of the estimator. </dd>
 <dt><code>samplesize</code></dt><dd> object of class <code>"numeric"</code> &mdash;
-the samplesize at which the estimate was evaluated. </dd>
-<dt><code>nuis.idx</code></dt><dd> object of class <code>"OptionalNumeric"</code>: 
+the samplesize (only complete cases are counted)
+at which the estimate was evaluated. </dd>
+<dt><code>completecases</code></dt><dd> object of class <code>"logical"</code> &mdash;
+complete cases at which the estimate was evaluated. </dd>
+<dt><code>nuis.idx</code></dt><dd> object of class <code>"OptionalNumeric"</code>:
 indices of <code>estimate</code> belonging to the nuisance part. </dd>
 <dt><code>fixed</code></dt><dd> object of class <code>"OptionalNumeric"</code>: 
 the fixed and known part of the parameter. </dd>
@@ -113,10 +118,18 @@
 accessor function for slot <code>estimate.call</code>. </dd>
 </p>
 <p>
-<dt>samplesize</dt><dd><code>signature(object = "Estimate")</code>: 
-accessor function for slot <code>samplesize</code>. </dd>
+<dt>samplesize</dt><dd><code>signature(object = "Estimate")</code>:
+(with additional argument <code>onlycompletecases</code>
+defaulting to <code>TRUE</code> returns the sample size;
+in case there are any incomplete cases and argument
+<code>onlycompletecases</code> is <code>FALSE</code>, the number of
+these is added to slot <code>samplesize</code>. </dd>
 </p>
 <p>
+<dt>completecases</dt><dd><code>signature(object = "Estimate")</code>:
+accessor function for slot <code>completecases</code>. </dd>
+</p>
+<p>
 <dt>asvar</dt><dd><code>signature(object = "Estimate")</code>: 
 accessor function for slot <code>asvar</code>. </dd>
 </p>

Modified: branches/distr-2.2/pkg/distrMod/chm/Estimator.html
===================================================================
--- branches/distr-2.2/pkg/distrMod/chm/Estimator.html	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/chm/Estimator.html	2009-08-25 17:34:02 UTC (rev 549)
@@ -1,10 +1,10 @@
 <html><head><title>Function to compute estimates</title>
-<meta http-equiv="Content-Type" content="text/html; charset=iso-8859-1">
+<meta http-equiv="Content-Type" content="text/html; charset=utf-8">
 <link rel="stylesheet" type="text/css" href="Rchm.css">
-</head>
-<body>
+</head><body>
 
-<table width="100%"><tr><td>Estimator(distrMod)</td><td align="right">R Documentation</td></tr></table><object type="application/x-oleobject" classid="clsid:1e2a7bd0-dab9-11d0-b93a-00c04fc99f9e">
+<table width="100%"><tr><td>Estimator(distrMod)</td><td align="right">R Documentation</td></tr></table>
+<object type="application/x-oleobject" classid="clsid:1e2a7bd0-dab9-11d0-b93a-00c04fc99f9e">
 <param name="keyword" value="R:   Estimator">
 <param name="keyword" value=" Function to compute estimates">
 </object>
@@ -25,7 +25,7 @@
 
 <pre>
 Estimator(x, estimator, name, Infos, asvar = NULL, nuis.idx,
-          trafo = NULL, fixed = NULL, asvar.fct, ...)
+          trafo = NULL, fixed = NULL, asvar.fct, na.rm = TRUE, ...)
 </pre>
 
 
@@ -34,29 +34,29 @@
 <table summary="R argblock">
 <tr valign="top"><td><code>x</code></td>
 <td>
-(empirical) data </td></tr>
+ (empirical) data </td></tr>
 <tr valign="top"><td><code>estimator</code></td>
 <td>
-function: estimator to be evaluated on <code>x</code>. </td></tr>
+ function: estimator to be evaluated on <code>x</code>. </td></tr>
 <tr valign="top"><td><code>name</code></td>
 <td>
-optional name for estimator. </td></tr>
+ optional name for estimator. </td></tr>
 <tr valign="top"><td><code>Infos</code></td>
 <td>
-character: optional informations about estimator </td></tr>
+ character: optional informations about estimator </td></tr>
 <tr valign="top"><td><code>asvar</code></td>
 <td>
-optionally the asymptotic (co)variance of the estimator </td></tr>
+ optionally the asymptotic (co)variance of the estimator </td></tr>
 <tr valign="top"><td><code>nuis.idx</code></td>
 <td>
-optionally the indices of the estimate belonging 
+ optionally the indices of the estimate belonging 
 to nuisance parameter</td></tr>
 <tr valign="top"><td><code>fixed</code></td>
 <td>
-optionally (numeric) the fixed part of the parameter</td></tr>
+ optionally (numeric) the fixed part of the parameter</td></tr>
 <tr valign="top"><td><code>trafo</code></td>
 <td>
-an object of class <code>MatrixorFunction</code> &ndash; a transformation
+ an object of class <code>MatrixorFunction</code> &ndash; a transformation
 for the main parameter</td></tr>
 <tr valign="top"><td><code>asvar.fct</code></td>
 <td>
@@ -65,12 +65,16 @@
 <code>L2Fam</code>((the parametric model as object of class <code>L2ParamFamily</code>)) 
 and <code>param</code> (the parameter value as object of class 
 <code>ParamFamParameter</code>); arguments are called by name; <code>asvar.fct</code>
-may also process further arguments passed through the <code>...</code> argument</td></tr>
+may also process further arguments passed through the <code>...</code> argument</td></tr>              
+<tr valign="top"><td><code>na.rm</code></td>
+<td>
+logical: if  <code>TRUE</code>, the estimator is evaluated at <code>complete.cases(x)</code>.</td></tr>
 <tr valign="top"><td><code>...</code></td>
 <td>
-further arguments to <code>estimator</code>. </td></tr>
+ further arguments to <code>estimator</code>. </td></tr>
 </table>
 
+
 <h3>Details</h3>
 
 <p>
@@ -83,21 +87,19 @@
 <h3>Value</h3>
 
 <p>
-An object of S4-class <code>"Estimate"</code>.</p>
+An object of S4-class <code>"Estimate"</code>.
+</p>
 
+
 <h3>Author(s)</h3>
 
-<p>
-Matthias Kohl <a href="mailto:Matthias.Kohl at stamats.de">Matthias.Kohl at stamats.de</a>,<br>
-Peter Ruckdeschel <a href="mailto:Peter.Ruckdeschel at itwm.fraunhofer.de">Peter.Ruckdeschel at itwm.fraunhofer.de</a>
-</p>
+<p>Matthias Kohl <a href="mailto:Matthias.Kohl at stamats.de">Matthias.Kohl at stamats.de</a>,<br>
+Peter Ruckdeschel <a href="mailto:Peter.Ruckdeschel at itwm.fraunhofer.de">Peter.Ruckdeschel at itwm.fraunhofer.de</a></p>
 
 
 <h3>See Also</h3>
 
-<p>
-<code><a href="Estimate-class.html">Estimate-class</a></code>
-</p>
+<p><code></code> </p>
 
 
 <h3>Examples</h3>
@@ -110,8 +112,15 @@
 Estimator(X, estimator = rowMeans, name = "mean")
 </pre>
 
+<script Language="JScript">
+function findlink(pkg, fn) {
+var Y, link;
+Y = location.href.lastIndexOf("\\") + 1;
+link = location.href.substring(0, Y);
+link = link + "../../" + pkg + "/chtml/" + pkg + ".chm::/" + fn;
+location.href = link;
+}
+</script>
 
-
 <hr><div align="center">[Package <em>distrMod</em> version 2.2 <a href="00Index.html">Index</a>]</div>
-
 </body></html>

Modified: branches/distr-2.2/pkg/distrMod/chm/MCEstimator.html
===================================================================
--- branches/distr-2.2/pkg/distrMod/chm/MCEstimator.html	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/chm/MCEstimator.html	2009-08-25 17:34:02 UTC (rev 549)
@@ -1,10 +1,10 @@
 <html><head><title>Function to compute minimum criterion estimates</title>
-<meta http-equiv="Content-Type" content="text/html; charset=iso-8859-1">
+<meta http-equiv="Content-Type" content="text/html; charset=utf-8">
 <link rel="stylesheet" type="text/css" href="Rchm.css">
-</head>
-<body>
+</head><body>
 
-<table width="100%"><tr><td>MCEstimator(distrMod)</td><td align="right">R Documentation</td></tr></table><object type="application/x-oleobject" classid="clsid:1e2a7bd0-dab9-11d0-b93a-00c04fc99f9e">
+<table width="100%"><tr><td>MCEstimator(distrMod)</td><td align="right">R Documentation</td></tr></table>
+<object type="application/x-oleobject" classid="clsid:1e2a7bd0-dab9-11d0-b93a-00c04fc99f9e">
 <param name="keyword" value="R:   MCEstimator">
 <param name="keyword" value=" Function to compute minimum criterion estimates">
 </object>
@@ -30,7 +30,7 @@
 <pre>
 MCEstimator(x, ParamFamily, criterion, crit.name, 
             startPar = NULL, Infos, trafo = NULL, 
-            penalty = 1e20, validity.check = TRUE, asvar.fct, ...)
+            penalty = 1e20, validity.check = TRUE, asvar.fct, na.rm = TRUE, ...)
 </pre>
 
 
@@ -39,19 +39,19 @@
 <table summary="R argblock">
 <tr valign="top"><td><code>x</code></td>
 <td>
-(empirical) data </td></tr>
+ (empirical) data </td></tr>
 <tr valign="top"><td><code>ParamFamily</code></td>
 <td>
-object of class <code>"ParamFamily"</code> </td></tr>
+ object of class <code>"ParamFamily"</code> </td></tr>
 <tr valign="top"><td><code>criterion</code></td>
 <td>
-function: criterion to minimize; see Details section. </td></tr>
+ function: criterion to minimize; see Details section. </td></tr>
 <tr valign="top"><td><code>crit.name</code></td>
 <td>
-optional name for criterion. </td></tr>
+ optional name for criterion. </td></tr>
 <tr valign="top"><td><code>startPar</code></td>
 <td>
-initial information used by <code>optimize</code> resp. <code>optim</code>;
+ initial information used by <code>optimize</code> resp. <code>optim</code>;
 i.e; if (total) parameter is of length 1, <code>startPar</code> is 
 a search interval, else it is an initial parameter value; if <code>NULL</code>
 slot <code>startPar</code> of <code>ParamFamily</code> is used to produce it;
@@ -59,10 +59,10 @@
 in which case slot <code>untransformed.estimate</code> is used.</td></tr>
 <tr valign="top"><td><code>Infos</code></td>
 <td>
-character: optional informations about estimator </td></tr>
+ character: optional informations about estimator </td></tr>
 <tr valign="top"><td><code>trafo</code></td>
 <td>
-an object of class <code>MatrixorFunction</code> &ndash; a transformation
+ an object of class <code>MatrixorFunction</code> &ndash; a transformation
 for the main parameter</td></tr>
 <tr valign="top"><td><code>penalty</code></td>
 <td>
@@ -78,19 +78,23 @@
 <code>L2Fam</code>((the parametric model as object of class <code>L2ParamFamily</code>)) 
 and <code>param</code> (the parameter value as object of class 
 <code>ParamFamParameter</code>); arguments are called by name; <code>asvar.fct</code>
-may also process further arguments passed through the <code>...</code> argument</td></tr>
+may also process further arguments passed through the <code>...</code> argument</td></tr>              
+<tr valign="top"><td><code>na.rm</code></td>
+<td>
+logical: if  <code>TRUE</code>, the estimator is evaluated at <code>complete.cases(x)</code>.</td></tr>
 <tr valign="top"><td><code>...</code></td>
 <td>
-further arguments to <code>criterion</code> or <code>optimize</code> 
+ further arguments to <code>criterion</code> or <code>optimize</code>
 or <code>optim</code>, respectively. </td></tr>
 </table>
 
+
 <h3>Details</h3>
 
 <p>
 The argument <code>criterion</code> has to be a function with arguments the 
 empirical data as well as an object of class <code>"Distribution"</code> 
-and possibly <code>...</code>. Uses <code><a href="mleCalc-methods.html">mceCalc</a></code>
+and possibly <code>...</code>. Uses <code></code>
 for method dispatch.
 </p>
 
@@ -99,33 +103,29 @@
 
 <p>
 An object of S4-class <code>"MCEstimate"</code> which inherits from class 
-<code>"Estimate"</code>.</p>
+<code>"Estimate"</code>.
+</p>
 
+
 <h3>Note</h3>
 
-<p>
-The criterion function may be called together with a parameter <code>thetaPar</code>
+<p>The criterion function may be called together with a parameter <code>thetaPar</code>
 which is the current parameter value under consideration, i.e.; the value
 under which the model distribution is considered. Hence, if desired,
 particular criterion functions could make use of this information, by, say
-computing the criterion differently for different parameter values.
-</p>
+computing the criterion differently for different parameter values.</p>
 
 
 <h3>Author(s)</h3>
 
-<p>
-Matthias Kohl <a href="mailto:Matthias.Kohl at stamats.de">Matthias.Kohl at stamats.de</a>,<br>
-Peter Ruckdeschel <a href="mailto:Peter.Ruckdeschel at itwm.fraunhofer.de">Peter.Ruckdeschel at itwm.fraunhofer.de</a>
-</p>
+<p>Matthias Kohl <a href="mailto:Matthias.Kohl at stamats.de">Matthias.Kohl at stamats.de</a>,<br>
+Peter Ruckdeschel <a href="mailto:Peter.Ruckdeschel at itwm.fraunhofer.de">Peter.Ruckdeschel at itwm.fraunhofer.de</a></p>
 
 
 <h3>See Also</h3>
 
-<p>
-<code><a href="ParamFamily-class.html">ParamFamily-class</a></code>, <code><a href="ParamFamily.html">ParamFamily</a></code>, 
-<code><a href="MCEstimate-class.html">MCEstimate-class</a></code>
-</p>
+<p><code></code>, <code></code>, 
+<code></code> </p>
 
 
 <h3>Examples</h3>
@@ -174,8 +174,15 @@
 #            asis.smooth.discretize = "smooth", crit.name = "Hellinger distance")
 </pre>
 
+<script Language="JScript">
+function findlink(pkg, fn) {
+var Y, link;
+Y = location.href.lastIndexOf("\\") + 1;
+link = location.href.substring(0, Y);
+link = link + "../../" + pkg + "/chtml/" + pkg + ".chm::/" + fn;
+location.href = link;
+}
+</script>
 
-
 <hr><div align="center">[Package <em>distrMod</em> version 2.2 <a href="00Index.html">Index</a>]</div>
-
 </body></html>

Modified: branches/distr-2.2/pkg/distrMod/chm/MDEstimator.html
===================================================================
--- branches/distr-2.2/pkg/distrMod/chm/MDEstimator.html	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/chm/MDEstimator.html	2009-08-25 17:34:02 UTC (rev 549)
@@ -26,7 +26,7 @@
 <pre>
 MDEstimator(x, ParamFamily, distance = KolmogorovDist, dist.name, 
             paramDepDist = FALSE, startPar = NULL,  Infos, trafo = NULL,
-            penalty = 1e20, asvar.fct, ...)
+            penalty = 1e20, asvar.fct, na.rm = TRUE, ...)
 </pre>
 
 
@@ -78,9 +78,12 @@
 and <code>param</code> (the parameter value as object of class 
 <code>ParamFamParameter</code>); arguments are called by name; <code>asvar.fct</code>
 may also process further arguments passed through the <code>...</code> argument</td></tr>              
+<tr valign="top"><td><code>na.rm</code></td>
+<td>
+logical: if  <code>TRUE</code>, the estimator is evaluated at <code>complete.cases(x)</code>.</td></tr>
 <tr valign="top"><td><code>...</code></td>
 <td>
- further arguments to <code>criterion</code> or <code>optimize</code> 
+ further arguments to <code>criterion</code> or <code>optimize</code>
 or <code>optim</code>, respectively. </td></tr>
 </table>
 

Modified: branches/distr-2.2/pkg/distrMod/chm/MLEstimator.html
===================================================================
--- branches/distr-2.2/pkg/distrMod/chm/MLEstimator.html	2009-08-25 15:48:12 UTC (rev 548)
+++ branches/distr-2.2/pkg/distrMod/chm/MLEstimator.html	2009-08-25 17:34:02 UTC (rev 549)
@@ -1,10 +1,10 @@
 <html><head><title>Function to compute maximum likelihood estimates</title>
-<meta http-equiv="Content-Type" content="text/html; charset=iso-8859-1">
+<meta http-equiv="Content-Type" content="text/html; charset=utf-8">
 <link rel="stylesheet" type="text/css" href="Rchm.css">
-</head>
-<body>
+</head><body>
 
-<table width="100%"><tr><td>MLEstimator(distrMod)</td><td align="right">R Documentation</td></tr></table><object type="application/x-oleobject" classid="clsid:1e2a7bd0-dab9-11d0-b93a-00c04fc99f9e">
+<table width="100%"><tr><td>MLEstimator(distrMod)</td><td align="right">R Documentation</td></tr></table>
+<object type="application/x-oleobject" classid="clsid:1e2a7bd0-dab9-11d0-b93a-00c04fc99f9e">
 <param name="keyword" value="R:   MLEstimator">
 <param name="keyword" value=" Function to compute maximum likelihood estimates">
 </object>
@@ -27,7 +27,7 @@
 
 <pre>
 MLEstimator(x, ParamFamily, startPar = NULL, 
-            Infos, trafo = NULL, penalty = 1e20, ...)
+            Infos, trafo = NULL, penalty = 1e20, na.rm = TRUE, ...)
 </pre>
 
 
@@ -36,13 +36,13 @@
 <table summary="R argblock">
 <tr valign="top"><td><code>x</code></td>
 <td>
-(empirical) data </td></tr>
+ (empirical) data </td></tr>
 <tr valign="top"><td><code>ParamFamily</code></td>
 <td>
-object of class <code>"ParamFamily"</code> </td></tr>
+ object of class <code>"ParamFamily"</code> </td></tr>
 <tr valign="top"><td><code>startPar</code></td>
 <td>
-initial information used by <code>optimize</code> resp. <code>optim</code>;
+ initial information used by <code>optimize</code> resp. <code>optim</code>;
 i.e; if (total) parameter is of length 1, <code>startPar</code> is 
 a search interval, else it is an initial parameter value; if <code>NULL</code>
 slot <code>startPar</code> of <code>ParamFamily</code> is used to produce it;
@@ -50,27 +50,31 @@
 in which case slot <code>untransformed.estimate</code> is used.</td></tr>
 <tr valign="top"><td><code>Infos</code></td>
 <td>
-character: optional informations about estimator </td></tr>
+ character: optional informations about estimator </td></tr>
 <tr valign="top"><td><code>trafo</code></td>
 <td>
-an object of class <code>MatrixorFunction</code> &ndash; a transformation
+ an object of class <code>MatrixorFunction</code> &ndash; a transformation
 for the main parameter</td></tr>
 <tr valign="top"><td><code>penalty</code></td>
 <td>
 (non-negative) numeric: penalizes non valid parameter-values</td></tr>
+<tr valign="top"><td><code>na.rm</code></td>
+<td>
+logical: if  <code>TRUE</code>, the estimator is evaluated at <code>complete.cases(x)</code>.</td></tr>
 <tr valign="top"><td><code>...</code></td>
 <td>
-further arguments to <code>criterion</code> or <code>optimize</code> 
+ further arguments to <code>criterion</code> or <code>optimize</code>
 or <code>optim</code>, respectively. </td></tr>
 </table>
 
+
 <h3>Details</h3>
 
 <p>
-The function uses <code><a href="mleCalc-methods.html">mleCalc</a></code>
+The function uses <code></code>
 for method dispatch; this method by default  
-calls <code><a href="mleCalc-methods.html">mceCalc</a></code> using the negative log-likelihood
-as criterion which should be minimized.
+calls <code></code> using the negative log-likelihood
+as criterion which should be minimized. 
 </p>
 
 
@@ -78,23 +82,21 @@
 
 <p>
[TRUNCATED]

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


More information about the Distr-commits mailing list