On May 10, 2008, at 7:30 AM, Hans W Borchers wrote:

For learning purposes mainly I attempted to implement hashes/maps/ dictionaries (Python lingua) as S4 classes, see the coding below. I came across some rough S4
edges, but in the end it worked (for one dictionary).

When testing ones sees that the dictionaries D1 and D2 share their environments [EMAIL PROTECTED] and [EMAIL PROTECTED], though I thought a new and empty environment would be
generated each time 'new("Dict")' is called.

QUESTION: How can I separate the environments [EMAIL PROTECTED] and [EMAIL 
PROTECTED] ?

The problem you are encountering is that the "prototype" is only created once. Because environments are passed by reference, [EMAIL PROTECTED] and [EMAIL PROTECTED] are the exact same environment:

> D1 <- new("Dict")
> D1
> [EMAIL PROTECTED]
<environment: 0x182ac870>
> D2 <- new("Dict")
> [EMAIL PROTECTED]
<environment: 0x182ac870>

You have assumed that setClass will be executed for each new dictionary, or at least that the prototype(...) part of it would run each time. Not wanting right now to dig into the internals of setClass, my guess is that it only creates a prototype once, and then just reuses it each time, with something like an assignment operator. One solution, very similar to what Martin just suggested, is below. I believe another solution might be to have the hash be a list containing an environment, though I haven't tried that.

The solution is to create a constructor function, the function "newDict" below:

setClass("Dict",
    representation (hash = "environment"))
)
newDict <- function() {
        obj <- new("Dict")
        [EMAIL PROTECTED] <- new.env(hash=T, parent = emptyenv())
        obj
}

In practice, you would probably want newDict to accept an arguments, which may be a list or another Dict object, and then use that as a starting point for the new hash.

Here's a sample run:

> # ---- Some tests ----
> D1 <- newHash()
> D2 <- newHash()
> [EMAIL PROTECTED]
<environment: 0x1e80c98>
> [EMAIL PROTECTED]            # Notice the different address
<environment: 0x1e868fc>
> hput(D1, "a", 1)
> hget(D1, "a")
[1] 1
> show(D1)
[1] "a"
> hput(D2, "c", 3)
> hget(D2, "a")      # Does the correct thing this time
NULL
> hget(D2, "c")
[1] 3
> show(D2)
[1] "c"
> hclear(D2)
> show(D1)        # Works properly now
[1] "a"
> #---------------------

Haris Skiadas
Department of Mathematics and Computer Science
Hanover College

Reading the articles mentioned in "Tipps and Tricks" didn't help me really.
Of course, I will welcome other corrections and improvements as well.
Working in R 2.7.0 under Windows.

Hans Werner



#-- Class and method definition for dictionaries -------------------------------

setClass("Dict",
    representation (hash = "environment"),
    prototype (hash = new.env(hash=T, parent = emptyenv()))
)

setMethod("show", signature(object="Dict"),
    definition = function(object) ls([EMAIL PROTECTED])
)

setGeneric("hclear", function(object) standardGeneric("hclear"))
setMethod("hclear", signature(object="Dict"),
    function(object) rm(list=ls([EMAIL PROTECTED]), [EMAIL PROTECTED])
)

setGeneric("hput", function(object, key, value) standardGeneric ("hput")) setMethod("hput", signature(object="Dict", key="character", value="ANY"),
    function(object, key, value) assign(key, value, [EMAIL PROTECTED])
)

setGeneric("hget", function(object, key, ...) standardGeneric("hget"))
setMethod("hget", signature(object="Dict", key="character"),
    function(object, key) {
        if (exists(key, [EMAIL PROTECTED], inherits = FALSE)) {
            get(key, [EMAIL PROTECTED])
        } else {
            return(NULL)
        }
    }
)

# ---- Some tests ----
D1 <- new("Dict")
hput(D1, "a", 1)   # Same as: [EMAIL PROTECTED] <- 1
hput(D1, "b", 2)
hget(D1, "a")
hget(D1, "b")
show(D1)

D2 <- new("Dict")
hput(D2, "c", 3)
hput(D2, "d", 4)
hget(D2, "a")      # Wrong: was defined only for D1
hget(D2, "b")
show(D2)

hclear(D2)         # Wrong: clears D1 too
show(D1)
#---------------------

______________________________________________
R-help@r-project.org 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.

Reply via email to