[Robast-commits] r617 - in branches/robast-0.9/pkg/RobAStBase: . R man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Sat Feb 23 22:54:42 CET 2013


Author: ruckdeschel
Date: 2013-02-23 22:54:42 +0100 (Sat, 23 Feb 2013)
New Revision: 617

Added:
   branches/robast-0.9/pkg/RobAStBase/R/move2bckRefParam.R
   branches/robast-0.9/pkg/RobAStBase/man/mov2bckRef-methods.Rd
Modified:
   branches/robast-0.9/pkg/RobAStBase/NAMESPACE
   branches/robast-0.9/pkg/RobAStBase/R/AllGeneric.R
   branches/robast-0.9/pkg/RobAStBase/R/InfluenceCurve.R
   branches/robast-0.9/pkg/RobAStBase/R/kStepEstimator.R
   branches/robast-0.9/pkg/RobAStBase/man/InfluenceCurve-class.Rd
   branches/robast-0.9/pkg/RobAStBase/man/internals.Rd
   branches/robast-0.9/pkg/RobAStBase/man/kStepEstimator.Rd
Log:
RobAStBase: 
+ new S4methods/functions moveL2Fam2RefParam and moveICBackFromRefParam to only solve optimization problems for  ICs at reference parameters (if these are available) and the to backtransform the IC to the original parameter (is not yet in place in optIC; still testing necessary).
+ the accessor to slot Risks now checks if all items of the list are already evaluated or if some calls still have to be forced; to this end it uses new auxiliary .evalListRec
+ in kStepEstimator one can now delay evaluations of covariance matrices, depending on new argument  withEvalAsVar



Modified: branches/robast-0.9/pkg/RobAStBase/NAMESPACE
===================================================================
--- branches/robast-0.9/pkg/RobAStBase/NAMESPACE	2013-02-17 00:57:24 UTC (rev 616)
+++ branches/robast-0.9/pkg/RobAStBase/NAMESPACE	2013-02-23 21:54:42 UTC (rev 617)
@@ -59,6 +59,8 @@
               "Mroot","kStepEstimator.start")
 exportMethods("pICList","ICList", "ksteps", "uksteps", 
               "start", "startval", "ustartval")
+exportMethods("moveL2Fam2RefParam",
+			  "moveICBackFromRefParam")			  
 exportMethods("ddPlot", "qqplot")
 exportMethods("cutoff.quantile", "cutoff.quantile<-")
 exportMethods("samplesize<-", "samplesize")

Modified: branches/robast-0.9/pkg/RobAStBase/R/AllGeneric.R
===================================================================
--- branches/robast-0.9/pkg/RobAStBase/R/AllGeneric.R	2013-02-17 00:57:24 UTC (rev 616)
+++ branches/robast-0.9/pkg/RobAStBase/R/AllGeneric.R	2013-02-23 21:54:42 UTC (rev 617)
@@ -217,9 +217,6 @@
 if(!isGeneric("radius")){
     setGeneric("radius", function(object) standardGeneric("radius"))
 }
-if(!isGeneric("radius")){
-    setGeneric("radius", function(object) standardGeneric("radius"))
-}
 
 if(!isGeneric("samplesize<-")){
     setGeneric("samplesize<-",
@@ -229,3 +226,12 @@
     setGeneric("getRiskFctBV", function(risk, biastype) standardGeneric("getRiskFctBV"))
 }
 
+if(!isGeneric("moveL2Fam2RefParam")){
+    setGeneric("moveL2Fam2RefParam", function(L2Fam, ...)
+                standardGeneric("moveL2Fam2RefParam"))
+}
+
+if(!isGeneric("moveICBackFromRefParam")){
+    setGeneric("moveICBackFromRefParam", function(IC, L2Fam, ...)
+               standardGeneric("moveICBackFromRefParam"))
+}

Modified: branches/robast-0.9/pkg/RobAStBase/R/InfluenceCurve.R
===================================================================
--- branches/robast-0.9/pkg/RobAStBase/R/InfluenceCurve.R	2013-02-17 00:57:24 UTC (rev 616)
+++ branches/robast-0.9/pkg/RobAStBase/R/InfluenceCurve.R	2013-02-23 21:54:42 UTC (rev 617)
@@ -28,10 +28,26 @@
     return(IC1)
 }
 
