Skip to content

Commit

Permalink
More cloud resource fields
Browse files Browse the repository at this point in the history
  • Loading branch information
wlandau-lilly committed Nov 10, 2023
1 parent ab200be commit 63cd359
Show file tree
Hide file tree
Showing 8 changed files with 249 additions and 46 deletions.
37 changes: 25 additions & 12 deletions R/class_resources_aws.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,24 +2,30 @@ resources_aws_init <- function(
bucket = NULL,
prefix = tar_path_objects_dir_cloud(),
region = NULL,
part_size = 5 * (2 ^ 20),
endpoint = NULL,
s3_force_path_style = NULL,
version = "latest",
part_size = 5 * (2 ^ 20),
page_size = 1000L,
max_tries = NULL,
seconds_timeout = NULL,
close_connection = NULL,
s3_force_path_style = NULL,
verbose = TRUE,
args = list()
) {
resources_aws_new(
bucket = bucket,
prefix = prefix,
region = region,
part_size = part_size,
endpoint = endpoint,
s3_force_path_style = s3_force_path_style,
version = version,
part_size = part_size,
page_size = page_size,
max_tries = max_tries,
seconds_timeout = seconds_timeout,
close_connection = close_connection,
s3_force_path_style = s3_force_path_style,
verbose = verbose,
args = args
)
}
Expand All @@ -28,51 +34,58 @@ resources_aws_new <- function(
bucket = NULL,
prefix = NULL,
region = NULL,
part_size = NULL,
endpoint = NULL,
s3_force_path_style = NULL,
version = NULL,
part_size = NULL,
page_size = NULL,
max_tries = NULL,
seconds_timeout = NULL,
close_connection = NULL,
s3_force_path_style = NULL,
verbose = TRUE,
args = NULL
) {
force(bucket)
force(prefix)
force(region)
force(part_size)
force(endpoint)
force(s3_force_path_style)
force(version)
force(part_size)
force(page_size)
force(max_tries)
force(seconds_timeout)
force(close_connection)
force(s3_force_path_style)
force(verbose)
force(args)
enclass(environment(), c("tar_resources_aws", "tar_resources"))
}

