Getting the actual source expression that defines the S4 reference class from its associated object

In short (actual question)

How can I access the actual source code / expression that defines the S4 reference class (see ?setRefClass ) from an object returned by either getClass("MyClass") or getRefClass("MyClass") (so after it was found, not examining the actual source file)?

Homework I did

Since all objects are in R, I can get the source code / expression

1) A regular function, simply exploring the corresponding object:

 foo <- function(x) print(x) > foo function(x) print(x) 

2) A formal method, getting the method object of a specific method using selectMethod :

 setGeneric(name="myMethod", signature=c("x"), def=function(x) standardGeneric("myMethod") ) setMethod( f="myMethod", signature=signature(x="numeric"), definition=function(x) print(x) ) def <- selectMethod(f="myMethod", signature=c(x="numeric")) # Get actual source code/expression > attributes(def)$srcref function(x) print(x) 

But for S4 reference classes, everything looks different:

 setRefClass(Class="MyClass", fields=list(x.1="character")) def <- getRefClass("MyClass") # Inspect object >> no expression > def Generator object for class "MyClass": Class fields: Name: x.1 Class: character Class Methods: "callSuper", "copy", "export", "field", "getClass", "getRefClass", "import", "initFields", "show", "trace", "untrace" Reference Superclasses: "envRefClass" def.temp <- attributes(attributes(def)$.xData$def) # Inspect attributes >> no expression > attributes(def.temp) $names [1] "fieldClasses" "fieldPrototypes" "refMethods" "refSuperClasses" [5] "slots" "contains" "virtual" "prototype" [9] "validity" "access" "className" "package" [13] "subclasses" "versionKey" "sealed" "class" # Alternatively: > names(attributes(getClass("MyClass"))) [1] "fieldClasses" "fieldPrototypes" "refMethods" "refSuperClasses" [5] "slots" "contains" "virtual" "prototype" [9] "validity" "access" "className" "package" [13] "subclasses" "versionKey" "sealed" "class" 

I can not find the attribute that stores the actual source code / expression that exactly defines the class.

Just to make sure: this expression is what I would like to get

 setRefClass(Class="MyClass", fields=list(x.1="character")) 

Background / Motivation

I work a lot with S4 Reference Classes ( ?setRefClass ) and thus aspects of OOP such as class inheritance play a big role in my daily work. I also adhere to the “ one def per file ” paradigm to keep things organized, so the various class definitions are stored in separate files , where the file names correspond to the names of the corresponding classes.

As in everything in life, there are some advantages, but also some inherent disadvantages:

Aspect 1

Short or long, you get an inheritance structure that no longer matches the alphabetical file order of the individual source files. Thus, simply searching one file after another will result in an error at a certain point where any required superclass has not yet been found.

 dir.create("classes", showWarnings=FALSE) write("setRefClass(Class=\"A\", contains=\"B\", fields=list(x.3=\"logical\"))", file="classes/class_A.R") write("setRefClass(Class=\"B\", contains=\"C\", fields=list(x.2=\"numeric\"))", file="classes/class_B.R") write("setRefClass(Class=\"C\", fields=list(x.1=\"character\"))", file="classes/class_C.R") 

class_A.R is the first file in the classes folder, but for its source we first need to specify class_B.R (since this file defines class B ), which, in turn, requires class C and, therefore, the preliminary source of class_C.R .

So the correct sorting is:

 c("class_C.R", "class_B.R", "class_A.R") 

Aspect 2

For certain tasks, you need / need the " several defs per file " paradigm: quick and easy distribution of the necessary objects / functions / classes to work processes during parallelization, code organization during the actual creation of the package, etc.

 path <- "classes/classes.R" file.create(path) write("setRefClass(Class=\"C\", fields=list(x.1=\"character\"))", file=path, append=TRUE) write("setRefClass(Class=\"B\", contains=\"C\", fields=list(x.2=\"numeric\"))", file=path, append=TRUE) write("setRefClass(Class=\"A\", contains=\"B\", fields=list(x.3=\"logical\"))", file=path, append=TRUE) 

Ad aspect 1

I don’t like the idea of ​​saving some kind of manual link to the mapping, which determines the correct search order, since I think that the work that the computer can easily do for me (figuring out the correct sort). The only thing you need to do is find the superclasses of each class (like your dependencies), and then get the correct sorting - this is a piece of cake.

EDIT

In case someone is interested: I came up with a working approach for this. Just email me if you want to see some kind of code. It is based on the analysis (without evaluation) of the corresponding class source files to examine the value of the contains argument, which lists superclasses. Then, the whole process recursively repeats for the source files of these superclasses until you end up with the correct sort. This is not too much time.

