[R] scoping problems

Peter Dalgaard BSA p.dalgaard at biostat.ku.dk
Fri Jul 14 00:14:36 CEST 2000


"Heberto Ghezzo" <Heberto at meakins.lan.mcgill.ca> writes:

> Again the same type of problem with scoping.
> I wrote the simple functions below, 'by' is from Trevor Hastie 
> modified by F.Harrel and copied from the list.
> 
> epi.crosstab <- function(vec1, vec2, vec3=NULL, row.labels = 
> NULL, col.labels = NULL)
> {
>    if(!is.null(vec3) ){
>          data <- eval(epi.file,sys.frame(sys.parent()))

Um, I don't think that line is significantly different from
data<-epi.file. If you really want to be sure that you get the
epi.file from the parent frame, try get("epi.file",parent.frame()), or
if you must, evalq(epi.file, parent.frame()).

>          by(vec3, xtab(vec1,vec2, row.labels = row.labels, col.labels = 
>                 col.labels),data=data)
>      }
>     if(is.null(vec3))
>         xtab(vec1, vec2, row.labels = row.labels, col.labels=               
>                col.labels)
> }
>  
> by <- function(group, exp, data=data)
> {
>    G <- substitute(group)
>    exp <- substitute(exp)
>    G <- factor(eval(G))
>    for(group in levels(G)) {
>        eval(exp, envir=c(data[G == group, ]))
>    }
>    invisible()
> }

Actually by() exists in R now... Not exactly that one, though.

> xtab <- function(vector1, vector2,row.labels=NULL,col.labels=NULL)
> {
>    table(vector1, vector2)
> }
> 
> now I have a data.frame that is always called 'epi.file' and is 
> attached to frame 1, MILK, COFFEE and WATER are variables in 
> the frame
> 
> > epi.crosstab(MILK,COFFEE)
>        vector2
> vector1  N  Y
>       N 44 27
>       Y  0  4
> ==Why it does print vector1, vector 2 and not MILK and COFFEE ?

Because you're calling table with arguments (vector1,vector2). R is
not a macro language, so without further magic there is no way for
table to know which names it has been called with higher up. 

> > epi.crosstab(MILK,COFFEE,WATER)
> Error in eval(expr, envir, enclos) : Object "vec3" not found
> > 
> 
> Can somebody be so kind as to try to explain which scoping rule 
> now I did violate and where should I put 'eval' 'substitute' etc so it 
> works.

Your by() function is performing substitute magic, and expects the
first argument to be a symbol that exists in the data frame, which
vec3 clearly does not. I think that what you want is

eval(substitute(by(vec3, xtab(vec1,vec2, row.labels = row.labels, col.labels = 
                 col.labels),data=data)))

and xtab() needs to contain a similar construction.

-- 
   O__  ---- Peter Dalgaard             Blegdamsvej 3  
  c/ /'_ --- Dept. of Biostatistics     2200 Cph. N   
 (*) \(*) -- University of Copenhagen   Denmark      Ph: (+45) 35327918
~~~~~~~~~~ - (p.dalgaard at biostat.ku.dk)             FAX: (+45) 35327907
-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-
r-help mailing list -- Read http://www.ci.tuwien.ac.at/~hornik/R/R-FAQ.html
Send "info", "help", or "[un]subscribe"
(in the "body", not the subject !)  To: r-help-request at stat.math.ethz.ch
_._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._



More information about the R-help mailing list