Hi,

There seems to be a problem with setGroupGeneric() from package 'methods'. The 
symptoms are somewhat erratic, in the sense that small changes may lead to any 
of the following behaviours.

1.Package works without problems on Windows and installs on Linux but gives 
error when loaded with library().

2.Package installs on both systems and gives error when loaded on any of them.

3. Package builds but fails to install on both systems.

4.Package fails to build on both systems.

Other combinations, depending also on the R version occur, as well.
The package in question is a pure R package with no OS specific code.
The error message in all cases is:

Error in .setupMethodsTables(generic) :
  trying to get slot "group" from an object of a basic class ("NULL") with no 
slots
Error: package or namespace load failed for 'pctsData'


Similar problem has been  reported before at
http://stackoverflow.com/questions/12368439/defining-group-generic-functions-in-an-r-package
A solution given by Romain Francois was to enclose the offending code in 
evalqOnLoad() but this doesn't really solve the problem. 
The code in that question can serve as a minimal example and I have packed it 
in a package at 
http://www.maths.manchester.ac.uk/~gb/Rpackages/grgen_1.0.tar.gz
but that package gives the error at installation time and I do not know how to 
debug with the command line tools. 
The example below is with my local package which installs and gives the same 
error at attach time (I will make it available, together with its dependencies, 
if needed).

> sessionInfo()
R version 3.1.2 (2014-10-31)
Platform: x86_64-unknown-linux-gnu (64-bit)         (actually, Fedora)

locale:
 [1] LC_CTYPE=en_GB.UTF-8       LC_NUMERIC=C
 [3] LC_TIME=en_GB.UTF-8        LC_COLLATE=en_GB.UTF-8
 [5] LC_MONETARY=en_GB.UTF-8    LC_MESSAGES=en_GB.UTF-8
 [7] LC_PAPER=en_GB.UTF-8       LC_NAME=C
 [9] LC_ADDRESS=C               LC_TELEPHONE=C
[11] LC_MEASUREMENT=en_GB.UTF-8 LC_IDENTIFICATION=C

attached base packages:
[1] stats     graphics  grDevices utils     datasets  methods   base



> library(pctsData)

In one of the cases when the package installs  the problem seems to appear after

cacheMetaData -> .updateMethodsInTable -> .updateMethodsInTable -> 
.setupMethodsTables 

in one of the recursive calls to updateMethodsInTable (the place is marked with 
!!! towards the end of the code below). 
At the time of the error in .setupMethodsTables(generic)   'generic' is  NULL 
and  generic@group fails. The calling stack shown by the recover facility is 
this:

