[Robast-commits] r143 - in branches/robast-0.6/pkg/RobLox: . R

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Mon Aug 4 12:39:21 CEST 2008


Author: stamats
Date: 2008-08-04 12:39:21 +0200 (Mon, 04 Aug 2008)
New Revision: 143

Modified:
   branches/robast-0.6/pkg/RobLox/DESCRIPTION
   branches/robast-0.6/pkg/RobLox/R/colRoblox.R
   branches/robast-0.6/pkg/RobLox/R/roblox.R
   branches/robast-0.6/pkg/RobLox/R/rowRoblox.R
Log:
adapted to new implementation of class "Estimate" ...

Modified: branches/robast-0.6/pkg/RobLox/DESCRIPTION
===================================================================
--- branches/robast-0.6/pkg/RobLox/DESCRIPTION	2008-08-04 10:36:32 UTC (rev 142)
+++ branches/robast-0.6/pkg/RobLox/DESCRIPTION	2008-08-04 10:39:21 UTC (rev 143)
@@ -1,6 +1,6 @@
 Package: RobLox
 Version: 0.6.0
-Date: 2008-07-28
+Date: 2008-08-04
 Title: Optimally robust influence curves for location and scale
 Description: functions for the determination of optimally 
     robust influence curves in case of normal

Modified: branches/robast-0.6/pkg/RobLox/R/colRoblox.R
===================================================================
--- branches/robast-0.6/pkg/RobLox/R/colRoblox.R	2008-08-04 10:36:32 UTC (rev 142)
+++ branches/robast-0.6/pkg/RobLox/R/colRoblox.R	2008-08-04 10:39:21 UTC (rev 143)
@@ -2,6 +2,7 @@
 ## Evaluate roblox on columns of a matrix
 ###############################################################################
 colRoblox <- function(x, mean, sd, eps, eps.lower, eps.upper, initial.est, k = 1){
+    call.est <- match.call()
     if(missing(x))
         stop("'x' is missing with no default")
     if(is.data.frame(x))
@@ -12,6 +13,8 @@
         stop("'x' has to be a matrix resp. convertable to a matrix by 'as.matrix'
               or 'data.matrix'")
 
-    return(rowRoblox(x = t(x), mean = mean, sd = sd, eps = eps, eps.lower = eps.lower,
-                     eps.upper = eps.upper, initial.est = initial.est, k = k))
+    res <- rowRoblox(x = t(x), mean = mean, sd = sd, eps = eps, eps.lower = eps.lower,
+                     eps.upper = eps.upper, initial.est = initial.est, k = k)
+    res at estimate.call <- call.est
+    return(res)
 }

Modified: branches/robast-0.6/pkg/RobLox/R/roblox.R
===================================================================
--- branches/robast-0.6/pkg/RobLox/R/roblox.R	2008-08-04 10:36:32 UTC (rev 142)
+++ branches/robast-0.6/pkg/RobLox/R/roblox.R	2008-08-04 10:39:21 UTC (rev 143)
@@ -308,14 +308,14 @@
                                       info = c("roblox", "optimally robust IC for AL estimators and 'asMSE'"),
                                       w = w, biastype = symmetricBias(), normtype = NormType(),
                                       modifyIC = modIC))
