[Rd] predict.smooth.spline.fit and Recall() (Was: Re: Return function from function and Recall())

Prof Brian Ripley ripley at stats.ox.ac.uk
Wed Apr 5 13:26:50 CEST 2006


On Wed, 5 Apr 2006, Henrik Bengtsson wrote:

> Hi,
>
> forget about the below details.  It is not related to the fact that
> the function is returned from a function.  Sorry about that.  I've
> been troubleshooting soo much I've been shoting over the target.  Here
> is a much smaller reproducible example:
>
> x <- 1:10
> y <- 1:10 + rnorm(length(x))
> sp <- smooth.spline(x=x, y=y)
> ypred <- predict(sp$fit, x)
> # [1]  2.325181  2.756166  ...
> ypred2 <- predict(sp$fit, c(0,x))
> # Error in Recall(object, xrange) : couldn't find
> # function "predict.smooth.spline.fit"

It seems Recall is not searching (via findFun) from the right environment, 
but at a quick glance it is not obvious to me why.
You can replace Recall by predict.smooth.spline.fit for now.

As for

>> PS, may I suggest to modify page() so that
>> 'page(getAnywhere("predict.smooth.spline.fit"))' works? DS.

it is rather tricky.  page() takes a name aka symbol as its argument (and 
is thereby S-compatible), and also works with a bare character string 
(undocumented).  What you have here is a call that does not even return a 
function.  It is more reasonable that stats:::predict.smooth.spline.fit 
should work, and it is also a call.  I have in the past thought about 
special-casing that, but it is a valid name (you would have to back-quote 
it, but it does work).  So one possible way out would be to use get() on a 
name and evaluate calls, e.g.

page <- function(x, method = c("dput", "print"), ...)
{
     subx <- substitute(x)
     have_object <- FALSE
     if(is.call(subx)) {
         object <- x
         have_object <- TRUE
         subx <- deparse(subx)
     } else {
         if(is.character(x)) subx <- x
         else if(is.name(subx)) subx <- deparse(subx)
         if (!is.character(subx) || length(subx) != 1)
             stop("'page' requires a name, call or character string")
         parent <- parent.frame()
         if(exists(subx, envir = parent, inherits=TRUE)) {
             object <- get(subx, envir = parent, inherits=TRUE)
             have_object <- TRUE
         }
     }
     if(have_object) {
         method <- match.arg(method)
         file <- tempfile("Rpage.")
         if(method == "dput")
             dput(object, file)
         else {
             sink(file)
             print(object)
             sink()
         }
 	file.show(file, title = subx, delete.file = TRUE, ...)
     } else
 	stop(gettextf("no object named '%s' to show", subx), domain = NA)
}

which also allows 1-element character vectors (and I am not entirely sure 
we want that).


>
> /Henrik
>
>
> On 4/5/06, Henrik Bengtsson <hb at maths.lth.se> wrote:
>> Hi,
>>
>> yesterday I got very useful feedback on what is the best way to return
>> a function from a function.
>>
>> Now, I run into a problem calling a returned function that down the
>> stream uses Recall().  Below is a self-contained example.  I took away
>> yesterday's code for returning a minimal environment for the function,
>> because that is not related to this problem.
>>
>> getPredictor <- function(x, y) {
>>   sp <- smooth.spline(x=x, y=y, keep.data=FALSE)
>>   function(x, ...) predict(sp$fit, x, ...)$y
>> }
>>
>> # Simulate data
>> x <- 1:10
>> y <- 1:10 + rnorm(length(x))
>>
>> # Estimate predictor function
>> fcn <- getPredictor(x,y)
>>
>> # No extrapolation => no Recall()
>> ypred <- fcn(x)
>> print(ypred)
>> # Gives:  # [1]  2.325181  2.756166  ...
>>
>> # With extrapolation => Recall()
>> xextrap <- c(0,x)
>> ypred <- fcn(xextrap)
>> # Gives:  # Error in Recall(object, xrange) : couldn't find
>> # function "predict.smooth.spline.fit"
>>
>> To see what's the function looks like, do
>>
>> pfcn <- getAnywhere("predict.smooth.spline.fit")$obj[[2]]
>> page(pfcn)
>>
>> A workaround is to set the predict.smooth.spline.fit() in .GlobalEnv, i.e.
>>
>>  predict.smooth.spline.fit <- pfcn
>>
>> Does Recall() have a problem because predict.smooth.spline.fit() is
>> not exported, or what is going on?  Are there alternatives to the
>> above workaround?  I can see how such a workaround can become very
>> complicated with complex functions where it is hard to predict what
>> functions are called when.
>>
>> /Henrik
>>
>> PS, may I suggest to modify page() so that
>> 'page(getAnywhere("predict.smooth.spline.fit"))' works? DS.
>>
>
>
> --
> Henrik Bengtsson
> Mobile: +46 708 909208 (+2h UTC)
>
> ______________________________________________
> R-devel at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>
>

-- 
Brian D. Ripley,                  ripley at stats.ox.ac.uk
Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
University of Oxford,             Tel:  +44 1865 272861 (self)
1 South Parks Road,                     +44 1865 272866 (PA)
Oxford OX1 3TG, UK                Fax:  +44 1865 272595



More information about the R-devel mailing list