Skip to content

Commit

Permalink
Exit paginator when previous token matches current
Browse files Browse the repository at this point in the history
  • Loading branch information
DyfanJones authored Dec 20, 2023
2 parents 1de2019 + 496faaa commit a2eda71
Show file tree
Hide file tree
Showing 4 changed files with 164 additions and 22 deletions.
19 changes: 10 additions & 9 deletions paws.common/R/custom_s3.R
Original file line number Diff line number Diff line change
Expand Up @@ -161,22 +161,23 @@ sse_md5_build <- function(request) {
# encryption key. This handler does both if the MD5 has not been set by
# the caller.
sse_md5 <- function(params) {
return(.sse_md5(params, 'SSECustomer'))
return(.sse_md5(params, "SSECustomer"))
}

# S3 server-side encryption requires the encryption key to be sent to the
# server base64 encoded, as well as a base64-encoded MD5 hash of the
# encryption key. This handler does both if the MD5 has not been set by
# the caller specifically if the parameter is for the copy-source sse-c key.
copy_source_sse_md5 <- function(params) {
return(.sse_md5(params, 'CopySourceSSECustomer'))
return(.sse_md5(params, "CopySourceSSECustomer"))
}

.sse_md5 <- function(params, sse_member_prefix='SSECustomer') {
if (!.needs_s3_sse_customization(params, sse_member_prefix))
.sse_md5 <- function(params, sse_member_prefix = "SSECustomer") {
if (!.needs_s3_sse_customization(params, sse_member_prefix)) {
return(params)
sse_key_member <- paste0(sse_member_prefix, 'Key')
sse_md5_member <- paste0(sse_member_prefix, 'KeyMD5')
}
sse_key_member <- paste0(sse_member_prefix, "Key")
sse_md5_member <- paste0(sse_member_prefix, "KeyMD5")
key_md5_str <- base64enc::base64encode(
digest::digest(params[[sse_key_member]], serialize = FALSE, raw = TRUE)
)
Expand All @@ -186,9 +187,9 @@ copy_source_sse_md5 <- function(params) {
}

.needs_s3_sse_customization <- function(params, sse_member_prefix) {
return (
!is_empty(params[[paste0(sse_member_prefix, 'Key')]]) &
is_empty(params[[paste0(sse_member_prefix, 'KeyMD5')]])
return(
!is_empty(params[[paste0(sse_member_prefix, "Key")]]) &
is_empty(params[[paste0(sse_member_prefix, "KeyMD5")]])
)
}

Expand Down
51 changes: 41 additions & 10 deletions paws.common/R/paginate.R
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@
#' @param MaxItems Limits the maximum number of total returned items returned while paginating.
#' @param StartingToken Can be used to modify the starting marker or token of a paginator.
#' This argument if useful for resuming pagination from a previous token or starting pagination at a known position.
#' @param StopOnSameToken Exist paginator if previous token matches current token.
#' @param FUN the function to be applied to each response element of \code{operation}.
#' @param simplify See \link[base:sapply]{base::sapply()}.
#' @param ... optional arguments to \code{FUN}.
Expand All @@ -39,7 +40,8 @@
paginate <- function(Operation,
PageSize = NULL,
MaxItems = NULL,
StartingToken = NULL) {
StartingToken = NULL,
StopOnSameToken = FALSE) {
fn <- substitute(Operation)
# rebuild fn for do.call
if (identical(fn[[1]], .do_call)) {
Expand All @@ -59,14 +61,26 @@ paginate <- function(Operation,
while (!identical(fn[[paginator$input_token[[1]]]], character(0))) {
resp <- eval(fn, envir = parent.frame())
new_tokens <- get_tokens(resp, paginator$output_token)

# Exit paginator if previous token matches current token
# https://github.com/smithy-lang/smithy-typescript/blob/main/packages/core/src/pagination/createPaginator.ts#L53
if (isTRUE(StopOnSameToken)) {
previous_token <- unlist(fn[[paginator$input_token]], use.names = F)
if (identical(previous_token, unlist(new_tokens, use.names = F))) {
break
}
}

# Update tokens
for (i in seq_along(new_tokens)) {
fn[[paginator$input_token[[i]]]] <- new_tokens[[i]]
}

result[[length(result) + 1]] <- resp

# exit if no more results
if (!is.null(paginator$more_results)) {
if (isFALSE(resp[[paginator$more_results]])) {
if (!is.null(paginator[["more_results"]])) {
if (isFALSE(resp[[paginator[["more_results"]]]])) {
break
}
}
Expand All @@ -87,7 +101,8 @@ paginate_lapply <- function(Operation,
...,
PageSize = NULL,
MaxItems = NULL,
StartingToken = NULL) {
StartingToken = NULL,
StopOnSameToken = FALSE) {
FUN <- match.fun(FUN)
fn <- substitute(Operation)

Expand All @@ -106,7 +121,8 @@ paginate_lapply <- function(Operation,
paginator = fn_update$paginator,
FUN = FUN,
...,
MaxItems = MaxItems
MaxItems = MaxItems,
StopOnSameToken = StopOnSameToken
)
return(result)
}
Expand All @@ -119,7 +135,8 @@ paginate_sapply <- function(Operation,
simplify = TRUE,
PageSize = NULL,
MaxItems = NULL,
StartingToken = NULL) {
StartingToken = NULL,
StopOnSameToken = FALSE) {
FUN <- match.fun(FUN)
fn <- substitute(Operation)

Expand All @@ -138,7 +155,8 @@ paginate_sapply <- function(Operation,
paginator = fn_update$paginator,
FUN = FUN,
...,
MaxItems = MaxItems
MaxItems = MaxItems,
StopOnSameToken = StopOnSameToken
)

if (!isFALSE(simplify)) {
Expand Down Expand Up @@ -234,21 +252,34 @@ paginate_xapply <- function(
paginator,
FUN,
...,
MaxItems = NULL) {
MaxItems = NULL,
StopOnSameToken = FALSE) {
primary_result_key <- paginator$result_key[[1]]
no_items <- 0
result <- list()
while (!identical(fn[[paginator$input_token[[1]]]], character(0))) {
resp <- eval(fn, envir = parent.frame(n = 2))
new_tokens <- get_tokens(resp, paginator$output_token)

# Exit paginator if previous token matches current token
# https://github.com/smithy-lang/smithy-typescript/blob/main/packages/core/src/pagination/createPaginator.ts#L53
if (isTRUE(StopOnSameToken)) {
previous_token <- unlist(fn[[paginator$input_token]], use.names = F)
if (identical(previous_token, unlist(new_tokens, use.names = F))) {
break
}
}

# Update tokens
for (i in seq_along(new_tokens)) {
fn[[paginator$input_token[[i]]]] <- new_tokens[[i]]
}

result[[length(result) + 1]] <- FUN(resp, ...)

# exit if no more results
if (!is.null(paginator$more_results)) {
if (isFALSE(resp[[paginator$more_results]])) {
if (!is.null(paginator[["more_results"]])) {
if (isFALSE(resp[[paginator[["more_results"]]]])) {
break
}
}
Expand Down
16 changes: 13 additions & 3 deletions paws.common/man/paginate.Rd

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

100 changes: 100 additions & 0 deletions paws.common/tests/testthat/test_paginate.R
Original file line number Diff line number Diff line change
Expand Up @@ -164,6 +164,57 @@ test_that("check paginate", {
expect_equal(actual, expected)
})

test_that("check paginate stop on same token", {
dummy_internal <- function(paginator) {
paginator
}
dummy_op <- function(x, NextToken = NULL, MaxKey = NULL) {
op <- dummy_internal(paginator = list(
input_token = "NextToken",
output_token = "NextToken",
limit_key = "MaxKey",
result_key = "Contents"
))
list(NextToken = NextToken, MaxKey = MaxKey)
}
mock_substitute <- mock2(substitute(dummy_op(x = "hi")))

mock_paginate_update_fn <- mock2(
list(
fn = substitute(dummy_op(x = "hi")),
paginator = list(
input_token = "NextToken",
output_token = "NextToken",
limit_key = "MaxKey",
result_key = "Contents"
)
)
)
mock_eval <- mock2(
list(Contents = list("foo"), NextToken = "token1"),
list(Contents = list("bar"), NextToken = "token2"),
list(Contents = list(), NextToken = "token2")
)

expected <- list(
list(Contents = list("foo"), NextToken = "token1"),
list(Contents = list("bar"), NextToken = "token2")
)

mockery::stub(paginate, "substitute", mock_substitute)
mockery::stub(paginate, "paginate_update_fn", mock_paginate_update_fn)
mockery::stub(paginate, "eval", mock_eval)

actual <- paginate("dummy", StopOnSameToken = TRUE)
actual_args <- mockery::mock_args(mock_eval)
expect_equal(lapply(actual_args, function(x) as.list(x[[1]][-1])), list(
list(x = "hi"),
list(x = "hi", NextToken = "token1"),
list(x = "hi", NextToken = "token2")
))
expect_equal(actual, expected)
})

########################################################################
# paginate_xapply
########################################################################
Expand Down Expand Up @@ -267,6 +318,55 @@ test_that("check paginate_xapply restrict MaxItems", {
expect_equal(actual, expected)
})

test_that("check paginate stop on same token", {
dummy_internal <- function(paginator) {
paginator
}
dummy_op <- function(x, NextToken = NULL, MaxKey = NULL) {
op <- dummy_internal(paginator = list(
input_token = "NextToken",
output_token = "NextToken",
limit_key = "MaxKey",
result_key = "Contents"
))
list(NextToken = NextToken, MaxKey = MaxKey)
}

mock_eval <- mock2(
list(Contents = list("foo"), NextToken = "token1"),
list(Contents = list("bar"), NextToken = "token2"),
list(Contents = list(), NextToken = "token2")
)

expected <- list(
list(Contents = list("foo"), NextToken = "token1"),
list(Contents = list("bar"), NextToken = "token2")
)

mockery::stub(paginate_xapply, "eval", mock_eval)

actual <- paginate_xapply(
substitute(dummy_op(x = "hi")),
paginator = list(
input_token = "NextToken",
output_token = "NextToken",
limit_key = "MaxKey",
result_key = "Contents"
),
FUN = function(resp) {
resp
},
MaxItems = NULL,
StopOnSameToken = TRUE
)
actual_args <- mockery::mock_args(mock_eval)
expect_equal(lapply(actual_args, function(x) as.list(x[[1]][-1])), list(
list(x = "hi"),
list(x = "hi", NextToken = "token1"),
list(x = "hi", NextToken = "token2")
))
expect_equal(actual, expected)
})

########################################################################
# paginate_lapply
Expand Down

0 comments on commit a2eda71

Please sign in to comment.