#' @export
resources_validate.tar_resources_aws <- function(resources) {
for (field in c("bucket", "prefix")) {
for (field in c("bucket", "prefix", "version")) {
tar_assert_scalar(resources[[field]])
tar_assert_chr(resources[[field]])
tar_assert_none_na(resources[[field]])
tar_assert_nzchar(resources[[field]])
}
for (field in c("region", "endpiont")) {
for (field in c("region", "endpoint")) {
tar_assert_scalar(resources[[field]] %|||% "x")
tar_assert_chr(resources[[field]] %|||% "x")
tar_assert_none_na(resources[[field]] %|||% "x")
}
for (field in c("part_size", "max_tries", "seconds_timeout")) {
for (field in c("part_size", "page_size", "max_tries", "seconds_timeout")) {
tar_assert_scalar(resources[[field]] %|||% 1L)
tar_assert_dbl(resources[[field]] %|||% 1L)
tar_assert_none_na(resources[[field]] %|||% 1L)
tar_assert_ge(resources[[field]] %|||% 1L, 0L)
}
for (field in c("close_connection", "s3_force_path_style")) {
for (field in c("close_connection", "s3_force_path_style", "verbose")) {
tar_assert_scalar(resources[[field]] %|||% TRUE)
tar_assert_lgl(resources[[field]] %|||% TRUE)
tar_assert_none_na(resources[[field]] %|||% TRUE)
}
tar_assert_in(resources$version, c("latest", "meta"))
resources_aws_validate_args(resources$args)
}

Expand Down
23 changes: 12 additions & 11 deletions R/class_resources_gcp.R
Original file line number Diff line number Diff line change
@@ -1,13 +1,15 @@
resources_gcp_init <- function(
bucket = NULL,
prefix = tar_path_objects_dir_cloud(),
version = "latest",
predefined_acl = "private",
max_tries = 5L,
verbose = FALSE
) {
resources_gcp_new(
bucket = bucket,
prefix = prefix,
version = version,
predefined_acl = predefined_acl,
max_tries = max_tries,
verbose = verbose
Expand All @@ -17,12 +19,14 @@ resources_gcp_init <- function(
resources_gcp_new <- function(
bucket = NULL,
prefix = NULL,
version = NULL,
predefined_acl = NULL,
max_tries = NULL,
verbose = NULL
) {
force(bucket)
force(prefix)
force(version)
force(predefined_acl)
force(max_tries)
force(verbose)
Expand All @@ -31,22 +35,19 @@ resources_gcp_new <- function(

#' @export
resources_validate.tar_resources_gcp <- function(resources) {
message <- "GCP resources require a valid bucket name."
tar_assert_scalar(resources$bucket, msg = message)
tar_assert_chr(resources$bucket, msg = message)
tar_assert_none_na(resources$bucket, msg = message)
tar_assert_nzchar(resources$bucket, msg = message)
tar_assert_scalar(resources$prefix)
tar_assert_chr(resources$prefix)
tar_assert_nzchar(resources$prefix)
tar_assert_scalar(resources$predefined_acl)
tar_assert_chr(resources$predefined_acl)
tar_assert_nzchar(resources$predefined_acl)
for (field in c("bucket", "prefix", "predefined_acl")) {
message <- paste("GCP resources require a valid", field)
tar_assert_scalar(resources[[field]], msg = message)
tar_assert_chr(resources[[field]], msg = message)
tar_assert_none_na(resources[[field]], msg = message)
tar_assert_nzchar(resources[[field]], msg = message)
}
tar_assert_scalar(resources$max_tries %|||% 1L)
tar_assert_dbl(resources$max_tries %|||% 1L)
tar_assert_none_na(resources$max_tries %|||% 1L)
tar_assert_ge(resources$max_tries %|||% 1L, 0L)
tar_assert_scalar(resources$verbose)
tar_assert_in(resources$version, c("latest", "meta"))
tar_assert_lgl(resources$verbose)
}

Expand Down
49 changes: 36 additions & 13 deletions R/tar_resources_aws.R
Original file line number Diff line number Diff line change
Expand Up @@ -23,11 +23,6 @@
#' was added on 2023-08-24: `targets` version 1.2.2.9000.)
#' @param region Character of length 1, AWS region containing the S3 bucket.
#' Set to `NULL` to use the default region.
#' @param part_size Positive numeric of length 1, number of bytes
#' for each part of a multipart upload. (Except the last part,
#' which is the remainder.) In a multipart upload, each part
#' must be at least 5 MB. The default value of the `part_size`
#' argument is `5 * (2 ^ 20)`.
#' @param endpoint Character of length 1, URL endpoint for S3 storage.
#' Defaults to the Amazon AWS endpoint if `NULL`. Example:
#' To use the S3 protocol with Google Cloud Storage,
Expand All @@ -45,14 +40,33 @@
#' object versioning turned on, `targets` may fail to record object
#' versions. Google Cloud Storage in particular has this
#' incompatibility.
#' @param s3_force_path_style Logical of length 1, whether to use path-style
#' addressing for S3 requests.
#' @param version Character of length 1: `"latest"` to read the latest
#' version of the target in the bucket (default), or `"meta"` to
#' read the version recorded in the metadata. This affects how `targets`
#' downloads target data and makes sure it is up to date. `"latest"`
#' is sufficient for most cases. Use `"meta"` if you are reverting to
#' a historical copy of the metadata (`_targets/meta/meta`) and wish to use
#' `targets` to use the corresponding old copies of versioned data in a
#' versioned bucket. The `version` argument is only applicable if
#' the bucket has versioning enabled.
#' @param part_size Positive numeric of length 1, number of bytes
#' for each part of a multipart upload. (Except the last part,
#' which is the remainder.) In a multipart upload, each part
#' must be at least 5 MB. The default value of the `part_size`
#' argument is `5 * (2 ^ 20)`.
#' @param page_size Positive integer of length 1, number of items in each
#' page for paginated HTTP requests such as listing objects.
#' @param max_tries Positive integer of length 1, maximum number of attempts
#' to access a network resource on AWS.
#' @param seconds_timeout Positive numeric of length 1,
#' number of seconds until an HTTP connection times out.
#' @param close_connection Logical of length 1, whether to close HTTP
#' connections immediately.
#' @param s3_force_path_style Logical of length 1, whether to use path-style
#' addressing for S3 requests.
#' @param verbose Logical of length 1, whether to print console messages
#' when running computationally expensive operations such as listing
#' objects in a large bucket.
#' @param ... Named arguments to functions in `paws.storage::s3()` to manage
#' S3 storage. The documentation of these specific functions
#' is linked from `https://www.paws-r-sdk.com/docs/s3/`.
Expand Down Expand Up @@ -89,22 +103,28 @@ tar_resources_aws <- function(
bucket = targets::tar_option_get("resources")$aws$bucket,
prefix = targets::tar_option_get("resources")$aws$prefix,
region = targets::tar_option_get("resources")$aws$region,
part_size = targets::tar_option_get("resources")$aws$part_size,
endpoint = targets::tar_option_get("resources")$aws$endpoint,
max_tries = targets::tar_option_get("resources")$aws$max_tries,
seconds_timeout = targets::tar_option_get("resources")$aws$seconds_timeout,
close_connection = targets::tar_option_get("resources")$aws$close_connection,
s3_force_path_style = targets::tar_option_get(
"resources"
)$aws$s3_force_path_style,
version = targets::tar_option_get("resources")$aws$version,
part_size = targets::tar_option_get("resources")$aws$part_size,
page_size = targets::tar_option_get("resources")$aws$page_size,
max_tries = targets::tar_option_get("resources")$aws$max_tries,
seconds_timeout = targets::tar_option_get("resources")$aws$seconds_timeout,
close_connection = targets::tar_option_get("resources")$aws$close_connection,
verbose = targets::tar_option_get("resources")$aws$verbose,
...
) {
if (is.null(prefix)) {
tar_warn_prefix()
prefix <- path_store_default()
}
prefix <- prefix %|||% targets::tar_path_objects_dir_cloud()
version <- version %|||% "latest"
part_size <- part_size %|||% (5 * (2 ^ 20))
page_size <- page_size %|||% 1000L
verbose <- verbose %|||% TRUE
args <- list(...)
default_args <- targets::tar_option_get("resources")$aws$args
for (name in names(default_args)) {
Expand All @@ -114,12 +134,15 @@ tar_resources_aws <- function(
bucket = bucket,
prefix = prefix,
region = region,
part_size = part_size,
endpoint = endpoint,
s3_force_path_style = s3_force_path_style,
version = version,
part_size = part_size,
page_size = page_size,
max_tries = max_tries,
seconds_timeout = seconds_timeout,
close_connection = close_connection,
s3_force_path_style = s3_force_path_style,
verbose = verbose,
args = args
)
resources_validate(out)
Expand Down
3 changes: 3 additions & 0 deletions R/tar_resources_gcp.R
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,7 @@
tar_resources_gcp <- function(
bucket = targets::tar_option_get("resources")$gcp$bucket,
prefix = targets::tar_option_get("resources")$gcp$prefix,
version = targets::tar_option_get("resources")$gcp$version,
predefined_acl = targets::tar_option_get("resources")$gcp$predefined_acl,
max_tries = targets::tar_option_get("resources")$gcp$max_tries,
verbose = targets::tar_option_get("resources")$gcp$verbose
Expand All @@ -44,11 +45,13 @@ tar_resources_gcp <- function(
tar_warn_prefix()
prefix <- path_store_default()
}
version <- version %|||% "latest"
predefined_acl <- predefined_acl %|||% "private"
verbose <- verbose %|||% FALSE
out <- resources_gcp_init(
bucket = bucket,
prefix = prefix,
version = version,
predefined_acl = predefined_acl,
max_tries = max_tries,
verbose = verbose
Expand Down
40 changes: 30 additions & 10 deletions man/tar_resources_aws.Rd

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

11 changes: 11 additions & 0 deletions man/tar_resources_gcp.Rd

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

Loading

0 comments on commit 63cd359

Please sign in to comment.