-                return(new("kStepEstimate", name = "Optimally robust estimate",
-                               estimate.call = es.call,
-                           estimate = robEst$est, samplesize = length(x), asvar = robEst$asvar,
+                return(new("kStepEstimate", name = "Optimally robust estimate", 
+                           estimate.call = es.call, estimate = robEst$est, 
+                           samplesize = length(x), asvar = robEst$asvar,
                            asbias = r*robEst$b, steps = k, pIC = IC1, Infos = Info.matrix))
             }else
-                return(new("kStepEstimate", name = "Optimally robust estimate",
-                               estimate.call = es.call,
-                           estimate = robEst$est, samplesize = length(x), asvar = robEst$asvar,
+                return(new("kStepEstimate", name = "Optimally robust estimate", 
+                           estimate.call = es.call, estimate = robEst$est, 
+                           samplesize = length(x), asvar = robEst$asvar,
                            asbias = r*robEst$b, steps = k, pIC = NULL, Infos = Info.matrix))
         }else{
             sqrtn <- sqrt(length(x))
@@ -422,14 +422,14 @@
                                       paste("least favorable contamination: ", round(r/sqrtn, 3), sep = ""),
                                       paste("maximum MSE-inefficiency: ", round(ineff, 3), sep = "")), 
                                       ncol = 2, dimnames = list(NULL, c("method", "message")))
-                return(new("kStepEstimate", name = "Optimally robust estimate",
-                               estimate.call = es.call,
-                           estimate = robEst$est, samplesize = length(x), asvar = robEst$asvar,
+                return(new("kStepEstimate", name = "Optimally robust estimate", 
+                           estimate.call = es.call, estimate = robEst$est, 
+                           samplesize = length(x), asvar = robEst$asvar,
                            asbias = r*robEst$b, steps = k, pIC = IC1, Infos = Info.matrix))
             }else
-                return(new("kStepEstimate", name = "Optimally robust estimate",
-                               estimate.call = es.call,
-                           estimate = robEst$est, samplesize = length(x), asvar = robEst$asvar,
+                return(new("kStepEstimate", name = "Optimally robust estimate", 
+                           estimate.call = es.call, estimate = robEst$est, 
+                           samplesize = length(x), asvar = robEst$asvar,
                            asbias = r*robEst$b, steps = k, pIC = NULL, Infos = Info.matrix))
         }
     }else{
@@ -488,15 +488,13 @@
                                           w = w, biastype = symmetricBias(), normtype = NormType(),
                                           modifyIC = modIC))
                     return(new("kStepEstimate", name = "Optimally robust estimate",
-                               estimate.call = es.call,
-                               estimate = robEst, samplesize = length(x), 
-                               asvar = as.matrix(A-r^2*b^2),
+                               estimate.call = es.call, estimate = robEst, 
+                               samplesize = length(x), asvar = as.matrix(A-r^2*b^2),
                                asbias = r*b, steps = k, pIC = IC1, Infos = Info.matrix))
                 }else
                     return(new("kStepEstimate", name = "Optimally robust estimate",
-                               estimate.call = es.call,
-                               estimate = robEst, samplesize = length(x), 
-                               asvar = as.matrix(A-r^2*b^2),
+                               estimate.call = es.call, estimate = robEst, 
+                               samplesize = length(x), asvar = as.matrix(A-r^2*b^2),
                                asbias = r*b, steps = k, pIC = NULL, Infos = Info.matrix))
             }else{
                 sqrtn <- sqrt(length(x))
@@ -566,15 +564,13 @@
                                  paste("maximum MSE-inefficiency: ", round(ineff, 3), sep = "")), 
                                  ncol = 2, dimnames = list(NULL, c("method", "message")))
                     return(new("kStepEstimate", name = "Optimally robust estimate",
-                               estimate.call = es.call,
-                               estimate = robEst, samplesize = length(x), 
-                               asvar = as.matrix(A-r^2*b^2),
+                               estimate.call = es.call, estimate = robEst, 
+                               samplesize = length(x), asvar = as.matrix(A-r^2*b^2),
                                asbias = r*b, steps = k, pIC = IC1, Infos = Info.matrix))
                 }else
                     return(new("kStepEstimate", name = "Optimally robust estimate",
-                               estimate.call = es.call,
-                               estimate = robEst, samplesize = length(x), 
-                               asvar = as.matrix(A-r^2*b^2),
+                               estimate.call = es.call, estimate = robEst, 
+                               samplesize = length(x), asvar = as.matrix(A-r^2*b^2),
                                asbias = r*b, steps = k, pIC = NULL, Infos = Info.matrix))
             }
         }
@@ -658,15 +654,13 @@
                                           w = w, biastype = symmetricBias(), normtype = NormType(),
                                           modifyIC = modIC))
                     return(new("kStepEstimate", name = "Optimally robust estimate",
-                               estimate.call = es.call,
-                               estimate = robEst$est, samplesize = length(x), 
-                               asvar = as.matrix(robEst$A-r^2*robEst$b^2),
+                               estimate.call = es.call, estimate = robEst$est, 
+                               samplesize = length(x), asvar = as.matrix(robEst$A-r^2*robEst$b^2),
                                asbias = r*robEst$b, steps = k, pIC = IC1, Infos = Info.matrix))
                 }else
                     return(new("kStepEstimate", name = "Optimally robust estimate",
-                               estimate.call = es.call,
-                               estimate = robEst$est, samplesize = length(x), 
-                               asvar = as.matrix(robEst$A-r^2*robEst$b^2),
+                               estimate.call = es.call, estimate = robEst$est, 
+                               samplesize = length(x), asvar = as.matrix(robEst$A-r^2*robEst$b^2),
                                asbias = r*robEst$b, steps = k, pIC = NULL, Infos = Info.matrix))
             }else{
                 sqrtn <- sqrt(length(x))
@@ -758,15 +752,13 @@
                                  paste("maximum MSE-inefficiency: ", round(ineff, 3), sep = "")), 
                                  ncol = 2, dimnames = list(NULL, c("method", "message")))
                     return(new("kStepEstimate", name = "Optimally robust estimate",
-                               estimate.call = es.call,
-                               estimate = robEst$est, samplesize = length(x), 
-                               asvar = as.matrix(robEst$A-r^2*robEst$b^2),
+                               estimate.call = es.call, estimate = robEst$est, 
+                               samplesize = length(x), asvar = as.matrix(robEst$A-r^2*robEst$b^2),
                                asbias = r*robEst$b, steps = k, pIC = IC1, Infos = Info.matrix))
                 }else
                     return(new("kStepEstimate", name = "Optimally robust estimate",
-                               estimate.call = es.call,
-                               estimate = robEst$est, samplesize = length(x), 
-                               asvar = as.matrix(robEst$A-r^2*robEst$b^2),
+                               estimate.call = es.call, estimate = robEst$est, 
+                               samplesize = length(x), asvar = as.matrix(robEst$A-r^2*robEst$b^2),
                                asbias = r*robEst$b, steps = k, pIC = NULL, Infos = Info.matrix))
             }
         }