===========================================
Enter a frame number, or 0 to exit

 1: library(pctsData)
 2: try({
    ns <- loadNamespace(package, c(which.lib.loc, lib.loc))
    env <-
 3: tryCatch(expr, error = function(e) {
    call <- conditionCall(e)
    if (!is
 4: tryCatchList(expr, classes, parentenv, handlers)
 5: tryCatchOne(expr, names, parentenv, handlers[[1]])
 6: doTryCatch(return(expr), name, parentenv, handler)
 7: loadNamespace(package, c(which.lib.loc, lib.loc))
 8: methods:::cacheMetaData(ns, TRUE, ns)
 9: .updateMethodsInTable(fdef, where, attach)
10: .updateMethodsInTable(getGeneric(g), where, attach)
11: .setupMethodsTables(generic)

==============================================

On a different Linux machine and R version (the standard faculty wide 
installation),  library(pctsData) completes fine but package "grgen" mentioned 
above still gives the error at installation time.
The session info for this case:

R version 3.0.2 (2013-09-25)
Platform: x86_64-redhat-linux-gnu (64-bit)

locale:
 [1] LC_CTYPE=en_GB.UTF-8       LC_NUMERIC=C              
 [3] LC_TIME=en_GB.UTF-8        LC_COLLATE=en_GB.UTF-8    
 [5] LC_MONETARY=en_GB.UTF-8    LC_MESSAGES=en_GB.UTF-8   
 [7] LC_PAPER=en_GB.UTF-8       LC_NAME=C                 
 [9] LC_ADDRESS=C               LC_TELEPHONE=C            
[11] LC_MEASUREMENT=en_GB.UTF-8 LC_IDENTIFICATION=C       

attached base packages:
[1] stats     graphics  grDevices utils     datasets  methods   base     

other attached packages:
[1] pctsData_0.0-3

loaded via a namespace

====================================================

Further details are after the signature below.

Georgi

--
Dr Georgi Boshnakov               tel: (+44) (0)161 306 3684
School of Mathematics             fax: (+44) (0)161 306 3669
Alan Turing Building 1.125
The University of Manchester      email: georgi.boshna...@manchester.ac.uk
Oxford Road
Manchester M13 9PL
UK

====================================================

Here is the relevant code from my package code. 
When I narrowed down the cause of the problem to setGroupGeneric, I found the 
following commented out excerpt, probably the error was the same. A change in 
the syntax back then removed the problem.

## 2011-07-07 I was not able to compile pcts properly since R moved from 2.7.x 
to 2.8.x.
##            Today I finally investigated and discovered that the reason is 
something to do
##            with the group generic. I looked in the sources of package 
"methods" for the
##            way group generics are defined and switched to using argument 
"known members"
##            (see below) instead of the following commands.

## setGroupGeneric("pcfData", function(x) NULL)
## setGeneric("pc.nseasons"        , group="pcfData")  # ima setGeneric i pri 
pcSeason. Check!
## setGeneric("pc.nepochs"         , group="pcfData")
## setGeneric("pc.nvariables"      , group="pcfData")
## setGeneric("pc.namesofseasons"  , group="pcfData")
## setGeneric("pc.namesofvariables", group="pcfData")
## setGeneric("pc.data.matrix"     , group="pcfData")
## setGeneric("pc.data.vec"        , group="pcfData")
## setGeneric("pc.data.Vec"        , group="pcfData")
## setGeneric("pc.data.tsvec"      , group="pcfData")
## setGeneric("pc.data.tsVec"      , group="pcfData")
# setGeneric("",group="pcfData")

setGeneric("pc.nepochs"         )
setGeneric("pc.nvariables"      )
setGeneric("pc.namesofseasons"  )
setGeneric("pc.namesofvariables")
setGeneric("pc.data.matrix"     )
setGeneric("pc.data.vec"        )
setGeneric("pc.data.Vec"        )
setGeneric("pc.data.tsvec"      )
setGeneric("pc.data.tsVec"      )

## 2014-11-24 modifying since causes problems on Linux (cannot load the 
package).
##                     no luck.
## setGroupGeneric("pcfData", function(x) NULL
##                 , knownMembers = c("pc.nepochs"
##                                  , "pc.nvariables"
##                                  , "pc.namesofseasons"
##                                  , "pc.namesofvariables"
##                                  , "pc.data.matrix"
##                                  , "pc.data.vec"
##                                  , "pc.data.Vec"
##                                  , "pc.data.tsvec"
##                                  , "pc.data.tsVec"
##                 ))

pcfData <- function(x) NULL
setGeneric("pcfData")

setGroupGeneric("pcfData", # def = function(x) NULL,
                knownMembers = c("pc.nepochs"
                                  , "pc.nvariables"
                                  , "pc.namesofseasons"
                                  , "pc.namesofvariables"
                                  , "pc.data.matrix"
                                  , "pc.data.vec"
                                  , "pc.data.Vec"
                                  , "pc.data.tsvec"
                                  , "pc.data.tsVec"
                                 ),
                where = topenv()
                )


#########################################################
Related code from "methods" package:

cacheMetaData <-
    function(where, attach = TRUE, searchWhere = as.environment(where),
             doCheck = TRUE)
{
    ## a collection of actions performed on attach or detach
    ## to update class and method information.
    pkg <- getPackageName(where)
    classes <- getClasses(where)
    for(cl in classes) {
        cldef <- (if(attach) get(classMetaName(cl), where) # NOT getClassDef, 
it will use cache
                  else  getClassDef(cl, searchWhere))
        if(is(cldef, "classRepresentation")) {
            if(attach) {
                .cacheClass(cl, cldef, is(cldef, "ClassUnionRepresentation"), 
where)
            }
            else if(identical(cldef@package, pkg)) {
                .uncacheClass(cl, cldef)
                .removeSuperclassBackRefs(cl, cldef, searchWhere)
            }
        }
    }
    generics <- .getGenerics(where)
    packages <- attr(generics, "package")
    if(length(packages) <  length(generics))
        packages <- rep(packages, length.out = length(generics))
    if(attach && exists(".requireCachedGenerics", where, inherits = FALSE)) {
        others <- get(".requireCachedGenerics", where)
        generics <- c(generics, others)
        packages <- c(packages, attr(others, "package"))
    }
    ## check for duplicates
    dups <- duplicated(generics) & duplicated(packages)
    generics <- generics[!dups]
    for(i in seq_along(generics)) {
        f <- generics[[i]]
        fpkg <- packages[[i]]
        if(!identical(fpkg, pkg) && doCheck) {
            if(attach) {
                env <- as.environment(where)
                ## All instances of this generic in different attached packages 
must
                ## agree with the cached version of the generic for consistent
                ## method selection.
                if(exists(f, envir = env, inherits = FALSE)) {
                    def <- get(f, envir = env)
                    fdef <- .genericOrImplicit(f, fpkg, env)
                    if(is.function(def)) {
                        ## exclude a non-function of the same name as a 
primitive with methods (!)
                        if(identical(environment(def), environment(fdef)))
                            next        # the methods are identical
                        else if( is(fdef, "genericFunction")) {
                            .assignOverBinding(f, fdef,  env, FALSE)
                        }
                    }     # else, go ahead to update primitive methods
                }
                else          # either imported generic or a primitive
                    fdef <- getGeneric(f, FALSE, searchWhere, fpkg)
            }
            else
                fdef <- getGeneric(f, FALSE, searchWhere, fpkg)
        }
        else
            fdef <- getGeneric(f, FALSE, searchWhere, fpkg)
        if(!is(fdef, "genericFunction"))
            next ## silently ignores all generics not visible from searchWhere
        if(attach)
            .cacheGeneric(f, fdef)
        else
            .uncacheGeneric(f, fdef)
        methods <- .updateMethodsInTable(fdef, where, attach)          ### !!!
        cacheGenericsMetaData(f, fdef, attach, where, fdef@package, methods)
    }
    .doLoadActions(where, attach)
    invisible(NULL) ## as some people call this at the end of functions
}

###############

# add objects to the generic function's environment that allow
# table-based dispatch of methods
.setupMethodsTables <- function(generic,
                initialize = !exists(".MTable", envir = env, inherits = FALSE))
{
    env <- environment(generic)
    if(initialize || !exists(".SigLength", envir = env, inherits = FALSE)) {
        nsig <- 1
        ## check that groups of generics agree on .SigLength; otherwise
        ## labels won't match
        for(gp in generic@group) {          ### !!!
            gpDef <- getGeneric(gp)
            if(is(gpDef, "genericFunction")) {
                .getMethodsTable(gpDef) # force initialization
                nsig <- max(nsig, get(".SigLength", envir = environment(gpDef)))
            }
        }
        assign(".SigLength", nsig, envir = env)
    }
    argSyms <- lapply(generic@signature, as.name)
    assign(".SigArgs", argSyms, envir = env)
    if(initialize) {
        mlist <- generic@default # from 2.11.0: method, primitive or NULL, not 
MethodsList
        mtable <- .mlistAddToTable(generic, mlist) # by default, adds to an 
empty table
        assign(".MTable", mtable, envir = env)
    }
    else ## the current .MTable
        mtable <- getMethodsForDispatch(generic)
    .resetInheritedMethods(env, mtable)
    if(is(generic, "groupGenericFunction")) {
        for(gp in generic@groupMembers) {
            gpDef <- getGeneric(gp)
            if(is(gpDef, "genericFunction"))
                .getMethodsTable(gpDef) # force initialization w. group methods
        }
    }
    NULL
}

###############

.updateMethodsInTable <- function(generic, where, attach) {
  fenv <- environment(generic)
  reset <- identical(attach, "reset")
  if(!exists(".MTable", envir = fenv, inherits = FALSE))
    .setupMethodsTables(generic)              ### !!!
  mtable <- get(".MTable", envir = fenv)
  if(!reset) {
    env <- as.environment(where)
    tname <- .TableMetaName(generic@generic, generic@package)
    if(exists(tname, envir = env, inherits = FALSE)) {
      .mergeMethodsTable(generic, mtable, get(tname, envir = env), attach)
    }
    ## else used to warn, but the generic may be implicitly required
    ## by class inheritance, without any explicit methods in this package
  }
  if(length(generic@group)) {
      groups <- as.list(generic@group)
      generics <- vector("list", length(groups))
      for(i in seq_along(groups))
        generics[[i]] <- getGeneric(groups[[i]])
    .checkGroupSigLength(groups, generics)
  }
  if(is(generic, "groupGenericFunction")) {
      .checkGroupSigLength(list(generic@generic), list(generic))
      for(g in getGroupMembers(generic))
          .updateMethodsInTable(getGeneric(g), where, attach)   ### !!! 
  }
  .resetInheritedMethods(fenv, mtable)
  mtable
}

______________________________________________
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel

Reply via email to