Skip to content

Commit

Permalink
Merge pull request #5 from quant-aq/lsm/organizations-networks
Browse files Browse the repository at this point in the history
add organizations and networks, remove teams
  • Loading branch information
lswainemoore authored Dec 13, 2023
2 parents 002b2bc + 1adeb14 commit b625b17
Show file tree
Hide file tree
Showing 11 changed files with 173 additions and 55 deletions.
6 changes: 4 additions & 2 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -4,12 +4,14 @@ S3method(as.data.frame,account)
S3method(as.data.frame,calibration_models)
S3method(as.data.frame,device_data)
S3method(as.data.frame,devices)
S3method(as.data.frame,teams)
S3method(as.data.frame,networks)
S3method(as.data.frame,organizations)
export(get_data)
export(get_data_by_date)
export(get_devices)
export(get_models)
export(get_teams)
export(get_networks)
export(get_organizations)
export(setup_client)
export(whoami)
importFrom(dplyr,across)
Expand Down
88 changes: 76 additions & 12 deletions R/wrappers.R
Original file line number Diff line number Diff line change
Expand Up @@ -46,32 +46,96 @@ as.data.frame.account <- function(x, ...){
mutate(across(c("last_seen", "member_since"), ~parse_date_time(.x, "Ymd H:M:S.")))
}

#' Get the user's teams information.
#' Get the user's organizations information.
#'
#' @param id The unique numeric identifier for the team
#' @returns The teams information
#' @param organization_id The unique numeric identifier for the org
#' @return The organizations information
#' @export
get_teams <- function(id = NULL){
get_organizations <- function(organization_id = NULL){
structure(
requests(paste("teams", id, sep = "/")),
class = "teams"
requests(paste("orgs", organization_id, sep = "/")),
class = "organizations"
)
}

#' Coerce teams information to data.frame
#' Coerce organizations information to data.frame
#'
#' @importFrom magrittr `%>%`
#'
#' @param x The teams class returned by [get_teams()]
#' @param x The organizations class returned by [get_organizations()]
#' @param ... Placeholder for passing through to as.data.frame.default
#' @returns A data.frame of teams information
#' @returns A data.frame of organizations information
#' @export
as.data.frame.teams <- function(x, ...){
if(!is.null(names(x))){ # if x has names, then there is only one team returned
as.data.frame.organizations <- function(x, ...){
if (!is.null(names(x))) { # if x has names, then there is only one org
x <- list(x)
}

return(do.call(rbind, lapply(x, rbind)) %>% as.data.frame)
# we've got a complicated structure, so it's easiest to decide what to do with
# the nested stuff first (by converting to strings)
stringified <- lapply(x, function(row) {
row$devices <- paste(row$devices, collapse=";")
row$networks <- paste(row$networks, collapse=";")
members <- lapply(row$members, function(member) {
return(paste(member$user, "-", member$role))
})
row$members <- paste(members, collapse = ";")
return(row)
})

# see: https://stackoverflow.com/a/68162050
df <- do.call(rbind, lapply(stringified, function(row) {
# need to unclass the row or when we run data.frame
# we'll do the whole thing again!
row %>% unclass %>% data.frame
}))
df %>% mutate(created_on = parse_date_time(df$created_on, "Ymd H:M:S.z"))
}

#' Get the user's networks information, within the context of an organization
#'
#' @param organization_id The unique numeric identifier for the parent org
#' @param network_id The unique numeric identifier for the network
#' @return The networks information
#' @export
get_networks <- function(organization_id, network_id = NULL){
structure(
requests(paste("orgs", organization_id, "networks", network_id, sep = "/")),
class = "networks"
)
}

#' Coerce networks information to data.frame
#'
#' @importFrom magrittr `%>%`
#'
#' @param x The networks class returned by [get_networks()]
#' @param ... Placeholder for passing through to as.data.frame.default
#' @returns A data.frame of networks information
#' @export
as.data.frame.networks <- function(x, ...){
if (!is.null(names(x))) { # if x has names, then there is only one network
x <- list(x)
}

# we've got a complicated structure, so it's easiest to decide what to do with
# the nested stuff first (by converting to strings)
stringified <- lapply(x, function(row) {
row$devices <- paste(row$devices, collapse=";")
members <- lapply(row$members, function(member) {
return(paste(member$user, "-", member$role))
})
row$members <- paste(members, collapse = ";")
return(row)
})

# see: https://stackoverflow.com/a/68162050
df <- do.call(rbind, lapply(stringified, function(row) {
# need to unclass the row or when we run data.frame
# we'll do the whole thing again!
row %>% unclass %>% data.frame
}))
df %>% mutate(created_on = parse_date_time(df$created_on, "Ymd H:M:S.z"))
}

#' Get the user's devices
Expand Down
20 changes: 16 additions & 4 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -79,13 +79,25 @@ x <- as.data.frame(get_data("<serial-number>", limit=10))
x <- as.data.frame(get_data("<serial-number>", raw=TRUE))
```

### `get_teams()`
### `get_organizations(organization_id=NULL)`

Return a list of all teams that you belong to.
Return a list of all organizations you can view,
or the particular organization with id=organization_id.

```R
# Get the list of teams
x <- get_teams()
# Get the list of organizations
x <- get_organizations()
```

### `get_networks(organization_id, network_id=NULL)`

Return a list of all networks you can can view in
the context of the particular organization with id=organization_id,
or the particular network with id=network_id within that organization.

```R
# Get the list of networks in organization 1
x <- get_networks(organization_id = 1)
```

### `get_devices(sn=NULL, limit=NULL, sort=NULL)`
Expand Down
19 changes: 19 additions & 0 deletions man/as.data.frame.networks.Rd

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

19 changes: 19 additions & 0 deletions man/as.data.frame.organizations.Rd

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

19 changes: 0 additions & 19 deletions man/as.data.frame.teams.Rd

This file was deleted.

19 changes: 19 additions & 0 deletions man/get_networks.Rd

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

17 changes: 17 additions & 0 deletions man/get_organizations.Rd

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

17 changes: 0 additions & 17 deletions man/get_teams.Rd

This file was deleted.

2 changes: 1 addition & 1 deletion tests/testthat/test-api_calls.R
Original file line number Diff line number Diff line change
Expand Up @@ -179,7 +179,7 @@ test_that("requests handles data-by-date",{
})

test_that("requests for something other than data with only one page returns as expected", {
x <- requests("teams")
x <- requests("orgs")

expect_true(is.list(x))
})
Expand Down
2 changes: 2 additions & 0 deletions tests/testthat/test-setup.R
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
test_that("giving a bad api key throws a 401 error", {
expect_error(setup_client(api_key = "fake_key"))
# need to reset this, because otherwise test environment remains polluted by bad key
setup_client(api_key=secret_decrypt("u7QHZzH2_KATioA_EjynwV8qi4JnDEI3raqjj6BMjS537hquEtsqcA", "QUANTAQ_PACKAGE_KEY"))
})

0 comments on commit b625b17

Please sign in to comment.