#### eval / parse / deparse / substitute etc
##- From: Peter Dalgaard BSA
##- Subject: Re: source() / eval() bug ??? (PR#96)
##- Date: 20 Jan 1999 14:56:24 +0100
e1 <- parse(text='c(F=(f <- .3), "Tail area" = 2 * if(f < 1) 30 else 90)')[[1]]
e1
str(eval(e1))
mode(e1)
( e2 <- quote(c(a=1,b=2)) )
names(e2)[2] <- "a b c"
e2
parse(text=deparse(e2))
##- From: Peter Dalgaard BSA
##- Date: 22 Jan 1999 11:47
( e3 <- quote(c(F=1,"tail area"=pf(1,1,1))) )
eval(e3)
names(e3)
names(e3)[2] <- "Variance ratio"
e3
eval(e3)
##- From: Peter Dalgaard BSA
##- Date: 2 Sep 1999
## The first failed in 0.65.0 :
attach(list(x=1))
evalq(dim(x) <- 1,pos.to.env(2))
dput(get("x", env=pos.to.env(2)))
e <- local({x <- 1;environment()})
evalq(dim(x) <- 1,e)
dput(get("x",env=e))
### Substitute, Eval, Parse, etc
## PR#3 : "..." matching
A <- function(x, y, ...) {
B <- function(a, b, ...) { match.call() }
B(x+y, ...)
}
(aa <- A(1,2,3))
all.equal(as.list(aa),
list(as.name("B"), a = expression(x+y)[[1]], ..1 = 3))
(a2 <- A(1,2, named = 3)) #A(1,2, named = 3)
all.equal(as.list(a2),
list(as.name("B"), a = expression(x+y)[[1]], named = 3))
CC <- function(...) match.call()
DD <- function(...) CC(...)
a3 <- DD(1,2,3)
all.equal(as.list(a3),
list(as.name("CC"), ..1 = 1, ..2 = 2, ..3 = 3))
## Bug PR#24
f <- function(x,...) substitute(list(x,...))
deparse(f(a, b)) == "list(a, b)" &&
deparse(f(b, a)) == "list(b, a)" &&
deparse(f(x, y)) == "list(x, y)" &&
deparse(f(y, x)) == "list(y, x)"
tt <- function(x) { is.vector(x); deparse(substitute(x)) }
a <- list(b=3); tt(a$b) == "a$b" # tends to break when ...
## Parser:
1 <
2
2 <=
3
4 >=
3
3 >
2
2 ==
2
## bug till ...
1 !=
3