+### helper function to recursively evaluate list
+.evalListRec <- function(list0){ ## a list
+    len <- length(list0)
+    for(i in 1:len) {
+        if(is.list(list0[[i]])){ list0[[i]] <- .evalListRec(list0[[i]])
+           }else list0[[i]] <- eval(list0[[i]])
+    }
+    return(list0)
+}
+
 ## access methods
 setMethod("name", "InfluenceCurve", function(object) object at name)
 setMethod("Curve", "InfluenceCurve", function(object) object at Curve)
-setMethod("Risks", "InfluenceCurve", function(object) object at Risks)
+setMethod("Risks", "InfluenceCurve", function(object){
+            risks <- object at Risks
+            risks <- .evalListRec(risks)
+            eval.parent(object at Risks <- risks)
+            risks
+})
+
 setMethod("Infos", "InfluenceCurve", function(object) object at Infos)
 
 ## add risk or information

Modified: branches/robast-0.9/pkg/RobAStBase/R/kStepEstimator.R
===================================================================
--- branches/robast-0.9/pkg/RobAStBase/R/kStepEstimator.R	2013-02-17 00:57:24 UTC (rev 616)
+++ branches/robast-0.9/pkg/RobAStBase/R/kStepEstimator.R	2013-02-23 21:54:42 UTC (rev 617)
@@ -14,7 +14,7 @@
                            withICList = getRobAStBaseOption("withICList"),
                            withPICList = getRobAStBaseOption("withPICList"),
                            na.rm = TRUE, startArgList = NULL, ...,
