rmetaprogrammings-expression

How to generate a pairlist with no defaults without using alist?


I'm experimenting with simple manipulation of R code and trying to generate an object equivalent to

substitute(function(x) x)

I am aware I can do something around these lines

as.call(list(as.symbol("function"), as.pairlist(alist(x=)), as.symbol("x")))

but I am looking for a way to achieve as.pairlist(alist(x=)) without resorting alist or, if that's not possible, allowing me to generate equivalent expression without hard-coding the thing or parsing strings.

I was tinkering with things like as.call(list(as.symbol("="), as.symbol("x"))), but that's seems to be a dead end for now.


Solution

  • A programmatic alternative to as.pairlist(alist(...)) is to initialize a pairlist of positive length then assign names (well, "tags") and values:

    zzz <- vector("pairlist", 1L)
    names(zzz) <- "x"
    zzz[[1L]] <- substitute()
    
    identical(zzz, as.pairlist(alist(x = )))
    ## [1] TRUE
    

    More generally:

    pl <- function(n, tags, values) {
        r <- vector("pairlist", n)
        if (n >= 1L) {
            names(r) <- tags
            for (i in seq_len(n)) {
                v <- values[[i]]
                if (missing(v) || !is.null(v))
                    r[[i]] <- values[[i]]
            }
        }
        r
    }
    
    identical(pl(3L, c("x", "y", "z"), list(substitute(), 0, NULL)),
              as.pairlist(alist(x = , y = 0, z = NULL)))
    ## [1] TRUE
    

    We condition on n >= 1L because a zero-length pairlist is NULL and assigning names or values to NULL is an error.

    We condition on missing(v) || !is.null(v) because we don't want to assign NULL to r[[i]] (which would decrease the length of r by 1) and we don't want to call is.null with no argument:

    v <- substitute()
    missing(v)
    ## [1] TRUE
    is.null(v)
    ## Error: argument "v" is missing, with no default