[R] inefficient ifelse() ?
William Dunlap
wdunlap at tibco.com
Wed Mar 2 00:08:33 CET 2011
Try using [<- more, instead of ifelse(). I rarely find
myself really using both of the calls to [<- that ifelse
makes. E.g., I use
x[x==999] <- NA
instead of
x <- ifelse(x==999, NA, x)
But if you find yourself using ifelse in a certain way often,
try writing a function that only allows that case. E.g.,
transform2 <- function(x, test, ifTrueFunction, ifFalseFunction)
{
stopifnot(is.logical(test), length(x) != length(test), is.function(ifTrueFunction), is.function(ifFalseFunction))
retval <- x # assume output is of same type as input
retval[test] <- ifTrueFunction(x[test])
retval[!test] <- ifFalseFunction(x[!test])
retval
}
transform2(x, x<=0, f, g)
Bill Dunlap
Spotfire, TIBCO Software
wdunlap tibco.com
> -----Original Message-----
> From: ivowel at gmail.com [mailto:ivowel at gmail.com] On Behalf Of
> ivo welch
> Sent: Tuesday, March 01, 2011 2:20 PM
> To: William Dunlap
> Cc: r-help
> Subject: Re: [R] inefficient ifelse() ?
>
> yikes. you are asking me too much.
>
> thanks everybody for the information. I learned something new.
>
> my suggestion would be for the much smarter language designers (than
> I) to offer us more or less blissfully ignorant users another
> vector-related construct in R. It could perhaps be named %if% %else%,
> analogous to if else (with naming inspired by %in%, and with
> evaluation only of relevant parts [just as if else for scalars]), with
> different outcomes in some cases, but with the advantage of typically
> evaluating only half as many conditions as the ifelse() vector
> construct. %if% %else% may work only in a subset of cases, but when
> it does work, it would be nice to have. it would probably be my first
> "goto" function, with ifelse() use only as a fallback.
>
> of course, I now know how to fix my specific issue. I was just
> surprised that my first choice, ifelse(), was not as optimized as I
> had thought.
>
> best,
>
> /iaw
>
>
> On Tue, Mar 1, 2011 at 5:13 PM, William Dunlap
> <wdunlap at tibco.com> wrote:
> > An ifelse-like function that only evaluated
> > what was needed would be fine, but it would
> > have to be different from ifelse itself. The
> > trick is to come up with a good parameterization.
> >
> > E.g., how would it deal with things like
> > ifelse(is.na(x), mean(x, na.rm=TRUE), x)
> > or
> > ifelse(x>1, log(x), runif(length(x),-1,0))
> > or
> > ifelse(x>1, log(x), -seq_along(x))
> > Would it reject such things? Deciding that the
> > x in mean(x,na.rm=TRUE) should be replaced by
> > x[is.na(x)] would be wrong. Deciding that
> > runif(length(x)) should be replaced by runif(sum(x>1))
> > seems a bit much to expect. Replacing seq_along(x) with
> > seq_len(sum(x>1)) is wrong. It would be better to
> > parameterize the new function so it wouldn't have to
> > think about those cases.
> >
> > Would you want it to depend only on a logical
> > vector or perhaps also on a factor (a vectorized
> > switch/case function)?
> >
> > Bill Dunlap
> > Spotfire, TIBCO Software
> > wdunlap tibco.com
> >
> >> -----Original Message-----
> >> From: r-help-bounces at r-project.org
> >> [mailto:r-help-bounces at r-project.org] On Behalf Of ivo welch
> >> Sent: Tuesday, March 01, 2011 12:36 PM
> >> To: Henrique Dallazuanna
> >> Cc: r-help
> >> Subject: Re: [R] inefficient ifelse() ?
> >>
> >> thanks, Henrique. did you mean
> >>
> >> as.vector(t(mapply(function(x, f)f(x), split(t, ((t %% 2)==0)),
> >> list(f, g)))) ?
> >>
> >> otherwise, you get a matrix.
> >>
> >> its a good solution, but unfortunately I don't think this
> can be used
> >> to redefine ifelse(cond,ift,iff) in a way that is transparent. the
> >> ift and iff functions will always be evaluated before the function
> >> call happens, even with lazy evaluation. :-(
> >>
> >> I still think that it makes sense to have a smarter
> vectorized %if% in
> >> a vectorized language like R. just my 5 cents.
> >>
> >> /iaw
> >>
> >> ----
> >> Ivo Welch (ivo.welch at brown.edu, ivo.welch at gmail.com)
> >>
> >>
> >>
> >>
> >>
> >> On Tue, Mar 1, 2011 at 2:33 PM, Henrique Dallazuanna
> >> <wwwhsd at gmail.com> wrote:
> >> > Try this:
> >> >
> >> > mapply(function(x, f)f(x), split(t, t %% 2), list(g, f))
> >> >
> >> > On Tue, Mar 1, 2011 at 4:19 PM, ivo welch
> <ivowel at gmail.com> wrote:
> >> >>
> >> >> dear R experts---
> >> >>
> >> >> t <- 1:30
> >> >> f <- function(t) { cat("f for", t, "\n"); return(2*t) }
> >> >> g <- function(t) { cat("g for", t, "\n"); return(3*t) }
> >> >> s <- ifelse( t%%2==0, g(t), f(t))
> >> >>
> >> >> shows that the ifelse function actually evaluates both f()
> >> and g() for
> >> >> all values first, and presumably then just picks left or
> >> right results
> >> >> based on t%%2. uggh... wouldn't it make more sense to
> >> evaluate only
> >> >> the relevant parts of each vector and then reassemble them?
> >> >>
> >> >> /iaw
> >> >> ----
> >> >> Ivo Welch
> >> >>
> >> >> ______________________________________________
> >> >> R-help at r-project.org mailing list
> >> >> https://stat.ethz.ch/mailman/listinfo/r-help
> >> >> PLEASE do read the posting guide
> >> >> http://www.R-project.org/posting-guide.html
> >> >> and provide commented, minimal, self-contained,
> reproducible code.
> >> >
> >> >
> >> >
> >> > --
> >> > Henrique Dallazuanna
> >> > Curitiba-Paraná-Brasil
> >> > 25° 25' 40" S 49° 16' 22" O
> >> >
> >>
> >> ______________________________________________
> >> R-help at r-project.org mailing list
> >> https://stat.ethz.ch/mailman/listinfo/r-help
> >> PLEASE do read the posting guide
> >> http://www.R-project.org/posting-guide.html
> >> and provide commented, minimal, self-contained, reproducible code.
> >>
> >
>
More information about the R-help
mailing list