paleolimbot commented on code in PR #38236:
URL: https://github.com/apache/arrow/pull/38236#discussion_r1362626982
##########
r/configure.win:
##########
@@ -38,8 +38,7 @@ GCS_LIBS="-lcurl -lnormaliz -lssh2 -lgdi32 -lssl -lcrypto
-lcrypt32 -lwldap32 \
function configure_release() {
VERSION=$(grep ^Version DESCRIPTION | sed s/Version:\ //)
# Try to find/download a C++ Arrow binary,
- # including possibly a local .zip file if RWINLIB_LOCAL is set
- "${R_HOME}/bin${R_ARCH_BIN}/Rscript.exe" "tools/winlibs.R" $VERSION
$RWINLIB_LOCAL
+ "${R_HOME}/bin${R_ARCH_BIN}/Rscript.exe" "tools/nixlibs.R" $VERSION
Review Comment:
Given that this is also being used on Windows now, should `nixlibs.R` be
renamed?
##########
r/tools/nixlibs.R:
##########
@@ -171,16 +162,16 @@ identify_binary <- function(lib =
Sys.getenv("LIBARROW_BINARY"), info = distro()
if (identical(lib, "false")) {
# Do not download a binary
- NULL
+ lib <- NULL
} else if (!identical(lib, "true")) {
# Env var provided an os-version to use, to override our logic.
# We don't validate that this exists. If it doesn't, the download will fail
# and the build will fall back to building from source
- lib
} else {
# See if we can find a suitable binary
- select_binary()
+ lib <- select_binary()
}
+ return(lib)
Review Comment:
```suggestion
lib
```
##########
r/tools/nixlibs.R:
##########
@@ -15,35 +15,54 @@
# specific language governing permissions and limitations
# under the License.
-args <- commandArgs(TRUE)
-VERSION <- args[1]
-dst_dir <- paste0("libarrow/arrow-", VERSION)
-
-# TESTING is set in test-nixlibs.R; it won't be set when called from configure
-test_mode <- exists("TESTING")
+#### Fuctions #### check end of file for main logic
+env_is <- function(var, value) identical(tolower(Sys.getenv(var)), value)
-# Prevent error with binary selection during testing.
-if (test_mode && is.na(VERSION)) {
- VERSION <- "8.0.0.9000"
+# Log messages in the style of the configure script
+lg <- function(..., .indent = "***") {
+ cat(.indent, " ", sprintf(...), "\n", sep = "")
}
-dev_version <- package_version(VERSION)[1, 4]
-is_release <- is.na(dev_version) || dev_version < "100"
-on_macos <- tolower(Sys.info()[["sysname"]]) == "darwin"
-checksum_path <- Sys.getenv("ARROW_R_CHECKSUM_PATH", "tools/checksums")
-
-# Small dev versions are added for R-only changes during CRAN submission.
-if (is_release) {
- VERSION <- package_version(VERSION)[1, 1:3]
- arrow_repo <- paste0(getOption("arrow.repo",
sprintf("https://apache.jfrog.io/artifactory/arrow/r/%s", VERSION)),
"/libarrow/")
-} else {
- arrow_repo <- paste0(getOption("arrow.dev_repo",
"https://nightlies.apache.org/arrow/r"), "/libarrow/")
+# Exit the script after logging with .status=1 instead of throwing an error
+exit <- function(..., .status = 1) {
+ lg(...)
+ q(save = "no", status = .status)
}
-options(.arrow.cleanup = character()) # To collect dirs to rm on exit
-on.exit(unlink(getOption(".arrow.cleanup")))
-env_is <- function(var, value) identical(tolower(Sys.getenv(var)), value)
+# checks the nightly repo for the latest nightly version X.Y.Z.100<dev>
+find_latest_nightly <- function(description_version) {
+ if (!startsWith(arrow_repo, "https://nightlies.apache.org/arrow/r")) {
+ lg("Detected non standard dev repo: %s, not checking latest nightly
version.", arrow_repo)
+ return(description_version)
+ }
+
+ res <- try(
+ {
+ url_file <- tempfile()
+ on.exit(unlink(url_file))
+ # Binaries are only uploaded if all jobs pass so can just look at the
source versions.
+ download.file("https://nightlies.apache.org/arrow/r/src/contrib",
url_file, quiet = TRUE)
+ urls <- readLines(url_file)
+ versions <- grep("arrow_.*\\.tar\\.gz", urls, value = TRUE)
+ versions <- sub(".*arrow_(.*)\\.tar\\.gz.*", "\\1", x = versions)
+ versions <- sapply(versions, package_version)
+ versions <- data.frame(do.call(rbind, versions))
+ matching_major <- versions[versions$X1 == description_version[1, 1], ]
+ latest <- matching_major[which.max(matching_major$X4), ]
+ package_version(paste0(latest, collapse = "."))
Review Comment:
```suggestion
matching_major <- versions[versions$X1 == description_version[1, 1], ,
drop = FALSE]
latest <- matching_major[which.max(matching_major$X4)[1], , drop =
TRUE]
package_version(paste0(latest, collapse = "."))
```
...ensures that `matching_major` stays a data.frame even if the subsetted
`versions` only has one row (and that `latest` is a matrix even when
`which.max()` returns `integer()`. You could also check for
`nrow(matching_major) == 0` and do something else instead of the `[1]` hack.
##########
r/tools/nixlibs.R:
##########
@@ -811,22 +802,90 @@ cmake_find_package <- function(pkg, version = NULL,
env_var_list) {
system(cmake_cmd, ignore.stdout = TRUE, ignore.stderr = TRUE) == 0
}
-#####
+############### Main logic #############
+args <- commandArgs(TRUE)
+VERSION <- args[1]
+
+# TESTING is set in test-nixlibs.R; it won't be set when called from configure
+test_mode <- exists("TESTING")
+
+# Prevent error with binary selection during testing.
+if (test_mode && is.na(VERSION)) {
+ VERSION <- "8.0.0.9000"
+}
+
+VERSION <- package_version(VERSION)
+dev_version <- VERSION[1, 4]
+# Small dev versions are added for R-only changes during CRAN submission
+is_release <- is.na(dev_version) || dev_version < "100"
+
+on_macos <- tolower(Sys.info()[["sysname"]]) == "darwin"
+on_windows <- tolower(Sys.info()[["sysname"]]) == "windows"
+
+# For local debugging, set ARROW_R_DEV=TRUE to make this script print more
+quietly <- !env_is("ARROW_R_DEV", "true")
+
+not_cran <- env_is("NOT_CRAN", "true")
+
+if (is_release) {
+ VERSION <- VERSION[1, 1:3]
+ arrow_repo <- paste0(getOption("arrow.repo",
sprintf("https://apache.jfrog.io/artifactory/arrow/r/%s", VERSION)),
"/libarrow/")
+} else {
+ not_cran <- TRUE
+ arrow_repo <- paste0(getOption("arrow.dev_repo",
"https://nightlies.apache.org/arrow/r"), "/libarrow/")
+ VERSION <- find_latest_nightly(VERSION)
+}
+
+options(.arrow.cleanup = character()) # To collect dirs to rm on exit
Review Comment:
It's possibly worth explaining in the comment that we need this to be a
global option to ensure that modifications that take place in the script are
picked up by the exit handler.
##########
r/tools/nixlibs.R:
##########
@@ -15,35 +15,54 @@
# specific language governing permissions and limitations
# under the License.
-args <- commandArgs(TRUE)
-VERSION <- args[1]
-dst_dir <- paste0("libarrow/arrow-", VERSION)
-
-# TESTING is set in test-nixlibs.R; it won't be set when called from configure
-test_mode <- exists("TESTING")
+#### Fuctions #### check end of file for main logic
+env_is <- function(var, value) identical(tolower(Sys.getenv(var)), value)
-# Prevent error with binary selection during testing.
-if (test_mode && is.na(VERSION)) {
- VERSION <- "8.0.0.9000"
+# Log messages in the style of the configure script
+lg <- function(..., .indent = "***") {
+ cat(.indent, " ", sprintf(...), "\n", sep = "")
}
-dev_version <- package_version(VERSION)[1, 4]
-is_release <- is.na(dev_version) || dev_version < "100"
-on_macos <- tolower(Sys.info()[["sysname"]]) == "darwin"
-checksum_path <- Sys.getenv("ARROW_R_CHECKSUM_PATH", "tools/checksums")
-
-# Small dev versions are added for R-only changes during CRAN submission.
-if (is_release) {
- VERSION <- package_version(VERSION)[1, 1:3]
- arrow_repo <- paste0(getOption("arrow.repo",
sprintf("https://apache.jfrog.io/artifactory/arrow/r/%s", VERSION)),
"/libarrow/")
-} else {
- arrow_repo <- paste0(getOption("arrow.dev_repo",
"https://nightlies.apache.org/arrow/r"), "/libarrow/")
+# Exit the script after logging with .status=1 instead of throwing an error
+exit <- function(..., .status = 1) {
+ lg(...)
+ q(save = "no", status = .status)
}
-options(.arrow.cleanup = character()) # To collect dirs to rm on exit
-on.exit(unlink(getOption(".arrow.cleanup")))
-env_is <- function(var, value) identical(tolower(Sys.getenv(var)), value)
+# checks the nightly repo for the latest nightly version X.Y.Z.100<dev>
+find_latest_nightly <- function(description_version) {
+ if (!startsWith(arrow_repo, "https://nightlies.apache.org/arrow/r")) {
+ lg("Detected non standard dev repo: %s, not checking latest nightly
version.", arrow_repo)
+ return(description_version)
+ }
+
+ res <- try(
+ {
+ url_file <- tempfile()
+ on.exit(unlink(url_file))
+ # Binaries are only uploaded if all jobs pass so can just look at the
source versions.
+ download.file("https://nightlies.apache.org/arrow/r/src/contrib",
url_file, quiet = TRUE)
+ urls <- readLines(url_file)
+ versions <- grep("arrow_.*\\.tar\\.gz", urls, value = TRUE)
+ versions <- sub(".*arrow_(.*)\\.tar\\.gz.*", "\\1", x = versions)
+ versions <- sapply(versions, package_version)
+ versions <- data.frame(do.call(rbind, versions))
Review Comment:
It may also useful here to `names(version) <- c("major", "minor", "patch")`
and/or assert that you actually have three columns.
##########
r/tools/nixlibs.R:
##########
@@ -15,35 +15,55 @@
# specific language governing permissions and limitations
# under the License.
-args <- commandArgs(TRUE)
-VERSION <- args[1]
-dst_dir <- paste0("libarrow/arrow-", VERSION)
+#### Fuctions #### check end of file for main logic
+env_is <- function(var, value) identical(tolower(Sys.getenv(var)), value)
-# TESTING is set in test-nixlibs.R; it won't be set when called from configure
-test_mode <- exists("TESTING")
+# Log messages in the style of the configure script
+lg <- function(..., .indent = "***") {
+ cat(.indent, " ", sprintf(...), "\n", sep = "")
+}
-# Prevent error with binary selection during testing.
-if (test_mode && is.na(VERSION)) {
- VERSION <- "8.0.0.9000"
+# Exit the script after logging with .status=1 instead of throwing an error
+exit <- function(..., .status = 1) {
+ lg(...)
+ q(save = "no", status = .status)
}
-dev_version <- package_version(VERSION)[1, 4]
-on_macos <- tolower(Sys.info()[["sysname"]]) == "darwin"
+# checks the nightly repo for the latest nightly version X.Y.Z.100<dev>
+find_latest_nightly <- function(description_version) {
+ if (!startsWith(arrow_repo, "https://nightlies.apache.org/arrow/r")) {
+ lg("Detected non standard dev repo: %s, not checking latest nightly
version.", arrow_repo)
+ return(description_version)
+ }
-# Small dev versions are added for R-only changes during CRAN submission.
-if (is.na(dev_version) || dev_version < "100") {
- VERSION <- package_version(VERSION)[1, 1:3]
- arrow_repo <- paste0(getOption("arrow.repo",
sprintf("https://apache.jfrog.io/artifactory/arrow/r/%s", VERSION)),
"/libarrow/")
-} else {
- arrow_repo <- paste0(getOption("arrow.dev_repo",
"https://nightlies.apache.org/arrow/r"), "/libarrow/")
+ res <- try(
+ {
+ url_file <- tempfile()
+ on.exit(unlink(url_file))
Review Comment:
I think you can also do
`readLines("https://nightlies.apache.org/arrow/r/src/contrib")` and skip the
temp file 🤷
##########
r/tools/nixlibs.R:
##########
@@ -15,35 +15,55 @@
# specific language governing permissions and limitations
# under the License.
-args <- commandArgs(TRUE)
-VERSION <- args[1]
-dst_dir <- paste0("libarrow/arrow-", VERSION)
+#### Fuctions #### check end of file for main logic
+env_is <- function(var, value) identical(tolower(Sys.getenv(var)), value)
-# TESTING is set in test-nixlibs.R; it won't be set when called from configure
-test_mode <- exists("TESTING")
+# Log messages in the style of the configure script
+lg <- function(..., .indent = "***") {
+ cat(.indent, " ", sprintf(...), "\n", sep = "")
+}
-# Prevent error with binary selection during testing.
-if (test_mode && is.na(VERSION)) {
- VERSION <- "8.0.0.9000"
+# Exit the script after logging with .status=1 instead of throwing an error
+exit <- function(..., .status = 1) {
+ lg(...)
+ q(save = "no", status = .status)
}
-dev_version <- package_version(VERSION)[1, 4]
-on_macos <- tolower(Sys.info()[["sysname"]]) == "darwin"
+# checks the nightly repo for the latest nightly version X.Y.Z.100<dev>
+find_latest_nightly <- function(description_version) {
+ if (!startsWith(arrow_repo, "https://nightlies.apache.org/arrow/r")) {
+ lg("Detected non standard dev repo: %s, not checking latest nightly
version.", arrow_repo)
+ return(description_version)
+ }
-# Small dev versions are added for R-only changes during CRAN submission.
-if (is.na(dev_version) || dev_version < "100") {
- VERSION <- package_version(VERSION)[1, 1:3]
- arrow_repo <- paste0(getOption("arrow.repo",
sprintf("https://apache.jfrog.io/artifactory/arrow/r/%s", VERSION)),
"/libarrow/")
-} else {
- arrow_repo <- paste0(getOption("arrow.dev_repo",
"https://nightlies.apache.org/arrow/r"), "/libarrow/")
+ res <- try(
+ {
+ url_file <- tempfile()
+ on.exit(unlink(url_file))
Review Comment:
I think you can also do
`readLines("https://nightlies.apache.org/arrow/r/src/contrib")` and skip the
temp file 🤷
##########
r/tools/nixlibs.R:
##########
@@ -15,35 +15,54 @@
# specific language governing permissions and limitations
# under the License.
-args <- commandArgs(TRUE)
-VERSION <- args[1]
-dst_dir <- paste0("libarrow/arrow-", VERSION)
-
-# TESTING is set in test-nixlibs.R; it won't be set when called from configure
-test_mode <- exists("TESTING")
+#### Fuctions #### check end of file for main logic
+env_is <- function(var, value) identical(tolower(Sys.getenv(var)), value)
-# Prevent error with binary selection during testing.
-if (test_mode && is.na(VERSION)) {
- VERSION <- "8.0.0.9000"
+# Log messages in the style of the configure script
+lg <- function(..., .indent = "***") {
+ cat(.indent, " ", sprintf(...), "\n", sep = "")
}
-dev_version <- package_version(VERSION)[1, 4]
-is_release <- is.na(dev_version) || dev_version < "100"
-on_macos <- tolower(Sys.info()[["sysname"]]) == "darwin"
-checksum_path <- Sys.getenv("ARROW_R_CHECKSUM_PATH", "tools/checksums")
-
-# Small dev versions are added for R-only changes during CRAN submission.
-if (is_release) {
- VERSION <- package_version(VERSION)[1, 1:3]
- arrow_repo <- paste0(getOption("arrow.repo",
sprintf("https://apache.jfrog.io/artifactory/arrow/r/%s", VERSION)),
"/libarrow/")
-} else {
- arrow_repo <- paste0(getOption("arrow.dev_repo",
"https://nightlies.apache.org/arrow/r"), "/libarrow/")
+# Exit the script after logging with .status=1 instead of throwing an error
+exit <- function(..., .status = 1) {
+ lg(...)
+ q(save = "no", status = .status)
}
-options(.arrow.cleanup = character()) # To collect dirs to rm on exit
-on.exit(unlink(getOption(".arrow.cleanup")))
-env_is <- function(var, value) identical(tolower(Sys.getenv(var)), value)
+# checks the nightly repo for the latest nightly version X.Y.Z.100<dev>
+find_latest_nightly <- function(description_version) {
+ if (!startsWith(arrow_repo, "https://nightlies.apache.org/arrow/r")) {
+ lg("Detected non standard dev repo: %s, not checking latest nightly
version.", arrow_repo)
+ return(description_version)
+ }
+
+ res <- try(
+ {
+ url_file <- tempfile()
+ on.exit(unlink(url_file))
+ # Binaries are only uploaded if all jobs pass so can just look at the
source versions.
+ download.file("https://nightlies.apache.org/arrow/r/src/contrib",
url_file, quiet = TRUE)
+ urls <- readLines(url_file)
+ versions <- grep("arrow_.*\\.tar\\.gz", urls, value = TRUE)
+ versions <- sub(".*arrow_(.*)\\.tar\\.gz.*", "\\1", x = versions)
+ versions <- sapply(versions, package_version)
+ versions <- data.frame(do.call(rbind, versions))
Review Comment:
```suggestion
versions <- as.data.frame(do.call(rbind, versions))
```
(technically does the same thing, but the uninitiated can easily mistake
this for creating a data frame with one column)
##########
r/tools/nixlibs.R:
##########
@@ -811,22 +802,90 @@ cmake_find_package <- function(pkg, version = NULL,
env_var_list) {
system(cmake_cmd, ignore.stdout = TRUE, ignore.stderr = TRUE) == 0
}
-#####
+############### Main logic #############
+args <- commandArgs(TRUE)
+VERSION <- args[1]
+
+# TESTING is set in test-nixlibs.R; it won't be set when called from configure
+test_mode <- exists("TESTING")
+
+# Prevent error with binary selection during testing.
+if (test_mode && is.na(VERSION)) {
+ VERSION <- "8.0.0.9000"
+}
+
+VERSION <- package_version(VERSION)
+dev_version <- VERSION[1, 4]
+# Small dev versions are added for R-only changes during CRAN submission
+is_release <- is.na(dev_version) || dev_version < "100"
+
+on_macos <- tolower(Sys.info()[["sysname"]]) == "darwin"
+on_windows <- tolower(Sys.info()[["sysname"]]) == "windows"
+
+# For local debugging, set ARROW_R_DEV=TRUE to make this script print more
+quietly <- !env_is("ARROW_R_DEV", "true")
+
+not_cran <- env_is("NOT_CRAN", "true")
+
+if (is_release) {
+ VERSION <- VERSION[1, 1:3]
+ arrow_repo <- paste0(getOption("arrow.repo",
sprintf("https://apache.jfrog.io/artifactory/arrow/r/%s", VERSION)),
"/libarrow/")
+} else {
+ not_cran <- TRUE
+ arrow_repo <- paste0(getOption("arrow.dev_repo",
"https://nightlies.apache.org/arrow/r"), "/libarrow/")
+ VERSION <- find_latest_nightly(VERSION)
+}
+
+options(.arrow.cleanup = character()) # To collect dirs to rm on exit
+on.exit(unlink(getOption(".arrow.cleanup")))
+
+# enable full featured builds for macOS in case of CRAN source builds.
+if (not_cran || on_macos) {
+ # Set more eager defaults
+ if (env_is("LIBARROW_BINARY", "")) {
+ Sys.setenv(LIBARROW_BINARY = "true")
+ }
+ if (env_is("LIBARROW_MINIMAL", "")) {
+ Sys.setenv(LIBARROW_MINIMAL = "false")
+ }
+}
+
+# The default will build from source as a fallback if a binary is not found or
shouldn't be used
+# Set LIBARROW_BUILD=FALSE to ensure that we use a previously built libarrow
+# and don't fall back to a full source build
+build_ok <- !env_is("LIBARROW_BUILD", "false")
+
+# Check if we're authorized to download (not asked an offline build).
+# (Note that cmake will still be downloaded if necessary
+# https://arrow.apache.org/docs/developers/cpp/building.html#offline-builds)
+download_ok <- !test_mode && !env_is("TEST_OFFLINE_BUILD", "true")
+
+# This "tools/thirdparty_dependencies" path, within the tar file, might exist
if
+# create_package_with_all_dependencies() was run, or if someone has created it
+# manually before running make build.
+# If you change this path, you also need to edit
+# `create_package_with_all_dependencies()` in install-arrow.R
+thirdparty_dependency_dir <- Sys.getenv("ARROW_THIRDPARTY_DEPENDENCY_DIR",
"tools/thirdparty_dependencies")
+
+# configure.win uses a different libarrow dir and and the zip is already nested
+dst_dir <- ifelse(on_windows, "windows", paste0("libarrow/arrow-", VERSION))
if (!test_mode && !file.exists(paste0(dst_dir, "/include/arrow/api.h"))) {
Review Comment:
On Windows I think this looks like
`/include/arrow-13.0.0.100000000xxx/api.h`, which is why on Windows it
currently attempts a download every time.
##########
r/tools/nixlibs.R:
##########
@@ -15,35 +15,54 @@
# specific language governing permissions and limitations
# under the License.
-args <- commandArgs(TRUE)
-VERSION <- args[1]
-dst_dir <- paste0("libarrow/arrow-", VERSION)
-
-# TESTING is set in test-nixlibs.R; it won't be set when called from configure
-test_mode <- exists("TESTING")
+#### Fuctions #### check end of file for main logic
+env_is <- function(var, value) identical(tolower(Sys.getenv(var)), value)
-# Prevent error with binary selection during testing.
-if (test_mode && is.na(VERSION)) {
- VERSION <- "8.0.0.9000"
+# Log messages in the style of the configure script
+lg <- function(..., .indent = "***") {
+ cat(.indent, " ", sprintf(...), "\n", sep = "")
}
-dev_version <- package_version(VERSION)[1, 4]
-is_release <- is.na(dev_version) || dev_version < "100"
-on_macos <- tolower(Sys.info()[["sysname"]]) == "darwin"
-checksum_path <- Sys.getenv("ARROW_R_CHECKSUM_PATH", "tools/checksums")
-
-# Small dev versions are added for R-only changes during CRAN submission.
-if (is_release) {
- VERSION <- package_version(VERSION)[1, 1:3]
- arrow_repo <- paste0(getOption("arrow.repo",
sprintf("https://apache.jfrog.io/artifactory/arrow/r/%s", VERSION)),
"/libarrow/")
-} else {
- arrow_repo <- paste0(getOption("arrow.dev_repo",
"https://nightlies.apache.org/arrow/r"), "/libarrow/")
+# Exit the script after logging with .status=1 instead of throwing an error
+exit <- function(..., .status = 1) {
+ lg(...)
+ q(save = "no", status = .status)
}
-options(.arrow.cleanup = character()) # To collect dirs to rm on exit
-on.exit(unlink(getOption(".arrow.cleanup")))
-env_is <- function(var, value) identical(tolower(Sys.getenv(var)), value)
+# checks the nightly repo for the latest nightly version X.Y.Z.100<dev>
+find_latest_nightly <- function(description_version) {
+ if (!startsWith(arrow_repo, "https://nightlies.apache.org/arrow/r")) {
+ lg("Detected non standard dev repo: %s, not checking latest nightly
version.", arrow_repo)
+ return(description_version)
+ }
+
+ res <- try(
+ {
+ url_file <- tempfile()
+ on.exit(unlink(url_file))
+ # Binaries are only uploaded if all jobs pass so can just look at the
source versions.
+ download.file("https://nightlies.apache.org/arrow/r/src/contrib",
url_file, quiet = TRUE)
+ urls <- readLines(url_file)
+ versions <- grep("arrow_.*\\.tar\\.gz", urls, value = TRUE)
+ versions <- sub(".*arrow_(.*)\\.tar\\.gz.*", "\\1", x = versions)
+ versions <- sapply(versions, package_version)
Review Comment:
```suggestion
versions <- lapply(versions, package_version)
```
##########
r/tools/nixlibs.R:
##########
@@ -133,16 +125,16 @@ identify_binary <- function(lib =
Sys.getenv("LIBARROW_BINARY"), info = distro()
if (identical(lib, "false")) {
# Do not download a binary
- NULL
+ lib <- NULL
} else if (!identical(lib, "true")) {
# Env var provided an os-version to use, to override our logic.
# We don't validate that this exists. If it doesn't, the download will fail
# and the build will fall back to building from source
- lib
Review Comment:
I think it clearly communicates what's happening and doesn't have any
undesirable side-effects? 🤷
##########
r/tools/nixlibs.R:
##########
@@ -777,22 +765,90 @@ cmake_find_package <- function(pkg, version = NULL,
env_var_list) {
system(cmake_cmd, ignore.stdout = TRUE, ignore.stderr = TRUE) == 0
}
-#####
+############### Main logic #############
+args <- commandArgs(TRUE)
+VERSION <- args[1]
+
+# TESTING is set in test-nixlibs.R; it won't be set when called from configure
+test_mode <- exists("TESTING")
+
+# Prevent error with binary selection during testing.
+if (test_mode && is.na(VERSION)) {
+ VERSION <- "8.0.0.9000"
+}
+
+VERSION <- package_version(VERSION)
+dev_version <- VERSION[1, 4]
+# Small dev versions are added for R-only changes during CRAN submission
+is_release <- is.na(dev_version) || dev_version < "100"
+
+on_macos <- tolower(Sys.info()[["sysname"]]) == "darwin"
+on_windows <- tolower(Sys.info()[["sysname"]]) == "windows"
+
+# For local debugging, set ARROW_R_DEV=TRUE to make this script print more
+quietly <- !env_is("ARROW_R_DEV", "true")
+
+not_cran <- env_is("NOT_CRAN", "true")
+
+if (is_release) {
+ VERSION <- VERSION[1, 1:3]
+ arrow_repo <- paste0(getOption("arrow.repo",
sprintf("https://apache.jfrog.io/artifactory/arrow/r/%s", VERSION)),
"/libarrow/")
+} else {
+ not_cran <- TRUE
+ arrow_repo <- paste0(getOption("arrow.dev_repo",
"https://nightlies.apache.org/arrow/r"), "/libarrow/")
+ VERSION <- find_latest_nightly(VERSION)
+}
+
+options(.arrow.cleanup = character()) # To collect dirs to rm on exit
+on.exit(unlink(getOption(".arrow.cleanup")))
Review Comment:
Or alternatively, ensure that this is the one and only `on.exit()` by
removing the one above.
I am also not sure that this will work on a vector of non-empty directories
(you may need to explicitly lapply and/or use `recursive = TRUE`)
##########
r/tools/nixlibs.R:
##########
@@ -133,16 +125,16 @@ identify_binary <- function(lib =
Sys.getenv("LIBARROW_BINARY"), info = distro()
if (identical(lib, "false")) {
# Do not download a binary
- NULL
+ lib <- NULL
} else if (!identical(lib, "true")) {
# Env var provided an os-version to use, to override our logic.
# We don't validate that this exists. If it doesn't, the download will fail
# and the build will fall back to building from source
- lib
Review Comment:
I think it clearly communicates what's happening and doesn't have any
undesirable side-effects? 🤷
--
This is an automated message from the Apache Git Service.
To respond to the message, please log on to GitHub and use the
URL above to go to the specific comment.
To unsubscribe, e-mail: [email protected]
For queries about this service, please contact Infrastructure at:
[email protected]