-                           withLogScale = TRUE){
+                           withLogScale = TRUE, withEvalAsVar = TRUE){
 
         if(missing(IC.UpdateInKer)) IC.UpdateInKer <- NULL
 ## save call
@@ -96,14 +96,20 @@
         pICList <- if(withPICList) vector("list", steps) else NULL
         ICList  <- if(withICList)  vector("list", steps) else NULL
 
+        cvar.fct <- function(L2, IC, dim, dimn =NULL){
+                if(is.null(dimn)){
+                   return(matrix(E(L2, IC %*% t(IC)),dim,dim))
+                }else{
+                   return(matrix(E(L2, IC %*% t(IC)),dim,dim, dimnames = dimn))
+                }
+        }
+
         ### update - function
         updateStep <- function(u.theta, theta, IC, L2Fam, Param,
                                withModif = TRUE, with.u.var = FALSE){
 
                 IC.c <- as(diag(p) %*% IC at Curve, "EuclRandVariable")
 
-
-
 #                print(theta)
                 tf <- trafo(L2Fam, Param)
                 Dtau <- tf$mat
@@ -161,18 +167,29 @@
                 var0 <- u.var <- NULL
                 if(with.u.var){
                    cnms <-  if(is.null(names(u.theta))) colnames(Dtau) else names(u.theta)
-                   if(!is.null(IC.tot.0))
-                      u.var <- matrix(E(L2Fam, IC.tot.0 %*% t(IC.tot.0)),
-                                  k,k, dimnames = list(cnms,cnms))
-                   if(!var.to.be.c)
-                       var0 <- matrix(E(L2Fam, IC.c %*% t(IC.c)),p,p)
+                   if(!is.null(IC.tot.0)){
+                      u.var <- substitute(do.call(cfct, args = list(L2F0, IC0,
+                                   dim0, dimn0)), list(cfct = cvar.fct,
+                                   L2F0 = L2Fam, IC0 = IC.tot.0, dim0 = k,
+                                   dimn0 = list(cnms,cnms)))
+                      if(withEvalAsVar) u.var <- eval(u.var)
+                     #         matrix(E(L2Fam, IC.tot.0 %*% t(IC.tot.0)),
+                     #             k,k, dimnames = list(cnms,cnms))
+                   }
+                   if(!var.to.be.c){
+                      var0 <- substitute(do.call(cfct, args = list(L2F0, IC0,
+                                   dim0, dimn0)), list(cfct = cvar.fct,
+                                   L2F0 = L2Fam, IC0 = IC.c, dim0 = p))
+                      if(withEvalAsVar) var0 <- eval(var0)
+                   }
                 }
 
                 if(withModif){
                    main(Param)[] <- .deleteDim(u.theta[idx])
                    if (lnx) nuisance(Param)[] <- .deleteDim(u.theta[nuis.idx])
 #                   print(L2Fam)
-                   L2Fam <- modifyModel(L2Fam, Param)
+                   L2Fam <- modifyModel(L2Fam, Param,
+                               .withL2derivDistr = L2Fam at .withEvalL2derivDistr)
 #                   print(L2Fam)
                    IC <- modifyIC(IC)(L2Fam, IC)
 #                   print(IC)
@@ -230,10 +247,10 @@
               Param <- upd$Param
               tf <- trafo(L2Fam, Param)
               Infos <- rbind(Infos, c("kStepEstimator",
-                  "computation of IC, trafo, asvar and asbias via useLast = TRUE"))
+               "computation of IC, trafo, asvar and asbias via useLast = TRUE"))
            }else{
               Infos <- rbind(Infos, c("kStepEstimator",
-                       "computation of IC, trafo, asvar and asbias via useLast = FALSE"))
+               "computation of IC, trafo, asvar and asbias via useLast = FALSE"))
            }
         }else{
            if(steps > 1)
@@ -286,7 +303,8 @@
         }else{
                 if(is(IC, "HampIC")){
                     r <- neighborRadius(IC)
-                    asBias <- r*getRiskIC(IC, risk = asBias(), neighbor = neighbor(IC))$asBias$value
+                    asBias <- r*getRiskIC(IC, risk = asBias(),
+                                          neighbor = neighbor(IC))$asBias$value
                 }else{
                     asBias <- NULL
                 }
@@ -305,20 +323,18 @@
           asVar <- asVar[idx,idx,drop=FALSE]
 #          print(asVar)
           names(theta) <- nms.theta.idx
-          dimnames(asVar) <- list(nms.theta.idx,nms.theta.idx)
+          dimnames(asVar) <- list(nms.theta.idx, nms.theta.idx)
         }
 
         return(new("kStepEstimate", estimate.call = es.call,
-                       name = paste(steps, "-step estimate", sep = ""),
-                       estimate = theta, samplesize = nrow(x0), asvar = asVar,
-                       trafo = tf, fixed = fixed,
-                       nuis.idx = nuis.idx, untransformed.estimate = u.theta,
-                       completecases = completecases,
-                       untransformed.asvar = u.var,
-                       asbias = asBias, pIC = IC, steps = steps, Infos = Infos,
-                       start = start, startval = start.val, ustartval = u.start.val,
-                       ksteps = ksteps, uksteps = uksteps,
-                       pICList = pICList, ICList = ICList))
+                name = paste(steps, "-step estimate", sep = ""),
+                estimate = theta, samplesize = nrow(x0), asvar = asVar,
+                trafo = tf, fixed = fixed, nuis.idx = nuis.idx,
+                untransformed.estimate = u.theta, completecases = completecases,
+                untransformed.asvar = u.var, asbias = asBias, pIC = IC,
+                steps = steps, Infos = Infos, start = start,
+                startval = start.val, ustartval = u.start.val, ksteps = ksteps,
+                uksteps = uksteps, pICList = pICList, ICList = ICList))
 }
 #  (est1.NS <- kStepEstimator(x, IC2.NS, est0, steps = 1))
 

