[R] Hashes as S4 Classes, or: How to separate environments

Martin Morgan mtmorgan at fhcrc.org
Sat May 10 14:46:55 CEST 2008


Hi Hans --

Hans W Borchers <hwborchers at gmail.com> writes:

> 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
> D1 at hash and D2 at hash, though I thought a new and empty environment would be
> generated each time 'new("Dict")' is called.
>
> QUESTION: How can I separate the environments D1 at hash and D2 at hash ?

The prototype is created once, at class creation time. So all objects
derived from the prototype share the same environment (other types
like 'list' would have the illusion of being created anew, because of
copy-on-change semantics). A solution is to have an initialize method
that recreates the hash each time.

setMethod("initialize", signature=signature(.Object="Dict"),
    function(.Object,
             hash=new.env(hash=TRUE, parent=emptyenv()),
             ...) {
        callNextMethod(.Object, hash=hash, ...)
    })

Another solution is to have a constructor that feeds Dict a new
environment

Dict <- function() {
    new("Dict", hash=new.env(hash=TRUE, parent=emptyenv())
}

The latter is perhaps preferable, both from an aesthetic / user point
of view ('Dict()' better than 'new("Dict")') and from the
nuances-of-S4 point of view (e.g., the default 'initialize' method is
documented, though not in so many words, as a copy constructor, taking
slots in it's first argument as defaults; 'initialize' above does not
satisfy that contract).

I know others have implemented Dict objects; it would be fun to hear
from them.

Martin

> 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(object at hash)
> )
>
> setGeneric("hclear", function(object) standardGeneric("hclear"))
> setMethod("hclear", signature(object="Dict"),
>     function(object) rm(list=ls(object at hash), envir=object at hash)
> )
>
> setGeneric("hput", function(object, key, value) standardGeneric("hput"))
> setMethod("hput", signature(object="Dict", key="character", value="ANY"),
>     function(object, key, value) assign(key, value, envir=object at hash)
> )
>
> setGeneric("hget", function(object, key, ...) standardGeneric("hget"))
> setMethod("hget", signature(object="Dict", key="character"),
>     function(object, key) {
>         if (exists(key, envir=object at hash, inherits = FALSE)) {
>             get(key, envir=object at hash)
>         } else {
>             return(NULL)
>         }
>     }
> )
>
> # ---- Some tests ----
> D1 <- new("Dict")
> hput(D1, "a", 1)   # Same as: D1 at hash$a <- 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 at 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.

-- 
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-help mailing list