[Rd] Defining an iterator

Martin Morgan mtmorgan at fhcrc.org
Mon Jan 26 02:06:10 CET 2009


Stavros Macrakis <macrakis at alum.mit.edu> writes:

> Inspired by Rudolf Biczok's query of Fri, Jan 23, 2009 at 1:25 AM, I
> tried to implement iteration in a generic way using S4. (Though I am
> admittedly still struggling with learning S4.)
>
>> setClass("foo",representation(bar="list"))
> [1] "foo"
>> x<-new("foo",bar=list(1,2,3))

As an idea...

It seems like iteration (might) imply that the class to be iterated
over has methods for determining its length, and for subsetting. So...

setClass("Class",
         representation=representation(slt="numeric"))

## basic methods: construction, slot access, show

Class <- function(slt, ...) {
    new("Class", slt=slt, ...)
}

slt <- function(x, ...) slot(x, "slt")

setMethod(show, "Class", function(object) {
    cat("class:", class(object), " length:", length(object), "\n")
    cat("slt:", slt(object), "\n")
})

## an 'iterator' interface

setMethod(length, "Class", function(x) {
    length(slot(x, "slt"))
})

setMethod("[", c("Class", "ANY", "missing"),
          function(x, i, j, ..., drop=TRUE)
{
    new("Class", x, slt=slt(x)[i])
})

setMethod("[[", c("Class", "ANY", "missing"),
          function(x, i, j, ..., drop=TRUE)
{
    slt(x)[[i]]
})

I'd then want a generic function whose responsibility it is to return
an iterator

setGeneric("iterator",
           function(x, ...) standardGeneric("iterator"))

and an implementation for my class

setMethod(iterator, "Class", function(x, ...) {
    seq_len(length(x))
})


I'd then use it as

> x <- Class(1:5)
> for (i in iterator(x)) print(x[[i]])
[1] 1
[1] 2
[1] 3
[1] 4
[1] 5

One could kludge a cleaner syntax by having Class contain an integer
vector whose length was kept in synch with the length of the instance.

Alternative strategies might have the 'iterator' function return a
list of objects of a class that 'knows' about x and where in the
iteration it is, with a syntax like

for (it in iterator(x)) print(it(x))

or to define 'iterator' to return an object that knows how to find the
next iterator

it = iterator(x)
while (!done(it)) {
  print(it(x))
  it = next(it)
}

Both of these imply that 'it' is a class, and that potentially many of
these objects are to be created; the efficiency of the S4 system would
not encourage this approach. They might also imply copying of x,
leading to both performance issues and problems about what the value
of x is supposed to be if modified during an iteration.

Martin

> Given this, I would not expect for(i in x)... to work, since R has no
> way of knowing that x at bar should be used as is.  What would it do if
> the representation included two lists?  What if list(1,2,3) is used by
> the class foo to represent something else?
>
> But I did hope that I could put in place some definitions so that the
> *class* could define an iterator.
>
> First I tried overloading `for` to allow the definition of iterator
> classes, but as a primitive function, `for` cannot be overloaded.
>
> Then I tried to see how the Containers package handles iterators:
>
>> library(Containers);.jinit();.jpackage("Containers")
>> ah = MaxHeap(); ah$insert(3)
>> for (i in ah) print(i)
> [1] NA
>> as.list(ah)
> [[1]]
> [1] NA
>
> Bit it appears that the Containers package's Iterators don't interface
> with R's `for` or type conversion system.
>
> So I gave up on iterators, but thought I'd try automatic conversion to lists.
>
> So I defined an automatic conversion from foo to list, since `for`'s
> seq argument is specified as "An expression evaluating to a vector
> (including a list...)":
>
>     setAs("foo","list",function(from)from at bar)
>
> This and various variants (using "numeric" or "vector" instead of
> "list") all give errors.  Is there perhaps some 'sequence' superclass
> that I am ignorant of?
>
> I *was* able to overload lapply:
>
>> setMethod("lapply","foo",function(X,FUN,...) lapply(X at bar,FUN,...))
>> lapply(x,dput); NULL
> 1
> 2
> 3
> NULL
>
> but of course that doesn't affect `for` and other places that expect sequences.
>
> Is there in fact some generic way to handle define iterators or
> abstract sequences in R?
>
>           -s
>
> ______________________________________________
> R-devel at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel

-- 
Martin Morgan
Computational Biology / Fred Hutchinson Cancer Research Center
1100 Fairview Ave. N.
PO Box 19024 Seattle, WA 98109

Location: Arnold Building M2 B169
Phone: (206) 667-2793



More information about the R-devel mailing list