Added: branches/robast-0.9/pkg/RobAStBase/R/move2bckRefParam.R
===================================================================
--- branches/robast-0.9/pkg/RobAStBase/R/move2bckRefParam.R	                        (rev 0)
+++ branches/robast-0.9/pkg/RobAStBase/R/move2bckRefParam.R	2013-02-23 21:54:42 UTC (rev 617)
@@ -0,0 +1,114 @@
+setMethod("moveL2Fam2RefParam", signature(L2Fam = "L2ParamFamily"),
+          function(L2Fam, ...) L2Fam)
+
+setMethod("moveL2Fam2RefParam", signature(L2Fam = "L2LocationFamily"),
+          function(L2Fam, ...){ param <- param(L2Fam)
+                                par0 <- 0; names(par0) <- L2Fam at locscalename
+                                main(param) <- par0
+                                modifyModel(L2Fam, param)})
+
+setMethod("moveL2Fam2RefParam", signature(L2Fam = "L2ScaleFamily"),
+          function(L2Fam, ...){ param <- param(L2Fam)
+                                locscalename <- L2Fam at locscalename
+                                param0 <- 1
+                                names(param0) <- locscalename["scale"]
+                                param1 <- 0
+                                names(param1) <- locscalename["loc"]
+                                main(param) <- param0
+                                fixed(param) <- param1
+                                modifyModel(L2Fam, param)})
+
+setMethod("moveL2Fam2RefParam", signature(L2Fam = "L2LocationScaleFamily"),
+          function(L2Fam, ...){
+              param <- param(L2Fam)
+              lcsname <- L2Fam at locscalename
+              lc <- lcsname["loc"];  sc <- lcsname["scale"]
+              nms.main <- names(main(param))
+                w <- which(length(lc%in% nms.main))
+                if(length(w)){
+                   mp <- main(param); mp[lc] <- 0; main(param) <- mp }
+                w <- which(length(sc%in% nms.main))
+                if(length(w)){
+                   mp <- main(param); mp[sc] <- 0; main(param) <- mp }
+              nms.nuis <- names(nuisance(param))
+                w <- which(length(lc%in% nms.nuis))
+                if(length(w)){
+                   mp <- nuisance(param); mp[lc] <- 0; nuisance(param) <- mp }
+                w <- which(length(sc%in% nms.nuis))
+                if(length(w)){
+                   mp <- nuisance(param); mp[sc] <- 0; nuisance(param) <- mp }
+              nms.fixed <- names(fixed(param))
+                w <- which(length(lc%in% nms.fixed))
+                if(length(w)){
+                   mp <- fixed(param); mp[lc] <- 0; fixed(param) <- mp }
+                w <- which(length(sc%in% nms.fixed))
+                if(length(w)){
+                   mp <- fixed(param); mp[sc] <- 0; fixed(param) <- mp }
+              modifyModel(L2Fam, param)})
+
+
+################################################################################
+
+### remains to be done: Risk trafo !!!
+
+setMethod("moveICBackFromRefParam", signature(IC = "IC", L2Fam = "L2ParamFamily"),
+          function(IC, L2Fam,...) IC)
+
+
+setMethod("moveICBackFromRefParam", signature(IC = "IC",
+           L2Fam = "L2LocationFamily"), function(IC, L2Fam, ...){
+              L2call <- L2Fam at fam.call
+              param <- param(L2Fam)
+              mu <- main(param)
+              IC.cf <- IC at Curve[[1]]@Map[[1]]
+              IC at Curve[[1]]@Map[[1]] <- function(x) IC.cf(x-mu)
+              CallL2Fam(IC) <- L2call
+              return(IC)})
+
+setMethod("moveICBackFromRefParam", signature(IC = "IC",
+           L2Fam = "L2ScaleFamily"), function(IC, L2Fam, ...){
+              L2call <- L2Fam at fam.call
+              param <- param(L2Fam)
+              mu <- fixed(param)
+              sig <- main(param)
+              IC.cf <- IC at Curve[[1]]@Map[[1]]
+              IC at Curve[[1]]@Map[[1]] <- function(x) sig*IC.cf((x-mu)/sig)
+              CallL2Fam(IC) <- L2call
+              return(IC)})
+
+setMethod("moveICBackFromRefParam", signature(IC = "IC",
+           L2Fam = "L2LocationScaleFamily"), function(IC, L2Fam, ...){
+              L2call <- L2Fam at fam.call
+              param <- param(L2Fam)
+              lcsname <- L2Fam at locscalename
+              lc <- lcsname["loc"];  sc <- lcsname["scale"]
+              nms.main <- names(main(param))
+                w <- which(length(lc%in% nms.main))
+                if(length(w)) mu<- main(param)[lc]
+                w <- which(length(sc%in% nms.main))
+                if(length(w)) sig <- main(param)[sc]
+              nms.nuis <- names(nuisance(param))
+                w <- which(length(lc%in% nms.nuis))
+                if(length(w)) mu<- nuisance(param)[lc]
+                w <- which(length(sc%in% nms.nuis))
+                if(length(w)) sig<- nuisance(param)[sc]
+              nms.fixed <- names(fixed(param))
+                w <- which(length(lc%in% nms.fixed))
+                if(length(w)) mu<- fixed(param)[lc]
+                w <- which(length(sc%in% nms.fixed))
+                if(length(w)) sig<- fixed(param)[sc]
+              IC.cf1 <- IC at Curve[[1]]@Map[[1]]
+              IC at Curve[[1]]@Map[[1]] <- function(x) sig*IC.cf1((x-mu)/sig)
+              if(length(IC at Curve[[1]]@Map)==2){
+                 IC.cf2 <- IC at Curve[[1]]@Map[[2]]
+                 IC at Curve[[1]]@Map[[2]] <- function(x) sig*IC.cf2((x-mu)/sig)
+              }
+              CallL2Fam(IC) <- L2call
+              return(IC)})
+
+setMethod("moveICBackFromRefParam", signature(IC = "HampIC",
+           L2Fam = "L2ParamFamily"), function(IC, L2Fam, ...){
+              IC <- moveICBackFromRefParam(as(IC,"IC"), L2Fam,...)
+              IC at modifyIC(L2Fam, IC)
+              return(IC)})
+

