Skip to content

Commit

Permalink
Add feature shared packrat
Browse files Browse the repository at this point in the history
  • Loading branch information
Valdimus committed Feb 15, 2017
1 parent 01cc6e2 commit 2a01ed5
Show file tree
Hide file tree
Showing 29 changed files with 145 additions and 106 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -22,4 +22,4 @@ Suggests:
Enhances: BiocInstaller
URL: https://github.com/rstudio/packrat/
BugReports: https://github.com/rstudio/packrat/issues
RoxygenNote: 5.0.1
RoxygenNote: 6.0.1
3 changes: 2 additions & 1 deletion R/aaa-globals.R
Original file line number Diff line number Diff line change
Expand Up @@ -37,5 +37,6 @@ new_defaults = function(value = list()) {
## These should be set on entering, exiting packrat mode
.packrat_mutables <- new_defaults(list(
origLibPaths = NULL,
project = NULL
project = NULL,
read.only = FALSE
))
6 changes: 4 additions & 2 deletions R/options.R
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,8 @@ VALID_OPTIONS <- list(
snapshot.recommended.packages = list(TRUE, FALSE),
snapshot.fields = function(x) {
is.null(x) || is.character(x)
}
},
read.only = list(TRUE, FALSE)
)

default_opts <- function() {
Expand All @@ -38,7 +39,8 @@ default_opts <- function() {
ignored.packages = NULL,
quiet.package.installation = TRUE,
snapshot.recommended.packages = FALSE,
snapshot.fields = c("Imports", "Depends", "LinkingTo")
snapshot.fields = c("Imports", "Depends", "LinkingTo"),
read.only = FALSE
)
}

Expand Down
174 changes: 107 additions & 67 deletions R/packrat-mode.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,22 @@ isPackratModeOn <- function(project = NULL) {
!is.na(Sys.getenv("R_PACKRAT_MODE", unset = NA))
}

