[R] Implementing trees in R
Gabor Grothendieck
ggrothendieck at gmail.com
Fri Mar 16 17:09:24 CET 2007
1. Here is your example redone using proto:
library(proto)
parent <- proto()
child <- proto(a = 1)
parent$child1 <- child
child$parent.env <- parent
# also just for illustration lets change a
parent$child1$a # 1
child$a <- 2
parent$child1$a # 2
2. To redefine $<- use S3 or S4 but it can be done
in conjunction with proto like this:
# constructor
node <- function(. = parent.frame(), ...)
structure(proto(...), class = c("node", "proto"))
"$<-.node" <- function(this, s, value) {
if (s == ".super")
parent.env(this) <- value
if (is.function(value))
environment(value) <- this
if (inherits(value, "node"))
parent.env(value) <- this
this[[as.character(substitute(s))]] <- value
this
}
p <- node(a = 1)
p$child <- node(b = 2)
p$child$parent.env()
p # same
On 3/16/07, Yuk Lap Yip (Kevin) <yuklap.yip at yale.edu> wrote:
> Hi Gabor,
>
> Thanks for the suggestions. I tried to look for the proto vignette
> document but could not find it, could you tell me how to reach it?
>
> Besides, is it possible to define my own node object type with a
> default behavior for the "<-" operator of its member variables being
> referencing rather than copying? Any good reference material/ similar
> code examples?
>
> Thanks.
>
> Gabor Grothendieck wrote:
> > Lists are not good for this. There is an example in section 3.3 of
> > the proto vignette of using proto objects for this. That section
> > also references an S4 example although its pretty messy with S4.
> >
> > You might want to look at the graph, RBGL and graphviz packages
> > in Bioconductor and the dynamicgraph, mathgraph and sna packages
> > on CRAN.
> >
> > On 3/16/07, Yuk Lap Yip (Kevin) <yuklap.yip at yale.edu> wrote:
> >> Hi all,
> >>
> >> I am rather new to R. Recently I have been trying to implement some
> >> tree algorithms in R. I used lists to model tree nodes. I thought
> >> something like this would work:
> >>
> >> parent <- list();
> >> child <- list();
> >> parent$child1 <- child;
> >> child$parent <- parent;
> >>
> >> When I tried to check whether a node is its parent's first child
> >> using "if (node$parent$child1 == node)", it always returned false. Then
> >> I realized that it does not really work because "parent$child1 <- child"
> >> actually makes a copy of child instead of referencing it. I think one
> >> possible fix is to keep a list of node objects, and make references
> >> using the positions in the list. For example, I think the following
> >> would work:
> >>
> >> parent <- list();
> >> child <- list();
> >> nodes <- list(parent, child);
> >> parent$child1 <- 2;
> >> child$parent <- 1;
> >>
> >> Then the "first child" test can be rewritten as "if
> >> (nodes[[nodes[[nodeId]]$parent]]$child1 == nodeId)". However, I would
> >> prefer not to implement trees in this way, as it requires the
> >> inconvenient and error-prone manipulations of node IDs.
> >>
> >> May I know if there is a way to make object references to lists? Or
> >> are there other ways to implement tree data structures in R?
> >>
> >> BTW, I checked how hclust was implemented, and noticed that it calls
> >> an external Fortran program. I would want a solution not involving any
> >> external programs.
> >>
> >> Thanks.
> >>
> >> --
> >>
> >>
> >> God bless.
> >>
> >> Kevin
> >>
> >> ______________________________________________
> >> R-help at stat.math.ethz.ch 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.
> >>
>
> --
>
>
> God bless.
>
> Kevin
>
>
More information about the R-help
mailing list