Modified: branches/robast-0.6/pkg/RobLox/R/rowRoblox.R
===================================================================
--- branches/robast-0.6/pkg/RobLox/R/rowRoblox.R	2008-08-04 10:36:32 UTC (rev 142)
+++ branches/robast-0.6/pkg/RobLox/R/rowRoblox.R	2008-08-04 10:39:21 UTC (rev 143)
@@ -72,6 +72,7 @@
 ## Evaluate roblox on rows of a matrix
 ###############################################################################
 rowRoblox <- function(x, mean, sd, eps, eps.lower, eps.upper, initial.est, k = 1){
+    es.call <- match.call()
     if(missing(x))
         stop("'x' is missing with no default")
     if(is.data.frame(x))
@@ -158,7 +159,8 @@
                                           "and 'asMSE'")),
                                   ncol = 2, dimnames = list(NULL, c("method", "message")))
             return(new("kStepEstimate", name = "Optimally robust estimate",
-                       estimate = robEst$est, samplesize = ncol(x), steps = k, 
+                       estimate.call = es.call, estimate = robEst$est, 
+                       samplesize = ncol(x), steps = k, 
                        pIC = NULL, Infos = Info.matrix))
 ## we need a class like "list of estimates" to set asvar and asbias consistently ...
 #            return(new("kStepEstimate", name = "Optimally robust estimate",
@@ -209,7 +211,8 @@
                                   paste("maximum MSE-inefficiency: ", round(ineff[1], 3), sep = "")), 
                                   ncol = 2, dimnames = list(NULL, c("method", "message")))
             return(new("kStepEstimate", name = "Optimally robust estimate",
-                       estimate = robEst$est, samplesize = ncol(x), steps = k, 
+                       estimate.call = es.call, estimate = robEst$est, #
+                       samplesize = ncol(x), steps = k, 
                        pIC = NULL, Infos = Info.matrix))
 ## we need a class like "list of estimates" to set asvar and asbias consistently ...
 #            return(new("kStepEstimate", name = "Optimally robust estimate",
@@ -252,7 +255,8 @@
                                               "and 'asMSE'")),
                                       ncol = 2, dimnames = list(NULL, c("method", "message")))
                 return(new("kStepEstimate", name = "Optimally robust estimate",
-                           estimate = robEst, samplesize = ncol(x), steps = k, 
+                           estimate.call = es.call, estimate = robEst, 
+                           samplesize = ncol(x), steps = k, 
                            pIC = NULL, Infos = Info.matrix))
 ## we need a class like "list of estimates" to set asvar and asbias consistently ...
 #                return(new("kStepEstimate", name = "Optimally robust estimate",
@@ -294,7 +298,8 @@
                                       paste("maximum MSE-inefficiency: ", round(ineff[1], 3), sep = "")), 
                                       ncol = 2, dimnames = list(NULL, c("method", "message")))
                 return(new("kStepEstimate", name = "Optimally robust estimate",
-                           estimate = robEst, samplesize = ncol(x), steps = k, 
+                           estimate.call = es.call, estimate = robEst, 
+                           samplesize = ncol(x), steps = k, 
                            pIC = NULL, Infos = Info.matrix))
 ## we need a class like "list of estimates" to set asvar and asbias consistently ...
 #                return(new("kStepEstimate", name = "Optimally robust estimate",
@@ -342,7 +347,8 @@
                                               "and 'asMSE'")),
                                       ncol = 2, dimnames = list(NULL, c("method", "message")))
                 return(new("kStepEstimate", name = "Optimally robust estimate",
-                           estimate = robEst$est, samplesize = ncol(x), steps = k, 
+                           estimate.call = es.call, estimate = robEst$est, 
+                           samplesize = ncol(x), steps = k, 
                            pIC = NULL, Infos = Info.matrix))
 ## we need a class like "list of estimates" to set asvar and asbias consistently ...
 #                return(new("kStepEstimate", name = "Optimally robust estimate",
@@ -387,7 +393,8 @@
                                       paste("maximum MSE-inefficiency: ", round(ineff[1], 3), sep = "")), 
                                       ncol = 2, dimnames = list(NULL, c("method", "message")))
                 return(new("kStepEstimate", name = "Optimally robust estimate",
-                           estimate = robEst$est, samplesize = ncol(x), steps = k, 
+                           estimate.call = es.call, estimate = robEst$est, 
+                           samplesize = ncol(x), steps = k, 
                            pIC = NULL, Infos = Info.matrix))
 ## we need a class like "list of estimates" to set asvar and asbias consistently ...
 #                return(new("kStepEstimate", name = "Optimally robust estimate",



More information about the Robast-commits mailing list