Skip to content

Commit

Permalink
Even better solution to issue #30.
Browse files Browse the repository at this point in the history
  • Loading branch information
dmurdoch committed Aug 29, 2024
1 parent 7a041cb commit 8774121
Show file tree
Hide file tree
Showing 2 changed files with 6 additions and 15 deletions.
6 changes: 4 additions & 2 deletions R/RowFactor.R
Original file line number Diff line number Diff line change
Expand Up @@ -57,9 +57,11 @@ RowFactor <- function(x, name = deparse(expr), levelnames=levels(x),
else insert <- nopagebreak
catname <- paste(insert, levelnames[i], sep="")
test <- i # Work around a bug in R 2.12.x!
test <- call("labelSubset",

# labelSubset is local; can't use call() here; see issue #30
test <- as.call(list(labelSubset,
subset = call("==", call("as.integer", call("as.factor", expr)), i),
label = deparse(expr))
label = deparse(expr)))
term <- call("*", call("Heading", makeName(catname)),
test)
if (i == 1)
Expand Down
15 changes: 2 additions & 13 deletions R/tabular.R
Original file line number Diff line number Diff line change
Expand Up @@ -629,21 +629,10 @@ tabular.formula <- function(table, data=NULL, n, suppressLabels=0, ...) {
if (missing(n) && inherits(data, "data.frame"))
n <- nrow(data)

# We need access to labelSubset() (and perhaps other functions in future)
# when evaluating a table expression (issue #30), but we don't want
# to mask the user's copy.

parent <- if (is.environment(data)) data else environment(table)
if (!exists("labelSubset", envir = parent)) {
withTableFns <- new.env(parent = parent)
withTableFns$labelSubset <- labelSubset
} else
withTableFns <- parent

if (is.null(data))
data <- withTableFns
data <- environment(table)
else if (is.list(data))
data <- list2env(data, parent = withTableFns)
data <- list2env(data, parent = environment(table))
else if (!is.environment(data))
stop("'data' must be a dataframe, list or environment")

Expand Down

0 comments on commit 8774121

Please sign in to comment.