# File src/library/tools/R/install.R
# Part of the R package, http://www.R-project.org
#
# Copyright (C) 1995-2014 The R Core Team
#
# NB: also copyright dates in Usages.
#
# This program is free software; you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation; either version 2 of the License, or
# (at your option) any later version.
#
# This program is distributed in the hope that it will be useful,
# but WITHOUT ANY WARRANTY; without even the implied warranty of
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
# GNU General Public License for more details.
#
# A copy of the GNU General Public License is available at
# http://www.r-project.org/Licenses/
#### R based engine for R CMD INSTALL SHLIB Rprof
####
##' @param args
## R developers can use this to debug the function by running it
## directly as tools:::.install_packages(args), where the args should
## be what commandArgs(TRUE) would return, that is a character vector
## of (space-delimited) terms that would be passed to R CMD INSTALL. E.g.
##
## tools:::.install_packages(c("--preclean", "--no-multiarch", "tree"))
##' @return ...
.install_packages <- function(args = NULL)
{
## calls system() on Windows for
## sh (configure.win/cleanup.win) make zip
dir.exists <- function(x) !is.na(isdir <- file.info(x)$isdir) & isdir
## global variables
curPkg <- character() # list of packages in current pkg
lockdir <- ""
is_first_package <- TRUE
stars <- "*"
## Need these here in case of an early error, e.g. missing etc/Makeconf
tmpdir <- ""
clean_on_error <- TRUE
do_exit_on_error <- function()
{
## If we are not yet processing a package, we will not have
## set curPkg
if(clean_on_error && length(curPkg)) {
pkgdir <- file.path(lib, curPkg)
if (nzchar(pkgdir) && dir.exists(pkgdir) &&
is_subdir(pkgdir, lib)) {
starsmsg(stars, "removing ", sQuote(pkgdir))
unlink(pkgdir, recursive = TRUE)
}
if (nzchar(lockdir) &&
dir.exists(lp <- file.path(lockdir, curPkg)) &&
is_subdir(lp, lockdir)) {
starsmsg(stars, "restoring previous ", sQuote(pkgdir))
if (WINDOWS) {
file.copy(lp, dirname(pkgdir), recursive = TRUE,
copy.date = TRUE)
unlink(lp, recursive = TRUE)
} else {
## some shells require that they be run in a known dir
setwd(startdir)
system(paste("mv", shQuote(lp), shQuote(pkgdir)))
}
}
}
do_cleanup()
q("no", status = 1, runLast = FALSE)
}
do_cleanup <- function()
{
if(nzchar(tmpdir)) do_cleanup_tmpdir()
if (!is_first_package) {
## Only need to do this in case we successfully installed
## at least one package
if (lib == .Library && "html" %in% build_help_types)
utils::make.packages.html(.Library, docdir = R.home("doc"))
}
if (nzchar(lockdir)) unlink(lockdir, recursive = TRUE)
}
do_cleanup_tmpdir <- function()
{
## Solaris will not remove any directory in the current path
setwd(startdir)
if (dir.exists(tmpdir)) unlink(tmpdir, recursive=TRUE)
}
on.exit(do_exit_on_error())
WINDOWS <- .Platform$OS.type == "windows"
MAKE <- Sys.getenv("MAKE") # FIXME shQuote, default?
rarch <- Sys.getenv("R_ARCH") # unix only
if (WINDOWS && nzchar(.Platform$r_arch))
rarch <- paste0("/", .Platform$r_arch)
test_archs <- rarch
SHLIB_EXT <- if (WINDOWS) ".dll" else {
## can we do better?
mconf <- file.path(R.home(), paste0("etc", rarch), "Makeconf")
## PCRE needed for Debian arm* platforms
sub(".*= ", "", grep("^SHLIB_EXT", readLines(mconf), value = TRUE,
perl = TRUE))
}
options(warn = 1)
invisible(Sys.setlocale("LC_COLLATE", "C")) # discard output
if (WINDOWS) {
rhome <- chartr("\\", "/", R.home())
## These might be needed for configure.win and Make{file,vars}.win
## Some people have *assumed* that R_HOME uses /
Sys.setenv(R_HOME = rhome)
if (nzchar(rarch)) Sys.setenv(R_ARCH = rarch, R_ARCH_BIN = rarch)
}
Usage <- function() {
cat("Usage: R CMD INSTALL [options] pkgs",
"",
"Install the add-on packages specified by pkgs. The elements of pkgs can",
"be relative or absolute paths to directories with the package",
"sources, or to gzipped package 'tar' archives. The library tree",
"to install to can be specified via '--library'. By default, packages are",
"installed in the library tree rooted at the first directory in",
".libPaths() for an R session run in the current environment",
"",
"Options:",
" -h, --help print short help message and exit",
" -v, --version print INSTALL version info and exit",
" -c, --clean remove files created during installation",
" --preclean remove files created during a previous run",
" -d, --debug turn on debugging messages",
if(WINDOWS) " and build a debug DLL",
" -l, --library=LIB install packages to library tree LIB",
" --no-configure do not use the package's configure script",
" --no-docs do not install HTML, LaTeX or examples help",
" --html build HTML help",
" --no-html do not build HTML help",
" --latex install LaTeX help",
" --example install R code for help examples",
" --fake do minimal install for testing purposes",
" --no-lock install on top of any existing installation",
" without using a lock directory",
" --lock use a per-library lock directory (default)",
" --pkglock use a per-package lock directory",
" (default for a single package)",
" --build build binaries of the installed package(s)",
" --install-tests install package-specific tests (if any)",
" --no-R, --no-libs, --no-data, --no-help, --no-demo, --no-exec,",
" --no-inst",
" suppress installation of the specified part of the",
" package for testing or other special purposes",
" --no-multiarch build only the main architecture",
" --libs-only only install the libs directory",
" --data-compress= none, gzip (default), bzip2 or xz compression",
" to be used for lazy-loading of data",
" --resave-data re-save data files as compactly as possible",
" --compact-docs re-compress PDF files under inst/doc",
" --with-keep.source",
" --without-keep.source",
" use (or not) 'keep.source' for R code",
" --byte-compile byte-compile R code",
" --no-byte-compile do not byte-compile R code",
" --no-test-load skip test of loading installed package",
" --no-clean-on-error do not remove installed package on error",
" --merge-multiarch multi-arch by merging (from a single tarball only)",
"\nfor Unix",
" --configure-args=ARGS",
" set arguments for the configure scripts (if any)",
" --configure-vars=VARS",
" set variables for the configure scripts (if any)",
" --dsym (OS X only) generate dSYM directory",
"\nand on Windows only",
" --force-biarch attempt to build both architectures",
" even if there is a non-empty configure.win",
" --compile-both compile both architectures on 32-bit Windows",
"",
"Which of --html or --no-html is the default depends on the build of R:",
paste0("for this one it is ",
if(static_html) "--html" else "--no-html", "."),
"",
"Report bugs at bugs.r-project.org .", sep = "\n")
}
# Check whether dir is a subdirectory of parent,
# to protect against malicious package names like ".." below
# Assumes that both directories exist
is_subdir <- function(dir, parent)
normalizePath(parent) == normalizePath(file.path(dir, ".."))
fullpath <- function(dir)
{
owd <- setwd(dir)
full <- getwd()
setwd(owd)
full
}
## used for LazyData, KeepSource, ByteCompile, Biarch
parse_description_field <- function(desc, field, default = TRUE)
{
tmp <- desc[field]
if (is.na(tmp)) default
else switch(tmp,
"yes"=, "Yes" =, "true" =, "True" =, "TRUE" = TRUE,
"no" =, "No" =, "false" =, "False" =, "FALSE" = FALSE,
## default
errmsg("invalid value of ", field, " field in DESCRIPTION")
)
}
starsmsg <- function(stars, ...)
message(stars, " ", ..., domain = NA)
errmsg <- function(...)
{
message("ERROR: ", ..., domain = NA)
do_exit_on_error()
}
pkgerrmsg <- function(msg, pkg)
{
message("ERROR: ", msg, " for package ", sQuote(pkg), domain = NA)
do_exit_on_error()
}
## 'pkg' is the absolute path to package sources.
do_install <- function(pkg)
{
if (WINDOWS && grepl("\\.zip$", pkg)) {
pkg_name <- basename(pkg)
pkg_name <- sub("\\.zip$", "", pkg_name)
pkg_name <- sub("_[0-9.-]+$", "", pkg_name)
utils:::unpackPkgZip(pkg, pkg_name, lib, libs_only)
return()
}
setwd(pkg)
## We checked this exists, but not that it is readable
desc <- tryCatch(read.dcf(fd <- file.path(pkg, "DESCRIPTION")),
error = identity)
if(inherits(desc, "error") || !length(desc))
stop(gettextf("error reading file '%s'", fd),
domain = NA, call. = FALSE)
desc <- desc[1L,]
## Let's see if we have a bundle
if (!is.na(desc["Bundle"])) {
stop("this seems to be a bundle -- and they are defunct")
} else {
pkg_name <- desc["Package"]
if (is.na(pkg_name)) errmsg("no 'Package' field in 'DESCRIPTION'")
curPkg <<- pkg_name
}
instdir <- file.path(lib, pkg_name)
Sys.setenv(R_PACKAGE_NAME = pkg_name, R_PACKAGE_DIR = instdir)
status <- .Rtest_package_depends_R_version()
if (status) do_exit_on_error()
dir.create(instdir, recursive = TRUE, showWarnings = FALSE)
if (!dir.exists(instdir)) {
message("ERROR: unable to create ", sQuote(instdir), domain = NA)
do_exit_on_error()
}
if (!is_subdir(instdir, lib)) {
message("ERROR: ", sQuote(pkg_name), " is not a legal package name",
domain = NA)
do_exit_on_error()
}
## Make sure we do not attempt installing to srcdir.
owd <- setwd(instdir)
if (owd == getwd()) pkgerrmsg("cannot install to srcdir", pkg_name)
setwd(owd)
## Figure out whether this is a source or binary package.
is_source_package <- is.na(desc["Built"])
if (is_source_package) {
## Find out if C++11 is requested in DESCRIPTION file
sys_requires <- desc["SystemRequirements"]
if (!is.na(sys_requires)) {
sys_requires <- unlist(strsplit(sys_requires, ","))
if(any(grepl("^[[:space:]]*C[+][+]11[[:space:]]*$",
sys_requires, ignore.case=TRUE))) {
Sys.setenv("R_PKG_CXX_STD"="CXX11")
on.exit(Sys.unsetenv("R_PKG_CXX_STD"))
}
}
}
if (!is_first_package) cat("\n")
if (is_source_package)
do_install_source(pkg_name, instdir, pkg, desc)
else
do_install_binary(pkg_name, instdir, desc)
## Add read permission to all, write permission to owner
## If group-write permissions were requested, set them
.Call(dirchmod, instdir, group.writable)
is_first_package <<- FALSE
if (tar_up) { # Unix only
starsmsg(stars, "creating tarball")
version <- desc["Version"]
filename <- if (!grepl("darwin", R.version$os)) {
paste0(pkg_name, "_", version, "_R_",
Sys.getenv("R_PLATFORM"), ".tar.gz")
} else {
paste0(pkg_name, "_", version,".tgz")
}
filepath <- file.path(startdir, filename)
owd <- setwd(lib)
res <- utils::tar(filepath, curPkg, compression = "gzip",
compression_level = 9L,
tar = Sys.getenv("R_INSTALL_TAR"))
if (res)
errmsg(sprintf("packaging into %s failed", sQuote(filename)))
message("packaged installation of ",
sQuote(pkg_name), " as ", sQuote(filename),
domain = NA)
setwd(owd)
}
if (zip_up) { # Windows only
starsmsg(stars, "MD5 sums")
.installMD5sums(instdir)
## we could use utils::zip() here.
ZIP <- "zip" # Windows only
version <- desc["Version"]
filename <- paste0(pkg_name, "_", version, ".zip")
filepath <- shQuote(file.path(startdir, filename))
## system(paste("rm -f", filepath))
unlink(filepath)
owd <- setwd(lib)
res <- system(paste(shQuote(ZIP), "-r9Xq", filepath,
paste(curPkg, collapse = " ")))
setwd(owd)
if (res)
message("running 'zip' failed", domain = NA)
else
message("packaged installation of ",
sQuote(pkg_name), " as ", filename, domain = NA)
}
if (Sys.getenv("_R_INSTALL_NO_DONE_") != "yes") {
## message("", domain = NA) # ensure next starts on a new line, for R CMD check
starsmsg(stars, "DONE (", pkg_name, ")")
}
curPkg <<- character()
}
## Unix only
do_install_binary <- function(pkg, instdir, desc)
{
starsmsg(stars, "installing *binary* package ", sQuote(pkg), " ...")
if (file.exists(file.path(instdir, "DESCRIPTION"))) {
if (nzchar(lockdir))
system(paste("mv", shQuote(instdir),
shQuote(file.path(lockdir, pkg))))
dir.create(instdir, recursive = TRUE, showWarnings = FALSE)
}
TAR <- Sys.getenv("TAR", 'tar')
res <- system(paste("cp -R .", shQuote(instdir),
"|| (", TAR, "cd - .| (cd", shQuote(instdir), "&&", TAR, "-xf -))"
))
if (res) errmsg("installing binary package failed")
if (tar_up) {
starsmsg(stars, sQuote(pkg),
" was already a binary package and will not be rebuilt")
tar_up <- FALSE
}
}
## to be run from package source directory
run_clean <- function()
{
if (dir.exists("src") && length(dir("src", all.files = TRUE) > 2L)) {
if (WINDOWS) archs <- c("i386", "x64")
else {
wd2 <- setwd(file.path(R.home("bin"), "exec"))
archs <- Sys.glob("*")
setwd(wd2)
}
if(length(archs))
for(arch in archs) {
ss <- paste("src", arch, sep = "-")
## it seems fixing permissions is sometimes needed
.Call(dirchmod, ss, group.writable)
unlink(ss, recursive = TRUE)
}
owd <- setwd("src")
if (WINDOWS) {
if (file.exists("Makefile.win"))
system(paste(MAKE, "-f Makefile.win clean"))
else
unlink(c("Makedeps",
Sys.glob("*_res.rc"),
Sys.glob("*.[do]")))
# system("rm -f *_res.rc *.o *.d Makedeps")
} else {
if (file.exists("Makefile")) system(paste(MAKE, "clean"))
else ## we will be using SHLIB --preclean
unlink(Sys.glob(paste0("*", SHLIB_EXT)))
}
setwd(owd)
}
if (WINDOWS) {
if (file.exists("cleanup.win")) system("sh ./cleanup.win")
} else if (file_test("-x", "cleanup")) system("./cleanup")
else if (file.exists("cleanup"))
warning("'cleanup' exists but is not executable -- see the 'R Installation and Administration Manual'", call. = FALSE)
}
do_install_source <- function(pkg_name, instdir, pkg_dir, desc)
{
Sys.setenv("R_INSTALL_PKG" = pkg_name)
on.exit(Sys.unsetenv("R_INSTALL_PKG"))
shlib_install <- function(instdir, arch)
{
## install.libs.R allows customization of the libs installation process
if (file.exists("install.libs.R")) {
message("installing via 'install.libs.R' to ", instdir,
domain = NA)
## the following variables are defined to be available,
## and to prevent abuse we don't expose anything else
local.env <- local({ SHLIB_EXT <- SHLIB_EXT
R_PACKAGE_DIR <- instdir
R_PACKAGE_NAME <- pkg_name
R_PACKAGE_SOURCE <- pkg_dir
R_ARCH <- arch
WINDOWS <- WINDOWS
environment()})
parent.env(local.env) <- .GlobalEnv
source("install.libs.R", local = local.env)
return(TRUE)
}
## otherwise proceed with the default which is to just copy *${SHLIB_EXT}
files <- Sys.glob(paste0("*", SHLIB_EXT))
if (length(files)) {
libarch <- if (nzchar(arch)) paste0("libs", arch) else "libs"
dest <- file.path(instdir, libarch)
message('installing to ', dest, domain = NA)
dir.create(dest, recursive = TRUE, showWarnings = FALSE)
file.copy(files, dest, overwrite = TRUE)
## not clear if this is still necessary, but sh version did so
if (!WINDOWS)
Sys.chmod(file.path(dest, files), dmode)
## OS X does not keep debugging symbols in binaries
## anymore so optionally we can create dSYMs. This is
## important since we will blow away .o files so there
## is no way to create it later.
if (dsym && length(grep("^darwin", R.version$os)) ) {
message(gettextf("generating debug symbols (%s)", "dSYM"),
domain = NA)
dylib <- Sys.glob(paste0(dest, "/*", SHLIB_EXT))
for (file in dylib) system(paste0("dsymutil ", file))
}
if(config_val_to_logical(Sys.getenv("_R_SHLIB_BUILD_OBJECTS_SYMBOL_TABLES_",
"TRUE"))
&& file_test("-f", "symbols.rds")) {
file.copy("symbols.rds", dest)
}
}
}
## This is only called for Makevars[.win], so assume it
## does create a shlib: not so reliably reported on Windows
## Note though that it may not create pkg_name.dll, and
## graph does not.
run_shlib <- function(pkg_name, srcs, instdir, arch)
{
args <- c(shargs, "-o", paste0(pkg_name, SHLIB_EXT), srcs)
if (WINDOWS && debug) args <- c(args, "--debug")
if (debug) message("about to run ",
"R CMD SHLIB ", paste(args, collapse = " "),
domain = NA)
if (.shlib_internal(args) == 0L) {
if(WINDOWS && !file.exists("install.libs.R")
&& !length(Sys.glob("*.dll"))) {
message("no DLL was created")
return(TRUE)
}
shlib_install(instdir, arch)
return(FALSE)
} else return(TRUE)
}
## Make the destination directories available to the developer's
## installation scripts (e.g. configure)
Sys.setenv(R_LIBRARY_DIR = lib)
if (nzchar(lib0)) {
## FIXME: is this needed?
## set R_LIBS to include the current installation directory
rlibs <- Sys.getenv("R_LIBS")
rlibs <- if (nzchar(rlibs)) paste(lib, rlibs, sep = .Platform$path.sep) else lib
Sys.setenv(R_LIBS = rlibs)
## This is needed
.libPaths(c(lib, .libPaths()))
}
Type <- desc["Type"]
if (!is.na(Type) && Type == "Frontend") {
if (WINDOWS) errmsg("'Frontend' packages are Unix-only")
starsmsg(stars, "installing *Frontend* package ", sQuote(pkg_name), " ...")
if (preclean) system(paste(MAKE, "clean"))
if (use_configure) {
if (file_test("-x", "configure")) {
res <- system(paste(paste(configure_vars, collapse = " "),
"./configure",
paste(configure_args, collapse = " ")))
if (res) pkgerrmsg("configuration failed", pkg_name)
} else if (file.exists("configure"))
errmsg("'configure' exists but is not executable -- see the 'R Installation and Administration Manual'")
}
if (file.exists("Makefile"))
if (system(MAKE)) pkgerrmsg("make failed", pkg_name)
if (clean) system(paste(MAKE, "clean"))
return()
}
if (!is.na(Type) && Type == "Translation")
errmsg("'Translation' packages are defunct")
OS_type <- desc["OS_type"]
if (WINDOWS) {
if ((!is.na(OS_type) && OS_type == "unix") && !fake)
errmsg(" Unix-only package")
} else {
if ((!is.na(OS_type) && OS_type == "windows") && !fake)
errmsg(" Windows-only package")
}
if(group.writable) { ## group-write modes if requested:
fmode <- "664"
dmode <- "775"
} else {
fmode <- "644"
dmode <- "755"
}
## At this point we check that we have the dependencies we need.
## We cannot use installed.packages() as other installs might be
## going on in parallel
pkgInfo <- .split_description(.read_description("DESCRIPTION"))
pkgs <- unique(c(names(pkgInfo$Depends), names(pkgInfo$Imports),
names(pkgInfo$LinkingTo)))
if (length(pkgs)) {
miss <- character()
for (pkg in pkgs) {
if(!length(find.package(pkg, quiet = TRUE)))
miss <- c(miss, pkg)
}
if (length(miss) > 1)
pkgerrmsg(sprintf("dependencies %s are not available",
paste(sQuote(miss), collapse = ", ")),
pkg_name)
else if (length(miss))
pkgerrmsg(sprintf("dependency %s is not available",
sQuote(miss)), pkg_name)
}
starsmsg(stars, "installing *source* package ",
sQuote(pkg_name), " ...")
stars <- "**"
res <- checkMD5sums(pkg_name, getwd())
if(!is.na(res) && res) {
starsmsg(stars,
gettextf("package %s successfully unpacked and MD5 sums checked",
sQuote(pkg_name)))
}
if (file.exists(file.path(instdir, "DESCRIPTION"))) {
## Back up a previous version
if (nzchar(lockdir)) {
if (debug) starsmsg(stars, "backing up earlier installation")
if(WINDOWS) {
file.copy(instdir, lockdir, recursive = TRUE,
copy.date = TRUE)
if (more_than_libs) unlink(instdir, recursive = TRUE)
} else if (more_than_libs)
system(paste("mv", shQuote(instdir),
shQuote(file.path(lockdir, pkg_name))))
else
file.copy(instdir, lockdir, recursive = TRUE,
copy.date = TRUE)
} else if (more_than_libs) unlink(instdir, recursive = TRUE)
dir.create(instdir, recursive = TRUE, showWarnings = FALSE)
}
if (preclean) run_clean()
if (use_configure) {
if (WINDOWS) {
if (file.exists("configure.win")) {
res <- system("sh ./configure.win")
if (res) pkgerrmsg("configuration failed", pkg_name)
} else if (file.exists("configure"))
message("\n",
" **********************************************\n",
" WARNING: this package has a configure script\n",
" It probably needs manual configuration\n",
" **********************************************\n\n", domain = NA)
} else {
## FIXME: should these be quoted?
if (file_test("-x", "configure")) {
cmd <- paste(paste(configure_vars, collapse = " "),
"./configure",
paste(configure_args, collapse = " "))
if (debug) message("configure command: ", sQuote(cmd),
domain = NA)
## in case the configure script calls SHLIB (some do)
cmd <- paste("_R_SHLIB_BUILD_OBJECTS_SYMBOL_TABLES_=false",
cmd)
res <- system(cmd)
if (res) pkgerrmsg("configuration failed", pkg_name)
} else if (file.exists("configure"))
errmsg("'configure' exists but is not executable -- see the 'R Installation and Administration Manual'")
}
}
if (more_than_libs) {
for (f in c("NAMESPACE", "LICENSE", "LICENCE", "NEWS"))
if (file.exists(f)) {
file.copy(f, instdir, TRUE)
Sys.chmod(file.path(instdir, f), fmode)
}
res <- try(.install_package_description('.', instdir))
if (inherits(res, "try-error"))
pkgerrmsg("installing package DESCRIPTION failed", pkg_name)
if (!file.exists(namespace <- file.path(instdir, "NAMESPACE")) ) {
if(dir.exists("R"))
errmsg("a 'NAMESPACE' file is required")
else writeLines("## package without R code", namespace)
}
}
if (install_libs && dir.exists("src") &&
length(dir("src", all.files = TRUE) > 2L)) {
starsmsg(stars, "libs")
if (!file.exists(file.path(R.home("include"), "R.h")))
## maybe even an error? But installing Fortran-based packages should work
warning("R include directory is empty -- perhaps need to install R-devel.rpm or similar", call. = FALSE)
has_error <- FALSE
linkTo <- pkgInfo$LinkingTo
if (!is.null(linkTo)) {
lpkgs <- sapply(linkTo, function(x) x[[1L]])
## we checked that these were all available earlier,
## but be cautious in case this changed.
paths <- find.package(lpkgs, quiet = TRUE)
bpaths <- basename(paths)
if (length(paths)) {
## check any version requirements
have_vers <-
(vapply(linkTo, length, 1L) > 1L) & lpkgs %in% bpaths
for (z in linkTo[have_vers]) {
p <- z[[1L]]
path <- paths[bpaths %in% p]
current <- readRDS(file.path(path, "Meta", "package.rds"))$DESCRIPTION["Version"]
target <- as.numeric_version(z$version)
if (!do.call(z$op, list(as.numeric_version(current), target)))
stop(gettextf("package %s %s was found, but %s %s is required by %s",
sQuote(p), current, z$op,
target, sQuote(pkgname)),
call. = FALSE, domain = NA)
}
clink_cppflags <- paste(paste0('-I"', paths, '/include"'),
collapse = " ")
Sys.setenv(CLINK_CPPFLAGS = clink_cppflags)
}
} else clink_cppflags <- ""
libdir <- file.path(instdir, paste0("libs", rarch))
dir.create(libdir, showWarnings = FALSE)
if (WINDOWS) {
owd <- setwd("src")
makefiles <- character()
if (!is.na(f <- Sys.getenv("R_MAKEVARS_USER", NA))) {
if (file.exists(f)) makefiles <- f
} else if (file.exists(f <- path.expand("~/.R/Makevars.win")))
makefiles <- f
else if (file.exists(f <- path.expand("~/.R/Makevars")))
makefiles <- f
if (file.exists("Makefile.win")) {
makefiles <- c("Makefile.win", makefiles)
message(" running 'src/Makefile.win' ...", domain = NA)
res <- system(paste("make --no-print-directory",
paste("-f", shQuote(makefiles), collapse = " ")))
if (res == 0) shlib_install(instdir, rarch)
else has_error <- TRUE
} else { ## no src/Makefile.win
srcs <- dir(pattern = "\\.([cfmM]|cc|cpp|f90|f95|mm)$",
all.files = TRUE)
archs <- if (!force_both && !grepl(" x64 ", win.version()))
"i386"
else {
## see what is installed
## NB, not R.home("bin")
f <- dir(file.path(R.home(), "bin"))
f[f %in% c("i386", "x64")]
}
one_only <- !multiarch
if(!one_only && file.exists("../configure.win")) {
## for now, hardcode some exceptions
## These are packages which have arch-independent
## code in configure.win
if(!pkg_name %in% c("AnalyzeFMRI", "CORElearn",
"PearsonDS", "PKI", "RGtk2",
"RNetCDF", "RODBC", "RSclient",
"Rcpp", "Runuran", "SQLiteMap",
"XML", "arulesSequences",
"cairoDevice", "diversitree",
"foreign", "fastICA", "glmnet",
"gstat", "igraph", "jpeg", "png",
"proj4", "randtoolbox", "rgdal",
"rngWELL", "rphast", "rtfbs",
"sparsenet", "tcltk2", "tiff",
"udunits2"))
one_only <- sum(nchar(readLines("../configure.win", warn = FALSE), "bytes")) > 0
if(one_only && !force_biarch) {
if(parse_description_field(desc, "Biarch", FALSE))
force_biarch <- TRUE
else
warning("this package has a non-empty 'configure.win' file,\nso building only the main architecture\n", call. = FALSE, domain = NA)
}
}
if(force_biarch) one_only <- FALSE
if(one_only || length(archs) < 2L)
has_error <- run_shlib(pkg_name, srcs, instdir, rarch)
else {
setwd(owd)
test_archs <- archs
for(arch in archs) {
message("", domain = NA) # a blank line
starsmsg("***", "arch - ", arch)
ss <- paste("src", arch, sep = "-")
dir.create(ss, showWarnings = FALSE)
file.copy(Sys.glob("src/*"), ss, recursive = TRUE)
## avoid read-only files/dir such as nested .svn
.Call(dirchmod, ss, group.writable)
setwd(ss)
ra <- paste0("/", arch)
Sys.setenv(R_ARCH = ra, R_ARCH_BIN = ra)
has_error <- run_shlib(pkg_name, srcs, instdir, ra)
setwd(owd)
if (has_error) break
}
}
}
setwd(owd)
} else { # not WINDOWS
if (file.exists("src/Makefile")) {
arch <- substr(rarch, 2, 1000)
starsmsg(stars, "arch - ", arch)
owd <- setwd("src")
system_makefile <-
file.path(R.home(), paste0("etc", rarch), "Makeconf")
site <- Sys.getenv("R_MAKEVARS_SITE", NA)
if (is.na(site)) site <- file.path(paste0(R.home("etc"), rarch), "Makevars.site")
makefiles <- c(system_makefile,
if(file.exists(site)) site,
"Makefile")
if (!is.na(f <- Sys.getenv("R_MAKEVARS_USER", NA))) {
if (file.exists(f)) makefiles <- c(makefiles, f)
} else if (file.exists(f <- path.expand(paste("~/.R/Makevars",
Sys.getenv("R_PLATFORM"), sep = "-"))))
makefiles <- c(makefiles, f)
else if (file.exists(f <- path.expand("~/.R/Makevars")))
makefiles <- c(makefiles, f)
res <- system(paste(MAKE,
paste("-f", shQuote(makefiles), collapse = " ")))
if (res == 0) shlib_install(instdir, rarch)
else has_error <- TRUE
setwd(owd)
} else { ## no src/Makefile
owd <- setwd("src")
srcs <- dir(pattern = "\\.([cfmM]|cc|cpp|f90|f95|mm)$",
all.files = TRUE)
## This allows Makevars to set OBJECTS or its own targets.
allfiles <- if (file.exists("Makevars")) c("Makevars", srcs) else srcs
wd2 <- setwd(file.path(R.home("bin"), "exec"))
archs <- Sys.glob("*")
setwd(wd2)
if (length(allfiles)) {
## if there is a configure script we install only the main
## sub-architecture
if (!multiarch || length(archs) <= 1 ||
file_test("-x", "../configure")) {
if (nzchar(rarch))
starsmsg("***", "arch - ",
substr(rarch, 2, 1000))
has_error <- run_shlib(pkg_name, srcs, instdir, rarch)
} else {
setwd(owd)
test_archs <- archs
for(arch in archs) {
if (arch == "R") {
## top-level, so one arch without subdirs
has_error <- run_shlib(pkg_name, srcs, instdir, "")
} else {
starsmsg("***", "arch - ", arch)
ss <- paste("src", arch, sep = "-")
dir.create(ss, showWarnings = FALSE)
file.copy(Sys.glob("src/*"), ss, recursive = TRUE)
setwd(ss)
ra <- paste0("/", arch)
## FIXME: do this lower down
Sys.setenv(R_ARCH = ra)
has_error <- run_shlib(pkg_name, srcs, instdir, ra)
Sys.setenv(R_ARCH = rarch)
setwd(owd)
if (has_error) break
}
}
}
} else warning("no source files found", call. = FALSE)
}
setwd(owd)
}
if (has_error)
pkgerrmsg("compilation failed", pkg_name)
## if we have subarchs, update DESCRIPTION
fi <- file.info(Sys.glob(file.path(instdir, "libs", "*")))
dirs <- basename(row.names(fi[fi$isdir %in% TRUE, ]))
## avoid DLLs installed by rogue packages
if(WINDOWS) dirs <- dirs[dirs %in% c("i386", "x64")]
if (length(dirs)) {
descfile <- file.path(instdir, "DESCRIPTION")
olddesc <- readLines(descfile, warn = FALSE)
olddesc <- grep("^Archs:", olddesc,
invert = TRUE, value = TRUE, useBytes = TRUE)
newdesc <- c(olddesc,
paste("Archs:", paste(dirs, collapse = ", "))
)
writeLines(newdesc, descfile, useBytes = TRUE)
}
} else if (multiarch) { # end of src dir
if (WINDOWS) {
wd2 <- setwd(file.path(R.home(), "bin")) # not R.home("bin")
archs <- Sys.glob("*")
setwd(wd2)
test_archs <- archs[archs %in% c("i386", "x64")]
} else {
wd2 <- setwd(file.path(R.home("bin"), "exec"))
test_archs <- Sys.glob("*")
setwd(wd2)
}
}
if (WINDOWS && "x64" %in% test_archs) {
## we cannot actually test x64 unless this is 64-bit
## Windows, even if it is installed.
if (!grepl(" x64 ", win.version())) test_archs <- "i386"
}
## R files must start with a letter
if (install_R && dir.exists("R") && length(dir("R"))) {
starsmsg(stars, "R")
dir.create(file.path(instdir, "R"), recursive = TRUE,
showWarnings = FALSE)
## This cannot be done in a C locale
res <- try(.install_package_code_files(".", instdir))
if (inherits(res, "try-error"))
pkgerrmsg("unable to collate and parse R files", pkg_name)
if (file.exists(f <- file.path("R", "sysdata.rda"))) {
comp <- TRUE
## (We set .libPaths)
if(!is.na(lazycompress <- desc["SysDataCompression"])) {
comp <- switch(lazycompress,
"none" = FALSE,
"gzip" = TRUE,
"bzip2" = 2L,
"xz" = 3L,
TRUE) # default to gzip
} else if(file.info(f)$size > 1e6) comp <- 3L # "xz"
res <- try(sysdata2LazyLoadDB(f, file.path(instdir, "R"),
compress = comp))
if (inherits(res, "try-error"))
pkgerrmsg("unable to build sysdata DB", pkg_name)
}
if (fake) {
## Fix up hook functions so they do not attempt to
## (un)load missing compiled code, initialize ...
## This does stop them being tested at all.
if (file.exists("NAMESPACE")) {
cat("",
'.onLoad <- .onAttach <- function(lib, pkg) NULL',
'.onUnload <- function(libpaths) NULL',
sep = "\n",
file = file.path(instdir, "R", pkg_name), append = TRUE)
##
", paste0("", nm, ""), "
\n"), outcon) for (f in nm) { MM <- M[first == f, ] if (f != " ") cat("\n', MM$HTopic, ' | \n', MM[, 3L],' |
', M$HTopic, ' | \n', M[, 3L],' |