Modified: branches/robast-0.9/pkg/RobAStBase/man/InfluenceCurve-class.Rd
===================================================================
--- branches/robast-0.9/pkg/RobAStBase/man/InfluenceCurve-class.Rd	2013-02-17 00:57:24 UTC (rev 616)
+++ branches/robast-0.9/pkg/RobAStBase/man/InfluenceCurve-class.Rd	2013-02-23 21:54:42 UTC (rev 617)
@@ -70,7 +70,9 @@
       function to add an information to slot \code{Infos}. }
 
     \item{Risks}{\code{signature(object = "InfluenceCurve")}: 
-      accessor function for slot \code{Risks}. }
+      accessor function for slot \code{Risks}. By means of internal
+      function \code{.evalListRec} recursively evaluates all non evaluated
+      calls and writes back the evaluated calls to the calling envirionment.}
 
     \item{Risks<-}{\code{signature(object = "InfluenceCurve")}: 
       replacement function for slot \code{Risks}. }

Modified: branches/robast-0.9/pkg/RobAStBase/man/internals.Rd
===================================================================
--- branches/robast-0.9/pkg/RobAStBase/man/internals.Rd	2013-02-17 00:57:24 UTC (rev 616)
+++ branches/robast-0.9/pkg/RobAStBase/man/internals.Rd	2013-02-23 21:54:42 UTC (rev 617)
@@ -11,6 +11,7 @@
 \usage{
 .eq(x,y = 0*x, tol = 1e-7)
 .getDistr(L2Fam)
+.evalListRec(list0)
 }
 
 \arguments{
@@ -18,17 +19,21 @@
   \item{y}{a (numeric) vector}
   \item{tol}{numeric --- tolerance}
   \item{L2fam}{object of class \code{L2ParamFamily}}
+  \item{list0}{a list}
 }
 
 \details{
-\code{.eq}checks equality of two vectors up to a given precision;
+\code{.eq} checks equality of two vectors up to a given precision;
 \code{.getDistr} produces a string with the class of the family and its parameter value;
+\code{.evalListRec} recursively goes through the entries of a list, evaluating
+   each entry.
 }
 
 
 \value{
 \item{.eq}{(a vector of) \code{logical}.}
 \item{.getDistr}{\code{character}.}
+\item{.evalListRec}{a list.}
 }
 
 

