Skip to content

Commit

Permalink
paginate through connect application lists
Browse files Browse the repository at this point in the history
fixes #860
  • Loading branch information
aronatkins committed Jun 21, 2023
1 parent 46e17b3 commit d089327
Show file tree
Hide file tree
Showing 3 changed files with 46 additions and 1 deletion.
3 changes: 3 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -167,6 +167,9 @@

* `applications()` now returns the application title, if available (#484).

* `applications()` processes multiple pages of results from a Connect server
(#860).

* `addConnectServer()` is slightly more robust to incorrect specification
(#603).

Expand Down
2 changes: 1 addition & 1 deletion R/client-connect.R
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ connectClient <- function(service, authInfo) {
c("account_id", names(filters)),
c(accountId, unname(filters))
), collapse = "&")
listRequest(service, authInfo, path, query, "applications")
listApplicationsRequest(service, authInfo, path, query, "applications")
},

createApplication = function(name, title, template, accountId, appMode) {
Expand Down
42 changes: 42 additions & 0 deletions R/client.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,8 @@ clientForAccount <- function(account) {
}
}

# Appropriate when the list API includes "count" and "total" fields in the response JSON and the API
# supports pagination with the query arguments count=PAGE_SIZE&offset=STARTING_POINT.
listRequest <- function(service, authInfo, path, query, listName, page = 100,
max = NULL) {

Expand Down Expand Up @@ -44,6 +46,46 @@ listRequest <- function(service, authInfo, path, query, listName, page = 100,
return(results)
}

# /__api__/applications response with { applications: [], count: M, total: N, continuation: "CONTINUATION" }
# To paginate, use the query arguments cont=CONTINUATION&start=START&count=MAX
listApplicationsRequest <- function(service, authInfo, path, query, listName, page = 100,
max = NULL) {

# accumulate multiple pages of results
start <- 0
cont <- ""
results <- list()

while (TRUE) {

# add query params
queryWithList <- paste(query,
"&count=", page,
"&start=", start,
"&cont=", cont,
sep = "")

# make request and append the results
response <- GET(service, authInfo, path, queryWithList)
results <- append(results, response[[listName]])

# update the starting point for the next request
start <- start + response$count
cont <- response$continuation

# get all results if no max was specified
if (is.null(max)) {
max <- response$total
}

# exit if we've got them all
if (length(results) >= response$total || length(results) >= max)
break
}

return(results)
}

filterQuery <- function(param, value, operator = NULL) {
if (is.null(operator)) {
op <- ":"
Expand Down

0 comments on commit d089327

Please sign in to comment.