[R] assign if not set; stand-alone R script, source'able too?

Gabor Grothendieck ggrothendieck at gmail.com
Tue Nov 20 02:56:03 CET 2007


Here are two solutions:

# 1
"%or%" <- function(x, y) if (is.na(x)) y else x
NA %or% 1 # 1
3 %or% 1 # 3

# 3
# can omit Negate<- line in R 2.7.0 since its predefined there
Negate <- function(f) function(...) ! match.fun(f)(...)
Filter(Negate(is.na), c(NA, 1))[1] # 1
Filter(Negate(is.na), c(3, 1))[1] # 3


On Nov 19, 2007 8:22 PM, Alexy Khrabrov <deliverable at gmail.com> wrote:
> Marc -- thanks, very interesting.
>
> I was in fact tinkering at a very simple default arguments assignment
> to a generic command-line R script header:
>
> #!/bin/sh
> # graph a fertility run
> tail --lines=+4 "$0" | R --vanilla --slave --args $*; exit
> args <- commandArgs()[-(1:4)]
>
> # the krivostroi library
> source("/w/ct/r/kriv/krivostroi.r")
>
> # NB: vector assignment in R? defaults?
> file    <- args[1]
> maxruns <- if (is.na(args[2])) 1 else args[2]
> prefix  <- if (is.na(args[3])) file.basename(file) else args[3]
>
> -- turns out, args[N] here are NA if not supplied on the command-
> line.  I'd like to see a nicer way to do it still, without repeating
> args[N] twice for each assignment though.
>
>
> Another thing from this snippet, unrelated to assignment, is that was
> the only way to get R script to be packed in a single file runnable
> from the command line in a stand alone way.  Yet when I want to source
> () it, R obviously chokes on the shell command tail.  My previous
> solution was to have a pair of files, script.r/script.sh for each R
> script, where .sh would look like
>
> echo "argv <- c('$1','$2'); source('main.r')" | R --vanilla --slave
>
> Wonder if there's a way to have a single file which is a stand-alone
> command script, and can be source()'d in R.
>
> Cheers,
> Alexy
>
> On Nov 20, 2007, at 4:03 AM, Marc Schwartz wrote:
> >
> > On Tue, 2007-11-20 at 03:32 +0300, Alexy Khrabrov wrote:
> >> What's the idiom of assigning a default value to a variable if it's
> >> not set?  In Ruby one can say
> >>
> >> v ||= default
> >>
> >> -- that's an or-assign, which triggers the assignment only if v is
> >> not set already.  Is there an R shorthand?
> >>
> >> Cheers,
> >> Alexy
> >
> > If 'v' is not set, then it does not exist, hence you can use exists
> > () to
> > check for it. However, you need to [potentially] distinguish where the
> > variable might be located. Keep in mind that R uses lexical scoping,
> > hence the exists() function has other arguments to define where to
> > look.
> >
> > A simple example:
> >
> >> v
> > Error: object "v" not found
> >
> > if (!exists("v")) v <- "Not Set"
> >
> >> v
> > [1] "Not Set"
> >
> > v <- "Set"
> >
> > if (!exists("v")) v <- "Not Set"
> >
> >> v
> > [1] "Set"
> >
> >
> > See ?exists for more information.
> >
> > That being said, just as an example of extending R, you could do the
> > following, which is to create a new function %||=% (think %in% or %*%)
> > which can then take two arguments, one preceding it and one following
> > it, and then basically do the same thing as above. Again here, scoping
> > is critical.
> >
> >
> > "%||=%" <- function(x, y)
> > {
> >   Var <- deparse(substitute(x))
> >   if (!exists(Var))
> >     assign(Var, y, parent.frame())
> > }
> >
> >> v
> > Error: object "v" not found
> >
> > v %||=% "Not Set"
> >
> >> v
> > [1] "Not Set"
> >
> > v <- "Set"
> >
> > v %||=% "Not Set"
> >
> >> v
> > [1] "Set"
>
> ______________________________________________
> 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