Skip to content

Commit

Permalink
Internal variable names now have prefix .listenv_var_; assign():ing…
Browse files Browse the repository at this point in the history
… variables of such names for other purpose is now invalid [#6]
  • Loading branch information
HenrikBengtsson committed Oct 17, 2015
1 parent 03021d5 commit a2a1199
Show file tree
Hide file tree
Showing 4 changed files with 23 additions and 37 deletions.
2 changes: 1 addition & 1 deletion NEWS
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Package: listenv
================

Version: 0.4.0-9000 [2015-10-07]
Version: 0.4.0-9000 [2015-10-17]
o Add support for assigning elements when creating list environment
similarly how to lists work, e.g. x <- listenv(a=1, b=2).
o DEPRECATED: Deprecated x <- listenv(length=n). Instead use
Expand Down
4 changes: 2 additions & 2 deletions R/get_variable.R
Original file line number Diff line number Diff line change
Expand Up @@ -51,8 +51,8 @@ get_variable.listenv <- function(x, name, mustExist=FALSE, create=!mustExist, ..
extra <- rep(NA_character_, times=i-length(map))
map <- c(map, extra)
}
## Create internal variable name
var <- tempvar(value=NULL, envir=x, inherits=FALSE)
## Create internal variable
var <- new_variable(x, value=NULL)
map[i] <- var
}

Expand Down
24 changes: 20 additions & 4 deletions R/listenv.R
Original file line number Diff line number Diff line change
Expand Up @@ -30,13 +30,15 @@ listenv <- function(...) {
}

## Allocate internal variables
maps <- sprintf("var%004d", seq_len(nargs))
maps <- sprintf(".listenv_var_%d", seq_len(nargs))
names(maps) <- names
for (kk in seq_len(nargs)) {
assign(maps[kk], value=args[[kk]], envir=env, inherits=FALSE)
}
metaenv$.listenv.map <- maps

assign(".listenv_var_count", nargs, envir=env, inherits=FALSE)

class(env) <- c("listenv", class(env))

env
Expand Down Expand Up @@ -315,6 +317,21 @@ as.list.listenv <- function(x, ...) {
}


new_variable <- function(envir, value) {
count <- get(".listenv_var_count", envir=envir, inherits=FALSE)

count <- count + 1L
name <- sprintf(".listenv_var_%f", count)

if (!missing(value)) {
assign(name, value, envir=envir, inherits=FALSE)
}

assign(".listenv_var_count", count, envir=envir, inherits=FALSE)

name
} # new_variable()


assign_by_name <- function(...) UseMethod("assign_by_name")

Expand Down Expand Up @@ -387,9 +404,8 @@ assign_by_index.listenv <- function(x, i, value) {
map <- c(map, extra)
}

## Create internal variable name
var <- tempvar(value=value, envir=x, inherits=FALSE)
map[i] <- var
## Create internal variable
map[i] <- new_variable(x, value=value)

## Update map
map(x) <- map
Expand Down
30 changes: 0 additions & 30 deletions R/utils.R
Original file line number Diff line number Diff line change
@@ -1,33 +1,3 @@
## From R.utils 2.0.2 (2015-05-23)
tempvar <- function(prefix="var", value, envir=parent.frame(), inherits=FALSE) {
maxTries <- 1e6
maxInt <- .Machine$integer.max

ii <- 0L
while (ii < maxTries) {
# Generate random variable name
idx <- sample.int(maxInt, size=1L)
name <- sprintf("%s%d", prefix, idx)

# Is it available?
if (!exists(name, envir=envir, inherits=inherits)) {
# Assign a value?
if (!missing(value)) {
assign(name, value, envir=envir, inherits=inherits)
}
return(name)
}

# Next try
ii <- ii + 1L
}

# Failed to find a unique temporary variable name
stop(sprintf("Failed to generate a unique non-existing temporary variable with prefix '%s'", prefix))
} # tempvar()



## From R.utils 2.0.2 (2015-05-23)
hpaste <- function(..., sep="", collapse=", ", lastCollapse=NULL, maxHead=if (missing(lastCollapse)) 3 else Inf, maxTail=if (is.finite(maxHead)) 1 else Inf, abbreviate="...") {
if (is.null(lastCollapse)) lastCollapse <- collapse
Expand Down

0 comments on commit a2a1199

Please sign in to comment.