Modified: branches/robast-0.9/pkg/RobAStBase/man/kStepEstimator.Rd
===================================================================
--- branches/robast-0.9/pkg/RobAStBase/man/kStepEstimator.Rd	2013-02-17 00:57:24 UTC (rev 616)
+++ branches/robast-0.9/pkg/RobAStBase/man/kStepEstimator.Rd	2013-02-23 21:54:42 UTC (rev 617)
@@ -13,7 +13,7 @@
       withICList = getRobAStBaseOption("withICList"),
       withPICList = getRobAStBaseOption("withPICList"),
       na.rm = TRUE, startArgList = NULL, ...,
-      withLogScale = TRUE)
+      withLogScale = TRUE, withEvalAsVar = TRUE)
 }
 \arguments{
   \item{x}{ sample }
@@ -42,9 +42,11 @@
   \item{withICList}{logical: shall slot \code{ICList} of return value
   be filled?}
   \item{...}{ additional parameters }
-  \item{withLogScale}{logical; shall a scale component (if existing and found
-   with name \code{scalename}) be computed on log-scale and backtransformed
-   afterwards? This avoids crossing 0.}
+  \item{withLogScale}{logical; if \code{TRUE}, a scale component (if existing
+   and found with name \code{scalename}) is computed on log-scale and
+   backtransformed afterwards (default). This avoids crossing 0. }
+  \item{withEvalAsVar}{logical; if \code{TRUE} (default), tells R to evaluate
+   the asymptotic variance or just to produces a call to do so.}
 }
 \details{
   Given an initial estimation \code{start}, a sample \code{x} 

Added: branches/robast-0.9/pkg/RobAStBase/man/mov2bckRef-methods.Rd
===================================================================
--- branches/robast-0.9/pkg/RobAStBase/man/mov2bckRef-methods.Rd	                        (rev 0)
+++ branches/robast-0.9/pkg/RobAStBase/man/mov2bckRef-methods.Rd	2013-02-23 21:54:42 UTC (rev 617)
@@ -0,0 +1,82 @@
+\name{movToRef-methods}
+\docType{methods}
+\alias{moveL2Fam2RefParam-methods}
+\alias{moveICBackFromRefParam-methods}
+\alias{moveICBackFromRefParam}
+\alias{moveL2Fam2RefParam}
+\alias{moveL2Fam2RefParam,L2ParamFamily-method}
+\alias{moveL2Fam2RefParam,L2LocationFamily-method}
+\alias{moveL2Fam2RefParam,L2ScaleFamily-method}
+\alias{moveL2Fam2RefParam,L2LocationScaleFamily-method}
+\alias{moveICBackFromRefParam,IC,L2ParamFamily-method}
+\alias{moveICBackFromRefParam,IC,L2LocationFamily-method}
+\alias{moveICBackFromRefParam,IC,L2ScaleFamily-method}
+\alias{moveICBackFromRefParam,IC,L2LocationScaleFamily-method}
+\alias{moveICBackFromRefParam,HampIC,L2ParamFamily-method}
+
+\title{Methods for Functions moving from and to reference parameter in Package `ROptEst' }
+
+\description{In \code{optIC} a gain in accuracy can be obtained when computing
+ the optimally-robust ICs at a reference parameter of the model (instead of an
+ arbtirary one). To this end, \code{moveL2Fam2RefParam} moved the model to
+ the reference parameter and \code{moveICBackFromRefParam} moves the obtained
+ optimal IC back to the original parameter.}
+
+\usage{moveL2Fam2RefParam(L2Fam, ...)
+       moveICBackFromRefParam(IC, L2Fam,...)
+}
+
+\arguments{
+  \item{L2Fam}{object of class \code{L2ParamFamily}}
+  \item{IC}{IC of class \code{HampIC}}
+  \item{\dots}{further arguments to be passed on. }
+}
+\section{Methods}{\describe{
+\item{moveL2Fam2RefParam}{\code{signature(L2Fam = "L2ParamFamily")}:
+      returns \code{L2Fam} unchanged. }
+\item{moveL2Fam2RefParam}{\code{signature(L2Fam = "L2LocationFamily")}:
+      moves \code{L2Fam} to location \code{0}. }
+\item{moveL2Fam2RefParam}{\code{signature(L2Fam = "L2ScaleFamily")}:
+      moves \code{L2Fam} to location \code{0} and scale \code{1}. }
+\item{moveL2Fam2RefParam}{\code{signature(L2Fam = "L2LocationScaleFamily")}:
+      moves \code{L2Fam} to location \code{0} and scale \code{1}. }
+\item{moveL2Fam2RefParam}{\code{signature(L2Fam = "L2LocationUnknownScaleFamily")}:
+      moves \code{L2Fam} to location \code{0} and scale \code{1}. }
+\item{moveL2Fam2RefParam}{\code{signature(L2Fam = "L2ScaleUnknownLocationFamily")}:
+      moves \code{L2Fam} to location \code{0} and scale \code{1}. }
+\item{moveICBackFromRefParam}{\code{signature(IC = "IC", L2Fam = "L2ParamFamily")}:
+      returns \code{IC} unchanged. }
+\item{moveICBackFromRefParam}{\code{signature(IC = "IC", L2Fam = "L2LocationFamily")}:
+      moves IC in \code{IC} back to original location in \code{L2Fam}. }
+\item{moveICBackFromRefParam}{\code{signature(IC = "IC", L2Fam = "L2ScaleFamily")}:
+      moves IC in \code{IC} back to original location and scale in \code{L2Fam},
+      rescaling risk where necessary. }
+\item{moveICBackFromRefParam}{\code{signature(IC = "IC", L2Fam = "L2LocationScaleFamily")}:
+      moves IC in \code{IC} back to original location and scale in \code{L2Fam},
+      rescaling risk where necessary. }
+\item{moveICBackFromRefParam}{\code{signature(IC = "IC", L2Fam = "L2LocationUnknownScaleFamily")}:
+      moves IC in \code{IC} back to original location and scale in \code{L2Fam},
+      rescaling risk where necessary. }
+\item{moveICBackFromRefParam}{\code{signature(IC = "IC", L2Fam = "L2ScaleUnknownLocationFamily")}:
+      moves IC in \code{IC} back to original location and scale in \code{L2Fam},
+      rescaling risk where necessary. }
+\item{moveICBackFromRefParam}{\code{signature(IC = "HampIC", L2Fam = "L2ParamFamily")}:
+      moves IC in \code{IC} back to original location and scale in \code{L2Fam}
+      (and in addition changes Lagrange multipliers accordingly),
+      rescaling risk where necessary. }
+}}
+\value{
+\item{\code{moveL2Fam2RefParam}}{the L2 Family transformed to reference parameter.}
+\item{\code{moveICBackFromRefParam}}{the backtransformed IC.}
+}
+
+\details{\code{moveL2Fam2RefParam} and \code{moveICBackFromRefParam} are used
+internally in functions \code{robest} and \code{roptest} to compute the
+optimally robust influence function according to the arguments given to them.}
+\author{Peter Ruckdeschel \email{Peter.Ruckdeschel at itwm.fraunhofer.de}}
+%\seealso{\code{\link{robest}},\code{\link{optIC}}, \code{\link{radiusMinimaxIC}}}
+%\examples{}
+\concept{asymptotic risk}
+\concept{risk}
+\keyword{classes}
+



More information about the Robast-commits mailing list