[Rd] how to write dput-able objects

Gabor Grothendieck ggrothendieck at gmail.com
Mon Feb 25 20:58:36 CET 2008


Try something like this.  If ..Name exists in the proto object
it uses that as the name; otherwise, it uses the name.proto()
heuristic to find the name.

library(proto)
dput.proto <- function(x, ...) {
    y <- as.list(x, all = TRUE)
    if (!exists("..Name", x)) y$..Name <- name.proto(x, parent.frame())
    y$.parent.Name <- name.proto(parent.env(x), parent.frame())
    dput(y, ...)
}
p <- proto(a = 1, f = function(.) { .$a <- .$a + 1})
q <- p$proto(a = 2)
dput.proto(p)
dput.proto(q)

Output:

> library(proto)
> p <- proto(a = 1, f = function(.) { .$a <- .$a + 1})
> q <- p$proto(a = 2)
> dput.proto(p)
structure(list(.super = <environment>, .that = <environment>,
    a = 1, f = function (.)
    {
        .$a <- .$a + 1
    }, ..Name = "p", .parent.Name = "R_GlobalEnv"), .Names = c(".super",
".that", "a", "f", "..Name", ".parent.Name"))
> dput.proto(q)
structure(list(.super = <environment>, .that = <environment>,
    a = 2, ..Name = "q", .parent.Name = "p"), .Names = c(".super",
".that", "a", "..Name", ".parent.Name"))



On Mon, Feb 25, 2008 at 2:17 PM, Vadim Organovich
<vogranovich at jumptrading.com> wrote:
> Thank you Gabor! This is very close indeed to what I need. If dput() were generic one could code dput.proto() and that would be it.
>
> Anyway, it is so close to what I need that I should be able to hack someting to make it work for my purposes. Thanks again!
>
> Vadim
>
> ________________________________________
> From: Gabor Grothendieck [ggrothendieck at gmail.com]
> Sent: Monday, February 25, 2008 12:16 PM
> To: Vadim Organovich
> Cc: r-devel at r-project.org
> Subject: Re: [Rd] how to write dput-able objects
>
>
> You might want to look at the proto package.  proto objects won't
> immediately dput either but it would not be hard to convert them to
> restorable character strings because the proto methods normally
> have their object as their parent environment so its implicit in the
> definition.  First define a proto object p with one variable 'a' and one
> method 'f' and a child object, q, whose 'a' component overrides the
> 'a' in its parent.
>
> > library(proto)
> > p <- proto(a=1, f = function(.) .$a <- .$a + 1)
> > q <- p$proto(a = 2)
> > p$as.list()
> $a
> [1] 1
>
> $f
> function(.) .$a <- .$a + 1
> <environment: 0x01d6e284>
>
> > name.proto(p)
> [1] "p"
> > name.proto(p$parent.env())
> [1] "R_GlobalEnv"
> > q$as.list()
> $a
> [1] 2
>
> > name.proto(q)
> [1] "q"
> > name.proto(q$parent.env())
> [1] "p"
>
> Note that the strings above have everything
> you would need to restore them.  We don't
> need the environment since we already know that
> f's environment must be p as it belongs to p.
>
> On Mon, Feb 25, 2008 at 12:47 PM, Vadim Organovich
> <vogranovich at jumptrading.com> wrote:
> > Hi,
> >
> > One way of doing object-oriented programming in R is to use function environment to hold object's data, see for example
> > @Article{Rnews:Chambers+Lang:2001a,
> >  author       = {John M. Chambers and Duncan Temple Lang},
> >  title        = {Object-Oriented Programming in {R}},
> >  journal      = {R News},
> >  year        = 2001,
> >  volume       = 1,
> >  number       = 3,
> >  pages        = {17--19},
> >  month        = {September},
> >  url        = http,
> >  pdf        = Rnews2001-3
> > }
> >
> > One deficiency of this approach is that dput() does not export all data pertained to the object. For example
> >
> > > objfactory <- function(nm) {
> > +   list(name = function() nm)
> > + }
> > >
> > >
> > > obj <- objfactory('foo')
> > >
> > > obj$name()
> > [1] "foo"
> > > dput(obj)
> > structure(list(name = function ()
> > nm), .Names = "name")
> > As one can see the data piece of the obj, nm='foo', is not exported. Is there a way to modify the original approach so that dput() will produce a self-sufficient dump of the object?
> >
> > Thanks,
> > Vadim
> >
> >        [[alternative HTML version deleted]]
> >
> > ______________________________________________
> > R-devel at r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
> >
>
> ______________________________________________
> R-devel at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>



More information about the R-devel mailing list