setPackratModeEnvironmentVar <- function() {
# Check if packrat is in readonly mode
# If state is TRUE, will use packrat state, if it's FALSE will use variable environnement
isReadOnly <- function(state=TRUE) {
#mutables <- get(".packrat_mutables", envir = asNamespace("packrat"))
if(state){
state <- .packrat_mutables$get()
return(state$read.only)
}
else{
return(Sys.getenv("R_PACKRAT_READONLY_MODE") == "1")
}
}

setPackratModeEnvironmentVar <- function(read.only=get_opts("read.only")) {
Sys.setenv("R_PACKRAT_MODE" = "1")
Sys.setenv("R_PACKRAT_READONLY_MODE" = if(read.only) "1" else "0")
}

ensurePkgTypeNotBoth <- function() {
Expand All @@ -13,7 +27,7 @@ ensurePkgTypeNotBoth <- function() {
oldPkgType
}

beforePackratModeOn <- function(project) {
beforePackratModeOn <- function(project, read.only=get_opts("read.only")) {

# Ensure that we leave packrat mode before transfering
# to a new project.
Expand All @@ -39,11 +53,13 @@ beforePackratModeOn <- function(project) {
.Library = .Library,
.Library.site = .Library.site,
project = project,
oldPkgType = oldPkgType
oldPkgType = oldPkgType,
read.only = read.only
)
} else {
state <- .packrat_mutables$get()
state$project <- project
state$read.only = read.only
}

state
Expand All @@ -59,60 +75,64 @@ afterPackratModeOn <- function(project,
project <- getProjectDir(project)
libRoot <- libraryRootDir(project)
localLib <- libDir(project)
dir.create(libRoot, recursive = TRUE, showWarnings = FALSE)

# Override auto.snapshot if running under RStudio, as it has its own packrat
# file handlers
if (!is.na(Sys.getenv("RSTUDIO", unset = NA))) {
auto.snapshot <- FALSE
}
if(!isReadOnly(state=FALSE))
{
dir.create(libRoot, recursive = TRUE, showWarnings = FALSE)

# If snapshot.lock exists, assume it's an orphan of an earlier, crashed
# R process -- remove it
if (file.exists(snapshotLockFilePath(project))) {
unlink(snapshotLockFilePath(project))
}
# Override auto.snapshot if running under RStudio, as it has its own packrat
# file handlers
if (!is.na(Sys.getenv("RSTUDIO", unset = NA))) {
auto.snapshot <- FALSE
}

# If snapshot.lock exists, assume it's an orphan of an earlier, crashed
# R process -- remove it
if (file.exists(snapshotLockFilePath(project))) {
unlink(snapshotLockFilePath(project))
}

# If there's a new library (created to make changes to packages loaded in the
# last R session), remove the old library and replace it with the new one.
newLibRoot <- newLibraryDir(project)
if (file.exists(newLibRoot)) {
message("Applying Packrat library updates ... ", appendLF = FALSE)
succeeded <- FALSE
if (file.rename(libRoot, oldLibraryDir(project))) {
if (file.rename(newLibRoot, libRoot)) {
succeeded <- TRUE
# If there's a new library (created to make changes to packages loaded in the
# last R session), remove the old library and replace it with the new one.
newLibRoot <- newLibraryDir(project)
if (file.exists(newLibRoot)) {
message("Applying Packrat library updates ... ", appendLF = FALSE)
succeeded <- FALSE
if (file.rename(libRoot, oldLibraryDir(project))) {
if (file.rename(newLibRoot, libRoot)) {
succeeded <- TRUE
} else {
# Moved the old library out of the way but couldn't move the new
# in its place; move the old library back
file.rename(oldLibraryDir(project), libRoot)
}
}
if (succeeded) {
message("OK")
} else {
# Moved the old library out of the way but couldn't move the new
# in its place; move the old library back
file.rename(oldLibraryDir(project), libRoot)
message("FAILED")
cat("Packrat was not able to make changes to its local library at\n",
localLib, ". Check this directory's permissions and run\n",
"packrat::restore() to try again.\n", sep = "")
}
}
if (succeeded) {
message("OK")
} else {
message("FAILED")
cat("Packrat was not able to make changes to its local library at\n",
localLib, ". Check this directory's permissions and run\n",
"packrat::restore() to try again.\n", sep = "")
}
}

# If the new library temporary folder exists, remove it now so we don't
# attempt to reapply the same failed changes
newLibDir <- newLibraryDir(project)
if (file.exists(newLibDir)) {
unlink(newLibDir, recursive = TRUE)
}
# If the new library temporary folder exists, remove it now so we don't
# attempt to reapply the same failed changes
newLibDir <- newLibraryDir(project)
if (file.exists(newLibDir)) {
unlink(newLibDir, recursive = TRUE)
}

oldLibDir <- oldLibraryDir(project)
if (file.exists(oldLibDir)) {
unlink(oldLibDir, recursive = TRUE)
}
oldLibDir <- oldLibraryDir(project)
if (file.exists(oldLibDir)) {
unlink(oldLibDir, recursive = TRUE)
}

# If the library directory doesn't exist, create it
if (!file.exists(localLib)) {
dir.create(localLib, recursive = TRUE)
# If the library directory doesn't exist, create it
if (!file.exists(localLib)) {
dir.create(localLib, recursive = TRUE)
}
}

# Clean the search path up -- unload libraries that may have been loaded before
Expand All @@ -128,16 +148,19 @@ afterPackratModeOn <- function(project,
useSymlinkedSystemLibrary(project = project)
}

# Refresh the contents of 'lib-ext' if necessary
symlinkExternalPackages(project = project)
if(!isReadOnly(state=FALSE)){
# Refresh the contents of 'lib-ext' if necessary
symlinkExternalPackages(project = project)
}

# Set the library
if (!file.exists(libExtDir(project)))
dir.create(libExtDir(project), recursive = TRUE)
setLibPaths(c(localLib, libExtDir(project)))

# Load any packages specified in external.packages
if (isTRUE(opts$load.external.packages.on.startup())) {
# Don't load external packages in read.only mode as the we don't own the packrat, is not sure that we can access to external package
if (isTRUE(opts$load.external.packages.on.startup()) && isFALSE(isReadOnly(state=FALSE))) {
lapply(opts$external.packages(), function(x) {
library(x, character.only = TRUE, quietly = TRUE)
})
Expand Down Expand Up @@ -165,12 +188,15 @@ afterPackratModeOn <- function(project,
message(msg)
}

# Insert hooks to library modifying functions to auto.snapshot on change
if (interactive() && isTRUE(auto.snapshot)) {
if (file.exists(getPackratDir(project))) {
addTaskCallback(snapshotHook, name = "packrat.snapshotHook")
} else {
warning("this project has not been packified; cannot activate automatic snapshotting")
if(!isReadOnly(state=FALSE))
{
# Insert hooks to library modifying functions to auto.snapshot on change
if (interactive() && isTRUE(auto.snapshot)) {
if (file.exists(getPackratDir(project))) {
addTaskCallback(snapshotHook, name = "packrat.snapshotHook")
} else {
warning("this project has not been packified; cannot activate automatic snapshotting")
}
}
}

Expand Down Expand Up @@ -206,20 +232,23 @@ afterPackratModeOn <- function(project,
}
}

# Update settings
updateSettings(project = project)

if(!isReadOnly(state=FALSE))
{
# Update settings
updateSettings(project = project)
}
invisible(getLibPaths())

}

setPackratModeOn <- function(project = NULL,
read.only = get_opts("read.only"),
auto.snapshot = get_opts("auto.snapshot"),
clean.search.path = TRUE,
print.banner = TRUE) {

state <- beforePackratModeOn(project = project)
setPackratModeEnvironmentVar()
state <- beforePackratModeOn(project = project, read.only=read.only)
setPackratModeEnvironmentVar(read.only=read.only)
afterPackratModeOn(project = project,
auto.snapshot = auto.snapshot,
clean.search.path = clean.search.path,
Expand All @@ -238,9 +267,12 @@ setPackratModeOff <- function(project = NULL,
}

Sys.unsetenv("R_PACKRAT_MODE")
Sys.unsetenv("R_PACKRAT_READONLY_MODE")

# Disable hooks that were turned on before
removeTaskCallback("packrat.snapshotHook")
if(!isReadOnly()){
# Disable hooks that were turned on before
removeTaskCallback("packrat.snapshotHook")
}

# Reset the library paths
libPaths <- .packrat_mutables$get("origLibPaths")
Expand Down Expand Up @@ -268,7 +300,6 @@ setPackratModeOff <- function(project = NULL,
# Default back to the current working directory for packrat function calls
.packrat_mutables$set(project = NULL)
Sys.unsetenv("R_PACKRAT_PROJECT_DIR")

invisible(getLibPaths())
}

Expand All @@ -295,6 +326,7 @@ checkPackified <- function(project = NULL, quiet = FALSE) {
##' will be toggled.
##' @param project The directory in which packrat mode is launched -- this is
##' where local libraries will be used and updated.
##' @param read.only Specfy that you want to use packrat in readonly mode (no modification can be done to the packrat in this mode)
##' @param auto.snapshot Perform automatic, asynchronous snapshots?
##' @param clean.search.path Detach and unload any packages loaded from non-system
##' libraries before entering packrat mode?
Expand All @@ -306,6 +338,7 @@ checkPackified <- function(project = NULL, quiet = FALSE) {
##' @export
packrat_mode <- function(on = NULL,
project = NULL,
read.only = FALSE,
auto.snapshot = get_opts("auto.snapshot"),
clean.search.path = TRUE) {

Expand All @@ -317,6 +350,7 @@ packrat_mode <- function(on = NULL,
clean.search.path = clean.search.path)
} else if (identical(on, TRUE)) {
setPackratModeOn(project = project,
read.only = read.only,
auto.snapshot = auto.snapshot,
clean.search.path = clean.search.path)
} else if (identical(on, FALSE)) {
Expand All @@ -331,17 +365,23 @@ packrat_mode <- function(on = NULL,
##' @name packrat-mode
##' @export
on <- function(project = NULL,
read.only = FALSE,
auto.snapshot = get_opts("auto.snapshot"),
clean.search.path = TRUE,
print.banner = TRUE) {

project <- getProjectDir(project)

# If there is no lockfile already, perform an init
if (!file.exists(lockFilePath(project = project)))
return(init(project = project))
if (!file.exists(lockFilePath(project = project))) {
if(read.only)
stop("You must specified a valid packrat path, I dont't find it in '", project, "'!")
else
return(init(project = project))
}

setPackratModeOn(project = project,
read.only = read.only,
auto.snapshot = auto.snapshot,
clean.search.path = clean.search.path,
print.banner = print.banner)
Expand Down
3 changes: 3 additions & 0 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -216,6 +216,9 @@ stopIfNotPackified <- function(project) {
call. = FALSE)
}
}
else if (isReadOnly() || isReadOnly(state = FALSE)) {
stop("Packrat is in readonly mode!", call. = FALSE)
}
}

# Expected to be used with .Rbuildignore, .Rinstignore
Expand Down
1 change: 0 additions & 1 deletion man/appDependencies.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 0 additions & 1 deletion man/bundle.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 0 additions & 1 deletion man/clean.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 0 additions & 1 deletion man/disable.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 0 additions & 1 deletion man/init.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 0 additions & 1 deletion man/install.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 0 additions & 1 deletion man/install_local.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 0 additions & 1 deletion man/migrate.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 0 additions & 1 deletion man/packify.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

Loading

0 comments on commit 2a01ed5

Please sign in to comment.