Here's the diagram:

 x <- list.files("classes", full.names=TRUE) code <- base::parse(file=x[1]) > code expression(setRefClass(Class="A", contains="B", fields=list(x.3="logical"))) superclasses <- eval(code[[1]][["contains"]]) > superclasses [1] "B" # Next: investigate source file for class 'B' 

Ad aspect 2

I also don’t like manual copy and paste, so I implemented a procedure that allows me to consolidate the source code, which is stored in separate files or drawn from the corresponding objects, into one “consolidated” file (via deparse(<source_code_expression>) and write(..., append=TRUE) ). As for classes, correct sorting is also important here, otherwise there will be errors when trying to source a consolidated file.

For both aspects, it would be nice to be able to choose how to get to the actual source code / expression for classes / functions / methods:

  • either by examining the code stored in the corresponding source files ( parse(file=*) )
  • or based on access to the desired information directly from the corresponding facility.

The second option will be a link to the actual question above.

+4
source share
2 answers

The "source" command code is not saved, so you will not see it by checking the object.

Take a look at the setRefClass source by typing it on the console and pressing [ENTER] . Note that you just passed the arguments to the function ... a new expression is not defined. So, when you getRefClass get everything that the class knows about itself.

You can restore it by creating a parseRefClassArgs function that rebuilds the arguments for setRefClass.

+1
source

Class definitions

Since we cannot evaluate files (because we don’t know the sort order), source or the study of certain classes is not included in the table. Here we parse the text in each file into a character vector, storing parsed lines starting with 'setRefClass'. The parser skips the empty space and performs other transformations to make the text more uniformly formatted, but the following will rely on the sequential definition of the class (for example, using named arguments).

 fls <- dir() names(fls) <- fls p0 <- lapply(fls, function(fl) as.character(parse(text=readLines(fl)))) p1 <- lapply(p0, grep, pattern="^setRefClass", value=TRUE) 

Imagine a goal for a data.frame file containing the class being defined, the class contained, and the name of the file in which the class is defined.

 df <- data.frame(Class=NA_character_, contains=NA_character_, File=rep(fls, sapply(p1, length)), stringsAsFactors=FALSE) 

and then fill it with pattern matching / substitution

 p2 <- unlist(p1, use.names=FALSE) pat <- '.*Class = "([[:alnum:]]+)".*' df[,"Class"] <- sub(pat, "\\1", p2) pat <- '.*contains = "([[:alnum:]]+)".*' idx <- grep(pat, p2) df[idx,"contains"] <- sub(pat, "\\1", p2[idx]) 

Finishing with (I added class A1, also derived from B, to class_A.R, for fun)

 > df Class contains File 1 AB class_A.R 2 A1 B class_A.R 3 BC class_B.R 4 C <NA> class_C.R 

Another strategy for collecting a class frame / contains intercepting calls to setRefClass

 gClass <- character() gcontains <- character() setRefClass <- function(Class, fields, contains=NA_character_, ...) { gClass <<- c(gClass, Class) gcontains <<- c(gcontains, contains) } 

gClass and gcontains will contain the relevant data for plotting the dependency graph after the source of the corresponding files (provided that the files can be obtained without class definitions).

 for (fl in dir()) source(fl) 

Dependencies

We need a dependency graph for classes that have dependencies. Therefore, we will use graph and RBGL packages from Bioconductor to build the corresponding graph.

 ## From --> To == contains --> Class m <- as.matrix(df[!is.na(df$contains), c("contains", "Class")]) gr <- ftM2graphNEL(m, edgemode="directed") 

then ask for a width search starting in each of our base package ( df[is.na(df$contains), "Class"] ), and use the received order to get the appropriate sort order

 o <- bfs(gr, "C") # order: breadth-first search unique(df[match(o, df$Class), "File"]) 

So,

 classDefFilesCollateOrder <- function(fls) { names(fls) <- fls p0 <- lapply(fls, function(fl) as.character(parse(text=readLines(fl)))) p1 <- lapply(p0, grep, pattern="^setRefClass", value=TRUE) df <- data.frame(Class=NA_character_, contains=NA_character_, File=rep(fls, sapply(p1, length)), stringsAsFactors=FALSE) p2 <- unlist(p1, use.names=FALSE) pat <- '.*Class = "([[:alnum:]]+)".*' df[,"Class"] <- sub(pat, "\\1", p2) pat <- '.*contains = "([[:alnum:]]+)".*' idx <- grep(pat, p2) df[idx, "contains"] <- sub(pat, "\\1", p2[idx]) ## From --> To == contains --> Class m <- as.matrix(df[!is.na(df$contains), c("contains", "Class")]) gr <- ftM2graphNEL(m, edgemode="directed") ## single class only base <- df$Class[is.na(df$contains)] if (length(base) != 1) stop("don't yet know how to deal with more than 1 base class") o <- bfs(gr, base) unique(df[match(o, df$Class), "File"]) } 
+1
source

All Articles